Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- addToStore :: forall a. NamedAlgo a => StorePathName -> NarSource MonadStore -> Bool -> RepairFlag -> MonadStore StorePath
- addTextToStore :: Text -> Text -> StorePathSet -> RepairFlag -> MonadStore StorePath
- addSignatures :: StorePath -> [ByteString] -> MonadStore ()
- addIndirectRoot :: StorePath -> MonadStore ()
- addTempRoot :: StorePath -> MonadStore ()
- buildPaths :: StorePathSet -> BuildMode -> MonadStore ()
- buildDerivation :: StorePath -> Derivation StorePath Text -> BuildMode -> MonadStore BuildResult
- ensurePath :: StorePath -> MonadStore ()
- findRoots :: MonadStore (Map ByteString StorePath)
- isValidPathUncached :: StorePath -> MonadStore Bool
- queryValidPaths :: StorePathSet -> SubstituteFlag -> MonadStore StorePathSet
- queryAllValidPaths :: MonadStore StorePathSet
- querySubstitutablePaths :: StorePathSet -> MonadStore StorePathSet
- queryPathInfoUncached :: StorePath -> MonadStore StorePathMetadata
- queryReferrers :: StorePath -> MonadStore StorePathSet
- queryValidDerivers :: StorePath -> MonadStore StorePathSet
- queryDerivationOutputs :: StorePath -> MonadStore StorePathSet
- queryDerivationOutputNames :: StorePath -> MonadStore StorePathSet
- queryPathFromHashPart :: StorePathHashPart -> MonadStore StorePath
- queryMissing :: StorePathSet -> MonadStore (StorePathSet, StorePathSet, StorePathSet, Integer, Integer)
- optimiseStore :: MonadStore ()
- runStore :: MonadStore a -> IO (Either String a, [Logger])
- syncWithGC :: MonadStore ()
- verifyStore :: CheckFlag -> RepairFlag -> MonadStore Bool
- module System.Nix.Store.Remote.Types
Documentation
:: forall a. NamedAlgo a | |
=> StorePathName | Name part of the newly created |
-> NarSource MonadStore | provide nar stream |
-> Bool | Add target directory recursively |
-> RepairFlag | Only used by local store backend |
-> MonadStore StorePath |
Pack Nar
and add it to the store.
:: Text | Name of the text |
-> Text | Actual text to add |
-> StorePathSet | Set of |
-> RepairFlag | Repair flag, must be |
-> MonadStore StorePath |
Add text to store.
Reference accepts repair but only uses it to throw error in case of remote talking to nix-daemon.
addSignatures :: StorePath -> [ByteString] -> MonadStore () Source #
addIndirectRoot :: StorePath -> MonadStore () Source #
addTempRoot :: StorePath -> MonadStore () Source #
Add temporary garbage collector root.
This root is removed as soon as the client exits.
buildPaths :: StorePathSet -> BuildMode -> MonadStore () Source #
Build paths if they are an actual derivations.
If derivation output paths are already valid, do nothing.
buildDerivation :: StorePath -> Derivation StorePath Text -> BuildMode -> MonadStore BuildResult Source #
ensurePath :: StorePath -> MonadStore () Source #
findRoots :: MonadStore (Map ByteString StorePath) Source #
Find garbage collector roots.
:: StorePathSet | Set of |
-> SubstituteFlag | Try substituting missing paths when |
-> MonadStore StorePathSet |
Query valid paths from set, optionally try to use substitutes.
queryMissing :: StorePathSet -> MonadStore (StorePathSet, StorePathSet, StorePathSet, Integer, Integer) Source #
optimiseStore :: MonadStore () Source #
syncWithGC :: MonadStore () Source #
verifyStore :: CheckFlag -> RepairFlag -> MonadStore Bool Source #