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-09-06 18:56:04 +00:00
|
|
|
transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> NamedThread
|
|
|
|
transfererThread st dstatus transferqueue slots = thread $ go =<< readProgramFile
|
2012-07-07 00:48:51 +00:00
|
|
|
where
|
2012-09-06 18:56:04 +00:00
|
|
|
thread = NamedThread thisThread
|
2012-08-28 21:17:09 +00:00
|
|
|
go program = forever $ inTransferSlot dstatus slots $
|
2012-08-29 20:30:40 +00:00
|
|
|
maybe (return Nothing) (uncurry $ startTransfer st dstatus program)
|
|
|
|
=<< getNextTransfer transferqueue dstatus notrunning
|
2012-07-29 17:37:26 +00:00
|
|
|
{- Skip transfers that are already running. -}
|
2012-09-13 04:57:52 +00:00
|
|
|
notrunning = isNothing . startedTime
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-08-29 21:32:41 +00:00
|
|
|
{- By the time this is called, the daemonstatus's transfer map should
|
2012-08-29 20:30:40 +00:00
|
|
|
- already have been updated to include the transfer. -}
|
|
|
|
startTransfer :: ThreadState -> DaemonStatusHandle -> FilePath -> Transfer -> TransferInfo -> TransferGenerator
|
|
|
|
startTransfer st dstatus program t info = case (transferRemote info, associatedFile info) of
|
|
|
|
(Just remote, Just file) -> ifM (runThreadState st $ shouldTransfer t info)
|
|
|
|
( do
|
|
|
|
debug thisThread [ "Transferring:" , show t ]
|
|
|
|
notifyTransfer dstatus
|
|
|
|
return $ Just (t, info, transferprocess remote file)
|
|
|
|
, do
|
|
|
|
debug thisThread [ "Skipping unnecessary transfer:" , show t ]
|
|
|
|
void $ removeTransfer dstatus t
|
|
|
|
return Nothing
|
|
|
|
)
|
|
|
|
_ -> return Nothing
|
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 }
|
when a Download finishes, queue Uploads
This ensures file propigate takes place in situations such as: Usb drive A
is connected to B. A's master branch is already in sync with B, but it is
being used to sneakernet some files around, so B downloads those. There is no
master branch change, so C does not request these files. B needs to upload
the files it just downloaded on to C, etc.
My first try at this, I saw loops happen. B uploaded to C, which then
tried to upload back to B (because it had not received the updated
git-annex branch from B yet). B already had the file, but it still created
a transfer info file from the incoming transfer, and its watcher saw
that be removed, and tried to upload back to C.
These loops should have been fixed by my previous commit. (They never
affected ssh remotes, only local ones, it seemed.) While C might still try
to upload to B, or to some other remote that already has the file, the
extra work dies out there.
2012-09-18 18:10:33 +00:00
|
|
|
{- Alerts are only shown for successful transfers.
|
|
|
|
- Transfers can temporarily fail for many reasons,
|
|
|
|
- so there's no point in bothering the user about
|
|
|
|
- those. The assistant should recover. -}
|
2012-09-17 17:41:13 +00:00
|
|
|
whenM ((==) ExitSuccess <$> waitForProcess pid) $ void $
|
2012-08-29 16:58:29 +00:00
|
|
|
addAlert dstatus $
|
2012-09-17 17:41:13 +00:00
|
|
|
makeAlertFiller True $
|
|
|
|
transferFileAlert direction True file
|
2012-08-10 19:45:00 +00:00
|
|
|
where
|
|
|
|
params =
|
2012-08-24 21:23:58 +00:00
|
|
|
[ Param "transferkey"
|
2012-09-24 17:36:05 +00:00
|
|
|
, Param "--quiet"
|
2012-08-24 21:23:58 +00:00
|
|
|
, 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
|
|
|
|
]
|
2012-08-29 20:30:40 +00:00
|
|
|
|
|
|
|
{- Checks if the file to download is already present, or the remote
|
|
|
|
- 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
|
|
|
|
key = transferKey t
|