fix haddock submodule pointer
[ghc-hetmet.git] / compiler / nativeGen / RegAlloc / Graph / TrivColorable.hs
1 {-# LANGUAGE BangPatterns #-}
2
3 module RegAlloc.Graph.TrivColorable (
4         trivColorable,
5 )
6
7 where
8
9 #include "HsVersions.h"
10
11 import RegClass
12 import Reg
13
14 import GraphBase
15
16 import UniqFM
17 import FastTypes
18 import Platform
19 import Panic
20
21
22 -- trivColorable ---------------------------------------------------------------
23
24 -- trivColorable function for the graph coloring allocator
25 --
26 --      This gets hammered by scanGraph during register allocation,
27 --      so needs to be fairly efficient.
28 --
29 --      NOTE:   This only works for arcitectures with just RcInteger and RcDouble
30 --              (which are disjoint) ie. x86, x86_64 and ppc
31 --
32 --      The number of allocatable regs is hard coded in here so we can do
33 --              a fast comparision in trivColorable.
34 --
35 --      It's ok if these numbers are _less_ than the actual number of free
36 --              regs, but they can't be more or the register conflict
37 --              graph won't color.
38 --
39 --      If the graph doesn't color then the allocator will panic, but it won't
40 --              generate bad object code or anything nasty like that.
41 --
42 --      There is an allocatableRegsInClass :: RegClass -> Int, but doing
43 --      the unboxing is too slow for us here.
44 --      TODO: Is that still true? Could we use allocatableRegsInClass
45 --      without losing performance now?
46 --
47 --      Look at includes/stg/MachRegs.h to get the numbers.
48 --
49
50
51 -- Disjoint registers ----------------------------------------------------------
52 --
53 --      The definition has been unfolded into individual cases for speed.
54 --      Each architecture has a different register setup, so we use a
55 --      different regSqueeze function for each.
56 --
57 accSqueeze
58         :: FastInt
59         -> FastInt
60         -> (reg -> FastInt)
61         -> UniqFM reg
62         -> FastInt
63
64 accSqueeze count maxCount squeeze ufm = acc count (eltsUFM ufm)
65   where acc count [] = count
66         acc count _ | count >=# maxCount = count
67         acc count (r:rs) = acc (count +# squeeze r) rs
68
69 {- Note [accSqueeze]
70 ~~~~~~~~~~~~~~~~~~~~
71 BL 2007/09
72 Doing a nice fold over the UniqSet makes trivColorable use
73 32% of total compile time and 42% of total alloc when compiling SHA1.lhs from darcs.
74 Therefore the UniqFM is made non-abstract and we use custom fold.
75
76 MS 2010/04
77 When converting UniqFM to use Data.IntMap, the fold cannot use UniqFM internal
78 representation any more. But it is imperative that the assSqueeze stops
79 the folding if the count gets greater or equal to maxCount. We thus convert
80 UniqFM to a (lazy) list, do the fold and stops if necessary, which was
81 the most efficient variant tried. Benchmark compiling 10-times SHA1.lhs follows.
82 (original = previous implementation, folding = fold of the whole UFM,
83  lazyFold = the current implementation,
84  hackFold = using internal representation of Data.IntMap)
85
86                                  original  folding   hackFold  lazyFold
87  -O -fasm (used everywhere)      31.509s   30.387s   30.791s   30.603s
88                                  100.00%   96.44%    97.72%    97.12%
89  -fregs-graph                    67.938s   74.875s   62.673s   64.679s
90                                  100.00%   110.21%   92.25%    95.20%
91  -fregs-iterative                89.761s   143.913s  81.075s   86.912s
92                                  100.00%   160.33%   90.32%    96.83%
93  -fnew-codegen                   38.225s   37.142s   37.551s   37.119s
94                                  100.00%   97.17%    98.24%    97.11%
95  -fnew-codegen -fregs-graph      91.786s   91.51s    87.368s   86.88s
96                                  100.00%   99.70%    95.19%    94.65%
97  -fnew-codegen -fregs-iterative  206.72s   343.632s  194.694s  208.677s
98                                  100.00%   166.23%   94.18%    100.95%
99 -}
100
101 -- TODO: We shouldn't be using defaultTargetPlatform here.
102 --       We should be passing DynFlags in instead, and looking at
103 --       its targetPlatform.
104
105 trivColorable
106         :: (RegClass -> VirtualReg -> FastInt)
107         -> (RegClass -> RealReg    -> FastInt)
108         -> Triv VirtualReg RegClass RealReg
109
110 trivColorable virtualRegSqueeze realRegSqueeze RcInteger conflicts exclusions
111         | let !cALLOCATABLE_REGS_INTEGER
112                   = iUnbox (case platformArch defaultTargetPlatform of
113                             ArchX86     -> 3
114                             ArchX86_64  -> 5
115                             ArchPPC     -> 16
116                             ArchSPARC   -> 14
117                             ArchPPC_64  -> panic "trivColorable ArchPPC_64"
118                             ArchUnknown -> panic "trivColorable ArchUnknown")
119         , count2        <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_INTEGER
120                                 (virtualRegSqueeze RcInteger)
121                                 conflicts
122
123         , count3        <- accSqueeze  count2    cALLOCATABLE_REGS_INTEGER
124                                 (realRegSqueeze   RcInteger)
125                                 exclusions
126
127         = count3 <# cALLOCATABLE_REGS_INTEGER
128
129 trivColorable virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions
130         | let !cALLOCATABLE_REGS_FLOAT
131                   = iUnbox (case platformArch defaultTargetPlatform of
132                             ArchX86     -> 0
133                             ArchX86_64  -> 0
134                             ArchPPC     -> 0
135                             ArchSPARC   -> 22
136                             ArchPPC_64  -> panic "trivColorable ArchPPC_64"
137                             ArchUnknown -> panic "trivColorable ArchUnknown")
138         , count2        <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_FLOAT
139                                 (virtualRegSqueeze RcFloat)
140                                 conflicts
141
142         , count3        <- accSqueeze  count2    cALLOCATABLE_REGS_FLOAT
143                                 (realRegSqueeze   RcFloat)
144                                 exclusions
145
146         = count3 <# cALLOCATABLE_REGS_FLOAT
147
148 trivColorable virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions
149         | let !cALLOCATABLE_REGS_DOUBLE
150                   = iUnbox (case platformArch defaultTargetPlatform of
151                             ArchX86     -> 6
152                             ArchX86_64  -> 0
153                             ArchPPC     -> 26
154                             ArchSPARC   -> 11
155                             ArchPPC_64  -> panic "trivColorable ArchPPC_64"
156                             ArchUnknown -> panic "trivColorable ArchUnknown")
157         , count2        <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_DOUBLE
158                                 (virtualRegSqueeze RcDouble)
159                                 conflicts
160
161         , count3        <- accSqueeze  count2    cALLOCATABLE_REGS_DOUBLE
162                                 (realRegSqueeze   RcDouble)
163                                 exclusions
164
165         = count3 <# cALLOCATABLE_REGS_DOUBLE
166
167 trivColorable virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts exclusions
168         | let !cALLOCATABLE_REGS_SSE
169                   = iUnbox (case platformArch defaultTargetPlatform of
170                             ArchX86     -> 8
171                             ArchX86_64  -> 10
172                             ArchPPC     -> 0
173                             ArchSPARC   -> 0
174                             ArchPPC_64  -> panic "trivColorable ArchPPC_64"
175                             ArchUnknown -> panic "trivColorable ArchUnknown")
176         , count2        <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_SSE
177                                 (virtualRegSqueeze RcDoubleSSE)
178                                 conflicts
179
180         , count3        <- accSqueeze  count2    cALLOCATABLE_REGS_SSE
181                                 (realRegSqueeze   RcDoubleSSE)
182                                 exclusions
183
184         = count3 <# cALLOCATABLE_REGS_SSE
185
186
187 -- Specification Code ----------------------------------------------------------
188 --
189 --      The trivColorable function for each particular architecture should
190 --      implement the following function, but faster.
191 --
192
193 {-
194 trivColorable :: RegClass -> UniqSet Reg -> UniqSet Reg -> Bool
195 trivColorable classN conflicts exclusions
196  = let
197
198         acc :: Reg -> (Int, Int) -> (Int, Int)
199         acc r (cd, cf)
200          = case regClass r of
201                 RcInteger       -> (cd+1, cf)
202                 RcFloat         -> (cd,   cf+1)
203                 _               -> panic "Regs.trivColorable: reg class not handled"
204
205         tmp                     = foldUniqSet acc (0, 0) conflicts
206         (countInt,  countFloat) = foldUniqSet acc tmp    exclusions
207
208         squeese         = worst countInt   classN RcInteger
209                         + worst countFloat classN RcFloat
210
211    in   squeese < allocatableRegsInClass classN
212
213 -- | Worst case displacement
214 --      node N of classN has n neighbors of class C.
215 --
216 --      We currently only have RcInteger and RcDouble, which don't conflict at all.
217 --      This is a bit boring compared to what's in RegArchX86.
218 --
219 worst :: Int -> RegClass -> RegClass -> Int
220 worst n classN classC
221  = case classN of
222         RcInteger
223          -> case classC of
224                 RcInteger       -> min n (allocatableRegsInClass RcInteger)
225                 RcFloat         -> 0
226
227         RcDouble
228          -> case classC of
229                 RcFloat         -> min n (allocatableRegsInClass RcFloat)
230                 RcInteger       -> 0
231
232 -- allocatableRegs is allMachRegNos with the fixed-use regs removed.
233 -- i.e., these are the regs for which we are prepared to allow the
234 -- register allocator to attempt to map VRegs to.
235 allocatableRegs :: [RegNo]
236 allocatableRegs
237    = let isFree i = isFastTrue (freeReg i)
238      in  filter isFree allMachRegNos
239
240
241 -- | The number of regs in each class.
242 --      We go via top level CAFs to ensure that we're not recomputing
243 --      the length of these lists each time the fn is called.
244 allocatableRegsInClass :: RegClass -> Int
245 allocatableRegsInClass cls
246  = case cls of
247         RcInteger       -> allocatableRegsInteger
248         RcFloat         -> allocatableRegsDouble
249
250 allocatableRegsInteger :: Int
251 allocatableRegsInteger
252         = length $ filter (\r -> regClass r == RcInteger)
253                  $ map RealReg allocatableRegs
254
255 allocatableRegsFloat :: Int
256 allocatableRegsFloat
257         = length $ filter (\r -> regClass r == RcFloat
258                  $ map RealReg allocatableRegs
259 -}