summaryrefslogtreecommitdiff
path: root/Remote.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-07-05 20:16:57 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-07-05 20:16:57 -0400
commit6040d8aed17de582f5d5c179040e29c599315e31 (patch)
treebb524b386d740353e35a99c235a5d9b6af1f4ddb /Remote.hs
parent9f1577f74684d8d627e75d3021eb1ff50ef7492f (diff)
factor out RemoteLog
Diffstat (limited to 'Remote.hs')
-rw-r--r--Remote.hs85
1 files changed, 2 insertions, 83 deletions
diff --git a/Remote.hs b/Remote.hs
index 623b85733..a86e1022c 100644
--- a/Remote.hs
+++ b/Remote.hs
@@ -17,7 +17,6 @@ module Remote (
keyPossibilities,
keyPossibilitiesTrusted,
- forceTrust,
remoteTypes,
genList,
byName,
@@ -27,24 +26,14 @@ module Remote (
prettyPrintUUIDs,
showTriedRemotes,
showLocations,
-
- remoteLog,
- readRemoteLog,
- configSet,
- keyValToConfig,
- configToKeyVal,
-
- prop_idempotent_configEscape
+ forceTrust
) where
import Control.Monad (filterM, liftM2)
import Data.List
import qualified Data.Map as M
-import Data.Maybe
-import Data.Char
import Data.String.Utils
-import qualified Branch
import Types
import Types.Remote
import UUID
@@ -53,6 +42,7 @@ import Config
import Trust
import LocationLog
import Messages
+import RemoteLog
import qualified Remote.Git
import qualified Remote.S3
@@ -215,74 +205,3 @@ forceTrust level remotename = do
r <- nameToUUID remotename
Annex.changeState $ \s ->
s { Annex.forcetrust = (r, level):Annex.forcetrust s }
-
-{- Filename of remote.log. -}
-remoteLog :: FilePath
-remoteLog = "remote.log"
-
-{- Adds or updates a remote's config in the log. -}
-configSet :: UUID -> RemoteConfig -> Annex ()
-configSet u c = do
- m <- readRemoteLog
- Branch.change remoteLog $ unlines $ sort $
- map toline $ M.toList $ M.insert u c m
- where
- toline (u', c') = u' ++ " " ++ (unwords $ configToKeyVal c')
-
-{- Map of remotes by uuid containing key/value config maps. -}
-readRemoteLog :: Annex (M.Map UUID RemoteConfig)
-readRemoteLog = return . remoteLogParse =<< Branch.get remoteLog
-
-remoteLogParse :: String -> M.Map UUID RemoteConfig
-remoteLogParse s =
- M.fromList $ catMaybes $ map parseline $ filter (not . null) $ lines s
- where
- parseline l
- | length w > 2 = Just (u, c)
- | otherwise = Nothing
- where
- w = words l
- u = w !! 0
- c = keyValToConfig $ tail w
-
-{- 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 = (>>= 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 = if ok
- then chr (read num) : unescape rest
- else '&' : unescape s
- where
- num = takeWhile isNumber s
- r = drop (length num) s
- rest = drop 1 r
- ok = not (null num) &&
- not (null r) && r !! 0 == ';'
-
-{- for quickcheck -}
-prop_idempotent_configEscape :: String -> Bool
-prop_idempotent_configEscape s = s == (configUnEscape $ configEscape s)