diff options
Diffstat (limited to 'compiler/nativeGen')
-rw-r--r-- | compiler/nativeGen/PPC/CodeGen.hs | 11 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Regs.hs | 7 | ||||
-rw-r--r-- | compiler/nativeGen/X86/CodeGen.hs | 23 | ||||
-rw-r--r-- | compiler/nativeGen/X86/Instr.hs | 12 | ||||
-rw-r--r-- | compiler/nativeGen/X86/Regs.hs | 11 |
5 files changed, 32 insertions, 32 deletions
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 367c0fbdec..1f036aa43e 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1379,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 @@ -1404,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 @@ -1412,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') diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs index 7dccb6040e..d4123aca84 100644 --- a/compiler/nativeGen/PPC/Regs.hs +++ b/compiler/nativeGen/PPC/Regs.hs @@ -55,8 +55,8 @@ import CLabel ( CLabel ) import Unique import CodeGen.Platform +import DynFlags import Outputable -import Constants import FastBool import FastTypes import Platform @@ -194,10 +194,11 @@ addrOffset addr off -- temporaries and for excess call arguments. @fpRel@, where -- applicable, is the same but for the frame pointer. -spRel :: Int -- desired stack offset in words, positive or negative +spRel :: DynFlags + -> Int -- desired stack offset in words, positive or negative -> AddrMode -spRel n = AddrRegImm sp (ImmInt (n * wORD_SIZE)) +spRel dflags n = AddrRegImm sp (ImmInt (n * wORD_SIZE dflags)) -- argRegs is the set of regs which are read for an n-argument call to C. diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 66ebf75629..b83ede89aa 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -52,7 +52,6 @@ import Outputable import Unique import FastString import FastBool ( isFastTrue ) -import Constants ( wORD_SIZE ) import DynFlags import Util @@ -1766,9 +1765,9 @@ genCCall32' dflags target dest_regs args = do -- alignment of 16n - word_size on procedure entry. Which we -- maintiain. See Note [rts/StgCRun.c : Stack Alignment on X86] sizes = map (arg_size . cmmExprType dflags . hintlessCmm) (reverse args) - raw_arg_size = sum sizes + wORD_SIZE + raw_arg_size = sum sizes + wORD_SIZE dflags arg_pad_size = (roundTo 16 $ raw_arg_size) - raw_arg_size - tot_arg_size = raw_arg_size + arg_pad_size - wORD_SIZE + tot_arg_size = raw_arg_size + arg_pad_size - wORD_SIZE dflags delta0 <- getDeltaNat setDeltaNat (delta0 - arg_pad_size) @@ -2026,14 +2025,14 @@ genCCall64' dflags target dest_regs args = do -- alignment of 16n - word_size on procedure entry. Which we -- maintiain. See Note [rts/StgCRun.c : Stack Alignment on X86] (real_size, adjust_rsp) <- - if (tot_arg_size + wORD_SIZE) `rem` 16 == 0 + if (tot_arg_size + wORD_SIZE dflags) `rem` 16 == 0 then return (tot_arg_size, nilOL) else do -- we need to adjust... delta <- getDeltaNat - setDeltaNat (delta - wORD_SIZE) - return (tot_arg_size + wORD_SIZE, toOL [ - SUB II64 (OpImm (ImmInt wORD_SIZE)) (OpReg rsp), - DELTA (delta - wORD_SIZE) ]) + setDeltaNat (delta - wORD_SIZE dflags) + return (tot_arg_size + wORD_SIZE dflags, toOL [ + SUB II64 (OpImm (ImmInt (wORD_SIZE dflags))) (OpReg rsp), + DELTA (delta - wORD_SIZE dflags) ]) -- push the stack args, right to left push_code <- push_args (reverse stack_args) nilOL @@ -2173,7 +2172,7 @@ genCCall64' dflags target dest_regs args = do let code' = code `appOL` arg_code `appOL` toOL [ SUB (intSize (wordWidth dflags)) (OpImm (ImmInt arg_size)) (OpReg rsp) , DELTA (delta-arg_size), - MOV (floatSize width) (OpReg arg_reg) (OpAddr (spRel platform 0))] + MOV (floatSize width) (OpReg arg_reg) (OpAddr (spRel dflags 0))] push_args rest code' | otherwise = do @@ -2196,7 +2195,7 @@ genCCall64' dflags target dest_regs args = do delta <- getDeltaNat setDeltaNat (delta - n * arg_size) return $ toOL [ - SUB II64 (OpImm (ImmInt (n * wORD_SIZE))) (OpReg rsp), + SUB II64 (OpImm (ImmInt (n * wORD_SIZE dflags))) (OpReg rsp), DELTA (delta - n * arg_size)] -- | We're willing to inline and unroll memcpy/memset calls that touch @@ -2288,7 +2287,7 @@ genSwitch dflags expr ids dynRef <- cmmMakeDynamicReference dflags addImportNat DataReference lbl (tableReg,t_code) <- getSomeReg $ dynRef let op = OpAddr (AddrBaseIndex (EABaseReg tableReg) - (EAIndex reg wORD_SIZE) (ImmInt 0)) + (EAIndex reg (wORD_SIZE dflags)) (ImmInt 0)) return $ if target32Bit (targetPlatform dflags) then e_code `appOL` t_code `appOL` toOL [ @@ -2326,7 +2325,7 @@ genSwitch dflags expr ids = do (reg,e_code) <- getSomeReg expr lbl <- getNewLabelNat - let op = OpAddr (AddrBaseIndex EABaseNone (EAIndex reg wORD_SIZE) (ImmCLbl lbl)) + let op = OpAddr (AddrBaseIndex EABaseNone (EAIndex reg (wORD_SIZE dflags)) (ImmCLbl lbl)) code = e_code `appOL` toOL [ JMP_TBL op ids ReadOnlyData lbl ] diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs index 50f5b4c874..7f0e48e769 100644 --- a/compiler/nativeGen/X86/Instr.hs +++ b/compiler/nativeGen/X86/Instr.hs @@ -625,9 +625,9 @@ x86_mkSpillInstr dflags reg delta slot let off_w = (off - delta) `div` (if is32Bit then 4 else 8) in case targetClassOfReg platform reg of RcInteger -> MOV (archWordSize is32Bit) - (OpReg reg) (OpAddr (spRel platform off_w)) - RcDouble -> GST FF80 reg (spRel platform off_w) {- RcFloat/RcDouble -} - RcDoubleSSE -> MOV FF64 (OpReg reg) (OpAddr (spRel platform off_w)) + (OpReg reg) (OpAddr (spRel dflags off_w)) + RcDouble -> GST FF80 reg (spRel dflags off_w) {- RcFloat/RcDouble -} + RcDoubleSSE -> MOV FF64 (OpReg reg) (OpAddr (spRel dflags off_w)) _ -> panic "X86.mkSpillInstr: no match" where platform = targetPlatform dflags is32Bit = target32Bit platform @@ -646,9 +646,9 @@ x86_mkLoadInstr dflags reg delta slot let off_w = (off-delta) `div` (if is32Bit then 4 else 8) in case targetClassOfReg platform reg of RcInteger -> MOV (archWordSize is32Bit) - (OpAddr (spRel platform off_w)) (OpReg reg) - RcDouble -> GLD FF80 (spRel platform off_w) reg {- RcFloat/RcDouble -} - RcDoubleSSE -> MOV FF64 (OpAddr (spRel platform off_w)) (OpReg reg) + (OpAddr (spRel dflags off_w)) (OpReg reg) + RcDouble -> GLD FF80 (spRel dflags off_w) reg {- RcFloat/RcDouble -} + RcDoubleSSE -> MOV FF64 (OpAddr (spRel dflags off_w)) (OpReg reg) _ -> panic "X86.x86_mkLoadInstr" where platform = targetPlatform dflags is32Bit = target32Bit platform diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index c88ea98425..4eec96f5e1 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -59,7 +59,6 @@ import Outputable import Platform import FastTypes import FastBool -import Constants -- | regSqueeze_class reg @@ -196,14 +195,14 @@ addrModeRegs _ = [] -- applicable, is the same but for the frame pointer. -spRel :: Platform +spRel :: DynFlags -> Int -- ^ desired stack offset in words, positive or negative -> AddrMode -spRel platform n - | target32Bit platform - = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt (n * wORD_SIZE)) +spRel dflags n + | target32Bit (targetPlatform dflags) + = AddrBaseIndex (EABaseReg esp) EAIndexNone (ImmInt (n * wORD_SIZE dflags)) | otherwise - = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt (n * wORD_SIZE)) + = AddrBaseIndex (EABaseReg rsp) EAIndexNone (ImmInt (n * wORD_SIZE dflags)) -- The register numbers must fit into 32 bits on x86, so that we can -- use a Word32 to represent the set of free registers in the register |