ghc-7.2.2: The GHC API

Vectorise.Env

Contents

Synopsis

Documentation

data Scope a b Source

Indicates what scope something (a variable) is in.

Constructors

Global a 
Local b 

Local Environments

data LocalEnv Source

The local environment.

emptyLocalEnv :: LocalEnvSource

Create an empty local environment.

Global Environments

data GlobalEnv Source

The global environment: entities that exist at top-level.

Constructors

GlobalEnv 

Fields

global_vars :: VarEnv Var

Mapping from global variables to their vectorised versions  aka the /vectorisation map/.

global_vect_decls :: VarEnv (Type, CoreExpr)

Mapping from global variables that have a vectorisation declaration to the right-hand side of that declaration and its type. This mapping only applies to non-scalar vectorisation declarations. All variables with a scalar vectorisation declaration are mentioned in global_scalars_vars.

global_scalar_vars :: VarSet

Purely scalar variables. Code which mentions only these variables doesn't have to be lifted. This includes variables from the current module that have a scalar vectorisation declaration and those that the vectoriser determines to be scalar.

global_scalar_tycons :: NameSet

Type constructors whose values can only contain scalar data. Scalar code may only operate on such data.

global_novect_vars :: VarSet

Variables that are not vectorised. (They may be referenced in the right-hand sides of vectorisation declarations, though.)

global_exported_vars :: VarEnv (Var, Var)

Exported variables which have a vectorised version.

global_tycons :: NameEnv TyCon

Mapping from TyCons to their vectorised versions. TyCons which do not have to be vectorised are mapped to themselves.

global_datacons :: NameEnv DataCon

Mapping from DataCons to their vectorised versions.

global_pa_funs :: NameEnv Var

Mapping from TyCons to their PA dfuns.

global_pr_funs :: NameEnv Var

Mapping from TyCons to their PR dfuns.

global_boxed_tycons :: NameEnv TyCon

Mapping from unboxed TyCons to their boxed versions.

global_inst_env :: (InstEnv, InstEnv)

External package inst-env & home-package inst-env for class instances.

global_fam_inst_env :: FamInstEnvs

External package inst-env & home-package inst-env for family instances.

global_bindings :: [(Var, CoreExpr)]

Hoisted bindings.

initGlobalEnv :: VectInfo -> [CoreVect] -> (InstEnv, InstEnv) -> FamInstEnvs -> GlobalEnvSource

Create an initial global environment.

extendImportedVarsEnv :: [(Var, Var)] -> GlobalEnv -> GlobalEnvSource

Extend the list of global variables in an environment.

setFamEnv :: FamInstEnv -> GlobalEnv -> GlobalEnvSource

Set the list of type family instances in an environment.

extendFamEnv :: [FamInst] -> GlobalEnv -> GlobalEnvSource

Extend the list of type family instances.

extendTyConsEnv :: [(Name, TyCon)] -> GlobalEnv -> GlobalEnvSource

Extend the list of type constructors in an environment.

extendDataConsEnv :: [(Name, DataCon)] -> GlobalEnv -> GlobalEnvSource

Extend the list of data constructors in an environment.

extendPAFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnvSource

Extend the list of PA functions in an environment.

setPRFunsEnv :: [(Name, Var)] -> GlobalEnv -> GlobalEnvSource

Set the list of PR functions in an environment.

setBoxedTyConsEnv :: [(Name, TyCon)] -> GlobalEnv -> GlobalEnvSource

Set the list of boxed type constructor in an environment.

modVectInfo :: GlobalEnv -> TypeEnv -> VectInfo -> VectInfoSource

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 definitions for the currently compiled module.