| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
|
|
|
|
| |
We had a constraint (a b ~R# Int), and were marking it as 'insoluble'.
That's bad; it isn't. And it caused Trac #15431. Soultion is simple.
I did a tiny refactor on can_eq_app, so that it is used only for
nominal equalities.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This fixes #15346, and is a team effort between Ryan Scott and
myself (mostly Ryan). We discovered two errors related to FC's
"push" rules, one in the TPush rule (as implemented in pushCoTyArg)
and one in KPush rule (it shows up in liftCoSubstVarBndr).
The solution: do what the paper says, instead of whatever random
thoughts popped into my head as I was actually implementing.
Also fixes #15419, which is actually the same underlying problem.
Test case: dependent/should_compile/T{15346,15419}.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: validate
Reviewers: RyanGlScott, bgamari
Reviewed By: RyanGlScott
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15365
Differential Revision: https://phabricator.haskell.org/D4998
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
In D4592, `AddWordC` is lowered as an unsigned subtraction instead
of an unsigned addition when compiling with LLVM.
This patch rectifies that.
Reviewers: angerman, bgamari, monoidal
Reviewed By: angerman, bgamari, monoidal
Subscribers: osa1, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4969
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
`collectLStmtsBinders` was returning nothing for `ApplicativeStmts`, which
caused the debugger to not track free variables in many cases when using
`ApplicativeDo`.
Test Plan:
* new test case
* validate
Reviewers: bgamari, erikd
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15422
Differential Revision: https://phabricator.haskell.org/D4991
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
This fixes the problem revealed by a new assert as it relates to valid
hole fits. However, tests `T10384`, `T14040a` and `TcStaticPointersFail02`
still fail the assert, but they are unrelated to valid hole fits.
Reviewers: bgamari, simonpj
Reviewed By: simonpj
Subscribers: simonpj, rwbarton, thomie, carter
GHC Trac Issues: #15384
Differential Revision: https://phabricator.haskell.org/D4994
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
While working on [D904](https://phabricator.haskell.org/D4904), I noticed that
'findTopDir' was being invoked three times. This isn't a big problem, because
it is usually very cheap. On windows, it does require some involved logic,
though, so to me it would make sense to only run it once.
Reviewers: bgamari, monoidal
Reviewed By: monoidal
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4987
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Previously, we were using `pprStmtContext` instead, which
led to error messages missing indefinite articles where they were
required.
Test Plan: make test TEST="T13242a T7786 Typeable1"
Reviewers: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15423
Differential Revision: https://phabricator.haskell.org/D4992
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari, osa1
Reviewed By: osa1
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4985
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
On Windows one is not allowed to drop the stack by more than a page size.
The reason for this is that the OS only allocates enough stack till what
the TEB specifies. After that a guard page is placed and the rest of the
virtual address space is unmapped.
The intention is that doing stack allocations will cause you to hit the
guard which will then map the next page in and move the guard. This is
done to prevent what in the Linux world is known as stack clash
vulnerabilities https://access.redhat.com/security/cve/cve-2017-1000364.
There are modules in GHC for which the liveliness analysis thinks the
reserved 8KB of spill slots isn't enough. One being DynFlags and the
other being Cabal.
Though I think the Cabal one is likely a bug:
```
4d6544: 81 ec 00 46 00 00 sub $0x4600,%esp
4d654a: 8d 85 94 fe ff ff lea -0x16c(%ebp),%eax
4d6550: 3b 83 1c 03 00 00 cmp 0x31c(%ebx),%eax
4d6556: 0f 82 de 8d 02 00 jb 4ff33a <_cLpg_info+0x7a>
4d655c: c7 45 fc 14 3d 50 00 movl $0x503d14,-0x4(%ebp)
4d6563: 8b 75 0c mov 0xc(%ebp),%esi
4d6566: 83 c5 fc add $0xfffffffc,%ebp
4d6569: 66 f7 c6 03 00 test $0x3,%si
4d656e: 0f 85 a6 d7 02 00 jne 503d1a <_cLpb_info+0x6>
4d6574: 81 c4 00 46 00 00 add $0x4600,%esp
```
It allocates nearly 18KB of spill slots for a simple 4 line function
and doesn't even use it. Note that this doesn't happen on x64 or
when making a validate build. Only when making a build without a
validate and build.mk.
This and the allocation in DynFlags means the stack allocation will jump
over the guard page into unmapped memory areas and GHC or an end program
segfaults.
The pagesize on x86 Windows is 4KB which means we hit it very easily for
these two modules, which explains the total DOA of GHC 32bit for the past
3 releases and the "random" segfaults on Windows.
```
0:000> bp 00503d29
0:000> gn
Breakpoint 0 hit
WARNING: Stack overflow detected. The unwound frames are extracted from outside
normal stack bounds.
eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40
eip=00503d29 esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc
cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202
setup+0x103d29:
00503d29 89442440 mov dword ptr [esp+40h],eax ss:002b:013e973c=????????
WARNING: Stack overflow detected. The unwound frames are extracted from outside
normal stack bounds.
WARNING: Stack overflow detected. The unwound frames are extracted from outside
normal stack bounds.
0:000> !teb
TEB at 00384000
ExceptionList: 013effcc
StackBase: 013f0000
StackLimit: 013eb000
```
This doesn't fix the liveliness analysis but does fix the allocations, by
emitting a function call to `__chkstk_ms` when doing allocations of larger
than a page, this will make sure the stack is probed every page so the kernel
maps in the next page.
`__chkstk_ms` is provided by `libGCC`, which is under the
`GNU runtime exclusion license`, so it's safe to link against it, even for
proprietary code. (Technically we already do since we link compiled C code in.)
For allocations smaller than a page we drop the stack and probe the new address.
This avoids the function call and still makes sure we hit the guard if needed.
PS: In case anyone is Wondering why we didn't notice this before, it's because we
only test x86_64 and on Windows 10. On x86_64 the page size is 8KB and also the
kernel is a bit more lenient on Windows 10 in that it seems to catch the segfault
and resize the stack if it was unmapped:
```
0:000> t
eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40
eip=00503d2d esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc
cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202
setup+0x103d2d:
00503d2d 8b461b mov eax,dword ptr [esi+1Bh] ds:002b:03b6b9e4=03cac431
0:000> !teb
TEB at 00384000
ExceptionList: 013effcc
StackBase: 013f0000
StackLimit: 013e9000
```
Likely Windows 10 has a guard page larger than previous versions.
This fixes the stack allocations, and as soon as I get the time I will look at
the liveliness analysis. I find it highly unlikely that simple Cabal function
requires ~2200 spill slots.
Test Plan: ./validate
Reviewers: simonmar, bgamari
Reviewed By: bgamari
Subscribers: AndreasK, rwbarton, thomie, carter
GHC Trac Issues: #15154
Differential Revision: https://phabricator.haskell.org/D4917
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari, osa1
Reviewed By: osa1
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15408
Differential Revision: https://phabricator.haskell.org/D4978
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: goldfire, bgamari, osa1
Reviewed By: osa1
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15407
Differential Revision: https://phabricator.haskell.org/D4977
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: goldfire, bgamari, RyanGlScott
Reviewed By: RyanGlScott
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15406
Differential Revision: https://phabricator.haskell.org/D4976
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: goldfire, bgamari, mpickering
Reviewed By: mpickering
Subscribers: mpickering, goldfire, rwbarton, thomie, carter
GHC Trac Issues: #15405
Differential Revision: https://phabricator.haskell.org/D4975
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* All the tests in tests/ghci.debugger now pass with
-fexternal-interpreter. These tests are now run with the ghci-ext way
in addition to the normal way so we won't break it in the future.
* I removed all the unsafeCoerce# calls from RtClosureInspect. Yay!
The main changes are:
* New messages: GetClosure and Seq. GetClosure is a remote interface to
GHC.Exts.Heap.getClosureData, which required Binary instances for
various datatypes. Fortunately this wasn't too painful thanks to
DeriveGeneric.
* No cheating by unsafeCoercing values when printing them. Now we have
to turn the Closure representation back into the native representation
when printing Int, Float, Double, Integer and Char. Of these, Integer
was the most painful - we now have a dependency on integer-gmp due to
needing access to the representation.
* Fixed a bug in rts/Heap.c - it was bogusly returning stack content as
pointers for an AP_STACK closure.
Test Plan:
* `cd testsuite/tests/ghci.debugger && make`
* validate
Reviewers: bgamari, patrickdoc, nomeata, angerman, hvr, erikd, goldfire
Subscribers: alpmestan, snowleopard, rwbarton, thomie, carter
GHC Trac Issues: #13184
Differential Revision: https://phabricator.haskell.org/D4955
|
|
|
|
|
|
| |
Some hash signs in documents in primops.txt.pp were not escaped
properly. Those raw hash signs were kept in haddock and texts
between those hash signs were interpreted as anchors by haddock.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Implementation of the "Embrace TypeInType" proposal was done according
to the spec, which specified that TypeOperators must imply NoStarIsType.
This implication was meant to prevent breakage and to be removed in 2
releases. However, compiling head.hackage has shown that this
implication only magnified the breakage, so there is no reason to have
it in the first place.
To remain in compliance with the three-release policy, we add a
workaround to define the (*) type operator even when -XStarIsType is on.
Test Plan: ./validate
Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr
Reviewed By: bgamari, RyanGlScott
Subscribers: harpocrates, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4865
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #15338 is yet another example where -Bsymbolic breaks
semantics of a C program: global variable duplication happens
and unsafePerformIO creates two stdout copies.
When -Bsymbolic is not used both C compiler and linker agree
on how global variables are handled. In case of sh4 it consists
on a few assertions:
1. global variable is exported from shared library
2. code is referred to this variable via GOT-like mechanism to allow
interposition
3. global variable is present .bss section on an executable
(as an R_*_COPY relocation: symbol contents is copied at executable
startup time)
4. and symbol in executable interposes symbol in shared library.
This way both code in shared library and code in executable refer
to a copy of global variable in .bss section of an executable.
Unfortunately -Bsymbolic option breaks assumption [2.] and generates
direct references to the symbol. This causes mismatch between
values seen from executable and values seen from shared library code.
This change disables '-Bsymbolic' for unregisterised targets.
Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
Test Plan: test 'ghc-pkg --version | cat' to emit data
Reviewers: simonmar, bgamari, jrtc27
Reviewed By: jrtc27
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15338
Differential Revision: https://phabricator.haskell.org/D4959
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
All these were detected by -fghci-leak-check when GHC was
compiled *without* optimisation (e.g. using the "quick" build flavour).
Unfortunately I don't know of a good way to keep this working. I'd like
to just disable the -fghci-leak-check flag when the compiler is built
without optimisation, but it doesn't look like we have an easy way to do
that. And even if we could, it would be fragile anyway,
Test Plan: `cd testsuite/tests/ghci; make`
Reviewers: bgamari, hvr, erikd, tdammers
Subscribers: tdammers, rwbarton, thomie, carter
GHC Trac Issues: #15246
Differential Revision: https://phabricator.haskell.org/D4872
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In the following
data FieldOcc pass = FieldOcc { extFieldOcc :: XFieldOcc pass
, rdrNameFieldOcc :: Located RdrName
-- ^ See Note [Located RdrNames] in HsExpr
}
| XFieldOcc
(XXFieldOcc pass)
we are using XFieldOcc for both the extFieldOcc type and the extra constructor.
The first one should be XCFieldOcc
Updates haddock submodule
closes #15386
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: simonmar, hvr, bgamari, erikd, fryguybob, rrnewton
Reviewed By: simonmar
Subscribers: fryguybob, rwbarton, thomie, carter
GHC Trac Issues: #15364
Differential Revision: https://phabricator.haskell.org/D4884
|
|
|
|
|
|
|
|
| |
A recent commit added extra calls to mkNakedCastTy to satisfy
Note [The tcType invariant]. However, some of these casts were
being applied to unsaturated type family applications, which
caused ASSERTion failures in TcFlatten later on. This patch
is more judicious in using mkNakedCastTy to avoid this problem.
|
|
|
|
|
|
|
| |
Previously, this check was done in mkDataCon. But this
sometimes caused assertion failures if an invalid data
con was made. I've moved the check to checkValidDataCon,
where we can be sure the datacon is otherwise valid first.
|
|
|
|
|
|
|
|
|
| |
This removes an ASSERTion that TcLevels should increase by
exactly one in every implication. While this is a sensible
goal, it's not true today, and we should not be crippling
DEBUG for everyone while debugging this.
The ASSERT was added in 261dd83cacec71edd551e9c581d05285c9ea3226
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
A conversation with Richard made me look at floatEqualities again, and
I did not find it easy to read. This patch refactors it sligtly, with
better variable naming and more comments.
I also fixed one latent bug, I think. In the old code, I think that an
inhomogeneous or insoluble equality (co :: t1~t2), which doesn't float,
and ended up in the badly-named 'non_eqs', would not end up in
extended_skols. Hence it would not capture an equality that mentioned
'co' in a cast.
It's still pretty horrible (as Richard and I have been discussing),
but better.
No change in behaviour; I don't know a program that would trigger
the latent bug, even if my reasoning is right.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This allows modification of each `HsGroup` after it has been renamed.
The old behaviour of keeping the renamed source until later can be
recovered if desired by using the `keepRenamedSource` plugin but it
shouldn't really be necessary as it can be inspected in the `TcGblEnv`.
Reviewers: nboldi, bgamari, alpmestan
Reviewed By: nboldi, alpmestan
Subscribers: alpmestan, rwbarton, thomie, carter
GHC Trac Issues: #15315
Differential Revision: https://phabricator.haskell.org/D4947
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari, alpmestan
Reviewed By: alpmestan
Subscribers: alpmestan, rwbarton, thomie, carter
GHC Trac Issues: #15335
Differential Revision: https://phabricator.haskell.org/D4927
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Also adds a comment to UnboundVarE clarifying that it also is used for
unbound constructor identifiers, since that isn't very clear from the
name.
Test Plan: testsuite/tests/th/T14627.hs
Reviewers: goldfire, bgamari
Reviewed By: goldfire
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4923
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
See https://ghc.haskell.org/trac/ghc/ticket/14471
Also fixes a parenthesization bug in pprStmt when ret_stripped is True
Test Plan: tests added to testsuite
Trac issues: #14471
Reviewers: goldfire, bgamari
Reviewed By: goldfire
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4912
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
One issue with valid hole fits is that the function names can often be
opaque for the uninitiated, such as `($)`. This diff adds a new flag,
`-fshow-docs-of-hole-fits` that adds the documentation of the identifier
in question to the message, using the same mechanism as the `:doc`
command.
As an example, with this flag enabled, the valid hole fits for `_ ::
[Int] -> Int` will include:
```
Valid hole fits include
head :: forall a. [a] -> a
{-^ Extract the first element of a list, which must be non-empty.-}
with head @Int
(imported from ‘Prelude’ (and originally defined in ‘GHC.List’))
```
And one of the refinement hole fits, `($) _`, will read:
```
Valid refinement hole fits include
...
($) (_ :: [Int] -> Int)
where ($) :: forall a b. (a -> b) -> a -> b
{-^ Application operator. This operator is redundant, since ordinary
application @(f x)@ means the same as @(f '$' x)@. However, '$' has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
> f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as @'map' ('$' 0) xs@,
or @'Data.List.zipWith' ('$') fs xs@.
Note that @($)@ is levity-polymorphic in its result type, so that
foo $ True where foo :: Bool -> Int#
is well-typed-}
with ($) @'GHC.Types.LiftedRep @[Int] @Int
(imported from ‘Prelude’ (and originally defined in ‘GHC.Base’))
```
Another example of where documentation can come in very handy, is when
working with the `lens` library.
When you compile
```
{-# OPTIONS_GHC -fno-show-provenance-of-hole-fits -fshow-docs-of-hole-fits #-}
module LensDemo where
import Control.Lens
import Control.Monad.State
newtype Test = Test { _value :: Int } deriving (Show)
value :: Lens' Test Int
value f (Test i) = Test <$> f i
updTest :: Test -> Test
updTest t = t &~ do
_ value (1 :: Int)
```
You get:
```
Valid hole fits include
(#=) :: forall s (m :: * -> *) a b.
MonadState s m =>
ALens s s a b -> b -> m ()
{-^ A version of ('Control.Lens.Setter..=') that works on 'ALens'.-}
with (#=) @Test @(StateT Test Identity) @Int @Int
(<#=) :: forall s (m :: * -> *) a b.
MonadState s m =>
ALens s s a b -> b -> m b
{-^ A version of ('Control.Lens.Setter.<.=') that works on 'ALens'.-}
with (<#=) @Test @(StateT Test Identity) @Int @Int
(<*=) :: forall s (m :: * -> *) a.
(MonadState s m, Num a) =>
LensLike' ((,) a) s a -> a -> m a
{-^ Multiply the target of a numerically valued 'Lens' into your 'Monad''s
state and return the result.
When you do not need the result of the multiplication,
('Control.Lens.Setter.*=') is more flexible.
@
('<*=') :: ('MonadState' s m, 'Num' a) => 'Lens'' s a -> a -> m a
('<*=') :: ('MonadState' s m, 'Num' a) => 'Control.Lens.Iso.Iso'' s a -> a -> m a
@-}
with (<*=) @Test @(StateT Test Identity) @Int
(<+=) :: forall s (m :: * -> *) a.
(MonadState s m, Num a) =>
LensLike' ((,) a) s a -> a -> m a
{-^ Add to the target of a numerically valued 'Lens' into your 'Monad''s state
and return the result.
When you do not need the result of the addition,
('Control.Lens.Setter.+=') is more flexible.
@
('<+=') :: ('MonadState' s m, 'Num' a) => 'Lens'' s a -> a -> m a
('<+=') :: ('MonadState' s m, 'Num' a) => 'Control.Lens.Iso.Iso'' s a -> a -> m a
@-}
with (<+=) @Test @(StateT Test Identity) @Int
(<-=) :: forall s (m :: * -> *) a.
(MonadState s m, Num a) =>
LensLike' ((,) a) s a -> a -> m a
{-^ Subtract from the target of a numerically valued 'Lens' into your 'Monad''s
state and return the result.
When you do not need the result of the subtraction,
('Control.Lens.Setter.-=') is more flexible.
@
('<-=') :: ('MonadState' s m, 'Num' a) => 'Lens'' s a -> a -> m a
('<-=') :: ('MonadState' s m, 'Num' a) => 'Control.Lens.Iso.Iso'' s a -> a -> m a
@-}
with (<-=) @Test @(StateT Test Identity) @Int
(<<*=) :: forall s (m :: * -> *) a.
(MonadState s m, Num a) =>
LensLike' ((,) a) s a -> a -> m a
{-^ Modify the target of a 'Lens' into your 'Monad''s state by multipling a value
and return the /old/ value that was replaced.
When you do not need the result of the operation,
('Control.Lens.Setter.*=') is more flexible.
@
('<<*=') :: ('MonadState' s m, 'Num' a) => 'Lens'' s a -> a -> m a
('<<*=') :: ('MonadState' s m, 'Num' a) => 'Iso'' s a -> a -> m a
@-}
with (<<*=) @Test @(StateT Test Identity) @Int
(Some hole fits suppressed; use -fmax-valid-hole-fits=N or -fno-max-valid-hole-fits)
```
Which allows you to see at a glance what opaque operators like `(<<*=)`
and `(<#=)` do.
Reviewers: bgamari, sjakobi
Reviewed By: sjakobi
Subscribers: sjakobi, alexbiehl, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4848
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: validate
Reviewers: bgamari, simonmar
Reviewed By: simonmar
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4957
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Currently, an `IfaceAppTy` has no way to tell whether its
argument is visible or not, so it simply treats all arguments as
visible, leading to #15330. We already have a solution for this
problem in the form of the `IfaceTcArgs` data structure, used by
`IfaceTyConApp` to represent the arguments to a type constructor.
Therefore, it makes sense to reuse this machinery for `IfaceAppTy`,
so this patch does just that.
This patch:
1. Renames `IfaceTcArgs` to `IfaceAppArgs` to reflect its more
general purpose.
2. Changes the second field of `IfaceAppTy` from `IfaceType` to
`IfaceAppArgs`, and propagates the necessary changes through. In
particular, pretty-printing an `IfaceAppTy` now goes through the
`IfaceAppArgs` pretty-printer, which correctly displays arguments
as visible or not for free, fixing #15330.
3. Changes `toIfaceTypeX` and related functions so that when
converting an `AppTy` to an `IfaceAppTy`, it flattens as many
argument `AppTy`s as possible, and then converts those arguments
into an `IfaceAppArgs` list, using the kind of the function
`Type` as a guide. (Doing so minimizes the number of times we need
to call `typeKind`, which is more expensive that finding the kind
of a `TyCon`.)
Test Plan: make test TEST=T15330
Reviewers: goldfire, simonpj, bgamari
Reviewed By: simonpj
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15330
Differential Revision: https://phabricator.haskell.org/D4938
|
|
|
|
| |
c.f. Trac #14873
|
|
|
|
|
| |
The removed line could cause GHC to hang by printing a
knot-tied type.
|
|
|
|
|
|
| |
This addresses #14808
[ci skip]
|
|
|
|
|
|
|
|
| |
Read that note -- it's necessary to make sure that we can
always call typeKind without panicking. As discussed on #14873,
there were more checks and zonking to do, implemented here.
There are no known bugs fixed by this patch, but there are likely
unknown ones.
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, we kind-checked associated types while while still
figuring out the kind of a CUSK class. This caused trouble, as
documented in Note [Don't process associated types in kcLHsQTyVars]
in TcTyClsDecls. This commit moves this process after the initial
kind of the class is determined.
Fixes #15142.
Test case: indexed-types/should_compile/T15142.hs
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, checking whether (tv |> co) ~ (tv |> co) got deferred,
because we looked for vars before stripping casts. (The left type
would get stripped, and then tv ~ (tv |> co) would scare the occurs-
checker.)
This opportunity for improvement presented itself in other work.
This is just an optimization. Some programs can now report more
errors simultaneously.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This was a tricky one.
During type checking we maintain TcType:
Note [The well-kinded type invariant]
That is, types are well-kinded /without/ zonking.
But in tcInferApps we were destroying that invariant by calling
substTy, which in turn uses smart constructors, which eliminate
apparently-redundant Refl casts.
This is horribly hard to debug beause they really are Refls and
so it "ought" to be OK to discard them. But it isn't, as the
above Note describes in some detail.
Maybe we should review the invariant? But for now I just followed
it, tricky thought it is.
This popped up because (for some reason) when I fixed Trac #15343,
that exposed this bug by making test polykinds/T14174a fail (in
Trac #14174 which indeed has the same origin).
So this patch fixes a long standing and very subtle bug.
One interesting point: I defined nakedSubstTy in a few lines by
using the generic mapType stuff. I note that the "normal"
TyCoRep.substTy does /not/ use mapType. But perhaps it should:
substTy has lots of $! strict applications in it, and they could
all be eliminated just by useing the StrictIdentity monad. And
that'd make it much easier to experiment with switching between
strict and lazy versions.
|
|
|
|
|
| |
And I added some HasDebugCallStack constraints to tcExpectedKind
and related functions too.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #15343 was caused by two things
First, in TcHsType.tcHsTypeApp, which deals with the type argment
in visible type application, we were failing to call
solveLocalEqualities. But the type argument is like a user type
signature so it's at least inconsitent not to do so.
I thought that would nail it. But it didn't. It turned out that we
were ended up calling decomposePiCos on a type looking like this
(f |> co) Int
where co :: (forall a. ty) ~ (t1 -> t2)
Now, 'co' is insoluble, and we'll report that later. But meanwhile
we don't want to crash in decomposePiCos.
My fix involves keeping track of the type on both sides of the
coercion, and ensuring that the outer shape matches before
decomposing. I wish there was a simpler way to do this. But
I think this one is at least robust.
I suppose it is possible that the decomposePiCos fix would
have cured the original report, but I'm leaving the one-line
tcHsTypeApp fix in too because it just seems more consistent.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch responds to Trac #15334 by making it an error to
write an instance declaration for a tuple constraint like
(Eq [a], Show [a]).
I then discovered that instance validity checking was
scattered betweeen TcInstDcls and TcValidity, so I took
the time to bring it all together, into
TcValidity.checkValidInstHead
In doing so I discovered that there are lot of special
cases. I have not changed them, but at least they are
all laid out clearly now.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
The patch is an attempt on #15192.
It defines a new coercion rule
```
| GRefl Role Type MCoercion
```
which correspondes to the typing rule
```
t1 : k1
------------------------------------
GRefl r t1 MRefl: t1 ~r t1
t1 : k1 co :: k1 ~ k2
------------------------------------
GRefl r t1 (MCo co) : t1 ~r t1 |> co
```
MCoercion wraps a coercion, which might be reflexive (MRefl)
or not (MCo co). To know more about MCoercion see #14975.
We keep Refl ty as a special case for nominal reflexive coercions,
naemly, Refl ty :: ty ~n ty.
This commit is meant to be a general performance improvement,
but there are a few regressions. See #15192, comment:13 for
more information.
Test Plan: ./validate
Reviewers: bgamari, goldfire, simonpj
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15192
Differential Revision: https://phabricator.haskell.org/D4747
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary: I needed this when debugging #15346.
Test Plan: Does it compile? It does? Cool.
Reviewers: bgamari, mpickering
Reviewed By: mpickering
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15311
Differential Revision: https://phabricator.haskell.org/D4944
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The logic for `DFunUnfolding` seemed quite confusing and unecessary. A
simpler strategy uses `maybeUnfoldingTemplate`, as that is what is
actually used when doing inlining and checking that has the right type.
Reviewers: simonpj, goldfire, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4919
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: validate
Reviewers: bgamari, alpmestan
Reviewed By: alpmestan
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15342
Differential Revision: https://phabricator.haskell.org/D4933
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
I discovered when debugging #15346 that the Core Lint error
message for ill typed casts always mentions types of enclosed
//expressions//, even if the thing being casted is actually a type.
This generalizes `mkCastErr` a bit to allow it to give the proper
labelling for kind coercions.
Test Plan: Run on failing program in #15346, read the Core Lint error
Reviewers: goldfire, bgamari, simonpj
Reviewed By: simonpj
Subscribers: simonpj, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4940
|