{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NoMonomorphismRestriction #-} module XMPPToTox ( module XMPPToTox , CryptoMessage(..) ) where import Control.Applicative import Control.Monad import Control.Monad.Catch import Data.Conduit import Data.Dependent.Sum import Data.Function import Data.Monoid import Data.Text (Text) import Data.Text.Encoding as T import Data.Word import Data.XML.Types as XML import Text.XML.Stream.Parse as XML import Data.Tox.Msg as Tox import Network.Tox.Crypto.Transport (CryptoMessage (..)) import XMPPServer as XMPP (JabberShow (..)) -- Debugging. Not real Tox message. funnyMessage :: MonadThrow m => Text -> ConduitM i CryptoMessage m () funnyMessage txt = yield $ Pkt Padding ==> Padded (T.encodeUtf8 txt) sendMsg :: MonadThrow m => Text -> ConduitM i CryptoMessage m () sendMsg txt = do yield $ Pkt MESSAGE ==> txt yield $ Pkt TYPING ==> False -- Message send implies not typing. eom :: MonadThrow m => ConduitM Event o m () eom = many_ ignoreAnyTreeContent msgToTox :: MonadThrow m => ConduitM Event CryptoMessage m (Maybe ()) msgToTox = tag' "{jabber:server}message" (requireAttr "type" >>= \case "chat" -> ignoreAttrs _ -> empty) $ \_ -> many_ $ choose [ tagIgnoreAttrs "{jabber:server}body" $ do content >>= sendMsg eom , tagIgnoreAttrs "{http://jabber.org/protocol/chatstates}composing" $ do yield $ Pkt TYPING ==> True eom , tagIgnoreAttrs "{http://jabber.org/protocol/chatstates}active" $ do yield $ Pkt TYPING ==> False eom , tagIgnoreAttrs "{http://jabber.org/protocol/chatstates}paused" $ do yield $ Pkt TYPING ==> False eom , ignoreAnyTreeContent ] readJabberShow :: Text -> JabberShow readJabberShow "xa" = ExtendedAway readJabberShow "chat" = Chatty readJabberShow "away" = XMPP.Away readJabberShow "dnd" = DoNotDisturb readJabberShow _ = Available -- | Convert XMPP "show" field to Tox USERSTATUS. jabberUserStatus :: JabberShow -> Tox.UserStatus jabberUserStatus Available = Online jabberUserStatus Chatty = Online jabberUserStatus XMPP.Away = Tox.Away jabberUserStatus ExtendedAway = Tox.Away jabberUserStatus Offline = Tox.Away jabberUserStatus DoNotDisturb = Busy requireMissing :: XML.Name -> AttrParser () requireMissing nm = force ("Unexpected "++show (XML.nameLocalName nm)++" attribute.") $ do m <- attr nm case m of Nothing -> return $ Just () Just _ -> return Nothing presenceToTox :: MonadThrow m => ConduitM Event CryptoMessage m (Maybe ()) presenceToTox = tag' "{jabber:server}presence" (requireMissing "type" >> ignoreAttrs) $ \_ -> do xs <- XML.many $ choose [ tagIgnoreAttrs "{jabber:server}show" $ do shw <- readJabberShow <$> content yield $ Pkt USERSTATUS ==> jabberUserStatus shw eom return (M USERSTATUS) , tagIgnoreAttrs "{jabber:server}status" -- TODO: The tag may occur multiple times for different "xml:lang" values. $ do txt <- content yield $ Pkt STATUSMESSAGE ==> txt eom return (M STATUSMESSAGE) , fmap (const (M Padding)) <$> ignoreAnyTreeContent -- Ignore the priority tag and anything else. ] when (not $ (M USERSTATUS) `elem` xs) $ do -- Missing element means Available. yield $ Pkt USERSTATUS ==> jabberUserStatus Available when (not $ (M STATUSMESSAGE) `elem` xs) $ do -- Missing implies empty status. yield $ Pkt STATUSMESSAGE ==> mempty unknownToTox :: MonadThrow m => ConduitM Event CryptoMessage m (Maybe ()) unknownToTox = tag anyName (\n -> ignoreAttrs >> return n) $ \n -> do funnyMessage $ nameLocalName n eom xmppToTox :: MonadThrow m => ConduitM XML.Event CryptoMessage m () xmppToTox = do eventBeginDocument <- await streamTag <- await fix $ \loop -> do got <- choose [ msgToTox , presenceToTox , unknownToTox ] forM_ got $ \_ -> loop