Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data ModuleName
- pprModuleName :: ModuleName -> SDoc
- moduleNameFS :: ModuleName -> FastString
- moduleNameString :: ModuleName -> String
- moduleNameSlashes :: ModuleName -> String
- moduleNameColons :: ModuleName -> String
- mkModuleName :: String -> ModuleName
- mkModuleNameFS :: FastString -> ModuleName
- stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
- data PackageKey
- fsToPackageKey :: FastString -> PackageKey
- packageKeyFS :: PackageKey -> FastString
- stringToPackageKey :: String -> PackageKey
- packageKeyString :: PackageKey -> String
- stablePackageKeyCmp :: PackageKey -> PackageKey -> Ordering
- primPackageKey :: PackageKey
- integerPackageKey :: PackageKey
- basePackageKey :: PackageKey
- rtsPackageKey :: PackageKey
- thPackageKey :: PackageKey
- dphSeqPackageKey :: PackageKey
- dphParPackageKey :: PackageKey
- mainPackageKey :: PackageKey
- thisGhcPackageKey :: PackageKey
- interactivePackageKey :: PackageKey
- isInteractiveModule :: Module -> Bool
- wiredInPackageKeys :: [PackageKey]
- data Module = Module {}
- pprModule :: Module -> SDoc
- mkModule :: PackageKey -> ModuleName -> Module
- stableModuleCmp :: Module -> Module -> Ordering
- class HasModule m where
- class ContainsModule t where
- extractModule :: t -> Module
- data ModLocation = ModLocation {}
- addBootSuffix :: FilePath -> FilePath
- addBootSuffix_maybe :: Bool -> FilePath -> FilePath
- addBootSuffixLocn :: 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
- foldModuleEnv :: (a -> b -> b) -> b -> ModuleEnv a -> b
- extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a
- filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a
- type ModuleNameEnv elt = UniqFM elt
- type ModuleSet = Map Module ()
- emptyModuleSet :: ModuleSet
- mkModuleSet :: [Module] -> ModuleSet
- moduleSetElts :: ModuleSet -> [Module]
- extendModuleSet :: ModuleSet -> Module -> ModuleSet
- elemModuleSet :: Module -> ModuleSet -> Bool
The ModuleName type
data ModuleName Source
A ModuleName is essentially a simple string, e.g. Data.List
.
pprModuleName :: ModuleName -> SDoc 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 underscores.
mkModuleName :: String -> ModuleName Source
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering Source
Compares module names lexically, rather than by their Unique
s
The PackageKey type
data PackageKey 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.
stablePackageKeyCmp :: PackageKey -> PackageKey -> Ordering Source
Compares package ids lexically, rather than by their Unique
s
Wired-in PackageKeys
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 PackageKey
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
).
mainPackageKey :: PackageKey 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.
isInteractiveModule :: Module -> Bool Source
The Module type
A Module is a pair of a PackageKey
and a ModuleName
.
mkModule :: PackageKey -> ModuleName -> Module Source
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
ContainsModule TcGblEnv | |
ContainsModule DsGblEnv | |
ContainsModule gbl => ContainsModule (Env gbl lcl) |
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
elemModuleEnv :: Module -> ModuleEnv a -> Bool Source
extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a Source
extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a Source
extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a Source
plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a Source
delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a Source
delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a Source
plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a Source
lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a Source
lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a Source
mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b Source
mkModuleEnv :: [(Module, a)] -> 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
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 ModuleName
s (actually, their Unique
s)
Sets of Modules
mkModuleSet :: [Module] -> ModuleSet Source
moduleSetElts :: ModuleSet -> [Module] Source
extendModuleSet :: ModuleSet -> Module -> ModuleSet Source
elemModuleSet :: Module -> ModuleSet -> Bool Source