X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectorise.hs;h=48aa05c8f83b6ccb8f19f7060917170c308f1cd1;hb=58de6cb725982dd1f57803cc838f233d5fd9c42c;hp=d85ef6ab4f751682c714cda5aed6ac8df390acc8;hpb=772810755a8519db4585f54a27dbbdd8b9127419;p=ghc-hetmet.git diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs index d85ef6a..48aa05c 100644 --- a/compiler/vectorise/Vectorise.hs +++ b/compiler/vectorise/Vectorise.hs @@ -42,7 +42,7 @@ import Module ( Module ) import DsMonad hiding (mapAndUnzipM) import DsUtils ( mkCoreTup, mkCoreTupTy ) -import Literal ( Literal ) +import Literal ( Literal, mkMachInt ) import PrelNames import TysWiredIn import TysPrim ( intPrimTy ) @@ -70,10 +70,10 @@ vectModule :: ModGuts -> VM ModGuts vectModule guts = do (types', fam_insts, tc_binds) <- vectTypeEnv (mg_types guts) - + let fam_inst_env' = extendFamInstEnvList (mg_fam_inst_env guts) fam_insts updGEnv (setFamInstEnv fam_inst_env') - + -- dicts <- mapM buildPADict pa_insts -- workers <- mapM vectDataConWorkers pa_insts binds' <- mapM vectTopBind (mg_binds guts) @@ -113,7 +113,7 @@ vectTopBinder var var' <- cloneId mkVectOcc var vty defGlobalVar var var' return var' - + vectTopRhs :: Var -> CoreExpr -> VM CoreExpr vectTopRhs var expr = do @@ -224,8 +224,8 @@ vectPolyExpr expr mono' <- vectExpr mono return $ mapVect abstract mono' where - (tvs, mono) = collectAnnTypeBinders expr - + (tvs, mono) = collectAnnTypeBinders expr + vectExpr :: CoreExprWithFVs -> VM VExpr vectExpr (_, AnnType ty) = liftM vType (vectType ty) @@ -243,6 +243,17 @@ vectExpr e@(_, AnnApp _ arg) where (fn, tys) = collectAnnTypeArgs e +vectExpr (_, AnnApp (_, AnnVar v) (_, AnnLit lit)) + | Just con <- isDataConId_maybe v + , is_special_con con + = do + let vexpr = App (Var v) (Lit lit) + lexpr <- liftPA vexpr + return (vexpr, lexpr) + where + is_special_con con = con `elem` [intDataCon, floatDataCon, doubleDataCon] + + vectExpr (_, AnnApp fn arg) = do arg_ty' <- vectType arg_ty @@ -289,6 +300,8 @@ vectExpr e@(fvs, AnnLam bndr _) where (bs,body) = collectAnnValBinders e +vectExpr e = pprPanic "vectExpr" (ppr $ deAnnotate e) + vectLam :: VarSet -> [Var] -> CoreExprWithFVs -> VM VExpr vectLam fvs bs body = do @@ -307,7 +320,7 @@ vectLam fvs bs body (vbndrs, vbody) <- vectBndrsIn (vs ++ bs) (vectExpr body) return $ vLams lc vbndrs vbody - + vectTyAppExpr :: CoreExprWithFVs -> [Type] -> VM VExpr vectTyAppExpr (_, AnnVar v) tys = vectPolyVar v tys vectTyAppExpr e tys = pprPanic "vectTyAppExpr" (ppr $ deAnnotate e) @@ -326,7 +339,7 @@ type CoreAltWithFVs = AnnAlt Id VarSet -- When lifting, we have to do it this way because v must have the type -- [:V(T):] but the scrutinee must be cast to the representation type. We also -- have to handle the case where v is a wild var correctly. --- +-- -- FIXME: this is too lazy vectAlgCase tycon ty_args scrut bndr ty [(DEFAULT, [], body)] @@ -337,6 +350,14 @@ vectAlgCase tycon ty_args scrut bndr ty [(DEFAULT, [], body)] (vbndr, vbody) <- vectBndrIn bndr (vectExpr body) return $ vCaseDEFAULT vscrut vbndr vty lty vbody +vectAlgCase tycon ty_args scrut bndr ty [(DataAlt dc, [], body)] + = do + vscrut <- vectExpr scrut + vty <- vectType ty + lty <- mkPArrayType vty + (vbndr, vbody) <- vectBndrIn bndr (vectExpr body) + return $ vCaseDEFAULT vscrut vbndr vty lty vbody + vectAlgCase tycon ty_args scrut bndr ty [(DataAlt dc, bndrs, body)] = do vect_tc <- maybeV (lookupTyCon tycon) @@ -368,7 +389,7 @@ vectAlgCase tycon ty_args scrut bndr ty alts shape_bndrs <- arrShapeVars repr (len, sel, indices) <- arrSelector repr (map Var shape_bndrs) - (vbndr, valts) <- vect_scrut_bndr $ mapM (proc_alt sel lty) alts' + (vbndr, valts) <- vect_scrut_bndr $ mapM (proc_alt sel vty lty) alts' let (vect_dcs, vect_bndrss, lift_bndrss, vbodies) = unzip4 valts vexpr <- vectExpr scrut @@ -399,14 +420,14 @@ vectAlgCase tycon ty_args scrut bndr ty alts cmp DEFAULT _ = LT cmp _ DEFAULT = GT - proc_alt sel lty (DataAlt dc, bndrs, body) + proc_alt sel vty lty (DataAlt dc, bndrs, body) = do vect_dc <- maybeV (lookupDataCon dc) let tag = mkDataConTag vect_dc fvs = freeVarsOf body `delVarSetList` bndrs (vect_bndrs, lift_bndrs, vbody) <- vect_alt_bndrs bndrs - $ \len -> packLiftingContext len sel tag fvs lty + $ \len -> packLiftingContext len sel tag fvs vty lty $ vectExpr body return (vect_dc, vect_bndrs, lift_bndrs, vbody) @@ -434,8 +455,9 @@ vectAlgCase tycon ty_args scrut bndr ty alts mk_vect_alt vect_dc bndrs body = (DataAlt vect_dc, bndrs, body) -packLiftingContext :: CoreExpr -> CoreExpr -> CoreExpr -> VarSet -> Type -> VM VExpr -> VM VExpr -packLiftingContext len shape tag fvs res_ty p +packLiftingContext :: CoreExpr -> CoreExpr -> CoreExpr -> VarSet + -> Type -> Type -> VM VExpr -> VM VExpr +packLiftingContext len shape tag fvs vty lty p = do select <- builtin selectPAIntPrimVar let sel_expr = mkApps (Var select) [shape, tag] @@ -447,9 +469,12 @@ packLiftingContext len shape tag fvs res_ty p . filter isLocalId $ varSetElems fvs (vexpr, lexpr) <- p + empty <- emptyPA vty return (vexpr, Let (NonRec sel_var sel_expr) . mkLets (concat bnds) - $ Case len lc_var res_ty [(DEFAULT, [], lexpr)]) + $ Case len lc_var lty + [(DEFAULT, [], lexpr), + (LitAlt (mkMachInt 0), [], empty)]) packFreeVar :: CoreExpr -> CoreExpr -> Var -> VM [CoreBind] packFreeVar len sel v