/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs

https://github.com/pepeiborra/ghc · Haskell · 278 lines · 147 code · 55 blank · 76 comment · 2 complexity · c11e034c10edeba1f8087b582dfb3f36 MD5 · raw file

  1. module RegAlloc.Graph.SpillCost (
  2. SpillCostRecord,
  3. plusSpillCostRecord,
  4. pprSpillCostRecord,
  5. SpillCostInfo,
  6. zeroSpillCostInfo,
  7. plusSpillCostInfo,
  8. slurpSpillCostInfo,
  9. chooseSpill,
  10. lifeMapFromSpillCostInfo
  11. )
  12. where
  13. import RegAlloc.Liveness
  14. import Instruction
  15. import RegClass
  16. import Reg
  17. import GraphBase
  18. import BlockId
  19. import OldCmm
  20. import UniqFM
  21. import UniqSet
  22. import Digraph (flattenSCCs)
  23. import Outputable
  24. import Platform
  25. import State
  26. import Data.List (nub, minimumBy)
  27. import Data.Maybe
  28. type SpillCostRecord
  29. = ( VirtualReg -- register name
  30. , Int -- number of writes to this reg
  31. , Int -- number of reads from this reg
  32. , Int) -- number of instrs this reg was live on entry to
  33. type SpillCostInfo
  34. = UniqFM SpillCostRecord
  35. zeroSpillCostInfo :: SpillCostInfo
  36. zeroSpillCostInfo = emptyUFM
  37. -- | Add two spillCostInfos
  38. plusSpillCostInfo :: SpillCostInfo -> SpillCostInfo -> SpillCostInfo
  39. plusSpillCostInfo sc1 sc2
  40. = plusUFM_C plusSpillCostRecord sc1 sc2
  41. plusSpillCostRecord :: SpillCostRecord -> SpillCostRecord -> SpillCostRecord
  42. plusSpillCostRecord (r1, a1, b1, c1) (r2, a2, b2, c2)
  43. | r1 == r2 = (r1, a1 + a2, b1 + b2, c1 + c2)
  44. | otherwise = error "RegSpillCost.plusRegInt: regs don't match"
  45. -- | Slurp out information used for determining spill costs
  46. -- for each vreg, the number of times it was written to, read from,
  47. -- and the number of instructions it was live on entry to (lifetime)
  48. --
  49. slurpSpillCostInfo :: (PlatformOutputable instr, Instruction instr)
  50. => Platform
  51. -> LiveCmmDecl statics instr
  52. -> SpillCostInfo
  53. slurpSpillCostInfo platform cmm
  54. = execState (countCmm cmm) zeroSpillCostInfo
  55. where
  56. countCmm CmmData{} = return ()
  57. countCmm (CmmProc info _ sccs)
  58. = mapM_ (countBlock info)
  59. $ flattenSCCs sccs
  60. -- lookup the regs that are live on entry to this block in
  61. -- the info table from the CmmProc
  62. countBlock info (BasicBlock blockId instrs)
  63. | LiveInfo _ _ (Just blockLive) _ <- info
  64. , Just rsLiveEntry <- mapLookup blockId blockLive
  65. , rsLiveEntry_virt <- takeVirtuals rsLiveEntry
  66. = countLIs rsLiveEntry_virt instrs
  67. | otherwise
  68. = error "RegAlloc.SpillCost.slurpSpillCostInfo: bad block"
  69. countLIs _ []
  70. = return ()
  71. -- skip over comment and delta pseudo instrs
  72. countLIs rsLive (LiveInstr instr Nothing : lis)
  73. | isMetaInstr instr
  74. = countLIs rsLive lis
  75. | otherwise
  76. = pprPanic "RegSpillCost.slurpSpillCostInfo"
  77. (text "no liveness information on instruction " <> pprPlatform platform instr)
  78. countLIs rsLiveEntry (LiveInstr instr (Just live) : lis)
  79. = do
  80. -- increment the lifetime counts for regs live on entry to this instr
  81. mapM_ incLifetime $ uniqSetToList rsLiveEntry
  82. -- increment counts for what regs were read/written from
  83. let (RU read written) = regUsageOfInstr instr
  84. mapM_ incUses $ catMaybes $ map takeVirtualReg $ nub read
  85. mapM_ incDefs $ catMaybes $ map takeVirtualReg $ nub written
  86. -- compute liveness for entry to next instruction.
  87. let liveDieRead_virt = takeVirtuals (liveDieRead live)
  88. let liveDieWrite_virt = takeVirtuals (liveDieWrite live)
  89. let liveBorn_virt = takeVirtuals (liveBorn live)
  90. let rsLiveAcross
  91. = rsLiveEntry `minusUniqSet` liveDieRead_virt
  92. let rsLiveNext
  93. = (rsLiveAcross `unionUniqSets` liveBorn_virt)
  94. `minusUniqSet` liveDieWrite_virt
  95. countLIs rsLiveNext lis
  96. incDefs reg = modify $ \s -> addToUFM_C plusSpillCostRecord s reg (reg, 1, 0, 0)
  97. incUses reg = modify $ \s -> addToUFM_C plusSpillCostRecord s reg (reg, 0, 1, 0)
  98. incLifetime reg = modify $ \s -> addToUFM_C plusSpillCostRecord s reg (reg, 0, 0, 1)
  99. takeVirtuals :: UniqSet Reg -> UniqSet VirtualReg
  100. takeVirtuals set = mapUniqSet get_virtual
  101. $ filterUniqSet isVirtualReg set
  102. where
  103. get_virtual (RegVirtual vr) = vr
  104. get_virtual _ = panic "getVirt"
  105. -- | Choose a node to spill from this graph
  106. chooseSpill
  107. :: SpillCostInfo
  108. -> Graph VirtualReg RegClass RealReg
  109. -> VirtualReg
  110. chooseSpill info graph
  111. = let cost = spillCost_length info graph
  112. node = minimumBy (\n1 n2 -> compare (cost $ nodeId n1) (cost $ nodeId n2))
  113. $ eltsUFM $ graphMap graph
  114. in nodeId node
  115. -- | Chaitins spill cost function is:
  116. --
  117. -- cost = sum loadCost * freq (u) + sum storeCost * freq (d)
  118. -- u <- uses (v) d <- defs (v)
  119. --
  120. -- There are no loops in our code at the momemnt, so we can set the freq's to 1
  121. -- We divide this by the degree if t
  122. --
  123. --
  124. -- If we don't have live range splitting then Chaitins function performs badly if we have
  125. -- lots of nested live ranges and very few registers.
  126. --
  127. -- v1 v2 v3
  128. -- def v1 .
  129. -- use v1 .
  130. -- def v2 . .
  131. -- def v3 . . .
  132. -- use v1 . . .
  133. -- use v3 . . .
  134. -- use v2 . .
  135. -- use v1 .
  136. --
  137. --
  138. -- defs uses degree cost
  139. -- v1: 1 3 3 1.5
  140. -- v2: 1 2 3 1.0
  141. -- v3: 1 1 3 0.666
  142. --
  143. -- v3 has the lowest cost, but if we only have 2 hardregs and we insert spill code for v3
  144. -- then this isn't going to improve the colorability of the graph.
  145. --
  146. -- When compiling SHA1, which as very long basic blocks and some vregs with very long live ranges
  147. -- the allocator seems to try and spill from the inside out and eventually run out of stack slots.
  148. --
  149. -- Without live range splitting, its's better to spill from the outside in so set the cost of very
  150. -- long live ranges to zero
  151. --
  152. {-
  153. spillCost_chaitin
  154. :: SpillCostInfo
  155. -> Graph Reg RegClass Reg
  156. -> Reg
  157. -> Float
  158. spillCost_chaitin info graph reg
  159. -- Spilling a live range that only lives for 1 instruction isn't going to help
  160. -- us at all - and we definately want to avoid trying to re-spill previously
  161. -- inserted spill code.
  162. | lifetime <= 1 = 1/0
  163. -- It's unlikely that we'll find a reg for a live range this long
  164. -- better to spill it straight up and not risk trying to keep it around
  165. -- and have to go through the build/color cycle again.
  166. | lifetime > allocatableRegsInClass (regClass reg) * 10
  167. = 0
  168. -- otherwise revert to chaitin's regular cost function.
  169. | otherwise = fromIntegral (uses + defs) / fromIntegral (nodeDegree graph reg)
  170. where (_, defs, uses, lifetime)
  171. = fromMaybe (reg, 0, 0, 0) $ lookupUFM info reg
  172. -}
  173. -- Just spill the longest live range.
  174. spillCost_length
  175. :: SpillCostInfo
  176. -> Graph VirtualReg RegClass RealReg
  177. -> VirtualReg
  178. -> Float
  179. spillCost_length info _ reg
  180. | lifetime <= 1 = 1/0
  181. | otherwise = 1 / fromIntegral lifetime
  182. where (_, _, _, lifetime)
  183. = fromMaybe (reg, 0, 0, 0)
  184. $ lookupUFM info reg
  185. lifeMapFromSpillCostInfo :: SpillCostInfo -> UniqFM (VirtualReg, Int)
  186. lifeMapFromSpillCostInfo info
  187. = listToUFM
  188. $ map (\(r, _, _, life) -> (r, (r, life)))
  189. $ eltsUFM info
  190. -- | Work out the degree (number of neighbors) of this node which have the same class.
  191. nodeDegree
  192. :: (VirtualReg -> RegClass)
  193. -> Graph VirtualReg RegClass RealReg
  194. -> VirtualReg
  195. -> Int
  196. nodeDegree classOfVirtualReg graph reg
  197. | Just node <- lookupUFM (graphMap graph) reg
  198. , virtConflicts <- length
  199. $ filter (\r -> classOfVirtualReg r == classOfVirtualReg reg)
  200. $ uniqSetToList
  201. $ nodeConflicts node
  202. = virtConflicts + sizeUniqSet (nodeExclusions node)
  203. | otherwise
  204. = 0
  205. -- | Show a spill cost record, including the degree from the graph and final calulated spill cos
  206. pprSpillCostRecord
  207. :: (VirtualReg -> RegClass)
  208. -> (Reg -> SDoc)
  209. -> Graph VirtualReg RegClass RealReg
  210. -> SpillCostRecord
  211. -> SDoc
  212. pprSpillCostRecord regClass pprReg graph (reg, uses, defs, life)
  213. = hsep
  214. [ pprReg (RegVirtual reg)
  215. , ppr uses
  216. , ppr defs
  217. , ppr life
  218. , ppr $ nodeDegree regClass graph reg
  219. , text $ show $ (fromIntegral (uses + defs)
  220. / fromIntegral (nodeDegree regClass graph reg) :: Float) ]