2012-07-05 20:34:20 +00:00
|
|
|
{- git-annex assistant data transferrer thread
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Assistant.Threads.Transferrer where
|
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
import Assistant.Common
|
2012-07-05 20:34:20 +00:00
|
|
|
import Assistant.ThreadedMonad
|
|
|
|
import Assistant.DaemonStatus
|
|
|
|
import Assistant.TransferQueue
|
2012-07-06 20:39:07 +00:00
|
|
|
import Assistant.TransferSlots
|
2012-08-06 21:09:23 +00:00
|
|
|
import Assistant.Alert
|
2012-07-05 20:34:20 +00:00
|
|
|
import Logs.Transfer
|
2012-07-07 16:50:20 +00:00
|
|
|
import Logs.Location
|
2012-07-05 20:34:20 +00:00
|
|
|
import Annex.Content
|
2012-07-07 16:50:20 +00:00
|
|
|
import qualified Remote
|
2012-08-24 21:23:58 +00:00
|
|
|
import Types.Key
|
2012-08-27 17:43:03 +00:00
|
|
|
import Locations.UserConfig
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-08-10 19:45:00 +00:00
|
|
|
import System.Process (create_group)
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
thisThread :: ThreadName
|
|
|
|
thisThread = "Transferrer"
|
|
|
|
|
2012-07-06 00:57:06 +00:00
|
|
|
{- For now only one transfer is run at a time. -}
|
|
|
|
maxTransfers :: Int
|
|
|
|
maxTransfers = 1
|
|
|
|
|
|
|
|
{- Dispatches transfers from the queue. -}
|
2012-07-06 20:39:07 +00:00
|
|
|
transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO ()
|
2012-08-27 17:43:03 +00:00
|
|
|
transfererThread st dstatus transferqueue slots = go =<< readProgramFile
|
2012-07-07 00:48:51 +00:00
|
|
|
where
|
2012-08-27 17:43:03 +00:00
|
|
|
go program = getNextTransfer transferqueue dstatus notrunning >>= handle program
|
|
|
|
handle program Nothing = go program
|
|
|
|
handle program (Just (t, info)) = do
|
2012-07-29 17:37:26 +00:00
|
|
|
ifM (runThreadState st $ shouldTransfer t info)
|
2012-07-20 23:29:59 +00:00
|
|
|
( do
|
|
|
|
debug thisThread [ "Transferring:" , show t ]
|
2012-07-29 12:52:57 +00:00
|
|
|
notifyTransfer dstatus
|
2012-08-27 17:43:03 +00:00
|
|
|
transferThread dstatus slots t info inTransferSlot program
|
2012-07-28 22:47:24 +00:00
|
|
|
, do
|
|
|
|
debug thisThread [ "Skipping unnecessary transfer:" , show t ]
|
|
|
|
-- getNextTransfer added t to the
|
|
|
|
-- daemonstatus's transfer map.
|
|
|
|
void $ removeTransfer dstatus t
|
2012-07-20 23:29:59 +00:00
|
|
|
)
|
2012-08-27 17:43:03 +00:00
|
|
|
go program
|
2012-07-29 17:37:26 +00:00
|
|
|
{- Skip transfers that are already running. -}
|
|
|
|
notrunning i = startedTime i == Nothing
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-07-29 17:37:26 +00:00
|
|
|
{- Checks if the file to download is already present, or the remote
|
2012-07-17 16:06:35 +00:00
|
|
|
- being uploaded to isn't known to have the file. -}
|
2012-07-29 17:37:26 +00:00
|
|
|
shouldTransfer :: Transfer -> TransferInfo -> Annex Bool
|
|
|
|
shouldTransfer t info
|
|
|
|
| transferDirection t == Download =
|
|
|
|
not <$> inAnnex key
|
|
|
|
| transferDirection t == Upload =
|
|
|
|
{- Trust the location log to check if the
|
|
|
|
- remote already has the key. This avoids
|
|
|
|
- a roundtrip to the remote. -}
|
|
|
|
case transferRemote info of
|
|
|
|
Nothing -> return False
|
|
|
|
Just remote ->
|
|
|
|
notElem (Remote.uuid remote)
|
|
|
|
<$> loggedLocations key
|
|
|
|
| otherwise = return False
|
2012-07-06 00:57:06 +00:00
|
|
|
where
|
2012-07-17 16:06:35 +00:00
|
|
|
key = transferKey t
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-08-10 19:45:00 +00:00
|
|
|
{- A sepeate git-annex process is forked off to run a transfer,
|
|
|
|
- running in its own process group. This allows killing it and all its
|
|
|
|
- children if the user decides to cancel the transfer.
|
2012-07-05 20:34:20 +00:00
|
|
|
-
|
fork off git-annex copy for transfers
This doesn't quite work, because canceling a transfer sends a signal
to git-annex, but not to rsync (etc).
Looked at making git-annex run in its own process group, which could then
be killed, and would kill child processes. But, rsync checks if it's
process group is the foreground process group and doesn't show progress if
not, and when git has run git-annex, if git-annex makes a new process
group, that is not the case. Also, if git has run git-annex, ctrl-c
wouldn't be propigated to it if it made a new process group.
So this seems like a blind alley, but recording it here just in case.
2012-08-10 18:14:08 +00:00
|
|
|
- A thread is forked off to run the process, and the thread
|
2012-08-10 19:45:00 +00:00
|
|
|
- occupies one of the transfer slots. If all slots are in use, this will
|
fork off git-annex copy for transfers
This doesn't quite work, because canceling a transfer sends a signal
to git-annex, but not to rsync (etc).
Looked at making git-annex run in its own process group, which could then
be killed, and would kill child processes. But, rsync checks if it's
process group is the foreground process group and doesn't show progress if
not, and when git has run git-annex, if git-annex makes a new process
group, that is not the case. Also, if git has run git-annex, ctrl-c
wouldn't be propigated to it if it made a new process group.
So this seems like a blind alley, but recording it here just in case.
2012-08-10 18:14:08 +00:00
|
|
|
- block until one becomes available. The thread's id is also recorded in
|
|
|
|
- the transfer info; the thread will also be killed when a transfer is
|
|
|
|
- stopped, to avoid it displaying any alert about the transfer having
|
|
|
|
- failed. -}
|
2012-08-27 17:43:03 +00:00
|
|
|
transferThread :: DaemonStatusHandle -> TransferSlots -> Transfer -> TransferInfo -> TransferSlotRunner -> FilePath -> IO ()
|
|
|
|
transferThread dstatus slots t info runner program = case (transferRemote info, associatedFile info) of
|
2012-07-07 16:50:20 +00:00
|
|
|
(Nothing, _) -> noop
|
|
|
|
(_, Nothing) -> noop
|
2012-07-17 16:06:35 +00:00
|
|
|
(Just remote, Just file) -> do
|
2012-08-12 16:36:08 +00:00
|
|
|
tid <- runner slots $
|
2012-07-18 23:13:56 +00:00
|
|
|
transferprocess remote file
|
2012-08-10 19:45:00 +00:00
|
|
|
updateTransferInfo dstatus t $ info { transferTid = Just tid }
|
2012-07-05 20:34:20 +00:00
|
|
|
where
|
2012-08-06 21:09:23 +00:00
|
|
|
direction = transferDirection t
|
|
|
|
isdownload = direction == Download
|
2012-07-07 16:50:20 +00:00
|
|
|
|
fork off git-annex copy for transfers
This doesn't quite work, because canceling a transfer sends a signal
to git-annex, but not to rsync (etc).
Looked at making git-annex run in its own process group, which could then
be killed, and would kill child processes. But, rsync checks if it's
process group is the foreground process group and doesn't show progress if
not, and when git has run git-annex, if git-annex makes a new process
group, that is not the case. Also, if git has run git-annex, ctrl-c
wouldn't be propigated to it if it made a new process group.
So this seems like a blind alley, but recording it here just in case.
2012-08-10 18:14:08 +00:00
|
|
|
transferprocess remote file = void $ do
|
2012-08-10 19:45:00 +00:00
|
|
|
(_, _, _, pid)
|
2012-08-27 17:43:03 +00:00
|
|
|
<- createProcess (proc program $ toCommand params)
|
2012-08-10 19:45:00 +00:00
|
|
|
{ create_group = True }
|
|
|
|
status <- waitForProcess pid
|
fork off git-annex copy for transfers
This doesn't quite work, because canceling a transfer sends a signal
to git-annex, but not to rsync (etc).
Looked at making git-annex run in its own process group, which could then
be killed, and would kill child processes. But, rsync checks if it's
process group is the foreground process group and doesn't show progress if
not, and when git has run git-annex, if git-annex makes a new process
group, that is not the case. Also, if git has run git-annex, ctrl-c
wouldn't be propigated to it if it made a new process group.
So this seems like a blind alley, but recording it here just in case.
2012-08-10 18:14:08 +00:00
|
|
|
addAlert dstatus $
|
2012-08-10 19:45:00 +00:00
|
|
|
makeAlertFiller (status == ExitSuccess) $
|
2012-08-06 21:09:23 +00:00
|
|
|
transferFileAlert direction file
|
2012-08-10 19:45:00 +00:00
|
|
|
where
|
|
|
|
params =
|
2012-08-24 21:23:58 +00:00
|
|
|
[ Param "transferkey"
|
|
|
|
, Param $ key2file $ transferKey t
|
2012-08-10 19:45:00 +00:00
|
|
|
, Param $ if isdownload
|
|
|
|
then "--from"
|
|
|
|
else "--to"
|
|
|
|
, Param $ Remote.name remote
|
2012-08-24 21:23:58 +00:00
|
|
|
, Param "--file"
|
2012-08-10 19:45:00 +00:00
|
|
|
, File file
|
|
|
|
]
|