- Apr 23, 2012
-
-
Simon Peyton Jones authored
Work in progress, on branch
-
- Apr 22, 2012
-
-
Simon Peyton Jones authored
So we never infer f :: Eq (Tree a) => blah when there isn't an instance for Eq (Tree a). This fixes Trac #6022. It does represent a change in behaviour: certain (bizarre) programs will be rejected that were previously accepted. Specifically, if you have module A where f x = ...somethign needing (C T)... moudule B where import A instance C T test = f True Here the (C T) instance is provided "later". But this is wierd; it would be better to give a type signature for f f :: C T => Bool -> Bool and then you'd be fine.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Fixes Trac #6020
-
Simon Peyton Jones authored
That in turn means that you can derive Show etc in other modules, fixing Trac #6031
-
- Apr 21, 2012
-
-
chak@cse.unsw.edu.au. authored
Xcode 4.3 installs the command line tools in a different location as earlier versions of Xcode. With the bootstrapping info, the build fails if the bootstrap compiler was built with an older version of Xcode.
-
- Apr 20, 2012
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
The trouble here is that given {-# LANGUAGE DataKinds, TypeFamilies #-} data instance Foo a = Bar (Bar a) we want to get a sensible message that we can't use the promoted 'Bar' constructor until after its definition; it's a staging error. Bud the staging mechanism that we use for vanilla data declarations don't work here. Solution is to perform strongly-connected component analysis on the instance declarations. But that in turn means that we need to track free-variable information on more HsSyn declarations, which is why so many files are touched. All the changes are boiler-platey except the ones in TcInstDcls.
-
chak@cse.unsw.edu.au. authored
- Apr 19, 2012
-
-
jpm@cs.ox.ac.uk authored
-
- Apr 16, 2012
-
-
pcapriotti authored
-
Simon Peyton Jones authored
Not only does this fix Trac #5853, but it also eliminate the horrid SimplEqsOnly part of the constraint simplifier. The new plan is described in TcRules Note [Simplifying RULE constraints]
-
Simon Peyton Jones authored
There was an ASSERT which does not hold during type checking (and should not) which is later checked by Core Lint
-
pcapriotti authored
-
pcapriotti authored
Use a free monad to specify the assembling procedure, so that it can be run multiple times without producing side effects. This paves the way for a more general implementation of variable-sized instructions, since we need to dry-run the bytecode assembler to determine the size of the operands for some instructions.
-
pcapriotti authored
-
pcapriotti authored
The bytecode generator used to keep track of the stack depth with a 16-bit counter, which could overflow for very large BCOs, resulting in incorrect bytecode. This commit switches to a word-sized counter, and eagerly panics whenever an operand is too big, instead of truncating the result. This allows us to work around the 16-bit limitation in the case of SLIDE instructions, since we can simply factor it into multiple SLIDEs with smaller arguments.
-
pcapriotti authored
-
pcapriotti authored
-
- Apr 13, 2012
-
-
Simon Peyton Jones authored
This is the last major addition to the kind-polymorphism story, by allowing (Trac #5938) type family F a -- F :: forall k. k -> * data T a -- T :: forall k. k -> * type instance F (T (a :: Maybe k)) = Char The new thing is the explicit 'k' in the type signature on 'a', which itself is inside a type pattern for F. Main changes are: * HsTypes.HsBSig now has a *pair* (kvs, tvs) of binders, the kind variables and the type variables * extractHsTyRdrTyVars returns a pair (kvs, tvs) and the function itself has moved from RdrHsSyn to RnTypes * Quite a bit of fiddling with TcHsType.tcHsPatSigType and tcPatSig which have become a bit simpler. I'm still not satisfied though. There's some consequential fiddling in TcRules too. * Removed the unused HsUtils.collectSigTysFromPats There's a consequential wibble to Haddock too
-
Simon Peyton Jones authored
A long-standing and egregious bug in the worker/wrapper code meant that some functions with the CPR property weren't getting a CPR w/w. And that had the effect of making a tail-recursive function not tail recursive. As well as increasing allocation. Fixes Trac #5920, and #5997. Nofib results (highlights): Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer2 -0.1% -15.3% 0.01 0.01 +0.0% mandel2 -0.0% -8.1% 0.01 0.01 +0.0% para -0.1% -11.8% -7.9% -7.8% +0.0% -------------------------------------------------------------------------------- Min -0.1% -15.3% -7.9% -7.8% -33.3% Max +0.0% +0.2% +6.3% +6.3% +3.7% Geometric Mean -0.0% -0.4% +0.1% +0.1% -0.5% Looks like a clear win. And I have not even recompiled the libraries, so it'll probably be a bit better in the ed.
-
Simon Peyton Jones authored
This change allows a top-level instance to be used even if there is a (potentially) overlapping local given. Which isn't fab, but it is what IncoherentInstances is *for*. This fixes the bug part of Trac #6002.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Two problems, for now at any rate a) Breaks the build with lots of errors like No instance for (Show (IO ())) arising from a use of `print' b) Discussion of the approache hasn't converged yet (Simon M had a number of suggestions) This reverts commit eecd7c98.
-
David Terei authored
This command allows you to lift user stmts in GHCi into an IO monad that implements the GHC.GHCi.GHCiSandboxIO type class. This allows for easy sandboxing of GHCi using :runmonad and Safe Haskell. Longer term it would be nice to allow a more general model for the Monad than GHCiSandboxIO but delaying this for the moment.
- Apr 12, 2012
-
-
David Terei authored
-
David Terei authored
-
Simon Marlow authored
-
Simon Marlow authored
-
Simon Marlow authored
This is a partial fix for #2786. It seems we still don't get NonTermination exceptions for interpreted computations, but we do now get the BlockedIndefinitely family.
-
pcapriotti authored
Display class method signature instead of user-provided signature.
-
- Apr 11, 2012
-
-
pcapriotti authored
-
pcapriotti authored
-
pcapriotti authored
Patch by Sam Anklesaria <amsay@amsay.net>
-