ghc-8.0.0.20160204: 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 
Data ModuleName 

Methods

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

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

toConstr :: ModuleName -> Constr Source

dataTypeOf :: ModuleName -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord ModuleName 
BinaryStringRep ModuleName 
Outputable ModuleName 
Uniquable ModuleName 
Binary ModuleName 

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 underscores.

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"

stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering Source

Compares module names lexically, rather than by their Uniques

The UnitId type

data UnitId Source

A string which uniquely identifies a package. For wired-in packages, it is just the package name, but for user compiled packages, it is a hash. ToDo: when the key is a hash, we can do more clever things than store the hex representation and hash-cons those strings.

Instances

Eq UnitId 

Methods

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

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

Data UnitId 

Methods

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

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

toConstr :: UnitId -> Constr Source

dataTypeOf :: UnitId -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord UnitId 
BinaryStringRep UnitId 
Outputable UnitId 
Uniquable UnitId 
Binary UnitId 

stableUnitIdCmp :: UnitId -> UnitId -> Ordering Source

Compares package ids lexically, rather than by their Uniques

Wired-in UnitIds

 

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.

holeUnitId :: UnitId Source

This is a fake package id used to provide identities to any un-implemented signatures. The set of hole identities is global over an entire compilation.

The Module type

data Module Source

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

Constructors

Module 

Instances

Eq Module 

Methods

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

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

Data Module 

Methods

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

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

toConstr :: Module -> Constr Source

dataTypeOf :: Module -> DataType Source

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

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

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

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

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

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

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

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

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

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

Ord Module 
Outputable Module 
Uniquable Module 
Binary Module 

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

Minimal complete definition

getModule

Methods

getModule :: m Module Source

class ContainsModule t where Source

Minimal complete definition

extractModule

Methods

extractModule :: t -> Module Source

The ModuleLocation type

data ModLocation Source

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

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

foldModuleEnv :: (a -> b -> b) -> b -> ModuleEnv a -> 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)

Sets of Modules

type ModuleSet = Map Module () Source

A set of Modules