test: avoid unnecessary tests of variants of git remote

Configuring chunking and encryption for a git remote has no effect, so
skip testing those variants in the TestRemote call.

It would be better if TestRemote itself could do this, but it
doesn't seem possible there. There is no way to look at a Remote and
tell if it supports chunking or encryption.

Note that, while the test suite displays output as it it's testing
exporting, it actually skips doing anything for the tests when run on
the git remote. So at least does not waste time even though the output
is not ideal.

This commit was sponsored by Noam Kremen on Patreon.
This commit is contained in:
Joey Hess 2021-01-11 13:31:36 -04:00
parent 5d2a7f7764
commit 09b0562ec3
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
2 changed files with 10 additions and 8 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RankNTypes, DeriveFunctor #-}
module Command.TestRemote where
@ -194,7 +194,7 @@ adjustRemoteConfig getcache r adjustconfig = do
data Described t = Described
{ getDesc :: String
, getVal :: t
}
} deriving Functor
type RunAnnex = forall a. Annex a -> IO a

14
Test.hs
View file

@ -1,6 +1,6 @@
{- git-annex test suite
-
- Copyright 2010-2020 Joey Hess <id@joeyh.name>
- Copyright 2010-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@ -229,12 +229,12 @@ testRemotes = testGroup "Remote Tests"
]
testGitRemote :: TestTree
testGitRemote = testRemote "git" $ \remotename -> do
testGitRemote = testRemote False "git" $ \remotename -> do
git "clone" [".", "remotedir"] "git clone"
git "remote" ["add", remotename, "remotedir"] "git remote add"
testDirectoryRemote :: TestTree
testDirectoryRemote = testRemote "directory" $ \remotename -> do
testDirectoryRemote = testRemote True "directory" $ \remotename -> do
createDirectory "remotedir"
git_annex "initremote"
[ remotename
@ -244,8 +244,8 @@ testDirectoryRemote = testRemote "directory" $ \remotename -> do
, "encryption=none"
] "init"
testRemote :: String -> (String -> IO ()) -> TestTree
testRemote remotetype setupremote =
testRemote :: Bool -> String -> (String -> IO ()) -> TestTree
testRemote testvariants remotetype setupremote =
withResource newEmptyTMVarIO (const noop) $ \getv ->
testGroup ("testremote type " ++ remotetype) $ concat
[ [testCase "init" (prep getv)]
@ -275,7 +275,9 @@ testRemote remotetype setupremote =
go getv = Command.TestRemote.mkTestTrees runannex mkrs mkunavailr mkexportr mkks
where
runannex = inmainrepo . annexeval
mkrs = Command.TestRemote.remoteVariants cache mkr basesz False
mkrs = if testvariants
then Command.TestRemote.remoteVariants cache mkr basesz False
else [fmap (fmap Just) mkr]
mkr = descas (remotetype ++ " remote") (fst <$> v)
mkunavailr = fst . snd <$> v
mkexportr = fst . snd . snd <$> v