Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- module GHC.Unit.Types
- module Language.Haskell.Syntax.Module.Name
- module GHC.Unit.Module.Location
- module GHC.Unit.Module.Env
- getModuleInstantiation :: Module -> (InstalledModule, Maybe InstantiatedModule)
- getUnitInstantiations :: Unit -> (UnitId, Maybe InstantiatedUnit)
- uninstantiateInstantiatedUnit :: InstantiatedUnit -> InstantiatedUnit
- uninstantiateInstantiatedModule :: InstantiatedModule -> InstantiatedModule
- mkHoleModule :: ModuleName -> GenModule (GenUnit u)
- isHoleModule :: GenModule (GenUnit u) -> Bool
- stableModuleCmp :: Module -> Module -> Ordering
- moduleStableString :: Module -> String
- moduleIsDefinite :: Module -> Bool
- class HasModule (m :: Type -> Type) where
- class ContainsModule t where
- extractModule :: t -> Module
- installedModuleEq :: InstalledModule -> Module -> Bool
Documentation
module GHC.Unit.Types
The ModuleName type
The ModLocation type
module GHC.Unit.Module.Location
ModuleEnv
module GHC.Unit.Module.Env
Generalization
getModuleInstantiation :: Module -> (InstalledModule, Maybe InstantiatedModule) 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.
getUnitInstantiations :: Unit -> (UnitId, Maybe InstantiatedUnit) Source #
Return the unit-id this unit is an instance of and the module instantiations (if any).
uninstantiateInstantiatedUnit :: InstantiatedUnit -> InstantiatedUnit Source #
Remove instantiations of the given instantiated unit
uninstantiateInstantiatedModule :: InstantiatedModule -> InstantiatedModule Source #
Remove instantiations of the given module instantiated unit
The Module type
mkHoleModule :: ModuleName -> GenModule (GenUnit u) Source #
Create a hole Module
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.
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"
class ContainsModule t where Source #
extractModule :: t -> Module Source #
Instances
ContainsModule DsGblEnv Source # | |
Defined in GHC.HsToCore.Types extractModule :: DsGblEnv -> Module Source # | |
ContainsModule TcGblEnv Source # | |
Defined in GHC.Tc.Types extractModule :: TcGblEnv -> Module Source # | |
ContainsModule gbl => ContainsModule (Env gbl lcl) Source # | |
Defined in GHC.Tc.Types extractModule :: Env gbl lcl -> Module Source # |
installedModuleEq :: InstalledModule -> Module -> Bool Source #
Test if a Module
corresponds to a given InstalledModule
,
modulo instantiation.