Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
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 StackUnqualCompName 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)
- haddockExecutables :: !Bool
- haddockTests :: !Bool
- haddockBenchmarks :: !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 :: ![StackUnqualCompName]
- interleavedOutput :: !Bool
- progressBar :: !ProgressBarFormat
- ddumpDir :: !(Maybe Text)
- data BuildSubset
- defaultBuildOpts :: BuildOpts
- data TaskType
- installLocationIsMutable :: InstallLocation -> IsMutable
- data TaskConfigOpts = TaskConfigOpts {}
- 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 -> PackageConfigureOpts -> 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.
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 mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # | |
Semigroup InstallLocation Source # | |
Defined in Stack.Types.Installed (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation # stimes :: Integral b => b -> InstallLocation -> InstallLocation # | |
Show InstallLocation Source # | |
Defined in Stack.Types.Installed showsPrec :: Int -> InstallLocation -> ShowS # show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS # | |
Eq InstallLocation Source # | |
Defined in Stack.Types.Installed (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # |
Type representing information about what is installed.
Library PackageIdentifier InstalledLibraryInfo | A library, including its installed package id and, optionally, its license. |
Executable PackageIdentifier | An executable. |
Instances
psVersion :: PackageSource -> Version Source #
A type representing tasks to perform when building.
Task | |
|
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.
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.BuildOptsCLI showsPrec :: Int -> FileWatchOpts -> ShowS # show :: FileWatchOpts -> String # showList :: [FileWatchOpts] -> ShowS # | |
Eq FileWatchOpts Source # | |
Defined in Stack.Types.BuildOptsCLI (==) :: 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.BuildOptsCLI showsPrec :: Int -> BuildSubset -> ShowS # show :: BuildSubset -> String # showList :: [BuildSubset] -> ShowS # | |
Eq BuildSubset Source # | |
Defined in Stack.Types.BuildOptsCLI (==) :: BuildSubset -> BuildSubset -> Bool # (/=) :: BuildSubset -> BuildSubset -> Bool # |
Type representing different types of task, depending on what is to be built.
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
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
Data ConfigCache Source # | |
Defined in Stack.Types.Build gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigCache -> c ConfigCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigCache # toConstr :: ConfigCache -> Constr # dataTypeOf :: ConfigCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigCache) # gmapT :: (forall b. Data b => b -> b) -> ConfigCache -> ConfigCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigCache -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigCache -> r # gmapQ :: (forall d. Data d => d -> u) -> ConfigCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigCache -> m ConfigCache # | |
Generic ConfigCache Source # | |
Defined in Stack.Types.Build type Rep ConfigCache :: Type -> Type # from :: ConfigCache -> Rep ConfigCache x # to :: Rep ConfigCache x -> ConfigCache # | |
Show ConfigCache Source # | |
Defined in Stack.Types.Build showsPrec :: Int -> ConfigCache -> ShowS # show :: ConfigCache -> String # showList :: [ConfigCache] -> ShowS # | |
NFData ConfigCache Source # | |
Defined in Stack.Types.Build rnf :: ConfigCache -> () # | |
Eq ConfigCache Source # | |
Defined in Stack.Types.Build (==) :: ConfigCache -> ConfigCache -> Bool # (/=) :: ConfigCache -> ConfigCache -> Bool # | |
type Rep ConfigCache Source # | |
Defined in Stack.Types.Build type Rep ConfigCache = D1 ('MetaData "ConfigCache" "Stack.Types.Build" "stack-3.1.1-I5OI2i8TUoz1thruFO0H72" 'False) (C1 ('MetaCons "ConfigCache" 'PrefixI 'True) ((S1 ('MetaSel ('Just "configureOpts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConfigureOpts) :*: (S1 ('MetaSel ('Just "deps") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set GhcPkgId)) :*: S1 ('MetaSel ('Just "components") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set ByteString)))) :*: (S1 ('MetaSel ('Just "buildHaddocks") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "pkgSrc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CachePkgSrc) :*: S1 ('MetaSel ('Just "pathEnvVar") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))) |
:: EnvConfig | |
-> BaseConfigOpts | |
-> Map PackageIdentifier GhcPkgId | dependencies |
-> Bool | local non-extra-dep? |
-> IsMutable | |
-> PackageConfigureOpts | |
-> ConfigureOpts |
Render a BaseConfigOpts
to an actual list of options
data CachePkgSrc Source #
Instances
Data CachePkgSrc Source # | |
Defined in Stack.Types.Build gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CachePkgSrc -> c CachePkgSrc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CachePkgSrc # toConstr :: CachePkgSrc -> Constr # dataTypeOf :: CachePkgSrc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CachePkgSrc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CachePkgSrc) # gmapT :: (forall b. Data b => b -> b) -> CachePkgSrc -> CachePkgSrc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CachePkgSrc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CachePkgSrc -> r # gmapQ :: (forall d. Data d => d -> u) -> CachePkgSrc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CachePkgSrc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CachePkgSrc -> m CachePkgSrc # | |
Generic CachePkgSrc Source # | |
Defined in Stack.Types.Build type Rep CachePkgSrc :: Type -> Type # from :: CachePkgSrc -> Rep CachePkgSrc x # to :: Rep CachePkgSrc x -> CachePkgSrc # | |
Read CachePkgSrc Source # | |
Defined in Stack.Types.Build readsPrec :: Int -> ReadS CachePkgSrc # readList :: ReadS [CachePkgSrc] # readPrec :: ReadPrec CachePkgSrc # readListPrec :: ReadPrec [CachePkgSrc] # | |
Show CachePkgSrc Source # | |
Defined in Stack.Types.Build showsPrec :: Int -> CachePkgSrc -> ShowS # show :: CachePkgSrc -> String # showList :: [CachePkgSrc] -> ShowS # | |
NFData CachePkgSrc Source # | |
Defined in Stack.Types.Build rnf :: CachePkgSrc -> () # | |
Eq CachePkgSrc Source # | |
Defined in Stack.Types.Build (==) :: CachePkgSrc -> CachePkgSrc -> Bool # (/=) :: CachePkgSrc -> CachePkgSrc -> Bool # | |
PersistField CachePkgSrc Source # | |
Defined in Stack.Types.Build | |
PersistFieldSql CachePkgSrc Source # | |
Defined in Stack.Types.Build sqlType :: Proxy CachePkgSrc -> SqlType # | |
type Rep CachePkgSrc Source # | |
Defined in Stack.Types.Build type Rep CachePkgSrc = D1 ('MetaData "CachePkgSrc" "Stack.Types.Build" "stack-3.1.1-I5OI2i8TUoz1thruFO0H72" 'False) (C1 ('MetaCons "CacheSrcUpstream" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CacheSrcLocal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) |
newtype FileCacheInfo Source #
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.
Instances
Generic (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build type Rep (PrecompiledCache base) :: Type -> Type # from :: PrecompiledCache base -> Rep (PrecompiledCache base) x # to :: Rep (PrecompiledCache base) x -> PrecompiledCache base # | |
Show (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build showsPrec :: Int -> PrecompiledCache base -> ShowS # show :: PrecompiledCache base -> String # showList :: [PrecompiledCache base] -> ShowS # | |
NFData (PrecompiledCache Abs) Source # | |
Defined in Stack.Types.Build rnf :: PrecompiledCache Abs -> () # | |
NFData (PrecompiledCache Rel) Source # | |
Defined in Stack.Types.Build rnf :: PrecompiledCache Rel -> () # | |
Eq (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build (==) :: PrecompiledCache base -> PrecompiledCache base -> Bool # (/=) :: PrecompiledCache base -> PrecompiledCache base -> Bool # | |
type Rep (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build type Rep (PrecompiledCache base) = D1 ('MetaData "PrecompiledCache" "Stack.Types.Build" "stack-3.1.1-I5OI2i8TUoz1thruFO0H72" 'False) (C1 ('MetaCons "PrecompiledCache" 'PrefixI 'True) (S1 ('MetaSel ('Just "library") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Path base File))) :*: (S1 ('MetaSel ('Just "subLibs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Path base File]) :*: S1 ('MetaSel ('Just "exes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Path base File])))) |
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
Instances
Eq KeepOutputOpen Source # | |
Defined in Stack.Types.Build (==) :: KeepOutputOpen -> KeepOutputOpen -> Bool # (/=) :: KeepOutputOpen -> KeepOutputOpen -> Bool # |