ghc-8.6.5: The GHC API

Safe HaskellNone
LanguageHaskell2010

Module

Contents

Synopsis

The ModuleName type

data ModuleName Source #

A ModuleName is essentially a simple string, e.g. Data.List.

Instances
Eq ModuleName Source # 
Instance details

Defined in Module

Data ModuleName Source # 
Instance details

Defined in Module

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName #

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) #

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

Ord ModuleName Source # 
Instance details

Defined in Module

NFData ModuleName Source # 
Instance details

Defined in Module

Methods

rnf :: ModuleName -> () #

BinaryStringRep ModuleName Source # 
Instance details

Defined in Module

Outputable ModuleName Source # 
Instance details

Defined in Module

Uniquable ModuleName Source # 
Instance details

Defined in Module

Binary ModuleName Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

moduleNameSlashes :: ModuleName -> String Source #

Returns the string version of the module name, with dots replaced by slashes.

moduleNameColons :: ModuleName -> String Source #

Returns the string version of the module name, with dots replaced by colons.

moduleStableString :: Module -> String Source #

Get a string representation of a Module that's unique and stable across recompilations. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"

moduleFreeHoles :: Module -> UniqDSet ModuleName Source #

Calculate the free holes of a Module. If this set is non-empty, this module was defined in an indefinite library that had required signatures.

If a module has free holes, that means that substitutions can operate on it; if it has no free holes, substituting over a module has no effect.

moduleIsDefinite :: Module -> Bool Source #

A Module is definite if it has no free holes.

stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering Source #

Compares module names lexically, rather than by their Uniques

The UnitId type

newtype ComponentId Source #

A ComponentId consists of the package name, package version, component ID, the transitive dependencies of the component, and other information to uniquely identify the source code and build configuration of a component.

This used to be known as an InstalledPackageId, but a package can contain multiple components and a ComponentId uniquely identifies a component within a package. When a package only has one component, the ComponentId coincides with the InstalledPackageId

Constructors

ComponentId FastString 
Instances
Eq ComponentId Source # 
Instance details

Defined in Module

Ord ComponentId Source # 
Instance details

Defined in Module

BinaryStringRep ComponentId Source # 
Instance details

Defined in Module

Outputable ComponentId Source # 
Instance details

Defined in Module

Uniquable ComponentId Source # 
Instance details

Defined in Module

Binary ComponentId Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

data UnitId Source #

A unit identifier identifies a (possibly partially) instantiated library. It is primarily used as part of Module, which in turn is used in Name, which is used to give names to entities when typechecking.

There are two possible forms for a UnitId. It can be a DefiniteUnitId, in which case we just have a string that uniquely identifies some fully compiled, installed library we have on disk. However, when we are typechecking a library with missing holes, we may need to instantiate a library on the fly (in which case we don't have any on-disk representation.) In that case, you have an IndefiniteUnitId, which explicitly records the instantiation, so that we can substitute over it.

Instances
Eq UnitId Source # 
Instance details

Defined in Module

Methods

(==) :: UnitId -> UnitId -> Bool #

(/=) :: UnitId -> UnitId -> Bool #

Data UnitId Source # 
Instance details

Defined in Module

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId #

toConstr :: UnitId -> Constr #

dataTypeOf :: UnitId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) #

gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId #

Ord UnitId Source # 
Instance details

Defined in Module

Show UnitId Source # 
Instance details

Defined in Module

NFData UnitId Source # 
Instance details

Defined in Module

Methods

rnf :: UnitId -> () #

Outputable UnitId Source # 
Instance details

Defined in Module

Uniquable UnitId Source # 
Instance details

Defined in Module

Binary UnitId Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

data IndefUnitId Source #

A unit identifier which identifies an indefinite library (with holes) that has been *on-the-fly* instantiated with a substitution indefUnitIdInsts. In fact, an indefinite unit identifier could have no holes, but we haven't gotten around to compiling the actual library yet.

An indefinite unit identifier pretty-prints to something like p[H=H,A=aimpl:A>] (p is the ComponentId, and the brackets enclose the module substitution).

Constructors

IndefUnitId 

Fields

indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId Source #

Injects an IndefUnitId (indefinite library which was on-the-fly instantiated) to a UnitId (either an indefinite or definite library).

newtype InstalledUnitId Source #

An installed unit identifier identifies a library which has been installed to the package database. These strings are provided to us via the -this-unit-id flag. The library in question may be definite or indefinite; if it is indefinite, none of the holes have been filled (we never install partially instantiated libraries.) Put another way, an installed unit id is either fully instantiated, or not instantiated at all.

Installed unit identifiers look something like p+af23SAj2dZ219, or maybe just p if they don't use Backpack.

Constructors

InstalledUnitId 

Fields

Instances
Eq InstalledUnitId Source # 
Instance details

Defined in Module

Ord InstalledUnitId Source # 
Instance details

Defined in Module

BinaryStringRep InstalledUnitId Source # 
Instance details

Defined in Module

Outputable InstalledUnitId Source # 
Instance details

Defined in Module

Uniquable InstalledUnitId Source # 
Instance details

Defined in Module

Binary InstalledUnitId Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

toInstalledUnitId :: UnitId -> InstalledUnitId Source #

Lossy conversion to the on-disk InstalledUnitId for a component.

type ShHoleSubst = ModuleNameEnv Module Source #

Substitution on module variables, mapping module names to module identifiers.

unitIdIsDefinite :: UnitId -> Bool Source #

A UnitId is definite if it has no free holes.

unitIdFreeHoles :: UnitId -> UniqDSet ModuleName Source #

Retrieve the set of free holes of a UnitId.

newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId Source #

Create a new, un-hashed unit identifier.

newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId Source #

Create a new IndefUnitId given an explicit module substitution.

newSimpleUnitId :: ComponentId -> UnitId Source #

Create a new simple unit identifier (no holes) from a ComponentId.

hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString Source #

Generate a uniquely identifying FastString for a unit identifier. This is a one-way function. You can rely on one special property: if a unit identifier is in most general form, its FastString coincides with its ComponentId. This hash is completely internal to GHC and is not used for symbol names or file paths.

fsToUnitId :: FastString -> UnitId Source #

Create a new simple unit identifier from a FastString. Internally, this is primarily used to specify wired-in unit identifiers.

stableUnitIdCmp :: UnitId -> UnitId -> Ordering Source #

Compares package ids lexically, rather than by their Uniques

HOLE renaming

renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId Source #

Substitutes holes in a UnitId, suitable for renaming when an include occurs; see Note [Representation of module/name variable].

p[A=A] maps to p[A=B] with A=B.

renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module Source #

Substitutes holes in a Module. NOT suitable for being called directly on a nameModule, see Note [Representation of module/name variable]. p[A=A]:B maps to p[A=q():A]:B with A=q():A; similarly, A maps to q():A.

renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId Source #

Like 'renameHoleUnitId, but requires only PackageConfigMap so it can be used by Packages.

Generalization

splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule) Source #

Given a possibly on-the-fly instantiated module, split it into a Module that we definitely can find on-disk, as well as an instantiation if we need to instantiate it on the fly. If the instantiation is Nothing no on-the-fly renaming is needed.

Parsers

Wired-in UnitIds

Certain packages are known to the compiler, in that we know about certain entities that reside in these packages, and the compiler needs to declare static Modules and Names that refer to these packages. Hence the wired-in packages can't include version numbers, since we don't want to bake the version numbers of these packages into GHC.

So here's the plan. Wired-in packages are still versioned as normal in the packages database, and you can still have multiple versions of them installed. However, for each invocation of GHC, only a single instance of each wired-in package will be recognised (the desired one is selected via -package/-hide-package), and GHC will use the unversioned UnitId below when referring to it, including in .hi files and object file symbols. Unselected versions of wired-in packages will be ignored, as will any other package that depends directly or indirectly on it (much as if you had used -ignore-package).

mainUnitId :: UnitId Source #

This is the package Id for the current program. It is the default package Id if you don't specify a package name. We don't add this prefix to symbol names, since there can be only one main package per program.

The Module type

data Module Source #

A Module is a pair of a UnitId and a ModuleName.

Module variables (i.e. H) which can be instantiated to a specific module at some later point in time are represented with moduleUnitId set to holeUnitId (this allows us to avoid having to make moduleUnitId a partial operation.)

Constructors

Module !UnitId !ModuleName 
Instances
Eq Module Source # 
Instance details

Defined in Module

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Data Module Source # 
Instance details

Defined in Module

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module #

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) #

gmapT :: (forall b. Data b => b -> b) -> Module -> Module #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

Ord Module Source # 
Instance details

Defined in Module

NFData Module Source # 
Instance details

Defined in Module

Methods

rnf :: Module -> () #

Outputable Module Source # 
Instance details

Defined in Module

Uniquable Module Source # 
Instance details

Defined in Module

Binary Module Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

mkHoleModule :: ModuleName -> Module Source #

Create a module variable at some ModuleName. See Note [Representation of module/name variables]

stableModuleCmp :: Module -> Module -> Ordering Source #

This gives a stable ordering, as opposed to the Ord instance which gives an ordering based on the Uniques of the components, which may not be stable from run to run of the compiler.

class HasModule m where Source #

Methods

getModule :: m Module Source #

Instances
HasModule CoreM Source # 
Instance details

Defined in CoreMonad

HasModule TcS Source # 
Instance details

Defined in TcSMonad

ContainsModule env => HasModule (IOEnv env) Source # 
Instance details

Defined in IOEnv

Methods

getModule :: IOEnv env Module Source #

class ContainsModule t where Source #

Methods

extractModule :: t -> Module Source #

Instances
ContainsModule TcGblEnv Source # 
Instance details

Defined in TcRnTypes

ContainsModule DsGblEnv Source # 
Instance details

Defined in TcRnTypes

ContainsModule gbl => ContainsModule (Env gbl lcl) Source # 
Instance details

Defined in TcRnTypes

Methods

extractModule :: Env gbl lcl -> Module Source #

Installed unit ids and modules

data InstalledModuleEnv elt Source #

A map keyed off of InstalledModule

installedModuleEq :: InstalledModule -> Module -> Bool Source #

Test if a Module corresponds to a given InstalledModule, modulo instantiation.

installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool Source #

Test if a UnitId corresponds to a given InstalledUnitId, modulo instantiation.

newtype DefUnitId Source #

A DefUnitId is an InstalledUnitId with the invariant that it only refers to a definite library; i.e., one we have generated code for.

Constructors

DefUnitId 
Instances
Eq DefUnitId Source # 
Instance details

Defined in Module

Ord DefUnitId Source # 
Instance details

Defined in Module

Outputable DefUnitId Source # 
Instance details

Defined in Module

Binary DefUnitId Source # 
Instance details

Defined in Module

The ModuleLocation type

data ModLocation Source #

Module Location

Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them

Instances
Show ModLocation Source # 
Instance details

Defined in Module

Outputable ModLocation Source # 
Instance details

Defined in Module

addBootSuffix :: FilePath -> FilePath Source #

Add the -boot suffix to .hs, .hi and .o files

addBootSuffix_maybe :: Bool -> FilePath -> FilePath Source #

Add the -boot suffix if the Bool argument is True

addBootSuffixLocn :: ModLocation -> ModLocation Source #

Add the -boot suffix to all file paths associated with the module

Module mappings

data ModuleEnv elt Source #

A map keyed off of Modules

extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a Source #

plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a Source #

mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b Source #

extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a Source #

ModuleName mappings

type ModuleNameEnv elt = UniqFM elt Source #

A map keyed off of ModuleNames (actually, their Uniques)

type DModuleNameEnv elt = UniqDFM elt Source #

A map keyed off of ModuleNames (actually, their Uniques) Has deterministic folds and can be deterministically converted to a list

Sets of Modules

type ModuleSet = Set NDModule Source #

A set of Modules