X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectType.hs;h=896139fdd5ac0b5609316e51c0a4cf6a8826c306;hb=fe5405d4b97a521e32899f6dc2153c556723ca62;hp=9d9db538974f66f4011097673e7f59e257520e07;hpb=063aba74bac532a9747e99da2c2d9c066ac76429;p=ghc-hetmet.git diff --git a/compiler/vectorise/VectType.hs b/compiler/vectorise/VectType.hs index 9d9db53..896139f 100644 --- a/compiler/vectorise/VectType.hs +++ b/compiler/vectorise/VectType.hs @@ -1,11 +1,13 @@ module VectType ( vectTyCon, vectType, vectTypeEnv, - PAInstance, painstInstance, buildPADict ) + PAInstance, buildPADict, + vectDataConWorkers ) where #include "HsVersions.h" import VectMonad import VectUtils +import VectCore import HscTypes ( TypeEnv, extendTypeEnvList, typeEnvTyCons ) import CoreSyn @@ -76,12 +78,13 @@ vectType ty = pprPanic "vectType:" (ppr ty) type TyConGroup = ([TyCon], UniqSet TyCon) data PAInstance = PAInstance { - painstInstance :: Instance + painstDFun :: Var + , painstOrigTyCon :: TyCon , painstVectTyCon :: TyCon , painstArrTyCon :: TyCon } -vectTypeEnv :: TypeEnv -> VM (TypeEnv, [FamInst], [PAInstance]) +vectTypeEnv :: TypeEnv -> VM (TypeEnv, [FamInst]) vectTypeEnv env = do cs <- readGEnv $ mk_map . global_tycons @@ -95,7 +98,7 @@ vectTypeEnv env vect_tcs = keep_tcs ++ new_tcs parr_tcs <- zipWithM buildPArrayTyCon orig_tcs vect_tcs - pa_insts <- zipWithM buildPAInstance vect_tcs parr_tcs + pa_insts <- sequence $ zipWith3 buildPAInstance orig_tcs vect_tcs parr_tcs let all_new_tcs = new_tcs ++ parr_tcs @@ -104,7 +107,7 @@ vectTypeEnv env ++ [ADataCon dc | tc <- all_new_tcs , dc <- tyConDataCons tc]) - return (new_env, map mkLocalFamInst parr_tcs, pa_insts) + return (new_env, map mkLocalFamInst parr_tcs) where tycons = typeEnvTyCons env groups = tyConGroups tycons @@ -191,6 +194,95 @@ vectDataCon dc rep_arg_tys = dataConRepArgTys dc tycon = dataConTyCon dc +vectDataConWorkers :: PAInstance -> VM [(Var, CoreExpr)] +vectDataConWorkers (PAInstance { painstOrigTyCon = orig_tc + , painstVectTyCon = vect_tc + , painstArrTyCon = arr_tc + }) + = do + shape <- tyConShape vect_tc + sequence_ (zipWith3 (vectDataConWorker shape vect_tc arr_tc arr_dc) + num_dcs + (inits repr_tys) + (tails repr_tys)) + takeHoisted + where + orig_dcs = tyConDataCons orig_tc + vect_dcs = tyConDataCons vect_tc + [arr_dc] = tyConDataCons arr_tc + + num_dcs = zip3 orig_dcs vect_dcs [0..] + repr_tys = map dataConRepArgTys vect_dcs + +vectDataConWorker :: Shape -> TyCon -> TyCon -> DataCon + -> (DataCon, DataCon, Int) -> [[Type]] -> [[Type]] + -> VM () +vectDataConWorker shape vect_tc arr_tc arr_dc (orig_dc, vect_dc, dc_num) pre (dc_tys : post) + = do + clo <- closedV + . inBind orig_worker + . polyAbstract tvs $ \abstract -> + liftM (abstract . vectorised) + $ buildClosures tvs [] dc_tys res_ty (liftM2 (,) mk_vect mk_lift) + + worker <- cloneId mkVectOcc orig_worker (exprType clo) + hoistBinding worker clo + defGlobalVar orig_worker worker + return () + where + tvs = tyConTyVars vect_tc + arg_tys = mkTyVarTys tvs + res_ty = mkTyConApp vect_tc arg_tys + + orig_worker = dataConWorkId orig_dc + + mk_vect = return . mkConApp vect_dc $ map Type arg_tys + mk_lift = do + len <- newLocalVar FSLIT("n") intPrimTy + arr_tys <- mapM mkPArrayType dc_tys + args <- mapM (newLocalVar FSLIT("xs")) arr_tys + shapes <- shapeReplicate shape (Var len) (mkIntLitInt dc_num) + + empty_pre <- mapM emptyPA (concat pre) + empty_post <- mapM emptyPA (concat post) + + return . mkLams (len : args) + . wrapFamInstBody arr_tc arg_tys + . mkConApp arr_dc + $ map Type arg_tys ++ shapes + ++ empty_pre + ++ map Var args + ++ empty_post + +data Shape = Shape { + shapeReprTys :: [Type] + , shapeStrictness :: [StrictnessMark] + , shapeLength :: [CoreExpr] -> VM CoreExpr + , shapeReplicate :: CoreExpr -> CoreExpr -> VM [CoreExpr] + } + +tyConShape :: TyCon -> VM Shape +tyConShape vect_tc + | isProductTyCon vect_tc + = return $ Shape { + shapeReprTys = [intPrimTy] + , shapeStrictness = [NotMarkedStrict] + , shapeLength = \[len] -> return len + , shapeReplicate = \len _ -> return [len] + } + + | otherwise + = do + repr_ty <- mkPArrayType intTy -- FIXME: we want to unbox this + return $ Shape { + shapeReprTys = [repr_ty] + , shapeStrictness = [MarkedStrict] + , shapeLength = \[sel] -> lengthPA sel + , shapeReplicate = \len n -> do + e <- replicatePA len n + return [e] + } + buildPArrayTyCon :: TyCon -> TyCon -> VM TyCon buildPArrayTyCon orig_tc vect_tc = fixV $ \repr_tc -> do @@ -243,7 +335,7 @@ buildPArrayDataCon :: Name -> TyCon -> TyCon -> VM DataCon buildPArrayDataCon orig_name vect_tc repr_tc = do dc_name <- cloneName mkPArrayDataConOcc orig_name - shape_ty <- mkPArrayType intTy -- FIXME: we want to unbox this! + shape <- tyConShape vect_tc repr_tys <- mapM mkPArrayType types wrk_name <- cloneName mkDataConWorkerOcc dc_name wrp_name <- cloneName mkDataConWrapperOcc dc_name @@ -251,13 +343,13 @@ buildPArrayDataCon orig_name vect_tc repr_tc let ids = mkDataConIds wrp_name wrk_name data_con data_con = mkDataCon dc_name False - (MarkedStrict : map (const NotMarkedStrict) repr_tys) + (shapeStrictness shape ++ map (const NotMarkedStrict) repr_tys) [] (tyConTyVars vect_tc) [] [] [] - (shape_ty : repr_tys) + (shapeReprTys shape ++ repr_tys) repr_tc [] ids @@ -267,70 +359,69 @@ buildPArrayDataCon orig_name vect_tc repr_tc types = [ty | dc <- tyConDataCons vect_tc , ty <- dataConRepArgTys dc] -buildPAInstance :: TyCon -> TyCon -> VM PAInstance -buildPAInstance vect_tc arr_tc +buildPAInstance :: TyCon -> TyCon -> TyCon -> VM PAInstance +buildPAInstance orig_tc vect_tc arr_tc = do - pa <- builtin paClass - let inst_ty = mkForAllTys tvs - . (mkFunTys $ mkPredTys [ClassP pa [ty] | ty <- arg_tys]) - $ mkPredTy (ClassP pa [mkTyConApp vect_tc arg_tys]) - - dfun <- newExportedVar (mkPADFunOcc $ getOccName vect_tc) inst_ty + dfun_ty <- paDFunType vect_tc + dfun <- newExportedVar (mkPADFunOcc $ getOccName vect_tc) dfun_ty return $ PAInstance { - painstInstance = mkLocalInstance dfun NoOverlap + painstDFun = dfun + , painstOrigTyCon = orig_tc , painstVectTyCon = vect_tc , painstArrTyCon = arr_tc } - where - tvs = tyConTyVars arr_tc - arg_tys = mkTyVarTys tvs buildPADict :: PAInstance -> VM [(Var, CoreExpr)] buildPADict (PAInstance { - painstInstance = inst + painstDFun = dfun , painstVectTyCon = vect_tc , painstArrTyCon = arr_tc }) - = localV . abstractOverTyVars (tyConTyVars arr_tc) $ \abstract -> + = polyAbstract (tyConTyVars arr_tc) $ \abstract -> do - meth_binds <- mapM mk_method paMethods + shape <- tyConShape vect_tc + meth_binds <- mapM (mk_method shape) paMethods let meth_exprs = map (Var . fst) meth_binds - pa_dc <- builtin paDictDataCon + pa_dc <- builtin paDataCon let dict = mkConApp pa_dc (Type (mkTyConApp vect_tc arg_tys) : meth_exprs) body = Let (Rec meth_binds) dict - return [(instanceDFunId inst, abstract body)] + return [(dfun, mkInlineMe $ abstract body)] where tvs = tyConTyVars arr_tc arg_tys = mkTyVarTys tvs - mk_method (name, build) + mk_method shape (name, build) = localV $ do - body <- build vect_tc arr_tc + body <- build shape vect_tc arr_tc var <- newLocalVar name (exprType body) return (var, mkInlineMe body) paMethods = [(FSLIT("lengthPA"), buildLengthPA), (FSLIT("replicatePA"), buildReplicatePA)] -buildLengthPA :: TyCon -> TyCon -> VM CoreExpr -buildLengthPA vect_tc arr_tc +buildLengthPA :: Shape -> 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 + 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 - shape <- newLocalVar FSLIT("sel") shape_ty - body <- lengthPA (Var shape) - wilds <- mapM newDummyVar repr_tys + + body <- shapeLength shape (map Var shapes) + return . Lam arg $ Case scrut (mkWildId scrut_ty) intPrimTy - [(DataAlt repr_dc, shape : wilds, body)] + [(DataAlt repr_dc, shapes ++ wilds, body)] where arg_tys = mkTyVarTys $ tyConTyVars arr_tc [repr_dc] = tyConDataCons arr_tc - shape_ty : repr_tys = dataConRepArgTys repr_dc + + shape_tys = shapeReprTys shape + repr_tys = drop (length shape_tys) (dataConRepArgTys repr_dc) -- data T = C0 t1 ... tm -- ... @@ -359,8 +450,8 @@ buildLengthPA vect_tc arr_tc -- -- -buildReplicatePA :: TyCon -> TyCon -> VM CoreExpr -buildReplicatePA vect_tc arr_tc +buildReplicatePA :: Shape -> TyCon -> TyCon -> VM CoreExpr +buildReplicatePA shape vect_tc arr_tc = do len_var <- newLocalVar FSLIT("n") intPrimTy val_var <- newLocalVar FSLIT("x") val_ty @@ -368,14 +459,16 @@ buildReplicatePA vect_tc arr_tc let len = Var len_var val = Var val_var - shape <- replicatePA len (ctr_num val) + 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] - $ mkConApp arr_dc (map (Type . TyVarTy) (tyConTyVars arr_tc) ++ (shape : reprs)) + . wrapFamInstBody arr_tc arg_tys + $ mkConApp arr_dc (map Type arg_tys ++ shape_reprs ++ reprs) where - val_ty = mkTyConApp vect_tc . mkTyVarTys $ tyConTyVars arr_tc - wild = mkWildId val_ty + 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