git-annex/Remote/Ddar.hs

230 lines
7.3 KiB
Haskell
Raw Normal View History

2014-05-15 18:44:00 +00:00
{- Using ddar as a remote. Based on bup and rsync remotes.
-
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
2014-05-15 18:44:00 +00:00
- Copyright 2014 Robie Basak <robie@justgohome.co.uk>
-
- Licensed under the GNU GPL version 3 or higher.
2014-05-15 18:44:00 +00:00
-}
{-# LANGUAGE BangPatterns #-}
2014-05-15 18:44:00 +00:00
module Remote.Ddar (remote) where
import qualified Data.Map as M
import qualified Data.ByteString.Lazy as L
2014-05-15 18:44:00 +00:00
import System.IO.Error
import Annex.Common
2014-05-15 18:44:00 +00:00
import Types.Remote
import Types.Creds
import qualified Git
import Config
import Config.Cost
import Annex.SpecialRemote.Config
2014-05-15 18:44:00 +00:00
import Remote.Helper.Special
2019-02-20 19:55:01 +00:00
import Remote.Helper.ExportImport
2014-05-15 18:44:00 +00:00
import Annex.Ssh
import Annex.UUID
import Utility.SshHost
import Types.ProposedAccepted
2014-05-15 18:44:00 +00:00
data DdarRepo = DdarRepo
{ ddarRepoConfig :: RemoteGitConfig
, ddarRepoLocation :: String
}
2014-05-15 18:44:00 +00:00
remote :: RemoteType
remote = specialRemoteType $ RemoteType
{ typename = "ddar"
, enumerate = const (findSpecialRemotes "ddarrepo")
, generate = gen
, configParser = mkRemoteConfigParser
[ optionalStringParser ddarrepoField
(FieldDesc "(required) location of ddar archive to use")
]
, setup = ddarSetup
, exportSupported = exportUnsupported
2019-02-20 19:55:01 +00:00
, importSupported = importUnsupported
}
2014-05-15 18:44:00 +00:00
ddarrepoField :: RemoteConfigField
ddarrepoField = Accepted "ddarrepo"
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> Annex (Maybe Remote)
gen r u rc gc rs = do
c <- parsedRemoteConfig remote rc
2014-05-15 18:44:00 +00:00
cst <- remoteCost gc $
if ddarLocal ddarrepo
then nearlyCheapRemoteCost
else expensiveRemoteCost
let specialcfg = (specialRemoteCfg c)
-- chunking would not improve ddar
{ chunkConfig = NoChunks
}
return $ Just $ specialRemote' specialcfg c
(store ddarrepo)
(retrieve ddarrepo)
(remove ddarrepo)
(checkKey ddarrepo)
(this c cst)
where
this c cst = Remote
2014-05-15 18:44:00 +00:00
{ uuid = u
, cost = cst
, name = Git.repoDescribe r
, storeKey = storeKeyDummy
, retrieveKeyFile = retrieveKeyFileDummy
, retrieveKeyFileCheap = Nothing
-- ddar communicates over ssh, not subject to http redirect
-- type attacks
, retrievalSecurityPolicy = RetrievalAllKeysSecure
, removeKey = removeKeyDummy
, lockContent = Nothing
, checkPresent = checkPresentDummy
, checkPresentCheap = ddarLocal ddarrepo
, exportActions = exportUnsupported
2019-02-20 19:55:01 +00:00
, importActions = importUnsupported
2014-05-15 18:44:00 +00:00
, whereisKey = Nothing
, remoteFsck = Nothing
, repairRepo = Nothing
, config = c
, getRepo = return r
2014-05-15 18:44:00 +00:00
, gitconfig = gc
, localpath = if ddarLocal ddarrepo && not (null $ ddarRepoLocation ddarrepo)
then Just $ ddarRepoLocation ddarrepo
2014-05-15 18:44:00 +00:00
else Nothing
, remotetype = remote
, availability = if ddarLocal ddarrepo then LocallyAvailable else GloballyAvailable
, readonly = False
, appendonly = False
, mkUnavailable = return Nothing
, getInfo = return [("repo", ddarRepoLocation ddarrepo)]
2014-12-08 17:40:15 +00:00
, claimUrl = Nothing
, checkUrl = Nothing
, remoteStateHandle = rs
2014-05-15 18:44:00 +00:00
}
ddarrepo = maybe (giveup "missing ddarrepo") (DdarRepo gc) (remoteAnnexDdarRepo gc)
2014-05-15 18:44:00 +00:00
ddarSetup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> Annex (RemoteConfig, UUID)
ddarSetup _ mu _ c gc = do
2014-05-15 18:44:00 +00:00
u <- maybe (liftIO genUUID) return mu
-- verify configuration is sane
let ddarrepo = maybe (giveup "Specify ddarrepo=") fromProposedAccepted $
M.lookup ddarrepoField c
(c', _encsetup) <- encryptionSetup c gc
2014-05-15 18:44:00 +00:00
-- The ddarrepo is stored in git config, as well as this repo's
-- persistant state, so it can vary between hosts.
gitConfigSpecialRemote u c' [("ddarrepo", ddarrepo)]
2014-05-15 18:44:00 +00:00
return (c', u)
store :: DdarRepo -> Storer
store ddarrepo = fileStorer $ \k src _p -> do
2014-05-15 18:44:00 +00:00
let params =
[ Param "c"
, Param "-N"
, Param $ serializeKey k
, Param $ ddarRepoLocation ddarrepo
2014-05-15 18:44:00 +00:00
, File src
]
unlessM (liftIO $ boolSystem "ddar" params) $
giveup "ddar failed"
2014-05-15 18:44:00 +00:00
{- Convert remote DdarRepo to host and path on remote end -}
splitRemoteDdarRepo :: DdarRepo -> (SshHost, String)
splitRemoteDdarRepo ddarrepo = (either error id $ mkSshHost host, ddarrepo')
2014-05-15 18:44:00 +00:00
where
(host, remainder) = span (/= ':') (ddarRepoLocation ddarrepo)
2014-05-15 18:44:00 +00:00
ddarrepo' = drop 1 remainder
{- Return the command and parameters to use for a ddar call that may need to be
- made on a remote repository. This will call ssh if needed. -}
ddarRemoteCall :: ConsumeStdin -> DdarRepo -> Char -> [CommandParam] -> Annex (String, [CommandParam])
ddarRemoteCall cs ddarrepo cmd params
2014-05-15 18:44:00 +00:00
| ddarLocal ddarrepo = return ("ddar", localParams)
| otherwise = sshCommand cs (host, Nothing) (ddarRepoConfig ddarrepo) remoteCommand
2014-05-15 18:44:00 +00:00
where
(host, ddarrepo') = splitRemoteDdarRepo ddarrepo
localParams = Param [cmd] : Param (ddarRepoLocation ddarrepo) : params
remoteCommand = unwords $ map shellEscape $ toCommand $
[Param "ddar", Param [cmd], Param ddarrepo'] ++ params
2014-05-15 18:44:00 +00:00
{- Specialized ddarRemoteCall that includes extraction command and flags -}
ddarExtractRemoteCall :: ConsumeStdin -> DdarRepo -> Key -> Annex (String, [CommandParam])
ddarExtractRemoteCall cs ddarrepo k =
ddarRemoteCall cs ddarrepo 'x' [Param "--force-stdout", Param $ serializeKey k]
2014-05-15 18:44:00 +00:00
retrieve :: DdarRepo -> Retriever
retrieve ddarrepo = byteRetriever $ \k sink -> do
(cmd, params) <- ddarExtractRemoteCall NoConsumeStdin ddarrepo k
let p = (proc cmd $ toCommand params)
{ std_out = CreatePipe }
bracketIO (createProcess p) cleanupProcess (go sink p)
where
go sink p (_, Just h, _, pid) = do
() <- sink =<< liftIO (L.hGetContents h)
liftIO $ do
hClose h
forceSuccessProcess p pid
go _ _ _ = error "internal"
2014-05-15 18:44:00 +00:00
remove :: DdarRepo -> Remover
2014-05-15 18:44:00 +00:00
remove ddarrepo key = do
(cmd, params) <- ddarRemoteCall NoConsumeStdin ddarrepo 'd'
[Param $ serializeKey key]
2020-05-14 18:08:09 +00:00
unlessM (liftIO $ boolSystem cmd params) $
giveup "ddar failed to remove"
2014-05-15 18:44:00 +00:00
ddarDirectoryExists :: DdarRepo -> Annex (Either String Bool)
ddarDirectoryExists ddarrepo
| ddarLocal ddarrepo = do
maybeStatus <- liftIO $ tryJust (guard . isDoesNotExistError) $ getFileStatus $ ddarRepoLocation ddarrepo
2014-05-15 18:44:00 +00:00
return $ case maybeStatus of
Left _ -> Right False
Right status -> Right $ isDirectory status
| otherwise = do
let remotecmd = unwords $ map shellEscape
[ "test", "-d", ddarrepo' ]
(sshcmd, sshps) <- sshCommand NoConsumeStdin (host, Nothing)
(ddarRepoConfig ddarrepo) remotecmd
exitCode <- liftIO $ safeSystem sshcmd sshps
2014-05-15 18:44:00 +00:00
case exitCode of
ExitSuccess -> return $ Right True
ExitFailure 1 -> return $ Right False
ExitFailure code -> return $ Left $ "ssh " ++
show (unwords $ toCommand sshps) ++
2014-05-15 18:44:00 +00:00
" failed with status " ++ show code
where
(host, ddarrepo') = splitRemoteDdarRepo ddarrepo
{- Use "ddar t" to determine if a given key is present in a ddar archive -}
inDdarManifest :: DdarRepo -> Key -> Annex (Either String Bool)
inDdarManifest ddarrepo k = do
(cmd, params) <- ddarRemoteCall NoConsumeStdin ddarrepo 't' []
let p = (proc cmd $ toCommand params)
{ std_out = CreatePipe }
liftIO $ catchMsgIO $ withCreateProcess p (go p)
2014-05-15 18:44:00 +00:00
where
k' = serializeKey k
go p _ (Just hout) _ pid = do
contents <- hGetContents hout
let !r = elem k' (lines contents)
forceSuccessProcess p pid
return r
go _ _ _ _ _ = error "internal"
2014-05-15 18:44:00 +00:00
checkKey :: DdarRepo -> CheckPresent
checkKey ddarrepo key = do
2014-05-15 18:44:00 +00:00
directoryExists <- ddarDirectoryExists ddarrepo
case directoryExists of
Left e -> error e
Right True -> either error return
=<< inDdarManifest ddarrepo key
Right False -> return False
2014-05-15 18:44:00 +00:00
ddarLocal :: DdarRepo -> Bool
ddarLocal = notElem ':' . ddarRepoLocation