@@ -11,7 +11,7 @@ import Control.Monad.IO.Class (MonadIO, liftIO)
1111import Crypto.Hash (SHA256 )
1212import Data.Some (Some (Some ))
1313import Data.Text (Text )
14- import Test.Hspec (Spec , SpecWith , around , describe , context )
14+ import Test.Hspec (ActionWith , Spec , SpecWith , around , describe , context )
1515import Test.Hspec.Expectations.Lifted
1616import Test.Hspec.Nix (forceRight )
1717import System.FilePath ((</>) )
@@ -44,14 +44,13 @@ import qualified Test.Hspec
4444
4545createProcessEnv
4646 :: FilePath
47- -> String
48- -> [String ]
47+ -> CreateProcess
4948 -> IO ProcessHandle
50- createProcessEnv fp proc args = do
49+ createProcessEnv fp cp = do
5150 mPath <- System.Environment. lookupEnv " PATH"
5251
5352 (_, _, _, ph) <-
54- System.Process. createProcess ( System.Process. proc proc args)
53+ System.Process. createProcess cp
5554 { cwd = Just fp
5655 , env = Just $ mockedEnv mPath fp
5756 }
@@ -112,7 +111,12 @@ startDaemon
112111 -> IO (ProcessHandle , RemoteStoreT m a -> Run m a )
113112startDaemon fp = do
114113 writeConf (fp </> " etc" </> " nix.conf" )
115- procHandle <- createProcessEnv fp " nix-daemon" []
114+ procHandle <-
115+ createProcessEnv
116+ fp
117+ $ System.Process. shell
118+ " nix-daemon 2>&1 | grep -v 'accepted connection'"
119+
116120 waitSocket sockFp 30
117121 pure ( procHandle
118122 , runStoreConnection (StoreConnection_Socket (StoreSocketPath sockFp))
@@ -160,7 +164,13 @@ withNixDaemon action =
160164 ((/= " NIX_REMOTE" ) . fst )
161165 $ mockedEnv Nothing path)
162166
163- ini <- createProcessEnv path " nix-store" [" --init" ]
167+ ini <-
168+ createProcessEnv
169+ path
170+ $ System.Process. shell
171+ -- see long note above @startDaemon@
172+ " nix-store --init 2>&1 | grep -v 'error: changing ownership'"
173+
164174 void $ System.Process. waitForProcess ini
165175
166176 writeFile (path </> " dummy" ) " Hello World"
@@ -254,7 +264,10 @@ _withBuilder
254264_withBuilder action = do
255265 path <-
256266 addTextToStore
257- (StoreText (forceRight $ System.Nix.StorePath. mkStorePathName " builder" ) builderSh)
267+ (StoreText
268+ (forceRight $ System.Nix.StorePath. mkStorePathName " builder" )
269+ builderSh
270+ )
258271 mempty
259272 RepairMode_DontRepair
260273 action path
@@ -263,138 +276,145 @@ builderSh :: Text
263276builderSh = " declare -xpexport > $out"
264277
265278spec :: Spec
266- spec = around withNixDaemon $
267-
268- describe " store" $ do
269-
270- context " syncWithGC" $
271- itRights " syncs with garbage collector" syncWithGC
272-
273- context " verifyStore" $ do
274- itRights " check=False repair=False" $
275- verifyStore
276- CheckMode_DontCheck
277- RepairMode_DontRepair
278- `shouldReturn` False
279-
280- itRights " check=True repair=False" $
281- verifyStore
282- CheckMode_DoCheck
283- RepairMode_DontRepair
284- `shouldReturn` False
285-
286- -- privileged
287- itRights " check=True repair=True" $
288- verifyStore
289- CheckMode_DoCheck
290- RepairMode_DoRepair
291- `shouldReturn` False
292-
293- context " addTextToStore" $
294- itRights " adds text to store" $ withPath pure
295-
296- context " isValidPath" $ do
297- itRights " validates path" $ withPath $ \ path -> do
298- liftIO $ print path
299- isValidPath path `shouldReturn` True
300- itLefts " fails on invalid path" $ do
301- setStoreDir (StoreDir " /asdf" )
302- isValidPath invalidPath
303-
304- context " queryAllValidPaths" $ do
305- itRights " empty query" queryAllValidPaths
306- itRights " non-empty query" $ withPath $ \ path ->
307- queryAllValidPaths `shouldReturn` Data.HashSet. fromList [path]
308-
309- context " queryPathInfo" $
310- itRights " queries path info" $ withPath $ \ path -> do
311- meta <- queryPathInfo path
312- (metadataReferences <$> meta) `shouldBe` (Just mempty )
313-
314- context " ensurePath" $
315- itRights " simple ensure" $ withPath ensurePath
316-
317- context " addTempRoot" $
318- itRights " simple addition" $ withPath addTempRoot
319-
320- context " addIndirectRoot" $
321- itRights " simple addition" $ withPath addIndirectRoot
322-
323- let toDerivedPathSet p = Data.Set. fromList [DerivedPath_Opaque p]
324-
325- context " buildPaths" $ do
326- itRights " build Normal" $ withPath $ \ path -> do
327- buildPaths (toDerivedPathSet path) BuildMode_Normal
328-
329- itRights " build Check" $ withPath $ \ path -> do
330- buildPaths (toDerivedPathSet path) BuildMode_Check
331-
332- itLefts " build Repair" $ withPath $ \ path -> do
333- buildPaths (toDerivedPathSet path) BuildMode_Repair
334-
335- context " roots" $ context " findRoots" $ do
336- itRights " empty roots" (findRoots `shouldReturn` mempty )
337-
338- itRights " path added as a temp root" $ withPath $ \ _ -> do
339- roots <- findRoots
340- roots `shouldSatisfy` ((== 1 ) . Data.Map. size)
341-
342- context " optimiseStore" $ itRights " optimises" optimiseStore
343-
344- context " queryMissing" $
345- itRights " queries" $ withPath $ \ path -> do
346- queryMissing (toDerivedPathSet path)
347- `shouldReturn`
348- Missing
349- { missingWillBuild = mempty
350- , missingWillSubstitute = mempty
351- , missingUnknownPaths = mempty
352- , missingDownloadSize = 0
353- , missingNarSize = 0
354- }
355-
356- context " addToStore" $
357- itRights " adds file to store" $ do
358- fp <-
279+ spec = do
280+ describe " Remote store protocol" $ do
281+ describe " Direct" $ makeProtoSpec withNixDaemon
282+
283+ makeProtoSpec
284+ :: (ActionWith
285+ (RemoteStoreT IO () -> Run IO () )
286+ -> IO ()
287+ )
288+ -> Spec
289+ makeProtoSpec f = around f $ do
290+ context " syncWithGC" $
291+ itRights " syncs with garbage collector" syncWithGC
292+
293+ context " verifyStore" $ do
294+ itRights " check=False repair=False" $
295+ verifyStore
296+ CheckMode_DontCheck
297+ RepairMode_DontRepair
298+ `shouldReturn` False
299+
300+ itRights " check=True repair=False" $
301+ verifyStore
302+ CheckMode_DoCheck
303+ RepairMode_DontRepair
304+ `shouldReturn` False
305+
306+ -- privileged
307+ itRights " check=True repair=True" $
308+ verifyStore
309+ CheckMode_DoCheck
310+ RepairMode_DoRepair
311+ `shouldReturn` False
312+
313+ context " addTextToStore" $
314+ itRights " adds text to store" $ withPath pure
315+
316+ context " isValidPath" $ do
317+ itRights " validates path" $ withPath $ \ path -> do
318+ isValidPath path `shouldReturn` True
319+
320+ itLefts " fails on invalid path" $ do
321+ setStoreDir (StoreDir " /asdf" )
322+ isValidPath invalidPath
323+
324+ context " queryAllValidPaths" $ do
325+ itRights " empty query" queryAllValidPaths
326+ itRights " non-empty query" $ withPath $ \ path ->
327+ queryAllValidPaths `shouldReturn` Data.HashSet. fromList [path]
328+
329+ context " queryPathInfo" $
330+ itRights " queries path info" $ withPath $ \ path -> do
331+ meta <- queryPathInfo path
332+ (metadataReferences <$> meta) `shouldBe` (Just mempty )
333+
334+ context " ensurePath" $
335+ itRights " simple ensure" $ withPath ensurePath
336+
337+ context " addTempRoot" $
338+ itRights " simple addition" $ withPath addTempRoot
339+
340+ context " addIndirectRoot" $
341+ itRights " simple addition" $ withPath addIndirectRoot
342+
343+ let toDerivedPathSet p = Data.Set. fromList [DerivedPath_Opaque p]
344+
345+ context " buildPaths" $ do
346+ itRights " build Normal" $ withPath $ \ path -> do
347+ buildPaths (toDerivedPathSet path) BuildMode_Normal
348+
349+ itRights " build Check" $ withPath $ \ path -> do
350+ buildPaths (toDerivedPathSet path) BuildMode_Check
351+
352+ itLefts " build Repair" $ withPath $ \ path -> do
353+ buildPaths (toDerivedPathSet path) BuildMode_Repair
354+
355+ context " roots" $ context " findRoots" $ do
356+ itRights " empty roots" (findRoots `shouldReturn` mempty )
357+
358+ itRights " path added as a temp root" $ withPath $ \ _ -> do
359+ roots <- findRoots
360+ roots `shouldSatisfy` ((== 1 ) . Data.Map. size)
361+
362+ context " optimiseStore" $ itRights " optimises" optimiseStore
363+
364+ context " queryMissing" $
365+ itRights " queries" $ withPath $ \ path -> do
366+ queryMissing (toDerivedPathSet path)
367+ `shouldReturn`
368+ Missing
369+ { missingWillBuild = mempty
370+ , missingWillSubstitute = mempty
371+ , missingUnknownPaths = mempty
372+ , missingDownloadSize = 0
373+ , missingNarSize = 0
374+ }
375+
376+ context " addToStore" $
377+ itRights " adds file to store" $ do
378+ fp <-
379+ liftIO
380+ $ System.IO.Temp. writeSystemTempFile
381+ " addition"
382+ " yolo"
383+
384+ addToStore
385+ (forceRight $ System.Nix.StorePath. mkStorePathName " tmp-addition" )
386+ (System.Nix.Nar. dumpPath fp)
387+ FileIngestionMethod_Flat
388+ (Some HashAlgo_SHA256 )
389+ RepairMode_DontRepair
390+
391+ context " with dummy" $ do
392+ itRights " adds dummy" dummy
393+
394+ itRights " valid dummy" $ do
395+ path <- dummy
396+ isValidPath path `shouldReturn` True
397+
398+ context " collectGarbage" $ do
399+ itRights " deletes a specific path from the store" $ withPath $ \ path -> do
400+ -- clear temp gc roots so the delete works. restarting the nix daemon should also do this...
401+ storeDir <- getStoreDir
402+ let tempRootsDir = Data.Text. unpack $ mconcat [ Data.Text.Encoding. decodeUtf8 (unStoreDir storeDir), " /../var/nix/temproots/" ]
403+ tempRootList <-
359404 liftIO
360- $ System.IO.Temp. writeSystemTempFile
361- " addition"
362- " yolo"
363-
364- addToStore
365- (forceRight $ System.Nix.StorePath. mkStorePathName " tmp-addition" )
366- (System.Nix.Nar. dumpPath fp)
367- FileIngestionMethod_Flat
368- (Some HashAlgo_SHA256 )
369- RepairMode_DontRepair
370-
371- context " with dummy" $ do
372- itRights " adds dummy" dummy
373-
374- itRights " valid dummy" $ do
375- path <- dummy
376- isValidPath path `shouldReturn` True
377-
378- context " collectGarbage" $ do
379- itRights " delete a specific path from the store" $ withPath $ \ path -> do
380- -- clear temp gc roots so the delete works. restarting the nix daemon should also do this...
381- storeDir <- getStoreDir
382- let tempRootsDir = Data.Text. unpack $ mconcat [ Data.Text.Encoding. decodeUtf8 (unStoreDir storeDir), " /../var/nix/temproots/" ]
383- tempRootList <-
384- liftIO
385- $ System.Directory. listDirectory
386- tempRootsDir
387- liftIO $ forM_ tempRootList $ \ entry -> do
388- System.Directory. removeFile
389- $ mconcat [ tempRootsDir, " /" , entry ]
390-
391- GCResult {.. } <-
392- collectGarbage
393- GCOptions
394- { gcOptionsOperation = GCAction_DeleteSpecific
395- , gcOptionsIgnoreLiveness = False
396- , gcOptionsPathsToDelete = Data.HashSet. fromList [path]
397- , gcOptionsMaxFreed = maxBound
398- }
399- gcResultDeletedPaths `shouldBe` Data.HashSet. fromList [path]
400- gcResultBytesFreed `shouldBe` 4
405+ $ System.Directory. listDirectory
406+ tempRootsDir
407+ liftIO $ forM_ tempRootList $ \ entry -> do
408+ System.Directory. removeFile
409+ $ mconcat [ tempRootsDir, " /" , entry ]
410+
411+ GCResult {.. } <-
412+ collectGarbage
413+ GCOptions
414+ { gcOptionsOperation = GCAction_DeleteSpecific
415+ , gcOptionsIgnoreLiveness = False
416+ , gcOptionsPathsToDelete = Data.HashSet. fromList [path]
417+ , gcOptionsMaxFreed = maxBound
418+ }
419+ gcResultDeletedPaths `shouldBe` Data.HashSet. fromList [path]
420+ gcResultBytesFreed `shouldBe` 4
0 commit comments