- Jul 14, 2018
-
-
Ö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 (cherry picked from commit 2625f131)
-
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 (cherry picked from commit 7fc418df)
-
Simon Peyton Jones authored
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. (cherry picked from commit aedbf7f1)
-
Ben Gamari authored
I believe this was originally introduced to help test DPH, which is now gone. (cherry picked from commit 0905fec0)
-
Ben Gamari authored
(cherry picked from commit c3328ff3)
-
Ben Gamari authored
(cherry picked from commit b794c7ed)
-
Ben Gamari authored
(cherry picked from commit c67cf9e9)
-
Ben Gamari authored
(cherry picked from commit cbd4b333)
-
(cherry picked from commit e40eb738)
-
- Jul 12, 2018
-
-
Ryan Scott authored
Summary: Before, we were using visible type application to apply impredicative types to `coerce` in `GeneralizedNewtypeDeriving`-generated bindings. This approach breaks down when combined with `QuantifiedConstraints` in certain ways, which #14883 and #15290 provide examples of. See Note [GND and QuantifiedConstraints] for all the gory details. To avoid this issue, we instead use an explicit type signature to instantiate each GND binding, and use that to bind any type variables that might be bound by a class method's type signature. This reduces the need to impredicative type applications, and more importantly, makes the programs from #14883 and #15290 work again. Test Plan: make test TEST="T15290b T15290c T15290d T14883" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14883, #15290 Differential Revision: https://phabricator.haskell.org/D4895 (cherry picked from commit 132273f3)
-
Ömer Sinan Ağacan authored
`extractSubTerms` (which is extracting pointer and non-pointer fields of a closure) was computing the alignment incorrectly when aligning a 64-bit value (e.g. a Double) on i386 by aligning it to 64-bits instead of to word size (32-bits). This is documented in `mkVirtHeapOffsetsWithPadding`: > Align the start offset (eg, 2-byte value should be 2-byte aligned). > But not more than to a word. Fixes #15061 Test Plan: Validated on both 32-bit and 64-bit. 32-bit fails with various unrelated stat failures, but no actual test failures. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15061 Differential Revision: https://phabricator.haskell.org/D4906 (cherry picked from commit 15bb4e0b)
-
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 (cherry picked from commit 030211d2)
-
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. (cherry picked from commit 5067b205)
-
Ryan Scott authored
Summary: `nlHsFunTy` wasn't parenthesizing its arguments at all, which led to `-ddump-deriv` producing incorrectly parenthesized types (since it uses `nlHsFunTy` to construct those types), as demonstrated in #15307. Fix this by changing `nlHsFunTy` to add parentheses à la `ppr_ty`: always parenthesizing the argument type with function precedence, and recursively processing the result type, adding parentheses for each function type it encounters. Test Plan: make test TEST=T14578 Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15307 Differential Revision: https://phabricator.haskell.org/D4890 (cherry picked from commit 59a15a56)
-
Ryan Scott authored
Summary: There was a buglet in `stripInvisArgs` (which is part of the pretty-printing pipeline for types) in which only invisble arguments which came before any visible arguments would be suppressed, but any invisble arguments that came //after// visible ones would still be printed, even if `-fprint-explicit-kinds` wasn't enabled. The fix is simple: make `stripInvisArgs` recursively process the remaining types even after a visible argument is encountered. Test Plan: make test TEST=T15308 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15308 Differential Revision: https://phabricator.haskell.org/D4891 (cherry picked from commit 93b7ac8d)
-
Simon Peyton Jones authored
...provoked by Trac #15308 (cherry picked from commit 3d002087)
-
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 (cherry picked from commit 1a79270c)
-
Ryan Scott authored
Summary: This was taken from Richard's branch, which in turn was submitted to Phab by Matthew, which in turn was commandeered by Ryan. This fixes an issue with newtype instances in which too many coercions were being applied in the worker. This fixes the issue by removing the data family instance axiom from the worker and moving to the wrapper. Moreover, we now require all newtype instances to have wrappers, for symmetry with data instances. Reviewers: goldfire, bgamari, simonpj, mpickering Reviewed By: mpickering Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15318 Differential Revision: https://phabricator.haskell.org/D4902 (cherry picked from commit 92751866)
-
Ömer Sinan Ağacan authored
(cherry picked from commit e835fdb1)
-
This is a one line fix (and a note) that fixes four tickets, #15007, #15321 and #15202, #15314 The issue was that errors caused by illegal candidates (according to GHC stage or being internal names) were leaking to the user, causing bewildering error messages. If a candidate causes the type checker to error, it is not a valid hole fit, and should be discarded. As mentioned in #15321, this can cause a pattern of omissions, which might be hard to discover. A better approach would be to gather the error messages, and ask users to report them as GHC bugs. This will be implemented in a subsequent change. Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15007, #15321, #15202, #15314 Differential Revision: https://phabricator.haskell.org/D4909 (cherry picked from commit 39de4e3d)
-
A GADT declaration surrounded in parens does not det the con_forall field correctly. e.g. data MaybeDefault v where TestParens :: (forall v . (Eq v) => MaybeDefault v) Closes #15323 (cherry picked from commit 6e4e6d1c)
-
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 (cherry picked from commit 2b1adaa7)
-
Ryan Scott authored
Summary: A simple oversight. Test Plan: make test TEST=T15324 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15324 Differential Revision: https://phabricator.haskell.org/D4910 (cherry picked from commit 57733978)
-
Ryan Scott authored
Another `-ddump-splices` bug that can be solved with more judicious use of parentheses. Test Plan: make test TEST=T15331 Reviewers: goldfire, bgamari, alanz, tdammers Reviewed By: tdammers Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15331 Differential Revision: https://phabricator.haskell.org/D4920 (cherry picked from commit b6a33861)
-
Ryan Scott authored
Summary: `ppr_tc_args` was printing invisible kind arguments even when `-fprint-explicit-kinds` wasn't enabled. Easily fixed. Test Plan: make test TEST=T15341 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15341 Differential Revision: https://phabricator.haskell.org/D4932 (cherry picked from commit dbdcacfc)
-
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. (cherry picked from commit cf67e59a)
-
Sylvain Henry authored
The recent patch "Built-in Natural literals in Core" (https://phabricator.haskell.org/rGHCfe770c211631e7b4c9b0b1e88ef9b6046c6 585ef) introduced a regression when desugaring large numbers. This patch fixes it and adds a regression test. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15301 Differential Revision: https://phabricator.haskell.org/D4885 (cherry picked from commit 987b5e7f)
-
- Jul 11, 2018
-
-
Ben Gamari authored
(cherry picked from commit 5a1290a8317056065f409ffd47fa6114172a1a15)
-
- Jun 27, 2018
-
-
Simon Peyton Jones authored
As Trac #15289 showed, we were carrying on after a type error in a pattern synonym, and then crashing. This patch improves error handling for pattern synonyms. I also moved a bit of code from TcBinds into TcPatSyn, which helpfully narrows the API. (cherry picked from commit 2896082e)
-
Make sure the original annotations are still accessible for a promoted type. Closes #15303 (cherry picked from commit e53c113d)
-
Simon Peyton Jones authored
The level numbers we were getting simply didn't obey the invariant (ImplicInv) in TcType Note [TcLevel and untouchable type variables] That leads to chaos. Easy to fix. I improved the documentation. I also added an assertion in TcSimplify that checks that level numbers go up by 1 as we dive inside implications, so that we catch the problem at source rather than than through its obscure consequences. That in turn showed up that TcRules was also generating constraints that didn't obey (ImplicInv), so I fixed that too. I have no idea what consequences were lurking behing that bug, but anyway now it's fixed. Hooray. (cherry picked from commit 261dd83c)
-
Simon Peyton Jones authored
The refactoring here is driven by the ghastly mess described in comment:24 of Trac #1520. The overall goal is to simplify the kind-checking of typev-variable binders, and in particular to narrow the use of the "in-scope tyvar binder" stuff, which is needed only for associated types: see the new Note [Kind-checking tyvar binders for associated types] in TcHsType. Now * The "in-scope tyvar binder" stuff is done only in - kcLHsQTyVars, which is used for the LHsQTyVars of a data/newtype, or type family declaration. - tcFamTyPats, which is used for associated family instances; it now calls tcImplicitQTKBndrs, which in turn usese newFlexiKindedQTyVar * tcExpicitTKBndrs (which is used only for function signatures, data con signatures, pattern synonym signatures, and expression type signatures) now does not go via the "in-scope tyvar binder" stuff at all. While I'm still not happy with all this code, the code is generally simpler, and I think this is a useful step forward. It does cure the problem too. (It's hard to trigger the problem in vanilla Haskell code, because the renamer would normally use different names for nested binders, so I can't offer a test.) (cherry picked from commit 9fc40c73)
-
Simon Peyton Jones authored
Trac #15290 showed that it's possible that we might attempt to use a quantified constraint to solve an equality in a situation where we don't have anywhere to put the evidence bindings. This made GHC crash. This patch stops the crash, but still rejects the pogram. See Note [Instances in no-evidence implications] in TcInteract. Finding this bug revealed another lurking bug: * An infelicity in the treatment of superclasses -- we were expanding them locally at the leaves, rather than at their binding site; see (3a) in Note [The superclass story]. As a consequence, TcRnTypes.superclassesMightHelp must look inside implications. In more detail: * Stop the crash, by making TcInteract.chooseInstance test for the no-evidence-bindings case. In that case we simply don't use the instance. This entailed a slight change to the type of chooseInstance. * Make TcSMonad.getPendingScDicts (now renamed getPendingGivenScs) return only Givens from the /current level/; and make TcRnTypes.superClassesMightHelp look inside implications. * Refactor the simpl_loop and superclass-expansion stuff in TcSimplify. The logic is much easier to understand now, and has less duplication. (cherry picked from commit 32eb4199)
-
- Jun 25, 2018
-
-
(cherry picked from commit 5db9f912)
-
- Jun 24, 2018
-
-
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 Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4865
-
The standard[1] for extension naming is to use the XC prefix for the internal extension points, rather than for a new constructor. This is violated for IPBind, having data IPBind id = IPBind (XIPBind id) (Either (Located HsIPName) (IdP id)) (LHsExpr id) | XCIPBind (XXIPBind id) Swap the usage of XIPBind and XCIPBind [1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow#Namingconventions Closes #15302 (cherry picked from commit 5f06cf6b)
-
- Jun 20, 2018
-
-
Ben Gamari authored
Bumps containers submodule, among others.
-
When GHC links binaries on windows, we pass a -L and -l flag to gcc for each dependency in the transitive dependency closure. As this will usually overflow the command argument limit on windows, we use response files to pass all arguments to gcc. gcc however internally passes only the -l flags via a response file to the collect2 command, but puts the -L flags on the command line. As such if we pass enough -L flags to gcc--even via a response file--we will eventually overflow the command line argument length limit due to gcc passing them to collect2 without resorting to a response file. To prevent this from happening we move all lirbaries into a shared temporary folder, and only need to pass a single -L flag to gcc. Ideally however this was fixed in gcc. Reviewers: bgamari, Phyx Reviewed By: bgamari Subscribers: erikd, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4762
-
* Use bool instead of HsBool * Use barf instead of sysErrorBelch; stg_exit Test Plan: Validate Reviewers: erikd, simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4874
-
Ryan Scott authored
After commit d650729f, the `HsEqTy` constructor of `HsType` is essentially dead code. Given that we want to remove `HsEqTy` anyway as a part of #10056 (comment:27), let's just rip it out. Bumps the haddock submodule. Test Plan: ./validate Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #10056 Differential Revision: https://phabricator.haskell.org/D4876
-