summaryrefslogtreecommitdiff
path: root/Remote/External.hs
blob: f88b069be63f9001608f0ae92bbabe7e20dbe240 (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
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
{- External special remote interface.
 -
 - Copyright 2013-2015 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

module Remote.External (remote) where

import Remote.External.Types
import qualified Annex
import Annex.Common
import Types.Remote
import Types.CleanupActions
import Types.UrlContents
import qualified Git
import Config
import Git.Config (isTrue, boolConfig)
import Git.Env
import Remote.Helper.Special
import Remote.Helper.ReadOnly
import Remote.Helper.Messages
import Utility.Metered
import Messages.Progress
import Types.Transfer
import Logs.PreferredContent.Raw
import Logs.RemoteState
import Logs.Web
import Config.Cost
import Annex.Content
import Annex.Url
import Annex.UUID
import Creds

import Control.Concurrent.STM
import Control.Concurrent.Async
import System.Log.Logger (debugM)
import qualified Data.Map as M

remote :: RemoteType
remote = RemoteType {
	typename = "external",
	enumerate = const (findSpecialRemotes "externaltype"),
	generate = gen,
	setup = externalSetup
}

gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
gen r u c gc
	-- readonly mode only downloads urls; does not use external program
	| remoteAnnexReadOnly gc = do
		cst <- remoteCost gc expensiveRemoteCost
		mk cst GloballyAvailable
			readonlyStorer
			retrieveUrl
			readonlyRemoveKey
			(checkKeyUrl r)
			Nothing
			Nothing
			Nothing
	| otherwise = do
		external <- newExternal externaltype u c gc
		Annex.addCleanup (RemoteCleanup u) $ stopExternal external
		cst <- getCost external r gc
		avail <- getAvailability external r gc
		mk cst avail
			(store external)
			(retrieve external)
			(remove external)
			(checkKey external)
			(Just (whereis external))
			(Just (claimurl external))
			(Just (checkurl external))
  where
	mk cst avail tostore toretrieve toremove tocheckkey towhereis toclaimurl tocheckurl = do
		let rmt = Remote
			{ uuid = u
			, cost = cst
			, name = Git.repoDescribe r
			, storeKey = storeKeyDummy
			, retrieveKeyFile = retreiveKeyFileDummy
			, retrieveKeyFileCheap = \_ _ _ -> return False
			, removeKey = removeKeyDummy
			, lockContent = Nothing
			, checkPresent = checkPresentDummy
			, checkPresentCheap = False
			, whereisKey = towhereis
			, remoteFsck = Nothing
			, repairRepo = Nothing
			, config = c
			, localpath = Nothing
			, repo = r
			, gitconfig = gc
			, readonly = False
			, availability = avail
			, remotetype = remote
			, mkUnavailable = gen r u c $
				gc { remoteAnnexExternalType = Just "!dne!" }
			, getInfo = return [("externaltype", externaltype)]
			, claimUrl = toclaimurl
			, checkUrl = tocheckurl
			}
		return $ Just $ specialRemote c
			(simplyPrepare tostore)
			(simplyPrepare toretrieve)
			(simplyPrepare toremove)
			(simplyPrepare tocheckkey)
			rmt
	externaltype = fromMaybe (error "missing externaltype") (remoteAnnexExternalType gc)

externalSetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
externalSetup mu _ c gc = do
	u <- maybe (liftIO genUUID) return mu
	let externaltype = fromMaybe (error "Specify externaltype=") $
		M.lookup "externaltype" c
	(c', _encsetup) <- encryptionSetup c gc

	c'' <- case M.lookup "readonly" c of
		Just v | isTrue v == Just True -> do
			setConfig (remoteConfig (fromJust (M.lookup "name" c)) "readonly") (boolConfig True)
			return c'
		_ -> do
			external <- newExternal externaltype u c' gc
			handleRequest external INITREMOTE Nothing $ \resp -> case resp of
				INITREMOTE_SUCCESS -> Just noop
				INITREMOTE_FAILURE errmsg -> Just $ error errmsg
				_ -> Nothing
			liftIO $ atomically $ readTMVar $ externalConfig external

	gitConfigSpecialRemote u c'' "externaltype" externaltype
	return (c'', u)

store :: External -> Storer
store external = fileStorer $ \k f p ->
	handleRequest external (TRANSFER Upload k f) (Just p) $ \resp ->
		case resp of
			TRANSFER_SUCCESS Upload k' | k == k' ->
				Just $ return True
			TRANSFER_FAILURE Upload k' errmsg | k == k' ->
				Just $ do
					warning errmsg
					return False
			_ -> Nothing

retrieve :: External -> Retriever
retrieve external = fileRetriever $ \d k p -> 
	handleRequest external (TRANSFER Download k d) (Just p) $ \resp ->
		case resp of
			TRANSFER_SUCCESS Download k'
				| k == k' -> Just $ return ()
			TRANSFER_FAILURE Download k' errmsg
				| k == k' -> Just $ do
					error errmsg
			_ -> Nothing

remove :: External -> Remover
remove external k = safely $ 
	handleRequest external (REMOVE k) Nothing $ \resp ->
		case resp of
			REMOVE_SUCCESS k'
				| k == k' -> Just $ return True
			REMOVE_FAILURE k' errmsg
				| k == k' -> Just $ do
					warning errmsg
					return False
			_ -> Nothing

checkKey :: External -> CheckPresent
checkKey external k = either error id <$> go
  where
	go = handleRequest external (CHECKPRESENT k) Nothing $ \resp ->
		case resp of
			CHECKPRESENT_SUCCESS k'
				| k' == k -> Just $ return $ Right True
			CHECKPRESENT_FAILURE k'
				| k' == k -> Just $ return $ Right False
			CHECKPRESENT_UNKNOWN k' errmsg
				| k' == k -> Just $ return $ Left errmsg
			_ -> Nothing

whereis :: External -> Key -> Annex [String]
whereis external k = handleRequest external (WHEREIS k) Nothing $ \resp -> case resp of
	WHEREIS_SUCCESS s -> Just $ return [s]
	WHEREIS_FAILURE -> Just $ return []
	UNSUPPORTED_REQUEST -> Just $ return []
	_ -> Nothing

safely :: Annex Bool -> Annex Bool
safely a = go =<< tryNonAsync a
  where
	go (Right r) = return r
	go (Left e) = do
		warning $ show e
		return False

{- Sends a Request to the external remote, and waits for it to generate
 - a Response. That is fed into the responsehandler, which should return
 - the action to run for it (or Nothing if there's a protocol error).
 -
 - While the external remote is processing the Request, it may send
 - any number of RemoteRequests, that are handled here.
 -
 - Only one request can be made at a time, so locking is used.
 -
 - May throw exceptions, for example on protocol errors, or
 - when the repository cannot be used.
 -}
handleRequest :: External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
handleRequest external req mp responsehandler = 
	withExternalLock external $ \lck ->
		handleRequest' lck external req mp responsehandler

handleRequest' :: ExternalLock -> External -> Request -> Maybe MeterUpdate -> (Response -> Maybe (Annex a)) -> Annex a
handleRequest' lck external req mp responsehandler
	| needsPREPARE req = do
		checkPrepared lck external
		go
	| otherwise = go
  where
	go = do
		sendMessage lck external req
		loop
	loop = receiveMessage lck external responsehandler
		(\rreq -> Just $ handleRemoteRequest rreq >> loop)
		(\msg -> Just $ handleAsyncMessage msg >> loop)

	handleRemoteRequest (PROGRESS bytesprocessed) =
		maybe noop (\a -> liftIO $ a bytesprocessed) mp
	handleRemoteRequest (DIRHASH k) = 
		send $ VALUE $ hashDirMixed def k
	handleRemoteRequest (DIRHASH_LOWER k) = 
		send $ VALUE $ hashDirLower def k
	handleRemoteRequest (SETCONFIG setting value) =
		liftIO $ atomically $ do
			let v = externalConfig external
			m <- takeTMVar v
			putTMVar v $ M.insert setting value m
	handleRemoteRequest (GETCONFIG setting) = do
		value <- fromMaybe "" . M.lookup setting
			<$> liftIO (atomically $ readTMVar $ externalConfig external)
		send $ VALUE value
	handleRemoteRequest (SETCREDS setting login password) = do
		c <- liftIO $ atomically $ readTMVar $ externalConfig external
		gc <- liftIO $ atomically $ readTMVar $ externalGitConfig external
		c' <- setRemoteCredPair encryptionAlreadySetup c gc (credstorage setting) $
			Just (login, password)
		void $ liftIO $ atomically $ swapTMVar (externalConfig external) c'
	handleRemoteRequest (GETCREDS setting) = do
		c <- liftIO $ atomically $ readTMVar $ externalConfig external
		gc <- liftIO $ atomically $ readTMVar $ externalGitConfig external
		creds <- fromMaybe ("", "") <$> 
			getRemoteCredPair c gc (credstorage setting)
		send $ CREDS (fst creds) (snd creds)
	handleRemoteRequest GETUUID = send $
		VALUE $ fromUUID $ externalUUID external
	handleRemoteRequest GETGITDIR = send . VALUE =<< fromRepo Git.localGitDir
	handleRemoteRequest (SETWANTED expr) =
		preferredContentSet (externalUUID external) expr
	handleRemoteRequest GETWANTED = do
		expr <- fromMaybe "" . M.lookup (externalUUID external)
			<$> preferredContentMapRaw
		send $ VALUE expr
	handleRemoteRequest (SETSTATE key state) =
		setRemoteState (externalUUID external) key state
	handleRemoteRequest (GETSTATE key) = do
		state <- fromMaybe ""
			<$> getRemoteState (externalUUID external) key
		send $ VALUE state
	handleRemoteRequest (SETURLPRESENT key url) =
		setUrlPresent (externalUUID external) key url
	handleRemoteRequest (SETURLMISSING key url) =
		setUrlMissing (externalUUID external) key url
	handleRemoteRequest (SETURIPRESENT key uri) =
		withurl (SETURLPRESENT key) uri
	handleRemoteRequest (SETURIMISSING key uri) =
		withurl (SETURLMISSING key) uri
	handleRemoteRequest (GETURLS key prefix) = do
		mapM_ (send . VALUE) =<< getUrlsWithPrefix key prefix
		send (VALUE "") -- end of list
	handleRemoteRequest (DEBUG msg) = liftIO $ debugM "external" msg
	handleRemoteRequest (VERSION _) =
		sendMessage lck external $ ERROR "too late to send VERSION"

	handleAsyncMessage (ERROR err) = error $ "external special remote error: " ++ err

	send = sendMessage lck external

	credstorage setting = CredPairStorage
		{ credPairFile = base
		, credPairEnvironment = (base ++ "login", base ++ "password")
		, credPairRemoteKey = Just setting
		}
	  where
		base = replace "/" "_" $ fromUUID (externalUUID external) ++ "-" ++ setting
			
	withurl mk uri = handleRemoteRequest $ mk $
		setDownloader (show uri) OtherDownloader

sendMessage :: Sendable m => ExternalLock -> External -> m -> Annex ()
sendMessage lck external m = 
	fromExternal lck external externalSend $ \h ->
		liftIO $ do
			protocolDebug external True line
			hPutStrLn h line
			hFlush h
  where
	line = unwords $ formatMessage m

{- Waits for a message from the external remote, and passes it to the
 - apppropriate handler. 
 -
 - If the handler returns Nothing, this is a protocol error.-}
receiveMessage
	:: ExternalLock
	-> External 
	-> (Response -> Maybe (Annex a))
	-> (RemoteRequest -> Maybe (Annex a))
	-> (AsyncMessage -> Maybe (Annex a))
	-> Annex a
receiveMessage lck external handleresponse handlerequest handleasync =
	go =<< fromExternal lck external externalReceive
		(liftIO . catchMaybeIO . hGetLine)
  where
	go Nothing = protocolError False ""
	go (Just s) = do
		liftIO $ protocolDebug external False s
		case parseMessage s :: Maybe Response of
			Just resp -> maybe (protocolError True s) id (handleresponse resp)
			Nothing -> case parseMessage s :: Maybe RemoteRequest of
				Just req -> maybe (protocolError True s) id (handlerequest req)
				Nothing -> case parseMessage s :: Maybe AsyncMessage of
					Just msg -> maybe (protocolError True s) id (handleasync msg)
					Nothing -> protocolError False s
	protocolError parsed s = error $ "external special remote protocol error, unexpectedly received \"" ++ s ++ "\" " ++
		if parsed then "(command not allowed at this time)" else "(unable to parse command)"

protocolDebug :: External -> Bool -> String -> IO ()
protocolDebug external sendto line = debugM "external" $ unwords
	[ externalRemoteProgram (externalType external)
	, if sendto then "<--" else "-->"
	, line
	]

{- Starts up the external remote if it's not yet running,
 - and passes a value extracted from its state to an action.
 -}
fromExternal :: ExternalLock -> External -> (ExternalState -> v) -> (v -> Annex a) -> Annex a
fromExternal lck external extractor a =
	go =<< liftIO (atomically (tryReadTMVar v))
  where
	go (Just st) = run st
	go Nothing = do
		st <- startExternal $ externalType external
		void $ liftIO $ atomically $ do
			void $ tryReadTMVar v
			putTMVar v st

		{- Handle initial protocol startup; check the VERSION
		 - the remote sends. -}
		receiveMessage lck external
			(const Nothing)
			(checkVersion lck external)
			(const Nothing)

		run st

	run st = a $ extractor st
	v = externalState external

{- Starts an external remote process running, but does not handle checking
 - VERSION, etc. -}
startExternal :: ExternalType -> Annex ExternalState
startExternal externaltype = do
	errrelayer <- mkStderrRelayer
	g <- Annex.gitRepo
	liftIO $ do
		p <- propgit g cmdp
		(Just hin, Just hout, Just herr, pid) <- 
			createProcess p `catchIO` runerr
		fileEncoding hin
		fileEncoding hout
		fileEncoding herr
		stderrelay <- async $ errrelayer herr
		checkearlytermination =<< getProcessExitCode pid
		return $ ExternalState
			{ externalSend = hin
			, externalReceive = hout
			, externalShutdown = do
				cancel stderrelay
				void $ waitForProcess pid
			, externalPrepared = Unprepared
			}
  where
	cmd = externalRemoteProgram externaltype
	cmdp = (proc cmd [])
		{ std_in = CreatePipe
		, std_out = CreatePipe
		, std_err = CreatePipe
		}
	propgit g p = do
		environ <- propGitEnv g
		return $ p { env = Just environ }

	runerr _ = error ("Cannot run " ++ cmd ++ " -- Make sure it's in your PATH and is executable.")

	checkearlytermination Nothing = noop
	checkearlytermination (Just exitcode) = ifM (inPath cmd)
		( error $ unwords [ "failed to run", cmd, "(" ++ show exitcode ++ ")" ]
		, do
			path <- intercalate ":" <$> getSearchPath
			error $ cmd ++ " is not installed in PATH (" ++ path ++ ")"
		)

stopExternal :: External -> Annex ()
stopExternal external = liftIO $ stop =<< atomically (tryReadTMVar v)
  where
	stop Nothing = noop
	stop (Just st) = do
		void $ atomically $ tryTakeTMVar v
		hClose $ externalSend st
		hClose $ externalReceive st
		externalShutdown st
	v = externalState external

externalRemoteProgram :: ExternalType -> String
externalRemoteProgram externaltype = "git-annex-remote-" ++ externaltype

checkVersion :: ExternalLock -> External -> RemoteRequest -> Maybe (Annex ())
checkVersion lck external (VERSION v) = Just $
	if v `elem` supportedProtocolVersions
		then noop
		else sendMessage lck external (ERROR "unsupported VERSION")
checkVersion _ _ _ = Nothing

{- If repo has not been prepared, sends PREPARE.
 -
 - If the repo fails to prepare, or failed before, throws an exception with
 - the error message. -}
checkPrepared :: ExternalLock -> External -> Annex ()
checkPrepared lck external = 
	fromExternal lck external externalPrepared $ \prepared ->
		case prepared of
			Prepared -> noop
			FailedPrepare errmsg -> error errmsg
			Unprepared -> 
				handleRequest' lck external PREPARE Nothing $ \resp ->
					case resp of
						PREPARE_SUCCESS -> Just $
							setprepared Prepared
						PREPARE_FAILURE errmsg -> Just $ do
							setprepared $ FailedPrepare errmsg
							error errmsg
						_ -> Nothing
  where
	setprepared status = liftIO . atomically $ do
		let v = externalState external
		st <- takeTMVar v
		void $ putTMVar v $ st { externalPrepared = status }

{- Caches the cost in the git config to avoid needing to start up an
 - external special remote every time time just to ask it what its
 - cost is. -}
getCost :: External -> Git.Repo -> RemoteGitConfig -> Annex Cost
getCost external r gc = catchNonAsync (go =<< remoteCost' gc) (const defcst)
  where
	go (Just c) = return c
	go Nothing = do
		c <- handleRequest external GETCOST Nothing $ \req -> case req of
			COST c -> Just $ return c
			UNSUPPORTED_REQUEST -> Just defcst
			_ -> Nothing
		setRemoteCost r c
		return c
	defcst = return expensiveRemoteCost

{- Caches the availability in the git config to avoid needing to start up an
 - external special remote every time time just to ask it what its
 - availability is.
 -
 - Most remotes do not bother to implement a reply to this request;
 - globally available is the default.
 -}
getAvailability :: External -> Git.Repo -> RemoteGitConfig -> Annex Availability
getAvailability external r gc = 
	maybe (catchNonAsync query (const defavail)) return (remoteAnnexAvailability gc)
  where
	query = do
		avail <- handleRequest external GETAVAILABILITY Nothing $ \req -> case req of
			AVAILABILITY avail -> Just $ return avail
			UNSUPPORTED_REQUEST -> Just defavail
			_ -> Nothing
		setRemoteAvailability r avail
		return avail
	defavail = return GloballyAvailable

claimurl :: External -> URLString -> Annex Bool
claimurl external url =
	handleRequest external (CLAIMURL url) Nothing $ \req -> case req of
		CLAIMURL_SUCCESS -> Just $ return True
		CLAIMURL_FAILURE -> Just $ return False
		UNSUPPORTED_REQUEST -> Just $ return False
		_ -> Nothing

checkurl :: External -> URLString -> Annex UrlContents
checkurl external url = 
	handleRequest external (CHECKURL url) Nothing $ \req -> case req of
		CHECKURL_CONTENTS sz f -> Just $ return $ UrlContents sz
			(if null f then Nothing else Just $ mkSafeFilePath f)
		-- Treat a single item multi response specially to
		-- simplify the external remote implementation.
		CHECKURL_MULTI ((_, sz, f):[]) ->
			Just $ return $ UrlContents sz $ Just $ mkSafeFilePath f
		CHECKURL_MULTI l -> Just $ return $ UrlMulti $ map mkmulti l
		CHECKURL_FAILURE errmsg -> Just $ error errmsg
		UNSUPPORTED_REQUEST -> error "CHECKURL not implemented by external special remote"
		_ -> Nothing
  where
	mkmulti (u, s, f) = (u, s, mkSafeFilePath f)

retrieveUrl :: Retriever
retrieveUrl = fileRetriever $ \f k p -> do
	us <- getWebUrls k
	unlessM (downloadUrl k p us f) $
		error "failed to download content"

checkKeyUrl :: Git.Repo -> CheckPresent
checkKeyUrl r k = do
	showChecking r
	us <- getWebUrls k
	anyM (\u -> withUrlOptions $ checkBoth u (keySize k)) us

getWebUrls :: Key -> Annex [URLString]
getWebUrls key = filter supported <$> getUrls key
  where
	supported u = snd (getDownloader u) == WebDownloader