Safe Haskell | None |
---|---|
Language | Haskell2010 |
Stack.Types.Build
Description
Build-specific types.
Synopsis
- data StackBuildException
- = Couldn'tFindPkgId PackageName
- | CompilerVersionMismatch (Maybe (CompilerVersion CVActual, Arch)) (CompilerVersion CVWanted, Arch) GHCVariant CompilerBuild VersionCheck (Maybe (Path Abs File)) Text
- | Couldn'tParseTargets [Text]
- | UnknownTargets (Set PackageName) (Map PackageName Version) (Path Abs File)
- | TestSuiteFailure PackageIdentifier (Map Text (Maybe ExitCode)) (Maybe (Path Abs File)) ByteString
- | TestSuiteTypeUnsupported TestSuiteInterface
- | ConstructPlanFailed String
- | CabalExitedUnsuccessfully ExitCode PackageIdentifier (Path Abs File) [String] (Maybe (Path Abs File)) [Text]
- | SetupHsBuildFailure ExitCode (Maybe PackageIdentifier) (Path Abs File) [String] (Maybe (Path Abs File)) [Text]
- | ExecutionFailure [SomeException]
- | LocalPackageDoesn'tMatchTarget PackageName Version Version
- | NoSetupHsFound (Path Abs Dir)
- | InvalidFlagSpecification (Set UnusedFlags)
- | TargetParseException [Text]
- | SolverGiveUp String
- | SolverMissingCabalInstall
- | SomeTargetsNotBuildable [(PackageName, NamedComponent)]
- | TestSuiteExeMissing Bool String String String
- | CabalCopyFailed Bool String
- | LocalPackagesPresent [PackageIdentifier]
- data FlagSource
- data UnusedFlags
- data InstallLocation
- data ModTime
- modTime :: UTCTime -> ModTime
- data Installed
- piiVersion :: PackageSource -> Version
- piiLocation :: PackageSource -> InstallLocation
- data Task = Task {}
- taskIsTarget :: Task -> Bool
- taskLocation :: Task -> InstallLocation
- data LocalPackage = LocalPackage {
- lpPackage :: !Package
- lpComponents :: !(Set NamedComponent)
- lpUnbuildable :: !(Set NamedComponent)
- lpWanted :: !Bool
- lpTestDeps :: !(Map PackageName VersionRange)
- lpBenchDeps :: !(Map PackageName VersionRange)
- lpTestBench :: !(Maybe Package)
- lpDir :: !(Path Abs Dir)
- lpCabalFile :: !(Path Abs File)
- lpForceDirty :: !Bool
- lpDirtyFiles :: !(Maybe (Set FilePath))
- lpNewBuildCaches :: !(Map NamedComponent (Map FilePath FileCacheInfo))
- lpComponentFiles :: !(Map NamedComponent (Set (Path Abs File)))
- lpLocation :: !(PackageLocation FilePath)
- data BaseConfigOpts = BaseConfigOpts {
- bcoSnapDB :: !(Path Abs Dir)
- bcoLocalDB :: !(Path Abs Dir)
- bcoSnapInstallRoot :: !(Path Abs Dir)
- bcoLocalInstallRoot :: !(Path Abs Dir)
- bcoBuildOpts :: !BuildOpts
- bcoBuildOptsCLI :: !BuildOptsCLI
- bcoExtraDBs :: ![Path Abs Dir]
- 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
- 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
- boptsInstallExes :: !Bool
- boptsInstallCompilerTool :: !Bool
- boptsPreFetch :: !Bool
- boptsKeepGoing :: !(Maybe Bool)
- boptsKeepTmpFiles :: !(Maybe Bool)
- boptsForceDirty :: !Bool
- boptsTests :: !Bool
- boptsTestOpts :: !TestOpts
- boptsBenchmarks :: !Bool
- boptsBenchmarkOpts :: !BenchmarkOpts
- boptsReconfigure :: !Bool
- boptsCabalVerbose :: !Bool
- boptsSplitObjs :: !Bool
- boptsSkipComponents :: ![Text]
- boptsInterleavedOutput :: !Bool
- data BuildSubset
- defaultBuildOpts :: BuildOpts
- data TaskType
- ttPackageLocation :: TaskType -> PackageLocationIndex FilePath
- data TaskConfigOpts = TaskConfigOpts {
- tcoMissing :: !(Set PackageIdentifier)
- tcoOpts :: !(Map PackageIdentifier GhcPkgId -> ConfigureOpts)
- newtype BuildCache = BuildCache {}
- buildCacheVC :: VersionConfig BuildCache
- data ConfigCache = ConfigCache {}
- configCacheVC :: VersionConfig ConfigCache
- configureOpts :: EnvConfig -> BaseConfigOpts -> Map PackageIdentifier GhcPkgId -> Bool -> InstallLocation -> Package -> ConfigureOpts
- data CachePkgSrc
- toCachePkgSrc :: PackageSource -> CachePkgSrc
- isStackOpt :: Text -> Bool
- wantedLocalPackages :: [LocalPackage] -> Set PackageName
- data FileCacheInfo = FileCacheInfo {
- fciModTime :: !ModTime
- fciSize :: !Word64
- fciHash :: !ByteString
- data ConfigureOpts = ConfigureOpts {}
- data PrecompiledCache = PrecompiledCache {}
- precompiledCacheVC :: VersionConfig PrecompiledCache
Documentation
data StackBuildException #
Constructors
Instances
Show StackBuildException # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> StackBuildException -> ShowS # show :: StackBuildException -> String # showList :: [StackBuildException] -> ShowS # | |
Exception StackBuildException # | |
Defined in Stack.Types.Build Methods toException :: StackBuildException -> SomeException # fromException :: SomeException -> Maybe StackBuildException # |
data FlagSource #
Constructors
FSCommandLine | |
FSStackYaml |
Instances
Eq FlagSource # | |
Defined in Stack.Types.Build | |
Ord FlagSource # | |
Defined in Stack.Types.Build Methods compare :: FlagSource -> FlagSource -> Ordering # (<) :: FlagSource -> FlagSource -> Bool # (<=) :: FlagSource -> FlagSource -> Bool # (>) :: FlagSource -> FlagSource -> Bool # (>=) :: FlagSource -> FlagSource -> Bool # max :: FlagSource -> FlagSource -> FlagSource # min :: FlagSource -> FlagSource -> FlagSource # | |
Show FlagSource # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> FlagSource -> ShowS # show :: FlagSource -> String # showList :: [FlagSource] -> ShowS # |
data UnusedFlags #
Constructors
UFNoPackage FlagSource PackageName | |
UFFlagsNotDefined FlagSource Package (Set FlagName) | |
UFSnapshot PackageName |
Instances
Eq UnusedFlags # | |
Defined in Stack.Types.Build | |
Ord UnusedFlags # | |
Defined in Stack.Types.Build Methods compare :: UnusedFlags -> UnusedFlags -> Ordering # (<) :: UnusedFlags -> UnusedFlags -> Bool # (<=) :: UnusedFlags -> UnusedFlags -> Bool # (>) :: UnusedFlags -> UnusedFlags -> Bool # (>=) :: UnusedFlags -> UnusedFlags -> Bool # max :: UnusedFlags -> UnusedFlags -> UnusedFlags # min :: UnusedFlags -> UnusedFlags -> UnusedFlags # | |
Show UnusedFlags # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> UnusedFlags -> ShowS # show :: UnusedFlags -> String # showList :: [UnusedFlags] -> ShowS # |
data InstallLocation #
A location to install a package into, either snapshot or local
Instances
Eq InstallLocation # | |
Defined in Stack.Types.Package Methods (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # | |
Show InstallLocation # | |
Defined in Stack.Types.Package Methods showsPrec :: Int -> InstallLocation -> ShowS # show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS # | |
Semigroup InstallLocation # | |
Defined in Stack.Types.Package Methods (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation # stimes :: Integral b => b -> InstallLocation -> InstallLocation # | |
Monoid InstallLocation # | |
Defined in Stack.Types.Package Methods mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # |
Used for storage and comparison.
Instances
Eq ModTime # | |
Data ModTime # | |
Defined in Stack.Types.Package Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModTime -> c ModTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModTime # toConstr :: ModTime -> Constr # dataTypeOf :: ModTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModTime) # gmapT :: (forall b. Data b => b -> b) -> ModTime -> ModTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModTime -> r # gmapQ :: (forall d. Data d => d -> u) -> ModTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModTime -> m ModTime # | |
Ord ModTime # | |
Show ModTime # | |
Generic ModTime # | |
NFData ModTime # | |
Defined in Stack.Types.Package | |
Store ModTime # | |
type Rep ModTime # | |
Constructors
Library PackageIdentifier GhcPkgId (Maybe (Either License License)) | |
Executable PackageIdentifier |
piiVersion :: PackageSource -> Version #
A task to perform when building
Constructors
Task | |
Fields
|
taskIsTarget :: Task -> Bool #
taskLocation :: Task -> InstallLocation #
data LocalPackage #
Information on a locally available package of source code
Constructors
LocalPackage | |
Fields
|
Instances
Show LocalPackage # | |
Defined in Stack.Types.Package Methods showsPrec :: Int -> LocalPackage -> ShowS # show :: LocalPackage -> String # showList :: [LocalPackage] -> ShowS # |
data BaseConfigOpts #
Basic information used to calculate what the configure options are
Constructors
BaseConfigOpts | |
Fields
|
Instances
Show BaseConfigOpts # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> BaseConfigOpts -> ShowS # show :: BaseConfigOpts -> String # showList :: [BaseConfigOpts] -> 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 #
Options for the FinalAction
DoBenchmarks
Constructors
BenchmarkOpts | |
Fields
|
Instances
Eq BenchmarkOpts # | |
Defined in Stack.Types.Config.Build Methods (==) :: BenchmarkOpts -> BenchmarkOpts -> Bool # (/=) :: BenchmarkOpts -> BenchmarkOpts -> Bool # | |
Show BenchmarkOpts # | |
Defined in Stack.Types.Config.Build Methods showsPrec :: Int -> BenchmarkOpts -> ShowS # show :: BenchmarkOpts -> String # showList :: [BenchmarkOpts] -> ShowS # |
data FileWatchOpts #
Constructors
NoFileWatch | |
FileWatch | |
FileWatchPoll |
Instances
Eq FileWatchOpts # | |
Defined in Stack.Types.Config.Build Methods (==) :: FileWatchOpts -> FileWatchOpts -> Bool # (/=) :: FileWatchOpts -> FileWatchOpts -> Bool # | |
Show FileWatchOpts # | |
Defined in Stack.Types.Config.Build Methods showsPrec :: Int -> FileWatchOpts -> ShowS # show :: FileWatchOpts -> String # showList :: [FileWatchOpts] -> ShowS # |
Build options that is interpreted by the build command. This is built up from BuildOptsCLI and BuildOptsMonoid
Constructors
BuildOpts | |
Fields
|
data BuildSubset #
Which subset of packages to build
Constructors
BSAll | |
BSOnlySnapshot | Only install packages in the snapshot database, skipping packages intended for the local database. |
BSOnlyDependencies |
Instances
Eq BuildSubset # | |
Defined in Stack.Types.Config.Build | |
Show BuildSubset # | |
Defined in Stack.Types.Config.Build Methods showsPrec :: Int -> BuildSubset -> ShowS # show :: BuildSubset -> String # showList :: [BuildSubset] -> ShowS # |
The type of a task, either building local code or something from the package index (upstream)
data TaskConfigOpts #
Given the IDs of any missing packages, produce the configure options
Constructors
TaskConfigOpts | |
Fields
|
Instances
Show TaskConfigOpts # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> TaskConfigOpts -> ShowS # show :: TaskConfigOpts -> String # showList :: [TaskConfigOpts] -> ShowS # |
newtype BuildCache #
Stored on disk to know whether the files have changed.
Constructors
BuildCache | |
Fields
|
Instances
Eq BuildCache # | |
Defined in Stack.Types.Build | |
Data BuildCache # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildCache -> c BuildCache # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildCache # toConstr :: BuildCache -> Constr # dataTypeOf :: BuildCache -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildCache) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildCache) # gmapT :: (forall b. Data b => b -> b) -> BuildCache -> BuildCache # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildCache -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildCache -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildCache -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildCache -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildCache -> m BuildCache # | |
Show BuildCache # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> BuildCache -> ShowS # show :: BuildCache -> String # showList :: [BuildCache] -> ShowS # | |
Generic BuildCache # | |
Defined in Stack.Types.Build Associated Types type Rep BuildCache :: Type -> Type # | |
NFData BuildCache # | |
Defined in Stack.Types.Build Methods rnf :: BuildCache -> () # | |
Store BuildCache # | |
Defined in Stack.Types.Build | |
type Rep BuildCache # | |
Defined in Stack.Types.Build type Rep BuildCache = D1 (MetaData "BuildCache" "Stack.Types.Build" "stack-1.9.3-5ihSa7Nq9ixFkDyEyQZs8l" True) (C1 (MetaCons "BuildCache" PrefixI True) (S1 (MetaSel (Just "buildCacheTimes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map FilePath FileCacheInfo)))) |
data ConfigCache #
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? |
-> InstallLocation | |
-> Package | |
-> ConfigureOpts |
Render a BaseConfigOpts
to an actual list of options
data CachePkgSrc #
Constructors
CacheSrcUpstream | |
CacheSrcLocal FilePath |
Instances
Eq CachePkgSrc # | |
Defined in Stack.Types.Build | |
Data CachePkgSrc # | |
Defined in Stack.Types.Build Methods 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 :: (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 # | |
Show CachePkgSrc # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> CachePkgSrc -> ShowS # show :: CachePkgSrc -> String # showList :: [CachePkgSrc] -> ShowS # | |
Generic CachePkgSrc # | |
Defined in Stack.Types.Build Associated Types type Rep CachePkgSrc :: Type -> Type # | |
NFData CachePkgSrc # | |
Defined in Stack.Types.Build Methods rnf :: CachePkgSrc -> () # | |
Store CachePkgSrc # | |
Defined in Stack.Types.Build | |
type Rep CachePkgSrc # | |
Defined in Stack.Types.Build type Rep CachePkgSrc = D1 (MetaData "CachePkgSrc" "Stack.Types.Build" "stack-1.9.3-5ihSa7Nq9ixFkDyEyQZs8l" False) (C1 (MetaCons "CacheSrcUpstream" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CacheSrcLocal" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))) |
isStackOpt :: Text -> Bool #
wantedLocalPackages :: [LocalPackage] -> Set PackageName #
Get set of wanted package names from locals.
data FileCacheInfo #
Constructors
FileCacheInfo | |
Fields
|
Instances
data ConfigureOpts #
Configure options to be sent to Setup.hs configure
Constructors
ConfigureOpts | |
Instances
data PrecompiledCache #
Information on a compiled package: the library conf file (if relevant), the sublibraries (if present) and all of the executable paths.
Constructors
PrecompiledCache | |