- Nov 02, 2017
-
-
Ryan Scott authored
This implements the `EmptyDataDeriving` proposal put forth in https://github.com/ghc-proposals/ghc-proposals/blob/dbf51608/proposals/0006-deriving-empty.rst. This has two major changes: * The introduction of an `EmptyDataDeriving` extension, which permits directly deriving `Eq`, `Ord`, `Read`, and `Show` instances for empty data types. * An overhaul in the code that is emitted in derived instances for empty data types. To see an overview of the changes brought forth, refer to the changes to the 8.4.1 release notes. Test Plan: ./validate Reviewers: bgamari, dfeuer, austin, hvr, goldfire Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #7401, #10577, #13117 Differential Revision: https://phabricator.haskell.org/D4047
-
- Oct 31, 2017
-
-
Simon Peyton Jones authored
This commit commit 85aa1f42 Date: Sun Oct 29 20:48:19 2017 -0400 Fix #14390 by making toIfaceTyCon aware of equality was a bit over-complicated. This patch simplifies the (horribly ad-hoc) treatement of IfaceEqualityTyCon, and documents it better. No visible change in behaviour.
-
- Oct 30, 2017
-
-
-
Simon Peyton Jones authored
-
Gabor Greif authored
-
Gabor Greif authored
-
Gabor Greif authored
-
Gabor Greif authored
-
Gabor Greif authored
and in comments
-
Simon Peyton Jones authored
-
This is another step for fixing #13825 and is based on D38 by Simon Marlow. The change allows storing multiple constructor fields within the same word. This currently applies only to `Float`s, e.g., ``` data Foo = Foo {-# UNPACK #-} !Float {-# UNPACK #-} !Float ``` on 64-bit arch, will now store both fields within the same constructor word. For `WordX/IntX` we'll need to introduce new primop types. Main changes: - We now use sizes in bytes when we compute the offsets for constructor fields in `StgCmmLayout` and introduce padding if necessary (word-sized fields are still word-aligned) - `ByteCodeGen` had to be updated to correctly construct the data types. This required some new bytecode instructions to allow pushing things that are not full words onto the stack (and updating `Interpreter.c`). Note that we only use the packed stuff when constructing data types (i.e., for `PACK`), in all other cases the behavior should not change. - `RtClosureInspect` was changed to handle the new layout when extracting subterms. This seems to be used by things like `:print`. I've also added a test for this. - I deviated slightly from Simon's approach and use `PrimRep` instead of `ArgRep` for computing the size of fields. This seemed more natural and in the future we'll probably want to introduce new primitive types (e.g., `Int8#`) and `PrimRep` seems like a better place to do that (where we already have `Int64Rep` for example). `ArgRep` on the other hand seems to be more focused on calling functions. Signed-off-by:
Michal Terepeta <michal.terepeta@gmail.com> Test Plan: ./validate Reviewers: bgamari, simonmar, austin, hvr, goldfire, erikd Reviewed By: bgamari Subscribers: maoe, rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3809
-
Ryan Scott authored
GHC was panicking when pretty-printing a heterogeneous equality type constructor (#14390) because the function which produced the type constructor, `toIfaceTyCon`, wasn't attaching the appropriate `IfaceTyConSort` for equality type constructors, which is `IfaceEqualityTyCon`. This is fixed easily enough. Test Plan: make test TEST=T14390 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14390 Differential Revision: https://phabricator.haskell.org/D4132
-
Alex Biehl authored
Depends on D4090 Reviewers: austin, bgamari, erikd, simonmar, alexbiehl Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4091
-
Here we add a flag to instruct the native code generator to add alignment checks in all info table dereferences. This is helpful in catching pointer tagging issues. Thanks to @jrtc27 for uncovering the tagging issues on Sparc which inspired this flag. Test Plan: Validate Reviewers: simonmar, austin, erikd Reviewed By: simonmar Subscribers: rwbarton, trofi, thomie, jrtc27 Differential Revision: https://phabricator.haskell.org/D4101
-
Hopefully these are more robust to NFS malfunction than BSD flock-style locks. See #13945. Test Plan: Validate via @simonpj Reviewers: austin, hvr Subscribers: rwbarton, thomie, erikd, simonpj GHC Trac Issues: #13945 Differential Revision: https://phabricator.haskell.org/D4129
-
- Oct 29, 2017
-
-
Joachim Breitner authored
The idea is described in #14152, and can be summarized: Float the exit path out of a joinrec, so that the simplifier can do more with it. See the test case for a nice example. The floating goes against what the simplifier usually does, hence we need to be careful not inline them back. The position of exitification in the pipeline was chosen after a small amount of experimentation, but may need to be improved. For example, exitification can allow rewrite rules to fire, but for that it would have to happen before the `simpl_phases`. Perf.haskell.org reports these nice performance wins: Nofib allocations fannkuch-redux 78446640 - 99.92% 64560 k-nucleotide 109466384 - 91.32% 9502040 simple 72424696 - 5.96% 68109560 Nofib instruction counts fannkuch-redux 1744331636 - 3.86% 1676999519 k-nucleotide 2318221965 - 6.30% 2172067260 scs 1978470869 - 3.35% 1912263779 simple 669858104 - 3.38% 647206739 spectral-norm 186423292 - 5.37% 176411536 Differential Revision: https://phabricator.haskell.org/D3903
-
Joachim Breitner authored
Previously, (since 33452dfc), simplNonRecJoinPoint would do the wrong thing in the presence of shadowing: It analyzed the RHS of a join binding with the environment for the body. In particular, with foo x = join x = x * x in x where there is shadowing, it renames the inner x to x1, and should produce foo x = join x1 = x * x in x1 but because the substitution (x ↦ x1) is also used on the RHS we get the bogus foo x = join x1 = x1 * x1 in x1 Fixed this by adding a `rhs_se` parameter, analogous to `simplNonRecE` and `simplLazyBind`. Differential Revision: https://phabricator.haskell.org/D4130
-
- Oct 28, 2017
-
-
Joachim Breitner authored
-
- Oct 27, 2017
-
-
niteria authored
Computing the number of constructors for TyCon is linear in the number of constructors. That's wasteful if all you want to check is if that number is smaller than what fits in tag bits (usually 8 things). What this change does is to use a function that can determine the ineqaulity without computing the size. This improves compile time on a module with a data type that has 10k constructors. The variance in total time is (suspiciously) high, but going by the best of 3 the numbers are 8.186s vs 7.511s. For 1000 constructors the difference isn't noticeable: 0.646s vs 0.624s. The hot spots were cgDataCon and cgEnumerationTyCon where tagForCon is called in a loop. One alternative would be to pass down the size. Test Plan: harbormaster Reviewers: bgamari, simonmar, austin Reviewed By: simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4116
-
Ben Gamari authored
-
Simon Marlow authored
Summary: It's simple to treat BodyStmt just like a BindStmt with a wildcard pattern, which is enough to fix #12143 without going all the way to using `<*` and `*>` (#10892). Test Plan: * new test cases in `ado004.hs` * validate Reviewers: niteria, simonpj, bgamari, austin, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #12143 Differential Revision: https://phabricator.haskell.org/D4128
-
Simon Peyton Jones authored
Trac #14379 showed a case where use of "forcing" to do "damn the torpedos" specialisation without resource limits (which 'vector' does a lot) led to exponential blowup. The fix is easy. Finding it wasn't. See Note [Forcing specialisation] and the one-line change in decreaseSpecCount.
-
Simon Peyton Jones authored
-
- Oct 26, 2017
-
-
Joachim Breitner authored
Do not use $SHELL as $SHELL is the user's preferred interactive shell. We do not want this to leak into the wrapper scripts.
-
-
Ben Gamari authored
This is breaking the build on some platforms. It's unclear exactly why but I don't have time to investigate at the moment.
-
Herbert Valerio Riedel authored
[skip ci]
-
- Oct 25, 2017
-
-
Improves compiler performance of deriving Read instances, as suggested in the issue. Additionally, we introduce `readSymField`, a companion to `readField` that parses symbol-type fields (where the field name is a symbol, e.g. `(#)`, rather than an alphanumeric identifier. The decision between these two functions is made a compile time, because we already know which one we need based on the field name. Reviewers: austin, hvr, bgamari, RyanGlScott Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4108
-
Test Plan: Consider whether this is a good idea. Reviewers: austin, hvr, bgamari, nomeata Reviewed By: bgamari, nomeata Subscribers: nomeata, rwbarton, thomie GHC Trac Issues: #14387 Differential Revision: https://phabricator.haskell.org/D4126
-
Begins to fix #14214. [skip ci] Test Plan: Read it. Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #14214 Differential Revision: https://phabricator.haskell.org/D4098
-
The lexer hacks around unicode by squishing any character into a 'Word8' and then storing the actual character in its state. This happens at 'alexGetByte'. That is all and well, but we ought to be careful that the characters we retrieve via 'alexInputPrevChar' also fit this convention. In fact, #13986 exposes nicely what can go wrong: the regex in the left context of the type application rule uses the '$idchar' character set which relies on the unicode hack. However, a left context corresponds to a call to 'alexInputPrevChar', and we end up passing full blown unicode characters to '$idchar', despite it not being equipped to deal with these. Test Plan: Added a regression test case Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #13986 Differential Revision: https://phabricator.haskell.org/D4105
-
Warning on declaring a partial record selector. However, disable warn with field names that start with underscore. Test Plan: Added 1 test case. Reviewers: austin, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: goldfire, simonpj, duog, rwbarton, thomie GHC Trac Issues: #7169 Differential Revision: https://phabricator.haskell.org/D4083
-
When allocating and potentially spilling registers, we need to check the desired allocations against current allocations to decide where we can spill to, cq. which allocations we can toss and if so, how. Previously, this was done by walking the Cartesian product of the current allocations (`assig`) and the allocations to keep (`keep`), which has quadratic complexity. This patch introduces two improvements: 1. pre-filter the `assig` list, because we are only interested in two types of allocations (in register, and in register+memory), which will only make up a small and constant portion of the list; and 2. use set / map operations instead of lists, which reduces algorithmic complexity. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4109
-
Replace a call to mapAccumR, which uses linear stack space, with a gadget that uses constant space. Remove an unused parameter from fromOnDiskName. The tests T1292_imports and T4239 are now reporting imported names in a different order. I don't completely understand why, but I presume it is because the symbol tables are now read more strictly. The new order seems better in T1792_imports, and equally random in T4239. There are several performance test improvements. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4124
-
This fixes the mirror script so it correctly queries haskell.org and if packages aren't found check repo.msys2.org. Also the mirror functionality now generates the md5 hashes after a mirror fetch that can be placed in the md5sums file. Test Plan: mk/get-win32-tarballs.sh fetch mirror and ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4118
-
Making the pretty-printer based assembly output stricter in strategically chosen locations produces a minor performance improvement when compiling large derived Read instance (on the order of 5-10%). Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4111
-
Andreas Klebinger authored
-
Ben Gamari authored
-
Joachim Breitner authored
I.e. instead of .. ghc-flag:: -XUnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. :type: dynamic :reverse: -XNoUnboxedTuples :category: one simply writes .. extension:: UnboxedTuples :shortdesc: Enable the use of unboxed tuple syntax. This allows language extensions to be referenced as If :extension:`UnboxedTuples` is enabled, then... This directive still creates the entries for the `-XUnboxedTuples` flag, so in particular, Set :ghc-flag:`-XUnboxedTuples` if you have to. still works, and lists of flags in general (e.g. for the manpage) include these. I also removed lots of links from the shortdesc of the extensions, when this link simply points to the section where the extension is defined. I removed the list of `-X` flags from the flag reference table, but added a table of extension under “10.1. Language options” Lots of text in the manual now refers to “extension `Foo`” rather than “flag `-XFoo`”. I consider `-XFoo` a historic artifact that stems from when language extensions were really just flags. These days, the use of `-XFoo` is (IMHO) deprecated: You should be using `LANGUAGE Foo`, or maybe the appropriate field in a `.cabal` file. See 9278994a which did this change to error messages already. Differential Revision: https://phabricator.haskell.org/D4112
-
Tamar Christina authored
This reverts commit 561bdca1. submodule
-