- 27 Jul, 2015 6 commits
-
-
Simon Marlow authored
This reverts commit 09d05050.
-
Simon Peyton Jones authored
Two main things here * Previously we only warned about the "head" function of the rule, but actually the warning applies to any free variable on the LHS. * We now warn not only when one of these free vars can inline, but also if it has an active RULE (c.f. Trac #10528) See Note [Rules and inlining/other rules] in Desugar This actually shows up quite a few warnings in the libraries, notably in Control.Arrow, where it correctly points out that rules like "compose/arr" forall f g . (arr f) . (arr g) = arr (f . g) might never fire, because the rule for 'arr' (dictionary selection) might fire first. I'm not really sure what to do here; there is some discussion in Trac #10595. A minor change is adding BasicTypes.pprRuleName to pretty-print RuleName.
-
Simon Peyton Jones authored
This is the right thing to do anyway, and fixes Trac #10528
-
rwbarton authored
It has no special treatment in the compiler any more. The last use was removed in 99d4e5b4 "Implement cardinality analysis". Test Plan: validate Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1099
-
spinda authored
UInfixT is like UInfixE or UInfixP but for types. Template Haskell splices can use it to punt fixity handling to GHC when constructing types. UInfixT is converted in compiler/hsSyn/Convert to a right-biased tree of HsOpTy, which is already rearranged in compiler/rename/RnTypes to match operator fixities. This patch consists of (1) adding UInfixT to the AST, (2) implementing the conversion and updating relevant comments, (3) updating pretty-printing and library support, and (4) adding tests. Test Plan: validate Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1088 GHC Trac Issues: #10522
-
Adam Sandberg Eriksson authored
This implements the `StrictData` language extension, which lets the programmer default to strict data fields in datatype declarations on a per-module basis. Specification and motivation can be found at https://ghc.haskell.org/trac/ghc/wiki/StrictPragma This includes a tricky parser change due to conflicts regarding `~` in the type level syntax: all ~'s are parsed as strictness annotations (see `strict_mark` in Parser.y) and then turned into equality constraints at the appropriate places using `RdrHsSyn.splitTilde`. Updates haddock submodule. Test Plan: Validate through Harbormaster. Reviewers: goldfire, austin, hvr, simonpj, tibbe, bgamari Reviewed By: simonpj, tibbe, bgamari Subscribers: lelf, simonpj, alanz, goldfire, thomie, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D1033 GHC Trac Issues: #8347
-
- 26 Jul, 2015 3 commits
-
-
rwbarton authored
-
rwbarton authored
Summary: I'm pretty sure that parentheses were intended here. But oddly, they make very little difference. The presumably intended expression (sizeofBigNat# bn ==# 1#) `andI#` (bigNatToWord bn `eqWord#` w#) is 1# exactly when bn consists of a single limb equal to w#, clearly. In the original expression sizeofBigNat# bn ==# 1# `andI#` (bigNatToWord bn `eqWord#` w#) the right-hand side of ==# is always 0# or 1#. So it is 1# when bn consists of a single limb equal to w#. It is also 1# when bn has zero limbs and the word past the end of bn does not happen to be equal to w#. So in practice the difference is that nullBigNat was eqBigNatWord# to almost everything, but eqBigNatWord# is never supposed to be called on nullBigNat anyways. Note that even the corrected version might perform an out-of-bounds memory access if passed nullBigNat, because `andI#` is not guaranteed to short-circuit, though in fact GHC does convert isZeroBigNat to a series of branches in my local build. Test Plan: validate Reviewers: hvr, bgamari, goldfire, austin Reviewed By: hvr, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1095
-
rwbarton authored
Summary: The form case na# ==# nb# of 0# -> ... _ -> ... sometimes generates convoluted assembly, see #10676. timesInt2Integer was the most spectacular offender, especially as it is a rather cheap function overall (no calls to gmp). I checked a few instances and some of the old generated assembly was fine already, but I changed them all for consistency. The new form is also more consistent with use of these primops in general. Test Plan: validate Reviewers: hvr, bgamari, goldfire, austin Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1094
-
- 25 Jul, 2015 2 commits
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Sergei Trofimovich authored
Noticed today that deprecation warnings are slightly broken in -HEAD: mtl-2.2.1/Control/Monad/Error/Class.hs:46:1: warning: Module ‘Control.Monad.Trans.Error’ is deprecated: ([", U, s, e, , C, o, n, t, r, o, l, ., M, o, n, a, d, ., T, r, a, n, s, ., E, x, c, e, p, t, , i, n, s, t, e, a, d, "], Use Control.Monad.Trans.Except instead) Commit e6191d1c slightly changed WarningTxt declaration: -data WarningTxt = WarningTxt (Located SourceText) [Located FastString] - | DeprecatedTxt (Located SourceText) [Located FastString] +data WarningTxt = WarningTxt (Located SourceText) + [Located (SourceText,FastString)] + | DeprecatedTxt (Located SourceText) + [Located (SourceText,FastString)] But 'moduleWarn' function was not updated to do the stripping. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Reviewers: austin, bgamari, hvr, goldfire, rwbarton, alanz Reviewed By: rwbarton, alanz Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1096 GHC Trac Issues: #10313
-
- 24 Jul, 2015 6 commits
-
-
Ben Gamari authored
-
Simon Peyton Jones authored
When staring at instanceCantMatch I realised that it was returning False (safe but inefficient) when it could validly return True, on arguments like [Nothing, Just Int] [Just Bool, Just Bool] This patch makes it a bit cleverer.
-
Simon Peyton Jones authored
This refactoring was triggered by Trac #10675. We were using 'improveClsFD' (previously called 'checkClsFD') for both * Improvement: improving a constraint against top-level instances * Consistency: checking when two top-level instances are consistent Using the same code for both seemed attractive at the time, but it's just too complicated. So I've split it: * Improvement: improveClsFD * Consistency: checkFunDeps Much clearer now!
-
Simon Peyton Jones authored
In "Improve strictness analysis for exceptions" commit 7c0fff41 Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Tue Jul 21 12:28:42 2015 +0100 I made catch# strict in its first argument. But today I found a very old comment suggesting the opposite. I disagree with the old comment, but I've elaborated the Note, which I reproduce here: {- Note [Strictness for mask/unmask/catch] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider this example, which comes from GHC.IO.Handle.Internals: wantReadableHandle3 f ma b st = case ... of DEFAULT -> case ma of MVar a -> ... 0# -> maskAsynchExceptions# (\st -> case ma of MVar a -> ...) The outer case just decides whether to mask exceptions, but we don't want thereby to hide the strictness in 'ma'! Hence the use of strictApply1Dmd. For catch, we know that the first branch will be evaluated, but not necessarily the second. Hence strictApply1Dmd and lazyApply1Dmd Howver, consider catch# (\st -> case x of ...) (..handler..) st We'll see that the entire thing is strict in 'x', so 'x' may be evaluated before the catch#. So fi evaluting 'x' causes a divide-by-zero exception, it won't be caught. This seems acceptable: - x might be evaluated somewhere else outside the catch# anyway - It's an imprecise eception anyway. Synchronous exceptions (in the IO monad) will never move in this way. There was originally a comment "Catch is actually strict in its first argument but we don't want to tell the strictness analyser about that, so that exceptions stay inside it." but tracing it back through the commit logs did not give any rationale. And making catch# lazy has performance costs for everyone.
-
Simon Peyton Jones authored
-
Ben Gamari authored
-
- 23 Jul, 2015 14 commits
-
-
Edward Z. Yang authored
A library name is a package name, package version, and hash of the version names of all textual dependencies (i.e. packages which were included.) A library name is a coarse approximation of installed package IDs, which are suitable for inclusion in package keys (you don't want to put an IPID in a package key, since it means the key will change any time the source changes.) - We define ShPackageKey, which is the semantic object which is hashed into a PackageKey. You can use 'newPackageKey' to hash a ShPackageKey to a PackageKey - Given a PackageKey, we can lookup its ShPackageKey with 'lookupPackageKey'. The way we can do this is by consulting the 'pkgKeyCache', which records a reverse mapping from every hash to the ShPackageKey. This means that if you load in PackageKeys from external sources (e.g. interface files), you also need to load in a mapping of PackageKeys to their ShPackageKeys so we can populate the cache. - We define a 'LibraryName' which encapsulates the full depenency resolution that Cabal may have selected; this is opaque to GHC but can be used to distinguish different versions of a package. - Definite packages don't have an interesting PackageKey, so we rely on Cabal to pass them to us. - We can pretty-print package keys while displaying the instantiation, but it's not wired up to anything (e.g. the Outputable instance of PackageKey). Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1056 GHC Trac Issues: #10566
-
Ben Gamari authored
-
thomie authored
Declaring a custom fixity for an infix data constructor should work: Prelude> data Infix a b = a :@: b; infixl 4 :@: This is a followup to #2947, which handled fixity declarations in ghci statements (e.g. let add = (+); infixl 6 `add`). Support for declarations (data, type, newtype, class, instance, deriving, and foreign) was added to GHCi in #4929. Reviewers: simonpj, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1028 GHC Trac Issues: #10018
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Add CoreSyn.chooseOrphanAnchor, and use it
-
Ben Gamari authored
C99 does not allow unnamed parameters in definition argument lists [1]. [1] http://stackoverflow.com/questions/8776810/parameter-name-omitted-c-vs-c
-
Ben Gamari authored
-
thomasw authored
When a constructor was mistakenly imported directly instead of as a constructor of a data type, a hint will be shown on how to correctly import it. Just like the constructor, the data type should be surrounded in parentheses if it is an operator (TypeOperator in this case). Instead of: error: In module ‘Data.Type.Equality’: ‘Refl’ is a data constructor of ‘:~:’ To import it use ‘import’ Data.Type.Equality( :~:( Refl ) ) or ‘import’ Data.Type.Equality( :~:(..) ) Print: error: In module ‘Data.Type.Equality’: ‘Refl’ is a data constructor of ‘(:~:)’ To import it use ‘import’ Data.Type.Equality( (:~:)( Refl ) ) or ‘import’ Data.Type.Equality( (:~:)(..) ) Test Plan: pass new test Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1093 GHC Trac Issues: #10668
-
rwbarton authored
GHC has used surrogate code points for roundtripping since 7.4. See Note [Roundtripping]. Also, improve the wording of that Note slightly. Test Plan: validate still passes Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1087
-
Ben Gamari authored
Accept next docstrings (`-- | Docstring`) on GADT constructors. I have confirmed that this adds no shift/reduce conflicts. Test Plan: haddockA034 Reviewers: austin, simonpj, simonmar Reviewed By: simonmar Subscribers: Fuuzetsu, simonmar, thomie, mpickering, edsko Differential Revision: https://phabricator.haskell.org/D1086
-
spinda authored
With -dynamic-too, .dyn_o files were not being generated for .hsig files. Normally, this is handled in the pipeline; however, the branch for .hsig files called compileEmptyStub directly instead of going through runPipeline. When compiling a Cabal package that included .hsig files, this triggered a linker error later on, as it expected a .dyn_o file to have been generated for each .hsig. The fix is to use runPipeline for .hsig files, just as with .hs files. Alternately, one could duplicate the logic for handling -dynamic-too in the .hsig branch, but simply calling runPipeline ends up being much cleaner. Test Plan: validate Reviewers: austin, ezyang, bgamari, thomie Reviewed By: ezyang, thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1084 GHC Trac Issues: #10660
-
thomie authored
Reviewers: austin, bgamari, Fuuzetsu Reviewed By: bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1025 GHC Trac Issues: #10398
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
In dataConCannotMatch we were using a GADT data con without properly instantiating the existential type variables. The fix is easy, and the code is tighter.
-
- 22 Jul, 2015 9 commits
-
-
Edward Z. Yang authored
Summary: It's shorter! And then when Backpack overrides lookupIfaceTop everyone will see the right information. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1090
-
Edward Z. Yang authored
Summary: These are going to be used by Backpack, but someone else might find them useful. They do the "obvious thing". Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: goldfire, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1089
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
Edward Z. Yang authored
Note: ModIface format change is BC, no need to recompile. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
thomie authored
It's failing at the moment with "The log length has exceeded the limit of 4 Megabytes". We don't seem to have periods of >10 minutes without output after all, which was the initial reason of not using `--quiet`.
-
thomie authored
-
gcampax authored
Summary: The current OS memory allocator conflates the concepts of allocating address space and allocating memory, which makes the HEAP_ALLOCED() implementation excessively complicated (as the only thing it cares about is address space layout) and slow. Instead, what we want is to allocate a single insanely large contiguous block of address space (to make HEAP_ALLOCED() checks fast), and then commit subportions of that in 1MB blocks as we did before. This is currently behind a flag, USE_LARGE_ADDRESS_SPACE, that is only enabled for certain OSes. Test Plan: validate Reviewers: simonmar, ezyang, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D524 GHC Trac Issues: #9706
-