summaryrefslogtreecommitdiff
path: root/ghc/compiler/cprAnalysis
Commit message (Collapse)AuthorAgeFilesLines
* [project @ 2001-07-23 10:54:46 by simonpj]simonpj2001-07-231-0/+6
| | | | | | | | | | | | | | | | | | --------------------------------- 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.
* [project @ 2001-06-25 14:36:04 by simonpj]simonpj2001-06-251-5/+1
| | | | Import wibbles
* [project @ 2000-12-08 12:13:13 by simonpj]simonpj2000-12-081-1/+4
| | | | | | | | | Correct CPR information. How it ever worked I don't know. * The CPR info on a newtype constructor should be NoCPR, whereas before it was ReturnsCPR! * Minor: don't change CPR info on implicit Ids
* [project @ 2000-12-06 13:03:28 by simonmar]simonmar2000-12-061-2/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* [project @ 2000-11-10 15:12:50 by simonpj]simonpj2000-11-101-2/+2
| | | | | | | | | | | | | | 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
* [project @ 2000-10-19 10:06:46 by sewardj]sewardj2000-10-191-7/+6
| | | | Fix simplifier stuff.
* [project @ 2000-09-14 13:46:39 by simonpj]simonpj2000-09-141-51/+37
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | --------------------------------------- Simon's tuning changes: early Sept 2000 --------------------------------------- Library changes ~~~~~~~~~~~~~~~ * Eta expand PrelShow.showLitChar. It's impossible to compile this well, and it makes a big difference to some programs (e.g. gen_regexps) * Make PrelList.concat into a good producer (in the foldr/build sense) Flag changes ~~~~~~~~~~~~ * Add -ddump-hi-diffs to print out changes in interface files. Useful when watching what the compiler is doing * Add -funfolding-update-in-place to enable the experimental optimisation that makes the inliner a bit keener to inline if it's in the RHS of a thunk that might be updated in place. Sometimes this is a bad idea (one example is in spectral/sphere; see notes in nofib/Simon-nofib-notes) Tuning things ~~~~~~~~~~~~~ * Fix a bug in SetLevels.lvlMFE. (change ctxt_lvl to dest_level) I don't think this has any performance effect, but it saves making a redundant let-binding that is later eliminated. * Desugar.dsProgram and DsForeign Glom together all the bindings into a single Rec. Previously the bindings generated by 'foreign' declarations were not glommed together, but this led to an infelicity (i.e. poorer code than necessary) in the modules that actually declare Float and Double (explained a bit more in Desugar.dsProgram) * OccurAnal.shortMeOut and IdInfo.shortableIdInfo Don't do the occurrence analyser's shorting out stuff for things which have rules. Comments near IdInfo.shortableIdInfo. This is deeply boring, and mainly to do with making rules work well. Maybe rules should have phases attached too.... * CprAnalyse.addIdCprInfo Be a bit more willing to add CPR information to thunks; in particular, if the strictness analyser has just discovered that this is a strict let, then the let-to-case transform will happen, and CPR is fine. This made a big difference to PrelBase.modInt, which had something like modInt = \ x -> let r = ... -> I# v in ...body strict in r... r's RHS isn't a value yet; but modInt returns r in various branches, so if r doesn't have the CPR property then neither does modInt * MkId.mkDataConWrapId Arrange that vanilla constructors, like (:) and I#, get unfoldings that are just a simple variable $w:, $wI#. This ensures they'll be inlined even into rules etc, which makes matching a bit more reliable. The downside is that in situations like (map (:) xs), we'll end up with (map (\y ys. $w: y ys) xs. Which is tiresome but it doesn't happen much. * SaAbsInt.findStrictness Deal with the case where a thing with no arguments is bottom. This is Good. E.g. module M where { foo = error "help" } Suppose we have in another module case M.foo of ... Then we'd like to do the case-of-error transform, without inlining foo. Tidying up things ~~~~~~~~~~~~~~~~~ * Reorganised Simplify.completeBinding (again). * Removed the is_bot field in CoreUnfolding (is_cheap is true if is_bot is!) This is just a tidy up * HsDecls and others Remove the NewCon constructor from ConDecl. It just added code, and nothing else. And it led to a bug in MkIface, which though that a newtype decl was always changing! * IdInfo and many others Remove all vestiges of UpdateInfo (hasn't been used for years)
* [project @ 2000-07-11 16:04:38 by simonmar]simonmar2000-07-111-8/+1
| | | | remove unused imports
* [project @ 2000-03-23 17:45:17 by simonpj]simonpj2000-03-231-222/+94
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* [project @ 1999-10-18 11:44:20 by kglynn]kglynn1999-10-181-1/+8
| | | | | | | | | | | The fix to ignore error() cases when doing CPR analysis exposed a problem with the Void type. A function that always constructs a void result was converted to w/w, but the worker was producing an unboxed tuple with 0 components. Not good. Fixed so that constructing a void gives CPR value Top. This is OK because we won't really be constructing a void each time, we will be returning a pointer to a shared void cell.
* [project @ 1999-10-13 09:25:59 by simonmar]simonmar1999-10-131-1/+1
| | | | Don't use variables beginning with underscore, 3.02 doesn't grok them.
* [project @ 1999-10-05 09:04:30 by kglynn]kglynn1999-10-051-109/+157
| | | | | | | | | | | | | | | | | | (keving) Much simplified and beautified CPR analysis code. (And also much shorter, we'd better write this up before it disappears). Added (constant) functions to the abstract domain. Note that Fun^n Bot (n >= 1) == Bot and likewise for Top Treats divergent computations as Bot (rather than Top as previous) so non-divergent paths dominate which allows us to generate more accurate CPR info (see e.g. chr). We use the result of strictness analysis to tell us if an Id is divergent (when applied to sufficient args), therefore we should run after the strictness analysis pass.
* [project @ 1999-07-15 14:08:03 by keithw]keithw1999-07-151-2/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit makes a start at implementing polymorphic usage annotations. * The module Type has now been split into TypeRep, containing the representation Type(..) and other information for `friends' only, and Type, providing the public interface to Type. Due to a bug in the interface-file slurping prior to ghc-4.04, {-# SOURCE #-} dependencies must unfortunately still refer to TypeRep even though they are not friends. * Unfoldings in interface files now print as __U instead of __u. UpdateInfo now prints as __UA instead of __U. * A new sort of variables, UVar, in their own namespace, uvName, has been introduced for usage variables. * Usage binders __fuall uv have been introduced. Usage annotations are now __u - ty (used once), __u ! ty (used possibly many times), __u uv ty (used uv times), where uv is a UVar. __o and __m have gone. All this still lives only in a TyNote, *for now* (but not for much longer). * Variance calculation for TyCons has moved from typecheck/TcTyClsDecls to types/Variance. * Usage annotation and inference are now done together in a single pass. Provision has been made for inferring polymorphic usage annotations (with __fuall) but this has not yet been implemented. Watch this space!
* [project @ 1999-07-14 22:10:40 by simonpj]simonpj1999-07-141-2/+3
| | | | | | | | | | | | | | | | | | [Simon: this should fix that -funfolding-use-threshold0 lint bug] [Kevin: have a look at WwLib.mkWwBodies. Isn't it a thing of beauty? Could you think about whether the CPR stuff could be cleaned up a bit? The strictness stuff is much shorter.] This commit tidies up WwLib.mkWwBodies, fixing a couple of bugs. * One bug showed up when CPR made a worker return an unboxed tuple, but the worker didn't have any other arguments. The "add a void arg" hack needed to be generalised a bit. * The other bug showed up when booting the compiler. There's a long comment near splitProductType in WwLib.lhs that explains the problem.
* [project @ 1999-07-14 14:40:20 by simonpj]simonpj1999-07-141-36/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* [project @ 1999-07-14 13:35:49 by sewardj]sewardj1999-07-141-4/+4
| | | | | Changed vars of the form _unused to zz_unused, since 3.02 doesn't understand this convention.
* [project @ 1999-06-29 06:26:37 by kglynn]kglynn1999-06-291-119/+190
| | | | | | CPR Analysis Mark 2. Slightly more elegant, and (I believe) now copes correctly with references to CAFS and non-top level function bindings.
* [project @ 1999-04-13 06:57:28 by kglynn]kglynn1999-04-131-0/+348
(keving) The CPR Analysis Pass Module