- Jun 02, 2018
-
-
Summary: Currently broken. Test Plan: Validate Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15186 Differential Revision: https://phabricator.haskell.org/D4757
-
Andreas Klebinger authored
* Use toBlockList instead of revPostorder. Block elimination works on a given Cmm graph by: * Getting a list of blocks. * Looking for duplicates in these blocks. * Removing all but one instance of duplicates. There are two (reasonable) ways to get the list of blocks. * The fast way: `toBlockList` This just flattens the underlying map into a list. * The convenient way: `revPostorder` Start at the entry label, scan for reachable blocks and return only these. This has the advantage of removing all dead code. If there is dead code the later is better. Work done on unreachable blocks is clearly wasted work. However by the point we run the common block elimination pass the input graph already had all dead code removed. This is done during control flow optimization in CmmContFlowOpt which is our first Cmm pass. This means common block elimination is free to use toBlockList because revPostorder would return the same blocks. (Although in a different order). * Change the triemap used for grouping by a label list from `(TM.ListMap UniqDFM)` to `ListMap (GenMap LabelMap)`. * Using GenMap offers leaf compression. Which is a trie optimization described by the Note [Compressed TrieMap] in CoreSyn/TrieMap.hs * Using LabelMap removes the overhead associated with UniqDFM. This is deterministic since if we have the same input keys the same LabelMap will be constructed. Test Plan: ci, profiling output Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: dfeuer, thomie, carter GHC Trac Issues: #15103 Differential Revision: https://phabricator.haskell.org/D4597
-
- Jun 01, 2018
-
-
Sergei Trofimovich authored
Noticed section mismatch on UNREG build failure: ``` HC [stage 1] libraries/integer-gmp/dist-install/build/GHC/Integer/Type.o error: conflicting types for 'ufu0_srt' static StgWord ufu0_srt[]__attribute__((aligned(8)))= { ^~~~~~~~ note: previous declaration of 'ufu0_srt' was here IRO_(ufu0_srt); ^~~~~~~~ ``` `IRO_` is a 'const' qualifier. The error is a leftover from commit 838b6903 "Merge FUN_STATIC closure with its SRT" where part of SRT was moved into closure itself and made SRTs writable. This change puts all SRTs into writable section. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Reviewers: simonmar, bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4731
-
Gabor Greif authored
-
- May 31, 2018
-
-
Andreas Klebinger authored
Jump tables always point to blocks when we first generate them. However there are rare situations where we can shortcut one of these blocks to a static address during the asm shortcutting pass. While we already updated the data section accordingly this patch also extends this to the references stored in JMP_TBL. Test Plan: ci Reviewers: bgamari Reviewed By: bgamari Subscribers: thomie, carter GHC Trac Issues: #15104 Differential Revision: https://phabricator.haskell.org/D4595
-
When linking dynamic libraries or executables, we compute the full transitive closure over the dependencies, and instruct the linker to link all dependencies. With deep dependency trees the number of transitive dependencies can grow quickly. macOS since the Sierra release has an upper limit on the load command sizes the linker parses when loading dynamic lirbaries. As such it is mandatory to keep the number of load commands (and their size) small on recent macOS releases. An approach that would just link direct dependencies as specified by the -package-id flag is insufficient, because GHC can inline across packages and the library or executable being linked could refer to symbols deep in the dependency tree. If we just recursively linked librarys and re-exported their symbols, this increases the number of symbols in libraries with many dependencies and ultimately puts excessive strain on the linker to the point where linking takes a lot longer than even the compilation of the modules. We can however build a list of symbols from the obejcts we want to link, and try to compute the libraries we need to link that contain those symbols from the transitive dependency closure. Luckily, we don't need to write this ourselves, but can use the ld64 `-dead_strip_dylibs` linker flag on macOS to achive the same result. This will link only the libraries that are actually referenced, which is usually a small subset of the full transitive dependency closure. As such we should stay within the load command size limit for almost all but pathological cases. Reviewers: bgamari Reviewed By: bgamari Subscribers: lelf, rwbarton, thomie, carter GHC Trac Issues: #14444 Differential Revision: https://phabricator.haskell.org/D4714
-
Previously we would allow the expiration time to overflow, which in practice meant that `threadDelay maxBound` we return far earlier than circa 2500 CE. For now we fix this by simply clamping to maxBound. Fixes #15158. Test Plan: Validate, run T8089 Reviewers: simonmar, hvr Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15158 Differential Revision: https://phabricator.haskell.org/D4719
-
Docstrings don't profit from FastString's interning, so we switch to a different type that doesn't incur this overhead. Updates the haddock submodule. Reviewers: alexbiehl, bgamari Reviewed By: alexbiehl, bgamari Subscribers: rwbarton, thomie, mpickering, carter GHC Trac Issues: #15157 Differential Revision: https://phabricator.haskell.org/D4743
-
Reviewers: ggreif Reviewed By: ggreif Subscribers: rwbarton, thomie, carter, ggreif Differential Revision: https://phabricator.haskell.org/D4750
-
On Fedora: `/usr/libexec/sphinx-build --version` outputs `sphinx-build 1.7.2`. In bindir we actually have sphinx-build-2 and sphinx-build-3 (python2 and python3 versions), which output `sphinx-build-2 1.7.2` and `sphinx-build-3 1.7.2` respectively. Dunno what version others are using but at least this change should works for most versions I suppose.
-
-
Roland Senn authored
Just look for the rule firing that we want to see instead of matching on the entire dump. Fixes #15088.
-
The warning does not consider the fact that the splice pattern may very well end up binding variables.
-
When we allocate the heap on POSIX platforms we generally just ask for a 1TB chunk of address space and call it a day. However, if the user has set a ulimit then this request will fail. In this case we would previously try successively smaller allocation requests, reducing the request size by a factor of two each time. However, this means that GHC will significantly allocate a significantly smaller heap than the available physical memory size in some circumstances. Imagine, for instance, a machine with 512 GB of physical memory but a ulimit of 511 GB: we would be limited to a 256 GB heap. We now use a less aggressive back-off policy, reducing by one-eighth the last allocation size each try. Thanks to luispedro for the suggested approach. Test Plan: Validate Reviewers: simonmar, erikd Subscribers: rwbarton, thomie GHC Trac Issues: #14492 Differential Revision: https://phabricator.haskell.org/D4215
-
- May 30, 2018
-
-
Ben Gamari authored
-
Ben Gamari authored
`ghc -M` currently doesn't properly account for ways when generating dependencies (#15197). This import ensures correct build-ordering between this module and GHC.Exts.Heap.InfoTableProf. Otherwise the profiled build may fail as described in #15197.
-
Matthew Pickering authored
This patch implements the API proposed as pull request #108 for plugin authors to influence the recompilation checker. It adds a new field to a plugin which computes a `FingerPrint`. This is recorded in interface files and if it changes then we recompile the module. There are also helper functions such as `purePlugin` and `impurePlugin` for constructing plugins which have simple recompilation semantics but in general, an author can compute a hash as they wish. Fixes #12567 and #7414 https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/002 2-plugin-recompilation.rst Reviewers: bgamari, ggreif Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #7414, #12567 Differential Revision: https://phabricator.haskell.org/D4366
-
I've changed the name from `Valid substitutions` to `Valid hole fits`, since "substitution" already has a well defined meaning within the theory. As part of this change, the flags and output is reanamed, with substitution turning into hole-fit in most cases. "hole fit" was already used internally in the code, it's clear and shouldn't cause any confusion. In this update, I've also reworked how we manage side-effects in the hole we are considering. This allows us to consider local bindings such as where clauses and arguments to functions, suggesting e.g. `a` for `head (x:xs) where head :: [a] -> a`. It also allows us to find suggestions such as `maximum` for holes of type `Ord a => a -> [a]`, and `max` when looking for a match for the hole in `g = foldl1 _`, where `g :: Ord a => [a] -> a`. We also show much improved output for refinement hole fits, and fixes #14990. We now show the correct type of the function, but we also now show what the arguments to the function should be e.g. `foldl1 (_ :: Integer -> Integer -> Integer)` when looking for `[Integer] -> Integer`. I've moved the bulk of the code from `TcErrors.hs` to a new file, `TcHoleErrors.hs`, since it was getting too big to not live on it's own. This addresses the considerations raised in #14969, and takes proper care to set the `tcLevel` of the variables to the right level before passing it to the simplifier. We now also zonk the suggestions properly, which improves the output of the refinement hole fits considerably. This also filters out suggestions from the `GHC.Err` module, since even though `error` and `undefined` are indeed valid hole fits, they are "trivial", and almost never useful to the user. We now find the hole fits using the proper manner, namely by solving nested implications. This entails that the givens are passed along using the implications the hole was nested in, which in turn should mean that there will be fewer weird bugs in the typed holes. I've also added a new sorting method (as suggested by SPJ) and sort by the size of the types needed to turn the hole fits into the type of the hole. This gives a reasonable approximation to relevance, and is much faster than the subsumption check. I've also added a flag to toggle whether to use this new sorting algorithm (as is done by default) or the subsumption algorithm. This fixes #14969 I've also added documentation for these new flags and update the documentation according to the new output. Reviewers: bgamari, goldfire Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14969, #14990, #10946 Differential Revision: https://phabricator.haskell.org/D4444
-
As noted in #15073, GeneralizedNewtypeDeriving may produce code that uses extensions that do not directly appear in the code written by the user. Make this clear in the users guide. [skip ci] Test Plan: Read it Reviewers: RyanGlScott Reviewed By: RyanGlScott Subscribers: fosskers, rwbarton, thomie, carter GHC Trac Issues: #15073 Differential Revision: https://phabricator.haskell.org/D4701
-
To resolve ticket #11295, I think it makes sense to stop hard-coding the pass sequences used by GHC when compiling with LLVM into the compiler itself. This patchset introduces a companion to the existing `llvm-targets` file called `llvm-passes`. The passes file is a simple association list that holds the default LLVM `opt` pass sequence used by GHC. This allows end users to easily save their favorite optimization flags when compiling with LLVM. The main benefit for ticket #11295 is that when adding a custom pass sequence, it tends to be an extremely long string that would be unsightly in the code. This is essentially part 1 of 2 for ticket #11295. Test Plan: ./validate Reviewers: bgamari, angerman Reviewed By: angerman Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4695
-
Ningning Xie authored
An attempt on #14975: During compilation, reflexive casts is discarded for computation. Currently in some places we use Maybe coercion as inputs. So if a cast is reflexive it is denoted as Nothing, otherwise Just coercion. This patch defines the type data MCoercion = MRefl | MCo Coercion which is isomorphic to Maybe Coercion but useful in a number of places, and super-helpful documentation. Test Plan: validate Reviewers: bgamari, goldfire, simonpj Reviewed By: goldfire Subscribers: mpickering, rwbarton, thomie, carter GHC Trac Issues: #14975 Differential Revision: https://phabricator.haskell.org/D4699
-
On 32-bit Linux `outofmem` did not fail with the expected out-of-memory error message, instead failing with, outofmem: internal error: getMBlock: mmap: Invalid argument This happened because, `my_mmap` would attempt to `madvise` even if the `mmap` call failed. So while `mmap` returns `ENOMEM` we nevertheless try to `madvise`, which clobbers `errno`, giving us the unexpected `EINVAL` error. Consequently we don't detect this to be an out-of-memory error. This should fix #15060. Test Plan: `make test TEST=outofmem` on i386 Reviewers: simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15060 Differential Revision: https://phabricator.haskell.org/D4704
-
Tao He authored
This ensures that the deferred type error can be emitted correctly. For `main` function in `Main` module, we have :Main.main = GHC.TopHandler.runMainIO main When the type of `main` is not `IO t` and the `-fdefer-type-errors` is enabled, the `ev_binds` of `main` function will contain deferred type errors. Previously, the `ev_binds` are bound to `runMainIO main`, rather than `main`, the type error exception at runtime cannot be handled properly. See Trac #13838. This patch fix that. Test Plan: make test TEST="T13838" Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13838 Differential Revision: https://phabricator.haskell.org/D4708
-
Simon PJ recently fixed the problem behind this failure so we can now expect this test to pass in all ways again. The fixes got introduced in the following commits: 86bba7d5 d191db48 Test Plan: T14732 (profasm way) Reviewers: bgamari, RyanGlScott, simonpj Reviewed By: RyanGlScott, simonpj Subscribers: simonpj, RyanGlScott, rwbarton, thomie, carter GHC Trac Issues: #15163 Differential Revision: https://phabricator.haskell.org/D4725
-
-
Moving fingerprintByteString to GHC.Fingerprint would require adding a dependency on bytestring to base.
-
AntC authored
Section 10.16 in the Users Guide. Also reviewed mentions/links from other sections: none need revision. Fixes #15146.
-
Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4735
-
Suppress warning about unused match. Fixes #15187 Reviewers: bgamari, simonmar, erikd, hvr Reviewed By: bgamari, simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4741
-
Guillaume Gardet authored
Namely armv6l-unknown-linux-gnueabihf and armv7l-unknown-linux-gnueabihf.
-
Ömer Sinan Ağacan authored
-
Ömer Sinan Ağacan authored
-
- May 29, 2018
-
-
Ben Gamari authored
Namely in T13719 and T13701.
-
Ben Gamari authored
-
David Feuer authored
When `readMVar` was implemented using `takeMVar` and `putMVar`, we needed to use `modifyMVarMasked` in `readChan` just in case the `readMVar` was interrupted between taking and putting. Now that `readMVar` uses an atomic primop, this is impossible, so we can safely unmask `readMVar`. Reviewers: hvr, bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4738
-
-
-
Gabor Greif authored
-
Gabor Greif authored
-
Gabor Greif authored
-