X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectType.hs;h=6f6fca8dbadc1737c4d5910a2f3e803978d2f68d;hb=724425265ded8958a719b3a62f43006674b506c8;hp=aa0eae2f1035a7a3de25555af6be180b76a30ab7;hpb=3b962ce87e2dbf6bdc1f3d1e083a74e5a9467665;p=ghc-hetmet.git diff --git a/compiler/vectorise/VectType.hs b/compiler/vectorise/VectType.hs index aa0eae2..6f6fca8 100644 --- a/compiler/vectorise/VectType.hs +++ b/compiler/vectorise/VectType.hs @@ -26,7 +26,7 @@ import Var ( Var ) import Id ( mkWildId ) import Name ( Name, getOccName ) import NameEnv -import TysWiredIn ( unitTy, intTy, intDataCon ) +import TysWiredIn ( unitTy, intTy, intDataCon, unitDataConId ) import TysPrim ( intPrimTy ) import Unique @@ -209,28 +209,48 @@ buildPReprTyCon orig_tc vect_tc tyvars = tyConTyVars vect_tc buildPReprType :: TyCon -> VM Type -buildPReprType = mkPRepr . map dataConRepArgTys . tyConDataCons - -buildToPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr -buildToPRepr _ vect_tc prepr_tc _ +buildPReprType = liftM repr_type . mkTyConRepr + +buildToPRepr :: TyConRepr -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildToPRepr (TyConRepr { + repr_tys = repr_tys + , repr_prod_tycons = prod_tycons + , repr_prod_tys = prod_tys + , repr_sum_tycon = repr_sum_tycon + , repr_type = repr_type + }) + 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 + arg <- newLocalVar FSLIT("x") arg_ty + vars <- mapM (mapM (newLocalVar FSLIT("x"))) repr_tys return . Lam arg . wrapFamInstBody prepr_tc var_tys - . Case (Var arg) (mkWildId arg_ty) res_ty - $ zipWith3 mk_alt data_cons bndrss alt_bodies + . Case (Var arg) (mkWildId arg_ty) repr_type + . mk_alts data_cons vars + . zipWith3 mk_prod prod_tycons repr_tys $ map (map Var) vars 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) + Just sum_tycon = repr_sum_tycon + sum_datacons = tyConDataCons sum_tycon + + mk_alts _ _ [] = [(DEFAULT, [], Var unitDataConId)] + mk_alts [dc] [vars] [expr] = [(DataAlt dc, vars, expr)] + mk_alts dcs vars exprs = zipWith4 mk_alt dcs vars sum_datacons exprs -buildToArrPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr + mk_alt dc vars sum_dc expr = (DataAlt dc, vars, + mkConApp sum_dc (map Type prod_tys ++ [expr])) + + mk_prod _ _ [] = Var unitDataConId + mk_prod _ _ [expr] = expr + mk_prod (Just tc) tys exprs = mkConApp dc (map Type tys ++ exprs) + where + [dc] = tyConDataCons tc + +buildToArrPRepr :: TyConRepr -> TyCon -> TyCon -> TyCon -> VM CoreExpr buildToArrPRepr _ vect_tc prepr_tc arr_tc = do arg_ty <- mkPArrayType el_ty @@ -267,7 +287,7 @@ buildToArrPRepr _ vect_tc prepr_tc arr_tc | otherwise = True -buildFromPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildFromPRepr :: TyConRepr -> TyCon -> TyCon -> TyCon -> VM CoreExpr buildFromPRepr _ vect_tc prepr_tc _ = do arg_ty <- mkPReprType res_ty @@ -285,11 +305,11 @@ buildFromPRepr _ vect_tc prepr_tc _ bndrs <- mapM (newLocalVar FSLIT("x")) $ dataConRepArgTys dc return (bndrs, mkConApp dc (map Type var_tys ++ map Var bndrs)) -buildFromArrPRepr :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildFromArrPRepr :: TyConRepr -> TyCon -> TyCon -> TyCon -> VM CoreExpr buildFromArrPRepr _ vect_tc prepr_tc arr_tc = mkFromArrPRepr undefined undefined undefined undefined undefined undefined -buildPRDict :: Shape -> TyCon -> TyCon -> TyCon -> VM CoreExpr +buildPRDict :: TyConRepr -> TyCon -> TyCon -> TyCon -> VM CoreExpr buildPRDict _ vect_tc prepr_tc _ = prCoerce prepr_tc var_tys =<< prDictOfType (mkTyConApp prepr_tc var_tys) @@ -382,12 +402,13 @@ buildTyConBindings :: TyCon -> TyCon -> TyCon -> TyCon -> Var buildTyConBindings orig_tc vect_tc prepr_tc arr_tc dfun = do shape <- tyConShape vect_tc + repr <- mkTyConRepr vect_tc sequence_ (zipWith4 (vectDataConWorker shape vect_tc arr_tc arr_dc) orig_dcs vect_dcs (inits repr_tys) (tails repr_tys)) - dict <- buildPADict shape vect_tc prepr_tc arr_tc dfun + dict <- buildPADict repr vect_tc prepr_tc arr_tc dfun binds <- takeHoisted return $ (dfun, dict) : binds where @@ -439,11 +460,11 @@ 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 -> TyCon -> Var -> VM CoreExpr -buildPADict shape vect_tc prepr_tc arr_tc dfun +buildPADict :: TyConRepr -> TyCon -> TyCon -> TyCon -> Var -> VM CoreExpr +buildPADict repr vect_tc prepr_tc arr_tc dfun = polyAbstract tvs $ \abstract -> do - meth_binds <- mapM (mk_method shape) paMethods + meth_binds <- mapM (mk_method repr) paMethods let meth_exprs = map (Var . fst) meth_binds pa_dc <- builtin paDataCon @@ -454,10 +475,10 @@ buildPADict shape vect_tc prepr_tc arr_tc dfun tvs = tyConTyVars arr_tc arg_tys = mkTyVarTys tvs - mk_method shape (name, build) + mk_method repr (name, build) = localV $ do - body <- build shape vect_tc prepr_tc arr_tc + body <- build repr vect_tc prepr_tc arr_tc var <- newLocalVar name (exprType body) return (var, mkInlineMe body) @@ -467,98 +488,6 @@ paMethods = [(FSLIT("toPRepr"), buildToPRepr), (FSLIT("fromArrPRepr"), buildFromArrPRepr), (FSLIT("dictPRepr"), buildPRDict)] -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 - shapes <- mapM (newLocalVar FSLIT("sh")) shape_tys - wilds <- mapM newDummyVar repr_tys - let scrut = unwrapFamInstScrut arr_tc arg_tys (Var arg) - scrut_ty = exprType scrut - - body <- shapeLength shape (map Var shapes) - - return . Lam arg - $ Case scrut (mkWildId scrut_ty) intPrimTy - [(DataAlt repr_dc, shapes ++ wilds, body)] - where - arg_tys = mkTyVarTys $ tyConTyVars arr_tc - [repr_dc] = tyConDataCons arr_tc - - shape_tys = shapeReprTys shape - repr_tys = drop (length shape_tys) (dataConRepArgTys repr_dc) - --- data T = C0 t1 ... tm --- ... --- Ck u1 ... un --- --- data [:T:] = A ![:Int:] [:t1:] ... [:un:] --- --- replicatePA :: Int# -> T -> [:T:] --- replicatePA n# t --- = let c = case t of --- C0 _ ... _ -> 0 --- ... --- Ck _ ... _ -> k --- --- xs1 = case t of --- C0 x1 _ ... _ -> replicatePA @t1 n# x1 --- _ -> emptyPA @t1 --- --- ... --- --- ysn = case t of --- Ck _ ... _ yn -> replicatePA @un n# yn --- _ -> emptyPA @un --- in --- A (replicatePA @Int n# c) xs1 ... ysn --- --- - -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 - - let len = Var len_var - val = Var val_var - - shape_reprs <- shapeReplicate shape len (ctr_num val) - reprs <- liftM concat $ mapM (mk_comp_arrs len val) vect_dcs - - return . mkLams [len_var, val_var] - . wrapFamInstBody arr_tc arg_tys - $ mkConApp arr_dc (map Type arg_tys ++ shape_reprs ++ reprs) - where - arg_tys = mkTyVarTys (tyConTyVars arr_tc) - val_ty = mkTyConApp vect_tc arg_tys - wild = mkWildId val_ty - vect_dcs = tyConDataCons vect_tc - [arr_dc] = tyConDataCons arr_tc - - ctr_num val = Case val wild intTy (zipWith ctr_num_alt vect_dcs [0..]) - ctr_num_alt dc i = (DataAlt dc, map mkWildId (dataConRepArgTys dc), - mkConApp intDataCon [mkIntLitInt i]) - - - mk_comp_arrs len val dc = let tys = dataConRepArgTys dc - wilds = map mkWildId tys - in - sequence (zipWith3 (mk_comp_arr len val dc) - tys (inits wilds) (tails wilds)) - - mk_comp_arr len val dc ty pre (_:post) - = do - var <- newLocalVar FSLIT("x") ty - rep <- replicatePA len (Var var) - empty <- emptyPA ty - arr_ty <- mkPArrayType ty - - return $ Case val wild arr_ty - [(DEFAULT, [], empty), (DataAlt dc, pre ++ (var : post), rep)] - -- | Split the given tycons into two sets depending on whether they have to be -- converted (first list) or not (second list). The first argument contains -- information about the conversion status of external tycons: