PageRenderTime 44ms CodeModel.GetById 16ms RepoModel.GetById 0ms app.codeStats 0ms

/compiler/nativeGen/RegAlloc/Graph/Stats.hs

https://github.com/dorchard/ghc
Haskell | 345 lines | 224 code | 88 blank | 33 comment | 2 complexity | e11eaca592791b4cd2b82dfed95caec4 MD5 | raw file
  1. -- | Carries interesting info for debugging / profiling of the
  2. -- graph coloring register allocator.
  3. module RegAlloc.Graph.Stats (
  4. RegAllocStats (..),
  5. pprStats,
  6. pprStatsSpills,
  7. pprStatsLifetimes,
  8. pprStatsConflict,
  9. pprStatsLifeConflict,
  10. countSRMs, addSRM
  11. ) where
  12. #include "nativeGen/NCG.h"
  13. import qualified GraphColor as Color
  14. import RegAlloc.Liveness
  15. import RegAlloc.Graph.Spill
  16. import RegAlloc.Graph.SpillCost
  17. import RegAlloc.Graph.TrivColorable
  18. import Instruction
  19. import RegClass
  20. import Reg
  21. import TargetReg
  22. import PprCmm()
  23. import Outputable
  24. import UniqFM
  25. import UniqSet
  26. import State
  27. import Data.List
  28. -- | Holds interesting statistics from the register allocator.
  29. data RegAllocStats statics instr
  30. -- Information about the initial conflict graph.
  31. = RegAllocStatsStart
  32. { -- | Initial code, with liveness.
  33. raLiveCmm :: [LiveCmmDecl statics instr]
  34. -- | The initial, uncolored graph.
  35. , raGraph :: Color.Graph VirtualReg RegClass RealReg
  36. -- | Information to help choose which regs to spill.
  37. , raSpillCosts :: SpillCostInfo }
  38. -- Information about an intermediate graph.
  39. -- This is one that we couldn't color, so had to insert spill code
  40. -- instruction stream.
  41. | RegAllocStatsSpill
  42. { -- | Code we tried to allocate registers for.
  43. raCode :: [LiveCmmDecl statics instr]
  44. -- | Partially colored graph.
  45. , raGraph :: Color.Graph VirtualReg RegClass RealReg
  46. -- | The regs that were coaleced.
  47. , raCoalesced :: UniqFM VirtualReg
  48. -- | Spiller stats.
  49. , raSpillStats :: SpillStats
  50. -- | Number of instructions each reg lives for.
  51. , raSpillCosts :: SpillCostInfo
  52. -- | Code with spill instructions added.
  53. , raSpilled :: [LiveCmmDecl statics instr] }
  54. -- a successful coloring
  55. | RegAllocStatsColored
  56. { -- | Code we tried to allocate registers for.
  57. raCode :: [LiveCmmDecl statics instr]
  58. -- | Uncolored graph.
  59. , raGraph :: Color.Graph VirtualReg RegClass RealReg
  60. -- | Coalesced and colored graph.
  61. , raGraphColored :: Color.Graph VirtualReg RegClass RealReg
  62. -- | Regs that were coaleced.
  63. , raCoalesced :: UniqFM VirtualReg
  64. -- | Code with coalescings applied.
  65. , raCodeCoalesced :: [LiveCmmDecl statics instr]
  66. -- | Code with vregs replaced by hregs.
  67. , raPatched :: [LiveCmmDecl statics instr]
  68. -- | Code with unneeded spill\/reloads cleaned out.
  69. , raSpillClean :: [LiveCmmDecl statics instr]
  70. -- | Final code.
  71. , raFinal :: [NatCmmDecl statics instr]
  72. -- | Spill\/reload\/reg-reg moves present in this code.
  73. , raSRMs :: (Int, Int, Int) }
  74. instance (Outputable statics, Outputable instr)
  75. => Outputable (RegAllocStats statics instr) where
  76. ppr (s@RegAllocStatsStart{}) = sdocWithPlatform $ \platform ->
  77. text "# Start"
  78. $$ text "# Native code with liveness information."
  79. $$ ppr (raLiveCmm s)
  80. $$ text ""
  81. $$ text "# Initial register conflict graph."
  82. $$ Color.dotGraph
  83. (targetRegDotColor platform)
  84. (trivColorable platform
  85. (targetVirtualRegSqueeze platform)
  86. (targetRealRegSqueeze platform))
  87. (raGraph s)
  88. ppr (s@RegAllocStatsSpill{}) =
  89. text "# Spill"
  90. $$ text "# Code with liveness information."
  91. $$ ppr (raCode s)
  92. $$ text ""
  93. $$ (if (not $ isNullUFM $ raCoalesced s)
  94. then text "# Registers coalesced."
  95. $$ (vcat $ map ppr $ ufmToList $ raCoalesced s)
  96. $$ text ""
  97. else empty)
  98. $$ text "# Spills inserted."
  99. $$ ppr (raSpillStats s)
  100. $$ text ""
  101. $$ text "# Code with spills inserted."
  102. $$ ppr (raSpilled s)
  103. ppr (s@RegAllocStatsColored { raSRMs = (spills, reloads, moves) })
  104. = sdocWithPlatform $ \platform ->
  105. text "# Colored"
  106. $$ text "# Code with liveness information."
  107. $$ ppr (raCode s)
  108. $$ text ""
  109. $$ text "# Register conflict graph (colored)."
  110. $$ Color.dotGraph
  111. (targetRegDotColor platform)
  112. (trivColorable platform
  113. (targetVirtualRegSqueeze platform)
  114. (targetRealRegSqueeze platform))
  115. (raGraphColored s)
  116. $$ text ""
  117. $$ (if (not $ isNullUFM $ raCoalesced s)
  118. then text "# Registers coalesced."
  119. $$ (vcat $ map ppr $ ufmToList $ raCoalesced s)
  120. $$ text ""
  121. else empty)
  122. $$ text "# Native code after coalescings applied."
  123. $$ ppr (raCodeCoalesced s)
  124. $$ text ""
  125. $$ text "# Native code after register allocation."
  126. $$ ppr (raPatched s)
  127. $$ text ""
  128. $$ text "# Clean out unneeded spill/reloads."
  129. $$ ppr (raSpillClean s)
  130. $$ text ""
  131. $$ text "# Final code, after rewriting spill/rewrite pseudo instrs."
  132. $$ ppr (raFinal s)
  133. $$ text ""
  134. $$ text "# Score:"
  135. $$ (text "# spills inserted: " <> int spills)
  136. $$ (text "# reloads inserted: " <> int reloads)
  137. $$ (text "# reg-reg moves remaining: " <> int moves)
  138. $$ text ""
  139. -- | Do all the different analysis on this list of RegAllocStats
  140. pprStats
  141. :: [RegAllocStats statics instr]
  142. -> Color.Graph VirtualReg RegClass RealReg
  143. -> SDoc
  144. pprStats stats graph
  145. = let outSpills = pprStatsSpills stats
  146. outLife = pprStatsLifetimes stats
  147. outConflict = pprStatsConflict stats
  148. outScatter = pprStatsLifeConflict stats graph
  149. in vcat [outSpills, outLife, outConflict, outScatter]
  150. -- | Dump a table of how many spill loads \/ stores were inserted for each vreg.
  151. pprStatsSpills
  152. :: [RegAllocStats statics instr] -> SDoc
  153. pprStatsSpills stats
  154. = let
  155. finals = [ s | s@RegAllocStatsColored{} <- stats]
  156. -- sum up how many stores\/loads\/reg-reg-moves were left in the code
  157. total = foldl' addSRM (0, 0, 0)
  158. $ map raSRMs finals
  159. in ( text "-- spills-added-total"
  160. $$ text "-- (stores, loads, reg_reg_moves_remaining)"
  161. $$ ppr total
  162. $$ text "")
  163. -- | Dump a table of how long vregs tend to live for in the initial code.
  164. pprStatsLifetimes
  165. :: [RegAllocStats statics instr] -> SDoc
  166. pprStatsLifetimes stats
  167. = let info = foldl' plusSpillCostInfo zeroSpillCostInfo
  168. [ raSpillCosts s
  169. | s@RegAllocStatsStart{} <- stats ]
  170. lifeBins = binLifetimeCount $ lifeMapFromSpillCostInfo info
  171. in ( text "-- vreg-population-lifetimes"
  172. $$ text "-- (instruction_count, number_of_vregs_that_lived_that_long)"
  173. $$ (vcat $ map ppr $ eltsUFM lifeBins)
  174. $$ text "\n")
  175. binLifetimeCount :: UniqFM (VirtualReg, Int) -> UniqFM (Int, Int)
  176. binLifetimeCount fm
  177. = let lifes = map (\l -> (l, (l, 1)))
  178. $ map snd
  179. $ eltsUFM fm
  180. in addListToUFM_C
  181. (\(l1, c1) (_, c2) -> (l1, c1 + c2))
  182. emptyUFM
  183. lifes
  184. -- | Dump a table of how many conflicts vregs tend to have in the initial code.
  185. pprStatsConflict
  186. :: [RegAllocStats statics instr] -> SDoc
  187. pprStatsConflict stats
  188. = let confMap = foldl' (plusUFM_C (\(c1, n1) (_, n2) -> (c1, n1 + n2)))
  189. emptyUFM
  190. $ map Color.slurpNodeConflictCount
  191. [ raGraph s | s@RegAllocStatsStart{} <- stats ]
  192. in ( text "-- vreg-conflicts"
  193. $$ text "-- (conflict_count, number_of_vregs_that_had_that_many_conflicts)"
  194. $$ (vcat $ map ppr $ eltsUFM confMap)
  195. $$ text "\n")
  196. -- | For every vreg, dump it's how many conflicts it has and its lifetime
  197. -- good for making a scatter plot.
  198. pprStatsLifeConflict
  199. :: [RegAllocStats statics instr]
  200. -> Color.Graph VirtualReg RegClass RealReg -- ^ global register conflict graph
  201. -> SDoc
  202. pprStatsLifeConflict stats graph
  203. = let lifeMap = lifeMapFromSpillCostInfo
  204. $ foldl' plusSpillCostInfo zeroSpillCostInfo
  205. $ [ raSpillCosts s | s@RegAllocStatsStart{} <- stats ]
  206. scatter = map (\r -> let lifetime = case lookupUFM lifeMap r of
  207. Just (_, l) -> l
  208. Nothing -> 0
  209. Just node = Color.lookupNode graph r
  210. in parens $ hcat $ punctuate (text ", ")
  211. [ doubleQuotes $ ppr $ Color.nodeId node
  212. , ppr $ sizeUniqSet (Color.nodeConflicts node)
  213. , ppr $ lifetime ])
  214. $ map Color.nodeId
  215. $ eltsUFM
  216. $ Color.graphMap graph
  217. in ( text "-- vreg-conflict-lifetime"
  218. $$ text "-- (vreg, vreg_conflicts, vreg_lifetime)"
  219. $$ (vcat scatter)
  220. $$ text "\n")
  221. -- | Count spill/reload/reg-reg moves.
  222. -- Lets us see how well the register allocator has done.
  223. countSRMs
  224. :: Instruction instr
  225. => LiveCmmDecl statics instr -> (Int, Int, Int)
  226. countSRMs cmm
  227. = execState (mapBlockTopM countSRM_block cmm) (0, 0, 0)
  228. countSRM_block
  229. :: Instruction instr
  230. => GenBasicBlock (LiveInstr instr)
  231. -> State (Int, Int, Int) (GenBasicBlock (LiveInstr instr))
  232. countSRM_block (BasicBlock i instrs)
  233. = do instrs' <- mapM countSRM_instr instrs
  234. return $ BasicBlock i instrs'
  235. countSRM_instr
  236. :: Instruction instr
  237. => LiveInstr instr -> State (Int, Int, Int) (LiveInstr instr)
  238. countSRM_instr li
  239. | LiveInstr SPILL{} _ <- li
  240. = do modify $ \(s, r, m) -> (s + 1, r, m)
  241. return li
  242. | LiveInstr RELOAD{} _ <- li
  243. = do modify $ \(s, r, m) -> (s, r + 1, m)
  244. return li
  245. | LiveInstr instr _ <- li
  246. , Just _ <- takeRegRegMoveInstr instr
  247. = do modify $ \(s, r, m) -> (s, r, m + 1)
  248. return li
  249. | otherwise
  250. = return li
  251. -- sigh..
  252. addSRM :: (Int, Int, Int) -> (Int, Int, Int) -> (Int, Int, Int)
  253. addSRM (s1, r1, m1) (s2, r2, m2)
  254. = let !s = s1 + s2
  255. !r = r1 + r2
  256. !m = m1 + m2
  257. in (s, r, m)