UI for making encrypted ssh remotes with gcrypt

Improved probing the remote server, so it gathers a list of the
capabilities it has. From that list, we can determine which types
of remotes are supported, and display an appropriate UI.

The new buttons for making gcrypt repos don't work yet, but the old buttons
for unencrypted git repo and encrypted rsync repo have been adapted to the
new data types and are working.

This commit was sponsored by David Schmitt.
This commit is contained in:
Joey Hess 2013-09-29 14:39:10 -04:00
parent 2f75512188
commit d83a244986
10 changed files with 141 additions and 105 deletions

View file

@ -9,7 +9,6 @@ module Assistant.MakeRemote where
import Assistant.Common import Assistant.Common
import Assistant.Ssh import Assistant.Ssh
import Assistant.Sync
import qualified Types.Remote as R import qualified Types.Remote as R
import qualified Remote import qualified Remote
import Remote.List import Remote.List
@ -21,8 +20,6 @@ import qualified Command.InitRemote
import Logs.UUID import Logs.UUID
import Logs.Remote import Logs.Remote
import Git.Remote import Git.Remote
import Config
import Config.Cost
import Creds import Creds
import Assistant.Gpg import Assistant.Gpg
import Utility.Gpg (KeyId) import Utility.Gpg (KeyId)
@ -30,17 +27,12 @@ import Utility.Gpg (KeyId)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Map as M import qualified Data.Map as M
{- Sets up and begins syncing with a new ssh or rsync remote. -} {- Sets up a new ssh or rsync remote. -}
makeSshRemote :: Bool -> SshData -> Maybe Cost -> Assistant Remote makeSshRemote :: Bool -> SshData -> Annex RemoteName
makeSshRemote forcersync sshdata mcost = do makeSshRemote forcersync sshdata =
r <- liftAnnex $ maker (sshRepoName sshdata) (sshUrl forcersync sshdata)
addRemote $ maker (sshRepoName sshdata)
(sshUrl forcersync sshdata)
liftAnnex $ maybe noop (setRemoteCost r) mcost
syncRemote r
return r
where where
rsync = forcersync || rsyncOnly sshdata rsync = forcersync || sshCapabilities sshdata == [RsyncCapable]
maker maker
| rsync = makeRsyncRemote | rsync = makeRsyncRemote
| otherwise = makeGitRemote | otherwise = makeGitRemote
@ -48,7 +40,7 @@ makeSshRemote forcersync sshdata mcost = do
{- Generates a ssh or rsync url from a SshData. -} {- Generates a ssh or rsync url from a SshData. -}
sshUrl :: Bool -> SshData -> String sshUrl :: Bool -> SshData -> String
sshUrl forcersync sshdata = addtrailingslash $ T.unpack $ T.concat $ sshUrl forcersync sshdata = addtrailingslash $ T.unpack $ T.concat $
if (forcersync || rsyncOnly sshdata) if (forcersync || sshCapabilities sshdata == [RsyncCapable])
then [u, h, T.pack ":", sshDirectory sshdata] then [u, h, T.pack ":", sshDirectory sshdata]
else [T.pack "ssh://", u, h, d] else [T.pack "ssh://", u, h, d]
where where
@ -146,7 +138,6 @@ makeRemote basename location a = do
g <- gitRepo g <- gitRepo
if not (any samelocation $ Git.remotes g) if not (any samelocation $ Git.remotes g)
then do then do
let name = uniqueRemoteName basename 0 g let name = uniqueRemoteName basename 0 g
a name a name
return name return name

View file

@ -12,7 +12,9 @@ import Assistant.Ssh
import Assistant.Pairing import Assistant.Pairing
import Assistant.Pairing.Network import Assistant.Pairing.Network
import Assistant.MakeRemote import Assistant.MakeRemote
import Assistant.Sync
import Config.Cost import Config.Cost
import Config
import Network.Socket import Network.Socket
import qualified Data.Text as T import qualified Data.Text as T
@ -43,7 +45,9 @@ finishedLocalPairing msg keypair = do
, "git-annex-shell -c configlist " ++ T.unpack (sshDirectory sshdata) , "git-annex-shell -c configlist " ++ T.unpack (sshDirectory sshdata)
] ]
Nothing Nothing
void $ makeSshRemote False sshdata (Just semiExpensiveRemoteCost) r <- liftAnnex $ addRemote $ makeSshRemote False sshdata
liftAnnex $ setRemoteCost r semiExpensiveRemoteCost
syncRemote r
{- Mostly a straightforward conversion. Except: {- Mostly a straightforward conversion. Except:
- * Determine the best hostname to use to contact the host. - * Determine the best hostname to use to contact the host.
@ -63,7 +67,7 @@ pairMsgToSshData msg = do
, sshRepoName = genSshRepoName hostname dir , sshRepoName = genSshRepoName hostname dir
, sshPort = 22 , sshPort = 22
, needsPubKey = True , needsPubKey = True
, rsyncOnly = False , sshCapabilities = [GitAnnexShellCapable, GitCapable, RsyncCapable]
} }
{- Finds the best hostname to use for the host that sent the PairMsg. {- Finds the best hostname to use for the host that sent the PairMsg.

View file

@ -25,10 +25,16 @@ data SshData = SshData
, sshRepoName :: String , sshRepoName :: String
, sshPort :: Int , sshPort :: Int
, needsPubKey :: Bool , needsPubKey :: Bool
, rsyncOnly :: Bool , sshCapabilities :: [SshServerCapability]
} }
deriving (Read, Show, Eq) deriving (Read, Show, Eq)
data SshServerCapability = GitAnnexShellCapable | GitCapable | RsyncCapable
deriving (Read, Show, Eq)
hasCapability :: SshData -> SshServerCapability -> Bool
hasCapability d c = c `elem` sshCapabilities d
data SshKeyPair = SshKeyPair data SshKeyPair = SshKeyPair
{ sshPubKey :: String { sshPubKey :: String
, sshPrivKey :: String , sshPrivKey :: String

View file

@ -205,7 +205,8 @@ enableAWSRemote _ _ = error "S3 not supported by this build"
makeAWSRemote :: SpecialRemoteMaker -> RemoteType -> StandardGroup -> AWSCreds -> RemoteName -> RemoteConfig -> Handler () makeAWSRemote :: SpecialRemoteMaker -> RemoteType -> StandardGroup -> AWSCreds -> RemoteName -> RemoteConfig -> Handler ()
makeAWSRemote maker remotetype defaultgroup (AWSCreds ak sk) name config = do makeAWSRemote maker remotetype defaultgroup (AWSCreds ak sk) name config = do
liftIO $ AWS.setCredsEnv (T.unpack ak, T.unpack sk) liftIO $ AWS.setCredsEnv (T.unpack ak, T.unpack sk)
setupCloudRemote defaultgroup $ maker hostname remotetype config setupCloudRemote defaultgroup Nothing $
maker hostname remotetype config
where where
{- AWS services use the remote name as the basis for a host {- AWS services use the remote name as the basis for a host
- name, so filter it to contain valid characters. -} - name, so filter it to contain valid characters. -}

View file

@ -17,7 +17,6 @@ import Assistant.MakeRemote
import Utility.Rsync (rsyncUrlIsShell) import Utility.Rsync (rsyncUrlIsShell)
import Logs.Remote import Logs.Remote
import Remote import Remote
import Logs.PreferredContent
import Types.StandardGroups import Types.StandardGroups
import Utility.UserInfo import Utility.UserInfo
import Utility.Gpg import Utility.Gpg
@ -54,7 +53,7 @@ mkSshData s = SshData
(maybe "" T.unpack $ inputDirectory s) (maybe "" T.unpack $ inputDirectory s)
, sshPort = inputPort s , sshPort = inputPort s
, needsPubKey = False , needsPubKey = False
, rsyncOnly = False , sshCapabilities = [] -- untested
} }
mkSshInput :: SshData -> SshInput mkSshInput :: SshData -> SshInput
@ -103,15 +102,12 @@ sshInputAForm hostnamefield def = SshInput
data ServerStatus data ServerStatus
= UntestedServer = UntestedServer
| UnusableServer Text -- reason why it's not usable | UnusableServer Text -- reason why it's not usable
| UsableRsyncServer | UsableServer [SshServerCapability]
| UsableSshInput
deriving (Eq) deriving (Eq)
usable :: ServerStatus -> Bool capabilities :: ServerStatus -> [SshServerCapability]
usable UntestedServer = False capabilities (UsableServer cs) = cs
usable (UnusableServer _) = False capabilities _ = []
usable UsableRsyncServer = True
usable UsableSshInput = True
getAddSshR :: Handler Html getAddSshR :: Handler Html
getAddSshR = postAddSshR getAddSshR = postAddSshR
@ -143,7 +139,7 @@ postEnableRsyncR :: UUID -> Handler Html
postEnableRsyncR = enableSpecialSshRemote "rsyncurl" enableRsyncNet enablersync postEnableRsyncR = enableSpecialSshRemote "rsyncurl" enableRsyncNet enablersync
where where
enablersync sshdata = redirect $ ConfirmSshR $ enablersync sshdata = redirect $ ConfirmSshR $
sshdata { rsyncOnly = True } sshdata { sshCapabilities = [RsyncCapable] }
{- This only handles gcrypt repositories that are located on ssh servers; {- This only handles gcrypt repositories that are located on ssh servers;
- ones on local drives are handled via another part of the UI. -} - ones on local drives are handled via another part of the UI. -}
@ -214,8 +210,9 @@ parseSshRsyncUrl u
- passwordless login is already enabled, use it. Otherwise, - passwordless login is already enabled, use it. Otherwise,
- a special ssh key will need to be generated just for this server. - a special ssh key will need to be generated just for this server.
- -
- Once logged into the server, probe to see if git-annex-shell is - Once logged into the server, probe to see if git-annex-shell,
- available, or rsync. Note that, ~/.ssh/git-annex-shell may be - git, and rsync are available.
- Note that, ~/.ssh/git-annex-shell may be
- 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)
@ -223,22 +220,23 @@ testServer (SshInput { inputHostname = Nothing }) = return $
Left $ UnusableServer "Please enter a host name." Left $ UnusableServer "Please enter a host name."
testServer sshinput@(SshInput { inputHostname = Just hn }) = do testServer sshinput@(SshInput { inputHostname = Just hn }) = do
status <- probe [sshOpt "NumberOfPasswordPrompts" "0"] status <- probe [sshOpt "NumberOfPasswordPrompts" "0"]
if usable status case capabilities status of
then ret status False [] -> do
else do
status' <- probe [] status' <- probe []
if usable status' case capabilities status' of
then ret status' True [] -> return $ Left status'
else return $ Left status' cs -> ret cs True
cs -> ret cs False
where where
ret status needspubkey = return $ Right $ (mkSshData sshinput) ret cs needspubkey = return $ Right $ (mkSshData sshinput)
{ needsPubKey = needspubkey { needsPubKey = needspubkey
, rsyncOnly = status == UsableRsyncServer , sshCapabilities = cs
} }
probe extraopts = do probe extraopts = do
let remotecommand = shellWrap $ intercalate ";" let remotecommand = shellWrap $ intercalate ";"
[ report "loggedin" [ report "loggedin"
, checkcommand "git-annex-shell" , checkcommand "git-annex-shell"
, checkcommand "git"
, checkcommand "rsync" , checkcommand "rsync"
, checkcommand shim , checkcommand shim
] ]
@ -256,14 +254,19 @@ testServer sshinput@(SshInput { inputHostname = Just hn }) = do
, remotecommand , remotecommand
] ]
parsetranscript . fst <$> sshTranscript sshopts Nothing parsetranscript . fst <$> sshTranscript sshopts Nothing
parsetranscript s parsetranscript s =
| reported "git-annex-shell" = UsableSshInput let cs = map snd $ filter (reported . fst)
| reported shim = UsableSshInput [ ("git-annex-shell", GitAnnexShellCapable)
| reported "rsync" = UsableRsyncServer , (shim, GitAnnexShellCapable)
| reported "loggedin" = UnusableServer , ("git", GitCapable)
"Neither rsync nor git-annex are installed on the server. Perhaps you should go install them?" , ("rsync", RsyncCapable)
| otherwise = UnusableServer $ T.pack $ ]
"Failed to ssh to the server. Transcript: " ++ s in if null cs
then if reported "loggedin"
then UnusableServer "Neither rsync nor git-annex are installed on the server. Perhaps you should go install them?"
else UnusableServer $ T.pack $
"Failed to ssh to the server. Transcript: " ++ s
else UsableServer cs
where where
reported r = token r `isInfixOf` s reported r = token r `isInfixOf` s
@ -286,7 +289,9 @@ showSshErr msg = sshConfigurator $
$(widgetFile "configurators/ssh/error") $(widgetFile "configurators/ssh/error")
getConfirmSshR :: SshData -> Handler Html getConfirmSshR :: SshData -> Handler Html
getConfirmSshR sshdata = sshConfigurator $ getConfirmSshR sshdata = sshConfigurator $ do
secretkeys <- sortBy (comparing snd) . M.toList
<$> liftIO secretKeys
$(widgetFile "configurators/ssh/confirm") $(widgetFile "configurators/ssh/confirm")
getRetrySshR :: SshData -> Handler () getRetrySshR :: SshData -> Handler ()
@ -300,6 +305,9 @@ getMakeSshGitR = makeSsh False
getMakeSshRsyncR :: SshData -> Handler Html getMakeSshRsyncR :: SshData -> Handler Html
getMakeSshRsyncR = makeSsh True getMakeSshRsyncR = makeSsh True
getMakeSshGCryptR :: SshData -> RepoKey -> Handler Html
getMakeSshGCryptR sshdata repokey = error "TODO"
makeSsh :: Bool -> SshData -> Handler Html makeSsh :: Bool -> SshData -> Handler Html
makeSsh rsync sshdata makeSsh rsync sshdata
| needsPubKey sshdata = do | needsPubKey sshdata = do
@ -312,27 +320,25 @@ makeSsh rsync sshdata
| otherwise = makeSsh' rsync sshdata sshdata Nothing | otherwise = makeSsh' rsync sshdata sshdata Nothing
makeSsh' :: Bool -> SshData -> SshData -> Maybe SshKeyPair -> Handler Html makeSsh' :: Bool -> SshData -> SshData -> Maybe SshKeyPair -> Handler Html
makeSsh' rsync origsshdata sshdata keypair = do makeSsh' rsynconly origsshdata sshdata keypair = do
sshSetup ["-p", show (sshPort origsshdata), sshhost, remoteCommand] "" $ sshSetup ["-p", show (sshPort origsshdata), sshhost, remoteCommand] "" $
makeSshRepo rsync sshdata makeSshRepo rsynconly sshdata
where where
sshhost = genSshHost (sshHostName origsshdata) (sshUserName origsshdata) sshhost = genSshHost (sshHostName origsshdata) (sshUserName origsshdata)
remotedir = T.unpack $ sshDirectory sshdata remotedir = T.unpack $ sshDirectory sshdata
remoteCommand = shellWrap $ intercalate "&&" $ catMaybes remoteCommand = shellWrap $ intercalate "&&" $ catMaybes
[ Just $ "mkdir -p " ++ shellEscape remotedir [ Just $ "mkdir -p " ++ shellEscape remotedir
, Just $ "cd " ++ shellEscape remotedir , Just $ "cd " ++ shellEscape remotedir
, if rsync then Nothing else Just "if [ ! -d .git ]; then git init --bare --shared; fi" , if rsynconly then Nothing else Just "if [ ! -d .git ]; then git init --bare --shared; fi"
, if rsync then Nothing else Just "git annex init" , if rsynconly then Nothing else Just "git annex init"
, if needsPubKey sshdata , if needsPubKey sshdata
then addAuthorizedKeysCommand (rsync || rsyncOnly sshdata) remotedir . sshPubKey <$> keypair then addAuthorizedKeysCommand rsynconly remotedir . sshPubKey <$> keypair
else Nothing else Nothing
] ]
makeSshRepo :: Bool -> SshData -> Handler Html makeSshRepo :: Bool -> SshData -> Handler Html
makeSshRepo forcersync sshdata = do makeSshRepo forcersync sshdata = setupCloudRemote TransferGroup Nothing $
r <- liftAssistant $ makeSshRemote forcersync sshdata Nothing makeSshRemote forcersync sshdata
liftAnnex $ setStandardGroup (Remote.uuid r) TransferGroup
redirect $ EditNewCloudRepositoryR $ Remote.uuid r
getAddRsyncNetR :: Handler Html getAddRsyncNetR :: Handler Html
getAddRsyncNetR = postAddRsyncNetR getAddRsyncNetR = postAddRsyncNetR
@ -394,7 +400,7 @@ getMakeRsyncNetGCryptR sshdata NoRepoKey = whenGcryptInstalled $
withNewSecretKey $ getMakeRsyncNetGCryptR sshdata . RepoKey withNewSecretKey $ getMakeRsyncNetGCryptR sshdata . RepoKey
getMakeRsyncNetGCryptR sshdata (RepoKey keyid) = whenGcryptInstalled $ do getMakeRsyncNetGCryptR sshdata (RepoKey keyid) = whenGcryptInstalled $ do
sshSetup [sshhost, gitinit] [] $ sshSetup [sshhost, gitinit] [] $
setupCloudRemote TransferGroup $ setupCloudRemote TransferGroup Nothing $
makeGCryptRemote (sshRepoName sshdata) (sshUrl True sshdata) keyid makeGCryptRemote (sshRepoName sshdata) (sshUrl True sshdata) keyid
where where
sshhost = genSshHost (sshHostName sshdata) (sshUserName sshdata) sshhost = genSshHost (sshHostName sshdata) (sshUserName sshdata)
@ -413,7 +419,7 @@ enableRsyncNetGCrypt sshinput reponame =
notencrypted = error "Unexpectedly found a non-encrypted git repository, instead of the expected encrypted git repository." notencrypted = error "Unexpectedly found a non-encrypted git repository, instead of the expected encrypted git repository."
enableRsyncNetGCrypt' :: SshData -> RemoteName -> Handler Html enableRsyncNetGCrypt' :: SshData -> RemoteName -> Handler Html
enableRsyncNetGCrypt' sshdata reponame = enableRsyncNetGCrypt' sshdata reponame =
setupCloudRemote TransferGroup $ setupCloudRemote TransferGroup Nothing $
enableSpecialRemote reponame GCrypt.remote $ M.fromList enableSpecialRemote reponame GCrypt.remote $ M.fromList
[("gitrepo", sshUrl True sshdata)] [("gitrepo", sshUrl True sshdata)]
@ -427,7 +433,7 @@ prepRsyncNet sshinput reponame a = do
(mkSshData sshinput) (mkSshData sshinput)
{ sshRepoName = reponame { sshRepoName = reponame
, needsPubKey = True , needsPubKey = True
, rsyncOnly = True , sshCapabilities = [RsyncCapable]
} }
{- I'd prefer to separate commands with && , but {- I'd prefer to separate commands with && , but
- rsync.net's shell does not support that. - rsync.net's shell does not support that.

View file

@ -126,7 +126,8 @@ postEnableWebDAVR _ = error "WebDAV not supported by this build"
makeWebDavRemote :: SpecialRemoteMaker -> RemoteName -> CredPair -> RemoteConfig -> Handler () makeWebDavRemote :: SpecialRemoteMaker -> RemoteName -> CredPair -> RemoteConfig -> Handler ()
makeWebDavRemote maker name creds config = do makeWebDavRemote maker name creds config = do
liftIO $ WebDAV.setCredsEnv creds liftIO $ WebDAV.setCredsEnv creds
setupCloudRemote TransferGroup $ maker name WebDAV.remote config setupCloudRemote TransferGroup Nothing $
maker name WebDAV.remote config
{- Only returns creds previously used for the same hostname. -} {- Only returns creds previously used for the same hostname. -}
previouslyUsedWebDAVCreds :: String -> Annex (Maybe CredPair) previouslyUsedWebDAVCreds :: String -> Annex (Maybe CredPair)

View file

@ -20,6 +20,7 @@ import qualified Remote.List as Remote
import qualified Assistant.Threads.Transferrer as Transferrer import qualified Assistant.Threads.Transferrer as Transferrer
import Logs.Transfer import Logs.Transfer
import qualified Config import qualified Config
import Config.Cost
import Config.Files import Config.Files
import Git.Config import Git.Config
import Assistant.Threads.Watcher import Assistant.Threads.Watcher
@ -125,12 +126,13 @@ getCurrentTransfers :: Handler TransferMap
getCurrentTransfers = currentTransfers <$> liftAssistant getDaemonStatus getCurrentTransfers = currentTransfers <$> liftAssistant getDaemonStatus
{- Runs an action that creates or enables a cloud remote, {- Runs an action that creates or enables a cloud remote,
- and finishes setting it up; adding it to a group if it's not already in - and finishes setting it up, then starts syncing with it,
- one, starts syncing with it, and finishes by displaying the page to edit - and finishes by displaying the page to edit it. -}
- it. -} setupCloudRemote :: StandardGroup -> Maybe Cost -> Annex RemoteName -> Handler a
setupCloudRemote :: StandardGroup -> Annex RemoteName -> Handler a setupCloudRemote defaultgroup mcost maker = do
setupCloudRemote defaultgroup maker = do
r <- liftAnnex $ addRemote maker r <- liftAnnex $ addRemote maker
liftAnnex $ setStandardGroup (Remote.uuid r) defaultgroup liftAnnex $ do
setStandardGroup (Remote.uuid r) defaultgroup
maybe noop (Config.setRemoteCost r) mcost
liftAssistant $ syncRemote r liftAssistant $ syncRemote r
redirect $ EditNewCloudRepositoryR $ Remote.uuid r redirect $ EditNewCloudRepositoryR $ Remote.uuid r

View file

@ -44,6 +44,7 @@
/config/repository/add/ssh/retry/#SshData RetrySshR GET /config/repository/add/ssh/retry/#SshData RetrySshR GET
/config/repository/add/ssh/make/git/#SshData MakeSshGitR GET /config/repository/add/ssh/make/git/#SshData MakeSshGitR GET
/config/repository/add/ssh/make/rsync/#SshData MakeSshRsyncR GET /config/repository/add/ssh/make/rsync/#SshData MakeSshRsyncR GET
/config/repository/add/ssh/make/gcrypt/#SshData/#RepoKey MakeSshGCryptR GET
/config/repository/add/cloud/rsync.net AddRsyncNetR GET POST /config/repository/add/cloud/rsync.net AddRsyncNetR GET POST
/config/repository/add/cloud/rsync.net/shared/#SshData MakeRsyncNetSharedR GET /config/repository/add/cloud/rsync.net/shared/#SshData MakeRsyncNetSharedR GET
/config/repository/add/cloud/rsync.net/gcrypt/#SshData/#RepoKey MakeRsyncNetGCryptR GET /config/repository/add/cloud/rsync.net/gcrypt/#SshData/#RepoKey MakeRsyncNetGCryptR GET

View file

@ -26,11 +26,11 @@
<p> <p>
$forall (keyid, name) <- secretkeys $forall (keyid, name) <- secretkeys
<p> <p>
<a .btn onclick="$('#setupmodal').modal('show');" href="@{MakeRsyncNetGCryptR sshdata (RepoKey keyid)}"> <a .btn href="@{MakeRsyncNetGCryptR sshdata (RepoKey keyid)}" onclick="$('#setupmodal').modal('show');">
<i .icon-lock></i> Encrypt repository # <i .icon-lock></i> Encrypt repository #
to ^{gpgKeyDisplay keyid (Just name)} to ^{gpgKeyDisplay keyid (Just name)}
<p> <p>
<a .btn onclick="$('#genkeymodal').modal('show');" href="@{MakeRsyncNetGCryptR sshdata NoRepoKey}"> <a .btn href="@{MakeRsyncNetGCryptR sshdata NoRepoKey}" onclick="$('#genkeymodal').modal('show');">
<i .icon-plus-sign></i> Encrypt repository # <i .icon-plus-sign></i> Encrypt repository #
with a new encryption key with a new encryption key
^{genKeyModal} ^{genKeyModal}

View file

@ -3,45 +3,69 @@
Ready to add remote server Ready to add remote server
<div .row-fluid> <div .row-fluid>
<div .span9> <div .span9>
<p> $if not (hasCapability sshdata GitAnnexShellCapable)
The server #{sshHostName sshdata} has been verified to be usable. <p>
<p>
You have two options for how to use the server:
<p>
$if not (rsyncOnly sshdata)
<a .btn .btn-primary href="@{MakeSshGitR sshdata}" onclick="$('#setupmodal').modal('show');">
Use a git repository on the server
$else
<a .btn .disabled .btn-warning href="@{RetrySshR sshdata}" onclick="$('#testmodal').modal('show');">
Use a git repository on the server (not available) #
<a .btn .btn-primary href="@{RetrySshR sshdata}" onclick="$('#testmodal').modal('show');">
Retry
<br>
<i .icon-warning-sign></i> # <i .icon-warning-sign></i> #
<i> The server #{sshHostName sshdata} can be used as is, but #
The server needs git and git-annex installed to use this option. installing #
<br> $if not (hasCapability sshdata GitCapable)
All your data will be uploaded to the server, including the full # git and git-annex #
git repository. This is a great choice if you want to set up # $else
other devices to use the same server, or share the repository with # git-annex #
others. on it would make it work better, and provide more options below. #
<p style="text-align: center"> <p>
-or- If you're able to install software on the server, do so and click
<a .btn href="@{RetrySshR sshdata}" onclick="$('#testmodal').modal('show');">
Retry
$else
<p>
The server #{sshHostName sshdata} has been verified to be usable. #
Depending on whether you trust this server, you can choose between #
storing your data on it encrypted, or unencrypted.
<h3>
Unencrypted repository
<p>
All your data will be uploaded to the server, including a clone of #
the git repository. This is a good choice if you want to set up #
other devices to use the same server, or share the repository with #
others.
<p>
<a .btn href="@{MakeSshGitR sshdata}" onclick="$('#setupmodal').modal('show');">
Make an unencrypted git repository on the server
<p style="text-align: center">
-or-
<h3>
Simple shared encryption
<p> <p>
<a .btn .btn-primary href="@{MakeSshRsyncR sshdata}" onclick="$('#setupmodal').modal('show');"> This allows everyone who has a clone of this repository to #
Use an encrypted rsync repository on the server decrypt the files stored on #{sshHostName sshdata}. That makes #
<br> it good for sharing. And it's easy to set up and use.
The contents of your files will be stored, fully encrypted, on the # <p>
server. The server will not store other information about your # <a .btn href="@{MakeSshRsyncR sshdata}" onclick="$('#setupmodal').modal('show');">
git repository. This is the best choice if you don't run the server # <i .icon-lock></i> Use shared encryption
yourself, or have sensitive data. $if hasCapability sshdata GitCapable
<div .span4> <p style="text-align: center">
$if needsPubKey sshdata -or-
<div .alert .alert-info> <h3>
<i .icon-info-sign></i> # Encrypt with GnuPG key
A ssh key will be installed on the server, allowing git-annex to # <p>
access it securely without a password. This stores an encrypted clone of your repository on #
#{sshHostName sshdata}, unlike shared encryption which only #
stores file contents there. So it's good for backups. But the #
encryption will prevent you from sharing the repository with #
friends, or easily accessing its contents on another computer.
<p>
$forall (keyid, name) <- secretkeys
<p>
<a .btn href="@{MakeSshGCryptR sshdata (RepoKey keyid)}" onclick="$('#setupmodal').modal('show');" >
<i .icon-lock></i> Encrypt repository #
to ^{gpgKeyDisplay keyid (Just name)}
<p>
<a .btn href="@{MakeSshGCryptR sshdata NoRepoKey}" onclick="$('#genkeymodal').modal('show');">
<i .icon-plus-sign></i> Encrypt repository #
with a new encryption key
^{sshTestModal} ^{sshTestModal}
^{genKeyModal}
<div .modal .fade #setupmodal> <div .modal .fade #setupmodal>
<div .modal-header> <div .modal-header>
<h3> <h3>