Browse Source

replace XMPP with Xmpp everywhere to unify style

replace SASL with Sasl
replace DIGEST_MD5 with DigestMD5
replace PLAIN with Plain
master
Philipp Balzarek 14 years ago
parent
commit
d23ae0f149
  1. 8
      examples/EchoClient.hs
  2. 12
      examples/Example.hs
  3. 2
      examples/IBR.hs
  4. 41
      pontarius.cabal
  5. 13
      source/Network/XMPP/Concurrent.hs
  6. 7
      source/Network/XMPP/IM.hs
  7. 34
      source/Network/Xmpp.hs
  8. 10
      source/Network/Xmpp/Bind.hs
  9. 13
      source/Network/Xmpp/Concurrent.hs
  10. 14
      source/Network/Xmpp/Concurrent/IQ.hs
  11. 60
      source/Network/Xmpp/Concurrent/Monad.hs
  12. 22
      source/Network/Xmpp/Concurrent/Threads.hs
  13. 14
      source/Network/Xmpp/Concurrent/Types.hs
  14. 7
      source/Network/Xmpp/IM.hs
  15. 6
      source/Network/Xmpp/IM/Message.hs
  16. 4
      source/Network/Xmpp/IM/Presence.hs
  17. 2
      source/Network/Xmpp/JID.hs
  18. 6
      source/Network/Xmpp/Marshal.hs
  19. 4
      source/Network/Xmpp/Message.hs
  20. 36
      source/Network/Xmpp/Monad.hs
  21. 4
      source/Network/Xmpp/Pickle.hs
  22. 4
      source/Network/Xmpp/Presence.hs
  23. 24
      source/Network/Xmpp/Sasl.hs
  24. 24
      source/Network/Xmpp/Sasl/DigestMD5.hs
  25. 16
      source/Network/Xmpp/Sasl/Plain.hs
  26. 6
      source/Network/Xmpp/Sasl/Sasl.hs
  27. 4
      source/Network/Xmpp/Sasl/Types.hs
  28. 14
      source/Network/Xmpp/Session.hs
  29. 12
      source/Network/Xmpp/Stream.hs
  30. 20
      source/Network/Xmpp/TLS.hs
  31. 30
      source/Network/Xmpp/Types.hs
  32. 4
      source/Network/Xmpp/Utilities.hs

8
examples/EchoClient.hs

@ -19,8 +19,8 @@ import Control.Monad (forever) @@ -19,8 +19,8 @@ import Control.Monad (forever)
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromJust, isJust)
import Network.XMPP
import Network.XMPP.IM
import Network.Xmpp
import Network.Xmpp.IM
-- Server and authentication details.
@ -47,9 +47,9 @@ main = do @@ -47,9 +47,9 @@ main = do
return ()
return ()
-- Pull message stanzas, verify that they originate from a `full' XMPP
-- Pull message stanzas, verify that they originate from a `full' Xmpp
-- address, and, if so, `echo' the message back.
echo :: XMPP ()
echo :: Xmpp ()
echo = forever $ do
result <- pullMessage
case result of

12
examples/Example.hs

@ -3,7 +3,7 @@ module Example where @@ -3,7 +3,7 @@ module Example where
import Data.Text as T
import Network.XMPP
import Network.Xmpp
import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad
@ -12,10 +12,10 @@ import Control.Monad.IO.Class @@ -12,10 +12,10 @@ import Control.Monad.IO.Class
philonous :: JID
philonous = read "uart14@species64739.dyndns.org"
attXmpp :: STM a -> XMPPThread a
attXmpp :: STM a -> XmppThread a
attXmpp = liftIO . atomically
autoAccept :: XMPPThread ()
autoAccept :: XmppThread ()
autoAccept = forever $ do
st <- pullPresence
case st of
@ -24,7 +24,7 @@ autoAccept = forever $ do @@ -24,7 +24,7 @@ autoAccept = forever $ do
Presence Nothing from idq (Just Subscribed) Nothing Nothing Nothing []
_ -> return ()
mirror :: XMPPThread ()
mirror :: XmppThread ()
mirror = forever $ do
st <- pullMessage
case st of
@ -43,8 +43,8 @@ main = do @@ -43,8 +43,8 @@ main = do
xmppThreadedBind (Just "botsi")
-- singleThreaded $ xmppBind (Just "botsi")
singleThreaded $ xmppSession
forkXMPP autoAccept
forkXMPP mirror
forkXmpp autoAccept
forkXmpp mirror
sendS . SPresence $ Presence Nothing Nothing Nothing Nothing
(Just Available) Nothing Nothing []
sendS . SMessage $ Message Nothing philonous Nothing Nothing Nothing

2
examples/IBR.hs

@ -11,7 +11,7 @@ this file may be used freely, as if it is in the public domain. @@ -11,7 +11,7 @@ this file may be used freely, as if it is in the public domain.
module Examples.IBR () where
import Network.XMPP
import Network.Xmpp
-- Server and authentication details.

41
pontarius.cabal

@ -50,26 +50,29 @@ Library @@ -50,26 +50,29 @@ Library
, xml-types-pickle -any
, data-default -any
, stringprep >= 0.1.5
Exposed-modules: Network.XMPP
, Network.XMPP.Bind
, Network.XMPP.Concurrent
, Network.XMPP.IM
, Network.XMPP.Marshal
, Network.XMPP.Monad
, Network.XMPP.Message
, Network.XMPP.Pickle
, Network.XMPP.Presence
, Network.XMPP.SASL
, Network.XMPP.Session
, Network.XMPP.Stream
, Network.XMPP.TLS
, Network.XMPP.Types
Exposed-modules: Network.Xmpp
, Network.Xmpp.Bind
, Network.Xmpp.Concurrent
, Network.Xmpp.IM
, Network.Xmpp.Marshal
, Network.Xmpp.Monad
, Network.Xmpp.Message
, Network.Xmpp.Pickle
, Network.Xmpp.Presence
, Network.Xmpp.Sasl
, Network.Xmpp.Sasl.Plain
, Network.Xmpp.Sasl.DigestMD5
, Network.Xmpp.Sasl.Types
, Network.Xmpp.Session
, Network.Xmpp.Stream
, Network.Xmpp.TLS
, Network.Xmpp.Types
Other-modules:
Network.XMPP.JID
, Network.XMPP.Concurrent.Types
, Network.XMPP.Concurrent.IQ
, Network.XMPP.Concurrent.Threads
, Network.XMPP.Concurrent.Monad
Network.Xmpp.JID
, Network.Xmpp.Concurrent.Types
, Network.Xmpp.Concurrent.IQ
, Network.Xmpp.Concurrent.Threads
, Network.Xmpp.Concurrent.Monad
, Text.XML.Stream.Elements
, Data.Conduit.BufferedSource
, Data.Conduit.TLS

13
source/Network/XMPP/Concurrent.hs

@ -1,13 +0,0 @@ @@ -1,13 +0,0 @@
module Network.XMPP.Concurrent
( Session
, XMPP
, module Network.XMPP.Concurrent.Monad
, module Network.XMPP.Concurrent.Threads
, module Network.XMPP.Concurrent.IQ
) where
import Network.XMPP.Concurrent.Types
import Network.XMPP.Concurrent.Monad
import Network.XMPP.Concurrent.Threads
import Network.XMPP.Concurrent.IQ

7
source/Network/XMPP/IM.hs

@ -1,7 +0,0 @@ @@ -1,7 +0,0 @@
module Network.XMPP.IM
( module Network.XMPP.IM.Message
, module Network.XMPP.IM.Presence
) where
import Network.XMPP.IM.Message
import Network.XMPP.IM.Presence

34
source/Network/XMPP.hs → source/Network/Xmpp.hs

@ -21,7 +21,7 @@ @@ -21,7 +21,7 @@
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
module Network.XMPP
module Network.Xmpp
( -- * Session management
withNewSession
, withSession
@ -96,7 +96,7 @@ module Network.XMPP @@ -96,7 +96,7 @@ module Network.XMPP
, Presence(..)
, PresenceError(..)
-- *** creating
, module Network.XMPP.Presence
, module Network.Xmpp.Presence
-- *** sending
, sendPresence
-- *** receiving
@ -127,7 +127,7 @@ module Network.XMPP @@ -127,7 +127,7 @@ module Network.XMPP
, iqRequestPayload
, iqResultPayload
-- * Threads
, XMPP
, Xmpp
, fork
, forkSession
-- * Misc
@ -138,23 +138,23 @@ import Data.Text as Text @@ -138,23 +138,23 @@ import Data.Text as Text
import Network
import qualified Network.TLS as TLS
import Network.XMPP.Bind
import Network.XMPP.Concurrent
import Network.XMPP.Concurrent.Types
import Network.XMPP.Message
import Network.XMPP.Monad
import Network.XMPP.Presence
import Network.XMPP.SASL
import Network.XMPP.SASL.Types
import Network.XMPP.Session
import Network.XMPP.Stream
import Network.XMPP.TLS
import Network.XMPP.Types
import Network.Xmpp.Bind
import Network.Xmpp.Concurrent
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Message
import Network.Xmpp.Monad
import Network.Xmpp.Presence
import Network.Xmpp.Sasl
import Network.Xmpp.Sasl.Types
import Network.Xmpp.Session
import Network.Xmpp.Stream
import Network.Xmpp.TLS
import Network.Xmpp.Types
import Control.Monad.Error
-- | Connect to host with given address.
connect :: HostName -> Text -> XMPPConMonad (Either StreamError ())
connect :: HostName -> Text -> XmppConMonad (Either StreamError ())
connect address hostname = xmppRawConnect address hostname >> xmppStartStream
-- | Authenticate to the server with the given username and password
@ -163,7 +163,7 @@ auth :: Text.Text -- ^ The username @@ -163,7 +163,7 @@ auth :: Text.Text -- ^ The username
-> Text.Text -- ^ The password
-> Maybe Text -- ^ The desired resource or 'Nothing' to let the server
-- assign one
-> XMPPConMonad (Either AuthError Text.Text)
-> XmppConMonad (Either AuthError Text.Text)
auth username passwd resource = runErrorT $ do
ErrorT $ xmppSASL [DIGEST_MD5Credentials Nothing username passwd]
res <- lift $ xmppBind resource

10
source/Network/XMPP/Bind.hs → source/Network/Xmpp/Bind.hs

@ -2,16 +2,16 @@ @@ -2,16 +2,16 @@
{-# OPTIONS_HADDOCK hide #-}
module Network.XMPP.Bind where
module Network.Xmpp.Bind where
import Data.Text as Text
import Data.XML.Pickle
import Data.XML.Types
import Network.XMPP.Types
import Network.XMPP.Pickle
import Network.XMPP.Monad
import Network.Xmpp.Types
import Network.Xmpp.Pickle
import Network.Xmpp.Monad
-- Produces a `bind' element, optionally wrapping a resource.
bindBody :: Maybe Text -> Element
@ -24,7 +24,7 @@ bindBody = pickleElem $ @@ -24,7 +24,7 @@ bindBody = pickleElem $
-- Sends a (synchronous) IQ set request for a (`Just') given or server-generated
-- resource and extract the JID from the non-error response.
xmppBind :: Maybe Text -> XMPPConMonad Text
xmppBind :: Maybe Text -> XmppConMonad Text
xmppBind rsrc = do
answer <- xmppSendIQ' "bind" Nothing Set Nothing (bindBody rsrc)
let Right IQResult{iqResultPayload = Just b} = answer -- TODO: Error handling

13
source/Network/Xmpp/Concurrent.hs

@ -0,0 +1,13 @@ @@ -0,0 +1,13 @@
module Network.Xmpp.Concurrent
( Session
, Xmpp
, module Network.Xmpp.Concurrent.Monad
, module Network.Xmpp.Concurrent.Threads
, module Network.Xmpp.Concurrent.IQ
) where
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Concurrent.Monad
import Network.Xmpp.Concurrent.Threads
import Network.Xmpp.Concurrent.IQ

14
source/Network/XMPP/Concurrent/IQ.hs → source/Network/Xmpp/Concurrent/IQ.hs

@ -1,4 +1,4 @@ @@ -1,4 +1,4 @@
module Network.XMPP.Concurrent.IQ where
module Network.Xmpp.Concurrent.IQ where
import Control.Concurrent.STM
import Control.Monad.IO.Class
@ -7,9 +7,9 @@ import Control.Monad.Trans.Reader @@ -7,9 +7,9 @@ import Control.Monad.Trans.Reader
import Data.XML.Types
import qualified Data.Map as Map
import Network.XMPP.Concurrent.Types
import Network.XMPP.Concurrent.Monad
import Network.XMPP.Types
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Concurrent.Monad
import Network.Xmpp.Types
-- | Sends an IQ, returns a 'TMVar' that will be filled with the first inbound
-- IQ with a matching ID that has type @result@ or @error@.
@ -18,7 +18,7 @@ sendIQ :: Maybe JID -- ^ Recipient (to) @@ -18,7 +18,7 @@ sendIQ :: Maybe JID -- ^ Recipient (to)
-> Maybe LangTag -- ^ Language tag of the payload (@Nothing@ for
-- default)
-> Element -- ^ The IQ body (there has to be exactly one)
-> XMPP (TMVar IQResponse)
-> Xmpp (TMVar IQResponse)
sendIQ to tp lang body = do -- TODO: Add timeout
newId <- liftIO =<< asks idGenerator
handlers <- asks iqHandlers
@ -36,14 +36,14 @@ sendIQ' :: Maybe JID @@ -36,14 +36,14 @@ sendIQ' :: Maybe JID
-> IQRequestType
-> Maybe LangTag
-> Element
-> XMPP IQResponse
-> Xmpp IQResponse
sendIQ' to tp lang body = do
ref <- sendIQ to tp lang body
liftIO . atomically $ takeTMVar ref
answerIQ :: IQRequestTicket
-> Either StanzaError (Maybe Element)
-> XMPP Bool
-> Xmpp Bool
answerIQ (IQRequestTicket
sentRef
(IQRequest iqid from _to lang _tp bd))

60
source/Network/XMPP/Concurrent/Monad.hs → source/Network/Xmpp/Concurrent/Monad.hs

@ -1,6 +1,6 @@ @@ -1,6 +1,6 @@
module Network.XMPP.Concurrent.Monad where
module Network.Xmpp.Concurrent.Monad where
import Network.XMPP.Types
import Network.Xmpp.Types
import Control.Concurrent
import Control.Concurrent.STM
@ -13,8 +13,8 @@ import Data.IORef @@ -13,8 +13,8 @@ import Data.IORef
import qualified Data.Map as Map
import Data.Text(Text)
import Network.XMPP.Concurrent.Types
import Network.XMPP.Monad
import Network.Xmpp.Concurrent.Types
import Network.Xmpp.Monad
-- | Register a new IQ listener. IQ requests matching the type and namespace
@ -24,7 +24,7 @@ import Network.XMPP.Monad @@ -24,7 +24,7 @@ import Network.XMPP.Monad
-- combination was alread handled.
listenIQChan :: IQRequestType -- ^ Type of IQs to receive (@Get@ or @Set@)
-> Text -- ^ Namespace of the child element
-> XMPP (Maybe (TChan IQRequestTicket))
-> Xmpp (Maybe (TChan IQRequestTicket))
listenIQChan tp ns = do
handlers <- asks iqHandlers
liftIO . atomically $ do
@ -41,7 +41,7 @@ listenIQChan tp ns = do @@ -41,7 +41,7 @@ listenIQChan tp ns = do
Just _iqCh' -> Nothing
-- | Get a duplicate of the stanza channel
getStanzaChan :: XMPP (TChan Stanza)
getStanzaChan :: Xmpp (TChan Stanza)
getStanzaChan = do
shadow <- asks sShadow
liftIO $ atomically $ dupTChan shadow
@ -49,7 +49,7 @@ getStanzaChan = do @@ -49,7 +49,7 @@ getStanzaChan = do
-- | Get the inbound stanza channel, duplicates from master if necessary. Please
-- note that once duplicated it will keep filling up, call 'dropMessageChan' to
-- allow it to be garbage collected.
getMessageChan :: XMPP (TChan (Either MessageError Message))
getMessageChan :: Xmpp (TChan (Either MessageError Message))
getMessageChan = do
mChR <- asks messagesRef
mCh <- liftIO $ readIORef mChR
@ -62,7 +62,7 @@ getMessageChan = do @@ -62,7 +62,7 @@ getMessageChan = do
Just mCh' -> return mCh'
-- | Analogous to 'getMessageChan'.
getPresenceChan :: XMPP (TChan (Either PresenceError Presence))
getPresenceChan :: Xmpp (TChan (Either PresenceError Presence))
getPresenceChan = do
pChR <- asks presenceRef
pCh <- liftIO $ readIORef pChR
@ -76,33 +76,33 @@ getPresenceChan = do @@ -76,33 +76,33 @@ getPresenceChan = do
-- | Drop the local end of the inbound stanza channel from our context so it can
-- be GC-ed.
dropMessageChan :: XMPP ()
dropMessageChan :: Xmpp ()
dropMessageChan = do
r <- asks messagesRef
liftIO $ writeIORef r Nothing
-- | Analogous to 'dropMessageChan'.
dropPresenceChan :: XMPP ()
dropPresenceChan :: Xmpp ()
dropPresenceChan = do
r <- asks presenceRef
liftIO $ writeIORef r Nothing
-- | Read an element from the inbound stanza channel, acquiring a copy of the
-- channel as necessary.
pullMessage :: XMPP (Either MessageError Message)
pullMessage :: Xmpp (Either MessageError Message)
pullMessage = do
c <- getMessageChan
liftIO $ atomically $ readTChan c
-- | Read an element from the inbound stanza channel, acquiring a copy of the
-- channel as necessary.
pullPresence :: XMPP (Either PresenceError Presence)
pullPresence :: Xmpp (Either PresenceError Presence)
pullPresence = do
c <- getPresenceChan
liftIO $ atomically $ readTChan c
-- | Send a stanza to the server.
sendStanza :: Stanza -> XMPP ()
sendStanza :: Stanza -> Xmpp ()
sendStanza a = do
out <- asks outCh
liftIO . atomically $ writeTChan out a
@ -116,7 +116,7 @@ forkSession sess = do @@ -116,7 +116,7 @@ forkSession sess = do
return $ sess {messagesRef = mCH', presenceRef = pCH'}
-- | Fork a new thread.
fork :: XMPP () -> XMPP ThreadId
fork :: Xmpp () -> Xmpp ThreadId
fork a = do
sess <- ask
sess' <- liftIO $ forkSession sess
@ -125,7 +125,7 @@ fork a = do @@ -125,7 +125,7 @@ fork a = do
-- | Pulls a message and returns it if the given predicate returns @True@.
filterMessages :: (MessageError -> Bool)
-> (Message -> Bool)
-> XMPP (Either MessageError Message)
-> Xmpp (Either MessageError Message)
filterMessages f g = do
s <- pullMessage
case s of
@ -136,7 +136,7 @@ filterMessages f g = do @@ -136,7 +136,7 @@ filterMessages f g = do
-- | Pulls a (non-error) message and returns it if the given predicate returns
-- @True@.
waitForMessage :: (Message -> Bool) -> XMPP Message
waitForMessage :: (Message -> Bool) -> Xmpp Message
waitForMessage f = do
s <- pullMessage
case s of
@ -145,7 +145,7 @@ waitForMessage f = do @@ -145,7 +145,7 @@ waitForMessage f = do
| otherwise -> waitForMessage f
-- | Pulls an error message and returns it if the given predicate returns @True@.
waitForMessageError :: (MessageError -> Bool) -> XMPP MessageError
waitForMessageError :: (MessageError -> Bool) -> Xmpp MessageError
waitForMessageError f = do
s <- pullMessage
case s of
@ -155,7 +155,7 @@ waitForMessageError f = do @@ -155,7 +155,7 @@ waitForMessageError f = do
-- | Pulls a (non-error) presence and returns it if the given predicate returns
-- @True@.
waitForPresence :: (Presence -> Bool) -> XMPP Presence
waitForPresence :: (Presence -> Bool) -> Xmpp Presence
waitForPresence f = do
s <- pullPresence
case s of
@ -165,11 +165,11 @@ waitForPresence f = do @@ -165,11 +165,11 @@ waitForPresence f = do
-- TODO: Wait for presence error?
-- | Run an XMPPMonad action in isolation. Reader and writer workers will be
-- | Run an XmppMonad action in isolation. Reader and writer workers will be
-- temporarily stopped and resumed with the new session details once the action
-- returns. The action will run in the calling thread. Any uncaught exceptions
-- will be interpreted as connection failure.
withConnection :: XMPPConMonad a -> XMPP (Either StreamError a)
withConnection :: XmppConMonad a -> Xmpp (Either StreamError a)
withConnection a = do
readerId <- asks readerThread
stateRef <- asks conStateRef
@ -193,7 +193,7 @@ withConnection a = do @@ -193,7 +193,7 @@ withConnection a = do
(\e -> atomically (putTMVar wait ()) >>
Ex.throwIO (e :: Ex.SomeException)
)
-- Run the XMPPMonad action, save the (possibly updated) states, release
-- Run the XmppMonad action, save the (possibly updated) states, release
-- the locks, and return the result.
Ex.catches
(do
@ -211,44 +211,44 @@ withConnection a = do @@ -211,44 +211,44 @@ withConnection a = do
]
-- | Send a presence stanza.
sendPresence :: Presence -> XMPP ()
sendPresence :: Presence -> Xmpp ()
sendPresence = sendStanza . PresenceS
-- | Send a message stanza.
sendMessage :: Message -> XMPP ()
sendMessage :: Message -> Xmpp ()
sendMessage = sendStanza . MessageS
-- | Executes a function to update the event handlers.
modifyHandlers :: (EventHandlers -> EventHandlers) -> XMPP ()
modifyHandlers :: (EventHandlers -> EventHandlers) -> Xmpp ()
modifyHandlers f = do
eh <- asks eventHandlers
liftIO . atomically $ writeTVar eh . f =<< readTVar eh
-- | Sets the handler to be executed when the session ends.
setSessionEndHandler :: XMPP () -> XMPP ()
setSessionEndHandler :: Xmpp () -> Xmpp ()
setSessionEndHandler eh = do
r <- ask
modifyHandlers (\s -> s{sessionEndHandler = runReaderT eh r})
-- | Sets the handler to be executed when the server connection is closed.
setConnectionClosedHandler :: (StreamError -> XMPP ()) -> XMPP ()
setConnectionClosedHandler :: (StreamError -> Xmpp ()) -> Xmpp ()
setConnectionClosedHandler eh = do
r <- ask
modifyHandlers (\s -> s{connectionClosedHandler = \e -> runReaderT (eh e) r})
-- | Run an event handler.
runHandler :: (EventHandlers -> IO a) -> XMPP a
runHandler :: (EventHandlers -> IO a) -> Xmpp a
runHandler h = do
eh <- liftIO . atomically . readTVar =<< asks eventHandlers
liftIO $ h eh
-- | End the current XMPP session.
endSession :: XMPP ()
-- | End the current Xmpp session.
endSession :: Xmpp ()
endSession = do -- TODO: This has to be idempotent (is it?)
void $ withConnection xmppKillConnection
liftIO =<< asks stopThreads
runHandler sessionEndHandler
-- | Close the connection to the server.
closeConnection :: XMPP ()
closeConnection :: Xmpp ()
closeConnection = void $ withConnection xmppKillConnection

22
source/Network/XMPP/Concurrent/Threads.hs → source/Network/Xmpp/Concurrent/Threads.hs

@ -1,8 +1,8 @@ @@ -1,8 +1,8 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.Concurrent.Threads where
module Network.Xmpp.Concurrent.Threads where
import Network.XMPP.Types
import Network.Xmpp.Types
import Control.Applicative((<$>),(<*>))
import Control.Concurrent
@ -20,10 +20,10 @@ import Data.Maybe @@ -20,10 +20,10 @@ import Data.Maybe
import Data.XML.Types
import Network.XMPP.Monad
import Network.XMPP.Marshal
import Network.XMPP.Pickle
import Network.XMPP.Concurrent.Types
import Network.Xmpp.Monad
import Network.Xmpp.Marshal
import Network.Xmpp.Pickle
import Network.Xmpp.Concurrent.Types
import Text.XML.Stream.Elements
@ -193,7 +193,7 @@ startThreads = do @@ -193,7 +193,7 @@ startThreads = do
, connectionClosedHandler = \_ -> return ()
}
-- | Creates and initializes a new XMPP session.
-- | Creates and initializes a new Xmpp session.
newSession :: IO Session
newSession = do
(mC, pC, sC, hand, outC, stopThreads', writeR, conS, rdr, eh) <- startThreads
@ -219,15 +219,15 @@ newSession = do @@ -219,15 +219,15 @@ newSession = do
eh
stopThreads'
-- | Creates a new session and runs the given XMPP computation.
withNewSession :: XMPP b -> IO (Session, b)
-- | Creates a new session and runs the given Xmpp computation.
withNewSession :: Xmpp b -> IO (Session, b)
withNewSession a = do
sess <- newSession
ret <- runReaderT a sess
return (sess, ret)
-- | Runs the given XMPP computation in the given session.
withSession :: Session -> XMPP a -> IO a
-- | Runs the given Xmpp computation in the given session.
withSession :: Session -> Xmpp a -> IO a
withSession = flip runReaderT
-- Acquires the write lock, pushes a space, and releases the lock.

14
source/Network/XMPP/Concurrent/Types.hs → source/Network/Xmpp/Concurrent/Types.hs

@ -1,7 +1,7 @@ @@ -1,7 +1,7 @@
{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Network.XMPP.Concurrent.Types where
module Network.Xmpp.Concurrent.Types where
import qualified Control.Exception.Lifted as Ex
import Control.Concurrent
@ -14,7 +14,7 @@ import qualified Data.Map as Map @@ -14,7 +14,7 @@ import qualified Data.Map as Map
import Data.Text(Text)
import Data.Typeable
import Network.XMPP.Types
import Network.Xmpp.Types
-- Map between the IQ request type and the "query" namespace pair, and the TChan
-- for the IQ request and "sent" boolean pair.
@ -22,14 +22,14 @@ type IQHandlers = (Map.Map (IQRequestType, Text) (TChan IQRequestTicket) @@ -22,14 +22,14 @@ type IQHandlers = (Map.Map (IQRequestType, Text) (TChan IQRequestTicket)
, Map.Map StanzaId (TMVar IQResponse)
)
-- Handlers to be run when the XMPP session ends and when the XMPP connection is
-- Handlers to be run when the Xmpp session ends and when the Xmpp connection is
-- closed.
data EventHandlers = EventHandlers
{ sessionEndHandler :: IO ()
, connectionClosedHandler :: StreamError -> IO ()
}
-- The Session object is the XMPP (ReaderT) state.
-- The Session object is the Xmpp (ReaderT) state.
data Session = Session
{ -- The original master channels that the reader puts stanzas
-- into. These are cloned by @get{STanza,Message,Presence}Chan
@ -51,14 +51,14 @@ data Session = Session @@ -51,14 +51,14 @@ data Session = Session
, readerThread :: ThreadId
, idGenerator :: IO StanzaId
-- Lock (used by withConnection) to make sure that a maximum of one
-- XMPPConMonad calculation is executed at any given time.
-- XmppConMonad calculation is executed at any given time.
, conStateRef :: TMVar XmppConnection
, eventHandlers :: TVar EventHandlers
, stopThreads :: IO ()
}
-- XMPP is a monad for concurrent XMPP usage.
type XMPP a = ReaderT Session IO a
-- Xmpp is a monad for concurrent Xmpp usage.
type Xmpp a = ReaderT Session IO a
-- Interrupt is used to signal to the reader thread that it should stop.
data Interrupt = Interrupt (TMVar ()) deriving Typeable

7
source/Network/Xmpp/IM.hs

@ -0,0 +1,7 @@ @@ -0,0 +1,7 @@
module Network.Xmpp.IM
( module Network.Xmpp.IM.Message
, module Network.Xmpp.IM.Presence
) where
import Network.Xmpp.IM.Message
import Network.Xmpp.IM.Presence

6
source/Network/XMPP/IM/Message.hs → source/Network/Xmpp/IM/Message.hs

@ -1,5 +1,5 @@ @@ -1,5 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.IM.Message
module Network.Xmpp.IM.Message
where
import Control.Applicative ((<$>))
@ -9,8 +9,8 @@ import Data.Text (Text) @@ -9,8 +9,8 @@ import Data.Text (Text)
import Data.XML.Pickle
import Data.XML.Types
import Network.XMPP.Types
import Network.XMPP.Pickle
import Network.Xmpp.Types
import Network.Xmpp.Pickle
data MessageBody = MessageBody (Maybe LangTag) Text
data MessageThread = MessageThread

4
source/Network/XMPP/IM/Presence.hs → source/Network/Xmpp/IM/Presence.hs

@ -1,7 +1,7 @@ @@ -1,7 +1,7 @@
module Network.XMPP.IM.Presence where
module Network.Xmpp.IM.Presence where
import Data.Text(Text)
import Network.XMPP.Types
import Network.Xmpp.Types
-- | An empty presence.
presence :: Presence

2
source/Network/XMPP/JID.hs → source/Network/Xmpp/JID.hs

@ -3,7 +3,7 @@ @@ -3,7 +3,7 @@
-- This module deals with JIDs, also known as XMPP addresses. For more
-- information on JIDs, see RFC 6122: XMPP: Address Format.
module Network.XMPP.JID
module Network.Xmpp.JID
( JID(..)
, fromText
, fromStrings

6
source/Network/XMPP/Marshal.hs → source/Network/Xmpp/Marshal.hs

@ -6,13 +6,13 @@ @@ -6,13 +6,13 @@
{-# OPTIONS_HADDOCK hide #-}
module Network.XMPP.Marshal where
module Network.Xmpp.Marshal where
import Data.XML.Pickle
import Data.XML.Types
import Network.XMPP.Pickle
import Network.XMPP.Types
import Network.Xmpp.Pickle
import Network.Xmpp.Types
xpStreamStanza :: PU [Node] (Either XmppStreamError Stanza)
xpStreamStanza = xpEither xpStreamError xpStanza

4
source/Network/XMPP/Message.hs → source/Network/Xmpp/Message.hs

@ -1,5 +1,5 @@ @@ -1,5 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
module Network.XMPP.Message
module Network.Xmpp.Message
( Message(..)
, MessageError(..)
, MessageType(..)
@ -9,7 +9,7 @@ module Network.XMPP.Message @@ -9,7 +9,7 @@ module Network.XMPP.Message
import Data.XML.Types
import Network.XMPP.Types
import Network.Xmpp.Types
-- | An empty message.
message :: Message

36
source/Network/XMPP/Monad.hs → source/Network/Xmpp/Monad.hs

@ -1,7 +1,7 @@ @@ -1,7 +1,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.Monad where
module Network.Xmpp.Monad where
import Control.Applicative((<$>))
import Control.Monad
@ -22,9 +22,9 @@ import Data.XML.Pickle @@ -22,9 +22,9 @@ import Data.XML.Pickle
import Data.XML.Types
import Network
import Network.XMPP.Types
import Network.XMPP.Marshal
import Network.XMPP.Pickle
import Network.Xmpp.Types
import Network.Xmpp.Marshal
import Network.Xmpp.Pickle
import System.IO
@ -32,28 +32,28 @@ import Text.XML.Stream.Elements @@ -32,28 +32,28 @@ import Text.XML.Stream.Elements
import Text.XML.Stream.Parse as XP
import Text.XML.Unresolved(InvalidEventStream(..))
pushElement :: Element -> XMPPConMonad Bool
pushElement :: Element -> XmppConMonad Bool
pushElement x = do
sink <- gets sConPushBS
liftIO . sink $ renderElement x
pushStanza :: Stanza -> XMPPConMonad Bool
pushStanza :: Stanza -> XmppConMonad Bool
pushStanza = pushElement . pickleElem xpStanza
pushOpenElement :: Element -> XMPPConMonad Bool
pushOpenElement :: Element -> XmppConMonad Bool
pushOpenElement e = do
sink <- gets sConPushBS
liftIO . sink $ renderOpenElement e
-- `Connect-and-resumes' the given sink to the connection source, and pulls a
-- `b' value.
pullToSink :: Sink Event IO b -> XMPPConMonad b
pullToSink :: Sink Event IO b -> XmppConMonad b
pullToSink snk = do
source <- gets sConSrc
(_, r) <- lift $ source $$+ snk
return r
pullElement :: XMPPConMonad Element
pullElement :: XmppConMonad Element
pullElement = do
Ex.catch (do
e <- pullToSink (elements =$ CL.head)
@ -64,7 +64,7 @@ pullElement = do @@ -64,7 +64,7 @@ pullElement = do
(\(InvalidEventStream s) -> liftIO . Ex.throwIO $ StreamXMLError s)
-- Pulls an element and unpickles it.
pullPickle :: PU [Node] a -> XMPPConMonad a
pullPickle :: PU [Node] a -> XmppConMonad a
pullPickle p = do
res <- unpickleElem p <$> pullElement
case res of
@ -72,7 +72,7 @@ pullPickle p = do @@ -72,7 +72,7 @@ pullPickle p = do
Right r -> return r
-- Pulls a stanza from the stream. Throws an error on failure.
pullStanza :: XMPPConMonad Stanza
pullStanza :: XmppConMonad Stanza
pullStanza = do
res <- pullPickle xpStreamStanza
case res of
@ -108,8 +108,8 @@ xmppNoConnection = XmppConnection @@ -108,8 +108,8 @@ xmppNoConnection = XmppConnection
zeroSource = liftIO . Ex.throwIO $ StreamConnectionError
-- Connects to the given hostname on port 5222 (TODO: Make this dynamic) and
-- updates the XMPPConMonad XmppConnection state.
xmppRawConnect :: HostName -> Text -> XMPPConMonad ()
-- updates the XmppConMonad XmppConnection state.
xmppRawConnect :: HostName -> Text -> XmppConMonad ()
xmppRawConnect host hostname = do
uname <- gets sUsername
con <- liftIO $ do
@ -131,12 +131,12 @@ xmppRawConnect host hostname = do @@ -131,12 +131,12 @@ xmppRawConnect host hostname = do
(hClose con)
put st
-- Execute a XMPPConMonad computation.
xmppNewSession :: XMPPConMonad a -> IO (a, XmppConnection)
-- Execute a XmppConMonad computation.
xmppNewSession :: XmppConMonad a -> IO (a, XmppConnection)
xmppNewSession action = runStateT action xmppNoConnection
-- Closes the connection and updates the XMPPConMonad XmppConnection state.
xmppKillConnection :: XMPPConMonad ()
-- Closes the connection and updates the XmppConMonad XmppConnection state.
xmppKillConnection :: XmppConMonad ()
xmppKillConnection = do
cc <- gets sCloseConnection
void . liftIO $ (Ex.try cc :: IO (Either Ex.SomeException ()))
@ -149,7 +149,7 @@ xmppSendIQ' :: StanzaId @@ -149,7 +149,7 @@ xmppSendIQ' :: StanzaId
-> IQRequestType
-> Maybe LangTag
-> Element
-> XMPPConMonad (Either IQError IQResult)
-> XmppConMonad (Either IQError IQResult)
xmppSendIQ' iqID to tp lang body = do
pushStanza . IQRequestS $ IQRequest iqID Nothing to lang tp body
res <- pullPickle $ xpEither xpIQError xpIQResult

4
source/Network/XMPP/Pickle.hs → source/Network/Xmpp/Pickle.hs

@ -5,7 +5,7 @@ @@ -5,7 +5,7 @@
-- Marshalling between XML and Native Types
module Network.XMPP.Pickle
module Network.Xmpp.Pickle
( mbToBool
, xpElemEmpty
, xmlLang
@ -24,7 +24,7 @@ module Network.XMPP.Pickle @@ -24,7 +24,7 @@ module Network.XMPP.Pickle
import Data.XML.Types
import Data.XML.Pickle
import Network.XMPP.Types
import Network.Xmpp.Types
import Text.XML.Stream.Elements

4
source/Network/XMPP/Presence.hs → source/Network/Xmpp/Presence.hs

@ -1,9 +1,9 @@ @@ -1,9 +1,9 @@
{-# OPTIONS_HADDOCK hide #-}
module Network.XMPP.Presence where
module Network.Xmpp.Presence where
import Data.Text(Text)
import Network.XMPP.Types
import Network.Xmpp.Types
-- | Add a recipient to a presence notification.
presTo :: Presence -> JID -> Presence

24
source/Network/XMPP/SASL.hs → source/Network/Xmpp/Sasl.hs

@ -1,6 +1,6 @@ @@ -1,6 +1,6 @@
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
module Network.XMPP.SASL where
module Network.Xmpp.Sasl where
import Control.Applicative
import Control.Arrow (left)
@ -23,25 +23,25 @@ import qualified Data.Text as Text @@ -23,25 +23,25 @@ import qualified Data.Text as Text
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Network.XMPP.Monad
import Network.XMPP.Stream
import Network.XMPP.Types
import Network.XMPP.Pickle
import Network.Xmpp.Monad
import Network.Xmpp.Stream
import Network.Xmpp.Types
import Network.Xmpp.Pickle
import qualified System.Random as Random
import Network.XMPP.SASL.SASL
import Network.XMPP.SASL.DIGEST_MD5
import Network.XMPP.SASL.PLAIN
import Network.XMPP.SASL.Types
import Network.Xmpp.Sasl.Sasl
import Network.Xmpp.Sasl.DigestMD5
import Network.Xmpp.Sasl.Plain
import Network.Xmpp.Sasl.Types
-- Uses the first supported mechanism to authenticate, if any. Updates the
-- XMPPConMonad state with non-password credentials and restarts the stream upon
-- XmppConMonad state with non-password credentials and restarts the stream upon
-- success. This computation wraps an ErrorT computation, which means that
-- catchError can be used to catch any errors.
xmppSASL :: [SASLCredentials] -- ^ Acceptable authentication mechanisms and
-- their corresponding credentials
-> XMPPConMonad (Either AuthError ())
-> XmppConMonad (Either AuthError ())
xmppSASL creds = runErrorT $ do
-- Chooses the first mechanism that is acceptable by both the client and the
-- server.
@ -49,7 +49,7 @@ xmppSASL creds = runErrorT $ do @@ -49,7 +49,7 @@ xmppSASL creds = runErrorT $ do
let cred = L.find (\cred -> credsToName cred `elem` mechanisms) creds
unless (isJust cred) (throwError $ AuthMechanismError mechanisms)
case fromJust cred of
DIGEST_MD5Credentials authzid authcid passwd -> ErrorT $ xmppDIGEST_MD5
DIGEST_MD5Credentials authzid authcid passwd -> ErrorT $ xmppDigestMD5
authzid
authcid
passwd

24
source/Network/XMPP/SASL/DIGEST_MD5.hs → source/Network/Xmpp/Sasl/DigestMD5.hs

@ -1,6 +1,6 @@ @@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.SASL.DIGEST_MD5 where
module Network.Xmpp.Sasl.DigestMD5 where
import Control.Applicative
import Control.Arrow (left)
@ -29,21 +29,21 @@ import qualified Data.ByteString as BS @@ -29,21 +29,21 @@ import qualified Data.ByteString as BS
import Data.XML.Types
import Network.XMPP.Monad
import Network.XMPP.Stream
import Network.XMPP.Types
import Network.XMPP.Pickle
import Network.Xmpp.Monad
import Network.Xmpp.Stream
import Network.Xmpp.Types
import Network.Xmpp.Pickle
import qualified System.Random as Random
import Network.XMPP.SASL.SASL
import Network.XMPP.SASL.Types
import Network.Xmpp.Sasl.Sasl
import Network.Xmpp.Sasl.Types
xmppDIGEST_MD5 :: Maybe Text -- Authorization identity (authzid)
xmppDigestMD5 :: Maybe Text -- Authorization identity (authzid)
-> Text -- Authentication identity (authzid)
-> Text -- Password (authzid)
-> XMPPConMonad (Either AuthError ())
xmppDIGEST_MD5 authzid authcid passwd = runErrorT $ do
-> XmppConMonad (Either AuthError ())
xmppDigestMD5 authzid authcid passwd = runErrorT $ do
realm <- gets sHostname
case realm of
Just realm' -> do
@ -53,9 +53,9 @@ xmppDIGEST_MD5 authzid authcid passwd = runErrorT $ do @@ -53,9 +53,9 @@ xmppDIGEST_MD5 authzid authcid passwd = runErrorT $ do
Nothing -> throwError AuthConnectionError
where
xmppDIGEST_MD5' :: Text -- ^ SASL realm
-> XMPPConMonad (Either AuthError ())
-> XmppConMonad (Either AuthError ())
xmppDIGEST_MD5' realm = runErrorT $ do
-- Push element and receive the challenge (in XMPPConMonad).
-- Push element and receive the challenge (in XmppConMonad).
_ <- lift . pushElement $ saslInitE "DIGEST-MD5" Nothing -- TODO: Check boolean?
challenge' <- lift $ B64.decode . Text.encodeUtf8 <$>
pullPickle challengePickle

16
source/Network/XMPP/SASL/PLAIN.hs → source/Network/Xmpp/Sasl/Plain.hs

@ -3,7 +3,7 @@ @@ -3,7 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.SASL.PLAIN where
module Network.Xmpp.Sasl.Plain where
import Control.Applicative
import Control.Arrow (left)
@ -32,23 +32,23 @@ import qualified Data.ByteString as BS @@ -32,23 +32,23 @@ import qualified Data.ByteString as BS
import Data.XML.Types
import Network.XMPP.Monad
import Network.XMPP.Stream
import Network.XMPP.Types
import Network.XMPP.Pickle
import Network.Xmpp.Monad
import Network.Xmpp.Stream
import Network.Xmpp.Types
import Network.Xmpp.Pickle
import qualified System.Random as Random
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Network.XMPP.SASL.SASL
import Network.XMPP.SASL.Types
import Network.Xmpp.Sasl.Sasl
import Network.Xmpp.Sasl.Types
xmppPLAIN :: Maybe T.Text
-> T.Text
-> T.Text
-> XMPPConMonad (Either AuthError ())
-> XmppConMonad (Either AuthError ())
xmppPLAIN authzid authcid passwd = runErrorT $ do
_ <- lift . pushElement $ saslInitE "PLAIN" $ -- TODO: Check boolean?
Just $ Text.decodeUtf8 $ B64.encode $ Text.encodeUtf8 $ plainMessage authzid authcid passwd

6
source/Network/XMPP/SASL/SASL.hs → source/Network/Xmpp/Sasl/Sasl.hs

@ -1,8 +1,8 @@ @@ -1,8 +1,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.SASL.SASL where
module Network.Xmpp.Sasl.Sasl where
import Network.XMPP.Types
import Network.Xmpp.Types
import Control.Monad.Error
import Data.Text
@ -12,7 +12,7 @@ import Data.XML.Types @@ -12,7 +12,7 @@ import Data.XML.Types
import qualified Data.ByteString as BS
import Data.Maybe (fromMaybe)
import Network.XMPP.Pickle
import Network.Xmpp.Pickle
-- The <auth xmlns='urn:ietf:params:xml:ns:xmpp-sasl'/> element, with an
-- optional round-trip value.

4
source/Network/XMPP/SASL/Types.hs → source/Network/Xmpp/Sasl/Types.hs

@ -1,8 +1,8 @@ @@ -1,8 +1,8 @@
module Network.XMPP.SASL.Types where
module Network.Xmpp.Sasl.Types where
import Control.Monad.Error
import Data.Text
import Network.XMPP.Types
import Network.Xmpp.Types
data AuthError = AuthXmlError
| AuthMechanismError [Text] -- ^ Wraps mechanisms offered

14
source/Network/XMPP/Session.hs → source/Network/Xmpp/Session.hs

@ -1,14 +1,14 @@ @@ -1,14 +1,14 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.Session where
module Network.Xmpp.Session where
import Data.XML.Pickle
import Data.XML.Types(Element)
import Network.XMPP.Monad
import Network.XMPP.Pickle
import Network.XMPP.Types
import Network.XMPP.Concurrent
import Network.Xmpp.Monad
import Network.Xmpp.Pickle
import Network.Xmpp.Types
import Network.Xmpp.Concurrent
sessionXML :: Element
sessionXML = pickleElem
@ -26,7 +26,7 @@ sessionIQ = IQRequestS $ IQRequest { iqRequestID = "sess" @@ -26,7 +26,7 @@ sessionIQ = IQRequestS $ IQRequest { iqRequestID = "sess"
-- Sends the session IQ set element and waits for an answer. Throws an error if
-- if an IQ error stanza is returned from the server.
xmppStartSession :: XMPPConMonad ()
xmppStartSession :: XmppConMonad ()
xmppStartSession = do
answer <- xmppSendIQ' "session" Nothing Set Nothing sessionXML
case answer of
@ -35,7 +35,7 @@ xmppStartSession = do @@ -35,7 +35,7 @@ xmppStartSession = do
-- Sends the session IQ set element and waits for an answer. Throws an error if
-- if an IQ error stanza is returned from the server.
startSession :: XMPP ()
startSession :: Xmpp ()
startSession = do
answer <- sendIQ' Nothing Set Nothing sessionXML
case answer of

12
source/Network/XMPP/Stream.hs → source/Network/Xmpp/Stream.hs

@ -1,7 +1,7 @@ @@ -1,7 +1,7 @@
{-# LANGUAGE NoMonomorphismRestriction, OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
module Network.XMPP.Stream where
module Network.Xmpp.Stream where
import qualified Control.Exception as Ex
import Control.Monad.Error
@ -15,9 +15,9 @@ import Data.XML.Pickle @@ -15,9 +15,9 @@ import Data.XML.Pickle
import Data.XML.Types
import Data.Void(Void)
import Network.XMPP.Monad
import Network.XMPP.Pickle
import Network.XMPP.Types
import Network.Xmpp.Monad
import Network.Xmpp.Pickle
import Network.Xmpp.Types
import Text.XML.Stream.Elements
import Text.XML.Stream.Parse as XP
@ -56,7 +56,7 @@ openElementFromEvents = do @@ -56,7 +56,7 @@ openElementFromEvents = do
_ -> throwError $ StreamConnectionError
-- Sends the initial stream:stream element and pulls the server features.
xmppStartStream :: XMPPConMonad (Either StreamError ())
xmppStartStream :: XmppConMonad (Either StreamError ())
xmppStartStream = runErrorT $ do
hostname' <- gets sHostname
case hostname' of
@ -69,7 +69,7 @@ xmppStartStream = runErrorT $ do @@ -69,7 +69,7 @@ xmppStartStream = runErrorT $ do
-- Creates a new connection source (of Events) using the raw source (of bytes)
-- and calls xmppStartStream.
xmppRestartStream :: XMPPConMonad (Either StreamError ())
xmppRestartStream :: XmppConMonad (Either StreamError ())
xmppRestartStream = do
raw <- gets sRawSrc
newsrc <- liftIO . bufferSource $ raw $= XP.parseBytes def

20
source/Network/XMPP/TLS.hs → source/Network/Xmpp/TLS.hs

@ -1,7 +1,7 @@ @@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.TLS where
module Network.Xmpp.TLS where
import qualified Control.Exception.Lifted as Ex
import Control.Monad
@ -12,10 +12,10 @@ import Data.Conduit.TLS as TLS @@ -12,10 +12,10 @@ import Data.Conduit.TLS as TLS
import Data.Typeable
import Data.XML.Types
import Network.XMPP.Monad
import Network.XMPP.Pickle(ppElement)
import Network.XMPP.Stream
import Network.XMPP.Types
import Network.Xmpp.Monad
import Network.Xmpp.Pickle(ppElement)
import Network.Xmpp.Stream
import Network.Xmpp.Types
starttlsE :: Element
starttlsE = Element "{urn:ietf:params:xml:ns:xmpp-tls}starttls" [] []
@ -35,19 +35,19 @@ exampleParams = TLS.defaultParams @@ -35,19 +35,19 @@ exampleParams = TLS.defaultParams
}
-- | Error conditions that may arise during TLS negotiation.
data XMPPTLSError = TLSError TLSError
data XmppTLSError = TLSError TLSError
| TLSNoServerSupport
| TLSNoConnection
| TLSStreamError StreamError
| XMPPTLSError -- General instance used for the Error instance
| XmppTLSError -- General instance used for the Error instance
deriving (Show, Eq, Typeable)
instance Error XMPPTLSError where
noMsg = XMPPTLSError
instance Error XmppTLSError where
noMsg = XmppTLSError
-- Pushes "<starttls/>, waits for "<proceed/>", performs the TLS handshake, and
-- restarts the stream. May throw errors.
startTLS :: TLS.TLSParams -> XMPPConMonad (Either XMPPTLSError ())
startTLS :: TLS.TLSParams -> XmppConMonad (Either XmppTLSError ())
startTLS params = Ex.handle (return . Left . TLSError) . runErrorT $ do
features <- lift $ gets sFeatures
handle' <- lift $ gets sConHandle

30
source/Network/XMPP/Types.hs → source/Network/Xmpp/Types.hs

@ -6,7 +6,7 @@ @@ -6,7 +6,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module Network.XMPP.Types
module Network.Xmpp.Types
( IQError(..)
, IQRequest(..)
, IQRequestType(..)
@ -32,13 +32,13 @@ module Network.XMPP.Types @@ -32,13 +32,13 @@ module Network.XMPP.Types
, StanzaId(..)
, StreamError(..)
, Version(..)
, XMPPConMonad
, XmppConMonad
, XmppConnection(..)
, XmppConnectionState(..)
, XMPPT(..)
, XmppT(..)
, XmppStreamError(..)
, parseLangTag
, module Network.XMPP.JID
, module Network.Xmpp.JID
)
where
@ -60,13 +60,13 @@ import Data.XML.Types @@ -60,13 +60,13 @@ import Data.XML.Types
import qualified Network as N
import Network.XMPP.JID
import Network.Xmpp.JID
import System.IO
-- |
-- Wraps a string of random characters that, when using an appropriate
-- @IDGenerator@, is guaranteed to be unique for the XMPP session.
-- @IDGenerator@, is guaranteed to be unique for the Xmpp session.
data StanzaId = SI !Text deriving (Eq, Ord)
@ -79,7 +79,7 @@ instance Read StanzaId where @@ -79,7 +79,7 @@ instance Read StanzaId where
instance IsString StanzaId where
fromString = SI . Text.pack
-- | The XMPP communication primities (Message, Presence and Info/Query) are
-- | The Xmpp communication primities (Message, Presence and Info/Query) are
-- called stanzas.
data Stanza = IQRequestS IQRequest
| IQResultS IQResult
@ -221,7 +221,7 @@ data PresenceError = PresenceError { presenceErrorID :: Maybe StanzaId @@ -221,7 +221,7 @@ data PresenceError = PresenceError { presenceErrorID :: Maybe StanzaId
, presenceErrorPayload :: [Element]
} deriving Show
-- | @PresenceType@ holds XMPP presence types. The "error" message type is left
-- | @PresenceType@ holds Xmpp presence types. The "error" message type is left
-- out as errors are using @PresenceError@.
data PresenceType = Subscribe | -- ^ Sender wants to subscribe to presence
Subscribed | -- ^ Sender has approved the subscription
@ -278,7 +278,7 @@ instance Read PresenceType where @@ -278,7 +278,7 @@ instance Read PresenceType where
-- readsPrec _ _ = []
-- | All stanzas (IQ, message, presence) can cause errors, which in the XMPP
-- | All stanzas (IQ, message, presence) can cause errors, which in the Xmpp
-- stream looks like <stanza-kind to='sender' type='error'>. These errors are
-- wrapped in the @StanzaError@ type.
-- TODO: Sender XML is (optional and is) not yet included.
@ -661,14 +661,14 @@ data XmppConnection = XmppConnection @@ -661,14 +661,14 @@ data XmppConnection = XmppConnection
}
-- |
-- The XMPP monad transformer. Contains internal state in order to
-- The Xmpp monad transformer. Contains internal state in order to
-- work with Pontarius. Pontarius clients needs to operate in this
-- context.
newtype XMPPT m a = XMPPT { runXMPPT :: StateT XmppConnection m a } deriving (Monad, MonadIO)
newtype XmppT m a = XmppT { runXmppT :: StateT XmppConnection m a } deriving (Monad, MonadIO)
-- | Low-level and single-threaded XMPP monad. See @XMPP@ for a concurrent
-- | Low-level and single-threaded Xmpp monad. See @Xmpp@ for a concurrent
-- implementation.
type XMPPConMonad a = StateT XmppConnection IO a
type XmppConMonad a = StateT XmppConnection IO a
-- Make XMPPT derive the Monad and MonadIO instances.
deriving instance (Monad m, MonadIO m) => MonadState (XmppConnection) (XMPPT m)
-- Make XmppT derive the Monad and MonadIO instances.
deriving instance (Monad m, MonadIO m) => MonadState (XmppConnection) (XmppT m)

4
source/Network/XMPP/Utilities.hs → source/Network/Xmpp/Utilities.hs

@ -7,9 +7,9 @@ @@ -7,9 +7,9 @@
{-# LANGUAGE OverloadedStrings #-}
module Network.XMPP.Utilities (idGenerator) where
module Network.Xmpp.Utilities (idGenerator) where
import Network.XMPP.Types
import Network.Xmpp.Types
import Control.Monad.STM
import Control.Concurrent.STM.TVar
Loading…
Cancel
Save