summaryrefslogtreecommitdiff
path: root/testsuite
Commit message (Collapse)AuthorAgeFilesLines
* testsuite: Add winio and winio_threaded wayswip/winioBen Gamari2020-07-1511-24/+13
| | | | Reverts many of the testsuite changes
* winio: Accept accepted stderr for linker_unload_multiple_objsAndreas Klebinger2020-07-151-0/+2
|
* winio: Accept accepted stderr for linker_unloadAndreas Klebinger2020-07-151-0/+2
|
* winio: Accept accepted stderr for T3807Andreas Klebinger2020-07-151-0/+4
|
* winio: fix T5435_dyn_gcc by accepting expected stderrAndreas Klebinger2020-07-151-0/+2
|
* winio: fix safePkg01 by accepting expected stderrAndreas Klebinger2020-07-151-0/+2
|
* winio: fix cabal01 by accepting expected stderrAndreas Klebinger2020-07-151-0/+2
|
* winio: fix cabal04 by filtering rts argsAndreas Klebinger2020-07-151-1/+1
|
* winio: Also accept T7037 stderrAndreas Klebinger2020-07-151-0/+2
|
* winio: Adjust T5435_dyn_asm stderrAndreas Klebinger2020-07-151-0/+2
| | | | | The warning about rtsopts having no consequences is expected. So accept new stderr.
* winio: Adjust T15261b stdout for --io-manager flag.Andreas Klebinger2020-07-151-1/+1
|
* winio: Fix stderr output for ghci/linking/dyn tests.Andreas Klebinger2020-07-153-1/+7
| | | | | We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds.
* winio: Fix cabal006 after upgrading cabal submoduleAndreas Klebinger2020-07-154-4/+4
| | | | Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions.
* winio: Switch Testsuite to test winio by defaultTamar Christina2020-07-151-1/+6
|
* Bump Cabal submoduleBen Gamari2020-07-1514-27/+25
| | | | | Updates a variety of tests as Cabal is now more strict about Cabal file form.
* testsuite: Add regression test for #17744Ben Gamari2020-07-154-0/+107
| | | | Test due to @monoidal.
* compiler: re-engineer the treatment of rebindable ifAlp Mestanogullari2020-07-1414-43/+193
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard.
* testsuite: Widen acceptance threshold on T5837wip/T18282Ben Gamari2020-07-131-1/+1
| | | | | | This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often.
* Reduce result discount in conSizeSimon Peyton Jones2020-07-1318-49/+99
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c
* Warn about empty Char enumerations (#18402)Aaron Allen2020-07-133-0/+19
| | | | | | | Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning.
* Give Uniq[D]FM a phantom type for its key.Andreas Klebinger2020-07-122-7/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM.
* add reproducer for #15630Artem Pelenitsyn2020-07-122-0/+61
|
* Improve eta-expansion using ArityTypeSimon Peyton Jones2020-07-116-36/+118
| | | | | | | | | | | | | | | | | | | | | | | | | | As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056
* Make arityType deal with join pointsSimon Peyton Jones2020-07-103-0/+102
| | | | | | | | | | | | | | | | | | | | | | | As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points.
* Fix GHCi :print on big-endian platformsStefan Schulze Frielinghaus2020-07-091-3/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455
* BigNum: rename BigNat typesSylvain Henry2020-07-071-1/+1
| | | | | | | | | | | | | | | Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this.
* testsuite: Widen T12234 acceptance window to 2%Ben Gamari2020-07-071-1/+1
| | | | | Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test.
* rts linker: teach the linker about GLIBC's special handling of *stat, mknod ↵Adam Sandberg Ericsson2020-07-075-0/+71
| | | | and atexit functions #7072
* add -flink-rts flag to link the rts when linking a shared or static library ↵Adam Sandberg Ericsson2020-07-073-1/+50
| | | | | | | | | | | | | | | | #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared.
* Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC versionHécate2020-07-033-0/+12
|
* Improve handling of data type return kindswip/T18300Simon Peyton Jones2020-07-0311-1/+80
| | | | | | | | | | | | | | | | | | Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD.
* NCG: correctly handle addresses with huge offsets (#15570)Sylvain Henry2020-07-022-0/+10
| | | | | | | | | | | | | | | | | | | Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace.
* Bump ghc-prim version to 0.7.0Ryan Scott2020-07-0271-79/+79
| | | | Fixes #18279. Bumps the `text` submodule.
* T16012: Be verbose on failure.Andreas Klebinger2020-07-022-2/+6
|
* Desugar quoted uses of DerivingVia and expression type signatures properlyRyan Scott2020-07-012-0/+30
| | | | | | | | | | | | | | | | | | | | | | | | | The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388.
* Implement -XLexicalNegation (GHC Proposal #229)Vladislav Zavialov2020-07-017-0/+70
| | | | | | | | This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule.
* Reject nested foralls/contexts in instance types more consistentlyRyan Scott2020-06-3017-37/+169
| | | | | | | | | | | | | | | | | | | | | | | | | | | GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271.
* Fix a typo in LintSimon Peyton Jones2020-06-282-0/+6
| | | | | | | This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399
* Fix duplicated words and typos in comments and user guideJan Hrček2020-06-282-2/+2
|
* Use NHsCoreTy to embed types into GND-generated codeRyan Scott2020-06-284-49/+37
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before.
* Fix ghc-bignum exceptionsSylvain Henry2020-06-274-3/+25
| | | | | | | | | | | | | | | We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch.
* Revamp the treatment of auxiliary bindings for derived instancesRyan Scott2020-06-274-51/+72
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321.
* Implement the proposed -XQualifiedDo extensionMatthias Pall Gissurarson2020-06-2640-2/+466
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors.
* Enable maxBound checks for OverloadedLists (Fixes #18172)Roland Senn2020-06-255-0/+97
| | | | | | | | | | | | | Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`.
* test suite: add reproducer for #17516Artem Pelenitsyn2020-06-253-0/+478
|
* In `:break ident` allow out of scope and nested identifiers (Fix #3000)Roland Senn2020-06-259-6/+73
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`.
* Add missing entry to freeNamesItem (#18369)Krzysztof Gogolewski2020-06-232-0/+11
|
* Fix a buglet in Simplify.simplCastSimon Peyton Jones2020-06-232-0/+11
| | | | | | | | | | | | | | | | | | | | | | | | This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal
* Fix issue #18262 by zonking constraints after solvingXavier Denis2020-06-234-0/+18
| | | | | | | | | | | | | Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results.
* Add tests for #17920Sylvain Henry2020-06-2310-9/+75
| | | | | | Metric Decrease: T12150 T12234