X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fvectorise%2FVectType.hs;h=e28b66ffa02e779cf19db9a7b4b9d62423616fe6;hp=eb7ce6de03b7e2914a65a49cd18e12ed7722c22a;hb=58eb6de8922742d301a6703b4a21504dd8d623a5;hpb=f03cf1b168c34d09766fda988921b8263e7e7300 diff --git a/compiler/vectorise/VectType.hs b/compiler/vectorise/VectType.hs index eb7ce6d..e28b66f 100644 --- a/compiler/vectorise/VectType.hs +++ b/compiler/vectorise/VectType.hs @@ -11,6 +11,7 @@ import VectCore import HscTypes ( TypeEnv, extendTypeEnvList, typeEnvTyCons ) import CoreSyn import CoreUtils +import BuildTyCl import DataCon import TyCon import Type @@ -25,7 +26,7 @@ import Var ( Var ) import Id ( mkWildId ) import Name ( Name, getOccName ) import NameEnv -import TysWiredIn ( intTy, intDataCon ) +import TysWiredIn ( unitTy, intTy, intDataCon ) import TysPrim ( intPrimTy ) import Unique @@ -96,19 +97,20 @@ vectTypeEnv env let orig_tcs = keep_tcs ++ conv_tcs vect_tcs = keep_tcs ++ new_tcs + repr_tcs <- zipWithM buildPReprTyCon orig_tcs vect_tcs 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) - let all_new_tcs = new_tcs ++ parr_tcs + let all_new_tcs = new_tcs ++ repr_tcs ++ parr_tcs let new_env = extendTypeEnvList env (map ATyCon all_new_tcs ++ [ADataCon dc | tc <- all_new_tcs , dc <- tyConDataCons tc]) - return (new_env, map mkLocalFamInst parr_tcs, concat binds) + return (new_env, map mkLocalFamInst (repr_tcs ++ parr_tcs), concat binds) where tycons = typeEnvTyCons env groups = tyConGroups tycons @@ -135,19 +137,16 @@ vectTyConDecl tc name' <- cloneName mkVectTyConOcc name rhs' <- vectAlgTyConRhs (algTyConRhs tc) - return $ mkAlgTyCon name' - kind - tyvars - [] -- no stupid theta - rhs' - [] -- no selector ids - NoParentTyCon -- FIXME - rec_flag -- FIXME: is this ok? - False -- FIXME: no generics - False -- not GADT syntax + liftDs $ buildAlgTyCon name' + tyvars + [] -- no stupid theta + rhs' + rec_flag -- FIXME: is this ok? + False -- FIXME: no generics + False -- not GADT syntax + Nothing -- not a family instance where name = tyConName tc - kind = tyConKind tc tyvars = tyConTyVars tc rec_flag = boolToRecFlag (isRecursiveTyCon tc) @@ -171,72 +170,83 @@ vectDataCon dc name' <- cloneName mkVectDataConOcc name tycon' <- vectTyCon tycon arg_tys <- mapM vectType rep_arg_tys - wrk_name <- cloneName mkDataConWorkerOcc name' - - let ids = mkDataConIds (panic "vectDataCon: wrapper id") - wrk_name - data_con - data_con = mkDataCon name' - False -- not infix - (map (const NotMarkedStrict) arg_tys) - [] -- no labelled fields - univ_tvs - [] -- no existential tvs for now - [] -- no eq spec for now - [] -- no theta - arg_tys - tycon' - [] -- no stupid theta - ids - return data_con + + liftDs $ buildDataCon name' + False -- not infix + (map (const NotMarkedStrict) arg_tys) + [] -- no labelled fields + univ_tvs + [] -- no existential tvs for now + [] -- no eq spec for now + [] -- no context + arg_tys + tycon' where name = dataConName dc univ_tvs = dataConUnivTyVars dc rep_arg_tys = dataConRepArgTys dc tycon = dataConTyCon dc +mk_fam_inst :: TyCon -> TyCon -> (TyCon, [Type]) +mk_fam_inst fam_tc arg_tc + = (fam_tc, [mkTyConApp arg_tc . mkTyVarTys $ tyConTyVars arg_tc]) + +mkSumOfProdRepr :: [[Type]] -> VM Type +mkSumOfProdRepr [] = panic "mkSumOfProdRepr" +mkSumOfProdRepr tys + = do + embed <- builtin embedTyCon + plus <- builtin plusTyCon + cross <- builtin crossTyCon + + return . foldr1 (mk_bin plus) + . map (mkprod cross) + . map (map (mk_un embed)) + $ tys + where + mkprod cross [] = unitTy + mkprod cross tys = foldr1 (mk_bin cross) tys + + mk_un tc ty = mkTyConApp tc [ty] + mk_bin tc ty1 ty2 = mkTyConApp tc [ty1,ty2] + +buildPReprTyCon :: TyCon -> TyCon -> VM TyCon +buildPReprTyCon orig_tc vect_tc + = do + name <- cloneName mkPReprTyConOcc (tyConName orig_tc) + rhs_ty <- buildPReprRhsTy vect_tc + prepr_tc <- builtin preprTyCon + liftDs $ buildSynTyCon name + tyvars + (SynonymTyCon rhs_ty) + (Just $ mk_fam_inst prepr_tc vect_tc) + where + tyvars = tyConTyVars vect_tc + +buildPReprRhsTy :: TyCon -> VM Type +buildPReprRhsTy = mkSumOfProdRepr . map dataConRepArgTys . tyConDataCons + buildPArrayTyCon :: TyCon -> TyCon -> VM TyCon buildPArrayTyCon orig_tc vect_tc = fixV $ \repr_tc -> do name' <- cloneName mkPArrayTyConOcc orig_name - parent <- buildPArrayParentInfo orig_name vect_tc repr_tc rhs <- buildPArrayTyConRhs orig_name vect_tc repr_tc - - return $ mkAlgTyCon name' - kind - tyvars - [] -- no stupid theta - rhs - [] -- no selector ids - parent - rec_flag -- FIXME: is this ok? - False -- FIXME: no generics - False -- not GADT syntax + parray <- builtin parrayTyCon + + liftDs $ buildAlgTyCon name' + tyvars + [] -- no stupid theta + rhs + rec_flag -- FIXME: is this ok? + False -- FIXME: no generics + False -- not GADT syntax + (Just $ mk_fam_inst parray vect_tc) where orig_name = tyConName orig_tc - name = tyConName vect_tc - kind = tyConKind vect_tc tyvars = tyConTyVars vect_tc rec_flag = boolToRecFlag (isRecursiveTyCon vect_tc) -buildPArrayParentInfo :: Name -> TyCon -> TyCon -> VM TyConParent -buildPArrayParentInfo orig_name vect_tc repr_tc - = do - parray_tc <- builtin parrayTyCon - co_name <- cloneName mkInstTyCoOcc (tyConName repr_tc) - - let inst_tys = [mkTyConApp vect_tc (map mkTyVarTy tyvars)] - - return . FamilyTyCon parray_tc inst_tys - $ mkFamInstCoercion co_name - tyvars - parray_tc - inst_tys - repr_tc - where - tyvars = tyConTyVars vect_tc - buildPArrayTyConRhs :: Name -> TyCon -> TyCon -> VM AlgTyConRhs buildPArrayTyConRhs orig_name vect_tc repr_tc = do @@ -249,24 +259,17 @@ buildPArrayDataCon orig_name vect_tc repr_tc dc_name <- cloneName mkPArrayDataConOcc orig_name shape <- tyConShape vect_tc repr_tys <- mapM mkPArrayType types - wrk_name <- cloneName mkDataConWorkerOcc dc_name - wrp_name <- cloneName mkDataConWrapperOcc dc_name - - let ids = mkDataConIds wrp_name wrk_name data_con - data_con = mkDataCon dc_name - False - (shapeStrictness shape ++ map (const NotMarkedStrict) repr_tys) - [] - (tyConTyVars vect_tc) - [] - [] - [] - (shapeReprTys shape ++ repr_tys) - repr_tc - [] - ids - - return data_con + + liftDs $ buildDataCon dc_name + False -- not infix + (shapeStrictness shape ++ map (const NotMarkedStrict) repr_tys) + [] -- no field labels + (tyConTyVars vect_tc) + [] -- no existentials + [] -- no eq spec + [] -- no context + (shapeReprTys shape ++ repr_tys) + repr_tc where types = [ty | dc <- tyConDataCons vect_tc , ty <- dataConRepArgTys dc] @@ -308,8 +311,9 @@ buildTyConBindings :: TyCon -> TyCon -> TyCon -> Var -> VM [(Var, CoreExpr)] buildTyConBindings orig_tc vect_tc arr_tc dfun = do shape <- tyConShape vect_tc - sequence_ (zipWith3 (vectDataConWorker shape vect_tc arr_tc arr_dc) - num_dcs + 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 arr_tc dfun @@ -320,13 +324,12 @@ buildTyConBindings orig_tc vect_tc arr_tc dfun 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]] + -> DataCon -> DataCon -> [[Type]] -> [[Type]] -> VM () -vectDataConWorker shape vect_tc arr_tc arr_dc (orig_dc, vect_dc, dc_num) pre (dc_tys : post) +vectDataConWorker shape vect_tc arr_tc arr_dc orig_dc vect_dc pre (dc_tys : post) = do clo <- closedV . inBind orig_worker @@ -350,7 +353,9 @@ vectDataConWorker shape vect_tc arr_tc arr_dc (orig_dc, vect_dc, dc_num) pre (dc 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) + shapes <- shapeReplicate shape + (Var len) + (mkDataConTag vect_dc) empty_pre <- mapM emptyPA (concat pre) empty_post <- mapM emptyPA (concat post)