add ssh confirmation page
also broke out webapp types into a separate module
This commit is contained in:
		
					parent
					
						
							
								51dfbd77d6
							
						
					
				
			
			
				commit
				
					
						837cd79e4f
					
				
			
		
					 14 changed files with 191 additions and 97 deletions
				
			
		| 
						 | 
				
			
			@ -12,6 +12,7 @@ module Assistant.Threads.WebApp where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.DashBoard
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Assistant.WebApp.Notifications
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -1,4 +1,4 @@
 | 
			
		|||
{- git-annex assistant webapp data types
 | 
			
		||||
{- git-annex assistant webapp core
 | 
			
		||||
 -
 | 
			
		||||
 - Copyright 2012 Joey Hess <joey@kitenet.net>
 | 
			
		||||
 -
 | 
			
		||||
| 
						 | 
				
			
			@ -6,45 +6,21 @@
 | 
			
		|||
 -}
 | 
			
		||||
 | 
			
		||||
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
 | 
			
		||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
 | 
			
		||||
 | 
			
		||||
module Assistant.WebApp where
 | 
			
		||||
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.ThreadedMonad
 | 
			
		||||
import Assistant.DaemonStatus
 | 
			
		||||
import Assistant.ScanRemotes
 | 
			
		||||
import Assistant.TransferQueue
 | 
			
		||||
import Assistant.TransferSlots
 | 
			
		||||
import Assistant.Alert
 | 
			
		||||
import Utility.NotificationBroadcaster
 | 
			
		||||
import Utility.WebApp
 | 
			
		||||
import Utility.Yesod
 | 
			
		||||
import Logs.Transfer
 | 
			
		||||
 | 
			
		||||
import Yesod
 | 
			
		||||
import Yesod.Static
 | 
			
		||||
import Text.Hamlet
 | 
			
		||||
import Data.Text (Text, pack, unpack)
 | 
			
		||||
import Data.Text (Text)
 | 
			
		||||
import Control.Concurrent.STM
 | 
			
		||||
 | 
			
		||||
staticFiles "static"
 | 
			
		||||
 | 
			
		||||
mkYesodData "WebApp" $(parseRoutesFile "Assistant/WebApp/routes")
 | 
			
		||||
 | 
			
		||||
data WebApp = WebApp
 | 
			
		||||
	{ threadState :: Maybe ThreadState
 | 
			
		||||
	, daemonStatus :: DaemonStatusHandle
 | 
			
		||||
	, scanRemotes :: ScanRemoteMap
 | 
			
		||||
	, transferQueue :: TransferQueue
 | 
			
		||||
	, transferSlots :: TransferSlots
 | 
			
		||||
	, secretToken :: Text
 | 
			
		||||
	, relDir :: Maybe FilePath
 | 
			
		||||
	, getStatic :: Static
 | 
			
		||||
	, webAppState :: TMVar WebAppState
 | 
			
		||||
	, postFirstRun :: Maybe (IO String)
 | 
			
		||||
	}
 | 
			
		||||
 | 
			
		||||
data NavBarItem = DashBoard | Config | About
 | 
			
		||||
	deriving (Eq)
 | 
			
		||||
 | 
			
		||||
| 
						 | 
				
			
			@ -87,29 +63,6 @@ bootstrap navbaritem content = do
 | 
			
		|||
	where
 | 
			
		||||
		navdetails i = (navBarName i, navBarRoute i, Just i == navbaritem)
 | 
			
		||||
 | 
			
		||||
instance Yesod WebApp where
 | 
			
		||||
	{- Require an auth token be set when accessing any (non-static route) -}
 | 
			
		||||
	isAuthorized _ _ = checkAuthToken secretToken
 | 
			
		||||
 | 
			
		||||
	{- Add the auth token to every url generated, except static subsite
 | 
			
		||||
         - urls (which can show up in Permission Denied pages). -}
 | 
			
		||||
	joinPath = insertAuthToken secretToken excludeStatic
 | 
			
		||||
		where
 | 
			
		||||
			excludeStatic [] = True
 | 
			
		||||
			excludeStatic (p:_) = p /= "static"
 | 
			
		||||
 | 
			
		||||
	makeSessionBackend = webAppSessionBackend
 | 
			
		||||
	jsLoader _ = BottomOfHeadBlocking
 | 
			
		||||
 | 
			
		||||
instance RenderMessage WebApp FormMessage where
 | 
			
		||||
	renderMessage _ _ = defaultFormMessage
 | 
			
		||||
 | 
			
		||||
type Form x = Html -> MForm WebApp WebApp (FormResult x, Widget)
 | 
			
		||||
 | 
			
		||||
data WebAppState = WebAppState
 | 
			
		||||
	{ showIntro :: Bool
 | 
			
		||||
	}
 | 
			
		||||
 | 
			
		||||
newWebAppState :: IO (TMVar WebAppState)
 | 
			
		||||
newWebAppState = liftIO $ atomically $
 | 
			
		||||
	newTMVar $ WebAppState { showIntro = True }
 | 
			
		||||
| 
						 | 
				
			
			@ -149,18 +102,6 @@ getNotifier selector = do
 | 
			
		|||
	webapp <- getYesod
 | 
			
		||||
	liftIO $ selector <$> getDaemonStatus (daemonStatus webapp)
 | 
			
		||||
 | 
			
		||||
instance PathPiece NotificationId where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
instance PathPiece AlertId where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
instance PathPiece Transfer where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
{- Adds the auth parameter as a hidden field on a form. Must be put into
 | 
			
		||||
 - every form. -}
 | 
			
		||||
webAppFormAuthToken :: Widget
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.Configurators where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Assistant.DaemonStatus
 | 
			
		||||
import Assistant.WebApp.Configurators.Local
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.Configurators.Local where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Assistant.Threads.MountWatcher (handleMount)
 | 
			
		||||
import Utility.Yesod
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.Configurators.Ssh where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Utility.Yesod
 | 
			
		||||
 | 
			
		||||
| 
						 | 
				
			
			@ -26,9 +27,7 @@ data SshServer = SshServer
 | 
			
		|||
	, username :: Maybe Text
 | 
			
		||||
	, directory :: Maybe Text
 | 
			
		||||
	}
 | 
			
		||||
	deriving Show
 | 
			
		||||
 | 
			
		||||
type PubKey = String
 | 
			
		||||
	deriving (Show)
 | 
			
		||||
 | 
			
		||||
sshServerAForm :: Text -> AForm WebApp WebApp SshServer
 | 
			
		||||
sshServerAForm localusername = SshServer
 | 
			
		||||
| 
						 | 
				
			
			@ -58,6 +57,7 @@ data ServerStatus
 | 
			
		|||
	| UnusableServer Text -- reason why it's not usable
 | 
			
		||||
	| UsableRsyncServer
 | 
			
		||||
	| UsableSshServer
 | 
			
		||||
	deriving (Eq)
 | 
			
		||||
 | 
			
		||||
usable :: ServerStatus -> Bool
 | 
			
		||||
usable UntestedServer = False
 | 
			
		||||
| 
						 | 
				
			
			@ -77,7 +77,14 @@ getAddSshR = bootstrap (Just Config) $ do
 | 
			
		|||
		FormSuccess sshserver -> do
 | 
			
		||||
			(status, sshserver', pubkey) <- liftIO $ testServer sshserver
 | 
			
		||||
			if usable status
 | 
			
		||||
				then error $ "TODO " ++ show sshserver'
 | 
			
		||||
				then lift $ redirect $ ConfirmSshR $
 | 
			
		||||
					SshData 
 | 
			
		||||
						{ sshHostName = fromJust $ hostname sshserver'
 | 
			
		||||
						, sshUserName = username sshserver'
 | 
			
		||||
						, sshDirectory = fromMaybe "" $ directory sshserver'
 | 
			
		||||
						, pubKey = pubkey
 | 
			
		||||
						, rsyncOnly = (status == UsableRsyncServer)
 | 
			
		||||
						}
 | 
			
		||||
				else showform form enctype status
 | 
			
		||||
		_ -> showform form enctype UntestedServer
 | 
			
		||||
	where
 | 
			
		||||
| 
						 | 
				
			
			@ -85,15 +92,6 @@ getAddSshR = bootstrap (Just Config) $ do
 | 
			
		|||
			let authtoken = webAppFormAuthToken
 | 
			
		||||
			$(widgetFile "configurators/addssh")
 | 
			
		||||
 | 
			
		||||
		buttonText :: ServerStatus -> Text
 | 
			
		||||
		buttonText UsableRsyncServer = "Make rsync repository"
 | 
			
		||||
		buttonText UsableSshServer = "Clone repository to ssh server"
 | 
			
		||||
		buttonText _ = "Check this server"
 | 
			
		||||
 | 
			
		||||
		willTest UntestedServer = True
 | 
			
		||||
		willTest (UnusableServer _) = True
 | 
			
		||||
		willTest _ = False
 | 
			
		||||
 | 
			
		||||
{- Test if we can ssh into the server.
 | 
			
		||||
 -
 | 
			
		||||
 - Two probe attempts are made. First, try sshing in using the existing
 | 
			
		||||
| 
						 | 
				
			
			@ -153,6 +151,7 @@ testServer sshserver = do
 | 
			
		|||
		report r = "echo " ++ token r
 | 
			
		||||
		sshopt k v = concat ["-o", k, "=", v]
 | 
			
		||||
 | 
			
		||||
{- The output of ssh, including both stdout and stderr. -}
 | 
			
		||||
sshTranscript :: [String] -> IO String
 | 
			
		||||
sshTranscript opts = do
 | 
			
		||||
	(readf, writef) <- createPipe
 | 
			
		||||
| 
						 | 
				
			
			@ -210,6 +209,26 @@ knownHost sshdir (SshServer { hostname = Just h }) =
 | 
			
		|||
		, return False
 | 
			
		||||
		)
 | 
			
		||||
 | 
			
		||||
genSshUrl :: SshData -> Text
 | 
			
		||||
genSshUrl s = T.concat ["ssh://", u, h, d, "/"]
 | 
			
		||||
	where
 | 
			
		||||
		u = maybe "" (\v -> T.concat [v, "@"]) $ sshUserName s
 | 
			
		||||
		h = sshHostName s
 | 
			
		||||
		d
 | 
			
		||||
			| "/" `T.isPrefixOf` sshDirectory s = d
 | 
			
		||||
			| otherwise = T.concat ["/~/", sshDirectory s]
 | 
			
		||||
 | 
			
		||||
getConfirmSshR :: SshData -> Handler RepHtml
 | 
			
		||||
getConfirmSshR sshdata = bootstrap (Just Config) $ do
 | 
			
		||||
	sideBarDisplay
 | 
			
		||||
	setTitle "Add a remote server"
 | 
			
		||||
	let authtoken = webAppFormAuthToken
 | 
			
		||||
	let haspubkey = isJust $ pubKey sshdata
 | 
			
		||||
	$(widgetFile "configurators/confirmssh")
 | 
			
		||||
 | 
			
		||||
getMakeSshR :: SshData -> Handler RepHtml
 | 
			
		||||
getMakeSshR sshdata = error "TODO"
 | 
			
		||||
	where
 | 
			
		||||
		makeAuthorizedKeys pubkey = Just $ join ";"
 | 
			
		||||
			[ "mkdir -p ~/.ssh"
 | 
			
		||||
			, "touch ~/.ssh/authorized_keys"
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.DashBoard where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Assistant.WebApp.Notifications
 | 
			
		||||
import Assistant.WebApp.Configurators
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -10,6 +10,7 @@
 | 
			
		|||
module Assistant.WebApp.Documentation where
 | 
			
		||||
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.SideBar
 | 
			
		||||
import Utility.Yesod
 | 
			
		||||
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.Notifications where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.DaemonStatus
 | 
			
		||||
import Utility.NotificationBroadcaster
 | 
			
		||||
import Utility.Yesod
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -11,6 +11,7 @@ module Assistant.WebApp.SideBar where
 | 
			
		|||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.WebApp
 | 
			
		||||
import Assistant.WebApp.Types
 | 
			
		||||
import Assistant.WebApp.Notifications
 | 
			
		||||
import Assistant.DaemonStatus
 | 
			
		||||
import Assistant.Alert
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
							
								
								
									
										95
									
								
								Assistant/WebApp/Types.hs
									
										
									
									
									
										Normal file
									
								
							
							
						
						
									
										95
									
								
								Assistant/WebApp/Types.hs
									
										
									
									
									
										Normal file
									
								
							| 
						 | 
				
			
			@ -0,0 +1,95 @@
 | 
			
		|||
{- git-annex assistant webapp types
 | 
			
		||||
 -
 | 
			
		||||
 - Copyright 2012 Joey Hess <joey@kitenet.net>
 | 
			
		||||
 -
 | 
			
		||||
 - Licensed under the GNU GPL version 3 or higher.
 | 
			
		||||
 -}
 | 
			
		||||
 | 
			
		||||
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
 | 
			
		||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
 | 
			
		||||
 | 
			
		||||
module Assistant.WebApp.Types where
 | 
			
		||||
 | 
			
		||||
import Assistant.Common
 | 
			
		||||
import Assistant.ThreadedMonad
 | 
			
		||||
import Assistant.DaemonStatus
 | 
			
		||||
import Assistant.ScanRemotes
 | 
			
		||||
import Assistant.TransferQueue
 | 
			
		||||
import Assistant.TransferSlots
 | 
			
		||||
import Assistant.Alert
 | 
			
		||||
import Utility.NotificationBroadcaster
 | 
			
		||||
import Utility.WebApp
 | 
			
		||||
import Logs.Transfer
 | 
			
		||||
 | 
			
		||||
import Yesod
 | 
			
		||||
import Yesod.Static
 | 
			
		||||
import Data.Text (Text, pack, unpack)
 | 
			
		||||
import Control.Concurrent.STM
 | 
			
		||||
 | 
			
		||||
staticFiles "static"
 | 
			
		||||
 | 
			
		||||
mkYesodData "WebApp" $(parseRoutesFile "Assistant/WebApp/routes")
 | 
			
		||||
 | 
			
		||||
data WebApp = WebApp
 | 
			
		||||
	{ threadState :: Maybe ThreadState
 | 
			
		||||
	, daemonStatus :: DaemonStatusHandle
 | 
			
		||||
	, scanRemotes :: ScanRemoteMap
 | 
			
		||||
	, transferQueue :: TransferQueue
 | 
			
		||||
	, transferSlots :: TransferSlots
 | 
			
		||||
	, secretToken :: Text
 | 
			
		||||
	, relDir :: Maybe FilePath
 | 
			
		||||
	, getStatic :: Static
 | 
			
		||||
	, webAppState :: TMVar WebAppState
 | 
			
		||||
	, postFirstRun :: Maybe (IO String)
 | 
			
		||||
	}
 | 
			
		||||
 | 
			
		||||
instance Yesod WebApp where
 | 
			
		||||
	{- Require an auth token be set when accessing any (non-static route) -}
 | 
			
		||||
	isAuthorized _ _ = checkAuthToken secretToken
 | 
			
		||||
 | 
			
		||||
	{- Add the auth token to every url generated, except static subsite
 | 
			
		||||
         - urls (which can show up in Permission Denied pages). -}
 | 
			
		||||
	joinPath = insertAuthToken secretToken excludeStatic
 | 
			
		||||
		where
 | 
			
		||||
			excludeStatic [] = True
 | 
			
		||||
			excludeStatic (p:_) = p /= "static"
 | 
			
		||||
 | 
			
		||||
	makeSessionBackend = webAppSessionBackend
 | 
			
		||||
	jsLoader _ = BottomOfHeadBlocking
 | 
			
		||||
 | 
			
		||||
instance RenderMessage WebApp FormMessage where
 | 
			
		||||
	renderMessage _ _ = defaultFormMessage
 | 
			
		||||
 | 
			
		||||
type Form x = Html -> MForm WebApp WebApp (FormResult x, Widget)
 | 
			
		||||
 | 
			
		||||
data WebAppState = WebAppState
 | 
			
		||||
	{ showIntro :: Bool
 | 
			
		||||
	}
 | 
			
		||||
 | 
			
		||||
type PubKey = String
 | 
			
		||||
 | 
			
		||||
data SshData = SshData
 | 
			
		||||
	{ sshHostName :: Text
 | 
			
		||||
	, sshUserName :: Maybe Text
 | 
			
		||||
	, sshDirectory :: Text
 | 
			
		||||
	, pubKey :: Maybe PubKey
 | 
			
		||||
	, rsyncOnly :: Bool
 | 
			
		||||
	}
 | 
			
		||||
	deriving (Read, Show, Eq)
 | 
			
		||||
 | 
			
		||||
instance PathPiece SshData where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
instance PathPiece NotificationId where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
instance PathPiece AlertId where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
 | 
			
		||||
instance PathPiece Transfer where
 | 
			
		||||
    toPathPiece = pack . show
 | 
			
		||||
    fromPathPiece = readish . unpack
 | 
			
		||||
| 
						 | 
				
			
			@ -7,6 +7,8 @@
 | 
			
		|||
/config/repository RepositoriesR GET
 | 
			
		||||
/config/repository/add/drive AddDriveR GET
 | 
			
		||||
/config/repository/add/ssh AddSshR GET
 | 
			
		||||
/config/repository/add/ssh/confirm/#SshData ConfirmSshR GET
 | 
			
		||||
/config/repository/add/ssh/make/#SshData MakeSshR GET
 | 
			
		||||
/config/repository/first FirstRepositoryR GET
 | 
			
		||||
 | 
			
		||||
/transfers/#NotificationId TransfersR GET
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -1,13 +1,13 @@
 | 
			
		|||
<div .span9 .hero-unit>
 | 
			
		||||
  <h2>
 | 
			
		||||
    Adding a remote server using ssh or rsync
 | 
			
		||||
    Adding a remote server using ssh
 | 
			
		||||
  <p>
 | 
			
		||||
    Clone this repository to a ssh or rsync server. Your data will be #
 | 
			
		||||
    Clone this repository to a ssh server. Your data will be #
 | 
			
		||||
    uploaded to the server. If you set up other devices to use the same #
 | 
			
		||||
    server, they will all be kept in sync, using the server as a central #
 | 
			
		||||
    hub.
 | 
			
		||||
  <p>
 | 
			
		||||
    You can use nearly any server that has ssh or rsync. For example, you #
 | 
			
		||||
    You can use nearly any server that has ssh and rsync. For example, you #
 | 
			
		||||
    could use a <a href="http://linode.com/">Linode</a> or another VPS, or #
 | 
			
		||||
    an account on a friend's server.
 | 
			
		||||
  <p>
 | 
			
		||||
| 
						 | 
				
			
			@ -25,9 +25,8 @@
 | 
			
		|||
        ^{form}
 | 
			
		||||
        ^{authtoken}
 | 
			
		||||
        <div .form-actions>
 | 
			
		||||
          <button .btn .btn-primary type=submit :willTest status:onclick="$('#testmodal').modal('show');">
 | 
			
		||||
            #{buttonText status}
 | 
			
		||||
$if willTest status
 | 
			
		||||
          <button .btn .btn-primary type=submit onclick="$('#testmodal').modal('show');">
 | 
			
		||||
            Check this server
 | 
			
		||||
<div .modal .fade #testmodal>
 | 
			
		||||
  <div .modal-header>
 | 
			
		||||
    <h3>
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
							
								
								
									
										31
									
								
								templates/configurators/confirmssh.hamlet
									
										
									
									
									
										Normal file
									
								
							
							
						
						
									
										31
									
								
								templates/configurators/confirmssh.hamlet
									
										
									
									
									
										Normal file
									
								
							| 
						 | 
				
			
			@ -0,0 +1,31 @@
 | 
			
		|||
<div .span9 .hero-unit>
 | 
			
		||||
  <h2>
 | 
			
		||||
    Ready to add remote server
 | 
			
		||||
  <div .row-fluid>
 | 
			
		||||
    <div .span8>
 | 
			
		||||
      <p>
 | 
			
		||||
        The server at #{sshHostName sshdata} has been verified to be usable.
 | 
			
		||||
        <br>
 | 
			
		||||
        Everything checks out!
 | 
			
		||||
      <p>
 | 
			
		||||
        <a .btn .btn-primary href="@{MakeSshR sshdata}" onclick="$('#setupmodal').modal('show');">
 | 
			
		||||
          Clone this repository to the remote server
 | 
			
		||||
    <div .span4>
 | 
			
		||||
      $if haspubkey
 | 
			
		||||
        <div .alert .alert-info>
 | 
			
		||||
          <i .icon-info-sign></i> #
 | 
			
		||||
          <p>
 | 
			
		||||
            A ssh key will be installed on the server, allowing git-annex to #
 | 
			
		||||
            access it securely without a password.
 | 
			
		||||
<div .modal .fade #setupmodal>
 | 
			
		||||
  <div .modal-header>
 | 
			
		||||
    <h3>
 | 
			
		||||
      Testing server ...
 | 
			
		||||
  <div .modal-body>
 | 
			
		||||
    <p>
 | 
			
		||||
      Setting up repository on the remote server. This could take a minute.
 | 
			
		||||
    $if haspubkey
 | 
			
		||||
      <p>
 | 
			
		||||
        You will be prompted once more for your ssh password. A ssh key
 | 
			
		||||
        is being installed on the server, allowing git-annex to access it
 | 
			
		||||
        securely without a password.
 | 
			
		||||
| 
						 | 
				
			
			@ -54,6 +54,6 @@
 | 
			
		|||
          <i .icon-plus-sign></i> Remote server
 | 
			
		||||
      <p>
 | 
			
		||||
        Set up a repository on a remote server using #
 | 
			
		||||
        <tt>ssh</tt> or <tt>rsync</tt>.
 | 
			
		||||
        <tt>ssh</tt>.
 | 
			
		||||
      <p>
 | 
			
		||||
        To build your own personal cloud.
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue