Maintainer | info@jonkri.com |
---|---|
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
The Extensible Messaging and Presence Protocol (XMPP) is an open technology for near-real-time communication, which powers a wide range of applications including instant messaging, presence, multi-party chat, voice and video calls, collaboration, lightweight middleware, content syndication, and generalized routing of XML data. XMPP provides a technology for the asynchronous, end-to-end exchange of structured data by means of direct, persistent XML streams among a distributed network of globally addressable, presence-aware clients and servers.
Pontarius XMPP is an XMPP client library, implementing the core capabilities of XMPP (RFC 6120): setup and tear-down of XML streams, channel encryption, authentication, error handling, and communication primitives for messaging.
For low-level access to Pontarius XMPP, see the Network.Xmpp.Internal module.
Getting Started
We use session
to create a session object and connect to a server. Here we
use the default SessionConfiguration
.
sess <- session realm (simpleAuth "myUsername" "mypassword") def
Defining AuthData
can be a bit unwieldy, so simpleAuth
gives us a
reasonable default. Though, for improved security, we should consider
restricting the mechanisms to scramSha1
whenever we can.
Next we have to set the presence to online, otherwise we won't be able to send or receive stanzas to/from other entities.
sendPresence presenceOnline sess
- data Session
- session :: HostName -> AuthData -> SessionConfiguration -> IO (Either XmppFailure Session)
- setConnectionClosedHandler :: (XmppFailure -> Session -> IO ()) -> Session -> IO ()
- reconnect :: Integer -> Session -> IO (Bool, [XmppFailure])
- reconnect' :: Session -> IO Integer
- reconnectNow :: Session -> IO (Maybe XmppFailure)
- data StreamConfiguration = StreamConfiguration {}
- data SessionConfiguration = SessionConfiguration {
- sessionStreamConfiguration :: StreamConfiguration
- onConnectionClosed :: Session -> XmppFailure -> IO ()
- sessionStanzaIDs :: IO (IO Text)
- plugins :: [Plugin]
- enableRoster :: Bool
- data ConnectionDetails
- data ConnectionState
- closeConnection :: Session -> IO ()
- endSession :: Session -> IO ()
- waitForStream :: Session -> IO ()
- type SaslHandler = (Text, StateT StreamState IO (Either XmppFailure (Maybe AuthFailure)))
- type AuthData = Maybe (ConnectionState -> [SaslHandler], Maybe Resource)
- type Username = Text
- type Password = Text
- type AuthZID = Text
- simpleAuth :: Username -> Password -> AuthData
- scramSha1 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- plain :: Username -> Maybe AuthZID -> Password -> SaslHandler
- digestMd5 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- data Jid
- jid :: QuasiQuoter
- jidQ :: QuasiQuoter
- isBare :: Jid -> Bool
- isFull :: Jid -> Bool
- jidFromText :: Text -> Maybe Jid
- jidFromTexts :: Maybe Text -> Text -> Maybe Text -> Maybe Jid
- jidToText :: Jid -> Text
- jidToTexts :: Jid -> (Maybe Text, Text, Maybe Text)
- toBare :: Jid -> Jid
- localpart :: Jid -> Maybe Text
- domainpart :: Jid -> Text
- resourcepart :: Jid -> Maybe Text
- parseJid :: String -> Jid
- getJid :: Session -> IO (Maybe Jid)
- getStanza :: Session -> IO (Stanza, [Annotation])
- getStanzaChan :: Session -> TChan (Stanza, [Annotation])
- newStanzaID :: Session -> IO Text
- data Message = Message {
- messageID :: !(Maybe Text)
- messageFrom :: !(Maybe Jid)
- messageTo :: !(Maybe Jid)
- messageLangTag :: !(Maybe LangTag)
- messageType :: !MessageType
- messagePayload :: ![Element]
- message :: Message
- data MessageError = MessageError {
- messageErrorID :: !(Maybe Text)
- messageErrorFrom :: !(Maybe Jid)
- messageErrorTo :: !(Maybe Jid)
- messageErrorLangTag :: !(Maybe LangTag)
- messageErrorStanzaError :: !StanzaError
- messageErrorPayload :: ![Element]
- data MessageType
- answerMessage :: Message -> [Element] -> Maybe Message
- sendMessage :: Message -> Session -> IO (Either XmppFailure ())
- pullMessage :: Session -> IO (Either MessageError Message)
- getMessage :: Session -> IO Message
- getMessageA :: Session -> IO (Annotated Message)
- waitForMessage :: (Message -> Bool) -> Session -> IO Message
- waitForMessageA :: (Annotated Message -> Bool) -> Session -> IO (Annotated Message)
- waitForMessageError :: (MessageError -> Bool) -> Session -> IO MessageError
- waitForMessageErrorA :: (Annotated MessageError -> Bool) -> Session -> IO (Annotated MessageError)
- filterMessages :: (MessageError -> Bool) -> (Message -> Bool) -> Session -> IO (Either MessageError Message)
- filterMessagesA :: (Annotated MessageError -> Bool) -> (Annotated Message -> Bool) -> Session -> IO (Either (Annotated MessageError) (Annotated Message))
- data Presence = Presence {
- presenceID :: !(Maybe Text)
- presenceFrom :: !(Maybe Jid)
- presenceTo :: !(Maybe Jid)
- presenceLangTag :: !(Maybe LangTag)
- presenceType :: !PresenceType
- presencePayload :: ![Element]
- data PresenceType
- data PresenceError = PresenceError {
- presenceErrorID :: !(Maybe Text)
- presenceErrorFrom :: !(Maybe Jid)
- presenceErrorTo :: !(Maybe Jid)
- presenceErrorLangTag :: !(Maybe LangTag)
- presenceErrorStanzaError :: !StanzaError
- presenceErrorPayload :: ![Element]
- presence :: Presence
- presenceOffline :: Presence
- presenceOnline :: Presence
- presenceSubscribe :: Jid -> Presence
- presenceSubscribed :: Jid -> Presence
- presenceUnsubscribe :: Jid -> Presence
- presenceUnsubscribed :: Jid -> Presence
- presTo :: Presence -> Jid -> Presence
- sendPresence :: Presence -> Session -> IO (Either XmppFailure ())
- pullPresence :: Session -> IO (Either PresenceError Presence)
- waitForPresence :: (Presence -> Bool) -> Session -> IO Presence
- data IQRequest = IQRequest {
- iqRequestID :: !Text
- iqRequestFrom :: !(Maybe Jid)
- iqRequestTo :: !(Maybe Jid)
- iqRequestLangTag :: !(Maybe LangTag)
- iqRequestType :: !IQRequestType
- iqRequestPayload :: !Element
- data IQRequestTicket
- iqRequestBody :: IQRequestTicket -> IQRequest
- data IQRequestType
- data IQResult = IQResult {
- iqResultID :: !Text
- iqResultFrom :: !(Maybe Jid)
- iqResultTo :: !(Maybe Jid)
- iqResultLangTag :: !(Maybe LangTag)
- iqResultPayload :: !(Maybe Element)
- data IQError = IQError {
- iqErrorID :: !Text
- iqErrorFrom :: !(Maybe Jid)
- iqErrorTo :: !(Maybe Jid)
- iqErrorLangTag :: !(Maybe LangTag)
- iqErrorStanzaError :: !StanzaError
- iqErrorPayload :: !(Maybe Element)
- data IQResponse
- sendIQ :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Session -> IO (Either XmppFailure (STM (Maybe (Annotated IQResponse))))
- sendIQ' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Session -> IO (Either IQSendError IQResponse)
- answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> IO (Maybe (Either XmppFailure ()))
- iqResult :: Maybe Element -> IQRequest -> IQResult
- listenIQ :: IQRequestType -> Text -> Session -> IO (Either (STM IQRequestTicket) (STM IQRequestTicket))
- unlistenIQ :: IQRequestType -> Text -> Session -> IO ()
- data StanzaErrorType
- data StanzaError = StanzaError {}
- associatedErrorType :: StanzaErrorCondition -> StanzaErrorType
- mkStanzaError :: StanzaErrorCondition -> StanzaError
- data StanzaErrorCondition
- = BadRequest
- | Conflict
- | FeatureNotImplemented
- | Forbidden
- | Gone (Maybe NonemptyText)
- | InternalServerError
- | ItemNotFound
- | JidMalformed
- | NotAcceptable
- | NotAllowed
- | NotAuthorized
- | PolicyViolation
- | RecipientUnavailable
- | Redirect (Maybe NonemptyText)
- | RegistrationRequired
- | RemoteServerNotFound
- | RemoteServerTimeout
- | ResourceConstraint
- | ServiceUnavailable
- | SubscriptionRequired
- | UndefinedCondition
- | UnexpectedRequest
- data SaslFailure = SaslFailure {
- saslFailureCondition :: SaslError
- saslFailureText :: Maybe (Maybe LangTag, Text)
- data IQSendError
- dupSession :: Session -> IO Session
- module Network.Xmpp.Lens
- type Annotated a = (a, [Annotation])
- data Annotation = forall f . (Typeable f, Show f) => Annotation {
- fromAnnotation :: f
- type Plugin = (Stanza -> IO (Either XmppFailure ())) -> ErrorT XmppFailure IO Plugin'
- data Plugin' = Plugin' {
- inHandler :: Stanza -> [Annotation] -> IO [(Stanza, [Annotation])]
- outHandler :: Stanza -> IO (Either XmppFailure ())
- onSessionUp :: Session -> IO ()
- data LangTag
- langTagFromText :: Text -> Maybe LangTag
- langTagToText :: LangTag -> Text
- parseLangTag :: String -> LangTag
- data XmppFailure
- = StreamErrorFailure StreamErrorInfo
- | StreamEndFailure
- | StreamCloseError ([Element], XmppFailure)
- | TcpConnectionFailure
- | XmppIllegalTcpDetails
- | TlsError XmppTlsError
- | TlsNoServerSupport
- | XmppNoStream
- | XmppAuthFailure AuthFailure
- | TlsStreamSecured
- | XmppOtherFailure
- | XmppIOException IOException
- | XmppInvalidXml String
- data StreamErrorInfo = StreamErrorInfo {
- errorCondition :: !StreamErrorCondition
- errorText :: !(Maybe (Maybe LangTag, NonemptyText))
- errorXml :: !(Maybe Element)
- data StreamErrorCondition
- = StreamBadFormat
- | StreamBadNamespacePrefix
- | StreamConflict
- | StreamConnectionTimeout
- | StreamHostGone
- | StreamHostUnknown
- | StreamImproperAddressing
- | StreamInternalServerError
- | StreamInvalidFrom
- | StreamInvalidNamespace
- | StreamInvalidXml
- | StreamNotAuthorized
- | StreamNotWellFormed
- | StreamPolicyViolation
- | StreamRemoteConnectionFailed
- | StreamReset
- | StreamResourceConstraint
- | StreamRestrictedXml
- | StreamSeeOtherHost
- | StreamSystemShutdown
- | StreamUndefinedCondition
- | StreamUnsupportedEncoding
- | StreamUnsupportedFeature
- | StreamUnsupportedStanzaType
- | StreamUnsupportedVersion
- data AuthFailure
- connectTls :: ResolvConf -> ClientParams -> String -> ErrorT XmppFailure IO StreamHandle
- def :: Default a => a
Session management
The Session object represents a single session with an XMPP server. You can
use session
to establish a session
:: HostName | The hostname / realm |
-> AuthData | |
-> SessionConfiguration | configuration details |
-> IO (Either XmppFailure Session) |
setConnectionClosedHandler :: (XmppFailure -> Session -> IO ()) -> Session -> IO () Source
Changes the handler to be executed when the server connection is closed. To avoid race conditions the initial value should be set in the configuration when creating the session
:: Integer | Maximum number of retries (numbers of 1 or less will perform exactly one retry) |
-> Session | Session to reconnect |
-> IO (Bool, [XmppFailure]) | Whether or not the reconnect attempt was successful, and a list of failure modes encountered |
Reconnect with the stored settings.
Waits a random amount of seconds (between 0 and 60 inclusive) before the first attempt and an increasing amount after each attempt after that. Caps out at 2-5 minutes.
This function does not set your presence to online, so you will have to do this yourself.
:: Session | Session to reconnect |
-> IO Integer | Number of failed retries before connection could be established |
Reconnect with the stored settings with an unlimited number of retries.
Waits a random amount of seconds (between 0 and 60 inclusive) before the first attempt and an increasing amount after each attempt after that. Caps out at 2-5 minutes.
This function does not set your presence to online, so you will have to do this yourself.
:: Session | session to reconnect |
-> IO (Maybe XmppFailure) |
Reconnect immediately with the stored settings. Returns Just
the error
when the reconnect attempt fails and Nothing when no failure was encountered.
This function does not set your presence to online, so you will have to do this yourself.
data StreamConfiguration Source
Configuration settings related to the stream.
StreamConfiguration | |
|
data SessionConfiguration Source
Configuration for the Session
object.
SessionConfiguration | |
|
data ConnectionDetails Source
Specify the method with which the connection is (re-)established
UseRealm | Use realm to resolv host. This is the default. |
UseSrv HostName | Use this hostname for a SRV lookup |
UseHost HostName PortID | Use specified host |
UseConnection (ErrorT XmppFailure IO StreamHandle) | Use custom method to create a StreamHandle. This
will also be used by reconnect. For example, to
establish TLS before starting the stream as done by
GCM, see |
data ConnectionState Source
Signals the state of the stream connection.
closeConnection :: Session -> IO () Source
Close the connection to the server. Closes the stream (by enforcing a write lock and sending a </stream:stream> element), waits (blocks) for three seconds, and then closes the connection.
endSession :: Session -> IO () Source
End the current XMPP session. Kills the associated threads and closes the connection.
Note that XMPP clients (that have signalled availability) should send "Unavailable" presence prior to disconnecting.
The connectionClosedHandler will not be called (to avoid possibly reestablishing the connection).
waitForStream :: Session -> IO () Source
Wait until the connection of the stream is re-established
Authentication handlers
The use of scramSha1
is recommended, but digestMd5
might be
useful for interaction with older implementations.
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.
type AuthData = Maybe (ConnectionState -> [SaslHandler], Maybe Resource) Source
SASL handlers and the desired JID resource
Nothing to disable authentication
The allowed SASL mecahnism can depend on the connection state. For example,
plain
should be avoided unless the connection state is Secured
It is recommended to leave the resource up to the server
simpleAuth :: Username -> Password -> AuthData Source
:: Username | username |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
:: Username | authentication ID (username) |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
:: Username | Authentication identity (authcid or username) |
-> Maybe AuthZID | Authorization identity (authzid) |
-> Password | Password |
-> SaslHandler |
Addressing
A JID (historically: Jabber ID) is XMPPs native format for addressing entities in the network. It is somewhat similar to an e-mail address, but contains three parts instead of two.
A JID is XMPP's native format for addressing entities in the network. It is somewhat similar to an e-mail address but contains three parts instead of two: localpart, domainpart, and resourcepart.
The localpart
of a JID is an optional identifier placed
before the domainpart and separated from the latter by a
'@' character. Typically a localpart uniquely identifies
the entity requesting and using network access provided by a
server (i.e., a local account), although it can also
represent other kinds of entities (e.g., a chat room
associated with a multi-user chat service). The entity
represented by an XMPP localpart is addressed within the
context of a specific domain (i.e.,
localpart@domainpart
).
The domainpart typically identifies the home server to which clients connect for XML routing and data management functionality. However, it is not necessary for an XMPP domainpart to identify an entity that provides core XMPP server functionality (e.g., a domainpart can identify an entity such as a multi-user chat service, a publish-subscribe service, or a user directory).
The resourcepart of a JID is an optional identifier placed
after the domainpart and separated from the latter by the
'/' character. A resourcepart can modify either a
localpart@domainpart
address or a mere domainpart
address. Typically a resourcepart uniquely identifies a
specific connection (e.g., a device or location) or object
(e.g., an occupant in a multi-user chat room) belonging to
the entity associated with an XMPP localpart at a domain
(i.e., localpart@domainpart/resourcepart
).
For more details see RFC 6122 http://xmpp.org/rfcs/rfc6122.html
jid :: QuasiQuoter Source
Constructs and validates a Jid
at compile time.
Syntax:
[jid|localpart@domainpart/resourcepart|]
>>>
[jid|foo@bar/quux|]
parseJid "foo@bar/quux"
>>>
Just [jid|foo@bar/quux|] == jidFromTexts (Just "foo") "bar" (Just "quux")
True
>>>
Just [jid|foo@bar/quux|] == jidFromText "foo@bar/quux"
True
See also jidFromText
Synonym for jid
jidFromText :: Text -> Maybe Jid Source
Parse a JID
>>>
localpart <$> jidFromText "foo@bar/quux"
Just (Just "foo")
>>>
domainpart <$> jidFromText "foo@bar/quux"
Just "bar"
>>>
resourcepart <$> jidFromText "foo@bar/quux"
Just (Just "quux")
- Counterexamples
A JID must only have one '@':
>>>
jidFromText "foo@bar@quux"
Nothing
'@' must come before '/':
>>>
jidFromText "foo/bar@quux"
Nothing
The domain part can't be empty:
>>>
jidFromText "foo@/quux"
Nothing
Both the local part and the resource part can be omitted (but the '@' and '/', must also be removed):
>>>
jidToTexts <$> jidFromText "bar"
Just (Nothing,"bar",Nothing)
>>>
jidToTexts <$> jidFromText "@bar"
Nothing
>>>
jidToTexts <$> jidFromText "bar/"
Nothing
jidFromTexts :: Maybe Text -> Text -> Maybe Text -> Maybe Jid Source
Convert localpart, domainpart, and resourcepart to a JID. Runs the appropriate stringprep profiles and validates the parts.
>>>
jidFromTexts (Just "foo") "bar" (Just "baz") == jidFromText "foo@bar/baz"
True
jidFromTexts (localpart j) (domainpart j) (resourcepart j) == Just j
jidToTexts :: Jid -> (Maybe Text, Text, Maybe Text) Source
Converts a JID to up to three Text values: (the optional) localpart, the domainpart, and (the optional) resourcepart.
>>>
jidToTexts [jid|foo@bar/quux|]
(Just "foo","bar",Just "quux")
>>>
jidToTexts [jid|bar/quux|]
(Nothing,"bar",Just "quux")
>>>
jidToTexts [jid|foo@bar|]
(Just "foo","bar",Nothing)
jidToTexts j == (localpart j, domainpart j, resourcepart j)
Returns the Jid
without the resourcepart (if any).
>>>
toBare [jid|foo@bar/quux|] == [jid|foo@bar|]
True
localpart :: Jid -> Maybe Text Source
Returns the localpart of the Jid
(if any).
>>>
localpart [jid|foo@bar/quux|]
Just "foo"
domainpart :: Jid -> Text Source
Returns the domainpart of the Jid
.
>>>
domainpart [jid|foo@bar/quux|]
"bar"
resourcepart :: Jid -> Maybe Text Source
Returns the resourcepart of the Jid
(if any).
>>>
resourcepart [jid|foo@bar/quux|]
Just "quux"
parseJid :: String -> Jid Source
Parses a JID string.
Note: This function is only meant to be used to reverse Jid
Show
operations; it will produce an undefined
value if the JID does not
validate; please refer to jidFromText
for a safe equivalent.
Stanzas
The basic protocol data unit in XMPP is the XML stanza. The stanza is
essentially a fragment of XML that is sent over a stream. Stanzas
come in
3 flavors:
- Message, for traditional push-style message passing between peers
- Presence, for communicating status updates
- Info/Query (or IQ), for request-response semantics communication
All stanza types have the following attributes in common:
- The id attribute is used by the originating entity to track any
response or error stanza that it might receive in relation to the
generated stanza from another entity (such as an intermediate server or
the intended recipient). It is up to the originating entity whether the
value of the
id
attribute is unique only within its current stream or unique globally. - The from attribute specifies the JID of the sender.
- The to attribute specifies the JID of the intended recipient for the stanza.
- The type attribute specifies the purpose or context of the message, presence, or IQ stanza. The particular allowable values for the 'type' attribute vary depending on whether the stanza is a message, presence, or IQ stanza.
getStanzaChan :: Session -> TChan (Stanza, [Annotation]) Source
Get the channel of incoming stanzas.
newStanzaID :: Session -> IO Text Source
Generates a new stanza identifier based on the sessionStanzaIDs
field of
SessionConfiguration
.
Messages
The message stanza is a push mechanism whereby one entity
pushes information to another entity, similar to the communications that
occur in a system such as email. It is not to be confused with
an InstantMessage
The message stanza. Used for push type communication.
Message | |
|
An empty message
message = Message { messageID = Nothing , messageFrom = Nothing , messageTo = Nothing , messageLangTag = Nothing , messageType = Normal , messagePayload = [] }
data MessageError Source
An error stanza generated in response to a Message
.
MessageError | |
|
data MessageType Source
The type of a Message being sent (http://xmpp.org/rfcs/rfc6121.html#message-syntax-type)
Chat | The message is sent in the context of a one-to-one chat session. Typically an interactive client will present a message of type chat in an interface that enables one-to-one chat between the two parties, including an appropriate conversation history. |
GroupChat | The message is sent in the context of a multi-user chat
environment (similar to that of |
Headline | The message provides an alert, a notification, or other transient information to which no reply is expected (e.g., news headlines, sports updates, near-real-time market data, or syndicated content). Because no reply to the message is expected, typically a receiving client will present a message of type headline in an interface that appropriately differentiates the message from standalone messages, chat messages, and groupchat messages (e.g., by not providing the recipient with the ability to reply). |
Normal | The message is a standalone message that is sent outside the context of a one-to-one conversation or groupchat, and to which it is expected that the recipient will reply. Typically a receiving client will present a message of type normal in an interface that enables the recipient to reply, but without a conversation history. This is the default value. |
Creating
Sending
sendMessage :: Message -> Session -> IO (Either XmppFailure ()) Source
Send a message stanza. Returns False
when the Message
could not be
sent.
Receiving
pullMessage :: Session -> IO (Either MessageError Message) Source
Draw and discard stanzas from the inbound channel until a message or message error is found. Returns the message or message error.
getMessage :: Session -> IO Message Source
Draw and discard stanzas from the inbound channel until a message is found. Returns the message.
getMessageA :: Session -> IO (Annotated Message) Source
Draw and discard stanzas from the inbound channel until a message is found. Returns the message with annotations.
waitForMessage :: (Message -> Bool) -> Session -> IO Message Source
Draw and discard stanzas from the inbound channel until a message matching the given predicate is found. Returns the matching message.
waitForMessageA :: (Annotated Message -> Bool) -> Session -> IO (Annotated Message) Source
Draw and discard stanzas from the inbound channel until a message matching the given predicate is found. Returns the matching message with annotations.
waitForMessageError :: (MessageError -> Bool) -> Session -> IO MessageError Source
Draw and discard stanzas from the inbound channel until a message error matching the given predicate is found. Returns the matching message error
waitForMessageErrorA :: (Annotated MessageError -> Bool) -> Session -> IO (Annotated MessageError) Source
Draw and discard stanzas from the inbound channel until a message error matching the given predicate is found. Returns the matching message error with annotations.
filterMessages :: (MessageError -> Bool) -> (Message -> Bool) -> Session -> IO (Either MessageError Message) Source
Draw and discard stanzas from the inbound channel until a message or message error matching the given respective predicate is found. Returns the matching message or message error.
filterMessagesA :: (Annotated MessageError -> Bool) -> (Annotated Message -> Bool) -> Session -> IO (Either (Annotated MessageError) (Annotated Message)) Source
Draw and discard stanzas from the inbound channel until a message or message error matching the given respective predicate is found. Returns the matching message or message error with annotations
Presence
XMPP includes the ability for an entity to advertise its network availability, or "presence", to other entities. In XMPP, this availability for communication is signaled end-to-end by means of a dedicated communication primitive: the presence stanza.
The presence stanza. Used for communicating status updates.
Presence | |
|
data PresenceType Source
PresenceType
holds Xmpp presence types. The "error" message type is left
out as errors are using PresenceError
.
Subscribe | Sender wants to subscribe to presence |
Subscribed | Sender has approved the subscription |
Unsubscribe | Sender is unsubscribing from presence |
Unsubscribed | Sender has denied or cancelled a subscription |
Probe | Sender requests current presence; should only be used by servers |
Available | Sender wants to express availability (no type attribute is defined) |
Unavailable |
data PresenceError Source
An error stanza generated in response to a Presence
.
PresenceError | |
|
Creating
presenceOffline :: Presence Source
Signal to the server that the client is no longer available for communication.
presenceOnline :: Presence Source
Signal to the server that the client is available for communication.
presenceSubscribe :: Jid -> Presence Source
Request subscription with an entity.
presenceSubscribed :: Jid -> Presence Source
Approve a subscripton of an entity.
presenceUnsubscribe :: Jid -> Presence Source
End a subscription with an entity.
presenceUnsubscribed :: Jid -> Presence Source
Deny a not-yet approved or terminate a previously approved subscription of an entity
Sending
Sends a presence stanza. In general, the presence stanza should have no
to
attribute, in which case the server to which the client is connected
will broadcast that stanza to all subscribed entities. However, a
publishing client may also send a presence stanza with a to
attribute, in
which case the server will route or deliver that stanza to the intended
recipient.
sendPresence :: Presence -> Session -> IO (Either XmppFailure ()) Source
Send a presence stanza.
Receiving
pullPresence :: Session -> IO (Either PresenceError Presence) Source
Read a presence stanza from the inbound stanza channel, discards any other stanzas. Returns the presence stanza.
waitForPresence :: (Presence -> Bool) -> Session -> IO Presence Source
Draw and discard stanzas from the inbound channel until a presence stanza matching the given predicate is found. Return the presence stanza with annotations.
IQ
Info/Query, or IQ, is a request-response mechanism, similar in some
ways to the Hypertext Transfer Protocol HTTP
. The semantics of IQ enable
an entity to make a request of, and receive a response from, another
entity. The data content and precise semantics of the request and response
is defined by the schema or other structural definition associated with the
XML namespace that qualifies the direct child element of the IQ element. IQ
interactions follow a common pattern of structured data exchange such as
get/result or set/result (although an error can be returned in reply to a
request if appropriate)
A "request" Info/Query (IQ) stanza is one with either "get" or "set" as type. It always contains an xml payload.
IQRequest | |
|
data IQRequestTicket Source
A received and wrapped up IQ request. Prevents you from (illegally) answering a single IQ request multiple times
iqRequestBody :: IQRequestTicket -> IQRequest Source
The actual IQ request that created this ticket.
data IQRequestType Source
The type of IQ request that is made.
The (non-error) answer to an IQ request.
IQResult | |
|
The answer to an IQ request that generated an error.
IQError | |
|
data IQResponse Source
:: Maybe Integer | Timeout . When the timeout is reached the response
TMVar will be filled with |
-> Maybe Jid | Recipient (to) |
-> IQRequestType | IQ type ( |
-> Maybe LangTag | Language tag of the payload ( |
-> Element | The IQ body (there has to be exactly one) |
-> Session | |
-> IO (Either XmppFailure (STM (Maybe (Annotated IQResponse)))) |
Sends an IQ, returns an STM action that returns the first inbound IQ with a
matching ID that has type result
or error
or Nothing if the timeout was
reached.
When sending the action fails, an XmppFailure is returned.
sendIQ' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Session -> IO (Either IQSendError IQResponse) Source
Like sendIQ
, but waits for the answer IQ. Discards plugin Annotations
answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> IO (Maybe (Either XmppFailure ())) Source
Answer an IQ request. Only the first answer ist sent and Just True is returned when the answer is sucessfully sent. If an error occured during sending Just False is returned (and another attempt can be undertaken). Subsequent answers after the first sucessful one are dropped and (False is returned in that case)
:: IQRequestType | |
-> Text | Namespace of the child element |
-> Session | |
-> IO (Either (STM IQRequestTicket) (STM IQRequestTicket)) |
Register your interest in inbound IQ stanzas of a specific type and namespace. The returned STM action yields the received, matching IQ stanzas.
If a handler for IQ stanzas with the given type and namespace is already registered, the producer will be wrapped in Left. In this case the returned request tickets may already be processed elsewhere.
Unregister a previously registered IQ handler. No more IQ stanzas will be delivered to any of the returned producers.
Errors
data StanzaErrorType Source
StanzaError
s always have one of these types.
data StanzaError Source
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.
associatedErrorType :: StanzaErrorCondition -> StanzaErrorType Source
The RECOMMENDED error type associated with an error condition. The following conditions allow for multiple types
FeatureNotImplemented
:Cancel
orModify
(returnsCancel
)PolicyViolation
:Modify
orWait
(Modify
)RemoteServerTimeout
:Wait
or unspecified other (Wait
)UndefinedCondition
: Any condition (Cancel
)
:: StanzaErrorCondition | condition |
-> StanzaError |
Create a StanzaError with condition
and the associatedErrorType
. Leave
the error text and the application specific condition empty
data StanzaErrorCondition Source
Stanza errors are accommodated with one of the error conditions listed below.
BadRequest | Malformed XML. |
Conflict | Resource or session with name already exists. |
FeatureNotImplemented | |
Forbidden | Insufficient permissions. |
Gone (Maybe NonemptyText) | Entity can no longer be contacted at this address. |
InternalServerError | |
ItemNotFound | |
JidMalformed | |
NotAcceptable | Does not meet policy criteria. |
NotAllowed | No entity may perform this action. |
NotAuthorized | Must provide proper credentials. |
PolicyViolation | The entity has violated some local service policy (e.g., a message contains words that are prohibited by the service) |
RecipientUnavailable | Temporarily unavailable. |
Redirect (Maybe NonemptyText) | Redirecting to other entity, usually temporarily. |
RegistrationRequired | |
RemoteServerNotFound | |
RemoteServerTimeout | |
ResourceConstraint | Entity lacks the necessary system resources. |
ServiceUnavailable | |
SubscriptionRequired | |
UndefinedCondition | Application-specific condition. |
UnexpectedRequest | Badly timed request. |
data SaslFailure Source
SaslFailure | |
|
data IQSendError Source
Error that can occur during sendIQ'
Threads
dupSession :: Session -> IO Session Source
Duplicate the inbound channel of the session object. Most receiving functions discard stanzas they are not interested in from the inbound channel. Duplicating the channel ensures that those stanzas can aren't lost and can still be handled somewhere else.
Lenses
Network.Xmpp doesn't re-export the accessors to avoid name clashes. To use them import Network.Xmpp.Lens
module Network.Xmpp.Lens
Plugins
type Annotated a = (a, [Annotation]) Source
data Annotation Source
Annotations are auxiliary data attached to received stanzas by Plugin
s 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.
forall f . (Typeable f, Show f) => Annotation | |
|
= (Stanza -> IO (Either XmppFailure ())) | pass stanza to next plugin |
-> ErrorT XmppFailure IO Plugin' |
Plugin' | |
|
LangTag
The language tag in accordance with RFC 5646 (in the form of "en-US"). It has a primary tag and a number of subtags. Two language tags are considered equal if and only if they contain the same tags (case-insensitive).
langTagFromText :: Text -> Maybe LangTag Source
Parses, validates, and possibly constructs a LangTag object.
langTagToText :: LangTag -> Text Source
parseLangTag :: String -> LangTag Source
Miscellaneous
data XmppFailure Source
Signals an XMPP stream error or another unpredicted stream-related situation. This error is fatal, and closes the XMPP stream.
StreamErrorFailure StreamErrorInfo | An error XML stream element has been encountered. |
StreamEndFailure | The stream has been closed.
This exception is caught by the
concurrent implementation, and
will thus not be visible
through use of |
StreamCloseError ([Element], XmppFailure) | When an XmppFailure is encountered in closeStreams, this constructor wraps the elements collected so far. |
TcpConnectionFailure | All attempts to TCP connect to the server failed. |
XmppIllegalTcpDetails | The TCP details provided did not validate. |
TlsError XmppTlsError | An error occurred in the TLS layer |
TlsNoServerSupport | The server does not support the use of TLS |
XmppNoStream | An action that required an active
stream were performed when the
|
XmppAuthFailure AuthFailure | Authentication with the server failed (unrecoverably) |
TlsStreamSecured | Connection already secured |
XmppOtherFailure | Undefined condition. More information should be available in the log. |
XmppIOException IOException | An |
XmppInvalidXml String | Received data is not valid XML |
data StreamErrorInfo Source
Encapsulates information about an XMPP stream error.
StreamErrorInfo | |
|
data StreamErrorCondition Source
StreamBadFormat | The entity has sent XML that cannot be processed. |
StreamBadNamespacePrefix | The entity has sent a namespace prefix that is unsupported, or has sent no namespace prefix on an element that needs such a prefix |
StreamConflict | The server either (1) is closing the existing stream for this entity because a new stream has been initiated that conflicts with the existing stream, or (2) is refusing a new stream for this entity because allowing the new stream would conflict with an existing stream (e.g., because the server allows only a certain number of connections from the same IP address or allows only one server-to-server stream for a given domain pair as a way of helping to ensure in-order processing |
StreamConnectionTimeout | One party is closing the stream because it has reason to believe that the other party has permanently lost the ability to communicate over the stream. |
StreamHostGone | The value of the |
StreamHostUnknown | The value of the |
StreamImproperAddressing | A stanza sent between two servers lacks a
|
StreamInternalServerError | The server has experienced a misconfiguration or other internal error that prevents it from servicing the stream. |
StreamInvalidFrom | The data provided in a |
StreamInvalidNamespace | The stream namespace name is something other than "http:/etherx.jabber.orgstreams" (see Section 11.2) or the content namespace declared as the default namespace is not supported (e.g., something other than "jabber:client" or "jabber:server"). |
StreamInvalidXml | The entity has sent invalid XML over the stream to a server that performs validation |
StreamNotAuthorized | The entity has attempted to send XML stanzas or other outbound data before the stream has been authenticated, or otherwise is not authorized to perform an action related to stream negotiation; the receiving entity MUST NOT process the offending data before sending the stream error. |
StreamNotWellFormed | The initiating entity has sent XML that violates the well-formedness rules of [XML] or [XML‑NAMES]. |
StreamPolicyViolation | The entity has violated some local service policy (e.g., a stanza exceeds a configured size limit); the server MAY choose to specify the policy in the <text/> element or in an application-specific condition element. |
StreamRemoteConnectionFailed | The server is unable to properly connect to a remote entity that is needed for authentication or authorization (e.g., in certain scenarios related to Server Dialback [XEP‑0220]); this condition is not to be used when the cause of the error is within the administrative domain of the XMPP service provider, in which case the <internal-server-error /> condition is more appropriate. |
StreamReset | The server is closing the stream because it has new (typically security-critical) features to offer, because the keys or certificates used to establish a secure context for the stream have expired or have been revoked during the life of the stream , because the TLS sequence number has wrapped, etc. The reset applies to the stream and to any security context established for that stream (e.g., via TLS and SASL), which means that encryption and authentication need to be negotiated again for the new stream (e.g., TLS session resumption cannot be used) |
StreamResourceConstraint | The server lacks the system resources necessary to service the stream. |
StreamRestrictedXml | he entity has attempted to send restricted XML features such as a comment, processing instruction, DTD subset, or XML entity reference |
StreamSeeOtherHost | The server will not provide service to the initiating entity but is redirecting traffic to another host under the administrative control of the same service provider. |
StreamSystemShutdown | The server is being shut down and all active streams are being closed. |
StreamUndefinedCondition | The error condition is not one of those defined by the other conditions in this list |
StreamUnsupportedEncoding | The initiating entity has encoded the stream in an encoding that is not supported by the server or has otherwise improperly encoded the stream (e.g., by violating the rules of the [UTF‑8] encoding). |
StreamUnsupportedFeature | The receiving entity has advertised a mandatory-to-negotiate stream feature that the initiating entity does not support, and has offered no other mandatory-to-negotiate feature alongside the unsupported feature. |
StreamUnsupportedStanzaType | The initiating entity has sent a first-level child of the stream that is not supported by the server, either because the receiving entity does not understand the namespace or because the receiving entity does not understand the element name for the applicable namespace (which might be the content namespace declared as the default namespace) |
StreamUnsupportedVersion | The |
data AuthFailure Source
Signals a SASL authentication error condition.
AuthNoAcceptableMechanism [Text] | No mechanism offered by the server was matched by the provided acceptable mechanisms; wraps the mechanisms offered by the server |
AuthSaslFailure SaslFailure | A SASL failure element was encountered |
AuthIllegalCredentials | The credentials provided did not conform to the SASLprep Stringprep profile |
AuthOtherFailure | Other failure; more information is available in the log |
:: ResolvConf | Resolv conf to use (try |
-> 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.