git-annex/Annex/Ssh.hs

66 lines
2 KiB
Haskell
Raw Normal View History

2011-07-06 00:36:43 +00:00
{- git-annex remote access with ssh
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2011-10-16 04:04:26 +00:00
module Annex.Ssh where
2011-12-20 18:37:53 +00:00
import Common
import qualified Git
2011-12-14 19:30:14 +00:00
import qualified Git.Url
import Types
import Config
import Annex.UUID
{- Generates parameters to ssh to a repository's host and run a command.
- Caller is responsible for doing any neccessary shellEscaping of the
- passed command. -}
sshToRepo :: Git.Repo -> [CommandParam] -> Annex [CommandParam]
sshToRepo repo sshcmd = do
s <- getConfig repo "ssh-options" ""
let sshoptions = map Param (words s)
2011-12-14 19:30:14 +00:00
let sshport = case Git.Url.port repo of
Nothing -> []
Just p -> [Param "-p", Param (show p)]
2011-12-14 19:30:14 +00:00
let sshhost = Param $ Git.Url.hostuser repo
return $ sshoptions ++ sshport ++ [sshhost] ++ sshcmd
2011-04-09 18:26:32 +00:00
{- Generates parameters to run a git-annex-shell command on a remote
- repository. -}
git_annex_shell :: Git.Repo -> String -> [CommandParam] -> Annex (Maybe (FilePath, [CommandParam]))
git_annex_shell r command params
| not $ Git.repoIsUrl r = return $ Just (shellcmd, shellopts)
| Git.repoIsSsh r = do
2011-10-11 18:43:45 +00:00
uuid <- getRepoUUID r
sshparams <- sshToRepo r [Param $ sshcmd uuid ]
2011-04-09 18:26:32 +00:00
return $ Just ("ssh", sshparams)
| otherwise = return Nothing
where
dir = Git.workTree r
shellcmd = "git-annex-shell"
2011-07-15 16:47:14 +00:00
shellopts = Param command : File dir : params
sshcmd uuid = unwords $
2011-12-09 05:57:13 +00:00
shellcmd : map shellEscape (toCommand shellopts) ++
uuidcheck uuid
uuidcheck NoUUID = []
uuidcheck (UUID u) = ["--uuid", u]
2011-04-09 18:26:32 +00:00
{- Uses a supplied function (such as boolSystem) to run a git-annex-shell
- command on a remote.
-
- Or, if the remote does not support running remote commands, returns
- a specified error value. -}
onRemote
:: Git.Repo
-> (FilePath -> [CommandParam] -> IO a, a)
-> String
-> [CommandParam]
-> Annex a
onRemote r (with, errorval) command params = do
s <- git_annex_shell r command params
case s of
Just (c, ps) -> liftIO $ with c ps
Nothing -> return errorval