summaryrefslogtreecommitdiff
path: root/ghc/compiler/nativeGen/AsmCodeGen.lhs
diff options
context:
space:
mode:
authorsewardj <unknown>2000-01-13 14:11:51 +0000
committersewardj <unknown>2000-01-13 14:11:51 +0000
commitd3d20ba70003e869af4d9f44d70d1d403d131812 (patch)
tree017795b2c12965557f78574c64fb93a9ed7f53a0 /ghc/compiler/nativeGen/AsmCodeGen.lhs
parent03d7cc2a4da848db9f39ea072310bb862347e929 (diff)
downloadhaskell-d3d20ba70003e869af4d9f44d70d1d403d131812.tar.gz
[project @ 2000-01-13 14:11:51 by sewardj]
Rearrange top-level nativeGen plumbing so that -ddump-stix is visible even if subsequent nativeGen passes crash.
Diffstat (limited to 'ghc/compiler/nativeGen/AsmCodeGen.lhs')
-rw-r--r--ghc/compiler/nativeGen/AsmCodeGen.lhs39
1 files changed, 18 insertions, 21 deletions
diff --git a/ghc/compiler/nativeGen/AsmCodeGen.lhs b/ghc/compiler/nativeGen/AsmCodeGen.lhs
index 7e92c9fe0c..4d1481c4c9 100644
--- a/ghc/compiler/nativeGen/AsmCodeGen.lhs
+++ b/ghc/compiler/nativeGen/AsmCodeGen.lhs
@@ -22,7 +22,8 @@ import PrimOp ( commutableOp, PrimOp(..) )
import RegAllocInfo ( mkMRegsState, MRegsState )
import Stix ( StixTree(..), StixReg(..), pprStixTrees )
import PrimRep ( isFloatingRep )
-import UniqSupply ( returnUs, thenUs, mapUs, initUs_, UniqSM, UniqSupply )
+import UniqSupply ( returnUs, thenUs, mapUs, initUs,
+ initUs_, UniqSM, UniqSupply )
import UniqFM ( UniqFM, emptyUFM, addToUFM, lookupUFM )
import Outputable
@@ -76,40 +77,36 @@ The machine-dependent bits break down as follows:
\end{description}
So, here we go:
+
\begin{code}
-nativeCodeGen :: AbstractC -> UniqSupply -> (SDoc, SDoc, SDoc, SDoc)
-nativeCodeGen absC us = initUs_ us (runNCG absC)
+nativeCodeGen :: AbstractC -> UniqSupply -> (SDoc, SDoc)
+nativeCodeGen absC us
+ = let (stixRaw, us1) = initUs us (genCodeAbstractC absC)
+ stixOpt = map (map genericOpt) stixRaw
+ stixFinal = map x86floatFix stixOpt
+ insns = initUs_ us1 (codeGen stixFinal)
+ debug_stix = vcat (map pprStixTrees stixFinal)
+ in
+ (debug_stix, insns)
-runNCG :: AbstractC -> UniqSM (SDoc, SDoc, SDoc, SDoc)
-runNCG absC
- = genCodeAbstractC absC `thenUs` \ stixRaw ->
- let
- stixOpt = map (map genericOpt) stixRaw
#if i386_TARGET_ARCH
- stixFinal = map floatFix stixOpt
+x86floatFix = floatFix
#else
- stixFinal = stixOpt
+x86floatFix = id
#endif
- in
- codeGen (stixRaw, stixOpt, stixFinal)
+
\end{code}
@codeGen@ is the top-level code-generation function:
\begin{code}
-codeGen :: ([[StixTree]],[[StixTree]],[[StixTree]])
- -> UniqSM (SDoc, SDoc, SDoc, SDoc)
+codeGen :: [[StixTree]] -> UniqSM SDoc
-codeGen (stixRaw, stixOpt, stixFinal)
+codeGen stixFinal
= mapUs genMachCode stixFinal `thenUs` \ dynamic_codes ->
let
static_instrs = scheduleMachCode dynamic_codes
in
- returnUs (
- text "ppr'd stixRaw",
- text "ppr'd stixOpt",
- vcat (map pprStixTrees stixFinal),
- vcat (map pprInstr static_instrs)
- )
+ returnUs (vcat (map pprInstr static_instrs))
\end{code}
Top level code generator for a chunk of stix code: