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