X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectorise.hs;h=03fa131ca93d134689a2d734e177460d48de32d9;hb=f363bf9a76bcaddc1bfea61135f4f4d2fbcfd955;hp=bb5aa0dc91a438732e5f8aa0558d192c3555340f;hpb=e12e8c14196fc87d15b382ef4c0201418f83b815;p=ghc-hetmet.git diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs index bb5aa0d..03fa131 100644 --- a/compiler/vectorise/Vectorise.hs +++ b/compiler/vectorise/Vectorise.hs @@ -46,11 +46,23 @@ import Outputable import FastString import Control.Monad ( liftM, liftM2, zipWithM, mapAndUnzipM ) -mkNDPVar :: FastString -> RdrName -mkNDPVar fs = mkRdrQual nDP_BUILTIN (mkVarOccFS fs) +mkNDPVar :: String -> RdrName +mkNDPVar s = mkRdrQual nDP_BUILTIN (mkVarOcc s) + +mkNDPVarFS :: FastString -> RdrName +mkNDPVarFS fs = mkRdrQual nDP_BUILTIN (mkVarOccFS fs) builtin_PAs :: [(Name, RdrName)] -builtin_PAs = [(intTyConName, mkNDPVar FSLIT("dPA_Int"))] +builtin_PAs = [ + mk closureTyConName FSLIT("dPA_Clo") + , mk intTyConName FSLIT("dPA_Int") + ] + ++ tups + where + mk name fs = (name, mkNDPVarFS fs) + + tups = mk_tup 0 : map mk_tup [2..3] + mk_tup n = (getName $ tupleTyCon Boxed n, mkNDPVar $ "dPA_" ++ show n) vectorise :: HscEnv -> UniqSupply -> RuleBase -> ModGuts -> IO (SimplCount, ModGuts) @@ -69,21 +81,17 @@ vectModule :: ModGuts -> VM ModGuts vectModule guts = do defTyConRdrPAs builtin_PAs - (types', fam_insts, pa_insts) <- vectTypeEnv (mg_types guts) + (types', fam_insts, tc_binds) <- 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') + let fam_inst_env' = extendFamInstEnvList (mg_fam_inst_env guts) fam_insts + updGEnv (setFamInstEnv fam_inst_env') - dicts <- mapM buildPADict pa_insts - workers <- mapM vectDataConWorkers pa_insts + -- dicts <- mapM buildPADict pa_insts + -- workers <- mapM vectDataConWorkers pa_insts binds' <- mapM vectTopBind (mg_binds guts) return $ guts { mg_types = types' - , mg_binds = Rec (concat workers ++ concat dicts) : binds' - , mg_inst_env = inst_env' + , mg_binds = Rec tc_binds : binds' , mg_fam_inst_env = fam_inst_env' - , mg_insts = mg_insts guts ++ insts , mg_fam_insts = mg_fam_insts guts ++ fam_insts } @@ -146,6 +154,14 @@ vectBndrIn v p x <- p return (vv, x) +vectBndrIn' :: Var -> (VVar -> VM a) -> VM (VVar, a) +vectBndrIn' v p + = localV + $ do + vv <- vectBndr v + x <- p vv + return (vv, x) + vectBndrsIn :: [Var] -> VM a -> VM ([VVar], a) vectBndrsIn vs p = localV @@ -219,6 +235,12 @@ vectExpr (_, AnnApp fn arg) arg' <- vectExpr arg mkClosureApp fn' arg' +vectExpr (_, AnnCase scrut bndr ty alts) + | isAlgType scrut_ty + = vectAlgCase scrut bndr ty alts + where + scrut_ty = exprType (deAnnotate scrut) + vectExpr (_, AnnCase expr bndr ty alts) = panic "vectExpr: case" @@ -271,3 +293,44 @@ vectTyAppExpr :: CoreExprWithFVs -> [Type] -> VM VExpr vectTyAppExpr (_, AnnVar v) tys = vectPolyVar v tys vectTyAppExpr e tys = pprPanic "vectTyAppExpr" (ppr $ deAnnotate e) +type CoreAltWithFVs = AnnAlt Id VarSet + +-- We convert +-- +-- case e :: t of v { ... } +-- +-- to +-- +-- V: let v = e in case v of _ { ... } +-- L: let v = e in case v `cast` ... of _ { ... } +-- +-- When lifting, we have to do it this way because v must have the type +-- [:V(T):] but the scrutinee must be cast to the representation type. +-- + +-- FIXME: this is too lazy +vectAlgCase scrut bndr ty [(DEFAULT, [], body)] + = do + vscrut <- vectExpr scrut + vty <- vectType ty + lty <- mkPArrayType vty + (vbndr, vbody) <- vectBndrIn bndr (vectExpr body) + return $ vCaseDEFAULT vscrut vbndr vty lty vbody + +vectAlgCase scrut bndr ty [(DataAlt dc, bndrs, body)] + = do + vty <- vectType ty + lty <- mkPArrayType vty + vexpr <- vectExpr scrut + (vbndr, (vbndrs, vbody)) <- vectBndrIn bndr + . vectBndrsIn bndrs + $ vectExpr body + + (vscrut, arr_tc, arg_tys) <- mkVScrut (vVar vbndr) + vect_dc <- maybeV (lookupDataCon dc) + let [arr_dc] = tyConDataCons arr_tc + let shape_tys = take (dataConRepArity arr_dc - length bndrs) + (dataConRepArgTys arr_dc) + shape_bndrs <- mapM (newLocalVar FSLIT("s")) shape_tys + return . vLet (vNonRec vbndr vexpr) + $ vCaseProd vscrut vty lty vect_dc arr_dc shape_bndrs vbndrs vbody