vectPolyVar,
vectLiteral
) where
+
import Vectorise.Utils
import Vectorise.Monad
import Vectorise.Env
-- Binders ----------------------------------------------------------------------------------------
+
-- | Vectorise a binder variable, along with its attached type.
vectBndr :: Var -> VM VVar
vectBndr v
where
mapTo vv lv env = env { local_vars = extendVarEnv (local_vars env) v (vv, lv) }
-
-- | Vectorise a binder variable, along with its attached type,
-- but give the result a new name.
vectBndrNew :: Var -> FastString -> VM VVar
where
upd vv env = env { local_vars = extendVarEnv (local_vars env) v vv }
-
-- | Vectorise a binder then run a computation with that binder in scope.
vectBndrIn :: Var -> VM a -> VM (VVar, a)
vectBndrIn v p
x <- p
return (vv, x)
-
-- | Vectorise a binder, give it a new name, then run a computation with that binder in scope.
vectBndrNewIn :: Var -> FastString -> VM a -> VM (VVar, a)
vectBndrNewIn v fs p
x <- p
return (vv, x)
-
-- | Vectorise some binders, then run a computation with them in scope.
vectBndrsIn :: [Var] -> VM a -> VM ([VVar], a)
vectBndrsIn vs p
-- Variables --------------------------------------------------------------------------------------
+
-- | Vectorise a variable, producing the vectorised and lifted versions.
vectVar :: Var -> VM VExpr
vectVar v
lexpr <- liftPD vexpr
return (vexpr, lexpr)
-
-- | Like `vectVar` but also add type applications to the variables.
+-- FIXME: 'vectVar' is really just a special case, which 'vectPolyVar' should handle fine as well —
+-- MERGE the two functions!
vectPolyVar :: Var -> [Type] -> VM VExpr
vectPolyVar v tys
= do vtys <- mapM vectType tys
-- Literals ---------------------------------------------------------------------------------------
+
-- | Lifted literals are created by replicating them
-- We use the the integer context in the `VM` state for the number
-- of elements in the output array.
vectLiteral lit
= do lexpr <- liftPD (Lit lit)
return (Lit lit, lexpr)
-