ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

Vectorise.Monad

Contents

Synopsis

Documentation

initV :: HscEnv -> ModGuts -> VectInfo -> VM a -> IO (Maybe (VectInfo, a)) Source #

Run a vectorisation computation.

Builtins

liftBuiltinDs :: (Builtins -> DsM a) -> VM a Source #

Lift a desugaring computation using the Builtins into the vectorisation monad.

builtin :: (Builtins -> a) -> VM a Source #

Project something from the set of builtins.

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.

addGlobalParallelVar :: Var -> VM () Source #

Mark the given variable as parallel — i.e., executing the associated code might involve parallel array computations.

addGlobalParallelTyCon :: TyCon -> VM () Source #

Mark the given type constructor as parallel — i.e., its values might embed parallel arrays.