git-annex/Assistant/WebApp/Configurators/XMPP.hs

227 lines
6.4 KiB
Haskell
Raw Normal View History

{- git-annex assistant XMPP configuration
-
- Copyright 2012 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
2013-06-05 01:02:09 +00:00
{-# LANGUAGE TypeFamilies, QuasiQuotes, TemplateHaskell, OverloadedStrings, FlexibleContexts #-}
{-# LANGUAGE CPP #-}
module Assistant.WebApp.Configurators.XMPP where
2012-11-25 04:26:46 +00:00
import Assistant.WebApp.Common
2012-11-03 01:13:06 +00:00
import Assistant.WebApp.Notifications
import Utility.NotificationBroadcaster
#ifdef WITH_XMPP
2013-06-21 02:25:45 +00:00
import qualified Remote
2012-11-02 16:59:31 +00:00
import Assistant.XMPP.Client
2012-11-03 01:13:06 +00:00
import Assistant.XMPP.Buddies
import Assistant.Types.Buddies
2012-11-03 18:16:17 +00:00
import Assistant.NetMessager
import Assistant.Alert
import Assistant.DaemonStatus
import Assistant.WebApp.RepoList
import Assistant.WebApp.Configurators
import Assistant.XMPP
import qualified Git.Remote.Remove
import Remote.List
import Creds
#endif
#ifdef WITH_XMPP
import Network.Protocol.XMPP
import Network
import qualified Data.Text as T
#endif
2013-03-24 22:55:19 +00:00
{- When appropriate, displays an alert suggesting to configure a cloud repo
- to suppliment an XMPP remote. -}
2013-03-24 22:55:19 +00:00
checkCloudRepos :: UrlRenderer -> Remote -> Assistant ()
#ifdef WITH_XMPP
2013-03-24 22:55:19 +00:00
checkCloudRepos urlrenderer r =
unlessM (syncingToCloudRemote <$> getDaemonStatus) $ do
buddyname <- getBuddyName $ Remote.uuid r
button <- mkAlertButton True "Add a cloud repository" urlrenderer $
2013-04-04 05:48:26 +00:00
NeedCloudRepoR $ Remote.uuid r
void $ addAlert $ cloudRepoNeededAlert buddyname button
#else
2013-03-24 22:55:19 +00:00
checkCloudRepos _ _ = noop
#endif
2013-04-16 23:23:26 +00:00
#ifdef WITH_XMPP
{- Returns the name of the friend corresponding to a
- repository's UUID, but not if it's our name. -}
getBuddyName :: UUID -> Assistant (Maybe String)
getBuddyName u = go =<< getclientjid
where
go Nothing = return Nothing
go (Just myjid) = (T.unpack . buddyName <$>)
. headMaybe
. filter (\j -> baseJID j /= baseJID myjid)
. map fst
. filter (\(_, r) -> Remote.uuid r == u)
<$> getXMPPRemotes
getclientjid = maybe Nothing parseJID . xmppClientID
<$> getDaemonStatus
2013-04-16 23:23:26 +00:00
#endif
getNeedCloudRepoR :: UUID -> Handler Html
#ifdef WITH_XMPP
getNeedCloudRepoR for = page "Cloud repository needed" (Just Configuration) $ do
buddyname <- liftAssistant $ getBuddyName for
$(widgetFile "configurators/xmpp/needcloudrepo")
#else
2013-04-16 23:23:26 +00:00
getNeedCloudRepoR _ = xmppPage $
$(widgetFile "configurators/xmpp/disabled")
#endif
getXMPPConfigR :: Handler Html
getXMPPConfigR = postXMPPConfigR
postXMPPConfigR :: Handler Html
postXMPPConfigR = xmppform DashboardR
getXMPPConfigForPairFriendR :: Handler Html
getXMPPConfigForPairFriendR = postXMPPConfigForPairFriendR
postXMPPConfigForPairFriendR :: Handler Html
postXMPPConfigForPairFriendR = xmppform StartXMPPPairFriendR
getXMPPConfigForPairSelfR :: Handler Html
getXMPPConfigForPairSelfR = postXMPPConfigForPairSelfR
postXMPPConfigForPairSelfR :: Handler Html
postXMPPConfigForPairSelfR = xmppform StartXMPPPairSelfR
xmppform :: Route WebApp -> Handler Html
2013-03-09 02:25:23 +00:00
#ifdef WITH_XMPP
xmppform next = xmppPage $ do
((result, form), enctype) <- liftH $ do
oldcreds <- liftAnnex getXMPPCreds
2014-04-18 00:07:09 +00:00
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ xmppAForm $
2012-10-26 21:13:30 +00:00
creds2Form <$> oldcreds
2012-11-25 04:38:11 +00:00
let showform problem = $(widgetFile "configurators/xmpp")
case result of
FormSuccess f -> either (showform . Just) (liftH . storecreds)
=<< liftIO (validateForm f)
_ -> showform Nothing
2012-10-31 06:34:03 +00:00
where
storecreds creds = do
void $ liftAnnex $ setXMPPCreds creds
2012-11-03 18:16:17 +00:00
liftAssistant notifyNetMessagerRestart
redirect next
#else
2013-05-02 17:04:49 +00:00
xmppform _ = xmppPage $
$(widgetFile "configurators/xmpp/disabled")
2012-11-03 01:13:06 +00:00
#endif
{- Called by client to get a list of buddies.
-
- Returns a div, which will be inserted into the calling page.
-}
getBuddyListR :: NotificationId -> Handler Html
2012-11-03 01:13:06 +00:00
getBuddyListR nid = do
waitNotifier getBuddyListBroadcaster nid
2012-11-25 04:26:46 +00:00
p <- widgetToPageContent buddyListDisplay
withUrlRenderer $ [hamlet|^{pageBody p}|]
2012-11-03 01:13:06 +00:00
buddyListDisplay :: Widget
buddyListDisplay = do
autoUpdate ident NotifierBuddyListR (10 :: Int) (10 :: Int)
#ifdef WITH_XMPP
myjid <- liftAssistant $ xmppClientID <$> getDaemonStatus
let isself (BuddyKey b) = Just b == myjid
buddies <- liftAssistant $ do
pairedwith <- map fst <$> getXMPPRemotes
2012-11-10 20:35:09 +00:00
catMaybes . map (buddySummary pairedwith)
<$> (getBuddyList <<~ buddyList)
2012-11-03 01:13:06 +00:00
$(widgetFile "configurators/xmpp/buddylist")
2013-10-02 05:06:59 +00:00
#else
noop
#endif
2012-11-03 01:13:06 +00:00
where
ident = "buddylist"
#ifdef WITH_XMPP
getXMPPRemotes :: Assistant [(JID, Remote)]
getXMPPRemotes = catMaybes . map pair . filter Remote.isXMPPRemote . syncGitRemotes
<$> getDaemonStatus
where
pair r = maybe Nothing (\jid -> Just (jid, r)) $
parseJID $ getXMPPClientID r
data XMPPForm = XMPPForm
{ formJID :: Text
, formPassword :: Text }
2012-10-26 21:13:30 +00:00
creds2Form :: XMPPCreds -> XMPPForm
creds2Form c = XMPPForm (xmppJID c) (xmppPassword c)
2013-06-03 20:33:05 +00:00
xmppAForm :: (Maybe XMPPForm) -> MkAForm XMPPForm
2015-01-28 20:11:28 +00:00
xmppAForm d = XMPPForm
<$> areq jidField (bfs "Jabber address") (formJID <$> d)
2014-04-18 00:07:09 +00:00
<*> areq passwordField (bfs "Password") Nothing
2013-06-03 20:33:05 +00:00
jidField :: MkField Text
jidField = checkBool (isJust . parseJID) bad textField
2012-10-31 06:34:03 +00:00
where
bad :: Text
bad = "This should look like an email address.."
validateForm :: XMPPForm -> IO (Either String XMPPCreds)
validateForm f = do
let jid = fromMaybe (error "bad JID") $ parseJID (formJID f)
let username = fromMaybe "" (strNode <$> jidNode jid)
testXMPP $ XMPPCreds
{ xmppUsername = username
, xmppPassword = formPassword f
, xmppHostname = T.unpack $ strDomain $ jidDomain jid
, xmppPort = 5222
, xmppJID = formJID f
}
testXMPP :: XMPPCreds -> IO (Either String XMPPCreds)
testXMPP creds = do
(good, bad) <- partition (either (const False) (const True) . snd)
<$> connectXMPP creds (const noop)
case good of
(((h, PortNumber p), _):_) -> return $ Right $ creds
{ xmppHostname = h
, xmppPort = fromIntegral p
}
(((h, _), _):_) -> return $ Right $ creds
{ xmppHostname = h
}
_ -> return $ Left $ intercalate "; " $ map formatlog bad
where
formatlog ((h, p), Left e) = "host " ++ h ++ ":" ++ showport p ++ " failed: " ++ show e
formatlog _ = ""
showport (PortNumber n) = show n
showport (Service s) = s
showport (UnixSocket s) = s
#endif
getDisconnectXMPPR :: Handler Html
getDisconnectXMPPR = do
#ifdef WITH_XMPP
rs <- filter Remote.isXMPPRemote . syncRemotes
<$> liftAssistant getDaemonStatus
liftAnnex $ do
mapM_ (inRepo . Git.Remote.Remove.remove . Remote.name) rs
void remoteListRefresh
removeCreds xmppCredsFile
liftAssistant $ do
updateSyncRemotes
notifyNetMessagerRestart
redirect DashboardR
#else
xmppPage $ $(widgetFile "configurators/xmpp/disabled")
#endif
xmppPage :: Widget -> Handler Html
xmppPage = page "Jabber" (Just Configuration)