2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
5 \section[CgBindery]{Utility functions related to doing @CgBindings@}
9 -- The above warning supression flag is a temporary kludge.
10 -- While working on this module you are encouraged to remove it and fix
11 -- any warnings in the module. See
12 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
17 StableLoc, VolatileLoc,
19 cgIdInfoId, cgIdInfoArgRep, cgIdInfoLF,
21 stableIdInfo, heapIdInfo,
22 taggedStableIdInfo, taggedHeapIdInfo,
23 letNoEscapeIdInfo, idInfoToAmode,
32 bindArgsToStack, rebindToStack,
33 bindNewToNode, bindNewToUntagNode, bindNewToReg, bindArgsToRegs,
35 getArgAmode, getArgAmodes,
37 getCAddrModeIfVolatile, getVolatileRegs,
50 import PprCmm ( {- instance Outputable -} )
68 %************************************************************************
70 \subsection[Bindery-datatypes]{Data types}
72 %************************************************************************
74 @(CgBinding a b)@ is a type of finite maps from a to b.
76 The assumption used to be that @lookupCgBind@ must get exactly one
77 match. This is {\em completely wrong} in the case of compiling
78 letrecs (where knot-tying is used). An initial binding is fed in (and
79 never evaluated); eventually, a correct binding is put into the
80 environment. So there can be two bindings for a given name.
83 type CgBindings = IdEnv CgIdInfo
87 { cg_id :: Id -- Id that this is the info for
88 -- Can differ from the Id at occurrence sites by
89 -- virtue of being externalised, for splittable C
91 , cg_vol :: VolatileLoc
93 , cg_lf :: LambdaFormInfo
94 , cg_tag :: {-# UNPACK #-} !Int -- tag to be added in idInfoToAmode
97 mkCgIdInfo id vol stb lf
98 = CgIdInfo { cg_id = id, cg_vol = vol, cg_stb = stb,
99 cg_lf = lf, cg_rep = idCgRep id, cg_tag = tag }
102 | Just con <- isDataConWorkId_maybe id,
103 {- Is this an identifier for a static constructor closure? -}
104 isNullaryRepDataCon con
105 {- If yes, is this a nullary constructor?
106 If yes, we assume that the constructor is evaluated and can
114 voidIdInfo id = CgIdInfo { cg_id = id, cg_vol = NoVolatileLoc
115 , cg_stb = VoidLoc, cg_lf = mkLFArgument id
116 , cg_rep = VoidArg, cg_tag = 0 }
117 -- Used just for VoidRep things
119 data VolatileLoc -- These locations die across a call
121 | RegLoc CmmReg -- In one of the registers (global or local)
122 | VirHpLoc VirtualHpOffset -- Hp+offset (address of closure)
123 | VirNodeLoc ByteOff -- Cts of offset indirect from Node
124 -- ie *(Node+offset).
125 -- NB. Byte offset, because we subtract R1's
126 -- tag from the offset.
128 mkTaggedCgIdInfo id vol stb lf con
129 = CgIdInfo { cg_id = id, cg_vol = vol, cg_stb = stb,
130 cg_lf = lf, cg_rep = idCgRep id, cg_tag = tagForCon con }
133 @StableLoc@ encodes where an Id can be found, used by
134 the @CgBindings@ environment in @CgBindery@.
140 | VirStkLoc VirtualSpOffset -- The thing is held in this
143 | VirStkLNE VirtualSpOffset -- A let-no-escape thing; the
144 -- value is this stack pointer
145 -- (as opposed to the contents of the slot)
148 | VoidLoc -- Used only for VoidRep variables. They never need to
149 -- be saved, so it makes sense to treat treat them as
150 -- having a stable location
154 instance Outputable CgIdInfo where
155 ppr (CgIdInfo id rep vol stb lf _) -- TODO, pretty pring the tag info
156 = ppr id <+> ptext (sLit "-->") <+> vcat [ppr vol, ppr stb]
158 instance Outputable VolatileLoc where
159 ppr NoVolatileLoc = empty
160 ppr (RegLoc r) = ptext (sLit "reg") <+> ppr r
161 ppr (VirHpLoc v) = ptext (sLit "vh") <+> ppr v
162 ppr (VirNodeLoc v) = ptext (sLit "vn") <+> ppr v
164 instance Outputable StableLoc where
165 ppr NoStableLoc = empty
166 ppr VoidLoc = ptext (sLit "void")
167 ppr (VirStkLoc v) = ptext (sLit "vs") <+> ppr v
168 ppr (VirStkLNE v) = ptext (sLit "lne") <+> ppr v
169 ppr (StableLoc a) = ptext (sLit "amode") <+> ppr a
172 %************************************************************************
174 \subsection[Bindery-idInfo]{Manipulating IdInfo}
176 %************************************************************************
179 stableIdInfo id amode lf_info = mkCgIdInfo id NoVolatileLoc (StableLoc amode) lf_info
180 heapIdInfo id offset lf_info = mkCgIdInfo id (VirHpLoc offset) NoStableLoc lf_info
181 letNoEscapeIdInfo id sp lf_info = mkCgIdInfo id NoVolatileLoc (VirStkLNE sp) lf_info
182 stackIdInfo id sp lf_info = mkCgIdInfo id NoVolatileLoc (VirStkLoc sp) lf_info
183 nodeIdInfo id offset lf_info = mkCgIdInfo id (VirNodeLoc (wORD_SIZE*offset)) NoStableLoc lf_info
184 regIdInfo id reg lf_info = mkCgIdInfo id (RegLoc reg) NoStableLoc lf_info
186 taggedStableIdInfo id amode lf_info con
187 = mkTaggedCgIdInfo id NoVolatileLoc (StableLoc amode) lf_info con
188 taggedHeapIdInfo id offset lf_info con
189 = mkTaggedCgIdInfo id (VirHpLoc offset) NoStableLoc lf_info con
190 untagNodeIdInfo id offset lf_info tag
191 = mkCgIdInfo id (VirNodeLoc (wORD_SIZE*offset - tag)) NoStableLoc lf_info
194 idInfoToAmode :: CgIdInfo -> FCode CmmExpr
196 = case cg_vol info of {
197 RegLoc reg -> returnFC (CmmReg reg) ;
198 VirNodeLoc nd_off -> returnFC (CmmLoad (cmmOffsetB (CmmReg nodeReg) nd_off)
200 VirHpLoc hp_off -> do { off <- getHpRelOffset hp_off
201 ; return $! maybeTag off };
205 StableLoc amode -> returnFC $! maybeTag amode
206 VirStkLoc sp_off -> do { sp_rel <- getSpRelOffset sp_off
207 ; return (CmmLoad sp_rel mach_rep) }
209 VirStkLNE sp_off -> getSpRelOffset sp_off
211 VoidLoc -> return $ pprPanic "idInfoToAmode: void" (ppr (cg_id info))
212 -- We return a 'bottom' amode, rather than panicing now
213 -- In this way getArgAmode returns a pair of (VoidArg, bottom)
214 -- and that's exactly what we want
216 NoStableLoc -> pprPanic "idInfoToAmode: no loc" (ppr (cg_id info))
219 mach_rep = argMachRep (cg_rep info)
221 maybeTag amode -- add the tag, if we have one
223 | otherwise = cmmOffsetB amode tag
224 where tag = cg_tag info
226 cgIdInfoId :: CgIdInfo -> Id
229 cgIdInfoLF :: CgIdInfo -> LambdaFormInfo
232 cgIdInfoArgRep :: CgIdInfo -> CgRep
233 cgIdInfoArgRep = cg_rep
235 maybeLetNoEscape (CgIdInfo { cg_stb = VirStkLNE sp_off }) = Just sp_off
236 maybeLetNoEscape other = Nothing
239 %************************************************************************
241 \subsection[CgMonad-bindery]{Monad things for fiddling with @CgBindings@}
243 %************************************************************************
245 .There are three basic routines, for adding (@addBindC@), modifying
246 (@modifyBindC@) and looking up (@getCgIdInfo@) bindings.
248 A @Id@ is bound to a @(VolatileLoc, StableLoc)@ triple.
249 The name should not already be bound. (nice ASSERT, eh?)
252 addBindC :: Id -> CgIdInfo -> Code
253 addBindC name stuff_to_bind = do
255 setBinds $ extendVarEnv binds name stuff_to_bind
257 addBindsC :: [(Id, CgIdInfo)] -> Code
258 addBindsC new_bindings = do
260 let new_binds = foldl (\ binds (name,info) -> extendVarEnv binds name info)
265 modifyBindC :: Id -> (CgIdInfo -> CgIdInfo) -> Code
266 modifyBindC name mangle_fn = do
268 setBinds $ modifyVarEnv mangle_fn binds name
270 getCgIdInfo :: Id -> FCode CgIdInfo
272 = do { -- Try local bindings first
273 ; local_binds <- getBinds
274 ; case lookupVarEnv local_binds id of {
275 Just info -> return info ;
278 { -- Try top-level bindings
279 static_binds <- getStaticBinds
280 ; case lookupVarEnv static_binds id of {
281 Just info -> return info ;
284 -- Should be imported; make up a CgIdInfo for it
288 if isExternalName name then do
289 let ext_lbl = CmmLit (CmmLabel (mkClosureLabel name))
290 return (stableIdInfo id ext_lbl (mkLFImported id))
292 if isVoidArg (idCgRep id) then
293 -- Void things are never in the environment
294 return (voidIdInfo id)
301 cgLookupPanic :: Id -> FCode a
303 = do static_binds <- getStaticBinds
304 local_binds <- getBinds
308 ptext (sLit "static binds for:"),
309 vcat [ ppr (cg_id info) | info <- varEnvElts static_binds ],
310 ptext (sLit "local binds for:"),
311 vcat [ ppr (cg_id info) | info <- varEnvElts local_binds ],
312 ptext (sLit "SRT label") <+> pprCLabel srt
316 %************************************************************************
318 \subsection[Bindery-nuke-volatile]{Nuking volatile bindings}
320 %************************************************************************
322 We sometimes want to nuke all the volatile bindings; we must be sure
323 we don't leave any (NoVolatile, NoStable) binds around...
326 nukeVolatileBinds :: CgBindings -> CgBindings
327 nukeVolatileBinds binds
328 = mkVarEnv (foldr keep_if_stable [] (varEnvElts binds))
330 keep_if_stable (CgIdInfo { cg_stb = NoStableLoc }) acc = acc
331 keep_if_stable info acc
332 = (cg_id info, info { cg_vol = NoVolatileLoc }) : acc
336 %************************************************************************
338 \subsection[lookup-interface]{Interface functions to looking up bindings}
340 %************************************************************************
343 getCAddrModeIfVolatile :: Id -> FCode (Maybe CmmExpr)
344 getCAddrModeIfVolatile id
345 = do { info <- getCgIdInfo id
346 ; case cg_stb info of
347 NoStableLoc -> do -- Aha! So it is volatile!
348 amode <- idInfoToAmode info
350 a_stable_loc -> return Nothing }
353 @getVolatileRegs@ gets a set of live variables, and returns a list of
354 all registers on which these variables depend. These are the regs
355 which must be saved and restored across any C calls. If a variable is
356 both in a volatile location (depending on a register) {\em and} a
357 stable one (notably, on the stack), we modify the current bindings to
358 forget the volatile one.
361 getVolatileRegs :: StgLiveVars -> FCode [GlobalReg]
363 getVolatileRegs vars = do
364 do { stuff <- mapFCs snaffle_it (varSetElems vars)
365 ; returnFC $ catMaybes stuff }
368 { info <- getCgIdInfo var
370 -- commoned-up code...
372 = -- We assume that all regs can die across C calls
373 -- We leave it to the save-macros to decide which
374 -- regs *really* need to be saved.
376 NoStableLoc -> returnFC (Just reg) -- got one!
377 is_a_stable_loc -> do
378 { -- has both volatile & stable locations;
379 -- force it to rely on the stable location
380 modifyBindC var nuke_vol_bind
383 ; case cg_vol info of
384 RegLoc (CmmGlobal reg) -> consider_reg reg
385 VirNodeLoc _ -> consider_reg node
386 other_loc -> returnFC Nothing -- Local registers
389 nuke_vol_bind info = info { cg_vol = NoVolatileLoc }
393 getArgAmode :: StgArg -> FCode (CgRep, CmmExpr)
394 getArgAmode (StgVarArg var)
395 = do { info <- getCgIdInfo var
396 ; amode <- idInfoToAmode info
397 ; return (cgIdInfoArgRep info, amode ) }
399 getArgAmode (StgLitArg lit)
400 = do { cmm_lit <- cgLit lit
401 ; return (typeCgRep (literalType lit), CmmLit cmm_lit) }
403 getArgAmode (StgTypeArg _) = panic "getArgAmode: type arg"
405 getArgAmodes :: [StgArg] -> FCode [(CgRep, CmmExpr)]
406 getArgAmodes [] = returnFC []
407 getArgAmodes (atom:atoms)
408 | isStgTypeArg atom = getArgAmodes atoms
409 | otherwise = do { amode <- getArgAmode atom
410 ; amodes <- getArgAmodes atoms
411 ; return ( amode : amodes ) }
414 %************************************************************************
416 \subsection[binding-and-rebinding-interface]{Interface functions for binding and re-binding names}
418 %************************************************************************
421 bindArgsToStack :: [(Id, VirtualSpOffset)] -> Code
425 bind(id, offset) = addBindC id (stackIdInfo id offset (mkLFArgument id))
427 bindArgsToRegs :: [(Id, GlobalReg)] -> Code
431 bind (arg, reg) = bindNewToReg arg (CmmGlobal reg) (mkLFArgument arg)
433 bindNewToNode :: Id -> VirtualHpOffset -> LambdaFormInfo -> Code
434 bindNewToNode id offset lf_info
435 = addBindC id (nodeIdInfo id offset lf_info)
437 bindNewToUntagNode :: Id -> VirtualHpOffset -> LambdaFormInfo -> Int -> Code
438 bindNewToUntagNode id offset lf_info tag
439 = addBindC id (untagNodeIdInfo id offset lf_info tag)
441 -- Create a new temporary whose unique is that in the id,
442 -- bind the id to it, and return the addressing mode for the
444 bindNewToTemp :: Id -> FCode LocalReg
446 = do addBindC id (regIdInfo id (CmmLocal temp_reg) lf_info)
450 temp_reg = LocalReg uniq (argMachRep (idCgRep id)) kind
451 kind = if isFollowableArg (idCgRep id)
454 lf_info = mkLFArgument id -- Always used of things we
455 -- know nothing about
457 bindNewToReg :: Id -> CmmReg -> LambdaFormInfo -> Code
458 bindNewToReg name reg lf_info
461 info = mkCgIdInfo name (RegLoc reg) NoStableLoc lf_info
465 rebindToStack :: Id -> VirtualSpOffset -> Code
466 rebindToStack name offset
467 = modifyBindC name replace_stable_fn
469 replace_stable_fn info = info { cg_stb = VirStkLoc offset }
472 %************************************************************************
474 \subsection[CgMonad-deadslots]{Finding dead stack slots}
476 %************************************************************************
478 nukeDeadBindings does the following:
480 - Removes all bindings from the environment other than those
481 for variables in the argument to nukeDeadBindings.
482 - Collects any stack slots so freed, and returns them to the stack free
484 - Moves the virtual stack pointer to point to the topmost used
487 You can have multi-word slots on the stack (where a Double# used to
488 be, for instance); if dead, such a slot will be reported as *several*
489 offsets (one per word).
491 Probably *naughty* to look inside monad...
494 nukeDeadBindings :: StgLiveVars -- All the *live* variables
496 nukeDeadBindings live_vars = do
498 let (dead_stk_slots, bs') =
501 [ (cg_id b, b) | b <- varEnvElts binds ]
502 setBinds $ mkVarEnv bs'
503 freeStackSlots dead_stk_slots
506 Several boring auxiliary functions to do the dirty work.
509 dead_slots :: StgLiveVars
513 -> ([VirtualSpOffset], [(Id,CgIdInfo)])
515 -- dead_slots carries accumulating parameters for
516 -- filtered bindings, dead slots
517 dead_slots live_vars fbs ds []
518 = (ds, reverse fbs) -- Finished; rm the dups, if any
520 dead_slots live_vars fbs ds ((v,i):bs)
521 | v `elementOfUniqSet` live_vars
522 = dead_slots live_vars ((v,i):fbs) ds bs
523 -- Live, so don't record it in dead slots
524 -- Instead keep it in the filtered bindings
530 -> dead_slots live_vars fbs ([offset-size+1 .. offset] ++ ds) bs
532 _ -> dead_slots live_vars fbs ds bs
535 size = cgRepSizeW (cg_rep i)
539 getLiveStackSlots :: FCode [VirtualSpOffset]
540 -- Return the offsets of slots in stack containig live pointers
542 = do { binds <- getBinds
543 ; return [off | CgIdInfo { cg_stb = VirStkLoc off,
544 cg_rep = rep } <- varEnvElts binds,
545 isFollowableArg rep] }
549 getLiveStackBindings :: FCode [(VirtualSpOffset, CgIdInfo)]
551 = do { binds <- getBinds
552 ; return [(off, bind) |
553 bind <- varEnvElts binds,
554 CgIdInfo { cg_stb = VirStkLoc off,
555 cg_rep = rep} <- [bind],
556 isFollowableArg rep] }