X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fvectorise%2FVectorise.hs;h=c5011633c628c058023c0d5c828a4502d112f190;hb=db0e973e613bdcf4805a75a42ab735bb205f0373;hp=fac66ec88de9fc1eb13f4f06fbbf3448034c234e;hpb=6bd4bdcbb35bb49728a025cf3b4b2a87793dbe8e;p=ghc-hetmet.git diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs index fac66ec..c501163 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 ) @@ -216,6 +216,8 @@ vectLiteral lit return (Lit lit, lexpr) vectPolyExpr :: CoreExprWithFVs -> VM VExpr +vectPolyExpr (_, AnnNote note expr) + = liftM (vNote note) $ vectPolyExpr expr vectPolyExpr expr = polyAbstract tvs $ \abstract -> do @@ -241,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 @@ -287,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 @@ -335,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) @@ -366,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 @@ -397,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) @@ -432,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] @@ -445,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