blob: 1e9a49f8a60248f9c69dc6b7d470dcd6e4b35b9f (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
|
-- | Free regs map for PowerPC
module GHC.CmmToAsm.Reg.Linear.PPC where
import GHC.Prelude
import GHC.CmmToAsm.PPC.Regs
import GHC.Platform.Reg.Class
import GHC.Platform.Reg
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Platform
import Data.Word
-- The PowerPC has 32 integer and 32 floating point registers.
-- This is 32bit PowerPC, so Word64 is inefficient - two Word32s are much
-- better.
-- Note that when getFreeRegs scans for free registers, it starts at register
-- 31 and counts down. This is a hack for the PowerPC - the higher-numbered
-- registers are callee-saves, while the lower regs are caller-saves, so it
-- makes sense to start at the high end.
-- Apart from that, the code does nothing PowerPC-specific, so feel free to
-- add your favourite platform to the #if (if you have 64 registers but only
-- 32-bit words).
data FreeRegs = FreeRegs !Word32 !Word32
deriving( Show ) -- The Show is used in an ASSERT
instance Outputable FreeRegs where
ppr = text . show
noFreeRegs :: FreeRegs
noFreeRegs = FreeRegs 0 0
releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg (RealRegSingle r) (FreeRegs g f)
| r > 31 = FreeRegs g (f .|. (1 `shiftL` (r - 32)))
| otherwise = FreeRegs (g .|. (1 `shiftL` r)) f
releaseReg _ _
= panic "RegAlloc.Linear.PPC.releaseReg: bad reg"
initFreeRegs :: Platform -> FreeRegs
initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform)
getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -- lazily
getFreeRegs cls (FreeRegs g f)
| RcFloat <- cls = [] -- no float regs on PowerPC, use double
| RcDouble <- cls = go f (0x80000000) 63
| RcInteger <- cls = go g (0x80000000) 31
where
go _ 0 _ = []
go x m i | x .&. m /= 0 = RealRegSingle i : (go x (m `shiftR` 1) $! i-1)
| otherwise = go x (m `shiftR` 1) $! i-1
allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg (RealRegSingle r) (FreeRegs g f)
| r > 31 = FreeRegs g (f .&. complement (1 `shiftL` (r - 32)))
| otherwise = FreeRegs (g .&. complement (1 `shiftL` r)) f
allocateReg _ _
= panic "RegAlloc.Linear.PPC.allocateReg: bad reg"
|