- 14 Dec, 2014 8 commits
-
-
Herbert Valerio Riedel authored
This also introduces a "bootstrap" `cabal_macros.h` header to provide the `MIN_VERSION_base()` macro during Cabal bootstrapping which as it is now used by `binary`.
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
The previous attempt failed, but hopefully this one succeeds... This also updates the perf-numbers for `haddock.base` and `haddock.Cabal` NB: this switches from `ghc-head` to `master` branch temporarily until GHC 7.10 has been properly branched off.
-
Sergei Trofimovich authored
Summary: And fix things all the way down to it. Namely: - remove 'r30' from free registers, it's an .LCTOC1 register for gcc. generated .plt stubs expect it to be initialised. - fix PicBase computation, which originally forgot to use 'tmp' reg in 'initializePicBase_ppc.fetchPC' - mark 'ForeighTarget's as implicitly using 'PicBase' register (see comment for details) - add 64-bit MO_Sub and test on alloclimit3/4 regtests - fix dynamic label offsets to match with .LCTOC1 offset Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Test Plan: validate passes equal amount of vanilla/dyn tests Reviewers: simonmar, erikd, austin Reviewed By: erikd, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D560 GHC Trac Issues: #8024, #9831
-
Herbert Valerio Riedel authored
This reverts commit 7f634320 again for now as it causes validate's bindist phase to fail with haddock: internal error: .../install dir/lib/ghc-7.9.20141214/html: getDirectoryContents: does not exist (No such file or directory)
-
Herbert Valerio Riedel authored
This also updates the perf-numbers for `haddock.base` and `haddock.Cabal` NB: this switches from `ghc-head` to `master` branch temporarily until GHC 7.10 has been properly branched off.
-
Erik de Castro Lopo authored
Summary: Signed-off-by: Erik de Castro Lopo <erikd@mega-nerd.com> Reviewers: austin, carter Reviewed By: carter Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D570 GHC Trac Issues: #9884
-
- 13 Dec, 2014 2 commits
-
-
Sergei Trofimovich authored
Summary: Found out when tracking down conflicts reported by happy. It was accidentally introduced in large Api Annotations patch: 803fc5db Before: unused rules: 1 shift/reduce conflicts: 60 reduce/reduce conflicts: 16 After: shift/reduce conflicts: 60 reduce/reduce conflicts: 12 Unused rule is seen in happy's --info= output as: rule 180 is unused ... decl_cls -> 'default' infixexp '::' sigtypedoc (180) decl_cls -> 'default' infixexp '::' sigtypedoc (181) While at it removed 'q' typo in parser conflict log :) Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Reviewers: simonmar, austin, alanz Reviewed By: alanz Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D569
-
eir@cis.upenn.edu authored
Doing so made the solver gobble up tons of memory, now that matchFam calls reduceTyFamApp_maybe. But, I don't know why, yet! Will look more closely at this soon.
-
- 12 Dec, 2014 2 commits
-
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
Summary: This is a rewrite of the algorithm to solve for Coercible "instances". A preliminary form of these ideas is at https://ghc.haskell.org/trac/ghc/wiki/Design/NewCoercibleSolver The basic idea here is that the `EqPred` constructor of `PredTree` now is parameterised by a new type `EqRel` (where `data EqRel = NomEq | ReprEq`). Thus, every equality constraint can now talk about nominal equality (the usual case) or representational equality (the `Coercible` case). This is a change from the previous behavior where `Coercible` was just considered a regular class with a special case in `matchClassInst`. Because of this change, representational equalities are now canonicalized just like nominal ones, allowing more equalities to be solved -- in particular, the case at the top of #9117. A knock-on effect is that the flattener must be aware of the choice of equality relation, because the inert set now stores both representational inert equalities alongside the nominal inert equalities. Of course, we can use representational equalities to rewrite only within another representational equality -- thus the parameterization of the flattener. A nice side effect of this change is that I've introduced a new type `CtFlavour`, which tracks G vs. W vs. D, removing some ugliness in the flattener. This commit includes some refactoring as discussed on D546. It also removes the ability of Deriveds to rewrite Deriveds. This fixes bugs #9117 and #8984. Reviewers: simonpj, austin, nomeata Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D546 GHC Trac Issues: #9117, #8984
-
- 11 Dec, 2014 5 commits
-
-
Simon Peyton Jones authored
Things get faster, except T5030
-
Simon Peyton Jones authored
The issue was that contInputType simply gave the wrong answer for type applications. There was no way to fix contInputType; it just didn't have enough information. So I did this: * Split the ApplyTo constructor of SimplUtils.SimplCont into ApplyToVal ApplyToTy I used record syntax for them; we should do this for some of the other constructors too. * The latter carries a sc_hole_ty, which is the type of the continuation's "hole" * Maintaining this type meant that I had do to something similar for SimplUtils.ArgSpec. * I renamed contInputType to contHoleType for consistency. * I did a bit of refactoring around the call to tryRules in Simplify, which was jolly confusing before. The resulting code is quite nice now. And it has the additional merit that it works. The tests are simply tc124 and T7891 with -O enabled.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
- 10 Dec, 2014 17 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Looking at some typechecker traces I could see places where we were laboriously creating a Refl coercion. This patch short-circuits the process. See TcCanonical: Note [unifyWanted and unifyDerived] Note [Decomposing TyConApps] I ended up with some refactoring, notably * I moved xCtEvidence, rewriteEvidence, rewriteEqEvidence from TcSMonad to TcCanonical There are some knock-on effects, but only minor ones.
-
Simon Peyton Jones authored
This short-cut can improve performance quite a bit, by short-circuiting the process of creating a fresh constraint and binding for each reduction. See Note [Reduce type family applications eagerly] in TcFlatten To do this I had to generalise the inert_flat_cache a bit, so that the rhs is not necessarily a type variable; but nothing fundamental.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Hardly used, not helpful. Use newEvVar instead.
-
Simon Peyton Jones authored
Trac #9872 showed the importance of processing goals in depth-first, so that we do not build up a huge pool of suspended function calls, waiting for their children to fire. There is a detailed explanation in Note [The flattening work list] in TcFlatten The effect for Trac #9872 (slow1.hs) is dramatic. We go from too long to wait down to 28Gbyte allocation. GHC 7.8.3 did 116Gbyte allocation!
-
eir@cis.upenn.edu authored
-
Marios Titas authored
Summary: When we call runHandlers, we must pass it a ForeignPtr. To ensure that this happens, we introduce a wrapper that receives a plain Ptr and converts it into a ForeignPtr. Then we adjust startSignalHandlers in rts/posix/Signals.c to call the wrapper instead of calling runHandlers directly. Reviewers: hvr, austin, rwbarton, simonmar Reviewed By: austin, simonmar Subscribers: simonmar, thomie, carter Differential Revision: https://phabricator.haskell.org/D515 GHC Trac Issues: #9817
-
Edward Z. Yang authored
Summary: Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D567
-
Edward Z. Yang authored
Summary: Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D565
-
Joachim Breitner authored
Summary: For compatibility with ARM machines from pre v6, the RTS provides implementations of certain atomic operations. Previously, these were only included in the threaded RTS. But ghc (the library) contains the code in compiler/cbits/genSym.c, which uses these operations if there is more than one capability. But there is only one libHSghc, so the linker wants to resolve these symbols in every case. By providing these operations in all RTSs, the linker is happy. The only downside is a small amount of dead code in the non-threaded RTS on old ARM machines. Test Plan: It helped here. Reviewers: bgamari, austin Reviewed By: bgamari, austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D564 GHC Trac Issues: #8951
-
David Feuer authored
Summary: `splitAt` is stricter than the Report specifies, so we should say so. Reviewers: hvr, austin Reviewed By: austin Subscribers: carter, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D562 GHC Trac Issues: #9870
-
Yuras authored
Summary: The error reports something like: The function ‘f’ is applied to three arguments, but its type ‘Int -> Float -> Char -> Bool’ has only three The original type was "Monad m => Int -> Float -> m Bool", but "m" was unified with "-> Char". Now it looks better: The function ‘f’ is applied to three arguments, its type is ‘Int -> Float -> m0 Bool’, it is specialized to ‘Int -> Float -> Char -> Bool’ Test Plan: T9605 Reviewers: simonpj, austin Reviewed By: austin Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D556 GHC Trac Issues: #9605
-
Facundo Domínguez authored
Summary: As proposed in [1], this extension introduces a new syntactic form `static e`, where `e :: a` can be any closed expression. The static form produces a value of type `StaticPtr a`, which works as a reference that programs can "dereference" to get the value of `e` back. References are like `Ptr`s, except that they are stable across invocations of a program. The relevant wiki pages are [2, 3], which describe the motivation/ideas and implementation plan respectively. [1] Jeff Epstein, Andrew P. Black, and Simon Peyton-Jones. Towards Haskell in the cloud. SIGPLAN Not., 46(12):118–129, September 2011. ISSN 0362-1340. [2] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers [3] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers/ImplementationPlanAuthored-by:
Facundo Domínguez <facundo.dominguez@tweag.io> Authored-by:
Mathieu Boespflug <m@tweag.io> Authored-by:
Alexander Vershilov <alexander.vershilov@tweag.io> Test Plan: `./validate` Reviewers: hvr, simonmar, simonpj, austin Reviewed By: simonpj, austin Subscribers: qnikst, bgamari, mboes, carter, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D550 GHC Trac Issues: #7015
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
- 09 Dec, 2014 1 commit
-
-
David Terei authored
-
- 08 Dec, 2014 5 commits
-
-
Gabor Greif authored
-
mjo authored
To actually *run* the doctests, you need to do a little hacking. Somewhere after the `GHC.Base` import, you'll need to reimport `Maybe(..)` from `Prelude`, clobbering the `GHC.Base` definition. After that, doctest should be runnable from the `Data/` directory. Reviewed By: austin, hvr Differential Revision: https://phabricator.haskell.org/D561
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
Simon Peyton Jones authored
-