[project @ 1996-04-05 08:26:04 by partain]
[ghc-hetmet.git] / ghc / compiler / stranal / WorkWrap.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1996
3 %
4 \section[WorkWrap]{Worker/wrapper-generating back-end of strictness analyser}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module WorkWrap ( workersAndWrappers ) where
10
11 import Ubiq{-uitous-}
12
13 import CoreSyn
14 import CoreUnfold       ( UnfoldingGuidance(..) )
15 import CoreUtils        ( coreExprType )
16 import Id               ( idWantsToBeINLINEd, getIdStrictness, mkWorkerId,
17                           getIdInfo
18                         )
19 import IdInfo           ( noIdInfo, addInfo_UF, indicatesWorker,
20                           mkStrictnessInfo, StrictnessInfo(..)
21                         )
22 import SaLib
23 import UniqSupply       ( returnUs, thenUs, mapUs, getUnique, UniqSM(..) )
24 import WwLib
25 import Util             ( panic{-ToDo:rm-} )
26
27 replaceIdInfo = panic "WorkWrap.replaceIdInfo (ToDo)"
28 iWantToBeINLINEd = panic "WorkWrap.iWantToBeINLINEd (ToDo)"
29 \end{code}
30
31 We take Core bindings whose binders have their strictness attached (by
32 the front-end of the strictness analyser), and we return some
33 ``plain'' bindings which have been worker/wrapper-ified, meaning:
34 \begin{enumerate}
35 \item
36 Functions have been split into workers and wrappers where appropriate;
37 \item
38 Binders' @IdInfos@ have been updated to reflect the existence
39 of these workers/wrappers (this is where we get STRICTNESS pragma
40 info for exported values).
41 \end{enumerate}
42
43 \begin{code}
44 workersAndWrappers :: [CoreBinding] -> UniqSM [CoreBinding]
45
46 workersAndWrappers top_binds
47   = mapUs (wwBind True{-top-level-}) top_binds `thenUs` \ top_binds2 ->
48     let
49         top_binds3 = map make_top_binding top_binds2
50     in
51     returnUs (concat top_binds3)
52   where
53     make_top_binding :: WwBinding -> [CoreBinding]
54
55     make_top_binding (WwLet binds) = binds
56 \end{code}
57
58 %************************************************************************
59 %*                                                                      *
60 \subsection[wwBind-wwExpr]{@wwBind@ and @wwExpr@}
61 %*                                                                      *
62 %************************************************************************
63
64 @wwBind@ works on a binding, trying each \tr{(binder, expr)} pair in
65 turn.  Non-recursive case first, then recursive...
66
67 \begin{code}
68 wwBind  :: Bool                 -- True <=> top-level binding
69         -> CoreBinding
70         -> UniqSM WwBinding     -- returns a WwBinding intermediate form;
71                                 -- the caller will convert to Expr/Binding,
72                                 -- as appropriate.
73
74 wwBind top_level (NonRec binder rhs)
75   = wwExpr rhs                  `thenUs` \ new_rhs ->
76     tryWW binder new_rhs        `thenUs` \ new_pairs ->
77     returnUs (WwLet [NonRec b e | (b,e) <- new_pairs])
78       -- Generated bindings must be non-recursive
79       -- because the original binding was.
80
81 ------------------------------
82
83 wwBind top_level (Rec pairs)
84   = mapUs do_one pairs          `thenUs` \ new_pairs ->
85     returnUs (WwLet [Rec (concat new_pairs)])
86   where
87     do_one (binder, rhs) = wwExpr rhs   `thenUs` \ new_rhs ->
88                            tryWW binder new_rhs
89 \end{code}
90
91 @wwExpr@ basically just walks the tree, looking for appropriate
92 annotations that can be used. Remember it is @wwBind@ that does the
93 matching by looking for strict arguments of the correct type.
94 @wwExpr@ is a version that just returns the ``Plain'' Tree.
95 ???????????????? ToDo
96
97 \begin{code}
98 wwExpr :: CoreExpr -> UniqSM CoreExpr
99
100 wwExpr e@(Var _)    = returnUs e
101 wwExpr e@(Lit _)    = returnUs e
102 wwExpr e@(Con  _ _) = returnUs e
103 wwExpr e@(Prim _ _) = returnUs e
104
105 wwExpr (Lam binder expr)
106   = wwExpr expr                 `thenUs` \ new_expr ->
107     returnUs (Lam binder new_expr)
108
109 wwExpr (App f a)
110   = wwExpr f                    `thenUs` \ new_f ->
111     returnUs (App new_f a)
112
113 wwExpr (SCC cc expr)
114   = wwExpr expr                 `thenUs` \ new_expr ->
115     returnUs (SCC cc new_expr)
116
117 wwExpr (Let bind expr)
118   = wwBind False{-not top-level-} bind  `thenUs` \ intermediate_bind ->
119     wwExpr expr                         `thenUs` \ new_expr ->
120     returnUs (mash_ww_bind intermediate_bind new_expr)
121   where
122     mash_ww_bind (WwLet  binds)   body = mkCoLetsNoUnboxed binds body
123     mash_ww_bind (WwCase case_fn) body = case_fn body
124
125 wwExpr (Case expr alts)
126   = wwExpr expr                         `thenUs` \ new_expr ->
127     ww_alts alts                        `thenUs` \ new_alts ->
128     returnUs (Case new_expr new_alts)
129   where
130     ww_alts (AlgAlts alts deflt)
131       = mapUs ww_alg_alt alts           `thenUs` \ new_alts ->
132         ww_deflt deflt                  `thenUs` \ new_deflt ->
133         returnUs (AlgAlts new_alts new_deflt)
134
135     ww_alts (PrimAlts alts deflt)
136       = mapUs ww_prim_alt alts          `thenUs` \ new_alts ->
137         ww_deflt deflt                  `thenUs` \ new_deflt ->
138         returnUs (PrimAlts new_alts new_deflt)
139
140     ww_alg_alt (con, binders, rhs)
141       = wwExpr rhs                      `thenUs` \ new_rhs ->
142         returnUs (con, binders, new_rhs)
143
144     ww_prim_alt (lit, rhs)
145       = wwExpr rhs                      `thenUs` \ new_rhs ->
146         returnUs (lit, new_rhs)
147
148     ww_deflt NoDefault
149       = returnUs NoDefault
150
151     ww_deflt (BindDefault binder rhs)
152       = wwExpr rhs                      `thenUs` \ new_rhs ->
153         returnUs (BindDefault binder new_rhs)
154 \end{code}
155
156 %************************************************************************
157 %*                                                                      *
158 \subsection[tryWW]{@tryWW@: attempt a worker/wrapper pair}
159 %*                                                                      *
160 %************************************************************************
161
162 @tryWW@ just accumulates arguments, converts strictness info from the
163 front-end into the proper form, then calls @mkWwBodies@ to do
164 the business.
165
166 We have to BE CAREFUL that we don't worker-wrapperize an Id that has
167 already been w-w'd!  (You can end up with several liked-named Ids
168 bouncing around at the same time---absolute mischief.)  So the
169 criterion we use is: if an Id already has an unfolding (for whatever
170 reason), then we don't w-w it.
171
172 The only reason this is monadised is for the unique supply.
173
174 \begin{code}
175 tryWW   :: Id                           -- the fn binder
176         -> CoreExpr             -- the bound rhs; its innards
177                                         --   are already ww'd
178         -> UniqSM [(Id, CoreExpr)]      -- either *one* or *two* pairs;
179                                         -- if one, then no worker (only
180                                         -- the orig "wrapper" lives on);
181                                         -- if two, then a worker and a
182                                         -- wrapper.
183 tryWW fn_id rhs
184   | idWantsToBeINLINEd fn_id
185     -- No point in worker/wrappering something that is going to be
186     -- INLINEd wholesale anyway.  If the strictness analyser is run
187     -- twice, this test also prevents wrappers (which are INLINEd)
188     -- from being re-done.
189   = do_nothing
190
191   | otherwise
192   = case (getIdStrictness fn_id) of
193
194       NoStrictnessInfo    -> do_nothing
195       BottomGuaranteed    -> do_nothing
196       StrictnessInfo [] _ -> do_nothing -- V weird (but possible?)
197
198       StrictnessInfo args_info _ ->
199         if not (indicatesWorker args_info) then
200             do_nothing
201         else
202
203         -- OK, it looks as if a worker is worth a try
204         let
205              (uvars, tyvars, args, body) = collectBinders rhs
206              body_ty                     = coreExprType body
207         in
208         mkWwBodies body_ty tyvars args args_info `thenUs` \ result ->
209         case result of
210
211           Nothing ->    -- Very peculiar. This can only happen if we hit an
212                         -- abstract type, which we shouldn't have since we've
213                         -- constructed the args_info in this module!
214
215                         -- False. We might hit the all-args-absent-and-the-
216                         -- body-is-unboxed case.  A Nothing is legit. (WDP 94/10)
217                         do_nothing
218
219           Just (wrapper_w_hole, worker_w_hole, worker_strictness, worker_ty_w_hole) ->
220
221                 -- Terrific!  It worked!
222             getUnique           `thenUs` \ worker_uniq ->
223             let
224                 worker_ty   = worker_ty_w_hole body_ty
225
226                 worker_id   = mkWorkerId worker_uniq fn_id worker_ty
227                                 (noIdInfo `addInfo` worker_strictness)
228
229                 wrapper_rhs = wrapper_w_hole worker_id
230                 worker_rhs  = worker_w_hole body
231
232                 revised_strictness_info
233                   = -- We know the basic strictness info already, but
234                     -- we need to slam in the exact identity of the
235                     -- worker Id:
236                     mkStrictnessInfo args_info (Just worker_id)
237
238                 wrapper_id  = fn_id `replaceIdInfo`
239                               (getIdInfo fn_id          `addInfo`
240                                revised_strictness_info  `addInfo_UF`
241                                iWantToBeINLINEd UnfoldAlways)
242                 -- NB! the "iWantToBeINLINEd" part adds an INLINE pragma to
243                 -- the wrapper, which is of course what we want.
244             in
245             returnUs [ (worker_id,  worker_rhs),   -- worker comes first
246                        (wrapper_id, wrapper_rhs) ] -- because wrapper mentions it
247   where
248     do_nothing = returnUs [ (fn_id, rhs) ]
249 \end{code}