plumb peer uuid through to runLocal
This will allow updating transfer logs with the uuid.
This commit is contained in:
		
					parent
					
						
							
								71ddb10699
							
						
					
				
			
			
				commit
				
					
						b16a1cee4b
					
				
			
		
					 3 changed files with 96 additions and 55 deletions
				
			
		
							
								
								
									
										19
									
								
								P2P/Annex.hs
									
										
									
									
									
								
							
							
						
						
									
										19
									
								
								P2P/Annex.hs
									
										
									
									
									
								
							|  | @ -8,7 +8,8 @@ | ||||||
| {-# LANGUAGE RankNTypes, FlexibleContexts #-} | {-# LANGUAGE RankNTypes, FlexibleContexts #-} | ||||||
| 
 | 
 | ||||||
| module P2P.Annex | module P2P.Annex | ||||||
| 	( RunEnv(..) | 	( RunMode(..) | ||||||
|  | 	, RunEnv(..) | ||||||
| 	, runFullProto | 	, runFullProto | ||||||
| 	) where | 	) where | ||||||
| 
 | 
 | ||||||
|  | @ -22,17 +23,23 @@ import Types.NumCopies | ||||||
| import Control.Monad.Free | import Control.Monad.Free | ||||||
| import qualified Data.ByteString.Lazy as L | import qualified Data.ByteString.Lazy as L | ||||||
| 
 | 
 | ||||||
|  | -- When we're serving a peer, we know their uuid, and can use it to update | ||||||
|  | -- transfer logs. | ||||||
|  | data RunMode | ||||||
|  | 	= Serving UUID | ||||||
|  | 	| Client | ||||||
|  | 
 | ||||||
| -- Full interpreter for Proto, that can receive and send objects. | -- Full interpreter for Proto, that can receive and send objects. | ||||||
| runFullProto :: RunEnv -> Proto a -> Annex (Maybe a) | runFullProto :: RunMode -> RunEnv -> Proto a -> Annex (Maybe a) | ||||||
| runFullProto runenv = go | runFullProto runmode runenv = go | ||||||
|   where |   where | ||||||
| 	go :: RunProto Annex | 	go :: RunProto Annex | ||||||
| 	go (Pure v) = pure (Just v) | 	go (Pure v) = pure (Just v) | ||||||
| 	go (Free (Net n)) = runNet runenv go n | 	go (Free (Net n)) = runNet runenv go n | ||||||
| 	go (Free (Local l)) = runLocal go l | 	go (Free (Local l)) = runLocal runmode go l | ||||||
| 
 | 
 | ||||||
| runLocal :: RunProto Annex -> LocalF (Proto a) -> Annex (Maybe a) | runLocal :: RunMode -> RunProto Annex -> LocalF (Proto a) -> Annex (Maybe a) | ||||||
| runLocal runner a = case a of | runLocal runmode runner a = case a of | ||||||
| 	TmpContentSize k next -> do | 	TmpContentSize k next -> do | ||||||
| 		tmp <- fromRepo $ gitAnnexTmpObjectLocation k | 		tmp <- fromRepo $ gitAnnexTmpObjectLocation k | ||||||
| 		size <- liftIO $ catchDefaultIO 0 $ getFileSize tmp | 		size <- liftIO $ catchDefaultIO 0 $ getFileSize tmp | ||||||
|  |  | ||||||
|  | @ -240,51 +240,74 @@ put key = do | ||||||
| 			net $ sendMessage (ERROR "expected PUT_FROM") | 			net $ sendMessage (ERROR "expected PUT_FROM") | ||||||
| 			return False | 			return False | ||||||
| 
 | 
 | ||||||
| -- | Serve the protocol. | data ServerHandler a | ||||||
|  | 	= ServerGot a | ||||||
|  | 	| ServerContinue | ||||||
|  | 	| ServerUnexpected | ||||||
|  | 
 | ||||||
|  | -- Server loop, getting messages from the client and handling them | ||||||
|  | serverLoop :: (Message -> Proto (ServerHandler a)) -> Proto (Maybe a) | ||||||
|  | serverLoop a = do | ||||||
|  | 	cmd <- net receiveMessage | ||||||
|  | 	case cmd of | ||||||
|  | 		-- When the client sends ERROR to the server, the server | ||||||
|  | 		-- gives up, since it's not clear what state the client | ||||||
|  | 		-- is in, and so not possible to recover. | ||||||
|  | 		ERROR _ -> return Nothing | ||||||
|  | 		_ -> do | ||||||
|  | 			v <- a cmd | ||||||
|  | 			case v of | ||||||
|  | 				ServerGot r -> return (Just r) | ||||||
|  | 				ServerContinue -> serverLoop a | ||||||
|  | 				-- If the client sends an unexpected message, | ||||||
|  | 				-- the server will respond with ERROR, and | ||||||
|  | 				-- always continues processing messages. | ||||||
| 				-- | 				-- | ||||||
| -- Note that if the client sends an unexpected message, the server will | 				-- Since the protocol is not versioned, this | ||||||
| -- respond with PTOTO_ERROR, and always continues processing messages. | 				-- is necessary to handle protocol changes | ||||||
| -- Since the protocol is not versioned, this is necessary to handle | 				-- robustly, since the client can detect when | ||||||
| -- protocol changes robustly, since the client can detect when it's | 				-- it's talking to a server that does not | ||||||
| -- talking to a server that does not support some new feature, and fall | 				-- support some new feature, and fall back. | ||||||
| -- back. | 				ServerUnexpected -> do | ||||||
| -- | 					net $ sendMessage (ERROR "unexpected command") | ||||||
| -- When the client sends ERROR to the server, the server gives up, | 					serverLoop a | ||||||
| -- since it's not clear what state the client is is, and so not possible to | 
 | ||||||
| -- recover. | -- | Serve the protocol, with an unauthenticated peer. Once the peer | ||||||
| serve :: UUID -> Proto () | -- successfully authenticates, returns their UUID. | ||||||
| serve myuuid = go Nothing | serveAuth :: UUID -> Proto (Maybe UUID) | ||||||
|  | serveAuth myuuid = serverLoop handler | ||||||
|   where |   where | ||||||
| 	go autheduuid = do | 	handler (AUTH theiruuid authtoken) = do | ||||||
| 		r <- net receiveMessage |  | ||||||
| 		case r of |  | ||||||
| 			AUTH theiruuid authtoken -> do |  | ||||||
| 		ok <- net $ checkAuthToken theiruuid authtoken | 		ok <- net $ checkAuthToken theiruuid authtoken | ||||||
| 		if ok | 		if ok | ||||||
| 			then do | 			then do | ||||||
| 				net $ sendMessage (AUTH_SUCCESS myuuid) | 				net $ sendMessage (AUTH_SUCCESS myuuid) | ||||||
| 						go (Just theiruuid) | 				return (ServerGot theiruuid) | ||||||
| 			else do | 			else do | ||||||
| 				net $ sendMessage AUTH_FAILURE | 				net $ sendMessage AUTH_FAILURE | ||||||
| 						go autheduuid | 				return ServerContinue | ||||||
| 			ERROR _ -> return () | 	handler _ = return ServerUnexpected | ||||||
| 			_ -> do |  | ||||||
| 				case autheduuid of |  | ||||||
| 					Just theiruuid -> authed theiruuid r |  | ||||||
| 					Nothing -> net $ sendMessage (ERROR "must AUTH first") |  | ||||||
| 				go autheduuid |  | ||||||
| 
 | 
 | ||||||
| 	authed _theiruuid r = case r of | -- | Serve the protocol, with a peer that has authenticated. | ||||||
| 		LOCKCONTENT key -> local $ tryLockContent key $ \locked -> do | serveAuthed :: UUID -> Proto () | ||||||
|  | serveAuthed myuuid = void $ serverLoop handler | ||||||
|  |   where | ||||||
|  | 	handler (LOCKCONTENT key) = do | ||||||
|  | 		local $ tryLockContent key $ \locked -> do | ||||||
| 			sendSuccess locked | 			sendSuccess locked | ||||||
| 			when locked $ do | 			when locked $ do | ||||||
| 				r' <- net receiveMessage | 				r' <- net receiveMessage | ||||||
| 				case r' of | 				case r' of | ||||||
| 					UNLOCKCONTENT -> return () | 					UNLOCKCONTENT -> return () | ||||||
| 					_ -> net $ sendMessage (ERROR "expected UNLOCKCONTENT") | 					_ -> net $ sendMessage (ERROR "expected UNLOCKCONTENT") | ||||||
| 		CHECKPRESENT key -> sendSuccess =<< local (checkContentPresent key) | 		return ServerContinue | ||||||
| 		REMOVE key ->  sendSuccess =<< local (removeContent key) | 	handler (CHECKPRESENT key) = do | ||||||
| 		PUT key -> do | 		sendSuccess =<< local (checkContentPresent key) | ||||||
|  | 		return ServerContinue | ||||||
|  | 	handler (REMOVE key) = do | ||||||
|  | 		sendSuccess =<< local (removeContent key) | ||||||
|  | 		return ServerContinue | ||||||
|  | 	handler (PUT key) = do | ||||||
| 		have <- local $ checkContentPresent key | 		have <- local $ checkContentPresent key | ||||||
| 		if have | 		if have | ||||||
| 			then net $ sendMessage ALREADY_HAVE | 			then net $ sendMessage ALREADY_HAVE | ||||||
|  | @ -292,11 +315,16 @@ serve myuuid = go Nothing | ||||||
| 				ok <- receiveContent key PUT_FROM | 				ok <- receiveContent key PUT_FROM | ||||||
| 				when ok $ | 				when ok $ | ||||||
| 					local $ setPresent key myuuid | 					local $ setPresent key myuuid | ||||||
|  | 		return ServerContinue | ||||||
|  | 	handler (GET offset key) = do | ||||||
|  | 		void $ sendContent key offset | ||||||
| 		-- setPresent not called because the peer may have | 		-- setPresent not called because the peer may have | ||||||
| 		-- requested the data but not permanently stored it. | 		-- requested the data but not permanently stored it. | ||||||
| 		GET offset key -> void $ sendContent key offset | 		return ServerContinue | ||||||
| 		CONNECT service -> net $ relayService service | 	handler (CONNECT service) = do | ||||||
| 		_ -> net $ sendMessage (ERROR "unexpected command") | 		net $ relayService service | ||||||
|  | 		return ServerContinue | ||||||
|  | 	handler _ = return ServerUnexpected | ||||||
| 
 | 
 | ||||||
| sendContent :: Key -> Offset -> Proto Bool | sendContent :: Key -> Offset -> Proto Bool | ||||||
| sendContent key offset = do | sendContent key offset = do | ||||||
|  |  | ||||||
|  | @ -17,6 +17,7 @@ import Utility.FileMode | ||||||
| import Utility.AuthToken | import Utility.AuthToken | ||||||
| import Remote.Helper.Tor | import Remote.Helper.Tor | ||||||
| import P2P.Protocol | import P2P.Protocol | ||||||
|  | import P2P.IO | ||||||
| import P2P.Annex | import P2P.Annex | ||||||
| import P2P.Auth | import P2P.Auth | ||||||
| import Annex.UUID | import Annex.UUID | ||||||
|  | @ -90,7 +91,12 @@ serveClient th u r q = bracket setup cleanup go | ||||||
| 				, runIhdl = h | 				, runIhdl = h | ||||||
| 				, runOhdl = h | 				, runOhdl = h | ||||||
| 				} | 				} | ||||||
| 			void $ runFullProto runenv (serve u) | 			v <- liftIO $ runNetProto runenv $ serveAuth u | ||||||
|  | 			case v of | ||||||
|  | 				Just (Just theiruuid) -> void $  | ||||||
|  | 					runFullProto (Serving theiruuid) runenv $ | ||||||
|  | 						serveAuthed u | ||||||
|  | 				_ -> return () | ||||||
| 		-- Merge the duplicated state back in. | 		-- Merge the duplicated state back in. | ||||||
| 		liftAnnex th $ mergeState st' | 		liftAnnex th $ mergeState st' | ||||||
| 		debugM "remotedaemon" "done with TOR connection" | 		debugM "remotedaemon" "done with TOR connection" | ||||||
|  |  | ||||||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue
	
	 Joey Hess
				Joey Hess