Safe Haskell | Safe-Infered |
---|
- module Vectorise.Monad.Base
- module Vectorise.Monad.Naming
- module Vectorise.Monad.Local
- module Vectorise.Monad.Global
- module Vectorise.Monad.InstEnv
- initV :: HscEnv -> ModGuts -> VectInfo -> VM a -> IO (Maybe (VectInfo, a))
- liftBuiltinDs :: (Builtins -> DsM a) -> VM a
- builtin :: (Builtins -> a) -> VM a
- builtins :: (a -> Builtins -> b) -> VM (a -> b)
- lookupVar :: Var -> VM (Scope Var (Var, Var))
- lookupVar_maybe :: Var -> VM (Maybe (Scope Var (Var, Var)))
- addGlobalScalarVar :: Var -> VM ()
- addGlobalScalarTyCon :: TyCon -> VM ()
Documentation
module Vectorise.Monad.Base
module Vectorise.Monad.Naming
module Vectorise.Monad.Local
module Vectorise.Monad.Global
module Vectorise.Monad.InstEnv
initV :: HscEnv -> ModGuts -> VectInfo -> VM a -> IO (Maybe (VectInfo, a))Source
Run a vectorisation computation.
Builtins
liftBuiltinDs :: (Builtins -> DsM a) -> VM aSource
Lift a desugaring computation using the Builtins
into the vectorisation monad.
builtins :: (a -> Builtins -> b) -> VM (a -> b)Source
Lift a function using the Builtins
into the vectorisation monad.
Variables
lookupVar :: Var -> VM (Scope Var (Var, Var))Source
Lookup the vectorised, and if local, also the lifted version of a variable.
- If it's in the global environment we get the vectorised version. * If it's in the local environment we get both the vectorised and lifted version.
addGlobalScalarVar :: Var -> VM ()Source
Mark the given variable as scalar — i.e., executing the associated code does not involve any parallel array computations.
addGlobalScalarTyCon :: TyCon -> VM ()Source
Mark the given type constructor as scalar — i.e., its values cannot embed parallel arrays.