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

160 lines
4.4 KiB
Haskell
Raw Normal View History

{- git-annex assistant XMPP configuration
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings #-}
{-# 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
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 Utility.SRV
#endif
import Yesod
#ifdef WITH_XMPP
import Network
import Network.Protocol.XMPP
import qualified Data.Text as T
import Control.Exception (SomeException)
#endif
{- Displays an alert suggesting to configure XMPP, with a button. -}
xmppNeeded :: Handler ()
#ifdef WITH_XMPP
xmppNeeded = whenM (isNothing <$> runAnnex Nothing getXMPPCreds) $ do
urlrender <- getUrlRender
void $ liftAssistant $ do
close <- asIO1 removeAlert
addAlert $ xmppNeededAlert $ AlertButton
{ buttonLabel = "Configure a Jabber account"
, buttonUrl = urlrender XMPPR
, buttonAction = Just close
}
#else
xmppNeeded = return ()
#endif
getXMPPR :: Handler RepHtml
#ifdef WITH_XMPP
2012-11-03 01:13:06 +00:00
getXMPPR = getXMPPR' ConfigR
#else
getXMPPR = xmppPage $
$(widgetFile "configurators/xmpp/disabled")
#endif
getXMPPForPairingR :: Handler RepHtml
#ifdef WITH_XMPP
2012-11-11 21:41:56 +00:00
getXMPPForPairingR = getXMPPR' StartXMPPPairR
2012-11-03 01:13:06 +00:00
#else
getXMPPForPairingR = xmppPage $
$(widgetFile "configurators/xmpp/disabled")
#endif
#ifdef WITH_XMPP
getXMPPR' :: Route WebApp -> Handler RepHtml
getXMPPR' redirto = xmppPage $ do
2012-10-26 21:13:30 +00:00
((result, form), enctype) <- lift $ do
oldcreds <- runAnnex Nothing getXMPPCreds
runFormGet $ renderBootstrap $ xmppAForm $
creds2Form <$> oldcreds
2012-11-25 04:38:11 +00:00
let showform problem = $(widgetFile "configurators/xmpp")
case result of
FormSuccess f -> either (showform . Just . show) (lift . storecreds)
=<< liftIO (validateForm f)
_ -> showform Nothing
2012-10-31 06:34:03 +00:00
where
storecreds creds = do
void $ runAnnex undefined $ setXMPPCreds creds
2012-11-03 18:16:17 +00:00
liftAssistant notifyNetMessagerRestart
2012-11-03 01:13:06 +00:00
redirect redirto
#endif
{- Called by client to get a list of buddies.
-
- Returns a div, which will be inserted into the calling page.
-}
getBuddyListR :: NotificationId -> Handler RepHtml
getBuddyListR nid = do
waitNotifier getBuddyListBroadcaster nid
2012-11-25 04:26:46 +00:00
p <- widgetToPageContent buddyListDisplay
hamletToRepHtml $ [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
2012-11-10 20:35:09 +00:00
buddies <- lift $ liftAssistant $ do
rs <- filter isXMPPRemote . syncGitRemotes <$> getDaemonStatus
2012-11-10 20:35:09 +00:00
let pairedwith = catMaybes $ map (parseJID . getXMPPClientID) rs
catMaybes . map (buddySummary pairedwith)
<$> (getBuddyList <<~ buddyList)
2012-11-03 01:13:06 +00:00
$(widgetFile "configurators/xmpp/buddylist")
#endif
2012-11-03 01:13:06 +00:00
where
ident = "buddylist"
#ifdef WITH_XMPP
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)
xmppAForm :: (Maybe XMPPForm) -> AForm WebApp WebApp XMPPForm
xmppAForm def = XMPPForm
<$> areq jidField "Jabber address" (formJID <$> def)
<*> areq passwordField "Password" Nothing
jidField :: Field WebApp WebApp 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 SomeException XMPPCreds)
validateForm f = do
let jid = fromMaybe (error "bad JID") $ parseJID (formJID f)
let domain = T.unpack $ strDomain $ jidDomain jid
hostports <- lookupSRV $ mkSRVTcp "xmpp-client" domain
let username = fromMaybe "" (strNode <$> jidNode jid)
case hostports of
((h, PortNumber p):_) -> testXMPP $ XMPPCreds
{ xmppUsername = username
, xmppPassword = formPassword f
, xmppHostname = h
, xmppPort = fromIntegral p
, xmppJID = formJID f
}
_ -> testXMPP $ XMPPCreds
{ xmppUsername = username
, xmppPassword = formPassword f
, xmppHostname = T.unpack $ strDomain $ jidDomain jid
, xmppPort = 5222
, xmppJID = formJID f
}
testXMPP :: XMPPCreds -> IO (Either SomeException XMPPCreds)
testXMPP creds = either Left (const $ Right creds)
<$> connectXMPP creds (const noop)
#endif
xmppPage :: Widget -> Handler RepHtml
2012-11-25 04:26:46 +00:00
xmppPage = page "Jabber" (Just Config)