Cabal-1.22.5.0: A framework for packaging Haskell software

CopyrightIsaac Jones 2003-2004
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Distribution.Simple.LocalBuildInfo

Contents

Description

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

Documentation

data LocalBuildInfo Source

Data cached after configuration step. See also ConfigFlags.

Constructors

LocalBuildInfo 

Fields

configFlags :: ConfigFlags

Options passed to the configuration step. Needed to re-run configuration when .cabal is out of date

extraConfigArgs :: [String]

Extra args on the command line for the configuration step. Needed to re-run configuration when .cabal is out of date

installDirTemplates :: InstallDirTemplates

The installation directories for the various different kinds of files TODO: inplaceDirTemplates :: InstallDirs FilePath

compiler :: Compiler

The compiler we're building with

hostPlatform :: Platform

The platform we're building for

buildDir :: FilePath

Where to build the package.

componentsConfigs :: [(ComponentName, ComponentLocalBuildInfo, [ComponentName])]

All the components to build, ordered by topological sort, and with their dependencies over the intrapackage dependency graph

installedPkgs :: InstalledPackageIndex

All the info about the installed packages that the current package depends on (directly or indirectly).

pkgDescrFile :: Maybe FilePath

the filename containing the .cabal file, if available

localPkgDescr :: PackageDescription

The resolved package description, that does not contain any conditionals.

pkgKey :: PackageKey

The package key for the current build, calculated from the package ID and the dependency graph.

instantiatedWith :: [(ModuleName, (InstalledPackageInfo, ModuleName))]
 
withPrograms :: ProgramConfiguration

Location and args for all programs

withPackageDB :: PackageDBStack

What package database to use, global/user

withVanillaLib :: Bool

Whether to build normal libs.

withProfLib :: Bool

Whether to build profiling versions of libs.

withSharedLib :: Bool

Whether to build shared versions of libs.

withDynExe :: Bool

Whether to link executables dynamically

withProfExe :: Bool

Whether to build executables for profiling.

withOptimization :: OptimisationLevel

Whether to build with optimization (if available).

withDebugInfo :: DebugInfoLevel

Whether to emit debug info (if available).

withGHCiLib :: Bool

Whether to build libs suitable for use with GHCi.

splitObjs :: Bool

Use -split-objs with GHC, if available

stripExes :: Bool

Whether to strip executables during install

stripLibs :: Bool

Whether to strip libraries during install

progPrefix :: PathTemplate

Prefix to be prepended to installed executables

progSuffix :: PathTemplate

Suffix to be appended to installed executables

relocatable :: Bool
 

externalPackageDeps :: LocalBuildInfo -> [(InstalledPackageId, PackageId)] Source

External package dependencies for the package as a whole. This is the union of the individual componentPackageDeps, less any internal deps.

inplacePackageId :: PackageId -> InstalledPackageId Source

The installed package Id we use for local packages registered in the local package db. This is what is used for intra-package deps between components.

Buildable package components

data ComponentLocalBuildInfo Source

Constructors

LibComponentLocalBuildInfo 

Fields

componentPackageDeps :: [(InstalledPackageId, PackageId)]

Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

componentExposedModules :: [ExposedModule]
 
componentPackageRenaming :: Map PackageName ModuleRenaming
 
componentLibraries :: [LibraryName]
 
ExeComponentLocalBuildInfo 

Fields

componentPackageDeps :: [(InstalledPackageId, PackageId)]

Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

componentPackageRenaming :: Map PackageName ModuleRenaming
 
TestComponentLocalBuildInfo 

Fields

componentPackageDeps :: [(InstalledPackageId, PackageId)]

Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

componentPackageRenaming :: Map PackageName ModuleRenaming
 
BenchComponentLocalBuildInfo 

Fields

componentPackageDeps :: [(InstalledPackageId, PackageId)]

Resolved internal and external package dependencies for this component. The BuildInfo specifies a set of build dependencies that must be satisfied in terms of version ranges. This field fixes those dependencies to the specific versions available on this machine for this compiler.

componentPackageRenaming :: Map PackageName ModuleRenaming
 

foldComponent :: (Library -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a Source

pkgComponents :: PackageDescription -> [Component] Source

All the components in the package (libs, exes, or test suites).

pkgEnabledComponents :: PackageDescription -> [Component] Source

All the components in the package that are buildable and enabled. Thus this excludes non-buildable components and test suites or benchmarks that have been disabled.

checkComponentsCyclic :: Ord key => [(node, key, [key])] -> Maybe [(node, key, [key])] Source

depLibraryPaths Source

Arguments

:: 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

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

withComponentsLBI :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () Source

Deprecated: Use withAllComponentsInBuildOrder

withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO () Source

If the package description has a library section, call the given function with the library build info as argument. Extended version of withLib that also gives corresponding build info.

withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO () Source

Perform the action on each buildable Executable in the package description. Extended version of withExe that also gives corresponding build info.

Installation directories