git-annex-shell gcryptsetup command
This was the least-bad alternative to get dedicated key gcrypt repos working in the assistant.
This commit is contained in:
parent
245d5590c9
commit
bddfbef8be
4 changed files with 65 additions and 23 deletions
35
Command/GCryptSetup.hs
Normal file
35
Command/GCryptSetup.hs
Normal file
|
@ -0,0 +1,35 @@
|
||||||
|
{- git-annex command
|
||||||
|
-
|
||||||
|
- Copyright 2013 Joey Hess <joey@kitenet.net>
|
||||||
|
-
|
||||||
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Command.GCryptSetup where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import Command
|
||||||
|
import Annex.UUID
|
||||||
|
import qualified Remote.GCrypt
|
||||||
|
import qualified Git
|
||||||
|
|
||||||
|
def :: [Command]
|
||||||
|
def = [dontCheck repoExists $ noCommit $
|
||||||
|
command "gcryptsetup" paramValue seek
|
||||||
|
SectionPlumbing "sets up gcrypt repository"]
|
||||||
|
|
||||||
|
seek :: [CommandSeek]
|
||||||
|
seek = [withStrings start]
|
||||||
|
|
||||||
|
start :: String -> CommandStart
|
||||||
|
start gcryptid = next $ next $ do
|
||||||
|
g <- gitRepo
|
||||||
|
u <- getUUID
|
||||||
|
gu <- Remote.GCrypt.getGCryptUUID True g
|
||||||
|
if u == NoUUID && gu == Nothing
|
||||||
|
then if Git.repoIsLocalBare g
|
||||||
|
then do
|
||||||
|
void $ Remote.GCrypt.setupRepo gcryptid g
|
||||||
|
return True
|
||||||
|
else error "cannot use gcrypt in a non-bare repository"
|
||||||
|
else error "gcryptsetup permission denied"
|
|
@ -30,24 +30,26 @@ import qualified Command.RecvKey
|
||||||
import qualified Command.SendKey
|
import qualified Command.SendKey
|
||||||
import qualified Command.TransferInfo
|
import qualified Command.TransferInfo
|
||||||
import qualified Command.Commit
|
import qualified Command.Commit
|
||||||
|
import qualified Command.GCryptSetup
|
||||||
|
|
||||||
cmds_readonly :: [Command]
|
cmds_readonly :: [Command]
|
||||||
cmds_readonly = concat
|
cmds_readonly = concat
|
||||||
[ Command.ConfigList.def
|
[ gitAnnexShellCheck Command.ConfigList.def
|
||||||
, Command.InAnnex.def
|
, gitAnnexShellCheck Command.InAnnex.def
|
||||||
, Command.SendKey.def
|
, gitAnnexShellCheck Command.SendKey.def
|
||||||
, Command.TransferInfo.def
|
, gitAnnexShellCheck Command.TransferInfo.def
|
||||||
]
|
]
|
||||||
|
|
||||||
cmds_notreadonly :: [Command]
|
cmds_notreadonly :: [Command]
|
||||||
cmds_notreadonly = concat
|
cmds_notreadonly = concat
|
||||||
[ Command.RecvKey.def
|
[ gitAnnexShellCheck Command.RecvKey.def
|
||||||
, Command.DropKey.def
|
, gitAnnexShellCheck Command.DropKey.def
|
||||||
, Command.Commit.def
|
, gitAnnexShellCheck Command.Commit.def
|
||||||
|
, Command.GCryptSetup.def
|
||||||
]
|
]
|
||||||
|
|
||||||
cmds :: [Command]
|
cmds :: [Command]
|
||||||
cmds = map gitAnnexShellCheck $ map adddirparam $ cmds_readonly ++ cmds_notreadonly
|
cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
|
||||||
where
|
where
|
||||||
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
|
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
|
||||||
|
|
||||||
|
@ -191,8 +193,8 @@ checkEnv var = do
|
||||||
|
|
||||||
{- Modifies a Command to check that it is run in either a git-annex
|
{- Modifies a Command to check that it is run in either a git-annex
|
||||||
- repository, or a repository with a gcrypt-id set. -}
|
- repository, or a repository with a gcrypt-id set. -}
|
||||||
gitAnnexShellCheck :: Command -> Command
|
gitAnnexShellCheck :: [Command] -> [Command]
|
||||||
gitAnnexShellCheck = addCheck okforshell . dontCheck repoExists
|
gitAnnexShellCheck = map $ addCheck okforshell . dontCheck repoExists
|
||||||
where
|
where
|
||||||
okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
|
okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
|
||||||
error "Not a git-annex or gcrypt repository."
|
error "Not a git-annex or gcrypt repository."
|
||||||
|
|
|
@ -9,7 +9,8 @@ module Remote.GCrypt (
|
||||||
remote,
|
remote,
|
||||||
gen,
|
gen,
|
||||||
getGCryptUUID,
|
getGCryptUUID,
|
||||||
coreGCryptId
|
coreGCryptId,
|
||||||
|
setupRepo
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -198,12 +199,12 @@ gCryptSetup mu c = go $ M.lookup "gitrepo" c
|
||||||
setupRepo :: Git.GCrypt.GCryptId -> Git.Repo -> Annex AccessMethod
|
setupRepo :: Git.GCrypt.GCryptId -> Git.Repo -> Annex AccessMethod
|
||||||
setupRepo gcryptid r
|
setupRepo gcryptid r
|
||||||
| Git.repoIsUrl r = do
|
| Git.repoIsUrl r = do
|
||||||
accessmethod <- rsyncsetup
|
(_, _, accessmethod) <- rsyncTransport r
|
||||||
case accessmethod of
|
case accessmethod of
|
||||||
AccessDirect -> return AccessDirect
|
AccessDirect -> rsyncsetup
|
||||||
AccessShell -> ifM usablegitannexshell
|
AccessShell -> ifM gitannexshellsetup
|
||||||
( return AccessShell
|
( return AccessShell
|
||||||
, return AccessDirect
|
, rsyncsetup
|
||||||
)
|
)
|
||||||
| Git.repoIsLocalUnknown r = localsetup =<< liftIO (Git.Config.read r)
|
| Git.repoIsLocalUnknown r = localsetup =<< liftIO (Git.Config.read r)
|
||||||
| otherwise = localsetup r
|
| otherwise = localsetup r
|
||||||
|
@ -220,15 +221,15 @@ setupRepo gcryptid r
|
||||||
-}
|
-}
|
||||||
rsyncsetup = Remote.Rsync.withRsyncScratchDir $ \tmp -> do
|
rsyncsetup = Remote.Rsync.withRsyncScratchDir $ \tmp -> do
|
||||||
liftIO $ createDirectoryIfMissing True $ tmp </> objectDir
|
liftIO $ createDirectoryIfMissing True $ tmp </> objectDir
|
||||||
(rsynctransport, rsyncurl, accessmethod) <- rsyncTransport r
|
(rsynctransport, rsyncurl, _) <- rsyncTransport r
|
||||||
let tmpconfig = tmp </> "config"
|
let tmpconfig = tmp </> "config"
|
||||||
void $ liftIO $ rsync $ rsynctransport ++
|
void $ liftIO $ rsync $ rsynctransport ++
|
||||||
[ Param $ rsyncurl ++ "/config"
|
[ Param $ rsyncurl ++ "/config"
|
||||||
, Param tmpconfig
|
, Param tmpconfig
|
||||||
]
|
]
|
||||||
liftIO $ do
|
liftIO $ do
|
||||||
Git.Config.changeFile tmpconfig coreGCryptId gcryptid
|
void $ Git.Config.changeFile tmpconfig coreGCryptId gcryptid
|
||||||
Git.Config.changeFile tmpconfig denyNonFastForwards (Git.Config.boolConfig False)
|
void $ Git.Config.changeFile tmpconfig denyNonFastForwards (Git.Config.boolConfig False)
|
||||||
ok <- liftIO $ rsync $ rsynctransport ++
|
ok <- liftIO $ rsync $ rsynctransport ++
|
||||||
[ Params "--recursive"
|
[ Params "--recursive"
|
||||||
, Param $ tmp ++ "/"
|
, Param $ tmp ++ "/"
|
||||||
|
@ -236,12 +237,12 @@ setupRepo gcryptid r
|
||||||
]
|
]
|
||||||
unless ok $
|
unless ok $
|
||||||
error "Failed to connect to remote to set it up."
|
error "Failed to connect to remote to set it up."
|
||||||
return accessmethod
|
return AccessDirect
|
||||||
|
|
||||||
{- Check if git-annex shell is installed, and is a new enough
|
{- Ask git-annex-shell to configure the repository as a gcrypt
|
||||||
- version to work in a gcrypt repo. -}
|
- repository. May fail if it is too old. -}
|
||||||
usablegitannexshell = either (const False) (const True)
|
gitannexshellsetup = Ssh.onRemote r (boolSystem, False)
|
||||||
<$> Ssh.onRemote r (Git.Config.fromPipe r, Left undefined) "configlist" [] []
|
"gcryptsetup" [ Param gcryptid ] []
|
||||||
|
|
||||||
denyNonFastForwards = "receive.denyNonFastForwards"
|
denyNonFastForwards = "receive.denyNonFastForwards"
|
||||||
|
|
||||||
|
|
|
@ -60,6 +60,10 @@ first "/~/" or "/~user/" is expanded to the specified home directory.
|
||||||
This commits any staged changes to the git-annex branch.
|
This commits any staged changes to the git-annex branch.
|
||||||
It also runs the annex-content hook.
|
It also runs the annex-content hook.
|
||||||
|
|
||||||
|
* gcryptsetup gcryptid
|
||||||
|
|
||||||
|
Sets up a repository as a gcrypt repository.
|
||||||
|
|
||||||
# OPTIONS
|
# OPTIONS
|
||||||
|
|
||||||
Most options are the same as in git-annex. The ones specific
|
Most options are the same as in git-annex. The ones specific
|
||||||
|
|
Loading…
Add table
Reference in a new issue