- 03 Oct, 2001 1 commit
-
-
simonmar authored
Don't print the "compilation IS NOT required" in quiet mode (-v0).
-
- 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!
-
- 21 Aug, 2001 1 commit
-
-
simonmar authored
Make local bindings work on the GHCi command line again.
-
- 20 Aug, 2001 1 commit
-
-
simonmar authored
Now copes with more forms of identifiers, as suggested by Marcin.
-
- 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.
-
- 16 Aug, 2001 1 commit
-
-
simonmar authored
Set the SrcLoc for expressions typed on the command line to <interactive>:1 rather than <no file>:0.
-
- 15 Aug, 2001 2 commits
- 24 Jul, 2001 1 commit
-
-
ken authored
Made some code #ifdef GHCI, so that it will compile without GHCI enabled.
-
- 18 Jul, 2001 1 commit
-
-
rrt authored
Add support for Hugs's :info command. Doesn't work yet, but shouldn't interfere with anything else. Some of the files touched are just to correct out-of-date comments. Highlights are: hscThing: like hscStmt, but just gets info about a single identifier cmInfoThing: exposes hscThing's functionality to the outside world
-
- 17 Jul, 2001 1 commit
-
-
sof authored
w
-
- 16 Jul, 2001 1 commit
-
-
sof authored
hscStmt: track changes made to the TC entry points typecheckExpr, typecheckStmt
-
- 13 Jul, 2001 1 commit
-
-
simonpj authored
------------------------------------ Tidy up the "syntax rebinding" story ------------------------------------ I found a bug in the code that dealt with re-binding implicit numerical syntax: literals (fromInteger/fromRational) negation (negate) n+k patterns (minus) This is triggered by the -fno-implicit-prelude flag, and it used to be handled via the PrelNames.SyntaxMap. But I found a nicer way to do it that involves much less code, and doesn't have the bug. The explanation is with RnEnv.lookupSyntaxName
-
- 12 Jul, 2001 1 commit
-
-
simonpj authored
-------------------------------------------- Fix another bug in the squash-newtypes story. -------------------------------------------- [This one was spotted by Marcin, and is now enshrined in test tc130.] The desugarer straddles the boundary between the type checker and Core, so it sometimes needs to look through newtypes/implicit parameters and sometimes not. This is really a bit painful, but I can't think of a better way to do it. The only simple way to fix things was to pass a bit more type information in the HsExpr type, from the type checker to the desugarer. That led to the non-local changes you can see. On the way I fixed one other thing. In various HsSyn constructors there is a Type that is bogus (bottom) before the type checker, and filled in with a real type by the type checker. In one place it was a (Maybe Type) which was Nothing before, and (Just ty) afterwards. I've defined a type synonym HsTypes.PostTcType for this, and a named bottom value HsTypes.placeHolderType to use when you want the bottom value.
-
- 15 Jun, 2001 1 commit
-
-
simonpj authored
Some tidying up * Remove CmStaticInfo - GhciMode moves to HscTypes - The package stuff moves to new module main/Packages.lhs [put any package-related stuff in the new module] * Add Outputable.docToSDoc
-
- 01 Jun, 2001 1 commit
-
-
apt authored
added support for emiting external core format
-
- 31 May, 2001 1 commit
-
-
simonmar authored
- add -hidir flag to control the destination for .hi files when doing multiple compilations (matches -odir). - change the ml_hi_file component of ModuleLocation from Maybe FilePath to FilePath. We never made use of its Maybeness. - clear out some unused code from the Hsc phase of run_phase and clean up a bit. Fix a bug with the -ohi option at the same time (I don't think it works in 5.xx.x before this patch).
-
- 22 May, 2001 1 commit
-
-
simonpj authored
------------------------------------------- Towards generalising 'foreign' declarations ------------------------------------------- This is a first step towards generalising 'foreign' declarations to handle langauges other than C. Quite a lot of files are touched, but nothing has really changed. Everything should work exactly as before. But please be on your guard for ccall-related bugs. Main things Basic data types: ForeignCall.lhs ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Remove absCSyn/CallConv.lhs * Add prelude/ForeignCall.lhs. This defines the ForeignCall type and its variants * Define ForeignCall.Safety to say whether a call is unsafe or not (was just a boolean). Lots of consequential chuffing. * Remove all CCall stuff from PrimOp, and put it in ForeignCall Take CCallOp out of the PrimOp type (where it was always a glitch) ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Add IdInfo.FCallId variant to the type IdInfo.GlobalIdDetails, along with predicates Id.isFCallId, Id.isFCallId_maybe * Add StgSyn.StgOp, to sum PrimOp with FCallOp, because it *is* useful to sum them together in Stg and AbsC land. If nothing else, it minimises changes. Also generally rename "CCall" stuff to "FCall" where it's generic to all foreign calls.
-
- 01 May, 2001 1 commit
-
-
simonmar authored
Add some {-# SCC #-} annotations, and fix a space leak.
-
- 26 Mar, 2001 1 commit
-
-
simonmar authored
Simplify the foreign-export stub processing. - DynFlags now has fields for the stub.h and stub.c filenames, for consistency with the normal hsc output file name. - codeOutput puts the stubs into these files rather than dreaming up new temporary names for them - now we don't have to move the stubs into the right place in DriverPipeline. - we do however have to inject the correct #includes into the stub.c file when it is generated: I'm now injecting the same includes as the .hc file gets plus "RtsAPI.h", which is probably more correct than the hacky hardcoded "Stg.h" we had before.
-
- 19 Mar, 2001 2 commits
-
-
simonpj authored
------------------------------- PS to: Improve orphan-module resolution ------------------------------- {This comment got missed out of the previous commit.} I also moved mkFinalIface from HscMain to MkIface, where it is much tidier. (This is related, because it's mkFinalIface that now sets mi_orphan.)
-
simonpj authored
------------------------------- Improve orphan-module resolution ------------------------------- Consider the following rule (and there are lots of these in the Prelude): fromIntegral T = fromIntegral_T where T is defined in the module being compiled. is an orphan. Of course it isn't, an declaring it an orphan would make the whole module an orphan module, which is bad. This commit arranges to determine orphan rules, and the orphan-hood of a module, much later than before. (Before mi_orphan was set by the renamer, now it is set by MkIface.)
-
- 15 Mar, 2001 1 commit
-
-
simonmar authored
Do a better job of telling the user whether we're interpreting a module or using an existing object file. eg. Main> :load A Skipping D ( D.hs, D.o ) Compiling C ( C.hs, interpreted ) Skipping B ( B.hs, B.o ) Compiling Main ( A.hs, interpreted ) Main>
-
- 14 Mar, 2001 1 commit
-
-
sewardj authored
Don't try and do `take' of a negative number in compMsg. The Golden Lemon award for 2001 goes to <name_deleted_to_protect_the_guilty_party>.
-
- 13 Mar, 2001 2 commits
-
-
simonmar authored
fix up for GHCi
-
simonmar authored
Some rearrangements that Simon & I have been working on recently: - CoreSat is now CorePrep, and is a general "prepare-for-code- generation" pass. It does cloning, saturation of constructors & primops, A-normal form, and a couple of other minor fiddlings. - CoreTidy no longer does cloning, and minor fiddlings. It doesn't need the unique supply any more, so that's removed. - CoreToStg now collects CafInfo and the list of CafRefs for each binding. The SRT pass is much simpler now. - IdInfo now has a CgInfo field for "code generator info". It currently contains arity (the actual code gen arity which affects the calling convention as opposed to the ArityInfo which is a measure of how many arguments the Id can be applied to before it does any work), and CafInfo. Previously we overloaded the ArityInfo field to contain both codegen arity and simplifier arity. Things are cleaner now. - CgInfo is collected by CoreToStg, and passed back into CoreTidy in a loop. The compiler will complain rather than going into a black hole if the CgInfo is pulled on too early. - Worker info in an interface file now comes with arity info attached. Previously the main arity info was overloaded for this purpose, but it lead to a few hacks in the compiler, this tidies things up somewhat. Bottom line: we removed several fragilities, and tidied up a number of things. Code size should be smaller, but we'll see...
-
- 08 Mar, 2001 2 commits
-
-
qrczak authored
s/setIdGlobalDetails/sedGlobalIdDetails/, and import it.
-
simonpj authored
-------------------- A major hygiene pass -------------------- 1. The main change here is to Move what was the "IdFlavour" out of IdInfo, and into the varDetails field of a Var It was a mess before, because the flavour was a permanent attribute of an Id, whereas the rest of the IdInfo was ephemeral. It's all much tidier now. Main places to look: Var.lhs Defn of VarDetails IdInfo.lhs Defn of GlobalIdDetails The main remaining infelicity is that SpecPragmaIds are right down in Var.lhs, which seems unduly built-in for such an ephemeral thing. But that is no worse than before. 2. Tidy up the HscMain story a little. Move mkModDetails from MkIface into CoreTidy (where it belongs more nicely) This was partly forced by (1) above, because I didn't want to make DictFun Ids into a separate kind of Id (which is how it was before). Not having them separate means we have to keep a list of them right through, rather than pull them out of the bindings at the end. 3. Add NameEnv as a separate module (to join NameSet). 4. Remove unnecessary {-# SOURCE #-} imports from FieldLabel.
-
- 06 Mar, 2001 1 commit
-
-
rrt authored
Use TMPDIR, not /tmp.
-
- 02 Mar, 2001 1 commit
-
-
simonmar authored
Fix :type again, by resurrecting typecheckExpr. Now the expression doesn't get the monomorphism restriction applied to it.
-
- 01 Mar, 2001 1 commit
-
-
simonmar authored
GHCi fixes: - expressions are now compiled in a pseudo-module "$Interactive", which avoids some problems with storage of demand-loaded declarations. - compilation manager now detects when it needs to read the interace for a module, even if it is already compiled. GHCi never demand-loads interfaces now. - (from Simon PJ) fix a problem with the recompilation checker, which meant that modules were sometimes not recompiled when they should have been. - ByteCodeGen/Link: move linker related stuff into ByteCodeLink.
-
- 28 Feb, 2001 1 commit
-
-
simonpj authored
Import/formatting wibbles
-
- 27 Feb, 2001 1 commit
-
-
simonmar authored
Need to tidy the expression before compiling it, purely in order to clone the ids in case of clashes.
-
- 26 Feb, 2001 3 commits
-
-
simonmar authored
Update the interactive context in cmRunStmt rather than hscMain.
-
simonmar authored
- message wibbles - in one-shot mode, make sure the interface file follows the module rather than the filename of the source.
-
simonmar authored
Implement do-style bindings on the GHCi command line. The syntax for a command-line is exactly that of a do statement, with the following meanings: - `pat <- expr' performs expr, and binds each of the variables in pat. - `let pat = expr; ...' binds each of the variables in pat, doesn't do any evaluation - `expr' behaves as `it <- expr' if expr is IO-typed, or `let it = expr' followed by `print it' otherwise.
-
- 23 Feb, 2001 1 commit
-
-
simonmar authored
Fix a problem with duplicate instances appearing in the interpreter after reloading modules.
-
- 20 Feb, 2001 2 commits
-
-
qrczak authored
Apply tweaks needed to let this compile: remove syn_map argument from typecheckExpr in HscMain, import PrelNum.fromInt to modules which use integer literals with -fno-implicit-prelude flag. It crashes later, on Directory.hs: ghc: panic! (the `impossible' happened): srtExpr I'm not sure if resolving numeric literals to top-level definitions of fromInt/fromInteger with -fno-implicit-prelude is a good idea. Using names from whatever module is called Prelude would be IMHO better, probably when -fglasgow-exts is given. Prel* modules themselves would import PrelNum as Prelude. Both schemes break for fromInt, which is non-standard and by default it's visible neither at the top level nor in the Prelude module. My proposal for dealing with it is as follows (assuming that fromInteger is taken from the module locally called Prelude instead of the top level): when the standard Prelude is used, take fromInt from PrelNum; when a Prelude replacement is used, use fromInt from it if available, otherwise use its fromInteger instead. That way Prelude replacements can ignore this non-standard extension and get the expected behavior, or they can also choose to use this extension (in a way compatible with Haskell implementations which allow to replace Prelude but don't have fromInt).
-
simonpj authored
Back end changes [CgExpr, ClosureInfo, CoreSat, CoreUtils, ~~~~~~~~~~~~~~~~ CmdLineOpts, HscMain, CoreToStg, StgSyn] * Move CoreTidy and interface-file dumping *before* CoreSat. In this way interface files are not in A-normal form, so they are less bulky, and a bit easier to use as input to the optimiser. So now CoreSat is regarded as a pre-pass to CoreToStg. Since CoreTidy pins on utterly-final IdInfo, CoreSat has to be very careful not to change the arity of any function. * CoreSat uses OrdList instead of lists to collect floating binds This in turn meant I could simplify the FloatingBind type a bit * Greatly simplfy the StgBinderInfo data type. It was gathering far more information than we needed. * Add a flag -fkeep-stg-types, which keeps type abstractions and applications in STG code, for the benefit of code generators that are typed; notably the .NET ILX code generator.
-
- 14 Feb, 2001 1 commit
-
-
simonmar authored
Tidy the type we get back from typecheckExpr.
-