summaryrefslogtreecommitdiff
path: root/libraries
Commit message (Collapse)AuthorAgeFilesLines
* Add INLINE pragamas on Traversable default methodsSimon Peyton Jones2016-12-211-0/+45
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I discovered, when debugging a performance regression in the compiler, that the list instance of mapM was not being inlined at call sites, with terrible runtime costs. It turned out that this was a serious (but not entirely obvious) omission of an INLINE pragmas in the class declaration for Traversable. This patch fixes it. I reproduce below the Note [Inline default methods], which I wrote at some length. We may well want to apply the same fix in other class declarations whose default methods are often used. {- Note [Inline default methods] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) mapM = traverse -- Default method instance Traversable [] where {-# INLINE traverse #-} traverse = ...code for traverse on lists ... This gives rise to a list-instance of mapM looking like this $fTraversable[]_$ctaverse = ...code for traverse on lists... {-# INLINE $fTraversable[]_$ctaverse #-} $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/ that's all! We get $fTraversable[]_$cmapM = ...code for traverse on lists... with NO INLINE pragma! This happens even though 'traverse' had an INLINE pragma becuase the author knew it should be inlined pretty vigorously. Indeed, it turned out that the rhs of $cmapM was just too big to inline, so all uses of mapM on lists used a terribly inefficient dictionary-passing style, because of its 'Monad m =>' type. Disaster! Solution: add an INLINE pragma on the default method: class ... => Traversable t where ... mapM :: Monad m => (a -> m b) -> t a -> m (t b) {-# INLINE mapM #-} -- VERY IMPORTANT! mapM = traverse
* Make CompactionFailed a newtypeRyan Scott2016-12-201-2/+2
|
* Allow use of the external interpreter in stage1.Shea Levy2016-12-205-82/+116
| | | | | | | | | | | | | | | | | | | Summary: Now that we have -fexternal-interpreter, we can lose most of the GHCI ifdefs. This was originally added in https://phabricator.haskell.org/D2826 but that led to a compatibility issue with ghc 7.10.x on Windows. That's fixed here and the revert reverted. Reviewers: goldfire, hvr, austin, bgamari, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2884 GHC Trac Issues: #13008
* Mark T8089 as unbroken since #7325 is now resolvedBen Gamari2016-12-191-3/+1
|
* Revert "Allow use of the external interpreter in stage1."Tamar Christina2016-12-195-116/+82
| | | | This reverts commit 52ba9470a7e85d025dc84a6789aa809cdd68b566.
* Fix #12998 by removing CTimerRyan Scott2016-12-183-12/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: CTimer is a wrapper around `timer_t`, which is a typedef for `void*` on most platforms. The issue is that GHC's `FPTOOLS_CHECK_HTYPE` is not robust enough to discern pointer types from non-pointer types, so it mistakenly labels `timer_t` as a `Double` or `Int32` (depending on how many bits a pointer takes up on your platform). This wreaks havoc when trying to give it certain type class instances, as noted in https://phabricator.haskell.org/rGHCffc2327070dbb664bdb407a804121eacb2a7c734. For now, the simplest thing to do would be removing `CTimer`, since: 1. The original author (@DanielG) didn't have a particular use in mind for `timer_t` when he fixed #12795. 2. `CTimer` hasn't appeared in a release of `base` yet. Fixes #12998. Reviewers: austin, hvr, bgamari, DanielG, trofi Reviewed By: bgamari, trofi Subscribers: thomie, DanielG, erikd Differential Revision: https://phabricator.haskell.org/D2876 GHC Trac Issues: #12795, #12998
* Introduce unboxedSum{Data,Type}Name to template-haskellRyan Scott2016-12-182-0/+45
| | | | | | | | | | | | | | | | | | | | | | | | | Summary: In D2448 (which introduced Template Haskell support for unboxed sums), I neglected to add `unboxedSumDataName` and `unboxedSumTypeName` functions, since there wasn't any way you could write unboxed sum data or type constructors in prefix form to begin with (see #12514). But even if you can't write these `Name`s directly in source code, it would still be nice to be able to use these `Name`s in Template Haskell (for instance, to be able to treat unboxed sum type constructors like any other type constructors). Along the way, this uncovered a minor bug in `isBuiltInOcc_maybe` in `TysWiredIn`, which was calculating the arity of unboxed sum data constructors incorrectly. Test Plan: make test TEST=T12478_5 Reviewers: osa1, goldfire, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2854 GHC Trac Issues: #12478, #12514
* Allow use of the external interpreter in stage1.Shea Levy2016-12-175-82/+116
| | | | | | | | | | | | Now that we have -fexternal-interpreter, we can lose most of the GHCI ifdefs. Reviewers: simonmar, goldfire, austin, hvr, bgamari Reviewed By: simonmar Subscribers: RyanGlScott, mpickering, angerman, thomie Differential Revision: https://phabricator.haskell.org/D2826
* Reexport Language.Haskell.TH.Lib from Language.Haskell.THRyan Scott2016-12-173-85/+115
| | | | | | | | | | | | | | | | | | | | Reexporting `Language.Haskell.TH.Lib` from `Language.Haskell.TH` ensures that `Language.Haskell.TH` will continue to expose all of the functions that `Language.Haskell.TH.Lib` does in the future. Fixes #12992. Test Plan: ./validate Reviewers: austin, bgamari, goldfire Reviewed By: bgamari, goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2867 GHC Trac Issues: #12992
* base: Add more POSIX types (fixes #12795)Daniel Gröber2016-12-154-5/+78
| | | | | | | | | | | | | | Test Plan: validate Reviewers: hvr, austin, RyanGlScott, bgamari Reviewed By: RyanGlScott, bgamari Subscribers: RyanGlScott, thomie, erikd Differential Revision: https://phabricator.haskell.org/D2664 GHC Trac Issues: #12795
* array: Check for integer overflow during allocationBen Gamari2016-12-151-0/+0
| | | | | | | | | | | | This fixes #229, where creating a new array can cause array to allocate a smaller array than it thinks it allocates due to integer overflow, resulting in memory unsafety. This breaks the rts/overflow1 test, which relied on this unchecked overflow. I fix it by reimplementing the test in terms of newByteArray# directly. Updates the array submodule.
* base: Bump version to 4.10.0.0Ben Gamari2016-12-1519-7/+7
| | | | Updates a number of submodules.
* Make unboxedTuple{Type,Data}Name support 0- and 1-tuplesRyan Scott2016-12-152-11/+11
| | | | | | | | | | | | | | | | | | | | | | | | Previously, these functions were hardcoded so as to always `error` whenever given an argument of 0 or 1. This restriction can be lifted pretty easily, however. This requires a slight tweak to `isBuiltInOcc_maybe` in `TysWiredIn` to allow it to recognize `Unit#` (which is the hard-wired `OccName` for unboxed 1-tuples). Fixes #12977. Test Plan: make test TEST=12977 Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2847 GHC Trac Issues: #12977
* base: Make raw buffer IO operations more strictBen Gamari2016-12-132-10/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Ticket #9696 reported that `readRawBufferPtr` and `writeRawBufferPtr` allocated unnecessarily. The binding is question was, ``` let { buf_s4VD [Dmd=<L,U(U)>] :: GHC.Ptr.Ptr GHC.Word.Word8 [LclId, Unf=OtherCon []] = NO_CCS GHC.Ptr.Ptr! [ds1_s4Vy]; } in case GHC.IO.FD.$wreadRawBufferPtr Main.main5 0# 0# buf_s4VD Main.main4 Main.main3 GHC.Prim.void# of ... ``` The problem was that GHC apparently couldn't tell that `readRawBufferPtr` would always demand the buffer. Here we simple add bang patterns on all of the small arguments of these functions to ensure that worker/wrappers can eliminate these allocations. Test Plan: Look at STG produced by testcase in #9696, verify no allocations Reviewers: austin, hvr, simonmar Reviewed By: simonmar Subscribers: RyanGlScott, simonmar, thomie Differential Revision: https://phabricator.haskell.org/D2813 GHC Trac Issues: #9696
* Make globals use sharedCAFMoritz Angermann2016-12-111-1/+1
| | | | | | | | | | | | | | | | | | | Summary: The use of globals is quite painful when multiple rts are loaded, e.g. when plugins are loaded, which bring in a second rts. The sharedCAF appraoch was employed for the FastStringTable; I've taken the libery to extend this to the other globals I could find. This is a reboot of D2575, that should hopefully not exhibit the same windows build issues. Reviewers: Phyx, simonmar, goldfire, bgamari, austin, hvr, erikd Reviewed By: Phyx, simonmar, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2773
* Rename TH constructors for deriving strategiesRyan Scott2016-12-092-6/+6
| | | | | | | | | | | | | | | | | | | After talking to Richard, he and I concluded that choosing the rather common name `Newtype` to represent the corresponding deriving strategy in Template Haskell was a poor choice of name. I've opted to rename it to something less common (`NewtypeStrategy`) while we still have time. I also renamed the corrsponding datatype in the GHC internals so as to match it. Reviewers: austin, goldfire, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2814 GHC Trac Issues: #10598
* Fix the test with -OSimon Marlow2016-12-071-1/+1
| | | | | Static string optimisation means we get a ForeignPtr with an IORef inside it, leading to a different error.
* Ignore output for compact_gc: sizes change when profilingSimon Marlow2016-12-072-14/+1
|
* Overhaul of Compact Regions (#12455)Simon Marlow2016-12-0734-163/+473
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This commit makes various improvements and addresses some issues with Compact Regions (aka Compact Normal Forms). This was the most important thing I wanted to fix. Compaction previously prevented GC from running until it was complete, which would be a problem in a multicore setting. Now, we compact using a hand-written Cmm routine that can be interrupted at any point. When a GC is triggered during a sharing-enabled compaction, the GC has to traverse and update the hash table, so this hash table is now stored in the StgCompactNFData object. Previously, compaction consisted of a deepseq using the NFData class, followed by a traversal in C code to copy the data. This is now done in a single pass with hand-written Cmm (see rts/Compact.cmm). We no longer use the NFData instances, instead the Cmm routine evaluates components directly as it compacts. The new compaction is about 50% faster than the old one with no sharing, and a little faster on average with sharing (the cost of the hash table dominates when we're doing sharing). Static objects that don't (transitively) refer to any CAFs don't need to be copied into the compact region. In particular this means we often avoid copying Char values and small Int values, because these are static closures in the runtime. Each Compact# object can support a single compactAdd# operation at any given time, so the Data.Compact library now enforces mutual exclusion using an MVar stored in the Compact object. We now get exceptions rather than killing everything with a barf() when we encounter an object that cannot be compacted (a function, or a mutable object). We now also detect pinned objects, which can't be compacted either. The Data.Compact API has been refactored and cleaned up. A new compactSize operation returns the size (in bytes) of the compact object. Most of the documentation is in the Haddock docs for the compact library, which I've expanded and improved here. Various comments in the code have been improved, especially the main Note [Compact Normal Forms] in rts/sm/CNF.c. I've added a few tests, and expanded a few of the tests that were there. We now also run the tests with GHCi, and in a new test way that enables sanity checking (+RTS -DS). There's a benchmark in libraries/compact/tests/compact_bench.hs for measuring compaction speed and comparing sharing vs. no sharing. The field totalDataW in StgCompactNFData was unnecessary. Test Plan: * new unit tests * validate * tested manually that we can compact Data.Aeson data Reviewers: gcampax, bgamari, ezyang, austin, niteria, hvr, erikd Subscribers: thomie, simonpj Differential Revision: https://phabricator.haskell.org/D2751 GHC Trac Issues: #12455
* Overhaul GC statsSimon Marlow2016-12-061-59/+201
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Visible API changes: * The C struct `GCDetails` gives the stats about a single GC. This is passed to the `gcDone()` callback if one is set via the RtsConfig. (previously we just passed a collection of values, so this is more extensible, at the expense of breaking the existing API) * `RTSStats` gives cumulative stats since the start of the program, and includes the `GCDetails` for the most recent GC. This struct can be obtained via `getRTSStats()` (the old `getGCStats()` has been removed, and `getGCStatsEnabled()` has been renamed to `getRTSStatsEnabled()`) Improvements: * The per-GC stats and cumulative stats are now cleanly separated. * Inside the RTS we have a top-level `RTSStats` struct to keep all our stats in, previously this was just a collection of strangely-named variables. This struct is mostly just copied in `getRTSStats()`, so the implementation of that function is a lot shorter. * Types are more consistent. We use a uint64_t byte count for all memory values, and Time for all time values. * Names are more consistent. We use a suffix `_bytes` for all byte counts and `_ns` for all time values. * We now collect information about the amount of memory in large objects and compact objects in `GCDetails`. (the latter was the reason I started doing this patch but it seems to have ballooned a bit!) * I fixed a bug in the calculation of the elapsed MUT time, and added an ASSERT to stop the calculations going wrong in the future. For now I kept the Haskell API in `GHC.Stats` the same, by impedence-matching with the new API. We could either break that API and make it match the C API more closely, or we could add a new API and deprecate the old one. Opinions welcome. This stuff is very easy to get wrong, and it's hard to test. Reviews welcome! Test Plan: manual testing validate Reviewers: bgamari, niteria, austin, ezyang, hvr, erikd, rwbarton, Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2756
* fdReady: use poll() instead of select()Simon Marlow2016-12-021-9/+33
| | | | | | | | | | | | | | | | | | | | select() is limited to 1024 file descriptors. This actually blew up in a very hard-to-debug way in our production system when using the hinotify package. Test Plan: libraries/tests pass, paricularly hGetBuf001 which exercises this code. Reviewers: niteria, erikd, austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2785 GHC Trac Issues: #12912
* Fix naming of the native latin1 encodingsKai Ruemmler2016-12-011-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | textEncodingName is notjust a string, it must be a valid input for mkTextEncoding, as stated in libraries/base/GHC/IO/Encoding/Types.hs. Test Plan: A working latin1 locale is required on the system. Reason: ghc's initial locale encoding defaults to ASCII, if either an unknown locale or unknown charset is used. For the bug to show up, ghc must start up using the latin1 encoding. From main directory in ghc do: $ ./configure && make clean && make boot && make inplace/bin/ghc-stage2 $ LC_CTYPE="de_DE.ISO-8859-1" ./inplace/bin/ghc-stage2 Before the patch, the last line leads to the exception thrown: ghc-stage2: mkTextEncoding: does not exist (unknown encoding:ISO8859-1(checked)//TRANSLIT) After the patch, ghc-stage2 prints a short usage summary as expected. Moreover, $ make test TEST=encoding005 continues to pass after the patch. Reviewers: austin, hvr, rwbarton, bgamari Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D2667
* Typos in commentsGabor Greif2016-12-013-3/+3
|
* Revert "Make globals use sharedCAF"Ben Gamari2016-11-301-1/+1
| | | | | This reverts commit 6f7ed1e51bf360621a3c2a447045ab3012f68575 due to breakage of the build on Windows.
* Added Eq1, Ord1, Read1 and Show1 instances for NonEmptyShane2016-11-292-0/+25
| | | | | | | | | | Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2755
* Make globals use sharedCAFMoritz Angermann2016-11-291-1/+1
| | | | | | | | | | | | | | | The use of globals is quite painful when multiple rts are loaded, e.g. when plugins are loaded, which bring in a second rts. The sharedCAF appraoch was employed for the FastStringTable; I've taken the libery to extend this to the other globals I could find. Reviewers: rwbarton, simonmar, austin, hvr, erikd, bgamari Reviewed By: simonmar, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2575
* Allow to unregister threadWaitReadSTM action.Alexander Vershilov2016-11-224-6/+30
| | | | | | | | | | | | | | | | | | | Allow to unregister threadWaitReadSTM/threadWaitWriteSTM on a non-threaded runtime. Previosly noop action was returned, as a result it was not possible to unregister action, unless data arrives to Fd or it's closed. Fixes #12852. Reviewers: simonmar, hvr, austin, bgamari, trofi Reviewed By: bgamari, trofi Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2729 GHC Trac Issues: #12852
* Add Data instance for ConstRyan Scott2016-11-182-0/+6
| | | | | | | | | | | | | | | | Summary: Fixes #12438. As discussed on the Haskell libraries mailing list here: https://mail.haskell.org/pipermail/libraries/2016-November/027396.html Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2726 GHC Trac Issues: #12438
* Revert "Add Data instance for Const"Ryan Scott2016-11-172-6/+0
| | | | | | This reverts commit 07e40e905357db805e6dbb557b35d6bdf76eaec6. This was meant for a local branch, but accidentally wound up in master. Oops.
* Add Data instance for ConstRyan Scott2016-11-172-0/+6
|
* Update xhtml submoduleErik de Castro Lopo2016-11-151-0/+0
| | | | | | | | | | | | Test Plan: validate Reviewers: hvr, austin, Phyx, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2701
* ghc: Fix ghc's template-haskell boundBen Gamari2016-11-121-1/+1
|
* template-haskell: Version bumpBen Gamari2016-11-122-2/+3
|
* Read parentheses betterDavid Feuer2016-11-101-7/+24
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Instead of pulling a token and looking for `'('` or `')'`, just look for the character itself. This prevents us from lexing every single item twice, once to see if it's a left parenthesis and once to actually parse it. Partially fixes #12665 Make parens faster more aggressively * Strip spaces before parsing, so we never have to strip the same spaces twice. * String parsers together manually, to try to avoid unnecessary closure creation. Test Plan: Validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2630 GHC Trac Issues: #12665
* Typos in commentsGabor Greif2016-10-311-1/+1
|
* Add and use a new dynamic-library-dirs field in the ghc-pkg infoDuncan Coutts2016-10-212-2/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Build systems / package managers want to be able to control the file layout of installed libraries. In general they may want/need to be able to put the static libraries and dynamic libraries in different places. The ghc-pkg library regisrtation needs to be able to handle this. This is already possible in principle by listing both a static lib dir and a dynamic lib dir in the library-dirs field (indeed some previous versions of Cabal did this for shared libs on ELF platforms). The downside of listing both dirs is twofold. There is a lack of precision, if we're not careful with naming then we could end up picking up the wrong library. The more immediate problem however is that if we list both directories then both directories get included into the ELF and Mach-O shared object runtime search paths. On ELF this merely slows down loading of shared libs (affecting prog startup time). On the latest OSX versions this provokes a much more serious problem: that there is a rather low limit on the total size of the section containing the runtime search path (and lib names and related) and thus listing any unnecessary directories wastes the limited space. So the solution in this patch is fairly straightforward: split the static and dynamic library search paths in the ghc-pkg db and its use within ghc. This is a traditional solution: pkg-config has the same static / dynamic split (though it describes in in terms of private and public, but it translates into different behaviour for static and dynamic linking). Indeed it would make perfect sense to also have a static/dynamic split for the list of the libraries to use i.e. to have dynamic variants of the hs-libraries and extra-libraries fields. These are not immediately required so this patch does not add it, but it is a reasonable direction to follow. To handle compatibility, if the new dynamic-library-dirs field is not specified then its value is taken from the library-dirs field. Contains Cabal submodule update. Test Plan: Run ./validate Get christiaanb and carter to test it on OSX Sierra, in combination with Cabal/cabal-install changes to the default file layout for libraries. Reviewers: carter, austin, hvr, christiaanb, bgamari Reviewed By: christiaanb, bgamari Subscribers: ezyang, Phyx, thomie Differential Revision: https://phabricator.haskell.org/D2611 GHC Trac Issues: #12479
* Add option to not retain CAFs to the linker APISimon Marlow2016-10-182-3/+24
|
* Bump parallel submoduleBen Gamari2016-10-171-0/+0
| | | | Includes testsuite fix for Python 3.
* Correct name of makeStableName in haddockReid Barton2016-10-161-1/+1
|
* Fix Windows build following D2588Ryan Scott2016-10-141-1/+6
| | | | | Commit 8c6a3d68c0301bb985aa2a462936bbcf7584ae9c inadvertently broke the build on Windows. This restores Windows compatibility.
* Add missing Semigroup instances for Monoidal datatypes in baseRyan Scott2016-10-142-0/+18
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: There are currently three datatypes that are exposed in `base` that have `Monoid` instances, but no `Semigroup` instances: * `IO` * `Event` (from `GHC.Event`) * `Lifetime` (from `GHC.Event`) (There is also `EventLifetime` in `GHC.Event.Internal`, but it is not exported directly, so I didn't bother with it.) Adding the `Semigroup` instances for these types directly in the modules in which they're defined resulted in some horrific import cycles, so I opted to take the easy approach of defining all of these instances in `Data.Semigroup`. (When `Semigroup` becomes a superclass of `Monoid`, these instances will have to be moved somehow.) Fixes #12464. Test Plan: It compiles Reviewers: hvr, ekmett, austin, bgamari Reviewed By: ekmett Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2588 GHC Trac Issues: #12464
* Clean up handling of known-key Names in interface filesBen Gamari2016-10-131-1/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously BinIface had some dedicated logic for handling tuple names in the symbol table. As it turns out, this logic was essentially dead code as it was superceded by the special handling of known-key things. Here we cull the tuple code-path and use the known-key codepath for all tuple-ish things. This had a surprising number of knock-on effects, * constraint tuple datacons had to be made known-key (previously they were not) * IfaceTopBndr was changed from being a synonym of OccName to a synonym of Name (since we now need to be able to deserialize Names directly from interface files) * the change to IfaceTopBndr complicated fingerprinting, since we need to ensure that we don't go looking for the fingerprint of the thing we are currently fingerprinting in the fingerprint environment (see notes in MkIface). Handling this required distinguishing between binding and non-binding Name occurrences in the Binary serializers. * the original name cache logic which previously lived in IfaceEnv has been moved to a new NameCache module * I ripped tuples and sums out of knownKeyNames since they introduce a very large number of entries. During interface file deserialization we use static functions (defined in the new KnownUniques module) to map from a Unique to a known-key Name (the Unique better correspond to a known-key name!) When we need to do an original name cache lookup we rely on the parser implemented in isBuiltInOcc_maybe. * HscMain.allKnownKeyNames was folded into PrelInfo.knownKeyNames. * Lots of comments were sprinkled about describing the new scheme. Updates haddock submodule. Test Plan: Validate Reviewers: niteria, simonpj, austin, hvr Reviewed By: simonpj Subscribers: simonmar, niteria, thomie Differential Revision: https://phabricator.haskell.org/D2467 GHC Trac Issues: #12532, #12415
* Cabal submodule update.Edward Z. Yang2016-10-131-0/+0
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Add missing @since annotationsRyan Scott2016-10-121-0/+2
|
* Escape lambda.Vaibhav Sagar2016-10-091-1/+1
| | | | | | | | | | | | | | Test Plan: View updated documentation? Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2583 GHC Trac Issues: #12672
* Cabal submodule update.Edward Z. Yang2016-10-081-0/+0
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Make InstalledUnitId be ONLY a FastString.Edward Z. Yang2016-10-082-28/+28
| | | | | | | | | | | | | | | | | | | | | It turns out that we don't really need to be able to extract a ComponentId from UnitId, except in one case. So compress UnitId into a single FastString. The one case where we do need the ComponentId is when we are compiling an instantiated version of a package; we need the ComponentId to look up the indefinite version of this package from the database. So now we just pass it in as an argument -this-component-id. Also: ghc-pkg now no longer will unregister a package if you register one with the same package name, if the instantiations don't match. Cabal submodule update which tracks the same data type change. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Distinguish between UnitId and InstalledUnitId.Edward Z. Yang2016-10-081-5/+9
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* The Backpack patch.Edward Z. Yang2016-10-082-33/+101
| | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This patch implements Backpack for GHC. It's a big patch but I've tried quite hard to keep things, by-in-large, self-contained. The user facing specification for Backpack can be found at: https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst A guide to the implementation can be found at: https://github.com/ezyang/ghc-proposals/blob/backpack-impl/proposals/0000-backpack-impl.rst Has a submodule update for Cabal, as well as a submodule update for filepath to handle more strict checking of cabal-version. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin, simonmar, bgamari, goldfire Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1482
* Exclude Cabal PackageTests from gen_contents_index.Edward Z. Yang2016-10-081-1/+2
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>