2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
4 \section[WorkWrap]{Worker/wrapper-generating back-end of strictness analyser}
7 module WorkWrap ( wwTopBinds, mkWrapper ) where
9 #include "HsVersions.h"
12 import CoreUnfold ( certainlyWillInline )
13 import CoreLint ( showPass, endPass )
14 import CoreUtils ( exprType, exprIsHNF )
15 import Id ( Id, idType, isOneShotLambda,
16 setIdNewStrictness, mkWorkerId,
17 setIdWorkerInfo, setInlinePragma,
19 import MkId ( lazyIdKey, lazyIdUnfolding )
21 import IdInfo ( WorkerInfo(..), arityInfo,
22 newDemandInfo, newStrictnessInfo, unfoldingInfo, inlinePragInfo
24 import NewDemand ( Demand(..), StrictSig(..), DmdType(..), DmdResult(..),
25 Demands(..), mkTopDmdType, isBotRes, returnsCPR, topSig, isAbsent
27 import UniqSupply ( UniqSupply, initUs_, returnUs, thenUs, mapUs, getUniqueUs, UniqSM )
28 import Unique ( hasKey )
29 import BasicTypes ( RecFlag(..), isNonRec )
30 import VarEnv ( isEmptyVarEnv )
31 import Maybes ( orElse )
34 import Util ( lengthIs, notNull )
38 We take Core bindings whose binders have:
42 \item Strictness attached (by the front-end of the strictness
45 \item Constructed Product Result information attached by the CPR
50 and we return some ``plain'' bindings which have been
51 worker/wrapper-ified, meaning:
55 \item Functions have been split into workers and wrappers where
56 appropriate. If a function has both strictness and CPR properties
57 then only one worker/wrapper doing both transformations is produced;
59 \item Binders' @IdInfos@ have been updated to reflect the existence of
60 these workers/wrappers (this is where we get STRICTNESS and CPR pragma
61 info for exported values).
66 wwTopBinds :: DynFlags
71 wwTopBinds dflags us binds
73 showPass dflags "Worker Wrapper binds";
75 -- Create worker/wrappers, and mark binders with their
76 -- "strictness info" [which encodes their worker/wrapper-ness]
77 let { binds' = workersAndWrappers us binds };
79 endPass dflags "Worker Wrapper binds"
80 Opt_D_dump_worker_wrapper binds'
86 workersAndWrappers :: UniqSupply -> [CoreBind] -> [CoreBind]
88 workersAndWrappers us top_binds
90 mapUs wwBind top_binds `thenUs` \ top_binds' ->
91 returnUs (concat top_binds')
94 %************************************************************************
96 \subsection[wwBind-wwExpr]{@wwBind@ and @wwExpr@}
98 %************************************************************************
100 @wwBind@ works on a binding, trying each \tr{(binder, expr)} pair in
101 turn. Non-recursive case first, then recursive...
105 -> UniqSM [CoreBind] -- returns a WwBinding intermediate form;
106 -- the caller will convert to Expr/Binding,
109 wwBind (NonRec binder rhs)
110 = wwExpr rhs `thenUs` \ new_rhs ->
111 tryWW NonRecursive binder new_rhs `thenUs` \ new_pairs ->
112 returnUs [NonRec b e | (b,e) <- new_pairs]
113 -- Generated bindings must be non-recursive
114 -- because the original binding was.
117 = mapUs do_one pairs `thenUs` \ new_pairs ->
118 returnUs [Rec (concat new_pairs)]
120 do_one (binder, rhs) = wwExpr rhs `thenUs` \ new_rhs ->
121 tryWW Recursive binder new_rhs
124 @wwExpr@ basically just walks the tree, looking for appropriate
125 annotations that can be used. Remember it is @wwBind@ that does the
126 matching by looking for strict arguments of the correct type.
127 @wwExpr@ is a version that just returns the ``Plain'' Tree.
130 wwExpr :: CoreExpr -> UniqSM CoreExpr
132 wwExpr e@(Type _) = returnUs e
133 wwExpr e@(Lit _) = returnUs e
134 wwExpr e@(Note InlineMe expr) = returnUs e
135 -- Don't w/w inside InlineMe's
138 | v `hasKey` lazyIdKey = returnUs lazyIdUnfolding
139 | otherwise = returnUs e
140 -- HACK alert: Inline 'lazy' after strictness analysis
141 -- (but not inside InlineMe's)
143 wwExpr (Lam binder expr)
144 = wwExpr expr `thenUs` \ new_expr ->
145 returnUs (Lam binder new_expr)
148 = wwExpr f `thenUs` \ new_f ->
149 wwExpr a `thenUs` \ new_a ->
150 returnUs (App new_f new_a)
152 wwExpr (Note note expr)
153 = wwExpr expr `thenUs` \ new_expr ->
154 returnUs (Note note new_expr)
156 wwExpr (Cast expr co)
157 = wwExpr expr `thenUs` \ new_expr ->
158 returnUs (Cast new_expr co)
160 wwExpr (Let bind expr)
161 = wwBind bind `thenUs` \ intermediate_bind ->
162 wwExpr expr `thenUs` \ new_expr ->
163 returnUs (mkLets intermediate_bind new_expr)
165 wwExpr (Case expr binder ty alts)
166 = wwExpr expr `thenUs` \ new_expr ->
167 mapUs ww_alt alts `thenUs` \ new_alts ->
168 returnUs (Case new_expr binder ty new_alts)
170 ww_alt (con, binders, rhs)
171 = wwExpr rhs `thenUs` \ new_rhs ->
172 returnUs (con, binders, new_rhs)
175 %************************************************************************
177 \subsection[tryWW]{@tryWW@: attempt a worker/wrapper pair}
179 %************************************************************************
181 @tryWW@ just accumulates arguments, converts strictness info from the
182 front-end into the proper form, then calls @mkWwBodies@ to do
185 We have to BE CAREFUL that we don't worker-wrapperize an Id that has
186 already been w-w'd! (You can end up with several liked-named Ids
187 bouncing around at the same time---absolute mischief.) So the
188 criterion we use is: if an Id already has an unfolding (for whatever
189 reason), then we don't w-w it.
191 The only reason this is monadised is for the unique supply.
195 -> Id -- The fn binder
196 -> CoreExpr -- The bound rhs; its innards
198 -> UniqSM [(Id, CoreExpr)] -- either *one* or *two* pairs;
199 -- if one, then no worker (only
200 -- the orig "wrapper" lives on);
201 -- if two, then a worker and a
203 tryWW is_rec fn_id rhs
204 | isNonRec is_rec && certainlyWillInline unfolding
205 -- No point in worker/wrappering a function that is going to be
206 -- INLINEd wholesale anyway. If the strictness analyser is run
207 -- twice, this test also prevents wrappers (which are INLINEd)
208 -- from being re-done.
210 -- It's very important to refrain from w/w-ing an INLINE function
211 -- If we do so by mistake we transform
212 -- f = __inline (\x -> E)
214 -- f = __inline (\x -> case x of (a,b) -> fw E)
215 -- fw = \ab -> (__inline (\x -> E)) (a,b)
216 -- and the original __inline now vanishes, so E is no longer
217 -- inside its __inline wrapper. Death! Disaster!
218 = returnUs [ (new_fn_id, rhs) ]
220 | is_thunk && worthSplittingThunk maybe_fn_dmd res_info
221 = ASSERT2( isNonRec is_rec, ppr new_fn_id ) -- The thunk must be non-recursive
222 splitThunk new_fn_id rhs
224 | is_fun && worthSplittingFun wrap_dmds res_info
225 = splitFun new_fn_id fn_info wrap_dmds res_info inline_prag rhs
228 = returnUs [ (new_fn_id, rhs) ]
231 fn_info = idInfo fn_id
232 maybe_fn_dmd = newDemandInfo fn_info
233 unfolding = unfoldingInfo fn_info
234 inline_prag = inlinePragInfo fn_info
236 -- In practice it always will have a strictness
237 -- signature, even if it's a uninformative one
238 strict_sig = newStrictnessInfo fn_info `orElse` topSig
239 StrictSig (DmdType env wrap_dmds res_info) = strict_sig
241 -- new_fn_id has the DmdEnv zapped.
242 -- (a) it is never used again
243 -- (b) it wastes space
244 -- (c) it becomes incorrect as things are cloned, because
245 -- we don't push the substitution into it
246 new_fn_id | isEmptyVarEnv env = fn_id
247 | otherwise = fn_id `setIdNewStrictness`
248 StrictSig (mkTopDmdType wrap_dmds res_info)
250 is_fun = notNull wrap_dmds
251 is_thunk = not is_fun && not (exprIsHNF rhs)
253 ---------------------
254 splitFun fn_id fn_info wrap_dmds res_info inline_prag rhs
255 = WARN( not (wrap_dmds `lengthIs` arity), ppr fn_id <+> (ppr arity $$ ppr wrap_dmds $$ ppr res_info) )
256 -- The arity should match the signature
257 mkWwBodies fun_ty wrap_dmds res_info one_shots `thenUs` \ (work_demands, wrap_fn, work_fn) ->
258 getUniqueUs `thenUs` \ work_uniq ->
260 work_rhs = work_fn rhs
261 work_id = mkWorkerId work_uniq fn_id (exprType work_rhs)
262 `setInlinePragma` inline_prag
263 -- Any inline pragma (which sets when inlining is active)
264 -- on the original function is duplicated on the worker and wrapper
265 -- It *matters* that the pragma stays on the wrapper
266 -- It seems sensible to have it on the worker too, although we
267 -- can't think of a compelling reason. (In ptic, INLINE things are
269 `setIdNewStrictness` StrictSig (mkTopDmdType work_demands work_res_info)
270 -- Even though we may not be at top level,
271 -- it's ok to give it an empty DmdEnv
273 wrap_rhs = wrap_fn work_id
274 wrap_id = fn_id `setIdWorkerInfo` HasWorker work_id arity
277 returnUs ([(work_id, work_rhs), (wrap_id, wrap_rhs)])
278 -- Worker first, because wrapper mentions it
279 -- mkWwBodies has already built a wrap_rhs with an INLINE pragma wrapped around it
281 fun_ty = idType fn_id
283 arity = arityInfo fn_info -- The arity is set by the simplifier using exprEtaExpandArity
284 -- So it may be more than the number of top-level-visible lambdas
286 work_res_info | isBotRes res_info = BotRes -- Cpr stuff done by wrapper
289 one_shots = get_one_shots rhs
291 -- If the original function has one-shot arguments, it is important to
292 -- make the wrapper and worker have corresponding one-shot arguments too.
293 -- Otherwise we spuriously float stuff out of case-expression join points,
294 -- which is very annoying.
295 get_one_shots (Lam b e)
296 | isId b = isOneShotLambda b : get_one_shots e
297 | otherwise = get_one_shots e
298 get_one_shots (Note _ e) = get_one_shots e
299 get_one_shots other = noOneShotInfo
304 Suppose x is used strictly (never mind whether it has the CPR
311 splitThunk transforms like this:
314 x* = case x-rhs of { I# a -> I# a }
317 Now simplifier will transform to
320 I# a -> let x* = I# a
323 which is what we want. Now suppose x-rhs is itself a case:
325 x-rhs = case e of { T -> I# a; F -> I# b }
327 The join point will abstract over a, rather than over (which is
328 what would have happened before) which is fine.
330 Notice that x certainly has the CPR property now!
332 In fact, splitThunk uses the function argument w/w splitting
333 function, so that if x's demand is deeper (say U(U(L,L),L))
334 then the splitting will go deeper too.
337 -- splitThunk converts the *non-recursive* binding
342 -- I# y -> let x = I# y in x }
343 -- See comments above. Is it not beautifully short?
346 = mkWWstr [fn_id] `thenUs` \ (_, wrap_fn, work_fn) ->
347 returnUs [ (fn_id, Let (NonRec fn_id rhs) (wrap_fn (work_fn (Var fn_id)))) ]
351 %************************************************************************
353 \subsection{Functions over Demands}
355 %************************************************************************
358 worthSplittingFun :: [Demand] -> DmdResult -> Bool
359 -- True <=> the wrapper would not be an identity function
360 worthSplittingFun ds res
361 = any worth_it ds || returnsCPR res
362 -- worthSplitting returns False for an empty list of demands,
363 -- and hence do_strict_ww is False if arity is zero and there is no CPR
365 -- We used not to split if the result is bottom.
366 -- [Justification: there's no efficiency to be gained.]
367 -- But it's sometimes bad not to make a wrapper. Consider
368 -- fw = \x# -> let x = I# x# in case e of
371 -- p3 -> the real stuff
372 -- The re-boxing code won't go away unless error_fn gets a wrapper too.
373 -- [We don't do reboxing now, but in general it's better to pass
374 -- an unboxed thing to f, and have it reboxed in the error cases....]
376 worth_it Abs = True -- Absent arg
377 worth_it (Eval (Prod ds)) = True -- Product arg to evaluate
378 worth_it other = False
380 worthSplittingThunk :: Maybe Demand -- Demand on the thunk
381 -> DmdResult -- CPR info for the thunk
383 worthSplittingThunk maybe_dmd res
384 = worth_it maybe_dmd || returnsCPR res
386 -- Split if the thing is unpacked
387 worth_it (Just (Eval (Prod ds))) = not (all isAbsent ds)
388 worth_it other = False
393 %************************************************************************
395 \subsection{The worker wrapper core}
397 %************************************************************************
399 @mkWrapper@ is called when importing a function. We have the type of
400 the function and the name of its worker, and we want to make its body (the wrapper).
403 mkWrapper :: Type -- Wrapper type
404 -> StrictSig -- Wrapper strictness info
405 -> UniqSM (Id -> CoreExpr) -- Wrapper body, missing worker Id
407 mkWrapper fun_ty (StrictSig (DmdType _ demands res_info))
408 = mkWwBodies fun_ty demands res_info noOneShotInfo `thenUs` \ (_, wrap_fn, _) ->
411 noOneShotInfo = repeat False