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