2015-09-14 18:49:48 +00:00
|
|
|
{- git-annex special remote configuration
|
|
|
|
-
|
2022-01-05 19:12:01 +00:00
|
|
|
- Copyright 2011-2021 Joey Hess <id@joeyh.name>
|
2015-09-14 18:49:48 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2015-09-14 18:49:48 +00:00
|
|
|
-}
|
|
|
|
|
2019-12-04 17:15:34 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2019-10-11 19:32:56 +00:00
|
|
|
module Annex.SpecialRemote (
|
|
|
|
module Annex.SpecialRemote,
|
|
|
|
module Annex.SpecialRemote.Config
|
|
|
|
) where
|
2015-09-14 18:49:48 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2019-10-10 16:48:26 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2019-10-10 19:31:10 +00:00
|
|
|
import Types.Remote (RemoteConfig, SetupStage(..), typename, setup)
|
2017-08-17 16:26:14 +00:00
|
|
|
import Types.GitConfig
|
2020-01-10 18:10:20 +00:00
|
|
|
import Types.ProposedAccepted
|
2019-10-11 19:32:56 +00:00
|
|
|
import Config
|
|
|
|
import Remote.List
|
2015-09-14 18:49:48 +00:00
|
|
|
import Logs.Remote
|
|
|
|
import Logs.Trust
|
2019-10-11 19:32:56 +00:00
|
|
|
import qualified Types.Remote as Remote
|
2016-11-30 18:35:24 +00:00
|
|
|
import Git.Types (RemoteName)
|
2023-04-12 16:33:17 +00:00
|
|
|
import Utility.SafeOutput
|
2015-09-14 18:49:48 +00:00
|
|
|
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
{- See if there's an existing special remote with this name.
|
|
|
|
-
|
2022-01-05 19:12:01 +00:00
|
|
|
- Remotes that are not dead come first in the list
|
|
|
|
- when a name appears multiple times. -}
|
2022-01-05 19:24:02 +00:00
|
|
|
findExisting :: RemoteName -> Annex [(UUID, RemoteConfig, Maybe (ConfigFrom UUID))]
|
2015-09-14 18:49:48 +00:00
|
|
|
findExisting name = do
|
2022-01-05 19:12:01 +00:00
|
|
|
(a, b) <- findExisting' name
|
2022-01-05 19:24:02 +00:00
|
|
|
return (a++b)
|
2022-01-05 19:12:01 +00:00
|
|
|
|
|
|
|
{- Dead remotes with the name are in the second list, all others in the
|
|
|
|
- first list. -}
|
|
|
|
findExisting' :: RemoteName -> Annex ([(UUID, RemoteConfig, Maybe (ConfigFrom UUID))], [(UUID, RemoteConfig, Maybe (ConfigFrom UUID))])
|
|
|
|
findExisting' name = do
|
2015-09-14 18:49:48 +00:00
|
|
|
t <- trustMap
|
2022-01-05 19:12:01 +00:00
|
|
|
partition (\(u, _, _) -> M.lookup u t /= Just DeadTrusted)
|
2019-11-18 20:09:09 +00:00
|
|
|
. findByRemoteConfig (\c -> lookupName c == Just name)
|
2020-09-22 17:52:26 +00:00
|
|
|
<$> Logs.Remote.remoteConfigMap
|
2015-09-14 18:49:48 +00:00
|
|
|
|
2019-10-11 16:45:30 +00:00
|
|
|
newConfig
|
|
|
|
:: RemoteName
|
|
|
|
-> Maybe (Sameas UUID)
|
|
|
|
-> RemoteConfig
|
|
|
|
-- ^ configuration provided by the user
|
|
|
|
-> M.Map UUID RemoteConfig
|
|
|
|
-- ^ configuration of other special remotes, to inherit from
|
|
|
|
-- when sameas is used
|
|
|
|
-> RemoteConfig
|
|
|
|
newConfig name sameas fromuser m = case sameas of
|
2020-01-10 18:10:20 +00:00
|
|
|
Nothing -> M.insert nameField (Proposed name) fromuser
|
2019-10-11 16:45:30 +00:00
|
|
|
Just (Sameas u) -> addSameasInherited m $ M.fromList
|
2020-01-10 18:10:20 +00:00
|
|
|
[ (sameasNameField, Proposed name)
|
|
|
|
, (sameasUUIDField, Proposed (fromUUID u))
|
2019-10-11 16:45:30 +00:00
|
|
|
] `M.union` fromuser
|
2015-09-14 18:49:48 +00:00
|
|
|
|
2015-10-26 18:55:40 +00:00
|
|
|
specialRemoteMap :: Annex (M.Map UUID RemoteName)
|
|
|
|
specialRemoteMap = do
|
2020-09-22 17:52:26 +00:00
|
|
|
m <- Logs.Remote.remoteConfigMap
|
2022-06-01 18:20:38 +00:00
|
|
|
return $ specialRemoteNameMap m
|
|
|
|
|
|
|
|
specialRemoteNameMap :: M.Map UUID RemoteConfig -> M.Map UUID RemoteName
|
|
|
|
specialRemoteNameMap = M.fromList . mapMaybe go . M.toList
|
2015-10-26 18:55:40 +00:00
|
|
|
where
|
2019-10-10 16:32:05 +00:00
|
|
|
go (u, c) = case lookupName c of
|
2015-10-26 18:55:40 +00:00
|
|
|
Nothing -> Nothing
|
|
|
|
Just n -> Just (u, n)
|
2015-09-14 18:49:48 +00:00
|
|
|
|
2019-10-10 16:32:05 +00:00
|
|
|
{- find the remote type -}
|
2015-09-14 18:49:48 +00:00
|
|
|
findType :: RemoteConfig -> Either String RemoteType
|
2020-01-10 18:10:20 +00:00
|
|
|
findType config = maybe unspecified (specified . fromProposedAccepted) $
|
|
|
|
M.lookup typeField config
|
2015-09-14 18:49:48 +00:00
|
|
|
where
|
|
|
|
unspecified = Left "Specify the type of remote with type="
|
|
|
|
specified s = case filter (findtype s) remoteTypes of
|
2020-01-20 20:05:51 +00:00
|
|
|
[] -> Left $ "Unknown remote type " ++ s
|
|
|
|
++ " (pick from: "
|
|
|
|
++ intercalate " " (map typename remoteTypes)
|
|
|
|
++ ")"
|
2015-09-14 18:49:48 +00:00
|
|
|
(t:_) -> Right t
|
|
|
|
findtype s i = typename i == s
|
|
|
|
|
|
|
|
autoEnable :: Annex ()
|
|
|
|
autoEnable = do
|
2022-06-01 18:20:38 +00:00
|
|
|
m <- autoEnableable
|
2019-10-11 19:32:56 +00:00
|
|
|
enabled <- getenabledremotes
|
2022-06-01 18:20:38 +00:00
|
|
|
forM_ (M.toList m) $ \(cu, c) -> unless (cu `M.member` enabled) $ do
|
2019-10-11 19:32:56 +00:00
|
|
|
let u = case findSameasUUID c of
|
|
|
|
Just (Sameas u') -> u'
|
|
|
|
Nothing -> cu
|
2019-10-10 16:32:05 +00:00
|
|
|
case (lookupName c, findType c) of
|
2023-04-12 16:33:17 +00:00
|
|
|
-- Avoid auto-enabling when the name contains a
|
|
|
|
-- control character, because git does not avoid
|
|
|
|
-- displaying control characters in the name of a
|
|
|
|
-- remote, and an attacker could leverage
|
|
|
|
-- autoenabling it as part of an attack.
|
|
|
|
(Just name, Right t) | safeOutput name == name -> do
|
2023-04-10 21:03:41 +00:00
|
|
|
showSideAction $ UnquotedString $ "Auto enabling special remote " ++ name
|
2017-08-17 16:26:14 +00:00
|
|
|
dummycfg <- liftIO dummyRemoteGitConfig
|
2021-03-17 13:41:12 +00:00
|
|
|
tryNonAsync (setup t (AutoEnable c) (Just u) Nothing c dummycfg) >>= \case
|
filter out control characters in warning messages
Converted warning and similar to use StringContainingQuotedPath. Most
warnings are static strings, some do refer to filepaths that need to be
quoted, and others don't need quoting.
Note that, since quote filters out control characters of even
UnquotedString, this makes all warnings safe, even when an attacker
sneaks in a control character in some other way.
When json is being output, no quoting is done, since json gets its own
quoting.
This does, as a side effect, make warning messages in json output not
be indented. The indentation is only needed to offset warning messages
underneath the display of the file they apply to, so that's ok.
Sponsored-by: Brett Eisenberg on Patreon
2023-04-10 18:47:32 +00:00
|
|
|
Left e -> warning (UnquotedString (show e))
|
2019-10-11 19:32:56 +00:00
|
|
|
Right (_c, _u) ->
|
|
|
|
when (cu /= u) $
|
2020-02-19 17:45:11 +00:00
|
|
|
setConfig (remoteAnnexConfig c "config-uuid") (fromUUID cu)
|
2015-09-14 18:49:48 +00:00
|
|
|
_ -> return ()
|
|
|
|
where
|
2019-10-11 19:32:56 +00:00
|
|
|
getenabledremotes = M.fromList
|
|
|
|
. map (\r -> (getcu r, r))
|
|
|
|
<$> remoteList
|
|
|
|
getcu r = fromMaybe
|
|
|
|
(Remote.uuid r)
|
|
|
|
(remoteAnnexConfigUUID (Remote.gitconfig r))
|
2022-06-01 18:20:38 +00:00
|
|
|
|
|
|
|
autoEnableable :: Annex (M.Map UUID RemoteConfig)
|
|
|
|
autoEnableable = do
|
|
|
|
tm <- trustMap
|
|
|
|
(M.filterWithKey (notdead tm) . M.filter configured)
|
|
|
|
<$> remoteConfigMap
|
|
|
|
where
|
|
|
|
configured c = fromMaybe False $
|
|
|
|
trueFalseParser' . fromProposedAccepted
|
|
|
|
=<< M.lookup autoEnableField c
|
|
|
|
notdead tm cu c =
|
|
|
|
let u = case findSameasUUID c of
|
|
|
|
Just (Sameas u') -> u'
|
|
|
|
Nothing -> cu
|
|
|
|
in lookupTrust' u tm /= DeadTrusted
|
|
|
|
|