2012-07-02 20:07:39 +00:00
|
|
|
{- git-annex assistant pending transfer queue
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
|
2012-07-02 20:07:39 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-07-02 20:07:39 +00:00
|
|
|
-}
|
|
|
|
|
2014-01-06 01:30:48 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
|
|
|
|
2012-07-25 18:54:09 +00:00
|
|
|
module Assistant.TransferQueue (
|
|
|
|
TransferQueue,
|
|
|
|
Schedule(..),
|
|
|
|
newTransferQueue,
|
2012-07-27 15:47:34 +00:00
|
|
|
getTransferQueue,
|
2012-07-25 18:54:09 +00:00
|
|
|
queueTransfers,
|
2012-09-18 18:24:51 +00:00
|
|
|
queueTransfersMatching,
|
2012-09-18 01:05:50 +00:00
|
|
|
queueDeferredDownloads,
|
2012-07-25 18:54:09 +00:00
|
|
|
queueTransfer,
|
|
|
|
queueTransferAt,
|
2012-08-23 19:22:23 +00:00
|
|
|
queueTransferWhenSmall,
|
2012-08-08 21:55:56 +00:00
|
|
|
getNextTransfer,
|
2012-08-29 20:30:40 +00:00
|
|
|
getMatchingTransfers,
|
2012-08-29 19:56:47 +00:00
|
|
|
dequeueTransfers,
|
2012-07-25 18:54:09 +00:00
|
|
|
) where
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-10-30 21:14:26 +00:00
|
|
|
import Assistant.Common
|
2012-07-05 16:21:22 +00:00
|
|
|
import Assistant.DaemonStatus
|
2012-10-30 18:34:48 +00:00
|
|
|
import Assistant.Types.TransferQueue
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2012-07-02 20:07:39 +00:00
|
|
|
import Logs.Transfer
|
|
|
|
import Types.Remote
|
2012-07-05 16:21:22 +00:00
|
|
|
import qualified Remote
|
2012-08-26 19:39:02 +00:00
|
|
|
import qualified Types.Remote as Remote
|
git style filename quoting controlled by core.quotePath
This is by no means complete, but escaping filenames in actionItemDesc does
cover most commands.
Note that for ActionItemBranchFilePath, the value is branch:file, and I
choose to only quote the file part (if necessary). I considered quoting the
whole thing. But, branch names cannot contain control characters, and while
they can contain unicode, git coes not quote unicode when displaying branch
names. So, it would be surprising for git-annex to quote unicode in a
branch name.
The find command is the most obvious command that still needs to be
dealt with. There are probably other places that filenames also get
displayed, eg embedded in error messages.
Some other commands use ActionItemOther with a filename, I think that
ActionItemOther should either be pre-sanitized, or should explicitly not
be used for filenames, so that needs more work.
When --json is used, unicode does not get escaped, but control
characters were already escaped in json.
(Key escaping may turn out to be needed, but I'm ignoring that for now.)
Sponsored-by: unqueued on Patreon
2023-04-08 18:20:02 +00:00
|
|
|
import qualified Annex
|
2012-10-09 16:18:41 +00:00
|
|
|
import Annex.Wanted
|
2013-04-25 05:09:37 +00:00
|
|
|
import Utility.TList
|
2012-07-02 20:07:39 +00:00
|
|
|
|
|
|
|
import Control.Concurrent.STM
|
2018-04-22 17:28:31 +00:00
|
|
|
import qualified Data.Map.Strict as M
|
2013-04-02 19:51:58 +00:00
|
|
|
import qualified Data.Set as S
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2013-03-01 19:23:59 +00:00
|
|
|
type Reason = String
|
|
|
|
|
2012-07-27 15:47:34 +00:00
|
|
|
{- Reads the queue's content without blocking or changing it. -}
|
2012-10-30 21:14:26 +00:00
|
|
|
getTransferQueue :: Assistant [(Transfer, TransferInfo)]
|
2013-04-25 05:33:44 +00:00
|
|
|
getTransferQueue = (atomically . readTList . queuelist) <<~ transferQueue
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-25 18:02:50 +00:00
|
|
|
stubInfo :: AssociatedFile -> Remote -> TransferInfo
|
2012-09-18 01:05:50 +00:00
|
|
|
stubInfo f r = stubTransferInfo
|
|
|
|
{ transferRemote = Just r
|
2012-07-02 20:07:39 +00:00
|
|
|
, associatedFile = f
|
|
|
|
}
|
|
|
|
|
2012-10-09 16:18:41 +00:00
|
|
|
{- Adds transfers to queue for some of the known remotes.
|
|
|
|
- Honors preferred content settings, only transferring wanted files. -}
|
2014-01-23 20:51:16 +00:00
|
|
|
queueTransfers :: Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant Bool
|
2012-09-18 18:24:51 +00:00
|
|
|
queueTransfers = queueTransfersMatching (const True)
|
|
|
|
|
|
|
|
{- Adds transfers to queue for some of the known remotes, that match a
|
2012-10-09 16:18:41 +00:00
|
|
|
- condition. Honors preferred content settings. -}
|
2014-01-23 20:51:16 +00:00
|
|
|
queueTransfersMatching :: (UUID -> Bool) -> Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant Bool
|
2013-03-01 19:23:59 +00:00
|
|
|
queueTransfersMatching matching reason schedule k f direction
|
2014-01-23 20:51:16 +00:00
|
|
|
| direction == Download = ifM (liftAnnex $ wantGet True (Just k) f)
|
|
|
|
( go
|
|
|
|
, return False
|
|
|
|
)
|
2012-10-09 16:18:41 +00:00
|
|
|
| otherwise = go
|
2012-10-30 21:14:26 +00:00
|
|
|
where
|
|
|
|
go = do
|
2017-09-20 17:27:59 +00:00
|
|
|
rs <- liftAnnex . selectremotes =<< getDaemonStatus
|
2012-10-30 21:14:26 +00:00
|
|
|
let matchingrs = filter (matching . Remote.uuid) rs
|
|
|
|
if null matchingrs
|
2014-01-23 20:51:16 +00:00
|
|
|
then do
|
|
|
|
defer
|
|
|
|
return False
|
|
|
|
else do
|
|
|
|
forM_ matchingrs $ \r ->
|
|
|
|
enqueue reason schedule (gentransfer r) (stubInfo f r)
|
|
|
|
return True
|
2017-09-20 17:27:59 +00:00
|
|
|
selectremotes st
|
2012-10-30 21:14:26 +00:00
|
|
|
{- Queue downloads from all remotes that
|
2013-04-02 19:51:58 +00:00
|
|
|
- have the key. The list of remotes is ordered with
|
|
|
|
- cheapest first. More expensive ones will only be tried
|
|
|
|
- if downloading from a cheap one fails. -}
|
2012-10-30 21:14:26 +00:00
|
|
|
| direction == Download = do
|
2013-04-02 19:51:58 +00:00
|
|
|
s <- locs
|
2017-09-20 17:27:59 +00:00
|
|
|
return $ filter (inset s) (downloadRemotes st)
|
2013-04-02 19:51:58 +00:00
|
|
|
{- Upload to all remotes that want the content and don't
|
|
|
|
- already have it. -}
|
|
|
|
| otherwise = do
|
|
|
|
s <- locs
|
2022-07-28 17:26:03 +00:00
|
|
|
filterM (wantGetBy True (Just k) f . Remote.uuid) $
|
2017-09-20 17:27:59 +00:00
|
|
|
filter (\r -> not (inset s r || Remote.readonly r))
|
|
|
|
(syncDataRemotes st)
|
2013-04-02 19:51:58 +00:00
|
|
|
where
|
2023-11-30 19:11:57 +00:00
|
|
|
locs = S.fromList . map Remote.uuid <$> Remote.keyPossibilities (Remote.IncludeIgnored False) k
|
2013-04-02 19:51:58 +00:00
|
|
|
inset s r = S.member (Remote.uuid r) s
|
2012-10-30 21:14:26 +00:00
|
|
|
gentransfer r = Transfer
|
|
|
|
{ transferDirection = direction
|
2019-11-22 20:24:04 +00:00
|
|
|
, transferKeyData = fromKey id k
|
2012-10-30 21:14:26 +00:00
|
|
|
, transferUUID = Remote.uuid r
|
|
|
|
}
|
|
|
|
defer
|
|
|
|
{- Defer this download, as no known remote has the key. -}
|
|
|
|
| direction == Download = do
|
|
|
|
q <- getAssistant transferQueue
|
|
|
|
void $ liftIO $ atomically $
|
2013-04-25 05:09:37 +00:00
|
|
|
consTList (deferreddownloads q) (k, f)
|
2012-10-30 21:14:26 +00:00
|
|
|
| otherwise = noop
|
2012-09-18 01:05:50 +00:00
|
|
|
|
|
|
|
{- Queues any deferred downloads that can now be accomplished, leaving
|
|
|
|
- any others in the list to try again later. -}
|
2013-03-01 19:23:59 +00:00
|
|
|
queueDeferredDownloads :: Reason -> Schedule -> Assistant ()
|
|
|
|
queueDeferredDownloads reason schedule = do
|
2012-10-30 21:14:26 +00:00
|
|
|
q <- getAssistant transferQueue
|
2013-04-25 05:09:37 +00:00
|
|
|
l <- liftIO $ atomically $ readTList (deferreddownloads q)
|
2017-09-20 17:27:59 +00:00
|
|
|
rs <- downloadRemotes <$> getDaemonStatus
|
2012-09-18 01:05:50 +00:00
|
|
|
left <- filterM (queue rs) l
|
|
|
|
unless (null left) $
|
2013-04-25 05:09:37 +00:00
|
|
|
liftIO $ atomically $ appendTList (deferreddownloads q) left
|
2012-10-30 21:14:26 +00:00
|
|
|
where
|
|
|
|
queue rs (k, f) = do
|
|
|
|
uuids <- liftAnnex $ Remote.keyLocations k
|
|
|
|
let sources = filter (\r -> uuid r `elem` uuids) rs
|
|
|
|
unless (null sources) $
|
|
|
|
forM_ sources $ \r ->
|
2013-03-13 17:05:30 +00:00
|
|
|
enqueue reason schedule
|
|
|
|
(gentransfer r) (stubInfo f r)
|
2012-10-30 21:14:26 +00:00
|
|
|
return $ null sources
|
|
|
|
where
|
|
|
|
gentransfer r = Transfer
|
|
|
|
{ transferDirection = Download
|
2019-11-22 20:24:04 +00:00
|
|
|
, transferKeyData = fromKey id k
|
2012-10-30 21:14:26 +00:00
|
|
|
, transferUUID = Remote.uuid r
|
|
|
|
}
|
|
|
|
|
2013-03-01 19:23:59 +00:00
|
|
|
enqueue :: Reason -> Schedule -> Transfer -> TransferInfo -> Assistant ()
|
|
|
|
enqueue reason schedule t info
|
2013-04-25 05:33:44 +00:00
|
|
|
| schedule == Next = go consTList
|
|
|
|
| otherwise = go snocTList
|
2012-10-30 21:14:26 +00:00
|
|
|
where
|
2013-03-07 16:35:42 +00:00
|
|
|
go modlist = whenM (add modlist) $ do
|
git style filename quoting controlled by core.quotePath
This is by no means complete, but escaping filenames in actionItemDesc does
cover most commands.
Note that for ActionItemBranchFilePath, the value is branch:file, and I
choose to only quote the file part (if necessary). I considered quoting the
whole thing. But, branch names cannot contain control characters, and while
they can contain unicode, git coes not quote unicode when displaying branch
names. So, it would be surprising for git-annex to quote unicode in a
branch name.
The find command is the most obvious command that still needs to be
dealt with. There are probably other places that filenames also get
displayed, eg embedded in error messages.
Some other commands use ActionItemOther with a filename, I think that
ActionItemOther should either be pre-sanitized, or should explicitly not
be used for filenames, so that needs more work.
When --json is used, unicode does not get escaped, but control
characters were already escaped in json.
(Key escaping may turn out to be needed, but I'm ignoring that for now.)
Sponsored-by: unqueued on Patreon
2023-04-08 18:20:02 +00:00
|
|
|
qp <- liftAnnex $ coreQuotePath <$> Annex.getGitConfig
|
|
|
|
debug [ "queued", describeTransfer qp t info, ": " ++ reason ]
|
2012-10-30 21:14:26 +00:00
|
|
|
notifyTransfer
|
2013-03-07 16:35:42 +00:00
|
|
|
add modlist = do
|
|
|
|
q <- getAssistant transferQueue
|
2013-04-02 20:17:06 +00:00
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ atomically $ ifM (checkRunningTransferSTM dstatus t)
|
|
|
|
( return False
|
|
|
|
, do
|
2013-04-25 05:33:44 +00:00
|
|
|
l <- readTList (queuelist q)
|
2013-04-02 20:17:06 +00:00
|
|
|
if (t `notElem` map fst l)
|
|
|
|
then do
|
|
|
|
void $ modifyTVar' (queuesize q) succ
|
2013-04-25 05:33:44 +00:00
|
|
|
void $ modlist (queuelist q) (t, info)
|
2013-04-02 20:17:06 +00:00
|
|
|
return True
|
|
|
|
else return False
|
|
|
|
)
|
2012-07-05 16:21:22 +00:00
|
|
|
|
2012-07-25 17:12:34 +00:00
|
|
|
{- Adds a transfer to the queue. -}
|
2013-03-01 19:23:59 +00:00
|
|
|
queueTransfer :: Reason -> Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
|
|
|
queueTransfer reason schedule f t remote =
|
|
|
|
enqueue reason schedule t (stubInfo f remote)
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2012-07-25 17:12:34 +00:00
|
|
|
{- Blocks until the queue is no larger than a given size, and then adds a
|
|
|
|
- transfer to the queue. -}
|
2013-03-01 19:23:59 +00:00
|
|
|
queueTransferAt :: Int -> Reason -> Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
|
|
|
queueTransferAt wantsz reason schedule f t remote = do
|
2012-10-30 21:14:26 +00:00
|
|
|
q <- getAssistant transferQueue
|
|
|
|
liftIO $ atomically $ do
|
2012-07-28 22:47:24 +00:00
|
|
|
sz <- readTVar (queuesize q)
|
2012-09-13 04:57:52 +00:00
|
|
|
unless (sz <= wantsz) $
|
|
|
|
retry -- blocks until queuesize changes
|
2013-03-01 19:23:59 +00:00
|
|
|
enqueue reason schedule t (stubInfo f remote)
|
2012-07-02 20:07:39 +00:00
|
|
|
|
2013-03-01 19:23:59 +00:00
|
|
|
queueTransferWhenSmall :: Reason -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
|
|
|
queueTransferWhenSmall reason = queueTransferAt 10 reason Later
|
2012-08-23 19:22:23 +00:00
|
|
|
|
2012-08-31 16:57:24 +00:00
|
|
|
{- Blocks until a pending transfer is available in the queue,
|
2012-07-29 17:37:26 +00:00
|
|
|
- and removes it.
|
|
|
|
-
|
|
|
|
- Checks that it's acceptable, before adding it to the
|
2013-03-01 19:23:59 +00:00
|
|
|
- currentTransfers map. If it's not acceptable, it's discarded.
|
2012-07-29 17:37:26 +00:00
|
|
|
-
|
|
|
|
- This is done in a single STM transaction, so there is no window
|
|
|
|
- where an observer sees an inconsistent status. -}
|
2012-10-30 21:14:26 +00:00
|
|
|
getNextTransfer :: (TransferInfo -> Bool) -> Assistant (Maybe (Transfer, TransferInfo))
|
|
|
|
getNextTransfer acceptable = do
|
|
|
|
q <- getAssistant transferQueue
|
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ atomically $ do
|
|
|
|
sz <- readTVar (queuesize q)
|
|
|
|
if sz < 1
|
|
|
|
then retry -- blocks until queuesize changes
|
2019-01-05 15:54:06 +00:00
|
|
|
else readTList (queuelist q) >>= \case
|
|
|
|
[] -> retry -- blocks until something is queued
|
|
|
|
(r@(t,info):rest) -> do
|
|
|
|
void $ modifyTVar' (queuesize q) pred
|
|
|
|
setTList (queuelist q) rest
|
|
|
|
if acceptable info
|
|
|
|
then do
|
|
|
|
adjustTransfersSTM dstatus $
|
|
|
|
M.insert t info
|
|
|
|
return $ Just r
|
|
|
|
else return Nothing
|
2012-08-08 21:55:56 +00:00
|
|
|
|
2012-08-29 20:30:40 +00:00
|
|
|
{- Moves transfers matching a condition from the queue, to the
|
|
|
|
- currentTransfers map. -}
|
2012-10-30 21:14:26 +00:00
|
|
|
getMatchingTransfers :: (Transfer -> Bool) -> Assistant [(Transfer, TransferInfo)]
|
|
|
|
getMatchingTransfers c = do
|
|
|
|
q <- getAssistant transferQueue
|
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ atomically $ do
|
|
|
|
ts <- dequeueTransfersSTM q c
|
|
|
|
unless (null ts) $
|
|
|
|
adjustTransfersSTM dstatus $ \m -> M.union m $ M.fromList ts
|
|
|
|
return ts
|
2012-08-29 20:30:40 +00:00
|
|
|
|
2012-08-29 19:56:47 +00:00
|
|
|
{- Removes transfers matching a condition from the queue, and returns the
|
|
|
|
- removed transfers. -}
|
2012-10-30 21:14:26 +00:00
|
|
|
dequeueTransfers :: (Transfer -> Bool) -> Assistant [(Transfer, TransferInfo)]
|
|
|
|
dequeueTransfers c = do
|
|
|
|
q <- getAssistant transferQueue
|
|
|
|
removed <- liftIO $ atomically $ dequeueTransfersSTM q c
|
2012-08-29 19:56:47 +00:00
|
|
|
unless (null removed) $
|
2012-10-30 21:14:26 +00:00
|
|
|
notifyTransfer
|
2012-08-29 19:56:47 +00:00
|
|
|
return removed
|
2012-08-29 20:30:40 +00:00
|
|
|
|
|
|
|
dequeueTransfersSTM :: TransferQueue -> (Transfer -> Bool) -> STM [(Transfer, TransferInfo)]
|
|
|
|
dequeueTransfersSTM q c = do
|
2014-01-06 01:30:48 +00:00
|
|
|
!(removed, ts) <- partition (c . fst) <$> readTList (queuelist q)
|
|
|
|
let !len = length ts
|
|
|
|
void $ writeTVar (queuesize q) len
|
2013-04-25 05:33:44 +00:00
|
|
|
setTList (queuelist q) ts
|
2012-08-29 20:30:40 +00:00
|
|
|
return removed
|