[project @ 2001-10-24 08:33:25 by simonpj]
[ghc-hetmet.git] / ghc / compiler / stranal / WorkWrap.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[WorkWrap]{Worker/wrapper-generating back-end of strictness analyser}
5
6 \begin{code}
7 module WorkWrap ( wwTopBinds, mkWrapper ) where
8
9 #include "HsVersions.h"
10
11 import CoreSyn
12 import CoreUnfold       ( certainlyWillInline )
13 import CoreLint         ( showPass, endPass )
14 import CoreUtils        ( exprType, exprIsValue )
15 import Id               ( Id, idType, isOneShotLambda,
16                           setIdNewStrictness, mkWorkerId,
17                           setIdWorkerInfo, setInlinePragma,
18                           idInfo )
19 import Type             ( Type )
20 import IdInfo           ( WorkerInfo(..), arityInfo,
21                           newDemandInfo, newStrictnessInfo, unfoldingInfo, inlinePragInfo
22                         )
23 import NewDemand        ( Demand(..), StrictSig(..), DmdType(..), DmdResult(..), Keepity(..),
24                           mkTopDmdType, isBotRes, returnsCPR, topSig
25                         )
26 import UniqSupply       ( UniqSupply, initUs_, returnUs, thenUs, mapUs, getUniqueUs, UniqSM )
27 import BasicTypes       ( RecFlag(..), isNonRec, Activation(..) )
28 import Maybes           ( orElse )
29 import CmdLineOpts
30 import WwLib
31 import Outputable
32 \end{code}
33
34 We take Core bindings whose binders have:
35
36 \begin{enumerate}
37
38 \item Strictness attached (by the front-end of the strictness
39 analyser), and / or
40
41 \item Constructed Product Result information attached by the CPR
42 analysis pass.
43
44 \end{enumerate}
45
46 and we return some ``plain'' bindings which have been
47 worker/wrapper-ified, meaning: 
48
49 \begin{enumerate} 
50
51 \item Functions have been split into workers and wrappers where
52 appropriate.  If a function has both strictness and CPR properties
53 then only one worker/wrapper doing both transformations is produced;
54
55 \item Binders' @IdInfos@ have been updated to reflect the existence of
56 these workers/wrappers (this is where we get STRICTNESS and CPR pragma
57 info for exported values).
58 \end{enumerate}
59
60 \begin{code}
61
62 wwTopBinds :: DynFlags 
63            -> UniqSupply
64            -> [CoreBind]
65            -> IO [CoreBind]
66
67 wwTopBinds dflags us binds
68   = do {
69         showPass dflags "Worker Wrapper binds";
70
71         -- Create worker/wrappers, and mark binders with their
72         -- "strictness info" [which encodes their worker/wrapper-ness]
73         let { binds' = workersAndWrappers us binds };
74
75         endPass dflags "Worker Wrapper binds" 
76                 Opt_D_dump_worker_wrapper binds'
77     }
78 \end{code}
79
80
81 \begin{code}
82 workersAndWrappers :: UniqSupply -> [CoreBind] -> [CoreBind]
83
84 workersAndWrappers us top_binds
85   = initUs_ us $
86     mapUs wwBind top_binds `thenUs` \ top_binds' ->
87     returnUs (concat top_binds')
88 \end{code}
89
90 %************************************************************************
91 %*                                                                      *
92 \subsection[wwBind-wwExpr]{@wwBind@ and @wwExpr@}
93 %*                                                                      *
94 %************************************************************************
95
96 @wwBind@ works on a binding, trying each \tr{(binder, expr)} pair in
97 turn.  Non-recursive case first, then recursive...
98
99 \begin{code}
100 wwBind  :: CoreBind
101         -> UniqSM [CoreBind]    -- returns a WwBinding intermediate form;
102                                 -- the caller will convert to Expr/Binding,
103                                 -- as appropriate.
104
105 wwBind (NonRec binder rhs)
106   = wwExpr rhs                          `thenUs` \ new_rhs ->
107     tryWW NonRecursive binder new_rhs   `thenUs` \ new_pairs ->
108     returnUs [NonRec b e | (b,e) <- new_pairs]
109       -- Generated bindings must be non-recursive
110       -- because the original binding was.
111
112 wwBind (Rec pairs)
113   = mapUs do_one pairs          `thenUs` \ new_pairs ->
114     returnUs [Rec (concat new_pairs)]
115   where
116     do_one (binder, rhs) = wwExpr rhs   `thenUs` \ new_rhs ->
117                            tryWW Recursive binder new_rhs
118 \end{code}
119
120 @wwExpr@ basically just walks the tree, looking for appropriate
121 annotations that can be used. Remember it is @wwBind@ that does the
122 matching by looking for strict arguments of the correct type.
123 @wwExpr@ is a version that just returns the ``Plain'' Tree.
124
125 \begin{code}
126 wwExpr :: CoreExpr -> UniqSM CoreExpr
127
128 wwExpr e@(Type _)   = returnUs e
129 wwExpr e@(Var _)    = returnUs e
130 wwExpr e@(Lit _)    = returnUs e
131
132 wwExpr (Lam binder expr)
133   = wwExpr expr                 `thenUs` \ new_expr ->
134     returnUs (Lam binder new_expr)
135
136 wwExpr (App f a)
137   = wwExpr f                    `thenUs` \ new_f ->
138     wwExpr a                    `thenUs` \ new_a ->
139     returnUs (App new_f new_a)
140
141 wwExpr (Note note expr)
142   = wwExpr expr                 `thenUs` \ new_expr ->
143     returnUs (Note note new_expr)
144
145 wwExpr (Let bind expr)
146   = wwBind bind                 `thenUs` \ intermediate_bind ->
147     wwExpr expr                 `thenUs` \ new_expr ->
148     returnUs (mkLets intermediate_bind new_expr)
149
150 wwExpr (Case expr binder alts)
151   = wwExpr expr                         `thenUs` \ new_expr ->
152     mapUs ww_alt alts                   `thenUs` \ new_alts ->
153     returnUs (Case new_expr binder new_alts)
154   where
155     ww_alt (con, binders, rhs)
156       = wwExpr rhs                      `thenUs` \ new_rhs ->
157         returnUs (con, binders, new_rhs)
158 \end{code}
159
160 %************************************************************************
161 %*                                                                      *
162 \subsection[tryWW]{@tryWW@: attempt a worker/wrapper pair}
163 %*                                                                      *
164 %************************************************************************
165
166 @tryWW@ just accumulates arguments, converts strictness info from the
167 front-end into the proper form, then calls @mkWwBodies@ to do
168 the business.
169
170 We have to BE CAREFUL that we don't worker-wrapperize an Id that has
171 already been w-w'd!  (You can end up with several liked-named Ids
172 bouncing around at the same time---absolute mischief.)  So the
173 criterion we use is: if an Id already has an unfolding (for whatever
174 reason), then we don't w-w it.
175
176 The only reason this is monadised is for the unique supply.
177
178 \begin{code}
179 tryWW   :: RecFlag
180         -> Id                           -- The fn binder
181         -> CoreExpr                     -- The bound rhs; its innards
182                                         --   are already ww'd
183         -> UniqSM [(Id, CoreExpr)]      -- either *one* or *two* pairs;
184                                         -- if one, then no worker (only
185                                         -- the orig "wrapper" lives on);
186                                         -- if two, then a worker and a
187                                         -- wrapper.
188 tryWW is_rec fn_id rhs
189   |  isNonRec is_rec && certainlyWillInline unfolding
190         -- No point in worker/wrappering a function that is going to be
191         -- INLINEd wholesale anyway.  If the strictness analyser is run
192         -- twice, this test also prevents wrappers (which are INLINEd)
193         -- from being re-done.
194         --      
195         -- It's very important to refrain from w/w-ing an INLINE function
196         -- If we do so by mistake we transform
197         --      f = __inline (\x -> E)
198         -- into
199         --      f = __inline (\x -> case x of (a,b) -> fw E)
200         --      fw = \ab -> (__inline (\x -> E)) (a,b)
201         -- and the original __inline now vanishes, so E is no longer
202         -- inside its __inline wrapper.  Death!  Disaster!
203   = returnUs [ (fn_id, rhs) ]
204
205   | is_thunk && worthSplittingThunk fn_dmd res_info
206   = ASSERT( isNonRec is_rec )   -- The thunk must be non-recursive
207     splitThunk fn_id rhs
208
209   | is_fun && worthSplittingFun wrap_dmds res_info
210   = splitFun fn_id fn_info wrap_dmds res_info inline_prag rhs
211
212   | otherwise
213   = returnUs [ (fn_id, rhs) ]
214
215   where
216     fn_info     = idInfo fn_id
217     fn_dmd      = newDemandInfo fn_info
218     unfolding   = unfoldingInfo fn_info
219     inline_prag = inlinePragInfo fn_info
220     strict_sig  = newStrictnessInfo fn_info `orElse` topSig
221
222     StrictSig (DmdType _ wrap_dmds res_info) = strict_sig
223
224     is_fun    = not (null wrap_dmds)
225     is_thunk  = not is_fun && not (exprIsValue rhs)
226
227 ---------------------
228 splitFun fn_id fn_info wrap_dmds res_info inline_prag rhs
229   = WARN( arity /= length wrap_dmds, ppr fn_id <+> (ppr arity $$ ppr wrap_dmds $$ ppr res_info) )
230         -- The arity should match the signature
231     mkWwBodies fun_ty wrap_dmds res_info one_shots      `thenUs` \ (work_demands, wrap_fn, work_fn) ->
232     getUniqueUs                                         `thenUs` \ work_uniq ->
233     let
234         work_rhs = work_fn rhs
235         work_id  = mkWorkerId work_uniq fn_id (exprType work_rhs) 
236                         `setInlinePragma` inline_prag
237                         `setIdNewStrictness` StrictSig (mkTopDmdType work_demands work_res_info)
238                                 -- Even though we may not be at top level, 
239                                 -- it's ok to give it an empty DmdEnv
240
241         wrap_rhs = wrap_fn work_id
242         wrap_id  = fn_id `setIdWorkerInfo` HasWorker work_id arity
243                          `setInlinePragma` AlwaysActive -- Zap any inline pragma;
244                                                         -- Put it on the worker instead
245     in
246     returnUs ([(work_id, work_rhs), (wrap_id, wrap_rhs)])
247         -- Worker first, because wrapper mentions it
248         -- mkWwBodies has already built a wrap_rhs with an INLINE pragma wrapped around it
249   where
250     fun_ty = idType fn_id
251
252     arity  = arityInfo fn_info  -- The arity is set by the simplifier using exprEtaExpandArity
253                                 -- So it may be more than the number of top-level-visible lambdas
254
255     work_res_info | isBotRes res_info = BotRes  -- Cpr stuff done by wrapper
256                   | otherwise         = TopRes
257
258     one_shots = get_one_shots rhs
259
260 -- If the original function has one-shot arguments, it is important to
261 -- make the wrapper and worker have corresponding one-shot arguments too.
262 -- Otherwise we spuriously float stuff out of case-expression join points,
263 -- which is very annoying.
264 get_one_shots (Lam b e)
265   | isId b    = isOneShotLambda b : get_one_shots e
266   | otherwise = get_one_shots e
267 get_one_shots (Note _ e) = get_one_shots e
268 get_one_shots other      = noOneShotInfo
269 \end{code}
270
271 Thunk splitting
272 ~~~~~~~~~~~~~~~
273 Suppose x is used strictly (never mind whether it has the CPR
274 property).  
275
276       let
277         x* = x-rhs
278       in body
279
280 splitThunk transforms like this:
281
282       let
283         x* = case x-rhs of { I# a -> I# a }
284       in body
285
286 Now simplifier will transform to
287
288       case x-rhs of 
289         I# a -> let x* = I# b 
290                 in body
291
292 which is what we want. Now suppose x-rhs is itself a case:
293
294         x-rhs = case e of { T -> I# a; F -> I# b }
295
296 The join point will abstract over a, rather than over (which is
297 what would have happened before) which is fine.
298
299 Notice that x certainly has the CPR property now!
300
301 In fact, splitThunk uses the function argument w/w splitting 
302 function, so that if x's demand is deeper (say U(U(L,L),L))
303 then the splitting will go deeper too.
304
305 \begin{code}
306 -- splitThunk converts the *non-recursive* binding
307 --      x = e
308 -- into
309 --      x = let x = e
310 --          in case x of 
311 --               I# y -> let x = I# y in x }
312 -- See comments above. Is it not beautifully short?
313
314 splitThunk fn_id rhs
315   = mkWWstr [fn_id]             `thenUs` \ (_, wrap_fn, work_fn) ->
316     returnUs [ (fn_id, Let (NonRec fn_id rhs) (wrap_fn (work_fn (Var fn_id)))) ]
317 \end{code}
318
319
320 %************************************************************************
321 %*                                                                      *
322 \subsection{Functions over Demands}
323 %*                                                                      *
324 %************************************************************************
325
326 \begin{code}
327 worthSplittingFun :: [Demand] -> DmdResult -> Bool
328                 -- True <=> the wrapper would not be an identity function
329 worthSplittingFun ds res
330   = any worth_it ds || returnsCPR res
331         -- worthSplitting returns False for an empty list of demands,
332         -- and hence do_strict_ww is False if arity is zero and there is no CPR
333
334         -- We used not to split if the result is bottom.
335         -- [Justification:  there's no efficiency to be gained.]
336         -- But it's sometimes bad not to make a wrapper.  Consider
337         --      fw = \x# -> let x = I# x# in case e of
338         --                                      p1 -> error_fn x
339         --                                      p2 -> error_fn x
340         --                                      p3 -> the real stuff
341         -- The re-boxing code won't go away unless error_fn gets a wrapper too.
342         -- [We don't do reboxing now, but in general it's better to pass 
343         --  an unboxed thing to f, and have it reboxed in the error cases....]
344   where
345     worth_it Abs        = True  -- Absent arg
346     worth_it (Seq _ ds) = True  -- Arg to evaluate
347     worth_it other      = False
348
349 worthSplittingThunk :: Demand           -- Demand on the thunk
350                     -> DmdResult        -- CPR info for the thunk
351                     -> Bool
352 worthSplittingThunk dmd res
353   = worth_it dmd || returnsCPR res
354   where
355         -- Split if the thing is unpacked
356     worth_it (Seq Defer ds) = False
357     worth_it (Seq _     ds) = any not_abs ds
358     worth_it other          = False
359
360     not_abs Abs   = False
361     not_abs other = True
362 \end{code}
363
364
365
366 %************************************************************************
367 %*                                                                      *
368 \subsection{The worker wrapper core}
369 %*                                                                      *
370 %************************************************************************
371
372 @mkWrapper@ is called when importing a function.  We have the type of 
373 the function and the name of its worker, and we want to make its body (the wrapper).
374
375 \begin{code}
376 mkWrapper :: Type               -- Wrapper type
377           -> StrictSig          -- Wrapper strictness info
378           -> UniqSM (Id -> CoreExpr)    -- Wrapper body, missing worker Id
379
380 mkWrapper fun_ty (StrictSig (DmdType _ demands res_info))
381   = mkWwBodies fun_ty demands res_info noOneShotInfo    `thenUs` \ (_, wrap_fn, _) ->
382     returnUs wrap_fn
383
384 noOneShotInfo = repeat False
385 \end{code}