- 01 Apr, 2003 1 commit
-
-
simonmar authored
Don't constant-fold (negateFloat# 0.0#), because the compiler's internal representation of floating-point literals (Rational) can't represent -0.0. This means that main = print (-0.0) now gives the same results with -O as it does without. Fixes test arith005.
-
- 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 Aug, 2002 1 commit
-
-
simonmar authored
Housekeeping: - The main goal is to remove dependencies on hslibs for a bootstrapped compiler, leaving only a requirement that the packages base, haskell98 and readline are built in stage 1 in order to bootstrap. We're almost there: Posix is still required for signal handling, but all other dependencies on hslibs are now gone. Uses of Addr and ByteArray/MutableByteArray array are all gone from the compiler. PrimPacked defines the Ptr type for GHC 4.08 (which didn't have it), and it defines simple BA and MBA types to replace uses of ByteArray and MutableByteArray respectively. - Clean up import lists. HsVersions.h now defines macros for some modules which have moved between GHC versions. eg. one now imports 'GLAEXTS' to get at unboxed types and primops in the compiler. Many import lists have been sorted as per the recommendations in the new style guidelines in the commentary. I've built the compiler with GHC 4.08.2, 5.00.2, 5.02.3, 5.04 and itself, and everything still works here. Doubtless I've got something wrong, though.
-
- 18 Jun, 2002 1 commit
-
-
simonpj authored
--------------------------------------- Rehash the handling of SeqOp --------------------------------------- See the comments in the commentary (Cunning Prelude Code). * Expunge SeqOp altogether * Add GHC.Base.lazy :: a -> a to GHC.Base * Add GHC.Base.lazy to basicTypes/MkId. The idea is that this defn will over-ride the info from GHC.Base.hi, thereby hiding strictness and unfolding * Make stranal/WorkWrap do a "manual inlining" for GHC.Base.lazy This happens nicely after the strictness analyser has run. * Expunge the SeqOp/ParOp magic in CorePrep * Expunge the RULE for seq in PrelRules * Change the defns of pseq/par in GHC.Conc to: {-# INLINE pseq #-} pseq :: a -> b -> b pseq x y = x `seq` lazy y {-# INLINE par #-} par :: a -> b -> b par x y = case (par# x) of { _ -> lazy y }
-
- 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.
-
- 01 Apr, 2002 1 commit
-
-
simonpj authored
------------------------------------ Change the treatment of the stupid context on data constructors ----------------------------------- Data types can have a context: data (Eq a, Ord b) => T a b = T1 a b | T2 a and that makes the constructors have a context too (notice that T2's context is "thinned"): T1 :: (Eq a, Ord b) => a -> b -> T a b T2 :: (Eq a) => a -> T a b Furthermore, this context pops up when pattern matching (though GHC hasn't implemented this, but it is in H98, and I've fixed GHC so that it now does): f (T2 x) = x gets inferred type f :: Eq a => T a b -> a I say the context is "stupid" because the dictionaries passed are immediately discarded -- they do nothing and have no benefit. It's a flaw in the language. Up to now I have put this stupid context into the type of the "wrapper" constructors functions, T1 and T2, but that turned out to be jolly inconvenient for generics, and record update, and other functions that build values of type T (because they don't have suitable dictionaries available). So now I've taken the stupid context out. I simply deal with it separately in the type checker on occurrences of a constructor, either in an expression or in a pattern. To this end * Lots of changes in DataCon, MkId * New function Inst.tcInstDataCon to instantiate a data constructor I also took the opportunity to * Rename dataConId --> dataConWorkId for consistency. * Tidied up MkId.rebuildConArgs quite a bit, and renamed it mkReboxingAlt * Add function DataCon.dataConExistentialTyVars, with the obvious meaning
-
- 13 Feb, 2002 1 commit
-
-
simonpj authored
---------------------------------- Do the Right Thing for TyCons where we can't see all their constructors. ---------------------------------- Inside a TyCon, three things can happen 1. GHC knows all the constructors, and has them to hand. (Nowadays, there may be zero constructors.) 2. GHC knows all the constructors, but has declined to slurp them all in, to avoid sucking in more declarations than necessary. All we remember is the number of constructors, so we can get the return convention right. 3. GHC doesn't know anything. This happens *only* for decls coming from .hi-boot files, where the programmer declines to supply a representation. Until now, these three cases have been conflated together. Matters are worse now that a TyCon really can have zero constructors. In fact, by confusing (3) with (1) we can actually generate bogus code. With this commit, the dataCons field of a TyCon is of type: data DataConDetails datacon = DataCons [datacon] -- Its data constructors, with fully polymorphic types -- A type can have zero constructors | Unknown -- We're importing this data type from an hi-boot file -- and we don't know what its constructors are | HasCons Int -- In a quest for compilation speed we have imported -- only the number of constructors (to get return -- conventions right) but not the constructors themselves This says exactly what is going on. There are lots of consequential small changes.
-
- 29 Jan, 2002 1 commit
-
-
simonpj authored
------------ Rule phasing ------------ This commit adds a little more control to when rules are enabled. {-# RULES "foo" [2] forall ... "baz" [~2] forall ... #-} Rule "foo" is active in phase 2 and later. The new thing is that the "~2" means that Rule "baz" is active in phase 3 and earlier. (Remember tha phases decrease towards zero.) All the machinery was there to implement this, it just needed the syntax. Why do this? Peter Gammie (at UNSW) found that rules weren't firing because of bindings of the form M.f = f f = .... where the rules where on the M.f binding. It turned out that an old hack (which have for some time elicited the harmless "shortMeOut" debug warnings) prevented this trivial construction from being correctly simplified. The hack in turn derived from a trick in the way the foldr/build rule was implemented....and that hack is no longer necessary now we can switch rules *off* as well as *on*. There are consequential changes in the Prelude foldr/build RULE stuff. It's a clean-up.... Instead of strange definitions like map = mapList which we had before, we have an ordinary recursive defn of map, together with rules to convert first to foldr/build form, and then (if nothing happens) back again. There's a fairly long comment about the general plan of attack in PrelBase, near the defn of map.
-
- 17 Oct, 2001 1 commit
-
-
simonpj authored
------------------------------------------- nullAddr# fix for the HEAD ------------------------------------------- *** DO NOT MERGE *** nullAddr# is simply a name for (Lit nullAddrLit). Up to now it has been a PrimOp with the rather stange type nullAddr# :: Int# -> Addr# which discards its argument. (I think the problem with nullary primops is to do with the top-level bindings in PrelPrimOpWrappers.) And there was a RULE in PrelRules to rewrite nullAddr _ ==> nullAddrLit It's excessive to make it a PrimOp. We can just treat it like unsafeCoerce#, which is made in MkId.lhs. So I've done that, and given it the more sensible type nullAddr# :: Addr# I fixed all the occurrences I could find.
-
- 01 Oct, 2001 1 commit
-
-
simonpj authored
Stuff to make a RULE work for eqString "foo" "foo" = True (etc.) The rule is of course a BuiltinRule in PrelRules
-
- 26 Sep, 2001 1 commit
-
-
simonpj authored
------------------ Simon's big commit ------------------ 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!
-
- 14 Sep, 2001 1 commit
-
-
simonpj authored
-------------------------- Add a rule-check pass (special request by Manuel) -------------------------- DO NOT merge with stable The flag -frule-check foo will report all sites at which RULES whose name starts with "foo.." might apply, but in fact the arguments don't match so the rule doesn't apply. The pass is run right after all the core-to-core passes. (Next thing to do: make the core-to-core script external, so you can fiddle with it. Meanwhile, the core-to-core script is in DriverState.builCoreToDo so you can move the CoreDoRuleCheck line around if you want. The format of the report is experimental: Manuel, feel free to fiddle with it. Most of the code is in specialise/Rules.lhs Incidental changes ~~~~~~~~~~~~~~~~~~ Change BuiltinRule so that the rule name is accessible without actually successfully applying the rule. This change affects quite a few files in a trivial way.
-
- 17 Aug, 2001 1 commit
-
-
apt authored
How I spent my summer vacation. Primops ------- The format of the primops.txt.pp file has been enhanced to allow (latex-style) primop descriptions to be included. There is a new flag to genprimopcode that generates documentation including these descriptions. A first cut at descriptions of the more interesting primops has been made, and the file has been reordered a bit. 31-bit words ------------ The front end now can cope with the possibility of 31-bit (or even 30-bit) Int# and Word# types. The only current use of this is to generate external .core files that can be translated into OCAML source files (OCAML uses a one-bit tag to distinguish integers from pointers). The only way to get this right now is by hand-defining the preprocessor symbol WORD_SIZE_IN_BITS, which is normally set automatically from the familiar WORD_SIZE_IN_BYTES. Just in case 31-bit words are used, we now have Int32# and Word32# primitive types and an associated family of operators, paralleling the existing 64-bit stuff. Of course, none of the operators actually need to be implemented in the absence of a 31-bit backend. There has also been some minor re-jigging of the 32 vs. 64 bit stuff. See the description at the top of primops.txt.pp file for more details. Note that, for the first time, the *type* of a primop can now depend on the target word size. Also, the family of primops intToInt8#, intToInt16#, etc. have been renamed narrow8Int#, narrow16Int#, etc., to emphasize that they work on Int#'s and don't actually convert between types. Addresses --------- As another part of coping with the possibility of 31-bit ints, the addr2Int# and int2Addr# primops are now thoroughly deprecated (and not even defined in the 31-bit case) and all uses of them have been removed except from the (deprecated) module hslibs/lang/Addr Addr# should now be treated as a proper abstract type, and has these suitable operators: nullAddr# : Int# -> Addr# (ignores its argument; nullary primops cause problems at various places) plusAddr# : Addr# -> Int# -> Addr# minusAddr : Addr# -> Addr# -> Int# remAddr# : Addr# -> Int# -> Int# Obviously, these don't allow completely arbitrary offsets if 31-bit ints are in use, but they should do for all practical purposes. It is also still possible to generate an address constant, and there is a built-in rule that makes use of this to remove the nullAddr# calls. Misc ---- There is a new compile flag -fno-code that causes GHC to quit after generating .hi files and .core files (if requested) but before generating STG. Z-encoded names for tuples have been rationalized; e.g., Z3H now means an unboxed 3-tuple, rather than an unboxed tuple with 3 commas (i.e., a 4-tuple)! Removed misc. litlits in hslibs/lang Misc. small changes to external core format. The external core description has also been substantially updated, and incorporates the automatically-generated primop documentation; its in the repository at /papers/ext-core/core.tex. A little make-system addition to allow passing CPP options to compiler and library builds.
-
- 14 Aug, 2001 1 commit
-
-
sewardj authored
Change the story about POSIX headers in C compilation. Until now, all C code in the RTS and library cbits has by default been compiled with settings for POSIXness enabled, that is: #define _POSIX_SOURCE 1 #define _POSIX_C_SOURCE 199309L #define _ISOC9X_SOURCE If you wanted to negate this, you'd have to define NON_POSIX_SOURCE before including headers. This scheme has some bad effects: * It means that ccall-unfoldings exported via interfaces from a module compiled with -DNON_POSIX_SOURCE may not compile when imported into a module which does not -DNON_POSIX_SOURCE. * It overlaps with the feature tests we do with autoconf. * It seems to have caused borkage in the Solaris builds for some considerable period of time. The New Way is: * The default changes to not-being-in-Posix mode. * If you want to force a C file into Posix mode, #include as the **first** include the new file ghc/includes/PosixSource.h. Most of the RTS C sources have this include now. * NON_POSIX_SOURCE is almost totally expunged. Unfortunately we have to retain some vestiges of it in ghc/compiler so that modules compiled via C on Solaris using older compilers don't break.
-
- 25 Jun, 2001 1 commit
-
-
simonpj authored
---------------- Squash newtypes ---------------- This commit squashes newtypes and their coerces, from the typechecker onwards. The original idea was that the coerces would not get in the way of optimising transformations, but despite much effort they continue to do so. There's no very good reason to retain newtype information beyond the typechecker, so now we don't. Main points: * The post-typechecker suite of Type-manipulating functions is in types/Type.lhs, as before. But now there's a new suite in types/TcType.lhs. The difference is that in the former, newtype are transparent, while in the latter they are opaque. The typechecker should only import TcType, not Type. * The operations in TcType are all non-monadic, and most of them start with "tc" (e.g. tcSplitTyConApp). All the monadic operations (used exclusively by the typechecker) are in a new module, typecheck/TcMType.lhs * I've grouped newtypes with predicate types, thus: data Type = TyVarTy Tyvar | .... | SourceTy SourceType data SourceType = NType TyCon [Type] | ClassP Class [Type] | IParam Type [SourceType was called PredType.] This is a little wierd in some ways, because NTypes can't occur in qualified types. However, the idea is that a SourceType is a type that is opaque to the type checker, but transparent to the rest of the compiler, and newtypes fit that as do implicit parameters and dictionaries. * Recursive newtypes still retain their coreces, exactly as before. If they were transparent we'd get a recursive type, and that would make various bits of the compiler diverge (e.g. things which do type comparison). * I've removed types/Unify.lhs (non-monadic type unifier and matcher), merging it into TcType. Ditto typecheck/TcUnify.lhs (monadic unifier), merging it into TcMType.
-
- 28 Apr, 2001 1 commit
-
-
qrczak authored
Add a builtin rule to a primop only if it does something.
-
- 27 Apr, 2001 1 commit
-
-
qrczak authored
Add builtin rules for {intToInt,wordToWord}{8,16,32}# applied to literals.
-
- 14 Apr, 2001 1 commit
-
-
qrczak authored
Do more Word arithmetic on constants at compile time.
-
- 15 Nov, 2000 1 commit
-
-
simonpj authored
I finally got tired of not having splitTyConApp tyConAppTyCon tyConAppArgs (Previously we called splitTyConApp_maybe, but it's a pain in the neck.)
-
- 23 Oct, 2000 2 commits
- 12 Oct, 2000 1 commit
-
-
simonmar authored
RdrName->Name fix
-
- 28 Sep, 2000 1 commit
-
-
simonpj authored
------------------------------------ Mainly PredTypes (28 Sept 00) ------------------------------------ Three things in this commit: 1. Main thing: tidy up PredTypes 2. Move all Keys into PrelNames 3. Check for unboxed tuples in function args 1. Tidy up PredTypes ~~~~~~~~~~~~~~~~~~~~ The main thing in this commit is to modify the representation of Types so that they are a (much) better for the qualified-type world. This should simplify Jeff's life as he proceeds with implicit parameters and functional dependencies. In particular, PredType, introduced by Jeff, is now blessed and dignified with a place in TypeRep.lhs: data PredType = Class Class [Type] | IParam Name Type Consider these examples: f :: (Eq a) => a -> Int g :: (?x :: Int -> Int) => a -> Int h :: (r\l) => {r} => {l::Int | r} Here the "Eq a" and "?x :: Int -> Int" and "r\l" are all called *predicates*, and are represented by a PredType. (We don't support TREX records yet, but the setup is designed to expand to allow them.) In addition, Type gains an extra constructor: data Type = .... | PredTy PredType so that PredType is injected directly into Type. So the type p => t is represented by PredType p `FunTy` t I have deleted the hackish IPNote stuff; predicates are dealt with entirely through PredTys, not through NoteTy at all. 2. Move Keys into PrelNames ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ This is just a housekeeping operation. I've moved all the pre-assigned Uniques (aka Keys) from Unique.lhs into PrelNames.lhs. I've also moved knowKeyRdrNames from PrelInfo down into PrelNames. This localises in PrelNames lots of stuff about predefined names. Previously one had to alter three files to add one, now only one. 3. Unboxed tuples ~~~~~~~~~~~~~~~~~~ Add a static check for unboxed tuple arguments. E.g. data T = T (# Int, Int #) is illegal
-
- 23 Jul, 2000 1 commit
-
-
panne authored
Strictfp-like behaviour is the default now, which can be switched off via -fexcess-precision. (Has anybody a better name for this option?)
-
- 16 Jul, 2000 1 commit
-
-
panne authored
This commit tries to fix the discrepancies between the results of floating point calculations during runtime and compile time, see e.g. fptools/ghc/tests/numeric/should_run/arith008.hs. Part of the story was the fact that floating point values are represented as Rationals in GHC and therefore never lost precision, at least for the operations for which constant folding is done. To compensate for this, before and after floating point operations the operands are temporarily converted to/from Float/Double. This is wrong, because host architecture and target architecture are confused this way, but in a non-cross-compiling scenario it works.
-
- 11 Jul, 2000 1 commit
-
-
simonmar authored
remove unused imports
-
- 02 Jul, 2000 1 commit
-
-
panne authored
Don't warn the user about integer overflow during constant folding anymore. It's not done at runtime either, and compilation of completely harmless things like ((124076834 :: Word32) + (2147483647 :: Word32)) yielded a warning.
-
- 22 Jun, 2000 1 commit
-
-
simonpj authored
*** MERGE WITH 4.07 *** * The divide by zero check in the constant-folding rules was testing the numerator not denominator! (For Float and Double.)
-
- 25 May, 2000 1 commit
-
-
simonpj authored
~~~~~~~~~~~~ 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[!]
-
- 12 May, 2000 3 commits
- 11 May, 2000 1 commit
-
-
panne authored
Added rules for constant folding with the folloging ops: WordQuotOp, WordRemOp, AndOp, OrOp, XorOp, Int2AddrOp, Addr2IntOp, Float2IntOp, DoubleNegOp, Double2IntOp, Double2FloatOp, Float2DoubleOp
-
- 22 Apr, 2000 1 commit
-
-
panne authored
Don't use coercion RULES with litlits (e.g. int2Word ``42''), once again found by *the* GHC test, HOpenGL + Quake level viewer. :-)
-
- 27 Mar, 2000 1 commit
-
-
simonpj authored
a) Move Unfolding and UnfoldingGuidance to CoreSyn As a result, remove several SOURCE imports Shrink CoreSyn.hi-boot considerably Delete CoreUnfold.hi-boot altogether b) Add CoreUtils.exprIsConApp_maybe Use in PrelRules to fix a bug in the dataToTag rule c) Fix boolean polarity error in Simplify.lhs
-
- 23 Mar, 2000 1 commit
-
-
simonpj authored
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.
-
- 04 Jan, 2000 1 commit
-
-
simonpj authored
This commit arranges that literal strings will fuse nicely, by expressing them as an application of build. * NoRepStr is now completely redundant, though I havn't removed it yet. * The unpackStr stuff moves from PrelPack to PrelBase. * There's a new form of Rule, a BuiltinRule, for rules that can't be expressed in Haskell. The string-fusion rule is one such. It's defined in prelude/PrelRules.lhs. * PrelRules.lhs also contains a great deal of code that implements constant folding. In due course this will replace ConFold.lhs, but for the moment it simply duplicates it.
-