X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fvectorise%2FVectType.hs;h=c77343b7e5b6ebc0b073ad84d3fb03b54edffdef;hp=e8afb46621c9bf4fe035a43fc4bd773cc782240d;hb=9396c0736a7e7d73c2a13f1a18104e0c43b924b0;hpb=7331582b8f67e005cbb839248eff492127f9bcbe diff --git a/compiler/vectorise/VectType.hs b/compiler/vectorise/VectType.hs index e8afb46..c77343b 100644 --- a/compiler/vectorise/VectType.hs +++ b/compiler/vectorise/VectType.hs @@ -37,7 +37,7 @@ import Digraph ( SCC(..), stronglyConnComp ) import Outputable import Control.Monad ( liftM, liftM2, zipWithM, zipWithM_ ) -import Data.List ( inits, tails, zipWith4 ) +import Data.List ( inits, tails, zipWith4, zipWith5 ) -- ---------------------------------------------------------------------------- -- Types @@ -101,8 +101,12 @@ vectTypeEnv env parr_tcs <- zipWithM buildPArrayTyCon orig_tcs vect_tcs dfuns <- mapM mkPADFun vect_tcs defTyConPAs (zip vect_tcs dfuns) - binds <- sequence (zipWith4 buildTyConBindings orig_tcs vect_tcs parr_tcs dfuns) - + binds <- sequence (zipWith5 buildTyConBindings orig_tcs + vect_tcs + repr_tcs + parr_tcs + dfuns) + let all_new_tcs = new_tcs ++ repr_tcs ++ parr_tcs let new_env = extendTypeEnvList env @@ -195,7 +199,7 @@ buildPReprTyCon :: TyCon -> TyCon -> VM TyCon buildPReprTyCon orig_tc vect_tc = do name <- cloneName mkPReprTyConOcc (tyConName orig_tc) - rhs_ty <- buildPReprRhsTy vect_tc + rhs_ty <- buildPReprType vect_tc prepr_tc <- builtin preprTyCon liftDs $ buildSynTyCon name tyvars @@ -204,27 +208,45 @@ buildPReprTyCon orig_tc vect_tc where tyvars = tyConTyVars vect_tc -buildPReprRhsTy :: TyCon -> VM Type -buildPReprRhsTy = buildPReprTy . map dataConRepArgTys . tyConDataCons +buildPReprType :: TyCon -> VM Type +buildPReprType = mkPRepr . map dataConRepArgTys . tyConDataCons + +buildToPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildToPRepr _ vect_tc prepr_tc _ + = do + arg <- newLocalVar FSLIT("x") arg_ty + bndrss <- mapM (mapM (newLocalVar FSLIT("x"))) rep_tys + (alt_bodies, res_ty) <- mkToPRepr $ map (map Var) bndrss + + return . Lam arg + . wrapFamInstBody prepr_tc var_tys + . Case (Var arg) (mkWildId arg_ty) res_ty + $ zipWith3 mk_alt data_cons bndrss alt_bodies + where + var_tys = mkTyVarTys $ tyConTyVars vect_tc + arg_ty = mkTyConApp vect_tc var_tys + data_cons = tyConDataCons vect_tc + rep_tys = map dataConRepArgTys data_cons + + mk_alt data_con bndrs body = (DataAlt data_con, bndrs, body) -buildPReprTy :: [[Type]] -> VM Type -buildPReprTy [] = panic "mkPRepr" -buildPReprTy tys +buildFromPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildFromPRepr _ vect_tc prepr_tc _ = do - embed <- builtin embedTyCon - plus <- builtin plusTyCon - cross <- builtin crossTyCon - - return . foldr1 (mk_bin plus) - . map (mkprod cross) - . map (map (mk_un embed)) - $ tys + arg_ty <- mkPReprType res_ty + arg <- newLocalVar FSLIT("x") arg_ty + alts <- mapM mk_alt data_cons + body <- mkFromPRepr (unwrapFamInstScrut prepr_tc var_tys (Var arg)) + res_ty alts + return $ Lam arg body where - mkprod cross [] = unitTy - mkprod cross tys = foldr1 (mk_bin cross) tys + var_tys = mkTyVarTys $ tyConTyVars vect_tc + res_ty = mkTyConApp vect_tc var_tys + data_cons = tyConDataCons vect_tc - mk_un tc ty = mkTyConApp tc [ty] - mk_bin tc ty1 ty2 = mkTyConApp tc [ty1,ty2] + mk_alt dc = do + bndrs <- mapM (newLocalVar FSLIT("x")) $ dataConRepArgTys dc + return (bndrs, mkConApp dc (map Type var_tys ++ map Var bndrs)) buildPArrayTyCon :: TyCon -> TyCon -> VM TyCon buildPArrayTyCon orig_tc vect_tc = fixV $ \repr_tc -> @@ -307,8 +329,9 @@ tyConShape vect_tc return [e] } -buildTyConBindings :: TyCon -> TyCon -> TyCon -> Var -> VM [(Var, CoreExpr)] -buildTyConBindings orig_tc vect_tc arr_tc dfun +buildTyConBindings :: TyCon -> TyCon -> TyCon -> TyCon -> Var + -> VM [(Var, CoreExpr)] +buildTyConBindings orig_tc vect_tc prepr_tc arr_tc dfun = do shape <- tyConShape vect_tc sequence_ (zipWith4 (vectDataConWorker shape vect_tc arr_tc arr_dc) @@ -316,7 +339,7 @@ buildTyConBindings orig_tc vect_tc arr_tc dfun vect_dcs (inits repr_tys) (tails repr_tys)) - dict <- buildPADict shape vect_tc arr_tc dfun + dict <- buildPADict shape vect_tc prepr_tc arr_tc dfun binds <- takeHoisted return $ (dfun, dict) : binds where @@ -368,8 +391,8 @@ vectDataConWorker shape vect_tc arr_tc arr_dc orig_dc vect_dc pre (dc_tys : post ++ map Var args ++ empty_post -buildPADict :: Shape -> TyCon -> TyCon -> Var -> VM CoreExpr -buildPADict shape vect_tc arr_tc dfun +buildPADict :: Shape -> TyCon -> TyCon -> TyCon -> Var -> VM CoreExpr +buildPADict shape vect_tc prepr_tc arr_tc dfun = polyAbstract tvs $ \abstract -> do meth_binds <- mapM (mk_method shape) paMethods @@ -386,15 +409,17 @@ buildPADict shape vect_tc arr_tc dfun mk_method shape (name, build) = localV $ do - body <- build shape vect_tc arr_tc + body <- build shape vect_tc prepr_tc arr_tc var <- newLocalVar name (exprType body) return (var, mkInlineMe body) paMethods = [(FSLIT("lengthPA"), buildLengthPA), - (FSLIT("replicatePA"), buildReplicatePA)] + (FSLIT("replicatePA"), buildReplicatePA), + (FSLIT("toPRepr"), buildToPRepr), + (FSLIT("fromPRepr"), buildFromPRepr)] -buildLengthPA :: Shape -> TyCon -> TyCon -> VM CoreExpr -buildLengthPA shape vect_tc arr_tc +buildLengthPA :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildLengthPA shape vect_tc _ arr_tc = do parr_ty <- mkPArrayType (mkTyConApp vect_tc arg_tys) arg <- newLocalVar FSLIT("xs") parr_ty @@ -442,8 +467,8 @@ buildLengthPA shape vect_tc arr_tc -- -- -buildReplicatePA :: Shape -> TyCon -> TyCon -> VM CoreExpr -buildReplicatePA shape vect_tc arr_tc +buildReplicatePA :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildReplicatePA shape vect_tc _ arr_tc = do len_var <- newLocalVar FSLIT("n") intPrimTy val_var <- newLocalVar FSLIT("x") val_ty