Cabal
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Types.LocalBuildConfig

Synopsis

The types

data PackageBuildDescr Source #

PackageBuildDescr contains the information Cabal determines after performing package-wide configuration of a package, before doing any per-component configuration.

Constructors

PackageBuildDescr 

Fields

  • configFlags :: ConfigFlags

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

  • flagAssignment :: FlagAssignment

    The final set of flags which were picked for this package

  • componentEnabledSpec :: ComponentRequestedSpec

    What components were enabled during configuration, and why.

  • compiler :: Compiler

    The compiler we're building with

  • hostPlatform :: Platform

    The platform we're building for

  • pkgDescrFile :: Maybe (SymbolicPath Pkg File)

    the filename containing the .cabal file, if available

  • localPkgDescr :: PackageDescription

    WARNING WARNING WARNING Be VERY careful about using this function; we haven't deprecated it but using it could introduce subtle bugs related to HookedBuildInfo.

    In principle, this is supposed to contain the resolved package description, that does not contain any conditionals. However, it MAY NOT contain the description with a HookedBuildInfo applied to it; see HookedBuildInfo for the whole sordid saga. As much as possible, Cabal library should avoid using this parameter.

  • installDirTemplates :: InstallDirTemplates

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

  • withPackageDB :: PackageDBStack

    What package database to use, global/user

  • extraCoverageFor :: [UnitId]

    For per-package builds-only: an extra list of libraries to be included in the hpc coverage report for testsuites run with --enable-coverage. Notably, this list must exclude indefinite libraries and instantiations because HPC does not support backpack (Nov. 2023).

Instances

Instances details
Structured PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Generic PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep PackageBuildDescr :: Type -> Type #

Read PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep PackageBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep PackageBuildDescr = D1 ('MetaData "PackageBuildDescr" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "PackageBuildDescr" '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 "compiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler) :*: S1 ('MetaSel ('Just "hostPlatform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Platform)))) :*: ((S1 ('MetaSel ('Just "pkgDescrFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (SymbolicPath Pkg 'File))) :*: S1 ('MetaSel ('Just "localPkgDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDescription)) :*: (S1 ('MetaSel ('Just "installDirTemplates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstallDirTemplates) :*: (S1 ('MetaSel ('Just "withPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: S1 ('MetaSel ('Just "extraCoverageFor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))))

data ComponentBuildDescr Source #

Information about individual components in a package, determined after the configure step.

Constructors

ComponentBuildDescr 

Fields

  • componentGraph :: Graph ComponentLocalBuildInfo

    All the components to build, ordered by topological sort, and with their INTERNAL dependencies over the intrapackage dependency graph. TODO: this is assumed to be short; otherwise we want some sort of ordered map.

  • componentNameMap :: Map ComponentName [ComponentLocalBuildInfo]

    A map from component name to all matching components. These coincide with $sel:componentGraph:ComponentBuildDescr There may be more than one matching component because of backpack instantiations

  • promisedPkgs :: Map (PackageName, ComponentName) PromisedComponent

    The packages we were promised, but aren't already installed. MP: Perhaps this just needs to be a Set UnitId at this stage.

  • installedPkgs :: InstalledPackageIndex

    All the info about the installed packages that the current package depends on (directly or indirectly). The copy saved on disk does NOT include internal dependencies (because we just don't have enough information at this point to have an InstalledPackageInfo for an internal dep), but we will often update it with the internal dependencies; see for example build. (This admonition doesn't apply for per-component builds.)

Instances

Instances details
Structured ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Generic ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep ComponentBuildDescr :: Type -> Type #

Read ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep ComponentBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep ComponentBuildDescr = D1 ('MetaData "ComponentBuildDescr" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "ComponentBuildDescr" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentGraph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Graph ComponentLocalBuildInfo)) :*: S1 ('MetaSel ('Just "componentNameMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ComponentName [ComponentLocalBuildInfo]))) :*: (S1 ('MetaSel ('Just "promisedPkgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (PackageName, ComponentName) PromisedComponent)) :*: S1 ('MetaSel ('Just "installedPkgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstalledPackageIndex))))

data LocalBuildDescr Source #

'LocalBuildDescr ' contains the information Cabal determines after performing package-wide and per-component configuration of a package.

This information can no longer be changed after that point.

Constructors

LocalBuildDescr 

Fields

Instances

Instances details
Structured LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Methods

structure :: Proxy LocalBuildDescr -> Structure

structureHash' :: Tagged LocalBuildDescr MD5

Generic LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep LocalBuildDescr :: Type -> Type #

Read LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildDescr Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildDescr = D1 ('MetaData "LocalBuildDescr" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "LocalBuildDescr" 'PrefixI 'True) (S1 ('MetaSel ('Just "packageBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageBuildDescr) :*: S1 ('MetaSel ('Just "componentBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentBuildDescr)))

data LocalBuildConfig Source #

LocalBuildConfig contains options that can be controlled by the user and serve as inputs to the configuration of a package.

Constructors

LocalBuildConfig 

Fields

Instances

Instances details
Structured LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Methods

structure :: Proxy LocalBuildConfig -> Structure

structureHash' :: Tagged LocalBuildConfig MD5

Generic LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep LocalBuildConfig :: Type -> Type #

Read LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildConfig Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep LocalBuildConfig = D1 ('MetaData "LocalBuildConfig" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "LocalBuildConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "extraConfigArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "withPrograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramDb) :*: S1 ('MetaSel ('Just "withBuildOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildOptions))))

data BuildOptions Source #

BuildOptions contains configuration options that can be controlled by the user.

Constructors

BuildOptions 

Fields

Instances

Instances details
Structured BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Methods

structure :: Proxy BuildOptions -> Structure

structureHash' :: Tagged BuildOptions MD5

Generic BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Associated Types

type Rep BuildOptions :: Type -> Type #

Read BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Show BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Binary BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

Eq BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep BuildOptions Source # 
Instance details

Defined in Distribution.Types.LocalBuildConfig

type Rep BuildOptions = D1 ('MetaData "BuildOptions" "Distribution.Types.LocalBuildConfig" "Cabal-3.14.1.0-inplace" 'False) (C1 ('MetaCons "BuildOptions" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "withVanillaLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withProfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "withProfLibShared") '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 "relocatable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))))

Conversion functions