-- | The assignment of virtual registers to stack slots

--      We have lots of stack slots. Memory-to-memory moves are a pain on most
--      architectures. Therefore, we avoid having to generate memory-to-memory moves
--      by simply giving every virtual register its own stack slot.

--      The StackMap stack map keeps track of virtual register - stack slot
--      associations and of which stack slots are still free. Once it has been
--      associated, a stack slot is never "freed" or removed from the StackMap again,
--      it remains associated until we are done with the current CmmProc.
--
module GHC.CmmToAsm.Reg.Linear.StackMap (
        StackSlot,
        StackMap(..),
        emptyStackMap,
        getStackSlotFor,
        getStackUse
)

where

import GHC.Prelude

import GHC.Types.Unique.FM
import GHC.Types.Unique


-- | Identifier for a stack slot.
type StackSlot = Int

data StackMap
        = StackMap
        { -- | The slots that are still available to be allocated.
          StackMap -> Int
stackMapNextFreeSlot  :: !Int

          -- See Note [UniqFM and the register allocator]
          -- | Assignment of vregs to stack slots.
        , StackMap -> UniqFM Unique Int
stackMapAssignment    :: UniqFM Unique StackSlot }


-- | An empty stack map, with all slots available.
emptyStackMap :: StackMap
emptyStackMap :: StackMap
emptyStackMap = Int -> UniqFM Unique Int -> StackMap
StackMap Int
0 UniqFM Unique Int
forall key elt. UniqFM key elt
emptyUFM


-- | If this vreg unique already has a stack assignment then return the slot number,
--      otherwise allocate a new slot, and update the map.
--
getStackSlotFor :: StackMap -> Unique -> (StackMap, Int)

getStackSlotFor :: StackMap -> Unique -> (StackMap, Int)
getStackSlotFor fs :: StackMap
fs@(StackMap Int
_ UniqFM Unique Int
reserved) Unique
reg
  | Just Int
slot <- UniqFM Unique Int -> Unique -> Maybe Int
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM Unique Int
reserved Unique
reg  =  (StackMap
fs, Int
slot)

getStackSlotFor (StackMap Int
freeSlot UniqFM Unique Int
reserved) Unique
reg =
    (Int -> UniqFM Unique Int -> StackMap
StackMap (Int
freeSlotInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (UniqFM Unique Int -> Unique -> Int -> UniqFM Unique Int
forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM Unique Int
reserved Unique
reg Int
freeSlot), Int
freeSlot)

-- | Return the number of stack slots that were allocated
getStackUse :: StackMap -> Int
getStackUse :: StackMap -> Int
getStackUse (StackMap Int
freeSlot UniqFM Unique Int
_) = Int
freeSlot