PageRenderTime 54ms CodeModel.GetById 20ms RepoModel.GetById 0ms app.codeStats 0ms

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

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