| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cachix.Client.Push
Synopsis
- pushSingleStorePath :: (MonadMask m, MonadIO m) => ClientEnv -> Store -> PushCache -> PushStrategy m r -> Text -> m r
- data PushCache = PushCache {
- pushCacheName :: Text
- pushCacheSigningKey :: SigningKey
- pushCacheToken :: Token
- data PushStrategy m r = PushStrategy {
- onAlreadyPresent :: m r
- onAttempt :: RetryStatus -> Int64 -> m ()
- on401 :: m r
- onError :: ClientError -> m r
- onDone :: m r
- withXzipCompressor :: forall a. (ConduitM ByteString ByteString (ResourceT IO) () -> m a) -> m a
- omitDeriver :: Bool
- defaultWithXzipCompressor :: forall m a. (ConduitM ByteString ByteString (ResourceT IO) () -> m a) -> m a
- defaultWithXzipCompressorWithLevel :: Int -> forall m a. (ConduitM ByteString ByteString (ResourceT IO) () -> m a) -> m a
- pushClosure :: (MonadIO m, MonadMask m) => (forall a b. (a -> m b) -> [a] -> m [b]) -> ClientEnv -> Store -> PushCache -> (Text -> PushStrategy m r) -> [Text] -> m [r]
- mapConcurrentlyBounded :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b)
Pushing a single path
Arguments
| :: (MonadMask m, MonadIO m) | |
| => ClientEnv | cachix base url, connection manager, see |
| -> Store | |
| -> PushCache | details for pushing to cache |
| -> PushStrategy m r | how to report results, (some) errors, and do some things |
| -> Text | store path |
| -> m r | r is determined by the |
Constructors
| PushCache | |
Fields
| |
data PushStrategy m r Source #
Constructors
| PushStrategy | |
Fields
| |
defaultWithXzipCompressor :: forall m a. (ConduitM ByteString ByteString (ResourceT IO) () -> m a) -> m a Source #
defaultWithXzipCompressorWithLevel :: Int -> forall m a. (ConduitM ByteString ByteString (ResourceT IO) () -> m a) -> m a Source #
Pushing a closure of store paths
Arguments
| :: (MonadIO m, MonadMask m) | |
| => (forall a b. (a -> m b) -> [a] -> m [b]) | Traverse paths, responsible for bounding parallel processing of paths For example: |
| -> ClientEnv | |
| -> Store | |
| -> PushCache | |
| -> (Text -> PushStrategy m r) | |
| -> [Text] | Initial store paths |
| -> m [r] | Every |
Push an entire closure
Note: onAlreadyPresent will be called less often in the future.
mapConcurrentlyBounded :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) Source #