add clusters to proxy log
Note that it's not defined what will happen if a cluster has the same name as a remote that has proxying enabled.
This commit is contained in:
parent
bbf261487d
commit
2028ad02b8
1 changed files with 13 additions and 3 deletions
|
@ -8,11 +8,13 @@
|
||||||
module Command.UpdateProxy where
|
module Command.UpdateProxy where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
import qualified Annex
|
||||||
import Logs.Proxy
|
import Logs.Proxy
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import qualified Remote as R
|
import qualified Remote as R
|
||||||
import qualified Types.Remote as R
|
import qualified Types.Remote as R
|
||||||
import Utility.SafeOutput
|
import Utility.SafeOutput
|
||||||
|
import Types.Cluster
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
@ -28,9 +30,12 @@ seek = withNothing (commandAction start)
|
||||||
start :: CommandStart
|
start :: CommandStart
|
||||||
start = startingCustomOutput (ActionItemOther Nothing) $ do
|
start = startingCustomOutput (ActionItemOther Nothing) $ do
|
||||||
rs <- R.remoteList
|
rs <- R.remoteList
|
||||||
let proxies = S.fromList $
|
let remoteproxies = S.fromList $ map mkproxy $
|
||||||
map (\r -> Proxy (R.uuid r) (R.name r)) $
|
filter (isproxy . R.gitconfig) rs
|
||||||
filter (isproxy . R.gitconfig) rs
|
clusterproxies <-
|
||||||
|
(S.fromList . map mkclusterproxy . M.toList . annexClusters)
|
||||||
|
<$> Annex.getGitConfig
|
||||||
|
let proxies = remoteproxies <> clusterproxies
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
oldproxies <- fromMaybe mempty . M.lookup u <$> getProxies
|
oldproxies <- fromMaybe mempty . M.lookup u <$> getProxies
|
||||||
if oldproxies == proxies
|
if oldproxies == proxies
|
||||||
|
@ -52,3 +57,8 @@ start = startingCustomOutput (ActionItemOther Nothing) $ do
|
||||||
_ -> noop
|
_ -> noop
|
||||||
|
|
||||||
isproxy c = remoteAnnexProxy c || not (null (remoteAnnexClusterNode c))
|
isproxy c = remoteAnnexProxy c || not (null (remoteAnnexClusterNode c))
|
||||||
|
|
||||||
|
mkproxy r = Proxy (R.uuid r) (R.name r)
|
||||||
|
|
||||||
|
mkclusterproxy (remotename, cu) =
|
||||||
|
Proxy (fromClusterUUID cu) remotename
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue