Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hercules.CNix.Store
Synopsis
- newtype Store = Store (Ptr (Ref NixStore))
- openStore :: IO Store
- releaseStore :: Store -> IO ()
- withStore :: MonadUnliftIO m => (Store -> m a) -> m a
- withStore' :: (Store -> IO r) -> IO r
- withStoreFromURI :: MonadUnliftIO m => Text -> (Store -> m r) -> m r
- storeUri :: MonadIO m => Store -> m ByteString
- storeDir :: MonadIO m => Store -> m ByteString
- getStoreProtocolVersion :: Store -> IO Int
- getClientProtocolVersion :: IO Int
- newtype StorePath = StorePath (ForeignPtr NixStorePath)
- parseStorePathBaseName :: ByteString -> IO StorePath
- parseStorePath :: Store -> ByteString -> IO StorePath
- followLinksToStorePath :: Store -> ByteString -> IO StorePath
- storePathToPath :: Store -> StorePath -> IO ByteString
- getStorePathBaseName :: StorePath -> IO ByteString
- getStorePathHash :: StorePath -> IO ByteString
- isValidPath :: Store -> StorePath -> IO Bool
- queryPathInfo :: Store -> StorePath -> IO (ForeignPtr (Ref ValidPathInfo))
- queryPathInfoFromClientCache :: Store -> StorePath -> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
- data ValidPathInfo
- validPathInfoNarSize :: ForeignPtr (Ref ValidPathInfo) -> Int64
- validPathInfoNarHash32 :: ForeignPtr (Ref ValidPathInfo) -> IO ByteString
- validPathInfoDeriver :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
- validPathInfoDeriver' :: ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
- validPathInfoReferences :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
- validPathInfoReferences' :: ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
- computeFSClosure :: Store -> ClosureParams -> StdSet NixStorePath -> IO (StdSet NixStorePath)
- data ClosureParams = ClosureParams {}
- defaultClosureParams :: ClosureParams
- ensurePath :: Store -> StorePath -> IO ()
- buildPaths :: Store -> StdVector NixStorePathWithOutputs -> IO ()
- buildPath :: Store -> StorePathWithOutputs -> IO ()
- addTemporaryRoot :: Store -> StorePath -> IO ()
- clearPathInfoCache :: Store -> IO ()
- clearSubstituterCaches :: IO ()
- newtype StorePathWithOutputs = StorePathWithOutputs (ForeignPtr NixStorePathWithOutputs)
- newStorePathWithOutputs :: StorePath -> [ByteString] -> IO StorePathWithOutputs
- getStorePath :: StorePathWithOutputs -> IO StorePath
- getOutputs :: StorePathWithOutputs -> IO [ByteString]
- newtype Derivation = Derivation (ForeignPtr Derivation)
- getDerivation :: Store -> StorePath -> IO Derivation
- getDerivationFromString :: Store -> ByteString -> ByteString -> IO Derivation
- getDerivationNameFromPath :: StorePath -> IO ByteString
- getDerivationPlatform :: Derivation -> IO ByteString
- getDerivationBuilder :: Derivation -> IO ByteString
- getDerivationArguments :: Derivation -> IO [ByteString]
- getDerivationEnv :: Derivation -> IO (Map ByteString ByteString)
- getDerivationSources :: Store -> Derivation -> IO [StorePath]
- getDerivationSources' :: Derivation -> IO [StorePath]
- getDerivationInputs :: Store -> Derivation -> IO [(StorePath, [ByteString])]
- getDerivationInputs' :: Derivation -> IO [(StorePath, [ByteString])]
- getDerivationOutputNames :: ForeignPtr Derivation -> IO [ByteString]
- data DerivationOutput = DerivationOutput {}
- data DerivationOutputDetail
- data FixedOutputHash = FixedOutputHash !FileIngestionMethod !Hash
- data FileIngestionMethod
- getDerivationOutputs :: Store -> ByteString -> Derivation -> IO [DerivationOutput]
- copyClosure :: Store -> Store -> [StorePath] -> IO ()
- data SecretKey
- parseSecretKey :: ByteString -> IO (ForeignPtr SecretKey)
- signPath :: Store -> Ptr SecretKey -> StorePath -> IO Bool
- data Hash = Hash !HashType !ShortByteString
- data HashType
- data Strings
- withStrings :: (Ptr Strings -> IO a) -> IO a
- withStringsOf :: [ByteString] -> (Ptr Strings -> IO a) -> IO a
- pushString :: Ptr Strings -> ByteString -> IO ()
- getStringsLength :: Ptr Strings -> IO CSize
- toByteStrings :: Ptr Strings -> IO [ByteString]
- toByteStringMap :: Ptr StringPairs -> IO (Map ByteString ByteString)
- forNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
- traverseNonNull :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
- deleteDerivationInputsIterator :: Ptr DerivationInputsIterator -> IO ()
- deleteDerivationOutputsIterator :: Ptr DerivationOutputsIterator -> IO ()
- deleteStringPairs :: Ptr StringPairs -> IO ()
- deleteStrings :: Ptr Strings -> IO ()
- finalizeDerivation :: FinalizerPtr Derivation
- finalizeRefValidPathInfo :: FinalizerPtr (Ref ValidPathInfo)
- finalizeSecretKey :: FinalizerPtr SecretKey
- finalizeStorePath :: FinalizerPtr NixStorePath
- finalizeStorePathWithOutputs :: FinalizerPtr NixStorePathWithOutputs
- finalizeStrings :: FinalizerPtr Strings
- moveStorePath :: Ptr NixStorePath -> IO StorePath
- moveStorePathMaybe :: Ptr NixStorePath -> IO (Maybe StorePath)
- unsafeMallocBS :: MonadIO m => IO CString -> m ByteString
- withPtr' :: Coercible a' (ForeignPtr a) => a' -> (Ptr a -> IO b) -> IO b
- data DerivationInputsIterator
- data DerivationOutputsIterator
- data NixStore
- data NixStorePath
- data Ref a
- data StringPairs
- context :: Context
Opening a Store
releaseStore :: Store -> IO () Source #
withStore :: MonadUnliftIO m => (Store -> m a) -> m a Source #
withStoreFromURI :: MonadUnliftIO m => Text -> (Store -> m r) -> m r Source #
Store properties
Store paths
Store-agnostic store path representation: hash and name. Does not have a storedir or subpath inside the store path.
Constructors
StorePath (ForeignPtr NixStorePath) |
Instances
Show StorePath Source # | |
Eq StorePath Source # | |
Ord StorePath Source # | |
HasEncapsulation NixStorePath StorePath Source # | |
Defined in Hercules.CNix.Store Methods moveToForeignPtrWrapper :: Ptr NixStorePath -> IO StorePath Source # |
parseStorePathBaseName :: ByteString -> IO StorePath Source #
Create StorePath
from hash and name.
Throws C++ BadStorePath
exception when invalid.
parseStorePath :: Store -> ByteString -> IO StorePath Source #
Parse a complete store path including storeDir into a StorePath
.
Throws C++ BadStorePath
exception when invalid.
followLinksToStorePath :: Store -> ByteString -> IO StorePath Source #
Follow symlinks to the store and chop off the parts after the top-level store name
storePathToPath :: Store -> StorePath -> IO ByteString Source #
getStorePathHash :: StorePath -> IO ByteString Source #
Store objects
Arguments
:: Store | |
-> StorePath | Exact store path, not a subpath |
-> IO (ForeignPtr (Ref ValidPathInfo)) | ValidPathInfo or exception |
queryPathInfoFromClientCache :: Store -> StorePath -> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo)))) Source #
Query only the local client cache ("narinfo cache") - does not query the actual store or daemon.
Returns Nothing
if nothing is known about the path.
Returns 'Just Nothing' if the path is known to not exist.
Returns 'Just (Just vpi)' if the path is known to exist, with the given ValidPathInfo
.
data ValidPathInfo Source #
Instances
Finalizer (Ref ValidPathInfo) Source # | |
Defined in Hercules.CNix.Store Methods |
validPathInfoNarSize :: ForeignPtr (Ref ValidPathInfo) -> Int64 Source #
The narSize field of a ValidPathInfo struct. Source: path-info.hh / store-api.hh
validPathInfoNarHash32 :: ForeignPtr (Ref ValidPathInfo) -> IO ByteString Source #
Copy the narHash field of a ValidPathInfo struct. Source: path-info.hh / store-api.hh
validPathInfoDeriver :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath) Source #
Deriver field of a ValidPathInfo struct. Source: store-api.hh
validPathInfoDeriver' :: ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath) Source #
validPathInfoReferences :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO [StorePath] Source #
References field of a ValidPathInfo struct. Source: store-api.hh
validPathInfoReferences' :: ForeignPtr (Ref ValidPathInfo) -> IO [StorePath] Source #
computeFSClosure :: Store -> ClosureParams -> StdSet NixStorePath -> IO (StdSet NixStorePath) Source #
data ClosureParams Source #
Constructors
ClosureParams | |
Fields
|
Realisation
buildPaths :: Store -> StdVector NixStorePathWithOutputs -> IO () Source #
Garbage collection
In-memory cache control
clearPathInfoCache :: Store -> IO () Source #
clearSubstituterCaches :: IO () Source #
Derivation references
newtype StorePathWithOutputs Source #
Constructors
StorePathWithOutputs (ForeignPtr NixStorePathWithOutputs) |
Instances
getOutputs :: StorePathWithOutputs -> IO [ByteString] Source #
Derivations
newtype Derivation Source #
Constructors
Derivation (ForeignPtr Derivation) |
Instances
HasEncapsulation Derivation Derivation Source # | |
Defined in Hercules.CNix.Store Methods moveToForeignPtrWrapper :: Ptr Derivation0 -> IO Derivation Source # |
getDerivation :: Store -> StorePath -> IO Derivation Source #
getDerivationFromString Source #
Arguments
:: Store | |
-> ByteString | Derivation name (store path name with ".drv" extension removed) |
-> ByteString | Contents |
-> IO Derivation |
getDerivationArguments :: Derivation -> IO [ByteString] Source #
getDerivationEnv :: Derivation -> IO (Map ByteString ByteString) Source #
getDerivationSources :: Store -> Derivation -> IO [StorePath] Source #
getDerivationSources' :: Derivation -> IO [StorePath] Source #
getDerivationInputs :: Store -> Derivation -> IO [(StorePath, [ByteString])] Source #
getDerivationInputs' :: Derivation -> IO [(StorePath, [ByteString])] Source #
Get the inputs of a derivation, ignoring dependencies on outputs of outputs (RFC 92 inputs).
data DerivationOutput Source #
Constructors
DerivationOutput | |
Instances
Show DerivationOutput Source # | |
Defined in Hercules.CNix.Store Methods showsPrec :: Int -> DerivationOutput -> ShowS # show :: DerivationOutput -> String # showList :: [DerivationOutput] -> ShowS # | |
Eq DerivationOutput Source # | |
Defined in Hercules.CNix.Store Methods (==) :: DerivationOutput -> DerivationOutput -> Bool # (/=) :: DerivationOutput -> DerivationOutput -> Bool # |
data DerivationOutputDetail Source #
Constructors
DerivationOutputInputAddressed StorePath | |
DerivationOutputCAFixed FixedOutputHash StorePath | |
DerivationOutputCAFloating FileIngestionMethod HashType | |
DerivationOutputDeferred |
Instances
Show DerivationOutputDetail Source # | |
Defined in Hercules.CNix.Store Methods showsPrec :: Int -> DerivationOutputDetail -> ShowS # show :: DerivationOutputDetail -> String # showList :: [DerivationOutputDetail] -> ShowS # | |
Eq DerivationOutputDetail Source # | |
Defined in Hercules.CNix.Store Methods (==) :: DerivationOutputDetail -> DerivationOutputDetail -> Bool # (/=) :: DerivationOutputDetail -> DerivationOutputDetail -> Bool # |
data FixedOutputHash Source #
Constructors
FixedOutputHash !FileIngestionMethod !Hash |
Instances
Show FixedOutputHash Source # | |
Defined in Hercules.CNix.Store Methods showsPrec :: Int -> FixedOutputHash -> ShowS # show :: FixedOutputHash -> String # showList :: [FixedOutputHash] -> ShowS # | |
Eq FixedOutputHash Source # | |
Defined in Hercules.CNix.Store Methods (==) :: FixedOutputHash -> FixedOutputHash -> Bool # (/=) :: FixedOutputHash -> FixedOutputHash -> Bool # |
data FileIngestionMethod Source #
See content-address.hh
Instances
Show FileIngestionMethod Source # | |
Defined in Hercules.CNix.Store Methods showsPrec :: Int -> FileIngestionMethod -> ShowS # show :: FileIngestionMethod -> String # showList :: [FileIngestionMethod] -> ShowS # | |
Eq FileIngestionMethod Source # | |
Defined in Hercules.CNix.Store Methods (==) :: FileIngestionMethod -> FileIngestionMethod -> Bool # (/=) :: FileIngestionMethod -> FileIngestionMethod -> Bool # |
getDerivationOutputs :: Store -> ByteString -> Derivation -> IO [DerivationOutput] Source #
Copying
Signing
Instances
Finalizer SecretKey Source # | |
Defined in Hercules.CNix.Store Methods |
parseSecretKey :: ByteString -> IO (ForeignPtr SecretKey) Source #
Hashes
See hash.hh
Constructors
Hash !HashType !ShortByteString |
See hash.hh
Instances
Utilities
A Nix Strings
aka std::liststd::string
withStringsOf :: [ByteString] -> (Ptr Strings -> IO a) -> IO a Source #
pushString :: Ptr Strings -> ByteString -> IO () Source #
toByteStrings :: Ptr Strings -> IO [ByteString] Source #
toByteStringMap :: Ptr StringPairs -> IO (Map ByteString ByteString) Source #
Deprecated
forNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b) Source #
Deprecated: Use forNonNull
instead
traverseNonNull :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b) Source #
Deprecated: Use traverseNonNull
instead
deleteDerivationInputsIterator :: Ptr DerivationInputsIterator -> IO () Source #
Deprecated: Use delete
instead
deleteDerivationOutputsIterator :: Ptr DerivationOutputsIterator -> IO () Source #
Deprecated: Use delete
instead
deleteStringPairs :: Ptr StringPairs -> IO () Source #
Deprecated: Use delete
instead
finalizeDerivation :: FinalizerPtr Derivation Source #
Deprecated: Use finalizer
instead
finalizeRefValidPathInfo :: FinalizerPtr (Ref ValidPathInfo) Source #
Deprecated: Use finalizer
instead
finalizeSecretKey :: FinalizerPtr SecretKey Source #
Deprecated: Use finalizer
instead
finalizeStorePath :: FinalizerPtr NixStorePath Source #
Deprecated: Use finalizer
instead
finalizeStorePathWithOutputs :: FinalizerPtr NixStorePathWithOutputs Source #
Deprecated: Use finalizer
instead
finalizeStrings :: FinalizerPtr Strings Source #
Deprecated: Use finalizer
instead
moveStorePath :: Ptr NixStorePath -> IO StorePath Source #
Deprecated: Use moveToForeignPtrWrapper
instead
Move ownership of a Ptr NixStorePath into StorePath
moveStorePathMaybe :: Ptr NixStorePath -> IO (Maybe StorePath) Source #
Deprecated: Use nullableMoveToForeignPtrWrapper
instead
Move ownership of a Ptr NixStorePath into StorePath
unsafeMallocBS :: MonadIO m => IO CString -> m ByteString Source #
Deprecated: Use unsafePackMallocCString
withPtr' :: Coercible a' (ForeignPtr a) => a' -> (Ptr a -> IO b) -> IO b Source #
Deprecated: Use HasEncapsulation
instead
data DerivationInputsIterator Source #
Instances
Delete DerivationInputsIterator Source # | |
Defined in Hercules.CNix.Store |
data DerivationOutputsIterator Source #
Instances
Delete DerivationOutputsIterator Source # | |
Defined in Hercules.CNix.Store |
data NixStorePath Source #
Instances
Finalizer NixStorePath Source # | |
Defined in Hercules.CNix.Store Methods | |
HasEncapsulation NixStorePath StorePath Source # | |
Defined in Hercules.CNix.Store Methods moveToForeignPtrWrapper :: Ptr NixStorePath -> IO StorePath Source # |
A Nix ref
, to be used in phantom types.
data StringPairs Source #
Instances
Delete StringPairs Source # | |
Defined in Hercules.CNix.Store |
Re-exports
Orphan instances
Delete DerivationInputsIterator Source # | |
Delete DerivationOutputsIterator Source # | |
Delete StringPairs Source # | |
Delete StringPairsIterator Source # | |
Delete Strings Source # | |
Finalizer Derivation Source # | |
Methods | |
Finalizer NixStorePath Source # | |
Methods | |
Finalizer NixStorePathWithOutputs Source # | |
Methods | |
Finalizer SecretKey Source # | |
Methods | |
Finalizer Strings Source # | |
Methods | |
Delete (Ref NixStore) Source # | |
Finalizer (Ref ValidPathInfo) Source # | |
Methods |