improve testremote command, adding chunk size testing
And also a --size parameter to configure the basic object size.
This commit is contained in:
parent
f4f82e2741
commit
20d7295386
2 changed files with 62 additions and 28 deletions
|
@ -11,6 +11,7 @@ import Common
|
||||||
import Command
|
import Command
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
import qualified Types.Remote as Remote
|
||||||
import Types
|
import Types
|
||||||
import Types.Key (key2file, keyBackendName, keySize)
|
import Types.Key (key2file, keyBackendName, keySize)
|
||||||
import Types.Backend (getKey, fsckKey)
|
import Types.Backend (getKey, fsckKey)
|
||||||
|
@ -20,45 +21,72 @@ import Backend
|
||||||
import qualified Backend.Hash
|
import qualified Backend.Hash
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
|
import Utility.DataUnits
|
||||||
import Messages
|
import Messages
|
||||||
import Types.Messages
|
import Types.Messages
|
||||||
|
import Remote.Helper.Chunked
|
||||||
|
|
||||||
import Test.Tasty
|
import Test.Tasty
|
||||||
import Test.Tasty.Runners
|
import Test.Tasty.Runners
|
||||||
import Test.Tasty.HUnit
|
import Test.Tasty.HUnit
|
||||||
import "crypto-api" Crypto.Random
|
import "crypto-api" Crypto.Random
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
|
import qualified Data.Map as M
|
||||||
|
|
||||||
def :: [Command]
|
def :: [Command]
|
||||||
def = [ command "testremote" paramRemote seek SectionTesting
|
def = [ withOptions [sizeOption] $
|
||||||
"test transfers to/from a remote"]
|
command "testremote" paramRemote seek SectionTesting
|
||||||
|
"test transfers to/from a remote"]
|
||||||
|
|
||||||
|
sizeOption :: Option
|
||||||
|
sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)"
|
||||||
|
|
||||||
seek :: CommandSeek
|
seek :: CommandSeek
|
||||||
seek = withWords start
|
seek ps = do
|
||||||
|
basesz <- fromInteger . fromMaybe (1024 * 1024)
|
||||||
|
<$> getOptionField sizeOption (pure . getsize)
|
||||||
|
withWords (start basesz) ps
|
||||||
|
where
|
||||||
|
getsize v = v >>= readSize dataUnits
|
||||||
|
|
||||||
start :: [String] -> CommandStart
|
start :: Int -> [String] -> CommandStart
|
||||||
start ws = do
|
start basesz ws = do
|
||||||
let name = unwords ws
|
let name = unwords ws
|
||||||
showStart "testremote" name
|
showStart "testremote" name
|
||||||
r <- either error id <$> Remote.byName' name
|
r <- either error id <$> Remote.byName' name
|
||||||
showSideAction "generating test keys"
|
showSideAction "generating test keys"
|
||||||
ks <- testKeys
|
ks <- mapM randKey (keySizes basesz)
|
||||||
next $ perform r ks
|
rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz)
|
||||||
|
next $ perform rs ks
|
||||||
|
|
||||||
perform :: Remote -> [Key] -> CommandPerform
|
perform :: [Remote] -> [Key] -> CommandPerform
|
||||||
perform r ks = do
|
perform rs ks = do
|
||||||
st <- Annex.getState id
|
st <- Annex.getState id
|
||||||
let tests = testGroup "Remote Tests" $
|
let tests = testGroup "Remote Tests" $
|
||||||
map (\k -> testGroup (descSize k) (testList st r k)) ks
|
[ testGroup (desc r k) (test st r k) | k <- ks, r <- rs ]
|
||||||
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
|
||||||
next $ cleanup r ks ok
|
next $ cleanup rs ks ok
|
||||||
where
|
where
|
||||||
descSize k = "key size " ++ show (keySize k)
|
desc r' k = unwords
|
||||||
|
[ "key size"
|
||||||
|
, show (keySize k)
|
||||||
|
, "chunk size"
|
||||||
|
, show (chunkConfig (Remote.config r'))
|
||||||
|
]
|
||||||
|
|
||||||
testList :: Annex.AnnexState -> Remote -> Key -> [TestTree]
|
-- To adjust a Remote to use a new chunk size, have to re-generate it with
|
||||||
testList st r k =
|
-- a modified config.
|
||||||
|
adjustChunkSize :: Remote -> Int -> Annex (Maybe Remote)
|
||||||
|
adjustChunkSize r chunksize = Remote.generate (Remote.remotetype r)
|
||||||
|
(Remote.repo r)
|
||||||
|
(Remote.uuid r)
|
||||||
|
(M.insert "chunk" (show chunksize) (Remote.config r))
|
||||||
|
(Remote.gitconfig r)
|
||||||
|
|
||||||
|
test :: Annex.AnnexState -> Remote -> Key -> [TestTree]
|
||||||
|
test st r k =
|
||||||
[ check "removeKey when not present" $
|
[ check "removeKey when not present" $
|
||||||
Remote.removeKey r k
|
Remote.removeKey r k
|
||||||
, present False
|
, present False
|
||||||
|
@ -88,24 +116,28 @@ testList st r k =
|
||||||
present b = check ("present " ++ show b) $
|
present b = check ("present " ++ show b) $
|
||||||
(== Right b) <$> Remote.hasKey r k
|
(== Right b) <$> Remote.hasKey r k
|
||||||
|
|
||||||
cleanup :: Remote -> [Key] -> Bool -> CommandCleanup
|
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
||||||
cleanup r ks ok = do
|
cleanup rs ks ok = do
|
||||||
forM_ ks (Remote.removeKey r)
|
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
||||||
forM_ ks removeAnnex
|
forM_ ks removeAnnex
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
-- Generate random keys of several interesting sizes, assuming a chunk
|
chunkSizes :: Int -> [Int]
|
||||||
-- size that is a uniform divisor of 1 MB.
|
chunkSizes base =
|
||||||
testKeys :: Annex [Key]
|
[ 0 -- no chunking
|
||||||
testKeys = mapM randKey
|
, base `div` 100
|
||||||
[ 0 -- empty key is a special case when chunking
|
, base `div` 1000
|
||||||
, mb
|
, base
|
||||||
, mb + 1
|
]
|
||||||
, mb - 1
|
|
||||||
, mb + mb
|
keySizes :: Int -> [Int]
|
||||||
|
keySizes base = filter (>= 0)
|
||||||
|
[ 0 -- empty key is a special case when chunking
|
||||||
|
, base
|
||||||
|
, base + 1
|
||||||
|
, base - 1
|
||||||
|
, base * 2
|
||||||
]
|
]
|
||||||
where
|
|
||||||
mb = 1024 * 2014
|
|
||||||
|
|
||||||
randKey :: Int -> Annex Key
|
randKey :: Int -> Annex Key
|
||||||
randKey sz = withTmpFile "randkey" $ \f h -> do
|
randKey sz = withTmpFile "randkey" $ \f h -> do
|
||||||
|
|
|
@ -974,6 +974,8 @@ subdirectories).
|
||||||
It's safe to run in an existing repository (the repository contents are
|
It's safe to run in an existing repository (the repository contents are
|
||||||
not altered), although it may perform expensive data transfers.
|
not altered), although it may perform expensive data transfers.
|
||||||
|
|
||||||
|
The --size option can be used to tune the size of the generated objects.
|
||||||
|
|
||||||
* `fuzztest`
|
* `fuzztest`
|
||||||
|
|
||||||
Generates random changes to files in the current repository,
|
Generates random changes to files in the current repository,
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue