Merge pull request #182 from haskell-nix/srk/test_fixes

Remote testsuite fixes for Nix 2.6
This commit is contained in:
Richard Marko 2022-03-07 17:06:00 +01:00 committed by GitHub
commit 83619f3824
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 3 additions and 86 deletions

View File

@ -90,8 +90,7 @@ test-suite hnix-store-remote-tests
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
main-is: Driver.hs main-is: Driver.hs
other-modules: other-modules:
Derivation NixDaemon
, NixDaemon
, Spec , Spec
, Util , Util
hs-source-dirs: tests hs-source-dirs: tests
@ -114,7 +113,6 @@ test-suite hnix-store-remote-tests
, tasty-hspec , tasty-hspec
, tasty-quickcheck , tasty-quickcheck
, linux-namespaces , linux-namespaces
, nix-derivation
, temporary , temporary
, text , text
, unix , unix

View File

@ -1,75 +0,0 @@
{-# language DataKinds #-}
module Derivation where
import Nix.Derivation ( Derivation(..)
, DerivationOutput(..)
)
import System.Nix.StorePath ( StorePath
, storePathToText
)
import System.Nix.Store.Remote ( MonadStore
, addToStore
, addTextToStore
)
import qualified Data.Map
import qualified Data.Set
import qualified Data.Text
import qualified Data.Text.Lazy.Builder
import qualified Data.Vector
import qualified System.Nix.Derivation
import qualified System.Nix.StorePath
import qualified System.Directory
import Crypto.Hash ( SHA256 )
drvSample :: StorePath -> StorePath -> StorePath -> Derivation StorePath Text
drvSample builder' buildScript out = Derivation
{ outputs = Data.Map.fromList [("out", DerivationOutput out "sha256" "test")]
, inputDrvs = Data.Map.fromList [(builder', Data.Set.fromList ["out"])]
, inputSrcs = Data.Set.fromList [buildScript]
, platform = "x86_64-linux"
, builder = storePathToText builder'
, args = Data.Vector.fromList ["-e", storePathToText buildScript]
, env = Data.Map.fromList [("testEnv", "true")]
}
withBash :: (StorePath -> MonadStore a) -> MonadStore a
withBash action = do
mfp <- liftIO $ System.Directory.findExecutable "bash"
case mfp of
Nothing -> error "No bash executable found"
Just fp -> do
let Right n = System.Nix.StorePath.makeStorePathName "bash"
pth <- addToStore @SHA256 n fp False (pure True) False
action pth
withBuildScript :: (StorePath -> MonadStore a) -> MonadStore a
withBuildScript action = do
pth <- addTextToStore "buildScript"
(Data.Text.concat ["declare -xp", "export > $out"])
mempty
False
action pth
withDerivation
:: (StorePath -> Derivation StorePath Text -> MonadStore a) -> MonadStore a
withDerivation action = withBuildScript $ \buildScript -> withBash $ \bash ->
do
outputPath <- addTextToStore "wannabe-output" "" mempty False
let d = drvSample bash buildScript outputPath
pth <- addTextToStore
"hnix-store-derivation"
( toText
$ Data.Text.Lazy.Builder.toLazyText
$ System.Nix.Derivation.buildDerivation d
)
mempty
False
liftIO $ print d
action pth d

View File

@ -27,7 +27,6 @@ import System.Nix.StorePath
import System.Nix.Store.Remote import System.Nix.Store.Remote
import System.Nix.Store.Remote.Protocol import System.Nix.Store.Remote.Protocol
import Derivation
import Crypto.Hash ( SHA256 import Crypto.Hash ( SHA256
) )
@ -49,6 +48,7 @@ mockedEnv mEnvPath fp = (fp </>) <<$>>
, ("NIX_LOG_DIR" , "var" </> "log") , ("NIX_LOG_DIR" , "var" </> "log")
, ("NIX_STATE_DIR" , "var" </> "nix") , ("NIX_STATE_DIR" , "var" </> "nix")
, ("NIX_CONF_DIR" , "etc") , ("NIX_CONF_DIR" , "etc")
, ("HOME" , "home")
-- , ("NIX_REMOTE", "daemon") -- , ("NIX_REMOTE", "daemon")
] <> foldMap (\x -> [("PATH", x)]) mEnvPath ] <> foldMap (\x -> [("PATH", x)]) mEnvPath
@ -260,9 +260,3 @@ spec_protocol = Hspec.around withNixDaemon $
path <- dummy path <- dummy
liftIO $ print path liftIO $ print path
isValidPathUncached path `shouldReturn` True isValidPathUncached path `shouldReturn` True
context "derivation" $
itRights "build derivation" $
withDerivation $ \path drv -> do
result <- buildDerivation path drv Normal
result `shouldSatisfy` ((== AlreadyValid) . status)

View File

@ -1,6 +1,6 @@
pkgs: hlib: helf: huper: { pkgs: hlib: helf: huper: {
hnix-store-remote = hnix-store-remote =
( helf.callCabal2nixWithOptions "hnix-store-remote" ./hnix-store-remote "-fio-testsuite" {} ( helf.callCabal2nixWithOptions "hnix-store-remote" ./hnix-store-remote "-fio-testsuite" { relude = helf.relude_1_0_0_1; }
).overrideAttrs (attrs: { ).overrideAttrs (attrs: {
buildInputs = attrs.buildInputs ++ [ buildInputs = attrs.buildInputs ++ [
pkgs.nix pkgs.nix