PageRenderTime 51ms CodeModel.GetById 22ms RepoModel.GetById 0ms app.codeStats 0ms

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

http://picorec.googlecode.com/
Haskell | 412 lines | 264 code | 80 blank | 68 comment | 13 complexity | 55e25b0a46fc4e74a351374168c61847 MD5 | raw file
Possible License(s): BSD-3-Clause, BSD-2-Clause
  1. {-# OPTIONS -fno-warn-missing-signatures #-}
  2. -- | Graph coloring register allocator.
  3. --
  4. -- TODO: The colors in graphviz graphs for x86_64 and ppc could be nicer.
  5. --
  6. module RegAlloc.Graph.Main (
  7. regAlloc
  8. )
  9. where
  10. import qualified GraphColor as Color
  11. import RegAlloc.Liveness
  12. import RegAlloc.Graph.Spill
  13. import RegAlloc.Graph.SpillClean
  14. import RegAlloc.Graph.SpillCost
  15. import RegAlloc.Graph.Stats
  16. import RegAlloc.Graph.TrivColorable
  17. import Instruction
  18. import TargetReg
  19. import RegClass
  20. import Reg
  21. import UniqSupply
  22. import UniqSet
  23. import UniqFM
  24. import Bag
  25. import Outputable
  26. import DynFlags
  27. import Data.List
  28. import Data.Maybe
  29. import Control.Monad
  30. -- | The maximum number of build\/spill cycles we'll allow.
  31. -- We should only need 3 or 4 cycles tops.
  32. -- If we run for any longer than this we're probably in an infinite loop,
  33. -- It's probably better just to bail out and report a bug at this stage.
  34. maxSpinCount :: Int
  35. maxSpinCount = 10
  36. -- | The top level of the graph coloring register allocator.
  37. regAlloc
  38. :: (Outputable instr, Instruction instr)
  39. => DynFlags
  40. -> UniqFM (UniqSet RealReg) -- ^ the registers we can use for allocation
  41. -> UniqSet Int -- ^ the set of available spill slots.
  42. -> [LiveCmmTop instr] -- ^ code annotated with liveness information.
  43. -> UniqSM ( [NatCmmTop instr], [RegAllocStats instr] )
  44. -- ^ code with registers allocated and stats for each stage of
  45. -- allocation
  46. regAlloc dflags regsFree slotsFree code
  47. = do
  48. -- TODO: the regClass function is currently hard coded to the default target
  49. -- architecture. Would prefer to determine this from dflags.
  50. -- There are other uses of targetRegClass later in this module.
  51. let triv = trivColorable
  52. targetVirtualRegSqueeze
  53. targetRealRegSqueeze
  54. (code_final, debug_codeGraphs, _)
  55. <- regAlloc_spin dflags 0
  56. triv
  57. regsFree slotsFree [] code
  58. return ( code_final
  59. , reverse debug_codeGraphs )
  60. regAlloc_spin
  61. dflags
  62. spinCount
  63. (triv :: Color.Triv VirtualReg RegClass RealReg)
  64. (regsFree :: UniqFM (UniqSet RealReg))
  65. slotsFree
  66. debug_codeGraphs
  67. code
  68. = do
  69. -- if any of these dump flags are turned on we want to hang on to
  70. -- intermediate structures in the allocator - otherwise tell the
  71. -- allocator to ditch them early so we don't end up creating space leaks.
  72. let dump = or
  73. [ dopt Opt_D_dump_asm_regalloc_stages dflags
  74. , dopt Opt_D_dump_asm_stats dflags
  75. , dopt Opt_D_dump_asm_conflicts dflags ]
  76. -- check that we're not running off down the garden path.
  77. when (spinCount > maxSpinCount)
  78. $ pprPanic "regAlloc_spin: max build/spill cycle count exceeded."
  79. ( text "It looks like the register allocator is stuck in an infinite loop."
  80. $$ text "max cycles = " <> int maxSpinCount
  81. $$ text "regsFree = " <> (hcat $ punctuate space $ map ppr
  82. $ uniqSetToList $ unionManyUniqSets $ eltsUFM regsFree)
  83. $$ text "slotsFree = " <> ppr (sizeUniqSet slotsFree))
  84. -- build a conflict graph from the code.
  85. (graph :: Color.Graph VirtualReg RegClass RealReg)
  86. <- {-# SCC "BuildGraph" #-} buildGraph code
  87. -- VERY IMPORTANT:
  88. -- We really do want the graph to be fully evaluated _before_ we start coloring.
  89. -- If we don't do this now then when the call to Color.colorGraph forces bits of it,
  90. -- the heap will be filled with half evaluated pieces of graph and zillions of apply thunks.
  91. --
  92. seqGraph graph `seq` return ()
  93. -- build a map of the cost of spilling each instruction
  94. -- this will only actually be computed if we have to spill something.
  95. let spillCosts = foldl' plusSpillCostInfo zeroSpillCostInfo
  96. $ map slurpSpillCostInfo code
  97. -- the function to choose regs to leave uncolored
  98. let spill = chooseSpill spillCosts
  99. -- record startup state
  100. let stat1 =
  101. if spinCount == 0
  102. then Just $ RegAllocStatsStart
  103. { raLiveCmm = code
  104. , raGraph = graph
  105. , raSpillCosts = spillCosts }
  106. else Nothing
  107. -- try and color the graph
  108. let (graph_colored, rsSpill, rmCoalesce)
  109. = {-# SCC "ColorGraph" #-}
  110. Color.colorGraph
  111. (dopt Opt_RegsIterative dflags)
  112. spinCount
  113. regsFree triv spill graph
  114. -- rewrite regs in the code that have been coalesced
  115. let patchF reg
  116. | RegVirtual vr <- reg
  117. = case lookupUFM rmCoalesce vr of
  118. Just vr' -> patchF (RegVirtual vr')
  119. Nothing -> reg
  120. | otherwise
  121. = reg
  122. let code_coalesced
  123. = map (patchEraseLive patchF) code
  124. -- see if we've found a coloring
  125. if isEmptyUniqSet rsSpill
  126. then do
  127. -- if -fasm-lint is turned on then validate the graph
  128. let graph_colored_lint =
  129. if dopt Opt_DoAsmLinting dflags
  130. then Color.validateGraph (text "")
  131. True -- require all nodes to be colored
  132. graph_colored
  133. else graph_colored
  134. -- patch the registers using the info in the graph
  135. let code_patched = map (patchRegsFromGraph graph_colored_lint) code_coalesced
  136. -- clean out unneeded SPILL/RELOADs
  137. let code_spillclean = map cleanSpills code_patched
  138. -- strip off liveness information,
  139. -- and rewrite SPILL/RELOAD pseudos into real instructions along the way
  140. let code_final = map stripLive code_spillclean
  141. -- record what happened in this stage for debugging
  142. let stat =
  143. RegAllocStatsColored
  144. { raCode = code
  145. , raGraph = graph
  146. , raGraphColored = graph_colored_lint
  147. , raCoalesced = rmCoalesce
  148. , raCodeCoalesced = code_coalesced
  149. , raPatched = code_patched
  150. , raSpillClean = code_spillclean
  151. , raFinal = code_final
  152. , raSRMs = foldl' addSRM (0, 0, 0) $ map countSRMs code_spillclean }
  153. let statList =
  154. if dump then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
  155. else []
  156. -- space leak avoidance
  157. seqList statList `seq` return ()
  158. return ( code_final
  159. , statList
  160. , graph_colored_lint)
  161. -- we couldn't find a coloring, time to spill something
  162. else do
  163. -- if -fasm-lint is turned on then validate the graph
  164. let graph_colored_lint =
  165. if dopt Opt_DoAsmLinting dflags
  166. then Color.validateGraph (text "")
  167. False -- don't require nodes to be colored
  168. graph_colored
  169. else graph_colored
  170. -- spill the uncolored regs
  171. (code_spilled, slotsFree', spillStats)
  172. <- regSpill code_coalesced slotsFree rsSpill
  173. -- recalculate liveness
  174. -- NOTE: we have to reverse the SCCs here to get them back into the reverse-dependency
  175. -- order required by computeLiveness. If they're not in the correct order
  176. -- that function will panic.
  177. code_relive <- mapM (regLiveness . reverseBlocksInTops) code_spilled
  178. -- record what happened in this stage for debugging
  179. let stat =
  180. RegAllocStatsSpill
  181. { raCode = code
  182. , raGraph = graph_colored_lint
  183. , raCoalesced = rmCoalesce
  184. , raSpillStats = spillStats
  185. , raSpillCosts = spillCosts
  186. , raSpilled = code_spilled }
  187. let statList =
  188. if dump
  189. then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
  190. else []
  191. -- space leak avoidance
  192. seqList statList `seq` return ()
  193. regAlloc_spin dflags (spinCount + 1) triv regsFree slotsFree'
  194. statList
  195. code_relive
  196. -- | Build a graph from the liveness and coalesce information in this code.
  197. buildGraph
  198. :: Instruction instr
  199. => [LiveCmmTop instr]
  200. -> UniqSM (Color.Graph VirtualReg RegClass RealReg)
  201. buildGraph code
  202. = do
  203. -- Slurp out the conflicts and reg->reg moves from this code
  204. let (conflictList, moveList) =
  205. unzip $ map slurpConflicts code
  206. -- Slurp out the spill/reload coalesces
  207. let moveList2 = map slurpReloadCoalesce code
  208. -- Add the reg-reg conflicts to the graph
  209. let conflictBag = unionManyBags conflictList
  210. let graph_conflict = foldrBag graphAddConflictSet Color.initGraph conflictBag
  211. -- Add the coalescences edges to the graph.
  212. let moveBag = unionBags (unionManyBags moveList2) (unionManyBags moveList)
  213. let graph_coalesce = foldrBag graphAddCoalesce graph_conflict moveBag
  214. return graph_coalesce
  215. -- | Add some conflict edges to the graph.
  216. -- Conflicts between virtual and real regs are recorded as exclusions.
  217. graphAddConflictSet
  218. :: UniqSet Reg
  219. -> Color.Graph VirtualReg RegClass RealReg
  220. -> Color.Graph VirtualReg RegClass RealReg
  221. graphAddConflictSet set graph
  222. = let virtuals = mkUniqSet
  223. [ vr | RegVirtual vr <- uniqSetToList set ]
  224. graph1 = Color.addConflicts virtuals classOfVirtualReg graph
  225. graph2 = foldr (\(r1, r2) -> Color.addExclusion r1 classOfVirtualReg r2)
  226. graph1
  227. [ (vr, rr)
  228. | RegVirtual vr <- uniqSetToList set
  229. , RegReal rr <- uniqSetToList set]
  230. in graph2
  231. -- | Add some coalesence edges to the graph
  232. -- Coalesences between virtual and real regs are recorded as preferences.
  233. graphAddCoalesce
  234. :: (Reg, Reg)
  235. -> Color.Graph VirtualReg RegClass RealReg
  236. -> Color.Graph VirtualReg RegClass RealReg
  237. graphAddCoalesce (r1, r2) graph
  238. | RegReal rr <- r1
  239. , RegVirtual vr <- r2
  240. = Color.addPreference (vr, classOfVirtualReg vr) rr graph
  241. | RegReal rr <- r2
  242. , RegVirtual vr <- r1
  243. = Color.addPreference (vr, classOfVirtualReg vr) rr graph
  244. | RegVirtual vr1 <- r1
  245. , RegVirtual vr2 <- r2
  246. = Color.addCoalesce
  247. (vr1, classOfVirtualReg vr1)
  248. (vr2, classOfVirtualReg vr2)
  249. graph
  250. -- We can't coalesce two real regs, but there could well be existing
  251. -- hreg,hreg moves in the input code. We'll just ignore these
  252. -- for coalescing purposes.
  253. | RegReal _ <- r1
  254. , RegReal _ <- r2
  255. = graph
  256. graphAddCoalesce _ _
  257. = panic "graphAddCoalesce: bogus"
  258. -- | Patch registers in code using the reg -> reg mapping in this graph.
  259. patchRegsFromGraph
  260. :: (Outputable instr, Instruction instr)
  261. => Color.Graph VirtualReg RegClass RealReg
  262. -> LiveCmmTop instr -> LiveCmmTop instr
  263. patchRegsFromGraph graph code
  264. = let
  265. -- a function to lookup the hardreg for a virtual reg from the graph.
  266. patchF reg
  267. -- leave real regs alone.
  268. | RegReal{} <- reg
  269. = reg
  270. -- this virtual has a regular node in the graph.
  271. | RegVirtual vr <- reg
  272. , Just node <- Color.lookupNode graph vr
  273. = case Color.nodeColor node of
  274. Just color -> RegReal color
  275. Nothing -> RegVirtual vr
  276. -- no node in the graph for this virtual, bad news.
  277. | otherwise
  278. = pprPanic "patchRegsFromGraph: register mapping failed."
  279. ( text "There is no node in the graph for register " <> ppr reg
  280. $$ ppr code
  281. $$ Color.dotGraph
  282. (\_ -> text "white")
  283. (trivColorable
  284. targetVirtualRegSqueeze
  285. targetRealRegSqueeze)
  286. graph)
  287. in patchEraseLive patchF code
  288. -----
  289. -- for when laziness just isn't what you wanted...
  290. --
  291. seqGraph :: Color.Graph VirtualReg RegClass RealReg -> ()
  292. seqGraph graph = seqNodes (eltsUFM (Color.graphMap graph))
  293. seqNodes :: [Color.Node VirtualReg RegClass RealReg] -> ()
  294. seqNodes ns
  295. = case ns of
  296. [] -> ()
  297. (n : ns) -> seqNode n `seq` seqNodes ns
  298. seqNode :: Color.Node VirtualReg RegClass RealReg -> ()
  299. seqNode node
  300. = seqVirtualReg (Color.nodeId node)
  301. `seq` seqRegClass (Color.nodeClass node)
  302. `seq` seqMaybeRealReg (Color.nodeColor node)
  303. `seq` (seqVirtualRegList (uniqSetToList (Color.nodeConflicts node)))
  304. `seq` (seqRealRegList (uniqSetToList (Color.nodeExclusions node)))
  305. `seq` (seqRealRegList (Color.nodePreference node))
  306. `seq` (seqVirtualRegList (uniqSetToList (Color.nodeCoalesce node)))
  307. seqVirtualReg :: VirtualReg -> ()
  308. seqVirtualReg reg = reg `seq` ()
  309. seqRealReg :: RealReg -> ()
  310. seqRealReg reg = reg `seq` ()
  311. seqRegClass :: RegClass -> ()
  312. seqRegClass c = c `seq` ()
  313. seqMaybeRealReg :: Maybe RealReg -> ()
  314. seqMaybeRealReg mr
  315. = case mr of
  316. Nothing -> ()
  317. Just r -> seqRealReg r
  318. seqVirtualRegList :: [VirtualReg] -> ()
  319. seqVirtualRegList rs
  320. = case rs of
  321. [] -> ()
  322. (r : rs) -> seqVirtualReg r `seq` seqVirtualRegList rs
  323. seqRealRegList :: [RealReg] -> ()
  324. seqRealRegList rs
  325. = case rs of
  326. [] -> ()
  327. (r : rs) -> seqRealReg r `seq` seqRealRegList rs
  328. seqList :: [a] -> ()
  329. seqList ls
  330. = case ls of
  331. [] -> ()
  332. (r : rs) -> r `seq` seqList rs