Safe Haskell | None |
---|---|
Language | Haskell98 |
- readGEnv :: (GlobalEnv -> a) -> VM a
- setGEnv :: GlobalEnv -> VM ()
- updGEnv :: (GlobalEnv -> GlobalEnv) -> VM ()
- isVectAvoidanceAggressive :: VM Bool
- defGlobalVar :: Var -> Var -> VM ()
- undefGlobalVar :: Var -> VM ()
- lookupVectDecl :: Var -> VM (Bool, Maybe (Type, CoreExpr))
- globalParallelVars :: VM VarSet
- globalParallelTyCons :: VM NameSet
- lookupTyCon :: TyCon -> VM (Maybe TyCon)
- defTyConName :: TyCon -> Name -> TyCon -> VM ()
- defTyCon :: TyCon -> TyCon -> VM ()
- globalVectTyCons :: VM (NameEnv TyCon)
- lookupDataCon :: DataCon -> VM (Maybe DataCon)
- defDataCon :: DataCon -> DataCon -> VM ()
- lookupTyConPA :: TyCon -> VM (Maybe Var)
- defTyConPAs :: [(TyCon, Var)] -> VM ()
- lookupTyConPR :: TyCon -> VM (Maybe Var)
Documentation
updGEnv :: (GlobalEnv -> GlobalEnv) -> VM () Source
Update the global environment using the provided function.
Configuration
isVectAvoidanceAggressive :: VM Bool Source
Should we avoid as much vectorisation as possible?
Set by '-f[no]-vectorisation-avoidance'
Vars
defGlobalVar :: Var -> Var -> VM () Source
Add a mapping between a global var and its vectorised version to the state.
undefGlobalVar :: Var -> VM () Source
Remove the mapping of a variable in the vectorisation map.
Vectorisation declarations
lookupVectDecl :: Var -> VM (Bool, Maybe (Type, CoreExpr)) Source
Check whether a variable has a vectorisation declaration.
The first component of the result indicates whether the variable has a NOVECTORISE
declaration.
The second component contains the given type and expression in case of a VECTORISE
declaration.
Scalars
globalParallelVars :: VM VarSet Source
Get the set of global parallel variables.
globalParallelTyCons :: VM NameSet Source
Get the set of all parallel type constructors (those that may embed parallelism) including both both those parallel type constructors declared in an imported module and those declared in the current module.
TyCons
defTyConName :: TyCon -> Name -> TyCon -> VM () Source
Add a mapping between plain and vectorised TyCon
s to the global environment.
The second argument is only to enable tracing for (mutually) recursively defined type constructors, where we must not pull at the vectorised type constructors (because that would pull too early at the recursive knot).
defTyCon :: TyCon -> TyCon -> VM () Source
Add a mapping between plain and vectorised TyCon
s to the global environment.
globalVectTyCons :: VM (NameEnv TyCon) Source
Get the set of all vectorised type constructors.
Datacons
lookupDataCon :: DataCon -> VM (Maybe DataCon) Source
Lookup the vectorised version of a DataCon
from the global environment.
defDataCon :: DataCon -> DataCon -> VM () Source
Add the mapping between plain and vectorised DataCon
s to the global environment.
PA Dictionaries
lookupTyConPA :: TyCon -> VM (Maybe Var) Source
Lookup the PA
dfun of a vectorised type constructor in the global environment.
defTyConPAs :: [(TyCon, Var)] -> VM () Source
Associate vectorised type constructors with the dfun of their PA
instances in the global
environment.