Browse Source

update to conduit 0.5 and xml-conduit 1.0

master
Philipp Balzarek 14 years ago
parent
commit
aec8b3e2c3
  1. 6
      pontarius-xmpp.cabal
  2. 24
      source/Data/Conduit/BufferedSource.hs
  3. 32
      source/Data/Conduit/TLS.hs
  4. 28
      source/Network/Xmpp.hs
  5. 7
      source/Network/Xmpp/Monad.hs
  6. 4
      source/Network/Xmpp/Stream.hs
  7. 9
      source/Text/XML/Stream/Elements.hs

6
pontarius-xmpp.cabal

@ -26,7 +26,7 @@ Library
hs-source-dirs: source hs-source-dirs: source
Exposed: True Exposed: True
Build-Depends: base >4 && <5 Build-Depends: base >4 && <5
, conduit -any , conduit >= 0.5
, void -any , void -any
, resourcet -any , resourcet -any
, containers -any , containers -any
@ -48,8 +48,8 @@ Library
, split -any , split -any
, stm -any , stm -any
, xml-types -any , xml-types -any
, xml-conduit -any , xml-conduit >= 1.0
, xml-types-pickle -any , xml-picklers >= 0.1
, data-default -any , data-default -any
, stringprep >= 0.1.5 , stringprep >= 0.1.5
Exposed-modules: Network.Xmpp Exposed-modules: Network.Xmpp

24
source/Data/Conduit/BufferedSource.hs

@ -1,20 +1,34 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Data.Conduit.BufferedSource where module Data.Conduit.BufferedSource where
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Trans.Class import Control.Monad.Trans.Class
import Control.Exception
import Data.IORef import Data.IORef
import Data.Conduit import Data.Conduit
import Data.Typeable(Typeable)
import qualified Data.Conduit.Internal as DCI
import qualified Data.Conduit.List as CL import qualified Data.Conduit.List as CL
data SourceClosed = SourceClosed deriving (Show, Typeable)
instance Exception SourceClosed
-- | Buffered source from conduit 0.3 -- | Buffered source from conduit 0.3
bufferSource :: MonadIO m => Source m o -> IO (Source m o) bufferSource :: MonadIO m => Source m o -> IO (Source m o)
bufferSource s = do bufferSource s = do
srcRef <- newIORef s srcRef <- newIORef . Just $ DCI.ResumableSource s (return ())
return $ do return $ do
src <- liftIO $ readIORef srcRef src' <- liftIO $ readIORef srcRef
src <- case src' of
Just s -> return s
Nothing -> liftIO $ throwIO SourceClosed
let go src = do let go src = do
(src', res) <- lift $ src $$+ CL.head (src', res) <- lift $ src $$++ CL.head
case res of case res of
Nothing -> return () Nothing -> liftIO $ writeIORef srcRef Nothing
Just x -> liftIO (writeIORef srcRef src') >> yield x >> go src' Just x -> do
liftIO (writeIORef srcRef $ Just src')
yield x
go src'
in go src in go src

32
source/Data/Conduit/TLS.hs

@ -16,6 +16,7 @@ import Crypto.Random
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Conduit import Data.Conduit
import Control.Monad
import Network.TLS as TLS import Network.TLS as TLS
import Network.TLS.Extra as TLSExtra import Network.TLS.Extra as TLSExtra
@ -33,25 +34,24 @@ tlsinit :: (MonadIO m, MonadIO m1) =>
tlsinit debug tlsParams handle = do tlsinit debug tlsParams handle = do
when debug . liftIO $ putStrLn "Debug mode enabled" when debug . liftIO $ putStrLn "Debug mode enabled"
gen <- liftIO $ (newGenIO :: IO SystemRandom) -- TODO: Find better random source? gen <- liftIO $ (newGenIO :: IO SystemRandom) -- TODO: Find better random source?
clientContext <- client tlsParams gen handle con <- client tlsParams gen handle
handshake clientContext handshake con
let src = sourceState let src = forever $ do
clientContext dt <- liftIO $ recvData con
(\con -> do
dt <- recvData con
when debug (liftIO $ BS.putStrLn dt) when debug (liftIO $ BS.putStrLn dt)
return $ StateOpen con dt) yield dt
let snk = sinkState let snk = do
clientContext d <- await
(\con bs -> do case d of
sendData con (BL.fromChunks [bs]) Nothing -> return ()
when debug (liftIO $ BS.putStrLn bs) Just x -> do
return (StateProcessing con)) sendData con (BL.fromChunks [x])
(\_ -> return ()) when debug (liftIO $ BS.putStrLn x)
snk
return ( src return ( src
, snk , snk
, \s -> do , \s -> do
when debug (liftIO $ BS.putStrLn s) when debug (liftIO $ BS.putStrLn s)
sendData clientContext $ BL.fromChunks [s] sendData con $ BL.fromChunks [s]
, clientContext , con
) )

28
source/Network/Xmpp.hs

@ -223,3 +223,31 @@ simpleAuth username passwd resource = flip auth resource $
scramSha1 username Nothing passwd scramSha1 username Nothing passwd
, digestMd5 username Nothing passwd , digestMd5 username Nothing passwd
] ]
-- | The quick and easy way to set up a connection to an XMPP server
--
-- This will
-- * connect to the host
-- * secure the connection with TLS
-- * authenticate to the server using either SCRAM-SHA1 (preferred) or
-- Digest-MD5
-- * bind a resource
--
-- Note that the server might assign a different resource even when we send
-- a preference.
simpleConnect :: HostName -- ^ Target host name
-> Text -- ^ User name (authcid)
-> Text -- ^ Password
-> Maybe Text -- ^ Desired resource (or Nothing to let the server
-- decide)
-> XmppConMonad ()
simpleConnect host username password resource = do
connect host username
startTLS exampleParams
saslResponse <- simpleAuth username password resource
case saslResponse of
Right _ -> return ()
Left e -> error $ show e
return ()

7
source/Network/Xmpp/Monad.hs

@ -78,8 +78,11 @@ pullElement = do
Just r -> return r Just r -> return r
) )
[ Ex.Handler (\StreamEnd -> Ex.throwIO StreamStreamEnd) [ Ex.Handler (\StreamEnd -> Ex.throwIO StreamStreamEnd)
, Ex.Handler (\(InvalidEventStream s) , Ex.Handler (\(InvalidXmppXml s)
-> liftIO . Ex.throwIO $ StreamXMLError s) -> liftIO . Ex.throwIO $ StreamXMLError s)
, Ex.Handler $ \(e :: InvalidEventStream)
-> liftIO . Ex.throwIO $ StreamXMLError (show e)
] ]
-- Pulls an element and unpickles it. -- Pulls an element and unpickles it.
@ -225,7 +228,7 @@ xmppCloseStreams = do
Left _ -> return (elems, False) Left _ -> return (elems, False)
Right elem -> collectElems (elem:elems) Right elem -> collectElems (elem:elems)
debugConduit :: MonadIO m => Pipe BS.ByteString BS.ByteString m () debugConduit :: Pipe l ByteString ByteString u IO b
debugConduit = forever $ do debugConduit = forever $ do
s <- await s <- await
case s of case s of

4
source/Network/Xmpp/Stream.hs

@ -30,7 +30,7 @@ import Text.XML.Stream.Parse as XP
-- Unpickles and returns a stream element. Throws a StreamXMLError on failure. -- Unpickles and returns a stream element. Throws a StreamXMLError on failure.
streamUnpickleElem :: PU [Node] a streamUnpickleElem :: PU [Node] a
-> Element -> Element
-> ErrorT StreamError (Pipe Event Void IO) a -> StreamSink a
streamUnpickleElem p x = do streamUnpickleElem p x = do
case unpickleElem p x of case unpickleElem p x of
Left l -> throwError $ StreamXMLError l Left l -> throwError $ StreamXMLError l
@ -38,7 +38,7 @@ streamUnpickleElem p x = do
-- This is the conduit sink that handles the stream XML events. We extend it -- This is the conduit sink that handles the stream XML events. We extend it
-- with ErrorT capabilities. -- with ErrorT capabilities.
type StreamSink a = ErrorT StreamError (Pipe Event Void IO) a type StreamSink a = ErrorT StreamError (Pipe Event Event Void () IO) a
-- Discards all events before the first EventBeginElement. -- Discards all events before the first EventBeginElement.
throwOutJunk :: Monad m => Sink Event m () throwOutJunk :: Monad m => Sink Event m ()

9
source/Text/XML/Stream/Elements.hs

@ -35,6 +35,10 @@ streamName =
data StreamEnd = StreamEnd deriving (Typeable, Show) data StreamEnd = StreamEnd deriving (Typeable, Show)
instance Exception StreamEnd instance Exception StreamEnd
data InvalidXmppXml = InvalidXmppXml String deriving (Show, Typeable)
instance Exception InvalidXmppXml
elements :: R.MonadThrow m => C.Conduit Event m Element elements :: R.MonadThrow m => C.Conduit Event m Element
elements = do elements = do
x <- C.await x <- C.await
@ -44,7 +48,7 @@ elements = do
elements elements
Just (EventEndElement streamName) -> lift $ R.monadThrow StreamEnd Just (EventEndElement streamName) -> lift $ R.monadThrow StreamEnd
Nothing -> return () Nothing -> return ()
_ -> lift $ R.monadThrow $ InvalidEventStream $ "not an element: " ++ show x _ -> lift $ R.monadThrow $ InvalidXmppXml $ "not an element: " ++ show x
where where
many' f = many' f =
go id go id
@ -58,7 +62,8 @@ elements = do
(y, ns) <- many' goN (y, ns) <- many' goN
if y == Just (EventEndElement n) if y == Just (EventEndElement n)
then return $ Element n as $ compressNodes ns then return $ Element n as $ compressNodes ns
else lift $ R.monadThrow $ InvalidEventStream $ "Missing end element for " ++ show n ++ ", got: " ++ show y else lift $ R.monadThrow $ InvalidXmppXml $
"Missing close tag: " ++ show n
goN = do goN = do
x <- await x <- await
case x of case x of

Loading…
Cancel
Save