2012-08-31 19:17:12 +00:00
|
|
|
{- git-annex assistant webapp configurator for ssh-based remotes
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
|
|
|
|
|
|
|
module Assistant.WebApp.Configurators.Ssh where
|
|
|
|
|
|
|
|
import Assistant.Common
|
2012-09-10 19:20:18 +00:00
|
|
|
import Assistant.Ssh
|
2012-08-31 19:17:12 +00:00
|
|
|
import Assistant.WebApp
|
2012-09-02 04:27:48 +00:00
|
|
|
import Assistant.WebApp.Types
|
2012-08-31 19:17:12 +00:00
|
|
|
import Assistant.WebApp.SideBar
|
|
|
|
import Utility.Yesod
|
2012-09-02 19:21:40 +00:00
|
|
|
import Assistant.WebApp.Configurators.Local
|
2012-09-02 21:32:24 +00:00
|
|
|
import qualified Types.Remote as R
|
|
|
|
import qualified Remote.Rsync as Rsync
|
|
|
|
import qualified Command.InitRemote
|
|
|
|
import Logs.UUID
|
|
|
|
import Logs.Remote
|
2012-08-31 19:17:12 +00:00
|
|
|
|
|
|
|
import Yesod
|
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
2012-09-02 21:32:24 +00:00
|
|
|
import qualified Data.Map as M
|
2012-08-31 22:59:57 +00:00
|
|
|
import Network.BSD
|
|
|
|
import System.Posix.User
|
2012-08-31 19:17:12 +00:00
|
|
|
|
2012-09-02 19:21:40 +00:00
|
|
|
sshConfigurator :: Widget -> Handler RepHtml
|
|
|
|
sshConfigurator a = bootstrap (Just Config) $ do
|
|
|
|
sideBarDisplay
|
|
|
|
setTitle "Add a remote server"
|
|
|
|
a
|
|
|
|
|
2012-08-31 22:59:57 +00:00
|
|
|
data SshServer = SshServer
|
|
|
|
{ hostname :: Maybe Text
|
|
|
|
, username :: Maybe Text
|
|
|
|
, directory :: Maybe Text
|
|
|
|
}
|
2012-09-02 04:27:48 +00:00
|
|
|
deriving (Show)
|
2012-09-02 01:10:40 +00:00
|
|
|
|
2012-09-04 19:27:06 +00:00
|
|
|
{- SshServer is only used for applicative form prompting, this converts
|
|
|
|
- the result of such a form into a SshData. -}
|
|
|
|
mkSshData :: SshServer -> SshData
|
|
|
|
mkSshData sshserver = SshData
|
|
|
|
{ sshHostName = fromMaybe "" $ hostname sshserver
|
|
|
|
, sshUserName = username sshserver
|
|
|
|
, sshDirectory = fromMaybe "" $ directory sshserver
|
2012-09-10 21:53:51 +00:00
|
|
|
, sshRepoName = genSshRepoName
|
|
|
|
(T.unpack $ fromJust $ hostname sshserver)
|
|
|
|
(maybe "" T.unpack $ directory sshserver)
|
2012-09-04 19:27:06 +00:00
|
|
|
, needsPubKey = False
|
|
|
|
, rsyncOnly = False
|
|
|
|
}
|
|
|
|
|
2012-09-03 04:39:55 +00:00
|
|
|
sshServerAForm :: (Maybe Text) -> AForm WebApp WebApp SshServer
|
2012-08-31 22:59:57 +00:00
|
|
|
sshServerAForm localusername = SshServer
|
|
|
|
<$> aopt check_hostname "Host name" Nothing
|
2012-09-03 04:39:55 +00:00
|
|
|
<*> aopt check_username "User name" (Just localusername)
|
2012-08-31 22:59:57 +00:00
|
|
|
<*> aopt textField "Directory" (Just $ Just $ T.pack gitAnnexAssistantDefaultDir)
|
|
|
|
where
|
|
|
|
check_hostname = checkM (liftIO . checkdns) textField
|
|
|
|
checkdns t = do
|
|
|
|
let h = T.unpack t
|
|
|
|
r <- catchMaybeIO $ getHostByName h
|
|
|
|
return $ case r of
|
|
|
|
-- canonicalize input hostname if it had no dot
|
|
|
|
Just hostentry
|
|
|
|
| '.' `elem` h -> Right t
|
|
|
|
| otherwise -> Right $ T.pack $ hostName hostentry
|
|
|
|
Nothing -> Left bad_hostname
|
|
|
|
|
|
|
|
check_username = checkBool (all (`notElem` "/:@ \t") . T.unpack)
|
|
|
|
bad_username textField
|
|
|
|
|
|
|
|
bad_hostname = "cannot resolve host name" :: Text
|
|
|
|
bad_username = "bad user name" :: Text
|
|
|
|
|
|
|
|
data ServerStatus
|
|
|
|
= UntestedServer
|
|
|
|
| UnusableServer Text -- reason why it's not usable
|
|
|
|
| UsableRsyncServer
|
|
|
|
| UsableSshServer
|
2012-09-02 04:27:48 +00:00
|
|
|
deriving (Eq)
|
2012-08-31 22:59:57 +00:00
|
|
|
|
2012-09-02 00:37:35 +00:00
|
|
|
usable :: ServerStatus -> Bool
|
|
|
|
usable UntestedServer = False
|
|
|
|
usable (UnusableServer _) = False
|
|
|
|
usable UsableRsyncServer = True
|
|
|
|
usable UsableSshServer = True
|
2012-08-31 22:59:57 +00:00
|
|
|
|
|
|
|
getAddSshR :: Handler RepHtml
|
2012-09-02 19:21:40 +00:00
|
|
|
getAddSshR = sshConfigurator $ do
|
2012-08-31 22:59:57 +00:00
|
|
|
u <- liftIO $ T.pack . userName
|
|
|
|
<$> (getUserEntryForID =<< getEffectiveUserID)
|
|
|
|
((result, form), enctype) <- lift $
|
2012-09-03 04:39:55 +00:00
|
|
|
runFormGet $ renderBootstrap $ sshServerAForm (Just u)
|
2012-08-31 22:59:57 +00:00
|
|
|
case result of
|
|
|
|
FormSuccess sshserver -> do
|
2012-09-03 00:43:32 +00:00
|
|
|
(status, needspubkey) <- liftIO $ testServer sshserver
|
2012-09-02 00:37:35 +00:00
|
|
|
if usable status
|
2012-09-02 04:27:48 +00:00
|
|
|
then lift $ redirect $ ConfirmSshR $
|
2012-09-04 19:27:06 +00:00
|
|
|
(mkSshData sshserver)
|
|
|
|
{ needsPubKey = needspubkey
|
2012-09-02 04:27:48 +00:00
|
|
|
, rsyncOnly = (status == UsableRsyncServer)
|
|
|
|
}
|
2012-09-02 00:37:35 +00:00
|
|
|
else showform form enctype status
|
2012-08-31 22:59:57 +00:00
|
|
|
_ -> showform form enctype UntestedServer
|
|
|
|
where
|
|
|
|
showform form enctype status = do
|
|
|
|
let authtoken = webAppFormAuthToken
|
2012-09-09 03:32:08 +00:00
|
|
|
$(widgetFile "configurators/ssh/add")
|
2012-08-31 22:59:57 +00:00
|
|
|
|
2012-09-02 00:37:35 +00:00
|
|
|
{- Test if we can ssh into the server.
|
|
|
|
-
|
|
|
|
- Two probe attempts are made. First, try sshing in using the existing
|
2012-09-02 01:10:40 +00:00
|
|
|
- configuration, but don't let ssh prompt for any password. If
|
2012-09-02 00:37:35 +00:00
|
|
|
- passwordless login is already enabled, use it. Otherwise,
|
2012-09-03 00:43:32 +00:00
|
|
|
- a special ssh key will need to be generated just for this server.
|
2012-09-02 00:37:35 +00:00
|
|
|
-
|
2012-09-02 01:10:40 +00:00
|
|
|
- Once logged into the server, probe to see if git-annex-shell is
|
2012-09-10 18:42:46 +00:00
|
|
|
- available, or rsync.
|
2012-09-02 00:37:35 +00:00
|
|
|
-}
|
2012-09-03 00:43:32 +00:00
|
|
|
testServer :: SshServer -> IO (ServerStatus, Bool)
|
|
|
|
testServer (SshServer { hostname = Nothing }) = return
|
|
|
|
(UnusableServer "Please enter a host name.", False)
|
2012-09-02 00:37:35 +00:00
|
|
|
testServer sshserver = do
|
2012-09-04 19:27:06 +00:00
|
|
|
status <- probe [sshOpt "NumberOfPasswordPrompts" "0"]
|
2012-09-02 00:37:35 +00:00
|
|
|
if usable status
|
2012-09-03 00:43:32 +00:00
|
|
|
then return (status, False)
|
2012-09-02 00:37:35 +00:00
|
|
|
else do
|
2012-09-04 19:27:06 +00:00
|
|
|
status' <- probe []
|
2012-09-03 00:43:32 +00:00
|
|
|
return (status', True)
|
2012-09-02 00:37:35 +00:00
|
|
|
where
|
2012-09-04 19:27:06 +00:00
|
|
|
probe extraopts = do
|
2012-09-02 01:10:40 +00:00
|
|
|
let remotecommand = join ";" $
|
2012-09-02 00:37:35 +00:00
|
|
|
[ report "loggedin"
|
|
|
|
, checkcommand "git-annex-shell"
|
|
|
|
, checkcommand "rsync"
|
|
|
|
]
|
2012-09-04 19:27:06 +00:00
|
|
|
knownhost <- knownHost sshserver
|
|
|
|
let sshopts = filter (not . null) $ extraopts ++
|
2012-09-02 00:37:35 +00:00
|
|
|
{- If this is an already known host, let
|
|
|
|
- ssh check it as usual.
|
|
|
|
- Otherwise, trust the host key. -}
|
2012-09-04 19:27:06 +00:00
|
|
|
[ if knownhost then "" else sshOpt "StrictHostKeyChecking" "no"
|
2012-09-02 00:37:35 +00:00
|
|
|
, "-n" -- don't read from stdin
|
2012-09-04 19:27:06 +00:00
|
|
|
, genSshHost (fromJust $ hostname sshserver) (username sshserver)
|
2012-09-02 00:37:35 +00:00
|
|
|
, remotecommand
|
|
|
|
]
|
2012-09-04 19:27:06 +00:00
|
|
|
parsetranscript . fst <$> sshTranscript sshopts ""
|
2012-09-02 00:37:35 +00:00
|
|
|
parsetranscript s
|
|
|
|
| reported "git-annex-shell" = UsableSshServer
|
|
|
|
| reported "rsync" = UsableRsyncServer
|
|
|
|
| reported "loggedin" = UnusableServer
|
|
|
|
"Neither rsync nor git-annex are installed on the server. Perhaps you should go install them?"
|
|
|
|
| otherwise = UnusableServer $ T.pack $
|
|
|
|
"Failed to ssh to the server. Transcript: " ++ s
|
|
|
|
where
|
|
|
|
reported r = token r `isInfixOf` s
|
|
|
|
checkcommand c = "if which " ++ c ++ "; then " ++ report c ++ "; fi"
|
|
|
|
token r = "git-annex-probe " ++ r
|
|
|
|
report r = "echo " ++ token r
|
2012-09-04 19:27:06 +00:00
|
|
|
|
2012-09-02 19:21:40 +00:00
|
|
|
{- user@host or host -}
|
|
|
|
genSshHost :: Text -> Maybe Text -> String
|
|
|
|
genSshHost host user = maybe "" (\v -> T.unpack v ++ "@") user ++ T.unpack host
|
|
|
|
|
2012-09-04 19:27:06 +00:00
|
|
|
{- Runs a ssh command; if it fails shows the user the transcript,
|
|
|
|
- and if it succeeds, runs an action. -}
|
|
|
|
sshSetup :: [String] -> String -> Handler RepHtml -> Handler RepHtml
|
|
|
|
sshSetup opts input a = do
|
|
|
|
(transcript, ok) <- liftIO $ sshTranscript opts input
|
|
|
|
if ok
|
|
|
|
then a
|
|
|
|
else showSshErr transcript
|
|
|
|
|
|
|
|
showSshErr :: String -> Handler RepHtml
|
|
|
|
showSshErr msg = sshConfigurator $
|
2012-09-09 03:32:08 +00:00
|
|
|
$(widgetFile "configurators/ssh/error")
|
2012-09-04 19:27:06 +00:00
|
|
|
|
2012-09-02 00:37:35 +00:00
|
|
|
{- Does ssh have known_hosts data for a hostname? -}
|
2012-09-03 00:43:32 +00:00
|
|
|
knownHost :: SshServer -> IO Bool
|
|
|
|
knownHost (SshServer { hostname = Nothing }) = return False
|
|
|
|
knownHost (SshServer { hostname = Just h }) = do
|
|
|
|
sshdir <- sshDir
|
2012-09-02 00:37:35 +00:00
|
|
|
ifM (doesFileExist $ sshdir </> "known_hosts")
|
|
|
|
( not . null <$> readProcess "ssh-keygen" ["-F", T.unpack h]
|
|
|
|
, return False
|
|
|
|
)
|
2012-09-02 01:10:40 +00:00
|
|
|
|
2012-09-02 04:27:48 +00:00
|
|
|
getConfirmSshR :: SshData -> Handler RepHtml
|
2012-09-02 19:21:40 +00:00
|
|
|
getConfirmSshR sshdata = sshConfigurator $ do
|
2012-09-02 04:27:48 +00:00
|
|
|
let authtoken = webAppFormAuthToken
|
2012-09-09 03:32:08 +00:00
|
|
|
$(widgetFile "configurators/ssh/confirm")
|
2012-09-02 04:27:48 +00:00
|
|
|
|
2012-09-02 21:32:24 +00:00
|
|
|
getMakeSshGitR :: SshData -> Handler RepHtml
|
|
|
|
getMakeSshGitR = makeSsh False
|
|
|
|
|
|
|
|
getMakeSshRsyncR :: SshData -> Handler RepHtml
|
|
|
|
getMakeSshRsyncR = makeSsh True
|
|
|
|
|
|
|
|
makeSsh :: Bool -> SshData -> Handler RepHtml
|
2012-09-03 00:43:32 +00:00
|
|
|
makeSsh rsync sshdata
|
|
|
|
| needsPubKey sshdata = do
|
2012-09-10 18:42:46 +00:00
|
|
|
keypair <- liftIO $ genSshKeyPair
|
|
|
|
sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
|
2012-09-10 21:53:51 +00:00
|
|
|
makeSshWithKeyPair rsync sshdata' (Just keypair)
|
|
|
|
| otherwise = makeSshWithKeyPair rsync sshdata Nothing
|
2012-09-03 00:43:32 +00:00
|
|
|
|
2012-09-10 21:53:51 +00:00
|
|
|
makeSshWithKeyPair :: Bool -> SshData -> Maybe SshKeyPair -> Handler RepHtml
|
|
|
|
makeSshWithKeyPair rsync sshdata keypair =
|
2012-09-04 19:27:06 +00:00
|
|
|
sshSetup [sshhost, remoteCommand] "" $
|
|
|
|
makeSshRepo rsync sshdata
|
2012-09-02 04:27:48 +00:00
|
|
|
where
|
2012-09-02 19:21:40 +00:00
|
|
|
sshhost = genSshHost (sshHostName sshdata) (sshUserName sshdata)
|
|
|
|
remotedir = T.unpack $ sshDirectory sshdata
|
|
|
|
remoteCommand = join "&&" $ catMaybes
|
|
|
|
[ Just $ "mkdir -p " ++ shellEscape remotedir
|
|
|
|
, Just $ "cd " ++ shellEscape remotedir
|
2012-09-02 21:32:24 +00:00
|
|
|
, if rsync then Nothing else Just $ "git init --bare --shared"
|
|
|
|
, if rsync then Nothing else Just $ "git annex init"
|
2012-09-10 21:53:51 +00:00
|
|
|
, if needsPubKey sshdata
|
|
|
|
then maybe Nothing (Just . makeAuthorizedKeysCommand (rsyncOnly sshdata) . sshPubKey) keypair
|
|
|
|
else Nothing
|
2012-09-02 04:27:48 +00:00
|
|
|
]
|
2012-09-04 19:27:06 +00:00
|
|
|
|
|
|
|
makeSshRepo :: Bool -> SshData -> Handler RepHtml
|
|
|
|
makeSshRepo forcersync sshdata = do
|
|
|
|
r <- runAnnex undefined $
|
|
|
|
addRemote $ maker (sshRepoName sshdata) sshurl
|
|
|
|
syncRemote r
|
|
|
|
redirect RepositoriesR
|
|
|
|
where
|
|
|
|
rsync = forcersync || rsyncOnly sshdata
|
|
|
|
maker
|
|
|
|
| rsync = makeRsyncRemote
|
|
|
|
| otherwise = makeGitRemote
|
|
|
|
sshurl = T.unpack $ T.concat $
|
|
|
|
if rsync
|
|
|
|
then [u, h, ":", sshDirectory sshdata, "/"]
|
|
|
|
else ["ssh://", u, h, d, "/"]
|
2012-09-02 21:32:24 +00:00
|
|
|
where
|
|
|
|
u = maybe "" (\v -> T.concat [v, "@"]) $ sshUserName sshdata
|
|
|
|
h = sshHostName sshdata
|
|
|
|
d
|
|
|
|
| "/" `T.isPrefixOf` sshDirectory sshdata = d
|
|
|
|
| otherwise = T.concat ["/~/", sshDirectory sshdata]
|
2012-09-04 19:27:06 +00:00
|
|
|
|
2012-09-02 21:32:24 +00:00
|
|
|
|
|
|
|
{- Inits a rsync special remote, and returns the name of the remote. -}
|
|
|
|
makeRsyncRemote :: String -> String -> Annex String
|
|
|
|
makeRsyncRemote name location = makeRemote name location $ const $ do
|
|
|
|
(u, c) <- Command.InitRemote.findByName name
|
|
|
|
c' <- R.setup Rsync.remote u $ M.union config c
|
|
|
|
describeUUID u name
|
|
|
|
configSet u c'
|
|
|
|
where
|
|
|
|
config = M.fromList
|
|
|
|
[ ("encryption", "shared")
|
|
|
|
, ("rsyncurl", location)
|
|
|
|
, ("type", "rsync")
|
|
|
|
]
|
|
|
|
|
2012-09-03 04:39:55 +00:00
|
|
|
getAddRsyncNetR :: Handler RepHtml
|
2012-09-04 19:27:06 +00:00
|
|
|
getAddRsyncNetR = do
|
|
|
|
((result, form), enctype) <- runFormGet $
|
|
|
|
renderBootstrap $ sshServerAForm Nothing
|
|
|
|
let showform status = bootstrap (Just Config) $ do
|
|
|
|
sideBarDisplay
|
|
|
|
setTitle "Add a Rsync.net repository"
|
2012-09-03 04:39:55 +00:00
|
|
|
let authtoken = webAppFormAuthToken
|
|
|
|
$(widgetFile "configurators/addrsync.net")
|
|
|
|
case result of
|
|
|
|
FormSuccess sshserver -> do
|
2012-09-04 19:27:06 +00:00
|
|
|
knownhost <- liftIO $ knownHost sshserver
|
2012-09-10 18:42:46 +00:00
|
|
|
keypair <- liftIO $ genSshKeyPair
|
|
|
|
sshdata <- liftIO $ setupSshKeyPair keypair
|
2012-09-04 19:27:06 +00:00
|
|
|
(mkSshData sshserver)
|
|
|
|
{ needsPubKey = True
|
|
|
|
, rsyncOnly = True
|
|
|
|
, sshRepoName = "rsync.net"
|
|
|
|
}
|
|
|
|
{- I'd prefer to separate commands with && , but
|
|
|
|
- rsync.net's shell does not support that.
|
|
|
|
-
|
|
|
|
- The dd method of appending to the
|
|
|
|
- authorized_keys file is the one recommended by
|
|
|
|
- rsync.net documentation. I touch the file first
|
|
|
|
- to not need to use a different method to create
|
|
|
|
- it.
|
|
|
|
-}
|
|
|
|
let remotecommand = join ";" $
|
|
|
|
[ "mkdir -p .ssh"
|
|
|
|
, "touch .ssh/authorized_keys"
|
|
|
|
, "dd of=.ssh/authorized_keys oflag=append conv=notrunc"
|
|
|
|
, "mkdir -p " ++ T.unpack (sshDirectory sshdata)
|
|
|
|
]
|
|
|
|
let sshopts = filter (not . null) $
|
|
|
|
[ if knownhost then "" else sshOpt "StrictHostKeyChecking" "no"
|
|
|
|
, genSshHost (sshHostName sshdata) (sshUserName sshdata)
|
|
|
|
, remotecommand
|
|
|
|
]
|
|
|
|
|
2012-09-03 04:39:55 +00:00
|
|
|
let host = fromMaybe "" $ hostname sshserver
|
2012-09-04 19:27:06 +00:00
|
|
|
checkhost host showform $
|
2012-09-10 18:42:46 +00:00
|
|
|
sshSetup sshopts (sshPubKey keypair) $
|
2012-09-04 19:27:06 +00:00
|
|
|
makeSshRepo True sshdata
|
2012-09-03 04:39:55 +00:00
|
|
|
_ -> showform UntestedServer
|
|
|
|
where
|
|
|
|
checkhost host showform a
|
|
|
|
| ".rsync.net" `T.isSuffixOf` T.toLower host = a
|
|
|
|
| otherwise = showform $ UnusableServer
|
|
|
|
"That is not a rsync.net host name."
|