more nice refactoring
This commit is contained in:
		
					parent
					
						
							
								7ab993ffc9
							
						
					
				
			
			
				commit
				
					
						0cf4c3ba9c
					
				
			
		
					 2 changed files with 75 additions and 92 deletions
				
			
		|  | @ -134,19 +134,7 @@ decodeStanza selfjid s@(ReceivedMessage m) | ||||||
| 	| messageFrom m == Nothing = [Ignorable s] | 	| messageFrom m == Nothing = [Ignorable s] | ||||||
| 	| messageFrom m == Just selfjid = [Ignorable s] | 	| messageFrom m == Just selfjid = [Ignorable s] | ||||||
| 	| messageType m == MessageError = [ProtocolError s] | 	| messageType m == MessageError = [ProtocolError s] | ||||||
| 	| otherwise = [fromMaybe (Unknown s) $ decode =<< gitAnnexTagInfo m] | 	| otherwise = [fromMaybe (Unknown s) (GotNetMessage <$> decodeMessage m)] | ||||||
|   where |  | ||||||
| 	decode i = GotNetMessage <$> |  | ||||||
| 		((\d -> d m i) =<< M.lookup (tagAttr i) decoders) |  | ||||||
| 	decoders = M.fromList |  | ||||||
| 		[ (pairAttr, decodePairingNotification) |  | ||||||
| 		, (canPushAttr, decodeCanPush) |  | ||||||
| 		, (pushRequestAttr, decodePushRequest) |  | ||||||
| 		, (startingPushAttr, decodeStartingPush) |  | ||||||
| 		, (receivePackAttr, decodeReceivePackOutput) |  | ||||||
| 		, (sendPackAttr, decodeSendPackOutput) |  | ||||||
| 		, (receivePackDoneAttr, decodeReceivePackDone) |  | ||||||
| 		] |  | ||||||
| decodeStanza _ s = [Unknown s] | decodeStanza _ s = [Unknown s] | ||||||
| 
 | 
 | ||||||
| {- Waits for a NetMessager message to be sent, and relays it to XMPP. -} | {- Waits for a NetMessager message to be sent, and relays it to XMPP. -} | ||||||
|  | @ -158,12 +146,8 @@ relayNetMessage selfjid = convert =<< waitNetMessage | ||||||
| 	convert (PairingNotification stage c u) = withclient c $ \tojid -> do | 	convert (PairingNotification stage c u) = withclient c $ \tojid -> do | ||||||
| 		changeBuddyPairing tojid True | 		changeBuddyPairing tojid True | ||||||
| 		return $ putStanza $ pairingNotification stage u tojid selfjid | 		return $ putStanza $ pairingNotification stage u tojid selfjid | ||||||
| 	convert (Pushing c CanPush) = sendclient c canPush | 	convert (Pushing c pushstage) = sendclient c $ | ||||||
| 	convert (Pushing c PushRequest) = sendclient c pushRequest | 		gitAnnexMessage $ encodePushStage pushstage | ||||||
| 	convert (Pushing c StartingPush) = sendclient c startingPush |  | ||||||
| 	convert (Pushing c (ReceivePackOutput b)) = sendclient c $ receivePackOutput b |  | ||||||
| 	convert (Pushing c (SendPackOutput b)) = sendclient c $ sendPackOutput b |  | ||||||
| 	convert (Pushing c (ReceivePackDone code)) = sendclient c $ receivePackDone code |  | ||||||
| 
 | 
 | ||||||
| 	sendclient c construct = withclient c $ \tojid -> | 	sendclient c construct = withclient c $ \tojid -> | ||||||
| 		return $ putStanza $ construct tojid selfjid | 		return $ putStanza $ construct tojid selfjid | ||||||
|  |  | ||||||
|  | @ -16,6 +16,7 @@ import Assistant.Pairing | ||||||
| import Network.Protocol.XMPP hiding (Node) | import Network.Protocol.XMPP hiding (Node) | ||||||
| import Data.Text (Text) | import Data.Text (Text) | ||||||
| import qualified Data.Text as T | import qualified Data.Text as T | ||||||
|  | import qualified Data.Map as M | ||||||
| import Data.ByteString (ByteString) | import Data.ByteString (ByteString) | ||||||
| import qualified Data.ByteString as B | import qualified Data.ByteString as B | ||||||
| import Data.XML.Types | import Data.XML.Types | ||||||
|  | @ -91,40 +92,31 @@ gitAnnexMessage elt tojid fromjid = (insertGitAnnexTag silentMessage elt) | ||||||
| pushNotification :: [UUID] -> Presence | pushNotification :: [UUID] -> Presence | ||||||
| pushNotification = gitAnnexPresence . gitAnnexTag pushAttr . encodePushNotification | pushNotification = gitAnnexPresence . gitAnnexTag pushAttr . encodePushNotification | ||||||
| 
 | 
 | ||||||
| pushAttr :: Name |  | ||||||
| pushAttr = "push" |  | ||||||
| 
 |  | ||||||
| uuidSep :: Text |  | ||||||
| uuidSep = "," |  | ||||||
| 
 |  | ||||||
| encodePushNotification :: [UUID] -> Text | encodePushNotification :: [UUID] -> Text | ||||||
| encodePushNotification = T.intercalate uuidSep . map (T.pack . fromUUID) | encodePushNotification = T.intercalate uuidSep . map (T.pack . fromUUID) | ||||||
| 
 | 
 | ||||||
| decodePushNotification :: Text -> [UUID] | decodePushNotification :: Text -> [UUID] | ||||||
| decodePushNotification = map (toUUID . T.unpack) . T.splitOn uuidSep | decodePushNotification = map (toUUID . T.unpack) . T.splitOn uuidSep | ||||||
| 
 | 
 | ||||||
|  | uuidSep :: Text | ||||||
|  | uuidSep = "," | ||||||
|  | 
 | ||||||
| {- A request for other git-annex clients to send presence. -} | {- A request for other git-annex clients to send presence. -} | ||||||
| presenceQuery :: Presence | presenceQuery :: Presence | ||||||
| presenceQuery = gitAnnexPresence $ gitAnnexTag queryAttr T.empty | presenceQuery = gitAnnexPresence $ gitAnnexTag queryAttr T.empty | ||||||
| 
 | 
 | ||||||
| queryAttr :: Name |  | ||||||
| queryAttr = "query" |  | ||||||
| 
 |  | ||||||
| {- A notification about a stage of pairing. -} | {- A notification about a stage of pairing. -} | ||||||
| pairingNotification :: PairStage -> UUID -> JID -> JID -> Message | pairingNotification :: PairStage -> UUID -> JID -> JID -> Message | ||||||
| pairingNotification pairstage u = gitAnnexMessage $  | pairingNotification pairstage u = gitAnnexMessage $  | ||||||
| 	gitAnnexTag pairAttr $ encodePairingNotification pairstage u | 	gitAnnexTag pairAttr $ encodePairingNotification pairstage u | ||||||
| 
 | 
 | ||||||
| pairAttr :: Name |  | ||||||
| pairAttr = "pair" |  | ||||||
| 
 |  | ||||||
| encodePairingNotification :: PairStage -> UUID -> Text | encodePairingNotification :: PairStage -> UUID -> Text | ||||||
| encodePairingNotification pairstage u = T.unwords $ map T.pack | encodePairingNotification pairstage u = T.unwords $ map T.pack | ||||||
| 	[ show pairstage | 	[ show pairstage | ||||||
| 	, fromUUID u | 	, fromUUID u | ||||||
| 	] | 	] | ||||||
| 
 | 
 | ||||||
| decodePairingNotification :: Message -> GitAnnexTagInfo -> Maybe NetMessage | decodePairingNotification :: Decoder | ||||||
| decodePairingNotification m = parse . words . T.unpack . tagValue | decodePairingNotification m = parse . words . T.unpack . tagValue | ||||||
|   where |   where | ||||||
| 	parse [stage, u] = PairingNotification | 	parse [stage, u] = PairingNotification | ||||||
|  | @ -133,70 +125,50 @@ decodePairingNotification m = parse . words . T.unpack . tagValue | ||||||
| 		<*> pure (toUUID u) | 		<*> pure (toUUID u) | ||||||
| 	parse _ = Nothing | 	parse _ = Nothing | ||||||
| 
 | 
 | ||||||
| canPush :: JID -> JID -> Message | encodePushStage :: PushStage -> Element | ||||||
| canPush = gitAnnexMessage $ gitAnnexTag canPushAttr T.empty | encodePushStage CanPush = gitAnnexTag canPushAttr T.empty | ||||||
| 
 | encodePushStage PushRequest = gitAnnexTag pushRequestAttr T.empty | ||||||
| decodeCanPush :: PushDecoder | encodePushStage StartingPush = gitAnnexTag startingPushAttr T.empty | ||||||
| decodeCanPush = mkPushDecoder $ const $ Just CanPush | encodePushStage (ReceivePackOutput b) =  | ||||||
| 
 | 	gitAnnexTagContent receivePackAttr T.empty $ encodeTagContent b | ||||||
| canPushAttr :: Name | encodePushStage (SendPackOutput b) = | ||||||
| canPushAttr = "canpush" | 	gitAnnexTagContent sendPackAttr T.empty $ encodeTagContent b | ||||||
| 
 | encodePushStage (ReceivePackDone code) = | ||||||
| pushRequest :: JID -> JID -> Message | 	gitAnnexTag receivePackDoneAttr $ T.pack $ show $ toi code | ||||||
| pushRequest = gitAnnexMessage $ gitAnnexTag pushRequestAttr T.empty |  | ||||||
| 
 |  | ||||||
| decodePushRequest :: PushDecoder |  | ||||||
| decodePushRequest = mkPushDecoder $ const $ Just PushRequest |  | ||||||
| 
 |  | ||||||
| pushRequestAttr :: Name |  | ||||||
| pushRequestAttr = "pushrequest" |  | ||||||
| 
 |  | ||||||
| startingPush :: JID -> JID -> Message |  | ||||||
| startingPush = gitAnnexMessage $ gitAnnexTag startingPushAttr T.empty |  | ||||||
| 
 |  | ||||||
| startingPushAttr :: Name |  | ||||||
| startingPushAttr = "startingpush" |  | ||||||
| 
 |  | ||||||
| decodeStartingPush :: PushDecoder |  | ||||||
| decodeStartingPush = mkPushDecoder $ const $ Just StartingPush |  | ||||||
| 
 |  | ||||||
| receivePackOutput :: ByteString -> JID -> JID -> Message |  | ||||||
| receivePackOutput = gitAnnexMessage . |  | ||||||
| 	gitAnnexTagContent receivePackAttr T.empty . encodeTagContent |  | ||||||
| 
 |  | ||||||
| receivePackAttr :: Name |  | ||||||
| receivePackAttr = "rp" |  | ||||||
| 
 |  | ||||||
| decodeReceivePackOutput :: PushDecoder |  | ||||||
| decodeReceivePackOutput = mkPushDecoder $ |  | ||||||
| 	fmap ReceivePackOutput . decodeTagContent . tagElement |  | ||||||
| 
 |  | ||||||
| sendPackOutput :: ByteString -> JID -> JID -> Message |  | ||||||
| sendPackOutput = gitAnnexMessage . |  | ||||||
| 	gitAnnexTagContent sendPackAttr T.empty . encodeTagContent |  | ||||||
| 
 |  | ||||||
| sendPackAttr :: Name |  | ||||||
| sendPackAttr = "sp" |  | ||||||
| 
 |  | ||||||
| decodeSendPackOutput :: PushDecoder |  | ||||||
| decodeSendPackOutput = mkPushDecoder $ |  | ||||||
| 	fmap SendPackOutput . decodeTagContent . tagElement |  | ||||||
| 
 |  | ||||||
| receivePackDone :: ExitCode -> JID -> JID -> Message |  | ||||||
| receivePackDone = gitAnnexMessage . gitAnnexTag receivePackDoneAttr . T.pack . show . toi |  | ||||||
|   where |   where | ||||||
| 	toi (ExitSuccess) = 0 | 	toi (ExitSuccess) = 0 | ||||||
| 	toi (ExitFailure i) = i | 	toi (ExitFailure i) = i | ||||||
| 
 | 
 | ||||||
| decodeReceivePackDone :: PushDecoder | decodeMessage :: Message -> Maybe NetMessage | ||||||
| decodeReceivePackDone = mkPushDecoder $ | decodeMessage m = decode =<< gitAnnexTagInfo m | ||||||
| 	fmap (ReceivePackDone . convert) . readish . T.unpack . tagValue |  | ||||||
|   where |   where | ||||||
| 	convert 0 = ExitSuccess | 	decode i = M.lookup (tagAttr i) decoders >>= rundecoder i | ||||||
| 	convert n = ExitFailure n | 	rundecoder i d = d m i | ||||||
|  | 	decoders = M.fromList $ zip | ||||||
|  | 		[ pairAttr | ||||||
|  | 		, canPushAttr | ||||||
|  | 		, pushRequestAttr | ||||||
|  | 		, startingPushAttr | ||||||
|  | 		, receivePackAttr | ||||||
|  | 		, sendPackAttr | ||||||
|  | 		, receivePackDoneAttr | ||||||
|  | 		] | ||||||
|  | 		[ decodePairingNotification | ||||||
|  | 		, mkPushDecoder $ const $ Just CanPush | ||||||
|  | 		, mkPushDecoder $ const $ Just PushRequest | ||||||
|  | 		, mkPushDecoder $ const $ Just StartingPush | ||||||
|  | 		, mkPushDecoder $  | ||||||
|  | 			fmap ReceivePackOutput . decodeTagContent . tagElement | ||||||
|  | 		, mkPushDecoder $ | ||||||
|  | 			fmap SendPackOutput . decodeTagContent . tagElement | ||||||
|  | 		, mkPushDecoder $ | ||||||
|  | 			fmap (ReceivePackDone . convertCode) . readish . | ||||||
|  | 				T.unpack . tagValue | ||||||
|  | 		] | ||||||
| 
 | 
 | ||||||
| receivePackDoneAttr :: Name | convertCode :: Int -> ExitCode | ||||||
| receivePackDoneAttr = "rpdone" | convertCode 0 = ExitSuccess | ||||||
|  | convertCode n = ExitFailure n | ||||||
| 
 | 
 | ||||||
| {- Base 64 encoding a ByteString to use as the content of a tag. -} | {- Base 64 encoding a ByteString to use as the content of a tag. -} | ||||||
| encodeTagContent :: ByteString -> [Node] | encodeTagContent :: ByteString -> [Node] | ||||||
|  | @ -227,9 +199,36 @@ silentMessage = (emptyMessage MessageChat) | ||||||
| extendedAway :: Element | extendedAway :: Element | ||||||
| extendedAway = Element "show" [] [NodeContent $ ContentText "xa"] | extendedAway = Element "show" [] [NodeContent $ ContentText "xa"] | ||||||
| 
 | 
 | ||||||
| type PushDecoder = Message -> GitAnnexTagInfo -> Maybe NetMessage | type Decoder = Message -> GitAnnexTagInfo -> Maybe NetMessage | ||||||
| 
 | 
 | ||||||
| mkPushDecoder :: (GitAnnexTagInfo -> Maybe PushStage) -> PushDecoder | mkPushDecoder :: (GitAnnexTagInfo -> Maybe PushStage) -> Decoder | ||||||
| mkPushDecoder a m i = Pushing | mkPushDecoder a m i = Pushing | ||||||
| 	<$> (formatJID <$> messageFrom m) | 	<$> (formatJID <$> messageFrom m) | ||||||
| 	<*> a i | 	<*> a i | ||||||
|  | 
 | ||||||
|  | pushAttr :: Name | ||||||
|  | pushAttr = "push" | ||||||
|  | 
 | ||||||
|  | queryAttr :: Name | ||||||
|  | queryAttr = "query" | ||||||
|  | 
 | ||||||
|  | pairAttr :: Name | ||||||
|  | pairAttr = "pair" | ||||||
|  | 
 | ||||||
|  | canPushAttr :: Name | ||||||
|  | canPushAttr = "canpush" | ||||||
|  | 
 | ||||||
|  | pushRequestAttr :: Name | ||||||
|  | pushRequestAttr = "pushrequest" | ||||||
|  | 
 | ||||||
|  | startingPushAttr :: Name | ||||||
|  | startingPushAttr = "startingpush" | ||||||
|  | 
 | ||||||
|  | receivePackAttr :: Name | ||||||
|  | receivePackAttr = "rp" | ||||||
|  | 
 | ||||||
|  | sendPackAttr :: Name | ||||||
|  | sendPackAttr = "sp" | ||||||
|  | 
 | ||||||
|  | receivePackDoneAttr :: Name | ||||||
|  | receivePackDoneAttr = "rpdone" | ||||||
|  |  | ||||||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue
	
	 Joey Hess
				Joey Hess