| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Most of the other users of the fptools build system have migrated to
Cabal, and with the move to darcs we can now flatten the source tree
without losing history, so here goes.
The main change is that the ghc/ subdir is gone, and most of what it
contained is now at the top level. The build system now makes no
pretense at being multi-project, it is just the GHC build system.
No doubt this will break many things, and there will be a period of
instability while we fix the dependencies. A straightforward build
should work, but I haven't yet fixed binary/source distributions.
Changes to the Building Guide will follow, too.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Flags cleanup.
Basically the purpose of this commit is to move more of the compiler's
global state into DynFlags, which is moving in the direction we need
to go for the GHC API which can have multiple active sessions
supported by a single GHC instance.
Before:
$ grep 'global_var' */*hs | wc -l
78
After:
$ grep 'global_var' */*hs | wc -l
27
Well, it's an improvement. Most of what's left won't really affect
our ability to host multiple sessions.
Lots of static flags have become dynamic flags (yay!). Notably lots
of flags that we used to think of as "driver" flags, like -I and -L,
are now dynamic. The most notable static flags left behind are the
"way" flags, eg. -prof. It would be nice to fix this, but it isn't
urgent.
On the way, lots of cleanup has happened. Everything related to
static and dynamic flags lives in StaticFlags and DynFlags
respectively, and they share a common command-line parser library in
CmdLineParser. The flags related to modes (--makde, --interactive
etc.) are now private to the front end: in fact private to Main
itself, for now.
|
|
|
|
|
| |
change trailing comments on #else/#endif lines to C style to avoid
warnings from gcc 3.3's preprocessor.
|
|
|
|
|
| |
Take the old strictness analyser out of #ifdef DEBUG and put it
instead in #ifdef OLD_STRICTNESS. DEBUG was getting a bit slow.
|
|
|
|
|
|
|
|
|
| |
Make the inclusion of the old strictness analyser, CPR analyser, and
the relevant IdInfo components, conditional on DEBUG. This makes
IdInfo smaller by three fields in a non-DEBUG compiler, and reduces
the risk that the unused fields could harbour space leaks.
Eventually these passes will go away altogether.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- Pet peeve removal / code tidyup, replaced various sub-optimal
uses of 'length' with something a bit better, i.e., replaced
the following patterns
* length as `cmpOp` length bs
* length as `cmpOp` val -- incl. uses where val == 1 and val == 0
* {take,drop,splitAt} (length as) bs
* length [ () | pat <- as ]
with uses of misc Util functions.
I'd be surprised if there's a noticeable reduction in running
times as a result of these changes, but every little bit helps.
[ The changes have been tested wrt testsuite/ - I'm seeing a couple
of unexpected breakages coming from CorePrep, but I'm currently
assuming that these are due to other recent changes. ]
- compMan/CompManager.lhs: restored 4.08 compilability + some code
cleanup.
None of these changes are HEADworthy.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------
Simon's big commit
------------------
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!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------------------
Switch to the new demand analyser
---------------------------------
This commit makes the new demand analyser the main beast,
with the old strictness analyser as a backup. When
DEBUG is on, the old strictness analyser is run too, and the
results compared.
WARNING: this isn't thorougly tested yet, so expect glitches.
Delay updating for a few days if the HEAD is mission critical
for you.
But do try it out. I'm away for 2.5 weeks from Thursday, so
it would be good to shake out any glaring bugs before then.
|
|
|
|
| |
Comment and import wibbles
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Re-engineer the transition from Core to STG syntax. Main changes in
this commit:
- a new pass, CoreSat, handles saturation of constructors and PrimOps,
and puts the syntax into STG-like normal form (applications to atoms
only, etc), modulo type applications and Notes.
- CoreToStg is now done at the same time as StgVarInfo. Most of the
contents of StgVarInfo.lhs have been copied into CoreToStg.lhs and
some simplifications made.
less major changes:
- globalisation of names for the purposes of object splitting is
now done by the C code generator (which is the Right Place in
principle, but it was a bit fiddly).
- CoreTidy now does cloning of local binders and collection of arity
info. The IdInfo from CoreTidy is now *almost* the final IdInfo we
put in the interface file, except for CafInfo. I'm going to move
the CafInfo collection into CoreTidy in due course too.
- and some other minor tidyups while I was in cluster-bomb commit mode.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
1. Outputable.PprStyle now carries a bit more information
In particular, the printing style tells whether to print
a name in unqualified form. This used to be embedded in
a Name, but since Names now outlive a single compilation unit,
that's no longer appropriate.
So now the print-unqualified predicate is passed in the printing
style, not embedded in the Name.
2. I tidied up HscMain a little. Many of the showPass messages
have migraged into the repective pass drivers
|
|
|
|
| |
Fix simplifier stuff.
|
|
|
|
| |
Remove wired-in names. Partially propogated.
|
|
|
|
| |
remove unused imports
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
MERGE 4.07
* This fix cures the weird 'ifaceBinds' error that
Sven and George tripped over. It was quite obscure!
Basically, there was a top level binding
f = x
lying around, which CoreToStg didn't like. Why hadn't
it been substituted away? Because it had a NOINLINE
pragma. Why did it have a NOINLINE pragma? Because
it's an always-diverging function, so we never want to
inline it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Make it so that recursive newtype declarations don't send
GHC into an infinite loop.
newtype T = MkT T
This happened because Type.repType looked throught newtypes,
and that never stopped! Now TcTyDecls.mkNewTyConRep does the job
more carefully, and the result is cached in the TyCon itself.
* Improve the handling of type signatures & pragmas. Previously a
mis-placed (say) SPECIALISE instance pragmas could be silently
ignored.
Both these changes involved moving quite a lot of stuff between modules.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This utterly gigantic commit is what I've been up to in background
mode in the last couple of months. Originally the main goal
was to get rid of Con (staturated constant applications)
in the CoreExpr type, but one thing led to another, and I kept
postponing actually committing. Sorry.
Simon, 23 March 2000
I've tested it pretty thoroughly, but doubtless things will break.
Here are the highlights
* Con is gone; the CoreExpr type is simpler
* NoRepLits have gone
* Better usage info in interface files => less recompilation
* Result type signatures work
* CCall primop is tidied up
* Constant folding now done by Rules
* Lots of hackery in the simplifier
* Improvements in CPR and strictness analysis
Many bug fixes including
* Sergey's DoCon compiles OK; no loop in the strictness analyser
* Volker Wysk's programs don't crash the CPR analyser
I have not done much on measuring compilation times and binary sizes;
they could have got worse. I think performance has got significantly
better, though, in most cases.
Removing the Con form of Core expressions
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The big thing is that
For every constructor C there are now *two* Ids:
C is the constructor's *wrapper*. It evaluates and unboxes arguments
before calling $wC. It has a perfectly ordinary top-level defn
in the module defining the data type.
$wC is the constructor's *worker*. It is like a primop that simply
allocates and builds the constructor value. Its arguments are the
actual representation arguments of the constructor.
Its type may be different to C, because:
- useless dict args are dropped
- strict args may be flattened
For every primop P there is *one* Id, its (curried) Id
Neither contructor worker Id nor the primop Id have a defminition anywhere.
Instead they are saturated during the core-to-STG pass, and the code generator
generates code for them directly. The STG language still has saturated
primops and constructor applications.
* The Const type disappears, along with Const.lhs. The literal part
of Const.lhs reappears as Literal.lhs. Much tidying up in here,
to bring all the range checking into this one module.
* I got rid of NoRep literals entirely. They just seem to be too much trouble.
* Because Con's don't exist any more, the funny C { args } syntax
disappears from inteface files.
Parsing
~~~~~~~
* Result type signatures now work
f :: Int -> Int = \x -> x
-- The Int->Int is the type of f
g x y :: Int = x+y
-- The Int is the type of the result of (g x y)
Recompilation checking and make
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* The .hi file for a modules is not touched if it doesn't change. (It used to
be touched regardless, forcing a chain of recompilations.) The penalty for this
is that we record exported things just as if they were mentioned in the body of
the module. And the penalty for that is that we may recompile a module when
the only things that have changed are the things it is passing on without using.
But it seems like a good trade.
* -recomp is on by default
Foreign declarations
~~~~~~~~~~~~~~~~~~~~
* If you say
foreign export zoo :: Int -> IO Int
then you get a C produre called 'zoo', not 'zzoo' as before.
I've also added a check that complains if you export (or import) a C
procedure whose name isn't legal C.
Code generation and labels
~~~~~~~~~~~~~~~~~~~~~~~~~~
* Now that constructor workers and wrappers have distinct names, there's
no need to have a Foo_static_closure and a Foo_closure for constructor Foo.
I nuked the entire StaticClosure story. This has effects in some of
the RTS headers (i.e. s/static_closure/closure/g)
Rules, constant folding
~~~~~~~~~~~~~~~~~~~~~~~
* Constant folding becomes just another rewrite rule, attached to the Id for the
PrimOp. To achieve this, there's a new form of Rule, a BuiltinRule (see CoreSyn.lhs).
The prelude rules are in prelude/PrelRules.lhs, while simplCore/ConFold.lhs has gone.
* Appending of constant strings now works, using fold/build fusion, plus
the rewrite rule
unpack "foo" c (unpack "baz" c n) = unpack "foobaz" c n
Implemented in PrelRules.lhs
* The CCall primop is tidied up quite a bit. There is now a data type CCall,
defined in PrimOp, that packages up the info needed for a particular CCall.
There is a new Id for each new ccall, with an big "occurrence name"
{__ccall "foo" gc Int# -> Int#}
In interface files, this is parsed as a single Id, which is what it is, really.
Miscellaneous
~~~~~~~~~~~~~
* There were numerous places where the host compiler's
minInt/maxInt was being used as the target machine's minInt/maxInt.
I nuked all of these; everything is localised to inIntRange and inWordRange,
in Literal.lhs
* Desugaring record updates was broken: it didn't generate correct matches when
used withe records with fancy unboxing etc. It now uses matchWrapper.
* Significant tidying up in codeGen/SMRep.lhs
* Add __word, __word64, __int64 terminals to signal the obvious types
in interface files. Add the ability to print word values in hex into
C code.
* PrimOp.lhs is no longer part of a loop. Remove PrimOp.hi-boot*
Types
~~~~~
* isProductTyCon no longer returns False for recursive products, nor
for unboxed products; you have to test for these separately.
There's no reason not to do CPR for recursive product types, for example.
Ditto splitProductType_maybe.
Simplification
~~~~~~~~~~~~~~~
* New -fno-case-of-case flag for the simplifier. We use this in the first run
of the simplifier, where it helps to stop messing up expressions that
the (subsequent) full laziness pass would otherwise find float out.
It's much more effective than previous half-baked hacks in inlining.
Actually, it turned out that there were three places in Simplify.lhs that
needed to know use this flag.
* Make the float-in pass push duplicatable bindings into the branches of
a case expression, in the hope that we never have to allocate them.
(see FloatIn.sepBindsByDropPoint)
* Arrange that top-level bottoming Ids get a NOINLINE pragma
This reduced gratuitous inlining of error messages.
But arrange that such things still get w/w'd.
* Arrange that a strict argument position is regarded as an 'interesting'
context, so that if we see
foldr k z (g x)
then we'll be inclined to inline g; this can expose a build.
* There was a missing case in CoreUtils.exprEtaExpandArity that meant
we were missing some obvious cases for eta expansion
Also improve the code when handling applications.
* Make record selectors (identifiable by their IdFlavour) into "cheap" operations.
[The change is a 2-liner in CoreUtils.exprIsCheap]
This means that record selection may be inlined into function bodies, which
greatly improves the arities of overloaded functions.
* Make a cleaner job of inlining "lone variables". There was some distributed
cunning, but I've centralised it all now in SimplUtils.analyseCont, which
analyses the context of a call to decide whether it is "interesting".
* Don't specialise very small functions in Specialise.specDefn
It's better to inline it. Rather like the worker/wrapper case.
* Be just a little more aggressive when floating out of let rhss.
See comments with Simplify.wantToExpose
A small change with an occasional big effect.
* Make the inline-size computation think that
case x of I# x -> ...
is *free*.
CPR analysis
~~~~~~~~~~~~
* Fix what was essentially a bug in CPR analysis. Consider
letrec f x = let g y = let ... in f e1
in
if ... then (a,b) else g x
g has the CPR property if f does; so when generating the final annotated
RHS for f, we must use an envt in which f is bound to its final abstract
value. This wasn't happening. Instead, f was given the CPR tag but g
wasn't; but of course the w/w pass gives rotten results in that case!!
(Because f's CPR-ness relied on g's.)
On they way I tidied up the code in CprAnalyse. It's quite a bit shorter.
The fact that some data constructors return a constructed product shows
up in their CPR info (MkId.mkDataConId) not in CprAnalyse.lhs
Strictness analysis and worker/wrapper
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* BIG THING: pass in the demand to StrictAnal.saExpr. This affects situations
like
f (let x = e1 in (x,x))
where f turns out to have strictness u(SS), say. In this case we can
mark x as demanded, and use a case expression for it.
The situation before is that we didn't "know" that there is the u(SS)
demand on the argument, so we simply computed that the body of the let
expression is lazy in x, and marked x as lazily-demanded. Then even after
f was w/w'd we got
let x = e1 in case (x,x) of (a,b) -> $wf a b
and hence
let x = e1 in $wf a b
I found a much more complicated situation in spectral/sphere/Main.shade,
which improved quite a bit with this change.
* Moved the StrictnessInfo type from IdInfo to Demand. It's the logical
place for it, and helps avoid module loops
* Do worker/wrapper for coerces even if the arity is zero. Thus:
stdout = coerce Handle (..blurg..)
==>
wibble = (...blurg...)
stdout = coerce Handle wibble
This is good because I found places where we were saying
case coerce t stdout of { MVar a ->
...
case coerce t stdout of { MVar b ->
...
and the redundant case wasn't getting eliminated because of the coerce.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
A regrettably-gigantic commit that puts in place what Simon PJ
has been up to for the last month or so, on and off.
The basic idea was to restore unfoldings to *occurrences* of
variables without introducing a space leak. I wanted to make
sure things improved relative to 4.04, and that proved depressingly
hard. On the way I discovered several quite serious bugs in the
simplifier.
Here's a summary of what's gone on.
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* No commas between for-alls in RULES. This makes the for-alls have
the same syntax as in types.
* Arrange that simplConArgs works in one less pass than before.
This exposed a bug: a bogus call to completeBeta.
* Add a top-level flag in CoreUnfolding, used in callSiteInline
* Extend w/w to use etaExpandArity, so it does eta/coerce expansion
* Implement inline phases. The meaning of the inline pragmas is
described in CoreUnfold.lhs. You can say things like
{#- INLINE 2 build #-}
to mean "inline build in phase 2"
* Don't float anything out of an INLINE.
Don't float things to top level unless they also escape a value lambda.
[see comments with SetLevels.lvlMFE
Without at least one of these changes, I found that
{-# INLINE concat #-}
concat = __inline (/\a -> foldr (++) [])
was getting floated to
concat = __inline( /\a -> lvl a )
lvl = ...inlined version of foldr...
Subsequently I found that not floating constants out of an INLINE
gave really bad code like
__inline (let x = e in \y -> ...)
so I now let things float out of INLINE
* Implement the "reverse-mapping" idea for CSE; actually it turned out to be easier
to implement it in SetLevels, and may benefit full laziness too.
* It's a good idea to inline inRange. Consider
index (l,h) i = case inRange (l,h) i of
True -> l+i
False -> error
inRange itself isn't strict in h, but if it't inlined then 'index'
*does* become strict in h. Interesting!
* Big change to the way unfoldings and occurrence info is propagated in the simplifier
The plan is described in Subst.lhs with the Subst type
Occurrence info is now in a separate IdInfo field than user pragmas
* I found that
(coerce T (coerce S (\x.e))) y
didn't simplify in one round. First we get to
(\x.e) y
and only then do the beta. Solution: cancel the coerces in the continuation
* Amazingly, CoreUnfold wasn't counting the cost of a function an application.
* Disable rules in initial simplifier run. Otherwise full laziness
doesn't get a chance to lift out a MFE before a rule (e.g. fusion)
zaps it. queens is a case in point
* Improve float-out stuff significantly. The big change is that if we have
\x -> ... /\a -> ...let p = ..a.. in let q = ...p...
where p's rhs doesn't x, we abstract a from p, so that we can get p past x.
(We did that before.) But we also substitute (p a) for p in q, and then
we can do the same thing for q. (We didn't do that, so q got stuck.)
This is much better. It involves doing a substitution "as we go" in SetLevels,
though.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This bunch of commits represents work in progress on inlining and
worker/wrapper stuff.
Currently, I think it makes the compiler slightly worse than 4.04, for
reasons I don't yet understand. But it means that Simon and I can
both peer at what is going on.
* Substantially improve handling of coerces in worker/wrapper
* exprIsDupable for an application (f e1 .. en) wasn't calling exprIsDupable
on the arguments!! So applications with few, but large, args were being dupliated.
* sizeExpr on an application wasn't doing a nukeScrutDiscount on the arg of
an application!! So bogus discounts could accumulate from arguments!
* Improve handling of INLINE pragmas in calcUnfoldingGuidance. It was really
wrong before
|
|
|
|
| |
Many small tuning changes
|
|
|
|
| |
Small fixes, including a significant full-laziness bug in OccurAnal
|
|
|
|
|
|
|
| |
Enable rules for simplification of SeqOp
Fix a related bug in WwLib that made it look as if the binder
in a case expression was being demanded, when it wasn't.
|
|
|
|
| |
RULES-NOTES
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
(keving)
Big Bang introduction of CPR Analysis Pass. Note that now
-fstrictness only does the strictness analysis phase, it is necessary
to follow this with -fworker-wrapper to actually do the required Core
transformations. The -O option in the ghc driver script has been
modified appropriately.
For now, CPR analysis is turned off. To try it, insert a
-fcpr_analyse between the -fstrictness and the -fworker-wrapper
options.
Misc. comments:
- The worker flag has been removed from an ID's StrictnessInfo field.
Now the worker info is an extra field in the Id's prag info.
- We do a nested CPR analysis, but worker-wrapper only looks at the
info for the outermost constructor, else laziness can be lost.
- Id's CPR Info in traces and interfaces file follows __M
- Worker-wrappery transformation now accounts for both strictness and
CPR analysis results.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Move 4.01 onto the main trunk.
|
|
|
|
| |
Reorganisation of Id, IdInfo. Remove StdIdInfo, PragmaInfo; add basicTypes/MkId.lhs
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The Great Multi-Parameter Type Classes Merge.
Notes from Simon (abridged):
* Multi-parameter type classes are fully implemented.
* Error messages from the type checker should be noticeably improved
* Warnings for unused bindings (-fwarn-unused-names)
* many other minor bug fixes.
Internally there are the following changes
* Removal of Haskell 1.2 compatibility.
* Dramatic clean-up of the PprStyle stuff.
* The type Type has been substantially changed.
* The dictionary for each class is represented by a new
data type for that purpose, rather than by a tuple.
|
| |
|
|
|
|
| |
Removed sa_top_binds, folded into SaTopBinds
|
|
|
|
| |
2.0x bootable;new PP
|
|
|
|
| |
Major update to more-or-less 2.02
|
|
|
|
| |
Pragmas in interface files added
|
|
|
|
| |
SLPJ new renamer and lots more
|
|
|
|
| |
simonpj changes through 960715
|
|
|
|
| |
partain changes to 960714
|
|
|
|
| |
SLPJ changes through 960604
|
|
|
|
| |
SLPJ changes through 960515
|
|
|
|
| |
SLPJ 1.3 changes to 960430
|
|
|
|
| |
Add SLPJ/WDP 1.3 changes through 960404
|
|
|
|
| |
Final compiler stuff before Sansom renamer 960321
|
|
|
|
| |
simonpj/sansom/partain/dnt 1.3 compiler stuff through 96/03/18
|
| |
|
|
Initial revision
|