[project @ 2001-07-23 16:16:47 by sof]
[ghc-hetmet.git] / ghc / compiler / stranal / WwLib.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[WwLib]{A library for the ``worker/wrapper'' back-end to the strictness analyser}
5
6 \begin{code}
7 module WwLib ( mkWwBodies ) where
8
9 #include "HsVersions.h"
10
11 import CoreSyn
12 import CoreUtils        ( exprType )
13 import Id               ( Id, idType, mkSysLocal, idNewDemandInfo, setIdNewDemandInfo,
14                           isOneShotLambda, setOneShotLambda,
15                           setIdInfo
16                         )
17 import IdInfo           ( vanillaIdInfo )
18 import DataCon          ( splitProductType_maybe, splitProductType )
19 import NewDemand        ( Demand(..), Keepity(..), DmdResult(..) ) 
20 import PrelInfo         ( realWorldPrimId, aBSENT_ERROR_ID )
21 import TysPrim          ( realWorldStatePrimTy )
22 import TysWiredIn       ( tupleCon )
23 import Type             ( Type, isUnLiftedType, mkFunTys,
24                           splitForAllTys, splitFunTys, splitNewType_maybe, isAlgType
25                         )
26 import BasicTypes       ( Arity, Boxity(..) )
27 import Var              ( Var, isId )
28 import UniqSupply       ( returnUs, thenUs, getUniqueUs, getUniquesUs, UniqSM )
29 import Util             ( zipWithEqual )
30 import Outputable
31 import List             ( zipWith4 )
32 \end{code}
33
34
35 %************************************************************************
36 %*                                                                      *
37 \subsection[mkWrapperAndWorker]{@mkWrapperAndWorker@}
38 %*                                                                      *
39 %************************************************************************
40
41 Here's an example.  The original function is:
42
43 \begin{verbatim}
44 g :: forall a . Int -> [a] -> a
45
46 g = /\ a -> \ x ys ->
47         case x of
48           0 -> head ys
49           _ -> head (tail ys)
50 \end{verbatim}
51
52 From this, we want to produce:
53 \begin{verbatim}
54 -- wrapper (an unfolding)
55 g :: forall a . Int -> [a] -> a
56
57 g = /\ a -> \ x ys ->
58         case x of
59           I# x# -> $wg a x# ys
60             -- call the worker; don't forget the type args!
61
62 -- worker
63 $wg :: forall a . Int# -> [a] -> a
64
65 $wg = /\ a -> \ x# ys ->
66         let
67             x = I# x#
68         in
69             case x of               -- note: body of g moved intact
70               0 -> head ys
71               _ -> head (tail ys)
72 \end{verbatim}
73
74 Something we have to be careful about:  Here's an example:
75
76 \begin{verbatim}
77 -- "f" strictness: U(P)U(P)
78 f (I# a) (I# b) = a +# b
79
80 g = f   -- "g" strictness same as "f"
81 \end{verbatim}
82
83 \tr{f} will get a worker all nice and friendly-like; that's good.
84 {\em But we don't want a worker for \tr{g}}, even though it has the
85 same strictness as \tr{f}.  Doing so could break laziness, at best.
86
87 Consequently, we insist that the number of strictness-info items is
88 exactly the same as the number of lambda-bound arguments.  (This is
89 probably slightly paranoid, but OK in practice.)  If it isn't the
90 same, we ``revise'' the strictness info, so that we won't propagate
91 the unusable strictness-info into the interfaces.
92
93
94 %************************************************************************
95 %*                                                                      *
96 \subsection{The worker wrapper core}
97 %*                                                                      *
98 %************************************************************************
99
100 @mkWwBodies@ is called when doing the worker/wrapper split inside a module.
101
102 \begin{code}
103 mkWwBodies :: Type                              -- Type of original function
104            -> [Demand]                          -- Strictness of original function
105            -> DmdResult                         -- Info about function result
106            -> [Bool]                            -- One-shot-ness of the function
107            -> UniqSM ([Demand],                 -- Demands for worker (value) args
108                       Id -> CoreExpr,           -- Wrapper body, lacking only the worker Id
109                       CoreExpr -> CoreExpr)     -- Worker body, lacking the original function rhs
110
111 -- wrap_fn_args E       = \x y -> E
112 -- work_fn_args E       = E x y
113
114 -- wrap_fn_str E        = case x of { (a,b) -> 
115 --                        case a of { (a1,a2) ->
116 --                        E a1 a2 b y }}
117 -- work_fn_str E        = \a2 a2 b y ->
118 --                        let a = (a1,a2) in
119 --                        let x = (a,b) in
120 --                        E
121
122 mkWwBodies fun_ty demands res_info one_shots
123   = mkWWargs fun_ty demands one_shots'  `thenUs` \ (wrap_args,   wrap_fn_args, work_fn_args, res_ty) ->
124     mkWWcpr res_ty res_info             `thenUs` \ (wrap_fn_cpr, work_fn_cpr,  cpr_res_ty) ->
125     mkWWstr cpr_res_ty wrap_args        `thenUs` \ (work_dmds,   wrap_fn_str,  work_fn_str) ->
126
127     returnUs (work_dmds,
128               Note InlineMe . wrap_fn_args . wrap_fn_cpr . wrap_fn_str . Var,
129               work_fn_str . work_fn_cpr . work_fn_args)
130         -- We use an INLINE unconditionally, even if the wrapper turns out to be
131         -- something trivial like
132         --      fw = ...
133         --      f = __inline__ (coerce T fw)
134         -- The point is to propagate the coerce to f's call sites, so even though
135         -- f's RHS is now trivial (size 1) we still want the __inline__ to prevent
136         -- fw from being inlined into f's RHS
137   where
138     one_shots' = one_shots ++ repeat False
139 \end{code}
140
141
142 %************************************************************************
143 %*                                                                      *
144 \subsection{Coercion stuff}
145 %*                                                                      *
146 %************************************************************************
147
148
149 We really want to "look through" coerces.
150 Reason: I've seen this situation:
151
152         let f = coerce T (\s -> E)
153         in \x -> case x of
154                     p -> coerce T' f
155                     q -> \s -> E2
156                     r -> coerce T' f
157
158 If only we w/w'd f, we'd get
159         let f = coerce T (\s -> fw s)
160             fw = \s -> E
161         in ...
162
163 Now we'll inline f to get
164
165         let fw = \s -> E
166         in \x -> case x of
167                     p -> fw
168                     q -> \s -> E2
169                     r -> fw
170
171 Now we'll see that fw has arity 1, and will arity expand
172 the \x to get what we want.
173
174 \begin{code}
175 -- mkWWargs is driven off the function type and arity.
176 -- It chomps bites off foralls, arrows, newtypes
177 -- and keeps repeating that until it's satisfied the supplied arity
178
179 mkWWargs :: Type
180          -> [Demand]
181          -> [Bool]                      -- True for a one-shot arg; ** may be infinite **
182          -> UniqSM  ([Var],             -- Wrapper args
183                      CoreExpr -> CoreExpr,      -- Wrapper fn
184                      CoreExpr -> CoreExpr,      -- Worker fn
185                      Type)                      -- Type of wrapper body
186
187 mkWWargs fun_ty demands one_shots
188   | Just rep_ty <- splitNewType_maybe fun_ty
189         -- The newtype case is for when the function has
190         -- a recursive newtype after the arrow (rare)
191         -- We check for arity >= 0 to avoid looping in the case
192         -- of a function whose type is, in effect, infinite
193         -- [Arity is driven by looking at the term, not just the type.]
194         --
195         -- It's also important when we have a function returning (say) a pair
196         -- wrapped in a recursive newtype, at least if CPR analysis can look 
197         -- through such newtypes, which it probably can since they are 
198         -- simply coerces.
199   = mkWWargs rep_ty demands one_shots   `thenUs` \ (wrap_args, wrap_fn_args, work_fn_args, res_ty) ->
200     returnUs (wrap_args,
201               Note (Coerce fun_ty rep_ty) . wrap_fn_args,
202               work_fn_args . Note (Coerce rep_ty fun_ty),
203               res_ty)
204
205   | not (null demands)
206   = getUniquesUs                `thenUs` \ wrap_uniqs ->
207     let
208       (tyvars, tau)             = splitForAllTys fun_ty
209       (arg_tys, body_ty)        = splitFunTys tau
210
211       n_demands = length demands
212       n_arg_tys = length arg_tys
213       n_args    = n_demands `min` n_arg_tys
214
215       new_fun_ty    = mkFunTys (drop n_demands arg_tys) body_ty
216       new_demands   = drop n_arg_tys demands
217       new_one_shots = drop n_args one_shots
218
219       val_args  = zipWith4 mk_wrap_arg wrap_uniqs arg_tys demands one_shots
220       wrap_args = tyvars ++ val_args
221     in
222     ASSERT( not (null tyvars) || not (null arg_tys) )
223     mkWWargs new_fun_ty
224              new_demands
225              new_one_shots      `thenUs` \ (more_wrap_args, wrap_fn_args, work_fn_args, res_ty) ->
226
227     returnUs (wrap_args ++ more_wrap_args,
228               mkLams wrap_args . wrap_fn_args,
229               work_fn_args . applyToVars wrap_args,
230               res_ty)
231
232   | otherwise
233   = returnUs ([], id, id, fun_ty)
234
235
236 applyToVars :: [Var] -> CoreExpr -> CoreExpr
237 applyToVars vars fn = mkVarApps fn vars
238
239 mk_wrap_arg uniq ty dmd one_shot 
240   = set_one_shot one_shot (setIdNewDemandInfo (mkSysLocal SLIT("w") uniq ty) dmd)
241   where
242     set_one_shot True  id = setOneShotLambda id
243     set_one_shot False id = id
244 \end{code}
245
246
247 %************************************************************************
248 %*                                                                      *
249 \subsection{Strictness stuff}
250 %*                                                                      *
251 %************************************************************************
252
253 \begin{code}
254 mkWWstr :: Type                                 -- Result type
255         -> [Var]                                -- Wrapper args; have their demand info on them
256                                                 -- *Includes type variables*
257         -> UniqSM ([Demand],                    -- Demand on worker (value) args
258                    CoreExpr -> CoreExpr,        -- Wrapper body, lacking the worker call
259                                                 -- and without its lambdas 
260                                                 -- This fn adds the unboxing, and makes the
261                                                 -- call passing the unboxed things
262                                 
263                    CoreExpr -> CoreExpr)        -- Worker body, lacking the original body of the function,
264                                                 -- but *with* lambdas
265
266 mkWWstr res_ty wrap_args
267   = mk_ww_str wrap_args         `thenUs` \ (work_args, take_apart, put_together) ->
268     let
269         work_dmds = [idNewDemandInfo v | v <- work_args, isId v]
270         apply_to args fn = mkVarApps fn args
271     in
272     if not (null work_dmds && isUnLiftedType res_ty) then
273         returnUs ( work_dmds, 
274                    take_apart . applyToVars work_args,
275                    mkLams work_args . put_together)
276     else
277         -- Horrid special case.  If the worker would have no arguments, and the
278         -- function returns a primitive type value, that would make the worker into
279         -- an unboxed value.  We box it by passing a dummy void argument, thus:
280         --
281         --      f = /\abc. \xyz. fw abc void
282         --      fw = /\abc. \v. body
283         --
284         -- We use the state-token type which generates no code
285     getUniqueUs                 `thenUs` \ void_arg_uniq ->
286     let
287         void_arg = mk_ww_local void_arg_uniq realWorldStatePrimTy
288     in
289     returnUs ([Lazy],           
290               take_apart . applyToVars [realWorldPrimId] . apply_to work_args,
291               mkLams work_args . Lam void_arg . put_together)
292
293         -- Empty case
294 mk_ww_str []
295   = returnUs ([],
296               \ wrapper_body -> wrapper_body,
297               \ worker_body  -> worker_body)
298
299
300 mk_ww_str (arg : ds)
301   | isTyVar arg
302   = mk_ww_str ds                `thenUs` \ (worker_args, wrap_fn, work_fn) ->
303     returnUs (arg : worker_args, wrap_fn, work_fn)
304
305   | otherwise
306   = case idNewDemandInfo arg of
307
308         -- Absent case.  We don't deal with absence for unlifted types,
309         -- though, because it's not so easy to manufacture a placeholder
310         -- We'll see if this turns out to be a problem
311       Abs | not (isUnLiftedType (idType arg)) ->
312         mk_ww_str ds            `thenUs` \ (worker_args, wrap_fn, work_fn) ->
313         returnUs (worker_args, wrap_fn, mk_absent_let arg . work_fn)
314
315         -- Seq and keep
316       Seq Keep _ [] ->  mk_ww_str ds            `thenUs` \ (worker_args, wrap_fn, work_fn) ->
317                         returnUs (arg : worker_args, mk_seq_case arg . wrap_fn, work_fn)
318                            -- Pass the arg, no need to rebox
319
320         -- Seq and discard
321       Seq Drop _ [] ->  mk_ww_str ds            `thenUs` \ (worker_args, wrap_fn, work_fn) ->
322                         returnUs (worker_args,  mk_seq_case arg . wrap_fn, mk_absent_let arg . work_fn)
323                            -- Don't pass the arg, build absent arg 
324
325         -- Unpack case
326       Seq keep _ cs 
327         | Just (arg_tycon, tycon_arg_tys, data_con, inst_con_arg_tys) 
328                 <- splitProductType_maybe (idType arg)
329         -> getUniquesUs                 `thenUs` \ uniqs ->
330            let
331              unpk_args      = zipWith mk_ww_local uniqs inst_con_arg_tys
332              unpk_args_w_ds = zipWithEqual "mk_ww_str" set_worker_arg_info unpk_args cs
333              unbox_fn       = mk_unpk_case arg unpk_args data_con arg_tycon
334              rebox_fn       = mk_pk_let arg data_con tycon_arg_tys unpk_args
335            in
336            mk_ww_str (unpk_args_w_ds ++ ds)             `thenUs` \ (worker_args, wrap_fn, work_fn) ->
337            case keep of
338              Keep -> returnUs (arg : worker_args, unbox_fn . wrap_fn, work_fn)
339                            -- Pass the arg, no need to rebox
340              Drop -> returnUs (worker_args,       unbox_fn . wrap_fn, work_fn . rebox_fn)
341                            -- Don't pass the arg, rebox instead
342
343         | otherwise -> 
344            WARN( True, ppr arg )
345            mk_ww_str ds         `thenUs` \ (worker_args, wrap_fn, work_fn) ->
346            returnUs (arg : worker_args, wrap_fn, work_fn)
347
348         -- Other cases
349       other_demand ->
350         mk_ww_str ds            `thenUs` \ (worker_args, wrap_fn, work_fn) ->
351         returnUs (arg : worker_args, wrap_fn, work_fn)
352   where
353         -- If the wrapper argument is a one-shot lambda, then
354         -- so should (all) the corresponding worker arguments be
355         -- This bites when we do w/w on a case join point
356     set_worker_arg_info worker_arg demand = set_one_shot (setIdNewDemandInfo worker_arg demand)
357
358     set_one_shot | isOneShotLambda arg = setOneShotLambda
359                  | otherwise           = \x -> x
360 \end{code}
361
362
363 %************************************************************************
364 %*                                                                      *
365 \subsection{CPR stuff}
366 %*                                                                      *
367 %************************************************************************
368
369
370 @mkWWcpr@ takes the worker/wrapper pair produced from the strictness
371 info and adds in the CPR transformation.  The worker returns an
372 unboxed tuple containing non-CPR components.  The wrapper takes this
373 tuple and re-produces the correct structured output.
374
375 The non-CPR results appear ordered in the unboxed tuple as if by a
376 left-to-right traversal of the result structure.
377
378
379 \begin{code}
380 mkWWcpr :: Type                              -- function body type
381         -> DmdResult                         -- CPR analysis results
382         -> UniqSM (CoreExpr -> CoreExpr,             -- New wrapper 
383                    CoreExpr -> CoreExpr,             -- New worker
384                    Type)                        -- Type of worker's body 
385
386 mkWWcpr body_ty RetCPR
387     | not (isAlgType body_ty)
388     = WARN( True, text "mkWWcpr: non-algebraic body type" <+> ppr body_ty )
389       returnUs (id, id, body_ty)
390
391     | n_con_args == 1 && isUnLiftedType con_arg_ty1
392         -- Special case when there is a single result of unlifted type
393     = getUniquesUs                      `thenUs` \ (work_uniq : arg_uniq : _) ->
394       let
395         work_wild = mk_ww_local work_uniq body_ty
396         arg       = mk_ww_local arg_uniq  con_arg_ty1
397       in
398       returnUs (\ wkr_call -> Case wkr_call arg [(DEFAULT, [], mkConApp data_con (map Type tycon_arg_tys ++ [Var arg]))],
399                 \ body     -> workerCase body work_wild [(DataAlt data_con, [arg], Var arg)],
400                 con_arg_ty1)
401
402     | otherwise         -- The general case
403     = getUniquesUs              `thenUs` \ uniqs ->
404       let
405         (wrap_wild : work_wild : args) = zipWith mk_ww_local uniqs (ubx_tup_ty : body_ty : con_arg_tys)
406         arg_vars                       = map Var args
407         ubx_tup_con                    = tupleCon Unboxed n_con_args
408         ubx_tup_ty                     = exprType ubx_tup_app
409         ubx_tup_app                    = mkConApp ubx_tup_con (map Type con_arg_tys   ++ arg_vars)
410         con_app                        = mkConApp data_con    (map Type tycon_arg_tys ++ arg_vars)
411       in
412       returnUs (\ wkr_call -> Case wkr_call wrap_wild [(DataAlt ubx_tup_con, args, con_app)],
413                 \ body     -> workerCase body work_wild [(DataAlt data_con,    args, ubx_tup_app)],
414                 ubx_tup_ty)
415     where
416       (_, tycon_arg_tys, data_con, con_arg_tys) = splitProductType "mkWWcpr" body_ty
417       n_con_args  = length con_arg_tys
418       con_arg_ty1 = head con_arg_tys
419
420 mkWWcpr body_ty other           -- No CPR info
421     = returnUs (id, id, body_ty)
422
423 -- If the original function looked like
424 --      f = \ x -> _scc_ "foo" E
425 --
426 -- then we want the CPR'd worker to look like
427 --      \ x -> _scc_ "foo" (case E of I# x -> x)
428 -- and definitely not
429 --      \ x -> case (_scc_ "foo" E) of I# x -> x)
430 --
431 -- This transform doesn't move work or allocation
432 -- from one cost centre to another
433
434 workerCase (Note (SCC cc) e) arg alts = Note (SCC cc) (Case e arg alts)
435 workerCase e                 arg alts = Case e arg alts
436 \end{code}
437
438
439 %************************************************************************
440 %*                                                                      *
441 \subsection{Utilities}
442 %*                                                                      *
443 %************************************************************************
444
445
446 \begin{code}
447 mk_absent_let arg body
448   | not (isUnLiftedType arg_ty)
449   = Let (NonRec arg (mkTyApps (Var aBSENT_ERROR_ID) [arg_ty])) body
450   | otherwise
451   = panic "WwLib: haven't done mk_absent_let for primitives yet"
452   where
453     arg_ty = idType arg
454
455 mk_unpk_case arg unpk_args boxing_con boxing_tycon body
456         -- A data type
457   = Case (Var arg) 
458          (sanitiseCaseBndr arg)
459          [(DataAlt boxing_con, unpk_args, body)]
460
461 mk_seq_case arg body = Case (Var arg) (sanitiseCaseBndr arg) [(DEFAULT, [], body)]
462
463 sanitiseCaseBndr :: Id -> Id
464 -- The argument we are scrutinising has the right type to be
465 -- a case binder, so it's convenient to re-use it for that purpose.
466 -- But we *must* throw away all its IdInfo.  In particular, the argument
467 -- will have demand info on it, and that demand info may be incorrect for
468 -- the case binder.  e.g.       case ww_arg of ww_arg { I# x -> ... }
469 -- Quite likely ww_arg isn't used in '...'.  The case may get discarded
470 -- if the case binder says "I'm demanded".  This happened in a situation 
471 -- like         (x+y) `seq` ....
472 sanitiseCaseBndr id = id `setIdInfo` vanillaIdInfo
473
474 mk_pk_let arg boxing_con con_tys unpk_args body
475   = Let (NonRec arg (mkConApp boxing_con con_args)) body
476   where
477     con_args = map Type con_tys ++ map Var unpk_args
478
479 mk_ww_local uniq ty = mkSysLocal SLIT("ww") uniq ty
480 \end{code}