summaryrefslogtreecommitdiff
path: root/compiler/nativeGen/RegSpillClean.hs
blob: 7b6567124fb45923d652ef65c49438171eee89d0 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
-- | Clean out unneeded spill/reload instrs
--
-- * Handling of join points
--
--   B1:                          B2:
--    ...                          ...
--       RELOAD SLOT(0), %r1          RELOAD SLOT(0), %r1
--       ... A ...                    ... B ...
--       jump B3                      jump B3
--
--                B3: ... C ...
--                    RELOAD SLOT(0), %r1
--                    ...
--
-- the plan:
--	So long as %r1 hasn't been written to in A, B or C then we don't need the
--	reload in B3.
--
--	What we really care about here is that on the entry to B3, %r1 will always
--	have the same value that is in SLOT(0) (ie, %r1 is _valid_)
--
--	This also works if the reloads in B1/B2 were spills instead, because
--	spilling %r1 to a slot makes that slot have the same value as %r1.
--

{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
--     http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details

module RegSpillClean (
	cleanSpills
)
where

import RegLiveness
import RegAllocInfo
import MachRegs
import MachInstrs
import Cmm

import UniqSet
import UniqFM
import State
import Outputable

import Data.Maybe
import Data.List

type Slot	= Int

-- | Clean out unneeded spill/reloads from this top level thing.
cleanSpills :: LiveCmmTop -> LiveCmmTop
cleanSpills cmm
	= evalState (cleanSpin 0 cmm) initCleanS

-- | do one pass of cleaning
cleanSpin :: Int -> LiveCmmTop -> CleanM LiveCmmTop

{-
cleanSpin spinCount code
 = do	jumpValid	<- gets sJumpValid
	pprTrace "cleanSpin"
	 	(  int spinCount
		$$ text "--- code"
		$$ ppr code
		$$ text "--- joins"
		$$ ppr jumpValid)
	 $ cleanSpin' spinCount code
-}

cleanSpin spinCount code
 = do
 	-- init count of cleaned spills/reloads
	modify $ \s -> s
		{ sCleanedSpillsAcc	= 0
		, sCleanedReloadsAcc	= 0 }

 	code'	<- mapBlockTopM cleanBlock code

	-- During the cleaning of each block we collected information about what regs
	--	were valid across each jump. Based on this, work out whether it will be
	--	safe to erase reloads after join points for the next pass.
	collateJoinPoints

	-- remember how many spills/reloads we cleaned in this pass
	spills		<- gets sCleanedSpillsAcc
	reloads		<- gets sCleanedReloadsAcc
	modify $ \s -> s
		{ sCleanedCount	= (spills, reloads) : sCleanedCount s }

	-- if nothing was cleaned in this pass or the last one
	--	then we're done and it's time to bail out
	cleanedCount	<- gets sCleanedCount
	if take 2 cleanedCount == [(0, 0), (0, 0)]
	   then return code

	-- otherwise go around again
	   else cleanSpin (spinCount + 1) code'


-- | Clean one basic block
cleanBlock :: LiveBasicBlock -> CleanM LiveBasicBlock
cleanBlock (BasicBlock id instrs)
 = do	jumpValid	<- gets sJumpValid
 	let assoc	= case lookupUFM jumpValid id of
				Just assoc	-> assoc
				Nothing		-> emptyAssoc

 	instrs_reload	<- cleanReload assoc        [] instrs
 	instrs_spill	<- cleanSpill  emptyUniqSet [] instrs_reload
	return	$ BasicBlock id instrs_spill


-- | Clean out unneeded reload instructions.
--	Walking forwards across the code
--	  On a reload, if we know a reg already has the same value as a slot
--	  then we don't need to do the reload.
--
cleanReload
	:: Assoc Reg Slot 	-- ^ a reg and slot are associated when they have the same value.
	-> [LiveInstr]		-- ^ acc
	-> [LiveInstr] 		-- ^ instrs to clean (in backwards order)
	-> CleanM [LiveInstr]	-- ^ cleaned instrs  (in forward   order)

cleanReload assoc acc []
	= return acc

cleanReload assoc acc (li@(Instr instr live) : instrs)

	| SPILL reg slot	<- instr
	= let	assoc'	= addAssoc reg slot	-- doing the spill makes reg and slot the same value
			$ deleteBAssoc slot 	-- slot value changes on spill
			$ assoc
	  in	cleanReload assoc' (li : acc) instrs

	| RELOAD slot reg	<- instr
	= if elemAssoc reg slot assoc

           -- reg and slot had the same value before reload
	   --	we don't need the reload.
	   then	do
		modify $ \s -> s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 }
	   	cleanReload assoc acc instrs

	   -- reg and slot had different values before reload
	   else
	    let assoc'	= addAssoc reg slot	-- doing the reload makes reg and slot the same value
			$ deleteAAssoc reg	-- reg value changes on reload
			$ assoc
	    in	cleanReload assoc' (li : acc) instrs

	-- on a jump, remember the reg/slot association.
	| targets		<- jumpDests instr []
	, not $ null targets
	= do	mapM_ (accJumpValid assoc) targets
		cleanReload assoc (li : acc) instrs

	-- writing to a reg changes its value.
	| RU read written	<- regUsage instr
	= let assoc'	= foldr deleteAAssoc assoc written
	  in  cleanReload assoc' (li : acc) instrs


-- | Clean out unneeded spill instructions.
--	Walking backwards across the code.
--	 If there were no reloads from a slot between a spill and the last one
--	 then the slot was never read and we don't need the spill.

cleanSpill
	:: UniqSet Int 		-- ^ slots that have been spilled, but not reload from
	-> [LiveInstr]		-- ^ acc
	-> [LiveInstr]		-- ^ instrs to clean (in forwards order)
	-> CleanM [LiveInstr]	-- ^ cleaned instrs  (in backwards order)

cleanSpill unused acc []
	= return  acc

cleanSpill unused acc (li@(Instr instr live) : instrs)
	| SPILL reg slot	<- instr
	= if elementOfUniqSet slot unused

	   -- we can erase this spill because the slot won't be read until after the next one
	   then do
		modify $ \s -> s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 }
	   	cleanSpill unused acc instrs

	   else do
		-- slots start off unused
		let unused'	= addOneToUniqSet unused slot
	   	cleanSpill unused' (li : acc) instrs

	-- if we reload from a slot then it's no longer unused
	| RELOAD slot reg	<- instr
	, unused'		<- delOneFromUniqSet unused slot
	= cleanSpill unused' (li : acc) instrs

	-- some other instruction
	| otherwise
	= cleanSpill unused (li : acc) instrs


-- collateJoinPoints:
--
-- | Look at information about what regs were valid across jumps and work out
--	whether it's safe to avoid reloads after join points.
--
collateJoinPoints :: CleanM ()
collateJoinPoints
 = modify $ \s -> s
 	{ sJumpValid	= mapUFM intersects (sJumpValidAcc s)
	, sJumpValidAcc	= emptyUFM }

intersects :: [Assoc Reg Slot]	-> Assoc Reg Slot
intersects []		= emptyAssoc
intersects assocs	= foldl1' intersectAssoc assocs



---------------
type CleanM = State CleanS
data CleanS
	= CleanS
	{ -- regs which are valid at the start of each block.
	  sJumpValid		:: UniqFM (Assoc Reg Slot)

 	  -- collecting up what regs were valid across each jump.
	  --	in the next pass we can collate these and write the results
	  --	to sJumpValid.
	, sJumpValidAcc		:: UniqFM [Assoc Reg Slot]

	  -- spills/reloads cleaned each pass (latest at front)
	, sCleanedCount		:: [(Int, Int)]

	  -- spills/reloads that have been cleaned in this pass so far.
	, sCleanedSpillsAcc	:: Int
	, sCleanedReloadsAcc	:: Int }

initCleanS
	= CleanS
	{ sJumpValid		= emptyUFM
	, sJumpValidAcc		= emptyUFM

	, sCleanedCount		= []

	, sCleanedSpillsAcc	= 0
	, sCleanedReloadsAcc	= 0 }


-- | Remember that these regs were valid before a jump to this block
accJumpValid :: Assoc Reg Slot -> BlockId -> CleanM ()
accJumpValid regs target
 	= modify $ \s -> s {
		sJumpValidAcc = addToUFM_C (++)
					(sJumpValidAcc s)
					target
					[regs] }


--------------
-- An association table / many to many mapping.
--	TODO: 	implement this better than a simple association list.
--		two maps of sets, one for each direction would be better
--
data Assoc a b
	= Assoc
	{ aList	:: [(a, b)] }

-- | an empty association
emptyAssoc :: Assoc a b
emptyAssoc = Assoc { aList = [] }


-- | add an association to the table.
addAssoc
	:: (Eq a, Eq b)
	=> a -> b -> Assoc a b -> Assoc a b

addAssoc a b m	= m { aList = (a, b) : aList m }


-- | check if these two things are associated
elemAssoc
	:: (Eq a, Eq b)
	=> a -> b -> Assoc a b -> Bool
elemAssoc a b m	= elem (a, b) $ aList m


-- | delete all associations with this A element
deleteAAssoc
	:: Eq a
	=> a -> Assoc a b -> Assoc a b

deleteAAssoc x m
	= m { aList = [ (a, b)	| (a, b) <- aList m
				, a /= x ] }


-- | delete all associations with this B element
deleteBAssoc
	:: Eq b
	=> b -> Assoc a b -> Assoc a b

deleteBAssoc x m
	= m { aList = [ (a, b) 	| (a, b) <- aList m
				, b /= x ] }


-- | intersect two associations
intersectAssoc
	:: (Eq a, Eq b)
	=> Assoc a b -> Assoc a b -> Assoc a b

intersectAssoc a1 a2
	= emptyAssoc
	{ aList	= intersect (aList a1) (aList a2) }