summaryrefslogtreecommitdiff
path: root/compiler/backpack
Commit message (Collapse)AuthorAgeFilesLines
* Refactor coercion holesSimon Peyton Jones2017-12-211-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | In fixing Trac #14584 I found that it would be /much/ more convenient if a "hole" in a coercion (much like a unification variable in a type) acutally had a CoVar associated with it rather than just a Unique. Then I can ask what the free variables of a coercion is, and get a set of CoVars including those as-yet-un-filled in holes. Once that is done, it makes no sense to stuff coercion holes inside UnivCo. They were there before so we could know the kind and role of a "hole" coercion, but once there is a CoVar we can get that info from the CoVar. So I removed HoleProv from UnivCoProvenance and added HoleCo to Coercion. In summary: * Add HoleCo to Coercion and remove HoleProv from UnivCoProvanance * Similarly in IfaceCoercion * Make CoercionHole have a CoVar in it, not a Unique * Make tyCoVarsOfCo return the free coercion-hole variables as well as the ordinary free CoVars. Similarly, remember to zonk the CoVar in a CoercionHole We could go further, and remove CoercionHole as a distinct type altogther, just collapsing it into HoleCo. But I have not done that yet.
* Levity polymorphic Backpack.Edward Z. Yang2017-10-161-0/+2
| | | | | | | | | | | | | | | | | | | | | This patch makes it possible to specify non * kinds of abstract data types in signatures, so you can have levity polymorphism through Backpack, without the runtime representation constraint! Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: andrewthad, bgamari, austin, goldfire Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie GHC Trac Issues: #13955 Differential Revision: https://phabricator.haskell.org/D3825
* Track the order of user-written tyvars in DataConRyan Scott2017-10-031-1/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | After typechecking a data constructor's type signature, its type variables are partitioned into two distinct groups: the universally quantified type variables and the existentially quantified type variables. Then, when prompted for the type of the data constructor, GHC gives this: ```lang=haskell MkT :: forall <univs> <exis>. (...) ``` For H98-style datatypes, this is a fine thing to do. But for GADTs, this can sometimes produce undesired results with respect to `TypeApplications`. For instance, consider this datatype: ```lang=haskell data T a where MkT :: forall b a. b -> T a ``` Here, the user clearly intended to have `b` be available for visible type application before `a`. That is, the user would expect `MkT @Int @Char` to be of type `Int -> T Char`, //not// `Char -> T Int`. But alas, up until now that was not how GHC operated—regardless of the order in which the user actually wrote the tyvars, GHC would give `MkT` the type: ```lang=haskell MkT :: forall a b. b -> T a ``` Since `a` is universal and `b` is existential. This makes predicting what order to use for `TypeApplications` quite annoying, as demonstrated in #11721 and #13848. This patch cures the problem by tracking more carefully the order in which a user writes type variables in data constructor type signatures, either explicitly (with a `forall`) or implicitly (without a `forall`, in which case the order is inferred). This is accomplished by adding a new field `dcUserTyVars` to `DataCon`, which is a subset of `dcUnivTyVars` and `dcExTyVars` that is permuted to the order in which the user wrote them. For more details, refer to `Note [DataCon user type variables]` in `DataCon.hs`. An interesting consequence of this design is that more data constructors require wrappers. This is because the workers always expect the first arguments to be the universal tyvars followed by the existential tyvars, so when the user writes the tyvars in a different order, a wrapper type is needed to swizzle the tyvars around to match the order that the worker expects. For more details, refer to `Note [Data con wrappers and GADT syntax]` in `MkId.hs`. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonpj Reviewed By: goldfire, simonpj Subscribers: ezyang, goldfire, rwbarton, thomie GHC Trac Issues: #11721, #13848 Differential Revision: https://phabricator.haskell.org/D3687
* compiler: introduce custom "GhcPrelude" PreludeHerbert Valerio Riedel2017-09-194-0/+8
| | | | | | | | | | | | | | | | | | This switches the compiler/ component to get compiled with -XNoImplicitPrelude and a `import GhcPrelude` is inserted in all modules. This is motivated by the upcoming "Prelude" re-export of `Semigroup((<>))` which would cause lots of name clashes in every modulewhich imports also `Outputable` Reviewers: austin, goldfire, bgamari, alanz, simonmar Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie, mpickering, bgamari Differential Revision: https://phabricator.haskell.org/D3989
* Preserve CoVar uniques during pretty printingRichard Eisenberg2017-07-271-0/+1
| | | | Previously, we did this for Types, but not for Coercions.
* Make module membership on ModuleGraph fasterBartosz Nitka2017-07-181-2/+3
| | | | | | | | | | | | | | | | | | | When loading/reloading with a large number of modules (>5000) the cost of linear lookups becomes significant. The changes here made `:reload` go from 6s to 1s on my test case. The bottlenecks were `needsLinker` in `DriverPipeline` and `getModLoop` in `GhcMake`. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie, rwbarton Differential Revision: https://phabricator.haskell.org/D3703
* Revert "Make module membership on ModuleGraph faster"Ben Gamari2017-06-271-3/+2
| | | | | | I had not intended on merging this. This reverts commit b0708588e87554899c2efc80a2d3eba353dbe926.
* Make module membership on ModuleGraph fasterBartosz Nitka2017-06-271-2/+3
| | | | | | | | | | | | | | | | | | | When loading/reloading with a large number of modules (>5000) the cost of linear lookups becomes significant. The changes here made `:reload` go from 6s to 1s on my test case. The bottlenecks were `needsLinker` in `DriverPipeline` and `getModLoop` in `GhcMake`. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3646
* Udate hsSyn AST to use Trees that GrowAlan Zimmerman2017-06-062-4/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Compile modules that are needed by template haskell, even with -fno-code.Douglas Wilson2017-05-201-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch relates to Trac #8025 The goal here is to enable typechecking of packages that contain some template haskell. Prior to this patch, compilation of a package with -fno-code would fail if any functions in the package were called from within a splice. downsweep is changed to do an additional pass over the modules, targetting any ModSummaries transitively depended on by a module that has LangExt.TemplateHaskell enabled. Those targeted modules have hscTarget changed from HscNothing to the default target of the platform. There is a small change to the prevailing_target logic to enable this. A simple test is added. I have benchmarked with and without a patched haddock (available:https://github.com/duog/haddock/tree/wip-no-explicit-th-compi lation). Running cabal haddock on the wreq package results in a 25% speedup on my machine: time output from patched cabal haddock: real 0m5.780s user 0m5.304s sys 0m0.496s time output from unpatched cabal haddock: real 0m7.712s user 0m6.888s sys 0m0.736s Reviewers: austin, bgamari, ezyang Reviewed By: bgamari Subscribers: bgamari, DanielG, rwbarton, thomie GHC Trac Issues: #8025 Differential Revision: https://phabricator.haskell.org/D3441
* Print warnings on parser failures (#12610).Dave Laing2017-05-151-1/+1
| | | | | | | | | | | | | | Test Plan: validate Reviewers: austin, bgamari, simonmar, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, thomie GHC Trac Issues: #12610 Differential Revision: https://phabricator.haskell.org/D3584
* Update Cabal submodule, with necessary wibbles.Edward Z. Yang2017-04-261-2/+1
| | | | | | | | | | | | Test Plan: validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3501
* Typos in comments [ci skip]Gabor Greif2017-03-301-1/+1
|
* Print out sub-libraries of packages more nicely.Edward Z. Yang2017-03-021-0/+2
| | | | | | | | | | | | | | | | | | Previously, we would print out the munged package name which looked like z-bkpcabal01-z-p-0.1.0.0. Now it looks like: bkpcabal01-0.1.0.0:p. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, bgamari, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3235
* Properly represent abstract classes in Class and IfaceDeclEdward Z. Yang2017-03-021-7/+11
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Previously, abstract classes looked very much like normal classes, except that they happened to have no methods, superclasses or ATs, and they came from boot files. This patch gives abstract classes a proper representation in Class and IfaceDecl, by moving the things which are never defined for abstract classes into ClassBody/IfaceClassBody. Because Class is abstract, this change had ~no disruption to any of the code in GHC; if you ask about the methods of an abstract class, we'll just give you an empty list. This also fixes a bug where abstract type classes were incorrectly treated as representationally injective (they're not!) Fixes #13347, and a TODO in the code. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, bgamari, austin Subscribers: goldfire, thomie Differential Revision: https://phabricator.haskell.org/D3236
* Improve pretty-printing of typesSimon Peyton Jones2017-02-281-2/+2
| | | | | | | | | | | | | | | | | | | | | | | When doing debug-printing it's really important that the free vars of a type are printed with their uniques. The IfaceTcTyVar thing was a stab in that direction, but it only worked for TcTyVars, not TyVars. This patch does it properly, by keeping track of the free vars of the type when translating Type -> IfaceType, and passing that down through toIfaceTypeX. Then when we find a variable, look in that set, and translate it to IfaceFreeTyVar if so. (I renamed IfaceTcTyVar to IfaceFreeTyVar.) Fiddly but not difficult. Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3201
* Clear import path in --backpack mode to not accidentally pick up source files.Edward Z. Yang2017-02-271-0/+2
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Treat all TyCon with hole names as skolem abstract.Edward Z. Yang2017-02-261-1/+1
| | | | | | | | | | | | | | | Summary: Fixes #13335. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: goldfire, austin, simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3211
* Record full FieldLabel in ifConFields.Edward Z. Yang2017-02-241-9/+4
| | | | | | | | | | | | | | | | | | | | | | Summary: The previous implementation tried to be "efficient" by storing field names once in IfaceConDecls, and only just enough information for us to reconstruct the FieldLabel. But this came at a bit of code complexity cost. This patch undos the optimization, instead storing a full FieldLabel at each data constructor. Consequently, this fixes bugs #12699 and #13250. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: adamgundry, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3174
* Include OverloadedRecordFields selectors in NameShape.Edward Z. Yang2017-02-231-1/+1
| | | | | | | | | | | | | | | Summary: Fixes #13323. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3175
* Have --backpack complain if multiple files are passed.Edward Z. Yang2017-02-231-2/+5
| | | | | | | | | | | | | | | Summary: At the moment it silently swallows the actual arguments; not good! Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: rwbarton, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3173
* Type-indexed TypeableBen Gamari2017-02-181-0/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This at long last realizes the ideas for type-indexed Typeable discussed in A Reflection on Types (#11011). The general sketch of the project is described on the Wiki (Typeable/BenGamari). The general idea is that we are adding a type index to `TypeRep`, data TypeRep (a :: k) This index allows the typechecker to reason about the type represented by the `TypeRep`. This index representation mechanism is exposed as `Type.Reflection`, which also provides a number of patterns for inspecting `TypeRep`s, ```lang=haskell pattern TRFun :: forall k (fun :: k). () => forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun pattern TRApp :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t -- | Pattern match on a type constructor. pattern TRCon :: forall k (a :: k). TyCon -> TypeRep a -- | Pattern match on a type constructor including its instantiated kind -- variables. pattern TRCon' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a ``` In addition, we give the user access to the kind of a `TypeRep` (#10343), typeRepKind :: TypeRep (a :: k) -> TypeRep k Moreover, all of this plays nicely with 8.2's levity polymorphism, including the newly levity polymorphic (->) type constructor. Library changes --------------- The primary change here is the introduction of a Type.Reflection module to base. This module provides access to the new type-indexed TypeRep introduced in this patch. We also continue to provide the unindexed Data.Typeable interface, which is simply a type synonym for the existentially quantified SomeTypeRep, data SomeTypeRep where SomeTypeRep :: TypeRep a -> SomeTypeRep Naturally, this change also touched Data.Dynamic, which can now export the Dynamic data constructor. Moreover, I removed a blanket reexport of Data.Typeable from Data.Dynamic (which itself doesn't even import Data.Typeable now). We also add a kind heterogeneous type equality type, (:~~:), to Data.Type.Equality. Implementation -------------- The implementation strategy is described in Note [Grand plan for Typeable] in TcTypeable. None of it was difficult, but it did exercise a number of parts of the new levity polymorphism story which had not yet been exercised, which took some sorting out. The rough idea is that we augment the TyCon produced for each type constructor with information about the constructor's kind (which we call a KindRep). This allows us to reconstruct the monomorphic result kind of an particular instantiation of a type constructor given its kind arguments. Unfortunately all of this takes a fair amount of work to generate and send through the compilation pipeline. In particular, the KindReps can unfortunately get quite large. Moreover, the simplifier will float out various pieces of them, resulting in numerous top-level bindings. Consequently we mark the KindRep bindings as noinline, ensuring that the float-outs don't make it into the interface file. This is important since there is generally little benefit to inlining KindReps and they would otherwise strongly affect compiler performance. Performance ----------- Initially I was hoping to also clear up the remaining holes in Typeable's coverage by adding support for both unboxed tuples (#12409) and unboxed sums (#13276). While the former was fairly straightforward, the latter ended up being quite difficult: while the implementation can support them easily, enabling this support causes thousands of Typeable bindings to be emitted to the GHC.Types as each arity-N sum tycon brings with it N promoted datacons, each of which has a KindRep whose size which itself scales with N. Doing this was simply too expensive to be practical; consequently I've disabled support for the time being. Even after disabling sums this change regresses compiler performance far more than I would like. In particular there are several testcases in the testsuite which consist mostly of types which regress by over 30% in compiler allocations. These include (considering the "bytes allocated" metric), * T1969: +10% * T10858: +23% * T3294: +19% * T5631: +41% * T6048: +23% * T9675: +20% * T9872a: +5.2% * T9872d: +12% * T9233: +10% * T10370: +34% * T12425: +30% * T12234: +16% * 13035: +17% * T4029: +6.1% I've spent quite some time chasing down the source of this regression and while I was able to make som improvements, I think this approach of generating Typeable bindings at time of type definition is doomed to give us unnecessarily large compile-time overhead. In the future I think we should consider moving some of all of the Typeable binding generation logic back to the solver (where it was prior to 91c6b1f54aea658b0056caec45655475897f1972). I've opened #13261 documenting this proposal.
* Fix #13214 by correctly setting up dep_orphs for signatures.Edward Z. Yang2017-02-111-1/+23
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Prior to this, I hadn't thought about orphan handling at all. This commit implements the semantics that if a signature (transitively) imports an orphan instance, that instance is considered in scope no matter what the implementing module is. (As it turns out, this is the semantics that falls out when orphans are recorded transitively.) This patch fixes a few bugs: 1. Put semantic modules in dep_orphs rather than identity modules. 2. Don't put the implementing module in dep_orphs when merging signatures (this is a silly bug that happened because we were reusing calculateAvails, which is designed for imports. It mostly works for signature merging, except this case.) 3. When renaming a signature, blast in the orphans of the implementing module inside Dependencies. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3095
* Ditch static flagsSylvain Henry2017-02-021-5/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | This patch converts the 4 lasting static flags (read from the command line and unsafely stored in immutable global variables) into dynamic flags. Most use cases have been converted into reading them from a DynFlags. In cases for which we don't have easy access to a DynFlags, we read from 'unsafeGlobalDynFlags' that is set at the beginning of each 'runGhc'. It's not perfect (not thread-safe) but it is still better as we can set/unset these 4 flags before each run when using GHC API. Updates haddock submodule. Rebased and finished by: bgamari Test Plan: validate Reviewers: goldfire, erikd, hvr, austin, simonmar, bgamari Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2839 GHC Trac Issues: #8440
* Join pointsLuke Maurer2017-02-011-2/+2
| | | | | | | | | | | | | | | | | | | This major patch implements Join Points, as described in https://ghc.haskell.org/trac/ghc/wiki/SequentCore. You have to read that page, and especially the paper it links to, to understand what's going on; but it is very cool. It's Luke Maurer's work, but done in close collaboration with Simon PJ. This Phab is a squash-merge of wip/join-points branch of http://github.com/lukemaurer/ghc. There are many, many interdependent changes. Reviewers: goldfire, mpickering, bgamari, simonmar, dfeuer, austin Subscribers: simonpj, dfeuer, mpickering, Mikolaj, thomie Differential Revision: https://phabricator.haskell.org/D2853
* Typos in comments [ci skip]Gabor Greif2017-01-261-1/+1
|
* Rewrite Backpack comments on never-exported TyThings.Edward Z. Yang2017-01-221-71/+42
| | | | | | | | | | | | | | | | | | | | | Summary: While thesing, I realized this part of the implementation didn't make very much sense, so I started working on some documentation updates to try to make things more explainable. The new docs are organized around the idea of a "never exported TyThing" (a non-implicit TyThing that never occurs in the export list of a module). I also removed some outdated information that predated the change of ModIface to store Names rather than OccNames. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Reviewers: simonpj, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2989
* Fix handling of closed type families in Backpack.Edward Z. Yang2017-01-111-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: A few related problems: - CoAxioms, like DFuns, are implicit and never exported, so we have to make sure we treat them the same way as DFuns: in RnModIface we need to rename references to them with rnIfaceImplicit and in mergeSignatures we need to NOT check them directly for compatibility (the test on the type family will do this check for us.) - But actually, we weren't checking if the axioms WERE consistent. This is because we were forwarding all embedded CoAxiom references in the type family TyThing to the merged version, but that reference was what checkBootDeclM was using as a comparison point. This is similar to a problem we saw with DFuns. To fix this, I refactored the handling of implicit entities in TcIface for Backpack. See Note [The implicit TypeEnv] for the gory details. Instead of passing the TypeEnv around explicitly, we stuffed it in IfLclEnv. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, simonpj, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2928
* Revamp Backpack/hs-boot handling of type class signatures.Edward Z. Yang2017-01-111-7/+10
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: A basket of fixes and improvements: - The permissible things that one can write in a type class definition in an hsig file has been reduced to encompass the following things: - Methods - Default method signatures (but NOT implementation) - MINIMAL pragma It is no longer necessary nor encouraged to specify that a method has a default if it is mentioned in a MINIMAL pragma; the MINIMAL pragma is assumed to provide the base truth as to what methods need to be implemented when writing instances of a type class. - Handling of default method signatures in hsig was previously buggy, as these identifiers were not exported, so we now treat them similarly to DFuns. - Default methods are merged, where methods with defaults override those without. - MINIMAL pragmas are merged by ORing together pragmas. - Matching has been relaxed: a method with a default can be used to fill a signature which did not declare the method as having a default, and a more relaxed MINIMAL pragma can be used (we check if the signature pragma implies the final implementation pragma, on the way fixing a bug with BooleanFormula.implies, see #13073) Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2925 GHC Trac Issues: #13041
* Support for using only partial pieces of included signatures.Edward Z. Yang2017-01-114-31/+129
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Generally speaking, it's not possible to "hide" a requirement from a package you include, because if there is some module relying on that requirement, well, you can't just wish it out of existence. However, some packages don't have any modules. For these, we can validly thin out requirements; indeed, this is very convenient if someone has published a large signature package but you only want some of the definitions. This patchset tweaks the interpretation of export lists in signatures: in particular, they no longer need to refer to entities that are defined locally; they range over both the current signature as well as any signatures that were inherited from signature packages (defined by having zero exposed modules.) In the process of doing this, I cleaned up a number of other things: * rnModIface and rnModExports now report errors that occurred during renaming and can propagate these to the TcM monad. This is important because in the current semantics, you can thin out a type which is referenced by a value you keep; in this situation, we need to error (to ensure that all types in signatures are rooted, so that we can determine their identities). * I ended up introducing a new construct 'dependency signature; to bkp files, to make it easier to tell if we were depending on a signature package. It's not difficult for Cabal to figure this out (I already have a patch for it.) Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2904 GHC Trac Issues: #12994
* Support for abi-depends for computing shadowing.Edward Z. Yang2016-12-211-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This is a complete fix based off of ed7af26606b3a605a4511065ca1a43b1c0f3b51d for handling shadowing and out-of-order -package-db flags simultaneously. The general strategy is we first put all databases together, overriding packages as necessary. Once this is done, we successfully prune out broken packages, including packages which depend on a package whose ABI differs from the ABI we need. Our check gracefully degrades in the absence of abi-depends, as we only check deps which are recorded in abi-depends. Contains time and Cabal submodule update. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: niteria, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2846 GHC Trac Issues: #12485
* Improve pretty-printing of typesSimon Peyton Jones2016-11-251-1/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | In this commit commit 6c0f10fac767c49b65ed71e8eb8e78ca4f9062d5 Author: Ben Gamari <bgamari.foss@gmail.com> Date: Sun Nov 13 16:17:37 2016 -0500 Kill Type pretty-printer we switched to pretty-printing a type by converting it to an IfaceType and pretty printing that. Very good. This patch fixes two things * The new story is terrible for debug-printing with -ddump-tc-trace, because all the extra info in an open type was discarded ty the conversion to IfaceType. This patch adds IfaceTcTyVar to IfaceType, to carry a TcTyVar in debug situations. Quite an easy change, happily. These things never show up in interface files. * Now that we are going via IfaceType, it's essential to tidy before converting; otherwise forall k_23 k_34. blah is printed as forall k k. blah which is very unhelpful. Again this only shows up in debug printing.
* API Annotations: make all ModuleName LocatedAlan Zimmerman2016-11-032-4/+8
| | | | | | | | | | | | | | | | | | Summary: This also changes the backpack Renaming type to use a Maybe for the renameTo field, to more accurately reflect the parsed source. Updates haddock submodule to match AST changes Test Plan: ./validate Reviewers: ezyang, bgamari, austin Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2670
* Zap redundant importsGabor Greif2016-10-301-2/+0
|
* Refactoring: Delete copied function in backpack/NameShapeMatthew Pickering2016-10-221-25/+2
| | | | | | | | | | | | | Also moved a few utility functions which work with Avails into the Avail module to avoid import loops and increase discoverability. Reviewers: austin, bgamari, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2629
* Add and use a new dynamic-library-dirs field in the ghc-pkg infoDuncan Coutts2016-10-211-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Only delete instances when merging when there is an exact match.Edward Z. Yang2016-10-201-2/+3
| | | | | | | | | | | | | | | | | | | Summary: Previously, we deleted if the heads matched, which meant that we effectively were picking an arbitrary instance if there were incompatible instances. The new behavior makes more sense, although without incoherent instances you are unlikely to be able to do anything useful with the instances. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2596
* Clean up handling of known-key Names in interface filesBen Gamari2016-10-131-18/+48
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Fix buildCsongor Kiss2016-10-082-3/+3
| | | | | | | | | | | | | | | | | - interaction between backpack and export list refactoring introduced a few syntax errors, and constructor arity mismatches - CPP macro used in backpack was not accepted by clang because of extraneous whitespace Signed-off-by: Csongor Kiss <kiss.csongor.kiss@gmail.com> Reviewers: austin, bgamari, mpickering Reviewed By: mpickering Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2582
* Make InstalledUnitId be ONLY a FastString.Edward Z. Yang2016-10-081-8/+19
| | | | | | | | | | | | | | | | | | | | | 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/+8
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* The Backpack patch.Edward Z. Yang2016-10-084-0/+1749
| | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Delete ShPackageKey for now.Edward Z. Yang2015-10-101-241/+0
| | | | Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Make derived names deterministicBartosz Nitka2015-09-211-42/+3
| | | | | | | | | | | | | | | | | | | | | | The names of auxiliary bindings end up in the interface file, and since uniques are nondeterministic, we end up with nondeterministic interface files. This uses the package and module name in the generated name, so I believe it should avoid problems from #7947 and be deterministic as well. The generated names look like this now: `$cLrlbmVwI3gpI8G2E6Hg3mO` and with `-ppr-debug`: `$c$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String`. Reviewed By: simonmar, austin, ezyang Differential Revision: https://phabricator.haskell.org/D1133 GHC Trac Issues: #4012
* Library names, with Cabal submodule updateEdward Z. Yang2015-07-231-0/+280
A library name is a package name, package version, and hash of the version names of all textual dependencies (i.e. packages which were included.) A library name is a coarse approximation of installed package IDs, which are suitable for inclusion in package keys (you don't want to put an IPID in a package key, since it means the key will change any time the source changes.) - We define ShPackageKey, which is the semantic object which is hashed into a PackageKey. You can use 'newPackageKey' to hash a ShPackageKey to a PackageKey - Given a PackageKey, we can lookup its ShPackageKey with 'lookupPackageKey'. The way we can do this is by consulting the 'pkgKeyCache', which records a reverse mapping from every hash to the ShPackageKey. This means that if you load in PackageKeys from external sources (e.g. interface files), you also need to load in a mapping of PackageKeys to their ShPackageKeys so we can populate the cache. - We define a 'LibraryName' which encapsulates the full depenency resolution that Cabal may have selected; this is opaque to GHC but can be used to distinguish different versions of a package. - Definite packages don't have an interesting PackageKey, so we rely on Cabal to pass them to us. - We can pretty-print package keys while displaying the instantiation, but it's not wired up to anything (e.g. the Outputable instance of PackageKey). Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1056 GHC Trac Issues: #10566