enableremote: Can now be used to explicitly enable git-annex to use git remotes. Using the command this way prevents other git-annex commands from probing new git remotes to auto-enable them.
This commit is contained in:
parent
afb332a142
commit
b33a649a25
3 changed files with 71 additions and 38 deletions
|
@ -19,6 +19,9 @@ git-annex (6.20160512) UNRELEASED; urgency=medium
|
||||||
when in a subdirectory of the repository. This affected git annex view.
|
when in a subdirectory of the repository. This affected git annex view.
|
||||||
* Fix crash when entering/changing view in a subdirectory of a repo that
|
* Fix crash when entering/changing view in a subdirectory of a repo that
|
||||||
has a dotfile in its root.
|
has a dotfile in its root.
|
||||||
|
* enableremote: Can now be used to explicitly enable git-annex to use
|
||||||
|
git remotes. Using the command this way prevents other git-annex
|
||||||
|
commands from probing new git remotes to auto-enable them.
|
||||||
* Support building with ghc 8.0.1.
|
* Support building with ghc 8.0.1.
|
||||||
* Pass the various gnupg-options configs to gpg in several cases where
|
* Pass the various gnupg-options configs to gpg in several cases where
|
||||||
they were not before. Most notably, gnupg-decrypt-options is now
|
they were not before. Most notably, gnupg-decrypt-options is now
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex command
|
{- git-annex command
|
||||||
-
|
-
|
||||||
- Copyright 2013 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2016 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -8,18 +8,22 @@
|
||||||
module Command.EnableRemote where
|
module Command.EnableRemote where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
import qualified Annex
|
||||||
import qualified Logs.Remote
|
import qualified Logs.Remote
|
||||||
import qualified Types.Remote as R
|
import qualified Types.Remote as R
|
||||||
|
import qualified Git.Types as Git
|
||||||
import qualified Annex.SpecialRemote
|
import qualified Annex.SpecialRemote
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Types.Remote as Remote
|
import qualified Types.Remote as Remote
|
||||||
|
import qualified Remote.Git
|
||||||
import Logs.UUID
|
import Logs.UUID
|
||||||
|
import Annex.UUID
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = command "enableremote" SectionSetup
|
cmd = command "enableremote" SectionSetup
|
||||||
"enables use of an existing special remote"
|
"enables git-annex to use a remote"
|
||||||
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
|
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
|
||||||
(withParams seek)
|
(withParams seek)
|
||||||
|
|
||||||
|
@ -27,43 +31,62 @@ seek :: CmdParams -> CommandSeek
|
||||||
seek = withWords start
|
seek = withWords start
|
||||||
|
|
||||||
start :: [String] -> CommandStart
|
start :: [String] -> CommandStart
|
||||||
start [] = unknownNameError "Specify the special remote to enable."
|
start [] = unknownNameError "Specify the remote to enable."
|
||||||
start (name:ws) = go =<< Annex.SpecialRemote.findExisting name
|
start (name:rest) = go =<< filter matchingname <$> Annex.fromRepo Git.remotes
|
||||||
where
|
where
|
||||||
config = Logs.Remote.keyValToConfig ws
|
matchingname r = Git.remoteName r == Just name
|
||||||
|
go [] = startSpecialRemote name (Logs.Remote.keyValToConfig rest)
|
||||||
go Nothing = do
|
=<< Annex.SpecialRemote.findExisting name
|
||||||
m <- Annex.SpecialRemote.specialRemoteMap
|
go (r:_) = startNormalRemote name r
|
||||||
confm <- Logs.Remote.readRemoteLog
|
|
||||||
v <- Remote.nameToUUID' name
|
type RemoteName = String
|
||||||
case v of
|
|
||||||
Right u | u `M.member` m ->
|
startNormalRemote :: RemoteName -> Git.Repo -> CommandStart
|
||||||
go (Just (u, fromMaybe M.empty (M.lookup u confm)))
|
startNormalRemote name r = do
|
||||||
_ -> unknownNameError "Unknown special remote."
|
showStart "enableremote" name
|
||||||
go (Just (u, c)) = do
|
next $ next $ do
|
||||||
let fullconfig = config `M.union` c
|
r' <- Remote.Git.configRead False r
|
||||||
t <- either error return (Annex.SpecialRemote.findType fullconfig)
|
u <- getRepoUUID r'
|
||||||
showStart "enableremote" name
|
return (u /= NoUUID)
|
||||||
gc <- maybe def Remote.gitconfig <$> Remote.byUUID u
|
|
||||||
next $ perform t u fullconfig gc
|
startSpecialRemote :: RemoteName -> Remote.RemoteConfig -> Maybe (UUID, Remote.RemoteConfig) -> CommandStart
|
||||||
|
startSpecialRemote name config Nothing = do
|
||||||
|
m <- Annex.SpecialRemote.specialRemoteMap
|
||||||
|
confm <- Logs.Remote.readRemoteLog
|
||||||
|
v <- Remote.nameToUUID' name
|
||||||
|
case v of
|
||||||
|
Right u | u `M.member` m ->
|
||||||
|
startSpecialRemote name config $
|
||||||
|
Just (u, fromMaybe M.empty (M.lookup u confm))
|
||||||
|
_ -> unknownNameError "Unknown remote name."
|
||||||
|
startSpecialRemote name config (Just (u, c)) = do
|
||||||
|
let fullconfig = config `M.union` c
|
||||||
|
t <- either error return (Annex.SpecialRemote.findType fullconfig)
|
||||||
|
showStart "enableremote" name
|
||||||
|
gc <- maybe def Remote.gitconfig <$> Remote.byUUID u
|
||||||
|
next $ performSpecialRemote t u fullconfig gc
|
||||||
|
|
||||||
|
performSpecialRemote :: RemoteType -> UUID -> R.RemoteConfig -> RemoteGitConfig -> CommandPerform
|
||||||
|
performSpecialRemote t u c gc = do
|
||||||
|
(c', u') <- R.setup t (Just u) Nothing c gc
|
||||||
|
next $ cleanupSpecialRemote u' c'
|
||||||
|
|
||||||
|
cleanupSpecialRemote :: UUID -> R.RemoteConfig -> CommandCleanup
|
||||||
|
cleanupSpecialRemote u c = do
|
||||||
|
Logs.Remote.configSet u c
|
||||||
|
return True
|
||||||
|
|
||||||
unknownNameError :: String -> Annex a
|
unknownNameError :: String -> Annex a
|
||||||
unknownNameError prefix = do
|
unknownNameError prefix = do
|
||||||
m <- Annex.SpecialRemote.specialRemoteMap
|
m <- Annex.SpecialRemote.specialRemoteMap
|
||||||
descm <- M.unionWith Remote.addName <$> uuidMap <*> pure m
|
descm <- M.unionWith Remote.addName <$> uuidMap <*> pure m
|
||||||
msg <- if M.null m
|
specialmsg <- if M.null m
|
||||||
then pure "(No special remotes are currently known; perhaps use initremote instead?)"
|
then pure "(No special remotes are currently known; perhaps use initremote instead?)"
|
||||||
else Remote.prettyPrintUUIDsDescs
|
else Remote.prettyPrintUUIDsDescs
|
||||||
"known special remotes"
|
"known special remotes"
|
||||||
descm (M.keys m)
|
descm (M.keys m)
|
||||||
error $ prefix ++ "\n" ++ msg
|
nouuids <- filterM (\r -> (==) NoUUID <$> getRepoUUID r)
|
||||||
|
=<< Annex.fromRepo Git.remotes
|
||||||
perform :: RemoteType -> UUID -> R.RemoteConfig -> RemoteGitConfig -> CommandPerform
|
let nouuidmsg = unlines $ map ("\t" ++) $
|
||||||
perform t u c gc = do
|
mapMaybe Git.remoteName nouuids
|
||||||
(c', u') <- R.setup t (Just u) Nothing c gc
|
error $ concat $ filter (not . null) [prefix ++ "\n", nouuidmsg, specialmsg]
|
||||||
next $ cleanup u' c'
|
|
||||||
|
|
||||||
cleanup :: UUID -> R.RemoteConfig -> CommandCleanup
|
|
||||||
cleanup u c = do
|
|
||||||
Logs.Remote.configSet u c
|
|
||||||
return True
|
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
# NAME
|
# NAME
|
||||||
|
|
||||||
git-annex enableremote - enables use of an existing special remote
|
git-annex enableremote - enables git-annex to use a remote
|
||||||
|
|
||||||
# SYNOPSIS
|
# SYNOPSIS
|
||||||
|
|
||||||
|
@ -8,15 +8,22 @@ git annex enableremote `name|uuid|desc [param=value ...]`
|
||||||
|
|
||||||
# DESCRIPTION
|
# DESCRIPTION
|
||||||
|
|
||||||
Enables use of an existing special remote in the current repository,
|
Enables use of an existing remote in the current repository.
|
||||||
which may be a different repository than the one in which it was
|
|
||||||
originally created with the initremote command.
|
|
||||||
|
|
||||||
The name of the remote is the same name used when originally
|
This is often used to enable use of a special (non-git) remote, by
|
||||||
|
a different repository than the one in which it was
|
||||||
|
originally created with the initremote command.
|
||||||
|
|
||||||
|
It can also be used to explicitly enable a git remote,
|
||||||
|
so that git-annex can store the contents of files there. First
|
||||||
|
run `git remote add`, and then `git annex enableremote` with the name of
|
||||||
|
the remote.
|
||||||
|
|
||||||
|
When enabling a special remote, specify the same name used when originally
|
||||||
creating that remote with `git annex initremote`. Run
|
creating that remote with `git annex initremote`. Run
|
||||||
`git annex enableremote` without any name to get a list of
|
`git annex enableremote` without any name to get a list of
|
||||||
special remote names. Or you can specify the uuid or description of the
|
special remote names. Or you can specify the uuid or description of the
|
||||||
remote.
|
special remote.
|
||||||
|
|
||||||
Some special remotes may need parameters to be specified every time they are
|
Some special remotes may need parameters to be specified every time they are
|
||||||
enabled. For example, the directory special remote requires a directory=
|
enabled. For example, the directory special remote requires a directory=
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue