{-# LANGUAGE CPP #-}

module GHC.CmmToAsm.X86.Regs (
        -- squeese functions for the graph allocator
        virtualRegSqueeze,
        realRegSqueeze,

        -- immediates
        Imm(..),
        strImmLit,
        litToImm,

        -- addressing modes
        AddrMode(..),
        addrOffset,

        -- registers
        spRel,
        argRegs,
        allArgRegs,
        allIntArgRegs,
        callClobberedRegs,
        instrClobberedRegs,
        allMachRegNos,
        classOfRealReg,
        showReg,

        -- machine specific
        EABase(..), EAIndex(..), addrModeRegs,

        eax, ebx, ecx, edx, esi, edi, ebp, esp,


        rax, rbx, rcx, rdx, rsi, rdi, rbp, rsp,
        r8,  r9,  r10, r11, r12, r13, r14, r15,
        lastint,
        xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
        xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15,
        xmm,
        firstxmm, lastxmm,

        ripRel,
        allFPArgRegs,

        allocatableRegs
)

where

#include "HsVersions.h"

import GHC.Prelude

import GHC.Platform.Regs
import GHC.Platform.Reg
import GHC.Platform.Reg.Class

import GHC.Cmm
import GHC.Cmm.CLabel           ( CLabel )
import GHC.Utils.Outputable
import GHC.Platform

import qualified Data.Array as A

-- | regSqueeze_class reg
--      Calculate the maximum number of register colors that could be
--      denied to a node of this class due to having this reg
--      as a neighbour.
--
{-# INLINE virtualRegSqueeze #-}
virtualRegSqueeze :: RegClass -> VirtualReg -> Int

virtualRegSqueeze :: RegClass -> VirtualReg -> Int
virtualRegSqueeze RegClass
cls VirtualReg
vr
 = case RegClass
cls of
        RegClass
RcInteger
         -> case VirtualReg
vr of
                VirtualRegI{}           -> Int
1
                VirtualRegHi{}          -> Int
1
                VirtualReg
_other                  -> Int
0

        RegClass
RcDouble
         -> case VirtualReg
vr of
                VirtualRegD{}           -> Int
1
                VirtualRegF{}           -> Int
0
                VirtualReg
_other                  -> Int
0


        RegClass
_other -> Int
0

{-# INLINE realRegSqueeze #-}
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze :: RegClass -> RealReg -> Int
realRegSqueeze RegClass
cls RealReg
rr
 = case RegClass
cls of
        RegClass
RcInteger
         -> case RealReg
rr of
                RealRegSingle Int
regNo
                        | Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
firstxmm -> Int
1
                        | Bool
otherwise     -> Int
0

                RealRegPair{}           -> Int
0

        RegClass
RcDouble
         -> case RealReg
rr of
                RealRegSingle Int
regNo
                        | Int
regNo Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstxmm  -> Int
1
                        | Bool
otherwise     -> Int
0

                RealRegPair{}           -> Int
0


        RegClass
_other -> Int
0

-- -----------------------------------------------------------------------------
-- Immediates

data Imm
  = ImmInt      Int
  | ImmInteger  Integer     -- Sigh.
  | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
  | ImmLit      SDoc        -- Simple string
  | ImmIndex    CLabel Int
  | ImmFloat    Rational
  | ImmDouble   Rational
  | ImmConstantSum Imm Imm
  | ImmConstantDiff Imm Imm

strImmLit :: String -> Imm
strImmLit :: String -> Imm
strImmLit String
s = SDoc -> Imm
ImmLit (String -> SDoc
text String
s)


litToImm :: CmmLit -> Imm
litToImm :: CmmLit -> Imm
litToImm (CmmInt Integer
i Width
w)        = Integer -> Imm
ImmInteger (Width -> Integer -> Integer
narrowS Width
w Integer
i)
                -- narrow to the width: a CmmInt might be out of
                -- range, but we assume that ImmInteger only contains
                -- in-range values.  A signed value should be fine here.
litToImm (CmmFloat Rational
f Width
W32)    = Rational -> Imm
ImmFloat Rational
f
litToImm (CmmFloat Rational
f Width
W64)    = Rational -> Imm
ImmDouble Rational
f
litToImm (CmmLabel CLabel
l)        = CLabel -> Imm
ImmCLbl CLabel
l
litToImm (CmmLabelOff CLabel
l Int
off) = CLabel -> Int -> Imm
ImmIndex CLabel
l Int
off
litToImm (CmmLabelDiffOff CLabel
l1 CLabel
l2 Int
off Width
_)
                             = Imm -> Imm -> Imm
ImmConstantSum
                               (Imm -> Imm -> Imm
ImmConstantDiff (CLabel -> Imm
ImmCLbl CLabel
l1) (CLabel -> Imm
ImmCLbl CLabel
l2))
                               (Int -> Imm
ImmInt Int
off)
litToImm CmmLit
_                   = String -> Imm
forall a. String -> a
panic String
"X86.Regs.litToImm: no match"

-- addressing modes ------------------------------------------------------------

data AddrMode
        = AddrBaseIndex EABase EAIndex Displacement
        | ImmAddr Imm Int

data EABase       = EABaseNone  | EABaseReg Reg | EABaseRip
data EAIndex      = EAIndexNone | EAIndex Reg Int
type Displacement = Imm


addrOffset :: AddrMode -> Int -> Maybe AddrMode
addrOffset :: AddrMode -> Int -> Maybe AddrMode
addrOffset AddrMode
addr Int
off
  = case AddrMode
addr of
      ImmAddr Imm
i Int
off0      -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (Imm -> Int -> AddrMode
ImmAddr Imm
i (Int
off0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
off))

      AddrBaseIndex EABase
r EAIndex
i (ImmInt Int
n) -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (Int -> Imm
ImmInt (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
off)))
      AddrBaseIndex EABase
r EAIndex
i (ImmInteger Integer
n)
        -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (Int -> Imm
ImmInt (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
off))))

      AddrBaseIndex EABase
r EAIndex
i (ImmCLbl CLabel
lbl)
        -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (CLabel -> Int -> Imm
ImmIndex CLabel
lbl Int
off))

      AddrBaseIndex EABase
r EAIndex
i (ImmIndex CLabel
lbl Int
ix)
        -> AddrMode -> Maybe AddrMode
forall a. a -> Maybe a
Just (EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
r EAIndex
i (CLabel -> Int -> Imm
ImmIndex CLabel
lbl (Int
ixInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
off)))

      AddrMode
_ -> Maybe AddrMode
forall a. Maybe a
Nothing  -- in theory, shouldn't happen


addrModeRegs :: AddrMode -> [Reg]
addrModeRegs :: AddrMode -> [Reg]
addrModeRegs (AddrBaseIndex EABase
b EAIndex
i Imm
_) =  [Reg]
b_regs [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ [Reg]
i_regs
  where
   b_regs :: [Reg]
b_regs = case EABase
b of { EABaseReg Reg
r -> [Reg
r]; EABase
_ -> [] }
   i_regs :: [Reg]
i_regs = case EAIndex
i of { EAIndex Reg
r Int
_ -> [Reg
r]; EAIndex
_ -> [] }
addrModeRegs AddrMode
_ = []


-- registers -------------------------------------------------------------------

-- @spRel@ gives us a stack relative addressing mode for volatile
-- temporaries and for excess call arguments.  @fpRel@, where
-- applicable, is the same but for the frame pointer.


spRel :: Platform
      -> Int -- ^ desired stack offset in bytes, positive or negative
      -> AddrMode
spRel :: Platform -> Int -> AddrMode
spRel Platform
platform Int
n
 | Platform -> Bool
target32Bit Platform
platform
    = EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex (Reg -> EABase
EABaseReg Reg
esp) EAIndex
EAIndexNone (Int -> Imm
ImmInt Int
n)
 | Bool
otherwise
    = EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex (Reg -> EABase
EABaseReg Reg
rsp) EAIndex
EAIndexNone (Int -> Imm
ImmInt Int
n)

-- The register numbers must fit into 32 bits on x86, so that we can
-- use a Word32 to represent the set of free registers in the register
-- allocator.



firstxmm :: RegNo
firstxmm :: Int
firstxmm  = Int
16

--  on 32bit platformOSs, only the first 8 XMM/YMM/ZMM registers are available
lastxmm :: Platform -> RegNo
lastxmm :: Platform -> Int
lastxmm Platform
platform
 | Platform -> Bool
target32Bit Platform
platform = Int
firstxmm Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7  -- xmm0 - xmmm7
 | Bool
otherwise            = Int
firstxmm Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
15 -- xmm0 -xmm15

lastint :: Platform -> RegNo
lastint :: Platform -> Int
lastint Platform
platform
 | Platform -> Bool
target32Bit Platform
platform = Int
7 -- not %r8..%r15
 | Bool
otherwise            = Int
15

intregnos :: Platform -> [RegNo]
intregnos :: Platform -> [Int]
intregnos Platform
platform = [Int
0 .. Platform -> Int
lastint Platform
platform]



xmmregnos :: Platform -> [RegNo]
xmmregnos :: Platform -> [Int]
xmmregnos Platform
platform = [Int
firstxmm  .. Platform -> Int
lastxmm Platform
platform]

floatregnos :: Platform -> [RegNo]
floatregnos :: Platform -> [Int]
floatregnos Platform
platform = Platform -> [Int]
xmmregnos Platform
platform

-- argRegs is the set of regs which are read for an n-argument call to C.
-- For archs which pass all args on the stack (x86), is empty.
-- Sparc passes up to the first 6 args in regs.
argRegs :: RegNo -> [Reg]
argRegs :: Int -> [Reg]
argRegs Int
_       = String -> [Reg]
forall a. String -> a
panic String
"MachRegs.argRegs(x86): should not be used!"

-- | The complete set of machine registers.
allMachRegNos :: Platform -> [RegNo]
allMachRegNos :: Platform -> [Int]
allMachRegNos Platform
platform = Platform -> [Int]
intregnos Platform
platform [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Platform -> [Int]
floatregnos Platform
platform

-- | Take the class of a register.
{-# INLINE classOfRealReg #-}
classOfRealReg :: Platform -> RealReg -> RegClass
-- On x86, we might want to have an 8-bit RegClass, which would
-- contain just regs 1-4 (the others don't have 8-bit versions).
-- However, we can get away without this at the moment because the
-- only allocatable integer regs are also 8-bit compatible (1, 3, 4).
classOfRealReg :: Platform -> RealReg -> RegClass
classOfRealReg Platform
platform RealReg
reg
    = case RealReg
reg of
        RealRegSingle Int
i
            | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Platform -> Int
lastint Platform
platform -> RegClass
RcInteger
            | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Platform -> Int
lastxmm Platform
platform -> RegClass
RcDouble
            | Bool
otherwise             -> String -> RegClass
forall a. String -> a
panic String
"X86.Reg.classOfRealReg registerSingle too high"
        RealReg
_   -> String -> RegClass
forall a. String -> a
panic String
"X86.Regs.classOfRealReg: RegPairs on this arch"

-- | Get the name of the register with this number.
-- NOTE: fixme, we dont track which "way" the XMM registers are used
showReg :: Platform -> RegNo -> String
showReg :: Platform -> Int -> String
showReg Platform
platform Int
n
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
firstxmm Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Platform -> Int
lastxmm  Platform
platform = String
"%xmm" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
firstxmm)
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
8   Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
firstxmm      = String
"%r" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
        | Bool
otherwise      = Platform -> Array Int String
regNames Platform
platform Array Int String -> Int -> String
forall i e. Ix i => Array i e -> i -> e
A.! Int
n

regNames :: Platform -> A.Array Int String
regNames :: Platform -> Array Int String
regNames Platform
platform
    = if Platform -> Bool
target32Bit Platform
platform
      then (Int, Int) -> [String] -> Array Int String
forall i e. Ix i => (i, i) -> [e] -> Array i e
A.listArray (Int
0,Int
8) [String
"%eax", String
"%ebx", String
"%ecx", String
"%edx", String
"%esi", String
"%edi", String
"%ebp", String
"%esp"]
      else (Int, Int) -> [String] -> Array Int String
forall i e. Ix i => (i, i) -> [e] -> Array i e
A.listArray (Int
0,Int
8) [String
"%rax", String
"%rbx", String
"%rcx", String
"%rdx", String
"%rsi", String
"%rdi", String
"%rbp", String
"%rsp"]



-- machine specific ------------------------------------------------------------


{-
Intel x86 architecture:
- All registers except 7 (esp) are available for use.
- Only ebx, esi, edi and esp are available across a C call (they are callee-saves).
- Registers 0-7 have 16-bit counterparts (ax, bx etc.)
- Registers 0-3 have 8 bit counterparts (ah, bh etc.)

The fp registers are all Double registers; we don't have any RcFloat class
regs.  @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should
never generate them.

TODO: cleanup modelling float vs double registers and how they are the same class.
-}


eax, ebx, ecx, edx, esp, ebp, esi, edi :: Reg

eax :: Reg
eax   = Int -> Reg
regSingle Int
0
ebx :: Reg
ebx   = Int -> Reg
regSingle Int
1
ecx :: Reg
ecx   = Int -> Reg
regSingle Int
2
edx :: Reg
edx   = Int -> Reg
regSingle Int
3
esi :: Reg
esi   = Int -> Reg
regSingle Int
4
edi :: Reg
edi   = Int -> Reg
regSingle Int
5
ebp :: Reg
ebp   = Int -> Reg
regSingle Int
6
esp :: Reg
esp   = Int -> Reg
regSingle Int
7




{-
AMD x86_64 architecture:
- All 16 integer registers are addressable as 8, 16, 32 and 64-bit values:

  8     16    32    64
  ---------------------
  al    ax    eax   rax
  bl    bx    ebx   rbx
  cl    cx    ecx   rcx
  dl    dx    edx   rdx
  sil   si    esi   rsi
  dil   si    edi   rdi
  bpl   bp    ebp   rbp
  spl   sp    esp   rsp
  r10b  r10w  r10d  r10
  r11b  r11w  r11d  r11
  r12b  r12w  r12d  r12
  r13b  r13w  r13d  r13
  r14b  r14w  r14d  r14
  r15b  r15w  r15d  r15
-}

rax, rbx, rcx, rdx, rsp, rbp, rsi, rdi,
  r8, r9, r10, r11, r12, r13, r14, r15,
  xmm0, xmm1, xmm2, xmm3, xmm4, xmm5, xmm6, xmm7,
  xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15 :: Reg

rax :: Reg
rax   = Int -> Reg
regSingle Int
0
rbx :: Reg
rbx   = Int -> Reg
regSingle Int
1
rcx :: Reg
rcx   = Int -> Reg
regSingle Int
2
rdx :: Reg
rdx   = Int -> Reg
regSingle Int
3
rsi :: Reg
rsi   = Int -> Reg
regSingle Int
4
rdi :: Reg
rdi   = Int -> Reg
regSingle Int
5
rbp :: Reg
rbp   = Int -> Reg
regSingle Int
6
rsp :: Reg
rsp   = Int -> Reg
regSingle Int
7
r8 :: Reg
r8    = Int -> Reg
regSingle Int
8
r9 :: Reg
r9    = Int -> Reg
regSingle Int
9
r10 :: Reg
r10   = Int -> Reg
regSingle Int
10
r11 :: Reg
r11   = Int -> Reg
regSingle Int
11
r12 :: Reg
r12   = Int -> Reg
regSingle Int
12
r13 :: Reg
r13   = Int -> Reg
regSingle Int
13
r14 :: Reg
r14   = Int -> Reg
regSingle Int
14
r15 :: Reg
r15   = Int -> Reg
regSingle Int
15
xmm0 :: Reg
xmm0  = Int -> Reg
regSingle Int
16
xmm1 :: Reg
xmm1  = Int -> Reg
regSingle Int
17
xmm2 :: Reg
xmm2  = Int -> Reg
regSingle Int
18
xmm3 :: Reg
xmm3  = Int -> Reg
regSingle Int
19
xmm4 :: Reg
xmm4  = Int -> Reg
regSingle Int
20
xmm5 :: Reg
xmm5  = Int -> Reg
regSingle Int
21
xmm6 :: Reg
xmm6  = Int -> Reg
regSingle Int
22
xmm7 :: Reg
xmm7  = Int -> Reg
regSingle Int
23
xmm8 :: Reg
xmm8  = Int -> Reg
regSingle Int
24
xmm9 :: Reg
xmm9  = Int -> Reg
regSingle Int
25
xmm10 :: Reg
xmm10 = Int -> Reg
regSingle Int
26
xmm11 :: Reg
xmm11 = Int -> Reg
regSingle Int
27
xmm12 :: Reg
xmm12 = Int -> Reg
regSingle Int
28
xmm13 :: Reg
xmm13 = Int -> Reg
regSingle Int
29
xmm14 :: Reg
xmm14 = Int -> Reg
regSingle Int
30
xmm15 :: Reg
xmm15 = Int -> Reg
regSingle Int
31

ripRel :: Displacement -> AddrMode
ripRel :: Imm -> AddrMode
ripRel Imm
imm      = EABase -> EAIndex -> Imm -> AddrMode
AddrBaseIndex EABase
EABaseRip EAIndex
EAIndexNone Imm
imm


 -- so we can re-use some x86 code:
{-
eax = rax
ebx = rbx
ecx = rcx
edx = rdx
esi = rsi
edi = rdi
ebp = rbp
esp = rsp
-}

xmm :: RegNo -> Reg
xmm :: Int -> Reg
xmm Int
n = Int -> Reg
regSingle (Int
firstxmmInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n)




-- | these are the regs which we cannot assume stay alive over a C call.
callClobberedRegs       :: Platform -> [Reg]
-- caller-saves registers
callClobberedRegs :: Platform -> [Reg]
callClobberedRegs Platform
platform
 | Platform -> Bool
target32Bit Platform
platform = [Reg
eax,Reg
ecx,Reg
edx] [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle (Platform -> [Int]
floatregnos Platform
platform)
 | Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
   = [Reg
rax,Reg
rcx,Reg
rdx,Reg
r8,Reg
r9,Reg
r10,Reg
r11]
   -- Only xmm0-5 are caller-saves registers on 64bit windows.
   -- ( https://docs.microsoft.com/en-us/cpp/build/register-usage )
   -- For details check the Win64 ABI.
   [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
xmm [Int
0  .. Int
5]
 | Bool
otherwise
    -- all xmm regs are caller-saves
    -- caller-saves registers
    = [Reg
rax,Reg
rcx,Reg
rdx,Reg
rsi,Reg
rdi,Reg
r8,Reg
r9,Reg
r10,Reg
r11]
   [Reg] -> [Reg] -> [Reg]
forall a. [a] -> [a] -> [a]
++ (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle (Platform -> [Int]
floatregnos Platform
platform)

allArgRegs :: Platform -> [(Reg, Reg)]
allArgRegs :: Platform -> [(Reg, Reg)]
allArgRegs Platform
platform
 | Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32 = [Reg] -> [Reg] -> [(Reg, Reg)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Reg
rcx,Reg
rdx,Reg
r8,Reg
r9]
                                          ((Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle [Int
firstxmm ..])
 | Bool
otherwise = String -> [(Reg, Reg)]
forall a. String -> a
panic String
"X86.Regs.allArgRegs: not defined for this arch"

allIntArgRegs :: Platform -> [Reg]
allIntArgRegs :: Platform -> [Reg]
allIntArgRegs Platform
platform
 | (Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32) Bool -> Bool -> Bool
|| Platform -> Bool
target32Bit Platform
platform
    = String -> [Reg]
forall a. String -> a
panic String
"X86.Regs.allIntArgRegs: not defined for this platform"
 | Bool
otherwise = [Reg
rdi,Reg
rsi,Reg
rdx,Reg
rcx,Reg
r8,Reg
r9]


-- | on 64bit platforms we pass the first 8 float/double arguments
-- in the xmm registers.
allFPArgRegs :: Platform -> [Reg]
allFPArgRegs :: Platform -> [Reg]
allFPArgRegs Platform
platform
 | Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
== OS
OSMinGW32
    = String -> [Reg]
forall a. String -> a
panic String
"X86.Regs.allFPArgRegs: not defined for this platform"
 | Bool
otherwise = (Int -> Reg) -> [Int] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Reg
regSingle [Int
firstxmm .. Int
firstxmm Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7 ]


-- Machine registers which might be clobbered by instructions that
-- generate results into fixed registers, or need arguments in a fixed
-- register.
instrClobberedRegs :: Platform -> [Reg]
instrClobberedRegs :: Platform -> [Reg]
instrClobberedRegs Platform
platform
 | Platform -> Bool
target32Bit Platform
platform = [ Reg
eax, Reg
ecx, Reg
edx ]
 | Bool
otherwise            = [ Reg
rax, Reg
rcx, Reg
rdx ]

--

-- allocatableRegs is allMachRegNos with the fixed-use regs removed.
-- i.e., these are the regs for which we are prepared to allow the
-- register allocator to attempt to map VRegs to.
allocatableRegs :: Platform -> [RealReg]
allocatableRegs :: Platform -> [RealReg]
allocatableRegs Platform
platform
   = let isFree :: Int -> Bool
isFree Int
i = Platform -> Int -> Bool
freeReg Platform
platform Int
i
     in  (Int -> RealReg) -> [Int] -> [RealReg]
forall a b. (a -> b) -> [a] -> [b]
map Int -> RealReg
RealRegSingle ([Int] -> [RealReg]) -> [Int] -> [RealReg]
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter Int -> Bool
isFree (Platform -> [Int]
allMachRegNos Platform
platform)