summaryrefslogtreecommitdiff
path: root/Command/Multicast.hs
blob: 9a518a18f1476ebbe483f225d68c92f49f43c860 (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
{- git-annex command
 -
 - Copyright 2017 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

{-# LANGUAGE CPP #-}

module Command.Multicast where

import Command
import Logs.Multicast
import Annex.Multicast
import Annex.WorkTree
import Annex.Content
import Annex.UUID
import Annex.Perms
import Utility.FileMode
#ifndef mingw32_HOST_OS
import Creds
#endif
import qualified Limit
import Types.FileMatcher
import qualified Git.LsFiles as LsFiles
import Utility.Hash
import Utility.Tmp
import Config

import Data.Char
import qualified Data.ByteString.Lazy.UTF8 as B8
import qualified Data.Map as M
import Control.Concurrent.Async

cmd :: Command
cmd = command "multicast" SectionCommon "multicast file distribution"
	paramNothing (seek <$$> optParser)

data MultiCastAction
	= GenAddress
	| Send
	| Receive
	deriving (Show)

data MultiCastOptions = MultiCastOptions MultiCastAction [CommandParam] [FilePath]
	deriving (Show)

optParser :: CmdParamsDesc -> Parser MultiCastOptions
optParser _ = MultiCastOptions 
	<$> (genaddressp <|> sendp <|> receivep)
	<*> many uftpopt
	<*> cmdParams paramPaths
  where
	genaddressp = flag' GenAddress
		( long "gen-address"
		<> help "generate multicast encryption key and store address in git-annex branch"
		)
	sendp = flag' Send
		( long "send"
		<> help "multicast files"
		)
	receivep = flag' Receive
		( long "receive"
		<> help "listen for multicast files and store in repository"
		)
	uftpopt = Param <$> strOption
		( long "uftp-opt"
		<> short 'U'
		<> help "passed on to uftp/uftpd"
		<> metavar "OPTION"
		)

seek :: MultiCastOptions -> CommandSeek
seek (MultiCastOptions GenAddress _ _) = commandAction genAddress 
seek (MultiCastOptions Send ups fs) = commandAction $ send ups fs
seek (MultiCastOptions Receive ups []) = commandAction $ receive ups
seek (MultiCastOptions Receive _ _) = giveup "Cannot specify list of files with --receive; this receives whatever files the sender chooses to send."

genAddress :: CommandStart
genAddress = do
	showStart' "gen-address" Nothing
	k <- uftpKey
	(s, ok) <- case k of
		KeyContainer s -> liftIO $ genkey (Param s)
		KeyFile f -> do
			createAnnexDirectory (takeDirectory f)
			liftIO $ nukeFile f
			liftIO $ protectedOutput $ genkey (File f)
	case (ok, parseFingerprint s) of
		(False, _) -> giveup $ "uftp_keymgt failed: " ++ s
		(_, Nothing) -> giveup $ "Failed to find fingerprint in uftp_keymgt output: " ++ s
		(True, Just fp) -> next $ next $ do
			recordFingerprint fp =<< getUUID
			return True
  where
 	-- Annoyingly, the fingerprint is output to stderr.
	genkey p = processTranscript "uftp_keymgt" ps Nothing
	  where
		ps = toCommand $
			[ Param "-g"
			, keyparam
			, p
			]
	-- uftp only supports rsa up to 2048 which is on the lower
	-- limit of secure RSA key sizes. Instead, use an EC curve.
	-- Except for on Windows XP, secp521r1 is supported on all
	-- platforms by uftp. DJB thinks it's pretty good compared
	-- with other NIST curves: "there's one standard NIST curve
	-- using a nice prime, namely 2521−1  but the sheer size of this
	-- prime makes it much slower than NIST P-256"
	-- (http://blog.cr.yp.to/20140323-ecdsa.html)
	-- Since this key is only used to set up the block encryption,
	-- its slow speed is ok.
	keyparam = Param "ec:secp521r1"

parseFingerprint :: String -> Maybe Fingerprint
parseFingerprint = Fingerprint <$$> lastMaybe . filter isfingerprint . words 
  where
	isfingerprint s = 
		let os = filter (all isHexDigit) (splitc ':' s)
		in length os == 20
	
send :: [CommandParam] -> [FilePath] -> CommandStart
send ups fs = withTmpFile "send" $ \t h -> do
	-- Need to be able to send files with the names of git-annex
	-- keys, and uftp does not allow renaming the files that are sent.
	-- In a direct mode repository, the annex objects do not have
	-- the names of keys, and would have to be copied, which is too
	-- expensive.
	whenM isDirect $
		giveup "Sorry, multicast send cannot be done from a direct mode repository."
	
	showStart' "generating file list" Nothing
	fs' <- seekHelper LsFiles.inRepo =<< workTreeItems fs
	matcher <- Limit.getMatcher
	let addlist f o = whenM (matcher $ MatchingFile $ FileInfo f f) $
		liftIO $ hPutStrLn h o
	forM_ fs' $ \f -> do
		mk <- lookupFile f
		case mk of
			Nothing -> noop
			Just k -> withObjectLoc k (addlist f) (const noop)
	liftIO $ hClose h
	showEndOk

	showStart' "sending files" Nothing
	showOutput
	serverkey <- uftpKey
	u <- getUUID
	withAuthList $ \authlist -> do
		let ps =
			-- Force client authentication.
			[ Param "-c"
			, Param "-Y", Param "aes256-cbc"
			, Param "-h", Param "sha512"
			-- Picked ecdh_ecdsa for perfect forward secrecy,
			-- and because a EC key exchange algorithm is
			-- needed since all keys are EC.
			, Param "-e", Param "ecdh_ecdsa"
			, Param "-k", uftpKeyParam serverkey
			, Param "-U", Param (uftpUID u)
			-- only allow clients on the authlist
			, Param "-H", Param ("@"++authlist)
			-- pass in list of files to send
			, Param "-i", File t
			] ++ ups
		liftIO (boolSystem "uftp" ps) >>= showEndResult
	stop

receive :: [CommandParam] -> CommandStart
receive ups = do
	showStart' "receiving multicast files" Nothing
	showNote "Will continue to run until stopped by ctrl-c"
	
	showOutput
	clientkey <- uftpKey
	u <- getUUID
	(callback, environ, statush) <- liftIO multicastCallbackEnv
	tmpobjdir <- fromRepo gitAnnexTmpObjectDir
	createAnnexDirectory tmpobjdir
	withTmpDirIn tmpobjdir "multicast" $ \tmpdir -> withAuthList $ \authlist -> do
		abstmpdir <- liftIO $ absPath tmpdir
		abscallback <- liftIO $ searchPath callback
		let ps =
			-- Avoid it running as a daemon.
			[ Param "-d"
			-- Require encryption.
			, Param "-E"
			, Param "-k", uftpKeyParam clientkey
			, Param "-U", Param (uftpUID u)
			-- Only allow servers on the authlist
			, Param "-S", Param authlist
			-- Receive files into tmpdir
			-- (it needs an absolute path)
			, Param "-D", File abstmpdir
			-- Run callback after each file received
			-- (it needs an absolute path)
			, Param "-s", Param (fromMaybe callback abscallback)
			] ++ ups
		runner <- liftIO $ async $
			hClose statush
				`after` boolSystemEnv "uftpd" ps (Just environ)
		mapM_ storeReceived . lines =<< liftIO (hGetContents statush)
		showEndResult =<< liftIO (wait runner)
	stop

storeReceived :: FilePath -> Annex ()
storeReceived f = do
	case file2key (takeFileName f) of
		Nothing -> do
			warning $ "Received a file " ++ f ++ " that is not a git-annex key. Deleting this file."
			liftIO $ nukeFile f
		Just k -> void $
			getViaTmp' AlwaysVerify k $ \dest -> unVerified $
				liftIO $ catchBoolIO $ do
					rename f dest
					return True

-- Under Windows, uftp uses key containers, which are not files on the
-- filesystem.
data UftpKey = KeyFile FilePath | KeyContainer String

uftpKeyParam :: UftpKey -> CommandParam
uftpKeyParam (KeyFile f) = File f
uftpKeyParam (KeyContainer s) = Param s

uftpKey :: Annex UftpKey
#ifdef mingw32_HOST_OS
uftpKey = do
	u <- getUUID
	return $ KeyContainer $ "annex-" ++ fromUUID u
#else
uftpKey = KeyFile <$> cacheCredsFile "multicast"
#endif

-- uftp needs a unique UID for each client and server, which 
-- is a 8 digit hex number in the form "0xnnnnnnnn"
-- Derive it from the UUID.
uftpUID :: UUID -> String
uftpUID u = "0x" ++ (take 8 $ show $ sha2_256 $ B8.fromString (fromUUID u))

withAuthList :: (FilePath -> Annex a) -> Annex a
withAuthList a = do
	m <- knownFingerPrints
	withTmpFile "authlist" $ \t h -> do
		liftIO $ hPutStr h (genAuthList m)
		liftIO $ hClose h
		a t

genAuthList :: M.Map UUID Fingerprint -> String
genAuthList = unlines . map fmt . M.toList
  where
	fmt (u, Fingerprint f) = uftpUID u ++ "|" ++ f