| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Most of the other users of the fptools build system have migrated to
Cabal, and with the move to darcs we can now flatten the source tree
without losing history, so here goes.
The main change is that the ghc/ subdir is gone, and most of what it
contained is now at the top level. The build system now makes no
pretense at being multi-project, it is just the GHC build system.
No doubt this will break many things, and there will be a period of
instability while we fix the dependencies. A straightforward build
should work, but I haven't yet fixed binary/source distributions.
Changes to the Building Guide will follow, too.
|
|
|
|
|
| |
When the volatile regs attached to a CmmCall is Nothing, it means
"save everything", not "save nothing".
|
|
|
|
| |
Remove duplicate imports
|
|
|
|
| |
Add callerSaveVolatileRegs for saving registers around C calls
|
|
|
|
| |
Sparc updates from Peter A Jonsson <pj at ludd.ltu.se>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Catch an exception in Template Haskell code
Merge to STABLE
If the code run by a Template Haskell splice fails with, say,
a pattern-match failure, we should not report it as a GHC panic.
It's a bug in the user's program.
This commit fixes up the exception handling to do the right thing.
Fixes SourceForge item #1201666
TH_fail tests it.
|
|
|
|
|
| |
showReg(x86_64): fix
callerSaves: fix
|
|
|
|
|
|
|
|
|
|
|
| |
x86_64 hacking:
- use %rip-relative addressing in a couple of places
- floating-point comparisons handle NaN properly
I believe the x86_64 NCG is now ready for prime time. It is
successfully bootstrapping the compiler, and I think this fixes the
last of the test failures.
|
|
|
|
| |
wibble
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
First cut at the x86_64 native code generator. Lots of code is shared
with i386, but floating point uses SSE2.
This more or less works, the things I know that don't work are:
- the floating-point primitives (sin, cos etc.) are missing
- floating-point comparisons involving NaN are wrong
- there's no PIC support yet
Also, I have a long list of small things to fix up to improve
performance.
I think the small memory model is assumed, for now.
|
|
|
|
|
|
|
| |
Tweaks to get the GHC sources through Haddock. Doesn't quite work
yet, because Haddock complains about the recursive modules. Haddock
needs to understand SOURCE imports (it can probably just ignore them
as a first attempt).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Position Independent Code and Dynamic Linking Support, Part 1
This commit allows generation of position independent code (PIC) that fully supports dynamic linking on Mac OS X and PowerPC Linux.
Other platforms are not yet supported, and there is no support for actually linking or using dynamic libraries - so if you use the -fPIC or -dynamic code generation flags, you have to type your (platform-specific) linker command lines yourself.
nativeGen/PositionIndependentCode.hs:
New file. Look here for some more comments on how this works.
cmm/CLabel.hs:
Add support for DynamicLinkerLabels and PIC base labels - for use inside the NCG.
needsCDecl: Case alternative labels now need C decls, see the codeGen/CgInfoTbls.hs below for details
cmm/Cmm.hs:
Add CmmPicBaseReg (used in NCG),
and CmmLabelDiffOff (used in NCG and for offsets in info tables)
cmm/CmmParse.y:
support offsets in info tables
cmm/PprC.hs:
support CmmLabelDiffOff
Case alternative labels now need C decls (see the codeGen/CgInfoTbls.hs for details), so we need to pprDataExterns for info tables.
cmm/PprCmm.hs:
support CmmLabelDiffOff
codeGen/CgInfoTbls.hs:
no longer store absolute addresses in info tables, instead, we store offsets.
Also, for vectored return points, emit the alternatives _after_ the vector table. This is to work around a limitation in Apple's as, which refuses to handle label differences where one label is at the end of a section. Emitting alternatives after vector info tables makes sure this never happens in GHC generated code. Case alternatives now require prototypes in hc code, though (see changes in PprC.hs, CLabel.hs).
main/CmdLineOpts.lhs:
Add a new option, -fPIC.
main/DriverFlags.hs:
Pass the correct options for PIC to gcc, depending on the platform. Only for powerpc for now.
nativeGen/AsmCodeGen.hs:
Many changes...
Mac OS X-specific management of import stubs is no longer, it's now part of a general mechanism to handle such things for all platforms that need it (Darwin [both ppc and x86], Linux on ppc, and some platforms we don't support).
Move cmmToCmm into its own monad which can accumulate a list of imported symbols. Make it call cmmMakeDynamicReference at the right places.
nativeGen/MachCodeGen.hs:
nativeGen/MachInstrs.hs:
nativeGen/MachRegs.lhs:
nativeGen/PprMach.hs:
nativeGen/RegAllocInfo.hs:
Too many changes to enumerate here, PowerPC specific.
nativeGen/NCGMonad.hs:
NatM still tracks imported symbols, as more labels can be created during code generation (float literals, jump tables; on some platforms all data access has to go through the dynamic linking mechanism).
driver/mangler/ghc-asm.lprl:
Mangle absolute addresses in info tables to offsets.
Correctly pass through GCC-generated PIC for Mac OS X and powerpc linux.
includes/Cmm.h:
includes/InfoTables.h:
includes/Storage.h:
includes/mkDerivedConstants.c:
rts/GC.c:
rts/GCCompact.c:
rts/HeapStackCheck.cmm:
rts/Printer.c:
rts/RetainerProfile.c:
rts/Sanity.c:
Adapt to the fact that info tables now contain offsets.
rts/Linker.c:
Mac-specific: change machoInitSymbolsWithoutUnderscore to support PIC.
|
|
|
|
| |
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.
|
|
|
|
|
|
| |
gcc 3.3's cpp fix on sparc.
Could be merged to stable if it's not too late.
|
|
|
|
|
| |
change trailing comments on #else/#endif lines to C style to avoid
warnings from gcc 3.3's preprocessor.
|
|
|
|
| |
Prune imports
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Merge the eval-apply-branch on to the HEAD
------------------------------------------
This is a change to GHC's evaluation model in order to ultimately make
GHC more portable and to reduce complexity in some areas.
At some point we'll update the commentary to describe the new state of
the RTS. Pending that, the highlights of this change are:
- No more Su. The Su register is gone, update frames are one
word smaller.
- Slow-entry points and arg checks are gone. Unknown function calls
are handled by automatically-generated RTS entry points (AutoApply.hc,
generated by the program in utils/genapply).
- The stack layout is stricter: there are no "pending arguments" on
the stack any more, the stack is always strictly a sequence of
stack frames.
This means that there's no need for LOOKS_LIKE_GHC_INFO() or
LOOKS_LIKE_STATIC_CLOSURE() any more, and GHC doesn't need to know
how to find the boundary between the text and data segments (BIG WIN!).
- A couple of nasty hacks in the mangler caused by the neet to
identify closure ptrs vs. info tables have gone away.
- Info tables are a bit more complicated. See InfoTables.h for the
details.
- As a side effect, GHCi can now deal with polymorphic seq. Some bugs
in GHCi which affected primitives and unboxed tuples are now
fixed.
- Binary sizes are reduced by about 7% on x86. Performance is roughly
similar, some programs get faster while some get slower. I've seen
GHCi perform worse on some examples, but haven't investigated
further yet (GHCi performance *should* be about the same or better
in theory).
- Internally the code generator is rather better organised. I've moved
info-table generation from the NCG into the main codeGen where it is
shared with the C back-end; info tables are now emitted as arrays
of words in both back-ends. The NCG is one step closer to being able
to support profiling.
This has all been fairly thoroughly tested, but no doubt I've messed
up the commit in some way.
|
|
|
|
|
|
|
|
|
|
|
| |
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)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
| |
On sparc, do not make %i7 and %o7 available for allocation. Quite how
it ever worked before I don't know (and I bootstrapped the compiler with
the sparc NCG). Perhaps it was all just an illusion. Reminds me of how
Bobby Ewing was (utterly implausibly) bought back to life in Dallas.
|
|
|
|
| |
Changes needed to get the head to compile on sparc-solaris.
|
|
|
|
|
|
|
|
|
|
| |
Figure out CafInfo during CoreTidy. This is the final piece of the
puzzle in getting the final IdInfo from the Core2Core phases, rather
than waiting for the STG code.
This simplifies the SRT phase, in that it no longer has to have a
complicated circular algorithm to figure out the CafInfo at the same
time as the SRT layout.
|
|
|
|
| |
baseRegOffset: handle long-regs correctly.
|
|
|
|
| |
Make the back-end world compile.
|
|
|
|
| |
Remove wired-in names. Partially propogated.
|
|
|
|
| |
Gratuitously remove a gratuitous ineficiency in allocatableRegs.
|
|
|
|
|
|
|
|
| |
Make the x86 NCG work again following recent sparc hackage.
Also, fix the x86 bits pertaining to the floats-promoted-to-doubles-
in-ccalls problem. So this problem should no longer exist on x86
or sparc via NCG.
|
|
|
|
|
|
| |
* linux_TARGET_ARCH => i386_TARGET_ARCH
* move callClobberedRegs into safety in front of the register
#define-orgy (what the ... is this cpp-ery for? %-]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
I lied earlier. _ccall_GC_ should work now.
|
|
|
|
| |
Text => Show
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
Teach magicIdRegMaybe about R9 and R10.
|
|
|
|
|
| |
Implement the HP_CHK_GEN macro. As a result, teach mkNativeHdr et al
about R9 and R10.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Major reworking of the x86 floating point code generation.
Intel, in their infinite wisdom, selected a stack model for floating
point registers on x86. That might have made sense back in 1979 --
nowadays we can see it for the nonsense it really is. A stack model
fits poorly with the existing nativeGen infrastructure, which assumes
flat integer and FP register sets. Prior to this commit, nativeGen
could not generate correct x86 FP code -- to do so would have meant
somehow working the register-stack paradigm into the register
allocator and spiller, which sounds very difficult.
We have decided to cheat, and go for a simple fix which requires no
infrastructure modifications, at the expense of generating ropey but
correct FP code. All notions of the x86 FP stack and its insns have
been removed. Instead, we pretend (to the instruction selector and
register allocator) that x86 has six floating point registers, %fake0
.. %fake5, which can be used in the usual flat manner. We further
claim that x86 has floating point instructions very similar to SPARC
and Alpha, that is, a simple 3-operand register-register arrangement.
Code generation and register allocation proceed on this basis.
When we come to print out the final assembly, our convenient fiction
is converted to dismal reality. Each fake instruction is
independently converted to a series of real x86 instructions.
%fake0 .. %fake5 are mapped to %st(0) .. %st(5). To do reg-reg
arithmetic operations, the two operands are pushed onto the top of the
FP stack, the operation done, and the result copied back into the
relevant register. There are only six %fake registers because 2 are
needed for the translation, and x86 has 8 in total.
The translation is inefficient but is simple and it works. A cleverer
translation would handle a sequence of insns, simulating the FP stack
contents, would not impose a fixed mapping from %fake to %st regs, and
hopefully could avoid most of the redundant reg-reg moves of the
current translation.
|
|
|
|
|
|
| |
Don't spew floating/double literals into assembly output, since this
causes difficulties with FP numbers near the edges of the allowed
ranges. Instead, convert them to a sequence of bytes and emit those.
|
|
|
|
| |
Another cosmetic change - avoid desugar warning
|
|
|
|
| |
Move 4.01 onto the main trunk.
|
|
|
|
| |
StCall now takes extra callconv arg; StixPrim.primCode doesn't flush stdout and stderr anymore (it's done in the .hc code)
|
|
|
|
| |
buglet (showSDoc, not show)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The Great Multi-Parameter Type Classes Merge.
Notes from Simon (abridged):
* Multi-parameter type classes are fully implemented.
* Error messages from the type checker should be noticeably improved
* Warnings for unused bindings (-fwarn-unused-names)
* many other minor bug fixes.
Internally there are the following changes
* Removal of Haskell 1.2 compatibility.
* Dramatic clean-up of the PprStyle stuff.
* The type Type has been substantially changed.
* The dictionary for each class is represented by a new
data type for that purpose, rather than by a tuple.
|
|
|
|
| |
fix to have it compile with 2.09 (and later)
|