summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorRoman Leshchinskiy <rl@cse.unsw.edu.au>2007-08-08 05:04:33 +0000
committerRoman Leshchinskiy <rl@cse.unsw.edu.au>2007-08-08 05:04:33 +0000
commitf363bf9a76bcaddc1bfea61135f4f4d2fbcfd955 (patch)
tree6a3bb7d4e05e12e67878898533f1aec8da7e9574
parent5eec4625961ca9064216f0161288e0d46628c10f (diff)
downloadhaskell-f363bf9a76bcaddc1bfea61135f4f4d2fbcfd955.tar.gz
Vectorise Case on products
-rw-r--r--compiler/vectorise/VectCore.hs24
-rw-r--r--compiler/vectorise/VectUtils.hs8
-rw-r--r--compiler/vectorise/Vectorise.hs55
3 files changed, 84 insertions, 3 deletions
diff --git a/compiler/vectorise/VectCore.hs b/compiler/vectorise/VectCore.hs
index 1ccc3813ce..de832793f6 100644
--- a/compiler/vectorise/VectCore.hs
+++ b/compiler/vectorise/VectCore.hs
@@ -7,13 +7,17 @@ module VectCore (
vNonRec, vRec,
vVar, vType, vNote, vLet,
- vLams, vLamsWithoutLC, vVarApps
+ vLams, vLamsWithoutLC, vVarApps,
+ vCaseDEFAULT, vCaseProd
) where
#include "HsVersions.h"
import CoreSyn
+import CoreUtils ( exprType )
+import DataCon ( DataCon )
import Type ( Type )
+import Id ( mkWildId )
import Var
type Vect a = (a,a)
@@ -69,4 +73,20 @@ vVarApps lc (ve, le) vvs = (ve `mkVarApps` vs, le `mkVarApps` (lc : ls))
where
(vs,ls) = unzip vvs
-
+vCaseDEFAULT :: VExpr -> VVar -> Type -> Type -> VExpr -> VExpr
+vCaseDEFAULT (vscrut, lscrut) (vbndr, lbndr) vty lty (vbody, lbody)
+ = (Case vscrut vbndr vty (mkDEFAULT vbody),
+ Case lscrut lbndr lty (mkDEFAULT lbody))
+ where
+ mkDEFAULT e = [(DEFAULT, [], e)]
+
+vCaseProd :: VExpr -> Type -> Type
+ -> DataCon -> DataCon -> [Var] -> [VVar] -> VExpr -> VExpr
+vCaseProd (vscrut, lscrut) vty lty vdc ldc sh_bndrs bndrs
+ (vbody,lbody)
+ = (Case vscrut (mkWildId $ exprType vscrut) vty
+ [(DataAlt vdc, vbndrs, vbody)],
+ Case lscrut (mkWildId $ exprType lscrut) lty
+ [(DataAlt ldc, sh_bndrs ++ lbndrs, lbody)])
+ where
+ (vbndrs, lbndrs) = unzip bndrs
diff --git a/compiler/vectorise/VectUtils.hs b/compiler/vectorise/VectUtils.hs
index eec57d7538..46766ea8d1 100644
--- a/compiler/vectorise/VectUtils.hs
+++ b/compiler/vectorise/VectUtils.hs
@@ -4,7 +4,7 @@ module VectUtils (
mkDataConTag,
splitClosureTy,
mkPADictType, mkPArrayType,
- parrayReprTyCon, parrayReprDataCon,
+ parrayReprTyCon, parrayReprDataCon, mkVScrut,
paDictArgType, paDictOfType, paDFunType,
paMethod, lengthPA, replicatePA, emptyPA, liftPA,
polyAbstract, polyApply, polyVApply,
@@ -120,6 +120,12 @@ parrayReprDataCon ty
let [dc] = tyConDataCons tc
return (dc, arg_tys)
+mkVScrut :: VExpr -> VM (VExpr, TyCon, [Type])
+mkVScrut (ve, le)
+ = do
+ (tc, arg_tys) <- parrayReprTyCon (exprType ve)
+ return ((ve, unwrapFamInstScrut tc arg_tys le), tc, arg_tys)
+
paDictArgType :: TyVar -> VM (Maybe Type)
paDictArgType tv = go (TyVarTy tv) (tyVarKind tv)
where
diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs
index 06fc542212..03fa131ca9 100644
--- a/compiler/vectorise/Vectorise.hs
+++ b/compiler/vectorise/Vectorise.hs
@@ -154,6 +154,14 @@ vectBndrIn v p
x <- p
return (vv, x)
+vectBndrIn' :: Var -> (VVar -> VM a) -> VM (VVar, a)
+vectBndrIn' v p
+ = localV
+ $ do
+ vv <- vectBndr v
+ x <- p vv
+ return (vv, x)
+
vectBndrsIn :: [Var] -> VM a -> VM ([VVar], a)
vectBndrsIn vs p
= localV
@@ -227,6 +235,12 @@ vectExpr (_, AnnApp fn arg)
arg' <- vectExpr arg
mkClosureApp fn' arg'
+vectExpr (_, AnnCase scrut bndr ty alts)
+ | isAlgType scrut_ty
+ = vectAlgCase scrut bndr ty alts
+ where
+ scrut_ty = exprType (deAnnotate scrut)
+
vectExpr (_, AnnCase expr bndr ty alts)
= panic "vectExpr: case"
@@ -279,3 +293,44 @@ vectTyAppExpr :: CoreExprWithFVs -> [Type] -> VM VExpr
vectTyAppExpr (_, AnnVar v) tys = vectPolyVar v tys
vectTyAppExpr e tys = pprPanic "vectTyAppExpr" (ppr $ deAnnotate e)
+type CoreAltWithFVs = AnnAlt Id VarSet
+
+-- We convert
+--
+-- case e :: t of v { ... }
+--
+-- to
+--
+-- V: let v = e in case v of _ { ... }
+-- L: let v = e in case v `cast` ... of _ { ... }
+--
+-- 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.
+--
+
+-- FIXME: this is too lazy
+vectAlgCase scrut bndr ty [(DEFAULT, [], 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 scrut bndr ty [(DataAlt dc, bndrs, body)]
+ = do
+ vty <- vectType ty
+ lty <- mkPArrayType vty
+ vexpr <- vectExpr scrut
+ (vbndr, (vbndrs, vbody)) <- vectBndrIn bndr
+ . vectBndrsIn bndrs
+ $ vectExpr body
+
+ (vscrut, arr_tc, arg_tys) <- mkVScrut (vVar vbndr)
+ vect_dc <- maybeV (lookupDataCon dc)
+ let [arr_dc] = tyConDataCons arr_tc
+ let shape_tys = take (dataConRepArity arr_dc - length bndrs)
+ (dataConRepArgTys arr_dc)
+ shape_bndrs <- mapM (newLocalVar FSLIT("s")) shape_tys
+ return . vLet (vNonRec vbndr vexpr)
+ $ vCaseProd vscrut vty lty vect_dc arr_dc shape_bndrs vbndrs vbody