| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Stack.Types.Build
Description
Build-specific types.
Synopsis
- data InstallLocation
- data Installed
- psVersion :: PackageSource -> Version
- data Task = Task {
- taskType :: !TaskType
- configOpts :: !TaskConfigOpts
- buildHaddocks :: !Bool
- present :: !(Map PackageIdentifier GhcPkgId)
- allInOne :: !Bool
- cachePkgSrc :: !CachePkgSrc
- buildTypeConfig :: !Bool
- taskAnyMissing :: Task -> Bool
- taskIsTarget :: Task -> Bool
- taskLocation :: Task -> InstallLocation
- taskProvides :: Task -> PackageIdentifier
- taskTargetIsMutable :: Task -> IsMutable
- taskTypeLocation :: TaskType -> InstallLocation
- taskTypePackageIdentifier :: TaskType -> PackageIdentifier
- data LocalPackage = LocalPackage {
- package :: !Package
- components :: !(Set NamedComponent)
- unbuildable :: !(Set NamedComponent)
- wanted :: !Bool
- testBench :: !(Maybe Package)
- cabalFP :: !(Path Abs File)
- buildHaddocks :: !Bool
- forceDirty :: !Bool
- dirtyFiles :: !(MemoizedWith EnvConfig (Maybe (Set FilePath)))
- newBuildCaches :: !(MemoizedWith EnvConfig (Map NamedComponent (Map FilePath FileCacheInfo)))
- componentFiles :: !(MemoizedWith EnvConfig (Map NamedComponent (Set (Path Abs File))))
- data Plan = Plan {
- tasks :: !(Map PackageName Task)
- finals :: !(Map PackageName Task)
- unregisterLocal :: !(Map GhcPkgId (PackageIdentifier, Text))
- installExes :: !(Map Text InstallLocation)
- data TestOpts = TestOpts {
- rerunTests :: !Bool
- additionalArgs :: ![String]
- coverage :: !Bool
- disableRun :: !Bool
- maximumTimeSeconds :: !(Maybe Int)
- allowStdin :: !Bool
- data BenchmarkOpts = BenchmarkOpts {
- additionalArgs :: !(Maybe String)
- disableRun :: !Bool
- data FileWatchOpts
- data BuildOpts = BuildOpts {
- libProfile :: !Bool
- exeProfile :: !Bool
- libStrip :: !Bool
- exeStrip :: !Bool
- buildHaddocks :: !Bool
- haddockOpts :: !HaddockOpts
- openHaddocks :: !Bool
- haddockDeps :: !(Maybe Bool)
- haddockInternal :: !Bool
- haddockHyperlinkSource :: !Bool
- haddockForHackage :: !Bool
- installExes :: !Bool
- installCompilerTool :: !Bool
- preFetch :: !Bool
- keepGoing :: !(Maybe Bool)
- keepTmpFiles :: !Bool
- forceDirty :: !Bool
- tests :: !Bool
- testOpts :: !TestOpts
- benchmarks :: !Bool
- benchmarkOpts :: !BenchmarkOpts
- reconfigure :: !Bool
- cabalVerbose :: !CabalVerbosity
- splitObjs :: !Bool
- skipComponents :: ![Text]
- interleavedOutput :: !Bool
- progressBar :: !ProgressBarFormat
- ddumpDir :: !(Maybe Text)
- data BuildSubset
- defaultBuildOpts :: BuildOpts
- data TaskType
- installLocationIsMutable :: InstallLocation -> IsMutable
- data TaskConfigOpts = TaskConfigOpts {
- missing :: !(Set PackageIdentifier)
- opts :: !(Map PackageIdentifier GhcPkgId -> ConfigureOpts)
- newtype BuildCache = BuildCache {}
- data ConfigCache = ConfigCache {
- configureOpts :: !ConfigureOpts
- deps :: !(Set GhcPkgId)
- components :: !(Set ByteString)
- buildHaddocks :: !Bool
- pkgSrc :: !CachePkgSrc
- pathEnvVar :: !Text
- configureOpts :: EnvConfig -> BaseConfigOpts -> Map PackageIdentifier GhcPkgId -> Bool -> IsMutable -> Package -> ConfigureOpts
- data CachePkgSrc
- toCachePkgSrc :: PackageSource -> CachePkgSrc
- newtype FileCacheInfo = FileCacheInfo {}
- data PrecompiledCache base = PrecompiledCache {}
- data ExcludeTHLoading
- data ConvertPathsToAbsolute
- data KeepOutputOpen
Documentation
data InstallLocation Source #
Type representing user package databases that packages can be installed into.
Constructors
| Snap | The write-only package database, formerly known as the snapshot database. |
| Local | The mutable package database, formerly known as the local database. |
Instances
| Monoid InstallLocation Source # | |
Defined in Stack.Types.Installed Methods mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # | |
| Semigroup InstallLocation Source # | |
Defined in Stack.Types.Installed Methods (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation # stimes :: Integral b => b -> InstallLocation -> InstallLocation # | |
| Show InstallLocation Source # | |
Defined in Stack.Types.Installed Methods showsPrec :: Int -> InstallLocation -> ShowS # show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS # | |
| Eq InstallLocation Source # | |
Defined in Stack.Types.Installed Methods (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # | |
Type representing information about what is installed.
Constructors
| Library PackageIdentifier InstalledLibraryInfo | A library, including its installed package id and, optionally, its license. |
| Executable PackageIdentifier | An executable. |
psVersion :: PackageSource -> Version Source #
A type representing tasks to perform when building.
Constructors
| Task | |
Fields
| |
taskAnyMissing :: Task -> Bool Source #
Were any of the dependencies missing?
taskIsTarget :: Task -> Bool Source #
taskLocation :: Task -> InstallLocation Source #
A function to yield the relevant database (write-only or mutable) of the given task.
taskProvides :: Task -> PackageIdentifier Source #
A function to yield the package name and version to be built by the given task.
taskTargetIsMutable :: Task -> IsMutable Source #
taskTypeLocation :: TaskType -> InstallLocation Source #
A function to yield the relevant database (write-only or mutable) of a
given TaskType value.
taskTypePackageIdentifier :: TaskType -> PackageIdentifier Source #
A function to yield the package name and version of a given TaskType
value.
data LocalPackage Source #
Information on a locally available package of source code.
Constructors
| LocalPackage | |
Fields
| |
Instances
| Show LocalPackage Source # | |
Defined in Stack.Types.Package Methods showsPrec :: Int -> LocalPackage -> ShowS # show :: LocalPackage -> String # showList :: [LocalPackage] -> ShowS # | |
A complete plan of what needs to be built and how to do it
Constructors
| Plan | |
Fields
| |
Options for the FinalAction DoTests
Constructors
| TestOpts | |
Fields
| |
data BenchmarkOpts Source #
Options for the FinalAction DoBenchmarks
Constructors
| BenchmarkOpts | |
Fields
| |
Instances
| Show BenchmarkOpts Source # | |
Defined in Stack.Types.BuildOpts Methods showsPrec :: Int -> BenchmarkOpts -> ShowS # show :: BenchmarkOpts -> String # showList :: [BenchmarkOpts] -> ShowS # | |
| Eq BenchmarkOpts Source # | |
Defined in Stack.Types.BuildOpts Methods (==) :: BenchmarkOpts -> BenchmarkOpts -> Bool # (/=) :: BenchmarkOpts -> BenchmarkOpts -> Bool # | |
data FileWatchOpts Source #
Constructors
| NoFileWatch | |
| FileWatch | |
| FileWatchPoll |
Instances
| Show FileWatchOpts Source # | |
Defined in Stack.Types.BuildOptsCLI Methods showsPrec :: Int -> FileWatchOpts -> ShowS # show :: FileWatchOpts -> String # showList :: [FileWatchOpts] -> ShowS # | |
| Eq FileWatchOpts Source # | |
Defined in Stack.Types.BuildOptsCLI Methods (==) :: FileWatchOpts -> FileWatchOpts -> Bool # (/=) :: FileWatchOpts -> FileWatchOpts -> Bool # | |
Build options that is interpreted by the build command. This is built up from BuildOptsCLI and BuildOptsMonoid
Constructors
| BuildOpts | |
Fields
| |
data BuildSubset Source #
Which subset of packages to build
Constructors
| BSAll | |
| BSOnlySnapshot | Only install packages in the snapshot database, skipping packages intended for the local database. |
| BSOnlyDependencies | |
| BSOnlyLocals | Refuse to build anything in the snapshot database, see https://github.com/commercialhaskell/stack/issues/5272 |
Instances
| Show BuildSubset Source # | |
Defined in Stack.Types.BuildOptsCLI Methods showsPrec :: Int -> BuildSubset -> ShowS # show :: BuildSubset -> String # showList :: [BuildSubset] -> ShowS # | |
| Eq BuildSubset Source # | |
Defined in Stack.Types.BuildOptsCLI | |
Type representing different types of task, depending on what is to be built.
Constructors
| TTLocalMutable LocalPackage | Building local source code. |
| TTRemotePackage IsMutable Package PackageLocationImmutable | Building something from the package index (upstream). |
data TaskConfigOpts Source #
Given the IDs of any missing packages, produce the configure options
Constructors
| TaskConfigOpts | |
Fields
| |
Instances
| Show TaskConfigOpts Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> TaskConfigOpts -> ShowS # show :: TaskConfigOpts -> String # showList :: [TaskConfigOpts] -> ShowS # | |
newtype BuildCache Source #
Stored on disk to know whether the files have changed.
Constructors
| BuildCache | |
Fields
| |
Instances
data ConfigCache Source #
Stored on disk to know whether the flags have changed.
Constructors
| ConfigCache | |
Fields
| |
Instances
Arguments
| :: EnvConfig | |
| -> BaseConfigOpts | |
| -> Map PackageIdentifier GhcPkgId | dependencies |
| -> Bool | local non-extra-dep? |
| -> IsMutable | |
| -> Package | |
| -> ConfigureOpts |
Render a BaseConfigOpts to an actual list of options
data CachePkgSrc Source #
Constructors
| CacheSrcUpstream | |
| CacheSrcLocal FilePath |
Instances
newtype FileCacheInfo Source #
Constructors
| FileCacheInfo | |
Instances
data PrecompiledCache base Source #
Information on a compiled package: the library .conf file (if relevant), the sub-libraries (if present) and all of the executable paths.
Constructors
| PrecompiledCache | |
Instances
data ExcludeTHLoading Source #
Constructors
| ExcludeTHLoading | |
| KeepTHLoading |
data ConvertPathsToAbsolute Source #
Constructors
| ConvertPathsToAbsolute | |
| KeepPathsAsIs |
data KeepOutputOpen Source #
special marker for expected failures in curator builds, using those we need to keep log handle open as build continues further even after a failure
Constructors
| KeepOpen | |
| CloseOnException |
Instances
| Eq KeepOutputOpen Source # | |
Defined in Stack.Types.Build Methods (==) :: KeepOutputOpen -> KeepOutputOpen -> Bool # (/=) :: KeepOutputOpen -> KeepOutputOpen -> Bool # | |