|  | 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. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | Relax the restrictions on conflicting packages.  This should address
many of the traps that people have been falling into with the current
package story.
Now, a local module can shadow a module in an exposed package, as long
as the package is not otherwise required by the program.  GHC checks
for conflicts when it knows the dependencies of the module being
compiled.
Also, we now check for module conflicts in exposed packages only when
importing a module: if an import can be satisfied from multiple
packages, that's an error.  It's not possible to prevent GHC from
starting by installing packages now (unless you install another base
package).
It seems to be possible to confuse GHCi by having a local module
shadowing a package module that goes away and comes back again.  I
think it's nearly right, but strange happenings have been observed.
I'll try to merge this into the STABLE branch. | 
| | 
| 
| 
| 
| 
| 
| | Tweaks to get the GHC sources through Haddock.  Doesn't quite work
yet, because Haddock complains about the recursive modules.  Haddock
needs to understand SOURCE imports (it can probably just ignore them
as a first attempt). | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | Further integration with the new package story.  GHC now supports
pretty much everything in the package proposal.
  - GHC now works in terms of PackageIds (<pkg>-<version>) rather than
    just package names.  You can still specify package names without
    versions on the command line, as long as the name is unambiguous.
  - GHC understands hidden/exposed modules in a package, and will refuse
    to import a hidden module.  Also, the hidden/eposed status of packages
    is taken into account.
  - I had to remove the old package syntax from ghc-pkg, backwards
    compatibility isn't really practical.
  - All the package.conf.in files have been rewritten in the new syntax,
    and contain a complete list of modules in the package.  I've set all
    the versions to 1.0 for now - please check your package(s) and fix the
    version number & other info appropriately.
  - New options:
	-hide-package P    sets the expose flag on package P to False
	-ignore-package P  unregisters P for this compilation
	For comparison, -package P sets the expose flag on package P
        to True, and also causes P to be linked in eagerly.
        -package-name is no longer officially supported.  Unofficially, it's
	a synonym for -ignore-package, which has more or less the same effect
	as -package-name used to.
	Note that a package may be hidden and yet still be linked into
	the program, by virtue of being a dependency of some other package.
	To completely remove a package from the compiler's internal database,
        use -ignore-package.
	The compiler will complain if any two packages in the
        transitive closure of exposed packages contain the same
        module.
	You *must* use -ignore-package P when compiling modules for
        package P, if package P (or an older version of P) is already
        registered.  The compiler will helpfully complain if you don't.
	The fptools build system does this.
   - Note: the Cabal library won't work yet.  It still thinks GHC uses
     the old package config syntax.
Internal changes/cleanups:
   - The ModuleName type has gone away.  Modules are now just (a
     newtype of) FastStrings, and don't contain any package information.
     All the package-related knowledge is in DynFlags, which is passed
     down to where it is needed.
   - DynFlags manipulation has been cleaned up somewhat: there are no
     global variables holding DynFlags any more, instead the DynFlags
     are passed around properly.
   - There are a few less global variables in GHC.  Lots more are
     scheduled for removal.
   - -i is now a dynamic flag, as are all the package-related flags (but
     using them in {-# OPTIONS #-} is Officially Not Recommended).
   - make -j now appears to work under fptools/libraries/.  Probably
     wouldn't take much to get it working for a whole build. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | -------------------------------
	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. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | ------------------------
       Tidy up the code generator
	------------------------
The code generation for 'case' expressions had grown
huge and gnarly.  This commit removes about 120 lines of
code, and makes it a lot easier to read too. I think the code
generated is identical.
Part of this was to simplify the StgCase data type, so
that it is more like the Core case: there is a simple list
of alternatives, and the DEFAULT (if present) must be the
first.  This tidies and simplifies other Stg passes. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | Change the way SRTs are represented:
Previously, the SRT associated with a function or thunk would be a
sub-list of the enclosing top-level function's SRT.  But this approach
can lead to lots of duplication: if a CAF is referenced in several
different thunks, then it may appear several times in the SRT.
Let-no-escapes compound the problem, because the occurrence of a
let-no-escape-bound variable would expand to all the CAFs referred to
by the let-no-escape.
The new way is to describe the SRT associated with a function or thunk
as a (pointer+offset,bitmap) pair, where the pointer+offset points
into some SRT table (the enclosing function's SRT), and the bitmap
indicates which entries in this table are "live" for this closure.
The bitmap is stored in the 16 bits previously used for the length
field, but this rarely overflows.  When it does overflow, we store the
bitmap externally in a new "SRT descriptor".
Now the enclosing SRT can be a set, hence eliminating the duplicates.
Also, we now have one SRT per top-level function in a recursive group,
where previously we used to have one SRT for the whole group.  This
helps keep the size of SRTs down.
Bottom line: very little difference most of the time.  GHC itself got
slightly smaller.  One bad case of a module in GHC which had a huge
SRT has gone away.
While I was in the area:
  - Several parts of the back-end require bitmaps.  Functions for
    creating bitmaps are now centralised in the Bitmap module.
  - We were trying to be independent of word-size in a couple of
    places in the back end, but we've now abandoned that strategy so I
    simplified things a bit. | 
| | 
| 
| 
| 
| | minor tidyup - move CollectedCCs tysyn to CostCentre (from SCCFinal), and
make use of it where that cost-centre info triple is being passed&returned. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | - 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. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | -------------------------------------------
	Towards generalising 'foreign' declarations
	-------------------------------------------
This is a first step towards generalising 'foreign' declarations to
handle langauges other than C.  Quite a lot of files are touched,
but nothing has really changed.  Everything should work exactly as
before.
	But please be on your guard for ccall-related bugs.
Main things
Basic data types: ForeignCall.lhs
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Remove absCSyn/CallConv.lhs
* Add prelude/ForeignCall.lhs.  This defines the ForeignCall
  type and its variants
* Define ForeignCall.Safety to say whether a call is unsafe
  or not (was just a boolean).  Lots of consequential chuffing.
* Remove all CCall stuff from PrimOp, and put it in ForeignCall
Take CCallOp out of the PrimOp type (where it was always a glitch)
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Add IdInfo.FCallId variant to the type IdInfo.GlobalIdDetails,
	along with predicates Id.isFCallId, Id.isFCallId_maybe
* Add StgSyn.StgOp, to sum PrimOp with FCallOp, because it
  *is* useful to sum them together in Stg and AbsC land.  If
  nothing else, it minimises changes.
Also generally rename "CCall" stuff to "FCall" where it's generic
to all foreign calls. | 
| | 
| 
| 
| 
| | Re-instate filtering of the CAF refs for recursive bindings.  This may
be the cause of GC being real slow on a bootstrapped compiler right now. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | Some rearrangements that Simon & I have been working on recently:
    - CoreSat is now CorePrep, and is a general "prepare-for-code-
      generation" pass.  It does cloning, saturation of constructors &
      primops, A-normal form, and a couple of other minor fiddlings.
    - CoreTidy no longer does cloning, and minor fiddlings.  It doesn't
      need the unique supply any more, so that's removed.
    - CoreToStg now collects CafInfo and the list of CafRefs for each
      binding.  The SRT pass is much simpler now.
    - IdInfo now has a CgInfo field for "code generator info".  It currently
      contains arity (the actual code gen arity which affects the calling
      convention as opposed to the ArityInfo which is a measure of how
      many arguments the Id can be applied to before it does any work), and
      CafInfo.
      Previously we overloaded the ArityInfo field to contain both
      codegen arity and simplifier arity.  Things are cleaner now.
    - CgInfo is collected by CoreToStg, and passed back into CoreTidy in
      a loop.  The compiler will complain rather than going into a black
      hole if the CgInfo is pulled on too early.
    - Worker info in an interface file now comes with arity info attached.
      Previously the main arity info was overloaded for this purpose, but
      it lead to a few hacks in the compiler, this tidies things up somewhat.
Bottom line: we removed several fragilities, and tidied up a number of
things.  Code size should be smaller, but we'll see... | 
| | 
| 
| 
| | use `mayHaveCafRefs'. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| | Figure out CafInfo during CoreTidy.  This is the final piece of the
puzzle in getting the final IdInfo from the Core2Core phases, rather
than waiting for the STG code.
This simplifies the SRT phase, in that it no longer has to have a
complicated circular algorithm to figure out the CafInfo at the same
time as the SRT layout. | 
| | 
| 
| 
| | import wibble | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| | merge recent changes from before-ghci-branch onto the HEAD | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 1. Make the new version machinery work.
   I think it does now!
2. Consequence of (1): Move the generation of
   default method names to one place (namely
   in RdrHsSyn.mkClassOpSigDM
3. Major clean up on HsDecls.TyClDecl
   These big constructors should have been records
   ages ago, and they are now.  At last. | 
| | 
| 
| 
| | Unused imports and suchlike | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | Version management
[WARNING: may not work!  Don't update till I've tested it.]
This commit is a first stab at getting version management to
work properly.  The main trick is to get consistent naming when
comparing old and new versions of the same module.  
Some functionality has moved arond between
  coreSyn/CoreTidy, which tidies up the result of
			the middle end of the compiler
	Main change: now responsible for figuring out which
	Ids are "external" (i.e visible to importing modules),
	and constructing the final IdInfo for each Id
  main/MkIface, which produces the ModIface and ModDetails
		for the module being compiled
	Main change: CoreTidy does more, so MkIface does less
  stgSyn/CoreToStg, which converts Core to STG
	Main change: responsible for globalising internal
	names when we are doing object code splitting 
			
The game plan is documented at the top of CoreTidy. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | The main thing in this commit is to change StgAlts so that
it carries a TyCon, and not a Type.  Furthermore, the TyCon
is derived from the alternatives, so it should have its
constructors etc, even if there's a module loop involved, so that
some versions of the TyCon don't have the constructors visible.
There's a comment in StgSyn.lhs, with the type decl for StgAlts
Also: a start on hscExpr in HscMain. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| | Changing the way we know whether
something is exported.
THIS COMMIT WON'T EVEN COMPILE
(I'm doing it to transfer from my laptop.)
Wait till later today before updating. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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 | 
| | 
| 
| 
| | Dealing with instance-decl imports; and removing unnecessary imports | 
| | 
| 
| 
| | Make HscMain compile.  Hurrah! | 
| | 
| 
| 
| | Make the back-end world compile. | 
| | 
| 
| 
| | remove unused imports | 
| | 
| 
| 
| | dumps go to stdout now | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | *** MERGE WITH 4.07 (once I've checked it works) ***
* Fix result type signatures.  Note that a consequential change is that
  an ordinary binding with a variable on the left
	f = e
  is now treated as a FunMonoBind, not a PatMonoBind.  This makes
  a few things a bit simpler (eg rnMethodBinds)
* Fix warnings for unused imports.  This meant moving where provenances
  are improved in RnNames.  Move mkExportAvails from RnEnv to RnNames.
* Print module names right (small change in Module.lhs and Rename.lhs)
* Remove a few unused bindings
  
* Add a little hack to let us print info about join points that turn
  out not to be let-no-escaped.  The idea is to call them "$j" and report
  any such variables that are not let-no-escaped.
* Some small things aiming towards -ddump-types (harmless but incomplete) | 
| | 
| 
| 
| | Finally retire the update analyser. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | - generalise the per-module initialisation stubs so that we use it
  in normal (non-profiled) code too.  The initialisation stubs are
  now called '__init_<module>' rather than '_reg<module>'.
- Register foreign exported functions as stable pointers in the
  initialisation code for the module.  This fixes the foreign export
  problems reported by several people.
- remove the concept of "module groups" from the profiling subsystem.
- change the profiling semantics slightly; it should be unnecessary
  to use '-caf-all' to get reasonable profiles now. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| 
| 
| 
| | FFI wibble:
* disallow the use of {Mutable}ByteArrays in 'safe' foreign imports.
* ensure that ForeignObjs live across a _ccall_GC_. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| | Minor cleanup | 
| | 
| 
| 
| | "oops" | 
| | 
| 
| 
| | Fixes for case-of-case and let-no-escape. | 
| | 
| 
| 
| | RULES-NOTES | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | - Fix the tagToEnum# support in the code generator
- Make isDeadBinder work on case binders
- Fix compiling of
	case x `op` y of z {
		True  -> ... z ...
		False -> ... z ...
- Clean up CgCase a little.
- Don't generate specialised tag2con functions for derived Enum/Ix
  instances; use tagToEnum# instead. | 
| | 
| 
| 
| | PAPs are ReEntrant, not SingleEntry. | 
| | 
| 
| 
| 
| 
| | s/show/showSDoc/
Discovered-by: removing instance Show (->) :-) | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | - import list tweaks
- moved the code that decides that a StgCon really shouldn't
  be mapped to a static constructor but an updateable thunk
  if it contains lit-lits from the codegen into the CoreToStg
  translation.
  Added an extra case to this code to deal with StgCon's that contain
  references to values that reside in a DLL, where we also have to
  opt for an updateable thunk instead of a static constructor. Only
  applies when compiling on/for Win32 platforms. | 
| | 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| 
| | 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. | 
| | 
| 
| 
| | More import list updates | 
| | 
| 
| 
| | Import lists updated | 
| | 
| 
| 
| | Reorganisation of Id, IdInfo.  Remove StdIdInfo, PragmaInfo; add basicTypes/MkId.lhs | 
| | 
| 
| 
| | change a few datatypes to newtypes. |