summaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-04-26 18:22:44 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-04-26 18:22:52 -0400
commit8d7348fe1be96f95eda6c8cf386b54825e0b69fd (patch)
tree30cd1c58fcd6766573892873a2cd7f9fa999c196 /Command
parentee51adad7bdad29e77e5d51a192c8de5653fd06e (diff)
To enable an existing special remote, the new enableremote command must be used. The initremote command now is used only to create new special remotes.
Diffstat (limited to 'Command')
-rw-r--r--Command/EnableRemote.hs56
-rw-r--r--Command/InitRemote.hs52
2 files changed, 81 insertions, 27 deletions
diff --git a/Command/EnableRemote.hs b/Command/EnableRemote.hs
new file mode 100644
index 000000000..ea606c284
--- /dev/null
+++ b/Command/EnableRemote.hs
@@ -0,0 +1,56 @@
+{- git-annex command
+ -
+ - Copyright 2013 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.EnableRemote where
+
+import Common.Annex
+import Command
+import qualified Logs.Remote
+import qualified Types.Remote as R
+import qualified Command.InitRemote as InitRemote
+
+import qualified Data.Map as M
+
+def :: [Command]
+def = [command "enableremote"
+ (paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
+ seek SectionSetup "enables use of an existing special remote"]
+
+seek :: [CommandSeek]
+seek = [withWords start]
+
+start :: [String] -> CommandStart
+start [] = unknownNameError "Specify the name of the special remote to enable."
+start (name:ws) = go =<< InitRemote.findExisting name
+ where
+ config = Logs.Remote.keyValToConfig ws
+
+ go Nothing = unknownNameError "Unknown special remote name."
+ go (Just (u, c)) = do
+ let fullconfig = config `M.union` c
+ t <- InitRemote.findType fullconfig
+
+ showStart "enableremote" name
+ next $ perform t u fullconfig
+
+unknownNameError :: String -> Annex a
+unknownNameError prefix = do
+ names <- InitRemote.remoteNames
+ error $ prefix ++
+ if null names
+ then ""
+ else " Known special remotes: " ++ intercalate " " names
+
+perform :: RemoteType -> UUID -> R.RemoteConfig -> CommandPerform
+perform t u c = do
+ c' <- R.setup t u c
+ next $ cleanup u c'
+
+cleanup :: UUID -> R.RemoteConfig -> CommandCleanup
+cleanup u c = do
+ Logs.Remote.configSet u c
+ return True
diff --git a/Command/InitRemote.hs b/Command/InitRemote.hs
index 948b6ef63..684a2cc91 100644
--- a/Command/InitRemote.hs
+++ b/Command/InitRemote.hs
@@ -1,6 +1,6 @@
{- git-annex command
-
- - Copyright 2011 Joey Hess <joey@kitenet.net>
+ - Copyright 2011,2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -23,26 +23,23 @@ import Data.Ord
def :: [Command]
def = [command "initremote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
- seek SectionSetup "sets up a special (non-git) remote"]
+ seek SectionSetup "creates a special (non-git) remote"]
seek :: [CommandSeek]
seek = [withWords start]
start :: [String] -> CommandStart
-start [] = do
- names <- remoteNames
- error $ "Specify a name for the remote. " ++
- if null names
- then ""
- else "Either a new name, or one of these existing special remotes: " ++ intercalate " " names
-start (name:ws) = do
- (u, c) <- findByName name
- let fullconfig = config `M.union` c
- t <- findType fullconfig
-
- showStart "initremote" name
- next $ perform t u name $ M.union config c
-
+start [] = error "Specify a name for the remote."
+start (name:ws) = ifM (isJust <$> findExisting name)
+ ( error $ "There is already a special remote named \"" ++ name ++
+ "\". (Use enableremote to enable an existing special remote.)"
+ , do
+ (u, c) <- generateNew name
+ t <- findType config
+
+ showStart "initremote" name
+ next $ perform t u name $ M.union config c
+ )
where
config = Logs.Remote.keyValToConfig ws
@@ -57,21 +54,22 @@ cleanup u name c = do
Logs.Remote.configSet u c
return True
-{- Look up existing remote's UUID and config by name, or generate a new one -}
-findByName :: String -> Annex (UUID, R.RemoteConfig)
-findByName name = do
+{- See if there's an existing special remote with this name. -}
+findExisting :: String -> Annex (Maybe (UUID, R.RemoteConfig))
+findExisting name = do
t <- trustMap
matches <- sortBy (comparing $ \(u, _c) -> M.lookup u t )
- . findByName' name
+ . findByName name
<$> Logs.Remote.readRemoteLog
- maybe generate return $ headMaybe matches
- where
- generate = do
- uuid <- liftIO genUUID
- return (uuid, M.insert nameKey name M.empty)
+ return $ headMaybe matches
+
+generateNew :: String -> Annex (UUID, R.RemoteConfig)
+generateNew name = do
+ uuid <- liftIO genUUID
+ return (uuid, M.singleton nameKey name)
-findByName' :: String -> M.Map UUID R.RemoteConfig -> [(UUID, R.RemoteConfig)]
-findByName' n = filter (matching . snd) . M.toList
+findByName :: String -> M.Map UUID R.RemoteConfig -> [(UUID, R.RemoteConfig)]
+findByName n = filter (matching . snd) . M.toList
where
matching c = case M.lookup nameKey c of
Nothing -> False