summaryrefslogtreecommitdiff
path: root/Presence/Stanza/Build.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Presence/Stanza/Build.hs')
-rw-r--r--Presence/Stanza/Build.hs142
1 files changed, 142 insertions, 0 deletions
diff --git a/Presence/Stanza/Build.hs b/Presence/Stanza/Build.hs
new file mode 100644
index 00000000..5c4d371a
--- /dev/null
+++ b/Presence/Stanza/Build.hs
@@ -0,0 +1,142 @@
1{-# LANGUAGE CPP #-}
2module Stanza.Build where
3
4import Control.Monad
5import Control.Concurrent.STM
6import Data.Maybe
7import Data.Text (Text)
8import Data.XML.Types as XML
9
10#ifdef THREAD_DEBUG
11import Control.Concurrent.Lifted.Instrument
12#else
13import Control.Concurrent
14import GHC.Conc (labelThread)
15#endif
16
17import EventUtil
18import LockedChan
19import Stanza.Types
20
21makeMessage :: Text -> Text -> Text -> Text -> IO Stanza
22makeMessage namespace from to bod =
23 stanzaFromList typ
24 $ [ EventBeginElement (mkname namespace "message")
25 [ attr "from" from
26 , attr "to" to
27 ]
28 , EventBeginElement (mkname namespace "body") []
29 , EventContent (ContentText bod)
30 , EventEndElement (mkname namespace "body")
31 , EventEndElement (mkname namespace "message") ]
32 where
33 typ = Message { msgThread = Nothing
34 , msgLangMap = [("", lsm)]
35 }
36 lsm = LangSpecificMessage
37 { msgBody = Just bod
38 , msgSubject = Nothing }
39
40makeInformSubscription :: Text -> Text -> Text -> Bool -> IO Stanza
41makeInformSubscription namespace from to approved =
42 stanzaFromList (PresenceInformSubscription approved)
43 $ [ EventBeginElement (mkname namespace "presence")
44 [ attr "from" from
45 , attr "to" to
46 , attr "type" $ if approved then "subscribed"
47 else "unsubscribed" ]
48 , EventEndElement (mkname namespace "presence")]
49
50makePresenceStanza :: Text -> Maybe Text -> JabberShow -> IO Stanza
51makePresenceStanza namespace mjid pstat = do
52 stanzaFromList PresenceStatus { presenceShow = pstat
53 , presencePriority = Nothing
54 , presenceStatus = []
55 , presenceWhiteList = []
56 }
57 $ [ EventBeginElement (mkname namespace "presence")
58 (setFrom $ typ pstat) ]
59 ++ (shw pstat >>= jabberShow) ++
60 [ EventEndElement (mkname namespace "presence")]
61 where
62 setFrom = maybe id
63 (\jid -> (attr "from" jid :) )
64 mjid
65 typ Offline = [attr "type" "unavailable"]
66 typ _ = []
67 shw ExtendedAway = ["xa"]
68 shw Chatty = ["chat"]
69 shw Away = ["away"]
70 shw DoNotDisturb = ["dnd"]
71 shw _ = []
72 jabberShow stat =
73 [ EventBeginElement "{jabber:client}show" []
74 , EventContent (ContentText stat)
75 , EventEndElement "{jabber:client}show" ]
76
77makeRosterUpdate :: Text -> Text -> [(Name, Text)] -> IO Stanza
78makeRosterUpdate tojid contact as = do
79 let attrs = map (uncurry attr) as
80 stanzaFromList Unrecognized
81 [ EventBeginElement "{jabber:client}iq"
82 [ attr "to" tojid
83 , attr "id" "someid"
84 , attr "type" "set"
85 ]
86 , EventBeginElement "{jabber:iq:roster}query" []
87 , EventBeginElement "{jabber:iq:roster}item" (attr "jid" contact : attrs)
88 , EventEndElement "{jabber:iq:roster}item"
89 , EventEndElement "{jabber:iq:roster}query"
90 , EventEndElement "{jabber:client}iq"
91 ]
92
93makePong :: Text -> Maybe Text -> Text -> Text -> [XML.Event]
94makePong namespace mid to from =
95 -- Note: similar to session reply
96 [ EventBeginElement (mkname namespace "iq")
97 $(case mid of
98 Just c -> (("id",[ContentText c]):)
99 _ -> id)
100 [ attr "type" "result"
101 , attr "to" to
102 , attr "from" from
103 ]
104 , EventEndElement (mkname namespace "iq")
105 ]
106
107
108mkname :: Text -> Text -> XML.Name
109mkname namespace name = (Name name (Just namespace) Nothing)
110
111
112stanzaFromList :: StanzaType -> [Event] -> IO Stanza
113stanzaFromList stype reply = do
114 let stanzaTag = listToMaybe reply
115 mid = stanzaTag >>= lookupAttrib "id" . tagAttrs
116 mfrom = stanzaTag >>= lookupAttrib "from" . tagAttrs
117 mto = stanzaTag >>= lookupAttrib "to" . tagAttrs
118 {-
119 isInternal (InternalEnableHack {}) = True
120 isInternal (InternalCacheId {}) = True
121 isInternal _ = False
122 -}
123 (donevar,replyChan,replyClsrs) <- atomically $ do
124 donevar <- newEmptyTMVar -- TMVar ()
125 replyChan <- newLockedChan
126 replyClsrs <- newTVar (Just [])
127 return (donevar,replyChan, replyClsrs)
128 t <- forkIO $ do
129 forM_ reply $ atomically . writeLChan replyChan
130 atomically $ do putTMVar donevar ()
131 writeTVar replyClsrs Nothing
132 labelThread t $ concat $ "stanza." : take 1 (words $ show stype)
133 return Stanza { stanzaType = stype
134 , stanzaId = mid
135 , stanzaTo = mto -- as-is from reply list
136 , stanzaFrom = mfrom -- as-is from reply list
137 , stanzaChan = replyChan
138 , stanzaClosers = replyClsrs
139 , stanzaInterrupt = donevar
140 , stanzaOrigin = LocalPeer
141 }
142