Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Scope a b
- data LocalEnv = LocalEnv {
- local_vars :: VarEnv (Var, Var)
- local_tyvars :: [TyVar]
- local_tyvar_pa :: VarEnv CoreExpr
- local_bind_name :: FastString
- emptyLocalEnv :: LocalEnv
- data GlobalEnv = GlobalEnv {
- global_vect_avoid :: Bool
- global_vars :: VarEnv Var
- global_parallel_vars :: VarSet
- global_vect_decls :: VarEnv (Maybe (Type, CoreExpr))
- global_tycons :: NameEnv TyCon
- global_parallel_tycons :: NameSet
- global_datacons :: NameEnv DataCon
- global_pa_funs :: NameEnv Var
- global_pr_funs :: NameEnv Var
- global_inst_env :: (InstEnv, InstEnv)
- global_fam_inst_env :: FamInstEnvs
- global_bindings :: [(Var, CoreExpr)]
- initGlobalEnv :: Bool -> VectInfo -> [CoreVect] -> (InstEnv, InstEnv) -> FamInstEnvs -> GlobalEnv
- extendImportedVarsEnv :: [(Var, Var)] -> GlobalEnv -> GlobalEnv
- extendFamEnv :: [FamInst] -> GlobalEnv -> GlobalEnv
- setPAFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv
- setPRFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv
- modVectInfo :: GlobalEnv -> [Id] -> [TyCon] -> [CoreVect] -> VectInfo -> VectInfo
Documentation
Local Environments
The local environment.
LocalEnv | |
|
emptyLocalEnv :: LocalEnv Source
Create an empty local environment.
Global Environments
The global environment: entities that exist at top-level.
GlobalEnv | |
|
initGlobalEnv :: Bool -> VectInfo -> [CoreVect] -> (InstEnv, InstEnv) -> FamInstEnvs -> GlobalEnv Source
Create an initial global environment.
We add scalar variables and type constructors identified by vectorisation pragmas already here to the global table, so that we can query scalarness during vectorisation, and especially, when vectorising the scalar entities' definitions themselves.
extendImportedVarsEnv :: [(Var, Var)] -> GlobalEnv -> GlobalEnv Source
Extend the list of global variables in an environment.
extendFamEnv :: [FamInst] -> GlobalEnv -> GlobalEnv Source
Extend the list of type family instances.
setPAFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv Source
Set the list of PA functions in an environment.
setPRFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnv Source
Set the list of PR functions in an environment.
modVectInfo :: GlobalEnv -> [Id] -> [TyCon] -> [CoreVect] -> VectInfo -> VectInfo Source
Compute vectorisation information that goes into ModGuts
(and is stored in interface files).
The incoming vectInfo
is that from the HscEnv
and EPS
. The outgoing one contains only the
declarations for the currently compiled module; this includes variables, type constructors, and
data constructors referenced in VECTORISE pragmas, even if they are defined in an imported
module.
The variables explicitly include class selectors and dfuns.