blob: f0505ac7145ff1b35721afbe69043fbc79e97184 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
|
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module XMPPToTox
( module XMPPToTox
, CryptoMessage(..)
, MessageID(..)
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Catch
import Data.Conduit
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 Network.Tox.Crypto.Transport (CryptoMessage (..), MessageID (..))
import Text.XML.Stream.Parse as XML
import XMPPServer (JabberShow(..))
-- Debugging. Not real Tox message.
funnyMessage :: MonadThrow m => Text -> ConduitM i CryptoMessage m ()
funnyMessage txt = yield $ UpToN Padding (T.encodeUtf8 txt)
sendMsg :: MonadThrow m => Text -> ConduitM i CryptoMessage m ()
sendMsg txt = do
yield $ UpToN MESSAGE (T.encodeUtf8 txt)
yield $ TwoByte TYPING 0 -- 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 $ TwoByte TYPING 1
eom
, tagIgnoreAttrs "{http://jabber.org/protocol/chatstates}active"
$ do yield $ TwoByte TYPING 0
eom
, tagIgnoreAttrs "{http://jabber.org/protocol/chatstates}paused"
$ do yield $ TwoByte TYPING 0
eom
, ignoreAnyTreeContent
]
readJabberShow :: Text -> JabberShow
readJabberShow "xa" = ExtendedAway
readJabberShow "chat" = Chatty
readJabberShow "away" = Away
readJabberShow "dnd" = DoNotDisturb
readJabberShow _ = Available
-- | Convert XMPP "show" field to Tox USERSTATUS.
jabberUserStatus :: JabberShow -> Word8
jabberUserStatus Available = 0
jabberUserStatus Chatty = 0
jabberUserStatus Away = 1
jabberUserStatus ExtendedAway = 1
jabberUserStatus Offline = 1
jabberUserStatus DoNotDisturb = 2
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 $ TwoByte USERSTATUS $ jabberUserStatus shw
eom
return USERSTATUS
, tagIgnoreAttrs "{jabber:server}status"
-- TODO: The <status> tag may occur multiple times for different "xml:lang" values.
$ do txt <- content
yield $ UpToN STATUSMESSAGE $ T.encodeUtf8 txt
eom
return STATUSMESSAGE
, fmap (const Padding) <$> ignoreAnyTreeContent -- Ignore the priority tag and anything else.
]
when (not $ USERSTATUS `elem` xs) $ do
-- Missing <show> element means Available.
yield $ TwoByte USERSTATUS $ jabberUserStatus Available
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
|