port transferkeys to windows; make stopping in progress transfers work too (probably)

transferkeys had used special FDs for communication, but that would be
quite annoying to do in Windows.

Instead, use stdin and stdout. But, to avoid commands like rsync stomping
on them and messing up the communications channel, they're duplicated to a
different handle; stdin is replaced with a null handle, and stdout is
replaced with a copy of stderr. This should all work in windows too.

Stopping in progress transfers may work on windows.. if the types unify
anyway. ;) May need some more porting.
This commit is contained in:
Joey Hess 2013-12-10 23:19:18 -04:00
parent 0fbbe79d8f
commit 2fd63f3cfa
6 changed files with 51 additions and 79 deletions

View file

@ -38,6 +38,8 @@ import qualified Control.Concurrent.MSemN as MSemN
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import System.Posix.Process (getProcessGroupIDOf) import System.Posix.Process (getProcessGroupIDOf)
import System.Posix.Signals (signalProcessGroup, sigTERM, sigKILL) import System.Posix.Signals (signalProcessGroup, sigTERM, sigKILL)
#else
import System.Win32.Console (generateConsoleCtrlEvent, cTRL_C_EVENT, cTRL_BREAK_EVENT)
#endif #endif
type TransferGenerator = Assistant (Maybe (Transfer, TransferInfo, Transferrer -> Assistant ())) type TransferGenerator = Assistant (Maybe (Transfer, TransferInfo, Transferrer -> Assistant ()))
@ -252,18 +254,21 @@ cancelTransfer pause t = do
signalthread tid signalthread tid
| pause = throwTo tid PauseTransfer | pause = throwTo tid PauseTransfer
| otherwise = killThread tid | otherwise = killThread tid
{- In order to stop helper processes like rsync,
- kill the whole process group of the process
- running the transfer. -}
killproc pid = void $ tryIO $ do killproc pid = void $ tryIO $ do
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
{- In order to stop helper processes like rsync,
- kill the whole process group of the process
- running the transfer. -}
g <- getProcessGroupIDOf pid g <- getProcessGroupIDOf pid
void $ tryIO $ signalProcessGroup sigTERM g void $ tryIO $ signalProcessGroup sigTERM g
threadDelay 50000 -- 0.05 second grace period graceperiod
void $ tryIO $ signalProcessGroup sigKILL g void $ tryIO $ signalProcessGroup sigKILL g
#else #else
error "TODO: cancelTransfer not implemented on Windows" void $ tryIO $ generateConsoleCtrlEvent cTRL_C_EVENT pid
graceperiod
void $ tryIO $ generateConsoleCtrlEvent cTRL_BREAK_EVENT pid
#endif #endif
graceperiod = threadDelay 50000 -- 0.05 second
{- Start or resume a transfer. -} {- Start or resume a transfer. -}
startTransfer :: Transfer -> Assistant () startTransfer :: Transfer -> Assistant ()

View file

@ -5,8 +5,6 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE CPP #-}
module Assistant.TransferrerPool where module Assistant.TransferrerPool where
import Assistant.Common import Assistant.Common
@ -14,12 +12,10 @@ import Assistant.Types.TransferrerPool
import Logs.Transfer import Logs.Transfer
import Utility.Batch import Utility.Batch
#ifndef mingw32_HOST_OS
import qualified Command.TransferKeys as T import qualified Command.TransferKeys as T
#endif
import Control.Concurrent.STM import Control.Concurrent.STM
import System.Process (create_group) import System.Process (create_group, std_in, std_out)
import Control.Exception (throw) import Control.Exception (throw)
import Control.Concurrent import Control.Concurrent
@ -44,46 +40,30 @@ withTransferrer program batchmaker pool a = do
- finish. -} - finish. -}
performTransfer :: Transferrer -> Transfer -> AssociatedFile -> IO Bool performTransfer :: Transferrer -> Transfer -> AssociatedFile -> IO Bool
performTransfer transferrer t f = catchBoolIO $ do performTransfer transferrer t f = catchBoolIO $ do
#ifndef mingw32_HOST_OS
T.sendRequest t f (transferrerWrite transferrer) T.sendRequest t f (transferrerWrite transferrer)
T.readResponse (transferrerRead transferrer) T.readResponse (transferrerRead transferrer)
#else
error "TODO performTransfer not implemented on Windows"
#endif
{- Starts a new git-annex transferkeys process, setting up a pipe {- Starts a new git-annex transferkeys process, setting up handles
- that will be used to communicate with it. -} - that will be used to communicate with it. -}
mkTransferrer :: FilePath -> BatchCommandMaker -> IO Transferrer mkTransferrer :: FilePath -> BatchCommandMaker -> IO Transferrer
mkTransferrer program batchmaker = do mkTransferrer program batchmaker = do
#ifndef mingw32_HOST_OS
(myread, twrite) <- createPipe
(tread, mywrite) <- createPipe
mapM_ (\fd -> setFdOption fd CloseOnExec True) [myread, mywrite]
let params =
[ Param "transferkeys"
, Param "--readfd", Param $ show tread
, Param "--writefd", Param $ show twrite
]
{- It runs as a batch job. -} {- It runs as a batch job. -}
let (program', params') = batchmaker (program, params) let (program', params') = batchmaker (program, [Param "transferkeys"])
{- It's put into its own group so that the whole group can be {- It's put into its own group so that the whole group can be
- killed to stop a transfer. -} - killed to stop a transfer. -}
(_, _, _, pid) <- createProcess (proc program' $ toCommand params') (Just writeh, Just readh, _, pid) <- createProcess
{ create_group = True } (proc program' $ toCommand params')
closeFd twrite { create_group = True
closeFd tread , std_in = CreatePipe
myreadh <- fdToHandle myread , std_out = CreatePipe
mywriteh <- fdToHandle mywrite }
fileEncoding myreadh fileEncoding readh
fileEncoding mywriteh fileEncoding writeh
return $ Transferrer return $ Transferrer
{ transferrerRead = myreadh { transferrerRead = readh
, transferrerWrite = mywriteh , transferrerWrite = writeh
, transferrerHandle = pid , transferrerHandle = pid
} }
#else
error "TODO mkTransferrer not implemented on Windows"
#endif
{- Checks if a Transferrer is still running. If not, makes a new one. -} {- Checks if a Transferrer is still running. If not, makes a new one. -}
checkTransferrer :: FilePath -> BatchCommandMaker -> Transferrer -> IO Transferrer checkTransferrer :: FilePath -> BatchCommandMaker -> Transferrer -> IO Transferrer

View file

@ -16,39 +16,21 @@ import Logs.Location
import Logs.Transfer import Logs.Transfer
import qualified Remote import qualified Remote
import Types.Key import Types.Key
import qualified Option
import GHC.IO.Handle
data TransferRequest = TransferRequest Direction Remote Key AssociatedFile data TransferRequest = TransferRequest Direction Remote Key AssociatedFile
def :: [Command] def :: [Command]
def = [withOptions options $ def = [command "transferkeys" paramNothing seek
command "transferkeys" paramNothing seek
SectionPlumbing "transfers keys"] SectionPlumbing "transfers keys"]
options :: [Option]
options = [readFdOption, writeFdOption]
readFdOption :: Option
readFdOption = Option.field [] "readfd" paramNumber "read from this fd"
writeFdOption :: Option
writeFdOption = Option.field [] "writefd" paramNumber "write to this fd"
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withField readFdOption convertFd $ \readh -> seek = [withNothing start]
withField writeFdOption convertFd $ \writeh ->
withNothing $ start readh writeh]
convertFd :: Maybe String -> Annex (Maybe Handle) start :: CommandStart
convertFd Nothing = return Nothing start = withHandles $ \(readh, writeh) -> do
convertFd (Just s) = liftIO $ runRequests readh writeh runner
case readish s of
Nothing -> error "bad fd"
Just fd -> Just <$> fdToHandle fd
start :: Maybe Handle -> Maybe Handle -> CommandStart
start readh writeh = do
runRequests (fromMaybe stdin readh) (fromMaybe stdout writeh) runner
stop stop
where where
runner (TransferRequest direction remote key file) runner (TransferRequest direction remote key file)
@ -61,6 +43,21 @@ start readh writeh = do
| otherwise = download (Remote.uuid remote) key file forwardRetry $ \p -> | otherwise = download (Remote.uuid remote) key file forwardRetry $ \p ->
getViaTmp key $ \t -> Remote.retrieveKeyFile remote key file t p getViaTmp key $ \t -> Remote.retrieveKeyFile remote key file t p
{- stdin and stdout are connected with the caller, to be used for
- communication with it. But doing a transfer might involve something
- that tries to read from stdin, or write to stdout. To avoid that, close
- stdin, and duplicate stderr to stdout. Return two new handles
- that are duplicates of the original (stdin, stdout). -}
withHandles :: ((Handle, Handle) -> Annex a) -> Annex a
withHandles a = do
readh <- liftIO $ hDuplicate stdin
writeh <- liftIO $ hDuplicate stdout
liftIO $ do
nullh <- openFile devNull ReadMode
nullh `hDuplicateTo` stdin
stderr `hDuplicateTo` stdout
a (readh, writeh)
runRequests runRequests
:: Handle :: Handle
-> Handle -> Handle

View file

@ -1,6 +1,6 @@
{- git-annex main program {- git-annex main program
- -
- Copyright 2010 Joey Hess <joey@kitenet.net> - Copyright 2010-2013 Joey Hess <joey@kitenet.net>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
@ -23,9 +23,7 @@ import qualified Command.Get
import qualified Command.FromKey import qualified Command.FromKey
import qualified Command.DropKey import qualified Command.DropKey
import qualified Command.TransferKey import qualified Command.TransferKey
#ifndef mingw32_HOST_OS
import qualified Command.TransferKeys import qualified Command.TransferKeys
#endif
import qualified Command.ReKey import qualified Command.ReKey
import qualified Command.Reinject import qualified Command.Reinject
import qualified Command.Fix import qualified Command.Fix
@ -129,9 +127,7 @@ cmds = concat
, Command.FromKey.def , Command.FromKey.def
, Command.DropKey.def , Command.DropKey.def
, Command.TransferKey.def , Command.TransferKey.def
#ifndef mingw32_HOST_OS
, Command.TransferKeys.def , Command.TransferKeys.def
#endif
, Command.ReKey.def , Command.ReKey.def
, Command.Fix.def , Command.Fix.def
, Command.Fsck.def , Command.Fsck.def

View file

@ -26,12 +26,12 @@ module Utility.Process (
withHandle, withHandle,
withBothHandles, withBothHandles,
withQuietOutput, withQuietOutput,
withNullHandle,
createProcess, createProcess,
startInteractiveProcess, startInteractiveProcess,
stdinHandle, stdinHandle,
stdoutHandle, stdoutHandle,
stderrHandle, stderrHandle,
devNull,
) where ) where
import qualified System.Process import qualified System.Process
@ -280,20 +280,18 @@ withQuietOutput
:: CreateProcessRunner :: CreateProcessRunner
-> CreateProcess -> CreateProcess
-> IO () -> IO ()
withQuietOutput creator p = withNullHandle $ \nullh -> do withQuietOutput creator p = withFile devNull WriteMode $ \nullh -> do
let p' = p let p' = p
{ std_out = UseHandle nullh { std_out = UseHandle nullh
, std_err = UseHandle nullh , std_err = UseHandle nullh
} }
creator p' $ const $ return () creator p' $ const $ return ()
withNullHandle :: (Handle -> IO a) -> IO a devNull :: FilePath
withNullHandle = withFile devnull WriteMode
where
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
devnull = "/dev/null" devNull = "/dev/null"
#else #else
devnull = "NUL" devNull = "NUL"
#endif #endif
{- Extract a desired handle from createProcess's tuple. {- Extract a desired handle from createProcess's tuple.

View file

@ -17,10 +17,6 @@ now! --[[Joey]]
may be unsafe. may be unsafe.
* `git annex assistant` has not been tested, is probably quite incomplete * `git annex assistant` has not been tested, is probably quite incomplete
and/or buggy. and/or buggy.
* Assistant is known to not transfer any files.
(transferrer doesn't built yet)
Need a createPipe for windows. See the mkAnonPipe in
System.Process source. (cbits/runProcess.c)
* No XMPP support (needs a lot of C libraries which are available in * No XMPP support (needs a lot of C libraries which are available in
cygwin, but pkg-config does not list them once installed). cygwin, but pkg-config does not list them once installed).
* Doesn't daemonize. Maybe use * Doesn't daemonize. Maybe use