2012-09-10 19:20:18 +00:00
|
|
|
|
{- git-annex assistant ssh utilities
|
|
|
|
|
-
|
2013-10-01 20:08:01 +00:00
|
|
|
|
- Copyright 2012-2013 Joey Hess <joey@kitenet.net>
|
2012-09-10 19:20:18 +00:00
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
module Assistant.Ssh where
|
|
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
|
import Common.Annex
|
2013-05-12 23:19:28 +00:00
|
|
|
|
import Utility.Tmp
|
2012-10-25 22:17:32 +00:00
|
|
|
|
import Utility.UserInfo
|
2013-02-13 18:30:04 +00:00
|
|
|
|
import Utility.Shell
|
2013-10-01 20:08:01 +00:00
|
|
|
|
import Utility.Rsync
|
2013-11-12 18:54:02 +00:00
|
|
|
|
import Utility.FileMode
|
2012-10-31 19:17:00 +00:00
|
|
|
|
import Git.Remote
|
2012-09-10 19:20:18 +00:00
|
|
|
|
|
|
|
|
|
import Data.Text (Text)
|
|
|
|
|
import qualified Data.Text as T
|
2012-09-10 21:53:51 +00:00
|
|
|
|
import Data.Char
|
2013-06-25 19:23:46 +00:00
|
|
|
|
import Network.URI
|
2012-09-10 19:20:18 +00:00
|
|
|
|
|
|
|
|
|
data SshData = SshData
|
|
|
|
|
{ sshHostName :: Text
|
|
|
|
|
, sshUserName :: Maybe Text
|
|
|
|
|
, sshDirectory :: Text
|
|
|
|
|
, sshRepoName :: String
|
2012-12-06 21:09:08 +00:00
|
|
|
|
, sshPort :: Int
|
2012-09-10 19:20:18 +00:00
|
|
|
|
, needsPubKey :: Bool
|
2013-09-29 18:39:10 +00:00
|
|
|
|
, sshCapabilities :: [SshServerCapability]
|
2012-09-10 19:20:18 +00:00
|
|
|
|
}
|
|
|
|
|
deriving (Read, Show, Eq)
|
|
|
|
|
|
2013-09-29 18:39:10 +00:00
|
|
|
|
data SshServerCapability = GitAnnexShellCapable | GitCapable | RsyncCapable
|
|
|
|
|
deriving (Read, Show, Eq)
|
|
|
|
|
|
|
|
|
|
hasCapability :: SshData -> SshServerCapability -> Bool
|
|
|
|
|
hasCapability d c = c `elem` sshCapabilities d
|
|
|
|
|
|
2013-10-01 17:43:35 +00:00
|
|
|
|
onlyCapability :: SshData -> SshServerCapability -> Bool
|
|
|
|
|
onlyCapability d c = all (== c) (sshCapabilities d)
|
|
|
|
|
|
2012-09-10 19:20:18 +00:00
|
|
|
|
data SshKeyPair = SshKeyPair
|
|
|
|
|
{ sshPubKey :: String
|
|
|
|
|
, sshPrivKey :: String
|
|
|
|
|
}
|
|
|
|
|
|
2012-09-11 19:06:29 +00:00
|
|
|
|
instance Show SshKeyPair where
|
|
|
|
|
show = sshPubKey
|
|
|
|
|
|
2012-09-10 21:53:51 +00:00
|
|
|
|
type SshPubKey = String
|
|
|
|
|
|
2012-09-10 19:20:18 +00:00
|
|
|
|
{- ssh -ofoo=bar command-line option -}
|
|
|
|
|
sshOpt :: String -> String -> String
|
|
|
|
|
sshOpt k v = concat ["-o", k, "=", v]
|
|
|
|
|
|
|
|
|
|
sshDir :: IO FilePath
|
|
|
|
|
sshDir = do
|
|
|
|
|
home <- myHomeDir
|
|
|
|
|
return $ home </> ".ssh"
|
|
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
|
{- user@host or host -}
|
|
|
|
|
genSshHost :: Text -> Maybe Text -> String
|
|
|
|
|
genSshHost host user = maybe "" (\v -> T.unpack v ++ "@") user ++ T.unpack host
|
|
|
|
|
|
2013-10-01 20:08:01 +00:00
|
|
|
|
{- Generates a ssh or rsync url from a SshData. -}
|
|
|
|
|
genSshUrl :: SshData -> String
|
|
|
|
|
genSshUrl sshdata = addtrailingslash $ T.unpack $ T.concat $
|
|
|
|
|
if (onlyCapability sshdata RsyncCapable)
|
|
|
|
|
then [u, h, T.pack ":", sshDirectory sshdata]
|
|
|
|
|
else [T.pack "ssh://", u, h, d]
|
|
|
|
|
where
|
|
|
|
|
u = maybe (T.pack "") (\v -> T.concat [v, T.pack "@"]) $ sshUserName sshdata
|
|
|
|
|
h = sshHostName sshdata
|
|
|
|
|
d
|
|
|
|
|
| T.pack "/" `T.isPrefixOf` sshDirectory sshdata = sshDirectory sshdata
|
|
|
|
|
| T.pack "~/" `T.isPrefixOf` sshDirectory sshdata = T.concat [T.pack "/", sshDirectory sshdata]
|
|
|
|
|
| otherwise = T.concat [T.pack "/~/", sshDirectory sshdata]
|
|
|
|
|
addtrailingslash s
|
|
|
|
|
| "/" `isSuffixOf` s = s
|
|
|
|
|
| otherwise = s ++ "/"
|
|
|
|
|
|
|
|
|
|
{- Reverses genSshUrl -}
|
|
|
|
|
parseSshUrl :: String -> Maybe SshData
|
|
|
|
|
parseSshUrl u
|
|
|
|
|
| "ssh://" `isPrefixOf` u = fromssh (drop (length "ssh://") u)
|
|
|
|
|
| otherwise = fromrsync u
|
|
|
|
|
where
|
|
|
|
|
mkdata (userhost, dir) = Just $ SshData
|
|
|
|
|
{ sshHostName = T.pack host
|
|
|
|
|
, sshUserName = if null user then Nothing else Just $ T.pack user
|
|
|
|
|
, sshDirectory = T.pack dir
|
|
|
|
|
, sshRepoName = genSshRepoName host dir
|
|
|
|
|
-- dummy values, cannot determine from url
|
|
|
|
|
, sshPort = 22
|
|
|
|
|
, needsPubKey = True
|
|
|
|
|
, sshCapabilities = []
|
|
|
|
|
}
|
|
|
|
|
where
|
|
|
|
|
(user, host) = if '@' `elem` userhost
|
|
|
|
|
then separate (== '@') userhost
|
|
|
|
|
else ("", userhost)
|
|
|
|
|
fromrsync s
|
|
|
|
|
| not (rsyncUrlIsShell u) = Nothing
|
|
|
|
|
| otherwise = mkdata $ separate (== ':') s
|
|
|
|
|
fromssh = mkdata . break (== '/')
|
|
|
|
|
|
2012-10-31 19:17:00 +00:00
|
|
|
|
{- Generates a git remote name, like host_dir or host -}
|
2012-09-10 21:53:51 +00:00
|
|
|
|
genSshRepoName :: String -> FilePath -> String
|
|
|
|
|
genSshRepoName host dir
|
2012-10-31 19:17:00 +00:00
|
|
|
|
| null dir = makeLegalName host
|
|
|
|
|
| otherwise = makeLegalName $ host ++ "_" ++ dir
|
2012-09-10 21:53:51 +00:00
|
|
|
|
|
2012-09-10 19:20:18 +00:00
|
|
|
|
{- The output of ssh, including both stdout and stderr. -}
|
2013-02-26 17:04:37 +00:00
|
|
|
|
sshTranscript :: [String] -> (Maybe String) -> IO (String, Bool)
|
|
|
|
|
sshTranscript opts input = processTranscript "ssh" opts input
|
2012-09-10 19:20:18 +00:00
|
|
|
|
|
2012-09-10 22:18:55 +00:00
|
|
|
|
{- Ensure that the ssh public key doesn't include any ssh options, like
|
|
|
|
|
- command=foo, or other weirdness -}
|
|
|
|
|
validateSshPubKey :: SshPubKey -> IO ()
|
2013-06-12 03:12:01 +00:00
|
|
|
|
validateSshPubKey pubkey
|
|
|
|
|
| length (lines pubkey) == 1 =
|
|
|
|
|
either error return $ check $ words pubkey
|
|
|
|
|
| otherwise = error "too many lines in ssh public key"
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
|
|
|
|
check [prefix, _key, comment] = do
|
|
|
|
|
checkprefix prefix
|
|
|
|
|
checkcomment comment
|
|
|
|
|
check [prefix, _key] =
|
|
|
|
|
checkprefix prefix
|
|
|
|
|
check _ = err "wrong number of words in ssh public key"
|
2012-10-18 04:29:27 +00:00
|
|
|
|
|
2012-10-31 06:34:03 +00:00
|
|
|
|
ok = Right ()
|
|
|
|
|
err msg = Left $ unwords [msg, pubkey]
|
2012-10-18 04:29:27 +00:00
|
|
|
|
|
2012-10-31 06:34:03 +00:00
|
|
|
|
checkprefix prefix
|
|
|
|
|
| ssh == "ssh" && all isAlphaNum keytype = ok
|
|
|
|
|
| otherwise = err "bad ssh public key prefix"
|
|
|
|
|
where
|
|
|
|
|
(ssh, keytype) = separate (== '-') prefix
|
2012-10-18 04:29:27 +00:00
|
|
|
|
|
2013-06-11 03:54:28 +00:00
|
|
|
|
checkcomment comment = case filter (not . safeincomment) comment of
|
|
|
|
|
[] -> ok
|
|
|
|
|
badstuff -> err $ "bad comment in ssh public key (contains: \"" ++ badstuff ++ "\")"
|
|
|
|
|
safeincomment c = isAlphaNum c || c == '@' || c == '-' || c == '_' || c == '.'
|
2012-09-10 21:53:51 +00:00
|
|
|
|
|
2012-11-05 16:21:13 +00:00
|
|
|
|
addAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO Bool
|
2013-10-01 17:43:35 +00:00
|
|
|
|
addAuthorizedKeys gitannexshellonly dir pubkey = boolSystem "sh"
|
|
|
|
|
[ Param "-c" , Param $ addAuthorizedKeysCommand gitannexshellonly dir pubkey ]
|
2012-09-11 04:23:34 +00:00
|
|
|
|
|
2012-11-05 16:21:13 +00:00
|
|
|
|
removeAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO ()
|
2013-10-01 17:43:35 +00:00
|
|
|
|
removeAuthorizedKeys gitannexshellonly dir pubkey = do
|
|
|
|
|
let keyline = authorizedKeysLine gitannexshellonly dir pubkey
|
2012-09-11 04:23:34 +00:00
|
|
|
|
sshdir <- sshDir
|
2013-01-03 20:11:19 +00:00
|
|
|
|
let keyfile = sshdir </> "authorized_keys"
|
2012-09-11 04:23:34 +00:00
|
|
|
|
ls <- lines <$> readFileStrict keyfile
|
2012-09-13 04:57:52 +00:00
|
|
|
|
writeFile keyfile $ unlines $ filter (/= keyline) ls
|
2012-09-10 21:53:51 +00:00
|
|
|
|
|
2012-09-10 19:20:18 +00:00
|
|
|
|
{- Implemented as a shell command, so it can be run on remote servers over
|
2012-09-26 22:59:18 +00:00
|
|
|
|
- ssh.
|
|
|
|
|
-
|
|
|
|
|
- The ~/.ssh/git-annex-shell wrapper script is created if not already
|
|
|
|
|
- present.
|
|
|
|
|
-}
|
2012-11-05 16:21:13 +00:00
|
|
|
|
addAuthorizedKeysCommand :: Bool -> FilePath -> SshPubKey -> String
|
2013-10-01 17:43:35 +00:00
|
|
|
|
addAuthorizedKeysCommand gitannexshellonly dir pubkey = intercalate "&&"
|
2012-09-10 21:53:51 +00:00
|
|
|
|
[ "mkdir -p ~/.ssh"
|
2013-04-23 00:24:53 +00:00
|
|
|
|
, intercalate "; "
|
2012-09-26 22:59:18 +00:00
|
|
|
|
[ "if [ ! -e " ++ wrapper ++ " ]"
|
2013-04-23 00:24:53 +00:00
|
|
|
|
, "then (" ++ intercalate ";" (map echoval script) ++ ") > " ++ wrapper
|
2012-09-26 22:59:18 +00:00
|
|
|
|
, "fi"
|
|
|
|
|
]
|
|
|
|
|
, "chmod 700 " ++ wrapper
|
2012-09-10 21:53:51 +00:00
|
|
|
|
, "touch ~/.ssh/authorized_keys"
|
|
|
|
|
, "chmod 600 ~/.ssh/authorized_keys"
|
|
|
|
|
, unwords
|
|
|
|
|
[ "echo"
|
2013-10-01 17:43:35 +00:00
|
|
|
|
, shellEscape $ authorizedKeysLine gitannexshellonly dir pubkey
|
2012-09-10 21:53:51 +00:00
|
|
|
|
, ">>~/.ssh/authorized_keys"
|
2012-09-10 19:20:18 +00:00
|
|
|
|
]
|
2012-09-10 21:53:51 +00:00
|
|
|
|
]
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
|
|
|
|
echoval v = "echo " ++ shellEscape v
|
|
|
|
|
wrapper = "~/.ssh/git-annex-shell"
|
|
|
|
|
script =
|
2013-05-06 19:58:13 +00:00
|
|
|
|
[ shebang_portable
|
2012-10-31 06:34:03 +00:00
|
|
|
|
, "set -e"
|
2013-03-12 11:12:39 +00:00
|
|
|
|
, "if [ \"x$SSH_ORIGINAL_COMMAND\" != \"x\" ]; then"
|
|
|
|
|
, runshell "$SSH_ORIGINAL_COMMAND"
|
|
|
|
|
, "else"
|
|
|
|
|
, runshell "$@"
|
|
|
|
|
, "fi"
|
2012-10-31 06:34:03 +00:00
|
|
|
|
]
|
2013-03-12 11:12:39 +00:00
|
|
|
|
runshell var = "exec git-annex-shell -c \"" ++ var ++ "\""
|
2012-09-10 21:53:51 +00:00
|
|
|
|
|
2012-11-05 16:21:13 +00:00
|
|
|
|
authorizedKeysLine :: Bool -> FilePath -> SshPubKey -> String
|
2013-10-01 17:43:35 +00:00
|
|
|
|
authorizedKeysLine gitannexshellonly dir pubkey
|
|
|
|
|
| gitannexshellonly = limitcommand ++ pubkey
|
2012-09-10 19:20:18 +00:00
|
|
|
|
{- TODO: Locking down rsync is difficult, requiring a rather
|
|
|
|
|
- long perl script. -}
|
2013-10-01 17:43:35 +00:00
|
|
|
|
| otherwise = pubkey
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2012-11-05 16:21:13 +00:00
|
|
|
|
limitcommand = "command=\"GIT_ANNEX_SHELL_DIRECTORY="++shellEscape dir++" ~/.ssh/git-annex-shell\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding "
|
2012-09-10 19:20:18 +00:00
|
|
|
|
|
|
|
|
|
{- Generates a ssh key pair. -}
|
|
|
|
|
genSshKeyPair :: IO SshKeyPair
|
2013-05-12 23:19:28 +00:00
|
|
|
|
genSshKeyPair = withTmpDir "git-annex-keygen" $ \dir -> do
|
2012-09-10 19:20:18 +00:00
|
|
|
|
ok <- boolSystem "ssh-keygen"
|
|
|
|
|
[ Param "-P", Param "" -- no password
|
|
|
|
|
, Param "-f", File $ dir </> "key"
|
|
|
|
|
]
|
|
|
|
|
unless ok $
|
|
|
|
|
error "ssh-keygen failed"
|
|
|
|
|
SshKeyPair
|
|
|
|
|
<$> readFile (dir </> "key.pub")
|
|
|
|
|
<*> readFile (dir </> "key")
|
|
|
|
|
|
|
|
|
|
{- Installs a ssh key pair, and sets up ssh config with a mangled hostname
|
|
|
|
|
- that will enable use of the key. This way we avoid changing the user's
|
|
|
|
|
- regular ssh experience at all. Returns a modified SshData containing the
|
2013-04-14 19:34:59 +00:00
|
|
|
|
- mangled hostname.
|
|
|
|
|
-
|
2013-04-15 00:00:32 +00:00
|
|
|
|
- Note that the key files are put in ~/.ssh/git-annex/, rather than directly
|
2013-04-14 19:34:59 +00:00
|
|
|
|
- in ssh because of an **INSANE** behavior of gnome-keyring: It loads
|
2013-07-27 17:00:49 +00:00
|
|
|
|
- ~/.ssh/ANYTHING.pub, and uses them indiscriminately. But using this key
|
2013-04-14 19:34:59 +00:00
|
|
|
|
- for a normal login to the server will force git-annex-shell to run,
|
|
|
|
|
- and locks the user out. Luckily, it does not recurse into subdirectories.
|
2013-07-31 17:30:49 +00:00
|
|
|
|
-
|
|
|
|
|
- Similarly, IdentitiesOnly is set in the ssh config to prevent the
|
|
|
|
|
- ssh-agent from forcing use of a different key.
|
2013-04-14 19:34:59 +00:00
|
|
|
|
-}
|
2012-09-10 19:20:18 +00:00
|
|
|
|
setupSshKeyPair :: SshKeyPair -> SshData -> IO SshData
|
|
|
|
|
setupSshKeyPair sshkeypair sshdata = do
|
|
|
|
|
sshdir <- sshDir
|
2013-04-14 19:34:59 +00:00
|
|
|
|
createDirectoryIfMissing True $ parentDir $ sshdir </> sshprivkeyfile
|
2012-09-10 19:20:18 +00:00
|
|
|
|
|
2013-11-12 18:54:02 +00:00
|
|
|
|
unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $
|
|
|
|
|
writeFileProtected (sshdir </> sshprivkeyfile) (sshPrivKey sshkeypair)
|
2012-09-13 04:57:52 +00:00
|
|
|
|
unlessM (doesFileExist $ sshdir </> sshpubkeyfile) $
|
2012-09-10 19:20:18 +00:00
|
|
|
|
writeFile (sshdir </> sshpubkeyfile) (sshPubKey sshkeypair)
|
|
|
|
|
|
2012-12-06 21:09:08 +00:00
|
|
|
|
setSshConfig sshdata
|
2013-07-31 17:30:49 +00:00
|
|
|
|
[ ("IdentityFile", "~/.ssh/" ++ sshprivkeyfile)
|
|
|
|
|
, ("IdentitiesOnly", "yes")
|
|
|
|
|
]
|
2012-12-06 21:09:08 +00:00
|
|
|
|
where
|
2013-04-15 00:00:32 +00:00
|
|
|
|
sshprivkeyfile = "git-annex" </> "key." ++ mangleSshHostName sshdata
|
2012-12-06 21:09:08 +00:00
|
|
|
|
sshpubkeyfile = sshprivkeyfile ++ ".pub"
|
|
|
|
|
|
webapp: Improve handling of remotes whose setup has stalled.
This includes recovery from the ssh-agent problem that led to many reporting
http://git-annex.branchable.com/bugs/Internal_Server_Error:_Unknown_UUID/
(Including fixing up .ssh/config to set IdentitiesOnly.)
Remotes that have no known uuid are now displayed in the webapp as
"unfinished". There's a link to check their status, and if the remote
has been set annex-ignore, a retry button can be used to unset that and
try again to set up the remote.
As this bug has shown, the process of adding a ssh remote has some failure
modes that are not really ideal. It would certianly be better if, when
setting up a ssh remote it would detect if it's failed to get the UUID,
and handle that in the remote setup process, rather than waiting until
later and handling it this way.
However, that's hard to do, particularly for local pairing, since the
PairListener runs as a background thread. The best it could do is pop up an
alert if there's a problem. This solution is not much different.
Also, this solution handles cases where the user has gotten their repo into
a mess manually and let's the assistant help with cleaning it up.
This commit was sponsored by Chia Shee Liang. Thanks!
2013-07-31 20:01:20 +00:00
|
|
|
|
{- Fixes git-annex ssh key pairs configured in .ssh/config
|
|
|
|
|
- by old versions to set IdentitiesOnly. -}
|
|
|
|
|
fixSshKeyPair :: IO ()
|
|
|
|
|
fixSshKeyPair = do
|
|
|
|
|
sshdir <- sshDir
|
|
|
|
|
let configfile = sshdir </> "config"
|
|
|
|
|
whenM (doesFileExist configfile) $ do
|
|
|
|
|
ls <- lines <$> readFileStrict configfile
|
|
|
|
|
let ls' = fixSshKeyPair' ls
|
|
|
|
|
when (ls /= ls') $
|
|
|
|
|
viaTmp writeFile configfile $ unlines ls'
|
|
|
|
|
|
|
|
|
|
{- Strategy: Search for IdentityFile lines in for files with key.git-annex
|
|
|
|
|
- in their names. These are for git-annex ssh key pairs.
|
|
|
|
|
- Add the IdentitiesOnly line immediately after them, if not already
|
|
|
|
|
- present. -}
|
|
|
|
|
fixSshKeyPair' :: [String] -> [String]
|
|
|
|
|
fixSshKeyPair' = go []
|
|
|
|
|
where
|
|
|
|
|
go c [] = reverse c
|
|
|
|
|
go c (l:[])
|
|
|
|
|
| all (`isInfixOf` l) indicators = go (fixedline l:l:c) []
|
|
|
|
|
| otherwise = go (l:c) []
|
|
|
|
|
go c (l:next:rest)
|
|
|
|
|
| all (`isInfixOf` l) indicators && not ("IdentitiesOnly" `isInfixOf` next) =
|
|
|
|
|
go (fixedline l:l:c) (next:rest)
|
|
|
|
|
| otherwise = go (l:c) (next:rest)
|
|
|
|
|
indicators = ["IdentityFile", "key.git-annex"]
|
|
|
|
|
fixedline tmpl = takeWhile isSpace tmpl ++ "IdentitiesOnly yes"
|
|
|
|
|
|
2012-12-06 21:09:08 +00:00
|
|
|
|
{- Setups up a ssh config with a mangled hostname.
|
|
|
|
|
- Returns a modified SshData containing the mangled hostname. -}
|
|
|
|
|
setSshConfig :: SshData -> [(String, String)] -> IO SshData
|
|
|
|
|
setSshConfig sshdata config = do
|
|
|
|
|
sshdir <- sshDir
|
|
|
|
|
createDirectoryIfMissing True sshdir
|
|
|
|
|
let configfile = sshdir </> "config"
|
2012-09-10 19:20:18 +00:00
|
|
|
|
unlessM (catchBoolIO $ isInfixOf mangledhost <$> readFile configfile) $
|
2012-12-06 21:09:08 +00:00
|
|
|
|
appendFile configfile $ unlines $
|
2012-09-10 19:20:18 +00:00
|
|
|
|
[ ""
|
|
|
|
|
, "# Added automatically by git-annex"
|
|
|
|
|
, "Host " ++ mangledhost
|
2012-12-06 21:09:08 +00:00
|
|
|
|
] ++ map (\(k, v) -> "\t" ++ k ++ " " ++ v)
|
|
|
|
|
(settings ++ config)
|
2012-09-10 19:20:18 +00:00
|
|
|
|
return $ sshdata { sshHostName = T.pack mangledhost }
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2012-12-06 21:09:08 +00:00
|
|
|
|
mangledhost = mangleSshHostName sshdata
|
|
|
|
|
settings =
|
|
|
|
|
[ ("Hostname", T.unpack $ sshHostName sshdata)
|
|
|
|
|
, ("Port", show $ sshPort sshdata)
|
|
|
|
|
]
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
2013-04-16 17:49:39 +00:00
|
|
|
|
{- This hostname is specific to a given repository on the ssh host,
|
|
|
|
|
- so it is based on the real hostname, the username, and the directory.
|
2013-06-25 19:23:46 +00:00
|
|
|
|
-
|
|
|
|
|
- The mangled hostname has the form "git-annex-realhostname-username_dir".
|
|
|
|
|
- The only use of "-" is to separate the parts shown; this is necessary
|
|
|
|
|
- to allow unMangleSshHostName to work. Any unusual characters in the
|
|
|
|
|
- username or directory are url encoded, except using "." rather than "%"
|
|
|
|
|
- (the latter has special meaning to ssh).
|
2013-04-16 17:49:39 +00:00
|
|
|
|
-}
|
2012-12-06 21:09:08 +00:00
|
|
|
|
mangleSshHostName :: SshData -> String
|
2013-04-16 17:49:39 +00:00
|
|
|
|
mangleSshHostName sshdata = "git-annex-" ++ T.unpack (sshHostName sshdata)
|
2013-06-25 19:23:46 +00:00
|
|
|
|
++ "-" ++ escape extra
|
2012-12-06 21:09:08 +00:00
|
|
|
|
where
|
2013-04-23 00:24:53 +00:00
|
|
|
|
extra = intercalate "_" $ map T.unpack $ catMaybes
|
2013-04-16 17:49:39 +00:00
|
|
|
|
[ sshUserName sshdata
|
|
|
|
|
, Just $ sshDirectory sshdata
|
|
|
|
|
]
|
|
|
|
|
safe c
|
|
|
|
|
| isAlphaNum c = True
|
|
|
|
|
| c == '_' = True
|
|
|
|
|
| otherwise = False
|
2013-06-25 19:23:46 +00:00
|
|
|
|
escape s = replace "%" "." $ escapeURIString safe s
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
2013-04-16 17:49:39 +00:00
|
|
|
|
{- Extracts the real hostname from a mangled ssh hostname. -}
|
2012-09-13 20:47:44 +00:00
|
|
|
|
unMangleSshHostName :: String -> String
|
2013-04-16 17:49:39 +00:00
|
|
|
|
unMangleSshHostName h = case split "-" h of
|
2013-04-23 00:24:53 +00:00
|
|
|
|
("git":"annex":rest) -> intercalate "-" (beginning rest)
|
2013-04-16 17:49:39 +00:00
|
|
|
|
_ -> h
|
2012-09-11 01:55:59 +00:00
|
|
|
|
|
|
|
|
|
{- Does ssh have known_hosts data for a hostname? -}
|
|
|
|
|
knownHost :: Text -> IO Bool
|
|
|
|
|
knownHost hostname = do
|
|
|
|
|
sshdir <- sshDir
|
|
|
|
|
ifM (doesFileExist $ sshdir </> "known_hosts")
|
2012-09-27 15:27:16 +00:00
|
|
|
|
( not . null <$> checkhost
|
2012-09-11 01:55:59 +00:00
|
|
|
|
, return False
|
|
|
|
|
)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
|
|
|
|
{- ssh-keygen -F can crash on some old known_hosts file -}
|
|
|
|
|
checkhost = catchDefaultIO "" $
|
|
|
|
|
readProcess "ssh-keygen" ["-F", T.unpack hostname]
|