module RegAlloc.Linear.PPC.FreeRegs
where
import GhcPrelude
import PPC.Regs
import RegClass
import Reg
import Outputable
import GHC.Platform
import Data.Word
import Data.Bits
data FreeRegs = FreeRegs !Word32 !Word32
deriving( Int -> FreeRegs -> ShowS
[FreeRegs] -> ShowS
FreeRegs -> String
(Int -> FreeRegs -> ShowS)
-> (FreeRegs -> String) -> ([FreeRegs] -> ShowS) -> Show FreeRegs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FreeRegs] -> ShowS
$cshowList :: [FreeRegs] -> ShowS
show :: FreeRegs -> String
$cshow :: FreeRegs -> String
showsPrec :: Int -> FreeRegs -> ShowS
$cshowsPrec :: Int -> FreeRegs -> ShowS
Show )
noFreeRegs :: FreeRegs
noFreeRegs :: FreeRegs
noFreeRegs = Word32 -> Word32 -> FreeRegs
FreeRegs Word32
0 Word32
0
releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg (RealRegSingle Int
r) (FreeRegs Word32
g Word32
f)
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 = Word32 -> Word32 -> FreeRegs
FreeRegs Word32
g (Word32
f Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word32
1 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` (Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)))
| Bool
otherwise = Word32 -> Word32 -> FreeRegs
FreeRegs (Word32
g Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word32
1 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
r)) Word32
f
releaseReg RealReg
_ FreeRegs
_
= String -> FreeRegs
forall a. String -> a
panic String
"RegAlloc.Linear.PPC.releaseReg: bad reg"
initFreeRegs :: Platform -> FreeRegs
initFreeRegs :: Platform -> FreeRegs
initFreeRegs Platform
platform = (FreeRegs -> RealReg -> FreeRegs)
-> FreeRegs -> [RealReg] -> FreeRegs
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((RealReg -> FreeRegs -> FreeRegs)
-> FreeRegs -> RealReg -> FreeRegs
forall a b c. (a -> b -> c) -> b -> a -> c
flip RealReg -> FreeRegs -> FreeRegs
releaseReg) FreeRegs
noFreeRegs (Platform -> [RealReg]
allocatableRegs Platform
platform)
getFreeRegs :: RegClass -> FreeRegs -> [RealReg]
getFreeRegs :: RegClass -> FreeRegs -> [RealReg]
getFreeRegs RegClass
cls (FreeRegs Word32
g Word32
f)
| RegClass
RcDouble <- RegClass
cls = Word32 -> Word32 -> Int -> [RealReg]
forall a. (Num a, Bits a) => a -> a -> Int -> [RealReg]
go Word32
f (Word32
0x80000000) Int
63
| RegClass
RcInteger <- RegClass
cls = Word32 -> Word32 -> Int -> [RealReg]
forall a. (Num a, Bits a) => a -> a -> Int -> [RealReg]
go Word32
g (Word32
0x80000000) Int
31
| Bool
otherwise = String -> SDoc -> [RealReg]
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"RegAllocLinear.getFreeRegs: Bad register class" (RegClass -> SDoc
forall a. Outputable a => a -> SDoc
ppr RegClass
cls)
where
go :: a -> a -> Int -> [RealReg]
go a
_ a
0 Int
_ = []
go a
x a
m Int
i | a
x a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
m a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
0 = Int -> RealReg
RealRegSingle Int
i RealReg -> [RealReg] -> [RealReg]
forall a. a -> [a] -> [a]
: (a -> a -> Int -> [RealReg]
go a
x (a
m a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
1) (Int -> [RealReg]) -> Int -> [RealReg]
forall a b. (a -> b) -> a -> b
$! Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
| Bool
otherwise = a -> a -> Int -> [RealReg]
go a
x (a
m a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
1) (Int -> [RealReg]) -> Int -> [RealReg]
forall a b. (a -> b) -> a -> b
$! Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1
allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg (RealRegSingle Int
r) (FreeRegs Word32
g Word32
f)
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
31 = Word32 -> Word32 -> FreeRegs
FreeRegs Word32
g (Word32
f Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32 -> Word32
forall a. Bits a => a -> a
complement (Word32
1 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` (Int
r Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
32)))
| Bool
otherwise = Word32 -> Word32 -> FreeRegs
FreeRegs (Word32
g Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32 -> Word32
forall a. Bits a => a -> a
complement (Word32
1 Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` Int
r)) Word32
f
allocateReg RealReg
_ FreeRegs
_
= String -> FreeRegs
forall a. String -> a
panic String
"RegAlloc.Linear.PPC.allocateReg: bad reg"