|
|
|
|
|
|
Synopsis |
|
|
|
|
The ModuleName type
|
|
data ModuleName |
A ModuleName is essentially a simple string, e.g. Data.List.
| Instances | |
|
|
pprModuleName :: ModuleName -> SDoc |
|
moduleNameFS :: ModuleName -> FastString |
|
moduleNameString :: ModuleName -> String |
|
moduleNameSlashes :: ModuleName -> String |
Returns the string version of the module name, with dots replaced by slashes
|
|
mkModuleName :: String -> ModuleName |
|
mkModuleNameFS :: FastString -> ModuleName |
|
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering |
Compares module names lexically, rather than by their Uniques
|
|
The PackageId type
|
|
data PackageId |
Essentially just a string identifying a package, including the version: e.g. parsec-1.0
| Instances | |
|
|
fsToPackageId :: FastString -> PackageId |
|
packageIdFS :: PackageId -> FastString |
|
stringToPackageId :: String -> PackageId |
|
packageIdString :: PackageId -> String |
|
stablePackageIdCmp :: PackageId -> PackageId -> Ordering |
Compares package ids lexically, rather than by their Uniques
|
|
Wired-in PackageIds
|
|
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 PackageId 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).
|
|
primPackageId :: PackageId |
|
integerPackageId :: PackageId |
|
basePackageId :: PackageId |
|
rtsPackageId :: PackageId |
|
haskell98PackageId :: PackageId |
|
sybPackageId :: PackageId |
|
thPackageId :: PackageId |
|
dphSeqPackageId :: PackageId |
|
dphParPackageId :: PackageId |
|
mainPackageId :: PackageId |
|
The Module type
|
|
data Module |
|
|
modulePackageId :: Module -> PackageId |
|
moduleName :: Module -> ModuleName |
|
pprModule :: Module -> SDoc |
|
mkModule :: PackageId -> ModuleName -> Module |
|
stableModuleCmp :: Module -> Module -> Ordering |
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.
|
|
The ModuleLocation type
|
|
data ModLocation |
Where a module lives on the file system: the actual locations
of the .hs, .hi and .o files, if we have them
| Constructors | | Instances | |
|
|
addBootSuffix :: FilePath -> FilePath |
Add the -boot suffix to .hs, .hi and .o files
|
|
addBootSuffix_maybe :: Bool -> FilePath -> FilePath |
Add the -boot suffix if the Bool argument is True
|
|
addBootSuffixLocn :: ModLocation -> ModLocation |
Add the -boot suffix to all file paths associated with the module
|
|
Module mappings
|
|
type ModuleEnv elt = FiniteMap Module elt |
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.
A map keyed off of Modules
|
|
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] |
|
unitModuleEnv :: Module -> a -> ModuleEnv a |
|
isEmptyModuleEnv :: ModuleEnv a -> Bool |
|
foldModuleEnv :: (a -> b -> b) -> b -> ModuleEnv a -> b |
|
extendModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a |
|
filterModuleEnv :: (a -> Bool) -> ModuleEnv a -> ModuleEnv a |
|
ModuleName mappings
|
|
type ModuleNameEnv elt = UniqFM elt |
A map keyed off of ModuleNames (actually, their Uniques)
|
|
Sets of Modules
|
|
type ModuleSet = FiniteMap Module () |
A set of Modules
|
|
emptyModuleSet :: ModuleSet |
|
mkModuleSet :: [Module] -> ModuleSet |
|
moduleSetElts :: ModuleSet -> [Module] |
|
extendModuleSet :: ModuleSet -> Module -> ModuleSet |
|
elemModuleSet :: Module -> ModuleSet -> Bool |
|
Produced by Haddock version 2.4.2 |