X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FbasicTypes%2FMkId.lhs;h=16c45b758395b1e708144b5a6dcc0cdbfe1858b4;hb=e2587381bec9e1ef5953c2596c4090af05d39aac;hp=29ccb62de4c681eeabb53afa9bd3db2386e09c64;hpb=ad9239172c453e4244de8eccc172e2c679766ea5;p=ghc-hetmet.git diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 29ccb62..16c45b7 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -65,7 +65,7 @@ import DataCon import Id import Var ( Var, TyVar, mkCoVar, mkExportedLocalVar ) import IdInfo -import NewDemand +import Demand import CoreSyn import Unique import PrelNames @@ -265,7 +265,7 @@ mkDataConIds wrap_name wkr_name data_con wkr_arity = dataConRepArity data_con wkr_info = noCafIdInfo `setArityInfo` wkr_arity - `setAllStrictnessInfo` Just wkr_sig + `setStrictnessInfo` Just wkr_sig `setUnfoldingInfo` evaldUnfolding -- Record that it's evaluated, -- even if arity = 0 @@ -329,7 +329,7 @@ mkDataConIds wrap_name wkr_name data_con -- It's important to specify the arity, so that partial -- applications are treated as values `setUnfoldingInfo` wrap_unf - `setAllStrictnessInfo` Just wrap_sig + `setStrictnessInfo` Just wrap_sig all_strict_marks = dataConExStricts data_con ++ dataConStrictMarks data_con wrap_sig = mkStrictSig (mkTopDmdType arg_dmds cpr_info) @@ -345,7 +345,7 @@ mkDataConIds wrap_name wkr_name data_con -- ...(let w = C x in ...(w p q)...)... -- we want to see that w is strict in its two arguments - wrap_unf = mkInlineRule InlSat wrap_rhs (length dict_args + length id_args) + wrap_unf = mkInlineRule wrap_rhs (Just (length dict_args + length id_args)) wrap_rhs = mkLams wrap_tvs $ mkLams eq_args $ mkLams dict_args $ mkLams id_args $ @@ -457,17 +457,21 @@ mkDictSelId no_unf name clas -- But it's type must expose the representation of the dictionary -- to get (say) C a -> (a -> a) - info = noCafIdInfo - `setArityInfo` 1 - `setAllStrictnessInfo` Just strict_sig - `setSpecInfo` mkSpecInfo [rule] - `setInlinePragInfo` neverInlinePragma + base_info = noCafIdInfo + `setArityInfo` 1 + `setStrictnessInfo` Just strict_sig `setUnfoldingInfo` (if no_unf then noUnfolding - else mkImplicitUnfolding rhs) - -- Experimental: NOINLINE, so that their rule matches - - -- We no longer use 'must-inline' on record selectors. They'll - -- inline like crazy if they scrutinise a constructor + else mkImplicitUnfolding rhs) + -- In module where class op is defined, we must add + -- the unfolding, even though it'll never be inlined + -- becuase we use that to generate a top-level binding + -- for the ClassOp + + info = base_info `setSpecInfo` mkSpecInfo [rule] + `setInlinePragInfo` neverInlinePragma + -- Add a magic BuiltinRule, and never inline it + -- so that the rule is always available to fire. + -- See Note [ClassOp/DFun selection] in TcInstDcls n_ty_args = length tyvars @@ -484,11 +488,12 @@ mkDictSelId no_unf name clas -- It's worth giving one, so that absence info etc is generated -- even if the selector isn't inlined strict_sig = mkStrictSig (mkTopDmdType [arg_dmd] TopRes) - arg_dmd | isNewTyCon tycon = evalDmd - | otherwise = Eval (Prod [ if the_arg_id == id then evalDmd else Abs - | id <- arg_ids ]) + arg_dmd | new_tycon = evalDmd + | otherwise = Eval (Prod [ if the_arg_id == id then evalDmd else Abs + | id <- arg_ids ]) tycon = classTyCon clas + new_tycon = isNewTyCon tycon [data_con] = tyConDataCons tycon tyvars = dataConUnivTyVars data_con arg_tys = {- ASSERT( isVanillaDataCon data_con ) -} dataConRepArgTys data_con @@ -497,8 +502,8 @@ mkDictSelId no_unf name clas the_arg_id = arg_ids !! index pred = mkClassPred clas (mkTyVarTys tyvars) - dict_id = mkTemplateLocal 1 $ mkPredTy pred - (eq_ids,n) = mkCoVarLocals 2 $ mkPredTys eq_theta + dict_id = mkTemplateLocal 1 $ mkPredTy pred + (eq_ids,n) = mkCoVarLocals 2 $ mkPredTys eq_theta arg_ids = mkTemplateLocalsNum n arg_tys mkCoVarLocals i [] = ([],i) @@ -507,20 +512,20 @@ mkDictSelId no_unf name clas in (y:ys,j) rhs = mkLams tyvars (Lam dict_id rhs_body) - rhs_body | isNewTyCon tycon = unwrapNewTypeBody tycon (map mkTyVarTy tyvars) (Var dict_id) - | otherwise = Case (Var dict_id) dict_id (idType the_arg_id) - [(DataAlt data_con, eq_ids ++ arg_ids, Var the_arg_id)] + rhs_body | new_tycon = unwrapNewTypeBody tycon (map mkTyVarTy tyvars) (Var dict_id) + | otherwise = Case (Var dict_id) dict_id (idType the_arg_id) + [(DataAlt data_con, eq_ids ++ arg_ids, Var the_arg_id)] -dictSelRule :: Int -> Arity -> [CoreExpr] -> Maybe CoreExpr +dictSelRule :: Int -> Arity -> IdUnfoldingFun -> [CoreExpr] -> Maybe CoreExpr -- Oh, very clever -- op_i t1..tk (df s1..sn d1..dm) = op_i_helper s1..sn d1..dm -- op_i t1..tk (D t1..tk op1 ... opm) = opi -- -- NB: the data constructor has the same number of type args as the class op -dictSelRule index n_ty_args args +dictSelRule index n_ty_args id_unf args | (dict_arg : _) <- drop n_ty_args args - , Just (_, _, val_args) <- exprIsConApp_maybe dict_arg + , Just (_, _, val_args) <- exprIsConApp_maybe id_unf dict_arg = Just (val_args !! index) | otherwise = Nothing @@ -754,7 +759,7 @@ mkPrimOpId prim_op info = noCafIdInfo `setSpecInfo` mkSpecInfo (primOpRules prim_op name) `setArityInfo` arity - `setAllStrictnessInfo` Just strict_sig + `setStrictnessInfo` Just strict_sig -- For each ccall we manufacture a separate CCallOpId, giving it -- a fresh unique, a type that is correct for this particular ccall, @@ -780,7 +785,7 @@ mkFCallId uniq fcall ty info = noCafIdInfo `setArityInfo` arity - `setAllStrictnessInfo` Just strict_sig + `setStrictnessInfo` Just strict_sig (_, tau) = tcSplitForAllTys ty (arg_tys, _) = tcSplitFunTys tau @@ -942,17 +947,19 @@ seqId = pcMiscPrelId seqName ty info [x,y] = mkTemplateLocals [alphaTy, openBetaTy] rhs = mkLams [alphaTyVar,openBetaTyVar,x,y] (Case (Var x) x openBetaTy [(DEFAULT, [], Var y)]) + -- See Note [Built-in RULES for seq] seq_cast_rule = BuiltinRule { ru_name = fsLit "seq of cast" , ru_fn = seqName , ru_nargs = 4 , ru_try = match_seq_of_cast } -match_seq_of_cast :: [CoreExpr] -> Maybe CoreExpr -- Note [RULES for seq] -match_seq_of_cast [Type _, Type res_ty, Cast scrut co, expr] +match_seq_of_cast :: IdUnfoldingFun -> [CoreExpr] -> Maybe CoreExpr + -- See Note [Built-in RULES for seq] +match_seq_of_cast _ [Type _, Type res_ty, Cast scrut co, expr] = Just (Var seqId `mkApps` [Type (fst (coercionKind co)), Type res_ty, scrut, expr]) -match_seq_of_cast _ = Nothing +match_seq_of_cast _ _ = Nothing ------------------------------------------------ lazyId :: Id -- See Note [lazyId magic] @@ -974,10 +981,10 @@ b) Its fixity is set in LoadIface.ghcPrimIface c) It has quite a bit of desugaring magic. See DsUtils.lhs Note [Desugaring seq (1)] and (2) and (3) -d) There is some special rule handing: Note [RULES for seq] +d) There is some special rule handing: Note [User-defined RULES for seq] -Note [RULES for seq] -~~~~~~~~~~~~~~~~~~~~ +Note [User-defined RULES for seq] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Roman found situations where he had case (f n) of _ -> e where he knew that f (which was strict in n) would terminate if n did. @@ -999,12 +1006,20 @@ To make this work, we need to be careful that the magical desugaring done in Note [seqId magic] item (c) is *not* done on the LHS of a rule. Or rather, we arrange to un-do it, in DsBinds.decomposeRuleLhs. -We also have the following builtin rule: +Note [Built-in RULES for seq] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We also have the following built-in rule for seq seq (x `cast` co) y = seq x y This eliminates unnecessary casts and also allows other seq rules to -match more often. +match more often. Notably, + + seq (f x `cast` co) y --> seq (f x) y + +and now a user-defined rule for seq (see Note [User-defined RULES for seq]) +may fire. + Note [lazyId magic] ~~~~~~~~~~~~~~~~~~~ @@ -1139,7 +1154,7 @@ pc_bottoming_Id :: Name -> Type -> Id pc_bottoming_Id name ty = pcMiscPrelId name ty bottoming_info where - bottoming_info = vanillaIdInfo `setAllStrictnessInfo` Just strict_sig + bottoming_info = vanillaIdInfo `setStrictnessInfo` Just strict_sig `setArityInfo` 1 -- Make arity and strictness agree