Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ModuleName
- pprModuleName :: ModuleName -> SDoc
- moduleNameFS :: ModuleName -> FastString
- moduleNameString :: ModuleName -> String
- moduleNameSlashes :: ModuleName -> String
- moduleNameColons :: ModuleName -> String
- moduleStableString :: Module -> String
- moduleFreeHoles :: Module -> UniqDSet ModuleName
- moduleIsDefinite :: Module -> Bool
- mkModuleName :: String -> ModuleName
- mkModuleNameFS :: FastString -> ModuleName
- stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
- newtype ComponentId = ComponentId FastString
- data UnitId
- unitIdFS :: UnitId -> FastString
- unitIdKey :: UnitId -> Unique
- data IndefUnitId = IndefUnitId {}
- data IndefModule = IndefModule {}
- indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId
- indefModuleToModule :: DynFlags -> IndefModule -> Module
- newtype InstalledUnitId = InstalledUnitId {}
- toInstalledUnitId :: UnitId -> InstalledUnitId
- type ShHoleSubst = ModuleNameEnv Module
- unitIdIsDefinite :: UnitId -> Bool
- unitIdString :: UnitId -> String
- unitIdFreeHoles :: UnitId -> UniqDSet ModuleName
- newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId
- newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId
- newSimpleUnitId :: ComponentId -> UnitId
- hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString
- fsToUnitId :: FastString -> UnitId
- stringToUnitId :: String -> UnitId
- stableUnitIdCmp :: UnitId -> UnitId -> Ordering
- renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module
- renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module
- splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule)
- splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId)
- generalizeIndefUnitId :: IndefUnitId -> IndefUnitId
- generalizeIndefModule :: IndefModule -> IndefModule
- parseModuleName :: ReadP ModuleName
- parseUnitId :: ReadP UnitId
- parseComponentId :: ReadP ComponentId
- parseModuleId :: ReadP Module
- parseModSubst :: ReadP [(ModuleName, Module)]
- primUnitId :: UnitId
- integerUnitId :: UnitId
- baseUnitId :: UnitId
- rtsUnitId :: UnitId
- thUnitId :: UnitId
- mainUnitId :: UnitId
- thisGhcUnitId :: UnitId
- isHoleModule :: Module -> Bool
- interactiveUnitId :: UnitId
- isInteractiveModule :: Module -> Bool
- wiredInUnitIds :: [UnitId]
- data Module = Module !UnitId !ModuleName
- moduleUnitId :: Module -> UnitId
- moduleName :: Module -> ModuleName
- pprModule :: Module -> SDoc
- mkModule :: UnitId -> ModuleName -> Module
- mkHoleModule :: ModuleName -> Module
- stableModuleCmp :: Module -> Module -> Ordering
- class HasModule m where
- class ContainsModule t where
- extractModule :: t -> Module
- data InstalledModule = InstalledModule {}
- data InstalledModuleEnv elt
- installedModuleEq :: InstalledModule -> Module -> Bool
- installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool
- installedUnitIdString :: InstalledUnitId -> String
- fsToInstalledUnitId :: FastString -> InstalledUnitId
- componentIdToInstalledUnitId :: ComponentId -> InstalledUnitId
- stringToInstalledUnitId :: String -> InstalledUnitId
- emptyInstalledModuleEnv :: InstalledModuleEnv a
- lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a
- extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a
- filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a
- delInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
- newtype DefUnitId = DefUnitId {}
- data ModLocation = ModLocation {}
- addBootSuffix :: FilePath -> FilePath
- removeBootSuffix :: FilePath -> FilePath
- addBootSuffix_maybe :: Bool -> FilePath -> FilePath
- addBootSuffixLocn :: ModLocation -> ModLocation
- addBootSuffixLocnOut :: ModLocation -> ModLocation
- data ModuleEnv elt
- elemModuleEnv :: Module -> ModuleEnv a -> Bool
- extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a
- extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a
- delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a
- plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a
- lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a
- mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b
- mkModuleEnv :: [(Module, a)] -> ModuleEnv a
- emptyModuleEnv :: ModuleEnv a
- moduleEnvKeys :: ModuleEnv a -> [Module]
- moduleEnvElts :: ModuleEnv a -> [a]
- moduleEnvToList :: ModuleEnv a -> [(Module, a)]
- unitModuleEnv :: Module -> a -> ModuleEnv a
- isEmptyModuleEnv :: ModuleEnv a -> Bool
- extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a
- filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a
- type ModuleNameEnv elt = UniqFM elt
- type DModuleNameEnv elt = UniqDFM elt
- type ModuleSet = Set NDModule
- emptyModuleSet :: ModuleSet
- mkModuleSet :: [Module] -> ModuleSet
- moduleSetElts :: ModuleSet -> [Module]
- extendModuleSet :: ModuleSet -> Module -> ModuleSet
- extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet
- delModuleSet :: ModuleSet -> Module -> ModuleSet
- elemModuleSet :: Module -> ModuleSet -> Bool
- intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- unitModuleSet :: Module -> ModuleSet
The ModuleName type
data ModuleName Source #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
pprModuleName :: ModuleName -> SDoc Source #
moduleNameFS :: ModuleName -> FastString Source #
moduleNameString :: ModuleName -> String Source #
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.
mkModuleName :: String -> ModuleName Source #
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering Source #
Compares module names lexically, rather than by their Unique
s
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
Instances
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
unitIdFS :: UnitId -> FastString Source #
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).
IndefUnitId | |
|
Instances
Eq IndefUnitId # | |
Defined in Module (==) :: IndefUnitId -> IndefUnitId -> Bool # (/=) :: IndefUnitId -> IndefUnitId -> Bool # | |
Ord IndefUnitId # | |
Defined in Module compare :: IndefUnitId -> IndefUnitId -> Ordering # (<) :: IndefUnitId -> IndefUnitId -> Bool # (<=) :: IndefUnitId -> IndefUnitId -> Bool # (>) :: IndefUnitId -> IndefUnitId -> Bool # (>=) :: IndefUnitId -> IndefUnitId -> Bool # max :: IndefUnitId -> IndefUnitId -> IndefUnitId # min :: IndefUnitId -> IndefUnitId -> IndefUnitId # | |
Outputable IndefUnitId # | |
Binary IndefUnitId # | |
data IndefModule Source #
Instances
Eq IndefModule # | |
Defined in Module (==) :: IndefModule -> IndefModule -> Bool # (/=) :: IndefModule -> IndefModule -> Bool # | |
Ord IndefModule # | |
Defined in Module compare :: IndefModule -> IndefModule -> Ordering # (<) :: IndefModule -> IndefModule -> Bool # (<=) :: IndefModule -> IndefModule -> Bool # (>) :: IndefModule -> IndefModule -> Bool # (>=) :: IndefModule -> IndefModule -> Bool # max :: IndefModule -> IndefModule -> IndefModule # min :: IndefModule -> IndefModule -> IndefModule # | |
Outputable IndefModule # | |
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).
indefModuleToModule :: DynFlags -> IndefModule -> Module Source #
Injects an IndefModule
to Module
(see also
indefUnitIdToUnitId
.
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.
InstalledUnitId | |
|
Instances
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.
unitIdString :: UnitId -> String Source #
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.
stringToUnitId :: String -> UnitId Source #
stableUnitIdCmp :: UnitId -> UnitId -> Ordering Source #
Compares package ids lexically, rather than by their Unique
s
HOLE renaming
renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId Source #
renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module Source #
renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId Source #
Like 'renameHoleUnitId, but requires only PackageConfigMap
so it can be used by Packages.
renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module Source #
Like renameHoleModule
, 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.
splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId) Source #
See splitModuleInsts
.
Parsers
parseModSubst :: ReadP [(ModuleName, Module)] Source #
Wired-in UnitIds
primUnitId :: UnitId Source #
baseUnitId :: UnitId Source #
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.
isHoleModule :: Module -> Bool Source #
isInteractiveModule :: Module -> Bool Source #
wiredInUnitIds :: [UnitId] Source #
The Module type
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.)
Instances
moduleUnitId :: Module -> UnitId Source #
moduleName :: Module -> ModuleName Source #
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 Unique
s of the components, which may
not be stable from run to run of the compiler.
class ContainsModule t where Source #
extractModule :: t -> Module Source #
Instances
ContainsModule TcGblEnv # | |
ContainsModule DsGblEnv # | |
ContainsModule gbl => ContainsModule (Env gbl lcl) # | |
Installed unit ids and modules
data InstalledModule Source #
A InstalledModule
is a Module
which contains a InstalledUnitId
.
Instances
Eq InstalledModule # | |
Defined in Module (==) :: InstalledModule -> InstalledModule -> Bool # (/=) :: InstalledModule -> InstalledModule -> Bool # | |
Ord InstalledModule # | |
Defined in Module compare :: InstalledModule -> InstalledModule -> Ordering # (<) :: InstalledModule -> InstalledModule -> Bool # (<=) :: InstalledModule -> InstalledModule -> Bool # (>) :: InstalledModule -> InstalledModule -> Bool # (>=) :: InstalledModule -> InstalledModule -> Bool # max :: InstalledModule -> InstalledModule -> InstalledModule # min :: InstalledModule -> InstalledModule -> InstalledModule # | |
Outputable InstalledModule # | |
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.
lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a Source #
extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a Source #
filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a 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.
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
ModLocation | |
|
Instances
addBootSuffix :: FilePath -> FilePath Source #
Add the -boot
suffix to .hs, .hi and .o files
removeBootSuffix :: FilePath -> FilePath Source #
Remove 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
addBootSuffixLocnOut :: ModLocation -> ModLocation Source #
Add the -boot
suffix to all output file paths associated with the
module, not including the input file itself
Module mappings
lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a Source #
mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b Source #
mkModuleEnv :: [(Module, a)] -> ModuleEnv a Source #
emptyModuleEnv :: ModuleEnv a Source #
moduleEnvKeys :: ModuleEnv a -> [Module] Source #
moduleEnvElts :: ModuleEnv a -> [a] Source #
moduleEnvToList :: ModuleEnv a -> [(Module, a)] Source #
unitModuleEnv :: Module -> a -> ModuleEnv a Source #
isEmptyModuleEnv :: ModuleEnv a -> Bool Source #
ModuleName mappings
type ModuleNameEnv elt = UniqFM elt Source #
A map keyed off of ModuleName
s (actually, their Unique
s)
type DModuleNameEnv elt = UniqDFM elt Source #
A map keyed off of ModuleName
s (actually, their Unique
s)
Has deterministic folds and can be deterministically converted to a list
Sets of Modules
mkModuleSet :: [Module] -> ModuleSet Source #
moduleSetElts :: ModuleSet -> [Module] Source #
unitModuleSet :: Module -> ModuleSet Source #