diff options
-rw-r--r-- | Presence/XMPP.hs | 38 |
1 files changed, 37 insertions, 1 deletions
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs index f81af7c0..bfa5827e 100644 --- a/Presence/XMPP.hs +++ b/Presence/XMPP.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | {-# LANGUAGE FlexibleContexts #-} | 2 | {-# LANGUAGE FlexibleContexts #-} |
3 | {-# LANGUAGE CPP #-} | ||
3 | module XMPP | 4 | module XMPP |
4 | ( module XMPPTypes | 5 | ( module XMPPTypes |
5 | , listenForXmppClients | 6 | , listenForXmppClients |
@@ -44,6 +45,9 @@ import GetHostByAddr | |||
44 | import Data.Monoid | 45 | import Data.Monoid |
45 | import qualified Data.Sequence as Seq | 46 | import qualified Data.Sequence as Seq |
46 | import Data.Foldable (toList) | 47 | import Data.Foldable (toList) |
48 | #ifdef RENDERFLUSH | ||
49 | import Data.Conduit.Blaze | ||
50 | #endif | ||
47 | 51 | ||
48 | data Commands = Send [XML.Event] | QuitThread | 52 | data Commands = Send [XML.Event] | QuitThread |
49 | deriving Prelude.Show | 53 | deriving Prelude.Show |
@@ -134,7 +138,7 @@ gatherElement opentag empty = gatherElement' (empty `mplus` return opentag) 1 | |||
134 | _ | eventIsEndElement tag -> cnt-1 | 138 | _ | eventIsEndElement tag -> cnt-1 |
135 | _ | eventIsBeginElement tag -> cnt+1 | 139 | _ | eventIsBeginElement tag -> cnt+1 |
136 | _ -> cnt | 140 | _ -> cnt |
137 | if (cnt>0) then gatherElement' ts' cnt' | 141 | if (cnt'>0) then gatherElement' ts' cnt' |
138 | else return ts' | 142 | else return ts' |
139 | 143 | ||
140 | voidMaybeT body = (>> return ()) . runMaybeT $ body | 144 | voidMaybeT body = (>> return ()) . runMaybeT $ body |
@@ -164,6 +168,11 @@ fromClient session cmdChan = voidMaybeT $ do | |||
164 | tag@(EventBeginElement _ _) -> do | 168 | tag@(EventBeginElement _ _) -> do |
165 | xs <- gatherElement tag Seq.empty | 169 | xs <- gatherElement tag Seq.empty |
166 | prettyPrint "client-in: ignoring..." (toList xs) | 170 | prettyPrint "client-in: ignoring..." (toList xs) |
171 | {- | ||
172 | liftIO (putStrLn "client-in: ignoring\n{") | ||
173 | liftIO (mapM_ print xs) | ||
174 | liftIO (putStrLn "}") | ||
175 | -} | ||
167 | loop | 176 | loop |
168 | _ -> loop | 177 | _ -> loop |
169 | 178 | ||
@@ -202,7 +211,16 @@ handleClient st src snk = do | |||
202 | pchan <- subscribe session Nothing | 211 | pchan <- subscribe session Nothing |
203 | cmdChan <- atomically newTChan | 212 | cmdChan <- atomically newTChan |
204 | 213 | ||
214 | #ifdef RENDERFLUSH | ||
215 | writer <- async ( toClient pchan cmdChan | ||
216 | $$ flushList | ||
217 | =$= renderBuilderFlush def | ||
218 | =$= builderToByteStringFlush | ||
219 | =$= discardFlush | ||
220 | =$ snk ) | ||
221 | #else | ||
205 | writer <- async ( toClient pchan cmdChan $$ renderChunks =$ snk ) | 222 | writer <- async ( toClient pchan cmdChan $$ renderChunks =$ snk ) |
223 | #endif | ||
206 | finally ( src $= parseBytes def $$ fromClient session cmdChan ) | 224 | finally ( src $= parseBytes def $$ fromClient session cmdChan ) |
207 | $ do | 225 | $ do |
208 | atomically $ writeTChan cmdChan QuitThread | 226 | atomically $ writeTChan cmdChan QuitThread |
@@ -231,8 +249,26 @@ seekRemotePeers config chan = do | |||
231 | -- TODO | 249 | -- TODO |
232 | return () | 250 | return () |
233 | 251 | ||
252 | #ifdef RENDERFLUSH | ||
253 | flushList :: Monad m => ConduitM [a] (Flush a) m () | ||
254 | flushList = fixMaybeT $ \loop -> do | ||
255 | xs <- mawait | ||
256 | lift ( CL.sourceList xs $$ CL.mapM_ (yield . Chunk) ) | ||
257 | lift ( yield Flush ) | ||
258 | loop | ||
259 | |||
260 | discardFlush :: Monad m => ConduitM (Flush a) a m () | ||
261 | discardFlush = fixMaybeT $ \loop -> do | ||
262 | x <- mawait | ||
263 | let unchunk (Chunk a) = a | ||
264 | ischunk (Chunk _) = True | ||
265 | ischunk _ = False | ||
266 | lift . when (ischunk x) $ yield (unchunk x) | ||
267 | loop | ||
268 | #else | ||
234 | renderChunks :: (MonadUnsafeIO m, MonadIO m) => ConduitM [Event] ByteString m () | 269 | renderChunks :: (MonadUnsafeIO m, MonadIO m) => ConduitM [Event] ByteString m () |
235 | renderChunks = fixMaybeT $ \loop -> do | 270 | renderChunks = fixMaybeT $ \loop -> do |
236 | xs <- mawait | 271 | xs <- mawait |
237 | lift . when (not . null $ xs) $ ( CL.sourceList xs $= renderBytes def $$ CL.mapM_ yield ) | 272 | lift . when (not . null $ xs) $ ( CL.sourceList xs $= renderBytes def $$ CL.mapM_ yield ) |
238 | loop | 273 | loop |
274 | #endif | ||