2012-09-10 19:20:18 +00:00
|
|
|
{- git-annex assistant ssh utilities
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Assistant.Ssh where
|
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
import Common.Annex
|
2012-09-10 19:20:18 +00:00
|
|
|
import Utility.TempFile
|
2012-10-25 22:17:32 +00:00
|
|
|
import Utility.UserInfo
|
2013-02-13 18:30:04 +00:00
|
|
|
import Utility.Shell
|
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
|
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
|
|
|
|
, rsyncOnly :: Bool
|
|
|
|
}
|
|
|
|
deriving (Read, Show, Eq)
|
|
|
|
|
|
|
|
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
|
|
|
|
|
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 ()
|
2012-10-18 04:29:27 +00:00
|
|
|
validateSshPubKey pubkey = either error return $ check $ words pubkey
|
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
|
|
|
|
2012-10-31 06:34:03 +00:00
|
|
|
checkcomment comment
|
2012-12-06 14:39:51 +00:00
|
|
|
| all (\c -> isAlphaNum c || c == '@' || c == '-' || c == '_' || c == '.') comment = ok
|
2012-10-31 06:34:03 +00:00
|
|
|
| otherwise = err "bad comment in ssh public key"
|
2012-09-10 21:53:51 +00:00
|
|
|
|
2012-11-05 16:21:13 +00:00
|
|
|
addAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO Bool
|
|
|
|
addAuthorizedKeys rsynconly dir pubkey = boolSystem "sh"
|
|
|
|
[ Param "-c" , Param $ addAuthorizedKeysCommand rsynconly dir pubkey ]
|
2012-09-11 04:23:34 +00:00
|
|
|
|
2012-11-05 16:21:13 +00:00
|
|
|
removeAuthorizedKeys :: Bool -> FilePath -> SshPubKey -> IO ()
|
|
|
|
removeAuthorizedKeys rsynconly dir pubkey = do
|
|
|
|
let keyline = authorizedKeysLine rsynconly 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
|
|
|
|
addAuthorizedKeysCommand rsynconly dir pubkey = join "&&"
|
2012-09-10 21:53:51 +00:00
|
|
|
[ "mkdir -p ~/.ssh"
|
2012-09-26 22:59:18 +00:00
|
|
|
, join "; "
|
|
|
|
[ "if [ ! -e " ++ wrapper ++ " ]"
|
|
|
|
, "then (" ++ join ";" (map echoval script) ++ ") > " ++ wrapper
|
|
|
|
, "fi"
|
|
|
|
]
|
|
|
|
, "chmod 700 " ++ wrapper
|
2012-09-10 21:53:51 +00:00
|
|
|
, "touch ~/.ssh/authorized_keys"
|
|
|
|
, "chmod 600 ~/.ssh/authorized_keys"
|
|
|
|
, unwords
|
|
|
|
[ "echo"
|
2012-11-05 16:21:13 +00:00
|
|
|
, shellEscape $ authorizedKeysLine rsynconly 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-02-13 18:30:04 +00:00
|
|
|
[ shebang
|
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
|
|
|
|
authorizedKeysLine rsynconly dir pubkey
|
2012-09-10 19:20:18 +00:00
|
|
|
{- TODO: Locking down rsync is difficult, requiring a rather
|
|
|
|
- long perl script. -}
|
2012-09-10 21:53:51 +00:00
|
|
|
| rsynconly = pubkey
|
2012-09-26 22:59:18 +00:00
|
|
|
| otherwise = limitcommand ++ 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
|
|
|
|
genSshKeyPair = withTempDir "git-annex-keygen" $ \dir -> do
|
|
|
|
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.
|
|
|
|
-
|
|
|
|
- Note that the key files are put in ~/.ssh/annex/, rather than directly
|
|
|
|
- in ssh because of an **INSANE** behavior of gnome-keyring: It loads
|
|
|
|
- ~/.ssh/*.pub, and uses them indiscriminately. But using this key
|
|
|
|
- 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.
|
|
|
|
-}
|
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
|
|
|
|
|
|
|
unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $ do
|
|
|
|
h <- fdToHandle =<<
|
|
|
|
createFile (sshdir </> sshprivkeyfile)
|
|
|
|
(unionFileModes ownerWriteMode ownerReadMode)
|
|
|
|
hPutStr h (sshPrivKey sshkeypair)
|
|
|
|
hClose h
|
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
|
|
|
|
[ ("IdentityFile", "~/.ssh/" ++ sshprivkeyfile) ]
|
|
|
|
where
|
2013-04-14 19:34:59 +00:00
|
|
|
sshprivkeyfile = "annex" </> "key." ++ mangleSshHostName sshdata
|
2012-12-06 21:09:08 +00:00
|
|
|
sshpubkeyfile = sshprivkeyfile ++ ".pub"
|
|
|
|
|
|
|
|
{- 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
|
|
|
|
2012-12-06 21:09:08 +00:00
|
|
|
mangleSshHostName :: SshData -> String
|
|
|
|
mangleSshHostName sshdata = "git-annex-" ++ host ++ (maybe "-" ('-':) user)
|
|
|
|
where
|
|
|
|
host = T.unpack $ sshHostName sshdata
|
|
|
|
user = T.unpack <$> sshUserName sshdata
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
|
|
unMangleSshHostName :: String -> String
|
|
|
|
unMangleSshHostName h
|
|
|
|
| "git-annex-" `isPrefixOf` h = join "-" (beginning $ drop 2 dashbits)
|
|
|
|
| otherwise = h
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
dashbits = split "-" 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]
|