| 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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for partial reloads in the GHC API.
This is mainly for VS: when editing a file you don't want to
continually reload the entire project whenever the current file
changes, you want to reload up to and including the current file only.
However, you also want to retain any other modules in the session that
are still stable.
I added a variant of :reload in GHCi to test this. You can say
':reload M' to reload up to module M only. This will bring M up to
date, and throw away any invalidated modules from the session.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------
Use merge-sort not quicksort
Nuke quicksort altogether
-------------------------------
Quicksort has O(n**2) behaviour worst case, and this occasionally bites.
In particular, when compiling large files consisting only of static data,
we get loads of top-level delarations -- and that led to more than half the
total compile time being spent in the strongly connected component analysis
for the occurrence analyser. Switching to merge sort completely solved the
problem.
I've nuked quicksort altogether to make sure this does not happen again.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------
GHC heart/lung transplant
-------------------------
This major commit changes the way that GHC deals with importing
types and functions defined in other modules, during renaming and
typechecking. On the way I've changed or cleaned up numerous other
things, including many that I probably fail to mention here.
Major benefit: GHC should suck in many fewer interface files when
compiling (esp with -O). (You can see this with -ddump-rn-stats.)
It's also some 1500 lines of code shorter than before.
** So expect bugs! I can do a 3-stage bootstrap, and run
** the test suite, but you may be doing stuff I havn't tested.
** Don't update if you are relying on a working HEAD.
In particular, (a) External Core and (b) GHCi are very little tested.
But please, please DO test this version!
------------------------
Big things
------------------------
Interface files, version control, and importing declarations
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* There is a totally new data type for stuff that lives in interface files:
Original names IfaceType.IfaceExtName
Types IfaceType.IfaceType
Declarations (type,class,id) IfaceSyn.IfaceDecl
Unfoldings IfaceSyn.IfaceExpr
(Previously we used HsSyn for type/class decls, and UfExpr for unfoldings.)
The new data types are in iface/IfaceType and iface/IfaceSyn. They are
all instances of Binary, so they can be written into interface files.
Previous engronkulation concering the binary instance of RdrName has
gone away -- RdrName is not an instance of Binary any more. Nor does
Binary.lhs need to know about the ``current module'' which it used to,
which made it specialised to GHC.
A good feature of this is that the type checker for source code doesn't
need to worry about the possibility that we might be typechecking interface
file stuff. Nor does it need to do renaming; we can typecheck direct from
IfaceSyn, saving a whole pass (module TcIface)
* Stuff from interface files is sucked in *lazily*, rather than being eagerly
sucked in by the renamer. Instead, we use unsafeInterleaveIO to capture
a thunk for the unfolding of an imported function (say). If that unfolding
is every pulled on, TcIface will scramble over the unfolding, which may
in turn pull in the interface files of things mentioned in the unfolding.
The External Package State is held in a mutable variable so that it
can be side-effected by this lazy-sucking-in process (which may happen
way later, e.g. when the simplifier runs). In effect, the EPS is a kind
of lazy memo table, filled in as we suck things in. Or you could think
of it as a global symbol table, populated on demand.
* This lazy sucking is very cool, but it can lead to truly awful bugs. The
intent is that updates to the symbol table happen atomically, but very bad
things happen if you read the variable for the table, and then force a
thunk which updates the table. Updates can get lost that way. I regret
this subtlety.
One example of the way it showed up is that the top level of TidyPgm
(which updates the global name cache) to be much more disciplined about
those updates, since TidyPgm may itself force thunks which allocate new
names.
* Version numbering in interface files has changed completely, fixing
one major bug with ghc --make. Previously, the version of A.f changed
only if A.f's type and unfolding was textually different. That missed
changes to things that A.f's unfolding mentions; which was fixed by
eagerly sucking in all of those things, and listing them in the module's
usage list. But that didn't work with --make, because they might have
been already sucked in.
Now, A.f's version changes if anything reachable from A.f (via interface
files) changes. A module with unchanged source code needs recompiling
only if the versions of any of its free variables changes. [This isn't
quite right for dictionary functions and rules, which aren't mentioned
explicitly in the source. There are extensive comments in module MkIface,
where all version-handling stuff is done.]
* We don't need equality on HsDecls any more (because they aren't used in
interface files). Instead we have a specialised equality for IfaceSyn
(eqIfDecl etc), which uses IfaceEq instead of Bool as its result type.
See notes in IfaceSyn.
* The horrid bit of the renamer that tried to predict what instance decls
would be needed has gone entirely. Instead, the type checker simply
sucks in whatever instance decls it needs, when it needs them. Easy!
Similarly, no need for 'implicitModuleFVs' and 'implicitTemplateHaskellFVs'
etc. Hooray!
Types and type checking
~~~~~~~~~~~~~~~~~~~~~~~
* Kind-checking of types is far far tidier (new module TcHsTypes replaces
the badly-named TcMonoType). Strangely, this was one of my
original goals, because the kind check for types is the Right Place to
do type splicing, but it just didn't fit there before.
* There's a new representation for newtypes in TypeRep.lhs. Previously
they were represented using "SourceTypes" which was a funny compromise.
Now they have their own constructor in the Type datatype. SourceType
has turned back into PredType, which is what it used to be.
* Instance decl overlap checking done lazily. Consider
instance C Int b
instance C a Int
These were rejected before as overlapping, because when seeking
(C Int Int) one couldn't tell which to use. But there's no problem when
seeking (C Bool Int); it can only be the second.
So instead of checking for overlap when adding a new instance declaration,
we check for overlap when looking up an Inst. If we find more than one
matching instance, we see if any of the candidates dominates the others
(in the sense of being a substitution instance of all the others);
and only if not do we report an error.
------------------------
Medium things
------------------------
* The TcRn monad is generalised a bit further. It's now based on utils/IOEnv.lhs,
the IO monad with an environment. The desugarer uses the monad too,
so that anything it needs can get faulted in nicely.
* Reduce the number of wired-in things; in particular Word and Integer
are no longer wired in. The latter required HsLit.HsInteger to get a
Type argument. The 'derivable type classes' data types (:+:, :*: etc)
are not wired in any more either (see stuff about derivable type classes
below).
* The PersistentComilerState is now held in a mutable variable
in the HscEnv. Previously (a) it was passed to and then returned by
many top-level functions, which was painful; (b) it was invariably
accompanied by the HscEnv. This change tidies up top-level plumbing
without changing anything important.
* Derivable type classes are treated much more like 'deriving' clauses.
Previously, the Ids for the to/from functions lived inside the TyCon,
but now the TyCon simply records their existence (with a simple boolean).
Anyone who wants to use them must look them up in the environment.
This in turn makes it easy to generate the to/from functions (done
in types/Generics) using HsSyn (like TcGenDeriv for ordinary derivings)
instead of CoreSyn, which in turn means that (a) we don't have to figure
out all the type arguments etc; and (b) it'll be type-checked for us.
Generally, the task of generating the code has become easier, which is
good for Manuel, who wants to make it more sophisticated.
* A Name now says what its "parent" is. For example, the parent of a data
constructor is its type constructor; the parent of a class op is its
class. This relationship corresponds exactly to the Avail data type;
there may be other places we can exploit it. (I made the change so that
version comparison in interface files would be a bit easier; but in
fact it tided up other things here and there (see calls to
Name.nameParent). For example, the declaration pool, of declararations
read from interface files, but not yet used, is now keyed only by the 'main'
name of the declaration, not the subordinate names.
* New types OccEnv and OccSet, with the usual operations.
OccNames can be efficiently compared, because they have uniques, thanks
to the hashing implementation of FastStrings.
* The GlobalRdrEnv is now keyed by OccName rather than RdrName. Not only
does this halve the size of the env (because we don't need both qualified
and unqualified versions in the env), but it's also more efficient because
we can use a UniqFM instead of a FiniteMap.
Consequential changes to Provenance, which has moved to RdrName.
* External Core remains a bit of a hack, as it was before, done with a mixture
of HsDecls (so that recursiveness and argument variance is still inferred),
and IfaceExprs (for value declarations). It's not thoroughly tested.
------------------------
Minor things
------------------------
* DataCon fields dcWorkId, dcWrapId combined into a single field
dcIds, that is explicit about whether the data con is a newtype or not.
MkId.mkDataConWorkId and mkDataConWrapId are similarly combined into
MkId.mkDataConIds
* Choosing the boxing strategy is done for *source* type decls only, and
hence is now in TcTyDecls, not DataCon.
* WiredIn names are distinguished by their n_sort field, not by their location,
which was rather strange
* Define Maybes.mapCatMaybes :: (a -> Maybe b) -> [a] -> [b]
and use it here and there
* Much better pretty-printing of interface files (--show-iface)
Many, many other small things.
------------------------
File changes
------------------------
* New iface/ subdirectory
* Much of RnEnv has moved to iface/IfaceEnv
* MkIface and BinIface have moved from main/ to iface/
* types/Variance has been absorbed into typecheck/TcTyDecls
* RnHiFiles and RnIfaces have vanished entirely. Their
work is done by iface/LoadIface
* hsSyn/HsCore has gone, replaced by iface/IfaceSyn
* typecheck/TcIfaceSig has gone, replaced by iface/TcIface
* typecheck/TcMonoType has been renamed to typecheck/TcHsType
* basicTypes/Var.hi-boot and basicTypes/Generics.hi-boot have gone altogether
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------
Implement recursive do-notation
--------------------------------
This commit adds recursive do-notation, which Hugs has had for some time.
mdo { x <- foo y ;
y <- baz x ;
return (y,x) }
turns into
do { (x,y) <- mfix (\~(x,y) -> do { x <- foo y;
y <- baz x }) ;
return (y,x) }
This is all based on work by Levent Erkok and John Lanuchbury.
The really tricky bit is in the renamer (RnExpr.rnMDoStmts) where
we break things up into minimal segments. The rest is easy, including
the type checker.
Levent laid the groundwork, and Simon finished it off. Needless to say,
I couldn't resist tidying up other stuff, so there's no guaranteed I
have not broken something.
|
|
|
|
|
|
|
| |
Finally separate the compiler from hslibs.
Mainly import wibbles, and use the new POSIX library when
bootstrapping.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- 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.
|
|
|
|
| |
Fixes to do with CM and module cycles. Also to do with OPTIONS pragmas.
|
|
|
|
|
| |
Final mods to make it compile with 4.08.1. You don't get an interpreter
like that, tho.
|
|
|
|
| |
remove last use of REALLY_HASKELL_1_3
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
~~~~~~~~~~~~
Apr/May 2000
~~~~~~~~~~~~
This is a pretty big commit! It adds stuff I've been working on
over the last month or so. DO NOT MERGE IT WITH 4.07!
Interface file formats have changed a little; you'll need
to make clean before remaking.
Simon PJ
Recompilation checking
~~~~~~~~~~~~~~~~~~~~~~
Substantial improvement in recompilation checking. The version management
is now entirely internal to GHC. ghc-iface.lprl is dead!
The trick is to generate the new interface file in two steps:
- first convert Types etc to HsTypes etc, and thereby
build a new ParsedIface
- then compare against the parsed (but not renamed) version of the old
interface file
Doing this meant adding code to convert *to* HsSyn things, and to
compare HsSyn things for equality. That is the main tedious bit.
Another improvement is that we now track version info for
fixities and rules, which was missing before.
Interface file reading
~~~~~~~~~~~~~~~~~~~~~~
Make interface files reading more robust.
* If the old interface file is unreadable, don't fail. [bug fix]
* If the old interface file mentions interfaces
that are unreadable, don't fail. [bug fix]
* When we can't find the interface file,
print the directories we are looking in. [feature]
Type signatures
~~~~~~~~~~~~~~~
* New flag -ddump-types to print type signatures
Type pruning
~~~~~~~~~~~~
When importing
data T = T1 A | T2 B | T3 C
it seems excessive to import the types A, B, C as well, unless
the constructors T1, T2 etc are used. A,B,C might be more types,
and importing them may mean reading more interfaces, and so on.
So the idea is that the renamer will just import the decl
data T
unless one of the constructors is used. This turns out to be quite
easy to implement. The downside is that we must make sure the
constructors are always available if they are really needed, so
I regard this as an experimental feature.
Elimininate ThinAir names
~~~~~~~~~~~~~~~~~~~~~~~~~
Eliminate ThinAir.lhs and all its works. It was always a hack, and now
the desugarer carries around an environment I think we can nuke ThinAir
altogether.
As part of this, I had to move all the Prelude RdrName defns from PrelInfo
to PrelMods --- so I renamed PrelMods as PrelNames.
I also had to move the builtinRules so that they are injected by the renamer
(rather than appearing out of the blue in SimplCore). This is if anything simpler.
Miscellaneous
~~~~~~~~~~~~~
* Tidy up the data types involved in Rules
* Eliminate RnEnv.better_provenance; use Name.hasBetterProv instead
* Add Unique.hasKey :: Uniquable a => a -> Unique -> Bool
It's useful in a lot of places
* Fix a bug in interface file parsing for __U[!]
|
|
|
|
|
| |
Use the slightly more standard non-standard module ST instead of the
completely non-standard MutableArray.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Main things:
* Add splitProductType_maybe to DataCon.lhs, with type
splitProductType_maybe
:: Type -- A product type, perhaps
-> Maybe (TyCon, -- The type constructor
[Type], -- Type args of the tycon
DataCon, -- The data constructor
[Type]) -- Its *representation* arg types
Then use it in many places (e.g. worker-wrapper places) instead
of a pile of junk
* Clean up various uses of dataConArgTys, which were plain wrong because
they weren't passed the existential type arguments. Most of these calls
are eliminated by using splitProductType_maybe above. I hope I correctly
squashed the others. This fixes a bug that Meurig's programs showed up.
module FailGHC (killSustainer) where
import Weak
import IOExts
data Sustainer = forall a . Sustainer (IORef (Maybe a)) (IO ())
killSustainer :: Sustainer -> IO ()
killSustainer (Sustainer _ act) = act
The above program used to kill the compiler.
* A fairly concerted attack on the Dreaded Space Leak.
- Add Type.seqType, CoreSyn.seqExpr, CoreSyn.seqRules
- Add some seq'ing when building Ids and IdInfos
These reduce the space usage a lot
- Add CoreSyn.coreBindsSize, which is pretty strict in the program,
and call it when we have -dshow-passes.
- Do not put the inlining in an Id that is being plugged into
the result-expression of the simplifier. This cures
a the 'wedge' in the space profile for reasons I don't understand fully
Together, these things reduce the max space usage when compiling PrelNum from
17M to about 7Mbytes.
I think there are now *too many* seqs, and they waste work, but I don't have
time to find which ones.
Furthermore, we aren't done. For some reason, some of the stuff allocated by
the simplifier makes it through all during code generation and I don't see why.
There's a should-be-unnecessary call to coreBindsSize in Main.main which
zaps some, but not all of this space.
-dshow-passes reduces space usage a bit, but I don't think it should really.
All the measurements were made on a compiler compiled with profiling by
GHC 3.03. I hope they carry over to other builds!
* One trivial thing: changed all variables 'label' to 'lbl', becuase the
former is a keyword with -fglagow-exts in GHC 3.03 (which I was compiling with).
Something similar in StringBuffer.
|
|
|
|
|
|
|
|
| |
- Fixes for bootstrapping with 3.01.
- Use 'official' extension interfaces rather than internal prelude
modules (such as ArrBase) where possible.
- Remove some cruft.
- Delete some unused imports found by '-fwarn-unused-imports'.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Misc changes to compile with new defns of ST, IO (and PrimIO)
|
|
|
|
| |
Removed use of COMPILING_GHC
|
|
|
|
| |
Replaced (old'ish) list-based code with ST and Array based one
|
|
|
|
| |
SLPJ 1.3 changes through 96/06/25
|
|
|
|
| |
simonpj/sansom/partain/dnt 1.3 compiler stuff through 96/03/18
|
|
Initial revision
|