Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Unit & Module types
This module is used to resolve the loops between Unit and Module types (Module references a Unit and vice-versa).
Synopsis
- data GenModule unit = Module {
- moduleUnit :: !unit
- moduleName :: !ModuleName
- type Module = GenModule Unit
- type InstalledModule = GenModule UnitId
- type InstantiatedModule = GenModule InstantiatedUnit
- mkModule :: u -> ModuleName -> GenModule u
- pprModule :: Module -> SDoc
- pprInstantiatedModule :: InstantiatedModule -> SDoc
- moduleFreeHoles :: GenModule (GenUnit u) -> UniqDSet ModuleName
- data GenUnit uid
- = RealUnit !(Definite uid)
- | VirtUnit !(GenInstantiatedUnit uid)
- | HoleUnit
- type Unit = GenUnit UnitId
- newtype UnitId = UnitId {}
- data GenInstantiatedUnit unit = InstantiatedUnit {
- instUnitFS :: !FastString
- instUnitKey :: !Unique
- instUnitInstanceOf :: !(Indefinite unit)
- instUnitInsts :: !(GenInstantiations unit)
- instUnitHoles :: UniqDSet ModuleName
- type InstantiatedUnit = GenInstantiatedUnit UnitId
- type IndefUnitId = Indefinite UnitId
- type DefUnitId = Definite UnitId
- type Instantiations = GenInstantiations UnitId
- type GenInstantiations unit = [(ModuleName, GenModule (GenUnit unit))]
- mkGenInstantiatedUnit :: (unit -> FastString) -> Indefinite unit -> GenInstantiations unit -> GenInstantiatedUnit unit
- mkInstantiatedUnit :: IndefUnitId -> Instantiations -> InstantiatedUnit
- mkInstantiatedUnitHash :: IndefUnitId -> Instantiations -> FastString
- mkGenVirtUnit :: (unit -> FastString) -> Indefinite unit -> [(ModuleName, GenModule (GenUnit unit))] -> GenUnit unit
- mkVirtUnit :: IndefUnitId -> Instantiations -> Unit
- mapGenUnit :: (u -> v) -> (v -> FastString) -> GenUnit u -> GenUnit v
- unitFreeModuleHoles :: GenUnit u -> UniqDSet ModuleName
- fsToUnit :: FastString -> Unit
- unitFS :: Unit -> FastString
- unitString :: Unit -> String
- toUnitId :: Unit -> UnitId
- virtualUnitId :: InstantiatedUnit -> UnitId
- stringToUnit :: String -> Unit
- stableUnitCmp :: Unit -> Unit -> Ordering
- unitIsDefinite :: Unit -> Bool
- unitIdString :: UnitId -> String
- stringToUnitId :: String -> UnitId
- newtype Definite unit = Definite {
- unDefinite :: unit
- data Indefinite unit = Indefinite {
- indefUnit :: !unit
- indefUnitPprInfo :: Maybe UnitPprInfo
- primUnitId :: UnitId
- bignumUnitId :: UnitId
- baseUnitId :: UnitId
- rtsUnitId :: UnitId
- thUnitId :: UnitId
- mainUnitId :: UnitId
- thisGhcUnitId :: UnitId
- interactiveUnitId :: UnitId
- primUnit :: Unit
- bignumUnit :: Unit
- baseUnit :: Unit
- rtsUnit :: Unit
- thUnit :: Unit
- mainUnit :: Unit
- thisGhcUnit :: Unit
- interactiveUnit :: Unit
- isInteractiveModule :: Module -> Bool
- wiredInUnitIds :: [UnitId]
- data IsBootInterface
- data GenWithIsBoot mod = GWIB {
- gwib_mod :: mod
- gwib_isBoot :: IsBootInterface
- type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
- type ModuleWithIsBoot = GenWithIsBoot Module
Modules
A generic module is a pair of a unit identifier and a ModuleName
.
Module | |
|
Instances
Functor GenModule Source # | |
Uniquable Module Source # | |
Outputable InstalledModule Source # | |
Defined in GHC.Unit.Types | |
Outputable InstantiatedModule Source # | |
Defined in GHC.Unit.Types | |
Outputable Module Source # | |
Data unit => Data (GenModule unit) Source # | |
Defined in GHC.Unit.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenModule unit -> c (GenModule unit) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenModule unit) Source # toConstr :: GenModule unit -> Constr Source # dataTypeOf :: GenModule unit -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenModule unit)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GenModule unit)) Source # gmapT :: (forall b. Data b => b -> b) -> GenModule unit -> GenModule unit Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GenModule unit -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenModule unit -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source # | |
NFData (GenModule a) Source # | |
Defined in GHC.Unit.Types | |
Binary a => Binary (GenModule a) Source # | |
Eq unit => Eq (GenModule unit) Source # | |
Ord unit => Ord (GenModule unit) Source # | |
Defined in GHC.Unit.Types compare :: GenModule unit -> GenModule unit -> Ordering # (<) :: GenModule unit -> GenModule unit -> Bool # (<=) :: GenModule unit -> GenModule unit -> Bool # (>) :: GenModule unit -> GenModule unit -> Bool # (>=) :: GenModule unit -> GenModule unit -> Bool # |
type InstalledModule = GenModule UnitId Source #
A InstalledModule
is a Module
whose unit is identified with an
UnitId
.
type InstantiatedModule = GenModule InstantiatedUnit Source #
An InstantiatedModule
is a Module
whose unit is identified with an InstantiatedUnit
.
mkModule :: u -> ModuleName -> GenModule u Source #
moduleFreeHoles :: GenModule (GenUnit u) -> 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.
Units
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 Unit
:
1) It can be a RealUnit
, in which case we just have a DefUnitId
that
uniquely identifies some fully compiled, installed library we have on disk.
2) It can be an VirtUnit
. 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
InstantiatedUnit
, which explicitly records the instantiation, so that we
can substitute over it.
RealUnit !(Definite uid) | Installed definite unit (either a fully instantiated unit or a closed unit) |
VirtUnit !(GenInstantiatedUnit uid) | Virtual unit instantiated on-the-fly. It may be definite if all the holes are instantiated but we don't have code objects for it. |
HoleUnit | Fake hole unit |
Instances
Data Unit Source # | |
Defined in GHC.Unit.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unit -> c Unit Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unit Source # toConstr :: Unit -> Constr Source # dataTypeOf :: Unit -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unit) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unit) Source # gmapT :: (forall b. Data b => b -> b) -> Unit -> Unit Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Unit -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source # | |
Show Unit Source # | |
NFData Unit Source # | |
Defined in GHC.Unit.Types | |
Uniquable Module Source # | |
Uniquable Unit Source # | |
Binary Unit Source # | |
Outputable Module Source # | |
Outputable Unit Source # | |
Eq Unit Source # | |
Ord Unit Source # | |
A UnitId identifies a built library in a database and is used to generate unique symbols, etc. It's usually of the form:
pkgname-1.2:libname+hash
These UnitId 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 as we can cheaply instantiate them on-the-fly, cf VirtUnit). Put another way, an installed unit id is either fully instantiated, or not instantiated at all.
UnitId | |
|
Instances
data GenInstantiatedUnit unit Source #
An instantiated unit.
It identifies an indefinite library (with holes) that has been instantiated.
This unit may be indefinite or not (i.e. with remaining holes or not). If it is definite, we don't know if it has already been compiled and installed in a database. Nevertheless, we have a mechanism called "improvement" to try to match a fully instantiated unit with existing compiled and installed units: see Note [VirtUnit to RealUnit improvement].
An indefinite unit identifier pretty-prints to something like
p[H=H,A=aimpl:A>]
(p
is the IndefUnitId
, and the
brackets enclose the module substitution).
InstantiatedUnit | |
|
Instances
type IndefUnitId = Indefinite UnitId Source #
An IndefUnitId
is an UnitId
with the invariant that it only
refers to an indefinite library; i.e., one that can be instantiated.
type Instantiations = GenInstantiations UnitId Source #
type GenInstantiations unit = [(ModuleName, GenModule (GenUnit unit))] Source #
mkGenInstantiatedUnit :: (unit -> FastString) -> Indefinite unit -> GenInstantiations unit -> GenInstantiatedUnit unit Source #
Create a new GenInstantiatedUnit
given an explicit module substitution.
mkInstantiatedUnit :: IndefUnitId -> Instantiations -> InstantiatedUnit Source #
Create a new InstantiatedUnit
given an explicit module substitution.
mkGenVirtUnit :: (unit -> FastString) -> Indefinite unit -> [(ModuleName, GenModule (GenUnit unit))] -> GenUnit unit Source #
Smart constructor for instantiated GenUnit
mkVirtUnit :: IndefUnitId -> Instantiations -> Unit Source #
Smart constructor for VirtUnit
mapGenUnit :: (u -> v) -> (v -> FastString) -> GenUnit u -> GenUnit v Source #
Map over the unit type of a GenUnit
unitFreeModuleHoles :: GenUnit u -> UniqDSet ModuleName Source #
Retrieve the set of free module holes of a Unit
.
fsToUnit :: FastString -> Unit Source #
Create a new simple unit identifier from a FastString
. Internally,
this is primarily used to specify wired-in unit identifiers.
unitFS :: Unit -> FastString Source #
unitString :: Unit -> String Source #
toUnitId :: Unit -> UnitId Source #
Return the UnitId of the Unit. For on-the-fly instantiated units, return the UnitId of the indefinite unit this unit is an instance of.
virtualUnitId :: InstantiatedUnit -> UnitId Source #
Return the virtual UnitId of an on-the-fly instantiated unit.
stringToUnit :: String -> Unit Source #
stableUnitCmp :: Unit -> Unit -> Ordering Source #
Compares unit ids lexically, rather than by their Unique
s
Unit Ids
unitIdString :: UnitId -> String Source #
stringToUnitId :: String -> UnitId Source #
Utils
newtype Definite unit Source #
A definite unit (i.e. without any free module hole)
Definite | |
|
Instances
Functor Definite Source # | |
Binary unit => Binary (Definite unit) Source # | |
Outputable unit => Outputable (Definite unit) Source # | |
Eq unit => Eq (Definite unit) Source # | |
Ord unit => Ord (Definite unit) Source # | |
Defined in GHC.Unit.Types compare :: Definite unit -> Definite unit -> Ordering # (<) :: Definite unit -> Definite unit -> Bool # (<=) :: Definite unit -> Definite unit -> Bool # (>) :: Definite unit -> Definite unit -> Bool # (>=) :: Definite unit -> Definite unit -> Bool # |
data Indefinite unit Source #
Indefinite | |
|
Instances
Wired-in units
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.
bignumUnit :: Unit Source #
thisGhcUnit :: Unit Source #
isInteractiveModule :: Module -> Bool Source #
wiredInUnitIds :: [UnitId] Source #
Boot modules
data IsBootInterface Source #
Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.
Instances
data GenWithIsBoot mod Source #
This data type just pairs a value mod
with an IsBootInterface flag. In
practice, mod
is usually a Module
or ModuleName
'.
GWIB | |
|
Instances
type ModuleWithIsBoot = GenWithIsBoot Module Source #