hook up syncing toggles
Although I observe that these toggles don't always prevent syncing. When a transfer scan is active, it will still queue items from the disabled remote. Also, transfers from a disabled remote show up as from "unknown", which is not ideal.
This commit is contained in:
parent
06831e7754
commit
3f06c883f2
4 changed files with 51 additions and 33 deletions
|
@ -13,6 +13,7 @@ import Assistant.Common
|
||||||
import Assistant.WebApp
|
import Assistant.WebApp
|
||||||
import Assistant.WebApp.Types
|
import Assistant.WebApp.Types
|
||||||
import Assistant.WebApp.SideBar
|
import Assistant.WebApp.SideBar
|
||||||
|
import Assistant.WebApp.Utility
|
||||||
import Assistant.WebApp.Configurators.Local
|
import Assistant.WebApp.Configurators.Local
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
import Utility.Yesod
|
import Utility.Yesod
|
||||||
|
@ -129,13 +130,14 @@ repoList onlyconfigured includehere
|
||||||
<*> pure (map snd l')
|
<*> pure (map snd l')
|
||||||
counter = map show ([1..] :: [Int])
|
counter = map show ([1..] :: [Int])
|
||||||
|
|
||||||
|
|
||||||
getEnableSyncR :: UUID -> Handler ()
|
getEnableSyncR :: UUID -> Handler ()
|
||||||
getEnableSyncR uuid = do
|
getEnableSyncR = flipSync True
|
||||||
error "TODO"
|
|
||||||
redirect RepositoriesR
|
|
||||||
|
|
||||||
getDisableSyncR :: UUID -> Handler ()
|
getDisableSyncR :: UUID -> Handler ()
|
||||||
getDisableSyncR uuid = do
|
getDisableSyncR = flipSync False
|
||||||
error "TODO"
|
|
||||||
|
flipSync :: Bool -> UUID -> Handler ()
|
||||||
|
flipSync enable uuid = do
|
||||||
|
mremote <- runAnnex undefined $ snd <$> Remote.repoFromUUID uuid
|
||||||
|
changeSyncable mremote enable
|
||||||
redirect RepositoriesR
|
redirect RepositoriesR
|
||||||
|
|
|
@ -16,8 +16,6 @@ import Assistant.WebApp.SideBar
|
||||||
import Assistant.WebApp.Utility
|
import Assistant.WebApp.Utility
|
||||||
import Utility.Yesod
|
import Utility.Yesod
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Remote.List as Remote
|
|
||||||
import qualified Types.Remote as Remote
|
|
||||||
import Logs.UUID
|
import Logs.UUID
|
||||||
import Logs.Group
|
import Logs.Group
|
||||||
import Logs.PreferredContent
|
import Logs.PreferredContent
|
||||||
|
@ -54,7 +52,8 @@ getRepoConfig uuid r = RepoConfig
|
||||||
maybe (RepoGroupCustom $ unwords $ S.toList groups) RepoGroupStandard
|
maybe (RepoGroupCustom $ unwords $ S.toList groups) RepoGroupStandard
|
||||||
(getStandardGroup groups)
|
(getStandardGroup groups)
|
||||||
|
|
||||||
{- Returns Just False if syncing has been disabled, or Just True when enabled. -}
|
{- Returns Just False if syncing should be disabled, Just True when enabled;
|
||||||
|
- Nothing when it is not changed. -}
|
||||||
setRepoConfig :: UUID -> Git.Repo -> RepoConfig -> Annex (Maybe Bool)
|
setRepoConfig :: UUID -> Git.Repo -> RepoConfig -> Annex (Maybe Bool)
|
||||||
setRepoConfig uuid r c = do
|
setRepoConfig uuid r c = do
|
||||||
describeUUID uuid $ T.unpack $ repoDescription c
|
describeUUID uuid $ T.unpack $ repoDescription c
|
||||||
|
@ -65,14 +64,9 @@ setRepoConfig uuid r c = do
|
||||||
( return Nothing
|
( return Nothing
|
||||||
, do
|
, do
|
||||||
syncable <- Config.repoSyncable r
|
syncable <- Config.repoSyncable r
|
||||||
if (syncable /= repoSyncable c)
|
return $ if (syncable /= repoSyncable c)
|
||||||
then do
|
then Just $ repoSyncable c
|
||||||
let key = Config.remoteConfig r "sync"
|
else Nothing
|
||||||
Config.setConfig key $
|
|
||||||
if syncable then "false" else "true"
|
|
||||||
void $ Remote.remoteListRefresh
|
|
||||||
return $ Just $ repoSyncable c
|
|
||||||
else return Nothing
|
|
||||||
)
|
)
|
||||||
|
|
||||||
editRepositoryAForm :: RepoConfig -> AForm WebApp WebApp RepoConfig
|
editRepositoryAForm :: RepoConfig -> AForm WebApp WebApp RepoConfig
|
||||||
|
@ -100,29 +94,19 @@ editForm new uuid = bootstrap (Just Config) $ do
|
||||||
sideBarDisplay
|
sideBarDisplay
|
||||||
setTitle "Configure repository"
|
setTitle "Configure repository"
|
||||||
|
|
||||||
(repo, mremote) <- lift $ runAnnex undefined getrepo
|
(repo, mremote) <- lift $ runAnnex undefined $ Remote.repoFromUUID uuid
|
||||||
curr <- lift $ runAnnex undefined $ getRepoConfig uuid repo
|
curr <- lift $ runAnnex undefined $ getRepoConfig uuid repo
|
||||||
((result, form), enctype) <- lift $
|
((result, form), enctype) <- lift $
|
||||||
runFormGet $ renderBootstrap $ editRepositoryAForm curr
|
runFormGet $ renderBootstrap $ editRepositoryAForm curr
|
||||||
case result of
|
case result of
|
||||||
FormSuccess input -> lift $ do
|
FormSuccess input -> lift $ do
|
||||||
r <- runAnnex undefined $
|
syncchanged <- runAnnex undefined $
|
||||||
setRepoConfig uuid repo input
|
setRepoConfig uuid repo input
|
||||||
maybe noop (uncurry changeSyncable) $
|
maybe noop (changeSyncable mremote) syncchanged
|
||||||
(,) <$> mremote <*> r
|
|
||||||
redirect RepositoriesR
|
redirect RepositoriesR
|
||||||
_ -> showform form enctype curr
|
_ -> showform form enctype curr
|
||||||
where
|
where
|
||||||
getrepo = ifM ((==) uuid <$> getUUID)
|
|
||||||
( (,) <$> gitRepo <*> pure Nothing
|
|
||||||
, do
|
|
||||||
remote <- fromMaybe (error "Unknown UUID") . M.lookup uuid
|
|
||||||
<$> Remote.remoteMap id
|
|
||||||
return (Remote.repo remote, Just remote)
|
|
||||||
)
|
|
||||||
showform form enctype curr = do
|
showform form enctype curr = do
|
||||||
let istransfer = repoGroup curr == RepoGroupStandard TransferGroup
|
let istransfer = repoGroup curr == RepoGroupStandard TransferGroup
|
||||||
let authtoken = webAppFormAuthToken
|
let authtoken = webAppFormAuthToken
|
||||||
$(widgetFile "configurators/editrepository")
|
$(widgetFile "configurators/editrepository")
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -8,6 +8,7 @@
|
||||||
module Assistant.WebApp.Utility where
|
module Assistant.WebApp.Utility where
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
|
import Assistant.WebApp
|
||||||
import Assistant.WebApp.Types
|
import Assistant.WebApp.Types
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
|
@ -15,9 +16,12 @@ import Assistant.TransferQueue
|
||||||
import Assistant.TransferSlots
|
import Assistant.TransferSlots
|
||||||
import Assistant.Sync
|
import Assistant.Sync
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
import qualified Types.Remote as Remote
|
||||||
|
import qualified Remote.List as Remote
|
||||||
import qualified Assistant.Threads.Transferrer as Transferrer
|
import qualified Assistant.Threads.Transferrer as Transferrer
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
import Locations.UserConfig
|
import Locations.UserConfig
|
||||||
|
import qualified Config
|
||||||
|
|
||||||
import Yesod
|
import Yesod
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -25,9 +29,14 @@ import Control.Concurrent
|
||||||
import System.Posix.Signals (signalProcessGroup, sigTERM, sigKILL)
|
import System.Posix.Signals (signalProcessGroup, sigTERM, sigKILL)
|
||||||
import System.Posix.Process (getProcessGroupIDOf)
|
import System.Posix.Process (getProcessGroupIDOf)
|
||||||
|
|
||||||
changeSyncable :: Remote -> Bool -> Handler ()
|
{- Use Nothing to change global sync setting. -}
|
||||||
changeSyncable r True = syncRemote r
|
changeSyncable :: (Maybe Remote) -> Bool -> Handler ()
|
||||||
changeSyncable r False = do
|
changeSyncable Nothing _ = noop -- TODO
|
||||||
|
changeSyncable (Just r) True = do
|
||||||
|
changeSyncFlag r True
|
||||||
|
syncRemote r
|
||||||
|
changeSyncable (Just r) False = do
|
||||||
|
changeSyncFlag r False
|
||||||
webapp <- getYesod
|
webapp <- getYesod
|
||||||
let dstatus = daemonStatus webapp
|
let dstatus = daemonStatus webapp
|
||||||
let st = fromJust $ threadState webapp
|
let st = fromJust $ threadState webapp
|
||||||
|
@ -41,6 +50,16 @@ changeSyncable r False = do
|
||||||
where
|
where
|
||||||
tofrom t = transferUUID t == Remote.uuid r
|
tofrom t = transferUUID t == Remote.uuid r
|
||||||
|
|
||||||
|
changeSyncFlag :: Remote -> Bool -> Handler ()
|
||||||
|
changeSyncFlag r enabled = runAnnex undefined $ do
|
||||||
|
Config.setConfig key value
|
||||||
|
void $ Remote.remoteListRefresh
|
||||||
|
where
|
||||||
|
key = Config.remoteConfig (Remote.repo r) "sync"
|
||||||
|
value
|
||||||
|
| enabled = "true"
|
||||||
|
| otherwise = "false"
|
||||||
|
|
||||||
{- Start syncing remote, using a background thread. -}
|
{- Start syncing remote, using a background thread. -}
|
||||||
syncRemote :: Remote -> Handler ()
|
syncRemote :: Remote -> Handler ()
|
||||||
syncRemote remote = do
|
syncRemote remote = do
|
||||||
|
|
13
Remote.hs
13
Remote.hs
|
@ -27,6 +27,7 @@ module Remote (
|
||||||
byCost,
|
byCost,
|
||||||
prettyPrintUUIDs,
|
prettyPrintUUIDs,
|
||||||
prettyListUUIDs,
|
prettyListUUIDs,
|
||||||
|
repoFromUUID,
|
||||||
remotesWithUUID,
|
remotesWithUUID,
|
||||||
remotesWithoutUUID,
|
remotesWithoutUUID,
|
||||||
keyLocations,
|
keyLocations,
|
||||||
|
@ -52,6 +53,7 @@ import Logs.UUID
|
||||||
import Logs.Trust
|
import Logs.Trust
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Remote.List
|
import Remote.List
|
||||||
|
import qualified Git
|
||||||
|
|
||||||
{- Map from UUIDs of Remotes to a calculated value. -}
|
{- Map from UUIDs of Remotes to a calculated value. -}
|
||||||
remoteMap :: (Remote -> a) -> Annex (M.Map UUID a)
|
remoteMap :: (Remote -> a) -> Annex (M.Map UUID a)
|
||||||
|
@ -145,6 +147,17 @@ prettyListUUIDs uuids = do
|
||||||
where
|
where
|
||||||
n = finddescription m u
|
n = finddescription m u
|
||||||
|
|
||||||
|
{- Gets the git repo associated with a UUID.
|
||||||
|
- There's no associated remote when this is the UUID of the local repo. -}
|
||||||
|
repoFromUUID :: UUID -> Annex (Git.Repo, Maybe Remote)
|
||||||
|
repoFromUUID u = ifM ((==) u <$> getUUID)
|
||||||
|
( (,) <$> gitRepo <*> pure Nothing
|
||||||
|
, do
|
||||||
|
remote <- fromMaybe (error "Unknown UUID") . M.lookup u
|
||||||
|
<$> remoteMap id
|
||||||
|
return (repo remote, Just remote)
|
||||||
|
)
|
||||||
|
|
||||||
{- Filters a list of remotes to ones that have the listed uuids. -}
|
{- Filters a list of remotes to ones that have the listed uuids. -}
|
||||||
remotesWithUUID :: [Remote] -> [UUID] -> [Remote]
|
remotesWithUUID :: [Remote] -> [UUID] -> [Remote]
|
||||||
remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs
|
remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue