| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cachix.Client.Push
Synopsis
- pushSingleStorePath :: (MonadMask m, MonadIO m) => PushParams m r -> StorePath -> m r
- uploadStorePath :: (MonadMask m, MonadIO m) => PushParams m r -> StorePath -> RetryStatus -> m r
- data PushParams m r = PushParams {
- pushParamsName :: Text
- pushParamsSecret :: PushSecret
- pushParamsStrategy :: StorePath -> PushStrategy m r
- pushParamsClientEnv :: ClientEnv
- pushParamsStore :: Store
- data PushSecret
- = PushToken Token
- | PushSigningKey Token SigningKey
- 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
- findPushSecret :: Maybe Config -> Text -> IO PushSecret
- pushClosure :: (MonadIO m, MonadMask m) => (forall a b. (a -> m b) -> [a] -> m [b]) -> PushParams m r -> [StorePath] -> m [r]
- getMissingPathsForClosure :: (MonadIO m, MonadMask m) => PushParams m r -> [StorePath] -> m [StorePath]
- mapConcurrentlyBounded :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b)
Pushing a single path
Arguments
| :: (MonadMask m, MonadIO m) | |
| => PushParams m r | details for pushing to cache |
| -> StorePath | store path |
| -> m r | r is determined by the |
Arguments
| :: (MonadMask m, MonadIO m) | |
| => PushParams m r | details for pushing to cache |
| -> StorePath | |
| -> RetryStatus | |
| -> m r | r is determined by the |
data PushParams m r Source #
Constructors
| PushParams | |
Fields
| |
data PushSecret Source #
Constructors
| PushToken Token | |
| PushSigningKey Token SigningKey |
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 #
Arguments
| :: Maybe Config | |
| -> Text | Cache name |
| -> IO PushSecret | Secret key or exception |
Find auth token or signing key in the Config or environment variable
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: |
| -> PushParams m r | |
| -> [StorePath] | Initial store paths |
| -> m [r] | Every |
Push an entire closure
Note: onAlreadyPresent will be called less often in the future.
getMissingPathsForClosure :: (MonadIO m, MonadMask m) => PushParams m r -> [StorePath] -> m [StorePath] Source #
mapConcurrentlyBounded :: Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) Source #