Maintainer | info@jonkri.com |
---|---|
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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.
- newtype Stream = Stream {}
- data StreamConfiguration = StreamConfiguration {}
- data StreamState = StreamState {
- streamConnectionState :: !ConnectionState
- streamHandle :: StreamHandle
- streamEventSource :: Source (ErrorT XmppFailure IO) Event
- streamFeatures :: !StreamFeatures
- streamAddress :: !(Maybe Text)
- streamFrom :: !(Maybe Jid)
- streamId :: !(Maybe Text)
- streamLang :: !(Maybe LangTag)
- streamJid :: !(Maybe Jid)
- streamConfiguration :: StreamConfiguration
- data StreamHandle = StreamHandle {
- streamSend :: ByteString -> IO (Either XmppFailure ())
- streamReceive :: Int -> IO (Either XmppFailure ByteString)
- streamFlush :: IO ()
- streamClose :: IO ()
- data StreamFeatures = StreamFeatures {
- streamTls :: !(Maybe Bool)
- streamSaslMechanisms :: ![Text]
- rosterVer :: !(Maybe Bool)
- streamOtherFeatures :: ![Element]
- openStream :: HostName -> StreamConfiguration -> IO (Either XmppFailure Stream)
- withStream :: StateT StreamState IO a -> Stream -> IO a
- tls :: Stream -> IO (Either XmppFailure ())
- data TlsBehaviour
- type SaslHandler = (Text, StateT StreamState IO (Either XmppFailure (Maybe AuthFailure)))
- auth :: [SaslHandler] -> Maybe Text -> Stream -> IO (Either XmppFailure (Maybe AuthFailure))
- data Stanza
- pushStanza :: Stanza -> Stream -> IO (Either XmppFailure ())
- pullStanza :: Stream -> IO (Either XmppFailure Stanza)
- writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ())
- pushIQ :: Text -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Stream -> IO (Either XmppFailure (Either IQError IQResult))
- iqError :: StanzaErrorCondition -> IQRequest -> IQError
- iqResult :: Maybe Element -> IQRequest -> IQResult
- associatedErrorType :: StanzaErrorCondition -> StanzaErrorType
- type Plugin = (Stanza -> IO (Either XmppFailure ())) -> ErrorT XmppFailure IO Plugin'
- data Plugin' = Plugin' {
- inHandler :: Stanza -> [Annotation] -> IO [(Stanza, [Annotation])]
- outHandler :: Stanza -> IO (Either XmppFailure ())
- onSessionUp :: Session -> IO ()
- data Annotation = forall f . (Typeable f, Show f) => Annotation {
- fromAnnotation :: f
- connectTls :: ResolvConf -> ClientParams -> String -> ErrorT XmppFailure IO StreamHandle
Stream
data StreamConfiguration Source
Configuration settings related to the stream.
StreamConfiguration | |
|
data StreamState Source
StreamState | |
|
data StreamHandle Source
Defines operations for sending, receiving, flushing, and closing on a stream.
StreamHandle | |
|
data StreamFeatures Source
StreamFeatures | |
|
openStream :: HostName -> StreamConfiguration -> IO (Either XmppFailure Stream) Source
Connects to the XMPP server and opens the XMPP stream against the given realm.
withStream :: StateT StreamState IO a -> Stream -> IO a Source
TLS
tls :: Stream -> IO (Either XmppFailure ()) Source
Checks for TLS support and run starttls procedure if applicable
data TlsBehaviour Source
How the client should behave in regards to TLS.
RequireTls | Require the use of TLS; disconnect if it's not offered. |
PreferTls | Negotitate TLS if it's available. |
PreferPlain | Negotitate TLS only if the server requires it |
RefuseTls | Never secure the stream with TLS. |
Auth
type SaslHandler = (Text, StateT StreamState IO (Either XmppFailure (Maybe AuthFailure))) Source
Tuple defining the SASL Handler's name, and a SASL mechanism computation.
The SASL mechanism is a stateful Stream
computation, which has the
possibility of resulting in an authentication error.
auth :: [SaslHandler] -> Maybe Text -> Stream -> IO (Either XmppFailure (Maybe AuthFailure)) Source
Authenticate to the server using the first matching method and bind a resource.
Stanzas
The Xmpp communication primities (Message, Presence and Info/Query) are called stanzas.
pushStanza :: Stanza -> Stream -> IO (Either XmppFailure ()) Source
Encode and send stanza
pullStanza :: Stream -> IO (Either XmppFailure Stanza) Source
Pulls a stanza (or stream error) from the stream.
writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ()) Source
IQ
pushIQ :: Text -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Stream -> IO (Either XmppFailure (Either IQError IQResult)) Source
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
associatedErrorType :: StanzaErrorCondition -> StanzaErrorType Source
The RECOMMENDED error type associated with an error condition. The following conditions allow for multiple types
FeatureNotImplemented
:Cancel
orModify
(returnsCancel
)PolicyViolation
:Modify
orWait
(Modify
)RemoteServerTimeout
:Wait
or unspecified other (Wait
)UndefinedCondition
: Any condition (Cancel
)
Plugins
= (Stanza -> IO (Either XmppFailure ())) | pass stanza to next plugin |
-> ErrorT XmppFailure IO Plugin' |
Plugin' | |
|
data Annotation Source
Annotations are auxiliary data attached to received stanzas by Plugin
s to
convey information regarding their operation. For example, a plugin for
encryption might attach information about whether a received stanza was
encrypted and which algorithm was used.
forall f . (Typeable f, Show f) => Annotation | |
|
:: ResolvConf | Resolv conf to use (try |
-> ClientParams | TLS parameters to use when securing the connection |
-> String | Host to use when connecting (will be resolved using SRV records) |
-> ErrorT XmppFailure IO StreamHandle |
Connect to an XMPP server and secure the connection with TLS before starting the XMPP streams
NB RFC 6120 does not specify this method, but some servers, notably GCS, seem to use it.