Make assignTemp_ less pessimistic
[ghc-hetmet.git] / compiler / codeGen / CgLetNoEscape.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
4 %
5 %********************************************************
6 %*                                                      *
7 \section[CgLetNoEscape]{Handling ``let-no-escapes''}
8 %*                                                      *
9 %********************************************************
10
11 \begin{code}
12 module CgLetNoEscape ( cgLetNoEscapeClosure ) where
13
14 #include "HsVersions.h"
15
16 import {-# SOURCE #-} CgExpr ( cgExpr )
17
18 import StgSyn
19 import CgMonad
20
21 import CgBindery
22 import CgCase
23 import CgCon
24 import CgHeapery
25 import CgInfoTbls
26 import CgStackery
27 import OldCmm
28 import OldCmmUtils
29 import CLabel
30 import ClosureInfo
31 import CostCentre
32 import Id
33 import SMRep
34 import BasicTypes
35 \end{code}
36
37 %************************************************************************
38 %*                                                                      *
39 \subsection[what-is-non-escaping]{What {\em is} a ``non-escaping let''?}
40 %*                                                                      *
41 %************************************************************************
42
43 [The {\em code} that detects these things is elsewhere.]
44
45 Consider:
46 \begin{verbatim}
47         let x = fvs \ args -> e
48         in
49                 if ... then x else
50                 if ... then x else ...
51 \end{verbatim}
52 @x@ is used twice (so we probably can't unfold it), but when it is
53 entered, the stack is deeper than it was when the definition of @x@
54 happened.  Specifically, if instead of allocating a closure for @x@,
55 we saved all @x@'s fvs on the stack, and remembered the stack depth at
56 that moment, then whenever we enter @x@ we can simply set the stack
57 pointer(s) to these remembered (compile-time-fixed) values, and jump
58 to the code for @x@.
59
60 All of this is provided x is:
61 \begin{enumerate}
62 \item
63 non-updatable;
64 \item
65 guaranteed to be entered before the stack retreats -- ie x is not
66 buried in a heap-allocated closure, or passed as an argument to something;
67 \item
68 all the enters have exactly the right number of arguments,
69 no more no less;
70 \item
71 all the enters are tail calls; that is, they return to the
72 caller enclosing the definition of @x@.
73 \end{enumerate}
74
75 Under these circumstances we say that @x@ is {\em non-escaping}.
76
77 An example of when (4) does {\em not} hold:
78 \begin{verbatim}
79         let x = ...
80         in case x of ...alts...
81 \end{verbatim}
82
83 Here, @x@ is certainly entered only when the stack is deeper than when
84 @x@ is defined, but here it must return to \tr{...alts...} So we can't
85 just adjust the stack down to @x@'s recalled points, because that
86 would lost @alts@' context.
87
88 Things can get a little more complicated.  Consider:
89 \begin{verbatim}
90         let y = ...
91         in let x = fvs \ args -> ...y...
92         in ...x...
93 \end{verbatim}
94
95 Now, if @x@ is used in a non-escaping way in \tr{...x...}, {\em and}
96 @y@ is used in a non-escaping way in \tr{...y...}, {\em then} @y@ is
97 non-escaping.
98
99 @x@ can even be recursive!  Eg:
100 \begin{verbatim}
101         letrec x = [y] \ [v] -> if v then x True else ...
102         in
103                 ...(x b)...
104 \end{verbatim}
105
106
107 %************************************************************************
108 %*                                                                      *
109 \subsection[codeGen-for-non-escaping]{Generating code for a ``non-escaping let''}
110 %*                                                                      *
111 %************************************************************************
112
113
114 Generating code for this is fun.  It is all very very similar to what
115 we do for a case expression.  The duality is between
116 \begin{verbatim}
117         let-no-escape x = b
118         in e
119 \end{verbatim}
120 and
121 \begin{verbatim}
122         case e of ... -> b
123 \end{verbatim}
124
125 That is, the RHS of @x@ (ie @b@) will execute {\em later}, just like
126 the alternative of the case; it needs to be compiled in an environment
127 in which all volatile bindings are forgotten, and the free vars are
128 bound only to stable things like stack locations..  The @e@ part will
129 execute {\em next}, just like the scrutinee of a case.
130
131 First, we need to save all @x@'s free vars
132 on the stack, if they aren't there already.
133
134 \begin{code}
135 cgLetNoEscapeClosure
136         :: Id                   -- binder
137         -> CostCentreStack      -- NB: *** NOT USED *** ToDo (WDP 94/06)
138         -> StgBinderInfo        -- NB: ditto
139         -> StgLiveVars          -- variables live in RHS, including the binders
140                                 -- themselves in the case of a recursive group
141         -> EndOfBlockInfo       -- where are we going to?
142         -> Maybe VirtualSpOffset -- Slot for current cost centre
143         -> RecFlag              -- is the binding recursive?
144         -> [Id]                 -- args (as in \ args -> body)
145         -> StgExpr              -- body (as in above)
146         -> FCode (Id, CgIdInfo)
147
148 -- ToDo: deal with the cost-centre issues
149
150 cgLetNoEscapeClosure 
151         bndr cc _ full_live_in_rhss 
152         rhs_eob_info cc_slot _ args body
153   = let
154         arity   = length args
155         lf_info = mkLFLetNoEscape arity
156     in
157     -- saveVolatileVarsAndRegs done earlier in cgExpr.
158
159     do  { (vSp, _) <- forkEvalHelp rhs_eob_info
160
161                 (do { allocStackTop retAddrSizeW
162                     ; nukeDeadBindings full_live_in_rhss })
163
164                 (do { deAllocStackTop retAddrSizeW
165                     ; abs_c <- forkProc $ cgLetNoEscapeBody bndr cc 
166                                                   cc_slot args body
167
168                         -- Ignore the label that comes back from
169                         -- mkRetDirectTarget.  It must be conjured up elswhere
170                     ; _ <- emitReturnTarget (idName bndr) abs_c
171                     ; return () })
172
173         ; returnFC (bndr, letNoEscapeIdInfo bndr vSp lf_info) }
174 \end{code}
175
176 \begin{code}
177 cgLetNoEscapeBody :: Id         -- Name of the joint point
178                   -> CostCentreStack
179                   -> Maybe VirtualSpOffset
180                   -> [Id]       -- Args
181                   -> StgExpr    -- Body
182                   -> Code
183
184 cgLetNoEscapeBody bndr _ cc_slot all_args body = do
185   { (arg_regs, ptrs, nptrs, ret_slot) <- bindUnboxedTupleComponents all_args
186
187      -- restore the saved cost centre.  BUT: we must not free the stack slot
188      -- containing the cost centre, because it might be needed for a
189      -- recursive call to this let-no-escape.
190   ; restoreCurrentCostCentre cc_slot False{-don't free-}
191
192         -- Enter the closures cc, if required
193   ; -- enterCostCentreCode closure_info cc IsFunction
194
195         -- The "return address" slot doesn't have a return address in it;
196         -- but the heap-check needs it filled in if the heap-check fails.
197         -- So we pass code to fill it in to the heap-check macro
198   ; sp_rel <- getSpRelOffset ret_slot
199
200   ; let lbl            = mkReturnInfoLabel (idUnique bndr)
201         frame_hdr_asst = oneStmt (CmmStore sp_rel (mkLblExpr lbl))
202
203         -- Do heap check [ToDo: omit for non-recursive case by recording in
204         --      in envt and absorbing at call site]
205   ; unbxTupleHeapCheck arg_regs ptrs nptrs frame_hdr_asst 
206                         (cgExpr body)
207   }
208 \end{code}