summaryrefslogtreecommitdiff
path: root/testsuite
Commit message (Collapse)AuthorAgeFilesLines
* Standalone kind signatures (#16794)wip/top-level-kind-signaturesVladislav Zavialov2019-09-25208-200/+1571
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Implements GHC Proposal #54: .../ghc-proposals/blob/master/proposals/0054-kind-signatures.rst With this patch, a type constructor can now be given an explicit standalone kind signature: {-# LANGUAGE StandaloneKindSignatures #-} type Functor :: (Type -> Type) -> Constraint class Functor f where fmap :: (a -> b) -> f a -> f b This is a replacement for CUSKs (complete user-specified kind signatures), which are now scheduled for deprecation. User-facing changes ------------------- * A new extension flag has been added, -XStandaloneKindSignatures, which implies -XNoCUSKs. * There is a new syntactic construct, a standalone kind signature: type <name> :: <kind> Declarations of data types, classes, data families, type families, and type synonyms may be accompanied by a standalone kind signature. * A standalone kind signature enables polymorphic recursion in types, just like a function type signature enables polymorphic recursion in terms. This obviates the need for CUSKs. * TemplateHaskell AST has been extended with 'KiSigD' to represent standalone kind signatures. * GHCi :info command now prints the kind signature of type constructors: ghci> :info Functor type Functor :: (Type -> Type) -> Constraint ... Limitations ----------- * 'forall'-bound type variables of a standalone kind signature do not scope over the declaration body, even if the -XScopedTypeVariables is enabled. See #16635 and #16734. * Wildcards are not allowed in standalone kind signatures, as partial signatures do not allow for polymorphic recursion. * Associated types may not be given an explicit standalone kind signature. Instead, they are assumed to have a CUSK if the parent class has a standalone kind signature and regardless of the -XCUSKs flag. * Standalone kind signatures do not support multiple names at the moment: type T1, T2 :: Type -> Type -- rejected type T1 = Maybe type T2 = Either String See #16754. * Creative use of equality constraints in standalone kind signatures may lead to GHC panics: type C :: forall (a :: Type) -> a ~ Int => Constraint class C a where f :: C a => a -> Int See #16758. Implementation notes -------------------- * The heart of this patch is the 'kcDeclHeader' function, which is used to kind-check a declaration header against its standalone kind signature. It does so in two rounds: 1. check user-written binders 2. instantiate invisible binders a la 'checkExpectedKind' * 'kcTyClGroup' now partitions declarations into declarations with a standalone kind signature or a CUSK (kinded_decls) and declarations without either (kindless_decls): * 'kinded_decls' are kind-checked with 'checkInitialKinds' * 'kindless_decls' are kind-checked with 'getInitialKinds' * DerivInfo has been extended with a new field: di_scoped_tvs :: ![(Name,TyVar)] These variables must be added to the context in case the deriving clause references tcTyConScopedTyVars. See #16731.
* base: Move Ix typeclass to GHC.IxBen Gamari2019-09-252-18/+18
| | | | | The `Ix` class seems rather orthogonal to its original home in `GHC.Arr`.
* PmCheck: Only ever check constantly many models against a single patternSebastian Graf2019-09-255-3/+65
| | | | | | | | | | | | | | | | | | | | | | | | | Introduces a new flag `-fmax-pmcheck-deltas` to achieve that. Deprecates the old `-fmax-pmcheck-iter` mechanism in favor of this new flag. From the user's guide: Pattern match checking can be exponential in some cases. This limit makes sure we scale polynomially in the number of patterns, by forgetting refined information gained from a partially successful match. For example, when matching `x` against `Just 4`, we split each incoming matching model into two sub-models: One where `x` is not `Nothing` and one where `x` is `Just y` but `y` is not `4`. When the number of incoming models exceeds the limit, we continue checking the next clause with the original, unrefined model. This also retires the incredibly hard to understand "maximum number of refinements" mechanism, because the current mechanism is more general and should catch the same exponential cases like PrelRules at the same time. ------------------------- Metric Decrease: T11822 -------------------------
* Add -Wderiving-defaults (#15839)Kari Pahula2019-09-255-3/+26
| | | | | | Enabling both DeriveAnyClass and GeneralizedNewtypeDeriving can cause a warning when no explicit deriving strategy is in use. This change adds an enable/suppress flag for it.
* testsuite: Mark threadstatus-9333 as fragile in profthreadedBen Gamari2019-09-241-1/+1
| | | | Due to #16555.
* Add -fkeep-going to make compiler continue despite errors (#15424)Kari Pahula2019-09-2311-0/+50
| | | | | Add a new optional failure handling for upsweep which continues the compilation on other modules if any of them has errors.
* Get rid of PmFakewip/pmcheck-nofakeSebastian Graf2019-09-211-1/+1
| | | | | | | | | | | | | | | | | | | The pattern match oracle can now cope with the abundance of information that ViewPatterns, NPlusKPats, overloaded lists, etc. provide. No need to have PmFake anymore! Also got rid of a spurious call to `allCompleteMatches`, which we used to call *for every constructor* match. Naturally this blows up quadratically for programs like `ManyAlternatives`. ------------------------- Metric Decrease: ManyAlternatives Metric Increase: T11822 -------------------------
* Fix bogus type of case expressionwip/T17056Simon Peyton Jones2019-09-203-1/+49
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Issue #17056 revealed that we were sometimes building a case expression whose type field (in the Case constructor) was bogus. Consider a phantom type synonym type S a = Int and we want to form the case expression case x of K (a::*) -> (e :: S a) We must not make the type field of the Case constructor be (S a) because 'a' isn't in scope. We must instead expand the synonym. Changes in this patch: * Expand synonyms in the new function CoreUtils.mkSingleAltCase. * Use mkSingleAltCase in MkCore.wrapFloat, which was the proximate source of the bug (when called by exprIsConApp_maybe) * Use mkSingleAltCase elsewhere * Documentation CoreSyn new invariant (6) in Note [Case expression invariants] CoreSyn Note [Why does Case have a 'Type' field?] CoreUtils Note [Care with the type of a case expression] * I improved Core Lint's error reporting, which was pretty confusing in this case, because it didn't mention that the offending type was the return type of a case expression. * A little bit of cosmetic refactoring in CoreUtils
* testsuite: Add test for #17202Ben Gamari2019-09-202-0/+21
|
* Module hierarchy: Hs (#13009)Sylvain Henry2019-09-2016-40/+40
| | | | | | | Add GHC.Hs module hierarchy replacing hsSyn. Metric Increase: haddock.compiler
* testsuite: Add testcase for #17206Ben Gamari2019-09-193-0/+19
|
* Add a regression test for #11822Sebastian Graf2019-09-193-4/+54
| | | | | The particular test is already fixed, but the issue seems to have multiple different test cases lumped together.
* Test #17077.Richard Eisenberg2019-09-193-0/+14
|
* Use level numbers for generalisationRichard Eisenberg2019-09-192-6/+12
| | | | | | | | This fixes #15809, and is covered in Note [Use level numbers for quantification] in TcMType. This patch removes the "global tyvars" from the environment, a nice little win.
* Refactor kindGeneralize and friendsRichard Eisenberg2019-09-191-5/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit should have no change in behavior.(*) The observation was that Note [Recipe for checking a signature] says that every metavariable in a type-checked type must either (A) be generalized (B) be promoted (C) be zapped. Yet the code paths for doing these were all somewhat separate. This led to some steps being skipped. This commit shores this all up. The key innovation is TcHsType.kindGeneralizeSome, with appropriate commentary. This commit also sets the stage for #15809, by turning the WARNing about bad level-numbers in generalisation into an ASSERTion. The actual fix for #15809 will be in a separate commit. Other changes: * zonkPromoteType is now replaced by kindGeneralizeNone. This might have a small performance degradation, because zonkPromoteType zonked and promoted all at once. The new code path promotes first, and then zonks. * A call to kindGeneralizeNone was added in tcHsPartialSigType. I think this was a lurking bug, because it did not follow Note [Recipe for checking a signature]. I did not try to come up with an example showing the bug. This is the (*) above. Because of this change, there is an error message regression in partial-sigs/should_fail/T14040a. This problem isn't really a direct result of this refactoring, but is a symptom of something deeper. See #16775, which addresses the deeper problem. * I added a short-cut to quantifyTyVars, in case there's nothing to quantify. * There was a horribly-outdated Note that wasn't referred to. Gone now. * While poking around with T14040a, I discovered a small mistake in the Coercion.simplifyArgsWorker. Easy to fix, happily. * See new Note [Free vars in coercion hole] in TcMType. Previously, we were doing the wrong thing when looking at a coercion hole in the gather-candidates algorithm. Fixed now, with lengthy explanation. Metric Decrease: T14683
* Add a missing update of sc_hole_ty (#16312)Simon Peyton Jones2019-09-192-0/+15
| | | | | | | | | | | In simplCast I totally failed to keep the sc_hole_ty field of ApplyToTy (see Note [The hole type in ApplyToTy]) up to date. When a cast goes by, of course the hole type changes. Amazingly this has not bitten us before, but #16312 finally triggered it. Fortunately the fix is simple. Fixes #16312.
* Improve error message for out-of-scope variables + VTASimon Peyton Jones2019-09-175-11/+9
| | | | | | | | | | As #13834 and #17150 report, we get a TERRIBLE error message when you have an out of scope variable applied in a visible type application: (outOfScope @Int True) This very simple patch improves matters. See TcExpr Note [VTA for out-of-scope functions]
* Fix #13571 by adding an extension flag checkRichard Eisenberg2019-09-178-3/+28
| | | | Test case: indexed-types/should_fail/T13571
* Encode shape information in `PmOracle`Sebastian Graf2019-09-1650-36/+877
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously, we had an elaborate mechanism for selecting the warnings to generate in the presence of different `COMPLETE` matching groups that, albeit finely-tuned, produced wrong results from an end user's perspective in some cases (#13363). The underlying issue is that at the point where the `ConVar` case has to commit to a particular `COMPLETE` group, there's not enough information to do so and the status quo was to just enumerate all possible complete sets nondeterministically. The `getResult` function would then pick the outcome according to metrics defined in accordance to the user's guide. But crucially, it lacked knowledge about the order in which affected clauses appear, leading to the surprising behavior in #13363. In !1010 we taught the term oracle to reason about literal values a variable can certainly not take on. This MR extends that idea to `ConLike`s and thereby fixes #13363: Instead of committing to a particular `COMPLETE` group in the `ConVar` case, we now split off the matching constructor incrementally and record the newly covered case as a refutable shape in the oracle. Whenever the set of refutable shapes covers any `COMPLETE` set, the oracle recognises vacuosity of the uncovered set. This patch goes a step further: Since at this point the information in value abstractions is merely a cut down representation of what the oracle knows, value abstractions degenerate to a single `Id`, the semantics of which is determined by the oracle state `Delta`. Value vectors become lists of `[Id]` given meaning to by a single `Delta`, value set abstractions (of which the uncovered set is an instance) correspond to a union of `Delta`s which instantiate the same `[Id]` (akin to models of formula). Fixes #11528 #13021, #13363, #13965, #14059, #14253, #14851, #15753, #17096, #17149 ------------------------- Metric Decrease: ManyAlternatives T11195 -------------------------
* Add a test to make sure we don't regress on #17140 in the futureAlp Mestanogullari2019-09-135-0/+29
|
* Fix scoping of implicit parametersSimon Peyton Jones2019-09-133-0/+26
| | | | | | | | There was an outright bug in TcInteract.solveOneFromTheOther which meant that we did not always pick the innermost implicit parameter binding, causing #17104. The fix is easy, just a rearrangement of conditional tests
* testsuite: check for RTS linkerPeter Trommler2019-09-112-1/+2
| | | | Fixes #16833
* Module hierarchy: StgToCmm (#13009)Sylvain Henry2019-09-102-3/+3
| | | | | | Add StgToCmm module hierarchy. Platform modules that are used in several other places (NCG, LLVM codegen, Cmm transformations) are put into GHC.Platform.
* Make the C-- O and C types constructors with DataKindsJohn Ericson2019-09-051-1/+3
| | | | | The tightens up the kinds a bit. I use type synnonyms to avoid adding promotion ticks everywhere.
* Add additional step to T16804Eric Wolf2019-08-316-198/+889
| | | | | | | | | | | | | | | | Add another small test step Use the same identifier name in different scopes and see, if ':uses' handles that. Add another test step to check wether local bindings with the same identifier name might get confused Add easier to understand test output Fix annotated lines from file correctly
* Fix #17112Sebastian Graf2019-08-282-0/+34
| | | | | | | | | | | | | The `mkOneConFull` function of the pattern match checker used to try to guess the type arguments of the data type's type constructor by looking at the ambient type of the match. This doesn't work well for Pattern Synonyms, where the result type isn't even necessarily a TyCon application, and it shows in #11336 and #17112. Also the effort seems futile; why try to try hard when the type checker has already done the hard lifting? After this patch, we instead supply the type constructors arguments as an argument to the function and lean on the type-annotated AST.
* Fix #17067 by making data family type constructors actually injectiveRyan Scott2019-08-182-0/+12
| | | | | | | | `TcTyClsDecls.tcFamDecl1` was using `NotInjective` when creating data family type constructors, which is just plain wrong. This tweaks it to use `Injective` instead. Fixes #17067.
* Make add_info attach unfoldings (#16615)Tobias Dammers2019-08-154-12/+28
|
* Add test cases for #16615Tobias Dammers2019-08-154-0/+43
|
* GHCi supports not-necessarily-lifted join pointsRichard Eisenberg2019-08-145-3/+2
| | | | | | | | | | | | | | | | Fixes #16509. See Note [Not-necessarily-lifted join points] in ByteCodeGen, which tells the full story. This commit also adds some comments and cleans some code in the byte-code generator, as I was exploring around trying to understand it. (This commit removes an old test -- this is really a GHCi problem, not a pattern-synonym problem.) test case: ghci/scripts/T16509
* Use os.devnull instead of '/dev/null' in the testsuite driver.Andreas Klebinger2019-08-141-4/+26
| | | | | | | | | | | | The later caused issues on windows by being translated into "\\dev\\null" and python then trying to open this non-existant file. So we now use os.devnull inside python and convert it to "/dev/null" when calling out to the shell, which is bound to run in a unix like environment. This fixes an issue a test producing unexpected stderr output failed with a framework failure instead of showing a diff of the output.
* Add test for #16893Ömer Sinan Ağacan2019-08-103-0/+93
|
* Fix bug preventing information about patterns from being serialized in .hie ↵Zubin Duggal2019-08-076-0/+87
| | | | files
* Fix testmniip2019-08-071-1/+1
|
* Explicitly number equations when printing axiom incompatibilitiesmniip2019-08-071-3/+3
|
* Fix testmniip2019-08-071-9/+7
|
* Add a -fprint-axiom-incomps option (#15546)mniip2019-08-073-0/+17
| | | | | | | | | | | | | | | | | | | | | | | | | | Supply branch incomps when building an IfaceClosedSynFamilyTyCon `pprTyThing` now has access to incomps. This also causes them to be written out to .hi files, but that doesn't pose an issue other than a more faithful bijection between `tyThingToIfaceDecl` and `tcIfaceDecl`. The machinery for displaying axiom incomps was already present but not in use. Since this is now a thing that pops up in ghci's :info the format was modified to look like a haskell comment. Documentation and a test for the new feature included. Test Plan: T15546 Reviewers: simonpj, bgamari, goldfire Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15546 Differential Revision: https://phabricator.haskell.org/D5097
* testsuite: Rework tracking of fragile testsBen Gamari2019-08-043-7/+18
| | | | | Breaks fragile tests into two groups, allowing us to easily preserve stdout/stderr of failing fragile tests.
* testsuite: Add testsuite for #16978Ben Gamari2019-08-042-0/+30
|
* Use injectiveVarsOfType to catch dodgy type family instance binders (#17008)Ryan Scott2019-08-025-0/+61
| | | | | | | | | | | | | | | | Previously, we detected dodgy type family instances binders by expanding type synonyms (via `exactTyCoVarsOfType`) and looking for type variables on the RHS that weren't mentioned on the (expanded) LHS. But this doesn't account for type families (like the example in #17008), so we instead use `injectiveVarsOfType` to only count LHS type variables that are in injective positions. That way, the `a` in `type instance F (x :: T a) = a` will not count if `T` is a type synonym _or_ a type family. Along the way, I moved `exactTyCoVarsOfType` to `TyCoFVs` to live alongside its sibling functions that also compute free variables. Fixes #17008.
* Rip out 9-year-old pattern variable hack (#17007)Ryan Scott2019-08-023-9/+23
| | | | | | | | | | | | | | | | | | GHC had an ad hoc validity check in place to rule out pattern variables bound by type synonyms, such as in the following example: ```hs type ItemColID a b = Int -- Discards a,b get :: ItemColID a b -> ItemColID a b get (x :: ItemColID a b) = x :: ItemColID a b ``` This hack is wholly unnecessary nowadays, since OutsideIn(X) is more than capable of instantiating `a` and `b` to `Any`. In light of this, let's rip out this validity check. Fixes #17007.
* Fix T16916 CI failures (#16966)Ivan Kasatenko2019-08-011-4/+8
| | | | | | | | | 1. Slightly increased the waiting time for the tested effect to be more profound. 2. Introduced measuring of the actual time spent waiting and adjusing CPU time by it to compensate for threadDelay waiting time inconsistencies.
* Apply a missing substitution in mkEtaWW (#16979)Simon Peyton Jones2019-07-303-0/+266
| | | | | | | | | | The `mkEtaWW` case for newtypes forgot to apply the substitution to the newtype coercion, resulting in the Core Lint errors observed in #16979. Easily fixed. Fixes #16979. Co-authored-by: Ryan Scott <ryan.gl.scott@gmail.com>
* Add regression test for #16946nineonine2019-07-262-0/+13
|
* TemplateHaskell: reifyType (#16976)Vladislav Zavialov2019-07-267-0/+66
|
* Change behaviour of -ddump-cmm-verbose to dump each Cmm pass output to a ↵nineonine2019-07-265-2/+34
| | | | separate file and add -ddump-cmm-verbose-by-proc to keep old behaviour (#16930)
* Banish reportFloatingViaTvs to the shadow realm (#15831, #16181)Ryan Scott2019-07-2613-19/+206
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | GHC used to reject programs of this form: ``` newtype Age = MkAge Int deriving Eq via Const Int a ``` That's because an earlier implementation of `DerivingVia` would generate the following instance: ``` instance Eq Age where (==) = coerce @(Const Int a -> Const Int a -> Bool) @(Age -> Age -> Bool) (==) ``` Note that the `a` in `Const Int a` is not bound anywhere, which causes all sorts of issues. I figured that no one would ever want to write code like this anyway, so I simply banned "floating" `via` type variables like `a`, checking for their presence in the aptly named `reportFloatingViaTvs` function. `reportFloatingViaTvs` ended up being implemented in a subtly incorrect way, as #15831 demonstrates. Following counsel with the sage of gold fire, I decided to abandon `reportFloatingViaTvs` entirely and opt for a different approach that would _accept_ the instance above. This is because GHC now generates this instance instead: ``` instance forall a. Eq Age where (==) = coerce @(Const Int a -> Const Int a -> Bool) @(Age -> Age -> Bool) (==) ``` Notice that we now explicitly quantify the `a` in `instance forall a. Eq Age`, so everything is peachy scoping-wise. See `Note [Floating `via` type variables]` in `TcDeriv` for the full scoop. A pleasant benefit of this refactoring is that it made it much easier to catch the problem observed in #16181, so this patch fixes that issue too. Fixes #15831. Fixes #16181.
* Make sure to load interfaces when running :instancesXavier Denis2019-07-234-0/+29
|
* Fix #8487: Debugger confuses variablesRoland Senn2019-07-214-0/+19
| | | | | | | | | | To display the free variables for a single breakpoint, GHCi pulls out the information from the fields `modBreaks_breakInfo` and `modBreaks_vars` of the `ModBreaks` data structure. For a specific breakpoint this gives 2 lists of types 'Id` (`Var`) and `OccName`. They are used to create the Id's for the free variables and must be kept in sync: If we remove an element from the Names list, then we also must remove the corresponding element from the OccNames list.
* Do not ignore events deletion when events to be added are provided (#16916)Ivan Kasatenko2019-07-213-0/+47
| | | | | | | | | | | Kqueue/kevent implementation used to ignore events to be unsubscribed from when events to be subscribed to were provided. This resulted in a lost notification subscription, when GHC runtime didn't listen for any events, yet the kernel considered otherwise and kept waking up the IO manager thread. This commit fixes this issue by always adding and removing all of the provided subscriptions.