summaryrefslogtreecommitdiff
path: root/Assistant/Threads/PairListener.hs
blob: d4f8a07c86f5c91475c096128cf791295de1a2db (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
{- git-annex assistant thread to listen for incoming pairing traffic
 -
 - Copyright 2012 Joey Hess <joey@kitenet.net>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

module Assistant.Threads.PairListener where

import Assistant.Common
import Assistant.Pairing
import Assistant.Pairing.Network
import Assistant.Pairing.MakeRemote
import Assistant.ThreadedMonad
import Assistant.ScanRemotes
import Assistant.DaemonStatus
import Assistant.WebApp
import Assistant.WebApp.Types
import Assistant.Alert
import Utility.Tense

import Network.Multicast
import Network.Socket
import qualified Data.Text as T
import Data.Char

thisThread :: ThreadName
thisThread = "PairListener"

pairListenerThread :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> UrlRenderer -> NamedThread
pairListenerThread st dstatus scanremotes urlrenderer = thread $ withSocketsDo $ do
	sock <- multicastReceiver (multicastAddress $ IPv4Addr undefined) pairingPort
	go sock []
	where
		thread = NamedThread thisThread
		
		go sock cache = getmsg sock [] >>= \msg -> case readish msg of
			Nothing -> go sock cache
			Just m -> do
				sane <- checkSane msg
				(pip, verified) <- verificationCheck m
					=<< (pairingInProgress <$> getDaemonStatus dstatus)
				let wrongstage = maybe False (\p -> pairMsgStage m < inProgressPairStage p) pip
				case (wrongstage, sane, pairMsgStage m) of
					-- ignore our own messages, and
					-- out of order messages
					(True, _, _) -> go sock cache
					(_, False, _) -> go sock cache
					(_, _, PairReq) -> do
						pairReqReceived verified dstatus urlrenderer m
						go sock $ invalidateCache m cache
					(_, _, PairAck) -> do
						pairAckReceived verified pip st dstatus scanremotes m cache
							>>= go sock
					(_, _, PairDone) -> do
						pairDoneReceived verified pip st dstatus scanremotes m
						go sock	cache

		{- As well as verifying the message using the shared secret,
		 - check its UUID against the UUID we have stored. If
		 - they're the same, someone is sending bogus messages,
		 - which could be an attempt to brute force the shared
		 - secret.
		 -}
		verificationCheck m (Just pip) = do
			let verified = verifiedPairMsg m pip
			let sameuuid = pairUUID (inProgressPairData pip) == pairUUID (pairMsgData $ m)
			if (not verified && sameuuid)
				then do
					runThreadState st $
						warning "detected possible pairing brute force attempt; disabled pairing"
					stopSending dstatus pip
					return (Nothing, False)
				else return (Just pip, verified && sameuuid)
		verificationCheck _ Nothing = return (Nothing, False)
		
		{- Various sanity checks on the content of the message. -}
		checkSane msg 
			{- Control characters could be used in a
			 - console poisoning attack. -}
			| any isControl msg || any (`elem` "\r\n") msg = do
				runThreadState st $
					warning "illegal control characters in pairing message; ignoring"
				return False
			| otherwise = return True

		{- PairReqs invalidate the cache of recently finished pairings.
		 - This is so that, if a new pairing is started with the
		 - same secret used before, a bogus PairDone is not sent. -}
		invalidateCache msg = 
			filter (\pip -> not $ verifiedPairMsg msg pip)

		getmsg sock c = do
			(msg, n, _) <- recvFrom sock chunksz
			if n < chunksz
				then return $ c ++ msg
				else getmsg sock $ c ++ msg
			where
				chunksz = 1024

{- Show an alert when a PairReq is seen.
 -
 - Pair request alerts from the same host combine,
 - so repeated requests do not add additional alerts. -}
pairReqReceived :: Bool -> DaemonStatusHandle -> UrlRenderer -> PairMsg -> IO ()
pairReqReceived True _ _ _ = noop -- ignore our own PairReq
pairReqReceived False dstatus urlrenderer msg = do
	url <- renderUrl urlrenderer (FinishPairR msg) []
	void $ addAlert dstatus $ pairRequestReceivedAlert repo
		(repo ++ " is sending a pair request.") $
		AlertButton
			{ buttonUrl = url
			, buttonLabel = T.pack "Respond"
			, buttonAction = Just onclick
			}
	where
		pairdata = pairMsgData msg
		repo = concat
			[ remoteUserName pairdata
			, "@"
			, fromMaybe (showAddr $ pairMsgAddr msg)
				(remoteHostName pairdata)
			, ":"
			, (remoteDirectory pairdata)
			]
		{- Remove the button when it's clicked, and change the
		 - alert to be in progress. This alert cannot be entirely
		 - removed since more pair request messages are coming in
		 - and would re-add it. -}
		onclick i = updateAlert dstatus i $ \alert -> Just $ alert
			{ alertButton = Nothing
			, alertClass = Activity
			, alertIcon = Just ActivityIcon
			, alertData = [UnTensed $ T.pack $ "pair request with " ++ repo ++ " in progress"]
			}

{- When a verified PairAck is seen, a host is ready to pair with us, and has
 - already configured our ssh key. Stop sending PairReqs, finish the pairing,
 - and send a single PairDone. 
 -}
pairAckReceived :: Bool -> Maybe PairingInProgress -> ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> PairMsg -> [PairingInProgress] -> IO [PairingInProgress]
pairAckReceived True (Just pip) st dstatus scanremotes msg cache = do
	stopSending dstatus pip
	setupAuthorizedKeys msg
	finishedPairing st dstatus scanremotes msg (inProgressSshKeyPair pip)
	startSending dstatus pip PairDone $ multicastPairMsg
		(Just 1) (inProgressSecret pip) (inProgressPairData pip)
	return $ pip:(take 10 cache)
{- A stale PairAck might also be seen, after we've finished pairing.
 - Perhaps our PairDone was not received. To handle this, we keep
 - a cache of recently finished pairings, and re-send PairDone in
 - response to stale PairAcks for them. -}
pairAckReceived _ _ _ dstatus _ msg cache = do
	let pips = filter (verifiedPairMsg msg) cache
	unless (null pips) $
		forM_ pips $ \pip ->
			startSending dstatus pip PairDone $ multicastPairMsg
				(Just 1) (inProgressSecret pip) (inProgressPairData pip)
	return cache

{- If we get a verified PairDone, the host has accepted our PairAck, and
 - has paired with us. Stop sending PairAcks, and finish pairing with them.
 -
 - TODO: Should third-party hosts remove their pair request alert when they
 - see a PairDone? 
 - Complication: The user could have already clicked on the alert and be
 - entering the secret. Would be better to start a fresh pair request in this
 - situation.
 -}
pairDoneReceived :: Bool -> Maybe PairingInProgress -> ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> PairMsg -> IO ()
pairDoneReceived False _ _ _ _ _ = noop -- not verified
pairDoneReceived True Nothing _ _ _ _ = noop -- not in progress
pairDoneReceived True (Just pip) st dstatus scanremotes msg = do
	stopSending dstatus pip
	finishedPairing st dstatus scanremotes msg (inProgressSshKeyPair pip)