add back lost check that git-annex-shell supports gcrypt
This commit is contained in:
parent
b6b461992e
commit
3192b059b5
3 changed files with 38 additions and 13 deletions
|
@ -10,6 +10,7 @@ module Git.Config where
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import System.Process (cwd, env)
|
import System.Process (cwd, env)
|
||||||
|
import Control.Exception.Extensible
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Git
|
import Git
|
||||||
|
@ -153,3 +154,17 @@ boolConfig False = "false"
|
||||||
|
|
||||||
isBare :: Repo -> Bool
|
isBare :: Repo -> Bool
|
||||||
isBare r = fromMaybe False $ isTrue =<< getMaybe "core.bare" r
|
isBare r = fromMaybe False $ isTrue =<< getMaybe "core.bare" r
|
||||||
|
|
||||||
|
{- Runs a command to get the configuration of a repo,
|
||||||
|
- and returns a repo populated with the configuration, as well as the raw
|
||||||
|
- output of the command. -}
|
||||||
|
fromPipe :: Repo -> String -> [CommandParam] -> IO (Either SomeException (Repo, String))
|
||||||
|
fromPipe r cmd params = try $
|
||||||
|
withHandle StdoutHandle createProcessSuccess p $ \h -> do
|
||||||
|
fileEncoding h
|
||||||
|
val <- hGetContentsStrict h
|
||||||
|
r' <- store val r
|
||||||
|
return (r', val)
|
||||||
|
where
|
||||||
|
p = proc cmd $ toCommand params
|
||||||
|
|
||||||
|
|
|
@ -209,7 +209,14 @@ 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 = rsyncsetup
|
| Git.repoIsUrl r = do
|
||||||
|
accessmethod <- rsyncsetup
|
||||||
|
case accessmethod of
|
||||||
|
AccessDirect -> return AccessDirect
|
||||||
|
AccessShell -> ifM usablegitannexshell
|
||||||
|
( return AccessShell
|
||||||
|
, return AccessDirect
|
||||||
|
)
|
||||||
| Git.repoIsLocalUnknown r = localsetup =<< liftIO (Git.Config.read r)
|
| Git.repoIsLocalUnknown r = localsetup =<< liftIO (Git.Config.read r)
|
||||||
| otherwise = localsetup r
|
| otherwise = localsetup r
|
||||||
where
|
where
|
||||||
|
@ -245,6 +252,11 @@ setupRepo gcryptid r
|
||||||
error "Failed to connect to remote to set it up."
|
error "Failed to connect to remote to set it up."
|
||||||
return accessmethod
|
return accessmethod
|
||||||
|
|
||||||
|
{- Check if git-annex shell is installed, and is a new enough
|
||||||
|
- version to work in a gcrypt repo. -}
|
||||||
|
usablegitannexshell = either (const False) (const True)
|
||||||
|
<$> Ssh.onRemote r (Git.Config.fromPipe r, Left undefined) "configlist" [] []
|
||||||
|
|
||||||
shellOrRsync :: Remote -> Annex a -> Annex a -> Annex a
|
shellOrRsync :: Remote -> Annex a -> Annex a -> Annex a
|
||||||
shellOrRsync r ashell arsync = case method of
|
shellOrRsync r ashell arsync = case method of
|
||||||
AccessShell -> ashell
|
AccessShell -> ashell
|
||||||
|
|
|
@ -165,18 +165,16 @@ tryGitConfigRead r
|
||||||
safely a = either (const $ return r) return
|
safely a = either (const $ return r) return
|
||||||
=<< liftIO (try a :: IO (Either SomeException Git.Repo))
|
=<< liftIO (try a :: IO (Either SomeException Git.Repo))
|
||||||
|
|
||||||
pipedconfig cmd params = try run :: IO (Either SomeException Git.Repo)
|
pipedconfig cmd params = do
|
||||||
where
|
v <- Git.Config.fromPipe r cmd params
|
||||||
run = withHandle StdoutHandle createProcessSuccess p $ \h -> do
|
case v of
|
||||||
fileEncoding h
|
Right (r', val) -> do
|
||||||
val <- hGetContentsStrict h
|
when (getUncachedUUID r' == NoUUID && not (null val)) $ do
|
||||||
r' <- Git.Config.store val r
|
warningIO $ "Failed to get annex.uuid configuration of repository " ++ Git.repoDescribe r
|
||||||
when (getUncachedUUID r' == NoUUID && not (null val)) $ do
|
warningIO $ "Instead, got: " ++ show val
|
||||||
warningIO $ "Failed to get annex.uuid configuration of repository " ++ Git.repoDescribe r
|
warningIO $ "This is unexpected; please check the network transport!"
|
||||||
warningIO $ "Instead, got: " ++ show val
|
return $ Right r'
|
||||||
warningIO $ "This is unexpected; please check the network transport!"
|
Left l -> return $ Left l
|
||||||
return r'
|
|
||||||
p = proc cmd $ toCommand params
|
|
||||||
|
|
||||||
geturlconfig headers = do
|
geturlconfig headers = do
|
||||||
v <- liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
|
v <- liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue