f59ef4eb7cffe65e128ab4b8d01ea181ce7a245d
[ghc-hetmet.git] / ghc / compiler / codeGen / CgLetNoEscape.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1994
3 %
4 %********************************************************
5 %*                                                      *
6 \section[CgLetNoEscape]{Handling ``let-no-escapes''}
7 %*                                                      *
8 %********************************************************
9
10 \begin{code}
11 #include "HsVersions.h"
12
13 module CgLetNoEscape ( cgLetNoEscapeClosure ) where
14
15 import Ubiq{-uitious-}
16 import CgLoop2          ( cgExpr )
17
18 import StgSyn
19 import CgMonad
20 import AbsCSyn
21
22 import CgBindery        ( letNoEscapeIdInfo, bindArgsToRegs,
23                           bindNewToAStack, bindNewToBStack
24                         )
25 import CgHeapery        ( heapCheck )
26 import CgRetConv        ( assignRegs )
27 import CgStackery       ( mkVirtStkOffsets )
28 import CgUsages         ( setRealAndVirtualSps, getVirtSps )
29 import CLabel           ( mkStdEntryLabel )
30 import ClosureInfo      ( mkLFLetNoEscape )
31 import HeapOffs         ( VirtualSpBOffset(..) )
32 import Id               ( idPrimRep )
33 \end{code}
34
35 %************************************************************************
36 %*                                                                      *
37 \subsection[what-is-non-escaping]{What {\em is} a ``non-escaping let''?}
38 %*                                                                      *
39 %************************************************************************
40
41 [The {\em code} that detects these things is elsewhere.]
42
43 Consider:
44 \begin{verbatim}
45         let x = fvs \ args -> e
46         in
47                 if ... then x else
48                 if ... then x else ...
49 \end{verbatim}
50 @x@ is used twice (so we probably can't unfold it), but when it is
51 entered, the stack is deeper than it was then the definition of @x@
52 happened.  Specifically, if instead of allocating a closure for @x@,
53 we saved all @x@'s fvs on the stack, and remembered the stack depth at
54 that moment, then whenever we enter @x@ we can simply set the stack
55 pointer(s) to these remembered (compile-time-fixed) values, and jump
56 to the code for @x@.
57
58 All of this is provided x is:
59 \begin{enumerate}
60 \item
61 non-updatable;
62 \item
63 guaranteed to be entered before the stack retreats -- ie x is not
64 buried in a heap-allocated closure, or passed as an argument to something;
65 \item
66 all the enters have exactly the right number of arguments,
67 no more no less;
68 \item
69 all the enters are tail calls; that is, they return to the
70 caller enclosing the definition of @x@.
71 \end{enumerate}
72
73 Under these circumstances we say that @x@ is {\em non-escaping}.
74
75 An example of when (4) does {\em not} hold:
76 \begin{verbatim}
77         let x = ...
78         in case x of ...alts...
79 \end{verbatim}
80
81 Here, @x@ is certainly entered only when the stack is deeper than when
82 @x@ is defined, but here it must return to \tr{...alts...} So we can't
83 just adjust the stack down to @x@'s recalled points, because that
84 would lost @alts@' context.
85
86 Things can get a little more complicated.  Consider:
87 \begin{verbatim}
88         let y = ...
89         in let x = fvs \ args -> ...y...
90         in ...x...
91 \end{verbatim}
92
93 Now, if @x@ is used in a non-escaping way in \tr{...x...}, {\em and}
94 @y@ is used in a non-escaping way in \tr{...y...}, {\em then} @y@ is
95 non-escaping.
96
97 @x@ can even be recursive!  Eg:
98 \begin{verbatim}
99         letrec x = [y] \ [v] -> if v then x True else ...
100         in
101                 ...(x b)...
102 \end{verbatim}
103
104
105 %************************************************************************
106 %*                                                                      *
107 \subsection[codeGen-for-non-escaping]{Generating code for a ``non-escaping let''}
108 %*                                                                      *
109 %************************************************************************
110
111
112 Generating code for this is fun.  It is all very very similar to what
113 we do for a case expression.  The duality is between
114 \begin{verbatim}
115         let-no-escape x = b
116         in e
117 \end{verbatim}
118 and
119 \begin{verbatim}
120         case e of ... -> b
121 \end{verbatim}
122
123 That is, the RHS of @x@ (ie @b@) will execute {\em later}, just like
124 the alternative of the case; it needs to be compiled in an environment
125 in which all volatile bindings are forgotten, and the free vars are
126 bound only to stable things like stack locations..  The @e@ part will
127 execute {\em next}, just like the scrutinee of a case.
128
129 First, we need to save all @x@'s free vars
130 on the stack, if they aren't there already.
131
132 \begin{code}
133 cgLetNoEscapeClosure
134         :: Id                   -- binder
135         -> CostCentre           -- NB: *** NOT USED *** ToDo (WDP 94/06)
136         -> StgBinderInfo        -- NB: ditto
137         -> StgLiveVars  -- variables live in RHS, including the binders
138                                 -- themselves in the case of a recursive group
139         -> EndOfBlockInfo       -- where are we going to?
140         -> Maybe VirtualSpBOffset -- Slot for current cost centre
141         -> [Id]                 -- args (as in \ args -> body)
142         -> StgExpr              -- body (as in above)
143         -> FCode (Id, CgIdInfo)
144
145 -- ToDo: deal with the cost-centre issues
146
147 cgLetNoEscapeClosure binder cc bi full_live_in_rhss rhs_eob_info maybe_cc_slot args body
148   = let
149         arity   = length args
150         lf_info = mkLFLetNoEscape arity full_live_in_rhss{-used???-}
151     in
152     forkEvalHelp
153         rhs_eob_info
154         (nukeDeadBindings full_live_in_rhss)
155         (forkAbsC (cgLetNoEscapeBody args body))
156                                         `thenFC` \ (vA, vB, code) ->
157     let
158         label = mkStdEntryLabel binder -- arity
159     in
160     absC (CCodeBlock label code) `thenC`
161     returnFC (binder, letNoEscapeIdInfo binder vA vB lf_info)
162 \end{code}
163
164 \begin{code}
165 cgLetNoEscapeBody :: [Id]               -- Args
166                   -> StgExpr    -- Body
167                   -> Code
168
169 cgLetNoEscapeBody all_args rhs
170   = getVirtSps          `thenFC` \ (vA, vB) ->
171     let
172         arg_kinds       = map idPrimRep all_args
173         (arg_regs, _)   = assignRegs [{-nothing live-}] arg_kinds
174         stk_args        = drop (length arg_regs) all_args
175
176         -- stk_args is the args which are passed on the stack at the fast-entry point
177         -- Using them, we define the stack layout
178         (spA_stk_args, spB_stk_args, stk_bxd_w_offsets, stk_ubxd_w_offsets)
179           = mkVirtStkOffsets
180                 vA vB           -- Initial virtual SpA, SpB
181                 idPrimRep
182                 stk_args
183     in
184
185         -- Bind args to appropriate regs/stk locns
186     bindArgsToRegs all_args arg_regs                `thenC`
187     mapCs bindNewToAStack stk_bxd_w_offsets         `thenC`
188     mapCs bindNewToBStack stk_ubxd_w_offsets        `thenC`
189     setRealAndVirtualSps spA_stk_args spB_stk_args  `thenC`
190
191 {-      ToDo: NOT SURE ABOUT COST CENTRES!
192         -- Enter the closures cc, if required
193         lexEnterCCcode closure_info maybe_cc        `thenC`
194 -}
195
196         -- [No need for stack check; forkEvalHelp dealt with that]
197
198         -- Do heap check [ToDo: omit for non-recursive case by recording in
199         --      in envt and absorbing at call site]
200     heapCheck arg_regs False {- Node doesn't point to it -}  (
201               -- heapCheck *encloses* the rest
202
203         -- Compile the body
204     cgExpr rhs
205     )
206 \end{code}