never executed always true always false
    1 
    2 -- | The assignment of virtual registers to stack slots
    3 
    4 --      We have lots of stack slots. Memory-to-memory moves are a pain on most
    5 --      architectures. Therefore, we avoid having to generate memory-to-memory moves
    6 --      by simply giving every virtual register its own stack slot.
    7 
    8 --      The StackMap stack map keeps track of virtual register - stack slot
    9 --      associations and of which stack slots are still free. Once it has been
   10 --      associated, a stack slot is never "freed" or removed from the StackMap again,
   11 --      it remains associated until we are done with the current CmmProc.
   12 --
   13 module GHC.CmmToAsm.Reg.Linear.StackMap (
   14         StackSlot,
   15         StackMap(..),
   16         emptyStackMap,
   17         getStackSlotFor,
   18         getStackUse
   19 )
   20 
   21 where
   22 
   23 import GHC.Prelude
   24 
   25 import GHC.Types.Unique.FM
   26 import GHC.Types.Unique
   27 
   28 
   29 -- | Identifier for a stack slot.
   30 type StackSlot = Int
   31 
   32 data StackMap
   33         = StackMap
   34         { -- | The slots that are still available to be allocated.
   35           stackMapNextFreeSlot  :: !Int
   36 
   37           -- See Note [UniqFM and the register allocator]
   38           -- | Assignment of vregs to stack slots.
   39         , stackMapAssignment    :: UniqFM Unique StackSlot }
   40 
   41 
   42 -- | An empty stack map, with all slots available.
   43 emptyStackMap :: StackMap
   44 emptyStackMap = StackMap 0 emptyUFM
   45 
   46 
   47 -- | If this vreg unique already has a stack assignment then return the slot number,
   48 --      otherwise allocate a new slot, and update the map.
   49 --
   50 getStackSlotFor :: StackMap -> Unique -> (StackMap, Int)
   51 
   52 getStackSlotFor fs@(StackMap _ reserved) reg
   53   | Just slot <- lookupUFM reserved reg  =  (fs, slot)
   54 
   55 getStackSlotFor (StackMap freeSlot reserved) reg =
   56     (StackMap (freeSlot+1) (addToUFM reserved reg freeSlot), freeSlot)
   57 
   58 -- | Return the number of stack slots that were allocated
   59 getStackUse :: StackMap -> Int
   60 getStackUse (StackMap freeSlot _) = freeSlot
   61