Cabal-3.4.1.0: A framework for packaging Haskell software
CopyrightIsaac Jones 2003-2004
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Simple.LocalBuildInfo

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

Instances

Instances details
Structured LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Generic LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Associated Types

type Rep LocalBuildInfo :: Type -> Type Source #

Read LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Show LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

Binary LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

type Rep LocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.LocalBuildInfo

type Rep LocalBuildInfo = D1 ('MetaData "LocalBuildInfo" "Distribution.Types.LocalBuildInfo" "Cabal-3.4.1.0" 'False) (C1 ('MetaCons "LocalBuildInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "configFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConfigFlags) :*: S1 ('MetaSel ('Just "flagAssignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment)) :*: (S1 ('MetaSel ('Just "componentEnabledSpec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentRequestedSpec) :*: S1 ('MetaSel ('Just "extraConfigArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "installDirTemplates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstallDirTemplates) :*: S1 ('MetaSel ('Just "compiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler)) :*: (S1 ('MetaSel ('Just "hostPlatform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Platform) :*: (S1 ('MetaSel ('Just "buildDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "cabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))))) :*: (((S1 ('MetaSel ('Just "componentGraph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Graph ComponentLocalBuildInfo)) :*: S1 ('MetaSel ('Just "componentNameMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ComponentName [ComponentLocalBuildInfo]))) :*: (S1 ('MetaSel ('Just "installedPkgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstalledPackageIndex) :*: S1 ('MetaSel ('Just "pkgDescrFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))) :*: ((S1 ('MetaSel ('Just "localPkgDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDescription) :*: S1 ('MetaSel ('Just "withPrograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramDb)) :*: (S1 ('MetaSel ('Just "withPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: (S1 ('MetaSel ('Just "withVanillaLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withProfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) :*: ((((S1 ('MetaSel ('Just "withSharedLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withStaticLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "withDynExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withFullyStaticExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "withProfExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withProfLibDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProfDetailLevel)) :*: (S1 ('MetaSel ('Just "withProfExeDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProfDetailLevel) :*: (S1 ('MetaSel ('Just "withOptimization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptimisationLevel) :*: S1 ('MetaSel ('Just "withDebugInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DebugInfoLevel))))) :*: (((S1 ('MetaSel ('Just "withGHCiLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "splitSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "splitObjs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "stripExes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "stripLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "exeCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "libCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "progPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PathTemplate) :*: (S1 ('MetaSel ('Just "progSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PathTemplate) :*: S1 ('MetaSel ('Just "relocatable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))))

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.

Buildable package components

data Component Source #

Instances

Instances details
HasBuildInfo Component Source # 
Instance details

Defined in Distribution.Types.Component

Methods

buildInfo :: Lens' Component BuildInfo Source #

buildable :: Lens' Component Bool Source #

buildTools :: Lens' Component [LegacyExeDependency] Source #

buildToolDepends :: Lens' Component [ExeDependency] Source #

cppOptions :: Lens' Component [String] Source #

asmOptions :: Lens' Component [String] Source #

cmmOptions :: Lens' Component [String] Source #

ccOptions :: Lens' Component [String] Source #

cxxOptions :: Lens' Component [String] Source #

ldOptions :: Lens' Component [String] Source #

pkgconfigDepends :: Lens' Component [PkgconfigDependency] Source #

frameworks :: Lens' Component [String] Source #

extraFrameworkDirs :: Lens' Component [String] Source #

asmSources :: Lens' Component [FilePath] Source #

cmmSources :: Lens' Component [FilePath] Source #

cSources :: Lens' Component [FilePath] Source #

cxxSources :: Lens' Component [FilePath] Source #

jsSources :: Lens' Component [FilePath] Source #

hsSourceDirs :: Lens' Component [FilePath] Source #

otherModules :: Lens' Component [ModuleName] Source #

virtualModules :: Lens' Component [ModuleName] Source #

autogenModules :: Lens' Component [ModuleName] Source #

defaultLanguage :: Lens' Component (Maybe Language) Source #

otherLanguages :: Lens' Component [Language] Source #

defaultExtensions :: Lens' Component [Extension] Source #

otherExtensions :: Lens' Component [Extension] Source #

oldExtensions :: Lens' Component [Extension] Source #

extraLibs :: Lens' Component [String] Source #

extraGHCiLibs :: Lens' Component [String] Source #

extraBundledLibs :: Lens' Component [String] Source #

extraLibFlavours :: Lens' Component [String] Source #

extraDynLibFlavours :: Lens' Component [String] Source #

extraLibDirs :: Lens' Component [String] Source #

includeDirs :: Lens' Component [FilePath] Source #

includes :: Lens' Component [FilePath] Source #

autogenIncludes :: Lens' Component [FilePath] Source #

installIncludes :: Lens' Component [FilePath] Source #

options :: Lens' Component (PerCompilerFlavor [String]) Source #

profOptions :: Lens' Component (PerCompilerFlavor [String]) Source #

sharedOptions :: Lens' Component (PerCompilerFlavor [String]) Source #

staticOptions :: Lens' Component (PerCompilerFlavor [String]) Source #

customFieldsBI :: Lens' Component [(String, String)] Source #

targetBuildDepends :: Lens' Component [Dependency] Source #

mixins :: Lens' Component [Mixin] Source #

Semigroup Component Source # 
Instance details

Defined in Distribution.Types.Component

Read Component Source # 
Instance details

Defined in Distribution.Types.Component

Show Component Source # 
Instance details

Defined in Distribution.Types.Component

Eq Component Source # 
Instance details

Defined in Distribution.Types.Component

data ComponentName Source #

Instances

Instances details
Parsec ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Pretty ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Structured ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Generic ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Associated Types

type Rep ComponentName :: Type -> Type Source #

Read ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Show ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Binary ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Eq ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

Ord ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

type Rep ComponentName Source # 
Instance details

Defined in Distribution.Types.ComponentName

data LibraryName Source #

Instances

Instances details
Structured LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Data LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Methods

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

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

toConstr :: LibraryName -> Constr Source #

dataTypeOf :: LibraryName -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LibraryName) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LibraryName) Source #

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

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

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

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

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

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

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

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

Generic LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Associated Types

type Rep LibraryName :: Type -> Type Source #

Read LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Show LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Binary LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

NFData LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Methods

rnf :: LibraryName -> () Source #

Eq LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

Ord LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

type Rep LibraryName Source # 
Instance details

Defined in Distribution.Types.LibraryName

type Rep LibraryName = D1 ('MetaData "LibraryName" "Distribution.Types.LibraryName" "Cabal-3.4.1.0" 'False) (C1 ('MetaCons "LMainLibName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSubLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName)))

componentNameString :: ComponentName -> Maybe UnqualComponentName Source #

This gets the underlying unqualified component name. In fact, it is guaranteed to uniquely identify a component, returning Nothing if the ComponentName was for the public library.

data ComponentLocalBuildInfo Source #

The first five fields are common across all algebraic variants.

Constructors

LibComponentLocalBuildInfo 

Fields

FLibComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    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.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

ExeComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    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.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

TestComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    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.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

BenchComponentLocalBuildInfo 

Fields

  • componentLocalName :: ComponentName

    It would be very convenient to store the literal Library here, but if we do that, it will get serialized (via the Binary) instance twice. So instead we just provide the ComponentName, which can be used to find the Component in the PackageDescription. NB: eventually, this will NOT uniquely identify the ComponentLocalBuildInfo.

  • componentComponentId :: ComponentId

    The computed ComponentId of this component.

  • componentUnitId :: UnitId

    The computed UnitId which uniquely identifies this component. Might be hashed.

  • componentPackageDeps :: [(UnitId, MungedPackageId)]

    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.

  • componentIncludes :: [(OpenUnitId, ModuleRenaming)]

    The set of packages that are brought into scope during compilation, including a ModuleRenaming which may used to hide or rename modules. This is what gets translated into -package-id arguments. This is a modernized version of componentPackageDeps, which is kept around for BC purposes.

  • componentExeDeps :: [UnitId]
     
  • componentInternalDeps :: [UnitId]

    The internal dependencies which induce a graph on the ComponentLocalBuildInfo of this package. This does NOT coincide with componentPackageDeps because it ALSO records 'build-tool' dependencies on executables. Maybe one day cabal-install will also handle these correctly too!

Instances

Instances details
IsNode ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Associated Types

type Key ComponentLocalBuildInfo Source #

Structured ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Generic ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Associated Types

type Rep ComponentLocalBuildInfo :: Type -> Type Source #

Read ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Show ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

Binary ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Key ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Rep ComponentLocalBuildInfo Source # 
Instance details

Defined in Distribution.Types.ComponentLocalBuildInfo

type Rep ComponentLocalBuildInfo = D1 ('MetaData "ComponentLocalBuildInfo" "Distribution.Types.ComponentLocalBuildInfo" "Cabal-3.4.1.0" 'False) ((C1 ('MetaCons "LibComponentLocalBuildInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: (S1 ('MetaSel ('Just "componentIsIndefinite_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "componentInstantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ModuleName, OpenModule)]) :*: S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)])))) :*: ((S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)]) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))) :*: ((S1 ('MetaSel ('Just "componentCompatPackageKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "componentCompatPackageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MungedPackageName)) :*: (S1 ('MetaSel ('Just "componentExposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExposedModule]) :*: S1 ('MetaSel ('Just "componentIsPublic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :+: C1 ('MetaCons "FLibComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))) :+: (C1 ('MetaCons "ExeComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: (C1 ('MetaCons "TestComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: C1 ('MetaCons "BenchComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))))))

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

componentBuildable :: Component -> Bool Source #

Is a component buildable (i.e., not marked with buildable: False)? See also this note in Distribution.Types.ComponentRequestedSpec.

Since: Cabal-2.0.0.2

pkgComponents :: PackageDescription -> [Component] Source #

All the components in the package.

pkgBuildableComponents :: PackageDescription -> [Component] Source #

A list of all components in the package that are buildable, i.e., were not marked with buildable: False. This does NOT indicate if we are actually going to build the component, see enabledComponents instead.

Since: Cabal-2.0.0.2

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

allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName] Source #

Get all module names that needed to be built by GHC; i.e., all of these ModuleNames 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.

Installation directories

data PathTemplateVariable Source #

Constructors

PrefixVar

The $prefix path variable

BindirVar

The $bindir path variable

LibdirVar

The $libdir path variable

LibsubdirVar

The $libsubdir path variable

DynlibdirVar

The $dynlibdir path variable

DatadirVar

The $datadir path variable

DatasubdirVar

The $datasubdir path variable

DocdirVar

The $docdir path variable

HtmldirVar

The $htmldir path variable

PkgNameVar

The $pkg package name path variable

PkgVerVar

The $version package version path variable

PkgIdVar

The $pkgid package Id path variable, eg foo-1.0

LibNameVar

The $libname path variable

CompilerVar

The compiler name and version, eg ghc-6.6.1

OSVar

The operating system name, eg windows or linux

ArchVar

The CPU architecture name, eg i386 or x86_64

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 pass, fail, or error.

BenchmarkNameVar

The name of the benchmark being run

Instances

Instances details
Structured PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Generic PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Associated Types

type Rep PathTemplateVariable :: Type -> Type Source #

Read PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Show PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Binary PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Eq PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

Ord PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

type Rep PathTemplateVariable Source # 
Instance details

Defined in Distribution.Simple.InstallDirs.Internal

type Rep PathTemplateVariable = D1 ('MetaData "PathTemplateVariable" "Distribution.Simple.InstallDirs.Internal" "Cabal-3.4.1.0" 'False) ((((C1 ('MetaCons "PrefixVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BindirVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LibdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LibsubdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynlibdirVar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DatadirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DatasubdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DocdirVar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HtmldirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PkgNameVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PkgVerVar" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PkgIdVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LibNameVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompilerVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OSVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchVar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AbiVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AbiTagVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExecutableNameVar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TestSuiteNameVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TestSuiteResultVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BenchmarkNameVar" 'PrefixI 'False) (U1 :: Type -> Type))))))

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

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

data CopyDest Source #

The location prefix for the copy command.

Constructors

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

Instances details
Generic CopyDest Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Associated Types

type Rep CopyDest :: Type -> Type Source #

Show CopyDest Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Binary CopyDest Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Eq CopyDest Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

type Rep CopyDest Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

type Rep CopyDest = D1 ('MetaData "CopyDest" "Distribution.Simple.InstallDirs" "Cabal-3.4.1.0" '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))))

type InstallDirTemplates = InstallDirs PathTemplate Source #

The installation directories in terms of PathTemplates 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.

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.

Constructors

InstallDirs 

Fields

Instances

Instances details
Functor InstallDirs Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Methods

fmap :: (a -> b) -> InstallDirs a -> InstallDirs b Source #

(<$) :: a -> InstallDirs b -> InstallDirs a Source #

Structured dir => Structured (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

(Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Semigroup dir => Semigroup (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Generic (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Associated Types

type Rep (InstallDirs dir) :: Type -> Type Source #

Methods

from :: InstallDirs dir -> Rep (InstallDirs dir) x Source #

to :: Rep (InstallDirs dir) x -> InstallDirs dir Source #

Read dir => Read (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Show dir => Show (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Binary dir => Binary (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Eq dir => Eq (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Methods

(==) :: InstallDirs dir -> InstallDirs dir -> Bool #

(/=) :: InstallDirs dir -> InstallDirs dir -> Bool #

type Rep (InstallDirs dir) Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

type Rep (InstallDirs dir) = D1 ('MetaData "InstallDirs" "Distribution.Simple.InstallDirs" "Cabal-3.4.1.0" 'False) (C1 ('MetaCons "InstallDirs" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "bindir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "libdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "libsubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir))) :*: ((S1 ('MetaSel ('Just "dynlibdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "flibdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "libexecdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "libexecsubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)))) :*: (((S1 ('MetaSel ('Just "includedir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "datadir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "datasubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "docdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir))) :*: ((S1 ('MetaSel ('Just "mandir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "htmldir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "haddockdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "sysconfdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir))))))

data PathTemplate Source #

An abstract path, possibly containing variables that need to be substituted for to get a real FilePath.

Instances

Instances details
Structured PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Generic PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Associated Types

type Rep PathTemplate :: Type -> Type Source #

Read PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Show PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Binary PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Eq PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

Ord PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

type Rep PathTemplate Source # 
Instance details

Defined in Distribution.Simple.InstallDirs

type Rep PathTemplate = D1 ('MetaData "PathTemplate" "Distribution.Simple.InstallDirs" "Cabal-3.4.1.0" 'True) (C1 ('MetaCons "PathTemplate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathComponent])))

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.