| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
Add Generalised Algebraic Data Types
------------------------------------
This rather big commit adds support for GADTs. For example,
data Term a where
Lit :: Int -> Term Int
App :: Term (a->b) -> Term a -> Term b
If :: Term Bool -> Term a -> Term a
..etc..
eval :: Term a -> a
eval (Lit i) = i
eval (App a b) = eval a (eval b)
eval (If p q r) | eval p = eval q
| otherwise = eval r
Lots and lots of of related changes throughout the compiler to make
this fit nicely.
One important change, only loosely related to GADTs, is that skolem
constants in the typechecker are genuinely immutable and constant, so
we often get better error messages from the type checker. See
TcType.TcTyVarDetails.
There's a new module types/Unify.lhs, which has purely-functional
unification and matching for Type. This is used both in the typechecker
(for type refinement of GADTs) and in Core Lint (also for type refinement).
|
|
|
|
| |
Merge backend-hacking-branch onto HEAD. Yay!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------------
Implement Rank-N types
----------------------
This commit implements the full glory of Rank-N types, using
the Odersky/Laufer approach described in their paper
"Putting type annotations to work"
In fact, I've had to adapt their approach to deal with the
full glory of Haskell (including pattern matching, and the
scoped-type-variable extension). However, the result is:
* There is no restriction to rank-2 types. You can nest forall's
as deep as you like in a type. For example, you can write a type
like
p :: ((forall a. Eq a => a->a) -> Int) -> Int
This is a rank-3 type, illegal in GHC 5.02
* When matching types, GHC uses the cunning Odersky/Laufer coercion
rules. For example, suppose we have
q :: (forall c. Ord c => c->c) -> Int
Then, is this well typed?
x :: Int
x = p q
Yes, it is, but GHC has to generate the right coercion. Here's
what it looks like with all the big lambdas and dictionaries put in:
x = p (\ f :: (forall a. Eq a => a->a) ->
q (/\c \d::Ord c -> f c (eqFromOrd d)))
where eqFromOrd selects the Eq superclass dictionary from the Ord
dicationary: eqFromOrd :: Ord a -> Eq a
* You can use polymorphic types in pattern type signatures. For
example:
f (g :: forall a. a->a) = (g 'c', g True)
(Previously, pattern type signatures had to be monotypes.)
* The basic rule for using rank-N types is that you must specify
a type signature for every binder that you want to have a type
scheme (as opposed to a plain monotype) as its type.
However, you don't need to give the type signature on the
binder (as I did above in the defn for f). You can give it
in a separate type signature, thus:
f :: (forall a. a->a) -> (Char,Bool)
f g = (g 'c', g True)
GHC will push the external type signature inwards, and use
that information to decorate the binders as it comes across them.
I don't have a *precise* specification of this process, but I
think it is obvious enough in practice.
* In a type synonym you can use rank-N types too. For example,
you can write
type IdFun = forall a. a->a
f :: IdFun -> (Char,Bool)
f g = (g 'c', g True)
As always, type synonyms must always occur saturated; GHC
expands them before it does anything else. (Still, GHC goes
to some trouble to keep them unexpanded in error message.)
The main plan is as before. The main typechecker for expressions,
tcExpr, takes an "expected type" as its argument. This greatly
improves error messages. The new feature is that when this
"expected type" (going down) meets an "actual type" (coming up)
we use the new subsumption function
TcUnify.tcSub
which checks that the actual type can be coerced into the
expected type (and produces a coercion function to demonstrate).
The main new chunk of code is TcUnify.tcSub. The unifier itself
is unchanged, but it has moved from TcMType into TcUnify. Also
checkSigTyVars has moved from TcMonoType into TcUnify.
Result: the new module, TcUnify, contains all stuff relevant
to subsumption and unification.
Unfortunately, there is now an inevitable loop between TcUnify
and TcSimplify, but that's just too bad (a simple TcUnify.hi-boot
file).
All of this doesn't come entirely for free. Here's the typechecker
line count (INCLUDING comments)
Before 16,551
After 17,116
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------
Simon's big commit
------------------
[ These files seem to have been left out for some reason ]
This commit, which I don't think I can sensibly do piecemeal, consists
of the things I've been doing recently, mainly directed at making
Manuel, George, and Marcin happier with RULES.
Reogranise the simplifier
~~~~~~~~~~~~~~~~~~~~~~~~~
1. The simplifier's environment is now an explicit parameter. This
makes it a bit easier to figure out where it is going.
2. Constructor arguments can now be arbitrary expressions, except
when the application is the RHS of a let(rec). This makes it much
easier to match rules like
RULES
"foo" f (h x, g y) = f' x y
In the simplifier, it's Simplify.mkAtomicArgs that ANF-ises a
constructor application where necessary. In the occurrence analyser,
there's a new piece of context info (OccEncl) to say whether a
constructor app is in a place where it should be in ANF. (Unless
it knows this it'll give occurrence info which will inline the
argument back into the constructor app.)
3. I'm experimenting with doing the "float-past big lambda" transformation
in the full laziness pass, rather than mixed in with the simplifier (was
tryRhsTyLam).
4. Arrange that
case (coerce (S,T) (x,y)) of ...
will simplify. Previous it didn't.
A local change to CoreUtils.exprIsConApp_maybe.
5. Do a better job in CoreUtils.exprEtaExpandArity when there's an
error function in one branch.
Phase numbers, RULES, and INLINE pragmas
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1. Phase numbers decrease from N towards zero (instead of increasing).
This makes it easier to add new earlier phases, which is what users want
to do.
2. RULES get their own phase number, N, and are disabled in phases before N.
e.g. {-# RULES "foo" [2] forall x y. f (x,y) = f' x y #-}
Note the [2], which says "only active in phase 2 and later".
3. INLINE and NOINLINE pragmas have a phase number to. This is now treated
in just the same way as the phase number on RULE; that is, the Id is not inlined
in phases earlier than N. In phase N and later the Id *may* be inlined, and
here is where INLINE and NOINLINE differ: INLNE makes the RHS look small, so
as soon as it *may* be inlined it probably *will* be inlined.
The syntax of the phase number on an INLINE/NOINLINE pragma has changed to be
like the RULES case (i.e. in square brackets). This should also make sure
you examine all such phase numbers; many will need to change now the numbering
is reversed.
Inlining Ids is no longer affected at all by whether the Id appears on the
LHS of a rule. Now it's up to the programmer to put a suitable INLINE/NOINLINE
pragma to stop it being inlined too early.
Implementation notes:
* A new data type, BasicTypes.Activation says when a rule or inline pragma
is active. Functions isAlwaysActive, isNeverActive, isActive, do the
obvious thing (all in BasicTypes).
* Slight change in the SimplifierSwitch data type, which led to a lot of
simplifier-specific code moving from CmdLineOpts to SimplMonad; a Good Thing.
* The InlinePragma in the IdInfo of an Id is now simply an Activation saying
when the Id can be inlined. (It used to be a rather bizarre pair of a
Bool and a (Maybe Phase), so this is much much easier to understand.)
* The simplifier has a "mode" environment switch, replacing the old
black list. Unfortunately the data type decl has to be in
CmdLineOpts, because it's an argument to the CoreDoSimplify switch
data SimplifierMode = SimplGently | SimplPhase Int
Here "gently" means "no rules, no inlining". All the crucial
inlining decisions are now collected together in SimplMonad
(preInlineUnconditionally, postInlineUnconditionally, activeInline,
activeRule).
Specialisation
~~~~~~~~~~~~~~
1. Only dictionary *functions* are made INLINE, not dictionaries that
have no parameters. (This inline-dictionary-function thing is Marcin's
idea and I'm still not sure whether it's a good idea. But it's definitely
a Bad Idea when there are no arguments.)
2. Be prepared to specialise an INLINE function: an easy fix in
Specialise.lhs
But there is still a problem, which is that the INLINE wins
at the call site, so we don't use the specialised version anyway.
I'm still unsure whether it makes sense to SPECIALISE something
you want to INLINE.
Random smaller things
~~~~~~~~~~~~~~~~~~~~~~
* builtinRules (there was only one, but may be more) in PrelRules are now
incorporated. They were being ignored before...
* OrdList.foldOL --> OrdList.foldrOL, OrdList.foldlOL
* Some tidying up of the tidyOpenTyVar, tidyTyVar functions. I've
forgotten exactly what!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Tidy up and improve "pattern contexts"
--------------------------------------
In various places (renamer, typechecker, desugarer) we need to know
what the context of a pattern match is (case expression, function defn,
let binding, etc). This commit tidies up the story quite a bit. I
think it represents a net decrease in code, and certainly it improves the
error messages from:
f x x = 3
Prevsiously we got a message like "Conflicting bindings for x in a pattern match",
but not it says "..in a defn of function f".
WARNING: the tidy up had a more global effect than I originally expected,
so it's possible that some other error messages look a bit peculiar. They
should be easy to fix, but tell us!
|
|
|
|
| |
Update NOTES
|
|
|
|
| |
Mainly renamer
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Simon's Marktoberdorf Commits
1. Tidy up the renaming story for "system binders", such as
dictionary functions, default methods, constructor workers etc. These
are now documented in HsDecls. The main effect of the change, apart
from tidying up, is to make the *type-checker* (instead of the
renamer) generate names for dict-funs and default-methods. This is
good because Sergei's generic-class stuff generates new classes at
typecheck time.
2. Fix the CSE pass so it does not require the no-shadowing invariant.
Keith discovered that the simplifier occasionally returns a result
with shadowing. After much fiddling around (which has improved the
code in the simplifier a bit) I found that it is nearly impossible to
arrange that it really does do no-shadowing. So I gave up and fixed
the CSE pass (which is the only one to rely on it) instead.
3. Fix a performance bug in the simplifier. The change is in
SimplUtils.interestingArg. It computes whether an argment should
be considered "interesting"; if a function is applied to an interesting
argument, we are more likely to inline that function.
Consider this case
let x = 3 in f x
The 'x' argument was considered "uninteresting" for a silly reason.
Since x only occurs once, it was unconditionally substituted, but
interestingArg didn't take account of that case. Now it does.
I also made interestingArg a bit more liberal. Let's see if we
get too much inlining now.
4. In the occurrence analyser, we were choosing a bad loop breaker.
Here's the comment that's now in OccurAnal.reOrderRec
score ((bndr, rhs), _, _)
| exprIsTrivial rhs = 3 -- Practically certain to be inlined
-- Used to have also: && not (isExportedId bndr)
-- But I found this sometimes cost an extra iteration when we have
-- rec { d = (a,b); a = ...df...; b = ...df...; df = d }
-- where df is the exported dictionary. Then df makes a really
-- bad choice for loop breaker
I also increased the score for bindings with a non-functional type, so that
dictionaries have a better chance of getting inlined early
5. Add a hash code to the InScopeSet (and make it properly abstract)
This should make uniqAway a lot more robust. Simple experiments suggest
that uniqAway no longer gets into the long iteration chains that it used
to.
6. Fix a bug in the inliner that made the simplifier tend to get into
a loop where it would keep iterating ("4 iterations, bailing out" message).
In SimplUtils.mkRhsTyLam we float bindings out past a big lambda, thus:
x = /\ b -> let g = \x -> f x x
in E
becomes
g* = /\a -> \x -> f x x
x = /\ b -> let g = g* b in E
It's essential that we don't simply inling g* back into the RHS of g,
else we will be back to square 1. The inliner is meant not to do this
because there's no benefit to the inlining, but the size calculation
was a little off in CoreUnfold.
7. In SetLevels we were bogus-ly building a Subst with an empty in-scope
set, so a WARNING popped up when compiling some modules. (knights/ChessSetList
was the example that tickled it.) Now in fact the warning wasn't an error,
but the Right Thing to do is to carry down a proper Subst in SetLevels, so
that is what I have now done. It is very little more expensive.
|
|
|
|
| |
Small fixes, including a significant full-laziness bug in OccurAnal
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Another big commit from Simon. Actually, the last one
didn't all go into the main trunk; because of a CVS glitch it
ended up in the wrong branch.
So this commit includes:
* Scoped type variables
* Warnings for unused variables should work now (they didn't before)
* Simplifier improvements:
- Much better treatment of strict arguments
- Better treatment of bottoming Ids
- No need for w/w split for fns that are merely strict
- Fewer iterations needed, I hope
* Less gratuitous renaming in interface files and abs C
* OccName is a separate module, and is an abstract data type
I think the whole Prelude and Exts libraries compile correctly.
Something isn't quite right about typechecking existentials though.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This massive commit is what Simon has been up to for a couple of weeks.
1. Scoped type variables are in
2. The typechecker works a bit differently.
In partiular, the compiler no longer has TcTyVars of
a different type than TyVars.
All the 's' and 'flexi' type parameters have vanished from Id, TyVar,
Type, etc.
The typchecker monad is now in the IO world (though I didn't get
around to removing the 's' parameter from the monad, but it's
no longer used)
Bottom line: significantly simpler,
fewer gratuitous conversions from TcType <-> Type
but less type security in the compiler
There was a reason for doing this now; somehow the 's' stuff
got in the way of kind inference for scoped type variables
and I lost patience with it.
3. Haskell98-style reporting of scope errors; i.e. you only get
an error if you use a variable that could mean two different things.
At the same time I did a lot of tidying-up in the renamer.
4. Mostly-complete fix to the reporting of unused variables, which
has never worked properly. (The 'mostly' bit is because it reports
those 'system' tycons like _C as unused. I'm on the job.)
5. The parser is a bit tider than it was. A few more ugn files give
a more refined C data type. I had to tackle this because of
the scoped type variables.
6. Haskell98-style fixities. Fixity decls can occur wherever a type
signature can
7. Some HsSyn changes that constitute minor tidy ups
Put TypeDecl and ClassDecl into one type [HsDecls]
Improved the HsMatch/GRHSs etc data types.
8. TcGRHSs is removed; combined into TcMatches.
I DO NOT PROMISE THAT ALL OF THIS WORKS. It compiles the Prelude,
but I have not tested it more than that. Stick to 4.01 if you want a
compiler that's sure to work.
|
| |
|
|
Major update to more-or-less 2.02
|