haskell-xmpp-2.0.4: Haskell XMPP (eXtensible Message Passing Protocol, a.k.a. Jabber) library
Copyright(c) Dmitry Astapov 2006 ; pierre 2007
LicenseBSD3
MaintainerDmitry Astapov <dastapov@gmail.com>, pierre <k.pierre.k@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Network.XMPP.Stream

Description

An XMPP stream: means to create and use one

Synopsis

Documentation

class XmppSendable t a where Source #

Sends message into Stream

Methods

xmppSend :: Monad t => a -> t () Source #

Instances

Instances details
MonadIO m => XmppSendable (XmppMonad m) Node Source # 
Instance details

Defined in Network.XMPP.Stream

Methods

xmppSend :: Node -> XmppMonad m () Source #

MonadIO m => XmppSendable (XmppMonad m) (Content Posn) Source # 
Instance details

Defined in Network.XMPP.Stream

MonadIO m => XmppSendable (XmppMonad m) (Stanza t 'Outgoing e) Source # 
Instance details

Defined in Network.XMPP.Stream

Methods

xmppSend :: Stanza t 'Outgoing e -> XmppMonad m () Source #

MonadIO m => XmppSendable (ReaderT (Thread e) m) (Stanza t 'Outgoing ()) Source # 
Instance details

Defined in Network.XMPP.Concurrent

Methods

xmppSend :: Stanza t 'Outgoing () -> ReaderT (Thread e) m () Source #

data Plugin Source #

Constructors

Plugin 

Fields

startM :: MonadIO m => XmppMonad m (Either XmppError [Attribute]) Source #

startM is a special accessor case, since it has to retrieve only opening tag of the 'stream' message, which encloses the whole XMPP stream. That's why it does it's own parsing, and does not rely on nextM

nextM :: MonadIO m => XmppMonad m (Either XmppError (Content Posn)) Source #

Selects next messages from stream

selectM :: MonadIO m => (Content Posn -> Bool) -> XmppMonad m (Either XmppError (Content Posn)) Source #

Selects next message matching predicate

xtractM :: MonadIO m => Text -> XmppMonad m [Content Posn] Source #

Pass in xtract query, return query result from the first message where it returns non-empty results

resetStreamHandle :: (MonadIO m, MonadState Stream m) => Handle -> m () Source #

Replaces contents of the Stream with the contents coming from given handle.

parse :: forall l e. (Alternative l, FromXML e) => Content Posn -> l (SomeStanza e) Source #

Parses XML element producing Stanza

parseM :: (FromXML e, MonadIO m) => XmppMonad m (Either XmppError (SomeStanza e)) Source #

Gets next message from stream and parses it | We shall skip over unknown messages, rather than crashing

waitAndProcess :: (FromXML e, MonadIO m) => (SomeStanza e -> Maybe a) -> XmppMonad m (Either XmppError a) Source #

Skips all messages, that will return result Nothing from computation | In other words - waits for appropriate message, defined by predicate

withUUID :: MonadIO m => (UUID -> Stanza t p e) -> m (Stanza t p e) Source #