summaryrefslogtreecommitdiff
path: root/testsuite
Commit message (Collapse)AuthorAgeFilesLines
* testsuite: Run tests in nonmoving_thr in speed==slowBen Gamari2019-11-081-0/+2
|
* SetLevels: Don't set context level when floating casesBen Gamari2019-11-083-1/+20
| | | | | | | | | | | When floating a single-alternative case we previously would set the context level to the level where we were floating the case. However, this is wrong as we are only moving the case and its binders. This resulted in #16978, where the disrepancy caused us to unnecessarily abstract over some free variables of the case body, resulting in shadowing and consequently Core Lint failures. (cherry picked from commit a2a0e6f3bb2d02a9347dec4c7c4f6d4480bc2421)
* Testsuite: Introduce req_rts_linkerStefan Schulze Frielinghaus2019-11-0816-37/+38
| | | | | Some tests depend on the RTS linker. Introduce a modifier to skip such tests, in case the RTS linker is not available.
* Clean up TH's treatment of unary tuples (or, #16881 part two)Ryan Scott2019-11-0711-30/+98
| | | | | | | | | | | | | | !1906 left some loose ends in regards to Template Haskell's treatment of unary tuples. This patch ends to tie up those loose ends: * In addition to having `TupleT 1` produce unary tuples, `TupE [exp]` and `TupP [pat]` also now produce unary tuples. * I have added various special cases in GHC's pretty-printers to ensure that explicit 1-tuples are printed using the `Unit` type. See `testsuite/tests/th/T17380`. * The GHC 8.10.1 release notes entry has been tidied up a little. Fixes #16881. Fixes #17371. Fixes #17380.
* Check EmptyCase by simply adding a non-void constraintSebastian Graf2019-11-0525-33/+168
| | | | | | | | | | | | | | | | | | | | | | | | | | | We can handle non-void constraints since !1733, so we can now express the strictness of `-XEmptyCase` just by adding a non-void constraint to the initial Uncovered set. For `case x of {}` we thus check that the Uncovered set `{ x | x /~ ⊥ }` is non-empty. This is conceptually simpler than the plan outlined in #17376, because it talks to the oracle directly. In order for this patch to pass the testsuite, I had to fix handling of newtypes in the pattern-match checker (#17248). Since we use a different code path (well, the main code path) for `-XEmptyCase` now, we apparently also handle #13717 correctly. There's also some dead code that we can get rid off now. `provideEvidence` has been updated to provide output more in line with the old logic, which used `inhabitationCandidates` under the hood. A consequence of the shift away from the `UncoveredPatterns` type is that we don't report reduced type families for empty case matches, because the pretty printer is pure and only knows the match variable's type. Fixes #13717, #17248, #17386
* testsuite: skip test requiring RTS linker on PowerPCPeter Trommler2019-11-0513-31/+21
| | | | | | | | | | The RTS linker is not available on 64-bit PowerPC. Instead of marking tests that require the RTS linker as broken on PowerPC 64-bit skip the respective tests on all platforms where the RTS linker or a statically linked external interpreter is not available. Fixes #11259
* Separate `LPat` from `Pat` on the type-levelSebastian Graf2019-11-021-8/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Since the Trees That Grow effort started, we had `type LPat = Pat`. This is so that `SrcLoc`s would only be annotated in GHC's AST, which is the reason why all GHC passes use the extension constructor `XPat` to attach source locations. See #15495 for the design discussion behind that. But now suddenly there are `XPat`s everywhere! There are several functions which dont't cope with `XPat`s by either crashing (`hsPatType`) or simply returning incorrect results (`collectEvVarsPat`). This issue was raised in #17330. I also came up with a rather clean and type-safe solution to the problem: We define ```haskell type family XRec p (f :: * -> *) = r | r -> p f type instance XRec (GhcPass p) f = Located (f (GhcPass p)) type instance XRec TH f = f p type LPat p = XRec p Pat ``` This is a rather modular embedding of the old "ping-pong" style, while we only pay for the `Located` wrapper within GHC. No ping-ponging in a potential Template Haskell AST, for example. Yet, we miss no case where we should've handled a `SrcLoc`: `hsPatType` and `collectEvVarsPat` are not callable at an `LPat`. Also, this gets rid of one indirection in `Located` variants: Previously, we'd have to go through `XPat` and `Located` to get from `LPat` to the wrapped `Pat`. Now it's just `Located` again. Thus we fix #17330.
* Make CSE delay inlining lessSimon Peyton Jones2019-11-017-5/+23
| | | | | | | | | CSE delays inlining a little bit, to avoid losing vital specialisations; see Note [Delay inlining after CSE] in CSE. But it was being over-enthusiastic. This patch makes the delay only apply to Ids with specialisation rules, which avoids unnecessary delay (#17409).
* testsuite: Add test for #17423Ben Gamari2019-11-012-0/+38
|
* template-haskell: require at least 1 GADT constructor name (#17379)Adam Sandberg Eriksson2019-11-015-0/+26
|
* testsuite: Make ExplicitForAllRules1 more robustBen Gamari2019-11-012-11/+15
| | | | Previously the test relied on `id` not inlining. Fix this.
* Add another test for #17267Simon Peyton Jones2019-11-013-0/+41
| | | | This one came in a comment from James Payor
* Fix running of ratio test casetaylorfausak2019-11-011-1/+1
|
* Add tests for rounding ratiostaylorfausak2019-11-012-0/+42
|
* Whitespace forward compatibility for proposal #229Vladislav Zavialov2019-10-3014-43/+23
| | | | | | | | GHC Proposal #229 changes the lexical rules of Haskell, which may require slight whitespace adjustments in certain cases. This patch changes formatting in a few places in GHC and its testsuite in a way that enables it to compile under the proposed rules.
* testsuite: Fix quoting of $(TEST_HC) in T12674Ben Gamari2019-10-291-2/+2
| | | | I have no idea how this went unnoticed until now.
* Attach API Annotations for {-# SOURCE #-} import pragmaAlan Zimmerman2019-10-284-0/+48
| | | | | | | Attach the API annotations for the start and end locations of the {-# SOURCE #-} pragma in an ImportDecl. Closes #17388
* Refactor TcDeriv to validity-check less in anyclass/via deriving (#13154)Ryan Scott2019-10-286-1/+123
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Due to the way `DerivEnv` is currently structured, there is an invariant that every derived instance must consist of a class applied to a non-empty list of argument types, where the last argument *must* be an application of a type constructor to some arguments. This works for many cases, but there are also some design patterns in standalone `anyclass`/`via` deriving that are made impossible due to enforcing this invariant, as documented in #13154. This fixes #13154 by refactoring `TcDeriv` and friends to perform fewer validity checks when using the `anyclass` or `via` strategies. The highlights are as followed: * Five fields of `DerivEnv` have been factored out into a new `DerivInstTys` data type. These fields only make sense for instances that satisfy the invariant mentioned above, so `DerivInstTys` is now only used in `stock` and `newtype` deriving, but not in other deriving strategies. * There is now a `Note [DerivEnv and DerivSpecMechanism]` describing the bullet point above in more detail, as well as explaining the exact requirements that each deriving strategy imposes. * I've refactored `mkEqnHelp`'s call graph to be slightly less complicated. Instead of the previous `mkDataTypeEqn`/`mkNewTypeEqn` dichotomy, there is now a single entrypoint `mk_eqn`. * Various bits of code were tweaked so as not to use fields that are specific to `DerivInstTys` so that they may be used by all deriving strategies, since not all deriving strategies use `DerivInstTys`.
* Fix #15344: use fail when desugaring applicative-doJosef Svenningsson2019-10-288-9/+234
| | | | | | | | | | | | | | | | Applicative-do has a bug where it fails to use the monadic fail method when desugaring patternmatches which can fail. See #15344. This patch fixes that problem. It required more rewiring than I had expected. Applicative-do happens mostly in the renamer; that's where decisions about scheduling are made. This schedule is then carried through the typechecker and into the desugarer which performs the actual translation. Fixing this bug required sending information about the fail method from the renamer, through the type checker and into the desugarer. Previously, the desugarer didn't have enough information to actually desugar pattern matches correctly. As a side effect, we also fix #16628, where GHC wouldn't catch missing MonadFail instances with -XApplicativeDo.
* Parenthesize nullary constraint tuples using sigPrec (#17403)Ryan Scott2019-10-274-0/+12
| | | | | | | | | We were using `appPrec`, not `sigPrec`, as the precedence when determining whether or not to parenthesize `() :: Constraint`, which lead to the parentheses being omitted in function contexts like `(() :: Constraint) => String`. Easily fixed. Fixes #17403.
* testsuite: Skip regalloc_unit_tests unless have_ncgBen Gamari2019-10-261-0/+1
| | | | | This is a unit test for the native code generator's register allocator; naturally. the NCG is required.
* Fix #14690 - :steplocal panics after break-on-errorRoland Senn2019-10-264-0/+19
| | | | | | | | | | | | | | `:steplocal` enables only breakpoints in the current top-level binding. When a normal breakpoint is hit, then the module name and the break id from the `BRK_FUN` byte code allow us to access the corresponding entry in a ModBreak table. From this entry we then get the SrcSpan (see compiler/main/InteractiveEval.hs:bindLocalsAtBreakpoint). With this source-span we can then determine the current top-level binding, needed for the steplocal command. However, if we break at an exception or at an error, we don't have an BRK_FUN byte-code, so we don't have any source information. The function `bindLocalsAtBreakpoint` creates an `UnhelpfulSpan`, which doesn't allow us to determine the current top-level binding. To avoid a `panic`, we have to check for `UnhelpfulSpan` in the function `ghc/GHCi/UI.hs:stepLocalCmd`. Hence a :steplocal command after a break-on-exception or a break-on-error is not possible.
* Implement shrinkSmallMutableArray# and resizeSmallMutableArray#.Andrew Martin2019-10-263-0/+90
| | | | | | | | | | | | | | | | | | | | | This is a part of GHC Proposal #25: "Offer more array resizing primitives". Resources related to the proposal: - Discussion: https://github.com/ghc-proposals/ghc-proposals/pull/121 - Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0025-resize-boxed.rst Only shrinkSmallMutableArray# is implemented as a primop since a library-space implementation of resizeSmallMutableArray# (in GHC.Exts) is no less efficient than a primop would be. This may be replaced by a primop in the future if someone devises a strategy for growing arrays in-place. The library-space implementation always copies the array when growing it. This commit also tweaks the documentation of the deprecated sizeofMutableByteArray#, removing the mention of concurrency. That primop is unsound even in single-threaded applications. Additionally, the non-negativity assertion on the existing shrinkMutableByteArray# primop has been removed since this predicate is trivially always true.
* testsuite: Use fragile modifier in TH_foreignInterruptibleBen Gamari2019-10-251-2/+1
| | | | It looks like this use of `skip` snuck through my previous refactoring.
* testsuite: Mark T13786 as fragile in unreg buildBen Gamari2019-10-251-1/+3
| | | | Due to #17018.
* Mark promoted InfixT names as IsPromoted (#17394)Ryan Scott2019-10-243-0/+19
| | | | | We applied a similar fix for `ConT` in #15572 but forgot to apply the fix to `InfixT` as well. This patch fixes #17394 by doing just that.
* Make isTcLevPoly more conservative with newtypes (#17360)Ryan Scott2019-10-243-0/+18
| | | | | | | | | | | | `isTcLevPoly` gives an approximate answer for when a type constructor is levity polymorphic when fully applied, where `True` means "possibly levity polymorphic" and `False` means "definitely not levity polymorphic". `isTcLevPoly` returned `False` for newtypes, which is incorrect in the presence of `UnliftedNewtypes`, leading to #17360. This patch tweaks `isTcLevPoly` to return `True` for newtypes instead. Fixes #17360.
* Parenthesize GADT return types in pprIfaceConDecl (#17384)Ryan Scott2019-10-244-0/+16
| | | | | | | We were using `pprIfaceAppArgs` instead of `pprParendIfaceAppArgs` in `pprIfaceConDecl`. Oops. Fixes #17384.
* Merge non-moving garbage collectorBen Gamari2019-10-236-55/+123
|\ | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This introduces a concurrent mark & sweep garbage collector to manage the old generation. The concurrent nature of this collector typically results in significantly reduced maximum and mean pause times in applications with large working sets. Due to the large and intricate nature of the change I have opted to preserve the fully-buildable history, including merge commits, which is described in the "Branch overview" section below. Collector design ================ The full design of the collector implemented here is described in detail in a technical note > B. Gamari. "A Concurrent Garbage Collector For the Glasgow Haskell > Compiler" (2018) This document can be requested from @bgamari. The basic heap structure used in this design is heavily inspired by > K. Ueno & A. Ohori. "A fully concurrent garbage collector for > functional programs on multicore processors." /ACM SIGPLAN Notices/ > Vol. 51. No. 9 (presented at ICFP 2016) This design is intended to allow both marking and sweeping concurrent to execution of a multi-core mutator. Unlike the Ueno design, which requires no global synchronization pauses, the collector introduced here requires a stop-the-world pause at the beginning and end of the mark phase. To avoid heap fragmentation, the allocator consists of a number of fixed-size /sub-allocators/. Each of these sub-allocators allocators into its own set of /segments/, themselves allocated from the block allocator. Each segment is broken into a set of fixed-size allocation blocks (which back allocations) in addition to a bitmap (used to track the liveness of blocks) and some additional metadata (used also used to track liveness). This heap structure enables collection via mark-and-sweep, which can be performed concurrently via a snapshot-at-the-beginning scheme (although concurrent collection is not implemented in this patch). Implementation structure ======================== The majority of the collector is implemented in a handful of files: * `rts/Nonmoving.c` is the heart of the beast. It implements the entry-point to the nonmoving collector (`nonmoving_collect`), as well as the allocator (`nonmoving_allocate`) and a number of utilities for manipulating the heap. * `rts/NonmovingMark.c` implements the mark queue functionality, update remembered set, and mark loop. * `rts/NonmovingSweep.c` implements the sweep loop. * `rts/NonmovingScav.c` implements the logic necessary to scavenge the nonmoving heap. Branch overview =============== ``` * wip/gc/opt-pause: | A variety of small optimisations to further reduce pause times. | * wip/gc/compact-nfdata: | Introduce support for compact regions into the non-moving |\ collector | \ | \ | | * wip/gc/segment-header-to-bdescr: | | | Another optimization that we are considering, pushing | | | some segment metadata into the segment descriptor for | | | the sake of locality during mark | | | | * | wip/gc/shortcutting: | | | Support for indirection shortcutting and the selector optimization | | | in the non-moving heap. | | | * | | wip/gc/docs: | |/ Work on implementation documentation. | / |/ * wip/gc/everything: | A roll-up of everything below. |\ | \ | |\ | | \ | | * wip/gc/optimize: | | | A variety of optimizations, primarily to the mark loop. | | | Some of these are microoptimizations but a few are quite | | | significant. In particular, the prefetch patches have | | | produced a nontrivial improvement in mark performance. | | | | | * wip/gc/aging: | | | Enable support for aging in major collections. | | | | * | wip/gc/test: | | | Fix up the testsuite to more or less pass. | | | * | | wip/gc/instrumentation: | | | A variety of runtime instrumentation including statistics | | / support, the nonmoving census, and eventlog support. | |/ | / |/ * wip/gc/nonmoving-concurrent: | The concurrent write barriers. | * wip/gc/nonmoving-nonconcurrent: | The nonmoving collector without the write barriers necessary | for concurrent collection. | * wip/gc/preparation: | A merge of the various preparatory patches that aren't directly | implementing the GC. | | * GHC HEAD . . . ```
| * testsuite: Don't run T7160 in nonmoving_thr waysBen Gamari2019-10-221-1/+1
| | | | | | | | The nonmoving way finalizes things in a different order.
| * testsuite: Don't run T9630 in nonmoving waysBen Gamari2019-10-221-1/+3
| | | | | | | | The nonmoving collector doesn't support -G1
| * testsuite: Skip T15892 in nonmoving_thr_ghcBen Gamari2019-10-221-1/+1
| |
| * testsuite: bug1010 requires -c, which isn't supported by nonmovingBen Gamari2019-10-221-1/+4
| |
| * testsuite: Ensure that threaded tests are run in nonmoving_thrBen Gamari2019-10-222-9/+13
| |
| * testsuite: Nonmoving collector doesn't support -G1Ben Gamari2019-10-221-1/+2
| |
| * testsuite: Don't run T15892 in nonmoving waysBen Gamari2019-10-221-3/+5
| | | | | | | | The nonmoving GC doesn't support `+RTS -G1`, which this test insists on.
| * testsuite: Add nonmoving_thr_ghc wayBen Gamari2019-10-221-1/+4
| | | | | | | | This uses the nonmoving collector when compiling the testcases.
| * testsuite: Add nonmoving_thr wayBen Gamari2019-10-221-3/+6
| |
| * testsuite: Add nonmoving WAYBen Gamari2019-10-201-2/+5
| | | | | | | | | | This simply runs the compile_and_run tests with `-xn`, enabling the nonmoving oldest generation.
| * rts/BlockAlloc: Allow aligned allocation requestswip/gc/aligned-block-allocationÖmer Sinan Ağacan2019-10-181-37/+84
| | | | | | | | | | | | | | | | | | | | | | This implements support for block group allocations which are aligned to an integral number of blocks. This will be used by the nonmoving garbage collector, which uses the block allocator to allocate the segments which back its heap. These segments are a fixed number of blocks in size, with each segment being aligned to the segment size boundary. This allows us to easily find the segment metadata stored at the beginning of the segment.
* | Add new flag for unarised STG dumpsÖmer Sinan Ağacan2019-10-231-34/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | Previously -ddump-stg would dump pre and post-unarise STGs. Now we have a new flag for post-unarise STG and -ddump-stg only dumps coreToStg output. STG dump flags after this commit: - -ddump-stg: Dumps CoreToStg output - -ddump-stg-unarised: Unarise output - -ddump-stg-final: STG right before code gen (includes CSE and lambda lifting)
* | Performance tests: Reduce acceptance threshold for bytes allocated testsMatthew Pickering2019-10-231-41/+41
| | | | | | | | | | | | | | The "new" performance testing infrastructure resets the baseline after every test so it's easy to miss gradual performance regressions over time. We should at least make these numbers smaller to catch patches which affect performance earlier.
* | Fix bug in the x86 backend involving the CFG.Andreas Klebinger2019-10-231-144/+240
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This is part two of fixing #17334. There are two parts to this commit: - A bugfix for computing loop levels - A bugfix of basic block invariants in the NCG. ----------------------------------------------------------- In the first bug we ended up with a CFG of the sort: [A -> B -> C] This was represented via maps as fromList [(A,B),(B,C)] and later transformed into a adjacency array. However the transformation did not include block C in the array (since we only looked at the keys of the map). This was still fine until we tried to look up successors for C and tried to read outside of the array bounds when accessing C. In order to prevent this in the future I refactored to code to include all nodes as keys in the map representation. And make this a invariant which is checked in a few places. Overall I expect this to make the code more robust as now any failed lookup will represent an error, versus failed lookups sometimes being expected and sometimes not. In terms of performance this makes some things cheaper (getting a list of all nodes) and others more expensive (adding a new edge). Overall this adds up to no noteable performance difference. ----------------------------------------------------------- Part 2: When the NCG generated a new basic block, it did not always insert a NEWBLOCK meta instruction in the stream which caused a quite subtle bug. During instruction selection a statement `s` in a block B with control of the sort: B -> C will sometimes result in control flow of the sort: ┌ < ┐ v ^ B -> B1 ┴ -> C as is the case for some atomic operations. Now to keep the CFG in sync when introducing B1 we clearly want to insert it between B and C. However there is a catch when we have to deal with self loops. We might start with code and a CFG of these forms: loop: stmt1 ┌ < ┐ .... v ^ stmtX loop ┘ stmtY .... goto loop: Now we introduce B1: ┌ ─ ─ ─ ─ ─┐ loop: │ ┌ < ┐ │ instrs v │ │ ^ .... loop ┴ B1 ┴ ┘ instrsFromX stmtY goto loop: This is simple, all outgoing edges from loop now simply start from B1 instead and the code generator knows which new edges it introduced for the self loop of B1. Disaster strikes if the statement Y follows the same pattern. If we apply the same rule that all outgoing edges change then we end up with: loop ─> B1 ─> B2 ┬─┐ │ │ └─<┤ │ │ └───<───┘ │ └───────<────────┘ This is problematic. The edge B1->B1 is modified as expected. However the modification is wrong! The assembly in this case looked like this: _loop: <instrs> _B1: ... cmpxchgq ... jne _B1 <instrs> <end _B1> _B2: ... cmpxchgq ... jne _B2 <instrs> jmp loop There is no edge _B2 -> _B1 here. It's still a self loop onto _B1. The problem here is that really B1 should be two basic blocks. Otherwise we have control flow in the *middle* of a basic block. A contradiction! So to account for this we add yet another basic block marker: _B: <instrs> _B1: ... cmpxchgq ... jne _B1 jmp _B1' _B1': <instrs> <end _B1> _B2: ... Now when inserting B2 we will only look at the outgoing edges of B1' and everything will work out nicely. You might also wonder why we don't insert jumps at the end of _B1'. There is no way another block ends up jumping to the labels _B1 or _B2 since they are essentially invisible to other blocks. View them as control flow labels local to the basic block if you'd like. Not doing this ultimately caused (part 2 of) #17334.
* | Allow command name resolution for GHCi commands with option `!` #17345Takenobu Tani2019-10-233-0/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit allows command name resolution for GHCi commands with option `!` as follows: ghci> :k! Int Int :: * = Int This commit changes implementation as follows: Before: * Prefix match with full string including the option `!` (e.g. `k!`) After (this patch): * Prefix match without option suffix `!` (e.g. `k`) * in addition, suffix match with option `!` See also #8305 and #8113
* | Reify oversaturated data family instances correctly (#17296)Ryan Scott2019-10-233-0/+57
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | `TcSplice` was not properly handling oversaturated data family instances, such as the example in #17296, as it dropped arguments due to carelessly zipping data family instance arguments with `tyConTyVars`. For data families, the number of `tyConTyVars` can sometimes be less than the number of arguments it can accept in a data family instance due to the fact that data family instances can be oversaturated. To account for this, `TcSplice.mkIsPolyTvs` has now been renamed to `tyConArgsPolyKinded` and now factors in `tyConResKind` in addition to `tyConTyVars`. I've also added `Note [Reified instances and explicit kind signatures]` which explains the various subtleties in play here. Fixes #17296.
* | compiler: introduce DynFlags pluginsAlp Mestanogullari2019-10-237-0/+80
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | They have type '[CommandLineOpts] -> Maybe (DynFlags -> IO DynFlags)'. All plugins that supply a non-Nothing 'dynflagsPlugin' will see their updates applied to the current DynFlags right after the plugins are loaded. One use case for this is to superseede !1580 for registering hooks from a plugin. Frontend/parser plugins were considered to achieve this but they respectively conflict with how this plugin is going to be used and don't allow overriding/modifying the DynFlags, which is how hooks have to be registered. This commit comes with a test, 'test-hook-plugin', that registers a "fake" meta hook that replaces TH expressions with the 0 integer literal.
* | Implement a coverage checker for injectivityRichard Eisenberg2019-10-2320-24/+107
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This fixes #16512. There are lots of parts of this patch: * The main payload is in FamInst. See Note [Coverage condition for injective type families] there for the overview. But it doesn't fix the bug. * We now bump the reduction depth every time we discharge a CFunEqCan. See Note [Flatten when discharging CFunEqCan] in TcInteract. * Exploration of this revealed a new, easy to maintain invariant for CTyEqCans. See Note [Almost function-free] in TcRnTypes. * We also realized that type inference for injectivity was a bit incomplete. This means we exchanged lookupFlattenTyVar for rewriteTyVar. See Note [rewriteTyVar] in TcFlatten. The new function is monadic while the previous one was pure, necessitating some faff in TcInteract. Nothing too bad. * zonkCt did not maintain invariants on CTyEqCan. It's not worth the bother doing so, so we just transmute CTyEqCans to CNonCanonicals. * The pure unifier was finding the fixpoint of the returned substitution, even when doing one-way matching (in tcUnifyTysWithTFs). Fixed now. Test cases: typecheck/should_fail/T16512{a,b}
* | CI: Always dump performance metrics.David Eichmann2019-10-226-20/+37
| |
* | Windows: Update tarballs to GCC 9.2 and remove MAX_PATH limit.Tamar Christina2019-10-206-12/+10
|/
* testsuite: Assert that testsuite ways are knownBen Gamari2019-10-172-28/+50
| | | | | This ensures that all testsuite way names given to `omit_ways`, `only_ways`, etc. are known ways.