responding to pair requests *almost* works

This commit is contained in:
Joey Hess 2012-09-10 17:53:51 -04:00
parent b573d91aa2
commit c20d6f4189
9 changed files with 189 additions and 122 deletions

View file

@ -286,9 +286,9 @@ sanityCheckFixAlert msg = Alert
alerthead = "The daily sanity check found and fixed a problem:" alerthead = "The daily sanity check found and fixed a problem:"
alertfoot = "If these problems persist, consider filing a bug report." alertfoot = "If these problems persist, consider filing a bug report."
pairRequestAlert :: AlertButton -> Alert pairingAlert :: AlertButton -> Alert
pairRequestAlert button = baseActivityAlert pairingAlert button = baseActivityAlert
{ alertData = [ UnTensed "Pairing request in progress" ] { alertData = [ UnTensed "Pairing in progress" ]
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButton = Just button
} }

View file

@ -34,6 +34,9 @@ fromPairMsg (PairMsg m) = m
pairMsgStage :: PairMsg -> PairStage pairMsgStage :: PairMsg -> PairStage
pairMsgStage (PairMsg (Verifiable (s, _) _)) = s pairMsgStage (PairMsg (Verifiable (s, _) _)) = s
pairMsgData :: PairMsg -> PairData
pairMsgData (PairMsg (Verifiable (_, d) _)) = d
data PairData = PairData data PairData = PairData
-- uname -n output, not a full domain name -- uname -n output, not a full domain name
{ remoteHostName :: Maybe HostName { remoteHostName :: Maybe HostName
@ -45,11 +48,11 @@ data PairData = PairData
} }
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
type SshPubKey = String
type UserName = String type UserName = String
{- A pairing that is in progress has a secret, and a thread that is {- A pairing that is in progress has a secret, a thread that is
- broadcasting pairing requests. -} - broadcasting pairing messages, and a SshKeyPair that has not yet been
- set up on disk. -}
data PairingInProgress = PairingInProgress data PairingInProgress = PairingInProgress
{ inProgressSecret :: Secret { inProgressSecret :: Secret
, inProgressThreadId :: ThreadId , inProgressThreadId :: ThreadId

View file

@ -30,7 +30,7 @@ multicastAddress :: SomeAddr -> HostName
multicastAddress (IPv4Addr _) = "224.0.0.1" multicastAddress (IPv4Addr _) = "224.0.0.1"
multicastAddress (IPv6Addr _) = "ff02::1" multicastAddress (IPv6Addr _) = "ff02::1"
{- Multicasts a message repeatedly on all interfaces forever, {- Multicasts a message repeatedly on all interfaces forever, until killed
- with a 2 second delay between each transmission. - with a 2 second delay between each transmission.
- -
- The remoteHostAddress is set to the interface's IP address. - The remoteHostAddress is set to the interface's IP address.

View file

@ -15,6 +15,7 @@ import qualified Data.Text as T
import qualified Control.Exception as E import qualified Control.Exception as E
import System.Process (CreateProcess(..)) import System.Process (CreateProcess(..))
import Control.Concurrent import Control.Concurrent
import Data.Char
data SshData = SshData data SshData = SshData
{ sshHostName :: Text { sshHostName :: Text
@ -31,6 +32,8 @@ data SshKeyPair = SshKeyPair
, sshPrivKey :: String , sshPrivKey :: String
} }
type SshPubKey = String
{- ssh -ofoo=bar command-line option -} {- ssh -ofoo=bar command-line option -}
sshOpt :: String -> String -> String sshOpt :: String -> String -> String
sshOpt k v = concat ["-o", k, "=", v] sshOpt k v = concat ["-o", k, "=", v]
@ -40,6 +43,15 @@ sshDir = do
home <- myHomeDir home <- myHomeDir
return $ home </> ".ssh" return $ home </> ".ssh"
{- host_dir, with all / in dir replaced by _, and bad characters removed -}
genSshRepoName :: String -> FilePath -> String
genSshRepoName host dir
| null dir = filter legal host
| otherwise = filter legal $ host ++ "_" ++ replace "/" "_" dir
where
legal '_' = True
legal c = isAlphaNum c
{- The output of ssh, including both stdout and stderr. -} {- The output of ssh, including both stdout and stderr. -}
sshTranscript :: [String] -> String -> IO (String, Bool) sshTranscript :: [String] -> String -> IO (String, Bool)
sshTranscript opts input = do sshTranscript opts input = do
@ -71,27 +83,30 @@ sshTranscript opts input = do
return () return ()
return (transcript, ok) return (transcript, ok)
makeAuthorizedKeys :: Bool -> SshPubKey -> IO Bool
makeAuthorizedKeys rsynconly pubkey = boolSystem "sh"
[ Param "-c" , Param $ makeAuthorizedKeysCommand rsynconly pubkey ]
{- Implemented as a shell command, so it can be run on remote servers over {- Implemented as a shell command, so it can be run on remote servers over
- ssh. -} - ssh. -}
makeAuthorizedKeys :: SshData -> SshKeyPair -> Maybe String makeAuthorizedKeysCommand :: Bool -> SshPubKey -> String
makeAuthorizedKeys sshdata keypair makeAuthorizedKeysCommand rsynconly pubkey = join "&&" $
| needsPubKey sshdata = Just $ join "&&" $ [ "mkdir -p ~/.ssh"
[ "mkdir -p ~/.ssh" , "touch ~/.ssh/authorized_keys"
, "touch ~/.ssh/authorized_keys" , "chmod 600 ~/.ssh/authorized_keys"
, "chmod 600 ~/.ssh/authorized_keys" , unwords
, unwords [ "echo"
[ "echo" , shellEscape $ authorizedKeysLine rsynconly pubkey
, shellEscape $ authorizedKeysLine sshdata keypair , ">>~/.ssh/authorized_keys"
, ">>~/.ssh/authorized_keys"
]
] ]
| otherwise = Nothing ]
authorizedKeysLine :: SshData -> SshKeyPair -> String authorizedKeysLine :: Bool -> SshPubKey -> String
authorizedKeysLine sshdata (SshKeyPair { sshPubKey = pubkey }) authorizedKeysLine rsynconly pubkey
{- TODO: Locking down rsync is difficult, requiring a rather {- TODO: Locking down rsync is difficult, requiring a rather
- long perl script. -} - long perl script. -}
| rsyncOnly sshdata = pubkey | rsynconly = pubkey
| otherwise = limitcommand "git-annex-shell -c" ++ pubkey | otherwise = limitcommand "git-annex-shell -c" ++ pubkey
where where
limitcommand c = "command=\"perl -e 'exec qw(" ++ c ++ "), $ENV{SSH_ORIGINAL_COMMAND}'\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding " limitcommand c = "command=\"perl -e 'exec qw(" ++ c ++ "), $ENV{SSH_ORIGINAL_COMMAND}'\",no-agent-forwarding,no-port-forwarding,no-X11-forwarding "

View file

@ -46,15 +46,20 @@ pairListenerThread st dstatus urlrenderer = thread $ withSocketsDo $ do
chunksz = 1024 chunksz = 1024
dispatch Nothing = noop dispatch Nothing = noop
dispatch (Just m) = case pairMsgStage m of dispatch (Just m@(PairMsg v)) = do
PairReq -> pairReqAlert dstatus urlrenderer m verified <- maybe False (verify v . inProgressSecret)
PairAck -> pairAckAlert dstatus m . pairingInProgress
PairDone -> pairDoneAlert dstatus m <$> getDaemonStatus dstatus
case pairMsgStage m of
PairReq -> pairReqReceived verified dstatus urlrenderer m
PairAck -> pairAckReceived verified dstatus m
PairDone -> pairDoneReceived verified dstatus m
{- Pair request alerts from the same host combine, {- Pair request alerts from the same host combine,
- so repeated requests do not add additional alerts. -} - so repeated requests do not add additional alerts. -}
pairReqAlert :: DaemonStatusHandle -> UrlRenderer -> PairMsg -> IO () pairReqReceived :: Bool -> DaemonStatusHandle -> UrlRenderer -> PairMsg -> IO ()
pairReqAlert dstatus urlrenderer msg = unlessM myreq $ do pairReqReceived True _ _ _ = noop -- ignore out own PairReq
pairReqReceived False dstatus urlrenderer msg = do
url <- renderUrl urlrenderer (FinishPairR msg) [] url <- renderUrl urlrenderer (FinishPairR msg) []
void $ addAlert dstatus $ pairRequestReceivedAlert repo void $ addAlert dstatus $ pairRequestReceivedAlert repo
(repo ++ " is sending a pair request.") $ (repo ++ " is sending a pair request.") $
@ -74,11 +79,6 @@ pairReqAlert dstatus urlrenderer msg = unlessM myreq $ do
, ":" , ":"
, (remoteDirectory pairdata) , (remoteDirectory pairdata)
] ]
{- Filter out our own pair request, by checking if we
- can verify using its secret. -}
myreq = maybe False (verified v . inProgressSecret)
. pairingInProgress
<$> getDaemonStatus dstatus
{- Remove the button when it's clicked, and change the {- Remove the button when it's clicked, and change the
- alert to be in progress. This alert cannot be entirely - alert to be in progress. This alert cannot be entirely
- removed since more pair request messages are coming in - removed since more pair request messages are coming in
@ -91,15 +91,16 @@ pairReqAlert dstatus urlrenderer msg = unlessM myreq $ do
} }
{- When a valid PairAck is seen, a host has successfully paired with {- When a valid PairAck is seen, a host has successfully paired with
- us, and we should finish pairing with them. Then send a PairDone. - us, and we should finish pairing with them. Then send a single PairDone.
- -
- A stale PairAck might also be seen, after we've finished pairing. - A stale PairAck might also be seen, after we've finished pairing.
- Perhaps our PairDone was not received. To handle this, we keep - Perhaps our PairDone was not received. To handle this, we keep
- a list of recently finished pairings, and re-send PairDone in - a list of recently finished pairings, and re-send PairDone in
- response to stale PairAcks for them. - response to stale PairAcks for them.
-} -}
pairAckAlert :: DaemonStatusHandle -> PairMsg -> IO () pairAckReceived :: Bool -> DaemonStatusHandle -> PairMsg -> IO ()
pairAckAlert dstatus msg = error "TODO" pairAckReceived False _ _ = noop -- not verified
pairAckReceived True dstatus msg = error "TODO"
{- If we get a valid PairDone, and are sending PairAcks, we can stop {- If we get a valid PairDone, and are sending PairAcks, we can stop
- sending them, as the message has been received. - sending them, as the message has been received.
@ -110,5 +111,6 @@ pairAckAlert dstatus msg = error "TODO"
- Note: This does allow a bad actor to squelch pairing on a network - Note: This does allow a bad actor to squelch pairing on a network
- by sending bogus PairDones. - by sending bogus PairDones.
-} -}
pairDoneAlert :: DaemonStatusHandle -> PairMsg -> IO () pairDoneReceived :: Bool -> DaemonStatusHandle -> PairMsg -> IO ()
pairDoneAlert dstatus msg = error "TODO" pairDoneReceived False _ _ = noop -- not verified
pairDoneReceived True dstatus msg = error "TODO"

View file

@ -11,12 +11,14 @@
- which prompts them for the same secret. - which prompts them for the same secret.
- * The secret is used to verify the PairReq. If it checks out, - * The secret is used to verify the PairReq. If it checks out,
- a PairAck is sent, and the other device adds the ssh key from the - a PairAck is sent, and the other device adds the ssh key from the
- PairReq. An Alert is displayed noting that the pairing has been set up. - PairReq to its authorized_keys, and sets up the remote.
- * The PairAck is received back at the device that started the process. - * The PairAck is received back at the device that started the process.
- It's verified using the stored secret. The ssh key from the PairAck - It's verified using the stored secret. The ssh key from the PairAck
- is added. An Alert is displayed noting that the pairing has been set - is added. An Alert is displayed noting that the pairing has been set
- up. The pairing secret is removed to prevent anyone cracking the - up. The pairing secret is removed to prevent anyone cracking the
- crypto. - crypto. Syncing starts. A PairDone is sent.
- * The PairDone is received, and an alert shown indicating pairing is
- done.
- -
- Copyright 2012 Joey Hess <joey@kitenet.net> - Copyright 2012 Joey Hess <joey@kitenet.net>
- -
@ -34,9 +36,10 @@ import Assistant.WebApp.Types
import Assistant.WebApp.SideBar import Assistant.WebApp.SideBar
import Utility.Yesod import Utility.Yesod
#ifdef WITH_PAIRING #ifdef WITH_PAIRING
import Assistant.Common
import Assistant.Pairing.Network import Assistant.Pairing.Network
import Assistant.Ssh import Assistant.Ssh
import Assistant.Common import qualified Assistant.WebApp.Configurators.Ssh as Ssh
import Assistant.Alert import Assistant.Alert
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Utility.Verifiable import Utility.Verifiable
@ -57,74 +60,110 @@ import Control.Concurrent
getStartPairR :: Handler RepHtml getStartPairR :: Handler RepHtml
#ifdef WITH_PAIRING #ifdef WITH_PAIRING
getStartPairR = promptSecret Nothing $ \rawsecret secret -> do getStartPairR = do
dstatus <- daemonStatus <$> lift getYesod
urlrender <- lift getUrlRender
let homeurl = urlrender HomeR
hostname <- liftIO getHostname
username <- liftIO getUserName
reldir <- fromJust . relDir <$> lift getYesod
keypair <- liftIO genSshKeyPair keypair <- liftIO genSshKeyPair
let pubkey = sshPubKey keypair ++ "foo" promptSecret Nothing $ startPairing PairReq keypair noop
let mkmsg addr = PairMsg $ mkVerifiable
(PairReq, PairData hostname addr username reldir pubkey) secret
liftIO $ do
pip <- PairingInProgress secret
<$> sendrequests mkmsg dstatus homeurl
<*> pure keypair
oldpip <- modifyDaemonStatus dstatus $
\s -> (s { pairingInProgress = Just pip }, pairingInProgress s)
maybe noop stopold oldpip
lift $ redirect $ InprogressPairR rawsecret
where
{- Sends pairing messages until the thread is killed,
- and shows an activity alert while doing it.
-
- The button returns the user to the HomeR. This is
- not ideal, but they have to be sent somewhere, and could
- have been on a page specific to the in-process pairing
- that just stopped.
-}
sendrequests mkmsg dstatus homeurl = forkIO $ do
tid <- myThreadId
let selfdestruct = AlertButton
{ buttonLabel = "Cancel"
, buttonUrl = homeurl
, buttonAction = Just $ const $ killThread tid
}
alertDuring dstatus (pairRequestAlert selfdestruct) $ do
_ <- E.try (multicastPairMsg mkmsg) :: IO (Either E.SomeException ())
return ()
stopold = killThread . inProgressThreadId
#else #else
getStartPairR = noPairing getStartPairR = noPairing
#endif #endif
getInprogressPairR :: Text -> Handler RepHtml
#ifdef WITH_PAIRING
getInprogressPairR secret = bootstrap (Just Config) $ do
sideBarDisplay
setTitle "Pairing"
$(widgetFile "configurators/pairing/inprogress")
#else
getInprogressPairR _ = noPairing
#endif
getFinishPairR :: PairMsg -> Handler RepHtml getFinishPairR :: PairMsg -> Handler RepHtml
#ifdef WITH_PAIRING #ifdef WITH_PAIRING
getFinishPairR msg = promptSecret (Just msg) $ \_ secret -> do getFinishPairR msg = promptSecret (Just msg) $ \_ secret -> do
error "TODO" keypair <- setup
startPairing PairAck keypair cleanup "" secret
where
pubkey = remoteSshPubKey $ pairMsgData msg
setup = do
unlessM (liftIO $ makeAuthorizedKeys False pubkey) $
error "failed setting up ssh authorized keys"
keypair <- liftIO genSshKeyPair
let d = pairMsgData msg
besthostname <- liftIO $ bestHostName d
let sshdata = SshData
{ sshHostName = T.pack besthostname
, sshUserName = Just (T.pack $ remoteUserName d)
, sshDirectory = T.pack (remoteDirectory d)
, sshRepoName = genSshRepoName besthostname (remoteDirectory d)
, needsPubKey = True
, rsyncOnly = False
}
sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
void $ lift $ Ssh.makeSshWithKeyPair False sshdata' (Just keypair)
return keypair
cleanup = error "TODO clean up authorized keys and generated ssh key and remove git remote"
#else #else
getFinishPairR _ = noPairing getFinishPairR _ = noPairing
#endif #endif
getInprogressPairR :: Text -> Handler RepHtml
#ifdef WITH_PAIRING #ifdef WITH_PAIRING
getInprogressPairR secret = pairPage $ do
$(widgetFile "configurators/pairing/inprogress")
#else
getInprogressPairR _ = noPairing
#endif
#ifdef WITH_PAIRING
{- Starts pairing, at either the PairReq (initiating host) or
- PairAck (responding host) stage.
-
- Displays an alert, and starts a thread sending the pairing message,
- which will continue running until the other host responds, or until
- canceled by the user. If canceled by the user, runs the oncancel action.
-
- Redirects to the pairing in progress page.
-}
startPairing :: PairStage -> SshKeyPair -> IO () -> Text -> Secret -> Widget
startPairing stage keypair oncancel displaysecret secret = do
dstatus <- daemonStatus <$> lift getYesod
urlrender <- lift getUrlRender
let homeurl = urlrender HomeR
sender <- mksender
liftIO $ do
pip <- PairingInProgress secret
<$> sendrequests sender dstatus homeurl
<*> pure keypair
oldpip <- modifyDaemonStatus dstatus $
\s -> (s { pairingInProgress = Just pip }, pairingInProgress s)
maybe noop stopold oldpip
lift $ redirect $ InprogressPairR displaysecret
where
mksender = do
hostname <- liftIO getHostname
username <- liftIO getUserName
reldir <- fromJust . relDir <$> lift getYesod
return $ multicastPairMsg $ \addr -> PairMsg $ mkVerifiable
(stage, PairData hostname addr username reldir (sshPubKey keypair)) secret
{- Sends pairing messages until the thread is killed,
- and shows an activity alert while doing it.
-
- The cancel button returns the user to the HomeR. This is
- not ideal, but they have to be sent somewhere, and could
- have been on a page specific to the in-process pairing
- that just stopped, so can't go back there.
-}
sendrequests sender dstatus homeurl = forkIO $ do
tid <- myThreadId
let selfdestruct = AlertButton
{ buttonLabel = "Cancel"
, buttonUrl = homeurl
, buttonAction = Just $ const $ do
oncancel
killThread tid
}
alertDuring dstatus (pairingAlert selfdestruct) $ do
_ <- E.try sender :: IO (Either E.SomeException ())
return ()
stopold = killThread . inProgressThreadId
data InputSecret = InputSecret { secretText :: Maybe Text } data InputSecret = InputSecret { secretText :: Maybe Text }
{- If a PairMsg is passed in, ensures that the user enters a secret
- that can validate it. -}
promptSecret :: Maybe PairMsg -> (Text -> Secret -> Widget) -> Handler RepHtml promptSecret :: Maybe PairMsg -> (Text -> Secret -> Widget) -> Handler RepHtml
promptSecret msg cont = bootstrap (Just Config) $ do promptSecret msg cont = pairPage $ do
sideBarDisplay
setTitle "Pairing"
((result, form), enctype) <- lift $ ((result, form), enctype) <- lift $
runFormGet $ renderBootstrap $ runFormGet $ renderBootstrap $
InputSecret <$> aopt textField "Secret phrase" Nothing InputSecret <$> aopt textField "Secret phrase" Nothing
@ -138,7 +177,7 @@ promptSecret msg cont = bootstrap (Just Config) $ do
Just problem -> Just problem ->
showform form enctype $ Just problem showform form enctype $ Just problem
Just m -> Just m ->
if verified (fromPairMsg m) secret if verify (fromPairMsg m) secret
then cont rawsecret secret then cont rawsecret secret
else showform form enctype $ Just else showform form enctype $ Just
"That's not the right secret phrase." "That's not the right secret phrase."
@ -168,6 +207,15 @@ secretProblem s
toSecret :: Text -> Secret toSecret :: Text -> Secret
toSecret s = B.fromChunks [T.encodeUtf8 $ T.toLower $ T.filter isAlphaNum s] toSecret s = B.fromChunks [T.encodeUtf8 $ T.toLower $ T.filter isAlphaNum s]
getUserName :: IO String
getUserName = userName <$> (getUserEntryForID =<< getEffectiveUserID)
pairPage :: Widget -> Handler RepHtml
pairPage w = bootstrap (Just Config) $ do
sideBarDisplay
setTitle "Pairing"
w
{- From Dickens -} {- From Dickens -}
sampleQuote :: Text sampleQuote :: Text
sampleQuote = T.unwords sampleQuote = T.unwords
@ -177,15 +225,10 @@ sampleQuote = T.unwords
, "it was the age of foolishness." , "it was the age of foolishness."
] ]
getUserName :: IO String
getUserName = userName <$> (getUserEntryForID =<< getEffectiveUserID)
#else #else
noPairing :: Handler RepHtml noPairing :: Handler RepHtml
noPairing = bootstrap (Just Config) $ do noPairing = pairPage $
sideBarDisplay
setTitle "Pairing"
$(widgetFile "configurators/pairing/disabled") $(widgetFile "configurators/pairing/disabled")
#endif #endif

View file

@ -49,7 +49,9 @@ mkSshData sshserver = SshData
{ sshHostName = fromMaybe "" $ hostname sshserver { sshHostName = fromMaybe "" $ hostname sshserver
, sshUserName = username sshserver , sshUserName = username sshserver
, sshDirectory = fromMaybe "" $ directory sshserver , sshDirectory = fromMaybe "" $ directory sshserver
, sshRepoName = genSshRepoName sshserver , sshRepoName = genSshRepoName
(T.unpack $ fromJust $ hostname sshserver)
(maybe "" T.unpack $ directory sshserver)
, needsPubKey = False , needsPubKey = False
, rsyncOnly = False , rsyncOnly = False
} }
@ -167,11 +169,6 @@ testServer sshserver = do
genSshHost :: Text -> Maybe Text -> String genSshHost :: Text -> Maybe Text -> String
genSshHost host user = maybe "" (\v -> T.unpack v ++ "@") user ++ T.unpack host genSshHost host user = maybe "" (\v -> T.unpack v ++ "@") user ++ T.unpack host
{- host_dir -}
genSshRepoName :: SshServer -> String
genSshRepoName s = (T.unpack $ fromJust $ hostname s) ++
(maybe "" (\d -> '_' : T.unpack d) (directory s))
{- Runs a ssh command; if it fails shows the user the transcript, {- Runs a ssh command; if it fails shows the user the transcript,
- and if it succeeds, runs an action. -} - and if it succeeds, runs an action. -}
sshSetup :: [String] -> String -> Handler RepHtml -> Handler RepHtml sshSetup :: [String] -> String -> Handler RepHtml -> Handler RepHtml
@ -211,11 +208,11 @@ makeSsh rsync sshdata
| needsPubKey sshdata = do | needsPubKey sshdata = do
keypair <- liftIO $ genSshKeyPair keypair <- liftIO $ genSshKeyPair
sshdata' <- liftIO $ setupSshKeyPair keypair sshdata sshdata' <- liftIO $ setupSshKeyPair keypair sshdata
makeSsh' rsync sshdata' (Just keypair) makeSshWithKeyPair rsync sshdata' (Just keypair)
| otherwise = makeSsh' rsync sshdata Nothing | otherwise = makeSshWithKeyPair rsync sshdata Nothing
makeSsh' :: Bool -> SshData -> Maybe SshKeyPair -> Handler RepHtml makeSshWithKeyPair :: Bool -> SshData -> Maybe SshKeyPair -> Handler RepHtml
makeSsh' rsync sshdata keypair = makeSshWithKeyPair rsync sshdata keypair =
sshSetup [sshhost, remoteCommand] "" $ sshSetup [sshhost, remoteCommand] "" $
makeSshRepo rsync sshdata makeSshRepo rsync sshdata
where where
@ -226,7 +223,9 @@ makeSsh' rsync sshdata keypair =
, Just $ "cd " ++ shellEscape remotedir , Just $ "cd " ++ shellEscape remotedir
, if rsync then Nothing else Just $ "git init --bare --shared" , if rsync then Nothing else Just $ "git init --bare --shared"
, if rsync then Nothing else Just $ "git annex init" , if rsync then Nothing else Just $ "git annex init"
, maybe Nothing (makeAuthorizedKeys sshdata) keypair , if needsPubKey sshdata
then maybe Nothing (Just . makeAuthorizedKeysCommand (rsyncOnly sshdata) . sshPubKey) keypair
else Nothing
] ]
makeSshRepo :: Bool -> SshData -> Handler RepHtml makeSshRepo :: Bool -> SshData -> Handler RepHtml

View file

@ -24,14 +24,14 @@ data Verifiable a = Verifiable
mkVerifiable :: Show a => a -> Secret -> Verifiable a mkVerifiable :: Show a => a -> Secret -> Verifiable a
mkVerifiable a secret = Verifiable a (calcDigest (show a) secret) mkVerifiable a secret = Verifiable a (calcDigest (show a) secret)
verified :: (Eq a, Show a) => Verifiable a -> Secret -> Bool verify :: (Eq a, Show a) => Verifiable a -> Secret -> Bool
verified v secret = v == mkVerifiable (verifiableVal v) secret verify v secret = v == mkVerifiable (verifiableVal v) secret
calcDigest :: String -> Secret -> HMACDigest calcDigest :: String -> Secret -> HMACDigest
calcDigest v secret = showDigest $ hmacSha1 secret $ fromString v calcDigest v secret = showDigest $ hmacSha1 secret $ fromString v
{- for quickcheck -} {- for quickcheck -}
prop_verifiable_sane :: String -> String -> Bool prop_verifiable_sane :: String -> String -> Bool
prop_verifiable_sane a s = verified (mkVerifiable a secret) secret prop_verifiable_sane a s = verify (mkVerifiable a secret) secret
where where
secret = fromString s secret = fromString s

View file

@ -1,10 +1,15 @@
<div .span9 .hero-unit> <div .span9 .hero-unit>
<h2> <h2>
Pairing in progress .. Pairing in progress ..
<p> $if T.null secret
Now you should either go tell the owner of the computer you want to pair # <p>
with the secret phrase you selected ("#{secret}"), or go enter it into # You do not need to leave this page open; pairing will finish #
the computer you want to pair with. automatically.
<p> $else
You do not need to leave this page open; pairing will finish automatically # <p>
as soon as the secret phrase is entered into the other computer. Now you should either go tell the owner of the computer you want to pair #
with the secret phrase you selected ("#{secret}"), or go enter it into #
the computer you want to pair with.
<p>
You do not need to leave this page open; pairing will finish automatically #
as soon as the secret phrase is entered into the other computer.