2012-07-03 14:58:40 +00:00
|
|
|
{- git-annex assistant transfer watching thread
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Assistant.Threads.TransferWatcher where
|
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
import Assistant.Common
|
2012-07-03 14:58:40 +00:00
|
|
|
import Assistant.ThreadedMonad
|
|
|
|
import Assistant.DaemonStatus
|
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
|
|
|
import Assistant.TransferQueue
|
2012-09-24 17:16:08 +00:00
|
|
|
import Annex.Content
|
2012-07-03 14:58:40 +00:00
|
|
|
import Logs.Transfer
|
|
|
|
import Utility.DirWatcher
|
|
|
|
import Utility.Types.DirWatcher
|
2012-08-27 18:04:06 +00:00
|
|
|
import qualified Remote
|
2012-07-03 14:58:40 +00:00
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
thisThread :: ThreadName
|
|
|
|
thisThread = "TransferWatcher"
|
|
|
|
|
2012-07-03 14:58:40 +00:00
|
|
|
{- This thread watches for changes to the gitAnnexTransferDir,
|
|
|
|
- and updates the DaemonStatus's map of ongoing transfers. -}
|
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
|
|
|
transferWatcherThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> NamedThread
|
|
|
|
transferWatcherThread st dstatus transferqueue = thread $ do
|
2012-10-12 05:17:45 +00:00
|
|
|
g <- runThreadState st gitRepo
|
2012-07-03 14:58:40 +00:00
|
|
|
let dir = gitAnnexTransferDir g
|
|
|
|
createDirectoryIfMissing True dir
|
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
|
|
|
let hook a = Just $ runHandler st dstatus transferqueue a
|
2012-07-03 14:58:40 +00:00
|
|
|
let hooks = mkWatchHooks
|
|
|
|
{ addHook = hook onAdd
|
|
|
|
, delHook = hook onDel
|
2012-09-20 21:24:40 +00:00
|
|
|
, modifyHook = hook onModify
|
2012-07-03 14:58:40 +00:00
|
|
|
, errHook = hook onErr
|
|
|
|
}
|
|
|
|
void $ watchDir dir (const False) hooks id
|
2012-07-20 23:29:59 +00:00
|
|
|
debug thisThread ["watching for transfers"]
|
2012-09-06 18:56:04 +00:00
|
|
|
where
|
|
|
|
thread = NamedThread thisThread
|
2012-07-03 14:58:40 +00:00
|
|
|
|
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
|
|
|
type Handler = ThreadState -> DaemonStatusHandle -> TransferQueue -> FilePath -> Maybe FileStatus -> IO ()
|
2012-07-03 14:58:40 +00:00
|
|
|
|
|
|
|
{- Runs an action handler.
|
|
|
|
-
|
|
|
|
- Exceptions are ignored, otherwise a whole thread could be crashed.
|
|
|
|
-}
|
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
|
|
|
runHandler :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Handler -> FilePath -> Maybe FileStatus -> IO ()
|
|
|
|
runHandler st dstatus transferqueue handler file filestatus = void $
|
2012-07-03 14:58:40 +00:00
|
|
|
either print (const noop) =<< tryIO go
|
|
|
|
where
|
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
|
|
|
go = handler st dstatus transferqueue file filestatus
|
2012-07-03 14:58:40 +00:00
|
|
|
|
|
|
|
{- Called when there's an error with inotify. -}
|
|
|
|
onErr :: Handler
|
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
|
|
|
onErr _ _ _ msg _ = error msg
|
2012-07-03 14:58:40 +00:00
|
|
|
|
2012-07-06 20:30:55 +00:00
|
|
|
{- Called when a new transfer information file is written. -}
|
2012-07-03 14:58:40 +00:00
|
|
|
onAdd :: Handler
|
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
|
|
|
onAdd st dstatus _ file _ = case parseTransferFile file of
|
2012-07-03 14:58:40 +00:00
|
|
|
Nothing -> noop
|
2012-07-28 22:02:11 +00:00
|
|
|
Just t -> go t =<< runThreadState st (checkTransfer t)
|
2012-07-05 20:34:20 +00:00
|
|
|
where
|
2012-07-06 22:44:13 +00:00
|
|
|
go _ Nothing = noop -- transfer already finished
|
2012-07-20 23:29:59 +00:00
|
|
|
go t (Just info) = do
|
2012-07-28 22:02:11 +00:00
|
|
|
debug thisThread
|
2012-07-20 23:29:59 +00:00
|
|
|
[ "transfer starting:"
|
|
|
|
, show t
|
|
|
|
]
|
2012-10-14 18:51:11 +00:00
|
|
|
r <- headMaybe . filter (sameuuid t)
|
|
|
|
<$> runThreadState st Remote.remoteList
|
2012-08-29 18:05:56 +00:00
|
|
|
updateTransferInfo dstatus t info
|
2012-08-27 18:04:06 +00:00
|
|
|
{ transferRemote = r }
|
|
|
|
sameuuid t r = Remote.uuid r == transferUUID t
|
2012-07-03 14:58:40 +00:00
|
|
|
|
2012-09-20 21:24:40 +00:00
|
|
|
{- Called when a transfer information file is updated.
|
|
|
|
-
|
|
|
|
- The only thing that should change in the transfer info is the
|
|
|
|
- bytesComplete, so that's the only thing updated in the DaemonStatus. -}
|
|
|
|
onModify :: Handler
|
|
|
|
onModify _ dstatus _ file _ = do
|
|
|
|
case parseTransferFile file of
|
|
|
|
Nothing -> noop
|
|
|
|
Just t -> go t =<< readTransferInfoFile Nothing file
|
|
|
|
where
|
|
|
|
go _ Nothing = noop
|
|
|
|
go t (Just newinfo) = alterTransferInfo dstatus t $ \info ->
|
|
|
|
info { bytesComplete = bytesComplete newinfo }
|
|
|
|
|
|
|
|
{- This thread can only watch transfer sizes when the DirWatcher supports
|
|
|
|
- tracking modificatons to files. -}
|
|
|
|
watchesTransferSize :: Bool
|
|
|
|
watchesTransferSize = modifyTracked
|
|
|
|
|
2012-07-18 23:13:56 +00:00
|
|
|
{- Called when a transfer information file is removed. -}
|
2012-07-03 14:58:40 +00:00
|
|
|
onDel :: Handler
|
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
|
|
|
onDel st dstatus transferqueue file _ = case parseTransferFile file of
|
2012-07-03 14:58:40 +00:00
|
|
|
Nothing -> noop
|
2012-07-20 23:29:59 +00:00
|
|
|
Just t -> do
|
|
|
|
debug thisThread
|
|
|
|
[ "transfer finishing:"
|
|
|
|
, show t
|
|
|
|
]
|
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
|
|
|
minfo <- removeTransfer dstatus t
|
|
|
|
|
|
|
|
{- Queue uploads of files we successfully downloaded,
|
|
|
|
- spreading them out to other reachable remotes. -}
|
|
|
|
case (minfo, transferDirection t) of
|
|
|
|
(Just info, Download) -> runThreadState st $
|
2012-09-24 17:16:08 +00:00
|
|
|
whenM (inAnnex $ transferKey t) $
|
|
|
|
queueTransfersMatching
|
|
|
|
(/= transferUUID t)
|
|
|
|
Later transferqueue dstatus
|
|
|
|
(transferKey t)
|
|
|
|
(associatedFile info)
|
|
|
|
Upload
|
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
|
|
|
_ -> noop
|