Safe Haskell | None |
---|---|
Language | Haskell2010 |
Distribution.Client.ProjectPlanning.Types
Description
Types used while planning how to build everything in a project.
Primarily this is the ElaboratedInstallPlan
.
Synopsis
- data SolverInstallPlan
- type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage
- normaliseConfiguredPackage :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
- data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage {
- elabUnitId :: UnitId
- elabComponentId :: ComponentId
- elabInstantiatedWith :: Map ModuleName Module
- elabLinkedInstantiatedWith :: Map ModuleName OpenModule
- elabIsCanonical :: Bool
- elabPkgSourceId :: PackageId
- elabModuleShape :: ModuleShape
- elabFlagAssignment :: FlagAssignment
- elabFlagDefaults :: FlagAssignment
- elabPkgDescription :: PackageDescription
- elabPkgSourceLocation :: PackageLocation (Maybe FilePath)
- elabPkgSourceHash :: Maybe PackageSourceHash
- elabLocalToProject :: Bool
- elabBuildStyle :: BuildStyle
- elabEnabledSpec :: ComponentRequestedSpec
- elabStanzasAvailable :: OptionalStanzaSet
- elabStanzasRequested :: OptionalStanzaMap (Maybe Bool)
- elabPackageDbs :: [Maybe PackageDBCWD]
- elabSetupPackageDBStack :: PackageDBStackCWD
- elabBuildPackageDBStack :: PackageDBStackCWD
- elabRegisterPackageDBStack :: PackageDBStackCWD
- elabInplaceSetupPackageDBStack :: PackageDBStackCWD
- elabInplaceBuildPackageDBStack :: PackageDBStackCWD
- elabInplaceRegisterPackageDBStack :: PackageDBStackCWD
- elabPkgDescriptionOverride :: Maybe CabalFileText
- elabBuildOptions :: BuildOptions
- elabDumpBuildInfo :: DumpBuildInfo
- elabProgramPaths :: Map String FilePath
- elabProgramArgs :: Map String [String]
- elabProgramPathExtra :: [FilePath]
- elabConfiguredPrograms :: [ConfiguredProgram]
- elabConfigureScriptArgs :: [String]
- elabExtraLibDirs :: [FilePath]
- elabExtraLibDirsStatic :: [FilePath]
- elabExtraFrameworkDirs :: [FilePath]
- elabExtraIncludeDirs :: [FilePath]
- elabProgPrefix :: Maybe PathTemplate
- elabProgSuffix :: Maybe PathTemplate
- elabInstallDirs :: InstallDirs FilePath
- elabHaddockHoogle :: Bool
- elabHaddockHtml :: Bool
- elabHaddockHtmlLocation :: Maybe String
- elabHaddockForeignLibs :: Bool
- elabHaddockForHackage :: HaddockTarget
- elabHaddockExecutables :: Bool
- elabHaddockTestSuites :: Bool
- elabHaddockBenchmarks :: Bool
- elabHaddockInternal :: Bool
- elabHaddockCss :: Maybe FilePath
- elabHaddockLinkedSource :: Bool
- elabHaddockQuickJump :: Bool
- elabHaddockHscolourCss :: Maybe FilePath
- elabHaddockContents :: Maybe PathTemplate
- elabHaddockIndex :: Maybe PathTemplate
- elabHaddockBaseUrl :: Maybe String
- elabHaddockResourcesDir :: Maybe String
- elabHaddockOutputDir :: Maybe FilePath
- elabHaddockUseUnicode :: Bool
- elabTestMachineLog :: Maybe PathTemplate
- elabTestHumanLog :: Maybe PathTemplate
- elabTestShowDetails :: Maybe TestShowDetails
- elabTestKeepTix :: Bool
- elabTestWrapper :: Maybe FilePath
- elabTestFailWhenNoTestSuites :: Bool
- elabTestTestOptions :: [PathTemplate]
- elabBenchmarkOptions :: [PathTemplate]
- elabSetupScriptStyle :: SetupScriptStyle
- elabSetupScriptCliVersion :: Version
- elabConfigureTargets :: [ComponentTarget]
- elabBuildTargets :: [ComponentTarget]
- elabTestTargets :: [ComponentTarget]
- elabBenchTargets :: [ComponentTarget]
- elabReplTarget :: [ComponentTarget]
- elabHaddockTargets :: [ComponentTarget]
- elabBuildHaddocks :: Bool
- elabPkgOrComp :: ElaboratedPackageOrComponent
- showElaboratedInstallPlan :: ElaboratedInstallPlan -> String
- elabDistDirParams :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> DistDirParams
- elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
- elabLibDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
- elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId]
- elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
- elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId]
- elabSetupDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
- elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
- elabInplaceDependencyBuildCacheFiles :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> ElaboratedConfiguredPackage -> [FilePath]
- elabRequiresRegistration :: ElaboratedConfiguredPackage -> Bool
- dataDirsEnvironmentForPlan :: DistDirLayout -> ElaboratedInstallPlan -> [(String, Maybe FilePath)]
- elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String
- elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String
- elabComponentName :: ElaboratedConfiguredPackage -> Maybe ComponentName
- data ElaboratedPackageOrComponent
- data ElaboratedComponent = ElaboratedComponent {
- compSolverName :: Component
- compComponentName :: Maybe ComponentName
- compLibDependencies :: [(ConfiguredId, Bool)]
- compLinkedLibDependencies :: [OpenUnitId]
- compExeDependencies :: [ConfiguredId]
- compPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)]
- compExeDependencyPaths :: [(ConfiguredId, FilePath)]
- compOrderLibDependencies :: [UnitId]
- data ElaboratedPackage = ElaboratedPackage {
- pkgInstalledId :: InstalledPackageId
- pkgLibDependencies :: ComponentDeps [(ConfiguredId, Bool)]
- pkgDependsOnSelfLib :: ComponentDeps [()]
- pkgExeDependencies :: ComponentDeps [ConfiguredId]
- pkgExeDependencyPaths :: ComponentDeps [(ConfiguredId, FilePath)]
- pkgPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)]
- pkgStanzasEnabled :: OptionalStanzaSet
- pkgWhyNotPerComponent :: NonEmpty NotPerComponentReason
- pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
- type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage
- data ElaboratedSharedConfig = ElaboratedSharedConfig {}
- type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage
- data BuildStyle
- data MemoryOrDisk
- isInplaceBuildStyle :: BuildStyle -> Bool
- type CabalFileText = ByteString
- data NotPerComponentReason
- data NotPerComponentBuildType
- whyNotPerComponent :: NotPerComponentReason -> String
- data ComponentTarget = ComponentTarget ComponentName SubComponentTarget
- showComponentTarget :: PackageId -> ComponentTarget -> String
- showTestComponentTarget :: PackageId -> ComponentTarget -> Maybe String
- showBenchComponentTarget :: PackageId -> ComponentTarget -> Maybe String
- data SubComponentTarget
- isSubLibComponentTarget :: ComponentTarget -> Bool
- isForeignLibComponentTarget :: ComponentTarget -> Bool
- isExeComponentTarget :: ComponentTarget -> Bool
- isTestComponentTarget :: ComponentTarget -> Bool
- isBenchComponentTarget :: ComponentTarget -> Bool
- componentOptionalStanza :: Component -> Maybe OptionalStanza
- componentTargetName :: ComponentTarget -> ComponentName
- data SetupScriptStyle
Documentation
data SolverInstallPlan Source #
Instances
Structured SolverInstallPlan Source # | |||||
Defined in Distribution.Client.SolverInstallPlan Methods structure :: Proxy SolverInstallPlan -> Structure # structureHash' :: Tagged SolverInstallPlan MD5 | |||||
Generic SolverInstallPlan Source # | |||||
Defined in Distribution.Client.SolverInstallPlan Associated Types
Methods from :: SolverInstallPlan -> Rep SolverInstallPlan x # to :: Rep SolverInstallPlan x -> SolverInstallPlan # | |||||
Binary SolverInstallPlan Source # | |||||
Defined in Distribution.Client.SolverInstallPlan Methods put :: SolverInstallPlan -> Put # get :: Get SolverInstallPlan # putList :: [SolverInstallPlan] -> Put # | |||||
type Rep SolverInstallPlan Source # | |||||
Defined in Distribution.Client.SolverInstallPlan |
Elaborated install plan types
type ElaboratedInstallPlan = GenericInstallPlan InstalledPackageInfo ElaboratedConfiguredPackage Source #
The combination of an elaborated install plan plus a
ElaboratedSharedConfig
contains all the details necessary to be able
to execute the plan without having to make further policy decisions.
It does not include dynamic elements such as resources (such as http connections).
normaliseConfiguredPackage :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage Source #
data ElaboratedConfiguredPackage Source #
Constructors
ElaboratedConfiguredPackage | |
Fields
|
Instances
elabDistDirParams :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> DistDirParams Source #
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath] Source #
This returns the paths of all the executables we depend on; we
must add these paths to PATH before invoking the setup script.
(This is usually what you want, not elabExeDependencies
, if you
actually want to build something.)
elabLibDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)] Source #
The library dependencies (i.e., the libraries we depend on, NOT
the dependencies of the library), NOT including setup dependencies.
These are passed to the Setup
script via --dependency
or --promised-dependency
.
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId] Source #
Like elabOrderDependencies
, but only returns dependencies on
libraries.
elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId] Source #
The executable dependencies (i.e., the executables we depend on); these are the executables we must add to the PATH before we invoke the setup script.
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId] Source #
Like elabOrderDependencies
, but only returns dependencies on
executables. (This coincides with elabExeDependencies
.)
elabSetupDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)] Source #
The setup dependencies (the library dependencies of the setup executable; note that it is not legal for setup scripts to have executable dependencies at the moment.)
elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName, Maybe PkgconfigVersion)] Source #
elabInplaceDependencyBuildCacheFiles :: DistDirLayout -> ElaboratedSharedConfig -> ElaboratedInstallPlan -> ElaboratedConfiguredPackage -> [FilePath] Source #
The cache files of all our inplace dependencies which, when updated, require us to rebuild. See #4202 for more details. Essentially, this is a list of filepaths that, if our dependencies get rebuilt, will themselves get updated.
Note: the hash of these cache files gets built into the build cache ourselves, which means that we end up tracking transitive dependencies!
Note: This tracks the "build" cache file, but not "registration" or "config" cache files. Why not? Arguably we should...
Note: This is a bit of a hack, because it is not really the hashes of the SOURCES of our (transitive) dependencies that we should use to decide whether or not to rebuild, but the output BUILD PRODUCTS. The strategy we use here will never work if we want to implement unchanging rebuilds.
elabRequiresRegistration :: ElaboratedConfiguredPackage -> Bool Source #
The packagecomponent containsis a library and so must be registered
dataDirsEnvironmentForPlan :: DistDirLayout -> ElaboratedInstallPlan -> [(String, Maybe FilePath)] Source #
Construct the environment needed for the data files to work.
This consists of a separate *_datadir
variable for each
inplace package in the plan.
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String Source #
User-friendly display string for an ElaboratedPlanPackage
.
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String Source #
A user-friendly descriptor for an ElaboratedConfiguredPackage
.
data ElaboratedPackageOrComponent Source #
Constructors
ElabPackage ElaboratedPackage | |
ElabComponent ElaboratedComponent |
Instances
Structured ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy ElaboratedPackageOrComponent -> Structure # structureHash' :: Tagged ElaboratedPackageOrComponent MD5 | |||||
Generic ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
| |||||
Show ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> ElaboratedPackageOrComponent -> ShowS # show :: ElaboratedPackageOrComponent -> String # showList :: [ElaboratedPackageOrComponent] -> ShowS # | |||||
Binary ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: ElaboratedPackageOrComponent -> Put # get :: Get ElaboratedPackageOrComponent # putList :: [ElaboratedPackageOrComponent] -> Put # | |||||
Eq ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: ElaboratedPackageOrComponent -> ElaboratedPackageOrComponent -> Bool # (/=) :: ElaboratedPackageOrComponent -> ElaboratedPackageOrComponent -> Bool # | |||||
type Rep ElaboratedPackageOrComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep ElaboratedPackageOrComponent = D1 ('MetaData "ElaboratedPackageOrComponent" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "ElabPackage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElaboratedPackage)) :+: C1 ('MetaCons "ElabComponent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElaboratedComponent))) |
data ElaboratedComponent Source #
Some extra metadata associated with an
ElaboratedConfiguredPackage
which indicates that the "package"
in question is actually a single component to be built. Arguably
it would be clearer if there were an ADT which branched into
package work items and component work items, but I've structured
it this way to minimize change to the existing code (which I
don't feel qualified to rewrite.)
Constructors
ElaboratedComponent | |
Fields
|
Instances
Structured ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy ElaboratedComponent -> Structure # structureHash' :: Tagged ElaboratedComponent MD5 | |||||
Generic ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: ElaboratedComponent -> Rep ElaboratedComponent x # to :: Rep ElaboratedComponent x -> ElaboratedComponent # | |||||
Show ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> ElaboratedComponent -> ShowS # show :: ElaboratedComponent -> String # showList :: [ElaboratedComponent] -> ShowS # | |||||
Binary ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: ElaboratedComponent -> Put # get :: Get ElaboratedComponent # putList :: [ElaboratedComponent] -> Put # | |||||
Eq ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: ElaboratedComponent -> ElaboratedComponent -> Bool # (/=) :: ElaboratedComponent -> ElaboratedComponent -> Bool # | |||||
type Rep ElaboratedComponent Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep ElaboratedComponent = D1 ('MetaData "ElaboratedComponent" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "ElaboratedComponent" 'PrefixI 'True) (((S1 ('MetaSel ('Just "compSolverName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Component) :*: S1 ('MetaSel ('Just "compComponentName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ComponentName))) :*: (S1 ('MetaSel ('Just "compLibDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConfiguredId, Bool)]) :*: S1 ('MetaSel ('Just "compLinkedLibDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [OpenUnitId]))) :*: ((S1 ('MetaSel ('Just "compExeDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ConfiguredId]) :*: S1 ('MetaSel ('Just "compPkgConfigDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(PkgconfigName, Maybe PkgconfigVersion)])) :*: (S1 ('MetaSel ('Just "compExeDependencyPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConfiguredId, FilePath)]) :*: S1 ('MetaSel ('Just "compOrderLibDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))) |
data ElaboratedPackage Source #
Constructors
ElaboratedPackage | |
Fields
|
Instances
Structured ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy ElaboratedPackage -> Structure # structureHash' :: Tagged ElaboratedPackage MD5 | |||||
Generic ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: ElaboratedPackage -> Rep ElaboratedPackage x # to :: Rep ElaboratedPackage x -> ElaboratedPackage # | |||||
Show ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> ElaboratedPackage -> ShowS # show :: ElaboratedPackage -> String # showList :: [ElaboratedPackage] -> ShowS # | |||||
Binary ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: ElaboratedPackage -> Put # get :: Get ElaboratedPackage # putList :: [ElaboratedPackage] -> Put # | |||||
Eq ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: ElaboratedPackage -> ElaboratedPackage -> Bool # (/=) :: ElaboratedPackage -> ElaboratedPackage -> Bool # | |||||
type Rep ElaboratedPackage Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep ElaboratedPackage = D1 ('MetaData "ElaboratedPackage" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "ElaboratedPackage" 'PrefixI 'True) (((S1 ('MetaSel ('Just "pkgInstalledId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstalledPackageId) :*: S1 ('MetaSel ('Just "pkgLibDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ComponentDeps [(ConfiguredId, Bool)]))) :*: (S1 ('MetaSel ('Just "pkgDependsOnSelfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ComponentDeps [()])) :*: S1 ('MetaSel ('Just "pkgExeDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ComponentDeps [ConfiguredId])))) :*: ((S1 ('MetaSel ('Just "pkgExeDependencyPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ComponentDeps [(ConfiguredId, FilePath)])) :*: S1 ('MetaSel ('Just "pkgPkgConfigDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(PkgconfigName, Maybe PkgconfigVersion)])) :*: (S1 ('MetaSel ('Just "pkgStanzasEnabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptionalStanzaSet) :*: S1 ('MetaSel ('Just "pkgWhyNotPerComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty NotPerComponentReason)))))) |
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId] Source #
See elabOrderDependencies
. This gives the unflattened version,
which can be useful in some circumstances.
type ElaboratedPlanPackage = GenericPlanPackage InstalledPackageInfo ElaboratedConfiguredPackage Source #
data ElaboratedSharedConfig Source #
Constructors
ElaboratedSharedConfig | |
Fields
|
Instances
data BuildStyle Source #
This is used in the install plan to indicate how the package will be built.
Constructors
BuildAndInstall | The classic approach where the package is built, then the files installed into some location and the result registered in a package db. If the package came from a tarball then it's built in a temp dir and the results discarded. |
BuildInplaceOnly MemoryOrDisk | For Such packages can still subsequently be installed. Typically For At the moment We use single constructor |
Instances
Structured BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Monoid BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods mempty :: BuildStyle # mappend :: BuildStyle -> BuildStyle -> BuildStyle # mconcat :: [BuildStyle] -> BuildStyle # | |||||
Semigroup BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (<>) :: BuildStyle -> BuildStyle -> BuildStyle # sconcat :: NonEmpty BuildStyle -> BuildStyle # stimes :: Integral b => b -> BuildStyle -> BuildStyle # | |||||
Generic BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
| |||||
Show BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> BuildStyle -> ShowS # show :: BuildStyle -> String # showList :: [BuildStyle] -> ShowS # | |||||
Binary BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Eq BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Ord BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods compare :: BuildStyle -> BuildStyle -> Ordering # (<) :: BuildStyle -> BuildStyle -> Bool # (<=) :: BuildStyle -> BuildStyle -> Bool # (>) :: BuildStyle -> BuildStyle -> Bool # (>=) :: BuildStyle -> BuildStyle -> Bool # max :: BuildStyle -> BuildStyle -> BuildStyle # min :: BuildStyle -> BuildStyle -> BuildStyle # | |||||
type Rep BuildStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep BuildStyle = D1 ('MetaData "BuildStyle" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "BuildAndInstall" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BuildInplaceOnly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MemoryOrDisk))) |
data MemoryOrDisk Source #
How BuildInplaceOnly
component is built.
Instances
Structured MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Generic MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
| |||||
Show MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> MemoryOrDisk -> ShowS # show :: MemoryOrDisk -> String # showList :: [MemoryOrDisk] -> ShowS # | |||||
Binary MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Eq MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types | |||||
Ord MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods compare :: MemoryOrDisk -> MemoryOrDisk -> Ordering # (<) :: MemoryOrDisk -> MemoryOrDisk -> Bool # (<=) :: MemoryOrDisk -> MemoryOrDisk -> Bool # (>) :: MemoryOrDisk -> MemoryOrDisk -> Bool # (>=) :: MemoryOrDisk -> MemoryOrDisk -> Bool # max :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk # min :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk # | |||||
type Rep MemoryOrDisk Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types |
isInplaceBuildStyle :: BuildStyle -> Bool Source #
type CabalFileText = ByteString Source #
data NotPerComponentReason Source #
Why did we fall-back to a per-package build, instead of using a per-component build?
Constructors
CuzBuildType !NotPerComponentBuildType | The build-type does not support per-component builds. |
CuzCabalSpecVersion | The Cabal spec version is too old for per-component builds. |
CuzNoBuildableComponents | There are no buildable components, so we fall-back to a per-package build for error-reporting purposes. |
CuzDisablePerComponent | The user passed |
Instances
Structured NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy NotPerComponentReason -> Structure # structureHash' :: Tagged NotPerComponentReason MD5 | |||||
Generic NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: NotPerComponentReason -> Rep NotPerComponentReason x # to :: Rep NotPerComponentReason x -> NotPerComponentReason # | |||||
Show NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> NotPerComponentReason -> ShowS # show :: NotPerComponentReason -> String # showList :: [NotPerComponentReason] -> ShowS # | |||||
Binary NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: NotPerComponentReason -> Put # get :: Get NotPerComponentReason # putList :: [NotPerComponentReason] -> Put # | |||||
Eq NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: NotPerComponentReason -> NotPerComponentReason -> Bool # (/=) :: NotPerComponentReason -> NotPerComponentReason -> Bool # | |||||
type Rep NotPerComponentReason Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep NotPerComponentReason = D1 ('MetaData "NotPerComponentReason" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) ((C1 ('MetaCons "CuzBuildType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NotPerComponentBuildType)) :+: C1 ('MetaCons "CuzCabalSpecVersion" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CuzNoBuildableComponents" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CuzDisablePerComponent" 'PrefixI 'False) (U1 :: Type -> Type))) |
data NotPerComponentBuildType Source #
Instances
Structured NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy NotPerComponentBuildType -> Structure # structureHash' :: Tagged NotPerComponentBuildType MD5 | |||||
Generic NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: NotPerComponentBuildType -> Rep NotPerComponentBuildType x # to :: Rep NotPerComponentBuildType x -> NotPerComponentBuildType # | |||||
Show NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> NotPerComponentBuildType -> ShowS # show :: NotPerComponentBuildType -> String # showList :: [NotPerComponentBuildType] -> ShowS # | |||||
Binary NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: NotPerComponentBuildType -> Put # get :: Get NotPerComponentBuildType # putList :: [NotPerComponentBuildType] -> Put # | |||||
Eq NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool # (/=) :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool # | |||||
type Rep NotPerComponentBuildType Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep NotPerComponentBuildType = D1 ('MetaData "NotPerComponentBuildType" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) ((C1 ('MetaCons "CuzConfigureBuildType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CuzCustomBuildType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CuzHooksBuildType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CuzMakeBuildType" 'PrefixI 'False) (U1 :: Type -> Type))) |
whyNotPerComponent :: NotPerComponentReason -> String Source #
Display the reason we had to fall-back to a per-package build instead of a per-component build.
Build targets
data ComponentTarget Source #
Specific targets within a package or component to act on e.g. to build, haddock or open a repl.
Constructors
ComponentTarget ComponentName SubComponentTarget |
Instances
Structured ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy ComponentTarget -> Structure # structureHash' :: Tagged ComponentTarget MD5 | |||||
Generic ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: ComponentTarget -> Rep ComponentTarget x # to :: Rep ComponentTarget x -> ComponentTarget # | |||||
Show ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> ComponentTarget -> ShowS # show :: ComponentTarget -> String # showList :: [ComponentTarget] -> ShowS # | |||||
Binary ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: ComponentTarget -> Put # get :: Get ComponentTarget # putList :: [ComponentTarget] -> Put # | |||||
Eq ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: ComponentTarget -> ComponentTarget -> Bool # (/=) :: ComponentTarget -> ComponentTarget -> Bool # | |||||
Ord ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods compare :: ComponentTarget -> ComponentTarget -> Ordering # (<) :: ComponentTarget -> ComponentTarget -> Bool # (<=) :: ComponentTarget -> ComponentTarget -> Bool # (>) :: ComponentTarget -> ComponentTarget -> Bool # (>=) :: ComponentTarget -> ComponentTarget -> Bool # max :: ComponentTarget -> ComponentTarget -> ComponentTarget # min :: ComponentTarget -> ComponentTarget -> ComponentTarget # | |||||
type Rep ComponentTarget Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep ComponentTarget = D1 ('MetaData "ComponentTarget" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "ComponentTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubComponentTarget))) |
showComponentTarget :: PackageId -> ComponentTarget -> String Source #
Unambiguously render a ComponentTarget
, e.g., to pass
to a Cabal Setup script.
data SubComponentTarget Source #
Either the component as a whole or detail about a file or module target within a component.
Constructors
WholeComponent | The component as a whole |
ModuleTarget ModuleName | A specific module within a component. |
FileTarget FilePath | A specific file within a component. Note that this does not carry the file extension. |
Instances
Structured SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods structure :: Proxy SubComponentTarget -> Structure # structureHash' :: Tagged SubComponentTarget MD5 | |||||
Generic SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Associated Types
Methods from :: SubComponentTarget -> Rep SubComponentTarget x # to :: Rep SubComponentTarget x -> SubComponentTarget # | |||||
Show SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods showsPrec :: Int -> SubComponentTarget -> ShowS # show :: SubComponentTarget -> String # showList :: [SubComponentTarget] -> ShowS # | |||||
Binary SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods put :: SubComponentTarget -> Put # get :: Get SubComponentTarget # putList :: [SubComponentTarget] -> Put # | |||||
Eq SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods (==) :: SubComponentTarget -> SubComponentTarget -> Bool # (/=) :: SubComponentTarget -> SubComponentTarget -> Bool # | |||||
Ord SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector Methods compare :: SubComponentTarget -> SubComponentTarget -> Ordering # (<) :: SubComponentTarget -> SubComponentTarget -> Bool # (<=) :: SubComponentTarget -> SubComponentTarget -> Bool # (>) :: SubComponentTarget -> SubComponentTarget -> Bool # (>=) :: SubComponentTarget -> SubComponentTarget -> Bool # max :: SubComponentTarget -> SubComponentTarget -> SubComponentTarget # min :: SubComponentTarget -> SubComponentTarget -> SubComponentTarget # | |||||
type Rep SubComponentTarget Source # | |||||
Defined in Distribution.Client.TargetSelector type Rep SubComponentTarget = D1 ('MetaData "SubComponentTarget" "Distribution.Client.TargetSelector" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "WholeComponent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModuleTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)) :+: C1 ('MetaCons "FileTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) |
componentTargetName :: ComponentTarget -> ComponentName Source #
Extract the component name from a ComponentTarget
.
Setup script
data SetupScriptStyle Source #
There are four major cases for Setup.hs handling:
build-type
Custom with acustom-setup
sectionbuild-type
Custom without acustom-setup
sectionbuild-type
not Custom withcabal-version > $our-cabal-version
build-type
not Custom withcabal-version <= $our-cabal-version
It's also worth noting that packages specifying cabal-version: >= 1.23
or later that have build-type
Custom will always have a custom-setup
section. Therefore in case 2, the specified cabal-version
will always be
less than 1.23.
In cases 1 and 2 we obviously have to build an external Setup.hs script, while in case 4 we can use the internal library API. In case 3 we also have to build an external Setup.hs script because the package needs a later Cabal lib version than we can support internally.
Constructors
SetupCustomExplicitDeps | |
SetupCustomImplicitDeps | |
SetupNonCustomExternalLib | |
SetupNonCustomInternalLib |
Instances
Structured SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods structure :: Proxy SetupScriptStyle -> Structure # structureHash' :: Tagged SetupScriptStyle MD5 | |||||
Generic SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Associated Types
Methods from :: SetupScriptStyle -> Rep SetupScriptStyle x # to :: Rep SetupScriptStyle x -> SetupScriptStyle # | |||||
Show SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods showsPrec :: Int -> SetupScriptStyle -> ShowS # show :: SetupScriptStyle -> String # showList :: [SetupScriptStyle] -> ShowS # | |||||
Binary SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods put :: SetupScriptStyle -> Put # get :: Get SetupScriptStyle # putList :: [SetupScriptStyle] -> Put # | |||||
Eq SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types Methods (==) :: SetupScriptStyle -> SetupScriptStyle -> Bool # (/=) :: SetupScriptStyle -> SetupScriptStyle -> Bool # | |||||
type Rep SetupScriptStyle Source # | |||||
Defined in Distribution.Client.ProjectPlanning.Types type Rep SetupScriptStyle = D1 ('MetaData "SetupScriptStyle" "Distribution.Client.ProjectPlanning.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) ((C1 ('MetaCons "SetupCustomExplicitDeps" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetupCustomImplicitDeps" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SetupNonCustomExternalLib" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetupNonCustomInternalLib" 'PrefixI 'False) (U1 :: Type -> Type))) |