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