Special remotes configured with autoenable=true will be automatically enabled when git-annex init is run.

This commit is contained in:
Joey Hess 2015-09-14 14:49:48 -04:00
parent 3f47d1b351
commit 9cfb96c53d
12 changed files with 148 additions and 64 deletions

85
Annex/SpecialRemote.hs Normal file
View file

@ -0,0 +1,85 @@
{- git-annex special remote configuration
-
- Copyright 2011-2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Annex.SpecialRemote where
import Common.Annex
import Remote (remoteTypes)
import Types.Remote (RemoteConfig, RemoteConfigKey, typename, setup)
import Logs.Remote
import Logs.Trust
import qualified Git.Config
import qualified Data.Map as M
import Data.Ord
type RemoteName = String
{- See if there's an existing special remote with this name.
-
- Prefer remotes that are not dead when a name appears multiple times. -}
findExisting :: RemoteName -> Annex (Maybe (UUID, RemoteConfig))
findExisting name = do
t <- trustMap
matches <- sortBy (comparing $ \(u, _c) -> M.lookup u t)
. findByName name
<$> Logs.Remote.readRemoteLog
return $ headMaybe matches
newConfig :: RemoteName -> RemoteConfig
newConfig = M.singleton nameKey
findByName :: RemoteName -> M.Map UUID RemoteConfig -> [(UUID, RemoteConfig)]
findByName n = filter (matching . snd) . M.toList
where
matching c = case M.lookup nameKey c of
Nothing -> False
Just n'
| n' == n -> True
| otherwise -> False
remoteNames :: Annex [RemoteName]
remoteNames = do
m <- Logs.Remote.readRemoteLog
return $ mapMaybe (M.lookup nameKey . snd) $ M.toList m
{- find the specified remote type -}
findType :: RemoteConfig -> Either String RemoteType
findType config = maybe unspecified specified $ M.lookup typeKey config
where
unspecified = Left "Specify the type of remote with type="
specified s = case filter (findtype s) remoteTypes of
[] -> Left $ "Unknown remote type " ++ s
(t:_) -> Right t
findtype s i = typename i == s
{- The name of a configured remote is stored in its config using this key. -}
nameKey :: RemoteConfigKey
nameKey = "name"
{- The type of a remote is stored in its config using this key. -}
typeKey :: RemoteConfigKey
typeKey = "type"
autoEnableKey :: RemoteConfigKey
autoEnableKey = "autoenable"
autoEnable :: Annex ()
autoEnable = do
remotemap <- M.filter wanted <$> readRemoteLog
forM_ (M.toList remotemap) $ \(u, c) ->
case (M.lookup nameKey c, findType c) of
(Just name, Right t) -> do
showSideAction $ "Auto enabling special remote " ++ name
res <- tryNonAsync $ setup t (Just u) Nothing c
case res of
Left e -> warning (show e)
Right _ -> return ()
_ -> return ()
where
wanted rc = fromMaybe False $
Git.Config.isTrue =<< M.lookup autoEnableKey rc

View file

@ -16,7 +16,7 @@ import qualified Remote.Rsync as Rsync
import qualified Remote.GCrypt as GCrypt
import qualified Git
import qualified Git.Command
import qualified Command.InitRemote
import qualified Annex.SpecialRemote
import Logs.UUID
import Logs.Remote
import Git.Remote
@ -46,10 +46,10 @@ addRemote a = do
{- Inits a rsync special remote, and returns its name. -}
makeRsyncRemote :: RemoteName -> String -> Annex String
makeRsyncRemote name location = makeRemote name location $ const $ void $
go =<< Command.InitRemote.findExisting name
go =<< Annex.SpecialRemote.findExisting name
where
go Nothing = setupSpecialRemote name Rsync.remote config Nothing
(Nothing, Command.InitRemote.newConfig name)
(Nothing, Annex.SpecialRemote.newConfig name)
go (Just (u, c)) = setupSpecialRemote name Rsync.remote config Nothing
(Just u, c)
config = M.fromList
@ -78,16 +78,16 @@ initSpecialRemote name remotetype mcreds config = go 0
go :: Int -> Annex RemoteName
go n = do
let fullname = if n == 0 then name else name ++ show n
r <- Command.InitRemote.findExisting fullname
r <- Annex.SpecialRemote.findExisting fullname
case r of
Nothing -> setupSpecialRemote fullname remotetype config mcreds
(Nothing, Command.InitRemote.newConfig fullname)
(Nothing, Annex.SpecialRemote.newConfig fullname)
Just _ -> go (n + 1)
{- Enables an existing special remote. -}
enableSpecialRemote :: SpecialRemoteMaker
enableSpecialRemote name remotetype mcreds config = do
r <- Command.InitRemote.findExisting name
r <- Annex.SpecialRemote.findExisting name
case r of
Nothing -> error $ "Cannot find a special remote named " ++ name
Just (u, c) -> setupSpecialRemote' False name remotetype config mcreds (Just u, c)

View file

@ -11,7 +11,7 @@ import Common.Annex
import Command
import qualified Logs.Remote
import qualified Types.Remote as R
import qualified Command.InitRemote as InitRemote
import qualified Annex.SpecialRemote
import qualified Data.Map as M
@ -26,21 +26,20 @@ seek = withWords start
start :: [String] -> CommandStart
start [] = unknownNameError "Specify the name of the special remote to enable."
start (name:ws) = go =<< InitRemote.findExisting name
start (name:ws) = go =<< Annex.SpecialRemote.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
t <- either error return (Annex.SpecialRemote.findType fullconfig)
showStart "enableremote" name
next $ perform t u fullconfig
unknownNameError :: String -> Annex a
unknownNameError prefix = do
names <- InitRemote.remoteNames
names <- Annex.SpecialRemote.remoteNames
error $ prefix ++ "\n" ++
if null names
then "(No special remotes are currently known; perhaps use initremote instead?)"

View file

@ -10,6 +10,7 @@ module Command.Init where
import Common.Annex
import Command
import Annex.Init
import qualified Annex.SpecialRemote
cmd :: Command
cmd = dontCheck repoExists $
@ -29,4 +30,5 @@ start ws = do
perform :: String -> CommandPerform
perform description = do
initialize $ if null description then Nothing else Just description
Annex.SpecialRemote.autoEnable
next $ return True

View file

@ -10,14 +10,12 @@ module Command.InitRemote where
import qualified Data.Map as M
import Common.Annex
import Annex.SpecialRemote
import Command
import qualified Remote
import qualified Logs.Remote
import qualified Types.Remote as R
import Logs.UUID
import Logs.Trust
import Data.Ord
cmd :: Command
cmd = command "initremote" SectionSetup
@ -38,7 +36,7 @@ start (name:ws) = ifM (isJust <$> findExisting name)
( error $ "There is already a remote named \"" ++ name ++ "\""
, do
let c = newConfig name
t <- findType config
t <- either error return (findType config)
showStart "initremote" name
next $ perform t name $ M.union config c
@ -57,47 +55,3 @@ cleanup u name c = do
describeUUID u name
Logs.Remote.configSet u c
return True
{- 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
<$> Logs.Remote.readRemoteLog
return $ headMaybe matches
newConfig :: String -> R.RemoteConfig
newConfig = M.singleton nameKey
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
Just n'
| n' == n -> True
| otherwise -> False
remoteNames :: Annex [String]
remoteNames = do
m <- Logs.Remote.readRemoteLog
return $ mapMaybe (M.lookup nameKey . snd) $ M.toList m
{- find the specified remote type -}
findType :: R.RemoteConfig -> Annex RemoteType
findType config = maybe unspecified specified $ M.lookup typeKey config
where
unspecified = error "Specify the type of remote with type="
specified s = case filter (findtype s) Remote.remoteTypes of
[] -> error $ "Unknown remote type " ++ s
(t:_) -> return t
findtype s i = R.typename i == s
{- The name of a configured remote is stored in its config using this key. -}
nameKey :: String
nameKey = "name"
{- The type of a remote is stored in its config using this key. -}
typeKey :: String
typeKey = "type"

View file

@ -13,6 +13,7 @@ import Annex.Init
import Annex.UUID
import Types.UUID
import qualified Remote
import qualified Annex.SpecialRemote
cmd :: Command
cmd = dontCheck repoExists $
@ -38,4 +39,5 @@ perform s = do
else Remote.nameToUUID s
storeUUID u
initialize'
Annex.SpecialRemote.autoEnable
next $ return True

2
debian/changelog vendored
View file

@ -24,6 +24,8 @@ git-annex (5.20150825) UNRELEASED; urgency=medium
the repository to a remote.
* Improve bash completion, so it completes names of remotes and backends
in appropriate places.
* Special remotes configured with autoenable=true will be automatically
enabled when git-annex init is run.
-- Joey Hess <id@joeyh.name> Tue, 01 Sep 2015 14:46:18 -0700

View file

@ -19,14 +19,14 @@ special remote names.
Some special remotes may need parameters to be specified every time they are
enabled. For example, the directory special remote requires a directory=
parameter.
parameter every time.
This command can also be used to modify the configuration of an existing
special remote, by specifying new values for parameters that were
originally set when using initremote. (However, some settings such as
special remote, by specifying new values for parameters that are
usually set when using initremote. (However, some settings such as
the as the encryption scheme cannot be changed once a special remote
has been created.)
The GPG keys that an encrypted special remote is encrypted with can be
changed using the keyid+= and keyid-= parameters. These respectively
add and remove keys from the list. However, note that removing a key
@ -45,6 +45,12 @@ on files that have already been copied to the remote. Hence using
keyid+= and keyid-= with such remotes should be used with care, and
make little sense except in cases like the revoked key example above.
If you get tired of manually enabling a special remote in each new clone,
you can pass "autoenable=true". Then when [[git-annex-init]](1) is run in
a new clone, it will will attempt to enable the special remote. Of course,
this works best when the special remote does not need anything special
to be done to get it enabled.
# SEE ALSO
[[git-annex]](1)

View file

@ -16,6 +16,14 @@ It's useful, but not mandatory, to initialize each new clone
of a repository with its own description. If you don't provide one,
one will be generated using the username, hostname and the path.
If any special remotes were configured with autoenable=true,
this will also attempt to enable them. See [[git-annex-initremote]](1).
To disable this, re-enable a remote with "autoenable=false", or
mark it as dead (see [[git-annex-dead]](1)).
This command is entirely safe, although usually pointless, to run inside an
already initialized git-annex repository.
# SEE ALSO
[[git-annex]](1)

View file

@ -36,6 +36,12 @@ encryption=pubkey, content in the special remote is directly encrypted
to the specified GPG keys, and additional ones cannot easily be given
access.
If you anticipate using the new special remote in other clones of the
repository, you can pass "autoenable=true". Then when [[git-annex-init]](1)
is run in a new clone, it will attempt to enable the special remote. Of
course, this works best when the special remote does not need anything
special to be done to get it enabled.
# OPTIONS
* `--fast`

View file

@ -17,6 +17,9 @@ Use this with caution; it can be confusing to have two existing
repositories with the same UUID. Also, you will probably want to run
a fsck.
Like `git annex init`, this attempts to enable any special remotes
that are configured with autoenable=true.
# SEE ALSO
[[git-annex]](1)

View file

@ -1,3 +1,20 @@
Just passing along from https://github.com/datalad/datalad/issues/77#issuecomment-134688459
joey: I do think there could be a use case for configuring a special remote with autoenable=true and have git-annex init try to enable all such remotes.
> [[done]], I made both `git init` and `git annex reinit` auto-enable
> such special remotes. For now, the assistant does not (could change).
>
> There was also the question of what to do when git-annex auto-inits
> in a clone of a repository. It wouldn't do for a command like
> `git annex find`'s output to include any messages that might be shown while
> auto-enabling special remotes as a result of an auto-init.
> Since I can't guarantee enabling special remotes will be quiet, I've not
> tried to auto-enable special remotes in this case.
>
> I think I'd have to
> exec a git-annex init process with stdout sent to stderr to implement
> this in a safe way, and due to calls to ensureInitialized in Remote.Git,
> which can auto-init a local remote, that gets particularly tricky. Best, I
> feel, to wait and see if anyone needs that.
--[[Joey]]