Skip to content

Commit 4777b21

Browse files
authored
Merge pull request #279 from squalus/narfrompath
remote: add NarFromPath client
2 parents b57f69b + 5225bb5 commit 4777b21

File tree

11 files changed

+151
-6
lines changed

11 files changed

+151
-6
lines changed

hnix-store-remote/hnix-store-remote.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -196,7 +196,8 @@ test-suite remote-io
196196
-- See https://github.com/redneb/hs-linux-namespaces/issues/3
197197
ghc-options: -rtsopts -fprof-auto "-with-rtsopts -V0"
198198
other-modules:
199-
NixDaemonSpec
199+
DataSink
200+
, NixDaemonSpec
200201
, SampleNar
201202
build-depends:
202203
base >=4.12 && <5

hnix-store-remote/src/System/Nix/Store/Remote/Arbitrary.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,7 @@ instance Arbitrary (Some StoreRequest) where
106106
, Some . EnsurePath <$> arbitrary
107107
, pure $ Some FindRoots
108108
, Some . IsValidPath <$> arbitrary
109+
, Some . NarFromPath <$> arbitrary
109110
, Some <$> (QueryValidPaths <$> arbitrary <*> arbitrary)
110111
, pure $ Some QueryAllValidPaths
111112
, Some . QuerySubstitutablePaths <$> arbitrary

hnix-store-remote/src/System/Nix/Store/Remote/Client.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module System.Nix.Store.Remote.Client
1111
, ensurePath
1212
, findRoots
1313
, isValidPath
14+
, narFromPath
1415
, queryValidPaths
1516
, queryAllValidPaths
1617
, querySubstitutablePaths
@@ -181,6 +182,18 @@ isValidPath
181182
-> m Bool
182183
isValidPath = doReq . IsValidPath
183184

185+
-- | Download a NAR file.
186+
narFromPath
187+
:: MonadRemoteStore m
188+
=> StorePath -- ^ Path to generate a NAR for
189+
-> Word64 -- ^ Byte length of NAR
190+
-> (ByteString -> IO()) -- ^ Data sink where NAR bytes will be written
191+
-> m ()
192+
narFromPath path narSize sink = do
193+
setDataSink sink
194+
setDataSinkSize narSize
195+
void $ doReq (NarFromPath path)
196+
184197
-- | Query valid paths from a set,
185198
-- optionally try to use substitutes
186199
queryValidPaths

hnix-store-remote/src/System/Nix/Store/Remote/Client/Core.hs

Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -91,6 +91,22 @@ doReq = \case
9191
processOutput
9292
pure NoReply
9393

94+
NarFromPath _ -> do
95+
maybeSink <- getDataSink
96+
sink <- case maybeSink of
97+
Nothing -> throwError RemoteStoreError_NoDataSinkProvided
98+
Just sink -> pure sink
99+
clearDataSink
100+
maybeNarSize <- getDataSinkSize
101+
narSize <- case maybeNarSize of
102+
Nothing -> throwError RemoteStoreError_NoDataSinkSizeProvided
103+
Just narSize -> pure narSize
104+
clearDataSinkSize
105+
soc <- getStoreSocket
106+
processOutput
107+
copyToSink sink narSize soc
108+
pure NoReply
109+
94110
_ -> do
95111
processOutput
96112
processReply
@@ -101,6 +117,24 @@ doReq = \case
101117
$ getReplyS @a
102118
)
103119

120+
copyToSink
121+
:: forall m
122+
. ( MonadIO m
123+
, MonadRemoteStore m
124+
)
125+
=> (ByteString -> IO()) -- ^ data sink
126+
-> Word64 -- ^ byte length to read
127+
-> Socket
128+
-> m ()
129+
copyToSink sink remainingBytes soc =
130+
when (remainingBytes > 0) $ do
131+
let chunkSize = 16384
132+
bytesToRead = min chunkSize remainingBytes
133+
bytes <- liftIO $ Network.Socket.ByteString.recv soc (fromIntegral bytesToRead)
134+
liftIO $ sink bytes
135+
let nextRemainingBytes = remainingBytes - (fromIntegral . Data.ByteString.length) bytes
136+
copyToSink sink nextRemainingBytes soc
137+
104138
writeFramedSource
105139
:: forall m
106140
. ( MonadIO m

hnix-store-remote/src/System/Nix/Store/Remote/MonadStore.hs

Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ data RemoteStoreState = RemoteStoreState {
4747
, remoteStoreStateMDataSink :: Maybe (ByteString -> IO ())
4848
-- ^ Sink for @Logger_Write@, called repeatedly by the daemon
4949
-- to dump us some data. Used by @ExportPath@ operation.
50+
, remoteStoreStateMDataSinkSize :: Maybe Word64
51+
-- ^ Byte length to be written to the sink, for NarForPath
5052
, remoteStoreStateMNarSource :: Maybe (NarSource IO)
5153
}
5254

@@ -80,6 +82,7 @@ data RemoteStoreError
8082
| RemoteStoreError_DataSourceZeroLengthRead -- remoteStoreStateMDataSource returned a zero length ByteString
8183
| RemoteStoreError_DataSourceReadTooLarge -- remoteStoreStateMDataSource returned a ByteString larger than the chunk size requested or the remaining bytes
8284
| RemoteStoreError_NoDataSinkProvided -- remoteStoreStateMDataSink is required but it is Nothing
85+
| RemoteStoreError_NoDataSinkSizeProvided -- remoteStoreStateMDataSinkSize is required but it is Nothing
8386
| RemoteStoreError_NoNarSourceProvided
8487
| RemoteStoreError_OperationFailed
8588
| RemoteStoreError_ProtocolMismatch
@@ -148,6 +151,7 @@ runRemoteStoreT sock =
148151
, remoteStoreStateLogs = mempty
149152
, remoteStoreStateMDataSource = Nothing
150153
, remoteStoreStateMDataSink = Nothing
154+
, remoteStoreStateMDataSinkSize = Nothing
151155
, remoteStoreStateMNarSource = Nothing
152156
}
153157

@@ -307,6 +311,34 @@ class ( MonadIO m
307311
=> m ()
308312
clearDataSink = lift clearDataSink
309313

314+
setDataSinkSize :: Word64 -> m ()
315+
default setDataSinkSize
316+
:: ( MonadTrans t
317+
, MonadRemoteStore m'
318+
, m ~ t m'
319+
)
320+
=> Word64
321+
-> m ()
322+
setDataSinkSize x = lift (setDataSinkSize x)
323+
324+
getDataSinkSize :: m (Maybe Word64)
325+
default getDataSinkSize
326+
:: ( MonadTrans t
327+
, MonadRemoteStore m'
328+
, m ~ t m'
329+
)
330+
=> m (Maybe Word64)
331+
getDataSinkSize = lift getDataSinkSize
332+
333+
clearDataSinkSize :: m ()
334+
default clearDataSinkSize
335+
:: ( MonadTrans t
336+
, MonadRemoteStore m'
337+
, m ~ t m'
338+
)
339+
=> m ()
340+
clearDataSinkSize = lift clearDataSinkSize
341+
310342
instance MonadRemoteStore m => MonadRemoteStore (StateT s m)
311343
instance MonadRemoteStore m => MonadRemoteStore (ReaderT r m)
312344
instance MonadRemoteStore m => MonadRemoteStore (ExceptT RemoteStoreError m)
@@ -347,6 +379,10 @@ instance MonadIO m => MonadRemoteStore (RemoteStoreT m) where
347379
getDataSink = RemoteStoreT (gets remoteStoreStateMDataSink)
348380
clearDataSink = RemoteStoreT $ modify $ \s -> s { remoteStoreStateMDataSink = Nothing }
349381

382+
setDataSinkSize x = RemoteStoreT $ modify $ \s -> s { remoteStoreStateMDataSinkSize = pure x }
383+
getDataSinkSize = RemoteStoreT (gets remoteStoreStateMDataSinkSize)
384+
clearDataSinkSize = RemoteStoreT $ modify $ \s -> s { remoteStoreStateMDataSinkSize = Nothing }
385+
350386
setNarSource x = RemoteStoreT $ modify $ \s -> s { remoteStoreStateMNarSource = pure x }
351387
takeNarSource = RemoteStoreT $ do
352388
x <- remoteStoreStateMNarSource <$> get

hnix-store-remote/src/System/Nix/Store/Remote/Serializer.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1135,6 +1135,9 @@ storeRequest = Serializer
11351135
WorkerOp_IsValidPath -> mapGetE $ do
11361136
Some . IsValidPath <$> getS storePath
11371137

1138+
WorkerOp_NarFromPath -> mapGetE $ do
1139+
Some . NarFromPath <$> getS storePath
1140+
11381141
WorkerOp_QueryValidPaths -> mapGetE $ do
11391142
paths <- getS (hashSet storePath)
11401143
substituteMode <- getS enum
@@ -1191,7 +1194,6 @@ storeRequest = Serializer
11911194
w@WorkerOp_ExportPath -> notYet w
11921195
w@WorkerOp_HasSubstitutes -> notYet w
11931196
w@WorkerOp_ImportPaths -> notYet w
1194-
w@WorkerOp_NarFromPath -> notYet w
11951197
w@WorkerOp_QueryDerivationOutputMap -> notYet w
11961198
w@WorkerOp_QueryDeriver -> notYet w
11971199
w@WorkerOp_QueryFailedPaths -> notYet w
@@ -1280,6 +1282,10 @@ storeRequest = Serializer
12801282
putS workerOp WorkerOp_IsValidPath
12811283
putS storePath path
12821284

1285+
Some (NarFromPath path) -> mapPutE $ do
1286+
putS workerOp WorkerOp_NarFromPath
1287+
putS storePath path
1288+
12831289
Some (QueryValidPaths paths substituteMode) -> mapPutE $ do
12841290
putS workerOp WorkerOp_QueryValidPaths
12851291

hnix-store-remote/src/System/Nix/Store/Remote/Server.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -181,6 +181,7 @@ processConnection workerHelper postGreet sock = do
181181
r@EnsurePath {} -> perform r
182182
r@FindRoots {} -> perform r
183183
r@IsValidPath {} -> perform r
184+
r@NarFromPath {} -> perform r
184185
r@QueryValidPaths {} -> perform r
185186
r@QueryAllValidPaths {} -> perform r
186187
r@QuerySubstitutablePaths {} -> perform r

hnix-store-remote/src/System/Nix/Store/Remote/Types/StoreRequest.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,11 @@ data StoreRequest :: Type -> Type where
104104
:: StorePath
105105
-> StoreRequest Bool
106106

107+
-- | Fetch a NAR from the server
108+
NarFromPath
109+
:: StorePath
110+
-> StoreRequest NoReply
111+
107112
-- | Query valid paths from set, optionally try to use substitutes.
108113
QueryValidPaths
109114
:: HashSet StorePath
@@ -179,6 +184,7 @@ instance {-# OVERLAPPING #-} Eq (Some StoreRequest) where
179184
Some (EnsurePath a) == Some (EnsurePath a') = a == a'
180185
Some (FindRoots) == Some (FindRoots) = True
181186
Some (IsValidPath a) == Some (IsValidPath a') = a == a'
187+
Some (NarFromPath a) == Some (NarFromPath a') = a == a'
182188
Some (QueryValidPaths a b) == Some (QueryValidPaths a' b') = (a, b) == (a', b')
183189
Some QueryAllValidPaths == Some QueryAllValidPaths = True
184190
Some (QuerySubstitutablePaths a) == Some (QuerySubstitutablePaths a') = a == a'
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
module DataSink
2+
3+
( DataSink(..)
4+
, dataSinkResult
5+
, dataSinkWriter
6+
, newDataSink
7+
)
8+
9+
where
10+
11+
import Data.ByteString (ByteString)
12+
13+
import Control.Monad.ST
14+
import Data.STRef
15+
16+
-- | Basic data sink for testing
17+
newtype DataSink = DataSink (STRef RealWorld ByteString)
18+
19+
newDataSink :: IO DataSink
20+
newDataSink = DataSink <$> (stToIO . newSTRef) mempty
21+
22+
dataSinkWriter :: DataSink -> (ByteString -> IO())
23+
dataSinkWriter (DataSink stref) chunk = stToIO (modifySTRef stref (chunk <>))
24+
25+
dataSinkResult :: DataSink -> IO ByteString
26+
dataSinkResult (DataSink stref) = (stToIO . readSTRef) stref

hnix-store-remote/tests-io/NixDaemonSpec.hs

Lines changed: 21 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23

34
module NixDaemonSpec
45
( enterNamespaces
@@ -35,6 +36,7 @@ import qualified Data.Map
3536
import qualified Data.Set
3637
import qualified Data.Text
3738
import qualified Data.Text.Encoding
39+
import qualified DataSink
3840
import qualified SampleNar
3941
import qualified System.Directory
4042
import qualified System.Environment
@@ -264,6 +266,9 @@ itLefts
264266
-> SpecWith (m () -> IO (Either a b, c))
265267
itLefts name action = it name action Data.Either.isLeft
266268

269+
sampleText :: Text
270+
sampleText = "test"
271+
267272
withPath
268273
:: MonadRemoteStore m
269274
=> (StorePath -> m a)
@@ -273,7 +278,7 @@ withPath action = do
273278
addTextToStore
274279
(StoreText
275280
(forceRight $ System.Nix.StorePath.mkStorePathName "hnix-store")
276-
"test"
281+
sampleText
277282
)
278283
mempty
279284
RepairMode_DontRepair
@@ -341,6 +346,7 @@ makeProtoSpec
341346
-> SpecFlavor
342347
-> Spec
343348
makeProtoSpec f flavor = around f $ do
349+
344350
context "syncWithGC" $
345351
itRights "syncs with garbage collector" syncWithGC
346352

@@ -499,3 +505,17 @@ makeProtoSpec f flavor = around f $ do
499505

500506
meta <- queryPathInfo sampleNar_storePath
501507
(metadataDeriverPath =<< meta) `shouldBe` metadataDeriverPath sampleNar_metadata
508+
509+
context "narFromPath" $ do
510+
itRights "downloads nar file" $ do
511+
unless (flavor == SpecFlavor_MITM) $ do
512+
withPath $ \path -> do
513+
maybeMetadata <- queryPathInfo path
514+
case maybeMetadata of
515+
Just Metadata{metadataNarBytes=Just narBytes} -> do
516+
dataSink <- liftIO DataSink.newDataSink
517+
narFromPath path narBytes (DataSink.dataSinkWriter dataSink)
518+
narData <- liftIO $ DataSink.dataSinkResult dataSink
519+
expectedNarData <- liftIO $ SampleNar.encodeNar (Data.Text.Encoding.encodeUtf8 sampleText)
520+
narData `shouldBe` expectedNarData
521+
_ -> expectationFailure "missing metadata or narBytes"

0 commit comments

Comments
 (0)