network-protocol-xmpp-0.4.9: Client library for the XMPP protocol.

Safe HaskellNone
LanguageHaskell2010

Network.Protocol.XMPP

Contents

Synopsis

JIDs

data JID Source #

Constructors

JID 

Fields

Instances
Eq JID Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

(==) :: JID -> JID -> Bool

(/=) :: JID -> JID -> Bool

Show JID Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

showsPrec :: Int -> JID -> ShowS

show :: JID -> String

showList :: [JID] -> ShowS

IsString JID Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

fromString :: String -> JID

data Node Source #

Instances
Eq Node Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

(==) :: Node -> Node -> Bool

(/=) :: Node -> Node -> Bool

Show Node Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

showsPrec :: Int -> Node -> ShowS

show :: Node -> String

showList :: [Node] -> ShowS

data Domain Source #

Instances
Eq Domain Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

(==) :: Domain -> Domain -> Bool

(/=) :: Domain -> Domain -> Bool

Show Domain Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

showsPrec :: Int -> Domain -> ShowS

show :: Domain -> String

showList :: [Domain] -> ShowS

data Resource Source #

Instances
Eq Resource Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

(==) :: Resource -> Resource -> Bool

(/=) :: Resource -> Resource -> Bool

Show Resource Source # 
Instance details

Defined in Network.Protocol.XMPP.JID

Methods

showsPrec :: Int -> Resource -> ShowS

show :: Resource -> String

showList :: [Resource] -> ShowS

strNode :: Node -> Text Source #

parseJID :: Text -> Maybe JID Source #

formatJID :: JID -> Text Source #

Stanzas

class Stanza a where Source #

Methods

stanzaTo :: a -> Maybe JID Source #

stanzaFrom :: a -> Maybe JID Source #

stanzaID :: a -> Maybe Text Source #

stanzaLang :: a -> Maybe Text Source #

stanzaPayloads :: a -> [Element] Source #

Instances
Stanza IQ Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: IQ -> Maybe JID Source #

stanzaFrom :: IQ -> Maybe JID Source #

stanzaID :: IQ -> Maybe Text Source #

stanzaLang :: IQ -> Maybe Text Source #

stanzaPayloads :: IQ -> [Element] Source #

stanzaToElement :: IQ -> Element Source #

Stanza Presence Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: Presence -> Maybe JID Source #

stanzaFrom :: Presence -> Maybe JID Source #

stanzaID :: Presence -> Maybe Text Source #

stanzaLang :: Presence -> Maybe Text Source #

stanzaPayloads :: Presence -> [Element] Source #

stanzaToElement :: Presence -> Element Source #

Stanza Message Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: Message -> Maybe JID Source #

stanzaFrom :: Message -> Maybe JID Source #

stanzaID :: Message -> Maybe Text Source #

stanzaLang :: Message -> Maybe Text Source #

stanzaPayloads :: Message -> [Element] Source #

stanzaToElement :: Message -> Element Source #

data ReceivedStanza Source #

Instances
Show ReceivedStanza Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> ReceivedStanza -> ShowS

show :: ReceivedStanza -> String

showList :: [ReceivedStanza] -> ShowS

data Message Source #

Constructors

Message 

Fields

Instances
Show Message Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> Message -> ShowS

show :: Message -> String

showList :: [Message] -> ShowS

Stanza Message Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: Message -> Maybe JID Source #

stanzaFrom :: Message -> Maybe JID Source #

stanzaID :: Message -> Maybe Text Source #

stanzaLang :: Message -> Maybe Text Source #

stanzaPayloads :: Message -> [Element] Source #

stanzaToElement :: Message -> Element Source #

data Presence Source #

Constructors

Presence 

Fields

Instances
Show Presence Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> Presence -> ShowS

show :: Presence -> String

showList :: [Presence] -> ShowS

Stanza Presence Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: Presence -> Maybe JID Source #

stanzaFrom :: Presence -> Maybe JID Source #

stanzaID :: Presence -> Maybe Text Source #

stanzaLang :: Presence -> Maybe Text Source #

stanzaPayloads :: Presence -> [Element] Source #

stanzaToElement :: Presence -> Element Source #

data IQ Source #

Constructors

IQ 

Fields

Instances
Show IQ Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> IQ -> ShowS

show :: IQ -> String

showList :: [IQ] -> ShowS

Stanza IQ Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

stanzaTo :: IQ -> Maybe JID Source #

stanzaFrom :: IQ -> Maybe JID Source #

stanzaID :: IQ -> Maybe Text Source #

stanzaLang :: IQ -> Maybe Text Source #

stanzaPayloads :: IQ -> [Element] Source #

stanzaToElement :: IQ -> Element Source #

data MessageType Source #

Instances
Eq MessageType Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

(==) :: MessageType -> MessageType -> Bool

(/=) :: MessageType -> MessageType -> Bool

Show MessageType Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> MessageType -> ShowS

show :: MessageType -> String

showList :: [MessageType] -> ShowS

data IQType Source #

Constructors

IQGet 
IQSet 
IQResult 
IQError 
Instances
Eq IQType Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

(==) :: IQType -> IQType -> Bool

(/=) :: IQType -> IQType -> Bool

Show IQType Source # 
Instance details

Defined in Network.Protocol.XMPP.Stanza

Methods

showsPrec :: Int -> IQType -> ShowS

show :: IQType -> String

showList :: [IQType] -> ShowS

The XMPP monad

data XMPP a Source #

Instances
Monad XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

(>>=) :: XMPP a -> (a -> XMPP b) -> XMPP b

(>>) :: XMPP a -> XMPP b -> XMPP b

return :: a -> XMPP a

fail :: String -> XMPP a

Functor XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

fmap :: (a -> b) -> XMPP a -> XMPP b

(<$) :: a -> XMPP b -> XMPP a

MonadFix XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

mfix :: (a -> XMPP a) -> XMPP a

Applicative XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

pure :: a -> XMPP a

(<*>) :: XMPP (a -> b) -> XMPP a -> XMPP b

liftA2 :: (a -> b -> c) -> XMPP a -> XMPP b -> XMPP c

(*>) :: XMPP a -> XMPP b -> XMPP b

(<*) :: XMPP a -> XMPP b -> XMPP a

MonadIO XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

liftIO :: IO a -> XMPP a

MonadError XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Associated Types

type ErrorType XMPP :: *

Methods

throwError :: ErrorType XMPP -> XMPP a

catchError :: XMPP a -> (ErrorType XMPP -> XMPP a) -> XMPP a

type ErrorType XMPP Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

type ErrorType XMPP = Error

data Server Source #

Constructors

Server 

Fields

data Error Source #

Constructors

AuthenticationFailure Element

The remote host refused the specified authentication credentials.

The included XML element is the error value that the server provided. It may contain additional information about why authentication failed.

AuthenticationError Text

There was an error while authenticating with the remote host.

InvalidStanza Element

An unrecognized or malformed Stanza was received from the remote host.

InvalidBindResult ReceivedStanza

The remote host sent an invalid reply to a resource bind request.

TransportError Text

There was an error with the underlying transport.

NoComponentStreamID

The remote host did not send a stream ID when accepting a component connection.

Instances
Show Error Source # 
Instance details

Defined in Network.Protocol.XMPP.Monad

Methods

showsPrec :: Int -> Error -> ShowS

show :: Error -> String

showList :: [Error] -> ShowS

runClient Source #

Arguments

:: Server 
-> JID

Client JID

-> Text

Username

-> Text

Password

-> XMPP a 
-> IO (Either Error a) 

runComponent Source #

Arguments

:: Server 
-> Text

Server secret

-> XMPP a 
-> IO (Either Error a) 

putStanza :: Stanza a => a -> XMPP () Source #

bindJID :: JID -> XMPP JID Source #

Send a <bind> message for the given JID, returning the server's reply. In most cases the reply will be the same as the input. However, if the input has no Resource, the returned JID will contain a generated Resource.

Clients must bind a JID before sending any Stanzas.

Resuming sessions

runXMPP :: Session -> XMPP a -> IO (Either Error a) Source #