- 04 Jan, 2020 1 commit
-
-
Sylvain Henry authored
* stgToCmm hook * cmmToRawCmm hook These hooks are used by Asterius and could be useful to other clients of the GHC API. It increases the Parser dependencies (test CountParserDeps) to 184. It's still less than 200 which was the initial request (cf https://mail.haskell.org/pipermail/ghc-devs/2019-September/018122.html) so I think it's ok to merge this.
-
- 01 Jan, 2020 1 commit
-
-
Ömer Sinan Ağacan authored
When dumping Cmm groups check if the group is empty, to avoid generating empty sections in dump files like ==================== Output Cmm ==================== [] Also fixes a few bad indentation in the code around changes.
-
- 31 Dec, 2019 1 commit
-
-
Sylvain Henry authored
-
- 18 Dec, 2019 1 commit
-
-
Sylvain Henry authored
* Add 'dumpAction' hook to DynFlags. It allows GHC API users to catch dumped intermediate codes and information. The format of the dump (Core, Stg, raw text, etc.) is now reported allowing easier automatic handling. * Add 'traceAction' hook to DynFlags. Some dumps go through the trace mechanism (for instance unfoldings that have been considered for inlining). This is problematic because: 1) dumps aren't written into files even with -ddump-to-file on 2) dumps are written on stdout even with GHC API 3) in this specific case, dumping depends on unsafe globally stored DynFlags which is bad for GHC API users We introduce 'traceAction' hook which allows GHC API to catch those traces and to avoid using globally stored DynFlags. * Avoid dumping empty logs via dumpAction/traceAction (but still write empty files to keep the existing behavior)
-
- 29 Nov, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
(Partial) ModIface and ModDetails are generated at the same time, but they're passed differently: ModIface is passed in HscStatus consturctors while ModDetails is returned in a tuple. This refactors ModDetails passing so that it's passed around with ModIface in HscStatus constructors. This makes the code more consistent and hopefully easier to understand: ModIface and ModDetails are really very closely related. It makes sense to treat them the same way.
-
- 13 Nov, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
HscRecomp users only need the ModLocation of the module being compiled, so only pass that to users instead of the entire ModSummary Metric Decrease: T4801
-
- 29 Oct, 2019 4 commits
-
-
Ömer Sinan Ağacan authored
-
Ömer Sinan Ağacan authored
-
Ömer Sinan Ağacan authored
The compilation phases now optionally return ModIface (for phases that generate an interface, currently only HscOut when (re)compiling a file). The value is then used by compileOne' to return the generated interface with HomeModInfo (which is then used by the batch mode compiler when building rest of the tree). hscIncrementalMode also returns a DynFlags with plugin info, to be used in the rest of the pipeline. Unfortunately this introduces a (perhaps less bad) hack in place of the previous IORef: we now record the DynFlags used to generate the partial infterface in HscRecomp and use the same DynFlags when generating the full interface. I spent almost three days trying to understand what's changing in DynFlags that causes a backpack test to fail, but I couldn't figure it out. There's a FIXME added next to the field so hopefully someone who understands this better than I do will fix it leter.
-
Ömer Sinan Ağacan authored
Make it evident in the constructors that the final interface is only available when HscStatus is not HscRecomp. (When HscStatus == HscRecomp we need to finish the compilation to get the final interface) `Maybe ModIface` return value of hscIncrementalCompile and the partial `expectIface` function are removed.
-
- 23 Oct, 2019 2 commits
-
-
Ömer Sinan Ağacan authored
Previously -ddump-stg would dump pre and post-unarise STGs. Now we have a new flag for post-unarise STG and -ddump-stg only dumps coreToStg output. STG dump flags after this commit: - -ddump-stg: Dumps CoreToStg output - -ddump-stg-unarised: Unarise output - -ddump-stg-final: STG right before code gen (includes CSE and lambda lifting)
-
Andreas Klebinger authored
19 times out of 20 we already have dynflags in scope. We could just always use `return dflags`. But this is in fact not free. When looking at some STG code I noticed that we always allocate a closure for this expression in the heap. Clearly a waste in these cases. For the other cases we can either just modify the callsite to get dynflags or use the _D variants of withTiming I added which will use getDynFlags under the hood.
-
- 01 Oct, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
This commit refactors interface file generation to allow information from the later passed (NCG, STG) to be stored in interface files. We achieve this by splitting interface file generation into two parts: * Partial interfaces, built based on the result of the core pipeline * A fully instantiated interface, which also contains the final fingerprints and can optionally contain information produced by the backend. This change is required by !1304 and !1530. -dynamic-too handling is refactored too: previously when generating code we'd branch on -dynamic-too *before* code generation, but now we do it after. (Original code written by @AndreasK in !1530) Performance ~~~~~~~~~~~ Before this patch interface files where created and immediately flushed to disk which made space leaks impossible. With this change we instead use NFData to force all iface related data structures to avoid space leaks. In the process of refactoring it was discovered that the code in the ToIface Module allocated a lot of thunks which were immediately forced when writing/forcing the interface file. So we made this module more strict to avoid creating many of those thunks. Bottom line is that allocations go down by about ~0.1% compared to master. Residency is not meaningfully different after this patch. Runtime was not benchmarked. Co-Authored-By:
Andreas Klebinger <klebinger.andreas@gmx.at> Co-Authored-By:
Ömer Sinan Ağacan <omer@well-typed.com>
-
- 20 Sep, 2019 1 commit
-
-
Sylvain Henry authored
Add GHC.Hs module hierarchy replacing hsSyn. Metric Increase: haddock.compiler
-
- 09 Sep, 2019 1 commit
-
-
Sylvain Henry authored
Add StgToCmm module hierarchy. Platform modules that are used in several other places (NCG, LLVM codegen, Cmm transformations) are put into GHC.Platform.
-
- 28 Aug, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
This generalizes code generators (outputAsm, outputLlvm, outputC, and the call site codeOutput) so that they'll return the return values of the passed Cmm streams. This allows accumulating data during Cmm generation and returning it to the call site in HscMain. Previously the Cmm streams were assumed to return (), so the code generators returned () as well. This change is required by !1304 and !1530. Skipping CI as this was tested before and I only updated the commit message. [skip ci]
-
- 23 Aug, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
Previously we were using an empty ModuleSRTInfo for each Cmm group with -split-section. As far as I can see this has no benefits, and simplifying this makes another patch simpler (!1304). We also remove some outdated comments: we no longer generate one module-level SRT.
-
- 07 Aug, 2019 1 commit
-
-
wz1000 authored
-
- 26 Jul, 2019 1 commit
-
-
Alex D authored
Change behaviour of -ddump-cmm-verbose to dump each Cmm pass output to a separate file and add -ddump-cmm-verbose-by-proc to keep old behaviour (#16930)
-
- 09 Jul, 2019 1 commit
-
-
Ryan Scott authored
To avoid having to `panic` any time a TTG extension constructor is consumed, this MR introduces an uninhabited 'NoExtCon' type and uses that in every extension constructor's type family instance where it is appropriate. This also introduces a 'noExtCon' function which eliminates a 'NoExtCon', much like 'Data.Void.absurd' eliminates a 'Void'. I also renamed the existing `NoExt` type to `NoExtField` to better distinguish it from `NoExtCon`. Unsurprisingly, there is a lot of code churn resulting from this. Bumps the Haddock submodule. Fixes #15247.
-
- 26 Jun, 2019 2 commits
-
-
Oleg Grenrus authored
-
Oleg Grenrus authored
This commit partly reverts e69619e9 commit by reintroducing Sf_SafeInferred SafeHaskellMode. We preserve whether module was declared or inferred Safe. When declared-Safe module imports inferred-Safe, we warn. This inferred status is volatile, often enough it's a happy coincidence, something which cannot be relied upon. However, explicitly Safe or Trustworthy packages won't accidentally become Unsafe. Updates haddock submodule.
-
- 20 Jun, 2019 1 commit
-
-
John Ericson authored
ghc-pkg needs to be aware of platforms so it can figure out which subdire within the user package db to use. This is admittedly roundabout, but maybe Cabal could use the same notion of a platform as GHC to good affect too.
-
- 18 Jun, 2019 1 commit
-
-
Ben Gamari authored
Fixes #16689.
-
- 04 Jun, 2019 1 commit
-
-
xldenis authored
This commit adds the `:instances` command to ghci following proosal number 41. This makes it possible to query which instances are available to a given type. The output of this command is all the possible instances with type variables and constraints instantiated.
-
- 31 May, 2019 1 commit
-
-
wz1000 authored
Implements #16686 The files version is automatically generated from the current GHC version in the same manner as normal interface files. This means that clients can first read the version and then decide how to read the rest of the file.
-
- 22 May, 2019 1 commit
-
-
Julian Leviston authored
-
- 12 Apr, 2019 1 commit
-
-
Andreas Klebinger authored
Intermediate STG does not contain free variables which can be useful sometimes. So adding a flag to dump that info.
-
- 06 Mar, 2019 1 commit
-
-
Ben Gamari authored
The splitter is an evil Perl script that processes assembler code. Its job can be done better by the linker's --gc-sections flag. GHC passes this flag to the linker whenever -split-sections is passed on the command line. This is based on @DemiMarie's D2768. Fixes Trac #11315 Fixes Trac #9832 Fixes Trac #8964 Fixes Trac #8685 Fixes Trac #8629
-
- 18 Feb, 2019 1 commit
-
-
Vladislav Zavialov authored
-
- 16 Feb, 2019 1 commit
-
-
Matthew Pickering authored
-
- 13 Jan, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
Instead of parsing and executing a statement or declaration directly we now parse them first and then execute in a separate step. This gives us the flexibility to inspect the parsed declaration before execution. Using this we now inspect parsed declarations, and if it's a single declaration of form `x = y` we execute it as `let x = y` instead, fixing a ton of problems caused by poor declaration support in GHCi. To avoid any users of the modules I left `execStmt` and `runDecls` unchanged and added `execStmt'` and `runDecls'` which work on parsed statements/declarations.
-
- 05 Jan, 2019 1 commit
-
-
Ömer Sinan Ağacan authored
Fixes #16131
-
- 11 Dec, 2018 1 commit
-
-
Alec Theriault authored
Adds a `-fenable-ide-info` flag which instructs GHC to generate `.hie` files (see the wiki page: https://ghc.haskell.org/trac/ghc/wiki/HIEFiles). This is a rebased version of Zubin Duggal's (@wz1000) GHC changes for his GSOC project, as posted here: https://gist.github.com/wz1000/5ed4ddd0d3e96d6bc75e095cef95363d. Test Plan: ./validate Reviewers: bgamari, gershomb, nomeata, alanz, sjakobi Reviewed By: alanz, sjakobi Subscribers: alanz, hvr, sjakobi, rwbarton, wz1000, carter Differential Revision: https://phabricator.haskell.org/D5239
-
- 08 Dec, 2018 3 commits
-
-
Matthew Pickering authored
This flag can be set to turn off the Safe Haskell checks. Whether a module is marked Safe/Unsafe/Trustworthy is ignored when this flag to set. Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: rwbarton, carter GHC Trac Issues: #15920 Differential Revision: https://phabricator.haskell.org/D5360
-
Ömer Sinan Ağacan authored
StgLint was incorrectly using isLocalId for bound id check to see whether an id is imported (in which case we don't expect it to be bound) or local. The problem with isLocalId is that its semantics changes after Core, as explained in the note: (last line) Note [GlobalId/LocalId] ~~~~~~~~~~~~~~~~~~~~~~~ A GlobalId is * always a constant (top-level) * imported, or data constructor, or primop, or record selector * has a Unique that is globally unique across the whole GHC invocation (a single invocation may compile multiple modules) * never treated as a candidate by the free-variable finder; it's a constant! A LocalId is * bound within an expression (lambda, case, local let(rec)) * or defined at top level in the module being compiled * always treated as a candidate by the free-variable finder After CoreTidy, top-level LocalIds are turned into GlobalIds We now pass current module as a parameter to StgLint, which uses it to see if an id should be bound (defined in the current module) or not (imported). Other changes: - Generalized StgLint to make it work on both StgTopBinding and CgStgTopBinding. - Bring all top-level binders into scope before linting top-level bindings to allow uses before definitions. TODO: We should remove the binder from local vars when checking RHSs of non-recursive bindings. Test Plan: This validates. Reviewers: simonpj, bgamari, sgraf Reviewed By: simonpj, sgraf Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5370
-
Ömer Sinan Ağacan authored
hscSimpleIface is returning a bool for whether there were _no changes_ in the iface file. The same bool is called "no_change_at_all" in mkIface_, and "no_change" in hscWriteIface and other functions. However it is called "changed" in HscMain.finish and hscMaybeWriteIface, which is confusing because "changed" and "no_change" have opposite meanings. This patch renames "changed" to "no_change" to fix this. Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5416
-
- 22 Nov, 2018 1 commit
-
-
David Eichmann authored
This patch fixes a fairly long-standing bug (dating back to 2015) in RdrName.bestImport, namely commit 9376249b Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Wed Oct 28 17:16:55 2015 +0000 Fix unused-import stuff in a better way In that patch got the sense of the comparison back to front, and thereby failed to implement the unused-import rules described in Note [Choosing the best import declaration] in RdrName This led to Trac #13064 and #15393 Fixing this bug revealed a bunch of unused imports in libraries; the ones in the GHC repo are part of this commit. The two important changes are * Fix the bug in bestImport * Modified the rules by adding (a) in Note [Choosing the best import declaration] in RdrName Reason: the previosu rules made Trac #5211 go bad again. And the new rule (a) makes sense to me. In unravalling this I also ended up doing a few other things * Refactor RnNames.ImportDeclUsage to use a [GlobalRdrElt] for the things that are used, rather than [AvailInfo]. This is simpler and more direct. * Rename greParentName to greParent_maybe, to follow GHC naming conventions * Delete dead code RdrName.greUsedRdrName Bumps a few submodules. Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27 Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5312
-
- 19 Nov, 2018 1 commit
-
-
Sebastian Graf authored
Summary: Currently, `CoreToStg` annotates `StgRhsClosure`s with their set of non-global free variables. This free variable information is only needed in the final code generation step (i.e. `StgCmm.codeGen`), which leads to transformations such as `StgCse` and `StgUnarise` having to maintain this information. This is tiresome and unnecessary, so this patch introduces a trees-to-grow-like approach that only introduces the free variable set into the syntax tree in the code gen pass, along with a free variable analysis on STG terms to generate that information. Fixes #15754. Reviewers: simonpj, osa1, bgamari, simonmar Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #15754 Differential Revision: https://phabricator.haskell.org/D5324
-
- 29 Oct, 2018 1 commit
-
-
Richard Eisenberg authored
This reverts commit 3a51abd0. I had hit the wrong button when trying to validate the original commit... and ended up committing it prematurely instead. This reversion commit also updates the comments to explain why we kind-generalise.
-