pontarius-xmpp-0.5.6.8: An XMPP client library
Stabilityunstable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Xmpp.Internal

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

Documentation

withConnection :: (Stream -> IO (b, Stream)) -> Session -> IO (Either XmppFailure b) Source #

Run an XmppConMonad 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 -> Context -> IO (Either StreamError a)

modifyHandlers :: (EventHandlers -> EventHandlers) -> Session -> IO () Source #

Executes a function to update the event handlers.

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

runHandler :: (EventHandlers -> IO a) -> Session -> IO a Source #

Run an event handler.

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).

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.

readWorker :: (XmppElement -> IO ()) -> (XmppFailure -> IO ()) -> TMVar Stream -> IO a Source #

startThreadsWith :: TMVar (ByteString -> IO (Either XmppFailure ())) -> (XmppElement -> IO ()) -> TMVar EventHandlers -> Stream -> Maybe Int -> IO (Either XmppFailure (IO (), TMVar Stream, ThreadId)) Source #

Runs thread in XmppState monad. Returns channel of incoming and outgoing stances, respectively, and an Action to stop the Threads and close the connection.

connPersist :: Maybe Int -> TMVar (ByteString -> IO a) -> IO () Source #

Sends a blank space every delay seconds to keep the connection alive.

sendRawStanza :: Stanza -> Session -> IO (Either XmppFailure ()) Source #

Send a stanza to the server without running plugins. (The stanza is sent as is)

sendStanza :: Stanza -> Session -> IO (Either XmppFailure ()) Source #

Send a stanza to the server, managed by plugins

getStanzaChan :: Session -> TChan (Stanza, [Annotation]) Source #

Get the channel of incoming stanzas.

getStanza :: Session -> IO (Stanza, [Annotation]) Source #

Get the next incoming stanza

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.

getJid :: Session -> IO (Maybe Jid) Source #

Return the JID assigned to us by the server

getFeatures :: Session -> IO StreamFeatures Source #

Return the stream features the server announced

waitForStream :: Session -> IO () Source #

Wait until the connection of the stream is re-established

type StanzaHandler Source #

Arguments

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

outgoing stanza

-> XmppElement

stanza to handle

-> [Annotation]

annotations added by previous handlers

-> IO [(XmppElement, [Annotation])]

modified stanzas and additional annotations

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

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

Instances

Instances details
Show Annotation Source # 
Instance details

Defined in Network.Xmpp.Concurrent.Types

type Annotated a = (a, [Annotation]) Source #

getAnnotation :: Typeable b => Annotated a -> Maybe b Source #

Retrieve the first matching annotation

data Plugin' Source #

Constructors

Plugin' 

Fields

type Plugin Source #

Arguments

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

pass stanza to next plugin

-> ExceptT XmppFailure IO Plugin' 

data SessionConfiguration Source #

Configuration for the Session object.

Constructors

SessionConfiguration 

Fields

Instances

Instances details
Default SessionConfiguration Source # 
Instance details

Defined in Network.Xmpp.Concurrent.Types

data EventHandlers Source #

Handlers to be run when the Xmpp session ends and when the Xmpp connection is closed.

Constructors

EventHandlers 

data Interrupt Source #

Interrupt is used to signal to the reader thread that it should stop. Th contained semphore signals the reader to resume it's work.

Constructors

Interrupt (TMVar ()) 

data Session Source #

The Session object represents a single session with an XMPP server. You can use session to establish a session

Constructors

Session 

type IQHandlers = (Map (IQRequestType, Text) (TChan IQRequestTicket), Map Text (Either (Maybe Jid) Jid, TMVar (Maybe (Annotated IQResponse)))) Source #

IQHandlers holds the registered channels for incoming IQ requests and TMVars of and TMVars for expected IQ responses (the second Text represent a stanza identifier.

data IQRequestTicket Source #

A received and wrapped up IQ request. Prevents you from (illegally) answering a single IQ request multiple times

Constructors

IQRequestTicket 

Fields

pullMessageA :: Session -> IO (Either (Annotated MessageError) (Annotated Message)) Source #

Draw and discard stanzas from the inbound channel until a message or message error is found. Returns the message or message error with annotations.

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.

getMessageA :: Session -> IO (Annotated Message) Source #

Draw and discard stanzas from the inbound channel until a message is found. Returns the message with annotations.

getMessage :: Session -> IO Message Source #

Draw and discard stanzas from the inbound channel until a message is found. Returns the 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.

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.

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.

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

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

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.

sendMessage :: Message -> Session -> IO (Either XmppFailure ()) Source #

Send a message stanza. Returns Left when the Message could not be sent.

pullPresenceA :: Session -> IO (Either (Annotated PresenceError) (Annotated Presence)) Source #

Read a presence stanza from the inbound stanza channel, discards any other stanzas. Returns the presence stanza with annotations.

pullPresence :: Session -> IO (Either PresenceError Presence) Source #

Read a presence stanza from the inbound stanza channel, discards any other stanzas. Returns the presence stanza.

waitForPresenceA :: (Annotated Presence -> Bool) -> Session -> IO (Annotated 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.

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.

sendPresence :: Presence -> Session -> IO (Either XmppFailure ()) Source #

Send a presence stanza.

sendIQ Source #

Arguments

:: Maybe Integer

Timeout . When the timeout is reached the response TMVar will be filled with IQResponseTimeout and the id is removed from the list of IQ handlers. Nothing deactivates the timeout

-> Maybe Jid

Recipient (to)

-> IQRequestType

IQ type (Get or Set)

-> Maybe LangTag

Language tag of the payload (Nothing for default)

-> Element

The IQ body (there has to be exactly one)

-> [ExtendedAttribute]

Additional stanza attributes

-> 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 -> [ExtendedAttribute] -> Session -> IO (Either IQSendError IQResponse) Source #

Like sendIQ, but waits for the answer IQ. Discards plugin Annotations

listenIQ Source #

Arguments

:: IQRequestType

Type of IQs to receive (Get or Set)

-> 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.

unlistenIQ Source #

Arguments

:: IQRequestType

Type of IQ (Get or Set)

-> Text

Namespace of the child element

-> Session 
-> IO () 

Unregister a previously registered IQ handler. No more IQ stanzas will be delivered to any of the returned producers.

answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> 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)

sendIQRequest :: (IQRequestClass a, MonadError IQRequestError m, MonadIO m) => Maybe Integer -> Maybe Jid -> a -> Session -> m (Either IQError (IQResponseType a)) Source #

Send an IQ request. May throw IQSendError, UnpickleError,

newSession :: Stream -> SessionConfiguration -> HostName -> Maybe (ConnectionState -> [SaslHandler], Maybe Text) -> IO (Either XmppFailure Session) Source #

Creates and initializes a new Xmpp context.

session Source #

Arguments

:: HostName

The hostname / realm

-> AuthData 
-> SessionConfiguration

configuration details

-> IO (Either XmppFailure Session) 

Creates a Session object by setting up a connection with an XMPP server.

Will connect to the specified host with the provided configuration. If the third parameter is a Just value, session will attempt to authenticate and acquire an XMPP resource.

newStanzaID :: Session -> IO Text Source #

Generates a new stanza identifier based on the sessionStanzaIDs field of SessionConfiguration.

reconnect Source #

Arguments

:: 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.

reconnect' Source #

Arguments

:: 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.

reconnectNow Source #

Arguments

:: 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.

simpleAuth :: Username -> Password -> AuthData Source #

Authenticate using, in order of preference, scramSha1, digestMd5 and finally, if both of those are not support and the stream is Secured with TLS, try plain

The resource will be decided by the server

sendRawStanza :: Stanza -> Session -> IO (Either XmppFailure ()) Source #

Send a stanza to the server without running plugins. (The stanza is sent as is)

sendStanza :: Stanza -> Session -> IO (Either XmppFailure ()) Source #

Send a stanza to the server, managed by plugins

getStanzaChan :: Session -> TChan (Stanza, [Annotation]) Source #

Get the channel of incoming stanzas.

getStanza :: Session -> IO (Stanza, [Annotation]) Source #

Get the next incoming stanza

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.

getJid :: Session -> IO (Maybe Jid) Source #

Return the JID assigned to us by the server

getFeatures :: Session -> IO StreamFeatures Source #

Return the stream features the server announced

waitForStream :: Session -> IO () Source #

Wait until the connection of the stream is re-established

sendIQ Source #

Arguments

:: Maybe Integer

Timeout . When the timeout is reached the response TMVar will be filled with IQResponseTimeout and the id is removed from the list of IQ handlers. Nothing deactivates the timeout

-> Maybe Jid

Recipient (to)

-> IQRequestType

IQ type (Get or Set)

-> Maybe LangTag

Language tag of the payload (Nothing for default)

-> Element

The IQ body (there has to be exactly one)

-> [ExtendedAttribute]

Additional stanza attributes

-> 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 -> [ExtendedAttribute] -> Session -> IO (Either IQSendError IQResponse) Source #

Like sendIQ, but waits for the answer IQ. Discards plugin Annotations

listenIQ Source #

Arguments

:: IQRequestType

Type of IQs to receive (Get or Set)

-> 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.

unlistenIQ Source #

Arguments

:: IQRequestType

Type of IQ (Get or Set)

-> Text

Namespace of the child element

-> Session 
-> IO () 

Unregister a previously registered IQ handler. No more IQ stanzas will be delivered to any of the returned producers.

answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> 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)

sendIQRequest :: (IQRequestClass a, MonadError IQRequestError m, MonadIO m) => Maybe Integer -> Maybe Jid -> a -> Session -> m (Either IQError (IQResponseType a)) Source #

Send an IQ request. May throw IQSendError, UnpickleError,

pullMessageA :: Session -> IO (Either (Annotated MessageError) (Annotated Message)) Source #

Draw and discard stanzas from the inbound channel until a message or message error is found. Returns the message or message error with annotations.

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.

getMessageA :: Session -> IO (Annotated Message) Source #

Draw and discard stanzas from the inbound channel until a message is found. Returns the message with annotations.

getMessage :: Session -> IO Message Source #

Draw and discard stanzas from the inbound channel until a message is found. Returns the 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.

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.

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.

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

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

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.

sendMessage :: Message -> Session -> IO (Either XmppFailure ()) Source #

Send a message stanza. Returns Left when the Message could not be sent.

withConnection :: (Stream -> IO (b, Stream)) -> Session -> IO (Either XmppFailure b) Source #

Run an XmppConMonad 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 -> Context -> IO (Either StreamError a)

modifyHandlers :: (EventHandlers -> EventHandlers) -> Session -> IO () Source #

Executes a function to update the event handlers.

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

runHandler :: (EventHandlers -> IO a) -> Session -> IO a Source #

Run an event handler.

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).

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.

pullPresenceA :: Session -> IO (Either (Annotated PresenceError) (Annotated Presence)) Source #

Read a presence stanza from the inbound stanza channel, discards any other stanzas. Returns the presence stanza with annotations.

pullPresence :: Session -> IO (Either PresenceError Presence) Source #

Read a presence stanza from the inbound stanza channel, discards any other stanzas. Returns the presence stanza.

waitForPresenceA :: (Annotated Presence -> Bool) -> Session -> IO (Annotated 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.

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.

sendPresence :: Presence -> Session -> IO (Either XmppFailure ()) Source #

Send a presence stanza.

readWorker :: (XmppElement -> IO ()) -> (XmppFailure -> IO ()) -> TMVar Stream -> IO a Source #

startThreadsWith :: TMVar (ByteString -> IO (Either XmppFailure ())) -> (XmppElement -> IO ()) -> TMVar EventHandlers -> Stream -> Maybe Int -> IO (Either XmppFailure (IO (), TMVar Stream, ThreadId)) Source #

Runs thread in XmppState monad. Returns channel of incoming and outgoing stances, respectively, and an Action to stop the Threads and close the connection.

connPersist :: Maybe Int -> TMVar (ByteString -> IO a) -> IO () Source #

Sends a blank space every delay seconds to keep the connection alive.

type StanzaHandler Source #

Arguments

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

outgoing stanza

-> XmppElement

stanza to handle

-> [Annotation]

annotations added by previous handlers

-> IO [(XmppElement, [Annotation])]

modified stanzas and additional annotations

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

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

Instances

Instances details
Show Annotation Source # 
Instance details

Defined in Network.Xmpp.Concurrent.Types

type Annotated a = (a, [Annotation]) Source #

getAnnotation :: Typeable b => Annotated a -> Maybe b Source #

Retrieve the first matching annotation

data Plugin' Source #

Constructors

Plugin' 

Fields

type Plugin Source #

Arguments

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

pass stanza to next plugin

-> ExceptT XmppFailure IO Plugin' 

data SessionConfiguration Source #

Configuration for the Session object.

Constructors

SessionConfiguration 

Fields

Instances

Instances details
Default SessionConfiguration Source # 
Instance details

Defined in Network.Xmpp.Concurrent.Types

data EventHandlers Source #

Handlers to be run when the Xmpp session ends and when the Xmpp connection is closed.

Constructors

EventHandlers 

data Interrupt Source #

Interrupt is used to signal to the reader thread that it should stop. Th contained semphore signals the reader to resume it's work.

Constructors

Interrupt (TMVar ()) 

data Session Source #

The Session object represents a single session with an XMPP server. You can use session to establish a session

Constructors

Session 

type IQHandlers = (Map (IQRequestType, Text) (TChan IQRequestTicket), Map Text (Either (Maybe Jid) Jid, TMVar (Maybe (Annotated IQResponse)))) Source #

IQHandlers holds the registered channels for incoming IQ requests and TMVars of and TMVars for expected IQ responses (the second Text represent a stanza identifier.

data IQRequestTicket Source #

A received and wrapped up IQ request. Prevents you from (illegally) answering a single IQ request multiple times

Constructors

IQRequestTicket 

Fields

data InstantMessage Source #

The instant message (IM) specific part of a message.

Instances

Instances details
Default InstantMessage Source # 
Instance details

Defined in Network.Xmpp.IM.Message

Methods

def :: InstantMessage #

instantMessage :: InstantMessage Source #

Empty instant message.

getIM :: Message -> Maybe InstantMessage Source #

Get the IM specific parts of a message. Returns Nothing when the received payload is not valid IM data.

withIM :: Message -> InstantMessage -> Message Source #

Append IM data to a message. Additional IM bodies with the same Langtag are discarded.

simpleIM Source #

Arguments

:: Jid

recipient

-> Text

body

-> Message 

Generate a simple message

answerIM :: [MessageBody] -> Message -> Maybe Message Source #

Generate an answer from a received message. The recepient is taken from the original sender, the sender is set to Nothing, message ID, language tag, message type as well as subject and thread are inherited.

Additional IM bodies with the same Langtag are discarded.

data IMPresence Source #

Constructors

IMP 

Instances

Instances details
Show IMPresence Source # 
Instance details

Defined in Network.Xmpp.IM.Presence

Default IMPresence Source # 
Instance details

Defined in Network.Xmpp.IM.Presence

Methods

def :: IMPresence #

Eq IMPresence Source # 
Instance details

Defined in Network.Xmpp.IM.Presence

getIMPresence :: Presence -> Maybe IMPresence Source #

Try to extract RFC6121 IM presence information from presence stanza. Returns Nothing when the data is malformed, (Just IMPresence) otherwise.

timeout :: Maybe Integer Source #

Timeout to use with IQ requests

rosterSet Source #

Arguments

:: Jid

JID of the item

-> Maybe Text

Name alias

-> [Text]

Groups (duplicates will be removed)

-> Session 
-> IO (Either IQSendError (Annotated IQResponse)) 

Add or update an item to the roster.

To update the item just send the complete set of new data.

rosterAdd :: Jid -> Maybe Text -> [Text] -> Session -> IO (Either IQSendError (Annotated IQResponse)) Source #

Synonym to rosterSet

rosterRemove :: Jid -> Session -> IO Bool Source #

Remove an item from the roster. Return True when the item is sucessfully removed or if it wasn't in the roster to begin with.

getRosterSTM :: Session -> STM Roster Source #

Retrieve the current Roster state (STM version)

getRoster :: Session -> IO Roster Source #

Retrieve the current Roster state

initRoster :: Session -> IO () Source #

Get the initial roster or refresh the roster. You don't need to call this on your own.

data Subscription Source #

Constructors

None

the user does not have a subscription to the contact's presence information, and the contact does not have a subscription to the user's presence information

To

the user has a subscription to the contact's presence information, but the contact does not have a subscription to the user's presence information

From

the contact has a subscription to the user's presence information, but the user does not have a subscription to the contact's presence information

Both

both the user and the contact have subscriptions to each other's presence information

Remove 

data Roster Source #

Constructors

Roster 

Fields

Instances

Instances details
Show Roster Source # 
Instance details

Defined in Network.Xmpp.IM.Roster.Types

data Item Source #

Roster Items

Constructors

Item 

Instances

Instances details
Show Item Source # 
Instance details

Defined in Network.Xmpp.IM.Roster.Types

Methods

showsPrec :: Int -> Item -> ShowS #

show :: Item -> String #

showList :: [Item] -> ShowS #

data RosterUpdate Source #

Constructors

RosterUpdateRemove Jid 
RosterUpdateAdd Item

New or updated item

Instances

Instances details
Show RosterUpdate Source # 
Instance details

Defined in Network.Xmpp.IM.Roster.Types

data QueryItem Source #

Instances

Instances details
Show QueryItem Source # 
Instance details

Defined in Network.Xmpp.IM.Roster.Types

data Query Source #

Constructors

Query 

Instances

Instances details
Show Query Source # 
Instance details

Defined in Network.Xmpp.IM.Roster.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

pickleElem :: PU [Node] a -> a -> Element Source #

mbl :: Maybe [a] -> [a] Source #

lmb :: [t] -> Maybe [t] Source #

xmppSasl Source #

Arguments

:: [SaslHandler]

Acceptable authentication mechanisms and their corresponding handlers

-> Stream 
-> IO (Either XmppFailure (Maybe AuthFailure)) 

Uses the first supported mechanism to authenticate, if any. Updates the state with non-password credentials and restarts the stream upon success. Returns Nothing on success, an AuthFailure if authentication fails, or an XmppFailure if anything else fails.

digestMd5 Source #

Arguments

:: Username

Authentication identity (authcid or username)

-> Maybe AuthZID

Authorization identity (authzid)

-> Password

Password

-> SaslHandler 

scramSha1 Source #

Arguments

:: Username

username

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

plain Source #

Arguments

:: Username

authentication ID (username)

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

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

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

xpSaslElement :: PU [Node] SaslElement Source #

Pickler for SaslElement.

quote :: ByteString -> ByteString Source #

Add quotationmarks around a byte string.

pullChallenge :: ExceptT AuthFailure (StateT StreamState IO) (Maybe ByteString) Source #

Pull the next element, checking that it is a challenge.

saslFromJust :: Maybe a -> ExceptT AuthFailure (StateT StreamState IO) a Source #

Extract value from Just, failing with AuthOtherFailure on Nothing.

pullSuccess :: ExceptT AuthFailure (StateT StreamState IO) (Maybe Text) Source #

Pull the next element and check that it is success.

pullFinalMessage :: ExceptT AuthFailure (StateT StreamState IO) (Maybe ByteString) Source #

Pull the next element. When it's success, return it's payload. If it's a challenge, send an empty response and pull success.

toPairs :: ByteString -> ExceptT AuthFailure (StateT StreamState IO) Pairs Source #

Extract p=q pairs from a challenge.

respond :: Maybe ByteString -> ExceptT AuthFailure (StateT StreamState IO) () Source #

Send a SASL response element. The content will be base64-encoded.

prepCredentials :: Text -> Maybe Text -> Text -> ExceptT AuthFailure (StateT StreamState IO) (Text, Maybe Text, Text) Source #

Run the appropriate stringprep profiles on the credentials. May fail with AuthStringPrepFailure

xorBS :: ByteString -> ByteString -> ByteString Source #

Bit-wise xor of byte strings

merge :: [ByteString] -> ByteString Source #

Join byte strings with ","

(+++) :: ByteString -> ByteString -> ByteString Source #

Infix concatenation of byte strings

digestMd5 Source #

Arguments

:: Username

Authentication identity (authcid or username)

-> Maybe AuthZID

Authorization identity (authzid)

-> Password

Password

-> SaslHandler 

scramSha1 Source #

Arguments

:: Username

username

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

plain Source #

Arguments

:: Username

authentication ID (username)

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

digestMd5 Source #

Arguments

:: Username

Authentication identity (authcid or username)

-> Maybe AuthZID

Authorization identity (authzid)

-> Password

Password

-> SaslHandler 

plain Source #

Arguments

:: Username

authentication ID (username)

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

hashToken :: Hash ctx hash => hash Source #

A nicer name for undefined, for use as a dummy token to determin the hash function to use

scram Source #

Arguments

:: Hash ctx hash 
=> hash

Dummy argument to determine the hash to use; you can safely pass undefined or a hashToken to it

-> Text

Authentication ID (user name)

-> Maybe Text

Authorization ID

-> Text

Password

-> ExceptT AuthFailure (StateT StreamState IO) () 

Salted Challenge Response Authentication Mechanism (SCRAM) SASL mechanism according to RFC 5802.

This implementation is independent and polymorphic in the used hash function.

scramSha1 Source #

Arguments

:: Username

username

-> Maybe AuthZID

authorization ID

-> Password

password

-> SaslHandler 

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.

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

presenceOnline :: Presence Source #

Signal to the server that the client is available for communication.

presenceOffline :: Presence Source #

Signal to the server that the client is no longer available for communication.

answerMessage :: Message -> [Element] -> Maybe Message Source #

Produce an answer message with the given payload, setting "from" to the "to" attributes in the original message. Produces a Nothing value of the provided message message has no "from" attribute. Sets the "from" attribute to Nothing to let the server assign one.

presTo :: Presence -> Jid -> Presence Source #

Add a recipient to a presence notification.

mkStanzaError Source #

Arguments

:: StanzaErrorCondition

condition

-> StanzaError 

Create a StanzaError with condition and the associatedErrorType. Leave the error text and the application specific condition empty

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

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

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

closeStreams :: Stream -> IO () Source #

Send "/stream:stream" and wait for the server to finish processing and to close the connection. Any remaining elements from the server are returned. Surpresses StreamEndFailure exceptions, but may throw a StreamCloseError.

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.

pullXmppElement :: Stream -> IO (Either XmppFailure XmppElement) Source #

Pulls a stanza, nonza or stream error from the stream.

killStream :: Stream -> IO (Either XmppFailure ()) Source #

Close the connection and updates the XmppConMonad Stream state. Does not send the stream end tag.

debugConduit :: (Show o, MonadIO m) => ConduitM o o m b Source #

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

Checks for TLS support and run starttls procedure if applicable

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)

-> ExceptT 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.

nonEmpty :: Text -> Maybe NonemptyText Source #

Check that Text contains at least one non-space character and wrap it

data IQError Source #

The answer to an IQ request that generated an error.

Instances

Instances details
Generic IQError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep IQError :: Type -> Type #

Methods

from :: IQError -> Rep IQError x #

to :: Rep IQError x -> IQError #

Show IQError Source # 
Instance details

Defined in Network.Xmpp.Types

Eq IQError Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: IQError -> IQError -> Bool #

(/=) :: IQError -> IQError -> Bool #

IsErrorStanza IQError Source # 
Instance details

Defined in Network.Xmpp.Lens

IsStanza IQError Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload IQError (Maybe Element) Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep IQError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep IQError = D1 ('MetaData "IQError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "IQError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "iqErrorID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "iqErrorFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "iqErrorTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "iqErrorLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "iqErrorStanzaError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StanzaError)) :*: (S1 ('MetaSel ('Just "iqErrorPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Element)) :*: S1 ('MetaSel ('Just "iqErrorAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

data IQRequest Source #

A "request" Info/Query (IQ) stanza is one with either "get" or "set" as type. It always contains an xml payload.

Instances

Instances details
Generic IQRequest Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep IQRequest :: Type -> Type #

Show IQRequest Source # 
Instance details

Defined in Network.Xmpp.Types

Eq IQRequest Source # 
Instance details

Defined in Network.Xmpp.Types

IsStanza IQRequest Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload IQRequest Element Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep IQRequest Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep IQRequest = D1 ('MetaData "IQRequest" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "IQRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "iqRequestID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "iqRequestFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "iqRequestTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "iqRequestLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "iqRequestType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IQRequestType)) :*: (S1 ('MetaSel ('Just "iqRequestPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element) :*: S1 ('MetaSel ('Just "iqRequestAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

data IQRequestType Source #

The type of IQ request that is made.

Constructors

Get 
Set 

Instances

Instances details
Generic IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep IQRequestType :: Type -> Type #

Read IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

Show IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

Eq IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

Ord IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep IQRequestType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep IQRequestType = D1 ('MetaData "IQRequestType" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "Get" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Set" 'PrefixI 'False) (U1 :: Type -> Type))

data IQResponse Source #

A "response" Info/Query (IQ) stanza is either an IQError, an IQ stanza of type "result" (IQResult)

Instances

Instances details
Show IQResponse Source # 
Instance details

Defined in Network.Xmpp.Types

Eq IQResponse Source # 
Instance details

Defined in Network.Xmpp.Types

data IQResult Source #

The (non-error) answer to an IQ request.

Instances

Instances details
Generic IQResult Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep IQResult :: Type -> Type #

Methods

from :: IQResult -> Rep IQResult x #

to :: Rep IQResult x -> IQResult #

Show IQResult Source # 
Instance details

Defined in Network.Xmpp.Types

Eq IQResult Source # 
Instance details

Defined in Network.Xmpp.Types

IsStanza IQResult Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload IQResult (Maybe Element) Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep IQResult Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep IQResult = D1 ('MetaData "IQResult" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "IQResult" 'PrefixI 'True) ((S1 ('MetaSel ('Just "iqResultID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "iqResultFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "iqResultTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: (S1 ('MetaSel ('Just "iqResultLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: (S1 ('MetaSel ('Just "iqResultPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Element)) :*: S1 ('MetaSel ('Just "iqResultAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

data LangTag Source #

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).

Constructors

LangTag 

Fields

Instances

Instances details
Read LangTag Source # 
Instance details

Defined in Network.Xmpp.Types

Show LangTag Source # 
Instance details

Defined in Network.Xmpp.Types

Eq LangTag Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: LangTag -> LangTag -> Bool #

(/=) :: LangTag -> LangTag -> Bool #

langTagFromText :: Text -> Maybe LangTag Source #

Parses, validates, and possibly constructs a LangTag object.

data Message Source #

The message stanza. Used for push type communication.

Instances

Instances details
Generic Message Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

Show Message Source # 
Instance details

Defined in Network.Xmpp.Types

Default Message Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

def :: Message #

Eq Message Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

IsStanza Message Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload Message [Element] Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep Message Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep Message = D1 ('MetaData "Message" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) ((S1 ('MetaSel ('Just "messageID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "messageFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "messageTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "messageLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "messageType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MessageType)) :*: (S1 ('MetaSel ('Just "messagePayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Element]) :*: S1 ('MetaSel ('Just "messageAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

message :: Message Source #

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.

Instances

Instances details
Generic MessageError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep MessageError :: Type -> Type #

Show MessageError Source # 
Instance details

Defined in Network.Xmpp.Types

Default MessageError Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

def :: MessageError #

Eq MessageError Source # 
Instance details

Defined in Network.Xmpp.Types

IsErrorStanza MessageError Source # 
Instance details

Defined in Network.Xmpp.Lens

IsStanza MessageError Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload MessageError [Element] Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep MessageError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep MessageError = D1 ('MetaData "MessageError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "MessageError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "messageErrorID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "messageErrorFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "messageErrorTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "messageErrorLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "messageErrorStanzaError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StanzaError)) :*: (S1 ('MetaSel ('Just "messageErrorPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Element]) :*: S1 ('MetaSel ('Just "messageErrorAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

data MessageType Source #

Constructors

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 IRC). Typically a receiving client will present a message of type groupchat in an interface that enables many-to-many chat between the parties, including a roster of parties in the chatroom and an appropriate conversation history.

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.

Instances

Instances details
Generic MessageType Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep MessageType :: Type -> Type #

Read MessageType Source # 
Instance details

Defined in Network.Xmpp.Types

Show MessageType Source # 
Instance details

Defined in Network.Xmpp.Types

Eq MessageType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep MessageType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep MessageType = D1 ('MetaData "MessageType" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "Chat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupChat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Headline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type)))

data Presence Source #

The presence stanza. Used for communicating status updates.

Instances

Instances details
Generic Presence Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep Presence :: Type -> Type #

Methods

from :: Presence -> Rep Presence x #

to :: Rep Presence x -> Presence #

Show Presence Source # 
Instance details

Defined in Network.Xmpp.Types

Default Presence Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

def :: Presence #

Eq Presence Source # 
Instance details

Defined in Network.Xmpp.Types

IsStanza Presence Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload Presence [Element] Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep Presence Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep Presence = D1 ('MetaData "Presence" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "Presence" 'PrefixI 'True) ((S1 ('MetaSel ('Just "presenceID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "presenceFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "presenceTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "presenceLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "presenceType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PresenceType)) :*: (S1 ('MetaSel ('Just "presencePayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Element]) :*: S1 ('MetaSel ('Just "presenceAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

presence :: Presence Source #

An empty presence.

data PresenceError Source #

An error stanza generated in response to a Presence.

Instances

Instances details
Generic PresenceError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep PresenceError :: Type -> Type #

Show PresenceError Source # 
Instance details

Defined in Network.Xmpp.Types

Eq PresenceError Source # 
Instance details

Defined in Network.Xmpp.Types

IsErrorStanza PresenceError Source # 
Instance details

Defined in Network.Xmpp.Lens

IsStanza PresenceError Source # 
Instance details

Defined in Network.Xmpp.Lens

HasStanzaPayload PresenceError [Element] Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep PresenceError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep PresenceError = D1 ('MetaData "PresenceError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "PresenceError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "presenceErrorID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "presenceErrorFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)) :*: S1 ('MetaSel ('Just "presenceErrorTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Jid)))) :*: ((S1 ('MetaSel ('Just "presenceErrorLangTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe LangTag)) :*: S1 ('MetaSel ('Just "presenceErrorStanzaError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StanzaError)) :*: (S1 ('MetaSel ('Just "presenceErrorPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Element]) :*: S1 ('MetaSel ('Just "presenceErrorAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ExtendedAttribute])))))

data PresenceType Source #

PresenceType holds Xmpp presence types. The "error" message type is left out as errors are using PresenceError.

Constructors

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 

Instances

Instances details
Generic PresenceType Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep PresenceType :: Type -> Type #

Read PresenceType Source # 
Instance details

Defined in Network.Xmpp.Types

Show PresenceType Source # 
Instance details

Defined in Network.Xmpp.Types

Eq PresenceType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep PresenceType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep PresenceType = D1 ('MetaData "PresenceType" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "Subscribe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Subscribed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unsubscribe" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Unsubscribed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Probe" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Available" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unavailable" 'PrefixI 'False) (U1 :: Type -> Type))))

data SaslError Source #

Constructors

SaslAborted

Client aborted.

SaslAccountDisabled

The account has been temporarily disabled.

SaslCredentialsExpired

The authentication failed because the credentials have expired.

SaslEncryptionRequired

The mechanism requested cannot be used the confidentiality and integrity of the underlying stream is protected (typically with TLS).

SaslIncorrectEncoding

The base64 encoding is incorrect.

SaslInvalidAuthzid

The authzid has an incorrect format or the initiating entity does not have the appropriate permissions to authorize that ID.

SaslInvalidMechanism

The mechanism is not supported by the receiving entity.

SaslMalformedRequest

Invalid syntax.

SaslMechanismTooWeak

The receiving entity policy requires a stronger mechanism.

SaslNotAuthorized

Invalid credentials provided, or some generic authentication failure has occurred.

SaslTemporaryAuthFailure

There receiving entity reported a temporary error condition; the initiating entity is recommended to try again later.

Instances

Instances details
Generic SaslError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep SaslError :: Type -> Type #

Read SaslError Source # 
Instance details

Defined in Network.Xmpp.Types

Show SaslError Source # 
Instance details

Defined in Network.Xmpp.Types

Eq SaslError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep SaslError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep SaslError = D1 ('MetaData "SaslError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (((C1 ('MetaCons "SaslAborted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SaslAccountDisabled" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SaslCredentialsExpired" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SaslEncryptionRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SaslIncorrectEncoding" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SaslInvalidAuthzid" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SaslInvalidMechanism" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SaslMalformedRequest" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SaslMechanismTooWeak" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SaslNotAuthorized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SaslTemporaryAuthFailure" 'PrefixI 'False) (U1 :: Type -> Type)))))

data SaslFailure Source #

Instances

Instances details
Generic SaslFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep SaslFailure :: Type -> Type #

Show SaslFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Eq SaslFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep SaslFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep SaslFailure = D1 ('MetaData "SaslFailure" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "SaslFailure" 'PrefixI 'True) (S1 ('MetaSel ('Just "saslFailureCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SaslError) :*: S1 ('MetaSel ('Just "saslFailureText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Maybe LangTag, Text)))))

data StreamFeatures Source #

Constructors

StreamFeatures 

Fields

data Stanza Source #

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

Instances

Instances details
Generic Stanza Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep Stanza :: Type -> Type #

Methods

from :: Stanza -> Rep Stanza x #

to :: Rep Stanza x -> Stanza #

Show Stanza Source # 
Instance details

Defined in Network.Xmpp.Types

Eq Stanza Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: Stanza -> Stanza -> Bool #

(/=) :: Stanza -> Stanza -> Bool #

IsStanza Stanza Source # 
Instance details

Defined in Network.Xmpp.Lens

type Rep Stanza Source # 
Instance details

Defined in Network.Xmpp.Types

data XmppElement Source #

Instances

Instances details
Show XmppElement Source # 
Instance details

Defined in Network.Xmpp.Types

Eq XmppElement Source # 
Instance details

Defined in Network.Xmpp.Types

messageS :: Stanza Source #

Empty message stanza

messageS = MessageS message

presenceS :: Stanza Source #

Empty presence stanza

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.

Instances

Instances details
Generic StanzaError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep StanzaError :: Type -> Type #

Show StanzaError Source # 
Instance details

Defined in Network.Xmpp.Types

Eq StanzaError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaError = D1 ('MetaData "StanzaError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "StanzaError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stanzaErrorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StanzaErrorType) :*: S1 ('MetaSel ('Just "stanzaErrorCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StanzaErrorCondition)) :*: (S1 ('MetaSel ('Just "stanzaErrorText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Maybe LangTag, NonemptyText))) :*: S1 ('MetaSel ('Just "stanzaErrorApplicationSpecificCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Element)))))

data StanzaErrorCondition Source #

Stanza errors are accommodated with one of the error conditions listed below.

Constructors

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.

Instances

Instances details
Generic StanzaErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep StanzaErrorCondition :: Type -> Type #

Read StanzaErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Show StanzaErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Eq StanzaErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaErrorCondition = D1 ('MetaData "StanzaErrorCondition" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((((C1 ('MetaCons "BadRequest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Conflict" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FeatureNotImplemented" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Forbidden" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gone" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NonemptyText)))))) :+: ((C1 ('MetaCons "InternalServerError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ItemNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JidMalformed" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NotAcceptable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NotAllowed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotAuthorized" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PolicyViolation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecipientUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Redirect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NonemptyText))) :+: (C1 ('MetaCons "RegistrationRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RemoteServerNotFound" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RemoteServerTimeout" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ResourceConstraint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ServiceUnavailable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SubscriptionRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UndefinedCondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnexpectedRequest" 'PrefixI 'False) (U1 :: Type -> Type))))))

data StanzaErrorType Source #

StanzaErrors always have one of these types.

Constructors

Cancel

Error is unrecoverable - do not retry

Continue

Conditition was a warning - proceed

Modify

Change the data and retry

Auth

Provide credentials and retry

Wait

Error is temporary - wait and retry

Instances

Instances details
Generic StanzaErrorType Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep StanzaErrorType :: Type -> Type #

Read StanzaErrorType Source # 
Instance details

Defined in Network.Xmpp.Types

Show StanzaErrorType Source # 
Instance details

Defined in Network.Xmpp.Types

Eq StanzaErrorType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaErrorType Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StanzaErrorType = D1 ('MetaData "StanzaErrorType" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "Cancel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Continue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Modify" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Auth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type))))

data XmppFailure Source #

Signals an XMPP stream error or another unpredicted stream-related situation. This error is fatal, and closes the XMPP stream.

Constructors

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 Session.

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 StreamState was Closed

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 IOException occurred

XmppInvalidXml String

Received data is not valid XML

Instances

Instances details
Exception XmppFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Generic XmppFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep XmppFailure :: Type -> Type #

Show XmppFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Eq XmppFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep XmppFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep XmppFailure = D1 ('MetaData "XmppFailure" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (((C1 ('MetaCons "StreamErrorFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StreamErrorInfo)) :+: (C1 ('MetaCons "StreamEndFailure" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamCloseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ([Element], XmppFailure))))) :+: (C1 ('MetaCons "TcpConnectionFailure" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "XmppIllegalTcpDetails" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TlsError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XmppTlsError))))) :+: ((C1 ('MetaCons "TlsNoServerSupport" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "XmppNoStream" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XmppAuthFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AuthFailure)))) :+: ((C1 ('MetaCons "TlsStreamSecured" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XmppOtherFailure" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "XmppIOException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IOException)) :+: C1 ('MetaCons "XmppInvalidXml" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data XmppTlsError Source #

Instances

Instances details
Generic XmppTlsError Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep XmppTlsError :: Type -> Type #

Show XmppTlsError Source # 
Instance details

Defined in Network.Xmpp.Types

Eq XmppTlsError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep XmppTlsError Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep XmppTlsError = D1 ('MetaData "XmppTlsError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "XmppTlsError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TLSError)) :+: C1 ('MetaCons "XmppTlsException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TLSException)))

data StreamErrorCondition Source #

Constructors

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 to attribute provided in the initial stream header corresponds to an FQDN that is no longer serviced by the receiving entity

StreamHostUnknown

The value of the to attribute provided in the initial stream header does not correspond to an FQDN that is serviced by the receiving entity.

StreamImproperAddressing

A stanza sent between two servers lacks a to or from attribute, the from or to attribute has no value, or the value violates the rules for XMPP addresses

StreamInternalServerError

The server has experienced a misconfiguration or other internal error that prevents it from servicing the stream.

StreamInvalidFrom

The data provided in a from attribute does not match an authorized JID or validated domain as negotiated (1) between two servers using SASL or Server Dialback, or (2) between a client and a server via SASL authentication and resource binding.

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 version attribute provided by the initiating entity in the stream header specifies a version of XMPP that is not supported by the server.

Instances

Instances details
Generic StreamErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep StreamErrorCondition :: Type -> Type #

Read StreamErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Show StreamErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

Eq StreamErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StreamErrorCondition Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StreamErrorCondition = D1 ('MetaData "StreamErrorCondition" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((((C1 ('MetaCons "StreamBadFormat" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamBadNamespacePrefix" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamConflict" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "StreamConnectionTimeout" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamHostGone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamHostUnknown" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "StreamImproperAddressing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamInternalServerError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamInvalidFrom" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "StreamInvalidNamespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamInvalidXml" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamNotAuthorized" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "StreamNotWellFormed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamPolicyViolation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamRemoteConnectionFailed" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "StreamReset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamResourceConstraint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamRestrictedXml" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "StreamSeeOtherHost" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StreamSystemShutdown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamUndefinedCondition" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StreamUnsupportedEncoding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamUnsupportedFeature" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StreamUnsupportedStanzaType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StreamUnsupportedVersion" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Version Source #

XMPP version number. Displayed as "<major>.<minor>". 2.4 is lesser than 2.13, which in turn is lesser than 12.3.

Constructors

Version 

Instances

Instances details
Generic Version Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Read Version Source # 
Instance details

Defined in Network.Xmpp.Types

Show Version Source # 
Instance details

Defined in Network.Xmpp.Types

Eq Version Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

Ord Version Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep Version Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep Version = D1 ('MetaData "Version" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "majorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Just "minorVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer)))

data StreamHandle Source #

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

Constructors

StreamHandle 

Fields

newtype Stream Source #

Constructors

Stream 

data StreamState Source #

Constructors

StreamState 

Fields

data ConnectionState Source #

Signals the state of the stream connection.

Constructors

Closed

Stream has not been established yet

Plain

Stream established, but not secured via TLS

Secured

Stream established and secured via TLS

Finished

Stream was closed

Instances

Instances details
Generic ConnectionState Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep ConnectionState :: Type -> Type #

Show ConnectionState Source # 
Instance details

Defined in Network.Xmpp.Types

Eq ConnectionState Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep ConnectionState Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep ConnectionState = D1 ('MetaData "ConnectionState" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "Closed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Plain" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Secured" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Finished" 'PrefixI 'False) (U1 :: Type -> Type)))

data StreamErrorInfo Source #

Encapsulates information about an XMPP stream error.

Instances

Instances details
Generic StreamErrorInfo Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep StreamErrorInfo :: Type -> Type #

Show StreamErrorInfo Source # 
Instance details

Defined in Network.Xmpp.Types

Eq StreamErrorInfo Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StreamErrorInfo Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep StreamErrorInfo = D1 ('MetaData "StreamErrorInfo" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) (C1 ('MetaCons "StreamErrorInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "errorCondition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StreamErrorCondition) :*: (S1 ('MetaSel ('Just "errorText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Maybe LangTag, NonemptyText))) :*: S1 ('MetaSel ('Just "errorXml") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Element)))))

data ConnectionDetails Source #

Specify the method with which the connection is (re-)established

Constructors

UseRealm

Use realm to resolv host. This is the default.

UseSrv HostName

Use this hostname for a SRV lookup

UseHost HostName PortNumber

Use specified host

UseConnection (ExceptT XmppFailure IO StreamHandle)

Use a 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 connectTls. You can also return an already established connection. This method should also return a hostname that is used for TLS signature verification. If startTLS is not used it can be left empty

data StreamConfiguration Source #

Configuration settings related to the stream.

Constructors

StreamConfiguration 

Fields

Instances

Instances details
Default StreamConfiguration Source # 
Instance details

Defined in Network.Xmpp.Types

xmppDefaultParams :: ClientParams Source #

Default parameters for TLS ciphersuite_all can be used to allow insecure ciphers

xmppDefaultParamsStrong :: ClientParams Source #

Default parameters for TLS restricted to strong ciphers

data Jid Source #

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

Instances

Instances details
Read Jid Source # 
Instance details

Defined in Network.Xmpp.Types

Show Jid Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

showsPrec :: Int -> Jid -> ShowS #

show :: Jid -> String #

showList :: [Jid] -> ShowS #

Eq Jid Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

(==) :: Jid -> Jid -> Bool #

(/=) :: Jid -> Jid -> Bool #

Ord Jid Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

compare :: Jid -> Jid -> Ordering #

(<) :: Jid -> Jid -> Bool #

(<=) :: Jid -> Jid -> Bool #

(>) :: Jid -> Jid -> Bool #

(>=) :: Jid -> Jid -> Bool #

max :: Jid -> Jid -> Jid #

min :: Jid -> Jid -> Jid #

Lift Jid Source # 
Instance details

Defined in Network.Xmpp.Types

Methods

lift :: Quote m => Jid -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Jid -> Code m Jid #

jidQ :: QuasiQuoter Source #

Synonym for jid

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

isBare :: Jid -> Bool Source #

Returns True if the JID is bare, that is, it doesn't have a resource part, and False otherwise.

>>> isBare [jid|foo@bar|]
True
>>> isBare [jid|foo@bar/quux|]
False

isFull :: Jid -> Bool Source #

Returns True if the JID is full, and False otherwise.

isFull = not . isBare
>>> isBare [jid|foo@bar|]
True
>>> isBare [jid|foo@bar/quux|]
False

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")

@ and / can occur in the domain part

>>> jidFromText "foo/bar@quux/foo"
Just parseJid "foo/bar@quux/foo"
  • Counterexamples

A JID must only have one '@':

>>> 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
\j -> jidFromTexts (localpart j) (domainpart j) (resourcepart j) == Just j

(<~) :: Jid -> Jid -> Bool Source #

The partial order of "definiteness". JID1 is less than or equal JID2 iff the domain parts are equal and JID1's local part and resource part each are either Nothing or equal to Jid2's

nodeprepProfile :: StringPrepProfile Source #

The nodeprep StringPrep profile.

resourceprepProfile :: StringPrepProfile Source #

The resourceprep StringPrep profile.

jidToText :: Jid -> Text Source #

Converts a JID to a Text.

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)

toBare :: Jid -> Jid Source #

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.

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.

Instances

Instances details
Generic TlsBehaviour Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep TlsBehaviour :: Type -> Type #

Show TlsBehaviour Source # 
Instance details

Defined in Network.Xmpp.Types

Eq TlsBehaviour Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep TlsBehaviour Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep TlsBehaviour = D1 ('MetaData "TlsBehaviour" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "RequireTls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PreferTls" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PreferPlain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RefuseTls" 'PrefixI 'False) (U1 :: Type -> Type)))

data AuthFailure Source #

Signals a SASL authentication error condition.

Constructors

AuthNoAcceptableMechanism [Text]

No mechanism offered by the server was matched by the provided acceptable mechanisms; wraps the mechanisms offered by the server

AuthStreamFailure XmppFailure 
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

Instances

Instances details
Generic AuthFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Associated Types

type Rep AuthFailure :: Type -> Type #

Show AuthFailure Source # 
Instance details

Defined in Network.Xmpp.Types

Eq AuthFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep AuthFailure Source # 
Instance details

Defined in Network.Xmpp.Types

type Rep AuthFailure = D1 ('MetaData "AuthFailure" "Network.Xmpp.Types" "pontarius-xmpp-0.5.6.8-E7Eo7yzJScdK4Fm8Il5mrG" 'False) ((C1 ('MetaCons "AuthNoAcceptableMechanism" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :+: C1 ('MetaCons "AuthStreamFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XmppFailure))) :+: (C1 ('MetaCons "AuthSaslFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SaslFailure)) :+: (C1 ('MetaCons "AuthIllegalCredentials" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AuthOtherFailure" 'PrefixI 'False) (U1 :: Type -> Type))))

checkHostName :: Text -> Maybe Text Source #

Validates the hostname string in accordance with RFC 1123.

withTMVar :: TMVar a -> (a -> IO (c, a)) -> IO c Source #

Apply f with the content of tv as state, restoring the original value when an exception occurs