| Commit message (Collapse) | Author | Age | Files | Lines |
| |
|
|
| |
Merge backend-hacking-branch onto HEAD. Yay!
|
| |
|
|
|
|
|
| |
PowerPC Linux support for registerised compilation and native code
generation. (object splitting and GHCi are still unsupported).
Code for other platforms is not affected, so MERGE TO STABLE.
|
| |
|
|
|
|
| |
PowerPC NCG bugfix: 2-byte data objects should be .short, not .byte
MERGE TO STABLE
|
| |
|
|
|
|
|
| |
pprInstr{PPC}: insist on xori,ori,andi being fed non-negative immediate values.
GAS is barfing on neg. values.
[ Don't have access to a PPC box right now to really test the change, so beware.]
|
| |
|
|
|
| |
change trailing comments on #else/#endif lines to C style to avoid
warnings from gcc 3.3's preprocessor.
|
| |
|
|
| |
Prune imports
|
| |
|
|
|
|
|
|
|
| |
Fix two bugs in the PowerPC NCG:
1. it generated a 'subfi' (subtract from with immediate) instruction,
which doesn't exist in the PowerPC architecture.
2. didn't correctly handle switch tables (test case cg048.hs).
MERGE TO STABLE
|
| |
|
|
| |
support many more MachOps in the PowerPC NCG
|
| |
|
|
|
|
|
|
|
|
| |
Mac OS X:
Add support for dynamic linker "symbol stubs". For every function that might
be imported from a dynamic library, we have to generate a short piece of
assembly code.
Extend the NatM monad to keep track of the list of imports (for which stubs
will be generated later).
Fix a bug concerning 64 bit ints (hi and low words were swapped in one place).
|
| |
|
|
|
|
|
|
|
|
|
| |
The Native Code Generator for PowerPC.
Still to be done:
*) Proper support of Floats and Doubles
currently it seems to work, but it's just guesswork.
*) Some missing operations, only needed for -O, AFAICT.
*) Mach-O dynamic linker stub generation.
(can't import foreign functions from dynamic libraries,
and it might fail for big programs)
|
| |
|
|
|
|
|
| |
Finally separate the compiler from hslibs.
Mainly import wibbles, and use the new POSIX library when
bootstrapping.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
|
| |
Fix syntax error in printing indirect calls in sparc assembly.
|
| |
|
|
| |
sparc NCG fixes for f-i-dynamic.
|
| |
|
|
|
| |
Teach the NCG how to do f-i-dynamic. Nothing unexpected.
sparc-side now needs fixing.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
Generate floating-point comparisons on x86 which deal with NaNs in what
I assume is an IEEE854 compliant fashion. For
== >= > <= <
if either arg is a NaN, produce False, and for
/=
if either arg is a NaN, produce True.
This is the behaviour that gcc has, by default.
Requires some ultramagical x86 code frags to be emitted. A big comment
in PprMach explains how it works.
|
| |
|
|
| |
Correctly handle signed vs unsigned integer division on x86.
|
| |
|
|
|
|
|
|
|
| |
Sparc NCG changes to track recent mulIntC# changes. The Prelude
can now finally be compiled with the sparc NCG.
Also (incidentally) emit sparc integer multiply insns directly
rather than calling a helper routine. Most sparcs should implement
them by now :)
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Get rid of multiple-result MachOps (MO_NatS_AddC, MO_NatS_SubC,
MO_NatS_MulC) which implement {add,sub,mul}IntC#. Supporting gunk
in the NCG disappears as a result.
Instead:
* {add,sub}IntC# are translated out during abstract C simplification,
turning into the xor-xor-invert-and-shift sequence previously defined
in PrimOps.h.
* mulIntC# is more difficult to get rid of portably. Instead we have
a new single-result PrimOp, mulIntMayOflo, with corresponding MachOp
MO_NatS_MulMayOflo. This tells you whether a W x W -> W signed
multiply might overflow, where W is the word size. When W=32, is
implemented by computing a 2W-long result. When W=64, we use the
previous approximation.
PrelNum.lhs' implementation of timesInteger changes slightly, to use
the new PrimOp.
|
| |
|
|
| |
Sparc NCG fixes for 16 bit loads/stores.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Make the sparc native code generator work again after recent
primop hackery.
* Track the change from PrimOp to MachOp at the Stix level.
* Teach the sparc insn selector how to generate 64-bit code.
* Fix various bogons in sparc {Int,Double,Float} <-> {Int,Double,Float}
conversions which only happened to generate correct code by
accident, so far.
* Synthesise BaseReg from &MainCapability.r on archs which do not
have BaseReg in a regiser (eg sparc :)
At the moment {add,sub,mul}Int# are not implemented. To be fixed.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add just enough infrastructure to the NCG that it can deal with simple 64-bit
code on 32-bit platforms. Main changes are:
* Addition of a simple 64-bit instruction selection fn iselExpr64 to MachCode.
This generates code for a 64-bit value and places the results into two
virtual registers, related thusly:
* Add a new type VRegUnique, which is used to label Stix virtual registers.
This type used to be a plain Unique, but that forces the assumption that
each Abstract-C level C temporary corresponds to exactly one Stix virtual
register, which is untrue when the C temporary is 64-bit sized on a
32-bit machine. In the new scheme, the Unique for the C temporary can
turn into two related VRegUniques, related by having the same embedded
unique.
* Made a start on 'target metrics' by adding ncg_target_is_32bits to the
end of Stix.lhs.
* Cleaned up numerous other gruesomenesses in the NCG which never came
to light before now. Got rid of MachMisc.sizeOf, which doesn't make
sense in a 64-bit setting, and replaced it by calls to
PrimRep.getPrimRepArrayElemSize, which, as far as I'm concerned, is the
definitive answer to the questio `How Big Is This PrimRep Really?'
Result: on x86-linux, at least, you can now compile the Entire Prelude
with -fasm! At this stage I cannot claim that the resulting code is
correct, but it's a start.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------
Translate out PrimOps at the AbstractC level
--------------------------------------------
This is the first in what might be a series of changes intended
to make GHC less dependent on its C back end. The main change is
to translate PrimOps into vanilla abstract C inside the compiler,
rather than having to duplicate that work in each code generation
route. The main changes are:
* A new type, MachOp, in compiler/absCSyn/MachOp.hs. A MachOp
is a primitive operation which we can reasonably expect the
native code generators to implement. The set is quite small
and unlikely to change much, if at all.
* Translations from PrimOps to MachOps, at the end of
absCSyn/AbsCUtils. This should perhaps be moved to a different
module, but it is hard to see how to do this without creating
a circular dep between it and AbsCUtils.
* The x86 insn selector has been updated to track these changes. The
sparc insn selector remains to be done.
As a result of this, it is possible to compile much more code via the
NCG than before. Almost all the Prelude can be compiled with it.
Currently it does not know how to do 64-bit code generation. Once
this is fixed, the entire Prelude should be compilable that way.
I also took the opportunity to clean up the NCG infrastructure.
The old Stix data type has been split into StixStmt (statements)
and StixExpr (now denoting values only). This removes a class
of impossible constructions and clarifies the NCG.
Still to do, in no particular order:
* String and literal lifting, currently done in the NCG at the top
of nativeGen/MachCode, should be done in the AbstractC flattener,
for the benefit of all targets.
* Further cleaning up of Stix assignments.
* Remove word-size dependency from Abstract C. (should be easy).
* Translate out MagicIds in the AbsC -> Stix translation, not
in the Stix constant folder. (!)
Testsuite failures caused by this:
* memo001 - fails (segfaults) for some unknown reason now.
* arith003 - wrong answer in gcdInt boundary cases.
* arith011 - wrong answer for shifts >= word size.
* cg044 - wrong answer for some FP boundary cases.
These should be fixed, but I don't think they are mission-critical for
anyone.
|
| |
|
|
|
|
|
|
|
|
|
| |
Updates to the native code generator following the changes to fix the
large block allocation bug, and changes to use the new
function-address cache in the register table to reduce code size.
Also: I changed the pretty-printing machinery for assembly code to use
Pretty rather than Outputable, since we don't make use of the styles
and it should improve performance. Perhaps the same should be done
for abstract C.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Add {intToInt,wordToWord}{8,16,32}# primops. WARNING: Not implemented
in ncg for Alpha and Sparc. But -O -fasm is not going to go far anyway
because of other omissions.
* Have full repertoire of 8,16,32-bit signed and unsigned MachMisc.Size
values. Again only x86 is fully supported. They are used for
{index,read,write}{Int,Word}{8,16,32}{OffAddr,Array}# and
{intToInt,wordToWord}{8,16,32}# primops.
* Have full repertoire of
{index,read,write}\
{Char,WideChar,Int,Word,Addr,Float,Double,StablePtr,\
{Int,Word}{8,16,32,64}}\
{OffAddr,Array} primops and appropriate instances.
There were various omissions in various places.
* Add {plus,minus,times}Word# primops to avoid so many Word# <-> Int#
coercions.
* Rewrite modules PrelWord and PrelInt almost from scratch.
* Simplify fromInteger and realToFrac rules. For each of
{Int,Word}{8,16,32} there is just a pair of fromInteger rules
replacing the source or target type with Int or Word. For
{Int,Word,Int64,Word64} there are rules from any to any.
Don't include rules which are derivable from inlining anyway,
e.g. those mentioning Integer. Old explicit coercions are simply
defined as appropriately typed fromInteger.
* Various old coercion functions marked as deprecated.
* Add instance Bits Int, and
instance {Show,Num,Real,Enum,Integral,Bounded,Ix,Read,Bits} Word.
* Coercions to sized integer types consistently behave as cutting the
right amount of bits from the infinite two-complement representation.
For example (fromIntegral (-1 :: Int8) :: Word64) == maxBound.
* ghc/tests/numeric/should_run/arith011 tests {Int,Word}64 and instance
Bits Int, and does not try to use overflowing toEnum. arith011.stdout
is not updated yet because of a problem I will tell about soon.
* Move fromInteger and realToFrac from Prelude to PrelReal.
Move fromInt from PrelNum to PrelReal and define as fromInteger.
Define toInt as fromInteger. fromInteger is the place to write
integer conversion rules for.
* Remove ArrayBase.newInitialisedArray, use default definition of
newArray instead.
* Bugs fixed:
- {quot,rem}Word# primop attributes.
- integerToInt64# for small negative values.
- {min,max}Bound::Int on 64-bit platforms.
- iShiftRL64#.
- Various Bits instances.
* Polishing:
- Use 'ppr' instead of 'pprPrimOp' and 'text . showPrimRep'.
- PrimRep.{primRepString,showPrimRepToUser} removed.
- MachMisc.sizeOf returns Int instead of Integer.
- Some eta reduction, parens, spacing, and reordering cleanups -
sorry, couldn't resist.
* Questions:
- Should iShiftRL and iShiftRL64 be removed? IMHO they should,
s/iShiftRA/iShiftR/, s/shiftRL/shiftR/. The behaviour on shifting
is a property of the signedness of the type, not the operation!
I haven't done this change.
|
| |
|
|
|
|
|
|
|
|
|
|
|
| |
Create PrimReps: {Int|Word}{8|16|32}Rep, for use in the native code
generator. And change the rep for character ops from Int8Rep to
Word8Rep. This fixes a bug in the sparc NCG in which chars loaded from
memory were incorrectly sign-extended to 32 bits. This problem
appeared when CharRep was turned into a 32-bit quantity, and
previous uses of it were replaced with Int8Rep, incorrectly, since
Int8Rep is signed. Also undo the kludge in the x86 section which
had (unknown to all) kept it working despite the change to Int8Rep.
sparc NCG now appears to work; hope the x86 side isn't now broken.
|
| |
|
|
|
| |
Put string literals in read-only data segments on platforms which
understand that.
|
| |
|
|
| |
Use ptext rather than text for doing constant data and strings.
|
| |
|
|
|
|
|
|
|
| |
Merge register allocation fix for idiv from before-ghci-branch:
1.59.2.1 +2 -37 fptools/ghc/compiler/nativeGen/MachCode.lhs
1.40.2.1 +15 -4 fptools/ghc/compiler/nativeGen/MachMisc.lhs
1.43.2.1 +20 -1 fptools/ghc/compiler/nativeGen/PprMach.lhs
1.26.2.1 +8 -15 fptools/ghc/compiler/nativeGen/RegAllocInfo.lhs
|
| |
|
|
| |
Dealing with instance-decl imports; and removing unnecessary imports
|
| |
|
|
| |
Make the back-end world compile.
|
| |
|
|
| |
Fix sparc NCG to track recent NCG switch table reg-alloc bug fix.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Make the register allocator deal properly with switch tables.
Previously, it didn't calculate the correct flow edges away from the
indirect jump (in fact it didn't reckon there were any flow edges
leaving it :) which makes a nonsense of the live variable analysis in
the branches.
A jump insn can now optionally be annotated with a list of destination
labels, and if so, the register allocator creates flow edges to all of
them.
Jump tables are now re-enabled. They remain disabled for 4.08.1,
since we aren't fixing the problem properly on that branch.
I assume this problem wasn't exposed by the old register allocator
because of the live-range-approximation hacks used in it. Since it
was undocumented, we'll never know.
Sparc builds will now break until I fix them.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Now Char, Char#, StgChar have 31 bits (physically 32).
"foo"# is still an array of bytes.
CharRep represents 32 bits (on a 64-bit arch too). There is also
Int8Rep, used in those places where bytes were originally meant.
readCharArray, indexCharOffAddr etc. still use bytes. Storable and
{I,M}Array use wide Chars.
In future perhaps all sized integers should be primitive types. Then
some usages of indexing primops scattered through the code could
be changed to then-available Int8 ones, and then Char variants of
primops could be made wide (other usages that handle text should use
conversion that will be provided later).
I/O and _ccall_ arguments assume ISO-8859-1. UTF-8 is internally used
for string literals (only).
Z-encoding is ready for Unicode identifiers.
Ranges of intlike and charlike closures are more easily configurable.
I've probably broken nativeGen/MachCode.lhs:chrCode for Alpha but I
don't know the Alpha assembler to fix it (what is zapnot?). Generally
I'm not sure if I've done the NCG changes right.
This commit breaks the binary compatibility (of course).
TODO:
* is* and to{Lower,Upper} in Char (in progress).
* Libraries for text conversion (in design / experiments),
to be plugged to I/O and a higher level foreign library.
* PackedString.
* StringBuffer and accepting source in encodings other than ISO-8859-1.
|
| |
|
|
| |
use Maybe.isJust instead of proprietary verison.
|
| |
|
|
| |
remove unused imports
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix up the sparc native code generator. Mostly dull stuff. Notable
changes:
* Cleaned up ccall mechanism for sparc somewhat.
* Rearranged assignment of sparc floating point registers (includes/MachRegs.h)
so the NCG's register allocator can handle the double-single pairing
issue without modification. Split VirtualRegF into VirtualRegF and
VirtualRegD, and split RcFloating into RcFloat and RcDouble. Net effect
is that there are now three register classes -- int, float and double,
and we pretend that sparc has some float and some double real regs.
* (A fix for all platforms): propagate MachFloats through as StFloats,
not StDoubles. Amazingly, until now literal floats had been converted
to and treated as doubles, including in ccalls.
|
| |
|
|
|
| |
Fix sparc bustage following latest round of NCG hacking (reg-alloc stuff).
Still won't work, but at least should compile again.
|
| |
|
|
|
|
| |
Emit slightly better x86 floating point code for comparisons, +, -,
* and /, in the common case where one of the source fake FP regs
is the same as the destination reg.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Major thing: new register allocator. Brief description follows.
Should correctly handle code with loops in, even though we don't
generate any such at the moment. A lot of comments. The previous
machinery for spilling is retained, as is the idea of a fast-and-easy
initial allocation attempt intended to deal with the majority of code
blocks (about 60% on x86) very cheaply. Many comments explaining
in detail how it works :-)
The Stix inliner is now on by default. Integer code seems to run
within about 1% of that -fvia-C. x86 fp code is significantly worse,
up to about 30% slower, depending on the amount of fp activity.
Minor thing: lazyfication of the top-level NCG plumbing, so that the
NCG doesn't require any greater residency than compiling to C, just a
bit more time. Created lazyThenUs and lazyMapUs for this purpose.
The new allocator is somewhat, although not catastophically, slower
than the old one. Fixing of the long-standing NCG space leak more
than makes up for it; overall hsc run-time is down about 5%, due to
significantly reduced GC time.
--------------------------------------------------------------------
Instructions are numbered sequentially, starting at zero.
A flow edge (FE) is a pair of insn numbers (MkFE Int Int) denoting
a possible flow of control from the first insn to the second.
The input to the register allocator is a list of instructions, which
mention Regs. A Reg can be a RealReg -- a real machine reg -- or a
VirtualReg, which carries a unique. After allocation, all the
VirtualReg references will have been converted into RealRegs, and
possibly some spill code will have been inserted.
The heart of the register allocator works in four phases.
1. (find_flow_edges) Calculate all the FEs for the code list.
Return them not as a [FE], but implicitly, as a pair of
Array Int [Int], being the successor and predecessor maps
for instructions.
2. (calc_liveness) Returns a FiniteMap FE RegSet. For each
FE, indicates the set of registers live on that FE. Note
that the set includes both RealRegs and VirtualRegs. The
former appear because the code could mention fixed register
usages, and we need to take them into account from the start.
3. (calc_live_range_sets) Invert the above mapping, giving a
FiniteMap Reg FeSet, indicating, for each virtual and real
reg mentioned in the code, which FEs it is live on.
4. (calc_vreg_to_rreg_mapping) For virtual reg, try and find
an allocatable real register for it. Each real register has
a "current commitment", indicating the set of FEs it is
currently live on. A virtual reg v can be assigned to
real reg r iff v's live-fe-set does not intersect with r's
current commitment fe-set. If the assignment is made,
v's live-fe-set is union'd into r's current commitment fe-set.
There is also the minor restriction that v and r must be of
the same register class (integer or floating).
Once this mapping is established, we simply apply it to the
input insns, and that's it.
If no suitable real register can be found, the vreg is mapped
to itself, and we deem allocation to have failed. The partially
allocated code is returned. The higher echelons of the allocator
(doGeneralAlloc and runRegAlloc) then cooperate to insert spill
code and re-run allocation, until a successful allocation is found.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Teach the NCG about the dereferencing and naming conventions to be
used when compiling for a DLLised world. Some cleanups on the way
too. The scheme is that
* All CLabels which are in different DLLs from the current module
will, via the renamer, already be such that labelDynamic returns
True for them.
* Redo the StixPrim/StixMacro stuff so that all references to symbols
in the RTS are via CLabels. That means that the usual labelDynamic
story can be used.
* When a label is printed in PprMach, labelDynamic is consulted, to
generate the __imp_ prefix if necessary.
* In MachCode.stmt2Instrs, selectively ask derefDLL to walk trees
before code generation and insert deferencing code around other-DLL
symbols.
* When generating Stix for SRTs, add 1 to other-DLL refs.
* When generating static closures, insert a zero word before
the _closure label.
|
| |
|
|
| |
pprInstr (ASCII True str): avoid escapery probs by translating into hex
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Many changes to improve the quality and correctness of generated code,
both for x86 and all-platforms. The intent is that the x86 NCG will
now be good enough for general use.
-- Add an almost-trivial Stix (generic) peephole optimiser, whose sole
purpose is elide assignments to temporaries used only once, in the
very next tree. This generates substantially better code for
conditionals on all platforms. Enhance Stix constant folding to
take advantage of the inlining.
The inlining presents subsequent insn selection phases with more
complex trees than would have previously been used to. This has
shown up several bugs in the x86 insn selectors, now fixed.
(assumptions that data size is Word, when could be Byte,
assumptions that an operand will always be in a temp reg, etc)
-- x86: Use the FLDZ and FLD1 insns.
-- x86: spill FP registers with 80-bit loads/stores so that
Intel's extra 16 bits of accuracy are not lost. If this isn't
done, FP spills are not suitably transparent. Increase the
number of spill words available to 2048.
-- x86: give the register allocator more flexibility in choosing
spill temporaries.
-- x86, RegAllocInfo.regUsage: fix error for GST, and rewrite to
make it clearer.
-- Correctly track movements in the C stack pointer, and generate
correct spill code for archs which spill against the stack pointer
even when the stack pointer moves. Redo the x86 ccall mechanism
to push args on the C stack in the normal way. Rather than have
the spiller have to analyse code sequences to determine the current
stack offset, the insn selectors communicate the current offset
whenever it changes by inserting a DELTA pseudo-insn. Then the
spiller only has to spot DELTAs.
This means having a new native-code-generator monad (Stix.NatM)
which carries both a UniqSupply and the current stack offset.
-- Remove the asmPar/asmSeq ways of grouping insns together.
In the presence of fixed registers, it is hard to demonstrate
that insn selectors using asmPar always give correct code, and
the extra complication doesn't help any.
Also, directly construct code sequences using tree-based ordered
lists (utils/OrdList.lhs) for linear-time appends, rather than
the bizarrely complex method using fns and fn composition.
-- Inline some hcats in printing of x86 address modes.
-- Document more of the hidden assumptions which insn selection relies
on, particular wrt addressing modes.
|
| |
|
|
|
|
| |
GSQRT, GSIN, GCOS, GTAN: if result size is float (as opposed to double),
truncate the result to that length by writing it into memory and
getting it back again (duh!), since that's what gcc does.
|
| |
|
|
|
|
|
|
|
| |
Fix x86 NCG so the compiler can compile itself `-O':
-- Implement fake x86 insn GITOD/GITOF.
-- Implement primops ReadMutVarOp and WriteMutVarOp.
-- Pro tem, disable use of %eax as a spill temp.
-- Clarify wording of Rules of the Game comment in MachCode.
|
| |
|
|
|
|
|
|
|
|
|
| |
-- Cosmetic changes in register allocator.
-- Implement macro HP_GEN_SEQ_NP.
-- MachCode(trivialCode, x86): because one of the operands is also
the destination (on this 2-address arch), it's invalid to sequence
the code to compute the operands using asmParThen [code1, code2].
since the order of assignments matters. Fixed.
|
| |
|
|
| |
Spilling and x86 shift-code cleanups.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Modifications to make x86 register spilling to work reasonably. It
should work ok most of the time, although there is still a remote
possibility that the allocator simply will be unable to complete
spilling, and will just give up.
-- Incrementally try with 0, 1, 2 and 3 spill regs, so as not to
unduly restrict the supply of regs in code which doesn't need spilling.
-- Remove the use of %ecx for shift values, so it is always available
as the first-choice spill temporary. For code which doesn't do
int division, make %edx and %eax available for spilling too.
Shifts by a non-constant amount (very rare) are now done by
a short test-and-jump sequence, so that %ecx is not tied up.
-- x86 FP: do sin, cos, tan in-line so we get the same answers as gcc.
-- Moved a little code around to remove recursive dependencies.
-- Fix a subtle bug in x86 regUsage, which could cause underestimation
of live ranges.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Commit all changes prior to addressing the x86 spilling situation in
the register allocator.
-- Fix nonsensical x86 addressing mode hacks in mangleIndexTree
and getAmode.
-- Make char-sized loads work properly, using MOVZBL.
-- In assignIntCode, use primRep on the assign node to determine
the size of data transfer, not the size of the source.
-- Redo Integer primitives to be in line with current representation
of Integers.
|