- 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
-
Ryan Scott authored
`(~)` is not an identifier according to GHC's parser, which is why GHCi's `:info` command wouldn't work on it. To rectify this, we apply the same fix that was put in place for `(->)`: add `(~)` to GHC's `identifier` parser production. Test Plan: make test TEST=T10059 Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, mpickering, carter GHC Trac Issues: #10059 Differential Revision: https://phabricator.haskell.org/D4877
-
Test Plan: Validate with numa support Subscribers: rwbarton, thomie, erikd, carter Differential Revision: https://phabricator.haskell.org/D4869
-
Gabor Greif authored
-
Ben Gamari authored
This reverts commit 50e7bff7. Reverts submodule changes. Sigh, the haskeline commit isn't quite upstream yet.
-
Specifically: * MonadFix * MonadZip * Data * Foldable * Traversable * Eq1 * Ord1 * Read1 * Show1 * Generic * Generic1 Fixes #15098. Reviewers: RyanGlScott, hvr Reviewed By: RyanGlScott Subscribers: sjakobi, rwbarton, thomie, ekmett, carter GHC Trac Issues: #15098 Differential Revision: https://phabricator.haskell.org/D4870
-
Test Plan: Used it in anger Reviewers: bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4873
-
Reviewers: hvr, bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4871
-
Ben Gamari authored
The stderr output is merely a guess at what we should expect, but currently this is certainly broken.
-
Ben Gamari authored
Darwin tends to give us a very small stack which the retainer profiler tends to overflow. Strangely, this manifested on CircleCI yet not Harbormaster. See #15287 and #11627.
-
Ben Gamari authored
Bumps containers submodule, among others.
-
- Jun 19, 2018
-
-
Ben Gamari authored
It's unclear what these are due to but they are causing the Darwin builds to fail.
-
Bumps haddock submodule.
-
Richard Eisenberg authored
This fixes #15282.
-
Alan Zimmerman authored
Summary: This patch completes the work for #14529 by making sure that all API Annotations end up attached to a SrcSpan that appears in the final ParsedSource. Updates Haddock submodule Test Plan: ./validate Reviewers: goldfire, bgamari Subscribers: rwbarton, thomie, mpickering, carter GHC Trac Issues: #14529 Differential Revision: https://phabricator.haskell.org/D4867
-
Simon Peyton Jones authored
-
Ömer Sinan Ağacan authored
- dataToExpQUnit - qq005 - qq006 - qq007 - qq008 - qq009 - T13949 - T8025
-
- Jun 18, 2018
-
-
Richard Eisenberg authored
[skip ci]
-
Gabor Greif authored
-
Simon Peyton Jones authored
When typechecking a type like Maybe (a :: <kind-sig>) with a kind signature, we were using tc_lhs_kind to typecheck the signature. But that's utterly wrong; we need the signature to be fully solid (non unresolved equalities) before using it. In the case of Trac #14904 we went on to instantiate the kind signature, when it still had embedded unsolved constraints. This tripped the level-checking assertion when unifying a variable. The fix looks pretty easy to me: just call tcLHsKind instead. I had to add KindSigCtxt to
-
Simon Peyton Jones authored
* Define Type.substTyVarBndrs, and use it * Rename substTyVarBndrCallback to substTyVarBndrUsing, and other analogous higher order functions. I kept stumbling over the name.
-
Simon Peyton Jones authored
Trac #14164 made GHC loop, a pretty serious error. It turned out that Unify.niFixTCvSubst was looping forever, because we had a substitution like a :-> ....(b :: (c :: d)).... d :-> ... We correctly recognised that d was free in the range of the substitution, but then failed to apply it "deeeply enough" to the range of the substiuttion, so d was /still/ free in the range, and we kept on going. Trac #9106 was caused by a similar problem, but alas my fix to Trac #9106 was inadequate when the offending type variable is more deeply buried. Urk. This time I think I've fixed it! It's much more subtle than I though, and it took most of a long train journey to figure it out. I wrote a long note to explain: Note [Finding the substitution fixpoint]
-
- Jun 17, 2018
-
-
Ryan Scott authored
This was a stderr file for a WIP test in D4728. I ended up removing the test, but forgot to remove the stderr file.
-
Add a flag `-Werror=compat` to GHC which has the effect of `-Werror=x -Werror=y ...`, where `x, y, ...` are warnings from the `-Wcompat` option group. Test Plan: ./validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15278 Differential Revision: https://phabricator.haskell.org/D4860
-
Ömer Sinan Ağacan authored
It seems like we currently support string literals in Cmm, so we can use __LINE__ CPP macro in assertion macros. This improves error messages that previously looked like ASSERTION FAILED: file (null), line 1302 (null) part now shows the actual file name. Also inline some single-use string literals in PrimOps.cmm. Reviewers: bgamari, simonmar, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4862
-
Gabor noticed C warning when building unregisterised 64-bit compiler on GHC.Integer.Types (from integer-simple). Minimised example with a warning: ```haskell {-# LANGUAGE MagicHash #-} {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -Wall #-} module M (bug) where import GHC.Prim (Word#, minusWord#, ltWord#) import GHC.Types (isTrue#) -- assume Word = Word64 bug :: Word# -> Word# bug x = if isTrue# (x `ltWord#` 0x8000000000000000##) then 0## else x `minusWord#` 0x8000000000000000## ``` ``` $ LANG=C x86_64-UNREG-linux-gnu-ghc -O1 -c M.hs -fforce-recomp /tmp/ghc30219_0/ghc_1.hc: In function 'M_bug_entry': /tmp/ghc30219_0/ghc_1.hc:20:14: error: warning: integer constant is so large that it is unsigned ``` It's caused by limited handling of integer literals in CmmRegOff. This change switches to use standard integer literal pretty-printer. C code before the change: ```c FN_(M_bug_entry) { W_ _sAg; _cAr: _sAg = *Sp; switch ((W_)(_sAg < 0x8000000000000000UL)) { case 0x1UL: goto _cAq; default: goto _cAp; } _cAp: R1.w = _sAg+-9223372036854775808; // ... ``` C code after the change: ```c FN_(M_bug_entry) { W_ _sAg; _cAr: _sAg = *Sp; switch ((W_)(_sAg < 0x8000000000000000UL)) { case 0x1UL: goto _cAq; default: goto _cAp; } _cAp: R1.w = _sAg+(-0x8000000000000000UL); ``` URL: https://mail.haskell.org/pipermail/ghc-devs/2018-June/015875.html Reported-by: Gabor Greif Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Test Plan: test generated code on unregisterised mips64 and amd64 Reviewers: simonmar, ggreif, bgamari Reviewed By: ggreif, bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4856
-
Ryan Scott authored
Trac #14845 brought to light a corner case where a data constructor could not be promoted (even with `-XTypeInType`) due to an unpromotable constraint in its context. However, the error message was less than helpful, so this patch adds an additional check to `tcTyVar` catch unpromotable data constructors like these //before// they're promoted, and to give a sensible error message in such cases. Test Plan: make test TEST="T13895 T14845" Reviewers: simonpj, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13895, #14845 Differential Revision: https://phabricator.haskell.org/D4728
-
Azel authored
Reviewers: sjakobi, dfeuer, bgamari, hvr Reviewed By: sjakobi, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15078 Differential Revision: https://phabricator.haskell.org/D4736
-
sgillespie authored
If a module cannot be found because it is ignored or from an unusable package, report this to the user and the reason it is unusable. Currently, GHC displays the standard "Cannot find module error". For example: ``` <no location info>: error: Could not find module ‘Control.Monad.Random’ Perhaps you meant Control.Monad.Reader (from mtl-2.2.2) Control.Monad.Cont (from mtl-2.2.2) Control.Monad.Error (from mtl-2.2.2) ``` GHC does, however, indicate unusable/ignored packages with the -v flag: ``` package MonadRandom-0.5.1-1421RgpXdhC8e8UI7D3emA is unusable due to missing dependencies: fail-4.9.0.0-BAHmj60kS5K7NVhhKpm9J5 ``` With this change, I took that message and added it to the output of the "Cannot find module" message. Reviewers: bgamari, dfeuer Reviewed By: bgamari Subscribers: Phyx, dfeuer, rwbarton, thomie, carter GHC Trac Issues: #4806 Differential Revision: https://phabricator.haskell.org/D4783
-