git-annex/Assistant/Threads/Transferrer.hs

114 lines
3.7 KiB
Haskell
Raw Normal View History

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
import Assistant.Common
2012-07-05 20:34:20 +00:00
import Assistant.ThreadedMonad
import Assistant.DaemonStatus
import Assistant.TransferQueue
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
import Logs.Location
2012-07-05 20:34:20 +00:00
import Annex.Content
import qualified Remote
import Types.Key
import Locations.UserConfig
2012-07-05 20:34:20 +00:00
import System.Process (create_group)
2012-07-05 20:34:20 +00:00
thisThread :: ThreadName
thisThread = "Transferrer"
{- For now only one transfer is run at a time. -}
maxTransfers :: Int
maxTransfers = 1
{- Dispatches transfers from the queue. -}
transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO ()
transfererThread st dstatus transferqueue slots = go =<< readProgramFile
where
go program = getNextTransfer transferqueue dstatus notrunning >>= handle program
handle program Nothing = go program
handle program (Just (t, info)) = do
ifM (runThreadState st $ shouldTransfer t info)
( do
debug thisThread [ "Transferring:" , show t ]
2012-07-29 12:52:57 +00:00
notifyTransfer dstatus
transferThread dstatus slots t info inTransferSlot program
, do
debug thisThread [ "Skipping unnecessary transfer:" , show t ]
-- getNextTransfer added t to the
-- daemonstatus's transfer map.
void $ removeTransfer dstatus t
)
go program
{- Skip transfers that are already running. -}
notrunning i = startedTime i == Nothing
2012-07-05 20:34:20 +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. -}
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
where
2012-07-17 16:06:35 +00:00
key = transferKey t
2012-07-05 20:34:20 +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
-
- A thread is forked off to run the process, and the thread
- occupies one of the transfer slots. If all slots are in use, this will
- 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. -}
transferThread :: DaemonStatusHandle -> TransferSlots -> Transfer -> TransferInfo -> TransferSlotRunner -> FilePath -> IO ()
transferThread dstatus slots t info runner program = case (transferRemote info, associatedFile info) of
(Nothing, _) -> noop
(_, Nothing) -> noop
2012-07-17 16:06:35 +00:00
(Just remote, Just file) -> do
tid <- runner slots $
transferprocess remote file
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
transferprocess remote file = void $ do
(_, _, _, pid)
<- createProcess (proc program $ toCommand params)
{ create_group = True }
status <- waitForProcess pid
addAlert dstatus $
makeAlertFiller (status == ExitSuccess) $
2012-08-06 21:09:23 +00:00
transferFileAlert direction file
where
params =
[ Param "transferkey"
, Param $ key2file $ transferKey t
, Param $ if isdownload
then "--from"
else "--to"
, Param $ Remote.name remote
, Param "--file"
, File file
]