X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectorise.hs;h=fa771d215a80a05b34a29ef99c9d0c5cdd909017;hb=f83010b119096699d1efef2f7bb45460719c48f9;hp=c974c2026a6d07fe4b8cf0cf6bd82a9612d2b000;hpb=8adf1ec28fe3a1549e39401e705d013f29da6ef6;p=ghc-hetmet.git diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs index c974c20..fa771d2 100644 --- a/compiler/vectorise/Vectorise.hs +++ b/compiler/vectorise/Vectorise.hs @@ -5,6 +5,7 @@ where import VectMonad import VectUtils +import VectType import DynFlags import HscTypes @@ -18,7 +19,8 @@ import Rules ( RuleBase ) import DataCon import TyCon import Type -import TypeRep +import FamInstEnv ( extendFamInstEnvList ) +import InstEnv ( extendInstEnvList ) import Var import VarEnv import VarSet @@ -38,8 +40,7 @@ import BasicTypes ( Boxity(..) ) import Outputable import FastString -import Control.Monad ( liftM, liftM2, mapAndUnzipM, zipWithM_ ) -import Data.Maybe ( maybeToList ) +import Control.Monad ( liftM, liftM2, mapAndUnzipM ) vectorise :: HscEnv -> UniqSupply -> RuleBase -> ModGuts -> IO (SimplCount, ModGuts) @@ -57,8 +58,22 @@ vectorise hsc_env _ _ guts vectModule :: ModGuts -> VM ModGuts vectModule guts = do + (types', fam_insts, pa_insts) <- vectTypeEnv (mg_types guts) + + let insts = map painstInstance pa_insts + fam_inst_env' = extendFamInstEnvList (mg_fam_inst_env guts) fam_insts + inst_env' = extendInstEnvList (mg_inst_env guts) insts + updGEnv (setInstEnvs inst_env' fam_inst_env') + + dicts <- mapM buildPADict pa_insts binds' <- mapM vectTopBind (mg_binds guts) - return $ guts { mg_binds = binds' } + return $ guts { mg_types = types' + , mg_binds = Rec (concat dicts) : binds' + , mg_inst_env = inst_env' + , mg_fam_inst_env = fam_inst_env' + , mg_insts = mg_insts guts ++ insts + , mg_fam_insts = mg_fam_insts guts ++ fam_insts + } vectTopBind :: CoreBind -> VM CoreBind vectTopBind b@(NonRec var expr) @@ -128,15 +143,6 @@ vectBndrsIn vs p -- ---------------------------------------------------------------------------- -- Expressions -replicateP :: CoreExpr -> CoreExpr -> VM CoreExpr -replicateP expr len - = do - dict <- paDictOfType ty - rep <- builtin replicatePAVar - return $ mkApps (Var rep) [Type ty, dict, expr, len] - where - ty = exprType expr - capply :: (CoreExpr, CoreExpr) -> (CoreExpr, CoreExpr) -> VM (CoreExpr, CoreExpr) capply (vfn, lfn) (varg, larg) = do @@ -155,7 +161,7 @@ vectVar lc v case r of Local es -> return es Global vexpr -> do - lexpr <- replicateP vexpr lc + lexpr <- replicatePA vexpr lc return (vexpr, lexpr) vectPolyVar :: CoreExpr -> Var -> [Type] -> VM (CoreExpr, CoreExpr) @@ -166,32 +172,11 @@ vectPolyVar lc v tys Local (vexpr, lexpr) -> liftM2 (,) (mk_app vexpr) (mk_app lexpr) Global poly -> do vexpr <- mk_app poly - lexpr <- replicateP vexpr lc + lexpr <- replicatePA vexpr lc return (vexpr, lexpr) where mk_app e = applyToTypes e =<< mapM vectType tys -abstractOverTyVars :: [TyVar] -> ((CoreExpr -> CoreExpr) -> VM a) -> VM a -abstractOverTyVars tvs p - = do - mdicts <- mapM mk_dict_var tvs - zipWithM_ (\tv -> maybe (defLocalTyVar tv) (defLocalTyVarWithPA tv . Var)) tvs mdicts - p (mk_lams mdicts) - where - mk_dict_var tv = do - r <- paDictArgType tv - case r of - Just ty -> liftM Just (newLocalVar FSLIT("dPA") ty) - Nothing -> return Nothing - - mk_lams mdicts = mkLams (tvs ++ [dict | Just dict <- mdicts]) - -applyToTypes :: CoreExpr -> [Type] -> VM CoreExpr -applyToTypes expr tys - = do - dicts <- mapM paDictOfType tys - return $ expr `mkTyApps` tys `mkApps` dicts - vectPolyExpr :: CoreExpr -> CoreExprWithFVs -> VM (CoreExpr, CoreExpr) vectPolyExpr lc expr = localV @@ -214,7 +199,7 @@ vectExpr lc (_, AnnVar v) = vectVar lc v vectExpr lc (_, AnnLit lit) = do let vexpr = Lit lit - lexpr <- replicateP vexpr lc + lexpr <- replicatePA vexpr lc return (vexpr, lexpr) vectExpr lc (_, AnnNote note expr) @@ -279,8 +264,8 @@ vectExpr lc (fvs, AnnLam bndr body) res_ty <- vectType (exprType $ deAnnotate body) -- FIXME: move the functions to the top level - mono_vfn <- applyToTypes (Var vfn_var) (map TyVarTy tyvars) - mono_lfn <- applyToTypes (Var lfn_var) (map TyVarTy tyvars) + mono_vfn <- applyToTypes (Var vfn_var) (mkTyVarTys tyvars) + mono_lfn <- applyToTypes (Var lfn_var) (mkTyVarTys tyvars) mk_clo <- builtin mkClosureVar mk_cloP <- builtin mkClosurePVar @@ -397,9 +382,9 @@ mkClosureMonoFns info arg body bind_lenv lenv lbody lc_bndr [lbndr] = do - lengthPA <- builtin lengthPAVar + len <- lengthPA (Var lbndr) return . Let (NonRec lbndr lenv) - $ Case (mkApps (Var lengthPA) [Type vty, (Var lbndr)]) + $ Case len lc_bndr (exprType lbody) [(DEFAULT, [], lbody)] @@ -421,36 +406,3 @@ vectTyAppExpr :: CoreExpr -> CoreExprWithFVs -> [Type] -> VM (CoreExpr, CoreExpr vectTyAppExpr lc (_, AnnVar v) tys = vectPolyVar lc v tys vectTyAppExpr lc e tys = pprPanic "vectTyAppExpr" (ppr $ deAnnotate e) --- ---------------------------------------------------------------------------- --- Types - -vectTyCon :: TyCon -> VM TyCon -vectTyCon tc - | isFunTyCon tc = builtin closureTyCon - | isBoxedTupleTyCon tc = return tc - | isUnLiftedTyCon tc = return tc - | otherwise = do - r <- lookupTyCon tc - case r of - Just tc' -> return tc' - - -- FIXME: just for now - Nothing -> pprTrace "ccTyCon:" (ppr tc) $ return tc - -vectType :: Type -> VM Type -vectType ty | Just ty' <- coreView ty = vectType ty' -vectType (TyVarTy tv) = return $ TyVarTy tv -vectType (AppTy ty1 ty2) = liftM2 AppTy (vectType ty1) (vectType ty2) -vectType (TyConApp tc tys) = liftM2 TyConApp (vectTyCon tc) (mapM vectType tys) -vectType (FunTy ty1 ty2) = liftM2 TyConApp (builtin closureTyCon) - (mapM vectType [ty1,ty2]) -vectType ty@(ForAllTy _ _) - = do - mdicts <- mapM paDictArgType tyvars - mono_ty' <- vectType mono_ty - return $ tyvars `mkForAllTys` ([dict | Just dict <- mdicts] `mkFunTys` mono_ty') - where - (tyvars, mono_ty) = splitForAllTys ty - -vectType ty = pprPanic "vectType:" (ppr ty) -