module GHC.CmmToAsm.SPARC.Stack (
        spRel,
        fpRel,
        spillSlotToOffset,
        maxSpillSlots
)

where

import GHC.Prelude

import GHC.CmmToAsm.SPARC.AddrMode
import GHC.CmmToAsm.SPARC.Regs
import GHC.CmmToAsm.SPARC.Base
import GHC.CmmToAsm.SPARC.Imm
import GHC.CmmToAsm.Config

import GHC.Utils.Outputable
import GHC.Utils.Panic

-- | Get an AddrMode relative to the address in sp.
--      This gives us a stack relative addressing mode for volatile
--      temporaries and for excess call arguments.
--
spRel :: Int            -- ^ stack offset in words, positive or negative
      -> AddrMode

spRel :: Int -> AddrMode
spRel Int
n = Reg -> Imm -> AddrMode
AddrRegImm Reg
sp (Int -> Imm
ImmInt (Int
n forall a. Num a => a -> a -> a
* Int
wordLength))


-- | Get an address relative to the frame pointer.
--      This doesn't work work for offsets greater than 13 bits; we just hope for the best
--
fpRel :: Int -> AddrMode
fpRel :: Int -> AddrMode
fpRel Int
n
        = Reg -> Imm -> AddrMode
AddrRegImm Reg
fp (Int -> Imm
ImmInt (Int
n forall a. Num a => a -> a -> a
* Int
wordLength))


-- | Convert a spill slot number to a *byte* offset, with no sign.
--
spillSlotToOffset :: NCGConfig -> Int -> Int
spillSlotToOffset :: NCGConfig -> Int -> Int
spillSlotToOffset NCGConfig
config Int
slot
        | Int
slot forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
slot forall a. Ord a => a -> a -> Bool
< NCGConfig -> Int
maxSpillSlots NCGConfig
config
        = Int
64 forall a. Num a => a -> a -> a
+ Int
spillSlotSize forall a. Num a => a -> a -> a
* Int
slot

        | Bool
otherwise
        = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"spillSlotToOffset:"
                      (   String -> SDoc
text String
"invalid spill location: " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
slot
                      SDoc -> SDoc -> SDoc
$$  String -> SDoc
text String
"maxSpillSlots:          " SDoc -> SDoc -> SDoc
<> Int -> SDoc
int (NCGConfig -> Int
maxSpillSlots NCGConfig
config))


-- | The maximum number of spill slots available on the C stack.
--      If we use up all of the slots, then we're screwed.
--
--      Why do we reserve 64 bytes, instead of using the whole thing??
--              -- BL 2009/02/15
--
maxSpillSlots :: NCGConfig -> Int
maxSpillSlots :: NCGConfig -> Int
maxSpillSlots NCGConfig
config
        = ((NCGConfig -> Int
ncgSpillPreallocSize NCGConfig
config forall a. Num a => a -> a -> a
- Int
64) forall a. Integral a => a -> a -> a
`div` Int
spillSlotSize) forall a. Num a => a -> a -> a
- Int
1