Safe Haskell | None |
---|---|
Language | Haskell2010 |
Stack.Types.Build
Description
Build-specific types.
Synopsis
- data StackBuildException
- = Couldn'tFindPkgId PackageName
- | CompilerVersionMismatch (Maybe (ActualCompiler, Arch)) (WantedCompiler, 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)
- | InvalidGhcOptionsSpecification [PackageName]
- | TargetParseException [Text]
- | SomeTargetsNotBuildable [(PackageName, NamedComponent)]
- | TestSuiteExeMissing Bool String String String
- | CabalCopyFailed Bool String
- | LocalPackagesPresent [PackageIdentifier]
- | CouldNotLockDistDir !(Path Abs File)
- data FlagSource
- data UnusedFlags
- data InstallLocation
- data Installed
- = Library PackageIdentifier GhcPkgId (Maybe (Either License License))
- | Executable PackageIdentifier
- 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
- lpTestDeps :: !(Map PackageName VersionRange)
- lpBenchDeps :: !(Map PackageName VersionRange)
- 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 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
- toMaximumTimeSeconds :: !(Maybe Int)
- 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 :: !Bool
- boptsForceDirty :: !Bool
- boptsTests :: !Bool
- boptsTestOpts :: !TestOpts
- boptsBenchmarks :: !Bool
- boptsBenchmarkOpts :: !BenchmarkOpts
- boptsReconfigure :: !Bool
- boptsCabalVerbose :: !Bool
- boptsSplitObjs :: !Bool
- boptsSkipComponents :: ![Text]
- boptsInterleavedOutput :: !Bool
- boptsDdumpDir :: !(Maybe Text)
- data BuildSubset
- defaultBuildOpts :: BuildOpts
- data TaskType
- data IsMutable
- 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
- isStackOpt :: Text -> Bool
- wantedLocalPackages :: [LocalPackage] -> Set PackageName
- newtype FileCacheInfo = FileCacheInfo {}
- data ConfigureOpts = ConfigureOpts {}
- data PrecompiledCache base = PrecompiledCache {}
Documentation
data StackBuildException Source #
Constructors
Instances
Show StackBuildException Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> StackBuildException -> ShowS show :: StackBuildException -> String # showList :: [StackBuildException] -> ShowS | |
Exception StackBuildException Source # | |
Defined in Stack.Types.Build Methods toException :: StackBuildException -> SomeException # fromException :: SomeException -> Maybe StackBuildException # |
data FlagSource Source #
Constructors
FSCommandLine | |
FSStackYaml |
Instances
Eq FlagSource Source # | |
Defined in Stack.Types.Build | |
Ord FlagSource Source # | |
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 Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> FlagSource -> ShowS show :: FlagSource -> String # showList :: [FlagSource] -> ShowS |
data UnusedFlags Source #
Constructors
UFNoPackage FlagSource PackageName | |
UFFlagsNotDefined FlagSource PackageName (Set FlagName) (Set FlagName) | |
UFSnapshot PackageName |
Instances
Eq UnusedFlags Source # | |
Defined in Stack.Types.Build | |
Ord UnusedFlags Source # | |
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 Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> UnusedFlags -> ShowS show :: UnusedFlags -> String # showList :: [UnusedFlags] -> ShowS |
data InstallLocation Source #
A location to install a package into, either snapshot or local
Instances
Eq InstallLocation Source # | |
Defined in Stack.Types.Package Methods (==) :: InstallLocation -> InstallLocation -> Bool # (/=) :: InstallLocation -> InstallLocation -> Bool # | |
Show InstallLocation Source # | |
Defined in Stack.Types.Package Methods showsPrec :: Int -> InstallLocation -> ShowS show :: InstallLocation -> String # showList :: [InstallLocation] -> ShowS | |
Semigroup InstallLocation Source # | |
Defined in Stack.Types.Package Methods (<>) :: InstallLocation -> InstallLocation -> InstallLocation # sconcat :: NonEmpty InstallLocation -> InstallLocation stimes :: Integral b => b -> InstallLocation -> InstallLocation | |
Monoid InstallLocation Source # | |
Defined in Stack.Types.Package Methods mappend :: InstallLocation -> InstallLocation -> InstallLocation # mconcat :: [InstallLocation] -> InstallLocation # |
Constructors
Library PackageIdentifier GhcPkgId (Maybe (Either License License)) | |
Executable PackageIdentifier |
psVersion :: PackageSource -> Version Source #
A task to perform when building
Constructors
Task | |
Fields
|
taskIsTarget :: Task -> Bool Source #
taskLocation :: Task -> InstallLocation Source #
taskTargetIsMutable :: Task -> IsMutable Source #
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 |
data BaseConfigOpts Source #
Basic information used to calculate what the configure options are
Constructors
BaseConfigOpts | |
Fields
|
Instances
Show BaseConfigOpts Source # | |
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 Source #
Options for the FinalAction
DoBenchmarks
Constructors
BenchmarkOpts | |
Fields
|
Instances
Eq BenchmarkOpts Source # | |
Defined in Stack.Types.Config.Build Methods (==) :: BenchmarkOpts -> BenchmarkOpts -> Bool # (/=) :: BenchmarkOpts -> BenchmarkOpts -> Bool # | |
Show BenchmarkOpts Source # | |
Defined in Stack.Types.Config.Build Methods showsPrec :: Int -> BenchmarkOpts -> ShowS show :: BenchmarkOpts -> String # showList :: [BenchmarkOpts] -> ShowS |
data FileWatchOpts Source #
Constructors
NoFileWatch | |
FileWatch | |
FileWatchPoll |
Instances
Eq FileWatchOpts Source # | |
Defined in Stack.Types.Config.Build Methods (==) :: FileWatchOpts -> FileWatchOpts -> Bool # (/=) :: FileWatchOpts -> FileWatchOpts -> Bool # | |
Show FileWatchOpts Source # | |
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 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
Eq BuildSubset Source # | |
Defined in Stack.Types.Config.Build | |
Show BuildSubset Source # | |
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 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
Eq BuildCache Source # | |
Defined in Stack.Types.Build | |
Show BuildCache Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> BuildCache -> ShowS show :: BuildCache -> String # showList :: [BuildCache] -> ShowS | |
Generic BuildCache Source # | |
Defined in Stack.Types.Build Associated Types type Rep BuildCache :: Type -> Type | |
ToJSON BuildCache Source # | |
Defined in Stack.Types.Build Methods toJSON :: BuildCache -> Value # toEncoding :: BuildCache -> Encoding # toJSONList :: [BuildCache] -> Value # toEncodingList :: [BuildCache] -> Encoding # | |
FromJSON BuildCache Source # | |
Defined in Stack.Types.Build | |
NFData BuildCache Source # | |
Defined in Stack.Types.Build Methods rnf :: BuildCache -> () # | |
type Rep BuildCache Source # | |
Defined in Stack.Types.Build type Rep BuildCache = D1 ('MetaData "BuildCache" "Stack.Types.Build" "stack-2.7.5-8K9XGfoZcI23Tpn97UPgr1" 'True) (C1 ('MetaCons "BuildCache" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildCacheTimes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map FilePath FileCacheInfo)))) |
data ConfigCache Source #
Stored on disk to know whether the flags have changed.
Constructors
ConfigCache | |
Fields
|
Instances
Eq ConfigCache Source # | |
Defined in Stack.Types.Build | |
Data ConfigCache Source # | |
Defined in Stack.Types.Build Methods 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 # | |
Show ConfigCache Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> ConfigCache -> ShowS show :: ConfigCache -> String # showList :: [ConfigCache] -> ShowS | |
Generic ConfigCache Source # | |
Defined in Stack.Types.Build Associated Types type Rep ConfigCache :: Type -> Type | |
NFData ConfigCache Source # | |
Defined in Stack.Types.Build Methods rnf :: ConfigCache -> () # | |
type Rep ConfigCache Source # | |
Defined in Stack.Types.Build type Rep ConfigCache = D1 ('MetaData "ConfigCache" "Stack.Types.Build" "stack-2.7.5-8K9XGfoZcI23Tpn97UPgr1" 'False) (C1 ('MetaCons "ConfigCache" 'PrefixI 'True) ((S1 ('MetaSel ('Just "configCacheOpts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConfigureOpts) :*: (S1 ('MetaSel ('Just "configCacheDeps") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set GhcPkgId)) :*: S1 ('MetaSel ('Just "configCacheComponents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set ByteString)))) :*: (S1 ('MetaSel ('Just "configCacheHaddock") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "configCachePkgSrc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CachePkgSrc) :*: S1 ('MetaSel ('Just "configCachePathEnvVar") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))) |
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
Eq CachePkgSrc Source # | |
Defined in Stack.Types.Build | |
Data CachePkgSrc Source # | |
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 :: 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 # | |
Read CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods readsPrec :: Int -> ReadS CachePkgSrc readList :: ReadS [CachePkgSrc] readPrec :: ReadPrec CachePkgSrc readListPrec :: ReadPrec [CachePkgSrc] | |
Show CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> CachePkgSrc -> ShowS show :: CachePkgSrc -> String # showList :: [CachePkgSrc] -> ShowS | |
Generic CachePkgSrc Source # | |
Defined in Stack.Types.Build Associated Types type Rep CachePkgSrc :: Type -> Type | |
NFData CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods rnf :: CachePkgSrc -> () # | |
PersistField CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods toPersistValue :: CachePkgSrc -> PersistValue fromPersistValue :: PersistValue -> Either Text CachePkgSrc | |
PersistFieldSql CachePkgSrc Source # | |
Defined in Stack.Types.Build Methods sqlType :: Proxy CachePkgSrc -> SqlType | |
type Rep CachePkgSrc Source # | |
Defined in Stack.Types.Build type Rep CachePkgSrc = D1 ('MetaData "CachePkgSrc" "Stack.Types.Build" "stack-2.7.5-8K9XGfoZcI23Tpn97UPgr1" '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 Source #
wantedLocalPackages :: [LocalPackage] -> Set PackageName Source #
Get set of wanted package names from locals.
newtype FileCacheInfo Source #
Constructors
FileCacheInfo | |
Instances
data ConfigureOpts Source #
Configure options to be sent to Setup.hs configure
Constructors
ConfigureOpts | |
Instances
Eq ConfigureOpts Source # | |
Defined in Stack.Types.Build Methods (==) :: ConfigureOpts -> ConfigureOpts -> Bool # (/=) :: ConfigureOpts -> ConfigureOpts -> Bool # | |
Data ConfigureOpts Source # | |
Defined in Stack.Types.Build Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigureOpts -> c ConfigureOpts # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigureOpts # toConstr :: ConfigureOpts -> Constr # dataTypeOf :: ConfigureOpts -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigureOpts) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigureOpts) # gmapT :: (forall b. Data b => b -> b) -> ConfigureOpts -> ConfigureOpts # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigureOpts -> r # gmapQ :: (forall d. Data d => d -> u) -> ConfigureOpts -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigureOpts -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigureOpts -> m ConfigureOpts # | |
Show ConfigureOpts Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> ConfigureOpts -> ShowS show :: ConfigureOpts -> String # showList :: [ConfigureOpts] -> ShowS | |
Generic ConfigureOpts Source # | |
Defined in Stack.Types.Build Associated Types type Rep ConfigureOpts :: Type -> Type | |
NFData ConfigureOpts Source # | |
Defined in Stack.Types.Build Methods rnf :: ConfigureOpts -> () # | |
type Rep ConfigureOpts Source # | |
Defined in Stack.Types.Build type Rep ConfigureOpts = D1 ('MetaData "ConfigureOpts" "Stack.Types.Build" "stack-2.7.5-8K9XGfoZcI23Tpn97UPgr1" 'False) (C1 ('MetaCons "ConfigureOpts" 'PrefixI 'True) (S1 ('MetaSel ('Just "coDirs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String]) :*: S1 ('MetaSel ('Just "coNoDirs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String]))) |
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.
Constructors
PrecompiledCache | |
Instances
Eq (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build Methods (==) :: PrecompiledCache base -> PrecompiledCache base -> Bool # (/=) :: PrecompiledCache base -> PrecompiledCache base -> Bool # | |
Show (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build Methods showsPrec :: Int -> PrecompiledCache base -> ShowS show :: PrecompiledCache base -> String # showList :: [PrecompiledCache base] -> ShowS | |
Generic (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build Associated Types type Rep (PrecompiledCache base) :: Type -> Type Methods from :: PrecompiledCache base -> Rep (PrecompiledCache base) x to :: Rep (PrecompiledCache base) x -> PrecompiledCache base | |
NFData (PrecompiledCache Abs) Source # | |
Defined in Stack.Types.Build Methods rnf :: PrecompiledCache Abs -> () # | |
NFData (PrecompiledCache Rel) Source # | |
Defined in Stack.Types.Build Methods rnf :: PrecompiledCache Rel -> () # | |
type Rep (PrecompiledCache base) Source # | |
Defined in Stack.Types.Build type Rep (PrecompiledCache base) = D1 ('MetaData "PrecompiledCache" "Stack.Types.Build" "stack-2.7.5-8K9XGfoZcI23Tpn97UPgr1" 'False) (C1 ('MetaCons "PrecompiledCache" 'PrefixI 'True) (S1 ('MetaSel ('Just "pcLibrary") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Path base File))) :*: (S1 ('MetaSel ('Just "pcSubLibs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Path base File]) :*: S1 ('MetaSel ('Just "pcExes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Path base File])))) |