| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Now Char, Char#, StgChar have 31 bits (physically 32).
"foo"# is still an array of bytes.
CharRep represents 32 bits (on a 64-bit arch too). There is also
Int8Rep, used in those places where bytes were originally meant.
readCharArray, indexCharOffAddr etc. still use bytes. Storable and
{I,M}Array use wide Chars.
In future perhaps all sized integers should be primitive types. Then
some usages of indexing primops scattered through the code could
be changed to then-available Int8 ones, and then Char variants of
primops could be made wide (other usages that handle text should use
conversion that will be provided later).
I/O and _ccall_ arguments assume ISO-8859-1. UTF-8 is internally used
for string literals (only).
Z-encoding is ready for Unicode identifiers.
Ranges of intlike and charlike closures are more easily configurable.
I've probably broken nativeGen/MachCode.lhs:chrCode for Alpha but I
don't know the Alpha assembler to fix it (what is zapnot?). Generally
I'm not sure if I've done the NCG changes right.
This commit breaks the binary compatibility (of course).
TODO:
* is* and to{Lower,Upper} in Char (in progress).
* Libraries for text conversion (in design / experiments),
to be plugged to I/O and a higher level foreign library.
* PackedString.
* StringBuffer and accepting source in encodings other than ISO-8859-1.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Many fixes to DLLisation. These were previously covered up because code was
leaking into the import libraries for DLLs, so the fact that some symbols
were thought of as local rather than in another DLL wasn't a problem.
The main problems addressed by this commit are:
1. Fixes RTS symbols working properly when DLLised. They didn't before.
2. Uses NULL instead of stg_error_entry, because DLL entry points can't be
used as static initialisers.
3. PrelGHC.hi-boot changed to be in package RTS, and export of PrelNum and
PrelErr moved to PrelBase, so that references to primops & the like
are cross-DLL as they should be.
4. Pass imports around as Modules rather than ModuleNames, so that
ModuleInitLabels can be checked to see if they're in a DLL or not.
|
|
|
|
|
|
| |
Panic if we try to allocate more than a block's worth of memory in one
go. No fix yet, but at least this is better than going into an
infinite loop at runtime.
|
|
|
|
| |
Remove dead code
|
|
|
|
| |
remove unused imports; misc cleanup
|
|
|
|
|
|
|
|
|
|
| |
New form of literal: MachLabel, for addresses of labels. Used by
foreign label instead of MachLitLit now.
Real lit-lits now cause the NCG to panic.
Also: removed CLitLit from AbsCSyn; it was only used in one place for
a purpose it shouldn't have been used for in the first place.
|
|
|
|
|
|
|
|
|
|
| |
Make object file splitting simpler, in preparation for conversion to
the new driver.
The "inject split markers" phase is now omitted, instead we generate
the split markers directly.
Driver: also removed now-defunct -fpedantic-bottoms flag.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
~~~~~~~~~~~~
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[!]
|
|
|
|
|
|
| |
GHC has instance amnesia again, so a bunch of funny
`import Ppr{Core,Type} ()? had to be added. Sorry,
but I need a bootstrapping GHC.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for 'packages'.
* A package is a group of modules.
* A package has a name (e.g. std)
* A package is built into a single library (Unix; e.g. libHSstd.a)
or a single DLL (Windows; e.g. HSstd.dll)
* The '-package-name foo' flag tells GHC that the module being compiled
is destined for package foo.
* The '-package foo' flag tells GHC to make available modules
from package 'foo'. It replaces '-syslib foo' which is now deprecated.
* Cross-package references cost an extra indirection in Windows,
but not Unix
* GHC does not maintain detailed cross-package dependency information.
It does remember which modules in other packages the current module
depends on, but not which things within those imported things.
All of this tidies up the Prelude enormously. The Prelude and
Standard Libraries are built into a singl package called 'std'. (This
is a change; the library is now called libHSstd.a instead of libHS.a)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Add new flag -fddump-minimal-imports, which dumps a file
M.imports that contains the (allegedly) minimal bunch of
imports that make the system work.
It's done by Rename.printMinimalImports
* Extend foreign import/export to handle
* Booleans
* newtypes
as requested by the FFI team
* Tidy up DsCCall quite a bit
Remove maybeBoxedPrimTy from TcHsSyn
|
|
|
|
|
| |
Use the decoded string, not the z-encoded string, for the closure
description.
|
|
|
|
| |
generate the correct closureTypeDescr for an LFCon.
|
|
|
|
|
|
| |
Fix a bug in import listing in interface files that meant we lost track of
interface files. This fixes the problem that led Sven to add lots of
import PprType() decls. I've removed them all again!
|
|
|
|
|
|
|
|
| |
Adding a bunch of `import PprType ()' to make 4.07 compile itself.
Strangely enough, compilation with 4.06 worked without these, so
this is probably only fighting the symptoms of something deeper,
and somebody should have a look at it. But for now, I simply need
a bootstrapping 4.07...
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
| |
Clean up the module initialisation stuff a bit, and add support for
module initialisation blocks in the native code generator.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- 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.
|
|
|
|
|
|
|
| |
ARR_HDR_SIZE --> ARR_WORDS_HDR_SIZE, and derived quantities in
Constants.h, Constants.lhs et al are similarly renamed.
new constant ARR_PTRS_HDR_SIZE, with corresponding derivatives.
|
|
|
|
| |
Bugfix (raiseError in non-enterable closures); added GranSim code to Schedule.c
|
|
|
|
|
| |
Merged GUM-4-04 branch into the main trunk. In particular merged GUM and
SMP code. Most of the GranSim code in GUM-4-04 still has to be carried over.
|
|
|
|
| |
Report slow-entry counts in ticky-ticky
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit adds in the current state of our SMP support. Notably,
this allows the new way 's' to be built, providing support for running
multiple Haskell threads simultaneously on top of any pthreads
implementation, the idea being to take advantage of commodity SMP
boxes.
Don't expect to get much of a speedup yet; due to the excessive
locking required to synchronise access to mutable heap objects, you'll
see a slowdown in most cases, even on a UP machine. The best I've
seen is a 1.6-1.7 speedup on an example that did no locking (two
optimised nfibs in parallel).
- new RTS -N flag specifies how many pthreads to start.
- new driver -smp flag, tells the driver to use way 's'.
- new compiler -fsmp option (not for user comsumption)
tells the compiler not to generate direct jumps to
thunk entry code.
- largely rewritten scheduler
- _ccall_GC is now done by handing back a "token" to the
RTS before executing the ccall; it should now be possible
to execute blocking ccalls in the current thread while
allowing the RTS to continue running Haskell threads as
normal.
- you can only call thread-safe C libraries from a way 's'
build, of course.
Pthread support is still incomplete, and weird things (including
deadlocks) are likely to happen.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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_.
|
|
|
|
|
|
|
| |
Crude allocation-counting extension to ticky-ticky profiling.
Allocations are counted against the closest lexically enclosing
function closure, so you need to map the output back to the STG code.
|
|
|
|
|
|
|
|
| |
A couple of fixes and cleanups to ticky-ticky profiling:
- remove UPD_EXISTING (doesn't make sense)
- add UPD_CON_IN_PLACE, now that we have in-place updates
- clean up the output a little.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Update to match CgUsages.hi-boot-5
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Add Type.repType
* Re-express splitRepTyConApp_maybe using repType
* Use the new repType in Core2Stg
The bug was that we ended up with a binding like
let x = /\a -> 3# +# y
in ...
and this should turn into an STG case, but the big lambda
fooled the core-to-STG pass
|
|
|
|
|
| |
Jump to the join point when returning a new constructor to a bind
default. Fixes: recent panic in mkStaticAlgReturnCode.
|
|
|
|
|
|
| |
- Implement update-in-place in certain very specialised circumstances
- Clean up abstract C a bit
- Speed up pretty-printing absC a bit.
|
|
|
|
| |
Many small tuning changes
|
|
|
|
|
| |
Move some code around to reduce the linkage between CgMonad and CgBindery,
and make the .hi-boot-5 file compatible with both 4.02 and 4.03.
|
|
|
|
| |
Remove debugging trace that sneaked in.
|
|
|
|
|
| |
Use ClosureInfo.hi-boot instead of ClosureInfo.hi (which might not be
built yet).
|
|
|
|
| |
Update the comment for buildLivenessMask to match reality.
|
|
|
|
|
|
|
| |
Allow reserving of stack slots for non-pointer data (eg. cost
centres). This means the previous hacks to keep the stack bitmaps
correct in the presence of cost centres are now unnecessary, and
case-of-case expressions will be compiled properly with profiling on.
|
|
|
|
| |
Existential constructors NEVER WORKED! You were JUST IMAGINING IT!
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Several bugfixes (from SLPJ's tree).
|
|
|
|
| |
RULES-NOTES
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Support for "unregisterised" builds. An unregisterised build doesn't
use the assembly mangler, doesn't do tail jumping (uses the
mini-interpreter), and doesn't use global register variables.
Plenty of cleanups and bugfixes in the process.
Add way 'u' to GhcLibWays to get unregisterised libs & RTS.
[ note: not *quite* working fully yet... there's still a bug or two
lurking ]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
(this is number 7 of 9 commits to be applied together)
The code generator now incorporates the update avoidance
optimisation: a thunk of __o type is now made SingleEntry rather
than Updatable.
We want to verify that SingleEntry thunks are indeed entered at most
once. In order to do this, -ticky turns on eager blackholing.
Ordinary thunks will be dealt with by the RTS, but CAFs are
blackholed by the code generator. We blackhole with new blackholes:
SE_CAF_BLACKHOLE. We will enter one of these if we attempt to enter
a SingleEntry thunk twice.
|
|
|
|
|
|
| |
Fix bug in tagToEnum#: if the amode of the tag overlapped with node,
bogus code would be generated. Now load the tag into a temporary
before doing the table lookup.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- 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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- New Wired-in Id: getTag# :: a -> Int#
for a data type, returns the tag of the constructor.
for a function, returns a spurious number probably.
dataToTag# is the name of the underlying primitive which
pulls out the tag (its argument is assumed to be
evaluated).
- Generate constructor tables for enumerated types, so we
can do tagToEnum#.
- Remove hacks in CoreToStg for dataToTag#.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Support for
dataToTag# :: a -> Int# (if a is a data type)
and (partial) support for
tagToEnum# :: Int# -> a (if a is an enumerated type)
The con2tag functions generated by derived Eq,Ord and Enum instances
are now replaced by dataToTag# for data types with a large number of
constructors.
|
|
|
|
|
| |
Remove hack to force setting the CCCS when we enter a function closure
defined inside a lambda. We use a more general solution now.
|
|
|
|
|
|
|
|
|
|
|
|
| |
Profiling fixes:
Function closures which are inside a lambda now *set* the CCCS,
instead of possibly appending to it.
In Simplify.lhs: allow inlining imported functions when profiling.
What we really want to do is allow any top-level binding to be
inlined, but there doesn't seem to be an easy way to tell whether a
binding is top-level or not.
|