summaryrefslogtreecommitdiff
path: root/compiler
Commit message (Collapse)AuthorAgeFilesLines
...
* Fix comment reference to T4818Ben Gamari2022-02-251-1/+2
|
* Ticky: Gate tag-inference dummy ticky-counters behind a flag.Andreas Klebinger2022-02-256-6/+14
| | | | | | | | | | 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.
* GHCi: don't normalise partially instantiated typessheaf2022-02-251-7/+30
| | | | | | | | | 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
* ghci: show helpful error message when loading module with SIMD vector ↵nineonine2022-02-242-0/+4
| | | | | | | 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-2427-49/+19
| | | | | 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.
* Allow `return` in more cases in ApplicativeDoZiyang Liu2022-02-241-17/+65
| | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* driver: Remove needsTemplateHaskellOrQQ from ModuleGraphMatthew Pickering2022-02-234-88/+89
| | | | | | | | | | | | | | | | | | | | | | | | | 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-232-37/+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`
* Prepare rechecking logic for new type in a few waysJohn Ericson2022-02-235-117/+129
| | | | | | | | | | | | Combine `MustCompile and `NeedsCompile` into a single case. `CompileReason` is put inside to destinguish the two. This makes a number of things easier. `Semigroup RecompileRequired` is no longer used, to make sure we skip doing work where possible. `recompThen` is very similar, but helps remember. `checkList` is rewritten with `recompThen`.
* Don't emit foreign exports initialiser code for empty CAF listCheng Shao2022-02-231-0/+1
|
* Use SrcSpan from the binder as initial source estimateMatthew Pickering2022-02-231-1/+8
| | | | | | | | | | | | There are some situations where we end up with no source notes in useful positions in an expression. In this case we currently fail to provide any source information about where an expression came from. This patch improves the initial estimate by using the position from the top-binder as the guess for the location of the whole inner expression. It provides quite a course estimate but it's better than nothing. Ticket #20847
* Introduce predicate for when to enable source notes (needSourceNotes)Matthew Pickering2022-02-234-8/+10
| | | | | | | | There were situations where we were using debugLevel == 0 as a proxy for whether to retain source notes but -finfo-table-map also enables and needs source notes so we should act consistently in both cases. Ticket #20847
* Kill derived constraintsRichard Eisenberg2022-02-2354-3080/+2999
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Co-authored by: Sam Derbyshire Previously, GHC had three flavours of constraint: Wanted, Given, and Derived. This removes Derived constraints. Though serving a number of purposes, the most important role of Derived constraints was to enable better error messages. This job has been taken over by the new RewriterSets, as explained in Note [Wanteds rewrite wanteds] in GHC.Tc.Types.Constraint. Other knock-on effects: - Various new Notes as I learned about under-described bits of GHC - A reshuffling around the AST for implicit-parameter bindings, with better integration with TTG. - Various improvements around fundeps. These were caused by the fact that, previously, fundep constraints were all Derived, and Derived constraints would get dropped. Thus, an unsolved Derived didn't stop compilation. Without Derived, this is no longer possible, and so we have to be considerably more careful around fundeps. - A nice little refactoring in GHC.Tc.Errors to center the work on a new datatype called ErrorItem. Constraints are converted into ErrorItems at the start of processing, and this allows for a little preprocessing before the main classification. - This commit also cleans up the behavior in generalisation around functional dependencies. Now, if a variable is determined by functional dependencies, it will not be quantified. This change is user facing, but it should trim down GHC's strange behavior around fundeps. - Previously, reportWanteds did quite a bit of work, even on an empty WantedConstraints. This commit adds a fast path. - Now, GHC will unconditionally re-simplify constraints during quantification. See Note [Unconditionally resimplify constraints when quantifying], in GHC.Tc.Solver. Close #18398. Close #18406. Solve the fundep-related non-confluence in #18851. Close #19131. Close #19137. Close #20922. Close #20668. Close #19665. ------------------------- Metric Decrease: LargeRecord T9872b T9872b_defer T9872d TcPlugin_RewritePerf -------------------------
* Remove -Wunticked-promoted-constructors from -WallKrzysztof Gogolewski2022-02-222-2/+1
| | | | | | | Update manual; explain ticks as optional disambiguation rather than the preferred default. This is a part of #20531.
* Forbid standalone instances for built-in classessheaf2022-02-221-14/+23
| | | | | | | | | | | | | | | | `check_special_inst_head` includes logic that disallows hand-written instances for built-in classes such as Typeable, KnownNat and KnownSymbol. However, it also allowed standalone deriving declarations. This was because we do want to allow standalone deriving instances with Typeable as they are harmless, but we certainly don't want to allow instances for e.g. KnownNat. This patch ensures that we don't allow derived instances for KnownNat, KnownSymbol (and also KnownChar, which was previously omitted entirely). Fixes #21087
* Reinstallable GHCZubin Duggal2022-02-213-3/+158
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch allows ghc and its dependencies to be built using a normal invocation of cabal-install. Each componenent which relied on generated files or additional configuration now has a Setup.hs file. There are also various fixes to the cabal files to satisfy cabal-install. There is a new hadrian command which will build a stage2 compiler and then a stage3 compiler by using cabal. ``` ./hadrian/build build-cabal ``` There is also a new CI job which tests running this command. For the 9.4 release we will upload all the dependent executables to hackage and then end users will be free to build GHC and GHC executables via cabal. There are still some unresolved questions about how to ensure soundness when loading plugins into a reinstalled GHC (#20742) which will be tighted up in due course. Fixes #19896
* Bump time submodule to 1.12.1Ben Gamari2022-02-201-1/+1
|
* Use diagnostics for "missing signature" errorssheaf2022-02-205-219/+334
| | | | | | | | | | | | This patch makes the "missing signature" errors from "GHC.Rename.Names" use the diagnostic infrastructure. This encompasses missing type signatures for top-level bindings and pattern synonyms, as well as missing kind signatures for type constructors. This patch also renames TcReportMsg to TcSolverReportMsg, and adds a few convenience functions to compute whether such a TcSolverReportMsg is an expected/actual message.
* Track object file dependencies for TH accurately (#20604)Zubin Duggal2022-02-2021-198/+299
| | | | | | | | | | | | | | | | | | | `hscCompileCoreExprHook` is changed to return a list of `Module`s required by a splice. These modules are accumulated in the TcGblEnv (tcg_th_needed_mods). Dependencies on the object files of these modules are recording in the interface. The data structures in `LoaderState` are replaced with more efficient versions to keep track of all the information required. The MultiLayerModulesTH_Make allocations increase slightly but runtime is faster. Fixes #20604 ------------------------- Metric Increase: MultiLayerModulesTH_Make -------------------------
* ghci: fix -ddump-stg-cg (#21052)nineonine2022-02-161-3/+3
| | | | | The pre-codegen Stg AST dump was not available in ghci because it was performed in 'doCodeGen'. This was now moved to 'coreToStg' area.
* Tag inference work.Andreas Klebinger2022-02-1263-278/+2909
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This does three major things: * Enforce the invariant that all strict fields must contain tagged pointers. * Try to predict the tag on bindings in order to omit tag checks. * Allows functions to pass arguments unlifted (call-by-value). The former is "simply" achieved by wrapping any constructor allocations with a case which will evaluate the respective strict bindings. The prediction is done by a new data flow analysis based on the STG representation of a program. This also helps us to avoid generating redudant cases for the above invariant. StrictWorkers are created by W/W directly and SpecConstr indirectly. See the Note [Strict Worker Ids] Other minor changes: * Add StgUtil module containing a few functions needed by, but not specific to the tag analysis. ------------------------- Metric Decrease: T12545 T18698b T18140 T18923 LargeRecord Metric Increase: LargeRecord ManyAlternatives ManyConstructors T10421 T12425 T12707 T13035 T13056 T13253 T13253-spj T13379 T15164 T18282 T18304 T18698a T1969 T20049 T3294 T4801 T5321FD T5321Fun T783 T9233 T9675 T9961 T19695 WWRec -------------------------
* Refine tcSemigroupWarnings to work in ghc-primMatthew Pickering2022-02-101-4/+7
| | | | | | | | | | | | | ghc-prim doesn't depend on base so can't have any Monoid or Semigroup instances. However, attempting to load these definitions ran into issues when the interface for `GHC.Base` did exist as that would try and load the interface for `GHC.Types` (which is the module we are trying to compile and has no interface). The fix is to just not do this check when we are compiling a module in ghc-prim. Fixes #21069
* Add late cost centre supportAndreas Klebinger2022-02-1012-6/+117
| | | | | This allows cost centres to be inserted after the core optimization pipeline has run.
* Include ru_name in toHsRule messageZiyang Liu2022-02-092-11/+9
| | | | See #18147
* ByteCode: avoid out-of-bound readSylvain Henry2022-02-091-5/+15
| | | | Cf https://gitlab.haskell.org/ghc/ghc/-/issues/18431#note_287139
* NCG: minor code factorizationSylvain Henry2022-02-092-51/+35
|
* driver: Filter out our own boot module in hptSomeThingsBelowMatthew Pickering2022-02-091-2/+5
| | | | | | | | | hptSomeThingsBelow would return a list of modules which contain the .hs-boot file for a particular module. This caused some problems because we would try and find the module in the HPT (but it's not there when we're compiling the module itself). Fixes #21058
* Rename -merge-objs flag to --merge-objsBen Gamari2022-02-091-1/+1
| | | | For consistency with --make and friends.
* Look through untyped TH splices in tcInferAppHead_maybeRyan Scott2022-02-092-13/+26
| | | | | | | | | | | Previously, surrounding a head expression with a TH splice would defeat `tcInferAppHead_maybe`, preventing some expressions from typechecking that used to typecheck in previous GHC versions (see #21038 for examples). This is simple enough to fix: just look through `HsSpliceE`s in `tcInferAppHead_maybe`. I've added some additional prose to `Note [Application chains and heads]` in `GHC.Tc.Gen.App` to accompany this change. Fixes #21038.
* StgToCmm: Get rid of GHC.Driver.Session importsJohn Ericson2022-02-087-38/+39
| | | | | `DynFlags` is gone, but let's move a few trivial things around to get rid of its module too.
* Document `hscIncrementalFrontend` and flip boolCale Gibbard2022-02-081-10/+21
|
* `hscSimpleIface` drop fingerprint param and retCale Gibbard2022-02-081-12/+10
| | | | | | | | | `hscSimpleIface` does not depend on or modify the `Maybe Fingerprint` it is given, only passes it through, so get rid of the extraneous passing. Perhaps the intent was that there would be an iface fingerprint check of some sort? but this was never done. If/when we we want to do that, we can add it back then.
* Fix some notesMatthew Pickering2022-02-0847-72/+70
|
* Relax TyEq:N: allow out-of-scope newtype DataConsheaf2022-02-081-8/+20
| | | | | | | | | | The 'bad_newtype' assertion in GHC.Tc.Solver.Canonical.canEqCanLHSFinish failed to account for the possibility that the newtype constructor might not be in scope, in which case we don't provide any guarantees about canonicalising away a newtype on the RHS of a representational equality. Fixes #21010
* Allow HasField in quantified constraintssheaf2022-02-081-0/+4
| | | | | | | | | | | | | | | | | | | | We perform validity checking on user-written HasField instances, for example to disallow: data Foo a = Foo { fld :: Int } instance HasField "fld" (Foo a) Bool However, these checks were also being made on quantified constraints, e.g. data Bar where Bar :: (forall a. HasField s (Foo a) Int) => Proxy s -> Bar This patch simply skips validity checking for quantified constraints, in line with what we already do for equality constraints such as Coercible. Fixes #20989
* Create `CoverageConfig`John Ericson2022-02-072-7/+27
| | | | | As requested by @mpickering to collect the information we project from `HscEnv`
* GHC.HsToCore.Coverage: No more HscEnv, less DynFlagsJohn Ericson2022-02-072-33/+31
| | | | Progress towards #20730
* Purge DynFlags from GHC.StgJohn Ericson2022-02-0618-89/+210
| | | | | Also derive some more instances. GHC doesn't need them, but downstream consumers may need to e.g. put stuff in maps.
* Make implication tidying agree with Note [Tidying multiple names at once]Matthew Pickering2022-02-051-2/+2
| | | | | | | | | | | Note [Tidying multiple names at once] indicates that if multiple variables have the same name then we shouldn't prioritise one of them and instead rename them all to a1, a2, a3... etc This patch implements that change, some error message changes as expected. Closes #20932
* Improve errors for non-existent labelsSimon Peyton Jones2022-02-046-41/+36
| | | | | | | | | | | | | | | | This patch fixes #17469, by improving matters when you use non-existent field names in a record construction: data T = MkT { x :: Int } f v = MkT { y = 3 } The check is now made in the renamer, in GHC.Rename.Env.lookupRecFieldOcc. That in turn led to a spurious error in T9975a, which is fixed by making GHC.Rename.Names.extendGlobalRdrEnvRn fail fast if it finds duplicate bindings. See Note [Fail fast on duplicate definitions] in that module for more details. This patch was originated and worked on by Alex D (@nineonine)
* Add a missing restoreLclEnvSimon Peyton Jones2022-02-041-2/+2
| | | | | | | | | | | | | | The commit commit 18df4013f6eaee0e1de8ebd533f7e96c4ee0ff04 Date: Sat Jan 22 01:12:30 2022 +0000 Define and use restoreLclEnv omitted to change one setLclEnv to restoreLclEnv, namely the one in GHC.Tc.Errors.warnRedundantConstraints. This new commit fixes the omission.
* Add Outputable instance for MessagesSimon Peyton Jones2022-02-041-2/+11
| | | | c.f. #20980
* Fix unsound behavior of unlifted datatypes in ghci (#20194)nineonine2022-02-041-19/+34
| | | | | | | | | | | | Previously, directly calling a function that pattern matches on an unlifted data type which has at least two constructors in GHCi resulted in a segfault. This happened due to unaccounted return frame info table pointer. The fix is to pop the above mentioned frame info table pointer when unlifted things are returned. See Note [Popping return frame for unlifted things] authors: bgamari, nineonine
* primops: Fix documentation of setByteArray#Ben Gamari2022-02-041-1/+1
| | | | | | Previously the documentation was subtly incorrect regarding the bounds of the operation. Fix this and add a test asserting that a zero-length operation is in fact a no-op.
* llvmGen: Handle unaligned loads/storesBen Gamari2022-02-041-7/+7
| | | | | This allows us to produce valid code for indexWord8ArrayAs*# on platforms that lack unaligned memory access.