2012-08-31 19:17:12 +00:00
|
|
|
|
{- git-annex assistant webapp configurator for ssh-based remotes
|
|
|
|
|
-
|
2015-07-20 22:38:23 +00:00
|
|
|
|
- Copyright 2012-2015 Joey Hess <id@joeyh.name>
|
2012-08-31 19:17:12 +00:00
|
|
|
|
-
|
2012-09-24 18:48:47 +00:00
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-08-31 19:17:12 +00:00
|
|
|
|
-}
|
|
|
|
|
|
2013-06-05 01:02:09 +00:00
|
|
|
|
{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
|
2015-05-10 19:54:58 +00:00
|
|
|
|
{-# LANGUAGE CPP, FlexibleContexts #-}
|
2012-08-31 19:17:12 +00:00
|
|
|
|
|
|
|
|
|
module Assistant.WebApp.Configurators.Ssh where
|
|
|
|
|
|
2012-11-25 04:26:46 +00:00
|
|
|
|
import Assistant.WebApp.Common
|
2013-09-26 20:09:45 +00:00
|
|
|
|
import Assistant.WebApp.Gpg
|
2012-09-10 19:20:18 +00:00
|
|
|
|
import Assistant.Ssh
|
2014-05-14 19:02:18 +00:00
|
|
|
|
import Annex.Ssh
|
2013-10-28 15:33:14 +00:00
|
|
|
|
import Assistant.WebApp.MakeRemote
|
2012-09-13 20:47:44 +00:00
|
|
|
|
import Logs.Remote
|
|
|
|
|
import Remote
|
2012-10-10 20:04:28 +00:00
|
|
|
|
import Types.StandardGroups
|
2012-10-25 22:17:32 +00:00
|
|
|
|
import Utility.UserInfo
|
2013-09-26 20:09:45 +00:00
|
|
|
|
import Utility.Gpg
|
2013-10-01 20:08:01 +00:00
|
|
|
|
import Types.Remote (RemoteConfig)
|
2015-07-20 22:38:23 +00:00
|
|
|
|
import Git.Types (RemoteName, fromRef)
|
2013-09-27 20:21:56 +00:00
|
|
|
|
import qualified Remote.GCrypt as GCrypt
|
2015-09-09 22:06:49 +00:00
|
|
|
|
import qualified Annex
|
2015-07-20 22:38:23 +00:00
|
|
|
|
import qualified Git.Construct
|
|
|
|
|
import qualified Git.Config
|
|
|
|
|
import qualified Git.Command
|
|
|
|
|
import qualified Remote.Helper.Ssh
|
|
|
|
|
import qualified Annex.Branch
|
2013-10-02 19:54:32 +00:00
|
|
|
|
import Annex.UUID
|
|
|
|
|
import Logs.UUID
|
2014-04-20 19:30:39 +00:00
|
|
|
|
import Assistant.RemoteControl
|
2014-05-15 19:15:19 +00:00
|
|
|
|
import Types.Creds
|
2014-05-14 19:02:18 +00:00
|
|
|
|
import Assistant.CredPairCache
|
2015-02-28 21:23:13 +00:00
|
|
|
|
import Annex.Path
|
2014-05-14 19:02:18 +00:00
|
|
|
|
import Utility.Tmp
|
|
|
|
|
import Utility.FileMode
|
|
|
|
|
import Utility.ThreadScheduler
|
2014-05-14 20:17:30 +00:00
|
|
|
|
import Utility.Env
|
2017-08-18 02:11:31 +00:00
|
|
|
|
import Utility.SshHost
|
2017-12-31 20:08:31 +00:00
|
|
|
|
import Utility.Process.Transcript
|
2012-08-31 19:17:12 +00:00
|
|
|
|
|
|
|
|
|
import qualified Data.Text as T
|
2012-09-13 20:47:44 +00:00
|
|
|
|
import qualified Data.Map as M
|
2012-09-29 16:49:23 +00:00
|
|
|
|
import Network.Socket
|
2013-09-26 20:09:45 +00:00
|
|
|
|
import Data.Ord
|
2012-08-31 19:17:12 +00:00
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
|
sshConfigurator :: Widget -> Handler Html
|
2012-12-30 03:10:18 +00:00
|
|
|
|
sshConfigurator = page "Add a remote server" (Just Configuration)
|
2012-09-02 19:21:40 +00:00
|
|
|
|
|
2012-09-13 20:47:44 +00:00
|
|
|
|
data SshInput = SshInput
|
2012-12-06 21:09:08 +00:00
|
|
|
|
{ inputHostname :: Maybe Text
|
|
|
|
|
, inputUsername :: Maybe Text
|
2014-05-14 19:02:18 +00:00
|
|
|
|
, inputAuthMethod :: AuthMethod
|
|
|
|
|
, inputPassword :: Maybe Text
|
2012-12-06 21:09:08 +00:00
|
|
|
|
, inputDirectory :: Maybe Text
|
|
|
|
|
, inputPort :: Int
|
2012-08-31 22:59:57 +00:00
|
|
|
|
}
|
2014-05-14 19:02:18 +00:00
|
|
|
|
|
|
|
|
|
data AuthMethod
|
|
|
|
|
= Password
|
|
|
|
|
| CachedPassword
|
|
|
|
|
| ExistingSshKey
|
|
|
|
|
deriving (Eq, Show)
|
2012-09-02 01:10:40 +00:00
|
|
|
|
|
2014-05-30 18:03:04 +00:00
|
|
|
|
-- Is a repository a new one that's being created, or did it already exist
|
|
|
|
|
-- and is just being added.
|
|
|
|
|
data RepoStatus = NewRepo | ExistingRepo
|
|
|
|
|
|
2012-09-13 20:47:44 +00:00
|
|
|
|
{- SshInput is only used for applicative form prompting, this converts
|
2012-09-04 19:27:06 +00:00
|
|
|
|
- the result of such a form into a SshData. -}
|
2012-09-13 20:47:44 +00:00
|
|
|
|
mkSshData :: SshInput -> SshData
|
|
|
|
|
mkSshData s = SshData
|
2012-12-06 21:09:08 +00:00
|
|
|
|
{ sshHostName = fromMaybe "" $ inputHostname s
|
|
|
|
|
, sshUserName = inputUsername s
|
|
|
|
|
, sshDirectory = fromMaybe "" $ inputDirectory s
|
2012-09-10 21:53:51 +00:00
|
|
|
|
, sshRepoName = genSshRepoName
|
2012-12-06 21:09:08 +00:00
|
|
|
|
(T.unpack $ fromJust $ inputHostname s)
|
|
|
|
|
(maybe "" T.unpack $ inputDirectory s)
|
|
|
|
|
, sshPort = inputPort s
|
2012-09-04 19:27:06 +00:00
|
|
|
|
, needsPubKey = False
|
2013-09-29 18:39:10 +00:00
|
|
|
|
, sshCapabilities = [] -- untested
|
2015-07-20 22:38:23 +00:00
|
|
|
|
, sshRepoUrl = Nothing
|
2012-09-04 19:27:06 +00:00
|
|
|
|
}
|
|
|
|
|
|
2013-03-16 16:58:59 +00:00
|
|
|
|
mkSshInput :: SshData -> SshInput
|
|
|
|
|
mkSshInput s = SshInput
|
|
|
|
|
{ inputHostname = Just $ sshHostName s
|
|
|
|
|
, inputUsername = sshUserName s
|
2014-05-14 19:02:18 +00:00
|
|
|
|
, inputAuthMethod = if needsPubKey s then CachedPassword else ExistingSshKey
|
|
|
|
|
, inputPassword = Nothing
|
2013-03-16 16:58:59 +00:00
|
|
|
|
, inputDirectory = Just $ sshDirectory s
|
|
|
|
|
, inputPort = sshPort s
|
|
|
|
|
}
|
|
|
|
|
|
2013-06-02 19:57:22 +00:00
|
|
|
|
sshInputAForm :: Field Handler Text -> SshInput -> AForm Handler SshInput
|
2015-01-28 20:11:28 +00:00
|
|
|
|
sshInputAForm hostnamefield d = normalize <$> gen
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2014-05-27 18:33:27 +00:00
|
|
|
|
gen = SshInput
|
2015-01-28 20:11:28 +00:00
|
|
|
|
<$> aopt check_hostname (bfs "Host name") (Just $ inputHostname d)
|
|
|
|
|
<*> aopt check_username (bfs "User name") (Just $ inputUsername d)
|
|
|
|
|
<*> areq (selectFieldList authmethods) (bfs "Authenticate with") (Just $ inputAuthMethod d)
|
2014-05-27 18:33:27 +00:00
|
|
|
|
<*> aopt passwordField (bfs "Password") Nothing
|
2015-01-28 20:11:28 +00:00
|
|
|
|
<*> aopt textField (bfs "Directory") (Just $ Just $ fromMaybe (T.pack gitAnnexAssistantDefaultDir) $ inputDirectory d)
|
|
|
|
|
<*> areq intField (bfs "Port") (Just $ inputPort d)
|
2014-05-27 18:33:27 +00:00
|
|
|
|
|
2014-05-14 19:02:18 +00:00
|
|
|
|
authmethods :: [(Text, AuthMethod)]
|
|
|
|
|
authmethods =
|
|
|
|
|
[ ("password", Password)
|
|
|
|
|
, ("existing ssh key", ExistingSshKey)
|
|
|
|
|
]
|
|
|
|
|
|
2015-05-10 19:54:58 +00:00
|
|
|
|
check_username = checkBool (all (`notElem` ("/:@ \t" :: String)) . T.unpack)
|
2013-05-04 20:36:51 +00:00
|
|
|
|
bad_username textField
|
|
|
|
|
|
2013-05-06 20:45:49 +00:00
|
|
|
|
bad_username = "bad user name" :: Text
|
2013-05-04 20:36:51 +00:00
|
|
|
|
bad_hostname = "cannot resolve host name" :: Text
|
|
|
|
|
|
2012-12-03 02:33:30 +00:00
|
|
|
|
check_hostname = checkM (liftIO . checkdns) hostnamefield
|
2012-10-31 06:34:03 +00:00
|
|
|
|
checkdns t = do
|
|
|
|
|
let h = T.unpack t
|
2013-05-04 18:25:30 +00:00
|
|
|
|
let canonname = Just $ defaultHints { addrFlags = [AI_CANONNAME] }
|
2012-10-31 06:34:03 +00:00
|
|
|
|
r <- catchMaybeIO $ getAddrInfo canonname (Just h) Nothing
|
2013-10-02 04:33:40 +00:00
|
|
|
|
return $ case mapMaybe addrCanonName <$> r of
|
2012-10-31 06:34:03 +00:00
|
|
|
|
-- canonicalize input hostname if it had no dot
|
|
|
|
|
Just (fullname:_)
|
|
|
|
|
| '.' `elem` h -> Right t
|
|
|
|
|
| otherwise -> Right $ T.pack fullname
|
|
|
|
|
Just [] -> Right t
|
|
|
|
|
Nothing -> Left bad_hostname
|
2012-08-31 22:59:57 +00:00
|
|
|
|
|
2014-05-27 18:33:27 +00:00
|
|
|
|
-- The directory is implicitly in home, so remove any leading ~/
|
|
|
|
|
normalize i = i { inputDirectory = normalizedir <$> inputDirectory i }
|
2015-01-28 20:11:28 +00:00
|
|
|
|
normalizedir dir
|
|
|
|
|
| "~/" `T.isPrefixOf` dir = T.drop 2 dir
|
|
|
|
|
| "/~/" `T.isPrefixOf` dir = T.drop 3 dir
|
|
|
|
|
| otherwise = dir
|
2014-05-27 18:33:27 +00:00
|
|
|
|
|
2012-08-31 22:59:57 +00:00
|
|
|
|
data ServerStatus
|
|
|
|
|
= UntestedServer
|
|
|
|
|
| UnusableServer Text -- reason why it's not usable
|
2015-07-20 22:38:23 +00:00
|
|
|
|
| ServerNeedsPubKey SshPubKey
|
2013-09-29 18:39:10 +00:00
|
|
|
|
| UsableServer [SshServerCapability]
|
2012-09-02 04:27:48 +00:00
|
|
|
|
deriving (Eq)
|
2012-08-31 22:59:57 +00:00
|
|
|
|
|
2013-09-29 18:39:10 +00:00
|
|
|
|
capabilities :: ServerStatus -> [SshServerCapability]
|
|
|
|
|
capabilities (UsableServer cs) = cs
|
|
|
|
|
capabilities _ = []
|
2012-08-31 22:59:57 +00:00
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
|
getAddSshR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
|
getAddSshR = postAddSshR
|
2013-06-27 05:15:28 +00:00
|
|
|
|
postAddSshR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
|
postAddSshR = sshConfigurator $ do
|
2016-06-08 19:04:15 +00:00
|
|
|
|
username <- liftIO $ either (const Nothing) (Just . T.pack) <$> myUserName
|
2013-06-03 17:51:54 +00:00
|
|
|
|
((result, form), enctype) <- liftH $
|
2014-04-18 00:07:09 +00:00
|
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ sshInputAForm textField $
|
2016-06-08 19:04:15 +00:00
|
|
|
|
SshInput Nothing username Password Nothing Nothing 22
|
2012-08-31 22:59:57 +00:00
|
|
|
|
case result of
|
2012-09-13 20:47:44 +00:00
|
|
|
|
FormSuccess sshinput -> do
|
2014-05-14 19:02:18 +00:00
|
|
|
|
s <- liftAssistant $ testServer sshinput
|
2012-09-13 20:47:44 +00:00
|
|
|
|
case s of
|
|
|
|
|
Left status -> showform form enctype status
|
2013-10-02 19:54:32 +00:00
|
|
|
|
Right (sshdata, u) -> liftH $ redirect $ ConfirmSshR sshdata u
|
2012-08-31 22:59:57 +00:00
|
|
|
|
_ -> showform form enctype UntestedServer
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2012-11-25 04:38:11 +00:00
|
|
|
|
showform form enctype status = $(widgetFile "configurators/ssh/add")
|
2012-08-31 22:59:57 +00:00
|
|
|
|
|
2013-03-16 16:58:59 +00:00
|
|
|
|
sshTestModal :: Widget
|
|
|
|
|
sshTestModal = $(widgetFile "configurators/ssh/testmodal")
|
|
|
|
|
|
2013-10-02 19:54:32 +00:00
|
|
|
|
sshSetupModal :: SshData -> Widget
|
|
|
|
|
sshSetupModal sshdata = $(widgetFile "configurators/ssh/setupmodal")
|
|
|
|
|
|
2013-09-27 03:28:25 +00:00
|
|
|
|
getEnableRsyncR :: UUID -> Handler Html
|
|
|
|
|
getEnableRsyncR = postEnableRsyncR
|
|
|
|
|
postEnableRsyncR :: UUID -> Handler Html
|
2014-05-22 18:10:48 +00:00
|
|
|
|
postEnableRsyncR = enableSshRemote getsshinput enableRsyncNet enablersync
|
2013-09-27 03:28:25 +00:00
|
|
|
|
where
|
2013-10-02 19:54:32 +00:00
|
|
|
|
enablersync sshdata u = redirect $ ConfirmSshR
|
|
|
|
|
(sshdata { sshCapabilities = [RsyncCapable] }) u
|
2013-10-01 20:08:01 +00:00
|
|
|
|
getsshinput = parseSshUrl <=< M.lookup "rsyncurl"
|
2013-09-27 03:28:25 +00:00
|
|
|
|
|
2013-09-26 21:26:13 +00:00
|
|
|
|
{- This only handles gcrypt repositories that are located on ssh servers;
|
|
|
|
|
- ones on local drives are handled via another part of the UI. -}
|
2013-10-02 19:54:32 +00:00
|
|
|
|
getEnableSshGCryptR :: UUID -> Handler Html
|
|
|
|
|
getEnableSshGCryptR = postEnableSshGCryptR
|
|
|
|
|
postEnableSshGCryptR :: UUID -> Handler Html
|
|
|
|
|
postEnableSshGCryptR u = whenGcryptInstalled $
|
2014-05-22 18:10:48 +00:00
|
|
|
|
enableSshRemote getsshinput enableRsyncNetGCrypt enablegcrypt u
|
2013-09-27 03:28:25 +00:00
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
|
enablegcrypt sshdata _ = prepSsh False sshdata $ \sshdata' ->
|
2013-10-01 17:43:35 +00:00
|
|
|
|
sshConfigurator $
|
|
|
|
|
checkExistingGCrypt sshdata' $
|
2016-11-16 01:29:54 +00:00
|
|
|
|
giveup "Expected to find an encrypted git repository, but did not."
|
2013-10-01 20:08:01 +00:00
|
|
|
|
getsshinput = parseSshUrl <=< M.lookup "gitrepo"
|
2013-09-26 21:26:13 +00:00
|
|
|
|
|
2014-05-22 18:10:48 +00:00
|
|
|
|
getEnableSshGitRemoteR :: UUID -> Handler Html
|
|
|
|
|
getEnableSshGitRemoteR = postEnableSshGitRemoteR
|
|
|
|
|
postEnableSshGitRemoteR :: UUID -> Handler Html
|
|
|
|
|
postEnableSshGitRemoteR = enableSshRemote getsshinput enableRsyncNet enablesshgitremote
|
|
|
|
|
where
|
|
|
|
|
enablesshgitremote sshdata u = redirect $ ConfirmSshR sshdata u
|
|
|
|
|
|
|
|
|
|
getsshinput = parseSshUrl <=< M.lookup "location"
|
|
|
|
|
|
|
|
|
|
{- To enable a remote that uses ssh as its transport,
|
|
|
|
|
- parse a config key to get its url, and display a form
|
|
|
|
|
- to prompt for its password.
|
2012-09-13 20:47:44 +00:00
|
|
|
|
-}
|
2014-05-22 18:10:48 +00:00
|
|
|
|
enableSshRemote :: (RemoteConfig -> Maybe SshData) -> (SshInput -> RemoteName -> Handler Html) -> (SshData -> UUID -> Handler Html) -> UUID -> Handler Html
|
2015-07-27 20:03:22 +00:00
|
|
|
|
enableSshRemote getsshdata rsyncnetsetup genericsetup u = do
|
2013-03-04 20:36:38 +00:00
|
|
|
|
m <- fromMaybe M.empty . M.lookup u <$> liftAnnex readRemoteLog
|
2015-07-27 20:03:22 +00:00
|
|
|
|
case (unmangle <$> getsshdata m, M.lookup "name" m) of
|
|
|
|
|
(Just sshdata, Just reponame)
|
|
|
|
|
| isGitLab sshdata -> enableGitLab sshdata
|
|
|
|
|
| otherwise -> sshConfigurator $ do
|
|
|
|
|
((result, form), enctype) <- liftH $
|
|
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $
|
|
|
|
|
sshInputAForm textField $ mkSshInput sshdata
|
|
|
|
|
case result of
|
|
|
|
|
FormSuccess sshinput
|
|
|
|
|
| isRsyncNet (inputHostname sshinput) ->
|
|
|
|
|
void $ liftH $ rsyncnetsetup sshinput reponame
|
|
|
|
|
| otherwise -> do
|
|
|
|
|
s <- liftAssistant $ testServer sshinput
|
|
|
|
|
case s of
|
|
|
|
|
Left status -> showform form enctype status
|
|
|
|
|
Right (sshdata', _u) -> void $ liftH $ genericsetup
|
|
|
|
|
( sshdata' { sshRepoName = reponame } ) u
|
|
|
|
|
_ -> showform form enctype UntestedServer
|
2012-10-31 20:14:52 +00:00
|
|
|
|
_ -> redirect AddSshR
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
|
unmangle sshdata = sshdata
|
2013-10-01 20:08:01 +00:00
|
|
|
|
{ sshHostName = T.pack $ unMangleSshHostName $
|
|
|
|
|
T.unpack $ sshHostName sshdata
|
|
|
|
|
}
|
2012-10-31 06:34:03 +00:00
|
|
|
|
showform form enctype status = do
|
2013-04-03 21:01:40 +00:00
|
|
|
|
description <- liftAnnex $ T.pack <$> prettyUUID u
|
2012-10-31 06:34:03 +00:00
|
|
|
|
$(widgetFile "configurators/ssh/enable")
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
2014-04-20 22:38:59 +00:00
|
|
|
|
{- To deal with git-annex and possibly even git and rsync not being
|
|
|
|
|
- available in the remote server's PATH, when git-annex was installed
|
|
|
|
|
- from the standalone tarball etc, look for a ~/.ssh/git-annex-wrapper
|
|
|
|
|
- and if it's there, use it to run a command. -}
|
|
|
|
|
wrapCommand :: String -> String
|
|
|
|
|
wrapCommand cmd = "if [ -x " ++ commandWrapper ++ " ]; then " ++ commandWrapper ++ " " ++ cmd ++ "; else " ++ cmd ++ "; fi"
|
|
|
|
|
|
|
|
|
|
commandWrapper :: String
|
|
|
|
|
commandWrapper = "~/.ssh/git-annex-wrapper"
|
|
|
|
|
|
2014-05-14 19:02:18 +00:00
|
|
|
|
{- Test if we can ssh into the server, using the specified AuthMethod.
|
2012-09-02 00:37:35 +00:00
|
|
|
|
-
|
2013-09-29 18:39:10 +00:00
|
|
|
|
- Once logged into the server, probe to see if git-annex-shell,
|
|
|
|
|
- git, and rsync are available.
|
2014-04-20 22:38:59 +00:00
|
|
|
|
-
|
2014-05-14 19:02:18 +00:00
|
|
|
|
- Note that ~/.ssh/git-annex-shell may be present, while
|
|
|
|
|
- git-annex-shell is not in PATH.
|
2014-04-20 22:38:59 +00:00
|
|
|
|
- Also, git and rsync may not be in PATH; as long as the commandWrapper
|
|
|
|
|
- is present, assume it is able to be used to run them.
|
2013-10-02 19:54:32 +00:00
|
|
|
|
-
|
|
|
|
|
- Also probe to see if there is already a git repository at the location
|
|
|
|
|
- with either an annex-uuid or a gcrypt-id set. (If not, returns NoUUID.)
|
2012-09-02 00:37:35 +00:00
|
|
|
|
-}
|
2014-05-14 19:02:18 +00:00
|
|
|
|
testServer :: SshInput -> Assistant (Either ServerStatus (SshData, UUID))
|
|
|
|
|
testServer (SshInput { inputHostname = Nothing }) = return $
|
2012-09-13 20:47:44 +00:00
|
|
|
|
Left $ UnusableServer "Please enter a host name."
|
2014-05-14 19:02:18 +00:00
|
|
|
|
testServer sshinput@(SshInput { inputHostname = Just hn }) = do
|
|
|
|
|
(status, u) <- probe
|
2013-09-29 18:39:10 +00:00
|
|
|
|
case capabilities status of
|
2014-05-14 19:02:18 +00:00
|
|
|
|
[] -> return $ Left status
|
|
|
|
|
cs -> do
|
|
|
|
|
let sshdata = (mkSshData sshinput)
|
|
|
|
|
{ needsPubKey = inputAuthMethod sshinput /= ExistingSshKey
|
|
|
|
|
, sshCapabilities = cs
|
|
|
|
|
}
|
|
|
|
|
return $ Right (sshdata, u)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
2014-05-14 19:02:18 +00:00
|
|
|
|
probe = do
|
2013-04-23 00:24:53 +00:00
|
|
|
|
let remotecommand = shellWrap $ intercalate ";"
|
2012-10-31 06:34:03 +00:00
|
|
|
|
[ report "loggedin"
|
|
|
|
|
, checkcommand "git-annex-shell"
|
2013-09-29 18:39:10 +00:00
|
|
|
|
, checkcommand "git"
|
2012-10-31 06:34:03 +00:00
|
|
|
|
, checkcommand "rsync"
|
|
|
|
|
, checkcommand shim
|
2014-04-20 22:38:59 +00:00
|
|
|
|
, checkcommand commandWrapper
|
2013-10-02 19:54:32 +00:00
|
|
|
|
, getgitconfig (T.unpack <$> inputDirectory sshinput)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
]
|
2014-05-14 19:02:18 +00:00
|
|
|
|
knownhost <- liftIO $ knownHost hn
|
2014-05-14 22:07:15 +00:00
|
|
|
|
let sshopts =
|
2012-10-31 06:34:03 +00:00
|
|
|
|
{- If this is an already known host, let
|
|
|
|
|
- ssh check it as usual.
|
|
|
|
|
- Otherwise, trust the host key. -}
|
2014-05-14 22:07:15 +00:00
|
|
|
|
[ sshOpt "StrictHostKeyChecking" $
|
|
|
|
|
if knownhost then "yes" else "no"
|
|
|
|
|
, "-n" -- don't read from stdin
|
|
|
|
|
, "-p", show (inputPort sshinput)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
]
|
2017-08-18 02:11:31 +00:00
|
|
|
|
let sshhost = genSshHost
|
|
|
|
|
(fromJust $ inputHostname sshinput)
|
|
|
|
|
(inputUsername sshinput)
|
|
|
|
|
parsetranscript . fst <$> sshAuthTranscript sshinput sshopts sshhost remotecommand Nothing
|
2013-09-29 18:39:10 +00:00
|
|
|
|
parsetranscript s =
|
|
|
|
|
let cs = map snd $ filter (reported . fst)
|
|
|
|
|
[ ("git-annex-shell", GitAnnexShellCapable)
|
|
|
|
|
, (shim, GitAnnexShellCapable)
|
|
|
|
|
, ("git", GitCapable)
|
|
|
|
|
, ("rsync", RsyncCapable)
|
2014-04-20 22:38:59 +00:00
|
|
|
|
, (commandWrapper, GitCapable)
|
|
|
|
|
, (commandWrapper, RsyncCapable)
|
2013-09-29 18:39:10 +00:00
|
|
|
|
]
|
2013-10-02 19:54:32 +00:00
|
|
|
|
u = fromMaybe NoUUID $ headMaybe $ mapMaybe finduuid $
|
|
|
|
|
map (separate (== '=')) $ lines s
|
2013-09-29 18:39:10 +00:00
|
|
|
|
in if null cs
|
2013-10-02 19:54:32 +00:00
|
|
|
|
then (UnusableServer unusablereason, u)
|
|
|
|
|
else (UsableServer cs, u)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
|
|
|
|
reported r = token r `isInfixOf` s
|
2013-10-02 19:54:32 +00:00
|
|
|
|
unusablereason = if reported "loggedin"
|
|
|
|
|
then "Neither rsync nor git-annex are installed on the server. Perhaps you should go install them?"
|
|
|
|
|
else T.pack $ "Failed to ssh to the server. Transcript: " ++ s
|
|
|
|
|
finduuid (k, v)
|
|
|
|
|
| k == "annex.uuid" = Just $ toUUID v
|
|
|
|
|
| k == GCrypt.coreGCryptId = Just $ genUUIDInNameSpace gCryptNameSpace v
|
|
|
|
|
| otherwise = Nothing
|
2013-03-29 17:09:30 +00:00
|
|
|
|
|
2012-10-31 06:34:03 +00:00
|
|
|
|
checkcommand c = "if which " ++ c ++ "; then " ++ report c ++ "; fi"
|
|
|
|
|
token r = "git-annex-probe " ++ r
|
2014-04-20 22:38:59 +00:00
|
|
|
|
report r = "echo " ++ shellEscape (token r)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
shim = "~/.ssh/git-annex-shell"
|
2013-10-02 19:54:32 +00:00
|
|
|
|
getgitconfig (Just d)
|
|
|
|
|
| not (null d) = "cd " ++ shellEscape d ++ " && git config --list"
|
|
|
|
|
getgitconfig _ = "echo"
|
2012-09-04 19:27:06 +00:00
|
|
|
|
|
2014-05-14 19:02:18 +00:00
|
|
|
|
{- Runs a ssh command to set up the repository; if it fails shows
|
|
|
|
|
- the user the transcript, and if it succeeds, runs an action. -}
|
2017-08-18 02:11:31 +00:00
|
|
|
|
sshSetup :: SshInput -> [String] -> SshHost -> String -> Maybe String -> Handler Html -> Handler Html
|
|
|
|
|
sshSetup sshinput opts sshhost cmd input a = do
|
|
|
|
|
(transcript, ok) <- liftAssistant $ sshAuthTranscript sshinput opts sshhost cmd input
|
2012-09-04 19:27:06 +00:00
|
|
|
|
if ok
|
2014-05-15 19:15:19 +00:00
|
|
|
|
then do
|
|
|
|
|
liftAssistant $ expireCachedCred $ getLogin sshinput
|
|
|
|
|
a
|
|
|
|
|
else sshErr sshinput transcript
|
2012-09-04 19:27:06 +00:00
|
|
|
|
|
2014-05-15 19:15:19 +00:00
|
|
|
|
sshErr :: SshInput -> String -> Handler Html
|
|
|
|
|
sshErr sshinput msg
|
|
|
|
|
| inputAuthMethod sshinput == CachedPassword =
|
|
|
|
|
ifM (liftAssistant $ isNothing <$> getCachedCred (getLogin sshinput))
|
|
|
|
|
( sshConfigurator $
|
|
|
|
|
$(widgetFile "configurators/ssh/expiredpassword")
|
|
|
|
|
, showerr
|
|
|
|
|
)
|
|
|
|
|
| otherwise = showerr
|
|
|
|
|
where
|
|
|
|
|
showerr = sshConfigurator $
|
|
|
|
|
$(widgetFile "configurators/ssh/error")
|
2012-09-04 19:27:06 +00:00
|
|
|
|
|
2014-05-14 21:13:20 +00:00
|
|
|
|
{- Runs a ssh command, returning a transcript of its output.
|
|
|
|
|
-
|
|
|
|
|
- Depending on the SshInput, avoids using a password, or uses a
|
|
|
|
|
- cached password. ssh is coaxed to use git-annex as SSH_ASKPASS
|
|
|
|
|
- to get the password.
|
|
|
|
|
-}
|
2017-08-18 02:11:31 +00:00
|
|
|
|
sshAuthTranscript :: SshInput -> [String] -> SshHost -> String -> (Maybe String) -> Assistant (String, Bool)
|
|
|
|
|
sshAuthTranscript sshinput opts sshhost cmd input = case inputAuthMethod sshinput of
|
2014-05-14 19:02:18 +00:00
|
|
|
|
ExistingSshKey -> liftIO $ go [passwordprompts 0] Nothing
|
|
|
|
|
CachedPassword -> setupAskPass
|
|
|
|
|
Password -> do
|
|
|
|
|
cacheCred (login, geti inputPassword) (Seconds $ 60 * 10)
|
|
|
|
|
setupAskPass
|
|
|
|
|
where
|
2014-05-15 19:15:19 +00:00
|
|
|
|
login = getLogin sshinput
|
2014-05-14 19:02:18 +00:00
|
|
|
|
geti f = maybe "" T.unpack (f sshinput)
|
|
|
|
|
|
2015-09-03 18:03:08 +00:00
|
|
|
|
go extraopts environ = processTranscript'
|
2017-08-18 02:11:31 +00:00
|
|
|
|
(askPass environ (proc "ssh" (extraopts ++ opts ++ [fromSshHost sshhost, cmd])))
|
2015-09-03 18:03:08 +00:00
|
|
|
|
-- Always provide stdin, even when empty.
|
|
|
|
|
(Just (fromMaybe "" input))
|
|
|
|
|
|
|
|
|
|
{- ssh will only use SSH_ASKPASS when DISPLAY is set and there
|
|
|
|
|
- is no controlling terminal. -}
|
|
|
|
|
askPass environ p = p
|
|
|
|
|
{ env = environ
|
|
|
|
|
#if MIN_VERSION_process(1,3,0)
|
|
|
|
|
, detach_console = True
|
|
|
|
|
, new_session = True
|
|
|
|
|
#endif
|
|
|
|
|
}
|
2014-05-14 19:02:18 +00:00
|
|
|
|
|
|
|
|
|
setupAskPass = do
|
2015-02-28 21:23:13 +00:00
|
|
|
|
program <- liftIO programPath
|
2014-05-14 19:02:18 +00:00
|
|
|
|
v <- getCachedCred login
|
|
|
|
|
liftIO $ case v of
|
|
|
|
|
Nothing -> go [passwordprompts 0] Nothing
|
|
|
|
|
Just pass -> withTmpFile "ssh" $ \passfile h -> do
|
|
|
|
|
hClose h
|
|
|
|
|
writeFileProtected passfile pass
|
2014-06-10 23:20:14 +00:00
|
|
|
|
environ <- getEnvironment
|
|
|
|
|
let environ' = addEntries
|
2014-05-14 19:02:18 +00:00
|
|
|
|
[ ("SSH_ASKPASS", program)
|
|
|
|
|
, (sshAskPassEnv, passfile)
|
|
|
|
|
, ("DISPLAY", ":0")
|
2014-06-10 23:20:14 +00:00
|
|
|
|
] environ
|
|
|
|
|
go [passwordprompts 1] (Just environ')
|
2014-05-14 19:02:18 +00:00
|
|
|
|
|
|
|
|
|
passwordprompts :: Int -> String
|
|
|
|
|
passwordprompts = sshOpt "NumberOfPasswordPrompts" . show
|
|
|
|
|
|
2014-05-15 19:15:19 +00:00
|
|
|
|
getLogin :: SshInput -> Login
|
|
|
|
|
getLogin sshinput = geti inputUsername ++ "@" ++ geti inputHostname
|
|
|
|
|
where
|
|
|
|
|
geti f = maybe "" T.unpack (f sshinput)
|
|
|
|
|
|
2014-04-20 22:38:59 +00:00
|
|
|
|
{- The UUID will be NoUUID when the repository does not already exist,
|
|
|
|
|
- or was not a git-annex repository before. -}
|
2013-10-02 19:54:32 +00:00
|
|
|
|
getConfirmSshR :: SshData -> UUID -> Handler Html
|
|
|
|
|
getConfirmSshR sshdata u
|
|
|
|
|
| u == NoUUID = handlenew
|
|
|
|
|
| otherwise = handleexisting =<< (M.lookup u <$> liftAnnex uuidMap)
|
|
|
|
|
where
|
|
|
|
|
handlenew = sshConfigurator $ do
|
2015-09-09 22:06:49 +00:00
|
|
|
|
cmd <- liftAnnex $ gpgCmd <$> Annex.getGitConfig
|
2013-10-02 19:54:32 +00:00
|
|
|
|
secretkeys <- sortBy (comparing snd) . M.toList
|
2015-09-09 22:06:49 +00:00
|
|
|
|
<$> liftIO (secretKeys cmd)
|
2013-10-02 19:54:32 +00:00
|
|
|
|
$(widgetFile "configurators/ssh/confirm")
|
2014-10-09 18:53:13 +00:00
|
|
|
|
handleexisting Nothing = sshConfigurator $
|
2013-10-02 19:54:32 +00:00
|
|
|
|
-- Not a UUID we know, so prompt about combining.
|
|
|
|
|
$(widgetFile "configurators/ssh/combine")
|
|
|
|
|
handleexisting (Just _) = prepSsh False sshdata $ \sshdata' -> do
|
|
|
|
|
m <- liftAnnex readRemoteLog
|
|
|
|
|
case M.lookup "type" =<< M.lookup u m of
|
|
|
|
|
Just "gcrypt" -> combineExistingGCrypt sshdata' u
|
2014-05-30 18:03:04 +00:00
|
|
|
|
_ -> makeSshRepo ExistingRepo sshdata'
|
2013-10-02 19:54:32 +00:00
|
|
|
|
|
|
|
|
|
{- The user has confirmed they want to combine with a ssh repository,
|
|
|
|
|
- which is not known to us. So it might be using gcrypt. -}
|
|
|
|
|
getCombineSshR :: SshData -> Handler Html
|
|
|
|
|
getCombineSshR sshdata = prepSsh False sshdata $ \sshdata' ->
|
|
|
|
|
sshConfigurator $
|
|
|
|
|
checkExistingGCrypt sshdata' $
|
2014-05-30 18:03:04 +00:00
|
|
|
|
void $ liftH $ makeSshRepo ExistingRepo sshdata'
|
2012-09-02 04:27:48 +00:00
|
|
|
|
|
2013-03-16 16:58:59 +00:00
|
|
|
|
getRetrySshR :: SshData -> Handler ()
|
|
|
|
|
getRetrySshR sshdata = do
|
2014-05-14 19:02:18 +00:00
|
|
|
|
s <- liftAssistant $ testServer $ mkSshInput sshdata
|
2013-10-02 19:54:32 +00:00
|
|
|
|
redirect $ either (const $ ConfirmSshR sshdata NoUUID) (uncurry ConfirmSshR) s
|
2013-03-16 16:58:59 +00:00
|
|
|
|
|
2014-04-20 22:38:59 +00:00
|
|
|
|
{- Making a new git repository. -}
|
2013-06-27 05:15:28 +00:00
|
|
|
|
getMakeSshGitR :: SshData -> Handler Html
|
2014-05-30 18:03:04 +00:00
|
|
|
|
getMakeSshGitR sshdata = prepSsh True sshdata (makeSshRepo NewRepo)
|
2012-09-02 21:32:24 +00:00
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
|
getMakeSshRsyncR :: SshData -> Handler Html
|
2014-05-30 18:03:04 +00:00
|
|
|
|
getMakeSshRsyncR sshdata = prepSsh False (rsyncOnly sshdata) (makeSshRepo NewRepo)
|
2013-10-01 17:43:35 +00:00
|
|
|
|
|
|
|
|
|
rsyncOnly :: SshData -> SshData
|
|
|
|
|
rsyncOnly sshdata = sshdata { sshCapabilities = [RsyncCapable] }
|
2012-09-02 21:32:24 +00:00
|
|
|
|
|
2013-09-29 18:39:10 +00:00
|
|
|
|
getMakeSshGCryptR :: SshData -> RepoKey -> Handler Html
|
2013-10-01 17:43:35 +00:00
|
|
|
|
getMakeSshGCryptR sshdata NoRepoKey = whenGcryptInstalled $
|
|
|
|
|
withNewSecretKey $ getMakeSshGCryptR sshdata . RepoKey
|
|
|
|
|
getMakeSshGCryptR sshdata (RepoKey keyid) = whenGcryptInstalled $
|
2014-05-30 18:03:04 +00:00
|
|
|
|
prepSsh False sshdata $ makeGCryptRepo NewRepo keyid
|
2013-10-01 17:43:35 +00:00
|
|
|
|
|
|
|
|
|
{- Detect if the user entered a location with an existing, known
|
|
|
|
|
- gcrypt repository, and enable it. Otherwise, runs the action. -}
|
|
|
|
|
checkExistingGCrypt :: SshData -> Widget -> Widget
|
2013-10-22 17:32:10 +00:00
|
|
|
|
checkExistingGCrypt sshdata nope = checkGCryptRepoEncryption repourl nope nope $ do
|
|
|
|
|
mu <- liftAnnex $ probeGCryptRemoteUUID repourl
|
|
|
|
|
case mu of
|
|
|
|
|
Just u -> void $ liftH $
|
|
|
|
|
combineExistingGCrypt sshdata u
|
2016-11-16 01:29:54 +00:00
|
|
|
|
Nothing -> giveup "The location contains a gcrypt repository that is not a git-annex special remote. This is not supported."
|
2013-10-01 17:43:35 +00:00
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
|
repourl = genSshUrl sshdata
|
2013-10-01 17:43:35 +00:00
|
|
|
|
|
|
|
|
|
{- Enables an existing gcrypt special remote. -}
|
|
|
|
|
enableGCrypt :: SshData -> RemoteName -> Handler Html
|
2014-05-30 18:49:25 +00:00
|
|
|
|
enableGCrypt sshdata reponame = setupRemote postsetup Nothing Nothing mk
|
|
|
|
|
where
|
|
|
|
|
mk = enableSpecialRemote reponame GCrypt.remote Nothing $
|
|
|
|
|
M.fromList [("gitrepo", genSshUrl sshdata)]
|
|
|
|
|
postsetup _ = redirect DashboardR
|
2013-09-29 18:39:10 +00:00
|
|
|
|
|
2013-10-02 19:54:32 +00:00
|
|
|
|
{- Combining with a gcrypt repository that may not be
|
|
|
|
|
- known in remote.log, so probe the gcrypt repo. -}
|
|
|
|
|
combineExistingGCrypt :: SshData -> UUID -> Handler Html
|
|
|
|
|
combineExistingGCrypt sshdata u = do
|
|
|
|
|
reponame <- liftAnnex $ getGCryptRemoteName u repourl
|
|
|
|
|
enableGCrypt sshdata reponame
|
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
|
repourl = genSshUrl sshdata
|
2013-10-02 19:54:32 +00:00
|
|
|
|
|
2013-10-01 17:43:35 +00:00
|
|
|
|
{- Sets up remote repository for ssh, or directory for rsync. -}
|
|
|
|
|
prepSsh :: Bool -> SshData -> (SshData -> Handler Html) -> Handler Html
|
2014-04-20 22:38:59 +00:00
|
|
|
|
prepSsh needsinit sshdata a
|
2012-09-03 00:43:32 +00:00
|
|
|
|
| needsPubKey sshdata = do
|
2015-07-20 22:38:23 +00:00
|
|
|
|
(sshdata', keypair) <- liftIO $ setupSshKeyPair sshdata
|
2014-04-20 22:38:59 +00:00
|
|
|
|
prepSsh' needsinit sshdata sshdata' (Just keypair) a
|
2012-12-06 21:09:08 +00:00
|
|
|
|
| sshPort sshdata /= 22 = do
|
|
|
|
|
sshdata' <- liftIO $ setSshConfig sshdata []
|
2014-04-20 22:38:59 +00:00
|
|
|
|
prepSsh' needsinit sshdata sshdata' Nothing a
|
|
|
|
|
| otherwise = prepSsh' needsinit sshdata sshdata Nothing a
|
2012-09-03 00:43:32 +00:00
|
|
|
|
|
2013-10-01 17:43:35 +00:00
|
|
|
|
prepSsh' :: Bool -> SshData -> SshData -> Maybe SshKeyPair -> (SshData -> Handler Html) -> Handler Html
|
2015-07-20 22:38:23 +00:00
|
|
|
|
prepSsh' needsinit origsshdata sshdata keypair a
|
2015-07-25 21:02:22 +00:00
|
|
|
|
| hasCapability sshdata PushCapable = do
|
|
|
|
|
{- To ensure the repository is initialized, try to push the
|
|
|
|
|
- git-annex branch to it. Then git-annex-shell will see
|
|
|
|
|
- the branch and auto-initialize. -}
|
2015-07-27 15:36:39 +00:00
|
|
|
|
when needsinit $ do
|
|
|
|
|
void $ liftAnnex $ inRepo $ Git.Command.runBool
|
|
|
|
|
[ Param "push"
|
|
|
|
|
, Param (genSshUrl sshdata)
|
|
|
|
|
, Param (fromRef Annex.Branch.name)
|
|
|
|
|
]
|
2015-07-25 21:02:22 +00:00
|
|
|
|
a sshdata
|
2015-07-20 22:38:23 +00:00
|
|
|
|
| otherwise = sshSetup (mkSshInput origsshdata)
|
2017-08-18 02:11:31 +00:00
|
|
|
|
[ "-p", show (sshPort origsshdata)
|
|
|
|
|
]
|
|
|
|
|
(genSshHost (sshHostName origsshdata) (sshUserName origsshdata))
|
|
|
|
|
remoteCommand
|
|
|
|
|
Nothing (a sshdata)
|
2012-10-31 06:34:03 +00:00
|
|
|
|
where
|
|
|
|
|
remotedir = T.unpack $ sshDirectory sshdata
|
2013-04-23 00:24:53 +00:00
|
|
|
|
remoteCommand = shellWrap $ intercalate "&&" $ catMaybes
|
2012-10-31 06:34:03 +00:00
|
|
|
|
[ Just $ "mkdir -p " ++ shellEscape remotedir
|
|
|
|
|
, Just $ "cd " ++ shellEscape remotedir
|
2014-04-20 22:38:59 +00:00
|
|
|
|
, if rsynconly then Nothing else Just $ unwords
|
|
|
|
|
[ "if [ ! -d .git ]; then"
|
|
|
|
|
, wrapCommand "git init --bare --shared"
|
|
|
|
|
, "&&"
|
|
|
|
|
, wrapCommand "git config receive.denyNonFastforwards"
|
|
|
|
|
, ";fi"
|
|
|
|
|
]
|
|
|
|
|
, if needsinit then Just (wrapCommand "git annex init") else Nothing
|
2013-10-01 20:16:38 +00:00
|
|
|
|
, if needsPubKey origsshdata
|
|
|
|
|
then addAuthorizedKeysCommand (hasCapability origsshdata GitAnnexShellCapable) remotedir . sshPubKey <$> keypair
|
2012-10-31 06:34:03 +00:00
|
|
|
|
else Nothing
|
|
|
|
|
]
|
2013-10-01 20:16:38 +00:00
|
|
|
|
rsynconly = onlyCapability origsshdata RsyncCapable
|
2013-10-01 17:43:35 +00:00
|
|
|
|
|
2014-05-30 18:03:04 +00:00
|
|
|
|
makeSshRepo :: RepoStatus -> SshData -> Handler Html
|
|
|
|
|
makeSshRepo rs sshdata
|
2014-05-22 18:53:00 +00:00
|
|
|
|
| onlyCapability sshdata RsyncCapable = setupCloudRemote TransferGroup Nothing mk
|
2014-05-30 18:03:04 +00:00
|
|
|
|
| otherwise = makeSshRepoConnection rs mk setup
|
2014-04-20 19:10:29 +00:00
|
|
|
|
where
|
2014-05-22 18:53:00 +00:00
|
|
|
|
mk = makeSshRemote sshdata
|
|
|
|
|
-- Record the location of the ssh remote in the remote log, so it
|
|
|
|
|
-- can easily be enabled elsewhere using the webapp.
|
|
|
|
|
setup r = do
|
|
|
|
|
m <- readRemoteLog
|
|
|
|
|
let c = fromMaybe M.empty (M.lookup (Remote.uuid r) m)
|
|
|
|
|
let c' = M.insert "location" (genSshUrl sshdata) $
|
|
|
|
|
M.insert "type" "git" $
|
|
|
|
|
M.insert "name" (fromMaybe (Remote.name r) (M.lookup "name" c)) c
|
|
|
|
|
configSet (Remote.uuid r) c'
|
|
|
|
|
|
2014-05-30 18:03:04 +00:00
|
|
|
|
makeSshRepoConnection :: RepoStatus -> Annex RemoteName -> (Remote -> Annex ()) -> Handler Html
|
|
|
|
|
makeSshRepoConnection rs mk setup = setupRemote postsetup mgroup Nothing mk
|
2014-04-20 19:30:39 +00:00
|
|
|
|
where
|
2014-05-30 18:03:04 +00:00
|
|
|
|
mgroup = case rs of
|
|
|
|
|
NewRepo -> Just TransferGroup
|
|
|
|
|
ExistingRepo -> Nothing
|
2014-05-22 18:53:00 +00:00
|
|
|
|
postsetup r = do
|
2014-04-20 19:30:39 +00:00
|
|
|
|
liftAssistant $ sendRemoteControl RELOAD
|
2014-05-22 18:53:00 +00:00
|
|
|
|
liftAnnex $ setup r
|
2014-05-30 18:17:20 +00:00
|
|
|
|
case rs of
|
|
|
|
|
NewRepo -> redirect $ EditNewRepositoryR (Remote.uuid r)
|
|
|
|
|
ExistingRepo -> redirect DashboardR
|
2014-04-20 19:30:39 +00:00
|
|
|
|
|
2014-05-30 18:03:04 +00:00
|
|
|
|
makeGCryptRepo :: RepoStatus -> KeyId -> SshData -> Handler Html
|
|
|
|
|
makeGCryptRepo rs keyid sshdata = makeSshRepoConnection rs mk (const noop)
|
2014-05-22 18:53:00 +00:00
|
|
|
|
where
|
|
|
|
|
mk = makeGCryptRemote (sshRepoName sshdata) (genSshUrl sshdata) keyid
|
2012-09-02 21:32:24 +00:00
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
|
getAddRsyncNetR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
|
getAddRsyncNetR = postAddRsyncNetR
|
2013-06-27 05:15:28 +00:00
|
|
|
|
postAddRsyncNetR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
|
postAddRsyncNetR = do
|
2013-10-14 16:19:11 +00:00
|
|
|
|
((result, form), enctype) <- runFormPostNoToken $
|
2014-04-18 00:07:09 +00:00
|
|
|
|
renderBootstrap3 bootstrapFormLayout $ sshInputAForm hostnamefield $
|
2014-05-14 19:02:18 +00:00
|
|
|
|
SshInput Nothing Nothing Password Nothing Nothing 22
|
2013-09-26 20:09:45 +00:00
|
|
|
|
let showform status = inpage $
|
|
|
|
|
$(widgetFile "configurators/rsync.net/add")
|
2012-09-03 04:39:55 +00:00
|
|
|
|
case result of
|
2012-09-13 20:47:44 +00:00
|
|
|
|
FormSuccess sshinput
|
2013-09-27 20:21:56 +00:00
|
|
|
|
| isRsyncNet (inputHostname sshinput) ->
|
|
|
|
|
go sshinput
|
2012-09-13 20:47:44 +00:00
|
|
|
|
| otherwise ->
|
|
|
|
|
showform $ UnusableServer
|
|
|
|
|
"That is not a rsync.net host name."
|
2012-09-03 04:39:55 +00:00
|
|
|
|
_ -> showform UntestedServer
|
2012-12-03 02:33:30 +00:00
|
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
|
inpage = page "Add a Rsync.net repository" (Just Configuration)
|
2013-04-26 03:44:55 +00:00
|
|
|
|
hostnamefield = textField `withExpandableNote` ("Help", help)
|
2012-12-03 02:33:30 +00:00
|
|
|
|
help = [whamlet|
|
2013-04-26 03:44:55 +00:00
|
|
|
|
<div>
|
|
|
|
|
When you sign up for a Rsync.net account, you should receive an #
|
|
|
|
|
email from them with the host name and user name to put here.
|
|
|
|
|
<div>
|
|
|
|
|
The host name will be something like "usw-s001.rsync.net", and the #
|
|
|
|
|
user name something like "7491"
|
2012-12-03 02:33:30 +00:00
|
|
|
|
|]
|
2013-09-27 20:21:56 +00:00
|
|
|
|
go sshinput = do
|
2013-09-26 20:09:45 +00:00
|
|
|
|
let reponame = genSshRepoName "rsync.net"
|
|
|
|
|
(maybe "" T.unpack $ inputDirectory sshinput)
|
2014-05-14 19:02:18 +00:00
|
|
|
|
|
2013-09-27 20:21:56 +00:00
|
|
|
|
prepRsyncNet sshinput reponame $ \sshdata -> inpage $
|
2013-10-01 17:43:35 +00:00
|
|
|
|
checkExistingGCrypt sshdata $ do
|
2015-09-09 22:06:49 +00:00
|
|
|
|
cmd <- liftAnnex $ gpgCmd <$> Annex.getGitConfig
|
2013-09-27 20:21:56 +00:00
|
|
|
|
secretkeys <- sortBy (comparing snd) . M.toList
|
2015-09-09 22:06:49 +00:00
|
|
|
|
<$> liftIO (secretKeys cmd)
|
2013-09-27 20:21:56 +00:00
|
|
|
|
$(widgetFile "configurators/rsync.net/encrypt")
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
2013-09-26 20:09:45 +00:00
|
|
|
|
getMakeRsyncNetSharedR :: SshData -> Handler Html
|
2014-05-30 18:03:04 +00:00
|
|
|
|
getMakeRsyncNetSharedR = makeSshRepo NewRepo . rsyncOnly
|
2013-09-26 20:09:45 +00:00
|
|
|
|
|
2014-05-30 18:03:04 +00:00
|
|
|
|
{- Make a new gcrypt special remote on rsync.net. -}
|
2013-09-26 20:09:45 +00:00
|
|
|
|
getMakeRsyncNetGCryptR :: SshData -> RepoKey -> Handler Html
|
2013-09-26 22:42:54 +00:00
|
|
|
|
getMakeRsyncNetGCryptR sshdata NoRepoKey = whenGcryptInstalled $
|
|
|
|
|
withNewSecretKey $ getMakeRsyncNetGCryptR sshdata . RepoKey
|
2013-10-02 04:33:40 +00:00
|
|
|
|
getMakeRsyncNetGCryptR sshdata (RepoKey keyid) = whenGcryptInstalled $
|
2017-08-18 02:11:31 +00:00
|
|
|
|
sshSetup (mkSshInput sshdata) [] sshhost gitinit Nothing $
|
2014-05-30 18:03:04 +00:00
|
|
|
|
makeGCryptRepo NewRepo keyid sshdata
|
2013-09-26 20:09:45 +00:00
|
|
|
|
where
|
|
|
|
|
sshhost = genSshHost (sshHostName sshdata) (sshUserName sshdata)
|
|
|
|
|
gitinit = "git init --bare " ++ T.unpack (sshDirectory sshdata)
|
|
|
|
|
|
2013-09-27 03:28:25 +00:00
|
|
|
|
enableRsyncNet :: SshInput -> String -> Handler Html
|
|
|
|
|
enableRsyncNet sshinput reponame =
|
2014-05-30 18:03:04 +00:00
|
|
|
|
prepRsyncNet sshinput reponame $ makeSshRepo ExistingRepo . rsyncOnly
|
2013-09-27 03:28:25 +00:00
|
|
|
|
|
2013-09-27 20:21:56 +00:00
|
|
|
|
enableRsyncNetGCrypt :: SshInput -> RemoteName -> Handler Html
|
2013-09-27 03:28:25 +00:00
|
|
|
|
enableRsyncNetGCrypt sshinput reponame =
|
2013-10-22 17:32:10 +00:00
|
|
|
|
prepRsyncNet sshinput reponame $ \sshdata -> whenGcryptInstalled $
|
|
|
|
|
checkGCryptRepoEncryption (genSshUrl sshdata) notencrypted notinstalled $
|
2013-10-01 17:43:35 +00:00
|
|
|
|
enableGCrypt sshdata reponame
|
2013-09-27 05:03:50 +00:00
|
|
|
|
where
|
2016-11-16 01:29:54 +00:00
|
|
|
|
notencrypted = giveup "Unexpectedly found a non-encrypted git repository, instead of the expected encrypted git repository."
|
2013-10-22 17:32:10 +00:00
|
|
|
|
notinstalled = error "internal"
|
2013-09-26 20:09:45 +00:00
|
|
|
|
|
2014-02-14 19:42:35 +00:00
|
|
|
|
{- Prepares rsync.net ssh key and creates the directory that will be
|
|
|
|
|
- used on rsync.net. If successful, runs an action with its SshData.
|
|
|
|
|
-
|
|
|
|
|
- To append the ssh key to rsync.net's authorized_keys, their
|
|
|
|
|
- documentation recommends a dd methodd, where the line is fed
|
|
|
|
|
- in to ssh over stdin.
|
|
|
|
|
-}
|
2013-09-26 20:09:45 +00:00
|
|
|
|
prepRsyncNet :: SshInput -> String -> (SshData -> Handler Html) -> Handler Html
|
|
|
|
|
prepRsyncNet sshinput reponame a = do
|
2012-12-06 21:09:08 +00:00
|
|
|
|
knownhost <- liftIO $ maybe (return False) knownHost (inputHostname sshinput)
|
2015-07-20 22:38:23 +00:00
|
|
|
|
(sshdata, keypair) <- liftIO $ setupSshKeyPair $
|
2012-09-13 20:47:44 +00:00
|
|
|
|
(mkSshData sshinput)
|
2012-10-31 20:14:52 +00:00
|
|
|
|
{ sshRepoName = reponame
|
2012-09-13 20:47:44 +00:00
|
|
|
|
, needsPubKey = True
|
2013-09-29 18:39:10 +00:00
|
|
|
|
, sshCapabilities = [RsyncCapable]
|
2012-09-13 20:47:44 +00:00
|
|
|
|
}
|
2014-02-14 19:42:35 +00:00
|
|
|
|
let sshhost = genSshHost (sshHostName sshdata) (sshUserName sshdata)
|
2017-08-18 02:11:31 +00:00
|
|
|
|
let torsyncnet
|
|
|
|
|
| knownhost = []
|
|
|
|
|
| otherwise = [sshOpt "StrictHostKeyChecking" "no"]
|
2012-09-13 20:47:44 +00:00
|
|
|
|
{- I'd prefer to separate commands with && , but
|
2014-02-14 19:42:35 +00:00
|
|
|
|
- rsync.net's shell does not support that. -}
|
2013-04-23 00:24:53 +00:00
|
|
|
|
let remotecommand = intercalate ";"
|
2012-09-13 20:47:44 +00:00
|
|
|
|
[ "mkdir -p .ssh"
|
|
|
|
|
, "touch .ssh/authorized_keys"
|
|
|
|
|
, "dd of=.ssh/authorized_keys oflag=append conv=notrunc"
|
|
|
|
|
, "mkdir -p " ++ T.unpack (sshDirectory sshdata)
|
|
|
|
|
]
|
2017-08-18 02:11:31 +00:00
|
|
|
|
sshSetup sshinput torsyncnet sshhost remotecommand
|
|
|
|
|
(Just $ sshPubKey keypair) (a sshdata)
|
2012-09-13 20:47:44 +00:00
|
|
|
|
|
|
|
|
|
isRsyncNet :: Maybe Text -> Bool
|
|
|
|
|
isRsyncNet Nothing = False
|
|
|
|
|
isRsyncNet (Just host) = ".rsync.net" `T.isSuffixOf` T.toLower host
|
2015-07-20 22:38:23 +00:00
|
|
|
|
|
2015-07-27 20:03:22 +00:00
|
|
|
|
data GitLabUrl = GitLabUrl { unGitLabUrl :: Text }
|
2015-07-20 22:38:23 +00:00
|
|
|
|
|
|
|
|
|
badGitLabUrl :: Text
|
|
|
|
|
badGitLabUrl = "Bad SSH clone url. Expected something like: git@gitlab.com:yourlogin/annex.git"
|
|
|
|
|
|
|
|
|
|
parseGitLabUrl :: GitLabUrl -> Maybe SshData
|
|
|
|
|
parseGitLabUrl (GitLabUrl t) =
|
|
|
|
|
let (u, r) = separate (== '@') (T.unpack t)
|
|
|
|
|
(h, p) = separate (== ':') r
|
|
|
|
|
in if null u || null h || null p
|
|
|
|
|
then Nothing
|
|
|
|
|
else Just $ SshData
|
|
|
|
|
{ sshHostName = T.pack h
|
|
|
|
|
, sshUserName = Just (T.pack u)
|
|
|
|
|
, sshDirectory = T.pack p
|
|
|
|
|
, sshRepoName = genSshRepoName h p
|
|
|
|
|
, sshPort = 22
|
|
|
|
|
, needsPubKey = False
|
|
|
|
|
, sshCapabilities =
|
|
|
|
|
[ GitAnnexShellCapable
|
|
|
|
|
, GitCapable
|
|
|
|
|
, PushCapable
|
|
|
|
|
]
|
|
|
|
|
, sshRepoUrl = Just (T.unpack t)
|
|
|
|
|
}
|
|
|
|
|
|
2015-07-27 20:03:22 +00:00
|
|
|
|
isGitLab :: SshData -> Bool
|
|
|
|
|
isGitLab d = T.pack "gitlab.com" `T.isSuffixOf` (T.toLower (sshHostName d))
|
|
|
|
|
|
|
|
|
|
toGitLabUrl :: SshData -> GitLabUrl
|
|
|
|
|
toGitLabUrl d = GitLabUrl $ T.concat
|
|
|
|
|
[ fromMaybe (T.pack "git") (sshUserName d)
|
|
|
|
|
, T.pack "@"
|
|
|
|
|
, sshHostName d
|
|
|
|
|
, T.pack ":"
|
|
|
|
|
, sshDirectory d
|
|
|
|
|
]
|
|
|
|
|
|
2015-07-20 22:38:23 +00:00
|
|
|
|
{- Try to ssh into the gitlab server, verify we can access the repository,
|
|
|
|
|
- and get the uuid of the repository, if it already has one.
|
|
|
|
|
-
|
|
|
|
|
- A repository on gitlab won't be initialized as a git-annex repo
|
|
|
|
|
- unless a git-annex branch was already pushed to it. So, if
|
|
|
|
|
- git-annex-shell fails to work that's probably why; verify if
|
|
|
|
|
- the server is letting us ssh in by running git send-pack
|
|
|
|
|
- (in dry run mode). -}
|
|
|
|
|
testGitLabUrl :: GitLabUrl -> Annex (ServerStatus, Maybe SshData, UUID)
|
|
|
|
|
testGitLabUrl glu = case parseGitLabUrl glu of
|
|
|
|
|
Nothing -> return (UnusableServer badGitLabUrl, Nothing, NoUUID)
|
2015-07-27 15:03:58 +00:00
|
|
|
|
Just sshdata ->
|
|
|
|
|
checkor sshdata $ do
|
|
|
|
|
(sshdata', keypair) <- liftIO $ setupSshKeyPair sshdata
|
|
|
|
|
checkor sshdata' $
|
|
|
|
|
return (ServerNeedsPubKey (sshPubKey keypair), Just sshdata', NoUUID)
|
|
|
|
|
where
|
|
|
|
|
checkor sshdata ora = do
|
2015-07-20 22:38:23 +00:00
|
|
|
|
u <- probeuuid sshdata
|
|
|
|
|
if u /= NoUUID
|
|
|
|
|
then return (UsableServer (sshCapabilities sshdata), Just sshdata, u)
|
|
|
|
|
else ifM (verifysshworks sshdata)
|
|
|
|
|
( return (UsableServer (sshCapabilities sshdata), Just sshdata, NoUUID)
|
2015-07-27 15:03:58 +00:00
|
|
|
|
, ora
|
2015-07-20 22:38:23 +00:00
|
|
|
|
)
|
|
|
|
|
probeuuid sshdata = do
|
|
|
|
|
r <- inRepo $ Git.Construct.fromRemoteLocation (fromJust $ sshRepoUrl sshdata)
|
|
|
|
|
getUncachedUUID . either (const r) fst <$>
|
2017-02-15 19:08:46 +00:00
|
|
|
|
Remote.Helper.Ssh.onRemote NoConsumeStdin r
|
|
|
|
|
(Git.Config.fromPipe r, return (Left $ error "configlist failed"))
|
|
|
|
|
"configlist" [] []
|
2015-07-20 22:38:23 +00:00
|
|
|
|
verifysshworks sshdata = inRepo $ Git.Command.runBool
|
|
|
|
|
[ Param "send-pack"
|
|
|
|
|
, Param (fromJust $ sshRepoUrl sshdata)
|
|
|
|
|
, Param "--dry-run"
|
|
|
|
|
, Param "--force"
|
|
|
|
|
, Param (fromRef Annex.Branch.name)
|
|
|
|
|
]
|
|
|
|
|
|
2015-07-27 20:03:22 +00:00
|
|
|
|
gitLabUrlAForm :: Maybe GitLabUrl -> AForm Handler GitLabUrl
|
|
|
|
|
gitLabUrlAForm defval = GitLabUrl <$> areq check_input (bfs "SSH clone url") (unGitLabUrl <$> defval)
|
2015-07-20 22:38:23 +00:00
|
|
|
|
where
|
|
|
|
|
check_input = checkBool (isJust . parseGitLabUrl . GitLabUrl)
|
|
|
|
|
badGitLabUrl textField
|
|
|
|
|
|
|
|
|
|
getAddGitLabR :: Handler Html
|
|
|
|
|
getAddGitLabR = postAddGitLabR
|
|
|
|
|
postAddGitLabR :: Handler Html
|
2015-07-27 20:03:22 +00:00
|
|
|
|
postAddGitLabR = promptGitLab Nothing
|
|
|
|
|
|
|
|
|
|
promptGitLab :: Maybe GitLabUrl -> Handler Html
|
|
|
|
|
promptGitLab defval = sshConfigurator $ do
|
2015-07-20 22:38:23 +00:00
|
|
|
|
((result, form), enctype) <- liftH $
|
2015-07-27 20:03:22 +00:00
|
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $
|
|
|
|
|
gitLabUrlAForm defval
|
2015-07-20 22:38:23 +00:00
|
|
|
|
case result of
|
|
|
|
|
FormSuccess gitlaburl -> do
|
|
|
|
|
(status, msshdata, u) <- liftAnnex $ testGitLabUrl gitlaburl
|
|
|
|
|
case (status, msshdata) of
|
|
|
|
|
(UsableServer _, Just sshdata) ->
|
|
|
|
|
liftH $ redirect $ ConfirmSshR sshdata u
|
|
|
|
|
_ -> showform form enctype status
|
|
|
|
|
_ -> showform form enctype UntestedServer
|
|
|
|
|
where
|
|
|
|
|
showform form enctype status = $(widgetFile "configurators/gitlab.com/add")
|
2015-07-27 20:03:22 +00:00
|
|
|
|
|
|
|
|
|
enableGitLab :: SshData -> Handler Html
|
|
|
|
|
enableGitLab = promptGitLab . Just . toGitLabUrl
|