PageRenderTime 47ms CodeModel.GetById 19ms RepoModel.GetById 0ms app.codeStats 0ms

/ghc-7.0.4/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs

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