webapp: Allow user to specify the ssh port when setting up a remote.
This commit is contained in:
parent
25bc68d764
commit
551924e6be
6 changed files with 77 additions and 36 deletions
|
@ -60,6 +60,7 @@ pairMsgToSshData msg = do
|
||||||
, sshUserName = Just (T.pack $ remoteUserName d)
|
, sshUserName = Just (T.pack $ remoteUserName d)
|
||||||
, sshDirectory = T.pack dir
|
, sshDirectory = T.pack dir
|
||||||
, sshRepoName = genSshRepoName hostname dir
|
, sshRepoName = genSshRepoName hostname dir
|
||||||
|
, sshPort = 22
|
||||||
, needsPubKey = True
|
, needsPubKey = True
|
||||||
, rsyncOnly = False
|
, rsyncOnly = False
|
||||||
}
|
}
|
||||||
|
|
|
@ -24,6 +24,7 @@ data SshData = SshData
|
||||||
, sshUserName :: Maybe Text
|
, sshUserName :: Maybe Text
|
||||||
, sshDirectory :: Text
|
, sshDirectory :: Text
|
||||||
, sshRepoName :: String
|
, sshRepoName :: String
|
||||||
|
, sshPort :: Int
|
||||||
, needsPubKey :: Bool
|
, needsPubKey :: Bool
|
||||||
, rsyncOnly :: Bool
|
, rsyncOnly :: Bool
|
||||||
}
|
}
|
||||||
|
@ -188,7 +189,6 @@ genSshKeyPair = withTempDir "git-annex-keygen" $ \dir -> do
|
||||||
setupSshKeyPair :: SshKeyPair -> SshData -> IO SshData
|
setupSshKeyPair :: SshKeyPair -> SshData -> IO SshData
|
||||||
setupSshKeyPair sshkeypair sshdata = do
|
setupSshKeyPair sshkeypair sshdata = do
|
||||||
sshdir <- sshDir
|
sshdir <- sshDir
|
||||||
let configfile = sshdir </> "config"
|
|
||||||
createDirectoryIfMissing True sshdir
|
createDirectoryIfMissing True sshdir
|
||||||
|
|
||||||
unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $ do
|
unlessM (doesFileExist $ sshdir </> sshprivkeyfile) $ do
|
||||||
|
@ -200,25 +200,39 @@ setupSshKeyPair sshkeypair sshdata = do
|
||||||
unlessM (doesFileExist $ sshdir </> sshpubkeyfile) $
|
unlessM (doesFileExist $ sshdir </> sshpubkeyfile) $
|
||||||
writeFile (sshdir </> sshpubkeyfile) (sshPubKey sshkeypair)
|
writeFile (sshdir </> sshpubkeyfile) (sshPubKey sshkeypair)
|
||||||
|
|
||||||
|
setSshConfig sshdata
|
||||||
|
[ ("IdentityFile", "~/.ssh/" ++ sshprivkeyfile) ]
|
||||||
|
where
|
||||||
|
sshprivkeyfile = "key." ++ mangleSshHostName sshdata
|
||||||
|
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"
|
||||||
unlessM (catchBoolIO $ isInfixOf mangledhost <$> readFile configfile) $
|
unlessM (catchBoolIO $ isInfixOf mangledhost <$> readFile configfile) $
|
||||||
appendFile configfile $ unlines
|
appendFile configfile $ unlines $
|
||||||
[ ""
|
[ ""
|
||||||
, "# Added automatically by git-annex"
|
, "# Added automatically by git-annex"
|
||||||
, "Host " ++ mangledhost
|
, "Host " ++ mangledhost
|
||||||
, "\tHostname " ++ T.unpack (sshHostName sshdata)
|
] ++ map (\(k, v) -> "\t" ++ k ++ " " ++ v)
|
||||||
, "\tIdentityFile ~/.ssh/" ++ sshprivkeyfile
|
(settings ++ config)
|
||||||
]
|
|
||||||
|
|
||||||
return $ sshdata { sshHostName = T.pack mangledhost }
|
return $ sshdata { sshHostName = T.pack mangledhost }
|
||||||
where
|
where
|
||||||
sshprivkeyfile = "key." ++ mangledhost
|
mangledhost = mangleSshHostName sshdata
|
||||||
sshpubkeyfile = sshprivkeyfile ++ ".pub"
|
settings =
|
||||||
mangledhost = mangleSshHostName
|
[ ("Hostname", T.unpack $ sshHostName sshdata)
|
||||||
(T.unpack $ sshHostName sshdata)
|
, ("Port", show $ sshPort sshdata)
|
||||||
(T.unpack <$> sshUserName sshdata)
|
]
|
||||||
|
|
||||||
mangleSshHostName :: String -> Maybe String -> String
|
mangleSshHostName :: SshData -> String
|
||||||
mangleSshHostName host user = "git-annex-" ++ host ++ (maybe "-" ('-':) user)
|
mangleSshHostName sshdata = "git-annex-" ++ host ++ (maybe "-" ('-':) user)
|
||||||
|
where
|
||||||
|
host = T.unpack $ sshHostName sshdata
|
||||||
|
user = T.unpack <$> sshUserName sshdata
|
||||||
|
|
||||||
unMangleSshHostName :: String -> String
|
unMangleSshHostName :: String -> String
|
||||||
unMangleSshHostName h
|
unMangleSshHostName h
|
||||||
|
|
|
@ -27,9 +27,10 @@ sshConfigurator :: Widget -> Handler RepHtml
|
||||||
sshConfigurator = page "Add a remote server" (Just Config)
|
sshConfigurator = page "Add a remote server" (Just Config)
|
||||||
|
|
||||||
data SshInput = SshInput
|
data SshInput = SshInput
|
||||||
{ hostname :: Maybe Text
|
{ inputHostname :: Maybe Text
|
||||||
, username :: Maybe Text
|
, inputUsername :: Maybe Text
|
||||||
, directory :: Maybe Text
|
, inputDirectory :: Maybe Text
|
||||||
|
, inputPort :: Int
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
@ -37,21 +38,23 @@ data SshInput = SshInput
|
||||||
- the result of such a form into a SshData. -}
|
- the result of such a form into a SshData. -}
|
||||||
mkSshData :: SshInput -> SshData
|
mkSshData :: SshInput -> SshData
|
||||||
mkSshData s = SshData
|
mkSshData s = SshData
|
||||||
{ sshHostName = fromMaybe "" $ hostname s
|
{ sshHostName = fromMaybe "" $ inputHostname s
|
||||||
, sshUserName = username s
|
, sshUserName = inputUsername s
|
||||||
, sshDirectory = fromMaybe "" $ directory s
|
, sshDirectory = fromMaybe "" $ inputDirectory s
|
||||||
, sshRepoName = genSshRepoName
|
, sshRepoName = genSshRepoName
|
||||||
(T.unpack $ fromJust $ hostname s)
|
(T.unpack $ fromJust $ inputHostname s)
|
||||||
(maybe "" T.unpack $ directory s)
|
(maybe "" T.unpack $ inputDirectory s)
|
||||||
|
, sshPort = inputPort s
|
||||||
, needsPubKey = False
|
, needsPubKey = False
|
||||||
, rsyncOnly = False
|
, rsyncOnly = False
|
||||||
}
|
}
|
||||||
|
|
||||||
sshInputAForm :: (Field WebApp WebApp Text) -> SshInput -> AForm WebApp WebApp SshInput
|
sshInputAForm :: (Field WebApp WebApp Text) -> SshInput -> AForm WebApp WebApp SshInput
|
||||||
sshInputAForm hostnamefield def = SshInput
|
sshInputAForm hostnamefield def = SshInput
|
||||||
<$> aopt check_hostname "Host name" (Just $ hostname def)
|
<$> aopt check_hostname "Host name" (Just $ inputHostname def)
|
||||||
<*> aopt check_username "User name" (Just $ username def)
|
<*> aopt check_username "User name" (Just $ inputUsername def)
|
||||||
<*> aopt textField "Directory" (Just $ Just $ fromMaybe (T.pack gitAnnexAssistantDefaultDir) $ directory def)
|
<*> aopt textField "Directory" (Just $ Just $ fromMaybe (T.pack gitAnnexAssistantDefaultDir) $ inputDirectory def)
|
||||||
|
<*> areq intField "Port" (Just $ inputPort def)
|
||||||
where
|
where
|
||||||
check_hostname = checkM (liftIO . checkdns) hostnamefield
|
check_hostname = checkM (liftIO . checkdns) hostnamefield
|
||||||
checkdns t = do
|
checkdns t = do
|
||||||
|
@ -90,7 +93,7 @@ getAddSshR = sshConfigurator $ do
|
||||||
u <- liftIO $ T.pack <$> myUserName
|
u <- liftIO $ T.pack <$> myUserName
|
||||||
((result, form), enctype) <- lift $
|
((result, form), enctype) <- lift $
|
||||||
runFormGet $ renderBootstrap $ sshInputAForm textField $
|
runFormGet $ renderBootstrap $ sshInputAForm textField $
|
||||||
SshInput Nothing (Just u) Nothing
|
SshInput Nothing (Just u) Nothing 22
|
||||||
case result of
|
case result of
|
||||||
FormSuccess sshinput -> do
|
FormSuccess sshinput -> do
|
||||||
s <- liftIO $ testServer sshinput
|
s <- liftIO $ testServer sshinput
|
||||||
|
@ -118,7 +121,7 @@ getEnableRsyncR u = do
|
||||||
runFormGet $ renderBootstrap $ sshInputAForm textField sshinput
|
runFormGet $ renderBootstrap $ sshInputAForm textField sshinput
|
||||||
case result of
|
case result of
|
||||||
FormSuccess sshinput'
|
FormSuccess sshinput'
|
||||||
| isRsyncNet (hostname sshinput') ->
|
| isRsyncNet (inputHostname sshinput') ->
|
||||||
void $ lift $ makeRsyncNet sshinput' reponame (const noop)
|
void $ lift $ makeRsyncNet sshinput' reponame (const noop)
|
||||||
| otherwise -> do
|
| otherwise -> do
|
||||||
s <- liftIO $ testServer sshinput'
|
s <- liftIO $ testServer sshinput'
|
||||||
|
@ -147,9 +150,10 @@ parseSshRsyncUrl :: String -> Maybe SshInput
|
||||||
parseSshRsyncUrl u
|
parseSshRsyncUrl u
|
||||||
| not (rsyncUrlIsShell u) = Nothing
|
| not (rsyncUrlIsShell u) = Nothing
|
||||||
| otherwise = Just $ SshInput
|
| otherwise = Just $ SshInput
|
||||||
{ hostname = val $ unMangleSshHostName host
|
{ inputHostname = val $ unMangleSshHostName host
|
||||||
, username = if null user then Nothing else val user
|
, inputUsername = if null user then Nothing else val user
|
||||||
, directory = val dir
|
, inputDirectory = val dir
|
||||||
|
, inputPort = 22
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
val = Just . T.pack
|
val = Just . T.pack
|
||||||
|
@ -170,9 +174,9 @@ parseSshRsyncUrl u
|
||||||
- present, while git-annex-shell is not in PATH.
|
- present, while git-annex-shell is not in PATH.
|
||||||
-}
|
-}
|
||||||
testServer :: SshInput -> IO (Either ServerStatus SshData)
|
testServer :: SshInput -> IO (Either ServerStatus SshData)
|
||||||
testServer (SshInput { hostname = Nothing }) = return $
|
testServer (SshInput { inputHostname = Nothing }) = return $
|
||||||
Left $ UnusableServer "Please enter a host name."
|
Left $ UnusableServer "Please enter a host name."
|
||||||
testServer sshinput@(SshInput { hostname = Just hn }) = do
|
testServer sshinput@(SshInput { inputHostname = Just hn }) = do
|
||||||
status <- probe [sshOpt "NumberOfPasswordPrompts" "0"]
|
status <- probe [sshOpt "NumberOfPasswordPrompts" "0"]
|
||||||
if usable status
|
if usable status
|
||||||
then ret status False
|
then ret status False
|
||||||
|
@ -200,7 +204,10 @@ testServer sshinput@(SshInput { hostname = Just hn }) = do
|
||||||
- Otherwise, trust the host key. -}
|
- Otherwise, trust the host key. -}
|
||||||
[ if knownhost then "" else sshOpt "StrictHostKeyChecking" "no"
|
[ if knownhost then "" else sshOpt "StrictHostKeyChecking" "no"
|
||||||
, "-n" -- don't read from stdin
|
, "-n" -- don't read from stdin
|
||||||
, genSshHost (fromJust $ hostname sshinput) (username sshinput)
|
, "-p", show (inputPort sshinput)
|
||||||
|
, genSshHost
|
||||||
|
(fromJust $ inputHostname sshinput)
|
||||||
|
(inputUsername sshinput)
|
||||||
, remotecommand
|
, remotecommand
|
||||||
]
|
]
|
||||||
parsetranscript . fst <$> sshTranscript sshopts ""
|
parsetranscript . fst <$> sshTranscript sshopts ""
|
||||||
|
@ -248,6 +255,9 @@ makeSsh rsync setup sshdata
|
||||||
keypair <- liftIO genSshKeyPair
|
keypair <- liftIO genSshKeyPair
|
||||||
sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
|
sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
|
||||||
makeSsh' rsync setup sshdata' (Just keypair)
|
makeSsh' rsync setup sshdata' (Just keypair)
|
||||||
|
| sshPort sshdata /= 22 = do
|
||||||
|
sshdata' <- liftIO $ setSshConfig sshdata []
|
||||||
|
makeSsh' rsync setup sshdata' Nothing
|
||||||
| otherwise = makeSsh' rsync setup sshdata Nothing
|
| otherwise = makeSsh' rsync setup sshdata Nothing
|
||||||
|
|
||||||
makeSsh' :: Bool -> (Remote -> Handler ()) -> SshData -> Maybe SshKeyPair -> Handler RepHtml
|
makeSsh' :: Bool -> (Remote -> Handler ()) -> SshData -> Maybe SshKeyPair -> Handler RepHtml
|
||||||
|
@ -277,14 +287,14 @@ getAddRsyncNetR :: Handler RepHtml
|
||||||
getAddRsyncNetR = do
|
getAddRsyncNetR = do
|
||||||
((result, form), enctype) <- runFormGet $
|
((result, form), enctype) <- runFormGet $
|
||||||
renderBootstrap $ sshInputAForm hostnamefield $
|
renderBootstrap $ sshInputAForm hostnamefield $
|
||||||
SshInput Nothing Nothing Nothing
|
SshInput Nothing Nothing Nothing 22
|
||||||
let showform status = page "Add a Rsync.net repository" (Just Config) $
|
let showform status = page "Add a Rsync.net repository" (Just Config) $
|
||||||
$(widgetFile "configurators/addrsync.net")
|
$(widgetFile "configurators/addrsync.net")
|
||||||
case result of
|
case result of
|
||||||
FormSuccess sshinput
|
FormSuccess sshinput
|
||||||
| isRsyncNet (hostname sshinput) -> do
|
| isRsyncNet (inputHostname sshinput) -> do
|
||||||
let reponame = genSshRepoName "rsync.net"
|
let reponame = genSshRepoName "rsync.net"
|
||||||
(maybe "" T.unpack $ directory sshinput)
|
(maybe "" T.unpack $ inputDirectory sshinput)
|
||||||
makeRsyncNet sshinput reponame setupGroup
|
makeRsyncNet sshinput reponame setupGroup
|
||||||
| otherwise ->
|
| otherwise ->
|
||||||
showform $ UnusableServer
|
showform $ UnusableServer
|
||||||
|
@ -306,7 +316,7 @@ getAddRsyncNetR = do
|
||||||
|
|
||||||
makeRsyncNet :: SshInput -> String -> (Remote -> Handler ()) -> Handler RepHtml
|
makeRsyncNet :: SshInput -> String -> (Remote -> Handler ()) -> Handler RepHtml
|
||||||
makeRsyncNet sshinput reponame setup = do
|
makeRsyncNet sshinput reponame setup = do
|
||||||
knownhost <- liftIO $ maybe (return False) knownHost (hostname sshinput)
|
knownhost <- liftIO $ maybe (return False) knownHost (inputHostname sshinput)
|
||||||
keypair <- liftIO $ genSshKeyPair
|
keypair <- liftIO $ genSshKeyPair
|
||||||
sshdata <- liftIO $ setupSshKeyPair keypair $
|
sshdata <- liftIO $ setupSshKeyPair keypair $
|
||||||
(mkSshData sshinput)
|
(mkSshData sshinput)
|
||||||
|
|
|
@ -46,6 +46,18 @@ withNote field note = field { fieldView = newview }
|
||||||
in [whamlet|^{fieldwidget} <span>^{note}</span>|]
|
in [whamlet|^{fieldwidget} <span>^{note}</span>|]
|
||||||
|
|
||||||
|
|
||||||
|
{- Makes a help button be displayed after a field, that displays a help
|
||||||
|
- widget when clicked. Requires a unique ident for the help. -}
|
||||||
|
withHelp :: Field sub master v -> GWidget sub master () -> Text -> Field sub master v
|
||||||
|
withHelp field help ident = withNote field note
|
||||||
|
where
|
||||||
|
note = [whamlet|
|
||||||
|
<a .btn data-toggle="collapse" data-target="##{ident}">
|
||||||
|
Help
|
||||||
|
<div ##{ident} .collapse>
|
||||||
|
^{help}
|
||||||
|
|]
|
||||||
|
|
||||||
data EnableEncryption = SharedEncryption | NoEncryption
|
data EnableEncryption = SharedEncryption | NoEncryption
|
||||||
deriving (Eq)
|
deriving (Eq)
|
||||||
|
|
||||||
|
|
2
debian/changelog
vendored
2
debian/changelog
vendored
|
@ -26,6 +26,8 @@ git-annex (3.20121128) UNRELEASED; urgency=low
|
||||||
when preferred content settings want it.
|
when preferred content settings want it.
|
||||||
* drop --auto: Fix dropping content when there are no preferred content
|
* drop --auto: Fix dropping content when there are no preferred content
|
||||||
settings.
|
settings.
|
||||||
|
* webapp: Allow user to specify the port when setting up a ssh or rsync
|
||||||
|
remote.
|
||||||
|
|
||||||
-- Joey Hess <joeyh@debian.org> Wed, 28 Nov 2012 13:31:07 -0400
|
-- Joey Hess <joeyh@debian.org> Wed, 28 Nov 2012 13:31:07 -0400
|
||||||
|
|
||||||
|
|
|
@ -26,3 +26,5 @@ this is not really a bug more of a wishlist feature.
|
||||||
|
|
||||||
|
|
||||||
[[!tag /design/assistant]]
|
[[!tag /design/assistant]]
|
||||||
|
|
||||||
|
> Ok, it has a port field now. [[done]] --[[Joey]]
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue