/compiler/GHC/CmmToAsm/Reg/Linear/Base.hs

https://github.com/bgamari/ghc · Haskell · 188 lines · 85 code · 47 blank · 56 comment · 0 complexity · c65677c1ea869e8e28949c771e5520a8 MD5 · raw file

  1. {-# LANGUAGE RecordWildCards #-}
  2. -- | Put common type definitions here to break recursive module dependencies.
  3. module GHC.CmmToAsm.Reg.Linear.Base (
  4. BlockAssignment,
  5. lookupBlockAssignment,
  6. lookupFirstUsed,
  7. emptyBlockAssignment,
  8. updateBlockAssignment,
  9. Loc(..),
  10. regsOfLoc,
  11. -- for stats
  12. SpillReason(..),
  13. RegAllocStats(..),
  14. -- the allocator monad
  15. RA_State(..),
  16. )
  17. where
  18. import GHC.Prelude
  19. import GHC.CmmToAsm.Reg.Linear.StackMap
  20. import GHC.CmmToAsm.Reg.Liveness
  21. import GHC.CmmToAsm.Config
  22. import GHC.Platform.Reg
  23. import GHC.Utils.Outputable
  24. import GHC.Types.Unique
  25. import GHC.Types.Unique.FM
  26. import GHC.Types.Unique.Supply
  27. import GHC.Cmm.BlockId
  28. import GHC.Cmm.Dataflow.Collections
  29. import GHC.CmmToAsm.Reg.Utils
  30. data ReadingOrWriting = Reading | Writing deriving (Eq,Ord)
  31. -- | Used to store the register assignment on entry to a basic block.
  32. -- We use this to handle join points, where multiple branch instructions
  33. -- target a particular label. We have to insert fixup code to make
  34. -- the register assignments from the different sources match up.
  35. --
  36. data BlockAssignment freeRegs
  37. = BlockAssignment { blockMap :: !(BlockMap (freeRegs, RegMap Loc))
  38. , firstUsed :: !(UniqFM VirtualReg RealReg) }
  39. -- | Find the register mapping for a specific BlockId.
  40. lookupBlockAssignment :: BlockId -> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
  41. lookupBlockAssignment bid ba = mapLookup bid (blockMap ba)
  42. -- | Lookup which register a virtual register was first assigned to.
  43. lookupFirstUsed :: VirtualReg -> BlockAssignment freeRegs -> Maybe RealReg
  44. lookupFirstUsed vr ba = lookupUFM (firstUsed ba) vr
  45. -- | An initial empty 'BlockAssignment'
  46. emptyBlockAssignment :: BlockAssignment freeRegs
  47. emptyBlockAssignment = BlockAssignment mapEmpty mempty
  48. -- | Add new register mappings for a specific block.
  49. updateBlockAssignment :: BlockId
  50. -> (freeRegs, RegMap Loc)
  51. -> BlockAssignment freeRegs
  52. -> BlockAssignment freeRegs
  53. updateBlockAssignment dest (freeRegs, regMap) (BlockAssignment {..}) =
  54. BlockAssignment (mapInsert dest (freeRegs, regMap) blockMap)
  55. (mergeUFM combWithExisting id (mapMaybeUFM fromLoc) (firstUsed) (toVRegMap regMap))
  56. where
  57. -- The blocks are processed in dependency order, so if there's already an
  58. -- entry in the map then keep that assignment rather than writing the new
  59. -- assignment.
  60. combWithExisting :: RealReg -> Loc -> Maybe RealReg
  61. combWithExisting old_reg _ = Just $ old_reg
  62. fromLoc :: Loc -> Maybe RealReg
  63. fromLoc (InReg rr) = Just rr
  64. fromLoc (InBoth rr _) = Just rr
  65. fromLoc _ = Nothing
  66. -- | Where a vreg is currently stored
  67. -- A temporary can be marked as living in both a register and memory
  68. -- (InBoth), for example if it was recently loaded from a spill location.
  69. -- This makes it cheap to spill (no save instruction required), but we
  70. -- have to be careful to turn this into InReg if the value in the
  71. -- register is changed.
  72. -- This is also useful when a temporary is about to be clobbered. We
  73. -- save it in a spill location, but mark it as InBoth because the current
  74. -- instruction might still want to read it.
  75. --
  76. data Loc
  77. -- | vreg is in a register
  78. = InReg !RealReg
  79. -- | vreg is held in a stack slot
  80. | InMem {-# UNPACK #-} !StackSlot
  81. -- | vreg is held in both a register and a stack slot
  82. | InBoth !RealReg
  83. {-# UNPACK #-} !StackSlot
  84. deriving (Eq, Show, Ord)
  85. instance Outputable Loc where
  86. ppr l = text (show l)
  87. -- | Get the reg numbers stored in this Loc.
  88. regsOfLoc :: Loc -> [RealReg]
  89. regsOfLoc (InReg r) = [r]
  90. regsOfLoc (InBoth r _) = [r]
  91. regsOfLoc (InMem _) = []
  92. -- | Reasons why instructions might be inserted by the spiller.
  93. -- Used when generating stats for -ddrop-asm-stats.
  94. --
  95. data SpillReason
  96. -- | vreg was spilled to a slot so we could use its
  97. -- current hreg for another vreg
  98. = SpillAlloc !Unique
  99. -- | vreg was moved because its hreg was clobbered
  100. | SpillClobber !Unique
  101. -- | vreg was loaded from a spill slot
  102. | SpillLoad !Unique
  103. -- | reg-reg move inserted during join to targets
  104. | SpillJoinRR !Unique
  105. -- | reg-mem move inserted during join to targets
  106. | SpillJoinRM !Unique
  107. -- | Used to carry interesting stats out of the register allocator.
  108. data RegAllocStats
  109. = RegAllocStats
  110. { ra_spillInstrs :: UniqFM Unique [Int] -- Keys are the uniques of regs
  111. -- and taken from SpillReason
  112. -- See Note [UniqFM and the register allocator]
  113. , ra_fixupList :: [(BlockId,BlockId,BlockId)]
  114. -- ^ (from,fixup,to) : We inserted fixup code between from and to
  115. }
  116. -- | The register allocator state
  117. data RA_State freeRegs
  118. = RA_State
  119. {
  120. -- | the current mapping from basic blocks to
  121. -- the register assignments at the beginning of that block.
  122. ra_blockassig :: BlockAssignment freeRegs
  123. -- | free machine registers
  124. , ra_freeregs :: !freeRegs
  125. -- | assignment of temps to locations
  126. , ra_assig :: RegMap Loc
  127. -- | current stack delta
  128. , ra_delta :: Int
  129. -- | free stack slots for spilling
  130. , ra_stack :: StackMap
  131. -- | unique supply for generating names for join point fixup blocks.
  132. , ra_us :: UniqSupply
  133. -- | Record why things were spilled, for -ddrop-asm-stats.
  134. -- Just keep a list here instead of a map of regs -> reasons.
  135. -- We don't want to slow down the allocator if we're not going to emit the stats.
  136. , ra_spills :: [SpillReason]
  137. -- | Native code generator configuration
  138. , ra_config :: !NCGConfig
  139. -- | (from,fixup,to) : We inserted fixup code between from and to
  140. , ra_fixups :: [(BlockId,BlockId,BlockId)]
  141. }