summaryrefslogtreecommitdiff
path: root/compiler/nativeGen/SPARC
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/nativeGen/SPARC')
-rw-r--r--compiler/nativeGen/SPARC/Base.hs6
-rw-r--r--compiler/nativeGen/SPARC/CodeGen.hs31
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Amode.hs3
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Base.hs9
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/CondCode.hs5
-rw-r--r--compiler/nativeGen/SPARC/CodeGen/Gen32.hs12
-rw-r--r--compiler/nativeGen/SPARC/Instr.hs17
-rw-r--r--compiler/nativeGen/SPARC/Ppr.hs40
-rw-r--r--compiler/nativeGen/SPARC/Stack.hs15
9 files changed, 80 insertions, 58 deletions
diff --git a/compiler/nativeGen/SPARC/Base.hs b/compiler/nativeGen/SPARC/Base.hs
index de11b9f77c..aa7b057e69 100644
--- a/compiler/nativeGen/SPARC/Base.hs
+++ b/compiler/nativeGen/SPARC/Base.hs
@@ -25,7 +25,7 @@ module SPARC.Base (
where
-import qualified Constants
+import DynFlags
import Panic
import Data.Int
@@ -40,9 +40,9 @@ wordLengthInBits
= wordLength * 8
-- Size of the available spill area
-spillAreaLength :: Int
+spillAreaLength :: DynFlags -> Int
spillAreaLength
- = Constants.rESERVED_C_STACK_BYTES
+ = rESERVED_C_STACK_BYTES
-- | We need 8 bytes because our largest registers are 64 bit.
spillSlotSize :: Int
diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs
index a3409dd28b..9d6aeaafc9 100644
--- a/compiler/nativeGen/SPARC/CodeGen.hs
+++ b/compiler/nativeGen/SPARC/CodeGen.hs
@@ -111,7 +111,9 @@ stmtsToInstrs stmts
stmtToInstrs :: CmmStmt -> NatM InstrBlock
-stmtToInstrs stmt = case stmt of
+stmtToInstrs stmt = do
+ dflags <- getDynFlags
+ case stmt of
CmmNop -> return nilOL
CmmComment s -> return (unitOL (COMMENT s))
@@ -119,14 +121,14 @@ stmtToInstrs stmt = case stmt of
| isFloatType ty -> assignReg_FltCode size reg src
| isWord64 ty -> assignReg_I64Code reg src
| otherwise -> assignReg_IntCode size reg src
- where ty = cmmRegType reg
+ where ty = cmmRegType dflags reg
size = cmmTypeSize ty
CmmStore addr src
| isFloatType ty -> assignMem_FltCode size addr src
| isWord64 ty -> assignMem_I64Code addr src
| otherwise -> assignMem_IntCode size addr src
- where ty = cmmExprType src
+ where ty = cmmExprType dflags src
size = cmmTypeSize ty
CmmCall target result_regs args _
@@ -163,9 +165,9 @@ temporary, then do the other computation, and then use the temporary:
-- | Convert a BlockId to some CmmStatic data
-jumpTableEntry :: Maybe BlockId -> CmmStatic
-jumpTableEntry Nothing = CmmStaticLit (CmmInt 0 wordWidth)
-jumpTableEntry (Just blockid) = CmmStaticLit (CmmLabel blockLabel)
+jumpTableEntry :: DynFlags -> Maybe BlockId -> CmmStatic
+jumpTableEntry dflags Nothing = CmmStaticLit (CmmInt 0 (wordWidth dflags))
+jumpTableEntry _ (Just blockid) = CmmStaticLit (CmmLabel blockLabel)
where blockLabel = mkAsmTempLabel (getUnique blockid)
@@ -203,11 +205,12 @@ assignReg_IntCode _ reg src = do
-- Floating point assignment to memory
assignMem_FltCode :: Size -> CmmExpr -> CmmExpr -> NatM InstrBlock
assignMem_FltCode pk addr src = do
+ dflags <- getDynFlags
Amode dst__2 code1 <- getAmode addr
(src__2, code2) <- getSomeReg src
tmp1 <- getNewRegNat pk
let
- pk__2 = cmmExprType src
+ pk__2 = cmmExprType dflags src
code__2 = code1 `appOL` code2 `appOL`
if sizeToWidth pk == typeWidth pk__2
then unitOL (ST pk src__2 dst__2)
@@ -321,8 +324,8 @@ genSwitch dflags expr ids
generateJumpTableForInstr :: DynFlags -> Instr
-> Maybe (NatCmmDecl CmmStatics Instr)
-generateJumpTableForInstr _ (JMP_TBL _ ids label) =
- let jumpTable = map jumpTableEntry ids
+generateJumpTableForInstr dflags (JMP_TBL _ ids label) =
+ let jumpTable = map (jumpTableEntry dflags) ids
in Just (CmmData ReadOnlyData (Statics label jumpTable))
generateJumpTableForInstr _ _ = Nothing
@@ -458,17 +461,21 @@ genCCall target dest_regs argsAndHints
-- | Generate code to calculate an argument, and move it into one
-- or two integer vregs.
arg_to_int_vregs :: CmmExpr -> NatM (OrdList Instr, [Reg])
-arg_to_int_vregs arg
+arg_to_int_vregs arg = do dflags <- getDynFlags
+ arg_to_int_vregs' dflags arg
+
+arg_to_int_vregs' :: DynFlags -> CmmExpr -> NatM (OrdList Instr, [Reg])
+arg_to_int_vregs' dflags arg
-- If the expr produces a 64 bit int, then we can just use iselExpr64
- | isWord64 (cmmExprType arg)
+ | isWord64 (cmmExprType dflags arg)
= do (ChildCode64 code r_lo) <- iselExpr64 arg
let r_hi = getHiVRegFromLo r_lo
return (code, [r_hi, r_lo])
| otherwise
= do (src, code) <- getSomeReg arg
- let pk = cmmExprType arg
+ let pk = cmmExprType dflags arg
case cmmTypeSize pk of
diff --git a/compiler/nativeGen/SPARC/CodeGen/Amode.hs b/compiler/nativeGen/SPARC/CodeGen/Amode.hs
index 92e70eb4dc..139064ccbd 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Amode.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Amode.hs
@@ -33,7 +33,8 @@ getAmode
-> NatM Amode
getAmode tree@(CmmRegOff _ _)
- = getAmode (mangleIndexTree tree)
+ = do dflags <- getDynFlags
+ getAmode (mangleIndexTree dflags tree)
getAmode (CmmMachOp (MO_Sub _) [x, CmmLit (CmmInt i _)])
| fits13Bits (-i)
diff --git a/compiler/nativeGen/SPARC/CodeGen/Base.hs b/compiler/nativeGen/SPARC/CodeGen/Base.hs
index 469361139b..367d9230ba 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Base.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Base.hs
@@ -29,6 +29,7 @@ import Size
import Reg
import CodeGen.Platform
+import DynFlags
import OldCmm
import OldPprCmm ()
import Platform
@@ -114,13 +115,13 @@ getRegisterReg platform (CmmGlobal mid)
-- Expand CmmRegOff. ToDo: should we do it this way around, or convert
-- CmmExprs into CmmRegOff?
-mangleIndexTree :: CmmExpr -> CmmExpr
+mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr
-mangleIndexTree (CmmRegOff reg off)
+mangleIndexTree dflags (CmmRegOff reg off)
= CmmMachOp (MO_Add width) [CmmReg reg, CmmLit (CmmInt (fromIntegral off) width)]
- where width = typeWidth (cmmRegType reg)
+ where width = typeWidth (cmmRegType dflags reg)
-mangleIndexTree _
+mangleIndexTree _ _
= panic "SPARC.CodeGen.Base.mangleIndexTree: no match"
diff --git a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
index 74f20196df..d459d98212 100644
--- a/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/CondCode.hs
@@ -93,14 +93,15 @@ condIntCode cond x y = do
condFltCode :: Cond -> CmmExpr -> CmmExpr -> NatM CondCode
condFltCode cond x y = do
+ dflags <- getDynFlags
(src1, code1) <- getSomeReg x
(src2, code2) <- getSomeReg y
tmp <- getNewRegNat FF64
let
promote x = FxTOy FF32 FF64 x tmp
- pk1 = cmmExprType x
- pk2 = cmmExprType y
+ pk1 = cmmExprType dflags x
+ pk2 = cmmExprType dflags y
code__2 =
if pk1 `cmmEqType` pk2 then
diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
index c2c47e99aa..f7c7419e15 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs
@@ -57,11 +57,12 @@ getRegister :: CmmExpr -> NatM Register
getRegister (CmmReg reg)
= do dflags <- getDynFlags
let platform = targetPlatform dflags
- return (Fixed (cmmTypeSize (cmmRegType reg))
- (getRegisterReg platform reg) nilOL)
+ return (Fixed (cmmTypeSize (cmmRegType dflags reg))
+ (getRegisterReg platform reg) nilOL)
getRegister tree@(CmmRegOff _ _)
- = getRegister (mangleIndexTree tree)
+ = do dflags <- getDynFlags
+ getRegister (mangleIndexTree dflags tree)
getRegister (CmmMachOp (MO_UU_Conv W64 W32)
[CmmMachOp (MO_U_Shr W64) [x,CmmLit (CmmInt 32 _)]]) = do
@@ -490,14 +491,15 @@ trivialFCode
-> NatM Register
trivialFCode pk instr x y = do
+ dflags <- getDynFlags
(src1, code1) <- getSomeReg x
(src2, code2) <- getSomeReg y
tmp <- getNewRegNat FF64
let
promote x = FxTOy FF32 FF64 x tmp
- pk1 = cmmExprType x
- pk2 = cmmExprType y
+ pk1 = cmmExprType dflags x
+ pk2 = cmmExprType dflags y
code__2 dst =
if pk1 `cmmEqType` pk2 then
diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs
index 021b2fb772..9404badea6 100644
--- a/compiler/nativeGen/SPARC/Instr.hs
+++ b/compiler/nativeGen/SPARC/Instr.hs
@@ -46,6 +46,7 @@ import Size
import CLabel
import CodeGen.Platform
import BlockId
+import DynFlags
import OldCmm
import FastString
import FastBool
@@ -372,15 +373,16 @@ sparc_patchJumpInstr insn patchF
-- | Make a spill instruction.
-- On SPARC we spill below frame pointer leaving 2 words/spill
sparc_mkSpillInstr
- :: Platform
+ :: DynFlags
-> Reg -- ^ register to spill
-> Int -- ^ current stack delta
-> Int -- ^ spill slot to use
-> Instr
-sparc_mkSpillInstr platform reg _ slot
- = let off = spillSlotToOffset slot
- off_w = 1 + (off `div` 4)
+sparc_mkSpillInstr dflags reg _ slot
+ = let platform = targetPlatform dflags
+ off = spillSlotToOffset dflags slot
+ off_w = 1 + (off `div` 4)
sz = case targetClassOfReg platform reg of
RcInteger -> II32
RcFloat -> FF32
@@ -392,14 +394,15 @@ sparc_mkSpillInstr platform reg _ slot
-- | Make a spill reload instruction.
sparc_mkLoadInstr
- :: Platform
+ :: DynFlags
-> Reg -- ^ register to load into
-> Int -- ^ current stack delta
-> Int -- ^ spill slot to use
-> Instr
-sparc_mkLoadInstr platform reg _ slot
- = let off = spillSlotToOffset slot
+sparc_mkLoadInstr dflags reg _ slot
+ = let platform = targetPlatform dflags
+ off = spillSlotToOffset dflags slot
off_w = 1 + (off `div` 4)
sz = case targetClassOfReg platform reg of
RcInteger -> II32
diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs
index e57e5e2725..55afac0ee2 100644
--- a/compiler/nativeGen/SPARC/Ppr.hs
+++ b/compiler/nativeGen/SPARC/Ppr.hs
@@ -38,6 +38,7 @@ import PprBase
import OldCmm
import OldPprCmm()
import CLabel
+import BlockId
import Unique ( Uniquable(..), pprUnique )
import Outputable
@@ -52,7 +53,7 @@ pprNatCmmDecl :: NatCmmDecl CmmStatics Instr -> SDoc
pprNatCmmDecl (CmmData section dats) =
pprSectionHeader section $$ pprDatas dats
-pprNatCmmDecl proc@(CmmProc _ lbl (ListGraph blocks)) =
+pprNatCmmDecl proc@(CmmProc top_info lbl (ListGraph blocks)) =
case topInfoTable proc of
Nothing ->
case blocks of
@@ -61,19 +62,15 @@ pprNatCmmDecl proc@(CmmProc _ lbl (ListGraph blocks)) =
blocks -> -- special case for code without info table:
pprSectionHeader Text $$
pprLabel lbl $$ -- blocks guaranteed not null, so label needed
- vcat (map pprBasicBlock blocks)
+ vcat (map (pprBasicBlock top_info) blocks)
- Just (Statics info_lbl info) ->
+ Just (Statics info_lbl _) ->
sdocWithPlatform $ \platform ->
- pprSectionHeader Text $$
- (
- (if platformHasSubsectionsViaSymbols platform
- then ppr (mkDeadStripPreventer info_lbl) <> char ':'
- else empty) $$
- vcat (map pprData info) $$
- pprLabel info_lbl
- ) $$
- vcat (map pprBasicBlock blocks) $$
+ (if platformHasSubsectionsViaSymbols platform
+ then pprSectionHeader Text $$
+ ppr (mkDeadStripPreventer info_lbl) <> char ':'
+ else empty) $$
+ vcat (map (pprBasicBlock top_info) blocks) $$
-- above: Even the first block gets a label, because with branch-chain
-- elimination, it might be the target of a goto.
(if platformHasSubsectionsViaSymbols platform
@@ -91,10 +88,18 @@ pprNatCmmDecl proc@(CmmProc _ lbl (ListGraph blocks)) =
else empty)
-pprBasicBlock :: NatBasicBlock Instr -> SDoc
-pprBasicBlock (BasicBlock blockid instrs) =
- pprLabel (mkAsmTempLabel (getUnique blockid)) $$
- vcat (map pprInstr instrs)
+pprBasicBlock :: BlockEnv CmmStatics -> NatBasicBlock Instr -> SDoc
+pprBasicBlock info_env (BasicBlock blockid instrs)
+ = maybe_infotable $$
+ pprLabel (mkAsmTempLabel (getUnique blockid)) $$
+ vcat (map pprInstr instrs)
+ where
+ maybe_infotable = case mapLookup blockid info_env of
+ Nothing -> empty
+ Just (Statics info_lbl info) ->
+ pprSectionHeader Text $$
+ vcat (map pprData info) $$
+ pprLabel info_lbl
pprDatas :: CmmStatics -> SDoc
@@ -333,7 +338,8 @@ pprSectionHeader seg
-- | Pretty print a data item.
pprDataItem :: CmmLit -> SDoc
pprDataItem lit
- = vcat (ppr_item (cmmTypeSize $ cmmLitType lit) lit)
+ = sdocWithDynFlags $ \dflags ->
+ vcat (ppr_item (cmmTypeSize $ cmmLitType dflags lit) lit)
where
imm = litToImm lit
diff --git a/compiler/nativeGen/SPARC/Stack.hs b/compiler/nativeGen/SPARC/Stack.hs
index 7f75693889..65dfef0e25 100644
--- a/compiler/nativeGen/SPARC/Stack.hs
+++ b/compiler/nativeGen/SPARC/Stack.hs
@@ -20,6 +20,7 @@ import SPARC.Regs
import SPARC.Base
import SPARC.Imm
+import DynFlags
import Outputable
-- | Get an AddrMode relative to the address in sp.
@@ -42,15 +43,15 @@ fpRel n
-- | Convert a spill slot number to a *byte* offset, with no sign.
--
-spillSlotToOffset :: Int -> Int
-spillSlotToOffset slot
- | slot >= 0 && slot < maxSpillSlots
+spillSlotToOffset :: DynFlags -> Int -> Int
+spillSlotToOffset dflags slot
+ | slot >= 0 && slot < maxSpillSlots dflags
= 64 + spillSlotSize * slot
| otherwise
= pprPanic "spillSlotToOffset:"
( text "invalid spill location: " <> int slot
- $$ text "maxSpillSlots: " <> int maxSpillSlots)
+ $$ text "maxSpillSlots: " <> int (maxSpillSlots dflags))
-- | The maximum number of spill slots available on the C stack.
@@ -59,7 +60,7 @@ spillSlotToOffset slot
-- Why do we reserve 64 bytes, instead of using the whole thing??
-- -- BL 2009/02/15
--
-maxSpillSlots :: Int
-maxSpillSlots
- = ((spillAreaLength - 64) `div` spillSlotSize) - 1
+maxSpillSlots :: DynFlags -> Int
+maxSpillSlots dflags
+ = ((spillAreaLength dflags - 64) `div` spillSlotSize) - 1