|
| 1 | +{-# LANGUAGE DataKinds #-} |
| 2 | +{-# LANGUAGE OverloadedStrings #-} |
| 3 | +{-# LANGUAGE ScopedTypeVariables #-} |
| 4 | +{-# LANGUAGE TypeApplications #-} |
| 5 | + |
| 6 | +module NixDaemon where |
| 7 | + |
| 8 | +import Prelude hiding (FilePath) |
| 9 | +import Control.Monad |
| 10 | +import Control.Monad.IO.Class (liftIO, MonadIO) |
| 11 | +import Control.Exception (bracket) |
| 12 | +import Control.Concurrent (threadDelay) |
| 13 | +import Data.Either (isRight, isLeft) |
| 14 | +import qualified Data.ByteString as BS |
| 15 | +import qualified Data.ByteString.Base64.Lazy as B64 |
| 16 | +import qualified Data.ByteString.Lazy as BSL |
| 17 | +import Data.Monoid ((<>)) |
| 18 | +import Data.Maybe (fromJust) |
| 19 | +import Data.Time |
| 20 | +import qualified Data.Text as T |
| 21 | +import qualified Data.Text.Lazy.Builder |
| 22 | +import qualified Data.HashSet as HS |
| 23 | +import qualified Data.Map.Strict as M |
| 24 | +import qualified Data.Set as S |
| 25 | +import qualified Data.Vector as V |
| 26 | +import System.Directory --(doesFileExist, createDirectory, copyFile) |
| 27 | +import System.IO.Temp -- (withSystemTempDirectory, writeSystemTempFile, createTempDirectory) |
| 28 | +import qualified System.IO as IO (hGetContents, hPutStr, openFile) |
| 29 | +import qualified System.Process as P |
| 30 | +import System.Posix.User as U |
| 31 | +import System.Linux.Namespaces as NS |
| 32 | +import Test.Tasty as T |
| 33 | +import Test.Tasty.Hspec (Spec, HasCallStack, describe, context) |
| 34 | +import qualified Test.Tasty.Hspec as Hspec |
| 35 | +import Test.Hspec.Expectations.Lifted |
| 36 | +import qualified Test.Tasty.HUnit as HU |
| 37 | +import Test.Tasty.QuickCheck |
| 38 | +import Text.Read (readMaybe) |
| 39 | + |
| 40 | +import Filesystem.Path |
| 41 | +import Filesystem.Path.CurrentOS |
| 42 | +import System.Nix.Build |
| 43 | +import System.Nix.Hash |
| 44 | +import System.Nix.Path |
| 45 | +import System.Nix.Nar |
| 46 | +import qualified System.Nix.ValidPath as VP |
| 47 | +import System.Nix.Store.Remote |
| 48 | +import System.Nix.Store.Remote.Logger |
| 49 | +import System.Nix.Store.Remote.Types |
| 50 | +import System.Nix.Store.Remote.Protocol |
| 51 | +import System.Nix.Store.Remote.Util |
| 52 | +import qualified System.Nix.GC as GC |
| 53 | + |
| 54 | +import Data.Proxy |
| 55 | + |
| 56 | +-- derivation parsing |
| 57 | +import qualified Nix.Derivation as Drv |
| 58 | +import qualified Data.Text.Lazy as TL |
| 59 | +import qualified Data.Text.Lazy.IO as TIO |
| 60 | +import qualified Data.Attoparsec.Text.Lazy as A |
| 61 | + |
| 62 | +createProcessEnv :: FilePath -> String -> [String] -> IO P.ProcessHandle |
| 63 | +createProcessEnv fp proc args =do |
| 64 | + (_, _, _, ph) <- P.createProcess (P.proc proc args) { P.cwd = Just $ encodeString fp |
| 65 | + , P.env = Just $ mockedEnv fp } |
| 66 | + return ph |
| 67 | + |
| 68 | +mockedEnv :: FilePath -> [(String, String)] |
| 69 | +mockedEnv fp = map (\(a, b) -> (a, encodeString b)) [ |
| 70 | + ("NIX_STORE_DIR", fp </> "store") |
| 71 | + , ("NIX_LOCALSTATE_DIR", fp </> "var") |
| 72 | + , ("NIX_LOG_DIR", fp </> "var" </> "log") |
| 73 | + , ("NIX_STATE_DIR", fp </> "var" </> "nix") |
| 74 | + , ("NIX_CONF_DIR", fp </> "etc") |
| 75 | +-- , ("NIX_REMOTE", "daemon") |
| 76 | + ] |
| 77 | + |
| 78 | +waitSocket :: FilePath -> Int -> IO () |
| 79 | +waitSocket fp 0 = fail "No socket" |
| 80 | +waitSocket fp x = do |
| 81 | + ex <- doesFileExist (encodeString fp) |
| 82 | + case ex of |
| 83 | + True -> return () |
| 84 | + False -> threadDelay 100000 >> waitSocket fp (x - 1) |
| 85 | + |
| 86 | +writeConf fp = do |
| 87 | + TIO.writeFile fp $ TL.unlines [ |
| 88 | + "build-users-group = " |
| 89 | + , "trusted-users = root" |
| 90 | + , "allowed-users = *" |
| 91 | + ] |
| 92 | + |
| 93 | +{- |
| 94 | + - we run in user namespace as root but groups are failed |
| 95 | + - => build-users-group has to be empty but we still |
| 96 | + - get an error (maybe older nix-daemon) |
| 97 | + - |
| 98 | +uid=0(root) gid=65534(nobody) groups=65534(nobody) |
| 99 | +
|
| 100 | +drwxr-xr-x 3 0 65534 60 Nov 29 05:53 store |
| 101 | +
|
| 102 | +accepted connection from pid 22959, user root (trusted) |
| 103 | +error: changing ownership of path '/run/user/1000/test-nix-store-06b0d249e5616122/store': Invalid argument |
| 104 | +-} |
| 105 | + |
| 106 | + |
| 107 | +startDaemon :: FilePath -> IO (P.ProcessHandle, MonadStore a -> IO (Either String a, [Logger])) |
| 108 | +startDaemon fp = do |
| 109 | + writeConf (encodeString $ fp </> "etc" </> "nix.conf") |
| 110 | + p <- createProcessEnv fp "nix-daemon" [] |
| 111 | + waitSocket sockFp 30 |
| 112 | + return (p, runStoreOpts (encodeString sockFp) (encodeString (fp </> "store"))) |
| 113 | + where |
| 114 | + sockFp = fp </> "var/nix/daemon-socket/socket" |
| 115 | + |
| 116 | +enterNamespaces = do |
| 117 | + uid <- getEffectiveUserID |
| 118 | + unshare [User, Network, Mount] |
| 119 | + writeUserMappings Nothing [UserMapping 0 uid 1] |
| 120 | + -- permission denied :( |
| 121 | + --writeGroupMappings Nothing [GroupMapping 65534 ? 1] True |
| 122 | + |
| 123 | +withNixDaemon action = do |
| 124 | + withSystemTempDirectory "test-nix-store" $ \pth -> do |
| 125 | + let path = decodeString pth -- oh my |
| 126 | + |
| 127 | + mapM_ (createDirectory . snd) (filter ((/= "NIX_REMOTE") . fst) $ mockedEnv path) |
| 128 | + |
| 129 | + ini <- createProcessEnv path "nix-store" ["--init"] |
| 130 | + P.waitForProcess ini |
| 131 | + |
| 132 | + bracket (startDaemon path) |
| 133 | + (P.terminateProcess . fst) |
| 134 | + (action . snd) |
| 135 | + |
| 136 | +checks action check = action >>= (`Hspec.shouldSatisfy` (check . fst)) |
| 137 | +it name action check = Hspec.it name $ \run -> (run (action >> return ())) `checks` check |
| 138 | +itRights name action = it name action isRight |
| 139 | +itLefts name action = it name action isLeft |
| 140 | + |
| 141 | +withPath action = do |
| 142 | + (Just path) <- addTextToStore "hnix-store" "test" (HS.fromList []) False |
| 143 | + action path |
| 144 | + |
| 145 | +{- |
| 146 | + - broken |
| 147 | +
|
| 148 | +withDrv action = withBuilder $ \builder -> withBash $ \bash -> do |
| 149 | + path <- addTextToStore "wannabe-output" "" (HS.fromList []) False |
| 150 | +
|
| 151 | + let unPath (Path digest pname) = pathNameContents pname |
| 152 | + d = drvSample (unPath bash) (fromText $ unPath builder) (decodeString $ ((T.unpack $ unPath path) ++ "-out")) |
| 153 | +
|
| 154 | + (Just path) <- addTextToStore "hnix-store-derivation" ( |
| 155 | + TL.toStrict $ Data.Text.Lazy.Builder.toLazyText $ Drv.buildDerivation d) |
| 156 | + (HS.fromList []) False |
| 157 | + liftIO $ print d |
| 158 | + action path d |
| 159 | +-} |
| 160 | + |
| 161 | +lal = do |
| 162 | + --fp <- fmap init <$> liftIO $ P.readProcess "which" ["bash"] "" |
| 163 | + --parent <- liftIO getCanonicalTemporaryDirectory |
| 164 | + --pth <- liftIO $ createTempDirectory parent "test-nix-store-import" |
| 165 | + --liftIO $ copyFile fp (pth ++ "/bash") |
| 166 | + nar <- liftIO $ localPackNar narEffectsIO "src" |
| 167 | + now <- liftIO $ getCurrentTime |
| 168 | + |
| 169 | + -- makeOutputPath "myout" digest "out" (StoreLocation) |
| 170 | + (Just path) <- addTextToStore "wannabe-output" "" (HS.fromList []) False |
| 171 | + let unPath (Path digest pname) = pathNameContents pname |
| 172 | + |
| 173 | + let vp = VP.ValidPath |
| 174 | + { VP.path = path |
| 175 | + , VP.deriver = Nothing |
| 176 | + , VP.narHash = (printAsBase32 @PathHashAlgo (hash "dunno")) |
| 177 | + , VP.references = HS.empty |
| 178 | + , VP.registrationTime = now |
| 179 | + , VP.narSize = 100 |
| 180 | + , VP.ultimate = True |
| 181 | + , VP.sigs = [] |
| 182 | + , VP.ca = "" |
| 183 | + } |
| 184 | + |
| 185 | + addToStoreNar vp nar False False |
| 186 | + |
| 187 | + --liftIO $ removeDirectoryRecursive pth |
| 188 | + |
| 189 | +{- |
| 190 | +withBash action = do |
| 191 | + fp <- fmap init <$> liftIO $ P.readProcess "which" ["bash"] "" |
| 192 | + path <- addToStore "bash" fp False (Proxy :: Proxy 'SHA256) (pure True) False |
| 193 | + action path |
| 194 | +-} |
| 195 | + |
| 196 | +withBuilder action = do |
| 197 | + (Just path) <- addTextToStore "builder" builderSh (HS.fromList []) False |
| 198 | + action path |
| 199 | + |
| 200 | +builderSh = T.concat [ "declare -xp", "export > $out" ] |
| 201 | + |
| 202 | +drvSample builder buildScript out = Drv.Derivation { |
| 203 | + Drv.outputs = M.fromList [ ("out", Drv.DerivationOutput out "sha256" "lal") ] |
| 204 | + , Drv.inputDrvs = M.empty -- Map FilePath (Set Text) |
| 205 | + , Drv.inputSrcs = S.fromList [ buildScript ] |
| 206 | + , Drv.platform = "x86_64-linux" |
| 207 | + , Drv.builder = builder |
| 208 | + , Drv.args = V.fromList ["-e", printFP buildScript ] |
| 209 | +-- , Drv.env = M.empty |
| 210 | + , Drv.env = M.fromList [("testEnv", "true")] |
| 211 | + } |
| 212 | + |
| 213 | +spec_protocol :: Spec |
| 214 | +spec_protocol = Hspec.around withNixDaemon $ do |
| 215 | + describe "store" $ do |
| 216 | + context "syncWithGC" $ do |
| 217 | + itRights "syncs with garbage collector" syncWithGC |
| 218 | + |
| 219 | + context "verifyStore" $ do |
| 220 | + itRights "check=False repair=False" $ do |
| 221 | + verifyStore False False `shouldReturn` False |
| 222 | + |
| 223 | + itRights "check=True repair=False" $ do |
| 224 | + verifyStore True False `shouldReturn` False |
| 225 | + |
| 226 | + --privileged |
| 227 | + itRights "check=True repair=True" $ do |
| 228 | + verifyStore True True `shouldReturn` False |
| 229 | + |
| 230 | + context "addTextToStore" $ do |
| 231 | + itRights "adds text to store" $ withPath $ const return () |
| 232 | + |
| 233 | + context "isValidPathUncached" $ do |
| 234 | + itRights "validates path" $ withPath $ \path -> do |
| 235 | + (isValidPathUncached path) `shouldReturn` True |
| 236 | + itLefts "fails on invalid path" $ isValidPathUncached $ fromJust $ mkPath "nopez" |
| 237 | + |
| 238 | + context "queryAllValidPaths" $ do |
| 239 | + itRights "empty query" $ queryAllValidPaths |
| 240 | + itRights "non-empty query" $ withPath $ \path -> queryAllValidPaths `shouldReturn` (HS.fromList [path]) |
| 241 | + |
| 242 | + context "queryPathInfoUncached" $ do |
| 243 | + itRights "queries path info" $ withPath $ queryPathInfoUncached |
| 244 | + |
| 245 | + {- |
| 246 | + context "ensurePath" $ do |
| 247 | + itRights "simple ensure" $ withPath $ ensurePath |
| 248 | +
|
| 249 | + context "addTempRoot" $ do |
| 250 | + itRights "simple addition" $ withPath $ addTempRoot |
| 251 | +
|
| 252 | + context "addIndirectRoot" $ do |
| 253 | + itRights "simple addition" $ withPath $ addIndirectRoot |
| 254 | +
|
| 255 | + context "collectGarbage" $ do |
| 256 | + itRights "simple collect nothing" $ do |
| 257 | + gc <- collectGarbage $ GC.Options |
| 258 | + { GC.operation = GC.DeleteDead |
| 259 | + , GC.pathsToDelete = HS.empty |
| 260 | + , GC.ignoreLiveness = False |
| 261 | + , GC.maxFreed = -1 } |
| 262 | +
|
| 263 | + gc `shouldBe` (GC.Result {GC.paths = HS.empty, GC.bytesFreed = 0}) |
| 264 | +
|
| 265 | + itLefts "cannot gargabe collect live path" $ withPath $ \path -> do |
| 266 | + ensurePath path |
| 267 | +
|
| 268 | + collectGarbage $ GC.Options |
| 269 | + { GC.operation = GC.DeleteSpecific |
| 270 | + , GC.pathsToDelete = HS.fromList [path] |
| 271 | + , GC.ignoreLiveness = False |
| 272 | + , GC.maxFreed = -1 } |
| 273 | + -} |
| 274 | + |
| 275 | + {- |
| 276 | + context "buildPaths" $ do |
| 277 | + itRights "build Normal" $ withPath $ \path -> do |
| 278 | + let pathSet = HS.fromList [path] |
| 279 | + buildPaths pathSet Normal |
| 280 | +
|
| 281 | + itRights "build Check" $ withPath $ \path -> do |
| 282 | + let pathSet = HS.fromList [path] |
| 283 | + buildPaths pathSet Check |
| 284 | +
|
| 285 | + itLefts "build Repair" $ withPath $ \path -> do |
| 286 | + let pathSet = HS.fromList [path] |
| 287 | + buildPaths pathSet Repair |
| 288 | + -} |
| 289 | + |
| 290 | + context "roots" $ do |
| 291 | + context "findRoots" $ do |
| 292 | + itRights "empty roots" $ (findRoots `shouldReturn` M.empty) |
| 293 | + |
| 294 | + itRights "path added as a temp root" $ withPath $ \path -> do |
| 295 | + roots <- findRoots |
| 296 | + roots `shouldSatisfy` ((==1) . M.size) |
| 297 | + |
| 298 | + |
| 299 | + {- |
| 300 | + context "optimiseStore" $ do |
| 301 | + itRights "optimises" $ optimiseStore |
| 302 | +
|
| 303 | + context "queryMissing" $ do |
| 304 | + itRights "queries" $ withPath $ \path -> do |
| 305 | + let pathSet = HS.fromList [path] |
| 306 | + queryMissing pathSet `shouldReturn` (HS.empty, HS.empty, HS.empty, 0, 0) |
| 307 | + -} |
| 308 | + |
| 309 | + {- |
| 310 | + context "addToStore" $ do |
| 311 | + itRights "adds file to store" $ do |
| 312 | + fp <- liftIO $ writeSystemTempFile "addition" "lal" |
| 313 | + res <- addToStore "test" fp False SHA256 (pure True) False |
| 314 | + liftIO $ print res |
| 315 | +
|
| 316 | + itRights "adds bash to store" $ withBash $ const return () |
| 317 | +
|
| 318 | + itRights "build derivation" $ do |
| 319 | + withDrv $ \path drv -> do |
| 320 | + res <- buildDerivation path drv Normal |
| 321 | + res `shouldSatisfy` ((==TransientFailure) . status) |
| 322 | + liftIO $ print res |
| 323 | +
|
| 324 | + --liftIO $ forever $ threadDelay 1000000 |
| 325 | +
|
| 326 | + return () |
| 327 | +
|
| 328 | + itRights "matches paths" $ do |
| 329 | + (Just path) <- addTextToStore "lal" "Hello World" (HS.fromList []) False |
| 330 | + liftIO $ print path |
| 331 | + return () |
| 332 | + -- /nix/store/fnxqxrjyhksy7x3ilzz9lixrynwcnz3q-lal |
| 333 | +
|
| 334 | +
|
| 335 | + -} |
| 336 | + {- |
| 337 | + itRights "nars" $ lal |
| 338 | + drv <- liftIO $ do |
| 339 | + text <- TIO.readFile drvFP' |
| 340 | + case A.parse Drv.parseDerivation text of |
| 341 | + A.Fail _uncomsumed _contexts error -> fail $ "Derivation parsing error " ++ error |
| 342 | + A.Done _unconsumed result -> return result |
| 343 | + -} |
| 344 | + |
| 345 | + |
| 346 | +{- |
| 347 | +pec_lol :: Spec |
| 348 | +pec_lol = around withNixDaemon $ do |
| 349 | + describe "store" $ do |
| 350 | + it "addsText" $ \run -> do |
| 351 | + (run $ addTextToStore "hnix-store" "test" (HS.fromList []) False) `checks` () |
| 352 | +-} |
0 commit comments