- Jun 18, 2017
-
-
Ryan Scott authored
Summary: This amounts to using `exactTyCoVarsOfType` instead of `tyCoVarsOfType` in the right place. I also fixed a similar issue for `-XDatatypeContexts` while I was in town (but couldn't be bothered to add a test for it). Test Plan: make test TEST=T13813 Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13813 Differential Revision: https://phabricator.haskell.org/D3635
-
Ryan Scott authored
s/tyVarsOfType/tyCoFVsOfType/g
-
- Jun 17, 2017
-
-
Tamar Christina authored
Summary: This patch drops the GCC driver and instead moves the only remaining path that we need to keep for backwards compatibility to the settings file. It also generalizes the code that expands `$TopDir` so it can expand it within any location in the string and also changes it so `$TopDir` is expanded only after the words call because `$TopDir` can contains spaces which would be horribly broken. Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd GHC Trac Issues: #13709 Differential Revision: https://phabricator.haskell.org/D3592
-
- Jun 16, 2017
-
-
Tamar Christina authored
Summary: There are various distros that build GHC using their own C compilers such as MSYS2. Currently they have to patch the build scripts everytime. This patch provides the configure argument `--enable-distro-toolchain` which allows one to build using any C compiler on the path. This is also useful for testing new versions of GCC. Test Plan: ./configure --enable-distro-toolchain && make - && make THREADS=9 test ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, erikd, #ghc_windows_task_force GHC Trac Issues: #13792 Differential Revision: https://phabricator.haskell.org/D3637
-
Simon Peyton Jones authored
The IdBindingInfo field of ATcId serves two purposes - to control generalisation when we have -XMonoLocalBinds - to check for floatability when dealing with (static e) These are related, but not the same, and they'd becomme confused. Trac #13804 showed this up via an example like this: f periph = let sr :: forall a. [a] -> [a] sr = if periph then reverse else id sr2 = sr -- The question: is sr2 generalised? -- It should be, because sr has a type sig -- even though it has periph free in (sr2 [True], sr2 "c") Here sr2 should be generalised, despite the free var 'periph' in 'sr' because 'sr' has a closed type signature. I documented all this very carefully this time, in TcRnTypes: Note [Meaning of IdBindingInfo] Note [Bindings with closed types: ClosedTypeId]
-
Test Plan: validate Reviewers: austin, hvr, erikd, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13832 Differential Revision: https://phabricator.haskell.org/D3652
-
- Jun 14, 2017
-
-
niteria authored
Currently GHC exposes the internal details of `ModuleGraph` which inhibits making `ModuleGraph` support faster lookups. Haddock relies on the internal representation by using `map` on `ModuleGraph`. See also https://github.com/haskell/haddock/issues/635 Adding `mapMG` should allow us to make `ModuleGraph` abstract. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, alexbiehl Reviewed By: bgamari, alexbiehl Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3645
-
Gabor Greif authored
-
- Jun 13, 2017
-
-
Gabor Greif authored
-
- Jun 12, 2017
-
-
sgillespie authored
Previously -w combined with -Wunrecognised-warning-flags would not report unrecognized flags. Reviewers: austin, bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie GHC Trac Issues: #12056 Differential Revision: https://phabricator.haskell.org/D3581
-
David Feuer authored
`coreBindsSize` forced a ton of structure to stop space leaks. Reid Barton has done some work recently to try to stop the leaks at their source instead. Memory residency remains well below the numbers Herbert posted on #13426 originally, but in some cases a ways above the ones from 8.0. I need to figure out how to get the numbers matched up to individual modules and do some profiling. Relates to #13426 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3606
-
Ryan Scott authored
`repNonArrowKind` was missing a case for `HsKindSig`, which this commit adds. Fixes #13781. Test Plan: make test TEST=T13781 Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie GHC Trac Issues: #13781 Differential Revision: https://phabricator.haskell.org/D3627
-
Ryan Scott authored
Commit 2b74bd9d did wonders for the program reported in #12545. Let's add a perf test for it to make sure it stays fast. Test Plan: make test TEST=T12545 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #12545 Differential Revision: https://phabricator.haskell.org/D3632
-
The problem was that the generated label included a freshly assigned Unique value. Test Plan: Added a new test and looked at the generated stub: ``` #include "HsFFI.h" #ifdef __cplusplus extern "C" { #endif extern HsInt zdmainzdAzdAzuzzlzzgzzg(StgStablePtr the_stableptr); extern HsInt zdmainzdAzdAzumkStringWriter(StgStablePtr the_stableptr); #ifdef __cplusplus } #endif ``` ./validate Reviewers: simonmar, austin, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13807 Differential Revision: https://phabricator.haskell.org/D3633
-
Put it in a GhcMonad. Stop accidentally reversing the list of instances. Add a comment noting the code is mostly copied from tcRnGetInfo. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3636
-
Fixes #13791. [skip ci] Test Plan: Read it Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #13791 Differential Revision: https://phabricator.haskell.org/D3639
-
Test Plan: validate Reviewers: bgamari, niteria, austin, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3640
-
Ben Gamari authored
This broke on 32-bit platforms.
-
- Jun 08, 2017
-
-
SantiM authored
In a previous change (commit 4fd6207e), the users guide was moved from XML to the RST format. This process introduced a typo: "No -O*-type option specified:" was changed to "-O*" (which is not correct). This change fixes it. See result in: https://prnt.sc/fh332n Fixes ticket #13756. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13756 Differential Revision: https://phabricator.haskell.org/D3631
-
This fixes the regressions in the haddock performance tests introduced in c9eb4385. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13789 Differential Revision: https://phabricator.haskell.org/D3629
-
This function in tcRnDriver, retrieves an index by name of all Class and Family instances in the current environment. This is to be used by haddock which currently looks up instances for each name, which looks at every instance for every lookup. Using this function instead of tcRnGetInfo, the haddock.base performance test improves by 10% Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3624
-
Remove filesToNotIntermediateClean from DynFlags, create a data type FilesToClean, and change filesToClean in DynFlags to be a FilesToClean. Modify SysTools.newTempName and the Temporary constructor of PipelineMonad.PipelineOutput to take a TempFileLifetime, which specifies whether a temp file should live until the end of GhcMonad.withSession, or until the next time cleanIntermediateTempFiles is called. These changes allow the cleaning of intermediate files in GhcMake to be much more efficient. HscTypes.hptObjs is removed as it is no longer used. A new performance test T13701 is added, which passes both with and without -keep-tmp-files. The test fails by 25% without the patch, and passes when -keep-tmp-files is added. Note that there are still at two hotspots caused by algorithms quadratic in the number of modules, however neither of them allocate. They are: * DriverPipeline.compileOne'.needsLinker * GhcMake.getModLoop DriverPipeline.compileOne'.needsLinker is changed slightly to improve the situation. I don't like adding these Types to DynFlags, but they need to be seen by Dynflags, SysTools and PipelineMonad. The alternative seems to be to create a new module. Reviewers: austin, hvr, bgamari, dfeuer, niteria, simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13701 Differential Revision: https://phabricator.haskell.org/D3620
-
This will qualify the libtool with the target, e.g. arch-vendor-os-libtool, instead of simply using libtool. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3617
-
This adds Global Offset Table logic, as well as PLT like logic for armv7 and aarch64; which replaces the preexisting symbolExtras logic, by placing the PLT tables next to the separtely loaded sections. This is needed to ensure that the symbol stubs are in range. Reviewers: bgamari, austin, erikd, simonmar Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3448
-
This is a module contributed by Austin Seipp which is fairly minimal (albeit requiring vector) but is still representative of contemporary Haskell. Reviewers: austin Subscribers: dfeuer, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3596
-
Ben Gamari authored
-
Ben Gamari authored
This reverts commit 667abf17.
-
Ben Gamari authored
[skip ci]
-
Simon Marlow authored
Summary: The problem occurred when * Threads A & B evaluate the same thunk * Thread A context-switches, so the thunk gets blackholed * Thread C enters the blackhole, creates a BLOCKING_QUEUE attached to the blackhole and thread A's `tso->bq` queue * Thread B updates the blackhole with a value, overwriting the BLOCKING_QUEUE * We GC, replacing A's update frame with stg_enter_checkbh * Throw an exception in A, which ignores the stg_enter_checkbh frame Now we have C blocked on A's tso->bq queue, but we forgot to check the queue because the stg_enter_checkbh frame has been thrown away by the exception. The solution and alternative designs are discussed in Note [upd-black-hole]. This also exposed a bug in the interpreter, whereby we were sometimes context-switching without calling `threadPaused()`. I've fixed this and added some Notes. Test Plan: * `cd testsuite/tests/concurrent && make slow` * validate Reviewers: niteria, bgamari, austin, erikd Reviewed By: erikd Subscribers: rwbarton, thomie GHC Trac Issues: #13751 Differential Revision: https://phabricator.haskell.org/D3630
-
Tamar Christina authored
Summary: Escape `\` in paths on Windows in `cwapper.c` when we re-output the paths. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13666 Differential Revision: https://phabricator.haskell.org/D3628
-
- Jun 07, 2017
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This patch fixes a bad bug in the specialiser, which showed up as Trac #13429. When specialising an imported DFun, the specialiser could generate a recusive loop where none existed in the original program. It's all rather tricky, and I've documented it at some length in Note [Avoiding loops] We'd encoutered exactly this before (Trac #3591) but I had failed to realise that the very same thing could happen for /imported/ DFuns. I did quite a bit of refactoring. The compiler seems to get a tiny bit faster on deriving/perf/T10858 but almost all the gain had occurred before now; this patch just pushed it over the line.
-
Simon Peyton Jones authored
-
- Jun 06, 2017
-
-
Gabor Greif authored
The output is not being checked in the test suite. However other tools may check it for obtaining the status of the remote slave. So I'd suggest to merge this to 8.2 branch, in order to not fragment the tooling's checks.
-
- Jun 05, 2017
-
-
Alan Zimmerman authored
Summary: See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow This commit prepares the ground for a full extensible AST, by replacing the type parameter for the hsSyn data types with a set of indices into type families, data GhcPs -- ^ Index for GHC parser output data GhcRn -- ^ Index for GHC renamer output data GhcTc -- ^ Index for GHC typechecker output These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var` Where the original name type is required in a polymorphic context, this is accessible via the IdP type family, defined as type family IdP p type instance IdP GhcPs = RdrName type instance IdP GhcRn = Name type instance IdP GhcTc = Id These types are declared in the new 'hsSyn/HsExtension.hs' module. To gain a better understanding of the extension mechanism, it has been applied to `HsLit` only, also replacing the `SourceText` fields in them with extension types. To preserve extension generality, a type class is introduced to capture the `SourceText` interface, which must be honoured by all of the extension points which originally had a `SourceText`. The class is defined as class HasSourceText a where -- Provide setters to mimic existing constructors noSourceText :: a sourceText :: String -> a setSourceText :: SourceText -> a getSourceText :: a -> SourceText And the constraint is captured in `SourceTextX`, which is a constraint type listing all the extension points that make use of the class. Updating Haddock submodule to match. Test Plan: ./validate Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari Subscribers: rwbarton, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D3609
-
Douglas Wilson authored
Previously modules with hscTarget == HscNothing were not desugared. This patch changes behavior so that all modules HsSrcFile Modules except GHC.Prim are desugared. Modules with hscTarget == HscNothing are not simplified. Warnings and errors produced by the desugarer will now be produced when compiling with -fno-code. HscMain.finishTypecheckingOnly is removed, HscMain.hscIncrementalCompile is simplified a bit, and HscMain.finish takes in the removed logic. I think this is easier to follow. Updates haddock submodule. Tests T8101, T8101b, T10600 are no longer expect_broken. Reviewers: ezyang, austin, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #10600 Differential Revision: https://phabricator.haskell.org/D3542
-
Simon Peyton Jones authored
Trac #13785 showed that we were emitting monomorphism warnings when we shouldn't. The fix turned out to be simple. In fact test T10935 then turned out to be another example of the over-noisy warning so I changed the test slightly.
-
Simon Peyton Jones authored
-
- Jun 02, 2017
-
-
Otherwise this will fail if the prefix path contains spaces. Thanks to marinelli for pointing this out. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3604
-
Ryan Scott authored
While investigating #12545, I discovered several places in the code that performed length-checks like so: ``` length ts == 4 ``` This is not ideal, since the length of `ts` could be much longer than 4, and we'd be doing way more work than necessary! There are already a slew of helper functions in `Util` such as `lengthIs` that are designed to do this efficiently, so I found every place where they ought to be used and did just that. I also defined a couple more utility functions for list length that were common patterns (e.g., `ltLength`). Test Plan: ./validate Reviewers: austin, hvr, goldfire, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3622
-