summaryrefslogtreecommitdiff
Commit message (Collapse)AuthorAgeFilesLines
* testsuite: Add test for #15232Ben Gamari2018-06-072-0/+13
| | | | | | | | Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15232 Differential Revision: https://phabricator.haskell.org/D4807
* Move 'HsBangTy' out in constructor argumentsAlec Theriault2018-06-076-2/+64
| | | | | | | | | | | | | | | | | | | | When run with -haddock, a constructor argument can have both a a strictness/unpackedness annotation and a docstring. The parser binds 'HsBangTy' more tightly than 'HsDocTy', yet for constructor arguments we really need the 'HsBangTy' on the outside. This commit does this shuffling in the 'mkConDeclH98' and 'mkGadtDecl' smart constructors. Test Plan: haddockA038, haddockC038 Reviewers: bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4727
* Check if both branches of an Cmm if have the same target.klebinger.andreas@gmx.at2018-06-075-4/+25
| | | | | | | | | | | | | | | | | | | | This for some reason or the other and makes it into the final binary. I've added the check to ContFlowOpt as that seems like a logical place for this. In a regular nofib run there were 30 occurences of this pattern. Test Plan: ci Reviewers: bgamari, simonmar, dfeuer, jrtc27, tdammers Reviewed By: bgamari, simonmar Subscribers: tdammers, dfeuer, rwbarton, thomie, carter GHC Trac Issues: #15188 Differential Revision: https://phabricator.haskell.org/D4740
* Fix unparseable pretty-printing of promoted data consAndreas Herrmann2018-06-0711-26/+147
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously we would print code which would not round-trip: ``` > :set -XDataKinds > :set -XPolyKinds > data Proxy k = Proxy > _ :: Proxy '[ 'True ] error: Found hole: _ :: Proxy '['True] > _ :: Proxy '['True] error: Invalid type signature: _ :: ... Should be of form <variable> :: <type> ``` Test Plan: Validate with T14343 Reviewers: RyanGlScott, goldfire, bgamari, tdammers Reviewed By: RyanGlScott, bgamari Subscribers: tdammers, rwbarton, thomie, carter GHC Trac Issues: #14343 Differential Revision: https://phabricator.haskell.org/D4746
* Index arrays more eagerlyDavid Feuer2018-06-071-9/+29
| | | | | | | | | | | | | | | Many basic functions in `GHC.Arr` were unreasonably lazy about performing array lookups. This could lead to useless thunks at best and memory leaks at worst. Use eager lookups where they're obviously appropriate. Reviewers: bgamari, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4773
* WorkWrap: Rip out unsafeGlobalDynFlags usage in mkWwInlineRuleBen Gamari2018-06-072-4/+4
| | | | | | Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4775
* Don't use unsafeGlobalDynFlags in optCoercionBen Gamari2018-06-077-44/+55
| | | | | | | | | | | | | | | | | This plumbs DynFlags through CoreOpt so optCoercion can finally eliminate its usage of `unsafeGlobalDynFlags`. Note that this doesn't completely eliminate `unsafeGlobalDynFlags` usage from this bit of the compiler. A few uses are introduced in call-sites where we don't (yet) have ready access to `DynFlags`. Test Plan: Validate Reviewers: goldfire Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4774
* Update hadrian submoduleBen Gamari2018-06-071-16/+6
|
* testsuite: Fix dynamic-paper stderr fileBen Gamari2018-06-071-1/+15
| | | | The stderr file was empty, yet GHC fails with an error.
* Remove ad-hoc special case in occAnalSimon Peyton Jones2018-06-0710-49/+55
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Back in 1999 I put this ad-hoc code in the Case-handling code for occAnal: occAnal env (Case scrut bndr ty alts) = ... -- Note [Case binder usage] -- ~~~~~~~~~~~~~~~~~~~~~~~~ -- The case binder gets a usage of either "many" or "dead", never "one". -- Reason: we like to inline single occurrences, to eliminate a binding, -- but inlining a case binder *doesn't* eliminate a binding. -- We *don't* want to transform -- case x of w { (p,q) -> f w } -- into -- case x of w { (p,q) -> f (p,q) } tag_case_bndr usage bndr = (usage', setIdOccInfo bndr final_occ_info) where occ_info = lookupDetails usage bndr usage' = usage `delDetails` bndr final_occ_info = case occ_info of IAmDead -> IAmDead _ -> noOccInfo But the comment looks wrong -- the bad inlining will not happen -- and I think it relates to some long-ago version of the simplifier. So I simply removed the special case, which gives more accurate occurrence-info to the case binder. Interestingly I got a slight improvement in nofib binary sizes. -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- cacheprof -0.1% +0.2% -0.7% -1.2% +8.6% -------------------------------------------------------------------------------- Min -0.2% 0.0% -14.5% -30.5% 0.0% Max -0.1% +0.2% +10.0% +10.0% +25.0% Geometric Mean -0.2% +0.0% -1.9% -5.4% +0.3% I have no idea if the improvement in runtime is real. I did look at the tiny increase in allocation for cacheprof and concluded that it was unimportant (I forget the details). Also the more accurate occ-info for the case binder meant that some inlining happens in one pass that previously took successive passes for the test dependent/should_compile/dynamic-paper (which has a known Russel-paradox infinite loop in the simplifier). In short, a small win: less ad-hoc complexity and slightly smaller binaries.
* Comments onlySimon Peyton Jones2018-06-072-26/+32
|
* Do not scavenge SMALL_MUT_ARR_PTRS_CLEAN in mut_listsÖmer Sinan Ağacan2018-06-071-0/+1
| | | | | | | | | | | | | | | | | | For the same reason with MUT_ARR_PTRS_CLEAN we don't need to scavenge SMALL_MUT_ARR_PTRS_CLEAN in mut_lists. Because SMALL_MUT_ARR_PTRS doesn't have a card table we don't have a special case when scavenging SMALL_MUT_ARR_PTRS_DIRTY in a mut_list. Test Plan: this validates Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar, bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4800
* Let the simplifier know that seq# forcesDavid Feuer2018-06-064-37/+123
| | | | | | | | | | | | | | | Add a special case in `simplAlt` to record that the result of `seq#` is in WHNF. Reviewers: simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15226 Differential Revision: https://phabricator.haskell.org/D4796
* rts: Reuse dbl_link_remove in a few placesÖmer Sinan Ağacan2018-06-051-16/+2
| | | | | | | | | | | | Test Plan: this validates Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4795
* Rename some mutable closure types for consistencyÖmer Sinan Ağacan2018-06-0524-176/+152
| | | | | | | | | | | | | | | | | | | | | | | SMALL_MUT_ARR_PTRS_FROZEN0 -> SMALL_MUT_ARR_PTRS_FROZEN_DIRTY SMALL_MUT_ARR_PTRS_FROZEN -> SMALL_MUT_ARR_PTRS_FROZEN_CLEAN MUT_ARR_PTRS_FROZEN0 -> MUT_ARR_PTRS_FROZEN_DIRTY MUT_ARR_PTRS_FROZEN -> MUT_ARR_PTRS_FROZEN_CLEAN Naming is now consistent with other CLEAR/DIRTY objects (MVAR, MUT_VAR, MUT_ARR_PTRS). (alternatively we could rename MVAR_DIRTY/MVAR_CLEAN etc. to MVAR0/MVAR) Removed a few comments in Scav.c about FROZEN0 being on the mut_list because it's now clear from the closure type. Reviewers: bgamari, simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4784
* Introduce DerivingViaRyan Scott2018-06-0438-381/+1608
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements the `DerivingVia` proposal put forth in https://github.com/ghc-proposals/ghc-proposals/pull/120. This introduces the `DerivingVia` deriving strategy. This is a generalization of `GeneralizedNewtypeDeriving` that permits the user to specify the type to `coerce` from. The major change in this patch is the introduction of the `ViaStrategy` constructor to `DerivStrategy`, which takes a type as a field. As a result, `DerivStrategy` is no longer a simple enumeration type, but rather something that must be renamed and typechecked. The process by which this is done is explained more thoroughly in section 3 of this paper ( https://www.kosmikus.org/DerivingVia/deriving-via-paper.pdf ), although I have inlined the relevant parts into Notes where possible. There are some knock-on changes as well. I took the opportunity to do some refactoring of code in `TcDeriv`, especially the `mkNewTypeEqn` function, since it was bundling all of the logic for (1) deriving instances for newtypes and (2) `GeneralizedNewtypeDeriving` into one huge broth. `DerivingVia` reuses much of part (2), so that was factored out as much as possible. Bumps the Haddock submodule. Test Plan: ./validate Reviewers: simonpj, bgamari, goldfire, alanz Subscribers: alanz, goldfire, rwbarton, thomie, mpickering, carter GHC Trac Issues: #15178 Differential Revision: https://phabricator.haskell.org/D4684
* Serialize docstrings to ifaces, display them with new GHCi :doc commandSimon Jakobi2018-06-0442-91/+816
| | | | | | | | | | | | | | | | | | | | | | | | If `-haddock` is set, we now extract docstrings from the renamed ast and serialize them in the .hi-files. This includes some of the changes from D4749 with the notable exceptions of the docstring lexing and renaming. A currently limited and experimental GHCi :doc command can be used to display docstrings for declarations. The formatting of pretty-printed docstrings is changed slightly, causing some changes in testsuite/tests/haddock. Test Plan: ./validate Reviewers: alexbiehl, hvr, gershomb, harpocrates, bgamari Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4758
* Also suppress uniques in cmm dumps with `-dsuppress-uniques`.klebinger.andreas@gmx.at2018-06-042-3/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Allows easier structural comparison of Cmm code. Before: ``` cxCH: // global _suEU::P64 = R1; if ((Sp + -16) < SpLim) (likely: False) goto cxCI; else goto cxCJ; ``` After ``` _lbl_: // global __locVar_::P64 = R1; if ((Sp + -16) < SpLim) (likely: False) goto cxBf; else goto cxBg; ``` Test Plan: Looking at dumps, ci Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4786
* Improve extendTvSubst assertionMatthew Pickering2018-06-041-1/+1
| | | | | | | | | | Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4790
* Add Outputable instance for HsArgMatthew Pickering2018-06-041-0/+4
| | | | | | | | | | Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4791
* Implement QuantifiedConstraintsSimon Peyton Jones2018-06-0444-542/+1779
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | We have wanted quantified constraints for ages and, as I hoped, they proved remarkably simple to implement. All the machinery was already in place. The main ticket is Trac #2893, but also relevant are #5927 #8516 #9123 (especially! higher kinded roles) #14070 #14317 The wiki page is https://ghc.haskell.org/trac/ghc/wiki/QuantifiedConstraints which in turn contains a link to the GHC Proposal where the change is specified. Here is the relevant Note: Note [Quantified constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The -XQuantifiedConstraints extension allows type-class contexts like this: data Rose f x = Rose x (f (Rose f x)) instance (Eq a, forall b. Eq b => Eq (f b)) => Eq (Rose f a) where (Rose x1 rs1) == (Rose x2 rs2) = x1==x2 && rs1 >= rs2 Note the (forall b. Eq b => Eq (f b)) in the instance contexts. This quantified constraint is needed to solve the [W] (Eq (f (Rose f x))) constraint which arises form the (==) definition. Here are the moving parts * Language extension {-# LANGUAGE QuantifiedConstraints #-} and add it to ghc-boot-th:GHC.LanguageExtensions.Type.Extension * A new form of evidence, EvDFun, that is used to discharge such wanted constraints * checkValidType gets some changes to accept forall-constraints only in the right places. * Type.PredTree gets a new constructor ForAllPred, and and classifyPredType analyses a PredType to decompose the new forall-constraints * Define a type TcRnTypes.QCInst, which holds a given quantified constraint in the inert set * TcSMonad.InertCans gets an extra field, inert_insts :: [QCInst], which holds all the Given forall-constraints. In effect, such Given constraints are like local instance decls. * When trying to solve a class constraint, via TcInteract.matchInstEnv, use the InstEnv from inert_insts so that we include the local Given forall-constraints in the lookup. (See TcSMonad.getInstEnvs.) * topReactionsStage calls doTopReactOther for CIrredCan and CTyEqCan, so they can try to react with any given quantified constraints (TcInteract.matchLocalInst) * TcCanonical.canForAll deals with solving a forall-constraint. See Note [Solving a Wanted forall-constraint] Note [Solving a Wanted forall-constraint] * We augment the kick-out code to kick out an inert forall constraint if it can be rewritten by a new type equality; see TcSMonad.kick_out_rewritable Some other related refactoring ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Move SCC on evidence bindings to post-desugaring, which fixed #14735, and is generally nicer anyway because we can use existing CoreSyn free-var functions. (Quantified constraints made the free-vars of an ev-term a bit more complicated.) * In LookupInstResult, replace GenInst with OneInst and NotSure, using the latter for multiple matches and/or one or more unifiers
* Document the fact that cmm dumps won't show unreachable blocks.klebinger.andreas@gmx.at2018-06-041-0/+3
| | | | | | | | | | Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4788
* Fix broken test T14547.HE, Tao2018-06-042-13/+27
| | | | | | | | | | | | | | | | | | | | | | Phab:D4571 lags behind HEAD for too many commits. The commit of Phab:4571 1f88f541aad1e36d01f22f9e71dfbc247e6558e2 brought some unintentional changes (not belong to [Phab:4571's Diff 16314](https://phabricator.haskell.org/differential/diff/16314/)) into ghc-head, breaking T14557. Let's fix that. Test Plan: make test TEST="T14547" Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15222 Differential Revision: https://phabricator.haskell.org/D4778
* Bump stm and haskeline submodulesBen Gamari2018-06-042-0/+0
|
* Refactor SetLevels.abstractVarsSimon Peyton Jones2018-06-041-14/+6
| | | | | This patch is pure refactoring: using utility functions rather than special-purpose code, especially for closeOverKinds
* Expand type synonyms when Linting a forallSimon Peyton Jones2018-06-044-8/+53
| | | | | | | | | | | | | | | Trac #14939 showed a type like type Alg cls ob = ob f :: forall (cls :: * -> Constraint) (b :: Alg cls *). b where the kind of the forall looks like (Alg cls *), with a free cls. This tripped up Core Lint. I fixed this by making Core Lint a bit more forgiving, expanding type synonyms if necessary. I'm worried that this might not be the whole story; notably typeKind looks suspect. But it certainly fixes this problem.
* Do a late CSE passSimon Peyton Jones2018-06-041-0/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | When investigating something else I found that a condition was being re-evaluated in wheel-seive1. Why, when CSE should find it? Because the opportunity only showed up after LiberateCase This patch adds a late CSE pass. Rather than give it an extra flag I do it when (cse && (spec_constr || liberate_case)), so roughly speaking it happense with -O2. In any case, CSE is very cheap. Nofib results are minor but in the right direction: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.1% -0.0% 0.163 0.163 0.0% eliza -0.1% -0.4% 0.001 0.001 0.0% fft2 -0.1% 0.0% 0.087 0.087 0.0% mate -0.0% -1.3% -0.8% -0.8% 0.0% paraffins -0.0% -0.1% +0.9% +0.9% 0.0% pic -0.0% -0.1% 0.009 0.009 0.0% wheel-sieve1 -0.2% -0.0% -0.1% -0.1% 0.0% -------------------------------------------------------------------------------- Min -0.6% -1.3% -2.4% -2.4% 0.0% Max +0.0% +0.0% +3.8% +3.8% +23.8% Geometric Mean -0.0% -0.0% +0.2% +0.2% +0.2%
* Provide `getWithUserData` and `putWithUserData`Matthew Pickering2018-06-041-7/+26
| | | | | | | | | | | | | | | | | | | | | Summary: This makes it possible to serialise Names and FastStrings in user programs, for example, when writing a source plugin. When writing my first source plugin, I wanted to serialise names but it wasn't possible easily without exporting additional constructors. This interface is sufficient and abstracts nicely over the symbol table and dictionary. Reviewers: alpmestan, bgamari Reviewed By: alpmestan Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15223 Differential Revision: https://phabricator.haskell.org/D4782
* testsuite: Really mark T14547 as brokenBen Gamari2018-06-031-1/+0
|
* testsuite: Mark T14547 as brokenBen Gamari2018-06-031-0/+1
|
* Add tests for #8128 and #8740Ryan Scott2018-06-035-0/+60
| | | | | Commit 08073e16cf672d8009309e4e55d4566af1ecaff4 (#11066) ended up fixing these, fortunately enough.
* Fix typo in OverloadedLabels docsJoachim Breitner2018-06-031-1/+1
| | | | as helpfully reported by elpinal (#15217).
* Improve exhaustiveness checking for literal values and patterns, fix #14546HE, Tao2018-06-0312-72/+308
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Currently, we parse both the **integral literal** value and the patterns as `OverLit HsIntegral`. For example: ``` case 0::Int of 0 -> putStrLn "A" 1 -> putStrLn "B" _ -> putStrLn "C" ``` When checking the exhaustiveness of pattern matching, we translate the `0` in value position as `PmOLit`, but translate the `0` and `1` in pattern position as `PmSLit`. The inconsistency leads to the failure of `eqPmLit` to detect the equality and report warning of "Pattern match is redundant" on pattern `0`, as reported in #14546. In this patch we remove the specialization of `OverLit` patterns, and keep the overloaded number literal in pattern as it is to maintain the consistency. Now we can capture the exhaustiveness of pattern `0` and the redundancy of pattern `1` and `_`. For **string literals**, we parse the string literals as `HsString`. When `OverloadedStrings` is enabled, it further be turned as `HsOverLit HsIsString`, whether it's type is `String` or not. For example: ``` case "foo" of "foo" -> putStrLn "A" "bar" -> putStrLn "B" "baz" -> putStrLn "C" ``` Previously, the overloaded string values are translated to `PmOLit` and the non-overloaded string values are translated to `PmSLit`. However the string patterns, both overloaded and non-overloaded, are translated to list of characters. The inconsistency leads to wrong warnings about redundant and non-exhaustive pattern matching warnings, as reported in #14546. In order to catch the redundant pattern in following case: ``` case "foo" of ('f':_) -> putStrLn "A" "bar" -> putStrLn "B" ``` In this patch, we translate non-overloaded string literals, both in value position and pattern position, as list of characters. For overloaded string literals, we only translate it to list of characters only when it's type is `stringTy`, since we know nothing about the `toString` methods. But we know that if two overloaded strings are syntax equal, then they are equal. Then if it's type is not `stringTy`, we just translate it to `PmOLit`. We can still capture the exhaustiveness of pattern `"foo"` and the redundancy of pattern `"bar"` and `"baz"` in the following code: ``` {-# LANGUAGE OverloadedStrings #-} main = do case "foo" of "foo" -> putStrLn "A" "bar" -> putStrLn "B" "baz" -> putStrLn "C" ``` Test Plan: make test TEST="T14546" Reviewers: bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: simonpj, thomie, carter GHC Trac Issues: #14546 Differential Revision: https://phabricator.haskell.org/D4571
* Allow aligning of cmm procs at specific boundryklebinger.andreas@gmx.at2018-06-033-0/+25
| | | | | | | | | | | | | | | | | | | | Allows to align CmmProcs at the given boundries. It makes performance usually worse but can be helpful to limit the effect of a unrelated function B becoming faster/slower after changing function A. Test Plan: ci, using it. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15148 Differential Revision: https://phabricator.haskell.org/D4706
* tcExtendTyVarEnv2 changed to tcExtendNameTyVarEnvAlanas Plascinskas2018-06-027-18/+18
| | | | | | | | | | | | Reviewers: mpickering, goldfire, bgamari Reviewed By: mpickering Subscribers: goldfire, rwbarton, thomie, carter GHC Trac Issues: #15017 Differential Revision: https://phabricator.haskell.org/D4732
* Turn "inaccessible code" error into a warningTobias Dammers2018-06-0214-44/+76
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | With GADTs, it is possible to write programs such that the type constraints make some code branches inaccessible. Take, for example, the following program :: {-# LANGUAGE GADTs #-} data Foo a where Foo1 :: Foo Char Foo2 :: Foo Int data TyEquality a b where Refl :: TyEquality a a checkTEQ :: Foo t -> Foo u -> Maybe (TyEquality t u) checkTEQ x y = error "unimportant" step2 :: Bool step2 = case checkTEQ Foo1 Foo2 of Just Refl -> True -- Inaccessible code Nothing -> False Clearly, the `Just Refl` case cannot ever be reached, because the `Foo1` and `Foo2` constructors say `t ~ Char` and `u ~ Int`, while the `Refl` constructor essentially mandates `t ~ u`, and thus `Char ~ Int`. Previously, GHC would reject such programs entirely; however, in practice this is too harsh. Accepting such code does little harm, since attempting to use the "impossible" code will still produce errors down the chain, while rejecting it means we cannot legally write or generate such code at all. Hence, we turn the error into a warning, and provide `-Winaccessible-code` to control GHC's behavior upon encountering this situation. Test Plan: ./validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11066 Differential Revision: https://phabricator.haskell.org/D4744
* Fix a bad interaction between GADTs and COMPLETE setsRyan Scott2018-06-024-5/+94
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As observed in #14059 (starting at comment 5), the error messages surrounding a program involving GADTs and a `COMPLETE` set became worse between 8.2 and 8.4. The culprit was a new validity check in 8.4 which filters out `COMPLETE` set candidates if a return type of any conlike in the set doesn't match the type of the scrutinee. However, this check was too conservative, since it removed perfectly valid `COMPLETE` sets that contained GADT constructors, which quite often have return types that don't match the type of a scrutinee. To fix this, I adopted the most straightforward possible solution of only performing this validity check on //pattern synonym// constructors, not //data// constructors. Note that this does not fix #14059 entirely, but instead simply fixes a particular buglet that was discovered in that ticket. Test Plan: make test TEST=T14059 Reviewers: bgamari, mpickering Reviewed By: mpickering Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14059 Differential Revision: https://phabricator.haskell.org/D4752
* Remove ~# from surface syntaxDavid Feuer2018-06-024-8/+2
| | | | | | | | | | | | | | | | | | | For some reason, it seems that the `ConstraintKinds` commit introduced `~#` into Haskell syntax, in a pretty broken manner. Unless and until we have an actual story for unboxed equality, it doesn't make sense to expose it. Moreover, the way it was donet was wrong enough and small enough that it will probably be easier to start over if we do that. Yank it out. Reviewers: bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, thomie, mpickering, carter GHC Trac Issues: #15209 Differential Revision: https://phabricator.haskell.org/D4763
* Handle abi-depends correctly in ghc-pkgTobias Dammers2018-06-023-23/+139
| | | | | | | | | | | | | | | | | | | | | | | | When inferring the correct abi-depends, we now look at all the package databases in the stack, up to and including the current one, because these are the ones that the current package can legally depend on. While doing so, we will issue warnings: - In verbose mode, we warn about every package that declares abi-depends:, whether we actually end up overriding them with the inferred ones or not ("possibly broken abi-depends"). - Otherwise, we only warn about packages whose declared abi-depends does not match what we inferred ("definitely broken abi-depends"). Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14381 Differential Revision: https://phabricator.haskell.org/D4729
* rts: Query system rlimit for maximum address-space sizeBen Gamari2018-06-021-0/+11
| | | | | | | | | | | | | | | | | When we attempt to reserve the heap, we query the system's rlimit to establish the starting point for our search over sizes. Test Plan: Validate Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14492 Differential Revision: https://phabricator.haskell.org/D4754
* Fix #15214 by listing (~) in isBuiltInOcc_maybeRyan Scott2018-06-024-0/+10
| | | | | | | | | | | | | | | | | This changes an obscure error (which mistakenly mentions Template Haskell) to one that makes more sense. Test Plan: make test TEST=T15214 Reviewers: bgamari, mpickering Reviewed By: bgamari, mpickering Subscribers: mpickering, rwbarton, thomie, carter GHC Trac Issues: #15214 Differential Revision: https://phabricator.haskell.org/D4768
* Check for singletons when creating Bag/OrdList from a list.klebinger.andreas@gmx.at2018-06-022-0/+2
| | | | | | | | | | | | | | | | | | | This gives us `One x` instead of `Many (x : [])` reducing overhead. For compiling spectral/simple with -O0 difference was ~ -0.05% allocations. The only drawback is that something like toOL (x:panic "") will now panic. But that seems like a reasonable tradeoff. Test Plan: ci, looking at +RTS -s Reviewers: bgamari, jmct Reviewed By: bgamari Subscribers: jmct, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4770
* Fix #13777 by improving the underdetermined CUSK error messageRyan Scott2018-06-026-4/+47
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | The error message that GHC emits from underdetermined CUSKs is rather poor, since: 1. It may print an empty list of user-written variables if there are none in the declaration. 2. It may not mention any `forall`-bound, underdetermined variables in the result kind. To resolve these issues, this patch: 1. Doesn't bother printing a herald about user-written variables if there are none. 2. Prints the result kind to advertise any underdetermination it may exhibit. Test Plan: make test TEST=T13777 Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13777 Differential Revision: https://phabricator.haskell.org/D4771
* Extended the plugin system to run plugins on more representationsBoldizsar Nemeth2018-06-0225-49/+676
| | | | | | | | | | | | | | | | | | | | Extend GHC plugins to access parsed, type checked representation, interfaces that are loaded. And splices that are evaluated. The goal is to enable development tools to access the GHC representation in the pre-existing build environment. See the full proposal here: https://ghc.haskell.org/trac/ghc/wiki/ExtendedPluginsProposal Reviewers: goldfire, bgamari, ezyang, angerman, mpickering Reviewed By: mpickering Subscribers: ezyang, angerman, mpickering, ulysses4ever, rwbarton, thomie, carter GHC Trac Issues: #14709 Differential Revision: https://phabricator.haskell.org/D4342
* Bump version of stm submodule back to 2.4Ben Gamari2018-06-021-0/+0
| | | | Haskeline doesn't have its upper bound lifted yet.
* testsuite: Don't assume location of bashBen Gamari2018-06-021-1/+1
|
* rts: Rip out support for STM invariantsBen Gamari2018-06-0221-547/+47
| | | | | | | | | | | | | | | | | | | | | | | This feature has some very serious correctness issues (#14310), introduces a great deal of complexity, and hasn't seen wide usage. Consequently we are removing it, as proposed in Proposal #77 [1]. This is heavily based on a patch from fryguybob. Updates stm submodule. [1] https://github.com/ghc-proposals/ghc-proposals/pull/77 Test Plan: Validate Reviewers: erikd, simonmar, hvr Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14310 Differential Revision: https://phabricator.haskell.org/D4760
* C codegen: print details of pprStatics panicsSergei Trofimovich2018-06-021-2/+2
| | | | Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
* vectorise: Put it out of its miseryBen Gamari2018-06-02208-16489/+97
| | | | | | | | | | | | | | | | | | | | | Poor DPH and its vectoriser have long been languishing; sadly it seems there is little chance that the effort will be rekindled. Every few years we discuss what to do with this mass of code and at least once we have agreed that it should be archived on a branch and removed from `master`. Here we do just that, eliminating heaps of dead code in the process. Here we drop the ParallelArrays extension, the vectoriser, and the `vector` and `primitive` submodules. Test Plan: Validate Reviewers: simonpj, simonmar, hvr, goldfire, alanz Reviewed By: simonmar Subscribers: goldfire, rwbarton, thomie, mpickering, carter Differential Revision: https://phabricator.haskell.org/D4761
* Add llvm-target for powerpc64le-unknown-linuxAlan Mock2018-06-022-0/+3
| | | | | | | | | | | | Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15212 Differential Revision: https://phabricator.haskell.org/D4765