X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FsimplCore%2FSimplify.lhs;h=693f1a2c6b64cd1256f65ddd5a2dc33160ee66c2;hb=ac4a2563ee5b8d6bb9d0a366fe0ff3ed3fde4bb2;hp=b7280924cb19844566a0e5ee008d2b01c862f935;hpb=cc51a698c0938edaa3ccc95db19150bbaec6f795;p=ghc-hetmet.git diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index b728092..693f1a2 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -238,7 +238,7 @@ simplTopBinds env binds simpl_bind env (Rec pairs) = simplRecBind env TopLevel pairs simpl_bind env (NonRec b r) = simplRecOrTopPair env' TopLevel b b' r where - (env', b') = addLetIdInfo env b (lookupRecBndr env b) + (env', b') = addBndrRules env b (lookupRecBndr env b) \end{code} @@ -256,17 +256,17 @@ simplRecBind :: SimplEnv -> TopLevelFlag -> [(InId, InExpr)] -> SimplM SimplEnv simplRecBind env top_lvl pairs - = do { let (env_with_info, triples) = mapAccumL add_info env pairs + = do { let (env_with_info, triples) = mapAccumL add_rules env pairs ; env' <- go (zapFloats env_with_info) triples ; return (env `addRecFloats` env') } -- addFloats adds the floats from env', -- *and* updates env with the in-scope set from env' where - add_info :: SimplEnv -> (InBndr,InExpr) -> (SimplEnv, (InBndr, OutBndr, InExpr)) - -- Substitute in IdInfo, agument envt - add_info env (bndr, rhs) = (env, (bndr, bndr', rhs)) + add_rules :: SimplEnv -> (InBndr,InExpr) -> (SimplEnv, (InBndr, OutBndr, InExpr)) + -- Add the (substituted) rules to the binder + add_rules env (bndr, rhs) = (env', (bndr, bndr', rhs)) where - (env', bndr') = addLetIdInfo env bndr (lookupRecBndr env bndr) + (env', bndr') = addBndrRules env bndr (lookupRecBndr env bndr) go env [] = return env @@ -586,6 +586,8 @@ completeBind env top_lvl old_bndr new_bndr new_rhs -- (for example) be no longer strictly demanded. -- The solution here is a bit ad hoc... info_w_unf = new_bndr_info `setUnfoldingInfo` unfolding + `setWorkerInfo` worker_info + final_info | loop_breaker = new_bndr_info | isEvaldUnfolding unfolding = zapDemandInfo info_w_unf `orElse` info_w_unf | otherwise = info_w_unf @@ -599,6 +601,7 @@ completeBind env top_lvl old_bndr new_bndr new_rhs return (addNonRec env final_id new_rhs) where unfolding = mkUnfolding (isTopLevel top_lvl) new_rhs + worker_info = substWorker env (workerInfo old_info) loop_breaker = isNonRuleLoopBreaker occ_info old_info = idInfo old_bndr occ_info = occInfo old_info @@ -739,7 +742,7 @@ simplType :: SimplEnv -> InType -> SimplM OutType -- Kept monadic just so we can do the seqType simplType env ty = -- pprTrace "simplType" (ppr ty $$ ppr (seTvSubst env)) $ - seqType new_ty `seq` returnSmpl new_ty + seqType new_ty `seq` return new_ty where new_ty = substTy env ty \end{code} @@ -905,7 +908,7 @@ simplNonRecE env bndr (rhs, rhs_se) (bndrs, body) cont | otherwise = do { (env1, bndr1) <- simplNonRecBndr env bndr - ; let (env2, bndr2) = addLetIdInfo env1 bndr bndr1 + ; let (env2, bndr2) = addBndrRules env1 bndr bndr1 ; env3 <- simplLazyBind env2 NotTopLevel NonRecursive bndr bndr2 rhs rhs_se ; simplLam env3 bndrs body cont } \end{code} @@ -936,8 +939,8 @@ simplNote env InlineMe e cont -- (even a type application -- anything except Stop) = simplExprF env e cont -simplNote env (CoreNote s) e cont - = simplExpr env e `thenSmpl` \ e' -> +simplNote env (CoreNote s) e cont = do + e' <- simplExpr env e rebuild env (Note (CoreNote s) e') cont \end{code} @@ -1006,8 +1009,8 @@ completeCall env var cont Just act_fn -> lookupRule act_fn in_scope rules var args ; case maybe_rule of { - Just (rule, rule_rhs) -> - tick (RuleFired (ru_name rule)) `thenSmpl_` + Just (rule, rule_rhs) -> do + tick (RuleFired (ru_name rule)) (if dopt Opt_D_dump_rule_firings dflags then pprTrace "Rule fired" (vcat [ text "Rule:" <+> ftext (ru_name rule), @@ -1016,20 +1019,18 @@ completeCall env var cont text "Cont: " <+> ppr call_cont]) else id) $ - simplExprF env rule_rhs (dropArgs (ruleArity rule) cont) - -- The ruleArity says how many args the rule consumed + simplExprF env rule_rhs (dropArgs (ruleArity rule) cont) + -- The ruleArity says how many args the rule consumed ; Nothing -> do -- No rules ------------- Next try inlining ---------------- { let arg_infos = [interestingArg arg | arg <- args, isValArg arg] n_val_args = length arg_infos - interesting_cont = interestingCallContext (notNull args) - (notNull arg_infos) - call_cont + interesting_cont = interestingCallContext call_cont active_inline = activeInline env var - maybe_inline = callSiteInline dflags active_inline - var arg_infos interesting_cont + maybe_inline = callSiteInline dflags active_inline var + (null args) arg_infos interesting_cont ; case maybe_inline of { Just unfolding -- There is an inlining! -> do { tick (UnfoldingDone var) @@ -1328,7 +1329,7 @@ where x::F Int. Then we'd like to rewrite (F Int) to Int, getting I# x# -> let x = x' `cast` sym co in rhs -so that 'rhs' can take advantage of hte form of x'. Notice that Note +so that 'rhs' can take advantage of the form of x'. Notice that Note [Case of cast] may then apply to the result. This showed up in Roman's experiments. Example: @@ -1464,7 +1465,7 @@ simplCaseBinder env scrut case_bndr alts -- See Note [no-case-of-case] = (env, case_bndr) - | otherwise -- Failed try [see Note 2 above] + | otherwise -- Failed try; see Note [Suppressing the case binder-swap] -- not (isEvaldUnfolding (idUnfolding v)) = case scrut of Var v -> (modifyInScope env1 v case_bndr', case_bndr') @@ -1542,7 +1543,7 @@ simplAlts env scrut case_bndr alts cont' do { let alt_env = zapFloats env ; (alt_env, scrut', case_bndr') <- simplCaseBinder alt_env scrut case_bndr alts - ; (imposs_deflt_cons, in_alts) <- prepareAlts scrut case_bndr' alts + ; (imposs_deflt_cons, in_alts) <- prepareAlts alt_env scrut case_bndr' alts ; alts' <- mapM (simplAlt alt_env imposs_deflt_cons case_bndr' cont') in_alts ; return (scrut', case_bndr', alts') } @@ -1571,19 +1572,19 @@ simplAlt env imposs_deflt_cons case_bndr' cont' (LitAlt lit, bndrs, rhs) simplAlt env imposs_deflt_cons case_bndr' cont' (DataAlt con, vs, rhs) = do { -- Deal with the pattern-bound variables - (env, vs') <- simplBinders env (add_evals con vs) - -- Mark the ones that are in ! positions in the -- data constructor as certainly-evaluated. - ; let vs'' = add_evals con vs' + -- NB: simplLamBinders preserves this eval info + let vs_with_evals = add_evals vs (dataConRepStrictness con) + ; (env, vs') <- simplLamBndrs env vs_with_evals -- Bind the case-binder to (con args) ; let inst_tys' = tyConAppArgs (idType case_bndr') - con_args = map Type inst_tys' ++ varsToCoreExprs vs'' + con_args = map Type inst_tys' ++ varsToCoreExprs vs' env' = addBinderUnfolding env case_bndr' (mkConApp con con_args) ; rhs' <- simplExprC env' rhs cont' - ; return (DataAlt con, vs'', rhs') } + ; return (DataAlt con, vs', rhs') } where -- add_evals records the evaluated-ness of the bound variables of -- a case pattern. This is *important*. Consider @@ -1594,9 +1595,7 @@ simplAlt env imposs_deflt_cons case_bndr' cont' (DataAlt con, vs, rhs) -- We really must record that b is already evaluated so that we don't -- go and re-evaluate it when constructing the result. -- See Note [Data-con worker strictness] in MkId.lhs - add_evals dc vs = cat_evals dc vs (dataConRepStrictness dc) - - cat_evals dc vs strs + add_evals vs strs = go vs strs where go [] [] = [] @@ -1607,12 +1606,15 @@ simplAlt env imposs_deflt_cons case_bndr' cont' (DataAlt con, vs, rhs) where zapped_v = zap_occ_info v evald_v = zapped_v `setIdUnfolding` evaldUnfolding - go _ _ = pprPanic "cat_evals" (ppr dc $$ ppr vs $$ ppr strs) + go _ _ = pprPanic "cat_evals" (ppr con $$ ppr vs $$ ppr strs) - -- If the case binder is alive, then we add the unfolding + -- zap_occ_info: if the case binder is alive, then we add the unfolding -- case_bndr = C vs -- to the envt; so vs are now very much alive - -- Note [Aug06] I can't see why this actually matters + -- Note [Aug06] I can't see why this actually matters, but it's neater + -- case e of t { (a,b) -> ...(case t of (p,q) -> p)... } + -- ==> case e of t { (a,b) -> ...(a)... } + -- Look, Ma, a is alive now. zap_occ_info | isDeadBinder case_bndr' = \id -> id | otherwise = zapOccInfo @@ -1738,7 +1740,7 @@ mkDupableCont :: SimplEnv -> SimplCont mkDupableCont env cont | contIsDupable cont - = returnSmpl (env, cont, mkBoringStop (contResultType cont)) + = return (env, cont, mkBoringStop (contResultType cont)) mkDupableCont env (Stop {}) = panic "mkDupableCont" -- Handled by previous eqn