split up ssh key generation and setup steps

This commit is contained in:
Joey Hess 2012-09-10 14:42:46 -04:00
parent f61531a26b
commit 34a0e09d4b

View file

@ -14,6 +14,7 @@ import Assistant.WebApp
import Assistant.WebApp.Types import Assistant.WebApp.Types
import Assistant.WebApp.SideBar import Assistant.WebApp.SideBar
import Utility.Yesod import Utility.Yesod
import Utility.TempFile
import Assistant.WebApp.Configurators.Local import Assistant.WebApp.Configurators.Local
import qualified Types.Remote as R import qualified Types.Remote as R
import qualified Remote.Rsync as Rsync import qualified Remote.Rsync as Rsync
@ -44,6 +45,11 @@ data SshServer = SshServer
} }
deriving (Show) deriving (Show)
data SshKeyPair = SshKeyPair
{ sshPubKey :: String
, sshPrivKey :: String
}
{- SshServer is only used for applicative form prompting, this converts {- SshServer is only used for applicative form prompting, this converts
- the result of such a form into a SshData. -} - the result of such a form into a SshData. -}
mkSshData :: SshServer -> SshData mkSshData :: SshServer -> SshData
@ -122,7 +128,7 @@ getAddSshR = sshConfigurator $ do
- a special ssh key will need to be generated just for this server. - a special ssh key will need to be generated just for this server.
- -
- Once logged into the server, probe to see if git-annex-shell is - Once logged into the server, probe to see if git-annex-shell is
- available, or rsync.\ - available, or rsync.
-} -}
testServer :: SshServer -> IO (ServerStatus, Bool) testServer :: SshServer -> IO (ServerStatus, Bool)
testServer (SshServer { hostname = Nothing }) = return testServer (SshServer { hostname = Nothing }) = return
@ -251,12 +257,13 @@ getMakeSshRsyncR = makeSsh True
makeSsh :: Bool -> SshData -> Handler RepHtml makeSsh :: Bool -> SshData -> Handler RepHtml
makeSsh rsync sshdata makeSsh rsync sshdata
| needsPubKey sshdata = do | needsPubKey sshdata = do
(pubkey, sshdata') <- liftIO $ genSshKey sshdata keypair <- liftIO $ genSshKeyPair
makeSsh' rsync sshdata' (Just pubkey) sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
makeSsh' rsync sshdata' (Just keypair)
| otherwise = makeSsh' rsync sshdata Nothing | otherwise = makeSsh' rsync sshdata Nothing
makeSsh' :: Bool -> SshData -> Maybe String -> Handler RepHtml makeSsh' :: Bool -> SshData -> Maybe SshKeyPair -> Handler RepHtml
makeSsh' rsync sshdata pubkey = makeSsh' rsync sshdata keypair =
sshSetup [sshhost, remoteCommand] "" $ sshSetup [sshhost, remoteCommand] "" $
makeSshRepo rsync sshdata makeSshRepo rsync sshdata
where where
@ -267,7 +274,7 @@ makeSsh' rsync sshdata pubkey =
, Just $ "cd " ++ shellEscape remotedir , Just $ "cd " ++ shellEscape remotedir
, if rsync then Nothing else Just $ "git init --bare --shared" , if rsync then Nothing else Just $ "git init --bare --shared"
, if rsync then Nothing else Just $ "git annex init" , if rsync then Nothing else Just $ "git annex init"
, maybe Nothing (makeAuthorizedKeys sshdata) pubkey , maybe Nothing (makeAuthorizedKeys sshdata) keypair
] ]
makeSshRepo :: Bool -> SshData -> Handler RepHtml makeSshRepo :: Bool -> SshData -> Handler RepHtml
@ -307,22 +314,22 @@ makeRsyncRemote name location = makeRemote name location $ const $ do
, ("type", "rsync") , ("type", "rsync")
] ]
makeAuthorizedKeys :: SshData -> String -> Maybe String makeAuthorizedKeys :: SshData -> SshKeyPair -> Maybe String
makeAuthorizedKeys sshdata pubkey makeAuthorizedKeys sshdata keypair
| needsPubKey sshdata = Just $ join "&&" $ | needsPubKey sshdata = Just $ join "&&" $
[ "mkdir -p ~/.ssh" [ "mkdir -p ~/.ssh"
, "touch ~/.ssh/authorized_keys" , "touch ~/.ssh/authorized_keys"
, "chmod 600 ~/.ssh/authorized_keys" , "chmod 600 ~/.ssh/authorized_keys"
, unwords , unwords
[ "echo" [ "echo"
, shellEscape $ authorizedKeysLine sshdata pubkey , shellEscape $ authorizedKeysLine sshdata keypair
, ">>~/.ssh/authorized_keys" , ">>~/.ssh/authorized_keys"
] ]
] ]
| otherwise = Nothing | otherwise = Nothing
authorizedKeysLine :: SshData -> String -> String authorizedKeysLine :: SshData -> SshKeyPair -> String
authorizedKeysLine sshdata pubkey authorizedKeysLine sshdata (SshKeyPair { sshPubKey = pubkey })
{- TODO: Locking down rsync is difficult, requiring a rather {- TODO: Locking down rsync is difficult, requiring a rather
- long perl script. -} - long perl script. -}
| rsyncOnly sshdata = pubkey | rsyncOnly sshdata = pubkey
@ -330,21 +337,38 @@ authorizedKeysLine sshdata pubkey
where where
limitcommand c = "command=\"perl -e 'exec qw(" ++ c ++ "), $ENV{SSH_ORIGINAL_COMMAND}'\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding " limitcommand c = "command=\"perl -e 'exec qw(" ++ c ++ "), $ENV{SSH_ORIGINAL_COMMAND}'\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding "
{- Returns the public key content, and a modified SshData with a {- Generates a ssh key pair. -}
- mangled hostname that will enable use of the key. genSshKeyPair :: IO SshKeyPair
- This way we avoid changing the user's regular ssh experience at all. -} genSshKeyPair = withTempDir "git-annex-keygen" $ \dir -> do
genSshKey :: SshData -> IO (String, SshData) ok <- boolSystem "ssh-keygen"
genSshKey sshdata = do [ 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
- mangled hostname. -}
setupSshKeyPair :: SshKeyPair -> SshData -> IO SshData
setupSshKeyPair sshkeypair sshdata = do
sshdir <- sshDir sshdir <- sshDir
let configfile = sshdir </> "config" let configfile = sshdir </> "config"
createDirectoryIfMissing True sshdir createDirectoryIfMissing True sshdir
unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $ do unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $ do
ok <- boolSystem "ssh-keygen" h <- fdToHandle =<<
[ Param "-P", Param "" -- no password createFile (sshdir </> sshprivkeyfile)
, Param "-f", File $ sshdir </> sshprivkeyfile (unionFileModes ownerWriteMode ownerReadMode)
] hPutStr h (sshPrivKey sshkeypair)
unless ok $ hClose h
error "ssh-keygen failed" unlessM (doesFileExist $ sshdir </> sshpubkeyfile) $ do
writeFile (sshdir </> sshpubkeyfile) (sshPubKey sshkeypair)
unlessM (catchBoolIO $ isInfixOf mangledhost <$> readFile configfile) $ unlessM (catchBoolIO $ isInfixOf mangledhost <$> readFile configfile) $
appendFile configfile $ unlines appendFile configfile $ unlines
[ "" [ ""
@ -353,8 +377,8 @@ genSshKey sshdata = do
, "\tHostname " ++ T.unpack (sshHostName sshdata) , "\tHostname " ++ T.unpack (sshHostName sshdata)
, "\tIdentityFile ~/.ssh/" ++ sshprivkeyfile , "\tIdentityFile ~/.ssh/" ++ sshprivkeyfile
] ]
pubkey <- readFile $ sshdir </> sshpubkeyfile
return (pubkey, sshdata { sshHostName = T.pack mangledhost }) return $ sshdata { sshHostName = T.pack mangledhost }
where where
sshprivkeyfile = "key." ++ mangledhost sshprivkeyfile = "key." ++ mangledhost
sshpubkeyfile = sshprivkeyfile ++ ".pub" sshpubkeyfile = sshprivkeyfile ++ ".pub"
@ -373,7 +397,8 @@ getAddRsyncNetR = do
case result of case result of
FormSuccess sshserver -> do FormSuccess sshserver -> do
knownhost <- liftIO $ knownHost sshserver knownhost <- liftIO $ knownHost sshserver
(pubkey, sshdata) <- liftIO $ genSshKey $ keypair <- liftIO $ genSshKeyPair
sshdata <- liftIO $ setupSshKeyPair keypair
(mkSshData sshserver) (mkSshData sshserver)
{ needsPubKey = True { needsPubKey = True
, rsyncOnly = True , rsyncOnly = True
@ -402,7 +427,7 @@ getAddRsyncNetR = do
let host = fromMaybe "" $ hostname sshserver let host = fromMaybe "" $ hostname sshserver
checkhost host showform $ checkhost host showform $
sshSetup sshopts pubkey $ sshSetup sshopts (sshPubKey keypair) $
makeSshRepo True sshdata makeSshRepo True sshdata
_ -> showform UntestedServer _ -> showform UntestedServer
where where