| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Build.Cache
Description
Cache information about previous builds
Synopsis
- tryGetBuildCache :: HasEnvConfig env => Path Abs Dir -> NamedComponent -> RIO env (Maybe (Map FilePath FileCacheInfo))
 - tryGetConfigCache :: HasEnvConfig env => Path Abs Dir -> RIO env (Maybe ConfigCache)
 - tryGetCabalMod :: HasEnvConfig env => Path Abs Dir -> RIO env (Maybe ModTime)
 - getInstalledExes :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> m [PackageIdentifier]
 - tryGetFlagCache :: HasEnvConfig env => Installed -> RIO env (Maybe ConfigCache)
 - deleteCaches :: (MonadIO m, MonadReader env m, HasEnvConfig env, MonadThrow m) => Path Abs Dir -> m ()
 - markExeInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> PackageIdentifier -> m ()
 - markExeNotInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> PackageIdentifier -> m ()
 - writeFlagCache :: HasEnvConfig env => Installed -> ConfigCache -> RIO env ()
 - writeBuildCache :: HasEnvConfig env => Path Abs Dir -> NamedComponent -> Map FilePath FileCacheInfo -> RIO env ()
 - writeConfigCache :: HasEnvConfig env => Path Abs Dir -> ConfigCache -> RIO env ()
 - writeCabalMod :: HasEnvConfig env => Path Abs Dir -> ModTime -> RIO env ()
 - setTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env ()
 - unsetTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env ()
 - checkTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env Bool
 - writePrecompiledCache :: HasEnvConfig env => BaseConfigOpts -> PackageLocationIndex FilePath -> ConfigureOpts -> Set GhcPkgId -> Installed -> [GhcPkgId] -> Set Text -> RIO env ()
 - readPrecompiledCache :: forall env. HasEnvConfig env => PackageLocationIndex FilePath -> ConfigureOpts -> Set GhcPkgId -> RIO env (Maybe PrecompiledCache)
 - newtype BuildCache = BuildCache {}
 
Documentation
tryGetBuildCache :: HasEnvConfig env => Path Abs Dir -> NamedComponent -> RIO env (Maybe (Map FilePath FileCacheInfo)) Source #
Try to read the dirtiness cache for the given package directory.
tryGetConfigCache :: HasEnvConfig env => Path Abs Dir -> RIO env (Maybe ConfigCache) Source #
Try to read the dirtiness cache for the given package directory.
tryGetCabalMod :: HasEnvConfig env => Path Abs Dir -> RIO env (Maybe ModTime) Source #
Try to read the mod time of the cabal file from the last build
getInstalledExes :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> m [PackageIdentifier] Source #
Get all of the installed executables
tryGetFlagCache :: HasEnvConfig env => Installed -> RIO env (Maybe ConfigCache) Source #
Loads the flag cache for the given installed extra-deps
deleteCaches :: (MonadIO m, MonadReader env m, HasEnvConfig env, MonadThrow m) => Path Abs Dir -> m () Source #
Delete the caches for the project.
markExeInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> PackageIdentifier -> m () Source #
Mark the given executable as installed
markExeNotInstalled :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadThrow m) => InstallLocation -> PackageIdentifier -> m () Source #
Mark the given executable as not installed
writeFlagCache :: HasEnvConfig env => Installed -> ConfigCache -> RIO env () Source #
writeBuildCache :: HasEnvConfig env => Path Abs Dir -> NamedComponent -> Map FilePath FileCacheInfo -> RIO env () Source #
Write the dirtiness cache for this package's files.
writeConfigCache :: HasEnvConfig env => Path Abs Dir -> ConfigCache -> RIO env () Source #
Write the dirtiness cache for this package's configuration.
writeCabalMod :: HasEnvConfig env => Path Abs Dir -> ModTime -> RIO env () Source #
See tryGetCabalMod
setTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env () Source #
Mark a test suite as having succeeded
unsetTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env () Source #
Mark a test suite as not having succeeded
checkTestSuccess :: HasEnvConfig env => Path Abs Dir -> RIO env Bool Source #
Check if the test suite already passed
writePrecompiledCache Source #
Arguments
| :: HasEnvConfig env | |
| => BaseConfigOpts | |
| -> PackageLocationIndex FilePath | |
| -> ConfigureOpts | |
| -> Set GhcPkgId | dependencies  | 
| -> Installed | library  | 
| -> [GhcPkgId] | sublibraries, in the GhcPkgId format  | 
| -> Set Text | executables  | 
| -> RIO env () | 
Write out information about a newly built package
Arguments
| :: HasEnvConfig env | |
| => PackageLocationIndex FilePath | target package  | 
| -> ConfigureOpts | |
| -> Set GhcPkgId | dependencies  | 
| -> RIO env (Maybe PrecompiledCache) | 
Check the cache for a precompiled package matching the given configuration.
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  | |
| Data BuildCache Source # | |
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 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 #  | |
| NFData BuildCache Source # | |
Defined in Stack.Types.Build Methods rnf :: BuildCache -> () #  | |
| Store BuildCache Source # | |
Defined in Stack.Types.Build  | |
| type Rep BuildCache Source # | |
Defined in Stack.Types.Build type Rep BuildCache = D1 (MetaData "BuildCache" "Stack.Types.Build" "stack-1.9.3-A8b1pQY9CjdHmL7IWv3q9b" True) (C1 (MetaCons "BuildCache" PrefixI True) (S1 (MetaSel (Just "buildCacheTimes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map FilePath FileCacheInfo))))  | |