2014-08-01 19:09:49 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
|
|
|
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.TestRemote where
|
|
|
|
|
|
|
|
import Common
|
|
|
|
import Command
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Remote
|
2014-08-01 20:50:24 +00:00
|
|
|
import qualified Types.Remote as Remote
|
2014-08-01 19:09:49 +00:00
|
|
|
import Types
|
|
|
|
import Types.Key (key2file, keyBackendName, keySize)
|
|
|
|
import Types.Backend (getKey, fsckKey)
|
|
|
|
import Types.KeySource
|
|
|
|
import Annex.Content
|
|
|
|
import Backend
|
|
|
|
import qualified Backend.Hash
|
|
|
|
import Utility.Tmp
|
|
|
|
import Utility.Metered
|
2014-08-01 20:50:24 +00:00
|
|
|
import Utility.DataUnits
|
2014-08-01 21:16:20 +00:00
|
|
|
import Utility.CopyFile
|
2014-08-01 19:09:49 +00:00
|
|
|
import Messages
|
|
|
|
import Types.Messages
|
2014-08-01 20:50:24 +00:00
|
|
|
import Remote.Helper.Chunked
|
2014-08-01 21:16:20 +00:00
|
|
|
import Locations
|
2014-08-01 19:09:49 +00:00
|
|
|
|
|
|
|
import Test.Tasty
|
|
|
|
import Test.Tasty.Runners
|
|
|
|
import Test.Tasty.HUnit
|
2014-08-01 21:16:20 +00:00
|
|
|
import Control.Exception
|
2014-08-01 19:09:49 +00:00
|
|
|
import "crypto-api" Crypto.Random
|
|
|
|
import qualified Data.ByteString as B
|
2014-08-01 21:16:20 +00:00
|
|
|
import qualified Data.ByteString.Lazy as L
|
2014-08-01 20:50:24 +00:00
|
|
|
import qualified Data.Map as M
|
2014-08-01 19:09:49 +00:00
|
|
|
|
|
|
|
def :: [Command]
|
2014-08-01 20:50:24 +00:00
|
|
|
def = [ withOptions [sizeOption] $
|
|
|
|
command "testremote" paramRemote seek SectionTesting
|
|
|
|
"test transfers to/from a remote"]
|
|
|
|
|
|
|
|
sizeOption :: Option
|
|
|
|
sizeOption = fieldOption [] "size" paramSize "base key size (default 1MiB)"
|
2014-08-01 19:09:49 +00:00
|
|
|
|
|
|
|
seek :: CommandSeek
|
2014-08-01 20:50:24 +00:00
|
|
|
seek ps = do
|
|
|
|
basesz <- fromInteger . fromMaybe (1024 * 1024)
|
|
|
|
<$> getOptionField sizeOption (pure . getsize)
|
|
|
|
withWords (start basesz) ps
|
|
|
|
where
|
|
|
|
getsize v = v >>= readSize dataUnits
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2014-08-01 20:50:24 +00:00
|
|
|
start :: Int -> [String] -> CommandStart
|
|
|
|
start basesz ws = do
|
2014-08-01 19:09:49 +00:00
|
|
|
let name = unwords ws
|
|
|
|
showStart "testremote" name
|
|
|
|
r <- either error id <$> Remote.byName' name
|
|
|
|
showSideAction "generating test keys"
|
2014-08-01 20:50:24 +00:00
|
|
|
ks <- mapM randKey (keySizes basesz)
|
|
|
|
rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz)
|
|
|
|
next $ perform rs ks
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2014-08-01 20:50:24 +00:00
|
|
|
perform :: [Remote] -> [Key] -> CommandPerform
|
|
|
|
perform rs ks = do
|
2014-08-01 19:09:49 +00:00
|
|
|
st <- Annex.getState id
|
|
|
|
let tests = testGroup "Remote Tests" $
|
2014-08-01 20:50:24 +00:00
|
|
|
[ testGroup (desc r k) (test st r k) | k <- ks, r <- rs ]
|
2014-08-01 19:09:49 +00:00
|
|
|
ok <- case tryIngredients [consoleTestReporter] mempty tests of
|
|
|
|
Nothing -> error "No tests found!?"
|
|
|
|
Just act -> liftIO act
|
2014-08-01 20:50:24 +00:00
|
|
|
next $ cleanup rs ks ok
|
2014-08-01 19:09:49 +00:00
|
|
|
where
|
2014-08-01 20:50:24 +00:00
|
|
|
desc r' k = unwords
|
|
|
|
[ "key size"
|
|
|
|
, show (keySize k)
|
|
|
|
, "chunk size"
|
|
|
|
, show (chunkConfig (Remote.config r'))
|
|
|
|
]
|
|
|
|
|
|
|
|
-- To adjust a Remote to use a new chunk size, have to re-generate it with
|
|
|
|
-- 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)
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2014-08-01 20:50:24 +00:00
|
|
|
test :: Annex.AnnexState -> Remote -> Key -> [TestTree]
|
|
|
|
test st r k =
|
2014-08-01 21:16:20 +00:00
|
|
|
[ check "removeKey when not present" remove
|
2014-08-01 19:09:49 +00:00
|
|
|
, present False
|
2014-08-01 21:16:20 +00:00
|
|
|
, check "storeKey" store
|
2014-08-01 19:09:49 +00:00
|
|
|
, present True
|
2014-08-01 21:16:20 +00:00
|
|
|
, check "storeKey when already present" store
|
2014-08-01 19:09:49 +00:00
|
|
|
, present True
|
|
|
|
, check "retrieveKeyFile" $ do
|
|
|
|
removeAnnex k
|
2014-08-01 21:16:20 +00:00
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "retrieveKeyFile resume from 33%" $ do
|
|
|
|
loc <- Annex.calcRepo (gitAnnexLocation k)
|
|
|
|
tmp <- prepTmp k
|
|
|
|
partial <- liftIO $ bracket (openBinaryFile loc ReadMode) hClose $ \h -> do
|
|
|
|
sz <- hFileSize h
|
|
|
|
L.hGet h $ fromInteger $ sz `div` 3
|
|
|
|
liftIO $ L.writeFile tmp partial
|
|
|
|
removeAnnex k
|
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "retrieveKeyFile resume from 0" $ do
|
|
|
|
tmp <- prepTmp k
|
|
|
|
liftIO $ writeFile tmp ""
|
|
|
|
removeAnnex k
|
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "retrieveKeyFile resume from end" $ do
|
|
|
|
loc <- Annex.calcRepo (gitAnnexLocation k)
|
|
|
|
tmp <- prepTmp k
|
|
|
|
void $ liftIO $ copyFileExternal loc tmp
|
|
|
|
removeAnnex k
|
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "removeKey when present" remove
|
2014-08-01 19:09:49 +00:00
|
|
|
, present False
|
|
|
|
]
|
|
|
|
where
|
|
|
|
check desc a = testCase desc $
|
|
|
|
Annex.eval st (Annex.setOutput QuietOutput >> a) @? "failed"
|
|
|
|
present b = check ("present " ++ show b) $
|
|
|
|
(== Right b) <$> Remote.hasKey r k
|
2014-08-01 21:16:20 +00:00
|
|
|
fsck = case maybeLookupBackendName (keyBackendName k) of
|
|
|
|
Nothing -> return True
|
|
|
|
Just b -> case fsckKey b of
|
|
|
|
Nothing -> return True
|
|
|
|
Just fscker -> fscker k (key2file k)
|
|
|
|
get = getViaTmp k $ \dest ->
|
|
|
|
Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate
|
|
|
|
store = Remote.storeKey r k Nothing nullMeterUpdate
|
|
|
|
remove = Remote.removeKey r k
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2014-08-01 20:50:24 +00:00
|
|
|
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
|
|
|
cleanup rs ks ok = do
|
|
|
|
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
2014-08-01 19:09:49 +00:00
|
|
|
forM_ ks removeAnnex
|
|
|
|
return ok
|
|
|
|
|
2014-08-01 20:50:24 +00:00
|
|
|
chunkSizes :: Int -> [Int]
|
|
|
|
chunkSizes base =
|
|
|
|
[ 0 -- no chunking
|
|
|
|
, base `div` 100
|
|
|
|
, base `div` 1000
|
|
|
|
, base
|
|
|
|
]
|
|
|
|
|
|
|
|
keySizes :: Int -> [Int]
|
|
|
|
keySizes base = filter (>= 0)
|
2014-08-01 19:09:49 +00:00
|
|
|
[ 0 -- empty key is a special case when chunking
|
2014-08-01 20:50:24 +00:00
|
|
|
, base
|
|
|
|
, base + 1
|
|
|
|
, base - 1
|
|
|
|
, base * 2
|
2014-08-01 19:09:49 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
randKey :: Int -> Annex Key
|
|
|
|
randKey sz = withTmpFile "randkey" $ \f h -> do
|
|
|
|
gen <- liftIO (newGenIO :: IO SystemRandom)
|
|
|
|
case genBytes sz gen of
|
|
|
|
Left e -> error $ "failed to generate random key: " ++ show e
|
|
|
|
Right (rand, _) -> liftIO $ B.hPut h rand
|
|
|
|
liftIO $ hClose h
|
|
|
|
let ks = KeySource
|
|
|
|
{ keyFilename = f
|
|
|
|
, contentLocation = f
|
|
|
|
, inodeCache = Nothing
|
|
|
|
}
|
|
|
|
k <- fromMaybe (error "failed to generate random key")
|
|
|
|
<$> getKey Backend.Hash.testKeyBackend ks
|
|
|
|
moveAnnex k f
|
|
|
|
return k
|