| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
| |
Subscribers: thomie, carter, RyanGlScott
GHC Trac Issues: #15067
Differential Revision: https://phabricator.haskell.org/D4622
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The element type of `List` maybe a type family instacen, rather than a
trivial type. For example in Trac #14547,
```
{-# LANGUAGE TypeFamilies, OverloadedLists #-}
class Foo f where
type It f
foo :: [It f] -> f
data List a = Empty | a :! List a deriving Show
instance Foo (List a) where
type It (List a) = a
foo [] = Empty
foo (x : xs) = x :! foo xs
```
Here the element type of `[]` is `It (List a)`, we should also normalize
it as `a`.
Test Plan: make test TEST="T14547"
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #14547
Differential Revision: https://phabricator.haskell.org/D4624
|
|
|
|
|
|
| |
This patch made the simplifier inline nested function bindings less aggressively
and, while it didn't seem to affect nofib, appears to have regressed T9630
rather considerably.
|
|
|
|
|
|
| |
@osa1 reported that the output on his machine has extra newlines:
https://phabricator.haskell.org/D4606#129092. This collapses consecutive
newlines.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: make test TEST=T15055
Reviewers: bgamari, RyanGlScott, osa1, Iceland_jack
Reviewed By: osa1
Subscribers: ulysses4ever, thomie, carter
GHC Trac Issues: #15055
Differential Revision: https://phabricator.haskell.org/D4621
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In `manifestSp` the unwind info was before the relevant instruction, not
after. I added some notes to establish semantics. Also removes
redundant annotation in stg_catch_frame.
For `makeFixupBlocks` it looks like we were off by `wORD_SIZE dflags`.
I'm not sure why, but it lines up with `manifestSp`. In fact it lines
up so well so that I can consolidate the Sp unwind logic in
`maybeAddUnwind`. I detected the problems with `makeFixupBlocks` by
running T14779b after patching D4559.
Test Plan: added a new test
Reviewers: bgamari, scpmw, simonmar, erikd
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #14999
Differential Revision: https://phabricator.haskell.org/D4606
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15093
Differential Revision: https://phabricator.haskell.org/D4645
|
|
|
|
|
|
| |
Trac #14904 was fixed in commit
faec8d358985e5d0bf363bd96f23fe76c9e281f7. Let's add some tests to
ensure that it stays fixed.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
We were unconditionally updating the nursery pointers to be
`nurseries[cap->no]`, but when using nursery chunks this might be
wrong. This manifested as a later assertion failure in allocate().
Test Plan: new test case
Reviewers: bgamari, niteria, erikd
Subscribers: thomie, carter
Differential Revision: https://phabricator.haskell.org/D4649
|
|
|
|
|
| |
This commit bumped T12425, T12234 and T12150 over their expected metrics on OS
X.
|
|
|
|
|
|
|
|
| |
Trac #15108 showed that the simple optimiser in CoreOpt
was accidentally eta-reducing a join point, so it didn't meet
its arity invariant.
This patch fixes it. See Note [Preserve join-binding arity].
|
|
|
|
| |
thanks to cdisselkoen for the nicely minimized test case.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Generally, when the type checker reports an error, more serious
ones suppress less serious ones.
A "variable out of scope" error is arguably the most serious of all,
so this patch moves it to the front of the list instead of the end.
This patch also fixes Trac #14149, which had
-fdefer-out-of-scope-variables, but also had a solid type error.
As things stood, the type error was not reported at all, and
compilation "succeeded" with error code 0. Yikes.
Note that
- "Hole errors" (including out of scope) are never suppressed.
(maybeReportHoleError vs maybeReportError in TcErorrs)
They can just get drowned by the noise.
- But with the new orientation, out of scope errors will suppress
type errors. That would be easy to change.
|
|
|
|
| |
Accidentally omitted from Trac #14955 commit.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
- remove PostRn/PostTc fields
- remove the HsVect In/Out distinction for Type, Class and Instance
- remove PlaceHolder in favour of NoExt
- Simplify OutputableX constraint
Updates haddock submodule
Test Plan: ./validate
Reviewers: goldfire, bgamari
Subscribers: goldfire, thomie, mpickering, carter
Differential Revision: https://phabricator.haskell.org/D4625
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Matthew Pickering uncovered a bad performance hole in the way
that single-method dictionaries work, described in Trac #14955.
See Note [Do not unpack class dictionaries] in WwLib.
I tried to fix this 6 years ago, but got it slightly wrong. This patch
fixes it, which makes a dramatic improvement in the test case.
Nofib highlights: not much happening:
Program Size Allocs Runtime Elapsed TotalMem
-----------------------------------------------------------------
VSM -0.3% +2.7% -7.4% -7.4% 0.0%
cacheprof -0.0% +0.1% +0.3% +0.7% 0.0%
integer -0.0% +1.1% +7.5% +7.5% 0.0%
tak -0.1% -0.2% 0.024 0.024 0.0%
-----------------------------------------------------------------
Min -4.4% -0.2% -7.4% -7.4% -8.0%
Max +0.6% +2.7% +7.5% +7.5% 0.0%
Geom Mean -0.1% +0.0% +0.1% +0.1% -0.2%
I investigated VSM. The patch unpacks class dictionaries a bit more
than before (i.e. does so if there is no INLINABLE pragma). And that
gives better code in VSM (less dictionary selection etc), but one closure
gets one word bigger.
I'll accept these changes in exchange for more robust performance.
Some ghci.debugger output wobbled around (order of bindings
being displayed). I have no idea why; but I accepted the changes.
|
|
|
|
|
|
|
|
|
|
|
|
| |
This relied on Int# being 64-bits. This is nothing a bit of CPP can't
fix, but I think the right solution would be to make out treatment of
word-size dependent types more consistent, as suggested by #11953.
Test Plan: Validate on i386
Subscribers: thomie, carter
Differential Revision: https://phabricator.haskell.org/D4614
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We simply truncate the result to 32-bits to ensure that the test passed
under both environments.
Test Plan: Validate on 32-bit
Subscribers: thomie, carter
GHC Trac Issues: #13623
Differential Revision: https://phabricator.haskell.org/D4615
|
|
|
|
| |
so that we notice if someone accidentially implements this...
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The coercion optimizer will take care of it anyway, and the check is
prohibitively expensive.
See Trac #14737.
Reviewers: bgamari
Subscribers: simonpj, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4568
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch has a single significant change:
strictness wrapper functions are inlined earlier,
in phase 2 rather than phase 0.
As shown by Trac #15056, this gives a better chance for RULEs to fire.
Before this change, a function that would have inlined early without
strictness analyss was instead inlining late. Result: applying
"optimisation" made the program worse.
This does not make too much difference in nofib, but I've stumbled
over the problem more than once, so even a "no-change" result would be
quite acceptable. Here are the headlines:
--------------------------------------------------------------------------------
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
cacheprof -0.5% -0.5% +2.5% +2.5% 0.0%
fulsom -1.0% +2.6% -0.1% -0.1% 0.0%
mate -0.6% +2.4% -0.9% -0.9% 0.0%
veritas -0.7% -23.2% 0.002 0.002 0.0%
--------------------------------------------------------------------------------
Min -1.4% -23.2% -12.5% -15.3% 0.0%
Max +0.6% +2.6% +4.4% +4.3% +19.0%
Geometric Mean -0.7% -0.2% -1.4% -1.7% +0.2%
* A worthwhile reduction in binary size.
* Runtimes are not to be trusted much but look as if they
are moving the right way.
* A really big win in veritas, described in comment:1 of
Trac #15056; more fusion rules fired.
* I investigated the losses in 'mate' and 'fulsom'; see #15056.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
While addressing nonlinear behavior related to coercion roles,
particularly `NthCo`, we noticed that coercion roles are recalculated
often even though they should be readily at hand already in most cases.
This patch adds a `Role` to the `NthCo` constructor so that we can cache
them rather than having to recalculate them on the fly.
https://ghc.haskell.org/trac/ghc/ticket/11735#comment:23 explains the
approach.
Performance improvement over GHC HEAD, when compiling Grammar.hs (see below):
GHC 8.2.1:
```
ghc Grammar.hs 176.27s user 0.23s system 99% cpu 2:56.81 total
```
before patch (but with other optimizations applied):
```
ghc Grammar.hs -fforce-recomp 175.77s user 0.19s system 100% cpu 2:55.78 total
```
after:
```
../../ghc/inplace/bin/ghc-stage2 Grammar.hs 10.32s user 0.17s system 98% cpu 10.678 total
```
Introduces the following regressions:
- perf/compiler/parsing001 (possibly false positive)
- perf/compiler/T9872
- perf/compiler/haddock.base
Reviewers: goldfire, bgamari, simonpj
Reviewed By: simonpj
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #11735
Differential Revision: https://phabricator.haskell.org/D4394
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We weren't linting the types used in `newFamInst`, which
might have been why #15012 went undiscovered for so long. Let's fix
that.
One has to be surprisingly careful with expanding type synonyms in
`lintType`, since in the offending program (simplified):
```lang=haskell
type FakeOut a = Int
type family TF a
type instance TF Int = FakeOut a
```
If one expands type synonyms, then `FakeOut a` will expand to
`Int`, which masks the issue (that `a` is unbound). I added an
extra Lint flag to configure whether type synonyms should be
expanded or not in Lint, and disabled this when calling `lintTypes`
from `newFamInst`.
As evidence that this works, I ran it on the offending program
from #15012, and voilà:
```
$ ghc3/inplace/bin/ghc-stage2 Bug.hs -dcore-lint
[1 of 1] Compiling Foo ( Bug.hs, Bug.o )
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 8.5.20180417 for x86_64-unknown-linux):
Core Lint error
<no location info>: warning:
In the type ‘... (Rec0 (FakeOut b_a1Qt))))’
@ b_a1Qt is out of scope
```
Test Plan: make test TEST=T15057
Reviewers: simonpj, goldfire, bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15057
Differential Revision: https://phabricator.haskell.org/D4611
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This fixes all unexpected passes and unexpected failures from a
`./validate --slow` run I did last week. I commented on many
tickets and created a few more as I was going through the failing
tests. A summary of the entire process is available at:
https://gist.github.com/alpmestan/c371840968f086c8dc5b56af8325f0a9
This is part of an attempt to have `./validate --slow` pass,
tracked in #14890. Another patch will be necessary for the unexpected
stats failures.
Test Plan: ./validate --slow (not green yet)
Reviewers: bgamari, simonmar
Subscribers: thomie, carter
Differential Revision: https://phabricator.haskell.org/D4546
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary: Bumps several submodules.
Test Plan: ./validate
Reviewers: hvr, bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15018
Differential Revision: https://phabricator.haskell.org/D4609
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, derived `Generic1` instances could have associated `Rep1`
type family instances with unbound variables, such as in the following
example:
```lang=haskell
data T a = MkT (FakeOut a) deriving Generic1
type FakeOut a = Int
==>
instance Generic1 T where
type Rep1 T = ... (Rec0 (FakeOut a))
```
Yikes! To avoid this, we simply map the last type variable in a
derived `Generic1` instance to `Any`.
Test Plan: make test TEST=T15012
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: simonpj, thomie, carter
GHC Trac Issues: #15012
Differential Revision: https://phabricator.haskell.org/D4602
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
For empty character literal, the `''`, report error message properly
rather than just throw a "parser error" with wrong error location.
Test Plan: make test TEST="T13450 T13450TH"
Reviewers: goldfire, bgamari
Reviewed By: bgamari
Subscribers: thomie, mpickering, carter
GHC Trac Issues: #13450
Differential Revision: https://phabricator.haskell.org/D4594
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Because the program doesn't have any binders that -XStrict can make
strict, the desugarer output should be identical when it's compiled with
and without -XStrict. This wasn't the case with GHC 8.2.2, but
apparently it was fixed some time between 8.2.2 and 8.4.1. We now add a
test case to make sure it stays fixed.
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: simonpj, rwbarton, thomie, carter
GHC Trac Issues: #14815
Differential Revision: https://phabricator.haskell.org/D4531
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
Differential Revision: https://phabricator.haskell.org/D4565
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
#14710 revealed two unfortunate regressions related to kind
polymorphism that had crept in in recent GHC releases:
1. While GHC was able to catch illegal uses of kind polymorphism
(i.e., if `PolyKinds` wasn't enabled) in limited situations, it
wasn't able to catch kind polymorphism of the following form:
```lang=haskell
f :: forall a. a -> a
f x = const x g
where
g :: Proxy (x :: a)
g = Proxy
```
Note that the variable `a` is being used as a kind variable in the
type signature of `g`, but GHC happily accepts it, even without
the use of `PolyKinds`.
2. If you have `PolyKinds` (but not `TypeInType`) enabled, then GHC
incorrectly accepts the following definition:
```lang=haskell
f :: forall k (a :: k). Proxy a
f = Proxy
```
Even though `k` is explicitly bound and then later used as a kind
variable within the same telescope.
This patch fixes these two bugs as follows:
1. Whenever we rename any `HsTyVar`, we check if the following three
criteria are met:
(a) It's a type variable
(b) It's used at the kind level
(c) `PolyKinds` is not enabled
If so, then we have found an illegal use of kind polymorphism, so
throw an error.
This check replaces the `checkBadKindBndrs` function, which could
only catch illegal uses of kind polymorphism in very limited
situations (when the bad kind variable happened to be implicitly
quantified in the same type signature).
2. In `extract_hs_tv_bndrs`, we must error if `TypeInType` is not
enabled and either of the following criteria are met:
(a) An explicitly bound type variable is used in kind position
in the body of a `forall` type.
(b) An explicitly bound type variable is used in kind position
in the kind of a bound type variable in a `forall` type.
`extract_hs_tv_bndrs` was checking (a), but not (b). Easily fixed.
Test Plan: ./validate
Reviewers: goldfire, simonpj, bgamari, hvr
Reviewed By: simonpj
Subscribers: thomie, carter
GHC Trac Issues: #14710
Differential Revision: https://phabricator.haskell.org/D4554
|
|
|
|
|
|
|
| |
I need to upgrade GHC on the CI builders before landing this due to a
bug in 8.2.1 triggered by this patch.
This reverts commit fea04defa64871caab6339ff3fc5511a272f37c7.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Until now GHC only supported basic constant folding (lit op lit, expr op
0, etc.).
This patch uses laws of +/-/* (associativity, commutativity,
distributivity) to support some constant folding into nested
expressions.
Examples of new transformations:
- simple nesting: (10 + x) + 10 becomes 20 + x
- deep nesting: 5 + x + (y + (z + (t + 5))) becomes 10 + (x + (y + (z + t)))
- distribution: (5 + x) * 6 becomes 30 + 6*x
- simple factorization: 5 + x + (x + (x + (x + 5))) becomes 10 + (4 *x)
- siblings: (5 + 4*x) - (3*x + 2) becomes 3 + x
Test Plan: validate
Reviewers: simonpj, austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
GHC Trac Issues: #9136
Differential Revision: https://phabricator.haskell.org/D2858
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Some of these tests instruct the RTS to ignore all RTS flags being
passed. While this is intended it causes test failures for some ways
like profiling which depend on passing RTS flags. So we skip these ways.
Test Plan: testsuite/tests/rts/flags$ make slow
Reviewers: bgamari, simonmar, alpmestan
Reviewed By: alpmestan
Subscribers: alpmestan, thomie, carter
GHC Trac Issues: #12870
Differential Revision: https://phabricator.haskell.org/D4585
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, GHC was quite eager to panic whenever it was fed
an archive file when `DYNAMIC_GHC_PROGRAMS=YES`. This ought to be an
explicit error message instead, so this patch accomplishes just that.
Test Plan: make test TEST=T14708
Reviewers: Phyx, hvr, bgamari
Reviewed By: Phyx
Subscribers: thomie, carter
GHC Trac Issues: #9438, #14708, #15032
Differential Revision: https://phabricator.haskell.org/D4589
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This takes care of bumping the `base` and `integer-gmp`
minor version numbers in anticipation of a GHC 8.4.2 release.
While I was in town, I also filled in a `@since TODO` Haddock
annotation for `powModSecInteger` in `integer-gmp` with
`1.0.2.0`, and updated the changelog accordingly.
Test Plan: ./validate
Reviewers: hvr, goldfire, bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15025
Differential Revision: https://phabricator.haskell.org/D4586
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
- Add the balance of the TTG extensions for hsSyn/HsBinds
- Move all the (now orphan) data instances into hsSyn/HsInstances and
use TTG Data instances Plan B
https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances#PLANB
Updates haddock submodule.
Illustrative numbers
Compiling HsInstances before using Plan B.
Max residency ~ 5G
<<ghc: 629,864,691,176 bytes, 5300 GCs,
321075437/1087762592 avg/max bytes residency (23 samples),
2953M in use, 0.000 INIT (0.000 elapsed),
383.511 MUT (384.986 elapsed), 37.426 GC (37.444 elapsed) :ghc>>
Using Plan B
Max residency 1.1G
<<ghc: 78,832,782,968 bytes, 2884 GCs,
222140352/386470152 avg/max bytes residency (34 samples),
1062M in use, 0.001 INIT (0.001 elapsed),
56.612 MUT (62.917 elapsed), 32.974 GC (32.923 elapsed) :ghc>>
Test Plan: ./validate
Reviewers: shayan-najd, goldfire, bgamari
Subscribers: goldfire, thomie, mpickering, carter
Differential Revision: https://phabricator.haskell.org/D4581
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This reverts commit ffb2738f86c4e4c3f0eaacf0a95d7326fdd2e383.
Due to #14987.
Reviewers: goldfire, RyanGlScott
Reviewed By: RyanGlScott
Subscribers: RyanGlScott, thomie, carter
GHC Trac Issues: #14987, #14838
Differential Revision: https://phabricator.haskell.org/D4545
|
|
|
|
|
| |
this succeeds on `master` right now, but I confirmed that it fails on
ghc-8.4.1-release.
|
|
|
|
|
|
|
|
|
|
|
|
| |
As the CSE transformation traverses the syntax tree, it needs to go past
the lambdas of a join point, and only look for CSE opportunities inside,
as a join point’s lambdas must be preserved. Simple fix; comes with a
Note and a test case.
Thanks to Ryan Scott for an excellently minimized test case, and for
bisecting GHC.
Differential Revision: https://phabricator.haskell.org/D4572
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The following commits were reverted prior to the release of GHC 8.4.1,
because the time to derive Data instances was too long [1].
438dd1cbba13d35f3452b4dcef3f94ce9a216905 Phab:D4147
e3ec2e7ae94524ebd111963faf34b84d942265b4 Phab:D4177
47ad6578ea460999b53eb4293c3a3b3017a56d65 Phab:D4186
The work is continuing, as the minimum bootstrap compiler is now
GHC 8.2.1, and this allows Plan B[2] for instances to be used. This
will land in a following commit.
Updates Haddock submodule
[1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances
[2] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances#PLANB
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
There has been at least one breaking change to
`template-haskell` (the removal of `qAddForeignFile`) which is
causing packages like `th-orphans` and `singletons` to fail to build
with GHC HEAD. Let's bump `template-haskell`'s major version number
so that these packages can properly guard against these changes.
While I was in town, I also started a `changelog` section for
the next major version of `template-haskell`, and copied over
finishing touches for `template-haskell-2.13.0.0`.
Test Plan: ./validate
Reviewers: bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
Differential Revision: https://phabricator.haskell.org/D4558
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Before, GHC would never print visible tyvars in the absence
of `-fprint-explicit-foralls`, which led to `:kind` displaying
incorrect kinds in GHCi. The fix is simple—simply check beforehand
if any of the type variable binders are required when deciding when
to pretty-print them.
Test Plan: make test TEST=T14238
Reviewers: simonpj, goldfire, bgamari
Subscribers: thomie, carter
GHC Trac Issues: #14238
Differential Revision: https://phabricator.haskell.org/D4564
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary: This seems to have changed recently but the new output looks plausible.
Reviewers: RyanGlScott
Reviewed By: RyanGlScott
Subscribers: RyanGlScott, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4561
|
|
|
|
|
|
|
|
|
| |
It turns out that solveEqualities really does need to use simpl_top.
I thought that solveWanteds would be enough, and no existing test
case showed up the different. #14991 shows that we need simpl_top.
Easy enough to fix.
test case: dependent/should_compile/T14991
|
|
|
|
|
|
| |
This fixes the SplitWD "unexpected pass". This test was fixed
by ef443820b71f5c9c2dca362217f1a9fbab6dd736 and somehow fell
through my validation cracks.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit:
commit fb050a330ad202c1eb43038dc18cca2a5be26f4a
Author: Simon Peyton Jones <simonpj@microsoft.com>
Date: Thu Oct 12 11:00:19 2017 +0100
Do not bind coercion variables in SpecConstr rules
arranged to reject any SpecConstr call pattern that mentioned
a coercion in the pattern.
There was a good reason for that
-- see Note [SpecConstr and casts] --
but I didn't realise how important it was to accept patterns
that mention casts in /terms/. Trac #14936 showed this up.
This patch just narrows the restriction to discard only
the cases where the coercion is mentioned only in types.
Fortunately that was pretty easy to do.
|
|
|
|
|
|
|
|
|
|
| |
Trac #14978 pointed out that single-constructor GADTs should be
unpackable without trouble.
Acutally I realise that even existentials should be unpackable
too, but that's a bit more work, so it's not part of this patch.
See Note [Unpacking GADTs and existentials] in MkId.
|
|
|
|
|
|
|
| |
These were fixed by faec8d358985e5d0bf363bd96f23fe76c9e281f7
test cases: typecheck/should_fail/T14884
ghci/scripts/T14969
|