X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectType.hs;h=cfcea389bba715344bcbeecdf886ba632981e292;hb=c245355e6f2c7b7c95e9af910c4d420e13af9413;hp=c7046d4ba5cd0d4cf7feb13c9cbd5f9b2dbdeffb;hpb=7c737416e30137e7053b4bcd0fdd563f07fa43b0;p=ghc-hetmet.git diff --git a/compiler/vectorise/VectType.hs b/compiler/vectorise/VectType.hs index c7046d4..cfcea38 100644 --- a/compiler/vectorise/VectType.hs +++ b/compiler/vectorise/VectType.hs @@ -45,6 +45,7 @@ import Util ( singleton ) import Digraph ( SCC(..), stronglyConnComp ) import Outputable +import FastString import Control.Monad ( liftM, liftM2, zipWithM, zipWithM_, mapAndUnzipM ) import Data.List ( inits, tails, zipWith4, zipWith5 ) @@ -278,7 +279,9 @@ voidRepr enumRepr :: VM Repr enumRepr = do - (arr_tycon, _) <- parrayReprTyCon intTy + tycon <- builtin enumerationTyCon + let [data_con] = tyConDataCons tycon + (arr_tycon, _) <- parrayReprTyCon (mkTyConApp tycon []) let [arr_data_con] = tyConDataCons arr_tycon return $ EnumRepr { @@ -287,9 +290,6 @@ enumRepr , enum_arr_tycon = arr_tycon , enum_arr_data_con = arr_data_con } - where - tycon = intTyCon - data_con = intDataCon unboxedProductRepr :: [Type] -> VM Repr unboxedProductRepr [] = voidRepr @@ -359,31 +359,38 @@ arrReprType :: Repr -> VM Type arrReprType = mkPArrayType . reprType arrShapeTys :: Repr -> VM [Type] -arrShapeTys (SumRepr {}) - = do - int_arr <- builtin parrayIntPrimTyCon - return [intPrimTy, mkTyConApp int_arr [], mkTyConApp int_arr []] +arrShapeTys (SumRepr {}) = sumShapeTys arrShapeTys (ProdRepr {}) = return [intPrimTy] arrShapeTys (IdRepr _) = return [] arrShapeTys (VoidRepr {}) = return [intPrimTy] -arrShapeTys (EnumRepr {}) = return [intPrimTy] +arrShapeTys (EnumRepr {}) = sumShapeTys + +sumShapeTys :: VM [Type] +sumShapeTys = do + int_arr <- builtin intPrimArrayTy + return [intPrimTy, int_arr, int_arr] + arrShapeVars :: Repr -> VM [Var] arrShapeVars repr = mapM (newLocalVar FSLIT("sh")) =<< arrShapeTys repr replicateShape :: Repr -> CoreExpr -> CoreExpr -> VM [CoreExpr] -replicateShape (ProdRepr {}) len _ = return [len] -replicateShape (SumRepr {}) len tag +replicateShape (ProdRepr {}) len _ = return [len] +replicateShape (SumRepr {}) len tag = replicateSumShape len tag +replicateShape (IdRepr _) _ _ = return [] +replicateShape (VoidRepr {}) len _ = return [len] +replicateShape (EnumRepr {}) len tag = replicateSumShape len tag + +replicateSumShape :: CoreExpr -> CoreExpr -> VM [CoreExpr] +replicateSumShape len tag = do rep <- builtin replicatePAIntPrimVar up <- builtin upToPAIntPrimVar return [len, Var rep `mkApps` [len, tag], Var up `App` len] -replicateShape (IdRepr _) _ _ = return [] -replicateShape (VoidRepr {}) len _ = return [len] -replicateShape (EnumRepr {}) len _ = return [len] arrSelector :: Repr -> [CoreExpr] -> VM (CoreExpr, CoreExpr, CoreExpr) -arrSelector (SumRepr {}) [len, sel, is] = return (len, sel, is) +arrSelector (SumRepr {}) [len, sel, is] = return (len, sel, is) +arrSelector (EnumRepr {}) [len, sel, is] = return (len, sel, is) emptyArrRepr :: Repr -> VM [CoreExpr] emptyArrRepr (SumRepr { sum_components = prods }) @@ -397,7 +404,7 @@ emptyArrRepr (IdRepr ty) emptyArrRepr (VoidRepr { void_tycon = tycon }) = liftM singleton $ emptyPA (mkTyConApp tycon []) emptyArrRepr (EnumRepr { enum_tycon = tycon }) - = liftM singleton $ emptyPA (mkTyConApp tycon []) + = return [] arrReprTys :: Repr -> VM [Type] arrReprTys (SumRepr { sum_components = reprs }) @@ -411,7 +418,7 @@ arrReprTys (IdRepr ty) arrReprTys (VoidRepr { void_tycon = tycon }) = liftM singleton $ mkPArrayType (mkTyConApp tycon []) arrReprTys (EnumRepr {}) - = liftM singleton $ mkPArrayType intPrimTy + = return [] arrReprTys' :: Repr -> VM [[Type]] arrReprTys' (SumRepr { sum_components = reprs }) @@ -425,7 +432,7 @@ arrReprVars repr mkRepr :: TyCon -> VM Repr mkRepr vect_tc | [tys] <- rep_tys = boxedProductRepr tys - | all null rep_tys = enumRepr + -- | all null rep_tys = enumRepr | otherwise = sumRepr =<< mapM unboxedProductRepr rep_tys where rep_tys = map dataConRepArgTys $ tyConDataCons vect_tc @@ -607,12 +614,13 @@ buildToArrPRepr repr vect_tc prepr_tc arr_tc . mkConApp data_con $ map Type tys ++ map Var (len_var : repr_vars) - to_repr [len_var] - [[repr_var]] + to_repr shape_vars + _ (EnumRepr { enum_arr_tycon = tycon , enum_arr_data_con = data_con }) = return . wrapFamInstBody tycon [] - $ mkConApp data_con [Var len_var, Var repr_var] + . mkConApp data_con + $ map Var shape_vars to_prod repr_vars@(r : _) (ProdRepr { prod_components = tys@(ty : _) @@ -708,15 +716,15 @@ buildFromArrPRepr repr vect_tc prepr_tc arr_tc from_prod (EnumRepr { enum_arr_tycon = tycon , enum_arr_data_con = data_con }) expr - [len_var] - [repr_var] + shape_vars + _ res_ty body = let scrut = unwrapFamInstScrut tycon [] expr scrut_ty = mkTyConApp tycon [] in return $ Case scrut (mkWildId scrut_ty) res_ty - [(DataAlt data_con, [len_var, repr_var], body)] + [(DataAlt data_con, shape_vars, body)] from_prod (IdRepr ty) expr @@ -1015,7 +1023,7 @@ fromVect (FunTy arg_ty res_ty) expr vres_ty <- vectType res_ty apply <- builtin applyClosureVar body <- fromVect res_ty - $ Var apply `mkTyApps` [arg_ty, res_ty] `mkApps` [expr, Var arg] + $ Var apply `mkTyApps` [varg_ty, vres_ty] `mkApps` [expr, varg] return $ Lam arg body fromVect ty expr = identityConv ty >> return expr @@ -1035,6 +1043,7 @@ identityConvTyCon :: TyCon -> VM () identityConvTyCon tc | isBoxedTupleTyCon tc = return () | isUnLiftedTyCon tc = return () - | otherwise = maybeV (lookupTyCon tc) >> return () - + | otherwise = do + tc' <- maybeV (lookupTyCon tc) + if tc == tc' then return () else noV