module Main (main) where
import Prelude ()
import BasicPrelude
import System.IO
(stdout, stderr, hSetBuffering, BufferMode(LineBuffering))
import Control.Concurrent (threadDelay)
import Control.Concurrent.STM (STM)
import Control.Error (exceptT, ExceptT(..), headZ, throwE)
import Control.Lens (over, set, at, _Right, traverseOf)
import Network (PortID (PortNumber))
import Data.Time.Clock (getCurrentTime)
import qualified Focus
import qualified StmContainers.Map as STMMap
import qualified Data.UUID as UUID
import qualified Data.UUID.V4 as UUID
import qualified Data.XML.Types as XML
import qualified Network.Protocol.XMPP as XMPP
import qualified Network.Protocol.XMPP.Internal as XMPP
import qualified Data.MIME as MIME
import qualified Data.MIME.EncodedWord as MIME
import Email
import IQManager
import Router
import Util
import VCard
newtype RawComponentStanza = RawComponentStanza XML.Element
instance XMPP.Stanza RawComponentStanza where
stanzaTo (RawComponentStanza el) =
XMPP.parseJID =<< XML.attributeText (s"to") el
stanzaFrom (RawComponentStanza el) =
XMPP.parseJID =<< XML.attributeText (s"from") el
stanzaID (RawComponentStanza el) = XML.attributeText (s"id") el
stanzaLang (RawComponentStanza el) = XML.attributeText (s"xml:lang") el
stanzaPayloads (RawComponentStanza el) = XML.elementChildren el
stanzaToElement (RawComponentStanza el) = el
defaultMessageError :: XML.Element
defaultMessageError = errorPayload "cancel" "undefined-condition"
(s"Unknown error sending message") []
overrideID :: Text -> XML.Element -> XML.Element
overrideID newID el = el {
XML.elementAttributes =
(s"id", [XML.ContentText newID]) :
XML.elementAttributes el
}
iqSetHandler ::
STMMap.Map (Maybe Text) XMPP.IQ
-> XMPP.JID
-> [XMPP.JID]
-> XMPP.IQ
-> XMPP.XMPP ()
iqSetHandler replyMap componentJid trustedJids iq@XMPP.IQ {
XMPP.iqFrom = Just from,
XMPP.iqTo = Just to,
XMPP.iqPayload = payload
} | to == componentJid && bareJid from `elem` trustedJids = do
uuid <- liftIO UUID.nextRandom
let sid = UUID.toText uuid
atomicUIO $ STMMap.insert iq (Just sid) replyMap
mapM_ XMPP.putStanza $
RawComponentStanza . overrideID sid <$> payload
void $ forkXMPP $ do
liftIO $ threadDelay 2000000
lookupIQ <- atomicUIO $ STMMap.focus
Focus.lookupAndDelete (Just sid) replyMap
forM_ lookupIQ $ \originalIQ ->
XMPP.putStanza $ iqReply Nothing originalIQ
iqSetHandler _ componentJid _ iq@XMPP.IQ {
XMPP.iqTo = Just XMPP.JID { XMPP.jidNode = Nothing },
XMPP.iqPayload = Just payload
} | [prompt] <- fmap (mconcat . XML.elementText) $
XML.isNamed (s"{jabber:iq:gateway}prompt") =<<
XML.elementChildren =<<
XML.isNamed (s"{jabber:iq:gateway}query") payload =
-- TODO: Check if prompt is a valid email address
XMPP.putStanza $ flip iqReply iq $ Just $ XML.Element
(s"{jabber:iq:gateway}query") [] [
XML.NodeElement $ mkElement
(s"{jabber:iq:gateway}jid") $
XMPP.formatJID $ componentJid {
XMPP.jidNode = Just $ XMPP.Node$
escapeJid prompt
}
]
iqSetHandler _ _ _ iq = XMPP.putStanza $ iqError notImplemented iq
addVCardData :: VCard -> MIME.MIMEMessage -> MIME.MIMEMessage
addVCardData vcard =
set (MIME.headers . at (s"X-URL"))
(MIME.encodeEncodedWords <$> headZ (url vcard)) .
over (MIME.headerFrom MIME.defaultCharsets) (map
(\(MIME.Mailbox name addr) ->
MIME.Mailbox (nickname vcard <|> fn vcard <|> name) addr
)
)
fetchAndAddVCardData ::
(XMPP.IQ -> XMPP.XMPP (STM (Maybe XMPP.IQ)))
-> MIME.MIMEMessage
-> Maybe XMPP.JID
-> XMPP.JID
-> XMPP.XMPP MIME.MIMEMessage
fetchAndAddVCardData sendIQ email from to =
(`addVCardData` email) . maybe emptyVCard parseVCard <$>
(atomicUIO =<< sendIQ (vcardRequest to) { XMPP.iqFrom = from })
messageHandler ::
MIME.Domain
-> String
-> (XMPP.IQ -> XMPP.XMPP (STM (Maybe XMPP.IQ)))
-> XMPP.Message
-> XMPP.XMPP ()
messageHandler fromDomain sendmail sendIQ message@XMPP.Message {
XMPP.messageFrom = from,
XMPP.messageTo = to
} = do
now <- liftIO getCurrentTime
exceptT XMPP.putStanza return $ do
email <- ExceptT $ traverseOf (_Right . emailMessage')
(\msg ->
maybe (return msg)
(fetchAndAddVCardData sendIQ msg to)
from
)
(messageToEmail fromDomain now message)
result <- sendEmail sendmail email
if result then return () else throwE $ messageError err message
where
err = errorPayload "cancel" "undefined-condition"
(s"Could not send email (maybe matched SPAM filter?)") []
messageErrorHandler ::
STMMap.Map (Maybe Text) XMPP.IQ
-> XMPP.Message
-> XMPP.XMPP ()
messageErrorHandler replyMap message = do
let errorElement = fromMaybe defaultMessageError $ errorChild message
lookupIQ <- atomicUIO $ STMMap.focus
Focus.lookupAndDelete (XMPP.stanzaID message) replyMap
forM_ lookupIQ $ \originalIQ ->
XMPP.putStanza $ iqError errorElement originalIQ
-- TODO: else, manual bounce?
iqGetHandler :: XMPP.IQ -> XMPP.XMPP ()
iqGetHandler iq@XMPP.IQ {
XMPP.iqTo = Just to,
XMPP.iqPayload = Just p
} | Nothing <- XMPP.jidNode to,
[_] <- XML.isNamed (s"{http://jabber.org/protocol/disco#info}query") p =
XMPP.putStanza $ iqReply (Just $ XML.Element
(s"{http://jabber.org/protocol/disco#info}query")
(maybeToList nodeAttribute) [
XML.NodeElement $ mkDiscoIdentity
(s"gateway") (s"smtp") (s"Cheogram SMTP")
]
) iq
| Nothing <- XMPP.jidNode to,
[_] <- XML.isNamed (s"{jabber:iq:gateway}query") p =
XMPP.putStanza $ flip iqReply iq $ Just $ XML.Element
(s"{jabber:iq:gateway}query") [] [
XML.NodeElement $ mkElement
(s"{jabber:iq:gateway}prompt")
(s"Email address"),
XML.NodeElement $ mkElement
(s"{jabber:iq:gateway}desc")
(s"Please enter your contact's email address.")
]
| Nothing <- XMPP.jidNode to,
[_] <- XML.isNamed (s"{vcard-temp}vCard") p =
XMPP.putStanza $ flip iqReply iq $ Just $ XML.Element
(s"{vcard-temp}vCard") [] [
XML.NodeElement $ mkElement (s"{vcard-temp}URL")
(s"https://smtp.cheogram.com"),
XML.NodeElement $ mkElement (s"{vcard-temp}DESC") (s"\
\A bidirectional gateway between XMPP and SMTP.\
\\n\nLicensed under AGPLv3+.\n\nSource code \
\for this gateway is available from \
\the listed homepage.\n\n\
\Part of the Soprani.ca project.")
]
where
nodeAttribute = fmap (\node -> (s"node", [XML.ContentText node])) $
XML.attributeText (s"node") p
iqGetHandler iq = XMPP.putStanza $ iqError notImplemented iq
presenceProbeHandler :: XMPP.Presence -> XMPP.XMPP ()
presenceProbeHandler XMPP.Presence {
XMPP.presenceFrom = Just from,
XMPP.presenceTo = Just to@XMPP.JID { XMPP.jidNode = Nothing }
} = XMPP.putStanza $ (XMPP.emptyPresence XMPP.PresenceAvailable) {
XMPP.presenceTo = Just from,
XMPP.presenceFrom = Just to
}
presenceProbeHandler _ = return ()
presenceSubscribeHandler :: XMPP.Presence -> XMPP.XMPP ()
presenceSubscribeHandler XMPP.Presence {
XMPP.presenceFrom = Just from,
XMPP.presenceTo = Just to@XMPP.JID { XMPP.jidNode = Nothing }
} = do
XMPP.putStanza $ (XMPP.emptyPresence XMPP.PresenceSubscribed) {
XMPP.presenceTo = Just from,
XMPP.presenceFrom = Just to
}
XMPP.putStanza $ (XMPP.emptyPresence XMPP.PresenceAvailable) {
XMPP.presenceTo = Just from,
XMPP.presenceFrom = Just to
}
presenceSubscribeHandler _ = return ()
main :: IO ()
main = do
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
(componentJidTxt:host:portTxt:secret:sendmailTxt:trustedTxt) <- getArgs
let Right (MIME.Mailbox _ (MIME.AddrSpec _ emailDomain)) =
MIME.parse (MIME.mailbox MIME.defaultCharsets)
(s"boop@" ++ encodeUtf8 componentJidTxt)
let Just componentJid = XMPP.parseJID componentJidTxt
let Just trustedJids = mapM XMPP.parseJID trustedTxt
let port = PortNumber $ read portTxt
let server = XMPP.Server componentJid (textToString host) port
let sendmail = textToString sendmailTxt
replyMap <- STMMap.newIO
exceptT print return $ runRoutedComponent server secret $ do
(sendIQ, iqReceived) <- iqManager
return $ defaultRoutes {
presenceProbeRoute = presenceProbeHandler,
presenceSubscribeRoute = presenceSubscribeHandler,
iqGetRoute = iqGetHandler,
iqSetRoute =
iqSetHandler replyMap componentJid trustedJids,
iqResultRoute = iqReceived,
iqErrorRoute = iqReceived,
messageNormalRoute =
messageHandler emailDomain sendmail sendIQ,
messageChatRoute =
messageHandler emailDomain sendmail sendIQ,
messageErrorRoute = messageErrorHandler replyMap
}