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

398 lines
11 KiB
Haskell
Raw Normal View History

2023-11-17 22:11:18 +03:00
{-# LANGUAGE OverloadedStrings #-}
2023-12-07 19:31:47 +03:00
module NixDaemonSpec
( enterNamespaces
, spec
) where
2023-12-07 19:31:47 +03:00
import Control.Monad (forM_, unless, void)
import Control.Monad.IO.Class (liftIO)
import Crypto.Hash (SHA256)
import Data.Some (Some(Some))
import Data.Text (Text)
2023-12-07 19:31:47 +03:00
import Test.Hspec (Spec, SpecWith, around, describe, context)
2023-11-22 16:53:03 +03:00
import Test.Hspec.Expectations.Lifted
import Test.Hspec.Nix (forceRight)
2023-12-07 19:31:47 +03:00
import System.FilePath ((</>))
import System.Linux.Namespaces (Namespace(..), GroupMapping(..), UserMapping(..))
import System.Nix.Hash (HashAlgo(HashAlgo_SHA256))
2023-12-07 19:31:47 +03:00
import System.Nix.Build (BuildMode(..))
import System.Nix.DerivedPath (DerivedPath(..))
2023-12-07 19:31:47 +03:00
import System.Nix.StorePath (StoreDir(..), StorePath)
import System.Nix.StorePath.Metadata (Metadata(..))
2023-11-22 16:53:03 +03:00
import System.Nix.Store.Remote
2023-12-07 19:31:47 +03:00
import System.Nix.Store.Remote.MonadStore (MonadRemoteStore)
import System.Process (CreateProcess(..), ProcessHandle)
import qualified Control.Concurrent
import qualified Control.Exception
import qualified Data.ByteString.Char8
import qualified Data.Either
import qualified Data.HashSet
import qualified Data.Map
import qualified Data.Set
import qualified Data.Text
import qualified Data.Text.Encoding
import qualified System.Directory
import qualified System.Environment
import qualified System.IO.Temp
import qualified System.Linux.Namespaces
import qualified System.Nix.StorePath
import qualified System.Nix.Nar
import qualified System.Nix.Store.Remote.MonadStore
import qualified System.Posix.User
import qualified System.Process
import qualified Test.Hspec
createProcessEnv
:: FilePath
-> String
-> [String]
-> IO ProcessHandle
createProcessEnv fp proc args = do
mPath <- System.Environment.lookupEnv "PATH"
(_, _, _, ph) <-
2023-12-07 19:31:47 +03:00
System.Process.createProcess (System.Process.proc proc args)
{ cwd = Just fp
, env = Just $ mockedEnv mPath fp
}
pure ph
2023-12-07 19:31:47 +03:00
mockedEnv
:: Maybe String
-> FilePath
-> [(String, FilePath)]
mockedEnv mEnvPath fp =
[ ("NIX_STORE_DIR" , fp </> "store")
, ("NIX_LOCALSTATE_DIR", fp </> "var")
, ("NIX_LOG_DIR" , fp </> "var" </> "log")
, ("NIX_STATE_DIR" , fp </> "var" </> "nix")
, ("NIX_CONF_DIR" , fp </> "etc")
, ("HOME" , fp </> "home")
-- , ("NIX_REMOTE", "daemon")
2021-08-06 19:18:38 +03:00
] <> foldMap (\x -> [("PATH", x)]) mEnvPath
2023-12-07 19:31:47 +03:00
waitSocket
:: FilePath
-> Int
-> IO ()
2021-01-14 16:15:47 +03:00
waitSocket _ 0 = fail "No socket"
waitSocket fp x = do
2023-12-07 19:31:47 +03:00
ex <- System.Directory.doesFileExist fp
unless ex $ do
Control.Concurrent.threadDelay 100000
waitSocket fp (x - 1)
2021-01-14 16:15:47 +03:00
writeConf :: FilePath -> IO ()
writeConf fp =
writeFile fp $ unlines
[ "build-users-group = "
, "trusted-users = root"
, "allowed-users = *"
, "fsync-metadata = false"
]
{-
- we run in user namespace as root but groups are failed
- => build-users-group has to be empty but we still
- get an error (maybe older nix-daemon)
-
uid=0(root) gid=65534(nobody) groups=65534(nobody)
drwxr-xr-x 3 0 65534 60 Nov 29 05:53 store
accepted connection from pid 22959, user root (trusted)
error: changing ownership of path '/run/user/1000/test-nix-store-06b0d249e5616122/store': Invalid argument
-}
startDaemon
:: FilePath
2023-12-07 19:31:47 +03:00
-> IO (ProcessHandle, MonadStore a -> Run IO a)
startDaemon fp = do
writeConf (fp </> "etc" </> "nix.conf")
2023-12-07 19:31:47 +03:00
procHandle <- createProcessEnv fp "nix-daemon" []
waitSocket sockFp 30
2023-12-07 19:31:47 +03:00
pure ( procHandle
, runStoreOpts
sockFp
(StoreDir
$ Data.ByteString.Char8.pack
$ fp </> "store"
)
)
where
sockFp = fp </> "var/nix/daemon-socket/socket"
2021-01-14 16:15:47 +03:00
enterNamespaces :: IO ()
enterNamespaces = do
2023-12-07 19:31:47 +03:00
uid <- System.Posix.User.getEffectiveUserID
gid <- System.Posix.User.getEffectiveGroupID
System.Linux.Namespaces.unshare
[User, Network, Mount]
-- fmap our (parent) uid to root
2023-12-07 19:31:47 +03:00
System.Linux.Namespaces.writeUserMappings
Nothing
[ UserMapping
0 -- inside namespace
uid -- outside namespace
1 --range
]
-- fmap our (parent) gid to root group
2023-12-07 19:31:47 +03:00
System.Linux.Namespaces.writeGroupMappings
Nothing
[ GroupMapping 0 gid 1 ]
True
2021-01-14 16:15:47 +03:00
withNixDaemon
2023-12-07 19:31:47 +03:00
:: ((MonadStore a -> Run IO a) -> IO a)
-> IO a
withNixDaemon action =
2023-12-07 19:31:47 +03:00
System.IO.Temp.withSystemTempDirectory "test-nix-store" $ \path -> do
2023-12-07 19:31:47 +03:00
mapM_ (System.Directory.createDirectory . snd)
(filter
((/= "NIX_REMOTE") . fst)
$ mockedEnv Nothing path)
ini <- createProcessEnv path "nix-store" ["--init"]
2023-12-07 19:31:47 +03:00
void $ System.Process.waitForProcess ini
writeFile (path </> "dummy") "Hello World"
2023-12-07 19:31:47 +03:00
System.Directory.setCurrentDirectory path
2023-12-07 19:31:47 +03:00
Control.Exception.bracket
(startDaemon path)
(System.Process.terminateProcess . fst)
(action . snd)
2023-12-07 19:31:47 +03:00
checks
:: ( Show a
, Show b
)
=> IO (a, b)
-> (a -> Bool)
-> IO ()
checks action check =
action >>= (`Test.Hspec.shouldSatisfy` (check . fst))
2021-01-14 16:15:47 +03:00
it
:: (Show a, Show b, Monad m)
=> String
-> m c
-> (a -> Bool)
2023-12-07 19:31:47 +03:00
-> SpecWith (m () -> IO (a, b))
it name action check =
2023-12-07 19:31:47 +03:00
Test.Hspec.it name $ \run -> run (void $ action) `checks` check
2021-01-14 16:15:47 +03:00
itRights
2023-12-07 19:31:47 +03:00
:: ( Show a
, Show b
, Show c
, Monad m
)
2021-01-14 16:15:47 +03:00
=> String
-> m d
2023-12-07 19:31:47 +03:00
-> SpecWith (m () -> IO (Either a b, c))
itRights name action = it name action Data.Either.isRight
2021-01-14 16:15:47 +03:00
itLefts
2023-12-07 19:31:47 +03:00
:: ( Show a
, Show b
, Show c
, Monad m
)
2021-01-14 16:15:47 +03:00
=> String
-> m d
2023-12-07 19:31:47 +03:00
-> SpecWith (m () -> IO (Either a b, c))
itLefts name action = it name action Data.Either.isLeft
2023-12-07 19:31:47 +03:00
withPath
:: (StorePath -> MonadStore a)
-> MonadStore a
withPath action = do
path <-
addTextToStore
(StoreText
2023-12-07 19:31:47 +03:00
(forceRight $ System.Nix.StorePath.mkStorePathName "hnix-store")
"test"
)
mempty
RepairMode_DontRepair
action path
2023-12-03 14:14:55 +03:00
-- | dummy path, adds <tmp>/dummy with "Hello World" contents
2021-01-14 16:15:47 +03:00
dummy :: MonadStore StorePath
dummy = do
addToStore
2023-12-07 19:31:47 +03:00
(forceRight $ System.Nix.StorePath.mkStorePathName "dummy")
(System.Nix.Nar.dumpPath "dummy")
FileIngestionMethod_Flat
(Some HashAlgo_SHA256)
RepairMode_DontRepair
invalidPath :: StorePath
invalidPath =
2023-12-07 19:31:47 +03:00
let name = forceRight $ System.Nix.StorePath.mkStorePathName "invalid"
in System.Nix.StorePath.unsafeMakeStorePath
(System.Nix.StorePath.mkStorePathHashPart
@SHA256
"invalid")
name
_withBuilder
:: MonadRemoteStore m
=> (StorePath -> m a)
-> m a
_withBuilder action = do
path <-
addTextToStore
2023-12-07 19:31:47 +03:00
(StoreText (forceRight $ System.Nix.StorePath.mkStorePathName "builder") builderSh)
mempty
RepairMode_DontRepair
action path
2021-01-14 16:15:47 +03:00
builderSh :: Text
builderSh = "declare -xpexport > $out"
2023-12-07 19:31:47 +03:00
spec :: Spec
spec = around withNixDaemon $
describe "store" $ do
context "syncWithGC" $
itRights "syncs with garbage collector" syncWithGC
context "verifyStore" $ do
itRights "check=False repair=False" $
verifyStore
CheckMode_DontCheck
RepairMode_DontRepair
`shouldReturn` False
itRights "check=True repair=False" $
verifyStore
CheckMode_DoCheck
RepairMode_DontRepair
`shouldReturn` False
--privileged
itRights "check=True repair=True" $
verifyStore
CheckMode_DoCheck
RepairMode_DoRepair
`shouldReturn` False
context "addTextToStore" $
2021-08-06 19:18:38 +03:00
itRights "adds text to store" $ withPath pure
context "isValidPath" $ do
itRights "validates path" $ withPath $ \path -> do
2021-08-06 15:38:17 +03:00
liftIO $ print path
isValidPath path `shouldReturn` True
itLefts "fails on invalid path"
2023-12-07 19:31:47 +03:00
$ System.Nix.Store.Remote.MonadStore.mapStoreConfig
(\sc -> sc { storeConfig_dir = StoreDir "/asdf" })
$ isValidPath invalidPath
context "queryAllValidPaths" $ do
2021-08-06 15:38:17 +03:00
itRights "empty query" queryAllValidPaths
itRights "non-empty query" $ withPath $ \path ->
2023-12-07 19:31:47 +03:00
queryAllValidPaths `shouldReturn` Data.HashSet.fromList [path]
context "queryPathInfo" $
itRights "queries path info" $ withPath $ \path -> do
meta <- queryPathInfo path
(metadataReferences <$> meta) `shouldBe` (Just mempty)
context "ensurePath" $
2021-08-06 15:38:17 +03:00
itRights "simple ensure" $ withPath ensurePath
context "addTempRoot" $
2021-08-06 15:38:17 +03:00
itRights "simple addition" $ withPath addTempRoot
context "addIndirectRoot" $
2021-08-06 15:38:17 +03:00
itRights "simple addition" $ withPath addIndirectRoot
let toDerivedPathSet p = Data.Set.fromList [DerivedPath_Opaque p]
context "buildPaths" $ do
itRights "build Normal" $ withPath $ \path -> do
buildPaths (toDerivedPathSet path) BuildMode_Normal
itRights "build Check" $ withPath $ \path -> do
buildPaths (toDerivedPathSet path) BuildMode_Check
itLefts "build Repair" $ withPath $ \path -> do
buildPaths (toDerivedPathSet path) BuildMode_Repair
context "roots" $ context "findRoots" $ do
2023-12-07 19:31:47 +03:00
itRights "empty roots" (findRoots `shouldReturn` mempty)
2021-01-14 16:15:47 +03:00
itRights "path added as a temp root" $ withPath $ \_ -> do
roots <- findRoots
2023-12-07 19:31:47 +03:00
roots `shouldSatisfy` ((== 1) . Data.Map.size)
2021-08-06 15:38:17 +03:00
context "optimiseStore" $ itRights "optimises" optimiseStore
context "queryMissing" $
itRights "queries" $ withPath $ \path -> do
queryMissing (toDerivedPathSet path)
`shouldReturn`
Missing
{ missingWillBuild = mempty
, missingWillSubstitute = mempty
, missingUnknownPaths = mempty
, missingDownloadSize = 0
, missingNarSize = 0
}
context "addToStore" $
itRights "adds file to store" $ do
2023-12-07 19:31:47 +03:00
fp <-
liftIO
$ System.IO.Temp.writeSystemTempFile
"addition"
"yolo"
addToStore
2023-12-07 19:31:47 +03:00
(forceRight $ System.Nix.StorePath.mkStorePathName "tmp-addition")
(System.Nix.Nar.dumpPath fp)
FileIngestionMethod_Flat
(Some HashAlgo_SHA256)
RepairMode_DontRepair
context "with dummy" $ do
itRights "adds dummy" dummy
itRights "valid dummy" $ do
path <- dummy
isValidPath path `shouldReturn` True
context "collectGarbage" $ do
itRights "delete a specific path from the store" $ withPath $ \path -> do
-- clear temp gc roots so the delete works. restarting the nix daemon should also do this...
storeDir <- getStoreDir
let tempRootsDir = Data.Text.unpack $ mconcat [ Data.Text.Encoding.decodeUtf8 (unStoreDir storeDir), "/../var/nix/temproots/" ]
2023-12-07 19:31:47 +03:00
tempRootList <-
liftIO
$ System.Directory.listDirectory
tempRootsDir
liftIO $ forM_ tempRootList $ \entry -> do
2023-12-07 19:31:47 +03:00
System.Directory.removeFile
$ mconcat [ tempRootsDir, "/", entry ]
GCResult{..} <-
collectGarbage
GCOptions
{ gcOptionsOperation = GCAction_DeleteSpecific
, gcOptionsIgnoreLiveness = False
2023-12-07 19:31:47 +03:00
, gcOptionsPathsToDelete = Data.HashSet.fromList [path]
, gcOptionsMaxFreed = maxBound
}
2023-12-07 19:31:47 +03:00
gcResultDeletedPaths `shouldBe` Data.HashSet.fromList [path]
gcResultBytesFreed `shouldBe` 4