{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
#ifdef __GHCIDE__
# define NIX_IS_AT_LEAST(mm,m,p) 1
#endif
module Hercules.CNix.Store
(
Store (..),
openStore,
releaseStore,
withStore,
withStore',
withStoreFromURI,
storeUri,
storeDir,
getStoreProtocolVersion,
getClientProtocolVersion,
StorePath (..),
parseStorePathBaseName,
parseStorePath,
followLinksToStorePath,
storePathToPath,
getStorePathBaseName,
getStorePathHash,
isValidPath,
queryPathInfo,
queryPathInfoFromClientCache,
ValidPathInfo,
validPathInfoNarSize,
validPathInfoNarHash32,
validPathInfoDeriver,
validPathInfoDeriver',
validPathInfoReferences,
validPathInfoReferences',
computeFSClosure,
ClosureParams(..),
defaultClosureParams,
ensurePath,
buildPaths,
buildPath,
addTemporaryRoot,
clearPathInfoCache,
clearSubstituterCaches,
StorePathWithOutputs (..),
newStorePathWithOutputs,
getStorePath,
getOutputs,
Derivation (..),
getDerivation,
getDerivationFromString,
getDerivationNameFromPath,
getDerivationPlatform,
getDerivationBuilder,
getDerivationArguments,
getDerivationEnv,
getDerivationSources,
getDerivationSources',
getDerivationInputs,
getDerivationInputs',
getDerivationOutputNames,
DerivationOutput (..),
DerivationOutputDetail (..),
FixedOutputHash (..),
FileIngestionMethod (..),
getDerivationOutputs,
copyClosure,
SecretKey,
parseSecretKey,
signPath,
Hash (..),
HashType (..),
Strings,
withStrings,
withStringsOf,
pushString,
getStringsLength,
toByteStrings,
toByteStringMap,
forNonNull,
traverseNonNull,
deleteDerivationInputsIterator,
deleteDerivationOutputsIterator,
deleteStringPairs,
deleteStrings,
finalizeDerivation,
finalizeRefValidPathInfo,
finalizeSecretKey,
finalizeStorePath,
finalizeStorePathWithOutputs,
finalizeStrings,
moveStorePath,
moveStorePathMaybe,
unsafeMallocBS,
withPtr',
DerivationInputsIterator,
DerivationOutputsIterator,
NixStore,
NixStorePath,
Ref,
StringPairs,
Hercules.CNix.Store.Context.context,
)
where
import Control.Exception
import Control.Monad.IO.Unlift
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString.Short as SBS
import Data.ByteString.Unsafe (unsafePackMallocCString)
import qualified Data.ByteString.Unsafe as BS
import Data.Coerce (coerce)
import qualified Data.Map as M
import Foreign (alloca, free)
import Foreign.ForeignPtr
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import Foreign.Storable (peek)
import Hercules.CNix.Encapsulation (HasEncapsulation (..), nullableMoveToForeignPtrWrapper)
import Hercules.CNix.Std.Set (StdSet, stdSetCtx)
import qualified Hercules.CNix.Std.Set as Std.Set
import Hercules.CNix.Std.String (stdStringCtx)
import qualified Hercules.CNix.Std.String as Std.String
import Hercules.CNix.Std.Vector
import qualified Hercules.CNix.Std.Vector as Std.Vector
import Hercules.CNix.Store.Context
( DerivationInputsIterator,
DerivationOutputsIterator,
NixStore,
NixStorePath,
Ref,
SecretKey,
StringPairs,
Strings,
ValidPathInfo,
context,
unsafeMallocBS,
)
import qualified Hercules.CNix.Store.Context as C hiding (context)
import Hercules.CNix.Memory (Delete(delete), Finalizer (finalizer), withDelete, toForeignPtr)
import qualified Hercules.CNix.Memory
import Hercules.CNix.Store.Instances ()
import qualified Language.C.Inline.Cpp as C
import qualified Language.C.Inline.Cpp.Exception as C
import Protolude
import System.IO.Unsafe (unsafePerformIO)
import qualified Prelude
C.context (context <> stdVectorCtx <> stdSetCtx <> stdStringCtx)
C.include "<cstring>"
C.include "<nix/config.h>"
C.include "<nix/shared.hh>"
C.include "<nix/store-api.hh>"
C.include "<nix/get-drvs.hh>"
C.include "<nix/derivations.hh>"
C.include "<nix/globals.hh>"
C.include "<nix/path.hh>"
C.include "<variant>"
C.include "<nix/worker-protocol.hh>"
C.include "<nix/path-with-outputs.hh>"
C.include "<nix/hash.hh>"
C.include "hercules-ci-cnix/store.hxx"
C.include "hercules-ci-cnix/string.hxx"
#if NIX_IS_AT_LEAST(2,19,0)
C.include "<nix/signals.hh>"
C.include "<nix/hash.hh>"
#endif
#if ! NIX_IS_AT_LEAST(2,20,0)
C.include "<nix/nar-info-disk-cache.hh>"
#endif
C.using "namespace nix"
C.using "namespace hercules_ci_cnix"
{-# DEPRECATED forNonNull "Use 'Hercules.CNix.Memory.forNonNull' instead" #-}
forNonNull :: Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
forNonNull :: forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
forNonNull = Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
forall (m :: * -> *) a b.
Applicative m =>
Ptr a -> (Ptr a -> m b) -> m (Maybe b)
Hercules.CNix.Memory.forNonNull
{-# DEPRECATED traverseNonNull "Use 'Hercules.CNix.Memory.traverseNonNull' instead" #-}
traverseNonNull :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
traverseNonNull :: forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
traverseNonNull = (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
forall (m :: * -> *) a b.
Applicative m =>
(Ptr a -> m b) -> Ptr a -> m (Maybe b)
Hercules.CNix.Memory.traverseNonNull
newtype Store = Store (Ptr (Ref NixStore))
instance Delete (Ref NixStore) where
delete :: Ptr (Ref NixStore) -> IO ()
delete Ptr (Ref NixStore)
store = [C.exp| void { delete $(refStore* store) } |]
openStore :: IO Store
openStore :: IO Store
openStore =
IO (Ptr (Ref NixStore)) -> IO Store
forall a b. Coercible a b => a -> b
coerce
[C.throwBlock| refStore * {
refStore s = openStore();
return new refStore(s);
} |]
releaseStore :: Store -> IO ()
releaseStore :: Store -> IO ()
releaseStore (Store Ptr (Ref NixStore)
store) = Ptr (Ref NixStore) -> IO ()
forall a. Delete a => Ptr a -> IO ()
delete Ptr (Ref NixStore)
store
withStore :: MonadUnliftIO m => (Store -> m a) -> m a
withStore :: forall (m :: * -> *) a. MonadUnliftIO m => (Store -> m a) -> m a
withStore Store -> m a
m = do
UnliftIO forall a. m a -> IO a
ul <- m (UnliftIO m)
forall (m :: * -> *). MonadUnliftIO m => m (UnliftIO m)
askUnliftIO
IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ (Store -> IO a) -> IO a
forall r. (Store -> IO r) -> IO r
withStore' ((Store -> IO a) -> IO a) -> (Store -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Store
a -> m a -> IO a
forall a. m a -> IO a
ul (Store -> m a
m Store
a)
withStore' ::
(Store -> IO r) ->
IO r
withStore' :: forall r. (Store -> IO r) -> IO r
withStore' =
IO Store -> (Store -> IO ()) -> (Store -> IO r) -> IO r
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Store
openStore Store -> IO ()
releaseStore
withStoreFromURI ::
MonadUnliftIO m =>
Text ->
(Store -> m r) ->
m r
withStoreFromURI :: forall (m :: * -> *) r.
MonadUnliftIO m =>
Text -> (Store -> m r) -> m r
withStoreFromURI Text
storeURIText Store -> m r
f = do
let storeURI :: ByteString
storeURI = Text -> ByteString
encodeUtf8 Text
storeURIText
(UnliftIO forall a. m a -> IO a
unlift) <- m (UnliftIO m)
forall (m :: * -> *). MonadUnliftIO m => m (UnliftIO m)
askUnliftIO
IO r -> m r
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO r -> m r) -> IO r -> m r
forall a b. (a -> b) -> a -> b
$
IO (Ptr (Ref NixStore)) -> (Ptr (Ref NixStore) -> IO r) -> IO r
forall a b. Delete a => IO (Ptr a) -> (Ptr a -> IO b) -> IO b
withDelete
[C.throwBlock| refStore* {
refStore s = openStore($bs-cstr:storeURI);
return new refStore(s);
}|]
(m r -> IO r
forall a. m a -> IO a
unlift (m r -> IO r)
-> (Ptr (Ref NixStore) -> m r) -> Ptr (Ref NixStore) -> IO r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Store -> m r
f (Store -> m r)
-> (Ptr (Ref NixStore) -> Store) -> Ptr (Ref NixStore) -> m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (Ref NixStore) -> Store
Store)
storeUri :: MonadIO m => Store -> m ByteString
storeUri :: forall (m :: * -> *). MonadIO m => Store -> m ByteString
storeUri (Store Ptr (Ref NixStore)
store) = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString (Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
[C.block| const char* {
std::string uri = (*$(refStore* store))->getUri();
return stringdup(uri);
} |]
storeDir :: MonadIO m => Store -> m ByteString
storeDir :: forall (m :: * -> *). MonadIO m => Store -> m ByteString
storeDir (Store Ptr (Ref NixStore)
store) = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString (Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
[C.block| const char* {
std::string uri = (*$(refStore* store))->storeDir;
return stringdup(uri);
} |]
getStoreProtocolVersion :: Store -> IO Int
getStoreProtocolVersion :: Store -> IO Int
getStoreProtocolVersion (Store Ptr (Ref NixStore)
store) =
CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
(CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.throwBlock| int {
Store &store = **$(refStore* store);
return store.getProtocol();
} |]
getClientProtocolVersion :: IO Int
getClientProtocolVersion :: IO Int
getClientProtocolVersion =
CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
(CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.throwBlock| int {
return PROTOCOL_VERSION;
} |]
newtype StorePath = StorePath (ForeignPtr NixStorePath)
instance HasEncapsulation NixStorePath StorePath
instance Finalizer NixStorePath where
finalizer :: FinalizerPtr NixStorePath
finalizer = FinalizerPtr NixStorePath
finalizeStorePath
finalizeStorePath :: FinalizerPtr NixStorePath
{-# NOINLINE finalizeStorePath #-}
finalizeStorePath :: FinalizerPtr NixStorePath
finalizeStorePath =
IO (FinalizerPtr NixStorePath) -> FinalizerPtr NixStorePath
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr NixStorePath)
[C.exp|
void (*)(nix::StorePath *) {
[](StorePath *v) {
delete v;
}
}
|]
{-# DEPRECATED finalizeStorePath "Use 'finalizer' instead" #-}
moveStorePath :: Ptr NixStorePath -> IO StorePath
moveStorePath :: Ptr NixStorePath -> IO StorePath
moveStorePath = Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
{-# DEPRECATED moveStorePath "Use 'moveToForeignPtrWrapper' instead" #-}
moveStorePathMaybe :: Ptr NixStorePath -> IO (Maybe StorePath)
moveStorePathMaybe :: Ptr NixStorePath -> IO (Maybe StorePath)
moveStorePathMaybe = Ptr NixStorePath -> IO (Maybe StorePath)
forall a b. HasEncapsulation a b => Ptr a -> IO (Maybe b)
nullableMoveToForeignPtrWrapper
{-# DEPRECATED moveStorePathMaybe "Use 'nullableMoveToForeignPtrWrapper' instead" #-}
instance Prelude.Show StorePath where
show :: StorePath -> String
show StorePath
storePath = IO String -> String
forall a. IO a -> a
unsafePerformIO do
ByteString
bs <-
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.block| const char* {
std::string s($fptr-ptr:(nix::StorePath *storePath)->to_string());
return stringdup(s);
}|]
String -> IO String
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a b. ConvertText a b => a -> b
toS (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
bs
instance Eq StorePath where
StorePath
a == :: StorePath -> StorePath -> Bool
== StorePath
b = StorePath -> StorePath -> Ordering
forall a. Ord a => a -> a -> Ordering
compare StorePath
a StorePath
b Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ
instance Ord StorePath where
compare :: StorePath -> StorePath -> Ordering
compare (StorePath ForeignPtr NixStorePath
a) (StorePath ForeignPtr NixStorePath
b) =
CInt -> CInt -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
CInt
0
[C.pure| int {
$fptr-ptr:(nix::StorePath *a)->to_string().compare($fptr-ptr:(nix::StorePath *b)->to_string())
}|]
parseStorePathBaseName :: ByteString -> IO StorePath
parseStorePathBaseName :: ByteString -> IO StorePath
parseStorePathBaseName ByteString
bs =
Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr NixStorePath -> IO StorePath)
-> IO (Ptr NixStorePath) -> IO StorePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| nix::StorePath *{
return new StorePath(std::string($bs-ptr:bs, $bs-len:bs));
}|]
parseStorePath :: Store -> ByteString -> IO StorePath
parseStorePath :: Store -> ByteString -> IO StorePath
parseStorePath (Store Ptr (Ref NixStore)
store) ByteString
bs =
Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr NixStorePath -> IO StorePath)
-> IO (Ptr NixStorePath) -> IO StorePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| nix::StorePath *{
return new StorePath(std::move((*$(refStore* store))->parseStorePath(std::string($bs-ptr:bs, $bs-len:bs))));
}|]
getStorePathBaseName :: StorePath -> IO ByteString
getStorePathBaseName :: StorePath -> IO ByteString
getStorePathBaseName (StorePath ForeignPtr NixStorePath
sp) = do
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.block| const char *{
std::string s($fptr-ptr:(nix::StorePath *sp)->to_string());
return stringdup(s);
}|]
getStorePathHash :: StorePath -> IO ByteString
getStorePathHash :: StorePath -> IO ByteString
getStorePathHash (StorePath ForeignPtr NixStorePath
sp) = do
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.block| const char *{
std::string s($fptr-ptr:(nix::StorePath *sp)->hashPart());
return stringdup(s);
}|]
storePathToPath :: Store -> StorePath -> IO ByteString
storePathToPath :: Store -> StorePath -> IO ByteString
storePathToPath (Store Ptr (Ref NixStore)
store) (StorePath ForeignPtr NixStorePath
sp) =
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.block| const char *{
Store & store = **$(refStore* store);
StorePath &sp = *$fptr-ptr:(nix::StorePath *sp);
std::string s(store.printStorePath(sp));
return stringdup(s);
}|]
ensurePath :: Store -> StorePath -> IO ()
ensurePath :: Store -> StorePath -> IO ()
ensurePath (Store Ptr (Ref NixStore)
store) (StorePath ForeignPtr NixStorePath
storePath) =
[C.throwBlock| void {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &storePath = *$fptr-ptr:(nix::StorePath *storePath);
store.ensurePath(storePath);
} |]
addTemporaryRoot :: Store -> StorePath -> IO ()
addTemporaryRoot :: Store -> StorePath -> IO ()
addTemporaryRoot (Store Ptr (Ref NixStore)
store) StorePath
storePath = do
[C.throwBlock| void {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &storePath = *$fptr-ptr:(nix::StorePath *storePath);
store.addTempRoot(storePath);
} |]
clearPathInfoCache :: Store -> IO ()
clearPathInfoCache :: Store -> IO ()
clearPathInfoCache (Store Ptr (Ref NixStore)
store) =
[C.throwBlock| void {
(*$(refStore* store))->clearPathInfoCache();
} |]
clearSubstituterCaches :: IO ()
clearSubstituterCaches :: IO ()
clearSubstituterCaches =
[C.throwBlock| void {
auto subs = nix::getDefaultSubstituters();
for (auto sub : subs) {
sub->clearPathInfoCache();
}
} |]
newtype StorePathWithOutputs = StorePathWithOutputs (ForeignPtr C.NixStorePathWithOutputs)
instance HasEncapsulation C.NixStorePathWithOutputs StorePathWithOutputs
instance Finalizer C.NixStorePathWithOutputs where
finalizer :: FinalizerPtr NixStorePathWithOutputs
finalizer = FinalizerPtr NixStorePathWithOutputs
finalizeStorePathWithOutputs
finalizeStorePathWithOutputs :: FinalizerPtr C.NixStorePathWithOutputs
{-# NOINLINE finalizeStorePathWithOutputs #-}
finalizeStorePathWithOutputs :: FinalizerPtr NixStorePathWithOutputs
finalizeStorePathWithOutputs =
IO (FinalizerPtr NixStorePathWithOutputs)
-> FinalizerPtr NixStorePathWithOutputs
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr NixStorePathWithOutputs)
[C.exp|
void (*)(nix::StorePathWithOutputs *) {
[](StorePathWithOutputs *v) {
delete v;
}
}
|]
{-# DEPRECATED finalizeStorePathWithOutputs "Use 'finalizer' instead" #-}
newStorePathWithOutputs :: StorePath -> [ByteString] -> IO StorePathWithOutputs
newStorePathWithOutputs :: StorePath -> [ByteString] -> IO StorePathWithOutputs
newStorePathWithOutputs StorePath
storePath [ByteString]
outputs = do
StdSet CStdString
set <- IO (StdSet CStdString)
forall a. HasStdSet a => IO (StdSet a)
Std.Set.new
[ByteString] -> (ByteString -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [ByteString]
outputs (\ByteString
o -> ByteString -> (Ptr CStdString -> IO ()) -> IO ()
forall a. ByteString -> (Ptr CStdString -> IO a) -> IO a
Std.String.withString ByteString
o (StdSet CStdString -> Ptr CStdString -> IO ()
forall a. HasStdSet a => StdSet a -> Ptr a -> IO ()
Std.Set.insertP StdSet CStdString
set))
Ptr NixStorePathWithOutputs -> IO StorePathWithOutputs
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr NixStorePathWithOutputs -> IO StorePathWithOutputs)
-> IO (Ptr NixStorePathWithOutputs) -> IO StorePathWithOutputs
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.exp| nix::StorePathWithOutputs * {
new StorePathWithOutputs {*$fptr-ptr:(nix::StorePath *storePath), *$fptr-ptr:(std::set<std::string>* set)}
}|]
getStorePath :: StorePathWithOutputs -> IO StorePath
getStorePath :: StorePathWithOutputs -> IO StorePath
getStorePath StorePathWithOutputs
swo = IO StorePath -> IO StorePath
forall a. IO a -> IO a
mask_ do
Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr NixStorePath -> IO StorePath)
-> IO (Ptr NixStorePath) -> IO StorePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.exp| nix::StorePath * {
new StorePath($fptr-ptr:(nix::StorePathWithOutputs *swo)->path)
}|]
getOutputs :: StorePathWithOutputs -> IO [ByteString]
getOutputs :: StorePathWithOutputs -> IO [ByteString]
getOutputs StorePathWithOutputs
swo = IO [ByteString] -> IO [ByteString]
forall a. IO a -> IO a
mask_ do
(Ptr CStdString -> IO ByteString)
-> [Ptr CStdString] -> IO [ByteString]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Ptr CStdString -> IO ByteString
Std.String.moveToByteString ([Ptr CStdString] -> IO [ByteString])
-> IO [Ptr CStdString] -> IO [ByteString]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< StdVector CStdString -> IO [Ptr CStdString]
forall a. HasStdVector a => StdVector a -> IO [Ptr a]
toListP (StdVector CStdString -> IO [Ptr CStdString])
-> IO (StdVector CStdString) -> IO [Ptr CStdString]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (CStdVector CStdString) -> IO (StdVector CStdString)
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr (CStdVector CStdString) -> IO (StdVector CStdString))
-> IO (Ptr (CStdVector CStdString)) -> IO (StdVector CStdString)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| std::vector<std::string>* {
auto r = new std::vector<std::string>();
for (auto s : $fptr-ptr:(nix::StorePathWithOutputs *swo)->outputs)
r->push_back(s);
return r;
}|]
buildPaths :: Store -> StdVector C.NixStorePathWithOutputs -> IO ()
buildPaths :: Store -> StdVector NixStorePathWithOutputs -> IO ()
buildPaths (Store Ptr (Ref NixStore)
store) (StdVector ForeignPtr (CStdVector NixStorePathWithOutputs)
paths) = do
[C.throwBlock| void {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
std::vector<StorePathWithOutputs> &paths = *$fptr-ptr:(std::vector<nix::StorePathWithOutputs>* paths);
store.buildPaths(toDerivedPaths(paths));
}|]
buildPath :: Store -> StorePathWithOutputs -> IO ()
buildPath :: Store -> StorePathWithOutputs -> IO ()
buildPath Store
store StorePathWithOutputs
spwo = do
Store -> StdVector NixStorePathWithOutputs -> IO ()
buildPaths Store
store (StdVector NixStorePathWithOutputs -> IO ())
-> IO (StdVector NixStorePathWithOutputs) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [StorePathWithOutputs] -> IO (StdVector NixStorePathWithOutputs)
forall a' a.
(Coercible a' (ForeignPtr a), HasStdVector a) =>
[a'] -> IO (StdVector a)
Std.Vector.fromListFP [StorePathWithOutputs
spwo]
newtype Derivation = Derivation (ForeignPtr C.Derivation)
instance HasEncapsulation C.Derivation Derivation
instance Finalizer C.Derivation where
finalizer :: FinalizerPtr Derivation
finalizer = FinalizerPtr Derivation
finalizeDerivation
finalizeDerivation :: FinalizerPtr C.Derivation
{-# NOINLINE finalizeDerivation #-}
finalizeDerivation :: FinalizerPtr Derivation
finalizeDerivation =
IO (FinalizerPtr Derivation) -> FinalizerPtr Derivation
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr Derivation)
[C.exp|
void (*)(Derivation *) {
[](Derivation *v) {
delete v;
}
} |]
{-# DEPRECATED finalizeDerivation "Use 'finalizer' instead" #-}
getDerivation :: Store -> StorePath -> IO Derivation
getDerivation :: Store -> StorePath -> IO Derivation
getDerivation (Store Ptr (Ref NixStore)
store) (StorePath ForeignPtr NixStorePath
spwo) = do
Ptr Derivation -> IO Derivation
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr Derivation -> IO Derivation)
-> IO (Ptr Derivation) -> IO Derivation
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| Derivation *{
ReceiveInterrupts _;
Store &store = **$(refStore* store);
return new Derivation(
store.derivationFromPath(*$fptr-ptr:(nix::StorePath *spwo))
);
} |]
getDerivationFromString ::
Store ->
ByteString ->
ByteString ->
IO Derivation
getDerivationFromString :: Store -> ByteString -> ByteString -> IO Derivation
getDerivationFromString (Store Ptr (Ref NixStore)
store) ByteString
name ByteString
contents = do
Ptr Derivation -> IO Derivation
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr Derivation -> IO Derivation)
-> IO (Ptr Derivation) -> IO Derivation
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| Derivation *{
Store &store = **$(refStore* store);
std::string name($bs-ptr:name, $bs-len:name);
return new Derivation(parseDerivation(store, std::string($bs-ptr:contents, $bs-len:contents), name));
}|]
getDerivationNameFromPath :: StorePath -> IO ByteString
getDerivationNameFromPath :: StorePath -> IO ByteString
getDerivationNameFromPath StorePath
storePath =
Ptr CChar -> IO ByteString
BS.unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| const char *{
StorePath &sp = *$fptr-ptr:(nix::StorePath *storePath);
std::string s(Derivation::nameFromPath(sp));
return stringdup(s);
}|]
data DerivationOutput = DerivationOutput
{ DerivationOutput -> ByteString
derivationOutputName :: !ByteString,
DerivationOutput -> Maybe StorePath
derivationOutputPath :: !(Maybe StorePath),
DerivationOutput -> DerivationOutputDetail
derivationOutputDetail :: !DerivationOutputDetail
}
deriving (DerivationOutput -> DerivationOutput -> Bool
(DerivationOutput -> DerivationOutput -> Bool)
-> (DerivationOutput -> DerivationOutput -> Bool)
-> Eq DerivationOutput
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DerivationOutput -> DerivationOutput -> Bool
== :: DerivationOutput -> DerivationOutput -> Bool
$c/= :: DerivationOutput -> DerivationOutput -> Bool
/= :: DerivationOutput -> DerivationOutput -> Bool
Eq, Int -> DerivationOutput -> ShowS
[DerivationOutput] -> ShowS
DerivationOutput -> String
(Int -> DerivationOutput -> ShowS)
-> (DerivationOutput -> String)
-> ([DerivationOutput] -> ShowS)
-> Show DerivationOutput
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DerivationOutput -> ShowS
showsPrec :: Int -> DerivationOutput -> ShowS
$cshow :: DerivationOutput -> String
show :: DerivationOutput -> String
$cshowList :: [DerivationOutput] -> ShowS
showList :: [DerivationOutput] -> ShowS
Show)
data DerivationOutputDetail
= DerivationOutputInputAddressed StorePath
| DerivationOutputCAFixed FixedOutputHash StorePath
| DerivationOutputCAFloating FileIngestionMethod HashType
| DerivationOutputDeferred
deriving (DerivationOutputDetail -> DerivationOutputDetail -> Bool
(DerivationOutputDetail -> DerivationOutputDetail -> Bool)
-> (DerivationOutputDetail -> DerivationOutputDetail -> Bool)
-> Eq DerivationOutputDetail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DerivationOutputDetail -> DerivationOutputDetail -> Bool
== :: DerivationOutputDetail -> DerivationOutputDetail -> Bool
$c/= :: DerivationOutputDetail -> DerivationOutputDetail -> Bool
/= :: DerivationOutputDetail -> DerivationOutputDetail -> Bool
Eq, Int -> DerivationOutputDetail -> ShowS
[DerivationOutputDetail] -> ShowS
DerivationOutputDetail -> String
(Int -> DerivationOutputDetail -> ShowS)
-> (DerivationOutputDetail -> String)
-> ([DerivationOutputDetail] -> ShowS)
-> Show DerivationOutputDetail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DerivationOutputDetail -> ShowS
showsPrec :: Int -> DerivationOutputDetail -> ShowS
$cshow :: DerivationOutputDetail -> String
show :: DerivationOutputDetail -> String
$cshowList :: [DerivationOutputDetail] -> ShowS
showList :: [DerivationOutputDetail] -> ShowS
Show)
data FixedOutputHash = FixedOutputHash !FileIngestionMethod {-# UNPACK #-} !Hash
deriving (FixedOutputHash -> FixedOutputHash -> Bool
(FixedOutputHash -> FixedOutputHash -> Bool)
-> (FixedOutputHash -> FixedOutputHash -> Bool)
-> Eq FixedOutputHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FixedOutputHash -> FixedOutputHash -> Bool
== :: FixedOutputHash -> FixedOutputHash -> Bool
$c/= :: FixedOutputHash -> FixedOutputHash -> Bool
/= :: FixedOutputHash -> FixedOutputHash -> Bool
Eq, Int -> FixedOutputHash -> ShowS
[FixedOutputHash] -> ShowS
FixedOutputHash -> String
(Int -> FixedOutputHash -> ShowS)
-> (FixedOutputHash -> String)
-> ([FixedOutputHash] -> ShowS)
-> Show FixedOutputHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FixedOutputHash -> ShowS
showsPrec :: Int -> FixedOutputHash -> ShowS
$cshow :: FixedOutputHash -> String
show :: FixedOutputHash -> String
$cshowList :: [FixedOutputHash] -> ShowS
showList :: [FixedOutputHash] -> ShowS
Show)
data FileIngestionMethod = Flat | Recursive
deriving (FileIngestionMethod -> FileIngestionMethod -> Bool
(FileIngestionMethod -> FileIngestionMethod -> Bool)
-> (FileIngestionMethod -> FileIngestionMethod -> Bool)
-> Eq FileIngestionMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileIngestionMethod -> FileIngestionMethod -> Bool
== :: FileIngestionMethod -> FileIngestionMethod -> Bool
$c/= :: FileIngestionMethod -> FileIngestionMethod -> Bool
/= :: FileIngestionMethod -> FileIngestionMethod -> Bool
Eq, Int -> FileIngestionMethod -> ShowS
[FileIngestionMethod] -> ShowS
FileIngestionMethod -> String
(Int -> FileIngestionMethod -> ShowS)
-> (FileIngestionMethod -> String)
-> ([FileIngestionMethod] -> ShowS)
-> Show FileIngestionMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileIngestionMethod -> ShowS
showsPrec :: Int -> FileIngestionMethod -> ShowS
$cshow :: FileIngestionMethod -> String
show :: FileIngestionMethod -> String
$cshowList :: [FileIngestionMethod] -> ShowS
showList :: [FileIngestionMethod] -> ShowS
Show)
data Hash = Hash !HashType {-# UNPACK #-} !ShortByteString
deriving (Hash -> Hash -> Bool
(Hash -> Hash -> Bool) -> (Hash -> Hash -> Bool) -> Eq Hash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Hash -> Hash -> Bool
== :: Hash -> Hash -> Bool
$c/= :: Hash -> Hash -> Bool
/= :: Hash -> Hash -> Bool
Eq, Int -> Hash -> ShowS
[Hash] -> ShowS
Hash -> String
(Int -> Hash -> ShowS)
-> (Hash -> String) -> ([Hash] -> ShowS) -> Show Hash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Hash -> ShowS
showsPrec :: Int -> Hash -> ShowS
$cshow :: Hash -> String
show :: Hash -> String
$cshowList :: [Hash] -> ShowS
showList :: [Hash] -> ShowS
Show)
data HashType = MD5 | SHA1 | SHA256 | SHA512
deriving (HashType -> HashType -> Bool
(HashType -> HashType -> Bool)
-> (HashType -> HashType -> Bool) -> Eq HashType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HashType -> HashType -> Bool
== :: HashType -> HashType -> Bool
$c/= :: HashType -> HashType -> Bool
/= :: HashType -> HashType -> Bool
Eq, Int -> HashType -> ShowS
[HashType] -> ShowS
HashType -> String
(Int -> HashType -> ShowS)
-> (HashType -> String) -> ([HashType] -> ShowS) -> Show HashType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HashType -> ShowS
showsPrec :: Int -> HashType -> ShowS
$cshow :: HashType -> String
show :: HashType -> String
$cshowList :: [HashType] -> ShowS
showList :: [HashType] -> ShowS
Show)
getDerivationOutputs :: Store -> ByteString -> Derivation -> IO [DerivationOutput]
getDerivationOutputs :: Store -> ByteString -> Derivation -> IO [DerivationOutput]
getDerivationOutputs (Store Ptr (Ref NixStore)
store) ByteString
drvName (Derivation ForeignPtr Derivation
derivationFPtr) =
ForeignPtr Derivation
-> (Ptr Derivation -> IO [DerivationOutput])
-> IO [DerivationOutput]
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Derivation
derivationFPtr \Ptr Derivation
derivation ->
IO (Ptr DerivationOutputsIterator)
-> (Ptr DerivationOutputsIterator -> IO [DerivationOutput])
-> IO [DerivationOutput]
forall a b. Delete a => IO (Ptr a) -> (Ptr a -> IO b) -> IO b
withDelete
[C.exp| DerivationOutputsIterator* {
new DerivationOutputsIterator($(Derivation *derivation)->outputs.begin())
}|] \Ptr DerivationOutputsIterator
i ->
(IO [DerivationOutput] -> IO [DerivationOutput])
-> IO [DerivationOutput]
forall a. (a -> a) -> a
fix ((IO [DerivationOutput] -> IO [DerivationOutput])
-> IO [DerivationOutput])
-> (IO [DerivationOutput] -> IO [DerivationOutput])
-> IO [DerivationOutput]
forall a b. (a -> b) -> a -> b
$ \IO [DerivationOutput]
continue -> do
Bool
isEnd <- (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { *$(DerivationOutputsIterator *i) == $(Derivation *derivation)->outputs.end() }|]
if Bool
isEnd
then [DerivationOutput] -> IO [DerivationOutput]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else
( IO ([DerivationOutput] -> [DerivationOutput])
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a. IO a -> IO a
mask_ do
(Ptr (Ptr CChar) -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr (Ptr CChar)
nameP -> (Ptr (Ptr NixStorePath)
-> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr (Ptr NixStorePath)
pathP -> (Ptr CInt -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr CInt
typP -> (Ptr CInt -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr CInt
fimP ->
(Ptr CInt -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr CInt
hashTypeP -> (Ptr (Ptr CChar) -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr (Ptr CChar)
hashValueP -> (Ptr CInt -> IO ([DerivationOutput] -> [DerivationOutput]))
-> IO ([DerivationOutput] -> [DerivationOutput])
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr CInt
hashSizeP -> do
[C.throwBlock| void {
Store &store = **$(refStore *store);
std::string drvName = std::string($bs-ptr:drvName, $bs-len:drvName);
nix::DerivationOutputs::iterator &i = *$(DerivationOutputsIterator *i);
const char *&name = *$(const char **nameP);
int &typ = *$(int *typP);
StorePath *& path = *$(nix::StorePath **pathP);
int &fim = *$(int *fimP);
int &hashType = *$(int *hashTypeP);
char *&hashValue = *$(char **hashValueP);
int &hashSize = *$(int *hashSizeP);
std::string nameString = i->first;
name = stringdup(nameString);
path = nullptr;
std::visit(overloaded {
#if NIX_IS_AT_LEAST(2, 18, 0)
[&](DerivationOutput::InputAddressed doi) -> void {
typ = 0;
path = new StorePath(doi.path);
},
[&](DerivationOutput::CAFixed dof) -> void {
typ = 1;
path = new StorePath(dof.path(store, $(Derivation *derivation)->name, nameString));
std::visit(overloaded {
[&](nix::FileIngestionMethod fim_) -> void {
switch (fim_) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
},
[&](nix::TextIngestionMethod) -> void {
// FIXME (RFC 92)
fim = -1;
}
}, dof.ca.method.raw);
const Hash & hash = dof.ca.hash;
#if NIX_IS_AT_LEAST(2, 20, 0)
switch (hash.algo) {
case HashAlgorithm::MD5:
hashType = 0;
break;
case HashAlgorithm::SHA1:
hashType = 1;
break;
case HashAlgorithm::SHA256:
hashType = 2;
break;
case HashAlgorithm::SHA512:
hashType = 3;
break;
#else
switch (hash.type) {
case htMD5:
hashType = 0;
break;
case htSHA1:
hashType = 1;
break;
case htSHA256:
hashType = 2;
break;
case htSHA512:
hashType = 3;
break;
#endif
default:
hashType = -1;
break;
}
hashSize = hash.hashSize;
hashValue = (char*)malloc(hashSize);
std::memcpy((void*)(hashValue),
(void*)(hash.hash),
hashSize);
},
[&](DerivationOutput::CAFloating dof) -> void {
typ = 2;
std::visit(overloaded {
[&](nix::FileIngestionMethod fim_) -> void {
switch (fim_) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
},
[&](nix::TextIngestionMethod) -> void {
// FIXME (RFC 92)
fim = -1;
}
}, dof.method.raw);
#if NIX_IS_AT_LEAST(2, 20, 0)
switch (dof.hashAlgo) {
case HashAlgorithm::MD5:
hashType = 0;
break;
case HashAlgorithm::SHA1:
hashType = 1;
break;
case HashAlgorithm::SHA256:
hashType = 2;
break;
case HashAlgorithm::SHA512:
hashType = 3;
break;
#else
switch (dof.hashType) {
case htMD5:
hashType = 0;
break;
case htSHA1:
hashType = 1;
break;
case htSHA256:
hashType = 2;
break;
case htSHA512:
hashType = 3;
break;
#endif
default:
hashType = -1;
break;
}
},
[&](DerivationOutput::Deferred) -> void {
typ = 3;
},
[&](DerivationOutput::Impure) -> void {
typ = 4;
},
},
i->second.raw
#else
[&](DerivationOutputInputAddressed doi) -> void {
typ = 0;
path = new StorePath(doi.path);
},
[&](DerivationOutputCAFixed dof) -> void {
typ = 1;
path = new StorePath(dof.path(store, $(Derivation *derivation)->name, nameString));
#if NIX_IS_AT_LEAST(2, 16, 0)
std::visit(overloaded {
[&](nix::FileIngestionMethod fim_) -> void {
switch (fim_) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
},
[&](nix::TextIngestionMethod) -> void {
// FIXME (RFC 92)
fim = -1;
}
# if NIX_IS_AT_LEAST(2, 17, 0)
}, dof.ca.method.raw);
# else
}, dof.ca.getMethod().raw);
# endif
#else
switch (dof.hash.method) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
#endif
#if NIX_IS_AT_LEAST(2, 17, 0)
const Hash & hash = dof.ca.hash;
#elif NIX_IS_AT_LEAST(2, 16, 0)
const Hash & hash = dof.ca.getHash();
#else
const Hash & hash = dof.hash.hash;
#endif
switch (hash.type) {
case htMD5:
hashType = 0;
break;
case htSHA1:
hashType = 1;
break;
case htSHA256:
hashType = 2;
break;
case htSHA512:
hashType = 3;
break;
default:
hashType = -1;
break;
}
hashSize = hash.hashSize;
hashValue = (char*)malloc(hashSize);
std::memcpy((void*)(hashValue),
(void*)(hash.hash),
hashSize);
},
[&](DerivationOutputCAFloating dof) -> void {
typ = 2;
#if NIX_IS_AT_LEAST(2, 16, 0)
std::visit(overloaded {
[&](nix::FileIngestionMethod fim_) -> void {
switch (fim_) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
},
[&](nix::TextIngestionMethod) -> void {
// FIXME (RFC 92)
fim = -1;
}
}, dof.method.raw);
#else
switch (dof.method) {
case nix::FileIngestionMethod::Flat:
fim = 0;
break;
case nix::FileIngestionMethod::Recursive:
fim = 1;
break;
default:
fim = -1;
break;
}
#endif
switch (dof.hashType) {
case htMD5:
hashType = 0;
break;
case htSHA1:
hashType = 1;
break;
case htSHA256:
hashType = 2;
break;
case htSHA512:
hashType = 3;
break;
default:
hashType = -1;
break;
}
},
[&](DerivationOutputDeferred) -> void {
typ = 3;
},
#if NIX_IS_AT_LEAST(2,8,0)
[&](DerivationOutputImpure) -> void {
typ = 4;
},
#endif
},
#if NIX_IS_AT_LEAST(2,8,0)
i->second.raw()
#else
i->second.output
#endif
#endif
);
i++;
}|]
name <- unsafePackMallocCString =<< peek nameP
path <- nullableMoveToForeignPtrWrapper =<< peek pathP
typ <- peek typP
let getFileIngestionMethod = peek fimP <&> \case 0 -> Flat; 1 -> Recursive; _ -> panic "getDerivationOutputs: unknown fim"
getHashType =
peek hashTypeP <&> \case
0 -> MD5
1 -> SHA1
2 -> SHA256
3 -> SHA512
_ -> panic "getDerivationOutputs: unknown hashType"
detail <- case typ of
0 -> pure $ DerivationOutputInputAddressed (fromMaybe (panic "getDerivationOutputs: impossible DOIA path missing") path)
1 -> do
hashValue <- peek hashValueP
hashSize <- peek hashSizeP
hashString <- SBS.packCStringLen (hashValue, fromIntegral hashSize)
free hashValue
hashType <- getHashType
fim <- getFileIngestionMethod
pure $ DerivationOutputCAFixed (FixedOutputHash fim (Hash hashType hashString)) (fromMaybe (panic "getDerivationOutputs: impossible DOCF path missing") path)
2 -> do
hashType <- getHashType
fim <- getFileIngestionMethod
pure $ DerivationOutputCAFloating fim hashType
3 -> pure DerivationOutputDeferred
4 -> panic "getDerivationOutputs: impure derivations not supported yet"
_ -> panic "getDerivationOutputs: impossible getDerivationOutputs typ"
pure
( DerivationOutput
{ derivationOutputName = name,
derivationOutputPath = path,
derivationOutputDetail = detail
}
:
)
)
<*> continue
instance Delete DerivationOutputsIterator where
delete a = [C.block| void { delete $(DerivationOutputsIterator *a); }|]
deleteDerivationOutputsIterator :: Ptr DerivationOutputsIterator -> IO ()
deleteDerivationOutputsIterator = delete
{-# DEPRECATED deleteDerivationOutputsIterator "Use 'delete' instead" #-}
getDerivationPlatform :: Derivation -> IO ByteString
getDerivationPlatform derivation =
BS.unsafePackMallocCString =<<
[C.exp| const char* {
stringdup($fptr-ptr:(Derivation *derivation)->platform)
} |]
getDerivationBuilder :: Derivation -> IO ByteString
getDerivationBuilder derivation =
BS.unsafePackMallocCString =<<
[C.exp| const char* {
stringdup($fptr-ptr:(Derivation *derivation)->builder)
} |]
getDerivationArguments :: Derivation -> IO [ByteString]
getDerivationArguments derivation =
withDelete
[C.throwBlock| Strings* {
Strings *r = new Strings();
for (auto i : $fptr-ptr:(Derivation *derivation)->args) {
r->push_back(i);
}
return r;
}|]
toByteStrings
getDerivationSources :: Store -> Derivation -> IO [StorePath]
getDerivationSources _ = getDerivationSources'
getDerivationSources' :: Derivation -> IO [StorePath]
getDerivationSources' derivation = mask_ do
vec <-
moveToForeignPtrWrapper
=<< [C.throwBlock| std::vector<nix::StorePath*>* {
auto r = new std::vector<StorePath *>();
for (auto s : $fptr-ptr:(Derivation *derivation)->inputSrcs)
r->push_back(new StorePath(s));
return r;
}|]
traverse moveToForeignPtrWrapper =<< Std.Vector.toList vec
getDerivationInputs :: Store -> Derivation -> IO [(StorePath, [ByteString])]
getDerivationInputs _ = getDerivationInputs'
getDerivationInputs' :: Derivation -> IO [(StorePath, [ByteString])]
#if NIX_IS_AT_LEAST(2, 18, 0)
getDerivationInputs' (Derivation derivationFPtr) =
withForeignPtr derivationFPtr \derivation ->
withDelete
[C.exp| DerivationInputsIterator* {
new DerivationInputsIterator($(Derivation *derivation)->inputDrvs.map.begin())
}|]
$ \i -> fix $ \continue -> do
isEnd <- (0 /=) <$> [C.exp| bool { *$(DerivationInputsIterator *i) == $(Derivation *derivation)->inputDrvs.map.end() }|]
if isEnd
then pure []
else do
name <-
[C.throwBlock| nix::StorePath *{
return new StorePath((*$(DerivationInputsIterator *i))->first);
}|]
>>= moveToForeignPtrWrapper
outs <-
withDelete
[C.block| Strings* {
Strings *r = new Strings();
for (const auto & i : (*$(DerivationInputsIterator *i))->second.value) {
r->push_back(i);
}
// for (const auto &i : iter->second.childMap) {
// TODO (RFC 92)
//}
return r;
}|]
toByteStrings
[C.block| void { (*$(DerivationInputsIterator *i))++; }|]
((name, outs) :) <$> continue
#else
getDerivationInputs' (Derivation derivationFPtr) =
withForeignPtr derivationFPtr \derivation ->
withDelete
[C.exp| DerivationInputsIterator* {
new DerivationInputsIterator($(Derivation *derivation)->inputDrvs.begin())
}|]
$ \i -> fix $ \continue -> do
isEnd <- (0 /=) <$> [C.exp| bool { *$(DerivationInputsIterator *i) == $(Derivation *derivation)->inputDrvs.end() }|]
if isEnd
then pure []
else do
name <-
[C.throwBlock| nix::StorePath *{
return new StorePath((*$(DerivationInputsIterator *i))->first);
}|]
>>= moveToForeignPtrWrapper
outs <-
withDelete
[C.block| Strings*{
Strings *r = new Strings();
for (auto i : (*$(DerivationInputsIterator *i))->second) {
r->push_back(i);
}
return r;
}|]
toByteStrings
[C.block| void { (*$(DerivationInputsIterator *i))++; }|]
((name, outs) :) <$> continue
#endif
instance Delete DerivationInputsIterator where
delete :: Ptr DerivationInputsIterator -> IO ()
delete Ptr DerivationInputsIterator
a = [C.block| void { delete $(DerivationInputsIterator *a); }|]
deleteDerivationInputsIterator :: Ptr DerivationInputsIterator -> IO ()
deleteDerivationInputsIterator :: Ptr DerivationInputsIterator -> IO ()
deleteDerivationInputsIterator = Ptr DerivationInputsIterator -> IO ()
forall a. Delete a => Ptr a -> IO ()
delete
{-# DEPRECATED deleteDerivationInputsIterator "Use 'delete' instead" #-}
getDerivationEnv :: Derivation -> IO (Map ByteString ByteString)
getDerivationEnv :: Derivation -> IO (Map ByteString ByteString)
getDerivationEnv (Derivation ForeignPtr Derivation
fptr) =
ForeignPtr Derivation
-> (Ptr Derivation -> IO (Map ByteString ByteString))
-> IO (Map ByteString ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Derivation
fptr \Ptr Derivation
ptr -> do
Ptr StringPairs
pairs <- [C.exp| StringPairs* { &$(Derivation *ptr)->env }|]
Ptr StringPairs -> IO (Map ByteString ByteString)
toByteStringMap Ptr StringPairs
pairs
getDerivationOutputNames :: ForeignPtr C.Derivation -> IO [ByteString]
getDerivationOutputNames :: ForeignPtr Derivation -> IO [ByteString]
getDerivationOutputNames ForeignPtr Derivation
fptr =
ForeignPtr Derivation
-> (Ptr Derivation -> IO [ByteString]) -> IO [ByteString]
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Derivation
fptr \Ptr Derivation
ptr -> IO (Ptr Strings)
-> (Ptr Strings -> IO [ByteString]) -> IO [ByteString]
forall a b. Delete a => IO (Ptr a) -> (Ptr a -> IO b) -> IO b
withDelete
[C.throwBlock| Strings* {
Strings *r = new Strings();
for (auto i : $(Derivation *ptr)->outputs) {
r->push_back(i.first);
}
return r;
}|]
Ptr Strings -> IO [ByteString]
toByteStrings
instance Delete StringPairs where
delete :: Ptr StringPairs -> IO ()
delete Ptr StringPairs
s = [C.block| void { delete $(StringPairs *s); }|]
deleteStringPairs :: Ptr StringPairs -> IO ()
deleteStringPairs :: Ptr StringPairs -> IO ()
deleteStringPairs = Ptr StringPairs -> IO ()
forall a. Delete a => Ptr a -> IO ()
delete
{-# DEPRECATED deleteStringPairs "Use 'delete' instead" #-}
instance Delete Strings where
delete :: Ptr Strings -> IO ()
delete Ptr Strings
s = [C.block| void { delete $(Strings *s); }|]
deleteStrings :: Ptr Strings -> IO ()
deleteStrings :: Ptr Strings -> IO ()
deleteStrings = Ptr Strings -> IO ()
forall a. Delete a => Ptr a -> IO ()
delete
{-# DEPRECATED deleteStrings "Use 'delete' instead" #-}
instance Finalizer Strings where
finalizer :: FinalizerPtr Strings
finalizer = FinalizerPtr Strings
finalizeStrings
finalizeStrings :: FinalizerPtr Strings
{-# NOINLINE finalizeStrings #-}
finalizeStrings :: FinalizerPtr Strings
finalizeStrings =
IO (FinalizerPtr Strings) -> FinalizerPtr Strings
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr Strings)
[C.exp|
void (*)(Strings *) {
[](Strings *v) {
delete v;
}
} |]
{-# DEPRECATED finalizeStrings "Use 'finalizer' instead" #-}
getStringsLength :: Ptr Strings -> IO C.CSize
getStringsLength :: Ptr Strings -> IO CSize
getStringsLength Ptr Strings
strings = [C.exp| size_t { $(Strings *strings)->size() }|]
toByteStrings :: Ptr Strings -> IO [ByteString]
toByteStrings :: Ptr Strings -> IO [ByteString]
toByteStrings Ptr Strings
strings = do
Ptr StringsIterator
i <- [C.exp| StringsIterator *{ new StringsIterator($(Strings *strings)->begin()) } |]
(IO [ByteString] -> IO [ByteString]) -> IO [ByteString]
forall a. (a -> a) -> a
fix ((IO [ByteString] -> IO [ByteString]) -> IO [ByteString])
-> (IO [ByteString] -> IO [ByteString]) -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$ \IO [ByteString]
go -> do
Bool
isEnd <- (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { *$(StringsIterator *i) == $(Strings *strings)->end() }|]
if Bool
isEnd
then [ByteString] -> IO [ByteString]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else do
Ptr CChar
s <- [C.exp| const char*{ stringdup(*(*$(StringsIterator *i))) }|]
ByteString
bs <- Ptr CChar -> IO ByteString
BS.unsafePackMallocCString Ptr CChar
s
[C.block| void { (*$(StringsIterator *i))++; }|]
(ByteString
bs ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:) ([ByteString] -> [ByteString])
-> IO [ByteString] -> IO [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [ByteString]
go
toByteStringMap :: Ptr StringPairs -> IO (Map ByteString ByteString)
toByteStringMap :: Ptr StringPairs -> IO (Map ByteString ByteString)
toByteStringMap Ptr StringPairs
strings =
[(ByteString, ByteString)] -> Map ByteString ByteString
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(ByteString, ByteString)] -> Map ByteString ByteString)
-> IO [(ByteString, ByteString)] -> IO (Map ByteString ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr StringPairsIterator -> IO [(ByteString, ByteString)])
-> IO [(ByteString, ByteString)]
forall {b}. (Ptr StringPairsIterator -> IO b) -> IO b
withStringPairIterator \Ptr StringPairsIterator
i ->
(IO [(ByteString, ByteString)] -> IO [(ByteString, ByteString)])
-> IO [(ByteString, ByteString)]
forall a. (a -> a) -> a
fix ((IO [(ByteString, ByteString)] -> IO [(ByteString, ByteString)])
-> IO [(ByteString, ByteString)])
-> (IO [(ByteString, ByteString)] -> IO [(ByteString, ByteString)])
-> IO [(ByteString, ByteString)]
forall a b. (a -> b) -> a -> b
$ \IO [(ByteString, ByteString)]
go -> do
Bool
isEnd <- (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { *$(StringPairsIterator *i) == $(StringPairs *strings)->end() }|]
if Bool
isEnd
then [(ByteString, ByteString)] -> IO [(ByteString, ByteString)]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
else do
Ptr CChar
k <- [C.exp| const char*{ stringdup((*$(StringPairsIterator *i))->first) }|]
Ptr CChar
v <- [C.exp| const char*{ stringdup((*$(StringPairsIterator *i))->second) }|]
ByteString
bk <- Ptr CChar -> IO ByteString
BS.unsafePackMallocCString Ptr CChar
k
ByteString
bv <- Ptr CChar -> IO ByteString
BS.unsafePackMallocCString Ptr CChar
v
[C.block| void { (*$(StringPairsIterator *i))++; }|]
((ByteString
bk, ByteString
bv) (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. a -> [a] -> [a]
:) ([(ByteString, ByteString)] -> [(ByteString, ByteString)])
-> IO [(ByteString, ByteString)] -> IO [(ByteString, ByteString)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(ByteString, ByteString)]
go
where
withStringPairIterator :: (Ptr StringPairsIterator -> IO b) -> IO b
withStringPairIterator =
IO (Ptr StringPairsIterator)
-> (Ptr StringPairsIterator -> IO b) -> IO b
forall a b. Delete a => IO (Ptr a) -> (Ptr a -> IO b) -> IO b
withDelete
[C.exp| StringPairsIterator *{ new StringPairsIterator($(StringPairs *strings)->begin()) }|]
instance Delete C.StringPairsIterator where
delete :: Ptr StringPairsIterator -> IO ()
delete Ptr StringPairsIterator
i = [C.block| void { delete $(StringPairsIterator *i); }|]
withStrings :: (Ptr Strings -> IO a) -> IO a
withStrings :: forall a. (Ptr Strings -> IO a) -> IO a
withStrings =
IO (Ptr Strings) -> (Ptr Strings -> IO a) -> IO a
forall a b. Delete a => IO (Ptr a) -> (Ptr a -> IO b) -> IO b
withDelete
IO (Ptr Strings)
[C.exp| Strings *{ new Strings() }|]
withStringsOf :: [ByteString] -> (Ptr Strings -> IO a) -> IO a
withStringsOf :: forall a. [ByteString] -> (Ptr Strings -> IO a) -> IO a
withStringsOf [ByteString]
paths Ptr Strings -> IO a
f =
(Ptr Strings -> IO a) -> IO a
forall a. (Ptr Strings -> IO a) -> IO a
withStrings \Ptr Strings
strings -> do
[ByteString] -> (ByteString -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [ByteString]
paths (Ptr Strings -> ByteString -> IO ()
pushString Ptr Strings
strings)
Ptr Strings -> IO a
f Ptr Strings
strings
pushString :: Ptr Strings -> ByteString -> IO ()
pushString :: Ptr Strings -> ByteString -> IO ()
pushString Ptr Strings
strings ByteString
s =
[C.block| void { $(Strings *strings)->push_back($bs-cstr:s); }|]
copyClosure :: Store -> Store -> [StorePath] -> IO ()
copyClosure :: Store -> Store -> [StorePath] -> IO ()
copyClosure (Store Ptr (Ref NixStore)
src) (Store Ptr (Ref NixStore)
dest) [StorePath]
pathList = do
(StdVector ForeignPtr (CStdVector (Ptr NixStorePath))
pathsVector') <- [Ptr NixStorePath] -> IO (StdVector (Ptr NixStorePath))
forall a. HasStdVectorCopyable a => [a] -> IO (StdVector a)
Std.Vector.fromList ([StorePath]
pathList [StorePath]
-> (StorePath -> Ptr NixStorePath) -> [Ptr NixStorePath]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(StorePath ForeignPtr NixStorePath
c) -> ForeignPtr NixStorePath -> Ptr NixStorePath
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr NixStorePath
c)
ForeignPtr (CStdVector (Ptr NixStorePath))
-> (Ptr (CStdVector (Ptr NixStorePath)) -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr (CStdVector (Ptr NixStorePath))
pathsVector' \Ptr (CStdVector (Ptr NixStorePath))
pathsVector ->
[C.throwBlock| void {
ReceiveInterrupts _;
ref<Store> src = *$(refStore* src);
ref<Store> dest = *$(refStore* dest);
std::vector<nix::StorePath *> &pathsVector = *$(std::vector<nix::StorePath*>* pathsVector);
StorePathSet pathSet;
for (auto spp : pathsVector)
pathSet.insert(*spp);
StorePathSet closurePaths;
src->computeFSClosure(pathSet, closurePaths);
nix::copyPaths(*src, *dest, closurePaths);
}|]
[StorePath] -> (StorePath -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [StorePath]
pathList (\(StorePath ForeignPtr NixStorePath
c) -> ForeignPtr NixStorePath -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr NixStorePath
c)
parseSecretKey :: ByteString -> IO (ForeignPtr SecretKey)
parseSecretKey :: ByteString -> IO (ForeignPtr SecretKey)
parseSecretKey ByteString
bs =
[C.throwBlock| SecretKey* {
return new SecretKey($bs-cstr:bs);
}|]
IO (Ptr SecretKey)
-> (Ptr SecretKey -> IO (ForeignPtr SecretKey))
-> IO (ForeignPtr SecretKey)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr SecretKey -> IO (ForeignPtr SecretKey)
forall a. Finalizer a => Ptr a -> IO (ForeignPtr a)
toForeignPtr
instance Finalizer SecretKey where
finalizer :: FinalizerPtr SecretKey
finalizer = FinalizerPtr SecretKey
finalizeSecretKey
finalizeSecretKey :: FinalizerPtr SecretKey
{-# NOINLINE finalizeSecretKey #-}
finalizeSecretKey :: FinalizerPtr SecretKey
finalizeSecretKey =
IO (FinalizerPtr SecretKey) -> FinalizerPtr SecretKey
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr SecretKey)
[C.exp|
void (*)(SecretKey *) {
[](SecretKey *v) {
delete v;
}
} |]
{-# DEPRECATED finalizeSecretKey "Use 'finalizer' instead" #-}
signPath ::
Store ->
Ptr SecretKey ->
StorePath ->
IO Bool
signPath :: Store -> Ptr SecretKey -> StorePath -> IO Bool
signPath (Store Ptr (Ref NixStore)
store) Ptr SecretKey
secretKey (StorePath ForeignPtr NixStorePath
path) =
(CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
1) (CInt -> Bool) -> IO CInt -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
[C.throwBlock| int {
ReceiveInterrupts _;
nix::ref<nix::Store> store = *$(refStore *store);
const StorePath &storePath = *$fptr-ptr:(nix::StorePath *path);
const SecretKey &secretKey = *$(SecretKey *secretKey);
auto currentInfo = store->queryPathInfo(storePath);
auto info2(*currentInfo);
info2.sigs.clear();
#if NIX_IS_AT_LEAST(2, 20, 0)
{
auto signer = std::make_unique<LocalSigner>(SecretKey { secretKey });
info2.sign(*store, *signer);
}
#else
info2.sign(*store, secretKey);
#endif
assert(!info2.sigs.empty());
auto sig = *info2.sigs.begin();
if (currentInfo->sigs.count(sig)) {
return 0;
} else {
store->addSignatures(storePath, info2.sigs);
return 1;
}
}|]
followLinksToStorePath :: Store -> ByteString -> IO StorePath
followLinksToStorePath :: Store -> ByteString -> IO StorePath
followLinksToStorePath (Store Ptr (Ref NixStore)
store) ByteString
bs =
Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr NixStorePath -> IO StorePath)
-> IO (Ptr NixStorePath) -> IO StorePath
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| nix::StorePath *{
ReceiveInterrupts _;
Store &store = **$(refStore* store);
std::string s = std::string($bs-ptr:bs, $bs-len:bs);
return new StorePath(store.followLinksToStorePath(s));
}|]
isValidPath :: Store -> StorePath -> IO Bool
isValidPath :: Store -> StorePath -> IO Bool
isValidPath (Store Ptr (Ref NixStore)
store) StorePath
path =
[C.throwBlock| bool {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &path = *$fptr-ptr:(nix::StorePath *path);
return store.isValidPath(path);
}|]
IO CBool -> (CBool -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= CBool
0)
queryPathInfo ::
Store ->
StorePath ->
IO (ForeignPtr (Ref ValidPathInfo))
queryPathInfo :: Store -> StorePath -> IO (ForeignPtr (Ref ValidPathInfo))
queryPathInfo (Store Ptr (Ref NixStore)
store) (StorePath ForeignPtr NixStorePath
pathFPtr) =
ForeignPtr NixStorePath
-> (Ptr NixStorePath -> IO (ForeignPtr (Ref ValidPathInfo)))
-> IO (ForeignPtr (Ref ValidPathInfo))
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr NixStorePath
pathFPtr \Ptr NixStorePath
path -> do
Ptr (Ref ValidPathInfo)
vpi <-
[C.throwBlock| refValidPathInfo* {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &path = *$(nix::StorePath *path);
return new refValidPathInfo(store.queryPathInfo(path));
}|]
Ptr (Ref ValidPathInfo) -> IO (ForeignPtr (Ref ValidPathInfo))
forall a. Finalizer a => Ptr a -> IO (ForeignPtr a)
toForeignPtr Ptr (Ref ValidPathInfo)
vpi
queryPathInfoFromClientCache ::
Store ->
StorePath ->
IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
queryPathInfoFromClientCache :: Store
-> StorePath -> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
queryPathInfoFromClientCache (Store Ptr (Ref NixStore)
store) (StorePath ForeignPtr NixStorePath
pathFPtr) =
ForeignPtr NixStorePath
-> (Ptr NixStorePath
-> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo)))))
-> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr NixStorePath
pathFPtr \Ptr NixStorePath
path ->
#if NIX_IS_AT_LEAST(2, 20, 0)
alloca \isKnownP -> do
mvpi <- [C.throwBlock| refValidPathInfo* {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &path = *$(nix::StorePath *path);
bool &isKnown = *$(bool* isKnownP);
std::optional<std::shared_ptr<const ValidPathInfo>> maybeVPI =
store.queryPathInfoFromClientCache(path);
if (!maybeVPI) {
isKnown = false;
return nullptr;
}
else {
isKnown = true;
std::shared_ptr<const ValidPathInfo> &vpi = *maybeVPI;
if (vpi)
return new refValidPathInfo(vpi);
else
return nullptr;
}
}|]
isKnown <- peek isKnownP <&> (/= 0)
for (guard isKnown) \_ -> do
mvpi & traverseNonNull toForeignPtr
#else
(Ptr CBool -> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo)))))
-> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca \Ptr CBool
isKnownP -> do
Ptr (Ref ValidPathInfo)
mvpi <- [C.throwBlock| refValidPathInfo* {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePath &path = *$(nix::StorePath *path);
bool &isKnown = *$(bool* isKnownP);
std::string uri = store.getUri();
ref<NarInfoDiskCache> cache = nix::getNarInfoDiskCache();
// std::pair<nix::NarInfoDiskCache::Outcome, std::shared_ptr<NarInfo>>
auto [outcome, maybeNarInfo] =
cache->lookupNarInfo(uri, std::string(path.hashPart()));
if (outcome == nix::NarInfoDiskCache::oValid) {
assert(maybeNarInfo);
isKnown = true;
return new refValidPathInfo(maybeNarInfo);
}
else if (outcome == nix::NarInfoDiskCache::oInvalid) {
isKnown = true;
return nullptr;
}
else {
// nix::NarInfoDiskCache::oUnknown or unexpected value
isKnown = false;
return nullptr;
}
}|]
Bool
isKnown <- Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek Ptr CBool
isKnownP IO CBool -> (CBool -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= CBool
0)
Maybe ()
-> (() -> IO (Maybe (ForeignPtr (Ref ValidPathInfo))))
-> IO (Maybe (Maybe (ForeignPtr (Ref ValidPathInfo))))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
isKnown) \()
_ -> do
Ptr (Ref ValidPathInfo)
mvpi Ptr (Ref ValidPathInfo)
-> (Ptr (Ref ValidPathInfo)
-> IO (Maybe (ForeignPtr (Ref ValidPathInfo))))
-> IO (Maybe (ForeignPtr (Ref ValidPathInfo)))
forall a b. a -> (a -> b) -> b
& (Ptr (Ref ValidPathInfo) -> IO (ForeignPtr (Ref ValidPathInfo)))
-> Ptr (Ref ValidPathInfo)
-> IO (Maybe (ForeignPtr (Ref ValidPathInfo)))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
traverseNonNull Ptr (Ref ValidPathInfo) -> IO (ForeignPtr (Ref ValidPathInfo))
forall a. Finalizer a => Ptr a -> IO (ForeignPtr a)
toForeignPtr
#endif
instance Finalizer (Ref ValidPathInfo) where
finalizer :: FinalizerPtr (Ref ValidPathInfo)
finalizer = FinalizerPtr (Ref ValidPathInfo)
finalizeRefValidPathInfo
finalizeRefValidPathInfo :: FinalizerPtr (Ref ValidPathInfo)
{-# NOINLINE finalizeRefValidPathInfo #-}
finalizeRefValidPathInfo :: FinalizerPtr (Ref ValidPathInfo)
finalizeRefValidPathInfo =
IO (FinalizerPtr (Ref ValidPathInfo))
-> FinalizerPtr (Ref ValidPathInfo)
forall a. IO a -> a
unsafePerformIO
IO (FinalizerPtr (Ref ValidPathInfo))
[C.exp|
void (*)(refValidPathInfo *) {
[](refValidPathInfo *v){ delete v; }
}|]
{-# DEPRECATED finalizeRefValidPathInfo "Use 'finalizer' instead" #-}
validPathInfoNarSize :: ForeignPtr (Ref ValidPathInfo) -> Int64
validPathInfoNarSize :: ForeignPtr (Ref ValidPathInfo) -> Int64
validPathInfoNarSize ForeignPtr (Ref ValidPathInfo)
vpi =
Integer -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Int64) -> Integer -> Int64
forall a b. (a -> b) -> a -> b
$
CLong -> Integer
forall a. Integral a => a -> Integer
toInteger
[C.pure| long
{ (*$fptr-ptr:(refValidPathInfo* vpi))->narSize }
|]
validPathInfoNarHash32 :: ForeignPtr (Ref ValidPathInfo) -> IO ByteString
validPathInfoNarHash32 :: ForeignPtr (Ref ValidPathInfo) -> IO ByteString
validPathInfoNarHash32 ForeignPtr (Ref ValidPathInfo)
vpi =
Ptr CChar -> IO ByteString
unsafePackMallocCString
(Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.block| const char *{
#if NIX_IS_AT_LEAST(2,20,0)
std::string s((*$fptr-ptr:(refValidPathInfo* vpi))->narHash.to_string(nix::HashFormat::Nix32, true));
#elif NIX_IS_AT_LEAST(2,19,0)
std::string s((*$fptr-ptr:(refValidPathInfo* vpi))->narHash.to_string(nix::HashFormat::Base32, true));
#else
std::string s((*$fptr-ptr:(refValidPathInfo* vpi))->narHash.to_string(nix::Base32, true));
#endif
return stringdup(s);
}|]
validPathInfoDeriver :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
validPathInfoDeriver :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
validPathInfoDeriver Store
_ = ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
validPathInfoDeriver'
validPathInfoDeriver' :: ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
validPathInfoDeriver' :: ForeignPtr (Ref ValidPathInfo) -> IO (Maybe StorePath)
validPathInfoDeriver' ForeignPtr (Ref ValidPathInfo)
vpi =
Ptr NixStorePath -> IO (Maybe StorePath)
forall a b. HasEncapsulation a b => Ptr a -> IO (Maybe b)
nullableMoveToForeignPtrWrapper
(Ptr NixStorePath -> IO (Maybe StorePath))
-> IO (Ptr NixStorePath) -> IO (Maybe StorePath)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| nix::StorePath * {
std::optional<StorePath> deriver = (*$fptr-ptr:(refValidPathInfo* vpi))->deriver;
return deriver ? new StorePath(*deriver) : nullptr;
}|]
validPathInfoReferences :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
validPathInfoReferences :: Store -> ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
validPathInfoReferences Store
_ = ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
validPathInfoReferences'
validPathInfoReferences' :: ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
validPathInfoReferences' :: ForeignPtr (Ref ValidPathInfo) -> IO [StorePath]
validPathInfoReferences' ForeignPtr (Ref ValidPathInfo)
vpi = do
StdVector (Ptr NixStorePath)
sps <-
Ptr (CStdVector (Ptr NixStorePath))
-> IO (StdVector (Ptr NixStorePath))
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
(Ptr (CStdVector (Ptr NixStorePath))
-> IO (StdVector (Ptr NixStorePath)))
-> IO (Ptr (CStdVector (Ptr NixStorePath)))
-> IO (StdVector (Ptr NixStorePath))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [C.throwBlock| std::vector<nix::StorePath *>* {
auto sps = new std::vector<nix::StorePath *>();
for (auto sp : (*$fptr-ptr:(refValidPathInfo* vpi))->references)
sps->push_back(new StorePath(sp));
return sps;
}|]
[Ptr NixStorePath]
l <- StdVector (Ptr NixStorePath) -> IO [Ptr NixStorePath]
forall a.
(HasStdVectorCopyable a, Storable a) =>
StdVector a -> IO [a]
Std.Vector.toList StdVector (Ptr NixStorePath)
sps
[Ptr NixStorePath]
-> (Ptr NixStorePath -> IO StorePath) -> IO [StorePath]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Ptr NixStorePath]
l Ptr NixStorePath -> IO StorePath
forall a b. HasEncapsulation a b => Ptr a -> IO b
moveToForeignPtrWrapper
data ClosureParams = ClosureParams
{ ClosureParams -> Bool
flipDirection :: Bool,
ClosureParams -> Bool
includeOutputs :: Bool,
ClosureParams -> Bool
includeDerivers :: Bool
}
defaultClosureParams :: ClosureParams
defaultClosureParams :: ClosureParams
defaultClosureParams =
ClosureParams
{ flipDirection :: Bool
flipDirection = Bool
False,
includeOutputs :: Bool
includeOutputs = Bool
False,
includeDerivers :: Bool
includeDerivers = Bool
False
}
computeFSClosure :: Store -> ClosureParams -> StdSet NixStorePath -> IO (StdSet NixStorePath)
computeFSClosure :: Store
-> ClosureParams -> StdSet NixStorePath -> IO (StdSet NixStorePath)
computeFSClosure (Store Ptr (Ref NixStore)
store) ClosureParams
params (Std.Set.StdSet ForeignPtr (CStdSet NixStorePath)
startingSet) = do
let countTrue :: Bool -> C.CInt
countTrue :: Bool -> CInt
countTrue Bool
True = CInt
1
countTrue Bool
False = CInt
0
flipDir :: CInt
flipDir = Bool -> CInt
countTrue (Bool -> CInt) -> Bool -> CInt
forall a b. (a -> b) -> a -> b
$ ClosureParams -> Bool
flipDirection ClosureParams
params
inclOut :: CInt
inclOut = Bool -> CInt
countTrue (Bool -> CInt) -> Bool -> CInt
forall a b. (a -> b) -> a -> b
$ ClosureParams -> Bool
includeOutputs ClosureParams
params
inclDrv :: CInt
inclDrv = Bool -> CInt
countTrue (Bool -> CInt) -> Bool -> CInt
forall a b. (a -> b) -> a -> b
$ ClosureParams -> Bool
includeDerivers ClosureParams
params
ret :: StdSet NixStorePath
ret@(Std.Set.StdSet ForeignPtr (CStdSet NixStorePath)
retSet) <- IO (StdSet NixStorePath)
forall a. HasStdSet a => IO (StdSet a)
Std.Set.new
[C.throwBlock| void {
ReceiveInterrupts _;
Store &store = **$(refStore* store);
StorePathSet &ret = *$fptr-ptr:(std::set<nix::StorePath>* retSet);
store.computeFSClosure(*$fptr-ptr:(std::set<nix::StorePath>* startingSet), ret,
$(int flipDir), $(int inclOut), $(int inclDrv));
}|]
StdSet NixStorePath -> IO (StdSet NixStorePath)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StdSet NixStorePath
ret
withPtr' :: (Coercible a' (ForeignPtr a)) => a' -> (Ptr a -> IO b) -> IO b
withPtr' :: forall a' a b.
Coercible a' (ForeignPtr a) =>
a' -> (Ptr a -> IO b) -> IO b
withPtr' a'
p = ForeignPtr a -> (Ptr a -> IO b) -> IO b
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (a' -> ForeignPtr a
forall a b. Coercible a b => a -> b
coerce a'
p)
{-# DEPRECATED withPtr' "Use 'HasEncapsulation' instead" #-}