{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- | Free regs map for i386
module GHC.CmmToAsm.Reg.Linear.X86 where

import GHC.Prelude

import GHC.CmmToAsm.X86.Regs
import GHC.Platform.Reg.Class
import GHC.Platform.Reg
import GHC.Utils.Panic
import GHC.Platform
import GHC.Utils.Outputable

import Data.Word
import Data.Bits

newtype FreeRegs = FreeRegs 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,Rational -> FreeRegs -> SDoc
FreeRegs -> SDoc
(FreeRegs -> SDoc)
-> (Rational -> FreeRegs -> SDoc) -> Outputable FreeRegs
forall a. (a -> SDoc) -> (Rational -> a -> SDoc) -> Outputable a
pprPrec :: Rational -> FreeRegs -> SDoc
$cpprPrec :: Rational -> FreeRegs -> SDoc
ppr :: FreeRegs -> SDoc
$cppr :: FreeRegs -> SDoc
Outputable)

noFreeRegs :: FreeRegs
noFreeRegs :: FreeRegs
noFreeRegs = Word32 -> FreeRegs
FreeRegs Word32
0

releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg (RealRegSingle Int
n) (FreeRegs Word32
f)
        = Word32 -> FreeRegs
FreeRegs (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
n))

releaseReg RealReg
_ FreeRegs
_
        = String -> FreeRegs
forall a. String -> a
panic String
"RegAlloc.Linear.X86.FreeRegs.releaseReg: no 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 :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazily
getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg]
getFreeRegs Platform
platform RegClass
cls (FreeRegs Word32
f) = Word32 -> Int -> [RealReg]
forall {a}. (Num a, Bits a) => a -> Int -> [RealReg]
go Word32
f Int
0

  where go :: a -> Int -> [RealReg]
go a
0 Int
_ = []
        go a
n Int
m
          | a
n a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
0 Bool -> Bool -> Bool
&& Platform -> RealReg -> RegClass
classOfRealReg Platform
platform (Int -> RealReg
RealRegSingle Int
m) RegClass -> RegClass -> Bool
forall a. Eq a => a -> a -> Bool
== RegClass
cls
          = Int -> RealReg
RealRegSingle Int
m RealReg -> [RealReg] -> [RealReg]
forall a. a -> [a] -> [a]
: (a -> Int -> [RealReg]
go (a
n 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
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))

          | Bool
otherwise
          = a -> Int -> [RealReg]
go (a
n 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
mInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        -- ToDo: there's no point looking through all the integer registers
        -- in order to find a floating-point one.

allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg (RealRegSingle Int
r) (FreeRegs Word32
f)
        = Word32 -> FreeRegs
FreeRegs (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))

allocateReg RealReg
_ FreeRegs
_
        = String -> FreeRegs
forall a. String -> a
panic String
"RegAlloc.Linear.X86.FreeRegs.allocateReg: no reg"