summaryrefslogtreecommitdiff
path: root/compiler/cmm/CmmLayoutStack.hs
Commit message (Collapse)AuthorAgeFilesLines
* BlockId: remove BlockMap and BlockSet synonymsMichal Terepeta2016-12-081-18/+18
| | | | | | | | | | | | | | | | | | | | This continues removal of `BlockId` module in favor of Hoopl's `Label`. Most of the changes here are mechanical, apart from the orphan `Outputable` instances for `LabelMap` and `LabelSet`. For now I've moved them to `cmm/Hoopl`, since it's already trying to manage all imports from Hoopl (to avoid any collisions). Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com> Test Plan: validate Reviewers: bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2800
* Use newBlockId instead of newLabelCBen Gamari2016-11-291-2/+1
| | | | | | | | | | | | | | | This seems like a clearer name and the fewer functions that one needs to remember, the better. Test Plan: validate Reviewers: austin, simonmar, michalt Reviewed By: simonmar, michalt Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2735
* Remove StgRubbishArg and CmmArgÖmer Sinan Ağacan2016-08-101-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The idea behind adding special "rubbish" arguments was in unboxed sum types depending on the tag some arguments are not used and we don't want to move some special values (like 0 for literals and some special pointer for boxed slots) for those arguments (to stack locations or registers). "StgRubbishArg" was an indicator to the code generator that the value won't be used. During Stg-to-Cmm we were then not generating any move or store instructions at all. This caused problems in the register allocator because some variables were only initialized in some code paths. As an example, suppose we have this STG: (after unarise) Lib.$WT = \r [dt_sit] case case dt_sit of { Lib.F dt_siv [Occ=Once] -> (#,,#) [1# dt_siv StgRubbishArg::GHC.Prim.Int#]; Lib.I dt_siw [Occ=Once] -> (#,,#) [2# StgRubbishArg::GHC.Types.Any dt_siw]; } of dt_six { (#,,#) us_giC us_giD us_giE -> Lib.T [us_giC us_giD us_giE]; }; This basically unpacks a sum type to an unboxed sum with 3 fields, and then moves the unboxed sum to a constructor (`Lib.T`). This is the Cmm for the inner case expression (case expression in the scrutinee position of the outer case): ciN: ... -- look at dt_sit's tag if (_ciT::P64 != 1) goto ciS; else goto ciR; ciS: -- Tag is 2, i.e. Lib.F _siw::I64 = I64[_siu::P64 + 6]; _giE::I64 = _siw::I64; _giD::P64 = stg_RUBBISH_ENTRY_info; _giC::I64 = 2; goto ciU; ciR: -- Tag is 1, i.e. Lib.I _siv::P64 = P64[_siu::P64 + 7]; _giD::P64 = _siv::P64; _giC::I64 = 1; goto ciU; Here one of the blocks `ciS` and `ciR` is executed and then the execution continues to `ciR`, but only `ciS` initializes `_giE`, in the other branch `_giE` is not initialized, because it's "rubbish" in the STG and so we don't generate an assignment during code generator. The code generator then panics during the register allocations: ghc-stage1: panic! (the 'impossible' happened) (GHC version 8.1.20160722 for x86_64-unknown-linux): LocalReg's live-in to graph ciY {_giE::I64} (`_giD` is also "rubbish" in `ciS`, but it's still initialized because it's a pointer slot, we have to initialize it otherwise garbage collector follows the pointer to some random place. So we only remove assignment if the "rubbish" arg has unboxed type.) This patch removes `StgRubbishArg` and `CmmArg`. We now always initialize rubbish slots. If the slot is for boxed types we use the existing `absentError`, otherwise we initialize the slot with literal 0. Reviewers: simonpj, erikd, austin, simonmar, bgamari Reviewed By: erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2446
* CmmLayoutStack: Minor simplificationÖmer Sinan Ağacan2016-08-041-2/+2
|
* Implement unboxed sum primitive typeÖmer Sinan Ağacan2016-07-211-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. - Simon Peyton Jones reviewed this patch many times, wrote some code, and helped with debugging. Reviewers: bgamari, alanz, goldfire, RyanGlScott, simonpj, austin, simonmar, hvr, erikd Reviewed By: simonpj Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259
* Document some codegen nondeterminismBartosz Nitka2016-07-071-4/+8
| | | | | | | | | Bit-for-bit reproducible binaries are not a goal for now, so this is just marking places that could be a problem. Doing this will allow eltsUFM to be removed and will leave only nonDetEltsUFM. GHC Trac: #4012
* Fix the removal of unnecessary stack checksJonas Scholl2016-02-091-6/+21
| | | | | | | | | | | | | | | | | | | | The module CmmLayoutStack removes stack checks if a function does not use stack space. However, it can only recognize checks of the form Sp < SpLim. However, these checks get sometimes rewritten to Sp >= SpLim (with both branches swapped), so we better recognize these checks too. Test Plan: ./validate Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1881 GHC Trac Issues: #11533
* Replace calls to `ptext . sLit` with `text`Jan Stolarek2016-01-181-2/+2
| | | | | | | | | | | | | | | | | | | | Summary: In the past the canonical way for constructing an SDoc string literal was the composition `ptext . sLit`. But for some time now we have function `text` that does the same. Plus it has some rules that optimize its runtime behaviour. This patch takes all uses of `ptext . sLit` in the compiler and replaces them with calls to `text`. The main benefits of this patch are clener (shorter) code and less dependencies between module, because many modules now do not need to import `FastString`. I don't expect any performance benefits - we mostly use SDocs to report errors and it seems there is little to be gained here. Test Plan: ./validate Reviewers: bgamari, austin, goldfire, hvr, alanz Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1784
* StgCmmForeign: Push local register creation into code generationBen Gamari2016-01-051-10/+5
| | | | | | | | | | | | | | | | | | | | | | | The interfaces to {save,load}ThreadState were quite messy due to the need to pass in local registers (produced with draws from a unique supply) since they were used from both FCode and UniqSM. This, however, is entirely unnecessary as we already have an abstraction to capture this effect: MonadUnique. Use it. This is part of an effort to properly represent stack unwinding information for foreign calls. Test Plan: validate Reviewers: austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1733
* Drop pre-AMP compatibility CPP conditionalsHerbert Valerio Riedel2015-12-311-2/+0
| | | | | | | | | | | | Since GHC 8.1/8.2 only needs to be bootstrap-able by GHC 7.10 and GHC 8.0 (and GHC 8.2), we can now finally drop all that pre-AMP compatibility CPP-mess for good! Reviewers: austin, goldfire, bgamari Subscribers: goldfire, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1724
* Add kind equalities to GHC.Richard Eisenberg2015-12-111-4/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule.
* Rearrange error msgs and add section markers (Trac #11014).Evan Laforge2015-11-241-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This puts the "Relevant bindings" section at the end. It uses a TcErrors.Report Monoid to divide messages by importance and then mappends them together. This is not the most efficient way since there are various intermediate Reports and list appends, but it probably doesn't matter since error messages shouldn't get that large, and are usually prepended. In practice, everything is `important` except `relevantBindings`, which is `supplementary`. ErrMsg's errMsgShortDoc and errMsgExtraInfo were extracted into ErrDoc, which has important, context, and suppelementary fields. Each of those three sections is marked with a bullet character, '•' on unicode terminals and '*' on ascii terminals. Since this breaks tons of tests, I also modified testlib.normalise_errmsg to strip out '•'s. --- Additional notes: To avoid prepending * to an empty doc, I needed to filter empty docs. This seemed less error-prone than trying to modify everyone who produces SDoc to instead produce Maybe SDoc. So I added `Outputable.isEmpty`. Unfortunately it needs a DynFlags, which is kind of bogus, but otherwise I think I'd need another Empty case for SDoc, and then it couldn't be a newtype any more. ErrMsg's errMsgShortString is only used by the Show instance, which is in turn only used by Show HscTypes.SourceError, which is in turn only needed for the Exception instance. So it's probably possible to get rid of errMsgShortString, but that would a be an unrelated cleanup. Fixes #11014. Test Plan: see above Reviewers: austin, simonpj, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: simonpj, nomeata, thomie Differential Revision: https://phabricator.haskell.org/D1427 GHC Trac Issues: #11014
* Support multiple debug output levelsBen Gamari2015-11-231-1/+1
| | | | | | | | | We now only strip block information from DebugBlocks when compiling with `-g1`, intended to be used when only minimal debug information is desired. `-g2` is assumed when `-g` is passed without any integer argument. Differential Revision: https://phabricator.haskell.org/D1281
* Annotate CmmBranch with an optional likely targetSimon Marlow2015-09-231-1/+1
| | | | | | | | | | | | | | | | | Summary: This allows the code generator to give hints to later code generation steps about which branch is most likely to be taken. Right now it is only taken into account in one place: a special case in CmmContFlowOpt that swapped branches over to maximise the chance of fallthrough, which is now disabled when there is a likelihood setting. Test Plan: validate Reviewers: austin, simonpj, bgamari, ezyang, tibbe Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1273
* Add unwind information to CmmPeter Wortmann2014-12-161-0/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Unwind information allows the debugger to discover more information about a program state, by allowing it to "reconstruct" other states of the program. In practice, this means that we explain to the debugger how to unravel stack frames, which comes down mostly to explaining how to find their Sp and Ip register values. * We declare yet another new constructor for CmmNode - and this time there's actually little choice, as unwind information can and will change mid-block. We don't actually make use of these capabilities, and back-end support would be tricky (generate new labels?), but it feels like the right way to do it. * Even though we only use it for Sp so far, we allow CmmUnwind to specify unwind information for any register. This is pretty cheap and could come in useful in future. * We allow full CmmExpr expressions for specifying unwind values. The advantage here is that we don't have to make up new syntax, and can e.g. use the WDS macro directly. On the other hand, the back-end will now have to simplify the expression until it can sensibly be converted into DWARF byte code - a process which might fail, yielding NCG panics. On the other hand, when you're writing Cmm by hand you really ought to know what you're doing. (From Phabricator D169)
* Tick scopesPeter Wortmann2014-12-161-12/+13
| | | | | | | | | | | | | | | | | | | | | | This patch solves the scoping problem of CmmTick nodes: If we just put CmmTicks into blocks we have no idea what exactly they are meant to cover. Here we introduce tick scopes, which allow us to create sub-scopes and merged scopes easily. Notes: * Given that the code often passes Cmm around "head-less", we have to make sure that its intended scope does not get lost. To keep the amount of passing-around to a minimum we define a CmmAGraphScoped type synonym here that just bundles the scope with a portion of Cmm to be assembled later. * We introduce new scopes at somewhat random places, aligning with getCode calls. This works surprisingly well, but we might have to add new scopes into the mix later on if we find things too be too coarse-grained. (From Phabricator D169)
* Fix Trac #9815Simon Peyton Jones2014-11-211-3/+3
| | | | | | | | | | | Dot-dot record-wildcard notation is simply illegal for constructors without any named fields, but that was neither documented nor checked. This patch does so - Make the check in RnPat - Add test T9815 - Fix CmmLayoutStack which was using the illegal form (!) - Document in user manual
* Per-thread allocation counters and limitsSimon Marlow2014-11-121-3/+6
| | | | | | | | This reverts commit f0fcc41d755876a1b02d1c7c79f57515059f6417. New changes: now works on 32-bit platforms too. I added some basic support for 64-bit subtraction and comparison operations to the x86 NCG.
* Make Applicative a superclass of MonadAustin Seipp2014-09-091-0/+4
| | | | | | | | | | | | | | | | | | | | | Summary: This includes pretty much all the changes needed to make `Applicative` a superclass of `Monad` finally. There's mostly reshuffling in the interests of avoid orphans and boot files, but luckily we can resolve all of them, pretty much. The only catch was that Alternative/MonadPlus also had to go into Prelude to avoid this. As a result, we must update the hsc2hs and haddock submodules. Signed-off-by: Austin Seipp <austin@well-typed.com> Test Plan: Build things, they might not explode horribly. Reviewers: hvr, simonmar Subscribers: simonmar Differential Revision: https://phabricator.haskell.org/D13
* Fix reference to noteSimon Marlow2014-08-011-1/+1
|
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-151-1/+1
| | | | | | | | | | | | | | | | | | In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
* Revert "Per-thread allocation counters and limits"Simon Marlow2014-05-041-6/+3
| | | | | | | | Problems were found on 32-bit platforms, I'll commit again when I have a fix. This reverts the following commits: 54b31f744848da872c7c6366dea840748e01b5cf b0534f78a73f972e279eed4447a5687bd6a8308e
* Per-thread allocation counters and limitsSimon Marlow2014-05-021-3/+6
| | | | | | | | | | | | | | | | | | | | | | | This tracks the amount of memory allocation by each thread in a counter stored in the TSO. Optionally, when the counter drops below zero (it counts down), the thread can be sent an asynchronous exception: AllocationLimitExceeded. When this happens, given a small additional limit so that it can handle the exception. See documentation in GHC.Conc for more details. Allocation limits are similar to timeouts, but - timeouts use real time, not CPU time. Allocation limits do not count anything while the thread is blocked or in foreign code. - timeouts don't re-trigger if the thread catches the exception, allocation limits do. - timeouts can catch non-allocating loops, if you use -fno-omit-yields. This doesn't work for allocation limits. I couldn't measure any impact on benchmarks with these changes, even for nofib/smp.
* Nuke dead codeJan Stolarek2014-02-011-24/+5
| | | | | | | | | | | | | * CmmRewriteAddignments module was replaced by CmmSink a long time ago. That module is now available at https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/Hoopl/Examples wiki page. * removeDeadAssignments function was not used and it was also moved to the above page. * I also nuked some commented out debugging code that was not used for 1,5 year.
* Typo in commentGabor Greif2014-01-161-1/+1
|
* Documentation on the stack layout algorithmSimon Marlow2014-01-161-5/+94
|
* More comments about stack layoutSimon Peyton Jones2013-10-181-5/+16
|
* Clarify comments and liberalise stack-check optimisation slightlySimon Peyton Jones2013-10-181-9/+10
| | | | | | The only substantive change here is to change "==" into ">=" in the Note [Always false stack check] code. This is semantically correct, but won't have any practical impact.
* Optimise stack checks that are always falseJan Stolarek2013-10-171-12/+12
| | | | | Fix a bug introduced in 94125c97e49987e91fa54da6c86bc6d17417f5cf. See Note [Always false stack check]
* Generate (old + 0) instead of Sp in stack checksJan Stolarek2013-10-161-10/+2
| | | | | | | | | | | | | | | | | | | | When compiling a function we can determine how much stack space it will use. We therefore need to perform only a single stack check at the beginning of a function to see if we have enough stack space. Instead of referring directly to Sp - as we used to do in the past - the code generator uses (old + 0) in the stack check. Stack layout phase turns (old + 0) into Sp. The idea here is that, while we need to perform only one stack check for each function, we could in theory place more stack checks later in the function. They would be redundant, but not incorrect (in a sense that they should not change program behaviour). We need to make sure however that a stack check inserted after incrementing the stack pointer checks for a respectively smaller stack space. This would not be the case if the code generator produced direct references to Sp. By referencing (old + 0) we make sure that we always check for a correct amount of stack: when converting (old + 0) to Sp the stack layout phase takes into account changes already made to stack pointer. The idea for this change came from observations made while debugging #8275.
* Improve sinking passJan Stolarek2013-09-121-10/+11
| | | | | | | | | | | | | | | | | | | | This commit does two things: * Allows duplicating of global registers and literals by inlining them. Previously we would only inline global register or literal if it was used only once. * Changes method of determining conflicts between a node and an assignment. New method has two advantages. It relies on DefinerOfRegs and UserOfRegs typeclasses, so if a set of registers defined or used by a node should ever change, `conflicts` function will use the changed definition. This definition also catches more cases than the previous one (namely CmmCall and CmmForeignCall) which is a step towards making it possible to run sinking pass before stack layout (currently this doesn't work). This patch also adds a lot of comments that are result of about two-week long investigation of how sinking pass works and why it does what it does.
* Fix a bug in stack layout with safe foreign calls (#8083)Simon Marlow2013-07-241-7/+8
| | | | | | | We weren't properly tracking the number of stack arguments in the continuation of a foreign call. It happened to work when the continuation was not a join point, but when it was a join point we were using the wrong amount of stack fixup.
* In CMM, only allow foreign calls to labels, not arbitrary expressionsIan Lynagh2013-04-241-2/+2
| | | | | | | | | I'm not sure if we want to make this change permanently, but for now it fixes the unreg build. I've also removed some redundant special-case code that generated prototypes for foreign functions. The standard pprTempAndExternDecls now generates them.
* Tidy up: move info-table related stuff to CmmInfoSimon Marlow2013-01-231-1/+1
| | | | Prep for #709
* Attach global register liveness info to Cmm procedures.Geoffrey Mainland2012-10-301-2/+2
| | | | | | | All Cmm procedures now include the set of global registers that are live on procedure entry, i.e., the global registers used to pass arguments to the procedure. Only global registers that are use to pass arguments are included in this list.
* Generalize register sets and liveness calculations.Geoffrey Mainland2012-10-301-6/+6
| | | | | | We would like to calculate register liveness for global registers as well as local registers, so this patch generalizes the existing infrastructure to set the stage.
* Add a type signature needed when using GADTsSimon Peyton Jones2012-10-121-0/+1
|
* Produce new-style Cmm from the Cmm parserSimon Marlow2012-10-081-3/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The main change here is that the Cmm parser now allows high-level cmm code with argument-passing and function calls. For example: foo ( gcptr a, bits32 b ) { if (b > 0) { // we can make tail calls passing arguments: jump stg_ap_0_fast(a); } return (x,y); } More details on the new cmm syntax are in Note [Syntax of .cmm files] in CmmParse.y. The old syntax is still more-or-less supported for those occasional code fragments that really need to explicitly manipulate the stack. However there are a couple of differences: it is now obligatory to give a list of live GlobalRegs on every jump, e.g. jump %ENTRY_CODE(Sp(0)) [R1]; Again, more details in Note [Syntax of .cmm files]. I have rewritten most of the .cmm files in the RTS into the new syntax, except for AutoApply.cmm which is generated by the genapply program: this file could be generated in the new syntax instead and would probably be better off for it, but I ran out of enthusiasm. Some other changes in this batch: - The PrimOp calling convention is gone, primops now use the ordinary NativeNodeCall convention. This means that primops and "foreign import prim" code must be written in high-level cmm, but they can now take more than 10 arguments. - CmmSink now does constant-folding (should fix #7219) - .cmm files now go through the cmmPipeline, and as a result we generate better code in many cases. All the object files generated for the RTS .cmm files are now smaller. Performance should be better too, but I haven't measured it yet. - RET_DYN frames are removed from the RTS, lots of code goes away - we now have some more canned GC points to cover unboxed-tuples with 2-4 pointers, which will reduce code size a little.
* Misc tidyupSimon Marlow2012-09-241-3/+3
|
* add a missing entryCodeSimon Marlow2012-09-201-1/+3
|
* Move wORD_SIZE into platformConstantsIan Lynagh2012-09-161-41/+43
|
* Pass DynFlags down to wordWidthIan Lynagh2012-09-121-11/+11
|
* Pass DynFlags down to gcWordIan Lynagh2012-09-121-2/+2
|
* Pass DynFlags down to bWordIan Lynagh2012-09-121-30/+33
| | | | | | I've switched to passing DynFlags rather than Platform, as (a) it's simpler to not have to extract targetPlatform in so many places, and (b) it may be useful to have DynFlags around in future.
* Cleanup: add mkIntExpr and zeroExpr utilsSimon Marlow2012-08-311-3/+3
|
* small cleanupSimon Marlow2012-08-071-5/+2
|
* Define callerSaves for all platformsIan Lynagh2012-08-071-1/+1
| | | | | | | | This means that we now generate the same code whatever platform we are on, which should help avoid changes on one platform breaking the build on another. It's also another step towards full cross-compilation.
* Add "Unregisterised" as a field in the settings fileIan Lynagh2012-08-071-1/+1
| | | | | | To explicitly choose whether you want an unregisterised build you now need to use the "--enable-unregisterised"/"--disable-unregisterised" configure flags.
* Continue by jumping to the top-of-stack after a safe foreign callSimon Marlow2012-08-061-5/+7
|
* No need to do removeDeadAssignments, just do cmmLiveness insteadSimon Marlow2012-08-021-1/+7
|