- Jul 14, 2018
-
-
Ben Gamari authored
I believe this was originally introduced to help test DPH, which is now gone.
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
- Jul 13, 2018
-
-
Simon Peyton Jones authored
-
Simon Marlow authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
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.
-
Ömer Sinan Ağacan authored
CONSTR_NOCAF was introduced with 55d535da as a replacement for CONSTR_STATIC and CONSTR_NOCAF_STATIC, however, as explained in Note [static constructors], we copy CONSTR_NOCAFs (which can also be seen in evacuate) during GC, and they can become dead, like other CONSTR_X_Ys. processHeapClosureForDead is updated to reflect this. Test Plan: Validates on x86_64. Existing failures on i386. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #7836, #15063, #15087, #15165 Differential Revision: https://phabricator.haskell.org/D4928
-
Simon Marlow authored
-
- Jul 12, 2018
-
-
There was a lock-order reversal between lockTSO() and the TVar lock, see #15136 for the details. It turns out we can fix this pretty easily by just deleting all the locking code(!). The principle for unblocking a `BlockedOnSTM` thread then becomes the same as for other kinds of blocking: if the TSO belongs to this capability then we do it directly, otherwise we send a message to the capability that owns the TSO. That is, a thread blocked on STM is owned by its capability, as it should be. The possible downside of this is that we might send multiple messages to wake up a thread when the thread is on another capability. This is safe, it's just not very efficient. I'll try to do some experiments to see if this is a problem. Test Plan: Test case from #15136 doesn't deadlock any more. Reviewers: bgamari, osa1, erikd Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15136 Differential Revision: https://phabricator.haskell.org/D4956
-
Matthew Pickering authored
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
-
Matthew Pickering authored
-
Krzysztof Gogolewski authored
Remove "dynamic + :set" category from documentation, because all dynamic flags support ":set"; this is a leftover of "static + :set". Test Plan: make html Reviewers: bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, osa1, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4942
-
Matthew Pickering authored
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
-
-
Bodigrim authored
-
Ningning Xie authored
-
AntC authored
as per comments on the ticket; also linked to Haskell folk art of 'Smart constructors'.
-
Ben Gamari authored
-
-
-
-
James Bowen authored
-
-
Ömer Sinan Ağacan authored
Test Plan: validate Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4957
-
- Jul 11, 2018
-
-
Ryan Scott authored
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
-
Simon Peyton Jones authored
c.f. Trac #14873
-
Simon Peyton Jones authored
-
Richard Eisenberg authored
The removed line could cause GHC to hang by printing a knot-tied type.
-
- Jul 10, 2018
-
-
Richard Eisenberg authored
This addresses #14808 [ci skip]
-
Richard Eisenberg authored
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.
-
Richard Eisenberg authored
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
-
Richard Eisenberg authored
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.
-
Simon Peyton Jones authored
This is a documentation-only fix, addressing Trac #15354.
-
Simon Peyton Jones authored
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.
-