- 15 Nov, 2013 4 commits
-
-
Simon Peyton Jones authored
When we have an equality constraint where the LHS and RHS have ill-matched kinds, it get turned into a CIrredEvCan because a CTyEqCan/CFunEqCan are guaranteed kind-compatible. But that in turn led to a bug because in the constraint c = (a:k1) ~ (b:k2) the kind variables k1 and k2 don't show up in tyVarsOfType c. Why not? Because it looks like (~) k1 (a:k1) (b:k2) Maybe (~) should have two kind arguments? That seemed like too big a change for not (we wait for NoKinds), so this patch fixes the bug for now.
-
Simon Peyton Jones authored
Accommodating Simon M's suggestion (Trac #4268, comment 17)
-
Simon Peyton Jones authored
-
parcs authored
During instance lookup, we can treat classes and data families like any other TyCon instead of special-casing them. This approach, aside from being simpler, has the benefit of returning extra relevant instances for classes and data families. For example, given class A a instance B (a :: Constraint) instance A B ":info B" will now also print "instance A B" where previously it didn't due to the special casing of class TyCons in lookupInsts. This improves upon the existing patch for Trac #4175
-
- 14 Nov, 2013 9 commits
-
-
Iavor S. Diatchki authored
The changes in more detail: * `TcBuiltInSynFamily` is now known as `BuiltinSynFamily` and lives in `CoAxiom` * `sfMatchFam` returns (CoAxiomRule, [Type], Type), which is enough to make Coersion or TcCoercion, depending on what what we need. * The rest of the compiler is updated to reflect these changes, most notably we can eliminate the cludge (XXX) in FamInstEnv and remove the lhs-boot file.
-
Duncan Coutts authored
It is important that if a program recieved ^C from the user, and the program terminates as a result, that it exit with SIGINT so that the parent process knows that was the case. For example cabal calling ghc will then be able to tell the difference between it failing and the user interrupting with ^C and report (or not) appropriately. So we should just let the UserInterrupt exception propagate to the top level error handler which will do the right thing. See http://www.cons.org/cracauer/sigint.html
-
Duncan Coutts authored
This is the RTS part of a patch to base's topHandler to handle exiting by a signal. The intended behaviour is that on Unix, throwing ExitFailure (-sig) results in the process terminating with that signal. Previously shutdownHaskellAndSignal was only used for exiting with SIGINT due to the UserInterrupt exception. Improve shutdownHaskellAndSignal to do the signal part more carefully. In particular, it (should) now reliably terminates the process one way or another. Previusly if the signal was blocked, ignored or handled then shutdownHaskellAndSignal would actually return! Also, the topHandler code has two paths a careful shutdown and a "fast exit" where it does not give finalisers a chance to run. We want to support that mode also when we want to exit by signal. So rather than the base code directly calling stg_exit as it did before, we have a fastExit bool paramater for both shutdownHaskellAnd{Exit,Signal}.
-
Simon Marlow authored
-
Simon Marlow authored
It wasn't actually broken, but it wasn't obviously right either.
-
Simon Marlow authored
-
Simon Marlow authored
-
Herbert Valerio Riedel authored
Cabal was already updated to 1.18.1.2. last month, but then got reverted by accident by 06aac68d Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
benl authored
The bitcast operation always needs a type for the source.
-
- 13 Nov, 2013 5 commits
-
-
parcs authored
We've already been making sure to strictly modify the global name cache in order to avoid space leaks. However, that does us little good if the fields of the name cache are not made strict as well.
-
parcs authored
-
parcs authored
-
Iavor S. Diatchki authored
The main change is to add a case to `reduceTyFamApp_maybe` to evaluate built-in type constructors (e.g., (+), (*), and friends). To avoid problems with recursive modules, I moved the definition of TcBuiltInSynFamily from `FamInst` to `FamInstEnv`. I am still not sure if this is the right place. There is also a wibble that it'd be nice to fix: when we evaluate a built-in type function, using`sfMatchFam`, we get a `TcCoercion`. However, `reduceTyFamApp_maybe` needs a `Corecion`. I couldn't find a nice way to convert between the two, so I resorted to a bit of hack (marked with `XXX`). The hack is that we happen to know that the built-in constructors for the type-nat functions always return coercions of shape `TcAxiomRuleCo`, with no assumptions, so it easy to convert `TcCoercion` to `Coercion` in this one case. This is enough to make things work, but it is clearly a cludge.
-
- 12 Nov, 2013 8 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
The presenting issue was that we were never eta-expanding f (\x -> case x of (a,b) -> \s -> blah) and that meant we were allocating two lambdas instead of one. See Note [Eta expanding lambdas] in SimplUtils. However I didn't want to eta expand the lambda, and then try all over again for tryEtaExpandRhs. Yet the latter is important in the context of a let-binding it can do simple arity analysis. So I ended up refactoring CallCtxt so that it tells when we are on the RHS of a let. I also moved findRhsArity from SimplUtils to CoreArity. Performance increases nicely. Here are the ones where allocation improved by more than 0.5%. Notice the nice decrease in binary size too. -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- ansi -2.3% -0.9% 0.00 0.00 +0.0% bspt -2.1% -9.7% 0.01 0.01 -33.3% fasta -1.8% -11.7% -3.4% -3.6% +0.0% fft -1.9% -1.3% 0.06 0.06 +11.1% reverse-complem -1.9% -18.1% -1.9% -2.8% +0.0% sphere -1.8% -4.5% 0.09 0.09 +0.0% transform -1.8% -2.3% -4.6% -3.1% +0.0% -------------------------------------------------------------------------------- Min -3.0% -18.1% -13.9% -14.6% -35.7% Max -1.3% +0.0% +7.7% +7.7% +50.0% Geometric Mean -1.9% -0.6% -2.1% -2.1% -0.2%
-
Simon Peyton Jones authored
This patch fixes a bad omission in CSE, thanks to 'michaelt' for spotting it, and correctly identifying the fix (in cseRhs). The trouble was with x1 = C a b x2 = C x1 b y1 = C a b y2 = C y1 b we were not commoning up y2=x2, because we failed to substitute y1:=x1, so y2's RHS looked different to x2's I also refactoring, so taht the cs_map in a CSEnv map is cs_map :: CoreMap (OutExpr, Id) instead of cs_map :: CoreMap (OutExpr, OutExpr) Much nicer! This doesn't make much difference to allocation, but it gives a surprisingly big benefit to binary size. -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- ansi -1.7% -0.8% 0.00 0.00 +0.0% bspt -1.6% -1.5% 0.01 0.01 +0.0% cacheprof -1.8% -0.2% +1.6% +1.9% +2.7% fft -1.4% -1.3% 0.06 0.06 +11.1% ida -1.4% -1.0% 0.12 0.12 +0.0% rfib -1.4% -0.1% 0.03 0.03 +0.0% scs -1.6% -0.1% +1.5% +1.5% +0.0% spectral-norm -1.3% -0.1% -0.2% -0.2% +0.0% tak -1.4% -0.1% 0.02 0.02 +0.0% veritas -1.4% -0.1% 0.00 0.00 +0.0% -------------------------------------------------------------------------------- Min -2.5% -1.5% -11.8% -11.8% -8.0% Max -1.0% +0.0% +2.7% +2.5% +11.1% Geometric Mean -1.3% -0.1% -2.6% -2.6% +0.0%
-
Simon Peyton Jones authored
This makes us give a civilised warning when we hit an {-# ANN f foo #-} pragma in a stage-1 compiler. We decided that, since it's a pragma, it does not need a language extension flag to enable it.
-
Simon Peyton Jones authored
Fixes Trac #8519
-
Gabor Greif authored
-
- 08 Nov, 2013 2 commits
-
-
parcs authored
Previously, a command like $ ghc -tmpdir blah Foo where the directory blah/ does not exist, would loop forever: getTempDir would repeatedly try to create a temporary subdirectory inside blah/, catching the does-not-exist error thrown by createDirectory and retrying, in vain, with another suffix. Now instead the above compiler invocation will fail with an error: blah/ghc25781_0: createDirectory: does not exist (No such file or directory)
-
Simon Peyton Jones authored
Fixes Trac #8037
-
- 07 Nov, 2013 5 commits
-
-
Herbert Valerio Riedel authored
This updates the files to the versions bundled with GNU automake 1.13.3 Signed-off-by:
Herbert Valerio Riedel <hvr@gnu.org>
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
pdfrod authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This is to allow class C a where type family F a type instance F a = Bool instance C Int where type instance F Int = Char Plus minor improvements relating to Trac #8506
-
- 06 Nov, 2013 7 commits
-
-
Simon Peyton Jones authored
See Trac #8278. Example new message: Couldn't match expected type ‛T8278a.Maybe’ with actual type ‛Maybe a0’ NB: ‛T8278a.Maybe’ is defined in ‛T8278a’ ‛Maybe’ is defined in ‛Data.Maybe’ in package ‛base’ In the first argument of ‛f’, namely ‛Nothing’ The "NB" is the new bit
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Instead of panic-ing we now give a sensible message. There is quite a bit of refactoring here too, removing several #ifdef GHCI things
-
Simon Peyton Jones authored
This should really be an error, but we'll just warn for now
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
A simple oversight, but crucial! tcLHsType was returning F k Int where k is a unification variable that has been unified with *
-
Simon Peyton Jones authored
-