- 16 Jan, 2008 1 commit
-
-
simonpj@microsoft.com authored
I can't remember where this bug showed up, but we were abstracting over a coercion variable (co :: a ~ T), without also abstracting over 'a'. The fix is simple.
-
- 07 Jan, 2008 1 commit
-
-
simonpj@microsoft.com authored
The float-out transformation must handle the case where a coercion variable is free, which in turn mentions type variables in its kind. Just like a term variable really. I did a bit of refactoring at the same time. Test is tc241 MERGE to stable branch
-
- 12 Nov, 2007 1 commit
-
-
simonpj@microsoft.com authored
-
- 04 Sep, 2007 1 commit
-
-
Ian Lynagh authored
-
- 03 Sep, 2007 1 commit
-
-
Ian Lynagh authored
Older GHCs can't parse OPTIONS_GHC. This also changes the URL referenced for the -w options from WorkingConventions#Warnings to CodingStyle#Warnings for the compiler modules.
-
- 01 Sep, 2007 1 commit
-
-
Ian Lynagh authored
-
- 05 Jun, 2007 1 commit
-
-
simonpj@microsoft.com authored
-
- 09 May, 2007 1 commit
-
-
simonpj@microsoft.com authored
This patch simplifies the code slightly, and simultaneously improves full laziness by floating allocations (lambdas, constructor apps) out of loops. See Note [Escaping a value lambda] in SetLevels, which explains. There's a test that shows it up: simplrun009 This relevant to SpecConstr, because a call looks like f lvl instead of f (\x. blah) and the latter is easier to match in a robust way.
-
- 02 Feb, 2007 1 commit
-
-
simonpj@microsoft.com authored
-
- 03 Jan, 2007 1 commit
-
-
simonpj@microsoft.com authored
Now that coercion variables mention types, a type-lambda binder can have free variables. This patch adjusts the free-variable finder to take account of this, by treating Ids and TyVars more uniformly. In addition, I fixed a bug in the specialiser that was missing a free type variable in a binder. And a bug in tyVarsOfInst that was missing the type variables in the kinds of the quantified tyvars.
-
- 15 Sep, 2006 1 commit
-
-
chak@cse.unsw.edu.au. authored
Fri Aug 4 18:13:20 EDT 2006 Manuel M T Chakravarty <chak@cse.unsw.edu.au> * Massive patch for the first months work adding System FC to GHC #30 Broken up massive patch -=chak Original log message: This is (sadly) all done in one patch to avoid Darcs bugs. It's not complete work... more FC stuff to come. A compiler using just this patch will fail dismally.
-
- 07 Apr, 2006 1 commit
-
-
Simon Marlow authored
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.
-
- 06 Jan, 2006 1 commit
-
-
simonmar authored
Add support for UTF-8 source files GHC finally has support for full Unicode in source files. Source files are now assumed to be UTF-8 encoded, and the full range of Unicode characters can be used, with classifications recognised using the implementation from Data.Char. This incedentally means that only the stage2 compiler will recognise Unicode in source files, because I was too lazy to port the unicode classifier code into libcompat. Additionally, the following synonyms for keywords are now recognised: forall symbol (U+2200) forall right arrow (U+2192) -> left arrow (U+2190) <- horizontal ellipsis (U+22EF) .. there are probably more things we could add here. This will break some source files if Latin-1 characters are being used. In most cases this should result in a UTF-8 decoding error. Later on if we want to support more encodings (perhaps with a pragma to specify the encoding), I plan to do it by recoding into UTF-8 before parsing. Internally, there were some pretty big changes: - FastStrings are now stored in UTF-8 - Z-encoding has been moved right to the back end. Previously we used to Z-encode every identifier on the way in for simplicity, and only decode when we needed to show something to the user. Instead, we now keep every string in its UTF-8 encoding, and Z-encode right before printing it out. To avoid Z-encoding the same string multiple times, the Z-encoding is cached inside the FastString the first time it is requested. This speeds up the compiler - I've measured some definite improvement in parsing at least, and I expect compilations overall to be faster too. It also cleans up a lot of cruft from the OccName interface. Z-encoding is nicely hidden inside the Outputable instance for Names & OccNames now. - StringBuffers are UTF-8 too, and are now represented as ForeignPtrs. - I've put together some test cases, not by any means exhaustive, but there are some interesting UTF-8 decoding error cases that aren't obvious. Also, take a look at unicode001.hs for a demo.
-
- 28 Apr, 2005 1 commit
-
-
simonpj authored
This big commit does several things at once (aeroplane hacking) which change the format of interface files. So you'll need to recompile your libraries! 1. The "stupid theta" of a newtype declaration ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Retain the "stupid theta" in a newtype declaration. For some reason this was being discarded, and putting it back in meant changing TyCon and IfaceSyn slightly. 2. Overlap flags travel with the instance ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Arrange that the ability to support overlap and incoherence is a property of the *instance declaration* rather than the module that imports the instance decl. This allows a library writer to define overlapping instance decls without the library client having to know. The implementation is that in an Instance we store the overlap flag, and preseve that across interface files 3. Nuke the "instnce pool" and "rule pool" ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A major tidy-up and simplification of the way that instances and rules are sucked in from interface files. Up till now an instance decl has been held in a "pool" until its "gates" (a set of Names) are in play, when the instance is typechecked and added to the InstEnv in the ExternalPackageState. This is complicated and error-prone; it's easy to suck in too few (and miss an instance) or too many (and thereby be forced to suck in its type constructors, etc). Now, as we load an instance from an interface files, we put it straight in the InstEnv... but the Instance we put in the InstEnv has some Names (the "rough-match" names) that can be used on lookup to say "this Instance can't match". The detailed dfun is only read lazily, and the rough-match thing meansn it is'nt poked on until it has a chance of being needed. This simply continues the successful idea for Ids, whereby they are loaded straightaway into the TypeEnv, but their TyThing is a lazy thunk, not poked on until the thing is looked up. Just the same idea applies to Rules. On the way, I made CoreRule and Instance into full-blown records with lots of info, with the same kind of key status as TyCon or DataCon or Class. And got rid of IdCoreRule altogether. It's all much more solid and uniform, but it meant touching a *lot* of modules. 4. Allow instance decls in hs-boot files ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Allowing instance decls in hs-boot files is jolly useful, becuase in a big mutually-recursive bunch of data types, you want to give the instances with the data type declarations. To achieve this * The hs-boot file makes a provisional name for the dict-fun, something like $fx9. * When checking the "mother module", we check that the instance declarations line up (by type) and generate bindings for the boot dfuns, such as $fx9 = $f2 where $f2 is the dfun generated by the mother module * In doing this I decided that it's cleaner to have DFunIds get their final External Name at birth. To do that they need a stable OccName, so I have an integer-valued dfun-name-supply in the TcM monad. That keeps it simple. This feature is hardly tested yet. 5. Tidy up tidying, and Iface file generation ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ main/TidyPgm now has two entry points: simpleTidyPgm is for hi-boot files, when typechecking only (not yet implemented), and potentially when compiling without -O. It ignores the bindings, and generates a nice small TypeEnv. optTidyPgm is the normal case: compiling with -O. It generates a TypeEnv rich in IdInfo MkIface.mkIface now only generates a ModIface. A separate procedure, MkIface.writeIfaceFile, writes the file out to disk.
-
- 18 Mar, 2005 1 commit
-
-
simonmar authored
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.
-
- 24 Dec, 2004 1 commit
-
-
simonpj authored
--------------------------- Refactor the simplifier --------------------------- Driven by a GADT bug, I have refactored the simpifier, and the way GHC treats substitutions. I hope I have gotten it right. Be cautious about updating. * coreSyn/Subst.lhs has gone * coreSyn/CoreSubst replaces it, except that it's quite a bit simpler * simplCore/SimplEnv is added, and contains the simplifier-specific substitution stuff Previously Subst was trying to be all things to all men, and that was making it Too Complicated. There may be a little more code now, but it's much easier to understand.
-
- 23 Dec, 2004 1 commit
-
-
simonpj authored
Simplifications, dead code elimination
-
- 22 Dec, 2004 1 commit
-
-
simonpj authored
---------------------------------------- New Core invariant: keep case alternatives in sorted order ---------------------------------------- We now keep the alternatives of a Case in the Core language in sorted order. Sorted, that is, by constructor tag for DataAlt by literal for LitAlt The main reason is that it makes matching and equality testing more robust. But in fact some lines of code vanished from SimplUtils.mkAlts. WARNING: no change to interface file formats, but you'll need to recompile your libraries so that they generate interface files that respect the invariant.
-
- 30 Sep, 2004 1 commit
-
-
simonpj authored
------------------------------------ Add Generalised Algebraic Data Types ------------------------------------ This rather big commit adds support for GADTs. For example, data Term a where Lit :: Int -> Term Int App :: Term (a->b) -> Term a -> Term b If :: Term Bool -> Term a -> Term a ..etc.. eval :: Term a -> a eval (Lit i) = i eval (App a b) = eval a (eval b) eval (If p q r) | eval p = eval q | otherwise = eval r Lots and lots of of related changes throughout the compiler to make this fit nicely. One important change, only loosely related to GADTs, is that skolem constants in the typechecker are genuinely immutable and constant, so we often get better error messages from the type checker. See TcType.TcTyVarDetails. There's a new module types/Unify.lhs, which has purely-functional unification and matching for Type. This is used both in the typechecker (for type refinement of GADTs) and in Core Lint (also for type refinement).
-
- 17 Aug, 2004 1 commit
-
-
simonpj authored
------------------------------- 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.
-
- 23 Sep, 2003 1 commit
-
-
simonpj authored
-------------------------- Much grunting about let-floating -------------------------- We want to avoid putting bindings between the '=' of a defn and a '\': let { f = let ... in \y-> ... } in ... Reason: float-in often follows float-out, and it may then add yte more bindings there, some of which may be strict. But f may by not be marked as not-demanded (for other reasons: see the call to zapDemandInfo in Simplify.completeLazyBind); and now the strict binding may not be able to float out again. (Well, it triggers the ASSERT in simplLazyBind.) So this commit adds FloatOut.floatNonRecRhs (to complement floatRhs) which is a big more vigorous about floating out. But that in turn showed up a pile of gore to do with unlifted bindings. We can't have them showing up at top level. After thrashing in the swamp for a while, I eventually arranged that let x# = e in b (where x# has an unlifted type) is treated exactly like case e of x# -> b That is, it is never floated. Yes, we lose opportunities to float some (very cheap! unlifted let-bindings are always cheap) out of a lambda, but we're missing much bigger opportunities already. For example: \x -> f (h y) where h :: Int -> Int# is expensive. We'd like to float the (h y) outside the \x, but we don't because it's unboxed. Possible solution: box it. Anyway, that's for the future.
-
- 13 Sep, 2002 1 commit
-
-
simonpj authored
-------------------------------------- Make Template Haskell into the HEAD -------------------------------------- This massive commit transfers to the HEAD all the stuff that Simon and Tim have been doing on Template Haskell. The meta-haskell-branch is no more! WARNING: make sure that you * Update your links if you are using link trees. Some modules have been added, some have gone away. * Do 'make clean' in all library trees. The interface file format has changed, and you can get strange panics (sadly) if GHC tries to read old interface files: e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05): Binary.get(TyClDecl): ForeignType * You need to recompile the rts too; Linker.c has changed However the libraries are almost unaltered; just a tiny change in Base, and to the exports in Prelude. NOTE: so far as TH itself is concerned, expression splices work fine, but declaration splices are not complete. --------------- The main change --------------- The main structural change: renaming and typechecking have to be interleaved, because we can't rename stuff after a declaration splice until after we've typechecked the stuff before (and the splice itself). * Combine the renamer and typecheker monads into one (TcRnMonad, TcRnTypes) These two replace TcMonad and RnMonad * Give them a single 'driver' (TcRnDriver). This driver replaces TcModule.lhs and Rename.lhs * The haskell-src library package has a module Language/Haskell/THSyntax which defines the Haskell data type seen by the TH programmer. * New modules: hsSyn/Convert.hs converts THSyntax -> HsSyn deSugar/DsMeta.hs converts HsSyn -> THSyntax * New module typecheck/TcSplice type-checks Template Haskell splices. ------------- Linking stuff ------------- * ByteCodeLink has been split into ByteCodeLink (which links) ByteCodeAsm (which assembles) * New module ghci/ObjLink is the object-code linker. * compMan/CmLink is removed entirely (was out of place) Ditto CmTypes (which was tiny) * Linker.c initialises the linker when it is first used (no need to call initLinker any more). Template Haskell makes it harder to know when and whether to initialise the linker. ------------------------------------- Gathering the LIE in the type checker ------------------------------------- * Instead of explicitly gathering constraints in the LIE tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE) we now dump the constraints into a mutable varabiable carried by the monad, so we get tcExpr :: RenamedExpr -> TcM TypecheckedExpr Much less clutter in the code, and more efficient too. (Originally suggested by Mark Shields.) ----------------- Remove "SysNames" ----------------- Because the renamer and the type checker were entirely separate, we had to carry some rather tiresome implicit binders (or "SysNames") along inside some of the HsDecl data structures. They were both tiresome and fragile. Now that the typechecker and renamer are more intimately coupled, we can eliminate SysNames (well, mostly... default methods still carry something similar). ------------- Clean up HsPat ------------- One big clean up is this: instead of having two HsPat types (InPat and OutPat), they are now combined into one. This is more consistent with the way that HsExpr etc is handled; there are some 'Out' constructors for the type checker output. So: HsPat.InPat --> HsPat.Pat HsPat.OutPat --> HsPat.Pat No 'pat' type parameter in HsExpr, HsBinds, etc Constructor patterns are nicer now: they use HsPat.HsConDetails for the three cases of constructor patterns: prefix, infix, and record-bindings The *same* data type HsConDetails is used in the type declaration of the data type (HsDecls.TyData) Lots of associated clean-up operations here and there. Less code. Everything is wonderful.
-
- 29 Jul, 2002 1 commit
-
-
simonmar authored
Type variables created by the typechecker didn't have the correct NameSpace: they were in the Var namespace rather than the TyVar namespace, which can lead to strange warnings about quantified type variables being not mentioned in the type when DEBUG is on. Name: - added mkSystemNameEncoded for use when the string is already encoded (saves re-encoding the string every time) - added mkSystemTvNameEncoded for making a type variable name, as above Var: - use mkSystemTvNameEncoded when making type variables Id: - add mkSysLocalUnencoded for the (rare) case when the string needs encoding TcMType: - use mkSystemTvNameEncoded rather than mkSystemName for making type variables SetLevels: - use mkSysLocalUnencoded since the names generated here need encoding.
-
- 29 Apr, 2002 1 commit
-
-
simonmar authored
FastString cleanup, stage 1. The FastString type is no longer a mixture of hashed strings and literal strings, it contains hashed strings only with O(1) comparison (except for UnicodeStr, but that will also go away in due course). To create a literal instance of FastString, use FSLIT(".."). By far the most common use of the old literal version of FastString was in the pattern ptext SLIT("...") this combination still works, although it doesn't go via FastString any more. The next stage will be to remove the need to use this special combination at all, using a RULE. To convert a FastString into an SDoc, now use 'ftext' instead of 'ptext'. I've also removed all the FAST_STRING related macros from HsVersions.h except for SLIT and FSLIT, just use the relevant functions from FastString instead.
-
- 04 Jan, 2002 1 commit
-
-
simonpj authored
---------------------------------------- Be a bit less gung ho about let-floating ---------------------------------------- Sometimes it's a bad idea to float cheap expressions outwards, even if they escape a value lambda. -- Even if it escapes a value lambda, we only -- float if it's not cheap (unless it'll get all the -- way to the top). I've seen cases where we -- float dozens of tiny free expressions, which cost -- more to allocate than to evaluate. -- NB: exprIsCheap is also true of bottom expressions, which -- is good; we don't want to share them -- -- It's only Really Bad to float a cheap expression out of a -- strict context, because that builds a thunk that otherwise -- would never be built. So another alternative would be to -- add -- || (strict_ctxt && not (exprIsBottom expr)) -- to the condition above. We should really try this out. The relevant function is lvlMFE, which has been subject to a lot of fiddling over the years. Probably this isn't the last time. This all actually showed up when I was compiling IA.lhs from Ian Lynagh.
-
- 14 Dec, 2001 1 commit
-
-
simonpj authored
------------------------- Performance tuning things ------------------------- I did some nofib tests, and fixed a number of performance problems. 1. Things were getting floated to top level, and that prevented some useful fusion happening. y = build g x = foldr k z y Fixed by arranging that we only get really keen on floating to top level in the second run of the let-float-out pass. 2. Some fettling up on the let-floater itself. It had some parameters that weren't even being used! And it was stupidly floating things out of a one-shot lambda, and the float-in pass didn't float them back in. I think I fixed both of these problems. 3. The eta-reducer was not eta-reducing (/\a -> g a) to g. In general it has to be a bit careful because "seq" means that (\x -> g x) is not in general the same as g ---- but it *is* the same for a type lambda. This turned out to be important in rule matching, where the foldr/build rule was not firing because the LHS of the rule looked like foldr k z (/\ a -> g a) = ... which never matched! Result, no fusion to speak of! 4. The simplifier was a bit too gung ho about inlining used-once things bound to constructor args. The comment is with Simplify.simplNonRecX.
-
- 12 Dec, 2001 1 commit
-
-
simonpj authored
Keep wibbling; this fixes the float-out crash
-
- 11 Dec, 2001 2 commits
-
-
simonpj authored
More inline/floating fixes; sigh
-
simonpj authored
------------------------------ Don't float out of INLINE blocks ------------------------------ We never want to float stuff out of an INLINE right hand side. This has been a long-standing thorn, and I managed to dislodge it yesterday (hence Lint errors). Fixed again, more robustly this time (I hope).
-
- 10 Dec, 2001 1 commit
-
-
simonpj authored
------------------------------ Don't do CPR w/w for constants ------------------------------ We don't want to do a CPR split for a constant function. So if the worker will get no (value) args, we disable the CPR transformation. This infelicity exposed a buglet in the full laziness transformation; we were floating an expression outside an InlineMe context. I've take the blunderbuss approach now, of effectively disabling full laziness inside an InlineMe. Seems reasonable.
-
- 01 Nov, 2001 1 commit
-
-
simonpj authored
--------------------------------------- Fix a unboxed-binding bug in SpecConstr --------------------------------------- [HEAD only] This fixes a rather obscure bug in the constructor specialiser discovered by Ralf Hinze. It was generating a specialised version of the function with no arguments --- and the function returned an unboxed type. Solution: same as for worker-wrapper; add a dummy argument. Several files are affected because I added CoreUtils.mkPiTypes, as a useful helper function.
-
- 26 Sep, 2001 1 commit
-
-
simonpj authored
------------------ Simon's big commit ------------------ [ These files seem to have been left out for some reason ] This commit, which I don't think I can sensibly do piecemeal, consists of the things I've been doing recently, mainly directed at making Manuel, George, and Marcin happier with RULES. Reogranise the simplifier ~~~~~~~~~~~~~~~~~~~~~~~~~ 1. The simplifier's environment is now an explicit parameter. This makes it a bit easier to figure out where it is going. 2. Constructor arguments can now be arbitrary expressions, except when the application is the RHS of a let(rec). This makes it much easier to match rules like RULES "foo" f (h x, g y) = f' x y In the simplifier, it's Simplify.mkAtomicArgs that ANF-ises a constructor application where necessary. In the occurrence analyser, there's a new piece of context info (OccEncl) to say whether a constructor app is in a place where it should be in ANF. (Unless it knows this it'll give occurrence info which will inline the argument back into the constructor app.) 3. I'm experimenting with doing the "float-past big lambda" transformation in the full laziness pass, rather than mixed in with the simplifier (was tryRhsTyLam). 4. Arrange that case (coerce (S,T) (x,y)) of ... will simplify. Previous it didn't. A local change to CoreUtils.exprIsConApp_maybe. 5. Do a better job in CoreUtils.exprEtaExpandArity when there's an error function in one branch. Phase numbers, RULES, and INLINE pragmas ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1. Phase numbers decrease from N towards zero (instead of increasing). This makes it easier to add new earlier phases, which is what users want to do. 2. RULES get their own phase number, N, and are disabled in phases before N. e.g. {-# RULES "foo" [2] forall x y. f (x,y) = f' x y #-} Note the [2], which says "only active in phase 2 and later". 3. INLINE and NOINLINE pragmas have a phase number to. This is now treated in just the same way as the phase number on RULE; that is, the Id is not inlined in phases earlier than N. In phase N and later the Id *may* be inlined, and here is where INLINE and NOINLINE differ: INLNE makes the RHS look small, so as soon as it *may* be inlined it probably *will* be inlined. The syntax of the phase number on an INLINE/NOINLINE pragma has changed to be like the RULES case (i.e. in square brackets). This should also make sure you examine all such phase numbers; many will need to change now the numbering is reversed. Inlining Ids is no longer affected at all by whether the Id appears on the LHS of a rule. Now it's up to the programmer to put a suitable INLINE/NOINLINE pragma to stop it being inlined too early. Implementation notes: * A new data type, BasicTypes.Activation says when a rule or inline pragma is active. Functions isAlwaysActive, isNeverActive, isActive, do the obvious thing (all in BasicTypes). * Slight change in the SimplifierSwitch data type, which led to a lot of simplifier-specific code moving from CmdLineOpts to SimplMonad; a Good Thing. * The InlinePragma in the IdInfo of an Id is now simply an Activation saying when the Id can be inlined. (It used to be a rather bizarre pair of a Bool and a (Maybe Phase), so this is much much easier to understand.) * The simplifier has a "mode" environment switch, replacing the old black list. Unfortunately the data type decl has to be in CmdLineOpts, because it's an argument to the CoreDoSimplify switch data SimplifierMode = SimplGently | SimplPhase Int Here "gently" means "no rules, no inlining". All the crucial inlining decisions are now collected together in SimplMonad (preInlineUnconditionally, postInlineUnconditionally, activeInline, activeRule). Specialisation ~~~~~~~~~~~~~~ 1. Only dictionary *functions* are made INLINE, not dictionaries that have no parameters. (This inline-dictionary-function thing is Marcin's idea and I'm still not sure whether it's a good idea. But it's definitely a Bad Idea when there are no arguments.) 2. Be prepared to specialise an INLINE function: an easy fix in Specialise.lhs But there is still a problem, which is that the INLINE wins at the call site, so we don't use the specialised version anyway. I'm still unsure whether it makes sense to SPECIALISE something you want to INLINE. Random smaller things ~~~~~~~~~~~~~~~~~~~~~~ * builtinRules (there was only one, but may be more) in PrelRules are now incorporated. They were being ignored before... * OrdList.foldOL --> OrdList.foldrOL, OrdList.foldlOL * Some tidying up of the tidyOpenTyVar, tidyTyVar functions. I've forgotten exactly what!
-
- 18 May, 2001 1 commit
-
-
simonpj authored
----------------------------- Get unbox-strict-fields right ----------------------------- The problem was that when a library was compiled *without* -funbox-strict-fields, and the main program was compiled *with* that flag, we were wrongly treating the fields of imported data types as unboxed. To fix this I added an extra constructor to StrictnessMark to express whether the "!" annotation came from an interface file (don't fiddle) or a source file (decide whether to unbox). On the way I tided things up: * StrictnessMark moves to Demand.lhs, and doesn't have the extra DataCon fields that kept it in DataCon before. * HsDecls.BangType has one constructor, not three, with a StrictnessMark field. * DataCon keeps track of its strictness signature (dcRepStrictness), but not its "user strict marks" (which were never used) * All the functions, like getUniquesDs, that used to take an Int saying how many uniques to allocate, now return an infinite list. This saves arguments and hassle. But it involved touching quite a few files. * rebuildConArgs takes a list of Uniques to use as its unique supply. This means I could combine DsUtils.rebuildConArgs with MkId.rebuildConArgs (hooray; the main point of the previous change) I also tidied up one or two error messages
-
- 19 Mar, 2001 1 commit
-
-
simonpj authored
------------------------------------------------------- Be more careful about floating out from INLINE pragmas ------------------------------------------------------- Given this: x = __inline__ (f (g y)) we were floating the (g y) out as a MFE, thus: lvl = g y x = __inline__ (f lvl) This is bad. The (g y) redex gets outside the __inline__ envelope, and may never get inlined. The solution involved a bit of fiddling in SetLevels.
-
- 07 Mar, 2001 1 commit
-
-
simonpj authored
Remove DOS Ctrl-Ms
-
- 01 Mar, 2001 1 commit
-
-
simonpj authored
Improve IdInfo substitution To get rules to work nicely, we need to make rules for recursive functions active in the RHS of the very recursive function itself. This can be done nicely: the change is to move the calls to simplIdInfo in Simplify to an earlier place. The second thing is that when doing simple expression substitution in a rule (which we do during simplification for rules attached to an Id) we were zapping the occurrence info carefully pinned on the rule binders when the rule was put into the Id's rules. This in turn meant that the simplifer ran more iterations than necessary when rules were fired. (Andrew Tolmach discovered this.) So I tidied up the interface to Subst a little. The relevant functions that have changed are simplBndr, simplBndrs, simplLetId, simplIdInfo, substAndCloneId, substAndCloneIds, substAndCloneRecIds, There are consequential changes in other modules, but it compiles at least the whole standard libraries happily, and the codegen tests, so I'm reasonably confident in it. But watch out for new strange happenings.
-
- 24 Nov, 2000 1 commit
-
-
simonpj authored
Unused imports and suchlike
-
- 14 Nov, 2000 1 commit
-
-
simonpj authored
Compiles now
-
- 14 Sep, 2000 1 commit
-
-
simonpj authored
--------------------------------------- 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)
-
- 07 Sep, 2000 1 commit
-
-
simonpj authored
A list of simplifier-related stuff, triggered by looking at GHC's performance. I don't guarantee that this lot will lead to a uniform improvement over 4.08, but it it should be a bit better. More work probably required. * Make the simplifier's Stop continuation record whether the expression being simplified is the RHS of a thunk, or (say) the body of a lambda or case RHS. In the thunk case we want to be a bit keener about inlining if the type of the thunk is amenable to update in place. * Fix interestingArg, which was being too liberal, and hence doing too much inlining. * Extended CoreUtils.exprIsCheap to make two more things cheap: - case (coerce x) of ... - let x = y +# z This makes a bit more eta expansion happen. It was provoked by a program of Marcin's. * MkIface.ifaceBinds. Make sure that we emit rules for things (like class operations) that don't get a top-level binding in the interface file. Previously such rules were silently forgotten. * Move transformRhs to *after* simplification, which makes it a little easier to do, and means that the arity it computes is readily available to completeBinding. This gets much better arities. * Do coerce splitting in completeBinding. This gets good code for newtype CInt = CInt Int test:: CInt -> Int test x = case x of 1 -> 2 2 -> 4 3 -> 8 4 -> 16 _ -> 0 * Modify the meaning of "arity" so that during compilation it means "if you apply this function to fewer args, it will do virtually no work". So, for example f = coerce t (\x -> e) has arity at least 1. When a function is exported, it's arity becomes the number of exposed, top-level lambdas, which is subtly different. But that's ok. I removed CoreUtils.exprArity altogether: it looked only at the exposed lambdas. Instead, we use exprEtaExpandArity exclusively. All of this makes I/O programs work much better.
-