summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Presence/XMLToByteStrings.hs64
-rw-r--r--Presence/XMPP.hs57
2 files changed, 70 insertions, 51 deletions
diff --git a/Presence/XMLToByteStrings.hs b/Presence/XMLToByteStrings.hs
new file mode 100644
index 00000000..d8d2e965
--- /dev/null
+++ b/Presence/XMLToByteStrings.hs
@@ -0,0 +1,64 @@
1{-# LANGUAGE CPP #-}
2module XMLToByteStrings (xmlToByteStrings) where
3
4import Control.Monad.IO.Class
5import Control.Monad.Trans.Class
6import Control.Monad.Trans.Maybe
7import Control.Monad.Fix
8import Control.Monad (when)
9import Data.Conduit
10import qualified Data.Conduit.List as CL
11import Data.XML.Types as XML (Event)
12import qualified Data.ByteString as S (ByteString)
13#ifdef RENDERFLUSH
14import Data.Conduit.Blaze (builderToByteStringFlush)
15import Text.XML.Stream.Render (def,renderBuilderFlush)
16#else
17import Text.XML.Stream.Render (def,renderBytes)
18#endif
19
20fixMaybeT f = (>> return ()) . runMaybeT . fix $ f
21mawait :: Monad m => MaybeT (ConduitM i o m) i
22mawait = MaybeT await
23
24
25xmlToByteStrings ::
26 ( MonadUnsafeIO m
27 , MonadIO m) =>
28 Source m [XML.Event] -> Sink S.ByteString m b -> m b
29xmlToByteStrings xmlSource snk
30#ifdef RENDERFLUSH
31 = xmlSource
32 $$ flushList
33 =$= renderBuilderFlush def
34 =$= builderToByteStringFlush
35 =$= discardFlush
36 =$ snk
37#else
38 = xmlSource $$ renderChunks =$ snk
39#endif
40
41#ifdef RENDERFLUSH
42flushList :: Monad m => ConduitM [a] (Flush a) m ()
43flushList = fixMaybeT $ \loop -> do
44 xs <- mawait
45 lift ( CL.sourceList xs $$ CL.mapM_ (yield . Chunk) )
46 lift ( yield Flush )
47 loop
48
49discardFlush :: Monad m => ConduitM (Flush a) a m ()
50discardFlush = fixMaybeT $ \loop -> do
51 x <- mawait
52 let unchunk (Chunk a) = a
53 ischunk (Chunk _) = True
54 ischunk _ = False
55 lift . when (ischunk x) $ yield (unchunk x)
56 loop
57#else
58renderChunks :: (MonadUnsafeIO m, MonadIO m) => ConduitM [Event] S.ByteString m ()
59renderChunks = fixMaybeT $ \loop -> do
60 xs <- mawait
61 lift . when (not . null $ xs) $ ( CL.sourceList xs $= renderBytes def $$ CL.mapM_ yield )
62 loop
63#endif
64
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs
index e51607b2..ec2feb3a 100644
--- a/Presence/XMPP.hs
+++ b/Presence/XMPP.hs
@@ -1,6 +1,5 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE CPP #-}
4{-# LANGUAGE ViewPatterns #-} 3{-# LANGUAGE ViewPatterns #-}
5module XMPP 4module XMPP
6 ( module XMPPTypes 5 ( module XMPPTypes
@@ -19,6 +18,8 @@ import XMPPTypes
19import SocketLike 18import SocketLike
20import ByteStringOperators 19import ByteStringOperators
21import ControlMaybe 20import ControlMaybe
21import XMLToByteStrings
22
22 23
23import Data.Maybe (catMaybes) 24import Data.Maybe (catMaybes)
24import Data.HList 25import Data.HList
@@ -70,9 +71,6 @@ import Data.Text.Lazy.Encoding as L (decodeUtf8)
70import Data.Text.Lazy (toStrict) 71import Data.Text.Lazy (toStrict)
71import qualified Data.Sequence as Seq 72import qualified Data.Sequence as Seq
72import Data.Foldable (toList) 73import Data.Foldable (toList)
73#ifdef RENDERFLUSH
74import Data.Conduit.Blaze
75#endif
76import Data.List (find) 74import Data.List (find)
77import qualified Text.Show.ByteString as L 75import qualified Text.Show.ByteString as L
78import NestingXML 76import NestingXML
@@ -631,16 +629,7 @@ handleClient st src snk = do
631 rchan <- subscribeToRoster session 629 rchan <- subscribeToRoster session
632 cmdChan <- atomically newTChan 630 cmdChan <- atomically newTChan
633 631
634#ifdef RENDERFLUSH 632 writer <- async ( toClient session pchan cmdChan rchan `xmlToByteStrings` snk )
635 writer <- async ( toClient session pchan cmdChan rchan
636 $$ flushList
637 =$= renderBuilderFlush def
638 =$= builderToByteStringFlush
639 =$= discardFlush
640 =$ snk )
641#else
642 writer <- async ( toClient session pchan cmdChan rchan $$ renderChunks =$ snk )
643#endif
644 finally ( src $= parseBytes def $$ fromClient session cmdChan ) 633 finally ( src $= parseBytes def $$ fromClient session cmdChan )
645 $ do 634 $ do
646 atomically $ writeTChan cmdChan QuitThread 635 atomically $ writeTChan cmdChan QuitThread
@@ -654,30 +643,6 @@ listenForXmppClients ::
654listenForXmppClients addr_family session_factory port st = do 643listenForXmppClients addr_family session_factory port st = do
655 doServer (addr_family .*. port .*. session_factory .*. st) handleClient 644 doServer (addr_family .*. port .*. session_factory .*. st) handleClient
656 645
657#ifdef RENDERFLUSH
658flushList :: Monad m => ConduitM [a] (Flush a) m ()
659flushList = fixMaybeT $ \loop -> do
660 xs <- mawait
661 lift ( CL.sourceList xs $$ CL.mapM_ (yield . Chunk) )
662 lift ( yield Flush )
663 loop
664
665discardFlush :: Monad m => ConduitM (Flush a) a m ()
666discardFlush = fixMaybeT $ \loop -> do
667 x <- mawait
668 let unchunk (Chunk a) = a
669 ischunk (Chunk _) = True
670 ischunk _ = False
671 lift . when (ischunk x) $ yield (unchunk x)
672 loop
673#else
674renderChunks :: (MonadUnsafeIO m, MonadIO m) => ConduitM [Event] ByteString m ()
675renderChunks = fixMaybeT $ \loop -> do
676 xs <- mawait
677 lift . when (not . null $ xs) $ ( CL.sourceList xs $= renderBytes def $$ CL.mapM_ yield )
678 loop
679#endif
680
681 646
682listenForRemotePeers 647listenForRemotePeers
683 :: (HList l, HHead l (XMPPPeerClass session), 648 :: (HList l, HHead l (XMPPPeerClass session),
@@ -1149,19 +1114,9 @@ handleOutgoingToPeer sock cache chan snk = do
1149 let failure cmd = do 1114 let failure cmd = do
1150 writeIORef failed cmd 1115 writeIORef failed cmd
1151 putStrLn $ "Failed: " ++ show cmd 1116 putStrLn $ "Failed: " ++ show cmd
1152 finally ( 1117 finally ( handleIO_ (return ())
1153#ifdef RENDERFLUSH 1118 (toPeer sock cache chan failure `xmlToByteStrings` snk) )
1154 handle (\(IOError _ _ _ _ _ _) -> return ()) $ 1119 $ L.putStrLn $ "(>P) disconnected " <++> showPeer (RemotePeer p)
1155 toPeer sock cache chan failure
1156 $$ flushList
1157 =$= renderBuilderFlush def
1158 =$= builderToByteStringFlush
1159 =$= discardFlush
1160 =$ snk
1161#else
1162 handle (\(IOError _ _ _ _ _ _) -> return ()) $ toPeer sock cache chan failure $$ renderChunks =$ snk
1163#endif
1164 ) $ L.putStrLn $ "(>P) disconnected " <++> showPeer (RemotePeer p)
1165 readIORef failed 1120 readIORef failed
1166 1121
1167connect' :: SockAddr -> Int -> IO (Maybe Socket) 1122connect' :: SockAddr -> Int -> IO (Maybe Socket)