Copyright | Isaac Jones 2003-2004 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Once a package has been configured we have resolved conditionals and
dependencies, configured the compiler and other needed external programs.
The LocalBuildInfo
is used to hold all this information. It holds the
install dirs, the compiler, the exact package dependencies, the configured
programs, the package database to use and a bunch of miscellaneous configure
flags. It gets saved and reloaded from a file (dist/setup-config
). It gets
passed in to very many subsequent build actions.
Synopsis
- data LocalBuildInfo where
- NewLocalBuildInfo { }
- pattern LocalBuildInfo :: ConfigFlags -> FlagAssignment -> ComponentRequestedSpec -> [String] -> InstallDirTemplates -> Compiler -> Platform -> Maybe (SymbolicPath Pkg File) -> Graph ComponentLocalBuildInfo -> Map ComponentName [ComponentLocalBuildInfo] -> Map (PackageName, ComponentName) PromisedComponent -> InstalledPackageIndex -> PackageDescription -> ProgramDb -> PackageDBStack -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> OptimisationLevel -> DebugInfoLevel -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> [UnitId] -> Bool -> LocalBuildInfo
- localComponentId :: LocalBuildInfo -> ComponentId
- localUnitId :: LocalBuildInfo -> UnitId
- localCompatPackageKey :: LocalBuildInfo -> String
- buildDir :: LocalBuildInfo -> SymbolicPath Pkg (Dir Build)
- packageRoot :: CommonSetupFlags -> FilePath
- progPrefix :: LocalBuildInfo -> PathTemplate
- progSuffix :: LocalBuildInfo -> PathTemplate
- interpretSymbolicPathLBI :: LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
- mbWorkDirLBI :: LocalBuildInfo -> Maybe (SymbolicPath CWD (Dir Pkg))
- absoluteWorkingDirLBI :: LocalBuildInfo -> IO (AbsolutePath (Dir Pkg))
- buildWays :: LocalBuildInfo -> (Bool -> [BuildWay], Bool -> BuildWay, BuildWay)
- data Component
- data ComponentName where
- CLibName LibraryName
- CNotLibName NotLibComponentName
- pattern CBenchName :: UnqualComponentName -> ComponentName
- pattern CExeName :: UnqualComponentName -> ComponentName
- pattern CFLibName :: UnqualComponentName -> ComponentName
- pattern CTestName :: UnqualComponentName -> ComponentName
- data LibraryName
- = LMainLibName
- | LSubLibName UnqualComponentName
- defaultLibName :: LibraryName
- showComponentName :: ComponentName -> String
- componentNameString :: ComponentName -> Maybe UnqualComponentName
- data ComponentLocalBuildInfo
- = LibComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentIsIndefinite_ :: Bool
- componentInstantiatedWith :: [(ModuleName, OpenModule)]
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- componentCompatPackageKey :: String
- componentCompatPackageName :: MungedPackageName
- componentExposedModules :: [ExposedModule]
- componentIsPublic :: Bool
- | FLibComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | ExeComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | TestComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | BenchComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- = LibComponentLocalBuildInfo {
- componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir Build)
- foldComponent :: (Library -> a) -> (ForeignLib -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a
- componentName :: Component -> ComponentName
- componentBuildInfo :: Component -> BuildInfo
- componentBuildable :: Component -> Bool
- pkgComponents :: PackageDescription -> [Component]
- pkgBuildableComponents :: PackageDescription -> [Component]
- lookupComponent :: PackageDescription -> ComponentName -> Maybe Component
- getComponent :: PackageDescription -> ComponentName -> Component
- allComponentsInBuildOrder :: LocalBuildInfo -> [ComponentLocalBuildInfo]
- depLibraryPaths :: Bool -> Bool -> LocalBuildInfo -> ComponentLocalBuildInfo -> IO [FilePath]
- allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName]
- withAllComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withBenchLBI :: PackageDescription -> LocalBuildInfo -> (Benchmark -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withTestLBI :: PackageDescription -> LocalBuildInfo -> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- enabledTestLBIs :: PackageDescription -> LocalBuildInfo -> [(TestSuite, ComponentLocalBuildInfo)]
- enabledBenchLBIs :: PackageDescription -> LocalBuildInfo -> [(Benchmark, ComponentLocalBuildInfo)]
- data InstallDirs dir = InstallDirs {
- prefix :: dir
- bindir :: dir
- libdir :: dir
- libsubdir :: dir
- dynlibdir :: dir
- flibdir :: dir
- libexecdir :: dir
- libexecsubdir :: dir
- includedir :: dir
- datadir :: dir
- datasubdir :: dir
- docdir :: dir
- mandir :: dir
- htmldir :: dir
- haddockdir :: dir
- sysconfdir :: dir
- type InstallDirTemplates = InstallDirs PathTemplate
- data CopyDest
- data PathTemplate
- data PathTemplateVariable
- type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)]
- defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
- defaultInstallDirs' :: Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
- combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c
- substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
- toPathTemplate :: FilePath -> PathTemplate
- fromPathTemplate :: PathTemplate -> FilePath
- combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplate
- initialPathTemplateEnv :: PackageIdentifier -> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
- platformTemplateEnv :: Platform -> PathTemplateEnv
- compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
- packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv
- abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
- installDirsTemplateEnv :: InstallDirs PathTemplate -> PathTemplateEnv
- absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest -> InstallDirs FilePath
- prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath)
- absoluteInstallCommandDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
- absoluteComponentInstallDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
- prefixRelativeComponentInstallDirs :: PackageId -> LocalBuildInfo -> UnitId -> InstallDirs (Maybe FilePath)
- substPathTemplate :: PackageId -> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath
Documentation
data LocalBuildInfo Source #
Data cached after configuration step. See also
ConfigFlags
.
NewLocalBuildInfo | |
|
pattern LocalBuildInfo :: ConfigFlags -> FlagAssignment -> ComponentRequestedSpec -> [String] -> InstallDirTemplates -> Compiler -> Platform -> Maybe (SymbolicPath Pkg File) -> Graph ComponentLocalBuildInfo -> Map ComponentName [ComponentLocalBuildInfo] -> Map (PackageName, ComponentName) PromisedComponent -> InstalledPackageIndex -> PackageDescription -> ProgramDb -> PackageDBStack -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> OptimisationLevel -> DebugInfoLevel -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> [UnitId] -> Bool -> LocalBuildInfo | This pattern synonym is for backwards compatibility, to adapt
to |
Instances
localComponentId :: LocalBuildInfo -> ComponentId Source #
Extract the ComponentId
from the public library component of a
LocalBuildInfo
if it exists, or make a fake component ID based
on the package ID.
localUnitId :: LocalBuildInfo -> UnitId Source #
Extract the UnitId
from the library component of a
LocalBuildInfo
if it exists, or make a fake unit ID based on
the package ID.
localCompatPackageKey :: LocalBuildInfo -> String Source #
Extract the compatibility package key from the public library component of a
LocalBuildInfo
if it exists, or make a fake package key based
on the package ID.
Convenience accessors
buildDir :: LocalBuildInfo -> SymbolicPath Pkg (Dir Build) Source #
packageRoot :: CommonSetupFlags -> FilePath Source #
The (relative or absolute) path to the package root, based on
- the working directory flag
- the
.cabal
path
interpretSymbolicPathLBI :: LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath Source #
Interpret a symbolic path with respect to the working directory
stored in LocalBuildInfo
.
Use this before directly interacting with the file system.
NB: when invoking external programs (such as GHC
), it is preferable to set
the working directory of the process rather than calling this function, as
this function will turn relative paths into absolute paths if the working
directory is an absolute path. This can degrade error messages, or worse,
break the behaviour entirely (because the program might expect certain paths
to be relative).
See Note [Symbolic paths] in Distribution.Utils.Path
mbWorkDirLBI :: LocalBuildInfo -> Maybe (SymbolicPath CWD (Dir Pkg)) Source #
Retrieve an optional working directory from LocalBuildInfo
.
absoluteWorkingDirLBI :: LocalBuildInfo -> IO (AbsolutePath (Dir Pkg)) Source #
Absolute path to the current working directory.
buildWays :: LocalBuildInfo -> (Bool -> [BuildWay], Bool -> BuildWay, BuildWay) Source #
Returns a list of ways, in the order which they should be built, and the way we build executable and foreign library components.
Ideally all this info should be fixed at configure time and not dependent on
additional info but LocalBuildInfo
is per package (not per component) so it's
currently not possible to configure components to be built in certain ways.
Buildable package components
Instances
data ComponentName #
CLibName LibraryName | |
CNotLibName NotLibComponentName |
pattern CBenchName :: UnqualComponentName -> ComponentName | |
pattern CExeName :: UnqualComponentName -> ComponentName | |
pattern CFLibName :: UnqualComponentName -> ComponentName | |
pattern CTestName :: UnqualComponentName -> ComponentName |
Instances
data LibraryName #
LMainLibName | |
LSubLibName UnqualComponentName |
Instances
componentNameString :: ComponentName -> Maybe UnqualComponentName #
data ComponentLocalBuildInfo Source #
The first five fields are common across all algebraic variants.
LibComponentLocalBuildInfo | |
| |
FLibComponentLocalBuildInfo | |
| |
ExeComponentLocalBuildInfo | |
| |
TestComponentLocalBuildInfo | |
| |
BenchComponentLocalBuildInfo | |
|
Instances
componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir Build) Source #
foldComponent :: (Library -> a) -> (ForeignLib -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a #
componentName :: Component -> ComponentName #
componentBuildInfo :: Component -> BuildInfo #
componentBuildable :: Component -> Bool #
pkgComponents :: PackageDescription -> [Component] #
pkgBuildableComponents :: PackageDescription -> [Component] #
lookupComponent :: PackageDescription -> ComponentName -> Maybe Component #
getComponent :: PackageDescription -> ComponentName -> Component #
:: Bool | Building for inplace? |
-> Bool | Generate prefix-relative library paths |
-> LocalBuildInfo | |
-> ComponentLocalBuildInfo | Component that is being built |
-> IO [FilePath] |
Determine the directories containing the dynamic libraries of the transitive dependencies of the component we are building.
When wanted, and possible, returns paths relative to the installDirs prefix
allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName] Source #
Get all module names that needed to be built by GHC; i.e., all
of these ModuleName
s have interface files associated with them
that need to be installed.
withAllComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each buildable Library
or Executable
(Component)
in the PackageDescription, subject to the build order specified by the
compBuildOrder
field of the given LocalBuildInfo
withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled library
in the package
description with the ComponentLocalBuildInfo
.
withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled Executable
in the package
description. Extended version of withExe
that also gives corresponding
build info.
withBenchLBI :: PackageDescription -> LocalBuildInfo -> (Benchmark -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled Benchmark
in the package
description.
withTestLBI :: PackageDescription -> LocalBuildInfo -> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
enabledTestLBIs :: PackageDescription -> LocalBuildInfo -> [(TestSuite, ComponentLocalBuildInfo)] Source #
enabledBenchLBIs :: PackageDescription -> LocalBuildInfo -> [(Benchmark, ComponentLocalBuildInfo)] Source #
Installation directories
data InstallDirs dir Source #
The directories where we will install files for packages.
We have several different directories for different types of files since many systems have conventions whereby different types of files in a package are installed in different directories. This is particularly the case on Unix style systems.
InstallDirs | |
|
Instances
type InstallDirTemplates = InstallDirs PathTemplate Source #
The installation directories in terms of PathTemplate
s that contain
variables.
The defaults for most of the directories are relative to each other, in
particular they are all relative to a single prefix. This makes it
convenient for the user to override the default installation directory
by only having to specify --prefix=... rather than overriding each
individually. This is done by allowing $-style variables in the dirs.
These are expanded by textual substitution (see substPathTemplate
).
A few of these installation directories are split into two components, the
dir and subdir. The full installation path is formed by combining the two
together with /
. The reason for this is compatibility with other Unix
build systems which also support --libdir
and --datadir
. We would like
users to be able to configure --libdir=/usr/lib64
for example but
because by default we want to support installing multiple versions of
packages and building the same package for multiple compilers we append the
libsubdir to get: /usr/lib64/$libname/$compiler
.
An additional complication is the need to support relocatable packages on systems which support such things, like Windows.
The location prefix for the copy command.
NoCopyDest | |
CopyTo FilePath | |
CopyToDb FilePath | when using the ${pkgroot} as prefix. The CopyToDb will adjust the paths to be relative to the provided package database when copying / installing. |
Instances
Structured CopyDest Source # | |
Defined in Distribution.Simple.InstallDirs structure :: Proxy CopyDest -> Structure structureHash' :: Tagged CopyDest MD5 | |
Generic CopyDest Source # | |
Show CopyDest Source # | |
Binary CopyDest Source # | |
Eq CopyDest Source # | |
type Rep CopyDest Source # | |
Defined in Distribution.Simple.InstallDirs type Rep CopyDest = D1 ('MetaData "CopyDest" "Distribution.Simple.InstallDirs" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "NoCopyDest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CopyTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "CopyToDb" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) |
data PathTemplate Source #
An abstract path, possibly containing variables that need to be
substituted for to get a real FilePath
.
Instances
data PathTemplateVariable Source #
PrefixVar | The |
BindirVar | The |
LibdirVar | The |
LibsubdirVar | The |
DynlibdirVar | The |
DatadirVar | The |
DatasubdirVar | The |
DocdirVar | The |
HtmldirVar | The |
PkgNameVar | The |
PkgVerVar | The |
PkgIdVar | The |
LibNameVar | The |
CompilerVar | The compiler name and version, eg |
OSVar | The operating system name, eg |
ArchVar | The CPU architecture name, eg |
AbiVar | The compiler's ABI identifier, |
AbiTagVar | The optional ABI tag for the compiler |
ExecutableNameVar | The executable name; used in shell wrappers |
TestSuiteNameVar | The name of the test suite being run |
TestSuiteResultVar | The result of the test suite being run, eg
|
BenchmarkNameVar | The name of the benchmark being run |
Instances
type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)] Source #
defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates Source #
defaultInstallDirs' :: Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates Source #
combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c Source #
substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates Source #
Substitute the install dir templates into each other.
To prevent cyclic substitutions, only some variables are allowed in particular dir templates. If out of scope vars are present, they are not substituted for. Checking for any remaining unsubstituted vars can be done as a subsequent operation.
The reason it is done this way is so that in prefixRelativeInstallDirs
we
can replace prefix
with the PrefixVar
and get resulting
PathTemplate
s that still have the PrefixVar
in them. Doing this makes it
each to check which paths are relative to the $prefix.
toPathTemplate :: FilePath -> PathTemplate Source #
Convert a FilePath
to a PathTemplate
including any template vars.
fromPathTemplate :: PathTemplate -> FilePath Source #
Convert back to a path, any remaining vars are included
initialPathTemplateEnv :: PackageIdentifier -> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv Source #
The initial environment has all the static stuff but no paths
platformTemplateEnv :: Platform -> PathTemplateEnv Source #
compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv Source #
packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv Source #
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv Source #
absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest -> InstallDirs FilePath Source #
Backwards compatibility function which computes the InstallDirs
assuming that $libname
points to the public library (or some fake
package identifier if there is no public library.) IF AT ALL
POSSIBLE, please use absoluteComponentInstallDirs
instead.
prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath) Source #
Backwards compatibility function which computes the InstallDirs
assuming that $libname
points to the public library (or some fake
package identifier if there is no public library.) IF AT ALL
POSSIBLE, please use prefixRelativeComponentInstallDirs
instead.
absoluteInstallCommandDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath Source #
absoluteComponentInstallDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath Source #
See absoluteInstallDirs
.
prefixRelativeComponentInstallDirs :: PackageId -> LocalBuildInfo -> UnitId -> InstallDirs (Maybe FilePath) Source #
substPathTemplate :: PackageId -> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath Source #