summaryrefslogtreecommitdiff
path: root/Command/TestRemote.hs
blob: 6dde4b9f03f01ae757cf0ea44550de8b5e5c8241 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
{- 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
import qualified Types.Remote as Remote
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
import Utility.DataUnits
import Messages
import Types.Messages
import Remote.Helper.Chunked

import Test.Tasty
import Test.Tasty.Runners
import Test.Tasty.HUnit
import "crypto-api" Crypto.Random
import qualified Data.ByteString as B
import qualified Data.Map as M

def :: [Command]
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)"

seek :: CommandSeek
seek ps = do
	basesz <- fromInteger . fromMaybe (1024 * 1024)
		<$> getOptionField sizeOption (pure . getsize)
	withWords (start basesz) ps
  where
	getsize v = v >>= readSize dataUnits

start :: Int -> [String] -> CommandStart
start basesz ws = do
	let name = unwords ws
	showStart "testremote" name
	r <- either error id <$> Remote.byName' name
	showSideAction "generating test keys"
	ks <- mapM randKey (keySizes basesz)
	rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz)
	next $ perform rs ks

perform :: [Remote] -> [Key] -> CommandPerform
perform rs ks = do
	st <- Annex.getState id
	let tests = testGroup "Remote Tests" $
		[ testGroup (desc r k) (test st r k) | k <- ks, r <- rs ]
	ok <- case tryIngredients [consoleTestReporter] mempty tests of
		Nothing -> error "No tests found!?"
		Just act -> liftIO act
	next $ cleanup rs ks ok
  where
	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)

test :: Annex.AnnexState -> Remote -> Key -> [TestTree]
test st r k =
	[ check "removeKey when not present" $
		Remote.removeKey r k
	, present False
	, check "storeKey" $
		Remote.storeKey r k Nothing nullMeterUpdate
	, present True
	, check "storeKey when already present" $
		Remote.storeKey r k Nothing nullMeterUpdate
	, present True
	, check "retrieveKeyFile" $ do
		removeAnnex k
		getViaTmp k $ \dest ->
			Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate
	, check "fsck downloaded object" $ do
		case maybeLookupBackendName (keyBackendName k) of
			Nothing -> return True
			Just b -> case fsckKey b of
				Nothing -> return True
				Just fscker -> fscker k (key2file k)
	, check "removeKey when present" $
		Remote.removeKey r k
	, 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

cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
cleanup rs ks ok = do
	forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
	forM_ ks removeAnnex
	return ok

chunkSizes :: Int -> [Int]
chunkSizes base = 
	[ 0 -- no chunking
	, base `div` 100
	, base `div` 1000
	, base
	]

keySizes :: Int -> [Int]
keySizes base = filter (>= 0)
	[ 0 -- empty key is a special case when chunking
	, base
	, base + 1
	, base - 1
	, base * 2
	]

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