ghc-8.0.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

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.

Constructors

LocalEnv 

Fields

emptyLocalEnv :: LocalEnv Source #

Create an empty local environment.

Global Environments

data GlobalEnv Source #

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

Constructors

GlobalEnv 

Fields

  • global_vect_avoid :: Bool

    True implies to avoid vectorisation as far as possible.

  • global_vars :: VarEnv Var

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

  • global_parallel_vars :: DVarSet

    The domain of global_vars.

    This information is not redundant as it is impossible to extract the domain from a VarEnv (which is keyed on uniques alone). Moreover, we have mapped variables that do not involve parallelism — e.g., the workers of vectorised, but scalar data types. In addition, workers of parallel data types that we could not vectorise also need to be tracked.

  • global_vect_decls :: VarEnv (Maybe (Type, CoreExpr))

    Mapping from global variables that have a vectorisation declaration to the right-hand side of that declaration and its type and mapping variables that have NOVECTORISE declarations to Nothing.

  • global_tycons :: NameEnv TyCon

    Mapping from TyCons to their vectorised versions. The vectorised version will be identical to the original version if it is not changed by vectorisation. In any case, if a tycon appears in the domain of this mapping, it was successfully vectorised.

  • global_parallel_tycons :: NameSet

    Type constructors whose definition directly or indirectly includes a parallel type, such as '[::]'.

    NB: This information is not redundant as some types have got a mapping in global_tycons (to a type other than themselves) and are still not parallel. An example is '(->)'. Moreover, some types have *not* got a mapping in global_tycons (because they couldn't be vectorised), but still contain parallel types.

  • 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_inst_env :: InstEnvs

    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 — temporary storage for toplevel bindings during code gen.

initGlobalEnv :: Bool -> VectInfo -> [CoreVect] -> InstEnvs -> 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.