This does not change the overall license of the git-annex program, which was already AGPL due to a number of sources files being AGPL already. Legally speaking, I'm adding a new license under which these files are now available; I already released their current contents under the GPL license. Now they're dual licensed GPL and AGPL. However, I intend for all my future changes to these files to only be released under the AGPL license, and I won't be tracking the dual licensing status, so I'm simply changing the license statement to say it's AGPL. (In some cases, others wrote parts of the code of a file and released it under the GPL; but in all cases I have contributed a significant portion of the code in each file and it's that code that is getting the AGPL license; the GPL license of other contributors allows combining with AGPL code.)
		
			
				
	
	
		
			121 lines
		
	
	
	
		
			3.6 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			121 lines
		
	
	
	
		
			3.6 KiB
			
		
	
	
	
		
			Haskell
		
	
	
	
	
	
{- git-annex assistant communication with remotedaemon
 | 
						|
 -
 | 
						|
 - Copyright 2014 Joey Hess <id@joeyh.name>
 | 
						|
 -
 | 
						|
 - Licensed under the GNU AGPL version 3 or higher.
 | 
						|
 -}
 | 
						|
 | 
						|
module Assistant.Threads.RemoteControl where
 | 
						|
 | 
						|
import Assistant.Common
 | 
						|
import RemoteDaemon.Types
 | 
						|
import Annex.Path
 | 
						|
import Utility.Batch
 | 
						|
import Utility.SimpleProtocol
 | 
						|
import Assistant.Alert
 | 
						|
import Assistant.Alert.Utility
 | 
						|
import Assistant.DaemonStatus
 | 
						|
import qualified Git
 | 
						|
import qualified Git.Types as Git
 | 
						|
import qualified Remote
 | 
						|
import qualified Types.Remote as Remote
 | 
						|
 | 
						|
import Control.Concurrent
 | 
						|
import Control.Concurrent.Async
 | 
						|
import Network.URI
 | 
						|
import qualified Data.Map as M
 | 
						|
import qualified Data.Set as S
 | 
						|
 | 
						|
remoteControlThread :: NamedThread
 | 
						|
remoteControlThread = namedThread "RemoteControl" $ do
 | 
						|
	program <- liftIO programPath
 | 
						|
	(cmd, params) <- liftIO $ toBatchCommand
 | 
						|
		(program, [Param "remotedaemon", Param "--foreground"])
 | 
						|
	let p = proc cmd (toCommand params)
 | 
						|
	(Just toh, Just fromh, _, pid) <- liftIO $ createProcess p
 | 
						|
		{ std_in = CreatePipe
 | 
						|
		, std_out = CreatePipe
 | 
						|
		}
 | 
						|
	
 | 
						|
	urimap <- liftIO . newMVar =<< liftAnnex getURIMap
 | 
						|
 | 
						|
	controller <- asIO $ remoteControllerThread toh
 | 
						|
	responder <- asIO $ remoteResponderThread fromh urimap
 | 
						|
 | 
						|
	-- run controller and responder until the remotedaemon dies
 | 
						|
	liftIO $ void $ tryNonAsync $ controller `concurrently` responder
 | 
						|
	debug ["remotedaemon exited"]
 | 
						|
	liftIO $ forceSuccessProcess p pid
 | 
						|
 | 
						|
-- feed from the remoteControl channel into the remotedaemon
 | 
						|
remoteControllerThread :: Handle -> Assistant ()
 | 
						|
remoteControllerThread toh = do
 | 
						|
	clicker <- getAssistant remoteControl
 | 
						|
	forever $ do
 | 
						|
		msg <- liftIO $ readChan clicker
 | 
						|
		debug [show msg]
 | 
						|
		liftIO $ do
 | 
						|
			hPutStrLn toh $ unwords $ formatMessage msg
 | 
						|
			hFlush toh
 | 
						|
 | 
						|
-- read status messages emitted by the remotedaemon and handle them
 | 
						|
remoteResponderThread :: Handle -> MVar (M.Map URI Remote) -> Assistant ()
 | 
						|
remoteResponderThread fromh urimap = go M.empty
 | 
						|
  where
 | 
						|
	go syncalerts = do
 | 
						|
		l <- liftIO $ hGetLine fromh
 | 
						|
		debug [l]
 | 
						|
		case parseMessage l of
 | 
						|
			Just (CONNECTED uri) -> changeconnected S.insert uri
 | 
						|
			Just (DISCONNECTED uri) -> changeconnected S.delete uri
 | 
						|
			Just (SYNCING uri) -> withr uri $ \r ->
 | 
						|
				if M.member (Remote.uuid r) syncalerts
 | 
						|
					then go syncalerts
 | 
						|
					else do
 | 
						|
						i <- addAlert $ syncAlert [r]
 | 
						|
						go (M.insert (Remote.uuid r) i syncalerts)
 | 
						|
			Just (DONESYNCING uri status) -> withr uri $ \r ->
 | 
						|
				case M.lookup (Remote.uuid r) syncalerts of
 | 
						|
					Nothing -> cont
 | 
						|
					Just i -> do
 | 
						|
						let (succeeded, failed) = if status
 | 
						|
							then ([r], [])
 | 
						|
							else ([], [r])
 | 
						|
						updateAlertMap $ mergeAlert i $
 | 
						|
							syncResultAlert succeeded failed
 | 
						|
						go (M.delete (Remote.uuid r) syncalerts)
 | 
						|
			Just (WARNING (RemoteURI uri) msg) -> do
 | 
						|
				void $ addAlert $
 | 
						|
					warningAlert ("RemoteControl "++ show uri) msg
 | 
						|
				cont
 | 
						|
			Nothing -> do
 | 
						|
				debug ["protocol error from remotedaemon: ", l]
 | 
						|
				cont
 | 
						|
	  where
 | 
						|
		cont = go syncalerts
 | 
						|
		withr uri = withRemote uri urimap cont
 | 
						|
		changeconnected sm uri = withr uri $ \r -> do
 | 
						|
			changeCurrentlyConnected $ sm $ Remote.uuid r
 | 
						|
			cont
 | 
						|
 | 
						|
getURIMap :: Annex (M.Map URI Remote)
 | 
						|
getURIMap = Remote.remoteMap' id (\r -> mkk . Git.location <$> Remote.getRepo r)
 | 
						|
  where
 | 
						|
	mkk (Git.Url u) = Just u
 | 
						|
	mkk _ = Nothing
 | 
						|
 | 
						|
withRemote
 | 
						|
	:: RemoteURI
 | 
						|
	-> MVar (M.Map URI Remote)
 | 
						|
	-> Assistant a
 | 
						|
	-> (Remote -> Assistant a)
 | 
						|
	-> Assistant a
 | 
						|
withRemote (RemoteURI uri) remotemap noremote a = do
 | 
						|
	m <- liftIO $ readMVar remotemap
 | 
						|
	case M.lookup uri m of
 | 
						|
		Just r -> a r
 | 
						|
		Nothing -> do
 | 
						|
			{- Reload map, in case a new remote has been added. -}
 | 
						|
			m' <- liftAnnex getURIMap
 | 
						|
			void $ liftIO $ swapMVar remotemap $ m'
 | 
						|
			maybe noremote a (M.lookup uri m')
 |