pontarius-xmpp-0.4.0.2: An XMPP client library

Maintainerinfo@jonkri.com
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Network.Xmpp.Internal

Contents

Description

This module allows for low-level access to Pontarius XMPP. Generally, the Network.Xmpp module should be used instead.

The Stream object provides the most low-level access to the XMPP stream: a simple and single-threaded interface which exposes the conduit Event source, as well as the input and output byte streams. Custom stateful Stream functions can be executed using withStream.

The TLS, SASL, and Session functionalities of Pontarius XMPP are built on top of this API.

Synopsis

Stream

newtype Stream Source

Constructors

Stream 

data StreamConfiguration Source

Configuration settings related to the stream.

Constructors

StreamConfiguration 

Fields

preferredLang :: !(Maybe LangTag)

Default language when no language tag is set

toJid :: !(Maybe (Jid, Bool))

JID to include in the stream element's to attribute when the connection is secured; if the boolean is set to True, then the JID is also included when the ConnectionState is Plain

connectionDetails :: ConnectionDetails

By settings this field, clients can specify the network interface to use, override the SRV lookup of the realm, as well as specify the use of a non-standard port when connecting by IP or connecting to a domain without SRV records.

resolvConf :: ResolvConf

DNS resolver configuration

establishSession :: Bool

Whether or not to perform the legacy session bind as defined in the (outdated) RFC 3921 specification

tlsBehaviour :: TlsBehaviour

How the client should behave in regards to TLS.

tlsParams :: ClientParams

Settings to be used for TLS negotitation

data StreamState Source

Constructors

StreamState 

Fields

streamConnectionState :: !ConnectionState

State of the stream - Closed, Plain, or Secured

streamHandle :: StreamHandle

Functions to send, receive, flush, and close the stream

streamEventSource :: Source (ErrorT XmppFailure IO) Event

Event conduit source, and its associated finalizer

streamFeatures :: !StreamFeatures

Stream features advertised by the server

streamAddress :: !(Maybe Text)

The hostname or IP specified for the connection

streamFrom :: !(Maybe Jid)

The hostname specified in the server's stream element's from attribute

streamId :: !(Maybe Text)

The identifier specified in the server's stream element's id attribute

streamLang :: !(Maybe LangTag)

The language tag value specified in the server's stream element's langtag attribute; will be a Just value once connected to the server TODO: Verify

streamJid :: !(Maybe Jid)

Our JID as assigned by the server

streamConfiguration :: StreamConfiguration

Configuration settings for the stream

data StreamHandle Source

Defines operations for sending, receiving, flushing, and closing on a stream.

Constructors

StreamHandle 

Fields

streamSend :: ByteString -> IO (Either XmppFailure ())

Sends may not interleave

streamReceive :: Int -> IO (Either XmppFailure ByteString)
 
streamFlush :: IO ()
 
streamClose :: IO ()
 

data StreamFeatures Source

Constructors

StreamFeatures 

Fields

streamTls :: !(Maybe Bool)
 
streamSaslMechanisms :: ![Text]
 
rosterVer :: !(Maybe Bool)

Nothing for no roster versioning, Just False for roster versioning and Just True when the server sends the non-standard "optional" element (observed with prosody).

streamOtherFeatures :: ![Element]
 

openStream :: HostName -> StreamConfiguration -> IO (Either XmppFailure Stream) Source

Connects to the XMPP server and opens the XMPP stream against the given realm.

TLS

tls :: Stream -> IO (Either XmppFailure ()) Source

Checks for TLS support and run starttls procedure if applicable

data TlsBehaviour Source

How the client should behave in regards to TLS.

Constructors

RequireTls

Require the use of TLS; disconnect if it's not offered.

PreferTls

Negotitate TLS if it's available.

PreferPlain

Negotitate TLS only if the server requires it

RefuseTls

Never secure the stream with TLS.

Auth

type SaslHandler = (Text, StateT StreamState IO (Either XmppFailure (Maybe AuthFailure))) Source

Tuple defining the SASL Handler's name, and a SASL mechanism computation. The SASL mechanism is a stateful Stream computation, which has the possibility of resulting in an authentication error.

auth :: [SaslHandler] -> Maybe Text -> Stream -> IO (Either XmppFailure (Maybe AuthFailure)) Source

Authenticate to the server using the first matching method and bind a resource.

Stanzas

data Stanza Source

The Xmpp communication primities (Message, Presence and Info/Query) are called stanzas.

pushStanza :: Stanza -> Stream -> IO (Either XmppFailure ()) Source

Encode and send stanza

pullStanza :: Stream -> IO (Either XmppFailure Stanza) Source

Pulls a stanza (or stream error) from the stream.

writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ()) Source

IQ

iqError :: StanzaErrorCondition -> IQRequest -> IQError Source

Create an IQ error response to an IQ request using the given condition. The error type is derived from the condition using associatedErrorType and both text and the application specific condition are left empty

iqResult :: Maybe Element -> IQRequest -> IQResult Source

Create an IQ Result matching an IQ request

associatedErrorType :: StanzaErrorCondition -> StanzaErrorType Source

The RECOMMENDED error type associated with an error condition. The following conditions allow for multiple types

Plugins

type Plugin Source

Arguments

 = (Stanza -> IO (Either XmppFailure ()))

pass stanza to next plugin

-> ErrorT XmppFailure IO Plugin' 

data Plugin' Source

Constructors

Plugin' 

Fields

inHandler :: Stanza -> [Annotation] -> IO [(Stanza, [Annotation])]

Resulting stanzas and additional Annotations

outHandler :: Stanza -> IO (Either XmppFailure ())
 
onSessionUp :: Session -> IO ()

In order to allow plugins to tie the knot (Plugin / Session) we pass the plugin the completed Session once it exists

data Annotation Source

Annotations are auxiliary data attached to received stanzas by Plugins to convey information regarding their operation. For example, a plugin for encryption might attach information about whether a received stanza was encrypted and which algorithm was used.

Constructors

forall f . (Typeable f, Show f) => Annotation 

Fields

fromAnnotation :: f
 

Instances

connectTls Source

Arguments

:: ResolvConf

Resolv conf to use (try defaultResolvConf as a default)

-> ClientParams

TLS parameters to use when securing the connection

-> String

Host to use when connecting (will be resolved using SRV records)

-> ErrorT XmppFailure IO StreamHandle 

Connect to an XMPP server and secure the connection with TLS before starting the XMPP streams

NB RFC 6120 does not specify this method, but some servers, notably GCS, seem to use it.