Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Build-specific types.
Synopsis
- data InstallLocation
- data Installed
- psVersion :: PackageSource -> Version
- data Task = Task {}
- taskIsTarget :: Task -> Bool
- taskLocation :: Task -> InstallLocation
- taskTargetIsMutable :: Task -> IsMutable
- data LocalPackage = LocalPackage {
- lpPackage :: !Package
- lpComponents :: !(Set NamedComponent)
- lpUnbuildable :: !(Set NamedComponent)
- lpWanted :: !Bool
- lpTestBench :: !(Maybe Package)
- lpCabalFile :: !(Path Abs File)
- lpBuildHaddocks :: !Bool
- lpForceDirty :: !Bool
- lpDirtyFiles :: !(MemoizedWith EnvConfig (Maybe (Set FilePath)))
- lpNewBuildCaches :: !(MemoizedWith EnvConfig (Map NamedComponent (Map FilePath FileCacheInfo)))
- lpComponentFiles :: !(MemoizedWith EnvConfig (Map NamedComponent (Set (Path Abs File))))
- data Plan = Plan {
- planTasks :: !(Map PackageName Task)
- planFinals :: !(Map PackageName Task)
- planUnregisterLocal :: !(Map GhcPkgId (PackageIdentifier, Text))
- planInstallExes :: !(Map Text InstallLocation)
- data TestOpts = TestOpts {
- toRerunTests :: !Bool
- toAdditionalArgs :: ![String]
- toCoverage :: !Bool
- toDisableRun :: !Bool
- toMaximumTimeSeconds :: !(Maybe Int)
- toAllowStdin :: !Bool
- data BenchmarkOpts = BenchmarkOpts {
- beoAdditionalArgs :: !(Maybe String)
- beoDisableRun :: !Bool
- data FileWatchOpts
- data BuildOpts = BuildOpts {
- boptsLibProfile :: !Bool
- boptsExeProfile :: !Bool
- boptsLibStrip :: !Bool
- boptsExeStrip :: !Bool
- boptsHaddock :: !Bool
- boptsHaddockOpts :: !HaddockOpts
- boptsOpenHaddocks :: !Bool
- boptsHaddockDeps :: !(Maybe Bool)
- boptsHaddockInternal :: !Bool
- boptsHaddockHyperlinkSource :: !Bool
- boptsHaddockForHackage :: !Bool
- boptsInstallExes :: !Bool
- boptsInstallCompilerTool :: !Bool
- boptsPreFetch :: !Bool
- boptsKeepGoing :: !(Maybe Bool)
- boptsKeepTmpFiles :: !Bool
- boptsForceDirty :: !Bool
- boptsTests :: !Bool
- boptsTestOpts :: !TestOpts
- boptsBenchmarks :: !Bool
- boptsBenchmarkOpts :: !BenchmarkOpts
- boptsReconfigure :: !Bool
- boptsCabalVerbose :: !CabalVerbosity
- boptsSplitObjs :: !Bool
- boptsSkipComponents :: ![Text]
- boptsInterleavedOutput :: !Bool
- boptsProgressBar :: !ProgressBarFormat
- boptsDdumpDir :: !(Maybe Text)
- data BuildSubset
- defaultBuildOpts :: BuildOpts
- data TaskType
- installLocationIsMutable :: InstallLocation -> IsMutable
- data TaskConfigOpts = TaskConfigOpts {
- tcoMissing :: !(Set PackageIdentifier)
- tcoOpts :: !(Map PackageIdentifier GhcPkgId -> ConfigureOpts)
- newtype BuildCache = BuildCache {}
- data ConfigCache = ConfigCache {}
- configureOpts :: EnvConfig -> BaseConfigOpts -> Map PackageIdentifier GhcPkgId -> Bool -> IsMutable -> Package -> ConfigureOpts
- data CachePkgSrc
- toCachePkgSrc :: PackageSource -> CachePkgSrc
- newtype FileCacheInfo = FileCacheInfo {}
- data PrecompiledCache base = PrecompiledCache {}
Documentation
data InstallLocation Source #
A location to install a package into, either snapshot or local
Instances
Monoid InstallLocation Source # | |
Defined in Stack.Types.Package mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # | |
Semigroup InstallLocation Source # | |
Defined in Stack.Types.Package (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation # stimes :: Integral b => b -> InstallLocation -> InstallLocation # | |
Show InstallLocation Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> InstallLocation -> ShowS # show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS # | |
Eq InstallLocation Source # | |
Defined in Stack.Types.Package (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # |
Instances
psVersion :: PackageSource -> Version Source #
A task to perform when building
Task | |
|
taskIsTarget :: Task -> Bool Source #
taskLocation :: Task -> InstallLocation Source #
taskTargetIsMutable :: Task -> IsMutable Source #
data LocalPackage Source #
Information on a locally available package of source code.
LocalPackage | |
|
Instances
Show LocalPackage Source # | |
Defined in Stack.Types.Package showsPrec :: Int -> LocalPackage -> ShowS # show :: LocalPackage -> String # showList :: [LocalPackage] -> ShowS # |
A complete plan of what needs to be built and how to do it
Plan | |
|
Options for the FinalAction
DoTests
TestOpts | |
|
data BenchmarkOpts Source #
Options for the FinalAction
DoBenchmarks
BenchmarkOpts | |
|
Instances
Show BenchmarkOpts Source # | |
Defined in Stack.Types.BuildOpts showsPrec :: Int -> BenchmarkOpts -> ShowS # show :: BenchmarkOpts -> String # showList :: [BenchmarkOpts] -> ShowS # | |
Eq BenchmarkOpts Source # | |
Defined in Stack.Types.BuildOpts (==) :: BenchmarkOpts -> BenchmarkOpts -> Bool # (/=) :: BenchmarkOpts -> BenchmarkOpts -> Bool # |
data FileWatchOpts Source #
Instances
Show FileWatchOpts Source # | |
Defined in Stack.Types.BuildOpts showsPrec :: Int -> FileWatchOpts -> ShowS # show :: FileWatchOpts -> String # showList :: [FileWatchOpts] -> ShowS # | |
Eq FileWatchOpts Source # | |
Defined in Stack.Types.BuildOpts (==) :: FileWatchOpts -> FileWatchOpts -> Bool # (/=) :: FileWatchOpts -> FileWatchOpts -> Bool # |
Build options that is interpreted by the build command. This is built up from BuildOptsCLI and BuildOptsMonoid
BuildOpts | |
|
data BuildSubset Source #
Which subset of packages to build
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.BuildOpts showsPrec :: Int -> BuildSubset -> ShowS # show :: BuildSubset -> String # showList :: [BuildSubset] -> ShowS # | |
Eq BuildSubset Source # | |
Defined in Stack.Types.BuildOpts (==) :: BuildSubset -> BuildSubset -> Bool # (/=) :: BuildSubset -> BuildSubset -> Bool # |
The type of a task, either building local code or something from the package index (upstream)
data TaskConfigOpts Source #
Given the IDs of any missing packages, produce the configure options
TaskConfigOpts | |
|
Instances
Show TaskConfigOpts Source # | |
Defined in Stack.Types.Build showsPrec :: Int -> TaskConfigOpts -> ShowS # show :: TaskConfigOpts -> String # showList :: [TaskConfigOpts] -> ShowS # |
newtype BuildCache Source #
Stored on disk to know whether the files have changed.
BuildCache | |
|
Instances
data ConfigCache Source #
Stored on disk to know whether the flags have changed.
ConfigCache | |
|
Instances
:: 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 #
Instances
newtype FileCacheInfo Source #
Instances
data PrecompiledCache base Source #
Information on a compiled package: the library conf file (if relevant), the sublibraries (if present) and all of the executable paths.