Fix warnings in CgTailCall
[ghc-hetmet.git] / compiler / codeGen / CgTailCall.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 % Code generation for tail calls.
6
7 \begin{code}
8 module CgTailCall (
9         cgTailCall, performTailCall,
10         performReturn, performPrimReturn,
11         returnUnboxedTuple, ccallReturnUnboxedTuple,
12         pushUnboxedTuple,
13         tailCallPrimOp,
14
15         pushReturnAddress
16     ) where
17
18 #include "HsVersions.h"
19
20 import CgMonad
21 import CgBindery
22 import CgInfoTbls
23 import CgCallConv
24 import CgStackery
25 import CgHeapery
26 import CgUtils
27 import CgTicky
28 import ClosureInfo
29 import SMRep
30 import Cmm      
31 import CmmUtils
32 import CLabel
33 import Type
34 import Id
35 import StgSyn
36 import PrimOp
37 import Outputable
38
39 import Control.Monad
40
41 -----------------------------------------------------------------------------
42 -- Tail Calls
43
44 cgTailCall :: Id -> [StgArg] -> Code
45
46 -- Here's the code we generate for a tail call.  (NB there may be no
47 -- arguments, in which case this boils down to just entering a variable.)
48 -- 
49 --    * Put args in the top locations of the stack.
50 --    * Adjust the stack ptr
51 --    * Make R1 point to the function closure if necessary.
52 --    * Perform the call.
53 --
54 -- Things to be careful about:
55 --
56 --    * Don't overwrite stack locations before you have finished with
57 --      them (remember you need the function and the as-yet-unmoved
58 --      arguments).
59 --    * Preferably, generate no code to replace x by x on the stack (a
60 --      common situation in tail-recursion).
61 --    * Adjust the stack high water mark appropriately.
62 -- 
63 -- Treat unboxed locals exactly like literals (above) except use the addr
64 -- mode for the local instead of (CLit lit) in the assignment.
65
66 cgTailCall fun args
67   = do  { fun_info <- getCgIdInfo fun
68
69         ; if isUnLiftedType (idType fun)
70           then  -- Primitive return
71                 ASSERT( null args )
72             do  { fun_amode <- idInfoToAmode fun_info
73                 ; performPrimReturn (cgIdInfoArgRep fun_info) fun_amode } 
74
75           else -- Normal case, fun is boxed
76             do  { arg_amodes <- getArgAmodes args
77                 ; performTailCall fun_info arg_amodes noStmts }
78         }
79                 
80
81 -- -----------------------------------------------------------------------------
82 -- The guts of a tail-call
83
84 performTailCall 
85         :: CgIdInfo             -- The function
86         -> [(CgRep,CmmExpr)]    -- Args
87         -> CmmStmts             -- Pending simultaneous assignments
88                                 --  *** GUARANTEED to contain only stack assignments.
89         -> Code
90
91 performTailCall fun_info arg_amodes pending_assts
92   | Just join_sp <- maybeLetNoEscape fun_info
93   =        -- A let-no-escape is slightly different, because we
94            -- arrange the stack arguments into pointers and non-pointers
95            -- to make the heap check easier.  The tail-call sequence
96            -- is very similar to returning an unboxed tuple, so we
97            -- share some code.
98      do { (final_sp, arg_assts) <- pushUnboxedTuple join_sp arg_amodes
99         ; emitSimultaneously (pending_assts `plusStmts` arg_assts)
100         ; let lbl = enterReturnPtLabel (idUnique (cgIdInfoId fun_info))
101         ; doFinalJump final_sp True {- Is LNE -} (jumpToLbl lbl) }
102
103   | otherwise
104   = do  { fun_amode <- idInfoToAmode fun_info
105         ; let assignSt  = CmmAssign nodeReg fun_amode
106               node_asst = oneStmt assignSt
107               opt_node_asst | nodeMustPointToIt lf_info = node_asst
108                             | otherwise                 = noStmts
109         ; EndOfBlockInfo sp _ <- getEndOfBlockInfo
110
111         ; case (getCallMethod fun_name fun_has_cafs lf_info (length arg_amodes)) of
112
113             -- Node must always point to things we enter
114             EnterIt -> do
115                 { emitSimultaneously (node_asst `plusStmts` pending_assts) 
116                 ; let target     = entryCode (closureInfoPtr (CmmReg nodeReg))
117                       enterClosure = stmtC (CmmJump target [])
118                       -- If this is a scrutinee
119                       -- let's check if the closure is a constructor
120                       -- so we can directly jump to the alternatives switch
121                       -- statement.
122                       jumpInstr = getEndOfBlockInfo >>=
123                                   maybeSwitchOnCons enterClosure
124                 ; doFinalJump sp False jumpInstr }
125     
126             -- A function, but we have zero arguments.  It is already in WHNF,
127             -- so we can just return it.  
128             -- As with any return, Node must point to it.
129             ReturnIt -> do
130                 { emitSimultaneously (node_asst `plusStmts` pending_assts)
131                 ; doFinalJump sp False emitReturnInstr }
132     
133             -- A real constructor.  Don't bother entering it, 
134             -- just do the right sort of return instead.
135             -- As with any return, Node must point to it.
136             ReturnCon _ -> do
137                 { emitSimultaneously (node_asst `plusStmts` pending_assts)
138                 ; doFinalJump sp False emitReturnInstr }
139
140             JumpToIt lbl -> do
141                 { emitSimultaneously (opt_node_asst `plusStmts` pending_assts)
142                 ; doFinalJump sp False (jumpToLbl lbl) }
143     
144             -- A slow function call via the RTS apply routines
145             -- Node must definitely point to the thing
146             SlowCall -> do 
147                 {  when (not (null arg_amodes)) $ do
148                    { if (isKnownFun lf_info) 
149                         then tickyKnownCallTooFewArgs
150                         else tickyUnknownCall
151                    ; tickySlowCallPat (map fst arg_amodes) 
152                    }
153
154                 ; let (apply_lbl, args, extra_args) 
155                         = constructSlowCall arg_amodes
156
157                 ; directCall sp apply_lbl args extra_args 
158                         (node_asst `plusStmts` pending_assts)
159
160                 }
161     
162             -- A direct function call (possibly with some left-over arguments)
163             DirectEntry lbl arity -> do
164                 { if arity == length arg_amodes
165                         then tickyKnownCallExact
166                         else do tickyKnownCallExtraArgs
167                                 tickySlowCallPat (map fst (drop arity arg_amodes))
168
169                 ; let
170                      -- The args beyond the arity go straight on the stack
171                      (arity_args, extra_args) = splitAt arity arg_amodes
172      
173                 ; directCall sp lbl arity_args extra_args
174                         (opt_node_asst `plusStmts` pending_assts)
175                 }
176         }
177   where
178     fun_id    = cgIdInfoId fun_info
179     fun_name  = idName fun_id
180     lf_info   = cgIdInfoLF fun_info
181     fun_has_cafs = idCafInfo fun_id
182     untag_node = CmmAssign nodeReg (cmmUntag (CmmReg nodeReg))
183     -- Test if closure is a constructor
184     maybeSwitchOnCons enterClosure eob
185               | EndOfBlockInfo _ (CaseAlts lbl _ _) <- eob
186               = do { is_constr <- newLabelC
187                    -- Is the pointer tagged?
188                    -- Yes, jump to switch statement
189                    ; stmtC (CmmCondBranch (cmmIsTagged (CmmReg nodeReg)) 
190                                 is_constr)
191                    -- No, enter the closure.
192                    ; enterClosure
193                    ; labelC is_constr
194                    ; stmtC (CmmJump (entryCode $ CmmLit (CmmLabel lbl)) [])
195                    }
196 {-
197               -- This is a scrutinee for a case expression
198               -- so let's see if we can directly inspect the closure
199               | EndOfBlockInfo _ (CaseAlts lbl _ _ _) <- eob
200               = do { no_cons <- newLabelC
201                    -- Both the NCG and gcc optimize away the temp
202                    ; z <- newTemp  wordRep
203                    ; stmtC (CmmAssign z tag_expr)
204                    ; let tag = CmmReg z
205                    -- Is the closure a cons?
206                    ; stmtC (CmmCondBranch (cond1 tag) no_cons)
207                    ; stmtC (CmmCondBranch (cond2 tag) no_cons)
208                    -- Yes, jump to switch statement
209                    ; stmtC (CmmJump (CmmLit (CmmLabel lbl)) [])
210                    ; labelC no_cons
211                    -- No, enter the closure.
212                    ; enterClosure
213                    }
214 -}
215               -- No case expression involved, enter the closure.
216               | otherwise
217               = do { stmtC untag_node
218                    ; enterClosure
219                    }
220         where
221           --cond1 tag  = cmmULtWord tag lowCons
222           -- More efficient than the above?
223 {-
224           tag_expr   = cmmGetClosureType (CmmReg nodeReg)
225           cond1 tag  = cmmEqWord tag (CmmLit (mkIntCLit 0))
226           cond2 tag  = cmmUGtWord tag highCons
227           lowCons    = CmmLit (mkIntCLit 1)
228             -- CONSTR
229           highCons   = CmmLit (mkIntCLit 8)
230             -- CONSTR_NOCAF_STATIC (from ClosureType.h)
231 -}
232
233 directCall :: VirtualSpOffset -> CLabel -> [(CgRep, CmmExpr)]
234            -> [(CgRep, CmmExpr)] -> CmmStmts
235            -> Code
236 directCall sp lbl args extra_args assts = do
237   let
238         -- First chunk of args go in registers
239         (reg_arg_amodes, stk_args) = assignCallRegs args
240      
241         -- Any "extra" arguments are placed in frames on the
242         -- stack after the other arguments.
243         slow_stk_args = slowArgs extra_args
244
245         reg_assts = assignToRegs reg_arg_amodes
246   --
247   (final_sp, stk_assts) <- mkStkAmodes sp (stk_args ++ slow_stk_args)
248
249   emitSimultaneously (reg_assts     `plusStmts`
250                       stk_assts     `plusStmts`
251                       assts)
252
253   doFinalJump final_sp False (jumpToLbl lbl)
254
255 -- -----------------------------------------------------------------------------
256 -- The final clean-up before we do a jump at the end of a basic block.
257 -- This code is shared by tail-calls and returns.
258
259 doFinalJump :: VirtualSpOffset -> Bool -> Code -> Code 
260 doFinalJump final_sp is_let_no_escape jump_code
261   = do  { -- Adjust the high-water mark if necessary
262           adjustStackHW final_sp
263
264         -- Push a return address if necessary (after the assignments
265         -- above, in case we clobber a live stack location)
266         --
267         -- DONT push the return address when we're about to jump to a
268         -- let-no-escape: the final tail call in the let-no-escape
269         -- will do this.
270         ; eob <- getEndOfBlockInfo
271         ; whenC (not is_let_no_escape) (pushReturnAddress eob)
272
273             -- Final adjustment of Sp/Hp
274         ; adjustSpAndHp final_sp
275
276             -- and do the jump
277         ; jump_code }
278
279 -- ----------------------------------------------------------------------------
280 -- A general return (just a special case of doFinalJump, above)
281
282 performReturn :: Code   -- The code to execute to actually do the return
283               -> Code
284
285 performReturn finish_code
286   = do  { EndOfBlockInfo args_sp _sequel <- getEndOfBlockInfo
287         ; doFinalJump args_sp False{-not a LNE-} finish_code }
288
289 -- ----------------------------------------------------------------------------
290 -- Primitive Returns
291 -- Just load the return value into the right register, and return.
292
293 performPrimReturn :: CgRep -> CmmExpr   -- The thing to return
294                   -> Code
295 performPrimReturn rep amode
296   =  do { whenC (not (isVoidArg rep))
297                 (stmtC (CmmAssign ret_reg amode))
298         ; performReturn emitReturnInstr }
299   where
300     ret_reg = dataReturnConvPrim rep
301
302 -- ---------------------------------------------------------------------------
303 -- Unboxed tuple returns
304
305 -- These are a bit like a normal tail call, except that:
306 --
307 --   - The tail-call target is an info table on the stack
308 --
309 --   - We separate stack arguments into pointers and non-pointers,
310 --     to make it easier to leave things in a sane state for a heap check.
311 --     This is OK because we can never partially-apply an unboxed tuple,
312 --     unlike a function.  The same technique is used when calling
313 --     let-no-escape functions, because they also can't be partially
314 --     applied.
315
316 returnUnboxedTuple :: [(CgRep, CmmExpr)] -> Code
317 returnUnboxedTuple amodes
318   = do  { (EndOfBlockInfo args_sp _sequel) <- getEndOfBlockInfo
319         ; tickyUnboxedTupleReturn (length amodes)
320         ; (final_sp, assts) <- pushUnboxedTuple args_sp amodes
321         ; emitSimultaneously assts
322         ; doFinalJump final_sp False{-not a LNE-} emitReturnInstr }
323
324 pushUnboxedTuple :: VirtualSpOffset             -- Sp at which to start pushing
325                  -> [(CgRep, CmmExpr)]          -- amodes of the components
326                  -> FCode (VirtualSpOffset,     -- final Sp
327                            CmmStmts)            -- assignments (regs+stack)
328
329 pushUnboxedTuple sp [] 
330   = return (sp, noStmts)
331 pushUnboxedTuple sp amodes
332   = do  { let   (reg_arg_amodes, stk_arg_amodes) = assignReturnRegs amodes
333         
334                 -- separate the rest of the args into pointers and non-pointers
335                 (ptr_args, nptr_args) = separateByPtrFollowness stk_arg_amodes
336                 reg_arg_assts = assignToRegs reg_arg_amodes
337                 
338             -- push ptrs, then nonptrs, on the stack
339         ; (ptr_sp,   ptr_assts)  <- mkStkAmodes sp ptr_args
340         ; (final_sp, nptr_assts) <- mkStkAmodes ptr_sp nptr_args
341
342         ; returnFC (final_sp,
343                     reg_arg_assts `plusStmts` 
344                     ptr_assts `plusStmts` nptr_assts) }
345     
346                   
347 -- -----------------------------------------------------------------------------
348 -- Returning unboxed tuples.  This is mainly to support _ccall_GC_, where
349 -- we want to do things in a slightly different order to normal:
350 -- 
351 --              - push return address
352 --              - adjust stack pointer
353 --              - r = call(args...)
354 --              - assign regs for unboxed tuple (usually just R1 = r)
355 --              - return to continuation
356 -- 
357 -- The return address (i.e. stack frame) must be on the stack before
358 -- doing the call in case the call ends up in the garbage collector.
359 -- 
360 -- Sadly, the information about the continuation is lost after we push it
361 -- (in order to avoid pushing it again), so we end up doing a needless
362 -- indirect jump (ToDo).
363
364 ccallReturnUnboxedTuple :: [(CgRep, CmmExpr)] -> Code -> Code
365 ccallReturnUnboxedTuple amodes before_jump
366   = do  { eob@(EndOfBlockInfo args_sp _) <- getEndOfBlockInfo
367
368         -- Push a return address if necessary
369         ; pushReturnAddress eob
370         ; setEndOfBlockInfo (EndOfBlockInfo args_sp OnStack)
371             (do { adjustSpAndHp args_sp
372                 ; before_jump
373                 ; returnUnboxedTuple amodes })
374     }
375
376 -- -----------------------------------------------------------------------------
377 -- Calling an out-of-line primop
378
379 tailCallPrimOp :: PrimOp -> [StgArg] -> Code
380 tailCallPrimOp op args
381  = do   {       -- We're going to perform a normal-looking tail call, 
382                 -- except that *all* the arguments will be in registers.
383                 -- Hence the ASSERT( null leftovers )
384           arg_amodes <- getArgAmodes args
385         ; let (arg_regs, leftovers) = assignPrimOpCallRegs arg_amodes
386               jump_to_primop = jumpToLbl (mkRtsPrimOpLabel op)
387
388         ; ASSERT(null leftovers) -- no stack-resident args
389           emitSimultaneously (assignToRegs arg_regs)
390
391         ; EndOfBlockInfo args_sp _ <- getEndOfBlockInfo
392         ; doFinalJump args_sp False{-not a LNE-} jump_to_primop }
393
394 -- -----------------------------------------------------------------------------
395 -- Return Addresses
396
397 -- We always push the return address just before performing a tail call
398 -- or return.  The reason we leave it until then is because the stack
399 -- slot that the return address is to go into might contain something
400 -- useful.
401 -- 
402 -- If the end of block info is 'CaseAlts', then we're in the scrutinee of a
403 -- case expression and the return address is still to be pushed.
404 -- 
405 -- There are cases where it doesn't look necessary to push the return
406 -- address: for example, just before doing a return to a known
407 -- continuation.  However, the continuation will expect to find the
408 -- return address on the stack in case it needs to do a heap check.
409
410 pushReturnAddress :: EndOfBlockInfo -> Code
411
412 pushReturnAddress (EndOfBlockInfo args_sp (CaseAlts lbl _ _))
413   = do  { sp_rel <- getSpRelOffset args_sp
414         ; stmtC (CmmStore sp_rel (mkLblExpr lbl)) }
415
416 pushReturnAddress _ = nopC
417
418 -- -----------------------------------------------------------------------------
419 -- Misc.
420
421 jumpToLbl :: CLabel -> Code
422 -- Passes no argument to the destination procedure
423 jumpToLbl lbl = stmtC (CmmJump (CmmLit (CmmLabel lbl)) [{- No args -}])
424
425 assignToRegs :: [(CmmExpr, GlobalReg)] -> CmmStmts
426 assignToRegs reg_args 
427   = mkStmts [ CmmAssign (CmmGlobal reg_id) expr
428             | (expr, reg_id) <- reg_args ] 
429 \end{code}
430
431
432 %************************************************************************
433 %*                                                                      *
434 \subsection[CgStackery-adjust]{Adjusting the stack pointers}
435 %*                                                                      *
436 %************************************************************************
437
438 This function adjusts the stack and heap pointers just before a tail
439 call or return.  The stack pointer is adjusted to its final position
440 (i.e. to point to the last argument for a tail call, or the activation
441 record for a return).  The heap pointer may be moved backwards, in
442 cases where we overallocated at the beginning of the basic block (see
443 CgCase.lhs for discussion).
444
445 These functions {\em do not} deal with high-water-mark adjustment.
446 That's done by functions which allocate stack space.
447
448 \begin{code}
449 adjustSpAndHp :: VirtualSpOffset        -- New offset for Arg stack ptr
450               -> Code
451 adjustSpAndHp newRealSp 
452   = do  { -- Adjust stack, if necessary.
453           -- NB: the conditional on the monad-carried realSp
454           --     is out of line (via codeOnly), to avoid a black hole
455         ; new_sp <- getSpRelOffset newRealSp
456         ; checkedAbsC (CmmAssign spReg new_sp)  -- Will generate no code in the case
457         ; setRealSp newRealSp                   -- where realSp==newRealSp
458
459           -- Adjust heap.  The virtual heap pointer may be less than the real Hp
460           -- because the latter was advanced to deal with the worst-case branch
461           -- of the code, and we may be in a better-case branch.  In that case,
462           -- move the real Hp *back* and retract some ticky allocation count.
463         ; hp_usg <- getHpUsage
464         ; let rHp = realHp hp_usg
465               vHp = virtHp hp_usg
466         ; new_hp <- getHpRelOffset vHp
467         ; checkedAbsC (CmmAssign hpReg new_hp)  -- Generates nothing when vHp==rHp
468         ; tickyAllocHeap (vHp - rHp)            -- ...ditto
469         ; setRealHp vHp
470         }
471 \end{code}
472