- Mar 19, 2025
-
-
Galen Sprout authored
This commit changes GHC.Driver.Flags.impliedXFlags to make the MonadComprehensions extension enable the ParallelListComp extension. Fixes #25645
-
-
As with ghc-prim, it makes sense to have some protection against accidental interface changes to this package caused by changes in ghc-internal.
-
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 e70d4140 does not ensure that all GHC-built object files have a default model of medium, and will raise an R_LARCH_B26 overflow error.
-
CentOS 7 is EoL and moreover we cannot even build images for it. See #25061.
-
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.
-
Fixes #25867. (Ben-raytrace being broken by library changes)
-
The new implementation generates correct code even if the registers overlap. Closes #25859
-
This also revealed that `readProcessEnvWithExitCode` and its local helpers were dead code.
-
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.
-
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,
-
- Mar 15, 2025
-
-
Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`, resulting in #25856.
-
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 -------------------------
-
- Mar 14, 2025
-
-
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
-
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
-
- Mar 13, 2025
-
-
-
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.
-
- Mar 12, 2025
-
-
These are no longer used. I noticed these while looking for uses of __PIC__ in Cmm sources.
-
Getting this file right has historically been quite painful as it is a dynamically-typed script running only late in the release pipeline.
-
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
-
-
This MR fixes #25672 See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make
-
- Mar 11, 2025
-
-
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`.
-
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.
-
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`.
-
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.
-
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
-
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).
-
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.
-
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.
-
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.
-
These tests can be expressed perfectly well using the testsuite driver itself.
-
-
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
-
Otherwise, we would not get a callstack printed out when the exception occurs. Fixes #25829
-