forget state of sameas remotes during DropDead transitions
It would have been a lot less round-about to just make git annex dead also add the uuids of sameas remotes to the trust.log as dead. But, that would fail in the case where there's an unmerged other clone that has a sameas remote that the current repo does not know about. Then it would not get marked as dead. Handling it at transition time avoids that scenario. Note that the generation of trustmap' in dropDead should only happen once, due to the partial application.
This commit is contained in:
parent
9828f45d85
commit
5e9a2cc37f
4 changed files with 51 additions and 90 deletions
|
@ -22,11 +22,10 @@ import qualified Annex.Branch
|
|||
import Types.Remote
|
||||
import Logs
|
||||
import Logs.UUIDBased
|
||||
import Logs.Remote.Pure
|
||||
import Annex.SpecialRemote.Config
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.Char
|
||||
import qualified Data.Attoparsec.ByteString.Lazy as A
|
||||
import Data.ByteString.Builder
|
||||
|
||||
{- Adds or updates a remote's config in the log. -}
|
||||
|
@ -40,71 +39,5 @@ configSet u cfg = do
|
|||
|
||||
{- Map of remotes by uuid containing key/value config maps. -}
|
||||
readRemoteLog :: Annex (M.Map UUID RemoteConfig)
|
||||
readRemoteLog = (\m -> M.map (addSameasInherited m) m)
|
||||
. simpleMap
|
||||
. parseLogOld remoteConfigParser
|
||||
readRemoteLog = calcRemoteConfigMap
|
||||
<$> Annex.Branch.get remoteLog
|
||||
|
||||
remoteConfigParser :: A.Parser RemoteConfig
|
||||
remoteConfigParser = keyValToConfig . words . decodeBS <$> A.takeByteString
|
||||
|
||||
showConfig :: RemoteConfig -> String
|
||||
showConfig = unwords . configToKeyVal
|
||||
|
||||
{- Given Strings like "key=value", generates a RemoteConfig. -}
|
||||
keyValToConfig :: [String] -> RemoteConfig
|
||||
keyValToConfig ws = M.fromList $ map (/=/) ws
|
||||
where
|
||||
(/=/) s = (k, v)
|
||||
where
|
||||
k = takeWhile (/= '=') s
|
||||
v = configUnEscape $ drop (1 + length k) s
|
||||
|
||||
configToKeyVal :: M.Map String String -> [String]
|
||||
configToKeyVal m = map toword $ sort $ M.toList m
|
||||
where
|
||||
toword (k, v) = k ++ "=" ++ configEscape v
|
||||
|
||||
configEscape :: String -> String
|
||||
configEscape = concatMap escape
|
||||
where
|
||||
escape c
|
||||
| isSpace c || c `elem` "&" = "&" ++ show (ord c) ++ ";"
|
||||
| otherwise = [c]
|
||||
|
||||
configUnEscape :: String -> String
|
||||
configUnEscape = unescape
|
||||
where
|
||||
unescape [] = []
|
||||
unescape (c:rest)
|
||||
| c == '&' = entity rest
|
||||
| otherwise = c : unescape rest
|
||||
entity s
|
||||
| not (null num) && ";" `isPrefixOf` r =
|
||||
chr (Prelude.read num) : unescape rest
|
||||
| otherwise =
|
||||
'&' : unescape s
|
||||
where
|
||||
num = takeWhile isNumber s
|
||||
r = drop (length num) s
|
||||
rest = drop 1 r
|
||||
|
||||
{- for quickcheck -}
|
||||
prop_isomorphic_configEscape :: String -> Bool
|
||||
prop_isomorphic_configEscape s = s == (configUnEscape . configEscape) s
|
||||
|
||||
prop_parse_show_Config :: RemoteConfig -> Bool
|
||||
prop_parse_show_Config c
|
||||
-- whitespace and '=' are not supported in config keys
|
||||
| any (\k -> any isSpace k || elem '=' k) (M.keys c) = True
|
||||
| any (any excluded) (M.keys c) = True
|
||||
| any (any excluded) (M.elems c) = True
|
||||
| otherwise = A.parseOnly remoteConfigParser (encodeBS $ showConfig c) ~~ Right c
|
||||
where
|
||||
normalize v = sort . M.toList <$> v
|
||||
a ~~ b = normalize a == normalize b
|
||||
-- limit to ascii alphanumerics for simplicity; characters not
|
||||
-- allowed by the current character set in the config may not
|
||||
-- round-trip in an identical representation due to the use of the
|
||||
-- filesystem encoding.
|
||||
excluded ch = not (isAlphaNum ch) || not (isAscii ch)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue