2014-08-01 19:09:49 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2014 Joey Hess <id@joeyh.name>
|
2014-08-01 19:09:49 +00:00
|
|
|
-
|
|
|
|
- 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)
|
2015-10-01 17:28:49 +00:00
|
|
|
import Types.Backend (getKey, verifyKeyContent)
|
2014-08-01 19:09:49 +00:00
|
|
|
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
|
2015-07-11 04:42:32 +00:00
|
|
|
import Git.Types
|
2014-08-01 19:09:49 +00:00
|
|
|
|
|
|
|
import Test.Tasty
|
|
|
|
import Test.Tasty.Runners
|
|
|
|
import Test.Tasty.HUnit
|
|
|
|
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
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2015-07-11 04:42:32 +00:00
|
|
|
cmd = command "testremote" SectionTesting
|
|
|
|
"test transfers to/from a remote"
|
|
|
|
paramRemote (seek <$$> optParser)
|
2014-08-01 20:50:24 +00:00
|
|
|
|
2015-07-11 04:42:32 +00:00
|
|
|
data TestRemoteOptions = TestRemoteOptions
|
|
|
|
{ testRemote :: RemoteName
|
|
|
|
, sizeOption :: ByteSize
|
|
|
|
}
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2015-07-11 04:42:32 +00:00
|
|
|
optParser :: CmdParamsDesc -> Parser TestRemoteOptions
|
|
|
|
optParser desc = TestRemoteOptions
|
|
|
|
<$> argument str ( metavar desc )
|
|
|
|
<*> option (str >>= maybe (fail "parse error") return . readSize dataUnits)
|
|
|
|
( long "size" <> metavar paramSize
|
|
|
|
<> value (1024 * 1024)
|
|
|
|
<> help "base key size (default 1MiB)"
|
|
|
|
)
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2015-07-11 04:42:32 +00:00
|
|
|
seek :: TestRemoteOptions -> CommandSeek
|
|
|
|
seek o = commandAction $ start (fromInteger $ sizeOption o) (testRemote o)
|
|
|
|
|
|
|
|
start :: Int -> RemoteName -> CommandStart
|
|
|
|
start basesz name = do
|
2014-08-01 19:09:49 +00:00
|
|
|
showStart "testremote" name
|
|
|
|
r <- either error id <$> Remote.byName' name
|
2015-10-11 17:29:44 +00:00
|
|
|
showAction "generating test keys"
|
2014-08-03 22:08:34 +00:00
|
|
|
fast <- Annex.getState Annex.fast
|
|
|
|
ks <- mapM randKey (keySizes basesz fast)
|
|
|
|
rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz fast)
|
2014-08-01 21:52:40 +00:00
|
|
|
rs' <- concat <$> mapM encryptionVariants rs
|
2014-08-10 18:52:58 +00:00
|
|
|
unavailrs <- catMaybes <$> mapM Remote.mkUnavailable [r]
|
|
|
|
next $ perform rs' unavailrs ks
|
2014-08-01 19:09:49 +00:00
|
|
|
|
2014-08-10 18:52:58 +00:00
|
|
|
perform :: [Remote] -> [Remote] -> [Key] -> CommandPerform
|
|
|
|
perform rs unavailrs ks = do
|
2014-08-01 19:09:49 +00:00
|
|
|
st <- Annex.getState id
|
2014-08-10 18:52:58 +00:00
|
|
|
let tests = testGroup "Remote Tests" $ concat
|
|
|
|
[ [ testGroup "unavailable remote" (testUnavailable st r (Prelude.head ks)) | r <- unavailrs ]
|
|
|
|
, [ 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 21:52:40 +00:00
|
|
|
desc r' k = intercalate "; " $ map unwords
|
|
|
|
[ [ "key size", show (keySize k) ]
|
2014-08-03 19:35:23 +00:00
|
|
|
, [ show (getChunkConfig (Remote.config r')) ]
|
2014-08-01 21:52:40 +00:00
|
|
|
, ["encryption", fromMaybe "none" (M.lookup "encryption" (Remote.config r'))]
|
2014-08-01 20:50:24 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
adjustChunkSize :: Remote -> Int -> Annex (Maybe Remote)
|
2014-08-01 21:52:40 +00:00
|
|
|
adjustChunkSize r chunksize = adjustRemoteConfig r
|
|
|
|
(M.insert "chunk" (show chunksize))
|
|
|
|
|
|
|
|
-- Variants of a remote with no encryption, and with simple shared
|
|
|
|
-- encryption. Gpg key based encryption is not tested.
|
|
|
|
encryptionVariants :: Remote -> Annex [Remote]
|
|
|
|
encryptionVariants r = do
|
|
|
|
noenc <- adjustRemoteConfig r (M.insert "encryption" "none")
|
|
|
|
sharedenc <- adjustRemoteConfig r $
|
|
|
|
M.insert "encryption" "shared" .
|
|
|
|
M.insert "highRandomQuality" "false"
|
|
|
|
return $ catMaybes [noenc, sharedenc]
|
|
|
|
|
|
|
|
-- Regenerate a remote with a modified config.
|
|
|
|
adjustRemoteConfig :: Remote -> (Remote.RemoteConfig -> Remote.RemoteConfig) -> Annex (Maybe Remote)
|
|
|
|
adjustRemoteConfig r adjustconfig = Remote.generate (Remote.remotetype r)
|
2014-08-01 20:50:24 +00:00
|
|
|
(Remote.repo r)
|
|
|
|
(Remote.uuid r)
|
2014-08-01 21:52:40 +00:00
|
|
|
(adjustconfig (Remote.config r))
|
2014-08-01 20:50:24 +00:00
|
|
|
(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
|
2015-10-09 19:48:02 +00:00
|
|
|
lockContentForRemoval k removeAnnex
|
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
|
2015-10-09 19:48:02 +00:00
|
|
|
lockContentForRemoval k removeAnnex
|
2014-08-01 21:16:20 +00:00
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "retrieveKeyFile resume from 0" $ do
|
|
|
|
tmp <- prepTmp k
|
|
|
|
liftIO $ writeFile tmp ""
|
2015-10-09 19:48:02 +00:00
|
|
|
lockContentForRemoval k removeAnnex
|
2014-08-01 21:16:20 +00:00
|
|
|
get
|
|
|
|
, check "fsck downloaded object" fsck
|
|
|
|
, check "retrieveKeyFile resume from end" $ do
|
|
|
|
loc <- Annex.calcRepo (gitAnnexLocation k)
|
|
|
|
tmp <- prepTmp k
|
2014-08-27 00:06:43 +00:00
|
|
|
void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp
|
2015-10-09 19:48:02 +00:00
|
|
|
lockContentForRemoval k removeAnnex
|
2014-08-01 21:16:20 +00:00
|
|
|
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
|
2015-10-01 17:28:49 +00:00
|
|
|
Just b -> case verifyKeyContent b of
|
2014-08-01 21:16:20 +00:00
|
|
|
Nothing -> return True
|
2015-10-01 17:28:49 +00:00
|
|
|
Just verifier -> verifier k (key2file k)
|
Do verification of checksums of annex objects downloaded from remotes.
* When annex objects are received into git repositories, their checksums are
verified then too.
* To get the old, faster, behavior of not verifying checksums, set
annex.verify=false, or remote.<name>.annex-verify=false.
* setkey, rekey: These commands also now verify that the provided file
matches the key, unless annex.verify=false.
* reinject: Already verified content; this can now be disabled by
setting annex.verify=false.
recvkey and reinject already did verification, so removed now duplicate
code from them. fsck still does its own verification, which is ok since it
does not use getViaTmp, so verification doesn't happen twice when using fsck
--from.
2015-10-01 19:54:37 +00:00
|
|
|
get = getViaTmp (RemoteVerify r) k $ \dest ->
|
2014-08-01 21:16:20 +00:00
|
|
|
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-10 18:52:58 +00:00
|
|
|
testUnavailable :: Annex.AnnexState -> Remote -> Key -> [TestTree]
|
|
|
|
testUnavailable st r k =
|
|
|
|
[ check (== Right False) "removeKey" $
|
|
|
|
Remote.removeKey r k
|
|
|
|
, check (== Right False) "storeKey" $
|
|
|
|
Remote.storeKey r k Nothing nullMeterUpdate
|
|
|
|
, check (`notElem` [Right True, Right False]) "checkPresent" $
|
|
|
|
Remote.checkPresent r k
|
|
|
|
, check (== Right False) "retrieveKeyFile" $
|
Do verification of checksums of annex objects downloaded from remotes.
* When annex objects are received into git repositories, their checksums are
verified then too.
* To get the old, faster, behavior of not verifying checksums, set
annex.verify=false, or remote.<name>.annex-verify=false.
* setkey, rekey: These commands also now verify that the provided file
matches the key, unless annex.verify=false.
* reinject: Already verified content; this can now be disabled by
setting annex.verify=false.
recvkey and reinject already did verification, so removed now duplicate
code from them. fsck still does its own verification, which is ok since it
does not use getViaTmp, so verification doesn't happen twice when using fsck
--from.
2015-10-01 19:54:37 +00:00
|
|
|
getViaTmp (RemoteVerify r) k $ \dest ->
|
2014-08-10 18:52:58 +00:00
|
|
|
Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate
|
|
|
|
, check (== Right False) "retrieveKeyFileCheap" $
|
other 80% of avoding verification when hard linking to objects in shared repo
In c6632ee5c8e66c26ef18317f56ae02bae1e7e280, it actually only handled
uploading objects to a shared repository. To avoid verification when
downloading objects from a shared repository, was a lot harder.
On the plus side, if the process of downloading a file from a remote
is able to verify its content on the side, the remote can indicate this
now, and avoid the extra post-download verification.
As of yet, I don't have any remotes (except Git) using this ability.
Some more work would be needed to support it in special remotes.
It would make sense for tahoe to implicitly verify things downloaded from it;
as long as you trust your tahoe server (which typically runs locally),
there's cryptographic integrity. OTOH, despite bup being based on shas,
a bup repo under an attacker's control could have the git ref used for an
object changed, and so a bup repo shouldn't implicitly verify. Indeed,
tahoe seems unique in being trustworthy enough to implicitly verify.
2015-10-02 17:56:42 +00:00
|
|
|
getViaTmp (RemoteVerify r) k $ \dest -> unVerified $
|
2015-04-14 20:35:10 +00:00
|
|
|
Remote.retrieveKeyFileCheap r k Nothing dest
|
2014-08-10 18:52:58 +00:00
|
|
|
]
|
|
|
|
where
|
|
|
|
check checkval desc a = testCase desc $ do
|
|
|
|
v <- Annex.eval st $ do
|
|
|
|
Annex.setOutput QuietOutput
|
|
|
|
either (Left . show) Right <$> tryNonAsync a
|
|
|
|
checkval v @? ("(got: " ++ show v ++ ")")
|
|
|
|
|
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)
|
2015-10-09 19:48:02 +00:00
|
|
|
forM_ ks $ \k -> lockContentForRemoval k removeAnnex
|
2014-08-01 19:09:49 +00:00
|
|
|
return ok
|
|
|
|
|
2014-08-03 22:08:34 +00:00
|
|
|
chunkSizes :: Int -> Bool -> [Int]
|
|
|
|
chunkSizes base False =
|
2014-08-01 20:50:24 +00:00
|
|
|
[ 0 -- no chunking
|
|
|
|
, base `div` 100
|
|
|
|
, base `div` 1000
|
|
|
|
, base
|
|
|
|
]
|
2014-08-04 12:24:06 +00:00
|
|
|
chunkSizes _ True =
|
2014-08-03 22:08:34 +00:00
|
|
|
[ 0
|
|
|
|
]
|
2014-08-01 20:50:24 +00:00
|
|
|
|
2014-08-03 22:08:34 +00:00
|
|
|
keySizes :: Int -> Bool -> [Int]
|
|
|
|
keySizes base fast = filter want
|
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
|
|
|
]
|
2014-08-03 22:08:34 +00:00
|
|
|
where
|
|
|
|
want sz
|
|
|
|
| fast = sz <= base && sz > 0
|
|
|
|
| otherwise = sz > 0
|
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
|