add support for readonly remotes

Currently only the web special remote is readonly, but it'd be possible to
also have readonly drives, or other remotes. These are handled in the
assistant by only downloading from them, and never trying to upload to
them.
This commit is contained in:
Joey Hess 2012-08-26 15:39:02 -04:00
parent 4d269db520
commit 271ea49978
13 changed files with 33 additions and 9 deletions

View file

@ -14,6 +14,7 @@ import Utility.ThreadScheduler
import Utility.TempFile import Utility.TempFile
import Utility.NotificationBroadcaster import Utility.NotificationBroadcaster
import Logs.Transfer import Logs.Transfer
import Logs.Trust
import qualified Remote import qualified Remote
import Control.Concurrent.STM import Control.Concurrent.STM
@ -81,8 +82,13 @@ modifyDaemonStatus dstatus a = do
sendNotification $ changeNotifier s sendNotification $ changeNotifier s
return b return b
{- Remotes ordered by cost, with dead ones thrown out. -}
calcKnownRemotes :: Annex [Remote] calcKnownRemotes :: Annex [Remote]
calcKnownRemotes = concat . Remote.byCost <$> Remote.enabledRemoteList calcKnownRemotes = do
rs <- concat . Remote.byCost <$> Remote.enabledRemoteList
alive <- snd <$> trustPartition DeadTrusted (map Remote.uuid rs)
let good r = Remote.uuid r `elem` alive
return $ filter good rs
{- Updates the cached ordered list of remotes from the list in Annex {- Updates the cached ordered list of remotes from the list in Annex
- state. -} - state. -}

View file

@ -16,6 +16,7 @@ import Assistant.DaemonStatus
import Assistant.Sync import Assistant.Sync
import Utility.ThreadScheduler import Utility.ThreadScheduler
import qualified Remote import qualified Remote
import qualified Types.Remote as Remote
import Data.Time.Clock import Data.Time.Clock
@ -51,8 +52,8 @@ pushThread st dstatus commitchan pushmap = do
now <- getCurrentTime now <- getCurrentTime
if shouldPush now commits if shouldPush now commits
then do then do
remotes <- filter (not . Remote.specialRemote) . remotes <- filter pushable . knownRemotes
knownRemotes <$> getDaemonStatus dstatus <$> getDaemonStatus dstatus
unless (null remotes) $ unless (null remotes) $
void $ alertWhile dstatus (pushAlert remotes) $ void $ alertWhile dstatus (pushAlert remotes) $
pushToRemotes thisThread now st (Just pushmap) remotes pushToRemotes thisThread now st (Just pushmap) remotes
@ -63,6 +64,11 @@ pushThread st dstatus commitchan pushmap = do
, "commits" , "commits"
] ]
refillCommits commitchan commits refillCommits commitchan commits
where
pushable r
| Remote.specialRemote r = False
| Remote.readonly r = False
| otherwise = True
{- Decide if now is a good time to push to remotes. {- Decide if now is a good time to push to remotes.
- -

View file

@ -16,6 +16,7 @@ import Assistant.Alert
import Logs.Transfer import Logs.Transfer
import Logs.Location import Logs.Location
import qualified Remote import qualified Remote
import qualified Types.Remote as Remote
import Utility.ThreadScheduler import Utility.ThreadScheduler
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
import Command import Command
@ -122,6 +123,7 @@ expensiveScan st dstatus transferqueue rs = do
, use $ check Download True , use $ check Download True
) )
check direction want key locs r check direction want key locs r
| direction == Upload && Remote.readonly r = Nothing
| (Remote.uuid r `elem` locs) == want = Just $ | (Remote.uuid r `elem` locs) == want = Just $
(r, Transfer direction (Remote.uuid r) key) (r, Transfer direction (Remote.uuid r) key)
| otherwise = Nothing | otherwise = Nothing

View file

@ -23,6 +23,7 @@ import Assistant.DaemonStatus
import Logs.Transfer import Logs.Transfer
import Types.Remote import Types.Remote
import qualified Remote import qualified Remote
import qualified Types.Remote as Remote
import Control.Concurrent.STM import Control.Concurrent.STM
import qualified Data.Map as M import qualified Data.Map as M
@ -78,7 +79,7 @@ queueTransfers schedule q dstatus k f direction = do
-- can be uploaded to, in order to ensure all -- can be uploaded to, in order to ensure all
-- remotes can access the content. Currently, -- remotes can access the content. Currently,
-- send to every remote we can. -- send to every remote we can.
| otherwise = return rs | otherwise = return $ filter (not . Remote.readonly) rs
gentransfer r = Transfer gentransfer r = Transfer
{ transferDirection = direction { transferDirection = direction
, transferKey = k , transferKey = k

View file

@ -12,12 +12,12 @@ module Assistant.WebApp.Configurators where
import Assistant.Common import Assistant.Common
import Assistant.WebApp import Assistant.WebApp
import Assistant.WebApp.SideBar import Assistant.WebApp.SideBar
import Assistant.DaemonStatus
import Assistant.Threads.MountWatcher (handleMount) import Assistant.Threads.MountWatcher (handleMount)
import Utility.Yesod import Utility.Yesod
import qualified Remote import qualified Remote
import qualified Types.Remote as Remote
import Remote.List import Remote.List
import Logs.Web (webUUID)
import Logs.Trust
import Annex.UUID (getUUID) import Annex.UUID (getUUID)
import Init import Init
import qualified Git import qualified Git
@ -60,11 +60,11 @@ getRepositoriesR = bootstrap (Just Config) $ do
{- A numbered list of known repositories, including the current one. -} {- A numbered list of known repositories, including the current one. -}
repoList :: Handler [(String, String)] repoList :: Handler [(String, String)]
repoList = do repoList = do
rs <- filter (not . Remote.readonly) . knownRemotes <$>
(liftIO . getDaemonStatus =<< daemonStatus <$> getYesod)
l <- runAnnex [] $ do l <- runAnnex [] $ do
u <- getUUID u <- getUUID
rs <- map Remote.uuid <$> Remote.remoteList Remote.prettyListUUIDs $ nub $ u:(map Remote.uuid rs)
rs' <- snd <$> trustPartition DeadTrusted rs
Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs'
return $ zip counter l return $ zip counter l
where where
counter = map show ([1..] :: [Int]) counter = map show ([1..] :: [Int])

View file

@ -64,6 +64,7 @@ gen r u c = do
then Just buprepo then Just buprepo
else Nothing else Nothing
, remotetype = remote , remotetype = remote
, readonly = False
} }
bupSetup :: UUID -> RemoteConfig -> Annex RemoteConfig bupSetup :: UUID -> RemoteConfig -> Annex RemoteConfig

View file

@ -54,6 +54,7 @@ gen r u c = do
config = Nothing, config = Nothing,
repo = r, repo = r,
localpath = Just dir, localpath = Just dir,
readonly = False,
remotetype = remote remotetype = remote
} }
where where

View file

@ -98,6 +98,7 @@ gen r u _ = new <$> remoteCost r defcst
then Just $ Git.repoPath r then Just $ Git.repoPath r
else Nothing else Nothing
, repo = r , repo = r
, readonly = False
, remotetype = remote , remotetype = remote
} }

View file

@ -50,6 +50,7 @@ gen r u c = do
config = Nothing, config = Nothing,
localpath = Nothing, localpath = Nothing,
repo = r, repo = r,
readonly = False,
remotetype = remote remotetype = remote
} }

View file

@ -61,6 +61,7 @@ gen r u c = do
, localpath = if rsyncUrlIsPath $ rsyncUrl o , localpath = if rsyncUrlIsPath $ rsyncUrl o
then Just $ rsyncUrl o then Just $ rsyncUrl o
else Nothing else Nothing
, readonly = False
, remotetype = remote , remotetype = remote
} }

View file

@ -61,6 +61,7 @@ gen' r u c cst =
config = c, config = c,
repo = r, repo = r,
localpath = Nothing, localpath = Nothing,
readonly = False,
remotetype = remote remotetype = remote
} }

View file

@ -49,6 +49,7 @@ gen r _ _ =
config = Nothing, config = Nothing,
localpath = Nothing, localpath = Nothing,
repo = r, repo = r,
readonly = True,
remotetype = remote remotetype = remote
} }

View file

@ -66,6 +66,8 @@ data RemoteA a = Remote {
repo :: Git.Repo, repo :: Git.Repo,
-- a Remote can be assocated with a specific local filesystem path -- a Remote can be assocated with a specific local filesystem path
localpath :: Maybe FilePath, localpath :: Maybe FilePath,
-- a Remote can be known to be readonly
readonly :: Bool,
-- the type of the remote -- the type of the remote
remotetype :: RemoteTypeA a remotetype :: RemoteTypeA a
} }