summaryrefslogtreecommitdiff
Commit message (Collapse)AuthorAgeFilesLines
* docs: Add note to unsafeCoerce function that you might want to use coerce ↵wip/coerce-docsMatthew Pickering2022-03-031-0/+4
| | | | | | [skip ci] Fixes #15429
* StgToCmm.cgTopBinding: no isNCG, use binBlobThreshdoyougnu2022-03-024-16/+22
| | | | | | | | | | | | | | | | | | | | | | | | | This is a one line change. It is a fixup from MR!7325, was pointed out in review of MR!7442, specifically: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7442#note_406581 The change removes isNCG check from cgTopBinding. Instead it changes the type of binBlobThresh in DynFlags from Word to Maybe Word, where a Just 0 or a Nothing indicates an infinite threshold and thus the disable CmmFileEmbed case in the original check. This improves the cohesion of the module because more NCG related Backend stuff is moved into, and checked in, StgToCmm.Config. Note, that the meaning of a Just 0 or a Nothing in binBlobThresh is indicated in a comment next to its field in GHC.StgToCmm.Config. DynFlags: binBlobThresh: Word -> Maybe Word StgToCmm.Config: binBlobThesh add not ncg check DynFlags.binBlob: move Just 0 check to dflags init StgToCmm.binBlob: only check isNCG, Just 0 check to dflags StgToCmm.Config: strictify binBlobThresh
* Ticky profiling improvements.Matthew Pickering2022-03-0220-54/+325
| | | | | | | | | | | | | | | | | | | | This adds a number of changes to ticky-ticky profiling. When an executable is profiled with IPE profiling it's now possible to associate id-related ticky counters to their source location. This works by emitting the info table address as part of the counter which can be looked up in the IPE table. Add a `-ticky-ap-thunk` flag. This flag prevents the use of some standard thunks which are precompiled into the RTS. This means reduced cache locality and increased code size. But it allows better attribution of execution cost to specific source locations instead of simple attributing it to the standard thunk. ticky-ticky now uses the `arg` field to emit additional information about counters in json format. When ticky-ticky is used in combination with the eventlog eventlog2html can be used to generate a html table from the eventlog similar to the old text output for ticky-ticky.
* Core Lint: collect args through floatable tickssheaf2022-03-013-1/+20
| | | | | | | | | | | | | | | | | | We were not looking through floatable ticks when collecting arguments in Core Lint, which caused `checkCanEtaExpand` to fail on something like: ```haskell reallyUnsafePtrEquality = \ @a -> (src<loc> reallyUnsafePtrEquality#) @Lifted @a @Lifted @a ``` We fix this by using `collectArgsTicks tickishFloatable` instead of `collectArgs`, to be consistent with the behaviour of eta expansion outlined in Note [Eta expansion and source notes] in GHC.Core.Opt.Arity. Fixes #21152.
* driver: Properly add an edge between a .hs and its hs-boot fileMatthew Pickering2022-03-0118-90/+78
| | | | | | | | | | | | | | As noted in #21071 we were missing adding this edge so there were situations where the .hs file would get compiled before the .hs-boot file which leads to issues with -j. I fixed this properly by adding the edge in downsweep so the definition of nodeDependencies can be simplified to avoid adding this dummy edge in. There are plenty of tests which seem to have these redundant boot files anyway so no new test. #21094 tracks the more general issue of identifying redundant hs-boot and SOURCE imports.
* Fix longstanding issue with moduleGraphNodes - no hs-boot files caseMatthew Pickering2022-03-011-12/+28
| | | | | | | | | | | | | | | | | | | | In the case when we tell moduleGraphNodes to drop hs-boot files the idea is to collapse hs-boot files into their hs file nodes. In the old code * nodeDependencies changed edges from IsBoot to NonBoot * moduleGraphNodes just dropped boot file nodes The net result is that any dependencies of the hs-boot files themselves were dropped. The correct thing to do is * nodeDependencies changes edges from IsBoot to NonBoot * moduleGraphNodes merges dependencies of IsBoot and NonBoot nodes. The result is a properly quotiented dependency graph which contains no hs-boot files nor hs-boot file edges. Why this didn't cause endless issues when compiling with boot files, we will never know.
* template-haskell: fix docstring for BytesTeo Camarasu2022-02-281-0/+1
| | | | | It seems like a commented out section of code was accidentally included in the docstring for a field.
* template-haskell: fix typo in docstring for OverlapTeo Camarasu2022-02-281-1/+1
|
* linking: Don't pass --hash-size and --reduce-memory-overhead to ldMatthew Pickering2022-02-281-14/+4
| | | | | | | | | | | | | | | | | | These flags were added to help with the high linking cost of the old split-objs mode. Now we are using split-sections these flags appear to make no difference to memory usage or time taken to link. I tested various configurations linking together the ghc library with -split-sections enabled. | linker | time (s) | | ------ | ------ | | gold | 0.95 | | ld | 1.6 | | ld (hash-size = 31, reduce-memory-overheads) | 1.6 | | ldd | 0.47 | Fixes #20967
* CLabel cleanup:Andreas Klebinger2022-02-285-28/+11
| | | | | | | | Remove these smart constructors for these reasons: * mkLocalClosureTableLabel : Does the same as the non-local variant. * mkLocalClosureLabel : Does the same as the non-local variant. * mkLocalInfoTableLabel : Decide if we make a local label based on the name and just use mkInfoTableLabel everywhere.
* hadrian: Suggest to the user to run ./configure if missing a settingMatthew Pickering2022-02-285-24/+31
| | | | | | | If a setting is missing from the configuration file it's likely the user needs to reconfigure. Fixes #20476
* Fix some hlint issues in ghc-heapSven Tennie2022-02-282-7/+4
| | | | | This does not fix all hlint issues as the criticised index and length expressions seem to be fine in context.
* Make modules in base stable.Hécate Moonlight2022-02-2863-63/+63
| | | | fix #18963
* Add Monoid a => Monoid (STM a) instanceOleg Grenrus2022-02-281-0/+8
|
* testsuite: Require LLVM for T15155lPeter Trommler2022-02-263-1/+4
|
* Core Lint: ensure primops can be eta-expandedsheaf2022-02-2613-31/+396
| | | | | | | | | | | | | | | | | | | This patch adds a check to Core Lint, checkCanEtaExpand, which ensures that primops and other wired-in functions with no binding such as unsafeCoerce#, oneShot, rightSection... can always be eta-expanded, by checking that the remaining argument types have a fixed RuntimeRep. Two subtleties came up: - the notion of arity in Core looks through newtypes, so we may need to unwrap newtypes in this check, - we want to avoid calling hasNoBinding on something whose unfolding we are in the process of linting, as this would cause a loop; to avoid this we add some information to the Core Lint environment that holds this information. Fixes #20480
* Error on anon wildcards in tcAnonWildCardOccsheaf2022-02-2618-122/+305
| | | | | | | | | | | | | | | | | The code in tcAnonWildCardOcc assumed that it could never encounter anonymous wildcards in illegal positions, because the renamer would have ruled them out. However, it's possible to sneak past the checks in the renamer by using Template Haskell. It isn't possible to simply pass on additional information when renaming Template Haskell brackets, because we don't know in advance in what context the bracket will be spliced in (see test case T15433b). So we accept that we might encounter these bogus wildcards in the typechecker and throw the appropriate error. This patch also migrates the error messages for illegal wildcards in types to use the diagnostic infrastructure. Fixes #15433
* Improve efficiency of extending a RuleEnv with a new RuleBaseMatthew Pickering2022-02-264-14/+35
| | | | | | | | | | | | | Essentially we apply the identity: > lookupNameEnv n (plusNameEnv_C (++) rb1 rb2) > = lookupNameEnv n rb1 ++ lookupNameEnv n rb2 The latter being more efficient as we don't construct an intermediate map. This is now quite important as each time we try and apply rules we need to combine the current EPS RuleBase with the HPT and ModGuts rule bases.
* Use a more up-to-date snapshot of the current rules in the simplifierMatthew Pickering2022-02-264-22/+37
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As the prescient (now deleted) note warns in simplifyPgmIO we have to be a bit careful about when we gather rules from the EPS so that we get the rules for imported bindings. ``` -- Get any new rules, and extend the rule base -- See Note [Overall plumbing for rules] in GHC.Core.Rules -- We need to do this regularly, because simplification can -- poke on IdInfo thunks, which in turn brings in new rules -- behind the scenes. Otherwise there's a danger we'll simply -- miss the rules for Ids hidden inside imported inlinings ``` Given the previous commit, the loading of unfoldings is now even more delayed so we need to be more careful to read the EPS rule base closer to the point where we decide to try rules. Without this fix GHC performance regressed by a noticeably amount because the `zip` rule was not brought into scope eagerly enough which led to a further series of unfortunate events in the simplifer which tipped `substTyWithCoVars` over the edge of the size threshold, stopped it being inlined and increased allocations by 10% in some cases. Furthermore, this change is noticeably in the testsuite as it changes T19790 so that the `length` rules from GHC.List fires earlier. ------------------------- Metric Increase: T9961 -------------------------
* Make typechecking unfoldings from interfaces lazierMatthew Pickering2022-02-262-44/+48
| | | | | | | | | | | | | The old logic was unecessarily strict in loading unfoldings because when reading the unfolding we would case on the result of attempting to load the template before commiting to which type of unfolding we were producing. Hence trying to inspect any of the information about an unfolding would force the template to be loaded. This also removes a potentially hard to discover bug where if the template failed to be typechecked for some reason then we would just not return an unfolding. Instead we now panic so these bad situations which should never arise can be identified.
* base: Improve documentation of `throwIO` (#19854)Sebastian Graf2022-02-251-4/+22
| | | | | | Now it takes a better account of precise vs. imprecise exception semantics. Fixes #19854.
* Derive Enum instances for CCallConv and SafetySylvain Henry2022-02-251-4/+9
| | | | This is used by the JS backend for serialization.
* Allow hscGenHardCode to not return CgInfosSylvain Henry2022-02-252-4/+4
| | | | | This is a minor change in preparation for the JS backend: CgInfos aren't mandatory and the JS backend won't return them.
* Testsuite: remove arch conditional in T8832Sylvain Henry2022-02-255-25/+5
| | | | Taken from !3658
* Allow qualified names in COMPLETE pragmassheaf2022-02-253-2/+22
| | | | | | | The parser didn't allow qualified constructor names to appear in COMPLETE pragmas. This patch fixes that. Fixes #20551
* Add test for #19271nineonine2022-02-253-1/+21
|
* Derive some stock instances for OverridingBoolsheaf2022-02-251-3/+10
| | | | | | | | | This patch adds some derived instances to `GHC.Data.Bool.OverridingBool`. It also changes the order of the constructors, so that the derived `Ord` instance matches the behaviour for `Maybe Bool`. Fixes #20326
* simplCore: Correctly extend in-scope set in rule matchingBen Gamari2022-02-251-25/+47
| | | | | | | | | | | | | | | | | | Note [Matching lets] in GHC.Core.Rules claims the following: > We use GHC.Core.Subst.substBind to freshen the binding, using an > in-scope set that is the original in-scope variables plus the > rs_bndrs (currently floated let-bindings). However, previously the implementation didn't actually do extend the in-scope set with rs_bndrs. This appears to be a regression which was introduced by 4ff4d434e9a90623afce00b43e2a5a1ccbdb4c05. Moreover, the originally reasoning was subtly wrong: we must rather use the in-scope set from rv_lcl, extended with rs_bndrs, not that of `rv_fltR` Fixes #21122.
* Fix comment reference to T4818Ben Gamari2022-02-251-1/+2
|
* Ticky: Gate tag-inference dummy ticky-counters behind a flag.Andreas Klebinger2022-02-258-7/+39
| | | | | | | | | | Tag inference included a way to collect stats about avoided tag-checks. This was dony by emitting "dummy" ticky entries with counts corresponding to predicted/unpredicated tag checks. This behaviour for ticky is now gated behind -fticky-tag-checks. I also documented ticky-LNE in the process.
* rts/adjustor: Always place adjustor templates in data sectionBen Gamari2022-02-251-4/+8
| | | | | | @nrnrnr points out that on his machine ld.lld rejects text relocations. Generalize the Darwin text-relocation avoidance logic to account for this.
* GHCi: don't normalise partially instantiated typessheaf2022-02-256-8/+56
| | | | | | | | | This patch skips performing type normalisation when we haven't fully instantiated the type. That is, in tcRnExpr (used only for :type in GHCi), skip normalisation if the result type responds True to isSigmaTy. Fixes #20974
* template-haskell: Fix two prettyprinter issuesMario Blažević2022-02-254-8/+80
| | | | | | Fix two issues regarding printing numeric literals. Fixing #20454.
* Remove test-bootstrap and cabal-reinstall jobs from fast-ci [skip ci]wip/fast-ci-fixesMatthew Pickering2022-02-251-0/+9
|
* ghci: show helpful error message when loading module with SIMD vector ↵nineonine2022-02-246-0/+17
| | | | | | | operations (#20214) Previously, when trying to load module with SIMD vector operations, ghci would panic in 'GHC.StgToByteCode.findPushSeq'. Now, a more helpful message is displayed.
* Suggestions due to hlintMatthew Pickering2022-02-2432-56/+22
| | | | | It turns out this job hasn't been running for quite a while (perhaps ever) so there are quite a few failures when running the linter locally.
* Add rule for generating HsBaseConfig.hMatthew Pickering2022-02-241-8/+9
| | | | | | If you are running the `lint:{base/compiler}` command locally then this improves the responsiveness because we don't re-run configure everytime if the header file already exists.
* Move linters into the treeMatthew Pickering2022-02-2442-163/+1166
| | | | | | | | | | This MR moves the GHC linters into the tree, so that they can be run directly using Hadrian. * Query all files tracked by Git instead of using changed files, so that we can run the exact same linting step locally and in a merge request. * Only check that the changelogs don't contain TBA when RELEASE=YES. * Add hadrian/lint script, which runs all the linting steps. * Ensure the hlint job exits with a failure if hlint is not installed (otherwise we were ignoring the failure). Given that hlint doesn't seem to be available in CI at the moment, I've temporarily allowed failure in the hlint job. * Run all linting tests in CI using hadrian.
* TH: fix pretty printing of GADTs with multiple constuctors (#20842)Zubin Duggal2022-02-245-2/+16
|
* Clarify laws of TestEqualityJohn Ericson2022-02-241-2/+16
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | It is unclear what `TestEquality` is for. There are 3 possible choices. Assuming ```haskell data Tag a where TagInt1 :: Tag Int TagInt2 :: Tag Int ``` Weakest -- type param equality semi-decidable --------------------------------------------- `Just Refl` merely means the type params are equal, the values being compared might not be. `Nothing` means the type params may or may not be not equal. ```haskell instance TestEquality Tag where testEquality TagInt1 TagInt1 = Nothing -- oopsie is allowed testEquality TagInt1 TagInt2 = Just Refl testEquality TagInt2 TagInt1 = Just Refl testEquality TagInt2 TagInt2 = Just Refl ``` This option is better demonstrated with a different type: ```haskell data Tag' a where TagInt1 :: Tag Int TagInt2 :: Tag a ``` ```haskell instance TestEquality Tag' where testEquality TagInt1 TagInt1 = Just Refl testEquality TagInt1 TagInt2 = Nothing -- can't be sure testEquality TagInt2 TagInt1 = Nothing -- can't be sure testEquality TagInt2 TagInt2 = Nothing -- can't be sure ``` Weaker -- type param equality decidable --------------------------------------- `Just Refl` merely means the type params are equal, the values being compared might not be. `Nothing` means the type params are not equal. ```haskell instance TestEquality Tag where testEquality TagInt1 TagInt1 = Just Refl testEquality TagInt1 TagInt2 = Just Refl testEquality TagInt2 TagInt1 = Just Refl testEquality TagInt2 TagInt2 = Just Refl ``` Strong -- Like `Eq` ------------------- `Just Refl` means the type params are equal, and the values are equal according to `Eq`. ```haskell instance TestEquality Tag where testEquality TagInt1 TagInt1 = Just Refl testEquality TagInt2 TagInt2 = Just Refl testEquality _ _ = Nothing ``` Strongest -- unique value concrete type --------------------------------------- `Just Refl` means the type params are equal, and the values are equal, and the class assume if the type params are equal the values must also be equal. In other words, the type is a singleton type when the type parameter is a closed term. ```haskell -- instance TestEquality -- invalid instance because two variants for `Int` ``` ------ The discussion in https://github.com/haskell/core-libraries-committee/issues/21 has decided on the "Weaker" option (confusingly formerly called the "Weakest" option). So that is what is implemented.
* Allow `return` in more cases in ApplicativeDoZiyang Liu2022-02-244-18/+88
| | | | | | | | | | | | | | | | | | | | | | | | | | | | The doc says that the last statement of an ado-block can be one of `return E`, `return $ E`, `pure E` and `pure $ E`. But `return` is not accepted in a few cases such as: ```haskell -- The ado-block only has one statement x :: F () x = do return () -- The ado-block only has let-statements besides the `return` y :: F () y = do let a = True return () ``` These currently require `Monad` instances. This MR fixes it. Normally `return` is accepted as the last statement because it is stripped in constructing an `ApplicativeStmt`, but this cannot be done in the above cases, so instead we replace `return` by `pure`. A similar but different issue (when the ado-block contains `BindStmt` or `BodyStmt`, the second last statement cannot be `LetStmt`, even if the last statement uses `pure`) is fixed in !6786.
* testsuite: Fix ipeMap testPeter Trommler2022-02-231-21/+21
| | | | | | | Pointers to closures must be untagged before use. Produce closures of different types so we get different info tables. Fixes #21112
* testsuite: Normalise output of ghci011 and T7627Matthew Pickering2022-02-231-2/+7
| | | | | | | | The outputs of these tests vary on the order interface files are loaded so we normalise the output to correct for these inconsequential differences. Fixes #21121
* driver: Remove needsTemplateHaskellOrQQ from ModuleGraphMatthew Pickering2022-02-2311-88/+114
| | | | | | | | | | | | | | | | | | | | | | | | | The idea of the needsTemplateHaskellOrQQ query is to check if any of the modules in a module graph need Template Haskell then enable -dynamic-too if necessary. This is quite imprecise though as it will enable -dynamic-too for all modules in the module graph even if only one module uses template haskell, with multiple home units, this is obviously even worse. With -fno-code we already have similar logic to enable code generation just for the modules which are dependeded on my TemplateHaskell modules so we use the same code path to decide whether to enable -dynamic-too rather than using this big hammer. This is part of the larger overall goal of moving as much statically known configuration into the downsweep as possible in order to have fully decided the build plan and all the options before starting to build anything. I also included a fix to #21095, a long standing bug with with the logic which is supposed to enable the external interpreter if we don't have the internal interpreter. Fixes #20696 #21095
* Remove mg_boot field from ModuleGraphMatthew Pickering2022-02-231-11/+1
| | | | | It was unused in the compiler so I have removed it to streamline ModuleGraph.
* Simplify/correct implementation of getModuleInfoMatthew Pickering2022-02-231-12/+3
|
* NCG: inline some 64-bit primops on x86/32-bit (#5444)Sylvain Henry2022-02-234-41/+272
| | | | | | | | Several 64-bit operation were implemented with FFI calls on 32-bit architectures but we can easily implement them with inline assembly code. Also remove unused hs_int64ToWord64 and hs_word64ToInt64 C functions.
* NCG: refactor the way registers are handledSylvain Henry2022-02-233-269/+229
| | | | | | | | | | | | * add getLocalRegReg to avoid allocating a CmmLocal just to call getRegisterReg * 64-bit registers: in the general case we must always use the virtual higher part of the register, so we might as well always return it with the lower part. The only exception is to implement 64-bit to 32-bit conversions. We now have to explicitly discard the higher part when matching on Reg64/RegCode64 datatypes instead of explicitly fetching the higher part from the lower part: much safer default.
* NCG: refactor X86 codegenSylvain Henry2022-02-231-932/+1054
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Preliminary work done to make working on #5444 easier. Mostly make make control-flow easier to follow: * renamed genCCall into genForeignCall * split genForeignCall into the part dispatching on PrimTarget (genPrim) and the one really generating code for a C call (cf ForeignTarget and genCCall) * made genPrim/genSimplePrim only dispatch on MachOp: each MachOp now has its own code generation function. * out-of-line primops are not handled in a partial `outOfLineCmmOp` anymore but in the code generation functions directly. Helper functions have been introduced (e.g. genLibCCall) for code sharing. * the latter two bullets make code generated for primops that are only sometimes out-of-line (e.g. Pdep or Memcpy) and the logic to select between inline/out-of-line much more localized * avoided passing is32bit as an argument as we can easily get it from NatM state when we really need it * changed genCCall type to avoid it being partial (it can't handle PrimTarget) * globally removed 12 calls to `panic` thanks to better control flow and types ("parse, don't validate" ftw!).
* Introduce `MaybeValidated` type to remove invalid statesJohn Ericson2022-02-232-63/+88
| | | | | | | | | | | | | | | | | | The old return type `(RecompRequired, Maybe _)`, was confusing because it was inhabited by values like `(UpToDate, Nothing)` that made no sense. The new type ensures: - you must provide a value if it is up to date. - you must provide a reason if you don't provide a value. it is used as the return value of: - `checkOldIface` - `checkByteCode` - `checkObjects`