summaryrefslogtreecommitdiff
path: root/testsuite/tests
Commit message (Collapse)AuthorAgeFilesLines
* Split HsConDecl{H98,GADT}DetailsRyan Scott2020-10-305-12/+14
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule.
* Check for large tuples more thoroughlywip/T18723Ryan Scott2020-10-2918-31/+283
| | | | | | | | | | | | | | | | | | | | This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump.
* Split GHC.Driver.TypesSylvain Henry2020-10-2912-11/+16
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule
* Widen acceptance threshold for T10421aJohn Ericson2020-10-291-1/+1
| | | | | | | Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being.
* Fix two constraint solving problemsSimon Peyton Jones2020-10-274-18/+27
| | | | | | | | | | | | | | | | | | | | | This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion
* Version bump: base-4.16 (#18712)Vladislav Zavialov2020-10-2710-13/+15
| | | | Also bumps upper bounds on base in boot libraries (incl. submodules).
* Fix error message location in tcCheckPatSynDeclSimon Peyton Jones2020-10-234-2/+27
| | | | | | | | Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed.
* Parser regression tests, close #12862 #12446wip/parsing-tests-12446-12862Vladislav Zavialov2020-10-215-0/+25
| | | | | These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing.
* testsuite: Mark T12971 as fragile on WindowsBen Gamari2020-10-201-1/+1
| | | | Due to #17945.
* API Annotations: Keep track of unicode for linear arrow notationwip/az/unicode-hsscaledAlan Zimmerman2020-10-207-23/+46
| | | | | | | | | | | The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule
* Compile modules with `-fobject-code` enabled to byte-code when loaded with ↵nineonine2020-10-203-0/+21
| | | | | | | | | | | | | | | `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly.
* testsuite: Add test for #18346Ben Gamari2020-10-203-0/+43
| | | | This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20.
* Implement -Woperator-whitespace (#18834)Vladislav Zavialov2020-10-196-1/+49
| | | | | | | | | | | | | | This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers.
* Apply suggestion to testsuite/tests/ffi/should_run/all.TDylanZA2020-10-171-1/+6
|
* When using rts_setInCallCapability, lock incall threadsDylan Yudaken2020-10-173-0/+116
| | | | | | | | This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability.
* Testsuite: Add dead arity analysis testsSebastian Graf2020-10-1755-2537/+809
| | | | | We didn't seem to test these old tests at all, judging from their expected output.
* Arity: Record arity types for non-recursive letsSebastian Graf2020-10-174-1/+108
| | | | | | | | | | | | | | | | | | | | | | | In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707
* Arity: Refactor fixed-point iteration in GHC.Core.Opt.AritySebastian Graf2020-10-171-7/+7
| | | | | | | | | | | | | | | Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment).
* Skip type family defaults with hs-boot and hsig filesJohn Ericson2020-10-1715-0/+253
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320
* testsuite: Account for -Wnoncanonical-monoid-instances changes on WindowsBen Gamari2020-10-163-9/+0
|
* Extend mAX_TUPLE_SIZE to 64GHC GitLab CI2020-10-154-21/+23
| | | | As well a ctuples and sums.
* Add flags for annotating Generic{,1} methods INLINE[1] (#11068)Andrzej Rybczak2020-10-158-0/+968
| | | | | | | | Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227
* testsuite: Add missing #include on <stdlib.h>Ben Gamari2020-10-151-0/+1
| | | | This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols.
* Fix some missed opportunities for preInlineUnconditionallySimon Peyton Jones2020-10-1421-395/+350
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370
* Add -Wnoncanonical-{monad,monoid}-instances to standardWarningsFumiaki Kinoshita2020-10-1429-74/+45
| | | | | | | | | ------------------------- Metric Decrease: T12425 Metric Increase: T17516 -------------------------
* Fix PostfixOperators (#18151)Vladislav Zavialov2020-10-143-0/+19
| | | | | This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case.
* Make DataKinds the sole arbiter of kind-level literals (and friends)Ryan Scott2020-10-143-0/+14
| | | | | | | | | | | | | | | | | | | | | | | Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831.
* Unification of Nat and NaturalsHaskellMouse2020-10-1311-33/+58
| | | | | | | | | | | | | | | | | | | | | | | This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated.
* Fall back to types when looking up data constructors (#18740)wip/ghc-18740-lookup-updateDaniel Rogozin2020-10-1114-6/+86
| | | | | | | | | | | | | | | | | | | | Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables.
* Bignum: fix bigNatCompareWord# bug (#18813)Sylvain Henry2020-10-103-0/+27
|
* Linear types: fix quantification in GADTs (#18790)Krzysztof Gogolewski2020-10-101-6/+21
|
* Testsuite: increase timeout for T18223 (#18795)Sylvain Henry2020-10-091-0/+2
|
* Add TyCon Set/Env and use them in a few places.Andreas Klebinger2020-10-091-1/+1
| | | | | | | | | | | Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles.
* Fix desugaring of record updates on data familiesSimon Peyton Jones2020-10-092-0/+34
| | | | | | | | | | | | This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners.
* Linear types: fix roles in GADTs (#18799)Krzysztof Gogolewski2020-10-093-0/+19
|
* Bignum: match on small Integer/NaturalSylvain Henry2020-10-093-0/+12
| | | | | | | | | Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test).
* Use proper RTS flags when collecting residency in perf tests.Andreas Klebinger2020-10-092-15/+12
| | | | | | | | | | | | | | | | | | | | Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 -------------------------
* Update containers to v0.6.4.1Simon Jakobi2020-10-091-1/+1
| | | | Updates containers submodule.
* Misc cleanupKrzysztof Gogolewski2020-10-076-6/+6
| | | | | | | | | | | * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732)
* Preserve as-parsed arrow type for HsUnrestrictedArrowAlan Zimmerman2020-10-075-2/+71
| | | | | | | | | | When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791
* WinIO: Small changes related to atomic request swaps.Andreas Klebinger2020-10-075-4/+63
| | | | | | | | | | | | Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things.
* Fix linear types in TH splices (#18465)Krzysztof Gogolewski2020-10-053-0/+25
|
* Reject linearity in kinds in checkValidType (#18780)Krzysztof Gogolewski2020-10-026-4/+29
| | | | Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673
* Bignum: implement integerPowMod (#18427)Sylvain Henry2020-10-024-22/+36
| | | | | | | Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing.
* Bignum: implement integerRecipMod (#18427)Sylvain Henry2020-10-025-6/+46
|
* Fix typos in commentsKrzysztof Gogolewski2020-10-021-1/+1
| | | | [skip ci]
* Bignum: add integerNegate RULESylvain Henry2020-10-013-0/+19
|
* Fix pretty-printing of the mult-polymorphic arrowVladislav Zavialov2020-10-015-11/+11
| | | | A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04)
* Add regression test for #18755.Richard Eisenberg2020-10-013-0/+6
| | | | Close #18755
* Don't attach CPR signatures to NOINLINE data structures (#18154)Sebastian Graf2020-10-011-3/+3
| | | | | | | | | | | | | | | | | Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected.