Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
System.Nix.Store.Remote.Client
Synopsis
- addToStore :: MonadRemoteStore m => StorePathName -> NarSource IO -> FileIngestionMethod -> Some HashAlgo -> RepairMode -> m StorePath
- addToStoreNar :: MonadRemoteStore m => StorePath -> Metadata StorePath -> RepairMode -> CheckMode -> (Word64 -> IO (Maybe ByteString)) -> m ()
- addTextToStore :: MonadRemoteStore m => StoreText -> HashSet StorePath -> RepairMode -> m StorePath
- addSignatures :: MonadRemoteStore m => StorePath -> Set Signature -> m ()
- addTempRoot :: MonadRemoteStore m => StorePath -> m ()
- addIndirectRoot :: MonadRemoteStore m => StorePath -> m ()
- buildPaths :: MonadRemoteStore m => Set DerivedPath -> BuildMode -> m ()
- buildDerivation :: MonadRemoteStore m => StorePath -> BuildMode -> m BuildResult
- collectGarbage :: MonadRemoteStore m => GCOptions -> m GCResult
- ensurePath :: MonadRemoteStore m => StorePath -> m ()
- findRoots :: MonadRemoteStore m => m (Map GCRoot StorePath)
- isValidPath :: MonadRemoteStore m => StorePath -> m Bool
- narFromPath :: MonadRemoteStore m => StorePath -> Word64 -> (ByteString -> IO ()) -> m ()
- queryValidPaths :: MonadRemoteStore m => HashSet StorePath -> SubstituteMode -> m (HashSet StorePath)
- queryAllValidPaths :: MonadRemoteStore m => m (HashSet StorePath)
- querySubstitutablePaths :: MonadRemoteStore m => HashSet StorePath -> m (HashSet StorePath)
- queryPathInfo :: MonadRemoteStore m => StorePath -> m (Maybe (Metadata StorePath))
- queryReferrers :: MonadRemoteStore m => StorePath -> m (HashSet StorePath)
- queryValidDerivers :: MonadRemoteStore m => StorePath -> m (HashSet StorePath)
- queryDerivationOutputs :: MonadRemoteStore m => StorePath -> m (HashSet StorePath)
- queryDerivationOutputNames :: MonadRemoteStore m => StorePath -> m (HashSet StorePathName)
- queryPathFromHashPart :: MonadRemoteStore m => StorePathHashPart -> m StorePath
- queryMissing :: MonadRemoteStore m => Set DerivedPath -> m Missing
- optimiseStore :: MonadRemoteStore m => m ()
- syncWithGC :: MonadRemoteStore m => m ()
- verifyStore :: MonadRemoteStore m => CheckMode -> RepairMode -> m Bool
- module System.Nix.Store.Remote.Client.Core
Documentation
Arguments
:: MonadRemoteStore m | |
=> StorePathName | Name part of the newly created |
-> NarSource IO | Provide nar stream |
-> FileIngestionMethod | Add target directory recursively |
-> Some HashAlgo | |
-> RepairMode | Only used by local store backend |
-> m StorePath |
Add NarSource
to the store
addToStoreNar :: MonadRemoteStore m => StorePath -> Metadata StorePath -> RepairMode -> CheckMode -> (Word64 -> IO (Maybe ByteString)) -> m () Source #
Arguments
:: MonadRemoteStore m | |
=> StoreText | |
-> HashSet StorePath | Set of |
-> RepairMode | Repair mode, must be |
-> m StorePath |
Add StoreText
to the store
Reference accepts repair but only uses it
to throw error in case of remote talking to nix-daemon.
addSignatures :: MonadRemoteStore m => StorePath -> Set Signature -> m () Source #
Add Signature
s to a store path
addTempRoot :: MonadRemoteStore m => StorePath -> m () Source #
Add temporary garbage collector root.
This root is removed as soon as the client exits.
addIndirectRoot :: MonadRemoteStore m => StorePath -> m () Source #
Add indirect garbage collector root.
buildPaths :: MonadRemoteStore m => Set DerivedPath -> BuildMode -> m () Source #
Build paths if they are an actual derivations.
If derivation output paths are already valid, do nothing.
buildDerivation :: MonadRemoteStore m => StorePath -> BuildMode -> m BuildResult Source #
Build a derivation available at StorePath
collectGarbage :: MonadRemoteStore m => GCOptions -> m GCResult Source #
ensurePath :: MonadRemoteStore m => StorePath -> m () Source #
isValidPath :: MonadRemoteStore m => StorePath -> m Bool Source #
Arguments
:: MonadRemoteStore m | |
=> StorePath | Path to generate a NAR for |
-> Word64 | Byte length of NAR |
-> (ByteString -> IO ()) | Data sink where NAR bytes will be written |
-> m () |
Download a NAR file.
Arguments
:: MonadRemoteStore m | |
=> HashSet StorePath | Set of |
-> SubstituteMode | Try substituting missing paths when |
-> m (HashSet StorePath) |
Query valid paths from a set, optionally try to use substitutes
queryAllValidPaths :: MonadRemoteStore m => m (HashSet StorePath) Source #
Query all valid paths
querySubstitutablePaths :: MonadRemoteStore m => HashSet StorePath -> m (HashSet StorePath) Source #
Query a set of paths substituable from caches
queryPathInfo :: MonadRemoteStore m => StorePath -> m (Maybe (Metadata StorePath)) Source #
Query path metadata
queryReferrers :: MonadRemoteStore m => StorePath -> m (HashSet StorePath) Source #
queryValidDerivers :: MonadRemoteStore m => StorePath -> m (HashSet StorePath) Source #
queryDerivationOutputs :: MonadRemoteStore m => StorePath -> m (HashSet StorePath) Source #
queryDerivationOutputNames :: MonadRemoteStore m => StorePath -> m (HashSet StorePathName) Source #
queryPathFromHashPart :: MonadRemoteStore m => StorePathHashPart -> m StorePath Source #
queryMissing :: MonadRemoteStore m => Set DerivedPath -> m Missing Source #
optimiseStore :: MonadRemoteStore m => m () Source #
syncWithGC :: MonadRemoteStore m => m () Source #
verifyStore :: MonadRemoteStore m => CheckMode -> RepairMode -> m Bool Source #