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