
Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC Commits: 44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00 iface: Store flags in interface files When reporting the reason why a module is recompiled (using `-dump-hi-diffs`), it is much more informative to inform the user about which flag exactly has changed, rather than just an opaque reference to a hash. Now, when the user enables `-fwrite-if-self-recomp-flags` there is a difference the precise part of the flags is reported: ``` codegen flags changed: before: [Opt_NoTypeableBinds, Opt_OmitYields] after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict] ``` Fixes #25571 - - - - - 324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00 Run fix-whitespace on compiler/ https://hackage.haskell.org/package/fix-whitespace IMO this should be included into lint suite - - - - - 1e53277a by sheaf at 2025-03-08T16:32:25-05:00 Allow defaulting of representational equalities This commit generalises the defaulting of equality constraints that was introduced in 663daf8d (with follow-up in 6863503c) to allow the defaulting of *representational* equality constraints. Now we default a representational equality ty1 ~R# ty2 by unifying ty1 ~# ty2. This allows the following defaulting to take place: - Coercible alpha[tau] Int ==> alpha := Int - Coercible (IO beta[tau]) (IO Char) ==> beta := Char See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default for more details. Fixes #21003 - - - - - d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00 Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well." This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0. As described in #25817 this commit introduced a subtle bug in AArch64 code generation. So for the time being I will simply revert it wholesale. - - - - - 68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00 Properly describe acceptance window for stat tests. The relative metric is already in %, so no need to multiply by 100. - - - - - cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00 wasm: do not use wasm type reflection in dyld The wasm dynamic linker used to depend on v8's experimental wasm type reflection support to generate stub functions when treating GOT.func items that aren't exported by any loaded library yet. However, as we work towards wasm ghci browser mode (#25399), we need to ensure the wasm dyld logic is portable across browsers. So this commit removes the usage of wasm type reflection in wasm dyld, and it shall only be added many months later when this feature is widely available in browsers. - - - - - 75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: don't create a wasm global for dyld poison There's a much more efficient way to convert an unsigned i32 to a signed one. Thanks, o3-mini-high. - - - - - fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00 wasm: revamp JSFFI internal implementation and documentation This patch revamps the wasm backend's JSFFI internal implementation and documentation: - `JSValManager` logic to allocate a key is simplified to simple bumping. According to experiments with all major browsers, the internal `Map` would overflow the heap much earlier before we really exhaust the 32-bit key space, so there's no point in the extra complexity. - `freeJSVal` is now idempotent and safe to call more than once. This is achieved by attaching the `StablePtr#` to the `JSVal#` closure and nullifying it when calling `freeJSVal`, so the same stable pointer cannot be double freed. - `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and always creates a new `Weak#` on the fly. Otherwise by finalizing that `Weak#`, user could accidentally drop the `JSVal`, but `mkWeakJSVal` is only supposed to create a `Weak` that observes the `JSVal`'s liveliness without actually interfering it. - `PromisePendingException` is no longer exported since it's never meant to be caught by user code; it's a severe bug if it's actually raised at runtime. - Everything exported by user-facing `GHC.Wasm.Prim` now has proper haddock documentation. - Note [JSVal representation for wasm] has been updated to reflect the new JSVal# memory layout. - - - - - cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00 users guide: Fix typo - - - - - 1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00 testsuite: Don't count fragile passes as failures in JUnit output As noted in #25806, the testsuite driver's JUnit output previously considered passes of fragile tests to be failures. Fix this. Closes #25806. - - - - - 589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00 Use panic rather than error in expectJust Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829 - - - - - d450e88e by sheaf at 2025-03-11T06:42:59-04:00 Solve Wanted quantified constraints from Givens This commit ensures we directly solve Wanted quantified constraints from matching inert Given quantified constraints,instead of going through the trouble of emitting an implication constraint and processing that. This is not just an optimisation; it makes our lives easier when generating RULEs for specialisation. See Note [Solving Wanted QCs from Given QCs] for details Fixes #25758 - - - - - 48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite: Add testcase for #25577 - - - - - d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00 testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests These tests can be expressed perfectly well using the testsuite driver itself. - - - - - 2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Assert that GOT relocations have GOT entries In #25577 we found that some GOT relocation types were not being given relocation entries. Add assertions to catch this sort of failure in the future. - - - - - 8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00 rts/linker/MachO: Account for internal GOT references in GOT construction Previously we failed to give GOT slots to symbols which were referred to by GOT relocations in the same module. This lead to #25577. Fix this by explicitly traversing relocation lists and maintaining a `needs_got` flag for each symbol. Fixes #25577. - - - - - 7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 One list in ConPat (part of #25127) This patch changes PrefixCon to use one list instead of two: -data HsConDetails tyarg arg rec - = PrefixCon [tyarg] [arg] +data HsConDetails arg rec + = PrefixCon [arg] | RecCon rec | InfixCon arg arg The [tyarg] list is now gone. To understand the effect of this change, recall that there are three instantiations of HsConDetails: 1. type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg (LPat p) -- arg (HsRecFields p (LPat p)) -- rec 2. type HsConDeclH98Details pass = HsConDetails Void -- tyarg (HsScaled pass (LBangType pass)) -- arg (XRec pass [LConDeclField pass]) -- rec 3. type HsPatSynDetails pass = HsConDetails Void -- tyarg (LIdP pass) -- arg [RecordPatSynField pass] -- rec In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg] list was always empty. Its removal is basically a no-op. The interesting case is (1), which is used in ConPat to represent pattern matching of the form (MkE @tp1 @tp2 p1 p2). With this patch, its representation is changed as follows: ConPat "MkE" [tp1, tp2] [p1, p2] -- old ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new The new mixed-list representation is consintent with lambdas, where InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body. The immediate effect of the new representation is an improvement to error messages. Consider the pattern (Con x @t y). Previously it resulted in a parse error because @t could not occur after x. Now it is reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication. In the long term, this is intended as preparation for #18389 and #25127, which would make (Con x @t y) potentially valid, e.g. if its type is Con :: forall a -> forall b. (a, b) -> T The TH AST is left unchanged for the moment to avoid breakage. - - - - - cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00 Error message with EmptyCase and RequiredTypeArguments (#25004) Fix a panic triggered by a combination of \case{} and forall t -> ghci> let f :: forall (xs :: Type) -> (); f = \case {} panic! (the 'impossible' happened) GHC version 9.10.1: Util: only The new error message looks like this: ghci> let f :: forall (xs :: Type) -> (); f = \case {} <interactive>:5:41: error: [GHC-48010] • Empty list of alternatives in \case expression checked against a forall-type: forall xs -> ... This is achieved as follows: * A new data type, BadEmptyCaseReason, is now used to describe why an empty case has been rejected. Used in TcRnEmptyCase. * HsMatchContextRn is passed to tcMatches, so that the type checker can attach the syntactic context to the error message. * tcMatches now rejects type arguments if the list of alternatives is empty. This is what fixes the bug. - - - - - 37d8b50b by sheaf at 2025-03-11T06:43:06-04:00 user's guide: consolidate defaulting documentation This commit adds a new section on defaulting, which consolidates various parts of documentation surrounding defaulting into one central place. It explains type class defaulting in detail, extensions to it with OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well as other defaulting mechanisms (e.g. kind-based defaulting such as RuntimeRep defaulting, and defaulting of equalities). - - - - - 0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: flesh out XOverloadedStrings docs This commit extends the documentation of the OverloadedStrings extension with some usage information, in particular suggestions to: - use default declarations, such as `default (Text)` or `default IsString(Text)` (with the NamedDefaults extension), - enable the ExtendedDefaultRules extension to relax the requirement that a defaultable type variable must only appear in unary standard classes Fixes #23388 - - - - - 2df171d4 by sheaf at 2025-03-11T06:43:06-04:00 user's guide: NamedDefaults vs ExtendedDefaultRules This commit clarifies the defaulting rules with NamedDefaults, in particular in situations where a type variable appears in other constraints than standard/unary constraints. - - - - - 77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Take into account all flags when computing iface_hash The "interface hash" should contain a hash of everything in the interface file. We are not doing that yet but at least a start is to include a hash of everything in `mi_self_recomp`, rather than just `mi_src_hash` and `mi_usages`. In particular, this fixes #25837, a bug where we should recompile a `dyn_hi` file but fail to do so. - - - - - 48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Pass -fPIC to dynamicToo001 test to avoid platform dependence issues On darwin platforms, `-fPIC` is always enabled but on linux it is only enabled in the dynamic flavour. This can cause a difference in interface files (see #25836). The purpose of this test isn't to test module A recompilation, so we avoid this platform dependency by always passing `-fPIC`. - - - - - 03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_used_th field from interface files In the distant past, recompilation checking was disabled for interfaces which used TemplateHaskell, but for several years now recompilation checking has been more fine-grained. This has rendered this field unused and lingering in an interface file. - - - - - 6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00 Remove mi_hpc field from interface files The `mi_hpc` field is not used for anything as far as I can discern so there is no reason to record in the private interface of a module that there are modules in the transitive closure which use `hpc`. You can freely mix modules which use `-fhpc` and ones which don't. Whether to recompile a module due to `-fhpc` being passed to the module itself is determined in `fingerprintDynFlags`. - - - - - b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00 We can't UNPACK multi-constructor GADTs This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make - - - - - 8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: Add explicit exports lists to all remaining modules - - - - - db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00 template-haskell: fix haddocks It seems that we need a direct dependency on ghc-internal, otherwise Haddock cannot find our haddocks The bug seems to be caused by Hadrian because if I rebuild with cabal-install (without this extra dependency) then I get accurate Haddocks. Resolves #25705 - - - - - 64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00 mk-ghcup-metadata: Clean up and add type annotations Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline. - - - - - b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00 rts: Drop imports of pthreads functions in cmm sources These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources. - - - - - 915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00 interfaces: Ensure that forceModIface deeply forces a ModIface A ModIface is the result of compilation that we keep for a long time in memory. Therefore, it's very important to manage what we are going to retain and remove any external references to things which we might have captured compilation. If storing your ModIface in memory uses too much space, then store less things or make it use a more efficient representation. In the past there have been many space leak bugs by not sufficiently forcing a ModIface (#15111) This patch adds all the missing NFData instances for all the places I could find where we weren't deeply forcing the structure. - - - - - 24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00 Add interface-stability test for ghc-prim - - - - - 0cb1db92 by sheaf at 2025-03-14T13:11:44-04:00 Don't report used duplicate record fields as unused This commit fixes the bug reported in #24035 in which the import of a duplicate record field could be erroneously reported as unused. The issue is that an import of the form "import M (fld)" can import several different 'Name's, and we should only report an error if ALL of those 'Name's are unused, not if ANY are. Note [Reporting unused imported duplicate record fields] in GHC.Rename.Names explains the solution to this problem. Fixes #24035 - - - - - f1830d74 by Matthew Pickering at 2025-03-14T13:12:21-04:00 binary: Directly copy ShortByteString to buffer rather than go via ByteString This avoids allocating an intermediate bytestring. I just noticed on a profile that `putFS` was allocating, and it seemed strange to me why since it should just copy the contents of the FastString into the already allocated buffer. It turned out we were going indirectly via a ByteString. Fixes #25861 - - - - - b15fca2b by Matthew Pickering at 2025-03-15T05:36:40-04:00 iface: Store logical parts of ModIface together The ModIface structure is divided into several logical parts: 1. mi_mod_info: Basic module metadata (name, version, etc.) 2. mi_public: The public interface of the module (the ABI), which includes: - Exports, declarations, fixities, warnings, annotations - Class and type family instances - Rewrite rules and COMPLETE pragmas - Safe Haskell and package trust information - ABI hashes for recompilation checking 4. mi_self_recomp: Information needed for self-recompilation checking (see Note [Self recompilation information in interface files]) 5. mi_simplified_core: Optional simplified Core for bytecode generation (only present when -fwrite-if-simplified-core is enabled) 6. mi_docs: Optional documentation (only present when -haddock is enabled) 7. mi_top_env: Information about the top-level environment of the original source 8. mi_ext_fields: Additional fields for extensibility This structure helps organize the interface data according to its purpose and usage patterns. Different parts of the compiler use different fields. By separating them logically in the interface we can arrange to only deserialize the fields that are needed. This patch also enforces the invariant that the fields of ModIface are lazy. If you are keeping a ModIface on disk, then force it using `forceModIface`. Otherwise, when the `ModIface` is read from disk, only the parts which are needed from the interface will be deserialised. In a follow-up patch I will tackle follow-up issues: * Recompilation checking doesn't take into account exported named defaults (#25855) * Recompilation checking does not take into account COMPLETE pragmas (#25854) * mi_deps_ field in an interface is confused about whether the information is for self-recompilation checking or part of the ABI (#25844) Fixes #25845 ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore ------------------------- - - - - - c758cb71 by Ben Gamari at 2025-03-15T05:37:17-04:00 configure: Fix incorrect SettingsLlvmAsFlags value Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`, resulting in #25856. - - - - - cfaaca14 by sheaf at 2025-03-18T20:05:03-04:00 Fix buglet in isEmptyWorkList There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it mistakenly ignored the 'wl_rw_eqs' field. This commit simply fixes that. No test case. - - - - - 9f9fe0b3 by sheaf at 2025-03-18T20:05:03-04:00 Add mapMaybeTM method to TrieMap class This commit adds a new method to the TrieMap class, mapMaybeTM, and adds implementations to all the instances. mapMaybeTM is useful when filtering containers that contain other containers. - - - - - 393531ff by Simon Peyton Jones at 2025-03-18T20:05:03-04:00 Specialising expressions -- at last This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas. * The old code path (using SpecSig and SpecPrag) still exists. * The new code path (using SpecSigE and SpecPragE) runs alongside it. * All SPECIALISE pragmas are routed through the new code path, except if you give multiple type sigs, when the old code path is still used. * Main documentation: Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig` Thanks to @sheaf for helping with this MR. The Big Thing is to introduce {-# SPECIALISE forall x. f @Int x True #-} where you can give type arguments and value argument to specialise; and you can quantify them with forall, just as in Rules. I thought it was going to be pretty simple, but it was a Long, Long Saga. Highlights * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig` - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag` - Renamer: uses `checkSpecESigShape` to decide which function to assocate the SPECIALISE pragma with - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag` - The rest is in `GHC.HsToCore.Binds.dsSpec` * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds that arise from the specialise expression. The mechanism is explained in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need to do this is explained in Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig. * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is very closely related. * The forall'd binders for SPECIALISE are the same as those for a RULE, so I refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions to rename, zonk, typecheck it. I refactored this data type a bit; nicer now. * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr. Previously it wasn't fully disabled (just set to the empty set), and that didn't quite work in the new regime. * There are knock-on changes to Template Haskell. * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify it /without/ inlining the let-bindings for evidence variables. I added a flag `so_inline` to the SimpleOpt optimiser to support this. The entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline` * Since forever we have had a hack for type variables on the LHS of RULES. I took the opportunity to tidy this up. The main action is in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS], and especially data construtor `SkolemiseFlexi` in data type `GHC.Tc.Zonk.Env.ZonkFlexi` * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate Reason: it now works for Ids as well, and I wanted to use isEvVar, which is defined in GHC.Core.Predicate Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy from GHC.Core.Type, modules now import the former directly. I also took the opportunity to remove unused exports from GHC.Core.Type.hs-boot * Flag stuff: - Add flag `-Wdeprecated-pragmas` and use it to control the warning when using old-style SPECIALISE pragmas with multiple type ascriptions, - Add flag `-Wuseless-specialisations` and use it to control the warning emitted when GHC determines that a SPECIALISE pragma would have no effect. Don't want if the SPECIALISE is SPECIALISE INLINE (#4444) In response to #25389, we continue to generate these seemingly code for these seemingly useless SPECIALISE pragmas - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`, * Split up old-style SPECIALISE pragmas in GHC.Internal.Float, GHC.Internal.Numeric, GHC.Internal.Real * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule) Smaller things: - Update the Users Guide - Add mention of the changes to the 9.14 release notes as well as the Template Haskell changelog, - - - - - 1884dd1a by Simon Peyton Jones at 2025-03-18T20:05:03-04:00 Add -Wrule-lhs-equalities warning This commit adds a new warning, controlled by the warning flag, -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives rise to equality constraints that previous GHC versions would have quantified over. GHC instead discards such RULES, as GHC was never able to generate a rule template that would ever fire; it's better to be explicit about the fact that the RULE doesn't work. - - - - - b00b3ef0 by Ben Gamari at 2025-03-18T20:05:41-04:00 compiler: Add export list to GHC.SysTools.Process This also revealed that `readProcessEnvWithExitCode` and its local helpers were dead code. - - - - - 25850b22 by ARATA Mizuki at 2025-03-18T20:06:25-04:00 Fix code generation for SSE vector operations The new implementation generates correct code even if the registers overlap. Closes #25859 - - - - - e576468c by Andreas Klebinger at 2025-03-18T20:07:02-04:00 Bump nofib submodule. Fixes #25867. (Ben-raytrace being broken by library changes) - - - - - 443fc8b1 by Sjoerd Visscher at 2025-03-19T12:01:04-04:00 Multiplicity annotation on records Needing to store multiplicity annotations on records triggered a refactoring of AST of data declarations: Moved HsBangTy and HsRecTy from HsType to HsTypeGhcPsExt, the extension of HsType during parsing, since they are only needed during parsing. New HsConDeclField that stores all source data shared by all constructor declaration fields: unpackedness, strictness, multiplicity, documentation and the type of the field. Merged HsMultAnn and HsArrowOf, so all multiplicity annotations share the same data type. HsBang was no longer needed as a separate type, and was inlined into HsSrcBang. - - - - - 313cf271 by Ben Gamari at 2025-03-19T12:01:43-04:00 gitlab-ci: Drop CentOS 7 binary distributions CentOS 7 is EoL and moreover we cannot even build images for it. See #25061. - - - - - 5b94f99f by Ben Gamari at 2025-03-19T12:02:21-04:00 rts: Ensure that WinIO flag is set when --io-manager=auto As noted in #25838, previously `selectIOManager` failed to set `rts_IOManagerIsWin32Native` in its `IO_MNGR_FLAG_AUTO`. This meant that the MIO path was taken when WinIO was supposedly selected, resulting in chaos. Fixes #25838. - - - - - 1a3f1131 by Peng Fan at 2025-03-19T12:03:10-04:00 Pass the mcmodel=medium parameter to CC via GHC Ensure that GHC-driver builds default to mcmodel=medium, so that GHC passes this default parameter to CC without having to add it to the compiled project. Commit e70d41406b5d5638b42c4d8222cd03e76bbfeb86 does not ensure that all GHC-built object files have a default model of medium, and will raise an R_LARCH_B26 overflow error. - - - - - 27cf7361 by Matthew Craven at 2025-03-19T12:03:48-04:00 Add interface-stability test for ghc-bignum As with ghc-prim, it makes sense to have some protection against accidental interface changes to this package caused by changes in ghc-internal. - - - - - 25d46547 by Matthew Craven at 2025-03-19T12:03:48-04:00 Add README reference for the interface-stability tests - - - - - 5d65393e by Simon Peyton Jones at 2025-03-20T05:41:24-04:00 Remove the Core flattener This big MR entirely removes the "flattener" that took a type and replaced each type-family application with a fresh type variable. The flattener had its origin in the paper Injective type families for Haskell But (a) #25657 showed that flattening doesn't really work. (b) since we wrote the paper we have introduced the so-called "fine-grained" unifier GHC.Core.Unify, which can return * SurelyApart * Unifiable subst * MaybeApart subst where the MaybeApart says that the two types are not unifiable by a substitution, but could (perhaps) be unified "later" after some type family reductions. This turns out to subsume flattening. This MR does a major refactor of GHC.Core.Unify to make it capable of subsuming flattening. The main payload is described in Note [Apartness and type families] and its many wrinkles. The key (non-refactoring) implementation change is to add `um_fam_env` to the `UMState` in the unification monad. Careful review with Richard revealed various bugs in the treament of `kco`, the kind coercion carried around by the unifier, so that is substantially fixed too: see Note [Kind coercions in Unify]. Compile-time performance is improved by 0.1% with a few improvements over 1% and one worsening by 1.3% namely T9872a. (I have not investigated the latter.) Metric Decrease: T9872b T9872c TcPlugin_RewritePerf Metric Increase: T9872a - - - - - 9003ef0a by sheaf at 2025-03-20T05:42:08-04:00 Remove SDoc from UnknownSubordinate/MissingBinding This commit replaces unstructured SDoc arguments in error message constructors with uses of the following two datatypes: - SigLike: for different kinds of signatures (e.g. standalone kind signatures, fixity signatures, COMPLETE pragmas, etc) - Subordinate: for class methods, associated types, and record fields The following error message constructors now no longer have any SDocs in them: - TcRnIllegalBuiltinSyntax: SDoc -> SigLike - MissingBinding: SDoc -> SigLike - UnknownSubordinate: SDoc -> (Name, Subordinate) - SuggestMoveToDeclarationSite: SDoc -> SigLike - - - - - 4329f3b6 by sheaf at 2025-03-20T05:42:08-04:00 Remove SDocs from HsDocContext This commit removes the remaining SDocs from the HsDocContext data type. It adds the following constructors: ClassInstanceCtx -- Class instances ClassMethodSigCtx -- Class method signatures SpecialiseSigCtx -- SPECIALISE pragmas PatSynSigCtx -- Pattern synonym signatures We now report a bit more information for errors while renaming class instances, which slightly improves renamer-emitted error messages. - - - - - 75c29aa1 by sheaf at 2025-03-20T05:42:08-04:00 Reject instance with non-class head in renamer This commit modifies rnClsInstDecl so that, when renaming, we reject a class instance declaration in which the head is not a class. Before this change, it would get rejected in the type-checker, but that meant that the renamer could emit unhelpful error messages, e.g.: data Foo m a instance Foo m where fmap _ x = case x of would rather unhelpfully say: ‘fmap’ is not a (visible) method of class ‘Foo’ when of course 'Foo' is not even a class. We now reject the above program with the following error message: Illegal instance for data type ‘Foo’. Instance heads must be of the form C ty_1 ... ty_n where ‘C’ is a class. Fixes #22688 - - - - - a8f543a9 by Cheng Shao at 2025-03-20T18:47:19-04:00 testsuite: mark T7919 as fragile on i386 as well T7919 may also fail i386 CI jobs with test timeout. - - - - - 256ac29c by sheaf at 2025-03-20T18:48:07-04:00 Don't cache solved [W] HasCallStack constraints This commit ensures we do not add solved Wanted constraints that mention HasCallStack or HasExceptionContext constraints to the set of solved Wanted dictionary constraints: caching them is invalid, because re-using such cached dictionaries means using an old call-stack instead of constructing a new one, as was reported in #25529. Fixes #25529. - - - - - 47646ce2 by Andrew Lelechenko at 2025-03-20T18:48:43-04:00 Improve haddock-visible documentation for GHC.Driver.Flags - - - - - 2e4e15ed by Sylvain Henry at 2025-03-21T17:49:36-04:00 Document -fnum-constant-folding (#25862) - - - - - 044a6e08 by sheaf at 2025-03-21T17:50:24-04:00 LLVM: fix typo in padLiveArgs This commit fixes a serious bug in the padLiveArgs function, which was incorrectly computing too many padding registers. This caused segfaults, e.g. in the UnboxedTuples test. Fixes #25770 Fixes #25773 - - - - - 1745c749 by Teo Camarasu at 2025-03-22T18:42:37-04:00 template-haskell: remove Language.Haskell.TH.Lib.Internal This module is purely used for the implementation of TH quote desugarring. Historically this needed to be exposed from `template-haskell`, since that's the package that the desugarred expressions referenced but since https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12479, this is no longer the case. Now these identifiers are in `ghc-internal`. Note that this module has carried the following warning for a long time:
This is not a part of the public API, and as such, there are no API guarantees for this module from version to version.
Resolves #24766 - - - - - 3bc507db by Alan Zimmerman at 2025-03-22T18:43:13-04:00 EPA: Fix exact printing of SPECIALISE pragma This commit fixes two minor issues with exactprinting of the SPECIALISE pragma after !12319 landed - The span for the RHS did not include the optional signature type - The `::` was printed twice when the legacy path was used Closes #25885 - - - - - bdf93da8 by sheaf at 2025-03-24T11:25:12+01:00 Renamer: improve handling of export children This commit refactors the 'childGREPriority' function which is used when renaming subordinate items in export lists and class declarations. Instead of having a complicated LookupChild parameter, we now simply pass the GREInfo of the parent, which allows us to decide what is a valid child: - classes can have children that are in the type constructor namespace, - promoted data constructors should be treated the same as normal data constructors. Fixes #24027 - - - - - 1dbc7846 by Matthew Pickering at 2025-03-24T15:35:17-04:00 Revert "mk-ghcup-metadata: Clean up and add type annotations" This reverts commit 64ea68d9a206ec4db5020b0a3fc563199ab18be3. See #25889 - - - - - 6941c825 by doyougnu at 2025-03-25T10:05:58-04:00 base: construct compat RTSFlags -- see CLC #289 - - - - - 730e6f77 by doyougnu at 2025-03-25T10:06:02-04:00 base: construct compat GHC.Stats -- see CLC #289 - - - - - cd9e6605 by Ben Gamari at 2025-03-25T17:59:52-04:00 rel_eng/upload: Clarify usage directions Previously it was not made clear that the directory name is significant. - - - - - 7d18c19b by Cheng Shao at 2025-03-25T22:00:56+00:00 ghci: make the Pipe type opaque This commit makes the Pipe type in ghci opaque, and introduce the mkPipeFromHandles constructor for creating a Pipe from a pair of Handles. Pipe is now just a pair of receiver/sender continuations under the hood. This allows a Pipe to be potentially backed by other IPC mechanisms (e.g. WebSockets) which is essential for wasm ghci browser mode. - - - - - a2103fd2 by Cheng Shao at 2025-03-25T22:00:56+00:00 ghci: use improved Pipe logic for wasm iserv This commit makes wasm iserv take advantage of the Pipe refactoring by passing binary receiver/sender js callbacks from the dyld script. This paves the way for piping the binary messages through WebSockets in order to run wasm iserv in the browser, but more importantly, it allows us to get rid of a horrible hack in the dyld script: we no longer have to fake magical wasi file descriptors that are backed by nodejs blocking I/O! The legacy hack was due to these facts: - iserv only supported exchanging binary messages via handles backed by file descriptors - In wasi you can't access host file descriptors passed by host ghc - The nodejs wasi implementation only allows mapping host directories into the wasi vfs, not host file descriptors - Named pipes with file paths (mkfifo) doesn't work well with nodejs wasi implementation, causes spurious testsuite failures on macos But starting from this point, we can fully take advantage of non-blocking I/O on the js side. - - - - - fa2fbd2b by Cheng Shao at 2025-03-25T22:00:56+00:00 ghci: fix ^C handling for wasm iserv This commit fixes ^C handling for wasm iserv. Previously we didn't handle it at all, so ^C would kill the node process and host ghc would then crash as well. But native ghc with external interpreter can handle ^C just fine and wasm should be no different. Hence the fix: wasm iserv exports its signal handler as a js callback to be handled by the dyld script. Also see added note for details. - - - - - efcebed6 by Cheng Shao at 2025-03-25T22:00:56+00:00 wasm: fix post-link.mjs for browser The wasm ghci browser mode needs to run dyld.mjs in the browser which imports post-link.mjs. This script makes post-link.mjs runnable in the browser by deferring node-specific module imports to their actual use sites. - - - - - 27bb73c6 by Cheng Shao at 2025-03-25T22:00:56+00:00 wasm: use console.assert in dyld script This commit uses console.assert() instead of node-specific strict assert in the dyld script, in order to make it runnable in the browser. console.assert() only warns and doesn't crash upon assertion failure, but this is fine; we can always trivially define a strict assert function shall it be necessary when debugging, and there hasn't been such an assertion failure seen in the wild for long enough. - - - - - 929df0ba by Cheng Shao at 2025-03-25T22:00:56+00:00 wasm: asyncify the dylink.0 custom section parser This commit refactors the simple binary parser in the dyld script in charge of parsing the dylink.0 custom section. Previously the parser was synchronous and operated on the entire input buffer; this was simple and easy and worked well enough when the input wasm modules are instantly read from local filesystem. However, when running dyld in the browser, the wasm modules are transferred via fetch() requests. The host ghc and the browser might not be on the same machine, so slow network uplink does need to be considered. We only need to parse dylink.0 custom section to extract dependency info, and dylink.0 is the very first custom section in the wasm shared library binary payload, so the parsing process should not require fetch() to complete and should return the parsing result asap. Hence the refactorings in this commit: asyncify the parser, make it only consume as many bytes as needed by invoking an async consumer callback. The input is a readable stream from the fetch() response; once the response is available, the async wasm compilation can start in the background, and dylink.0 parsing shall end asap which results in more wasm shared libraries to be loaded earlier. Profit. - - - - - 9a697181 by Cheng Shao at 2025-03-25T22:00:56+00:00 wasm: fix dyld setImmediate usage in browser The wasm dyld script used to only run in node and directly uses setImmediate in globalThis. In case of browsers, it needs to import setImmediate from the prelude, hence this commit. - - - - - d9b71e82 by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: fix dyld downsweep filepath handling in browser The wasm dyld downsweep logic used to rely on nodejs path module to handle filepaths. That's not available in browsers, so this commit implements poor man's filepath handling in js, which is not elegant for sure but works for both nodejs and the browser. - - - - - 7003a399 by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: isolate nodejs-specific logic with the isNode flag in dyld As we move towards supporting running the dyld script in the browser, this commit implements the isNode module-level binding which is true if dyld is running in nodejs. The nodejs-specific bits are gated under isNode. For the browser case, this commit introduces @bjorn3/browser_wasi_shim as the wasi implementation; we already use it in quite a few projects and it simply works. - - - - - 22ba2a78 by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: isolate dyld side effects that might require IPC This commit spins out a DyLDHost class from DyLD that handles side effects that must be run in the same host environment that runs wasm32-wasi-ghc. When the dyld script runs in the browser, it'll need to do IPC to find libraries, fetch wasm library, etc, and the other side of dyld that runs on nodejs would simply expose the DyLDHost methods as endpoints for WebSockets/HTTP. - - - - - e93fc33d by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: implement wasm ghci browser mode This commit implements the rest of dyld logic that delivers the ghci browser mode: - The dyld script can now fully run in the browser. It communicates back with dyld-on-nodejs via WebSockets and also plain HTTP 1.1 requests. - The host dyld starts a server and acts as a broker between the GHC process and the browser side. GHC doesn't need to know anything about the browser mode; no driver flags need to be added and no recompilation needs to happen, the GHC driver continues to use the original iserv binary messages protocol. - The dyld broker doesn't need to parse any message between the browser dyld and GHC; it merely sets up WebSockets connections to redirect these messages as well as ^C signals. - Plain HTTP 1.1 is used for IPC requests (e.g. downloading a wasm module). - The dyld broker serves a main.js script that bootstraps iserv in the browser, and a main.html empty page playground for testing. CORS is enabled so it could be possible to inject iserv into other websites and use ghci to play with them. - All the RPC logic is opaque to the DyLD class, the majority of the wasm dynamic linker code is already portable and runs fine in firefox/chrome/webkit. Closes #25399. - - - - - fc576798 by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: add puppeteer/playwright support for ghci browser mode This commit adds support for using puppeteer/playwright for automatically launching a headless browser that backs the ghci browser mode. This is useful for testing the ghci browser mode as a part of GHC testsuite, and it's also convenient for local development since the step to start iserv can be automated away. - - - - - ad7e271d by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: support wasi console redirect for the ghci browser mode This commit adds optional support for redirecting wasi console stdout/stderr back to the host when running wasm ghci browser mode. By default, the wasi console outputs are only available under F12 devtools console, but in case of testing against a mobile browser, the devtools console may not be readily available, and it would be more convenient to at least get wasi console output on the host side. The redirection logic is simple, just adding another two WebSockets connections that pump the line-buffered textual messages back to host. - - - - - 731217ce by Cheng Shao at 2025-03-25T22:00:57+00:00 wasm: add brotli compression for ghci browser mode This commit adds brotli compression for wasm shared libraries for ghci browser mode. With BROTLI_MIN_QUALITY, the overhead is negligible, and it helps reducing amount of transferred data when the browser connects to the server over a slow connection. - - - - - ac70e643 by Cheng Shao at 2025-03-26T13:37:19+00:00 testsuite: add browser001 test for wasm ghci browser mode This commit adds support for testing the wasm ghci browser mode in the testsuite, as well as a simple first test case browser001 that makes use of TH, JSFFI and browser-specific DOM API. See added note and comments for details. - - - - - 6ef5c0d2 by Cheng Shao at 2025-03-26T13:37:24+00:00 docs: add wasm ghci subsection in user manual This commit updates the user manual to add wasm ghci subsection. - - - - - 37381bcf by Cheng Shao at 2025-03-26T13:37:24+00:00 docs: update Note [The Wasm Dynamic Linker] This commit updates Note [The Wasm Dynamic Linker] to reflect recent developments, in particular the wasm ghci browser mode. - - - - - 4b5a0f61 by Cheng Shao at 2025-03-26T13:37:24+00:00 ci: bump DOCKER_REV and test wasm ghci browser mode This commit bumps the ci-images revision for updated wasm toolchain, and adds the launch options required to test wasm ghci browser mode. - - - - - c6a3bc8f by Cheng Shao at 2025-03-26T13:37:24+00:00 driver: implement wasm ghci browser mode flags This commit implements GHC driver flags that enable the wasm ghci browser mode. - - - - - f75e823e by Cheng Shao at 2025-03-26T18:01:54-04:00 rts: add hs_try_putmvar_with_value to RTS API This commit adds hs_try_putmvar_with_value to rts. It allows more flexibility than hs_try_putmvar by taking an additional value argument as a closure to be put into the MVar. This function is used & tested by the wasm backend runtime, though it makes sense to expose it as a public facing RTS API function as well. - - - - - 9cd9f347 by Cheng Shao at 2025-03-26T18:01:54-04:00 wasm: use MVar as JSFFI import blocking mechanism Previously, when blocking on a JSFFI import, we push a custom stg_jsffi_block stack frame and arrange the `promise.then` callback to write to that stack frame. It turns out we can simply use the good old MVar to implement the blocking logic, with a few benefits: - Less maintenance burden. We can drop the stg_jsffi_block related Cmm code without loss of functionality. - It interacts better with existing async exception mechanism. throwTo would properly block the caller if the target thread is masking async exceptions. - - - - - da34f0aa by Cheng Shao at 2025-03-26T18:01:54-04:00 wasm: properly pin the raiseJSException closure We used to use keepAlive# to pin the raiseJSException closure when blocking on a JSFFI import thunk, since it can potentially be used by RTS. But raiseJSException may be used in other places as well (e.g. the promise.throwTo logic), and it's better to simply unconditionally pin it in the JSFFI initialization logic. - - - - - dc904bfd by Cheng Shao at 2025-03-26T18:01:54-04:00 wasm: implement promise.throwTo() for async JSFFI exports This commit implements promise.throwTo() for wasm backend JSFFI exports. This allows the JavaScript side to interrupt Haskell computation by raising an async exception. See subsequent docs/test commits for more details. - - - - - 7f80455e by Cheng Shao at 2025-03-26T18:01:55-04:00 testsuite: add test for wasm promise.throwTo() logic This commit adds a test case to test the wasm backend promise.throwTo() logic. - - - - - afdd3fe7 by Cheng Shao at 2025-03-26T18:01:55-04:00 docs: document the wasm backend promise.throwTo() feature - - - - - 65dc65dc by sheaf at 2025-03-26T18:02:43-04:00 Refactor CtEvidence into Given/Wanted This commit is a simple refactoring which splits up the CtEvidence, giving each constructor its own datatype: data CtEvidence = CtGiven GivenCtEvidence | CtWanted WantedCtEvidence data GivenCtEvidence = GivenCt { ctev_pred :: TcPredType , ctev_evar :: EvVar , ctev_loc :: CtLoc } data WantedCtEvidence = WantedCt { ctev_pred :: TcPredType , ctev_dest :: TcEvDest , ctev_loc :: CtLoc , ctev_rewriters :: RewriterSet } This enables a few minor simplifications in the code, notably removing a panic from GHC.Tc.Solver.Solve.solveWantedForAll_implic. Fixes #25848 - - - - - ada04031 by sheaf at 2025-03-26T18:03:27-04:00 Export lists: same prio for NoParent & RightParent This commit ensures that, when we are renaming children in an export list item such as module M ( P(A,B,C) ) we consider children with NoParent to have the same priority as children which have the correct parent (P in this case). This is because we should **not** prioritise a data constructor (with the right parent) over a pattern synonym we are bundling (which, before bundling, has no parent). Fixes #25892 - - - - - 721628a0 by Adriaan Leijnse at 2025-03-27T09:10:10-04:00 TTG: Replace HsUnboundVar with HsHole Context: The HsUnboundVar constructor in Language.Haskell.Syntax.Expr contained a RdrName, which stood in the way of the work towards a dedicated haskell-syntax library. The constructor was overloaded for unbound variables, anonymous and named holes, and parse errors. This commit: Replaces HsUnboundVar with HsHole. In the surface syntax HsHole only represents an anonymous expression hole ("_"). It is extended with the XHole type family. In the concrete GHC implementation of the language on the other hand, HsHole is used for "any thing which is not necessarily a valid or fully defined program fragment, but for which a type can be derived". This use is similar to how HsUnboundVar was used, but the parse error case is now made explicit with a ParseError case for XHole. This is in anticipation of future work on a fault tolerant compilation pipeline. - - - - - dbd852f5 by Ben Gamari at 2025-03-27T09:10:48-04:00 rel_eng: Finish removal of CentOS jobs Remove centos7 from release fetch and ghcup metadata generation scripts. Closes #25893. - - - - - 0e0231e7 by Matthew Pickering at 2025-03-28T18:36:33-04:00 hadrian: Make hash_unit_ids into a flavour transformer (and enable for release flavour) The primary reason for this change is to make the `release` flavour enable `--hash-unit-ids` by default without any further user intervention. * Packagers don't have to be aware of this special flag they should be using. * release builds on CI are uniformly testing with hashes (see !13418) Fixes #25379 - - - - - 9fc54c12 by Rodrigo Mesquita at 2025-03-28T18:37:10-04:00 driver: Move DynFlags consistency fixes off Main These consistency fixes found in Main.hs are required for the proper functioning of the compiler and should live together with all remaining fixes in `makeDynFlagsConsistent`. This is especially relevant to GHC applications that shouldn't have to copy/fix themselves possibly inconsistent DynFlags. Additionally, outputs information when verbosity is high about these consistency fixes that were previously quiet, adds information to the Note on consistency of DynFlags, and improves one of the fixes that incorrectly used `dynNow`. - - - - - 2fdd0be9 by sheaf at 2025-03-28T18:37:53-04:00 Remove GhcHint from TcRnNotInScope constructor This is a tiny refactoring which: - removes GhcHint/ImportError fields from some constructors of TcRnMessage, using the TcRnMessageDetailed mechanism instead to report this informaiton: - removes the GhcHint and ImportErrors fields from TcRnNotInScope - removes the GhcHint field from TcRnTermNameInType - ensures that we only include these hints and import errors when the -fhelpful-errors flag is turned on Fixes #25874 - - - - - 9e5cd064 by ARATA Mizuki at 2025-03-31T14:53:34-04:00 Better support for SSE3 and SSE4.1 In particular: * Pass appropriate attributes to LLVM * Define preprocessor macros for them - - - - - c2c7dd51 by ARATA Mizuki at 2025-03-31T14:53:34-04:00 x86: Add support for SSSE3 This commit adds the `-mssse3` flag, which controls usage of SSSE3 instructions in x86 code generation. - - - - - d7c62580 by ARATA Mizuki at 2025-03-31T14:53:34-04:00 x86 NCG SIMD: Implement 128-bit integer vector arithmetics This commit implements the following operations on integer vectors: * negateIntNXM# * plus{Int,Word}NXM# * minus{Int,Word}NXM# * times{Int,Word}NXM# * quot{Int,Word}NXM# * rem{Int,Word}NXM# * min{Int,Word}NXM# * max{Int,Word}NXM# where (N,M) is one of (8,16), (16,8), (32,4), or (64,2). Closes #25643 - - - - - f5ea4e7e by ARATA Mizuki at 2025-03-31T14:53:34-04:00 x86 NCG SIMD: Implement 128-bit integer vector shuffle This commit implements the following operations: * shuffle{Int,Word}8X16# * shuffle{Int,Word}16X8# * shuffle{Int,Word}32X4# * shuffle{Int,Word}64X2# See #25643 - - - - - 5eeb6645 by Simon Peyton Jones at 2025-03-31T14:54:16-04:00 Re-jig the way that the Simplifier tries RULES As #25170 showed, if a new RULE appears, it could change the simplifier's behaviour a bit, even if it never fires; and that messes up deterministic compilation. (This was particularly nasty if the rule wasn't even transitively below the module being compiled.) This MR rejigs the use of `tryRules` so that behaviour does not change when a new, unrelated RULE is added. It's described in * Note [When to apply rewrite rules] * Note [tryRules: plan (BEFORE)] * Note [tryRules: plan (AFTER)] The main change is in the refactored version of * simplOutId * rebuildCall The little state machine that was embedded in ArgInfo is gone. As I wandered around the Simplifier I also found opportunities for some loosely-related refactoring: * In several places, the /substitution/ in the SimpleEnv is empty; all we care about is the in-scope set and the flags. So - I made a synonym `SimplEnvIS` that embodies that invariant, - used it in a number of type signatures (notably `rebuild`) - added some assertion checks (via `checkSimlEnvIS`) * I moved the hanlding of `runRW` out of `rebuildCall` (where we would have to test repeatedly) and into the new `simplOutId`, which fires up `rebuildCall`. Now it is only tested once. ------------------------- Metric Decrease: T9020 T9961 ------------------------- - - - - - f534474a by sheaf at 2025-03-31T14:54:59-04:00 Add comment: no qualified Names in the LocalRdrEnv This commit adds a reference to section 5.5.1 of the Haskell 2010 report, to explain that qualified names can't occur in the LocalRdrEnv. Fixes #25875 - - - - - d5ea80c6 by Patrick at 2025-03-31T14:55:42-04:00 Fix deadlock/loop in interface rehydration (#25858) In #25858, GHC hangs when processing modules with class defaults due to a circular dependency in the interface rehydration process. The deadlock/loop occurred when eager class defaults rehydration accessed not-yet-complete module details. To fix the immediate deadlock/loop. `tcIfaceDefaults` is refactored, we use the class name directly from the iface and use `forM` for lazy loading the class, which algins with the handling of other fields of ModDetails. This laziness ensure rehydration waits for HomePackageTable (HPT) to be updated and prevent premature evaluation of ModDetails inside `fixIO``. As suggested by Matthew, class defaults importing is also refactored to align with the compiler's established interface loading conventions. - add class defaults field to ExternalPackageState (EPS). - rehydrate and store class defaults in EPS at `loadInterface`. - Instead of using `tcIfaceDefaults` in `tcRnImports`, we add and use `tcGetClsDefaults` to read defaults directly from HPT or EPS when importing modules. Tests: - T25858, T25858v1-2: Test class hydration in defaults - T25858v3-4: Test type list hydration in defaults New Note [Tricky rehydrating IfaceDefaults loop] is added. Thanks to @sheaf (Sam), @mpickering (Matthew), and @simonpj (Simon) for their valuable input and analysis. Fixes #25858. - - - - - 2d419d8d by Matthew Pickering at 2025-04-02T16:12:36-04:00 Use unsafePerformIO in definition of computeFingerprint computeFingerprint is morally a pure function, which is implemented by mutating a buffer. Using unsafePerformIO inside the definition allows it to be used in pure contexts, fixing one place where an ad-hoc call to unsafePerformIO is already needed. - - - - - ccdf979b by Matthew Pickering at 2025-04-02T16:12:37-04:00 driver: Fix recompilation checking for exported defaults Since the exported defaults are not associated with any identifier from the module, they are just added to the export hash rather than the fine-grained recompilation logic. Fixes #25855 - - - - - c5bf9892 by Matthew Pickering at 2025-04-02T16:12:37-04:00 driver: Fix recompilation checking for COMPLETE pragmas A {-# COMPLETE P, Q #-} pragma is associated with the pattern synonyms P and Q during recompilation checking. Therefore, the existence of a pattern synonym becomes part of the ABI hash for P and Q. Then if a module uses these pattern synonyms and a complete pragma changes, it will trigger recompilation in that module. Fixes #25854 - - - - - d0fd9370 by sheaf at 2025-04-02T16:14:05-04:00 Handle named default exports separately This commit changes the way we check for duplicate exports of named default declarations. They are now treated entirely separately from other exports, because in an export list of the form module M ( default Cls, Cls ) the default declaration does not export the class 'Cls', but only its default declarations. Also fixes a bug in Backpack where named default exports were getting dropped entirely. No test for that. Fixes #25857 - - - - - 62d04494 by Cheng Shao at 2025-04-03T05:56:17-04:00 ci: add x86_64-linux-ubuntu24_04 nightly/release jobs - - - - - 327952e4 by Cheng Shao at 2025-04-03T05:56:17-04:00 rel-eng: add ubuntu24_04 bindists to ghcup metadata and fetch gitlab scripts - - - - - aa1e3b8b by sheaf at 2025-04-03T05:57:24-04:00 GHC settings: always unescape escaped spaces In #25204, it was noted that GHC didn't properly deal with having spaces in its executable path, as it would compute an invalid path for the C compiler. The original fix in 31bf85ee49fe2ca0b17eaee0774e395f017a9373 used a trick: escape spaces before splitting up flags into a list. This fixed the behaviour with extra flags (e.g. -I), but forgot to also unescape for non-flags, e.g. for an executable path (such as the C compiler). This commit rectifies this oversight by consistently unescaping the spaces that were introduced in order to split up argument lists. Fixes #25204 - - - - - 34a9b55d by lazyLambda at 2025-04-04T06:22:26-04:00 Driver: make MonadComprehensions imply ParallelListComp This commit changes GHC.Driver.Flags.impliedXFlags to make the MonadComprehensions extension enable the ParallelListComp extension. Fixes #25645 - - - - - d99eb7cd by sheaf at 2025-04-04T06:23:28-04:00 NamedDefaults: handle poly-kinded unary classes With this commit, we accept named default declarations for poly-kinded classes such as Typeable, e.g. default Typeable (Char) This used to fail because we assumed the kind of the class was monomorphic, e.g. Type -> Constraint (Type -> Type) -> Constraint Nat -> Constraint Now, we can handle a simple polymorphic class such as Typeable :: forall k. k -> Constraint Note that we keep the restriction that the class must only have one visible argument. This is all explained in the new Note [Instance check for default declarations] in GHC.Tc.Gen.Default. Fixes #25882 - - - - - 4cbc90de by sheaf at 2025-04-04T11:39:05-04:00 LLVM: add type annotations to AtomicFetch_cmm.cmm - - - - - e2237305 by sheaf at 2025-04-04T11:39:05-04:00 Cmm lint: lint argument types of CallishMachOps This commit adds a new check to Cmm lint to ensure that the argument types to a CallishMachOp are correct. The lack of this check was detected in the AtomicFetch test: the literals being passed as the second arguments to operations such as 'fetch_add', 'fetch_and'... were of the wrong width, which tripped up the LLVM backend. - - - - - 9363e547 by Cheng Shao at 2025-04-04T11:39:50-04:00 ci: add ghc-wasm-meta integration testing jobs This patch adds ghc-wasm-meta integration testing jobs to the CI pipeline, which are only triggered via the `test-wasm` MR label or manually when the `wasm` label is set. These jobs will fetch the wasm bindists and test them against a variety of downstream projects, similarly to head.hackage jobs for native bindists, offering a convenient way to catch potential downstream breakage while refactoring the wasm backend. - - - - - 27029e60 by Adam Gundry at 2025-04-04T11:40:36-04:00 base: Minor fixes to GHC.Records haddocks This corrects a stale reference to OverloadedRecordFields (which should be OverloadedRecordDot), fixes the haddock link syntax and adds an @since pragma. - - - - - f827c4c6 by Rodrigo Mesquita at 2025-04-07T11:22:10-04:00 Parametrize default logger action with Handles Introduce `defaultLogActionWithHandles` to allow GHC applications to use GHC's formatting but using custom handles. `defaultLogAction` is then trivially reimplemented as ``` defaultLogActionWithHandles stdout stderr ``` - - - - - 5dade5fd by sheaf at 2025-04-07T11:23:02-04:00 Finer-grained recompilation checking for exports This commit refines the recompilation checking logic, to avoid recompiling modules with an explicit import list when the modules they import start exporting new items. More specifically, when: 1. module N imports module M, 2. M is changed, but in a way that: a. preserves the exports that N imports b. does not introduce anything that forces recompilation downstream, such as orphan instances then we no longer require recompilation of N. Note that there is more to (2a) as initially meets the eye: - if N includes a whole module or "import hiding" import of M, then we require that the export list of M does not change, - if N only includes explicit imports, we check that the imported items don't change, e.g. - if we have @import M(T(K, f), g)@, we must check that N continues to export all these identifiers, with the same Avail structure (i.e. we should error if N stops bundling K or f with T) - if we have @import M(T(..))@, we must check that the children of T have not changed See Note [When to recompile when export lists change?] in GHC.Iface.Recomp. This is all tested in the new tests RecompExports{1,2,3,4,5} Fixes #25881 - - - - - f32d6c2b by Andreas Klebinger at 2025-04-07T22:01:25-04:00 NCG: AArch64 - Add -finter-module-far-jumps. When enabled the arm backend will assume jumps to targets outside of the current module are further than 128MB away. This will allow for code to work if: * The current module results in less than 128MB of code. * The whole program is loaded within a 4GB memory region. We have seen a few reports of broken linkers (#24648) where this flag might allow a program to compile/run successfully at a very small performance cost. ------------------------- Metric Increase: T783 ------------------------- - - - - - 553c280b by Andreas Klebinger at 2025-04-07T22:02:11-04:00 Revert "rts: fix small argument passing on big-endian arch (fix #23387)" Based on analysis documented in #25791 this doesn't fully fix the big while introducing new bugs on little endian architectures. A more complete fix will have to be implemented to fix #23387 This reverts commit 4f02d3c1a7b707e609bb3aea1dc6324fa19a5c39. - - - - - b0dc6599 by Andreas Klebinger at 2025-04-07T22:02:11-04:00 Interpreter: Fixes to handling of subword value reads/writes. Load subword values as full words from the stack truncating/expanding as neccesary when dealing with subwords. This way byte order is implicitly correct. This commit also fixes the order in which we are pushing literals onto the stack on big endian archs. Last but not least we enable a test for ghci which actually tests these subword operations. - - - - - ed38c09b by Cheng Shao at 2025-04-07T22:02:53-04:00 testsuite: don't test WasmControlFlow stdout This patch solves a potential test flakiness in `WasmControlFlow` by removing `WasmControlFlow.stdout` which is not so portable/stable as it seems. See added `Note [WasmControlFlow]` for more detailed explanation. - - - - - f807c590 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00 debugger: Add docs to obtainTermFromId - - - - - 5dba052d by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00 Move logic to find and set Breakpoint to GHC Breakpoints are uniquely identified by a module and an index unique within that module. `ModBreaks` of a Module contains arrays mapping from this unique breakpoint index to information about each breakpoint. For instance, `modBreaks_locs` stores the `SrcSpan` for each breakpoint. To find a breakpoint using the line number you need to go through all breakpoints in the array for a given module and look at the line and column stored in the `SrcSpan`s. Similarly for columns and finding breakpoints by name. This logic previously lived within the `GHCi` application sources, however, it is common to any GHC applications wanting to set breakpoints, like the upcoming `ghc-debugger`. This commit moves this logic for finding and setting breakpoints to the GHC library so it can be used by both `ghci` and `ghc-debugger`. - - - - - bc0b9f73 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00 Refactor and move logic for identifier breakpoints Breakpoints can be set on functions using syntax of the form `[Module.]function`. The parsing, resolution (e.g. inferring implicit module), and validation of this syntax for referring to functions was tightly coupled with its GHCi use. This commit extracts the general purpose bits of resolving this syntax into `GHC.Runtime.Debugger.Breakpoints` so it can be further used by other GHC applications and to improve the code structure of GHCi. Moreover, a few utilities that do splitting and joining of identifiers as strings were moved to `GHC.Runtime.Eval.Utils`, which also can be used in the future to clean up `GHC.Runtime.Eval` a bit. - - - - - 4f728d21 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00 debugger: derive Ord for BreakpointIds - - - - - 5528771c by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00 debugger: Move context utils from GHCi to GHC Moves `enclosingTickSpan`, `getCurrentBreakSpan`, and `getCurrentBreakModule`, general utilities on the internal debugger state, into the GHC library. - - - - - 4871f543 by sheaf at 2025-04-08T17:42:43-04:00 Implicit quantification in type synonyms: add test This adds a test for ticket #24090, which involves implicit quantification in type synonyms. The underlying issue was fixed in 0d4ee209dfe53e5074d786487f531dabc36d561c. - - - - - 48917d3c by sheaf at 2025-04-08T17:42:44-04:00 Turn on implicit-rhs-quantification by default This flag was added to GHC 9.8, and will be removed in a future GHC release. In preparation, this commit adds it to the default warning flags. - - - - - 629be068 by Rodrigo Mesquita at 2025-04-08T17:43:26-04:00 debugger: Add breakpoints to every Stmt While single-stepping through a Haskell program we stop at every breakpoint. However, we don't introduce breakpoints at every single expression (e.g. single variables) because they would be too many and uninteresting. That said, in a do-block, it is expected that stepping over would break at every line, even if it isn't particularly interesting (e.g. a single arg like getArgs). Moreover, let-statements in do-blocks, despite only being evaluated once needed, lead to surprising jumps while stepping through because some have outermost (outside the let) breakpoints while others don't. This commit makes every statement in a do-block have a breakpoint. This leads to predictable stepping through in a do-block. Duplicate breakpoints in the same location are avoided using the existing blacklist mechanism, which was missing a check in one relevant place. Fixes #25932 - - - - - 99a3affd by Matthew Pickering at 2025-04-08T17:44:08-04:00 driver: refactor: Split downsweep and MakeAction into separate modules. This will facilitate using the downsweep functions in other parts of the compiler than just --make mode. Also, the GHC.Driver.Make module was huge. Now it's still huge but slightly smaller! - - - - - ecfec4df by sheaf at 2025-04-09T14:13:12-04:00 Store user-written qualification in the GhcRn AST This commit ensures we store the original user-written module qualification in the renamed AST. This allows us to take into account the user-written qualification in error messages. Fixes #25877 - - - - - 97c884e2 by sheaf at 2025-04-09T14:13:12-04:00 TcRnIllegalTermLevelUse: simpler error when possible This commit makes GHC emit a simple error message in the case of an illegal term-level use of a data constructor: we will try to report an out-of-scope error instead of a "Illegal term level use" error, as the latter might be a bit overwhelming for newcomers. We do this when we have a data constructor import suggestion to provide to the user. For example: module M where { data A = A } module N where import M(A) x = Bool -- Illegal term-level use of Bool y = A -- Data constructor not in scope: A. -- Perhaps add 'A' to the import list of 'M'. This commit also revamps the "similar names" suggestion mechanism, and in particular its treatment of name spaces. Now, which name spaces we suggest is based solely on what we are looking for, and no longer on the NameSpace of the Name we have. This is because, for illegal term-level use errors, it doesn't make much sense to change the suggestions based on the fact that we resolved to e.g. a type constructor/class; what matters is what we were expecting to see in this position. See GHC.Rename.Unbound.{suggestionIsRelevant,relevantNameSpace} as well as the new constructors to GHC.Tc.Errors.Types.WhatLooking. Fixes #23982 - - - - - bff645ab by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00 driver: Split Session functions out of Main This commit moves out functions that help in creating and validating a GHC multi session from Main into the ghc library where they can be used by other GHC applications. Moreover, `Mode` processing and `checkOptions` linting were moved to separate modules within the ghc-bin executable package. In particular: - Move `Mode` types and functions (referring to the mode GHC is running on) to `ghc-bin:GHC.Driver.Session.Mode` - Move `checkOptions` and aux functions, which validates GHC DynFlags based on the mode, to `ghc-bin:GHC.Driver.Session.Lint` - Moves `initMulti`, `initMake`, and aux functions, which initializes a make/multi-unit session, into `ghc:GHC.Driver.Session.Units`. - - - - - 501b015e by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00 docs: Improve haddock of ExecComplete - - - - - dea98988 by Andreas Klebinger at 2025-04-09T19:23:57-04:00 Avoid oversaturing constructor workers. Constructor applications always need to take the exact number of arguments. If we can't ensure that instead apply the constructor worker like a regular function. Fixes #23865 - - - - - f1acdd2c by sheaf at 2025-04-09T19:25:41-04:00 NamedDefaults: require the class to be standard We now only default type variables if they only appear in constraints of the form `C v`, where `C` is either a standard class or a class with an in-scope default declaration. This rectifies an oversight in the original implementation of the NamedDefault extensions that was remarked in #25775; that implementation allowed type variables to appear in unary constraints which had arbitrary classes at the head. See the rewritten Note [How type-class constraints are defaulted] for details of the implementation. Fixes #25775 Fixes #25778 - - - - - 5712e0d6 by Vladislav Zavialov at 2025-04-10T05:17:38+00:00 Retry type/class declarations and instances (#12088) Retry type/class declarations and instances to account for non-lexical dependencies arising from type/data family instances. This patch improves the kind checker's ability to use type instances in kind checking of other declarations in the same module. * Key change: tcTyAndClassDecls now does multiple passes over the TyClGroups, as long as it is able to make progress. See the new Note [Retrying TyClGroups] in GHC.Tc.TyCl * Supporting change: FVs of a TyClGroup are now recorded in its extension field, namely XCTyClGroup. See the new Note [Prepare TyClGroup FVs] in GHC.Rename.Module * Instances are no longer inserted at the earliest positions where their FVs are bound. This is a simplification. See the new Note [Put instances at the end] in GHC.Rename.Module * Automatic unpacking is now more predictable, but fewer fields get unpacked by default. Use explicit {-# UNPACK #-} pragmas instead. See the new Note [Flaky -funbox-strict-fields with type/data families] For the wide range of newly accepted programs, consult the added test cases. Fixed tickets: #12088, #12239, #14668, #15561, #16410, #16448, #16693, #19611, #20875, #21172, #22257, #25238, #25834 Metric Decrease: T8095 - - - - - bc73a78d by sheaf at 2025-04-10T15:07:24-04:00 checkFamApp: don't be so eager to cycle break As remarked in #25933, a pure refactoring of checkTyEqRhs in ab77fc8c7adebd610aa0bd99d653f9a6cc78a374 inadvertently changed behaviour, as it caused GHC to introduce cycle-breaker variables in some unnecessary circumstances. This commit refactors 'GHC.Tc.Utils.Unify.checkFamApp' in a way that should restore the old behaviour, so that, when possible, we first recur into the arguments and only introduce a cycle breaker if this recursion fails (e.g. due to an occurs check failure). Fixes #25933 - - - - - 3acd8182 by Andreas Klebinger at 2025-04-10T22:32:12-04:00 Expand docs for RTS flag `-M`. The behaviour of how/when exceptions are raised was not really covered in the docs. - - - - - 026c1a39 by Adam Sandberg Ericsson at 2025-04-10T22:32:56-04:00 add cases for more SchedulerStatus codes in rts_checkSchedStatus - - - - - 5977c6a1 by sheaf at 2025-04-10T22:33:46-04:00 Squash warnings in GHC.Runtime.Heap.Inspect There were incomplete record selector warnings in GHC.Runtime.Heap.Inspect due to the use of the partial 'dataArgs' record selector. This is fixed by passing the fields to the 'extractSubTerms' function directly, rather than passing a value of the parent data type. - - - - - 07a15e2a by Sven Tennie at 2025-04-11T18:47:16+02:00 RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738) J_TBL result in local jumps, there should not deallocate stack slots (see Note [extra spill slots].) J is for non-local jumps, these may need to deallocate stack slots. - - - - - 805 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/LateCC/TopLevelBinds.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CallerCC/Types.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Rules/Config.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Type.hs-boot - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/BooleanFormula.hs - compiler/GHC/Data/Graph/Color.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - compiler/GHC/Driver/Config/StgToCmm.hs - + compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - + compiler/GHC/Driver/IncludeSpecs.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - + compiler/GHC/Driver/MakeAction.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - + compiler/GHC/Driver/Session/Units.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Decl.hs - compiler/GHC/Iface/Env.hs - compiler/GHC/Iface/Ext/Ast.hs - + compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Binary.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Recomp/Types.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/IfaceToCore.hs-boot - compiler/GHC/JS/Opt/Expr.hs - compiler/GHC/JS/Opt/Simple.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Platform.hs - compiler/GHC/Platform/LoongArch64.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Runtime/Debugger.hs - + compiler/GHC/Runtime/Debugger/Breakpoints.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - + compiler/GHC/Runtime/Eval/Utils.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - compiler/GHC/Runtime/Interpreter/Wasm.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/TagCheck.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Hole/Plugin.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - − compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Irred.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Rewrite.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Solver/Types.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TcRef.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/Env.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Annotations.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Breakpoint.hs - compiler/GHC/Types/CostCentre.hs - compiler/GHC/Types/CostCentre/State.hs - compiler/GHC/Types/DefaultEnv.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/GHC/Types/HpcInfo.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/ProfAuto.hs - compiler/GHC/Types/SafeHaskell.hs - compiler/GHC/Types/SourceFile.hs - compiler/GHC/Types/SptEntry.hs - compiler/GHC/Types/SrcLoc.hs - compiler/GHC/Types/TyThing/Ppr.hs - compiler/GHC/Types/Unique/Supply.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var/Env.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/ModDetails.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Logger.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Panic.hs - compiler/GHC/Utils/Unique.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/Language/Haskell/Syntax/Type.hs-boot - compiler/ghc.cabal.in - docs/users_guide/9.14.1-notes.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/exts/ffi.rst - docs/users_guide/exts/linear_types.rst - docs/users_guide/exts/monad_comprehensions.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/overloaded_strings.rst - docs/users_guide/exts/parallel_list_comprehensions.rst - docs/users_guide/exts/poly_kinds.rst - docs/users_guide/exts/pragmas.rst - + docs/users_guide/exts/type_defaulting.rst - docs/users_guide/exts/types.rst - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - docs/users_guide/runtime_control.rst - docs/users_guide/using-concurrent.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - docs/users_guide/using.rst - docs/users_guide/wasm.rst - + ghc/GHC/Driver/Session/Lint.hs - + ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/src/CommandLine.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Hadrian/Haskell/Hash.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Release.hs - libraries/array - libraries/base/src/GHC/RTS/Flags.hs - libraries/base/src/GHC/Records.hs - libraries/base/src/GHC/Stats.hs - libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs - libraries/ghc-boot/GHC/Serialized.hs - libraries/ghc-experimental/src/GHC/Wasm/Prim.hs - + libraries/ghc-internal/cbits/int64x2minmax.c - + libraries/ghc-internal/cbits/vectorQuotRem.c - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Float.hs - libraries/ghc-internal/src/GHC/Internal/Numeric.hs - libraries/ghc-internal/src/GHC/Internal/Real.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - libraries/ghc-internal/src/GHC/Internal/TypeError.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ResolvedBCO.hs - libraries/ghci/GHCi/Server.hs - libraries/ghci/GHCi/Signals.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs - − libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs - libraries/template-haskell/Language/Haskell/TH/Ppr.hs - libraries/template-haskell/Language/Haskell/TH/PprLib.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - m4/fp_settings.m4 - m4/fptools_set_c_ld_flags.m4 - nofib - rts/HeapStackCheck.cmm - rts/IOManager.c - rts/Interpreter.c - rts/PrimOps.cmm - rts/RtsAPI.c - rts/RtsSymbols.c - rts/include/HsFFI.h - rts/include/RtsAPI.h - rts/linker/MachO.c - rts/linker/MachOTypes.h - rts/wasm/JSFFI.c - rts/wasm/blocker.cmm - rts/wasm/jsval.cmm - rts/wasm/scheduler.cmm - testsuite/driver/junit.py - testsuite/driver/perf_notes.py - testsuite/tests/cmm/should_run/AtomicFetch_cmm.cmm - + testsuite/tests/core-to-stg/T23865.hs - testsuite/tests/core-to-stg/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/deSugar/should_compile/T10251.stderr - + testsuite/tests/default/T25775.hs - + testsuite/tests/default/T25775.stderr - + testsuite/tests/default/T25857.hs - + testsuite/tests/default/T25857.stderr - + testsuite/tests/default/T25858.hs - + testsuite/tests/default/T25858.stdout - + testsuite/tests/default/T25858v1.hs - + testsuite/tests/default/T25858v1.stdout - + testsuite/tests/default/T25858v1_helper.hs - + testsuite/tests/default/T25858v2.hs - + testsuite/tests/default/T25858v2.stdout - + testsuite/tests/default/T25858v2_helper.hs - + testsuite/tests/default/T25858v3.hs - + testsuite/tests/default/T25858v3.stdout - + testsuite/tests/default/T25858v3_helper.hs - + testsuite/tests/default/T25858v4.hs - + testsuite/tests/default/T25858v4.stdout - + testsuite/tests/default/T25882.hs - testsuite/tests/default/all.T - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail08.hs - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/dependent/should_compile/GADTSingletons.hs - + testsuite/tests/dependent/should_compile/T12088a.hs - + testsuite/tests/dependent/should_compile/T12088b.hs - + testsuite/tests/dependent/should_compile/T12088c.hs - + testsuite/tests/dependent/should_compile/T12088d.hs - + testsuite/tests/dependent/should_compile/T12088e.hs - + testsuite/tests/dependent/should_compile/T12088sg1.hs - + testsuite/tests/dependent/should_compile/T12088sg2.hs - + testsuite/tests/dependent/should_compile/T12088sg3.hs - + testsuite/tests/dependent/should_compile/T12239.hs - + testsuite/tests/dependent/should_compile/T14668a.hs - + testsuite/tests/dependent/should_compile/T14668b.hs - + testsuite/tests/dependent/should_compile/T15561.hs - + testsuite/tests/dependent/should_compile/T16410.hs - + testsuite/tests/dependent/should_compile/T16448.hs - + testsuite/tests/dependent/should_compile/T16693.hs - + testsuite/tests/dependent/should_compile/T19611.hs - + testsuite/tests/dependent/should_compile/T20875.hs - + testsuite/tests/dependent/should_compile/T21172.hs - + testsuite/tests/dependent/should_compile/T22257a.hs - + testsuite/tests/dependent/should_compile/T22257b.hs - + testsuite/tests/dependent/should_compile/T25238.hs - + testsuite/tests/dependent/should_compile/T25834.hs - testsuite/tests/dependent/should_compile/all.T - testsuite/tests/dependent/should_fail/T16326_Fail8.stderr - testsuite/tests/deriving/should_compile/T17324.stderr - testsuite/tests/deriving/should_compile/T17339.stderr - testsuite/tests/diagnostic-codes/codes.stdout - + testsuite/tests/driver/RecompCompletePragma/A1.hs - + testsuite/tests/driver/RecompCompletePragma/A2.hs - + testsuite/tests/driver/RecompCompletePragma/A3.hs - + testsuite/tests/driver/RecompCompletePragma/A4.hs - + testsuite/tests/driver/RecompCompletePragma/B1.hs - + testsuite/tests/driver/RecompCompletePragma/C1.hs - + testsuite/tests/driver/RecompCompletePragma/C2.hs - + testsuite/tests/driver/RecompCompletePragma/C3.hs - + testsuite/tests/driver/RecompCompletePragma/Makefile - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stderr - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityA.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityB.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stderr - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma2.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaA.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaB.hs - + testsuite/tests/driver/RecompCompletePragma/all.T - + testsuite/tests/driver/RecompExportedDefault/A.hs - + testsuite/tests/driver/RecompExportedDefault/A2.hs - + testsuite/tests/driver/RecompExportedDefault/A3.hs - + testsuite/tests/driver/RecompExportedDefault/A4.hs - + testsuite/tests/driver/RecompExportedDefault/Makefile - + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.hs - + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.stdout - + testsuite/tests/driver/RecompExportedDefault/all.T - + testsuite/tests/driver/RecompExports/Makefile - + testsuite/tests/driver/RecompExports/RecompExports1.stderr - + testsuite/tests/driver/RecompExports/RecompExports1.stdout - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports1_N.hs - + testsuite/tests/driver/RecompExports/RecompExports2.stderr - + testsuite/tests/driver/RecompExports/RecompExports2.stdout - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports2_N.hs - + testsuite/tests/driver/RecompExports/RecompExports3.stderr - + testsuite/tests/driver/RecompExports/RecompExports3.stdout - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports3_N.hs - + testsuite/tests/driver/RecompExports/RecompExports4.stderr - + testsuite/tests/driver/RecompExports/RecompExports4.stdout - + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports4_N.hs - + testsuite/tests/driver/RecompExports/RecompExports5.stdout - + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports5_N.hs - + testsuite/tests/driver/RecompExports/all.T - testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout - + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs - testsuite/tests/driver/dynamicToo/dynamicToo001/test.T - testsuite/tests/driver/inline-check.stderr - testsuite/tests/ffi/should_compile/all.T - testsuite/tests/ghc-api/Makefile - testsuite/tests/ghc-api/T18522-dbg-ppr.hs - + testsuite/tests/ghc-api/T25577.hs - testsuite/tests/ghc-api/all.T - testsuite/tests/ghc-api/exactprint/Test20239.stderr - testsuite/tests/ghc-api/settings-escape/T11938.hs → testsuite/tests/ghc-api/settings-escape/T24265.hs - testsuite/tests/ghc-api/settings-escape/T11938.stderr → testsuite/tests/ghc-api/settings-escape/T24265.stderr - + testsuite/tests/ghc-api/settings-escape/T25204.hs - + testsuite/tests/ghc-api/settings-escape/T25204.stdout - + testsuite/tests/ghc-api/settings-escape/T25204_C.c - testsuite/tests/ghc-api/settings-escape/all.T - + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/ghc version.h - testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib/.gitkeep → testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/.gitkeep - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - + testsuite/tests/ghci-browser/all.T - + testsuite/tests/ghci-browser/browser001.script - + testsuite/tests/ghci-browser/browser001.stdout - + testsuite/tests/ghci.debugger/scripts/T25932.hs - + testsuite/tests/ghci.debugger/scripts/T25932.script - + testsuite/tests/ghci.debugger/scripts/T25932.stdout - testsuite/tests/ghci.debugger/scripts/T8487.script - testsuite/tests/ghci.debugger/scripts/all.T - testsuite/tests/ghci.debugger/scripts/break018.script - testsuite/tests/ghci.debugger/scripts/break018.stdout - testsuite/tests/ghci.debugger/scripts/dynbrk004.stdout - testsuite/tests/ghci.debugger/scripts/dynbrk007.script - testsuite/tests/ghci.debugger/scripts/dynbrk007.stdout - testsuite/tests/ghci/scripts/T12550.stdout - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr - testsuite/tests/hpc/fork/hpc_fork.stdout - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - + testsuite/tests/indexed-types/should_compile/T25657.hs - testsuite/tests/indexed-types/should_compile/all.T - testsuite/tests/indexed-types/should_fail/T8550.stderr - testsuite/tests/interface-stability/README.mkd - testsuite/tests/interface-stability/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - + testsuite/tests/interface-stability/ghc-bignum-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout - + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/jsffi/all.T - + testsuite/tests/jsffi/cancel.hs - + testsuite/tests/jsffi/cancel.mjs - + testsuite/tests/jsffi/cancel.stdout - testsuite/tests/jsffi/jsffigc.hs - + testsuite/tests/linear/should_compile/NonLinearRecord.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs - + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/linters/notes.stdout - + testsuite/tests/llvm/should_run/T25770.hs - + testsuite/tests/llvm/should_run/T25770.stdout - testsuite/tests/llvm/should_run/all.T - testsuite/tests/module/T11970A.stderr - testsuite/tests/module/all.T - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod147.stderr - testsuite/tests/module/mod176.stderr - testsuite/tests/module/mod73.hs - testsuite/tests/module/mod73.stderr - testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_compile/T15279.stderr - testsuite/tests/parser/should_compile/T20452.stderr - testsuite/tests/parser/should_fail/T3811c.stderr - testsuite/tests/parser/should_fail/T7848.stderr - testsuite/tests/parser/should_fail/readFail038.stderr - testsuite/tests/parser/should_fail/unpack_inside_type.stderr - testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr - testsuite/tests/perf/compiler/WWRec.hs - testsuite/tests/perf/compiler/hard_hole_fits.hs - testsuite/tests/perf/compiler/hard_hole_fits.stderr - testsuite/tests/plugins/T20803-plugin/FixErrorsPlugin.hs - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/polykinds/T18300.hs - testsuite/tests/polykinds/T18300.stderr - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/Makefile - testsuite/tests/printer/T18791.stderr - testsuite/tests/printer/Test24533.stdout - + testsuite/tests/printer/Test25885.hs - testsuite/tests/printer/all.T - testsuite/tests/quasiquotation/T7918.hs - testsuite/tests/rename/should_compile/T14881.stderr - + testsuite/tests/rename/should_compile/T24027.hs - + testsuite/tests/rename/should_compile/T24027_aux.hs - + testsuite/tests/rename/should_compile/T24035.hs - + testsuite/tests/rename/should_compile/T24035_aux.hs - + testsuite/tests/rename/should_compile/T24035b.hs - + testsuite/tests/rename/should_compile/T24035b.stderr - + testsuite/tests/rename/should_compile/T25892.hs - + testsuite/tests/rename/should_compile/T25892_aux.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/SimilarNamesImport.stderr - testsuite/tests/rename/should_fail/T16114.stderr - testsuite/tests/rename/should_fail/T18240a.stderr - testsuite/tests/rename/should_fail/T19843c.stderr - testsuite/tests/rename/should_fail/T22478b.stderr - testsuite/tests/rename/should_fail/T22478e.stderr - testsuite/tests/rename/should_fail/T22478f.stderr - + testsuite/tests/rename/should_fail/T22688.hs - + testsuite/tests/rename/should_fail/T22688.stderr - testsuite/tests/rename/should_fail/T23510a.hs - testsuite/tests/rename/should_fail/T23510a.stderr - + testsuite/tests/rename/should_fail/T23982.hs - + testsuite/tests/rename/should_fail/T23982.stderr - + testsuite/tests/rename/should_fail/T23982_aux.hs - + testsuite/tests/rename/should_fail/T23982b.hs - + testsuite/tests/rename/should_fail/T23982b.stderr - + testsuite/tests/rename/should_fail/T23982b_aux.hs - + testsuite/tests/rename/should_fail/T25877.hs - + testsuite/tests/rename/should_fail/T25877.stderr - + testsuite/tests/rename/should_fail/T25877_aux.hs - testsuite/tests/rename/should_fail/T5951.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/rts/T13082/Makefile - testsuite/tests/rts/T13082/T13082_fail.stderr → testsuite/tests/rts/T13082/T13082_fail.stdout - testsuite/tests/rts/all.T - testsuite/tests/saks/should_fail/T16722.stderr - testsuite/tests/saks/should_fail/saks_fail003.stderr - testsuite/tests/showIface/Orphans.stdout - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/doublex2_arith.hs - + testsuite/tests/simd/should_run/doublex2_arith.stdout - + testsuite/tests/simd/should_run/doublex2_arith_baseline.hs - + testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout - + testsuite/tests/simd/should_run/doublex2_fma.hs - + testsuite/tests/simd/should_run/doublex2_fma.stdout - + testsuite/tests/simd/should_run/floatx4_arith.hs - + testsuite/tests/simd/should_run/floatx4_arith.stdout - + testsuite/tests/simd/should_run/floatx4_arith_baseline.hs - + testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout - + testsuite/tests/simd/should_run/floatx4_fma.hs - + testsuite/tests/simd/should_run/floatx4_fma.stdout - + testsuite/tests/simd/should_run/int16x8_arith.hs - + testsuite/tests/simd/should_run/int16x8_arith.stdout - + testsuite/tests/simd/should_run/int16x8_arith_baseline.hs - + testsuite/tests/simd/should_run/int16x8_arith_baseline.stdout - + testsuite/tests/simd/should_run/int16x8_shuffle.hs - + testsuite/tests/simd/should_run/int16x8_shuffle.stdout - + testsuite/tests/simd/should_run/int16x8_shuffle_baseline.hs - + testsuite/tests/simd/should_run/int16x8_shuffle_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_arith.hs - + testsuite/tests/simd/should_run/int32x4_arith.stdout - + testsuite/tests/simd/should_run/int32x4_arith_baseline.hs - + testsuite/tests/simd/should_run/int32x4_arith_baseline.stdout - + testsuite/tests/simd/should_run/int32x4_shuffle.hs - + testsuite/tests/simd/should_run/int32x4_shuffle.stdout - + testsuite/tests/simd/should_run/int32x4_shuffle_baseline.hs - + testsuite/tests/simd/should_run/int32x4_shuffle_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_arith.hs - + testsuite/tests/simd/should_run/int64x2_arith.stdout - + testsuite/tests/simd/should_run/int64x2_arith_baseline.hs - + testsuite/tests/simd/should_run/int64x2_arith_baseline.stdout - + testsuite/tests/simd/should_run/int64x2_shuffle.hs - + testsuite/tests/simd/should_run/int64x2_shuffle.stdout - + testsuite/tests/simd/should_run/int64x2_shuffle_baseline.hs - + testsuite/tests/simd/should_run/int64x2_shuffle_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_arith.hs - + testsuite/tests/simd/should_run/int8x16_arith.stdout - + testsuite/tests/simd/should_run/int8x16_arith_baseline.hs - + testsuite/tests/simd/should_run/int8x16_arith_baseline.stdout - + testsuite/tests/simd/should_run/int8x16_shuffle.hs - + testsuite/tests/simd/should_run/int8x16_shuffle.stdout - + testsuite/tests/simd/should_run/int8x16_shuffle_baseline.hs - + testsuite/tests/simd/should_run/int8x16_shuffle_baseline.stdout - + testsuite/tests/simd/should_run/word16x8_arith.hs - + testsuite/tests/simd/should_run/word16x8_arith.stdout - + testsuite/tests/simd/should_run/word16x8_arith_baseline.hs - + testsuite/tests/simd/should_run/word16x8_arith_baseline.stdout - + testsuite/tests/simd/should_run/word32x4_arith.hs - + testsuite/tests/simd/should_run/word32x4_arith.stdout - + testsuite/tests/simd/should_run/word32x4_arith_baseline.hs - + testsuite/tests/simd/should_run/word32x4_arith_baseline.stdout - + testsuite/tests/simd/should_run/word64x2_arith.hs - + testsuite/tests/simd/should_run/word64x2_arith.stdout - + testsuite/tests/simd/should_run/word64x2_arith_baseline.hs - + testsuite/tests/simd/should_run/word64x2_arith_baseline.stdout - + testsuite/tests/simd/should_run/word8x16_arith.hs - + testsuite/tests/simd/should_run/word8x16_arith.stdout - + testsuite/tests/simd/should_run/word8x16_arith_baseline.hs - + testsuite/tests/simd/should_run/word8x16_arith_baseline.stdout - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs - + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr - testsuite/tests/simplCore/should_compile/Makefile - testsuite/tests/simplCore/should_compile/RewriteHigherOrderPatterns.stderr - testsuite/tests/simplCore/should_compile/T12603.stdout - testsuite/tests/simplCore/should_compile/T15445.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T18668.stderr - + testsuite/tests/simplCore/should_compile/T24359a.hs - + testsuite/tests/simplCore/should_compile/T24359a.stderr - + testsuite/tests/simplCore/should_compile/T25389.hs - + testsuite/tests/simplCore/should_compile/T25389.stderr - + testsuite/tests/simplCore/should_compile/T3990b.hs - + testsuite/tests/simplCore/should_compile/T3990b.stdout - testsuite/tests/simplCore/should_compile/T4398.stderr - testsuite/tests/simplCore/should_compile/T5821.hs - testsuite/tests/simplCore/should_compile/T8537.stderr - + testsuite/tests/simplCore/should_compile/T9578b.hs - testsuite/tests/simplCore/should_compile/all.T - − testsuite/tests/simplCore/should_compile/simpl016.stderr - + testsuite/tests/simplCore/should_fail/T25117a.hs - + testsuite/tests/simplCore/should_fail/T25117a.stderr - + testsuite/tests/simplCore/should_fail/T25117b.hs - + testsuite/tests/simplCore/should_fail/T25117b.stderr - + testsuite/tests/simplCore/should_fail/T25672.hs - + testsuite/tests/simplCore/should_fail/T25672.stderr - testsuite/tests/simplCore/should_fail/all.T - + testsuite/tests/simplCore/should_run/T24359b.hs - + testsuite/tests/simplCore/should_run/T24359b.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/th/T13123.stderr - testsuite/tests/th/T15365.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T19363.stdout - testsuite/tests/th/T7064.stdout - testsuite/tests/th/TH_pragma.hs - testsuite/tests/th/TH_pragma.stderr - testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs - testsuite/tests/typecheck/should_compile/LoopOfTheDay1.hs - testsuite/tests/typecheck/should_compile/LoopOfTheDay2.hs - testsuite/tests/typecheck/should_compile/LoopOfTheDay3.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.hs - + testsuite/tests/typecheck/should_compile/RuleEqs.stderr - testsuite/tests/typecheck/should_compile/T10504.stderr - + testsuite/tests/typecheck/should_compile/T21003.hs - testsuite/tests/typecheck/should_compile/T2494.stderr - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs - + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_compile/tc186.hs - testsuite/tests/typecheck/should_compile/tc212.hs - testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr - testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs - + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr - testsuite/tests/typecheck/should_fail/T10495.hs - testsuite/tests/typecheck/should_fail/T10495.stderr - testsuite/tests/typecheck/should_fail/T12729.stderr - testsuite/tests/typecheck/should_fail/T12921.stderr - testsuite/tests/typecheck/should_fail/T16394.stderr - testsuite/tests/typecheck/should_fail/T19109.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - testsuite/tests/typecheck/should_fail/T23776.stderr - + testsuite/tests/typecheck/should_fail/T24090a.hs - + testsuite/tests/typecheck/should_fail/T24090a.stderr - + testsuite/tests/typecheck/should_fail/T24090b.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr → testsuite/tests/typecheck/should_fail/T24090b.stderr - + testsuite/tests/typecheck/should_fail/T25004.hs - + testsuite/tests/typecheck/should_fail/T25004.stderr - testsuite/tests/typecheck/should_fail/T5853.stderr - testsuite/tests/typecheck/should_fail/T6018fail.stderr - testsuite/tests/typecheck/should_fail/T7210.stderr - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs - testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr - testsuite/tests/typecheck/should_fail/all.T - + testsuite/tests/typecheck/should_run/T25529.hs - + testsuite/tests/typecheck/should_run/T25529.stdout - testsuite/tests/typecheck/should_run/all.T - + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs - + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr - testsuite/tests/warnings/should_compile/T19296.stderr - testsuite/tests/warnings/should_compile/WarnNoncanonical.stderr - testsuite/tests/warnings/should_compile/all.T - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs - + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr - testsuite/tests/warnings/should_fail/all.T - testsuite/tests/wasm/should_run/control-flow/README.md - − testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.stdout - testsuite/tests/wasm/should_run/control-flow/all.T - testsuite/tests/wcompat-warnings/Template.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/Parsers.hs - utils/dump-decls/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/html-test/ref/LinearTypes.html - utils/haddock/html-test/ref/QuasiExpr.html - utils/haddock/html-test/ref/TH.html - utils/haddock/html-test/ref/Threaded_TH.html - utils/haddock/html-test/src/LinearTypes.hs - utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex - utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs - utils/jsffi/dyld.mjs - utils/jsffi/post-link.mjs - utils/jsffi/prelude.mjs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1263d40ad2072f9eb4eff2ed5938115... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1263d40ad2072f9eb4eff2ed5938115... You're receiving this email because of your account on gitlab.haskell.org.