summaryrefslogtreecommitdiff
path: root/compiler/nativeGen/PPC/CodeGen.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/nativeGen/PPC/CodeGen.hs')
-rw-r--r--compiler/nativeGen/PPC/CodeGen.hs62
1 files changed, 33 insertions, 29 deletions
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index ce4a54ca9b..1f036aa43e 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -124,7 +124,7 @@ stmtToInstrs stmt = do
| target32Bit (targetPlatform dflags) &&
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
@@ -132,7 +132,7 @@ stmtToInstrs stmt = do
| target32Bit (targetPlatform dflags) &&
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 _
@@ -206,9 +206,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)
@@ -218,12 +218,12 @@ jumpTableEntry (Just blockid) = CmmStaticLit (CmmLabel blockLabel)
-- Expand CmmRegOff. ToDo: should we do it this way around, or convert
-- CmmExprs into CmmRegOff?
-mangleIndexTree :: CmmExpr -> CmmExpr
-mangleIndexTree (CmmRegOff reg off)
+mangleIndexTree :: DynFlags -> CmmExpr -> CmmExpr
+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 "PPC.CodeGen.mangleIndexTree: no match"
-- -----------------------------------------------------------------------------
@@ -370,11 +370,11 @@ getRegister' _ (CmmReg (CmmGlobal PicBaseReg))
return (Fixed archWordSize reg nilOL)
getRegister' dflags (CmmReg reg)
- = return (Fixed (cmmTypeSize (cmmRegType reg))
+ = return (Fixed (cmmTypeSize (cmmRegType dflags reg))
(getRegisterReg (targetPlatform dflags) reg) nilOL)
getRegister' dflags tree@(CmmRegOff _ _)
- = getRegister' dflags (mangleIndexTree tree)
+ = getRegister' dflags (mangleIndexTree dflags tree)
-- for 32-bit architectuers, support some 64 -> 32 bit conversions:
-- TO_W_(x), TO_W_(x >> 32)
@@ -561,8 +561,8 @@ getRegister' _ (CmmLit (CmmFloat f frep)) = do
`consOL` (addr_code `snocOL` LD size dst addr)
return (Any size code)
-getRegister' _ (CmmLit lit)
- = let rep = cmmLitType lit
+getRegister' dflags (CmmLit lit)
+ = let rep = cmmLitType dflags lit
imm = litToImm lit
code dst = toOL [
LIS dst (HA imm),
@@ -607,7 +607,8 @@ temporary, then do the other computation, and then use the temporary:
-}
getAmode :: CmmExpr -> NatM Amode
-getAmode tree@(CmmRegOff _ _) = getAmode (mangleIndexTree tree)
+getAmode tree@(CmmRegOff _ _) = do dflags <- getDynFlags
+ getAmode (mangleIndexTree dflags tree)
getAmode (CmmMachOp (MO_Sub W32) [x, CmmLit (CmmInt i _)])
| Just off <- makeImmediate W32 True (-i)
@@ -844,14 +845,14 @@ genCCall target dest_regs argsAndHints
= do dflags <- getDynFlags
let platform = targetPlatform dflags
case platformOS platform of
- OSLinux -> genCCall' platform GCPLinux target dest_regs argsAndHints
- OSDarwin -> genCCall' platform GCPDarwin target dest_regs argsAndHints
+ OSLinux -> genCCall' dflags GCPLinux target dest_regs argsAndHints
+ OSDarwin -> genCCall' dflags GCPDarwin target dest_regs argsAndHints
_ -> panic "PPC.CodeGen.genCCall: not defined for this os"
data GenCCallPlatform = GCPLinux | GCPDarwin
genCCall'
- :: Platform
+ :: DynFlags
-> GenCCallPlatform
-> CmmCallTarget -- function to call
-> [HintedCmmFormal] -- where to put the result
@@ -902,7 +903,7 @@ genCCall' _ _ (CmmPrim MO_WriteBarrier _) _ _
genCCall' _ _ (CmmPrim _ (Just stmts)) _ _
= stmtsToInstrs stmts
-genCCall' platform gcp target dest_regs argsAndHints
+genCCall' dflags gcp target dest_regs argsAndHints
= ASSERT (not $ any (`elem` [II16]) $ map cmmTypeSize argReps)
-- we rely on argument promotion in the codeGen
do
@@ -934,6 +935,8 @@ genCCall' platform gcp target dest_regs argsAndHints
`snocOL` BCTRL usedRegs
`appOL` codeAfter)
where
+ platform = targetPlatform dflags
+
initialStackOffset = case gcp of
GCPDarwin -> 24
GCPLinux -> 8
@@ -955,7 +958,7 @@ genCCall' platform gcp target dest_regs argsAndHints
= argsAndHints
args = map hintlessCmm argsAndHints'
- argReps = map cmmExprType args
+ argReps = map (cmmExprType dflags) args
roundTo a x | x `mod` a == 0 = x
| otherwise = x + a - (x `mod` a)
@@ -1060,23 +1063,23 @@ genCCall' platform gcp target dest_regs argsAndHints
GCPDarwin ->
case cmmTypeSize rep of
II8 -> (1, 0, 4, gprs)
+ II16 -> (1, 0, 4, gprs)
II32 -> (1, 0, 4, gprs)
-- The Darwin ABI requires that we skip a
-- corresponding number of GPRs when we use
-- the FPRs.
FF32 -> (1, 1, 4, fprs)
FF64 -> (2, 1, 8, fprs)
- II16 -> panic "genCCall' passArguments II16"
II64 -> panic "genCCall' passArguments II64"
FF80 -> panic "genCCall' passArguments FF80"
GCPLinux ->
case cmmTypeSize rep of
II8 -> (1, 0, 4, gprs)
+ II16 -> (1, 0, 4, gprs)
II32 -> (1, 0, 4, gprs)
-- ... the SysV ABI doesn't.
FF32 -> (0, 1, 4, fprs)
FF64 -> (0, 1, 8, fprs)
- II16 -> panic "genCCall' passArguments II16"
II64 -> panic "genCCall' passArguments II64"
FF80 -> panic "genCCall' passArguments FF80"
@@ -1089,7 +1092,7 @@ genCCall' platform gcp target dest_regs argsAndHints
| isWord64 rep -> toOL [MR (getHiVRegFromLo r_dest) r3,
MR r_dest r4]
| otherwise -> unitOL (MR r_dest r3)
- where rep = cmmRegType (CmmLocal dest)
+ where rep = cmmRegType dflags (CmmLocal dest)
r_dest = getRegisterReg platform (CmmLocal dest)
_ -> panic "genCCall' moveResult: Bad dest_regs"
@@ -1194,9 +1197,9 @@ generateJumpTableForInstr :: DynFlags -> Instr
generateJumpTableForInstr dflags (BCTR ids (Just lbl)) =
let jumpTable
| dopt Opt_PIC dflags = map jumpTableEntryRel ids
- | otherwise = map jumpTableEntry ids
+ | otherwise = map (jumpTableEntry dflags) ids
where jumpTableEntryRel Nothing
- = CmmStaticLit (CmmInt 0 wordWidth)
+ = CmmStaticLit (CmmInt 0 (wordWidth dflags))
jumpTableEntryRel (Just blockid)
= CmmStaticLit (CmmLabelDiffOff blockLabel lbl 0)
where blockLabel = mkAsmTempLabel (getUnique blockid)
@@ -1376,10 +1379,10 @@ coerceInt2FP fromRep toRep x = do
[CmmStaticLit (CmmInt 0x43300000 W32),
CmmStaticLit (CmmInt 0x80000000 W32)],
XORIS itmp src (ImmInt 0x8000),
- ST II32 itmp (spRel 3),
+ ST II32 itmp (spRel dflags 3),
LIS itmp (ImmInt 0x4330),
- ST II32 itmp (spRel 2),
- LD FF64 ftmp (spRel 2)
+ ST II32 itmp (spRel dflags 2),
+ LD FF64 ftmp (spRel dflags 2)
] `appOL` addr_code `appOL` toOL [
LD FF64 dst addr,
FSUB FF64 dst ftmp dst
@@ -1401,6 +1404,7 @@ coerceInt2FP fromRep toRep x = do
coerceFP2Int :: Width -> Width -> CmmExpr -> NatM Register
coerceFP2Int _ toRep x = do
+ dflags <- getDynFlags
-- the reps don't really matter: F*->FF64 and II32->I* are no-ops
(src, code) <- getSomeReg x
tmp <- getNewRegNat FF64
@@ -1409,7 +1413,7 @@ coerceFP2Int _ toRep x = do
-- convert to int in FP reg
FCTIWZ tmp src,
-- store value (64bit) from FP to stack
- ST FF64 tmp (spRel 2),
+ ST FF64 tmp (spRel dflags 2),
-- read low word of value (high word is undefined)
- LD II32 dst (spRel 3)]
+ LD II32 dst (spRel dflags 3)]
return (Any (intSize toRep) code')