added remote variants

Todo item is done at last.

Might later want to think about testing some other types of remotes that
can be tested locally. The git remote itself is probably already well
enough tested by the test suite that testremote is not needed. Could
test things like bup, or rsync to a local directory. Or even external,
although that would require embedding an external special remote program
into the test suite..
This commit is contained in:
Joey Hess 2020-04-30 13:49:22 -04:00
parent fc1ae62ef1
commit 9fa940569c
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 64 additions and 46 deletions

View file

@ -30,7 +30,7 @@ import Types.RemoteConfig
import Types.ProposedAccepted import Types.ProposedAccepted
import Annex.SpecialRemote.Config (exportTreeField) import Annex.SpecialRemote.Config (exportTreeField)
import Remote.Helper.Chunked import Remote.Helper.Chunked
import Remote.Helper.Encryptable (describeEncryption, encryptionField, highRandomQualityField) import Remote.Helper.Encryptable (encryptionField, highRandomQualityField)
import Git.Types import Git.Types
import Test.Tasty import Test.Tasty
@ -85,56 +85,63 @@ start o = starting "testremote" (ActionItemOther (Just (testRemote o))) $ do
let r' = if null (testReadonlyFile o) let r' = if null (testReadonlyFile o)
then r then r
else r { Remote.readonly = True } else r { Remote.readonly = True }
rs <- if Remote.readonly r' let drs = if Remote.readonly r'
then return [r'] then [Described "remote" (pure (Just r'))]
else remoteVariants r' basesz fast else remoteVariants (Described "remote" (pure r')) basesz fast
unavailr <- Remote.mkUnavailable r' unavailr <- Remote.mkUnavailable r'
let exportr = if Remote.readonly r' let exportr = if Remote.readonly r'
then return Nothing then return Nothing
else exportTreeVariant r' else exportTreeVariant r'
perform rs unavailr exportr ks perform drs unavailr exportr ks
where where
basesz = fromInteger $ sizeOption o basesz = fromInteger $ sizeOption o
remoteVariants :: Remote -> Int -> Bool -> Annex [Remote] perform :: [Described (Annex (Maybe Remote))] -> Maybe Remote -> Annex (Maybe Remote) -> [Key] -> CommandPerform
remoteVariants r basesz fast = do perform drs unavailr exportr ks = do
rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz fast)
concat <$> mapM encryptionVariants rs
perform :: [Remote] -> Maybe Remote -> Annex (Maybe Remote) -> [Key] -> CommandPerform
perform rs unavailr exportr ks = do
st <- liftIO . newTVarIO =<< Annex.getState id st <- liftIO . newTVarIO =<< Annex.getState id
let tests = testGroup "Remote Tests" $ mkTestTrees let tests = testGroup "Remote Tests" $ mkTestTrees
(runTestCase st) (runTestCase st)
(map (\r -> Described (descr r) (pure r)) rs) drs
(pure unavailr) (pure unavailr)
exportr exportr
(map (\k -> Described (desck k) (pure k)) ks) (map (\k -> Described (desck k) (pure k)) ks)
ok <- case tryIngredients [consoleTestReporter] mempty tests of ok <- case tryIngredients [consoleTestReporter] mempty tests of
Nothing -> error "No tests found!?" Nothing -> error "No tests found!?"
Just act -> liftIO act Just act -> liftIO act
rs <- catMaybes <$> mapM getVal drs
next $ cleanup rs ks ok next $ cleanup rs ks ok
where where
descr r = intercalate "; " $ map unwords
[ [ show (getChunkConfig (Remote.config r)) ]
, ["encryption", describeEncryption (Remote.config r)]
]
desck k = unwords [ "key size", show (fromKey keySize k) ] desck k = unwords [ "key size", show (fromKey keySize k) ]
remoteVariants :: Described (Annex Remote) -> Int -> Bool -> [Described (Annex (Maybe Remote))]
remoteVariants dr basesz fast =
concatMap encryptionVariants $
map chunkvariant (chunkSizes basesz fast)
where
chunkvariant sz = Described (getDesc dr ++ " chunksize=" ++ show sz) $ do
r <- getVal dr
adjustChunkSize r sz
adjustChunkSize :: Remote -> Int -> Annex (Maybe Remote) adjustChunkSize :: Remote -> Int -> Annex (Maybe Remote)
adjustChunkSize r chunksize = adjustRemoteConfig r $ adjustChunkSize r chunksize = adjustRemoteConfig r $
M.insert chunkField (Proposed (show chunksize)) M.insert chunkField (Proposed (show chunksize))
-- Variants of a remote with no encryption, and with simple shared -- Variants of a remote with no encryption, and with simple shared
-- encryption. Gpg key based encryption is not tested. -- encryption. Gpg key based encryption is not tested.
encryptionVariants :: Remote -> Annex [Remote] encryptionVariants :: Described (Annex (Maybe Remote)) -> [Described (Annex (Maybe Remote))]
encryptionVariants r = do encryptionVariants dr = [noenc, sharedenc]
noenc <- adjustRemoteConfig r $ where
M.insert encryptionField (Proposed "none") noenc = Described (getDesc dr ++ " encryption=none") $
sharedenc <- adjustRemoteConfig r $ getVal dr >>= \case
M.insert encryptionField (Proposed "shared") . Nothing -> return Nothing
M.insert highRandomQualityField (Proposed "false") Just r -> adjustRemoteConfig r $
return $ catMaybes [noenc, sharedenc] M.insert encryptionField (Proposed "none")
sharedenc = Described (getDesc dr ++ " encryption=shared") $
getVal dr >>= \case
Nothing -> return Nothing
Just r -> adjustRemoteConfig r $
M.insert encryptionField (Proposed "shared") .
M.insert highRandomQualityField (Proposed "false")
-- Variant of a remote with exporttree disabled. -- Variant of a remote with exporttree disabled.
disableExportTree :: Remote -> Annex Remote disableExportTree :: Remote -> Annex Remote
@ -182,7 +189,7 @@ runTestCase stv a = do
-- the provided actions are called. -- the provided actions are called.
mkTestTrees mkTestTrees
:: RunAnnex :: RunAnnex
-> [Described (Annex Remote)] -> [Described (Annex (Maybe Remote))]
-> Annex (Maybe Remote) -> Annex (Maybe Remote)
-> Annex (Maybe Remote) -> Annex (Maybe Remote)
-> [Described (Annex Key)] -> [Described (Annex Key)]
@ -203,7 +210,7 @@ mkTestTrees runannex mkrs mkunavailr mkexportr mkks = concat $
, [ getDesc k2 ] , [ getDesc k2 ]
] ]
test :: RunAnnex -> Annex Remote -> Annex Key -> [TestTree] test :: RunAnnex -> Annex (Maybe Remote) -> Annex Key -> [TestTree]
test runannex mkr mkk = test runannex mkr mkk =
[ check "removeKey when not present" $ \r k -> [ check "removeKey when not present" $ \r k ->
whenwritable r $ remove r k whenwritable r $ remove r k
@ -253,10 +260,11 @@ test runannex mkr mkk =
| Remote.readonly r = return True | Remote.readonly r = return True
| otherwise = a | otherwise = a
check desc a = testCase desc $ do check desc a = testCase desc $ do
let a' = do let a' = mkr >>= \case
r <- mkr Just r -> do
k <- mkk k <- mkk
a r k a r k
Nothing -> return True
runannex a' @? "failed" runannex a' @? "failed"
present r k b = (== Right b) <$> Remote.hasKey r k present r k b = (== Right b) <$> Remote.hasKey r k
fsck _ k = case maybeLookupBackendVariety (fromKey keyVariety k) of fsck _ k = case maybeLookupBackendVariety (fromKey keyVariety k) of

38
Test.hs
View file

@ -148,7 +148,7 @@ ingredients =
tests :: Bool -> Bool -> TestOptions -> TestTree tests :: Bool -> Bool -> TestOptions -> TestTree
tests crippledfilesystem adjustedbranchok opts = tests crippledfilesystem adjustedbranchok opts =
testGroup "Tests" $ properties testGroup "Tests" $ properties
: withTestMode remotetestmode Nothing testRemote : withTestMode remotetestmode Nothing testRemotes
: map (\(d, te) -> withTestMode te (Just initTests) (unitTests d)) testmodes : map (\(d, te) -> withTestMode te (Just initTests) (unitTests d)) testmodes
where where
testmodes = catMaybes testmodes = catMaybes
@ -207,16 +207,25 @@ properties = localOption (QuickCheckTests 1000) $ testGroup "QuickCheck" $
, Utility.Hash.props_macs_stable , Utility.Hash.props_macs_stable
] ]
testRemote :: TestTree testRemotes :: TestTree
testRemote = withResource newEmptyTMVarIO (const noop) $ \getv -> testRemotes = testGroup "Remote Tests"
testGroup "Remote Tests" $ concat [ testRemote "directory"
[ [testCase "init" (prep getv)] [ "directory=remotedir"
, go getv , "encryption=none"
] ]
(createDirectory "remotedir")
]
testRemote :: String -> [String] -> IO () -> TestTree
testRemote remotetype config preinitremote =
withResource newEmptyTMVarIO (const noop) $ \getv ->
testGroup ("remote type " ++ remotetype) $ concat
[ [testCase "init" (prep getv)]
, go getv
]
where where
reponame = "test repo" reponame = "test repo"
remotename = "dir" remotename = "testremote"
remotetype =" directory"
basesz = 1024 * 1024 basesz = 1024 * 1024
keysizes = Command.TestRemote.keySizes basesz False keysizes = Command.TestRemote.keySizes basesz False
prep getv = do prep getv = do
@ -225,17 +234,15 @@ testRemote = withResource newEmptyTMVarIO (const noop) $ \getv ->
innewrepo $ do innewrepo $ do
git_annex "init" [reponame, "--quiet"] git_annex "init" [reponame, "--quiet"]
@? "init failed" @? "init failed"
createDirectory "remotedir" preinitremote
git_annex "initremote" git_annex "initremote"
[ remotename ([ remotename
, "type=" ++ remotetype , "type=" ++ remotetype
, "directory=remotedir"
, "encryption=none"
, "--quiet" , "--quiet"
] ] ++ config)
@? "init failed" @? "init failed"
r <- annexeval $ either error return r <- annexeval $ either error return
=<< Remote.byName' remotename =<< Remote.byName' remotename
unavailr <- annexeval $ Types.Remote.mkUnavailable r unavailr <- annexeval $ Types.Remote.mkUnavailable r
exportr <- annexeval $ Command.TestRemote.exportTreeVariant r exportr <- annexeval $ Command.TestRemote.exportTreeVariant r
ks <- annexeval $ mapM Command.TestRemote.randKey keysizes ks <- annexeval $ mapM Command.TestRemote.randKey keysizes
@ -245,7 +252,8 @@ testRemote = withResource newEmptyTMVarIO (const noop) $ \getv ->
go getv = Command.TestRemote.mkTestTrees runannex mkrs mkunavailr mkexportr mkks go getv = Command.TestRemote.mkTestTrees runannex mkrs mkunavailr mkexportr mkks
where where
runannex = inmainrepo . annexeval runannex = inmainrepo . annexeval
mkrs = [descas (remotetype ++ " remote") (fst <$> v)] mkrs = Command.TestRemote.remoteVariants mkr basesz False
mkr = descas (remotetype ++ " remote") (fst <$> v)
mkunavailr = fst . snd <$> v mkunavailr = fst . snd <$> v
mkexportr = fst . snd . snd <$> v mkexportr = fst . snd . snd <$> v
mkks = map (\(sz, n) -> desckeysize sz (getk n)) mkks = map (\(sz, n) -> desckeysize sz (getk n))

View file

@ -10,3 +10,5 @@ that could then be added to the test suite's TestTree.
(See [[bugs/testremote_failures_starting_with_aeca7c220]]) (See [[bugs/testremote_failures_starting_with_aeca7c220]])
--[[Joey]] --[[Joey]]
> [[done]] --[[Joey]]