summaryrefslogtreecommitdiff
path: root/compiler/codeGen
diff options
context:
space:
mode:
authorIan Lynagh <ian@well-typed.com>2012-08-21 17:44:38 +0100
committerIan Lynagh <ian@well-typed.com>2012-08-21 17:44:38 +0100
commit75700644a7430612b40ba94476a5749594010671 (patch)
tree4f1717e39ef576a35cbd65706582067b56d14487 /compiler/codeGen
parent07295e96981b29cc6fb88b334d8ebd4b1b807516 (diff)
downloadhaskell-75700644a7430612b40ba94476a5749594010671.tar.gz
Move activeStgRegs into CodeGen.Platform
Diffstat (limited to 'compiler/codeGen')
-rw-r--r--compiler/codeGen/CgHeapery.lhs12
-rw-r--r--compiler/codeGen/CgUtils.hs128
-rw-r--r--compiler/codeGen/CodeGen/Platform.hs (renamed from compiler/codeGen/CodeGen/CallerSaves.hs)22
-rw-r--r--compiler/codeGen/CodeGen/Platform/ARM.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/NoRegs.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/PPC.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/SPARC.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/X86.hs4
-rw-r--r--compiler/codeGen/CodeGen/Platform/X86_64.hs4
-rw-r--r--compiler/codeGen/StgCmmUtils.hs2
11 files changed, 74 insertions, 118 deletions
diff --git a/compiler/codeGen/CgHeapery.lhs b/compiler/codeGen/CgHeapery.lhs
index c0c15131c4..2ce37cf565 100644
--- a/compiler/codeGen/CgHeapery.lhs
+++ b/compiler/codeGen/CgHeapery.lhs
@@ -526,8 +526,10 @@ do_checks' stk_expr hp_expr stk_nonzero hp_nonzero reg_save_code rts_lbl live
\begin{code}
hpChkGen :: CmmExpr -> CmmExpr -> CmmExpr -> Code
hpChkGen bytes liveness reentry
- = do_checks' (CmmLit (mkIntCLit 0)) bytes False True assigns
- stg_gc_gen (Just activeStgRegs)
+ = do dflags <- getDynFlags
+ let platform = targetPlatform dflags
+ do_checks' (CmmLit (mkIntCLit 0)) bytes False True assigns
+ stg_gc_gen (Just (activeStgRegs platform))
where
assigns = mkStmts [ mk_vanilla_assignment 9 liveness,
mk_vanilla_assignment 10 reentry ]
@@ -542,8 +544,10 @@ hpChkNodePointsAssignSp0 bytes sp0
stkChkGen :: CmmExpr -> CmmExpr -> CmmExpr -> Code
stkChkGen bytes liveness reentry
- = do_checks' bytes (CmmLit (mkIntCLit 0)) True False assigns
- stg_gc_gen (Just activeStgRegs)
+ = do dflags <- getDynFlags
+ let platform = targetPlatform dflags
+ do_checks' bytes (CmmLit (mkIntCLit 0)) True False assigns
+ stg_gc_gen (Just (activeStgRegs platform))
where
assigns = mkStmts [ mk_vanilla_assignment 9 liveness,
mk_vanilla_assignment 10 reentry ]
diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs
index b488f16299..4661450fe5 100644
--- a/compiler/codeGen/CgUtils.hs
+++ b/compiler/codeGen/CgUtils.hs
@@ -48,7 +48,7 @@ module CgUtils (
#include "../includes/stg/HaskellMachRegs.h"
import BlockId
-import CodeGen.CallerSaves
+import CodeGen.Platform
import CgMonad
import TyCon
import DataCon
@@ -70,6 +70,7 @@ import Util
import DynFlags
import FastString
import Outputable
+import Platform
import Data.Char
import Data.Word
@@ -805,75 +806,6 @@ srt_escape = -1
--
-- -----------------------------------------------------------------------------
--- | Here is where the STG register map is defined for each target arch.
--- The order matters (for the llvm backend anyway)! We must make sure to
--- maintain the order here with the order used in the LLVM calling conventions.
--- Note that also, this isn't all registers, just the ones that are currently
--- possbily mapped to real registers.
-activeStgRegs :: [GlobalReg]
-activeStgRegs = [
-#ifdef REG_Base
- BaseReg
-#endif
-#ifdef REG_Sp
- ,Sp
-#endif
-#ifdef REG_Hp
- ,Hp
-#endif
-#ifdef REG_R1
- ,VanillaReg 1 VGcPtr
-#endif
-#ifdef REG_R2
- ,VanillaReg 2 VGcPtr
-#endif
-#ifdef REG_R3
- ,VanillaReg 3 VGcPtr
-#endif
-#ifdef REG_R4
- ,VanillaReg 4 VGcPtr
-#endif
-#ifdef REG_R5
- ,VanillaReg 5 VGcPtr
-#endif
-#ifdef REG_R6
- ,VanillaReg 6 VGcPtr
-#endif
-#ifdef REG_R7
- ,VanillaReg 7 VGcPtr
-#endif
-#ifdef REG_R8
- ,VanillaReg 8 VGcPtr
-#endif
-#ifdef REG_R9
- ,VanillaReg 9 VGcPtr
-#endif
-#ifdef REG_R10
- ,VanillaReg 10 VGcPtr
-#endif
-#ifdef REG_SpLim
- ,SpLim
-#endif
-#ifdef REG_F1
- ,FloatReg 1
-#endif
-#ifdef REG_F2
- ,FloatReg 2
-#endif
-#ifdef REG_F3
- ,FloatReg 3
-#endif
-#ifdef REG_F4
- ,FloatReg 4
-#endif
-#ifdef REG_D1
- ,DoubleReg 1
-#endif
-#ifdef REG_D2
- ,DoubleReg 2
-#endif
- ]
-
-- | We map STG registers onto appropriate CmmExprs. Either they map
-- to real machine registers or stored as offsets from BaseReg. Given
-- a GlobalReg, get_GlobalReg_addr always produces the
@@ -899,60 +831,60 @@ get_Regtable_addr_from_offset _ offset =
-- | Fixup global registers so that they assign to locations within the
-- RegTable if they aren't pinned for the current target.
-fixStgRegisters :: RawCmmDecl -> RawCmmDecl
-fixStgRegisters top@(CmmData _ _) = top
+fixStgRegisters :: Platform -> RawCmmDecl -> RawCmmDecl
+fixStgRegisters _ top@(CmmData _ _) = top
-fixStgRegisters (CmmProc info lbl (ListGraph blocks)) =
- let blocks' = map fixStgRegBlock blocks
+fixStgRegisters platform (CmmProc info lbl (ListGraph blocks)) =
+ let blocks' = map (fixStgRegBlock platform) blocks
in CmmProc info lbl $ ListGraph blocks'
-fixStgRegBlock :: CmmBasicBlock -> CmmBasicBlock
-fixStgRegBlock (BasicBlock id stmts) =
- let stmts' = map fixStgRegStmt stmts
+fixStgRegBlock :: Platform -> CmmBasicBlock -> CmmBasicBlock
+fixStgRegBlock platform (BasicBlock id stmts) =
+ let stmts' = map (fixStgRegStmt platform) stmts
in BasicBlock id stmts'
-fixStgRegStmt :: CmmStmt -> CmmStmt
-fixStgRegStmt stmt
+fixStgRegStmt :: Platform -> CmmStmt -> CmmStmt
+fixStgRegStmt platform stmt
= case stmt of
CmmAssign (CmmGlobal reg) src ->
- let src' = fixStgRegExpr src
+ let src' = fixStgRegExpr platform src
baseAddr = get_GlobalReg_addr reg
- in case reg `elem` activeStgRegs of
+ in case reg `elem` activeStgRegs platform of
True -> CmmAssign (CmmGlobal reg) src'
False -> CmmStore baseAddr src'
CmmAssign reg src ->
- let src' = fixStgRegExpr src
+ let src' = fixStgRegExpr platform src
in CmmAssign reg src'
- CmmStore addr src -> CmmStore (fixStgRegExpr addr) (fixStgRegExpr src)
+ CmmStore addr src -> CmmStore (fixStgRegExpr platform addr) (fixStgRegExpr platform src)
CmmCall target regs args returns ->
let target' = case target of
- CmmCallee e conv -> CmmCallee (fixStgRegExpr e) conv
+ CmmCallee e conv -> CmmCallee (fixStgRegExpr platform e) conv
CmmPrim op mStmts ->
- CmmPrim op (fmap (map fixStgRegStmt) mStmts)
+ CmmPrim op (fmap (map (fixStgRegStmt platform)) mStmts)
args' = map (\(CmmHinted arg hint) ->
- (CmmHinted (fixStgRegExpr arg) hint)) args
+ (CmmHinted (fixStgRegExpr platform arg) hint)) args
in CmmCall target' regs args' returns
- CmmCondBranch test dest -> CmmCondBranch (fixStgRegExpr test) dest
+ CmmCondBranch test dest -> CmmCondBranch (fixStgRegExpr platform test) dest
- CmmSwitch expr ids -> CmmSwitch (fixStgRegExpr expr) ids
+ CmmSwitch expr ids -> CmmSwitch (fixStgRegExpr platform expr) ids
- CmmJump addr live -> CmmJump (fixStgRegExpr addr) live
+ CmmJump addr live -> CmmJump (fixStgRegExpr platform addr) live
-- CmmNop, CmmComment, CmmBranch, CmmReturn
_other -> stmt
-fixStgRegExpr :: CmmExpr -> CmmExpr
-fixStgRegExpr expr
+fixStgRegExpr :: Platform -> CmmExpr -> CmmExpr
+fixStgRegExpr platform expr
= case expr of
- CmmLoad addr ty -> CmmLoad (fixStgRegExpr addr) ty
+ CmmLoad addr ty -> CmmLoad (fixStgRegExpr platform addr) ty
CmmMachOp mop args -> CmmMachOp mop args'
- where args' = map fixStgRegExpr args
+ where args' = map (fixStgRegExpr platform) args
CmmReg (CmmGlobal reg) ->
-- Replace register leaves with appropriate StixTrees for
@@ -961,22 +893,22 @@ fixStgRegExpr expr
-- to mean the address of the reg table in MainCapability,
-- and for all others we generate an indirection to its
-- location in the register table.
- case reg `elem` activeStgRegs of
+ case reg `elem` activeStgRegs platform of
True -> expr
False ->
let baseAddr = get_GlobalReg_addr reg
in case reg of
- BaseReg -> fixStgRegExpr baseAddr
- _other -> fixStgRegExpr
+ BaseReg -> fixStgRegExpr platform baseAddr
+ _other -> fixStgRegExpr platform
(CmmLoad baseAddr (globalRegType reg))
CmmRegOff (CmmGlobal reg) offset ->
-- RegOf leaves are just a shorthand form. If the reg maps
-- to a real reg, we keep the shorthand, otherwise, we just
-- expand it and defer to the above code.
- case reg `elem` activeStgRegs of
+ case reg `elem` activeStgRegs platform of
True -> expr
- False -> fixStgRegExpr (CmmMachOp (MO_Add wordWidth) [
+ False -> fixStgRegExpr platform (CmmMachOp (MO_Add wordWidth) [
CmmReg (CmmGlobal reg),
CmmLit (CmmInt (fromIntegral offset)
wordWidth)])
diff --git a/compiler/codeGen/CodeGen/CallerSaves.hs b/compiler/codeGen/CodeGen/Platform.hs
index b6c709df8c..66e8f85aff 100644
--- a/compiler/codeGen/CodeGen/CallerSaves.hs
+++ b/compiler/codeGen/CodeGen/Platform.hs
@@ -1,5 +1,5 @@
-module CodeGen.CallerSaves (callerSaves) where
+module CodeGen.Platform (callerSaves, activeStgRegs) where
import CmmExpr
import Platform
@@ -30,3 +30,23 @@ callerSaves platform
| otherwise -> NoRegs.callerSaves
+-- | Here is where the STG register map is defined for each target arch.
+-- The order matters (for the llvm backend anyway)! We must make sure to
+-- maintain the order here with the order used in the LLVM calling conventions.
+-- Note that also, this isn't all registers, just the ones that are currently
+-- possbily mapped to real registers.
+activeStgRegs :: Platform -> [GlobalReg]
+activeStgRegs platform
+ = case platformArch platform of
+ ArchX86 -> X86.activeStgRegs
+ ArchX86_64 -> X86_64.activeStgRegs
+ ArchSPARC -> SPARC.activeStgRegs
+ ArchARM {} -> ARM.activeStgRegs
+ arch
+ | arch `elem` [ArchPPC, ArchPPC_64] ->
+ case platformOS platform of
+ OSDarwin -> PPC_Darwin.activeStgRegs
+ _ -> PPC.activeStgRegs
+
+ | otherwise -> NoRegs.activeStgRegs
+
diff --git a/compiler/codeGen/CodeGen/Platform/ARM.hs b/compiler/codeGen/CodeGen/Platform/ARM.hs
index 0116139313..cad3eb7f50 100644
--- a/compiler/codeGen/CodeGen/Platform/ARM.hs
+++ b/compiler/codeGen/CodeGen/Platform/ARM.hs
@@ -1,9 +1,9 @@
-module CodeGen.Platform.ARM (callerSaves) where
+module CodeGen.Platform.ARM where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_arm 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/NoRegs.hs b/compiler/codeGen/CodeGen/Platform/NoRegs.hs
index ff39dd90ae..6d7c3342d0 100644
--- a/compiler/codeGen/CodeGen/Platform/NoRegs.hs
+++ b/compiler/codeGen/CodeGen/Platform/NoRegs.hs
@@ -1,8 +1,8 @@
-module CodeGen.Platform.NoRegs (callerSaves) where
+module CodeGen.Platform.NoRegs where
import CmmExpr
#define MACHREGS_NO_REGS 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/PPC.hs b/compiler/codeGen/CodeGen/Platform/PPC.hs
index c4c975a58f..19d0609ae2 100644
--- a/compiler/codeGen/CodeGen/Platform/PPC.hs
+++ b/compiler/codeGen/CodeGen/Platform/PPC.hs
@@ -1,9 +1,9 @@
-module CodeGen.Platform.PPC (callerSaves) where
+module CodeGen.Platform.PPC where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_powerpc 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs b/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
index a0cbe7e433..a53ee06cc2 100644
--- a/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
+++ b/compiler/codeGen/CodeGen/Platform/PPC_Darwin.hs
@@ -1,10 +1,10 @@
-module CodeGen.Platform.PPC_Darwin (callerSaves) where
+module CodeGen.Platform.PPC_Darwin where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_powerpc 1
#define MACHREGS_darwin 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/SPARC.hs b/compiler/codeGen/CodeGen/Platform/SPARC.hs
index 86b949469e..391d6c8086 100644
--- a/compiler/codeGen/CodeGen/Platform/SPARC.hs
+++ b/compiler/codeGen/CodeGen/Platform/SPARC.hs
@@ -1,9 +1,9 @@
-module CodeGen.Platform.SPARC (callerSaves) where
+module CodeGen.Platform.SPARC where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_sparc 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/X86.hs b/compiler/codeGen/CodeGen/Platform/X86.hs
index c19bf9dcfb..c5ea94f68c 100644
--- a/compiler/codeGen/CodeGen/Platform/X86.hs
+++ b/compiler/codeGen/CodeGen/Platform/X86.hs
@@ -1,9 +1,9 @@
-module CodeGen.Platform.X86 (callerSaves) where
+module CodeGen.Platform.X86 where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_i386 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/CodeGen/Platform/X86_64.hs b/compiler/codeGen/CodeGen/Platform/X86_64.hs
index 59cf788e43..c5aa0808b6 100644
--- a/compiler/codeGen/CodeGen/Platform/X86_64.hs
+++ b/compiler/codeGen/CodeGen/Platform/X86_64.hs
@@ -1,9 +1,9 @@
-module CodeGen.Platform.X86_64 (callerSaves) where
+module CodeGen.Platform.X86_64 where
import CmmExpr
#define MACHREGS_NO_REGS 0
#define MACHREGS_x86_64 1
-#include "../../../../includes/CallerSaves.part.hs"
+#include "../../../../includes/CodeGen.Platform.hs"
diff --git a/compiler/codeGen/StgCmmUtils.hs b/compiler/codeGen/StgCmmUtils.hs
index ad435c740e..d6bc23c0d4 100644
--- a/compiler/codeGen/StgCmmUtils.hs
+++ b/compiler/codeGen/StgCmmUtils.hs
@@ -57,7 +57,7 @@ import StgCmmClosure
import Cmm
import BlockId
import MkGraph
-import CodeGen.CallerSaves
+import CodeGen.Platform
import CLabel
import CmmUtils