summaryrefslogtreecommitdiff
path: root/compiler/ghci/RtClosureInspect.hs
Commit message (Collapse)AuthorAgeFilesLines
* Module hierarchy: StgToCmm (#13009)Sylvain Henry2019-09-101-2/+2
| | | | | | Add StgToCmm module hierarchy. Platform modules that are used in several other places (NCG, LLVM codegen, Cmm transformations) are put into GHC.Platform.
* Remove unnecessary uses of UnboxedTuples pragma (see #13101 / #15454)Michael Sloan2019-04-011-1/+1
| | | | Also removes a couple unnecessary MagicHash pragmas
* Improve error recovery in the typecheckerSimon Peyton Jones2019-03-161-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Issue #16418 showed that we were carrying on too eagerly after a bogus type signature was identified (a bad telescope in fact), leading to a subsequent crash. This led me in to a maze of twisty little passages in the typechecker's error recovery, and I ended up doing some refactoring in TcRnMonad. Some specfifics * TcRnMonad.try_m is now called attemptM. * I switched the order of the result pair in tryTc, to make it consistent with other similar functions. * The actual exception used in the Tc monad is irrelevant so, to avoid polluting type signatures, I made tcTryM, a simple wrapper around tryM, and used it. The more important changes are in * TcSimplify.captureTopConstraints, where we should have been calling simplifyTop rather than reportUnsolved, so that levity defaulting takes place properly. * TcUnify.emitResidualTvConstraint, where we need to set the correct status for a new implication constraint. (Previously we ended up with an Insoluble constraint wrapped in an Unsolved implication, which meant that insolubleWC gave the wrong answer.
* Update Trac ticket URLs to point to GitLabRyan Scott2019-03-151-1/+1
| | | | | This moves all URL references to Trac tickets to their corresponding GitLab counterparts.
* Add AnonArgFlag to FunTySimon Peyton Jones2019-02-231-3/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The big payload of this patch is: Add an AnonArgFlag to the FunTy constructor of Type, so that (FunTy VisArg t1 t2) means (t1 -> t2) (FunTy InvisArg t1 t2) means (t1 => t2) The big payoff is that we have a simple, local test to make when decomposing a type, leading to many fewer calls to isPredTy. To me the code seems a lot tidier, and probably more efficient (isPredTy has to take the kind of the type). See Note [Function types] in TyCoRep. There are lots of consequences * I made FunTy into a record, so that it'll be easier when we add a linearity field, something that is coming down the road. * Lots of code gets touched in a routine way, simply because it pattern matches on FunTy. * I wanted to make a pattern synonym for (FunTy2 arg res), which picks out just the argument and result type from the record. But alas the pattern-match overlap checker has a heart attack, and either reports false positives, or takes too long. In the end I gave up on pattern synonyms. There's some commented-out code in TyCoRep that shows what I wanted to do. * Much more clarity about predicate types, constraint types and (in particular) equality constraints in kinds. See TyCoRep Note [Types for coercions, predicates, and evidence] and Note [Constraints in kinds]. This made me realise that we need an AnonArgFlag on AnonTCB in a TyConBinder, something that was really plain wrong before. See TyCon Note [AnonTCB InivsArg] * When building function types we must know whether we need VisArg (mkVisFunTy) or InvisArg (mkInvisFunTy). This turned out to be pretty easy in practice. * Pretty-printing of types, esp in IfaceType, gets tidier, because we were already recording the (->) vs (=>) distinction in an ad-hoc way. Death to IfaceFunTy. * mkLamType needs to keep track of whether it is building (t1 -> t2) or (t1 => t2). See Type Note [mkLamType: dictionary arguments] Other minor stuff * Some tidy-up in validity checking involving constraints; Trac #16263
* Support printing `integer-simple` Integers in GHCiAlec Theriault2019-01-161-1/+31
| | | | | | | | | | This means that `:p` no longer leaks the implementation details of `Integer` with `integer-simple`. The `print037` test case should exercise all possible code paths for GHCi's code around printing `Integer`s (both in `integer-simple` and `integer-gmp`). `ghc` the package now also has a Cabal `integer-simple` flag (like the `integer-gmp` one).
* ghci: Fix unused binder warnings when building with integer-simpleBen Gamari2018-12-171-2/+0
|
* Fix unused-import warningsDavid Eichmann2018-11-221-3/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch fixes a fairly long-standing bug (dating back to 2015) in RdrName.bestImport, namely commit 9376249b6b78610db055a10d05f6592d6bbbea2f Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Wed Oct 28 17:16:55 2015 +0000 Fix unused-import stuff in a better way In that patch got the sense of the comparison back to front, and thereby failed to implement the unused-import rules described in Note [Choosing the best import declaration] in RdrName This led to Trac #13064 and #15393 Fixing this bug revealed a bunch of unused imports in libraries; the ones in the GHC repo are part of this commit. The two important changes are * Fix the bug in bestImport * Modified the rules by adding (a) in Note [Choosing the best import declaration] in RdrName Reason: the previosu rules made Trac #5211 go bad again. And the new rule (a) makes sense to me. In unravalling this I also ended up doing a few other things * Refactor RnNames.ImportDeclUsage to use a [GlobalRdrElt] for the things that are used, rather than [AvailInfo]. This is simpler and more direct. * Rename greParentName to greParent_maybe, to follow GHC naming conventions * Delete dead code RdrName.greUsedRdrName Bumps a few submodules. Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27 Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5312
* Fix BLACKHOLE inspection in RtClosureInspectÖmer Sinan Ağacan2018-10-151-4/+16
| | | | | | | | | | | | | | | | | | | | | | | | | | When inspecing a BLACKHOLE if the BLACKHOLE points to a TSO or a BLOCKING_QUEUE we should return a suspension to the BLACKHOLE itself (instead of returning a suspension to the indirectee). The reason is because in the debugger when we want to evaluate this term we need to enter the BLACKHOLE and not to the TSO or BLOCKING_QUEUE. See the runtime panic caused by this in #8316. Note that while with this patch we do the right thing to evaluate thunks in GHCi, evaluating thunks that are owned by the evaluator thread in a breakpoint will cause a deadlock as we don't release the breakMVar, which is what blocks the evaluator thread from continuing with evaluation. So the GHCi thread will enter the BLACKHOLE, but owner of the BLACKHOLE is also blocked. Reviewers: simonmar, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #8316 Differential Revision: https://phabricator.haskell.org/D5179
* Coercion Quantificationningning2018-09-151-2/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch corresponds to #15497. According to https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase2, we would like to have coercion quantifications back. This will allow us to migrate (~#) to be homogeneous, instead of its current heterogeneous definition. This patch is (lots of) plumbing only. There should be no user-visible effects. An overview of changes: - Both `ForAllTy` and `ForAllCo` can quantify over coercion variables, but only in *Core*. All relevant functions are updated accordingly. - Small changes that should be irrelevant to the main task: 1. removed dead code `mkTransAppCo` in Coercion 2. removed out-dated Note Computing a coercion kind and roles in Coercion 3. Added `Eq4` in Note Respecting definitional equality in TyCoRep, and updated `mkCastTy` accordingly. 4. Various updates and corrections of notes and typos. - Haddock submodule needs to be changed too. Acknowledgments: This work was completed mostly during Ningning Xie's Google Summer of Code, sponsored by Google. It was advised by Richard Eisenberg, supported by NSF grant 1704041. Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari, hvr, erikd, simonmar Subscribers: RyanGlScott, monoidal, rwbarton, carter GHC Trac Issues: #15497 Differential Revision: https://phabricator.haskell.org/D5054
* Remove knot-tying bug in TcHsSyn.zonkTyVarOccSimon Peyton Jones2018-08-311-2/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | There was a subtle knot-tying bug in TcHsSyn.zonkTyVarOcc, revealed in Trac #15552. I fixed it by * Eliminating the short-circuiting optimisation in zonkTyVarOcc, instead adding a finite map to get sharing of zonked unification variables. See Note [Sharing when zonking to Type] in TcHsSyn * On the way I /added/ the short-circuiting optimisation to TcMType.zonkTcTyVar, which has no such problem. This turned out (based on non-systematic measurements) to be a modest win. See Note [Sharing in zonking] in TcMType On the way I renamed some of the functions in TcHsSyn: * Ones ending in "X" (like zonkTcTypeToTypeX) take a ZonkEnv * Ones that do not end in "x" (like zonkTcTypeToType), don't. Instead they whiz up an empty ZonkEnv.
* Clean up TcHsSyn.zonkEnvSimon Peyton Jones2018-08-241-12/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Triggered by Trac #15552, I'd been looking at ZonkEnv in TcHsSyn. This patch does some minor refactoring * Make ZonkEnv into a record with named fields, and use them. (I'm planning to add a new field, for TyCons, so this prepares the way.) * Replace UnboundTyVarZonker (a higer order function) with the simpler and more self-descriptive ZonkFlexi data type, below. It's just much more perspicuous and direct, and (I suspect) a tiny bit faster too -- no unknown function calls. data ZonkFlexi -- See Note [Un-unified unification variables] = DefaultFlexi -- Default unbound unificaiton variables to Any | SkolemiseFlexi -- Skolemise unbound unification variables -- See Note [Zonking the LHS of a RULE] | RuntimeUnkFlexi -- Used in the GHCi debugger There was one knock-on effect in the GHCi debugger -- the RuntimeUnkFlexi case. Somehow previously, these RuntimeUnk variables were sometimes getting SystemNames (and hence printed as 'a0', 'a1', etc) and sometimes not (and hence printed as 'a', 'b' etc). I'm not sure precisely why, but the new behaviour seems more uniform, so I just accepted the (small) renaming wibbles in some ghci.debugger tests. I had a quick look at perf: any changes are tiny.
* Turn on MonadFail desugaring by defaultHerbert Valerio Riedel2018-08-071-2/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This contains two commits: ---- Make GHC's code-base compatible w/ `MonadFail` There were a couple of use-sites which implicitly used pattern-matches in `do`-notation even though the underlying `Monad` didn't explicitly support `fail` This refactoring turns those use-sites into explicit case discrimations and adds an `MonadFail` instance for `UniqSM` (`UniqSM` was the worst offender so this has been postponed for a follow-up refactoring) --- Turn on MonadFail desugaring by default This finally implements the phase scheduled for GHC 8.6 according to https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail#Transitionalstrategy This also preserves some tests that assumed MonadFail desugaring to be active; all ghc boot libs were already made compatible with this `MonadFail` long ago, so no changes were needed there. Test Plan: Locally performed ./validate --fast Reviewers: bgamari, simonmar, jrtc27, RyanGlScott Reviewed By: bgamari Subscribers: bgamari, RyanGlScott, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5028
* Fix endian issues in ghc-heapPeter Trommler2018-07-271-3/+6
| | | | | | | | | | | | | | | | | | | | | | In test heap_all arity and n_args were swapped on big endian systems. Take care of endianness when reading parts of a machine word from a `Word`. This fixes one out of 36 failing tests reported in #15399. Test Plan: validate Reviewers: simonmar, bgamari, hvr, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15399 Differential Revision: https://phabricator.haskell.org/D5001
* Support the GHCi debugger with -fexternal-interpreterSimon Marlow2018-07-161-51/+127
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | * All the tests in tests/ghci.debugger now pass with -fexternal-interpreter. These tests are now run with the ghci-ext way in addition to the normal way so we won't break it in the future. * I removed all the unsafeCoerce# calls from RtClosureInspect. Yay! The main changes are: * New messages: GetClosure and Seq. GetClosure is a remote interface to GHC.Exts.Heap.getClosureData, which required Binary instances for various datatypes. Fortunately this wasn't too painful thanks to DeriveGeneric. * No cheating by unsafeCoercing values when printing them. Now we have to turn the Closure representation back into the native representation when printing Int, Float, Double, Integer and Char. Of these, Integer was the most painful - we now have a dependency on integer-gmp due to needing access to the representation. * Fixed a bug in rts/Heap.c - it was bogusly returning stack content as pointers for an AP_STACK closure. Test Plan: * `cd testsuite/tests/ghci.debugger && make` * validate Reviewers: bgamari, patrickdoc, nomeata, angerman, hvr, erikd, goldfire Subscribers: alpmestan, snowleopard, rwbarton, thomie, carter GHC Trac Issues: #13184 Differential Revision: https://phabricator.haskell.org/D4955
* Fix nptr field alignment in RtClosureInspectÖmer Sinan Ağacan2018-07-041-4/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | `extractSubTerms` (which is extracting pointer and non-pointer fields of a closure) was computing the alignment incorrectly when aligning a 64-bit value (e.g. a Double) on i386 by aligning it to 64-bits instead of to word size (32-bits). This is documented in `mkVirtHeapOffsetsWithPadding`: > Align the start offset (eg, 2-byte value should be 2-byte aligned). > But not more than to a word. Fixes #15061 Test Plan: Validated on both 32-bit and 64-bit. 32-bit fails with various unrelated stat failures, but no actual test failures. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15061 Differential Revision: https://phabricator.haskell.org/D4906
* RtClosureInspect: add some docs, remove unused stuffÖmer Sinan Ağacan2018-07-041-71/+58
| | | | | | | | | | | | Details are not documented, only the high-level functions Reviewers: simonpj, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4911
* Add HeapView functionalityPatrick Dougherty2018-05-201-163/+96
| | | | | | | | | | | | | | | | | | | | | This pulls parts of Joachim Breitner's ghc-heap-view library inside GHC. The bits added are the C hooks into the RTS and a basic Haskell wrapper to these C hooks. The main reason for these to be added to GHC proper is that the code needs to be kept in sync with the closure types defined by the RTS. It is expected that the version of HeapView shipped with GHC will always work with that version of GHC and that extra functionality can be layered on top with a library like ghc-heap-view distributed via Hackage. Test Plan: validate Reviewers: simonmar, hvr, nomeata, austin, Phyx, bgamari, erikd Reviewed By: bgamari Subscribers: carter, patrickdoc, tmcgilchrist, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3055
* Less Tc inside simplCore (Phase 1 for #14391)Artem Pelenitsyn2018-05-151-4/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Simplifier depends on typechecker in two points: `thNameToGhcName` (`lookupThName_maybe`, in particular) and `lookupGlobal`. We want to cut the ties in two steps. 1. (Presented in this commit), reimplement both functions in a way that doesn't use typechecker. 2. (Should follow), do code moving: a) `lookupGlobal` should go in some typechecker-free place; b) `thNameToGhcName` should leave simplifier, because it is not used there at all (probably, it should be placed somewhere where `GhcPlugins` can see it -- this is suggested by Joachim on Trac). Details ======= We redesigned lookup interface a bit so that it exposes some `IO`-equivalents of `Tc`-features in use. First, `CoreMonad.hs` still calls `lookupGlobal` which is no longer bound to the typechecker monad, but still resides in `TcEnv.hs` — it should be moved out of Tc-land at some point (“Phase 2”) in the future in order to achieve its part of the #14391's goal. Second, `lookupThName_maybe` is eliminated from `CoreMonad.hs` completely; this already achieves its part of the goal of #14391. Its client, though, `thNameToGhcName`, is better to be moved in the future also, for it is not used in the `CoreMonad.hs` (or anywhere else) anyway. Joachim suggested “any module reexported by GhcPlugins (or maybe even that module itself)”. As a side goal, we removed `initTcForLookup` which was instrumental for the past version of `lookupGlobal`. This, in turn, called for pushing some more parts of the lookup interface from the `Tc`-monad to `IO`, most notably, adding `IO`-version of `lookupOrig` and pushing `dataConInfoPtrToName` to `IO`. The `lookupOrig` part, in turn, triggered a slight redesign of name cache updating interface: we now have both, `updNameCacheIO` and `updNameCacheTc`, both accepting `mod` and `occ` to force them inside, instead of more error-prone outside before. But all these hardly have to do anything with #14391, mere refactoring. Reviewers: simonpj, nomeata, bgamari, hvr Reviewed By: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14391 Differential Revision: https://phabricator.haskell.org/D4503
* Allow packing constructor fieldsMichal Terepeta2017-10-291-29/+60
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* RtClosureInspect: Fix inspecting Char# on 64-bit big-endianJames Clarke2017-10-161-1/+4
| | | | | | | | | | | | | | | | | Char# is represented with a full machine word, whereas Char's Storable instance uses an Int32, so we can't just treat it like a single-element Char array. Instead, read it as an Int and use chr to turn it into a Char. This fixes Trac #11262. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #11262 Differential Revision: https://phabricator.haskell.org/D4089
* compiler: introduce custom "GhcPrelude" PreludeHerbert Valerio Riedel2017-09-191-0/+2
| | | | | | | | | | | | | | | | | | 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
* Add debugPprTypeSimon Peyton Jones2017-08-311-13/+13
| | | | | | | | | | | | | | | | | | | | | | | | | | | We pretty-print a type by converting it to an IfaceType and pretty-printing that. But (a) that's a bit indirect, and (b) delibrately loses information about (e.g.) the kind on the /occurrences/ of a type variable So this patch implements debugPprType, which pretty prints the type directly, with no fancy formatting. It's just used for debugging. I took the opportunity to refactor the debug-pretty-printing machinery a little. In particular, define these functions and use them: ifPprDeubug :: SDoc -> SDOc -> SDoc -- Says what to do with and without -dppr-debug whenPprDebug :: SDoc -> SDoc -- Says what to do with -dppr-debug; without is empty getPprDebug :: (Bool -> SDoc) -> SDoc getPprDebug used to be called sdocPprDebugWith whenPprDebug used to be called ifPprDebug So a lot of files get touched in a very mechanical way
* Fix #13819 by refactoring TypeEqOrigin.uo_thingRichard Eisenberg2017-07-271-2/+2
| | | | | | | | | | | | | | | | | | | | | | The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819
* Deal with exceptions in dsWhenNoErrsSimon Peyton Jones2017-05-041-7/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Gracious me. Ever since this patch commit 374457809de343f409fbeea0a885877947a133a2 Author: Jan Stolarek <jan.stolarek@p.lodz.pl> Date: Fri Jul 11 13:54:45 2014 +0200 Injective type families TcRnMonad.askNoErrs has been wrong. It looked like this askNoErrs :: TcRn a -> TcRn (a, Bool) askNoErrs m = do { errs_var <- newTcRef emptyMessages ; res <- setErrsVar errs_var m ; (warns, errs) <- readTcRef errs_var ; addMessages (warns, errs) ; return (res, isEmptyBag errs) } The trouble comes if 'm' throws an exception in the TcRn monad. Then 'errs_var is never read, so any errors are simply lost. This mistake was then propgated into DsMonad.dsWhenNoErrs, where it gave rise to Trac #13642. Thank to Ryan for narrowing it down so sharply. I did some refactoring, as usual.
* Upgrade UniqSet to a newtypeDavid Feuer2017-03-011-6/+5
| | | | | | | | | | | | | | | | | | | | | The fundamental problem with `type UniqSet = UniqFM` is that `UniqSet` has a key invariant `UniqFM` does not. For example, `fmap` over `UniqSet` will generally produce nonsense. * Upgrade `UniqSet` from a type synonym to a newtype. * Remove unused and shady `extendVarSet_C` and `addOneToUniqSet_C`. * Use cached unique in `tyConsOfType` by replacing `unitNameEnv (tyConName tc) tc` with `unitUniqSet tc`. Reviewers: austin, hvr, goldfire, simonmar, niteria, bgamari Reviewed By: niteria Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3146
* Ditch static flagsSylvain Henry2017-02-021-13/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Update levity polymorphismRichard Eisenberg2017-01-191-26/+23
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit implements the proposal in https://github.com/ghc-proposals/ghc-proposals/pull/29 and https://github.com/ghc-proposals/ghc-proposals/pull/35. Here are some of the pieces of that proposal: * Some of RuntimeRep's constructors have been shortened. * TupleRep and SumRep are now parameterized over a list of RuntimeReps. * This means that two types with the same kind surely have the same representation. Previously, all unboxed tuples had the same kind, and thus the fact above was false. * RepType.typePrimRep and friends now return a *list* of PrimReps. These functions can now work successfully on unboxed tuples. This change is necessary because we allow abstraction over unboxed tuple types and so cannot always handle unboxed tuples specially as we did before. * We sometimes have to create an Id from a PrimRep. I thus split PtrRep * into LiftedRep and UnliftedRep, so that the created Ids have the right strictness. * The RepType.RepType type was removed, as it didn't seem to help with * much. * The RepType.repType function is also removed, in favor of typePrimRep. * I have waffled a good deal on whether or not to keep VoidRep in TyCon.PrimRep. In the end, I decided to keep it there. PrimRep is *not* represented in RuntimeRep, and typePrimRep will never return a list including VoidRep. But it's handy to have in, e.g., ByteCodeGen and friends. I can imagine another design choice where we have a PrimRepV type that is PrimRep with an extra constructor. That seemed to be a heavier design, though, and I'm not sure what the benefit would be. * The last, unused vestiges of # (unliftedTypeKind) have been removed. * There were several pretty-printing bugs that this change exposed; * these are fixed. * We previously checked for levity polymorphism in the types of binders. * But we also must exclude levity polymorphism in function arguments. This is hard to check for, requiring a good deal of care in the desugarer. See Note [Levity polymorphism checking] in DsMonad. * In order to efficiently check for levity polymorphism in functions, it * was necessary to add a new bit of IdInfo. See Note [Levity info] in IdInfo. * It is now safe for unlifted types to be unsaturated in Core. Core Lint * is updated accordingly. * We can only know strictness after zonking, so several checks around * strictness in the type-checker (checkStrictBinds, the check for unlifted variables under a ~ pattern) have been moved to the desugarer. * Along the way, I improved the treatment of unlifted vs. banged * bindings. See Note [Strict binds checks] in DsBinds and #13075. * Now that we print type-checked source, we must be careful to print * ConLikes correctly. This is facilitated by a new HsConLikeOut constructor to HsExpr. Particularly troublesome are unlifted pattern synonyms that get an extra void# argument. * Includes a submodule update for haddock, getting rid of #. * New testcases: typecheck/should_fail/StrictBinds typecheck/should_fail/T12973 typecheck/should_run/StrictPats typecheck/should_run/T12809 typecheck/should_fail/T13105 patsyn/should_fail/UnliftedPSBind typecheck/should_fail/LevPolyBounded typecheck/should_compile/T12987 typecheck/should_compile/T11736 * Fixed tickets: #12809 #12973 #11736 #13075 #12987 * This also adds a test case for #13105. This test case is * "compile_fail" and succeeds, because I want the testsuite to monitor the error message. When #13105 is fixed, the test case will compile cleanly.
* Remove CONSTR_STATICSimon Marlow2016-11-141-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: We currently have two info tables for a constructor * XXX_con_info: the info table for a heap-resident instance of the constructor, It has type CONSTR, or one of the specialised types like CONSTR_1_0 * XXX_static_info: the info table for a static instance of this constructor, which has type CONSTR_STATIC or CONSTR_STATIC_NOCAF. I'm getting rid of the latter, and using the `con_info` info table for both static and dynamic constructors. For rationale and more details see Note [static constructors] in SMRep.hs. I also removed these macros: `isSTATIC()`, `ip_STATIC()`, `closure_STATIC()`, since they relied on the CONSTR/CONSTR_STATIC distinction, and anyway HEAP_ALLOCED() does the same job. Test Plan: validate Reviewers: bgamari, simonpj, austin, gcampax, hvr, niteria, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2690 GHC Trac Issues: #12455
* A collection of type-inference refactorings.Simon Peyton Jones2016-10-211-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch does a raft of useful tidy-ups in the type checker. I've been meaning to do this for some time, and finally made time to do it en route to ICFP. 1. Modify TcType.ExpType to make a distinct data type, InferResult for the Infer case, and consequential refactoring. 2. Define a new function TcUnify.fillInferResult, to fill in an InferResult. It uses TcMType.promoteTcType to promote the type to the level of the InferResult. See TcMType Note [Promoting a type] This refactoring is in preparation for an improvement to typechecking pattern bindings, coming next. I flirted with an elaborate scheme to give better higher rank inference, but it was just too complicated. See TcMType Note [Promotion and higher rank types] 3. Add to InferResult a new field ir_inst :: Bool to say whether or not the type used to fill in the InferResult should be deeply instantiated. See TcUnify Note [Deep instantiation of InferResult]. 4. Add a TcLevel to SkolemTvs. This will be useful generally - it's a fast way to see if the type variable escapes when floating (not used yet) - it provides a good consistency check when updating a unification variable (TcMType.writeMetaTyVarRef, the level_check_ok check) I originally had another reason (related to the flirting in (2), but I left it in because it seems like a step in the right direction. 5. Reduce and simplify the plethora of uExpType, tcSubType and related functions in TcUnify. It was such an opaque mess and it's still not great, but it's better. 6. Simplify the uo_expected field of TypeEqOrigin. Richard had generatlised it to a ExpType, but it was almost always a Check type. Now it's back to being a plain TcType which is much, much easier. 7. Improve error messages by refraining from skolemisation when it's clear that there's an error: see TcUnify Note [Don't skolemise unnecessarily] 8. Type.isPiTy and isForAllTy seem to be missing a coreView check, so I added it 9. Kill off tcs_used_tcvs. Its purpose is to track the givens used by wanted constraints. For dictionaries etc we do that via the free vars of the /bindings/ in the implication constraint ic_binds. But for coercions we just do update-in-place in the type, rather than generating a binding. So we need something analogous to bindings, to track what coercions we have added. That was the purpose of tcs_used_tcvs. But it only worked for a /single/ iteration, whereas we may have multiple iterations of solving an implication. Look at (the old) 'setImplicationStatus'. If the constraint is unsolved, it just drops the used_tvs on the floor. If it becomes solved next time round, we'll pick up coercions used in that round, but ignore ones used in the first round. There was an outright bug. Result = (potentialy) bogus unused-constraint errors. Constructing a case where this actually happens seems quite trick so I did not do so. Solution: expand EvBindsVar to include the (free vars of the) coercions, so that the coercions are tracked in essentially the same way as the bindings. This turned out to be much simpler. Less code, more correct. 10. Make the ic_binds field in an implication have type ic_binds :: EvBindsVar instead of (as previously) ic_binds :: Maybe EvBindsVar This is notably simpler, and faster to use -- less testing of the Maybe. But in the occaional situation where we don't have anywhere to put the bindings, the belt-and-braces error check is lost. So I put it back as an ASSERT in 'setImplicationStatus' (see the use of 'termEvidenceAllowed') All these changes led to quite bit of error message wibbling
* Fix #12442.Richard Eisenberg2016-09-231-1/+1
| | | | | | | | | | | | | | | | | | | The problem is described in the ticket. This patch adds new variants of the access points to the pure unifier that allow unification of types only when the caller wants this behavior. (The unifier used to also unify kinds.) This behavior is appropriate when the kinds are either already known to be the same, or the list of types provided are a list of well-typed arguments to some type constructor. In the latter case, unifying earlier types in the list will unify the kinds of any later (dependent) types. At use sites, I went through and chose the unification function according to the criteria above. This patch includes some modest performance improvements as we are now doing less work.
* RtClosureInspect: Fix off-by-one error in cvReconstructTypemniip2016-08-231-4/+3
| | | | | | | | | | | | | | | | | Replaced error-prone index manipulation on a pointer array with a simple fold on the array elements. Test Plan: Added a test case that triggers the bug Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2439 GHC Trac Issues: #12458
* Implement unboxed sum primitive typeÖmer Sinan Ağacan2016-07-211-13/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. - Simon Peyton Jones reviewed this patch many times, wrote some code, and helped with debugging. Reviewers: bgamari, alanz, goldfire, RyanGlScott, simonpj, austin, simonmar, hvr, erikd Reviewed By: simonpj Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259
* Remove some `undefined`sÖmer Sinan Ağacan2016-06-271-3/+2
| | | | | | These get annoying when `undefined` is actually used as placeholder in WIP code. Some of these were also completely redundant (just call `deAnnotate'` instead of `deAnnotate` etc.).
* Address #11471 by putting RuntimeRep in kinds.wip/runtime-repRichard Eisenberg2016-02-241-2/+2
| | | | | | | | | | | | | | | | | | | | | See Note [TYPE] in TysPrim. There are still some outstanding pieces in #11471 though, so this doesn't actually nail the bug. This commit also contains a few performance improvements: * Short-cut equality checking of nullary type syns * Compare types before kinds in eqType * INLINE coreViewOneStarKind * Store tycon binders separately from kinds. This resulted in a ~10% performance improvement in compiling the Cabal package. No change in functionality other than performance. (This affects the interface file format, though.) This commit updates the haddock submodule.
* Overhaul the Overhauled Pattern Match CheckerGeorge Karachalias2016-02-041-3/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Overhaul the Overhauled Pattern Match Checker * Changed the representation of Value Set Abstractions. Instead of using a prefix tree, we now use a list of Value Vector Abstractions. The set of constraints Delta for every Value Vector Abstraction is the oracle state so that we solve everything only once. * Instead of doing everything lazily, we prune at once (and in general everything is much stricter). Hence, an example written with pattern guards is checked in almost the same time as the equivalent with pattern matching. * Do not store the covered and the divergent sets at all. Since what we only need is a yes/no (does this clause cover anything? Does it force any thunk?) We just keep a boolean for each. * Removed flags `-Wtoo-many-guards` and `-ffull-guard-reasoning`. Replaced with `fmax-pmcheck-iterations=n`. Still debatable what should the default `n` be. * When a guard is for sure not going to contribute anything, we treat it as such: The oracle is not called and cases `CGuard`, `UGuard` and `DGuard` from the paper are not happening at all (the generation of a fresh variable, the unfolding of the pattern list etc.). his combined with the above seems to be enough to drop the memory increase for test T783 down to 18.7%. * Do not export function `dsPmWarn` (it is now called directly from within `checkSingle` and `checkMatches`). * Make `PmExprVar` hold a `Name` instead of an `Id`. The term oracle does not handle type information so using `Id` was a waste of time/space. * Added testcases T11195, T11303b (data families) and T11374 The patch addresses at least the following: Trac #11195, #11276, #11303, #11374, #11162 Test Plan: validate Reviewers: goldfire, bgamari, hvr, austin Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1795
* TyCoRep: Implement some helpers for dropping/checking Levity argumentsÖmer Sinan Ağacan2016-02-011-1/+1
| | | | | | | | | | | | | Also fix `isLevityTy` (it should use `coreView`) and start using `dropLevityArgs` in some places. Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1867
* Refactor the typechecker to use ExpTypes.Richard Eisenberg2016-01-271-4/+0
| | | | | | | | | | | | | | | | | | | | | The idea here is described in [wiki:Typechecker]. Briefly, this refactor keeps solid track of "synthesis" mode vs "checking" in GHC's bidirectional type-checking algorithm. When in synthesis mode, the expected type is just an IORef to write to. In addition, this patch does a significant reworking of RebindableSyntax, allowing much more freedom in the types of the rebindable operators. For example, we can now have `negate :: Int -> Bool` and `(>>=) :: m a -> (forall x. a x -> m b) -> m b`. The magic is in tcSyntaxOp. This addresses tickets #11397, #11452, and #11458. Tests: typecheck/should_compile/{RebindHR,RebindNegate,T11397,T11458} th/T11452
* Drop pre-AMP compatibility CPP conditionalsHerbert Valerio Riedel2015-12-311-7/+0
| | | | | | | | | | | | Since GHC 8.1/8.2 only needs to be bootstrap-able by GHC 7.10 and GHC 8.0 (and GHC 8.2), we can now finally drop all that pre-AMP compatibility CPP-mess for good! Reviewers: austin, goldfire, bgamari Subscribers: goldfire, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1724
* Adding flags: -ffull-guard-reasoning and too-many-guardsGeorge Karachalias2015-12-271-0/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Introduction of two new flags, for more precise control over the new pattern match checker's behaviour when reasoning about guards. This is supposed to address #11195 (and maybe more performance bugs related to the NP-Hardness of coverage checking). Expected behaviour: * When `-ffull-guard-reasoning` is on, run the new pattern match checker in its full power * When `-ffull-guard-reasoning` is off (the default), for every match, check a metric to see whether pattern match checking for it has high probability of being non performant (at the the moment we check whether the number of guards is over 20 but I would like to use a more precise measure in the future). If the probability is high: - Oversimplify the guards (less expressive but more performant) and run the checker, and - Issue a warning about the simplification that happened. A new flag `-Wtoo-many-guards/-Wno-too-many-guards` suppresses the warning about the simplification (useful when combined with -Werror). Test Plan: validate Reviewers: goldfire, austin, hvr, bgamari Reviewed By: bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1676 GHC Trac Issues: #11195
* Fix typechecking for pattern synonym signaturesSimon Peyton Jones2015-12-221-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Various tickets have revealed bad shortcomings in the typechecking of pattern type synonyms. Discussed a lot in (the latter part of) Trac #11224. This patch fixes the most complex issues: - Both parser and renamer now treat pattern synonyms as an ordinary LHsSigType. Nothing special. Hooray. - tcPatSynSig (now in TcPatSyn) typechecks the signature, and decomposes it into its pieces. See Note [Pattern synonym signatures] - tcCheckPatSyn has had a lot of refactoring. See Note [Checking against a pattern signature] The result is a lot tidier and more comprehensible. Plus, it actually works! NB: this patch doesn't actually address the precise target of #11224, namely "inlining pattern synonym does not preserve semantics". That's an unrelated bug, with a separate patch. ToDo: better documentation in the user manual Test Plan: Validate Reviewers: austin, hvr, goldfire Subscribers: goldfire, mpickering, thomie, simonpj Differential Revision: https://phabricator.haskell.org/D1685 GHC Trac Issues: #11224
* Remote GHCi, -fexternal-interpreterSimon Marlow2015-12-171-7/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: (Apologies for the size of this patch, I couldn't make a smaller one that was validate-clean and also made sense independently) (Some of this code is derived from GHCJS.) This commit adds support for running interpreted code (for GHCi and TemplateHaskell) in a separate process. The functionality is experimental, so for now it is off by default and enabled by the flag -fexternal-interpreter. Reaosns we want this: * compiling Template Haskell code with -prof does not require building the code without -prof first * when GHC itself is profiled, it can interpret unprofiled code, and the same applies to dynamic linking. We would no longer need to force -dynamic-too with TemplateHaskell, and we can load ordinary objects into a dynamically-linked GHCi (and vice versa). * An unprofiled GHCi can load and run profiled code, which means it can use the stack-trace functionality provided by profiling without taking the performance hit on the compiler that profiling would entail. Amongst other things; see https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi for more details. Notes on the implementation are in Note [Remote GHCi] in the new module compiler/ghci/GHCi.hs. It probably needs more documenting, feel free to suggest things I could elaborate on. Things that are not currently implemented for -fexternal-interpreter: * The GHCi debugger * :set prog, :set args in GHCi * `recover` in Template Haskell * Redirecting stdin/stdout for the external process These are all doable, I just wanted to get to a working validate-clean patch first. I also haven't done any benchmarking yet. I expect there to be slight hit to link times for byte code and some penalty due to having to serialize/deserialize TH syntax, but I don't expect it to be a serious problem. There's also lots of low-hanging fruit in the byte code generator/linker that we could exploit to speed things up. Test Plan: * validate * I've run parts of the test suite with EXTRA_HC_OPTS=-fexternal-interpreter, notably tests/ghci and tests/th. There are a few failures due to the things not currently implemented (see above). Reviewers: simonpj, goldfire, ezyang, austin, alanz, hvr, niteria, bgamari, gibiansky, luite Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1562
* Add kind equalities to GHC.Richard Eisenberg2015-12-111-26/+33
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule.
* Create a deterministic version of tyVarsOfTypeBartosz Nitka2015-11-211-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | I've run into situations where I need deterministic `tyVarsOfType` and this implementation achieves that and also brings an algorithmic improvement. Union of two `VarSet`s takes linear time the size of the sets and in the worst case we can have `n` unions of sets of sizes `(n-1, 1), (n-2, 1)...` making it quadratic. One reason why we need deterministic `tyVarsOfType` is in `abstractVars` in `SetLevels`. When we abstract type variables when floating we want them to be abstracted in deterministic order. Test Plan: harbormaster Reviewers: simonpj, goldfire, austin, hvr, simonmar, bgamari Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1468 GHC Trac Issues: #4012
* Make GHCi & TH work when the compiler is built with -profSimon Marlow2015-11-071-7/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Amazingly, there were zero changes to the byte code generator and very few changes to the interpreter - mainly because we've used good abstractions that hide the differences between profiling and non-profiling. So that bit was pleasantly straightforward, but there were a pile of other wibbles to get the whole test suite through. Note that a compiler built with -prof is now like one built with -dynamic, in that to use TH you have to build the code the same way. For dynamic, we automatically enable -dynamic-too when TH is required, but we don't have anything equivalent for profiling, so you have to explicitly use -prof when building code that uses TH with a profiled compiler. For this reason Cabal won't work with TH. We don't expect to ship a profiled compiler, so I think that's OK. Test Plan: validate with GhcProfiled=YES in validate.mk Reviewers: goldfire, bgamari, rwbarton, austin, hvr, erikd, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1407 GHC Trac Issues: #4837, #545
* Refactor tuple constraintsSimon Peyton Jones2015-05-181-3/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity - Haddock needs to absorb the change too; so there is a submodule update
* Revert multiple commitsAustin Seipp2015-05-141-4/+3
| | | | | | | | | | | | | | | | | | | | This reverts multiple commits from Simon: - 04a484eafc9eb9f8774b4bdd41a5dc6c9f640daf Test Trac #10359 - a9ccd37add8315e061c02e5bf26c08f05fad9ac9 Test Trac #10403 - c0aae6f699cbd222d826d0b8d78d6cb3f682079e Test Trac #10248 - eb6ca851f553262efe0824b8dcbe64952de4963d Make the "matchable-given" check happen first - ca173aa30467a0b1023682d573fcd94244d85c50 Add a case to checkValidTyCon - 51cbad15f86fca1d1b0e777199eb1079a1b64d74 Update haddock submodule - 6e1174da5b8e0b296f5bfc8b39904300d04eb5b7 Separate transCloVarSet from fixVarSet - a8493e03b89f3b3bfcdb6005795de050501f5c29 Fix imports in HscMain (stage2) - a154944bf07b2e13175519bafebd5a03926bf105 Two wibbles to fix the build - 5910a1bc8142b4e56a19abea104263d7bb5c5d3f Change in capitalisation of error msg - 130e93aab220bdf14d08028771f83df210da340b Refactor tuple constraints - 8da785d59f5989b9a9df06386d5bd13f65435bc0 Delete commented-out line These break the build by causing Haddock to fail mysteriously when trying to examine GHC.Prim it seems.
* Refactor tuple constraintsSimon Peyton Jones2015-05-131-3/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity
* Make the location in TcLclEnv and CtLoc into a RealSrcSpanSimon Peyton Jones2015-01-061-3/+1
| | | | | | | | | | | Previously it was a SrcSpan, which can be an UnhelpulSrcSpan, but actually for TcLclEnv and CtLoc we always know it is a real source location, and it's good to make the types reflect that fact. There is a continuing slight awkwardness (not new with this patch) about what "file name" to use for GHCi code. Current we say "<interactive>" which seems just about OK.
* Update Foreign.* for Safe Haskell now that they're safe by defaultDavid Terei2014-11-211-0/+4
|