Stability | unstable |
---|---|
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- withConnection :: (Stream -> IO (b, Stream)) -> Session -> IO (Either XmppFailure b)
- modifyHandlers :: (EventHandlers -> EventHandlers) -> Session -> IO ()
- setConnectionClosedHandler :: (XmppFailure -> Session -> IO ()) -> Session -> IO ()
- runConnectionClosedHandler :: Session -> XmppFailure -> IO ()
- runHandler :: (EventHandlers -> IO a) -> Session -> IO a
- endSession :: Session -> IO ()
- closeConnection :: Session -> IO ()
- readWorker :: (XmppElement -> IO ()) -> (XmppFailure -> IO ()) -> TMVar Stream -> IO a
- startThreadsWith :: TMVar (ByteString -> IO (Either XmppFailure ())) -> (XmppElement -> IO ()) -> TMVar EventHandlers -> Stream -> Maybe Int -> IO (Either XmppFailure (IO (), TMVar Stream, ThreadId))
- connPersist :: Maybe Int -> TMVar (ByteString -> IO a) -> IO ()
- semWrite :: WriteSemaphore -> ByteString -> IO (Either XmppFailure ())
- writeXmppElem :: WriteSemaphore -> XmppElement -> IO (Either XmppFailure ())
- writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ())
- sendRawStanza :: Stanza -> Session -> IO (Either XmppFailure ())
- sendStanza :: Stanza -> Session -> IO (Either XmppFailure ())
- getStanzaChan :: Session -> TChan (Stanza, [Annotation])
- getStanza :: Session -> IO (Stanza, [Annotation])
- dupSession :: Session -> IO Session
- getJid :: Session -> IO (Maybe Jid)
- getFeatures :: Session -> IO StreamFeatures
- waitForStream :: Session -> IO ()
- streamState :: Session -> STM ConnectionState
- type StanzaHandler = (XmppElement -> IO (Either XmppFailure ())) -> XmppElement -> [Annotation] -> IO [(XmppElement, [Annotation])]
- type Resource = Text
- type AuthData = Maybe (ConnectionState -> [SaslHandler], Maybe Resource)
- data Annotation = forall f.(Typeable f, Show f) => Annotation {
- fromAnnotation :: f
- type Annotated a = (a, [Annotation])
- getAnnotation :: Typeable b => Annotated a -> Maybe b
- data Plugin' = Plugin' {
- inHandler :: XmppElement -> [Annotation] -> IO [(XmppElement, [Annotation])]
- outHandler :: XmppElement -> IO (Either XmppFailure ())
- onSessionUp :: Session -> IO ()
- type Plugin = (XmppElement -> IO (Either XmppFailure ())) -> ExceptT XmppFailure IO Plugin'
- type RosterPushCallback = Roster -> RosterUpdate -> IO ()
- data SessionConfiguration = SessionConfiguration {
- sessionStreamConfiguration :: StreamConfiguration
- onConnectionClosed :: Session -> XmppFailure -> IO ()
- sessionStanzaIDs :: IO (IO Text)
- plugins :: [Plugin]
- enableRoster :: Bool
- initialRoster :: IO (Maybe Roster)
- onRosterPush :: Maybe RosterPushCallback
- enablePresenceTracking :: Bool
- onPresenceChange :: Maybe (Jid -> PeerStatus -> PeerStatus -> IO ())
- keepAlive :: Maybe Int
- data EventHandlers = EventHandlers {
- connectionClosedHandler :: XmppFailure -> IO ()
- data Interrupt = Interrupt (TMVar ())
- type WriteSemaphore = TMVar (ByteString -> IO (Either XmppFailure ()))
- data Session = Session {
- stanzaCh :: TChan (Stanza, [Annotation])
- iqHandlers :: TVar IQHandlers
- writeSemaphore :: WriteSemaphore
- readerThread :: ThreadId
- idGenerator :: IO Text
- streamRef :: TMVar Stream
- eventHandlers :: TMVar EventHandlers
- stopThreads :: IO ()
- rosterRef :: TVar Roster
- presenceRef :: TVar Peers
- conf :: SessionConfiguration
- sendStanza' :: Stanza -> IO (Either XmppFailure ())
- sRealm :: HostName
- sSaslCredentials :: Maybe (ConnectionState -> [SaslHandler], Maybe Text)
- reconnectWait :: TVar Int
- type IQHandlers = (Map (IQRequestType, Text) (TChan IQRequestTicket), Map Text (Either (Maybe Jid) Jid, TMVar (Maybe (Annotated IQResponse))))
- data IQRequestTicket = IQRequestTicket {
- answerTicket :: Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> IO (Maybe (Either XmppFailure ()))
- iqRequestBody :: IQRequest
- iqRequestAnnotations :: [Annotation]
- data IQSendError
- pullMessageA :: Session -> IO (Either (Annotated MessageError) (Annotated Message))
- pullMessage :: Session -> IO (Either MessageError Message)
- getMessageA :: Session -> IO (Annotated Message)
- getMessage :: Session -> IO Message
- waitForMessageA :: (Annotated Message -> Bool) -> Session -> IO (Annotated Message)
- waitForMessage :: (Message -> Bool) -> Session -> IO Message
- waitForMessageErrorA :: (Annotated MessageError -> Bool) -> Session -> IO (Annotated MessageError)
- waitForMessageError :: (MessageError -> Bool) -> Session -> IO MessageError
- filterMessagesA :: (Annotated MessageError -> Bool) -> (Annotated Message -> Bool) -> Session -> IO (Either (Annotated MessageError) (Annotated Message))
- filterMessages :: (MessageError -> Bool) -> (Message -> Bool) -> Session -> IO (Either MessageError Message)
- sendMessage :: Message -> Session -> IO (Either XmppFailure ())
- pullPresenceA :: Session -> IO (Either (Annotated PresenceError) (Annotated Presence))
- pullPresence :: Session -> IO (Either PresenceError Presence)
- waitForPresenceA :: (Annotated Presence -> Bool) -> Session -> IO (Annotated Presence)
- waitForPresence :: (Presence -> Bool) -> Session -> IO Presence
- sendPresence :: Presence -> Session -> IO (Either XmppFailure ())
- sendIQ :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either XmppFailure (STM (Maybe (Annotated IQResponse))))
- sendIQA' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError (Annotated IQResponse))
- sendIQ' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError IQResponse)
- listenIQ :: IQRequestType -> Text -> Session -> IO (Either (STM IQRequestTicket) (STM IQRequestTicket))
- unlistenIQ :: IQRequestType -> Text -> Session -> IO ()
- answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> IO (Maybe (Either XmppFailure ()))
- class IQRequestClass a where
- data IQResponseType a
- pickleRequest :: PU Element a
- pickleResponse :: PU [Element] (IQResponseType a)
- requestType :: a -> IQRequestType
- requestNamespace :: a -> Text
- data IQRequestError
- sendIQRequest :: (IQRequestClass a, MonadError IQRequestError m, MonadIO m) => Maybe Integer -> Maybe Jid -> a -> Session -> m (Either IQError (IQResponseType a))
- type IQRequestHandler a = a -> IO (Either StanzaError (IQResponseType a))
- runIQHandler :: IQRequestClass a => IQRequestHandler a -> Session -> IO ()
- newSession :: Stream -> SessionConfiguration -> HostName -> Maybe (ConnectionState -> [SaslHandler], Maybe Text) -> IO (Either XmppFailure Session)
- session :: HostName -> AuthData -> SessionConfiguration -> IO (Either XmppFailure Session)
- newStanzaID :: Session -> IO Text
- reconnect :: Integer -> Session -> IO (Bool, [XmppFailure])
- reconnect' :: Session -> IO Integer
- reconnectNow :: Session -> IO (Maybe XmppFailure)
- simpleAuth :: Username -> Password -> AuthData
- semWrite :: WriteSemaphore -> ByteString -> IO (Either XmppFailure ())
- writeXmppElem :: WriteSemaphore -> XmppElement -> IO (Either XmppFailure ())
- writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ())
- sendRawStanza :: Stanza -> Session -> IO (Either XmppFailure ())
- sendStanza :: Stanza -> Session -> IO (Either XmppFailure ())
- getStanzaChan :: Session -> TChan (Stanza, [Annotation])
- getStanza :: Session -> IO (Stanza, [Annotation])
- dupSession :: Session -> IO Session
- getJid :: Session -> IO (Maybe Jid)
- getFeatures :: Session -> IO StreamFeatures
- waitForStream :: Session -> IO ()
- streamState :: Session -> STM ConnectionState
- sendIQ :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either XmppFailure (STM (Maybe (Annotated IQResponse))))
- sendIQA' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError (Annotated IQResponse))
- sendIQ' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError IQResponse)
- listenIQ :: IQRequestType -> Text -> Session -> IO (Either (STM IQRequestTicket) (STM IQRequestTicket))
- unlistenIQ :: IQRequestType -> Text -> Session -> IO ()
- answerIQ :: IQRequestTicket -> Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> IO (Maybe (Either XmppFailure ()))
- class IQRequestClass a where
- data IQResponseType a
- pickleRequest :: PU Element a
- pickleResponse :: PU [Element] (IQResponseType a)
- requestType :: a -> IQRequestType
- requestNamespace :: a -> Text
- data IQRequestError
- sendIQRequest :: (IQRequestClass a, MonadError IQRequestError m, MonadIO m) => Maybe Integer -> Maybe Jid -> a -> Session -> m (Either IQError (IQResponseType a))
- type IQRequestHandler a = a -> IO (Either StanzaError (IQResponseType a))
- runIQHandler :: IQRequestClass a => IQRequestHandler a -> Session -> IO ()
- pullMessageA :: Session -> IO (Either (Annotated MessageError) (Annotated Message))
- pullMessage :: Session -> IO (Either MessageError Message)
- getMessageA :: Session -> IO (Annotated Message)
- getMessage :: Session -> IO Message
- waitForMessageA :: (Annotated Message -> Bool) -> Session -> IO (Annotated Message)
- waitForMessage :: (Message -> Bool) -> Session -> IO Message
- waitForMessageErrorA :: (Annotated MessageError -> Bool) -> Session -> IO (Annotated MessageError)
- waitForMessageError :: (MessageError -> Bool) -> Session -> IO MessageError
- filterMessagesA :: (Annotated MessageError -> Bool) -> (Annotated Message -> Bool) -> Session -> IO (Either (Annotated MessageError) (Annotated Message))
- filterMessages :: (MessageError -> Bool) -> (Message -> Bool) -> Session -> IO (Either MessageError Message)
- sendMessage :: Message -> Session -> IO (Either XmppFailure ())
- withConnection :: (Stream -> IO (b, Stream)) -> Session -> IO (Either XmppFailure b)
- modifyHandlers :: (EventHandlers -> EventHandlers) -> Session -> IO ()
- setConnectionClosedHandler :: (XmppFailure -> Session -> IO ()) -> Session -> IO ()
- runConnectionClosedHandler :: Session -> XmppFailure -> IO ()
- runHandler :: (EventHandlers -> IO a) -> Session -> IO a
- endSession :: Session -> IO ()
- closeConnection :: Session -> IO ()
- pullPresenceA :: Session -> IO (Either (Annotated PresenceError) (Annotated Presence))
- pullPresence :: Session -> IO (Either PresenceError Presence)
- waitForPresenceA :: (Annotated Presence -> Bool) -> Session -> IO (Annotated Presence)
- waitForPresence :: (Presence -> Bool) -> Session -> IO Presence
- sendPresence :: Presence -> Session -> IO (Either XmppFailure ())
- readWorker :: (XmppElement -> IO ()) -> (XmppFailure -> IO ()) -> TMVar Stream -> IO a
- startThreadsWith :: TMVar (ByteString -> IO (Either XmppFailure ())) -> (XmppElement -> IO ()) -> TMVar EventHandlers -> Stream -> Maybe Int -> IO (Either XmppFailure (IO (), TMVar Stream, ThreadId))
- connPersist :: Maybe Int -> TMVar (ByteString -> IO a) -> IO ()
- type StanzaHandler = (XmppElement -> IO (Either XmppFailure ())) -> XmppElement -> [Annotation] -> IO [(XmppElement, [Annotation])]
- type Resource = Text
- type AuthData = Maybe (ConnectionState -> [SaslHandler], Maybe Resource)
- data Annotation = forall f.(Typeable f, Show f) => Annotation {
- fromAnnotation :: f
- type Annotated a = (a, [Annotation])
- getAnnotation :: Typeable b => Annotated a -> Maybe b
- data Plugin' = Plugin' {
- inHandler :: XmppElement -> [Annotation] -> IO [(XmppElement, [Annotation])]
- outHandler :: XmppElement -> IO (Either XmppFailure ())
- onSessionUp :: Session -> IO ()
- type Plugin = (XmppElement -> IO (Either XmppFailure ())) -> ExceptT XmppFailure IO Plugin'
- type RosterPushCallback = Roster -> RosterUpdate -> IO ()
- data SessionConfiguration = SessionConfiguration {
- sessionStreamConfiguration :: StreamConfiguration
- onConnectionClosed :: Session -> XmppFailure -> IO ()
- sessionStanzaIDs :: IO (IO Text)
- plugins :: [Plugin]
- enableRoster :: Bool
- initialRoster :: IO (Maybe Roster)
- onRosterPush :: Maybe RosterPushCallback
- enablePresenceTracking :: Bool
- onPresenceChange :: Maybe (Jid -> PeerStatus -> PeerStatus -> IO ())
- keepAlive :: Maybe Int
- data EventHandlers = EventHandlers {
- connectionClosedHandler :: XmppFailure -> IO ()
- data Interrupt = Interrupt (TMVar ())
- type WriteSemaphore = TMVar (ByteString -> IO (Either XmppFailure ()))
- data Session = Session {
- stanzaCh :: TChan (Stanza, [Annotation])
- iqHandlers :: TVar IQHandlers
- writeSemaphore :: WriteSemaphore
- readerThread :: ThreadId
- idGenerator :: IO Text
- streamRef :: TMVar Stream
- eventHandlers :: TMVar EventHandlers
- stopThreads :: IO ()
- rosterRef :: TVar Roster
- presenceRef :: TVar Peers
- conf :: SessionConfiguration
- sendStanza' :: Stanza -> IO (Either XmppFailure ())
- sRealm :: HostName
- sSaslCredentials :: Maybe (ConnectionState -> [SaslHandler], Maybe Text)
- reconnectWait :: TVar Int
- type IQHandlers = (Map (IQRequestType, Text) (TChan IQRequestTicket), Map Text (Either (Maybe Jid) Jid, TMVar (Maybe (Annotated IQResponse))))
- data IQRequestTicket = IQRequestTicket {
- answerTicket :: Either StanzaError (Maybe Element) -> [ExtendedAttribute] -> IO (Maybe (Either XmppFailure ()))
- iqRequestBody :: IQRequest
- iqRequestAnnotations :: [Annotation]
- data IQSendError
- data MessageBody = MessageBody {
- bodyLang :: Maybe LangTag
- bodyContent :: Text
- data MessageThread = MessageThread {
- threadID :: Text
- threadParent :: Maybe Text
- data MessageSubject = MessageSubject {}
- data InstantMessage = InstantMessage {
- imThread :: Maybe MessageThread
- imSubject :: [MessageSubject]
- imBody :: [MessageBody]
- instantMessage :: InstantMessage
- getIM :: Message -> Maybe InstantMessage
- sanitizeIM :: InstantMessage -> InstantMessage
- withIM :: Message -> InstantMessage -> Message
- imToElements :: InstantMessage -> [Element]
- simpleIM :: Jid -> Text -> Message
- answerIM :: [MessageBody] -> Message -> Maybe Message
- xpIM :: PU [Element] InstantMessage
- xpMessageSubject :: PU [Element] [MessageSubject]
- xpMessageBody :: PU [Element] [MessageBody]
- xpMessageThread :: PU [Element] (Maybe MessageThread)
- data ShowStatus
- data IMPresence = IMP {
- showStatus :: Maybe ShowStatus
- status :: Maybe Text
- priority :: Maybe Int
- imPresence :: IMPresence
- getIMPresence :: Presence -> Maybe IMPresence
- withIMPresence :: IMPresence -> Presence -> Presence
- xpIMPresence :: PU [Element] IMPresence
- xpShow :: PU Text ShowStatus
- timeout :: Maybe Integer
- rosterSet :: Jid -> Maybe Text -> [Text] -> Session -> IO (Either IQSendError (Annotated IQResponse))
- rosterAdd :: Jid -> Maybe Text -> [Text] -> Session -> IO (Either IQSendError (Annotated IQResponse))
- rosterRemove :: Jid -> Session -> IO Bool
- getRosterSTM :: Session -> STM Roster
- getRoster :: Session -> IO Roster
- initRoster :: Session -> IO ()
- handleRoster :: Maybe Jid -> TVar Roster -> RosterPushCallback -> StanzaHandler
- retrieveRoster :: Maybe Roster -> Session -> IO (Maybe Roster)
- toItem :: QueryItem -> Item
- fromItem :: Item -> QueryItem
- xpItems :: PU [Node] [QueryItem]
- xpQuery :: PU [Node] Query
- xpSubscription :: PU Text Subscription
- data Subscription
- data Roster = Roster {}
- data Item = Item {
- riApproved :: Bool
- riAsk :: Bool
- riJid :: Jid
- riName :: Maybe Text
- riSubscription :: Subscription
- riGroups :: [Text]
- data RosterUpdate
- data QueryItem = QueryItem {
- qiApproved :: Maybe Bool
- qiAsk :: Bool
- qiJid :: Jid
- qiName :: Maybe Text
- qiSubscription :: Maybe Subscription
- qiGroups :: [Text]
- data Query = Query {
- queryVer :: Maybe Text
- queryItems :: [QueryItem]
- xpNonemptyText :: PU Text NonemptyText
- xpStreamElement :: PU [Node] (Either StreamErrorInfo XmppElement)
- xpStreamStanza :: PU [Node] (Either StreamErrorInfo Stanza)
- xpExtendedAttrs :: PU [Attribute] [ExtendedAttribute]
- xpStanza :: PU [Node] Stanza
- xpMessage :: PU [Node] Message
- xpPresence :: PU [Node] Presence
- xpIQRequest :: PU [Node] IQRequest
- xpIQResult :: PU [Node] IQResult
- xpStanzaErrorCondition :: PU [Node] StanzaErrorCondition
- xpStanzaError :: PU [Node] StanzaError
- xpMessageError :: PU [Node] MessageError
- xpPresenceError :: PU [Node] PresenceError
- xpIQError :: PU [Node] IQError
- xpStreamError :: PU [Node] StreamErrorInfo
- xpLangTag :: PU [Attribute] (Maybe LangTag)
- xpLang :: PU Text LangTag
- xmlLang :: Name
- pickleElem :: PU [Node] a -> a -> Element
- unpickleElem :: PU [Node] a -> Element -> Either UnpickleError a
- xpNodeElem :: PU [Node] a -> PU Element a
- mbl :: Maybe [a] -> [a]
- lmb :: [t] -> Maybe [t]
- xpStream :: PU [Node] (Text, Maybe Jid, Maybe Jid, Maybe Text, Maybe LangTag)
- xpStreamFeatures :: PU [Node] StreamFeatures
- xpJid :: PU Text Jid
- xpIQRequestType :: PU Text IQRequestType
- xpMessageType :: PU Text MessageType
- xpPresenceType :: PU Text PresenceType
- xpStanzaErrorType :: PU Text StanzaErrorType
- xpStreamErrorCondition :: PU Text StreamErrorCondition
- xmppSasl :: [SaslHandler] -> Stream -> IO (Either XmppFailure (Maybe AuthFailure))
- digestMd5 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- scramSha1 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- plain :: Username -> Maybe AuthZID -> Password -> SaslHandler
- auth :: [SaslHandler] -> Maybe Text -> Stream -> IO (Either XmppFailure (Maybe AuthFailure))
- makeNonce :: IO ByteString
- saslInitE :: Text -> Maybe Text -> Element
- saslResponseE :: Maybe Text -> Element
- xpSuccess :: PU [Node] (Maybe Text)
- pairs :: ByteString -> Either String Pairs
- xpFailure :: PU [Node] SaslFailure
- xpSaslError :: PU Text SaslError
- xpChallenge :: PU [Node] (Maybe Text)
- xpSaslElement :: PU [Node] SaslElement
- quote :: ByteString -> ByteString
- saslInit :: Text -> Maybe ByteString -> ExceptT AuthFailure (StateT StreamState IO) ()
- pullSaslElement :: ExceptT AuthFailure (StateT StreamState IO) SaslElement
- pullChallenge :: ExceptT AuthFailure (StateT StreamState IO) (Maybe ByteString)
- saslFromJust :: Maybe a -> ExceptT AuthFailure (StateT StreamState IO) a
- pullSuccess :: ExceptT AuthFailure (StateT StreamState IO) (Maybe Text)
- pullFinalMessage :: ExceptT AuthFailure (StateT StreamState IO) (Maybe ByteString)
- toPairs :: ByteString -> ExceptT AuthFailure (StateT StreamState IO) Pairs
- respond :: Maybe ByteString -> ExceptT AuthFailure (StateT StreamState IO) ()
- prepCredentials :: Text -> Maybe Text -> Text -> ExceptT AuthFailure (StateT StreamState IO) (Text, Maybe Text, Text)
- xorBS :: ByteString -> ByteString -> ByteString
- merge :: [ByteString] -> ByteString
- (+++) :: ByteString -> ByteString -> ByteString
- digestMd5 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- scramSha1 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- plain :: Username -> Maybe AuthZID -> Password -> SaslHandler
- digestMd5 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- plain :: Username -> Maybe AuthZID -> Password -> SaslHandler
- hashToken :: Hash ctx hash => hash
- scram :: Hash ctx hash => hash -> Text -> Maybe Text -> Text -> ExceptT AuthFailure (StateT StreamState IO) ()
- scramSha1 :: Username -> Maybe AuthZID -> Password -> SaslHandler
- nonAsciiSpaces :: Set Char
- toSpace :: Char -> Text
- saslPrepQuery :: StringPrepProfile
- saslPrepStore :: StringPrepProfile
- normalizePassword :: Text -> Maybe Text
- normalizeUsername :: Text -> Maybe Text
- type Username = Text
- type Password = Text
- type AuthZID = Text
- data SaslElement
- = SaslSuccess (Maybe Text)
- | SaslChallenge (Maybe Text)
- type Pairs = [(ByteString, ByteString)]
- type SaslHandler = (Text, StateT StreamState IO (Either XmppFailure (Maybe AuthFailure)))
- presenceSubscribe :: Jid -> Presence
- presenceSubscribed :: Jid -> Presence
- presenceUnsubscribe :: Jid -> Presence
- presenceUnsubscribed :: Jid -> Presence
- presenceOnline :: Presence
- presenceOffline :: Presence
- answerMessage :: Message -> [Element] -> Maybe Message
- presTo :: Presence -> Jid -> Presence
- mkStanzaError :: StanzaErrorCondition -> StanzaError
- iqError :: StanzaErrorCondition -> IQRequest -> IQError
- iqResult :: Maybe Element -> IQRequest -> IQResult
- associatedErrorType :: StanzaErrorCondition -> StanzaErrorType
- type StreamSink a = ConduitM Event Void (ExceptT XmppFailure IO) a
- tryIOError :: IO a -> IO (Either IOError a)
- connect :: HostName -> StreamConfiguration -> ExceptT XmppFailure IO (Maybe StreamHandle)
- elements :: MonadError XmppFailure m => ConduitT Event Element m ()
- readMaybe_ :: Read a => String -> Maybe a
- streamUnpickleElem :: PU [Node] a -> Element -> StreamSink a
- throwOutJunk :: Monad m => ConduitM Event a m ()
- openElementFromEvents :: StreamSink Element
- startStream :: StateT StreamState IO (Either XmppFailure ())
- pushXmlDecl :: StateT StreamState IO (Either XmppFailure ())
- pushOpenElement :: Element -> StateT StreamState IO (Either XmppFailure ())
- runEventsSink :: ConduitT Event Void (ExceptT XmppFailure IO) b -> StateT StreamState IO (Either XmppFailure b)
- streamS :: Maybe Jid -> StreamSink (Either Element (Text, Maybe Jid, Maybe Jid, Maybe Text, Maybe LangTag, StreamFeatures))
- flattenAttrs :: [(Name, [Content])] -> [(Name, Text)]
- pushElement :: Element -> StateT StreamState IO (Either XmppFailure ())
- closeStreams' :: StateT StreamState IO ()
- restartStream :: StateT StreamState IO (Either XmppFailure ())
- sourceStreamHandle :: (MonadIO m, MonadError XmppFailure m) => StreamHandle -> ConduitM i ByteString m ()
- bufferSrc :: ConduitT () o (ExceptT XmppFailure IO) () -> IO (ConduitM i o (ExceptT XmppFailure IO) ())
- sourceStreamHandleRaw :: (MonadIO m, MonadError XmppFailure m) => StreamHandle -> ConduitM i ByteString m ()
- logInput :: MonadIO m => ConduitM ByteString ByteString m ()
- zeroSource :: ConduitT () a (ExceptT XmppFailure IO) ()
- openStream :: HostName -> StreamConfiguration -> IO (Either XmppFailure Stream)
- createStream :: HostName -> StreamConfiguration -> ExceptT XmppFailure IO Stream
- withStream :: StateT StreamState IO a -> Stream -> IO a
- closeStreams :: Stream -> IO ()
- xmppNoStream :: StreamState
- debugOut :: MonadIO m => ByteString -> m ()
- wrapIOException :: MonadIO m => String -> IO a -> m (Either XmppFailure a)
- nsHack :: Element -> Element
- pushStanza :: Stanza -> Stream -> IO (Either XmppFailure ())
- withStream' :: StateT StreamState IO a -> Stream -> IO a
- pullElement :: StateT StreamState IO (Either XmppFailure Element)
- pullUnpickle :: PU [Node] a -> StateT StreamState IO (Either XmppFailure a)
- pullStanza :: Stream -> IO (Either XmppFailure Stanza)
- pullXmppElement :: Stream -> IO (Either XmppFailure XmppElement)
- catchPush :: IO () -> IO (Either XmppFailure ())
- zeroHandle :: StreamHandle
- handleToStreamHandle :: Handle -> StreamHandle
- mkStream :: StreamState -> IO Stream
- resolveAndConnectTcp :: HostName -> PortNumber -> IO (Maybe Handle)
- connectSrv :: ResolvConf -> String -> ExceptT XmppFailure IO (Maybe Handle)
- srvLookup :: Text -> ResolvSeed -> ExceptT XmppFailure IO (Maybe [(Domain, Word16)])
- resolvSrvsAndConnectTcp :: [(HostName, PortNumber)] -> IO (Maybe Handle)
- connectHandle :: AddrInfo -> IO Handle
- connectTcp :: [AddrInfo] -> IO (Maybe Handle)
- fixDnsResult :: Either e a -> Maybe a
- rethrowErrorCall :: IO a -> IO a
- killStream :: Stream -> IO (Either XmppFailure ())
- pushIQ :: Text -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Stream -> IO (Either XmppFailure (Either IQError IQResult))
- debugConduit :: (Show o, MonadIO m) => ConduitM o o m b
- mkBackend :: StreamHandle -> Backend
- starttlsE :: Element
- tls :: Stream -> IO (Either XmppFailure ())
- client :: MonadIO m => ClientParams -> Backend -> m Context
- tlsinit :: (MonadIO m, MonadIO m1) => ClientParams -> Backend -> m (ConduitT () ByteString m1 (), ConduitT ByteString Void m1 (), ByteString -> IO (), Int -> m1 ByteString, Context)
- mkReadBuffer :: IO ByteString -> IO (Int -> IO ByteString)
- connectTls :: ResolvConf -> ClientParams -> String -> ExceptT XmppFailure IO StreamHandle
- wrapExceptions :: IO a -> IO (Either XmppFailure a)
- newtype NonemptyText = Nonempty {
- fromNonempty :: Text
- nonEmpty :: Text -> Maybe NonemptyText
- text :: NonemptyText -> Text
- data IQError = IQError {
- iqErrorID :: !Text
- iqErrorFrom :: !(Maybe Jid)
- iqErrorTo :: !(Maybe Jid)
- iqErrorLangTag :: !(Maybe LangTag)
- iqErrorStanzaError :: !StanzaError
- iqErrorPayload :: !(Maybe Element)
- iqErrorAttributes :: ![ExtendedAttribute]
- data IQRequest = IQRequest {
- iqRequestID :: !Text
- iqRequestFrom :: !(Maybe Jid)
- iqRequestTo :: !(Maybe Jid)
- iqRequestLangTag :: !(Maybe LangTag)
- iqRequestType :: !IQRequestType
- iqRequestPayload :: !Element
- iqRequestAttributes :: ![ExtendedAttribute]
- data IQRequestType
- data IQResponse
- data IQResult = IQResult {
- iqResultID :: !Text
- iqResultFrom :: !(Maybe Jid)
- iqResultTo :: !(Maybe Jid)
- iqResultLangTag :: !(Maybe LangTag)
- iqResultPayload :: !(Maybe Element)
- iqResultAttributes :: ![ExtendedAttribute]
- data LangTag = LangTag {
- primaryTag :: !Text
- subtags :: ![Text]
- langTagQ :: QuasiQuoter
- langTagFromText :: Text -> Maybe LangTag
- langTagToText :: LangTag -> Text
- parseLangTag :: String -> LangTag
- type ExtendedAttribute = (Name, Text)
- data Message = Message {
- messageID :: !(Maybe Text)
- messageFrom :: !(Maybe Jid)
- messageTo :: !(Maybe Jid)
- messageLangTag :: !(Maybe LangTag)
- messageType :: !MessageType
- messagePayload :: ![Element]
- messageAttributes :: ![ExtendedAttribute]
- message :: Message
- data MessageError = MessageError {
- messageErrorID :: !(Maybe Text)
- messageErrorFrom :: !(Maybe Jid)
- messageErrorTo :: !(Maybe Jid)
- messageErrorLangTag :: !(Maybe LangTag)
- messageErrorStanzaError :: !StanzaError
- messageErrorPayload :: ![Element]
- messageErrorAttributes :: ![ExtendedAttribute]
- messageError :: MessageError
- data MessageType
- data Presence = Presence {
- presenceID :: !(Maybe Text)
- presenceFrom :: !(Maybe Jid)
- presenceTo :: !(Maybe Jid)
- presenceLangTag :: !(Maybe LangTag)
- presenceType :: !PresenceType
- presencePayload :: ![Element]
- presenceAttributes :: ![ExtendedAttribute]
- presence :: Presence
- data PresenceError = PresenceError {}
- data PresenceType
- data SaslError
- data SaslFailure = SaslFailure {}
- data StreamFeatures = StreamFeatures {
- streamFeaturesTls :: !(Maybe Bool)
- streamFeaturesMechanisms :: ![Text]
- streamFeaturesRosterVer :: !(Maybe Bool)
- streamFeaturesPreApproval :: !Bool
- streamFeaturesSession :: !(Maybe Bool)
- streamFeaturesOther :: ![Element]
- data Stanza
- data XmppElement
- = XmppStanza !Stanza
- | XmppNonza !Element
- messageS :: Stanza
- messageErrorS :: Stanza
- presenceS :: Stanza
- data StanzaError = StanzaError {}
- data StanzaErrorCondition
- = BadRequest
- | Conflict
- | FeatureNotImplemented
- | Forbidden
- | Gone (Maybe NonemptyText)
- | InternalServerError
- | ItemNotFound
- | JidMalformed
- | NotAcceptable
- | NotAllowed
- | NotAuthorized
- | PolicyViolation
- | RecipientUnavailable
- | Redirect (Maybe NonemptyText)
- | RegistrationRequired
- | RemoteServerNotFound
- | RemoteServerTimeout
- | ResourceConstraint
- | ServiceUnavailable
- | SubscriptionRequired
- | UndefinedCondition
- | UnexpectedRequest
- data StanzaErrorType
- data XmppFailure
- = StreamErrorFailure StreamErrorInfo
- | StreamEndFailure
- | StreamCloseError ([Element], XmppFailure)
- | TcpConnectionFailure
- | XmppIllegalTcpDetails
- | TlsError XmppTlsError
- | TlsNoServerSupport
- | XmppNoStream
- | XmppAuthFailure AuthFailure
- | TlsStreamSecured
- | XmppOtherFailure
- | XmppIOException IOException
- | XmppInvalidXml String
- data XmppTlsError
- data StreamErrorCondition
- = StreamBadFormat
- | StreamBadNamespacePrefix
- | StreamConflict
- | StreamConnectionTimeout
- | StreamHostGone
- | StreamHostUnknown
- | StreamImproperAddressing
- | StreamInternalServerError
- | StreamInvalidFrom
- | StreamInvalidNamespace
- | StreamInvalidXml
- | StreamNotAuthorized
- | StreamNotWellFormed
- | StreamPolicyViolation
- | StreamRemoteConnectionFailed
- | StreamReset
- | StreamResourceConstraint
- | StreamRestrictedXml
- | StreamSeeOtherHost
- | StreamSystemShutdown
- | StreamUndefinedCondition
- | StreamUnsupportedEncoding
- | StreamUnsupportedFeature
- | StreamUnsupportedStanzaType
- | StreamUnsupportedVersion
- data Version = Version {
- majorVersion :: !Integer
- minorVersion :: !Integer
- versionFromText :: Text -> Maybe Version
- data StreamHandle = StreamHandle {
- streamSend :: ByteString -> IO (Either XmppFailure ())
- streamReceive :: Int -> IO (Either XmppFailure ByteString)
- streamFlush :: IO ()
- streamClose :: IO ()
- newtype Stream = Stream {}
- data StreamState = StreamState {
- streamConnectionState :: !ConnectionState
- streamHandle :: StreamHandle
- streamEventSource :: ConduitT () Event (ExceptT XmppFailure IO) ()
- streamFeatures :: !StreamFeatures
- streamAddress :: !(Maybe Text)
- streamFrom :: !(Maybe Jid)
- streamId :: !(Maybe Text)
- streamLang :: !(Maybe LangTag)
- streamJid :: !(Maybe Jid)
- streamConfiguration :: StreamConfiguration
- data ConnectionState
- data StreamErrorInfo = StreamErrorInfo {
- errorCondition :: !StreamErrorCondition
- errorText :: !(Maybe (Maybe LangTag, NonemptyText))
- errorXml :: !(Maybe Element)
- data ConnectionDetails
- data StreamConfiguration = StreamConfiguration {
- preferredLang :: !(Maybe LangTag)
- toJid :: !(Maybe (Jid, Bool))
- connectionDetails :: ConnectionDetails
- resolvConf :: ResolvConf
- tlsBehaviour :: TlsBehaviour
- tlsParams :: ClientParams
- xmppDefaultParams :: ClientParams
- xmppDefaultParamsStrong :: ClientParams
- data Jid = Jid {
- localpart_ :: !(Maybe NonemptyText)
- domainpart_ :: !NonemptyText
- resourcepart_ :: !(Maybe NonemptyText)
- jidQ :: QuasiQuoter
- jid :: QuasiQuoter
- isBare :: Jid -> Bool
- isFull :: Jid -> Bool
- jidFromText :: Text -> Maybe Jid
- jidFromTexts :: Maybe Text -> Text -> Maybe Text -> Maybe Jid
- (<~) :: Jid -> Jid -> Bool
- nodeprepProfile :: StringPrepProfile
- resourceprepProfile :: StringPrepProfile
- jidToText :: Jid -> Text
- jidToTexts :: Jid -> (Maybe Text, Text, Maybe Text)
- toBare :: Jid -> Jid
- localpart :: Jid -> Maybe Text
- domainpart :: Jid -> Text
- resourcepart :: Jid -> Maybe Text
- parseJid :: String -> Jid
- data TlsBehaviour
- data AuthFailure
- openElementToEvents :: Element -> [Event]
- renderOpenElement :: Element -> ByteString
- renderElement :: Element -> ByteString
- checkHostName :: Text -> Maybe Text
- withTMVar :: TMVar a -> (a -> IO (c, a)) -> IO c
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
runConnectionClosedHandler :: Session -> XmppFailure -> IO () Source #
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.
semWrite :: WriteSemaphore -> ByteString -> IO (Either XmppFailure ()) Source #
writeXmppElem :: WriteSemaphore -> XmppElement -> IO (Either XmppFailure ()) Source #
writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ()) Source #
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.
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.
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
streamState :: Session -> STM ConnectionState Source #
type StanzaHandler Source #
= (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 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 | |
|
Instances
Show Annotation Source # | |
Defined in Network.Xmpp.Concurrent.Types showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # |
type Annotated a = (a, [Annotation]) Source #
getAnnotation :: Typeable b => Annotated a -> Maybe b Source #
Retrieve the first matching annotation
Plugin' | |
|
= (XmppElement -> IO (Either XmppFailure ())) | pass stanza to next plugin |
-> ExceptT XmppFailure IO Plugin' |
type RosterPushCallback = Roster -> RosterUpdate -> IO () Source #
data SessionConfiguration Source #
Configuration for the Session
object.
SessionConfiguration | |
|
Instances
data EventHandlers Source #
Handlers to be run when the Xmpp session ends and when the Xmpp connection is closed.
Interrupt is used to signal to the reader thread that it should stop. Th contained semphore signals the reader to resume it's work.
Instances
Exception Interrupt Source # | |
Defined in Network.Xmpp.Concurrent.Types toException :: Interrupt -> SomeException # fromException :: SomeException -> Maybe Interrupt # displayException :: Interrupt -> String # | |
Show Interrupt Source # | |
type WriteSemaphore = TMVar (ByteString -> IO (Either XmppFailure ())) Source #
The Session object represents a single session with an XMPP server. You can
use session
to establish a session
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
IQRequestTicket | |
|
data IQSendError Source #
Error that can occur during sendIQ'
Instances
Exception IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types | |
Show IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types showsPrec :: Int -> IQSendError -> ShowS # show :: IQSendError -> String # showList :: [IQSendError] -> ShowS # | |
Eq IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types (==) :: IQSendError -> IQSendError -> Bool # (/=) :: IQSendError -> IQSendError -> Bool # |
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.
:: Maybe Integer | Timeout . When the timeout is reached the response
TMVar will be filled with |
-> Maybe Jid | Recipient (to) |
-> IQRequestType | IQ type ( |
-> Maybe LangTag | Language tag of the payload ( |
-> Element | The IQ body (there has to be exactly one) |
-> [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.
sendIQA' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError (Annotated IQResponse)) Source #
Like sendIQ
, but waits for the answer IQ.
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
:: IQRequestType | |
-> Text | Namespace of the child element |
-> Session | |
-> IO (Either (STM IQRequestTicket) (STM IQRequestTicket)) |
Register your interest in inbound IQ stanzas of a specific type and namespace. The returned STM action yields the received, matching IQ stanzas.
If a handler for IQ stanzas with the given type and namespace is already registered, the producer will be wrapped in Left. In this case the returned request tickets may already be processed elsewhere.
Unregister a previously registered IQ handler. No more IQ stanzas will be delivered to any of the returned producers.
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)
class IQRequestClass a where Source #
data IQResponseType a Source #
pickleRequest :: PU Element a Source #
pickleResponse :: PU [Element] (IQResponseType a) Source #
requestType :: a -> IQRequestType Source #
requestNamespace :: a -> Text Source #
data IQRequestError Source #
Instances
Show IQRequestError Source # | |
Defined in Network.Xmpp.Concurrent.IQ showsPrec :: Int -> IQRequestError -> ShowS # show :: IQRequestError -> String # showList :: [IQRequestError] -> ShowS # |
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,
type IQRequestHandler a = a -> IO (Either StanzaError (IQResponseType a)) Source #
runIQHandler :: IQRequestClass a => IQRequestHandler a -> Session -> IO () Source #
newSession :: Stream -> SessionConfiguration -> HostName -> Maybe (ConnectionState -> [SaslHandler], Maybe Text) -> IO (Either XmppFailure Session) Source #
Creates and initializes a new Xmpp context.
:: HostName | The hostname / realm |
-> AuthData | |
-> SessionConfiguration | configuration details |
-> IO (Either XmppFailure Session) |
newStanzaID :: Session -> IO Text Source #
Generates a new stanza identifier based on the sessionStanzaIDs
field of
SessionConfiguration
.
:: Integer | Maximum number of retries (numbers of 1 or less will perform exactly one retry) |
-> Session | Session to reconnect |
-> IO (Bool, [XmppFailure]) | Whether or not the reconnect attempt was successful, and a list of failure modes encountered |
Reconnect with the stored settings.
Waits a random amount of seconds (between 0 and 60 inclusive) before the first attempt and an increasing amount after each attempt after that. Caps out at 2-5 minutes.
This function does not set your presence to online, so you will have to do this yourself.
:: Session | Session to reconnect |
-> IO Integer | Number of failed retries before connection could be established |
Reconnect with the stored settings with an unlimited number of retries.
Waits a random amount of seconds (between 0 and 60 inclusive) before the first attempt and an increasing amount after each attempt after that. Caps out at 2-5 minutes.
This function does not set your presence to online, so you will have to do this yourself.
:: Session | session to reconnect |
-> IO (Maybe XmppFailure) |
Reconnect immediately with the stored settings. Returns Just
the error
when the reconnect attempt fails and Nothing when no failure was encountered.
This function does not set your presence to online, so you will have to do this yourself.
semWrite :: WriteSemaphore -> ByteString -> IO (Either XmppFailure ()) Source #
writeXmppElem :: WriteSemaphore -> XmppElement -> IO (Either XmppFailure ()) Source #
writeStanza :: WriteSemaphore -> Stanza -> IO (Either XmppFailure ()) Source #
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.
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.
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
streamState :: Session -> STM ConnectionState Source #
:: Maybe Integer | Timeout . When the timeout is reached the response
TMVar will be filled with |
-> Maybe Jid | Recipient (to) |
-> IQRequestType | IQ type ( |
-> Maybe LangTag | Language tag of the payload ( |
-> Element | The IQ body (there has to be exactly one) |
-> [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.
sendIQA' :: Maybe Integer -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> [ExtendedAttribute] -> Session -> IO (Either IQSendError (Annotated IQResponse)) Source #
Like sendIQ
, but waits for the answer IQ.
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
:: IQRequestType | |
-> Text | Namespace of the child element |
-> Session | |
-> IO (Either (STM IQRequestTicket) (STM IQRequestTicket)) |
Register your interest in inbound IQ stanzas of a specific type and namespace. The returned STM action yields the received, matching IQ stanzas.
If a handler for IQ stanzas with the given type and namespace is already registered, the producer will be wrapped in Left. In this case the returned request tickets may already be processed elsewhere.
Unregister a previously registered IQ handler. No more IQ stanzas will be delivered to any of the returned producers.
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)
class IQRequestClass a where Source #
data IQResponseType a Source #
pickleRequest :: PU Element a Source #
pickleResponse :: PU [Element] (IQResponseType a) Source #
requestType :: a -> IQRequestType Source #
requestNamespace :: a -> Text Source #
data IQRequestError Source #
Instances
Show IQRequestError Source # | |
Defined in Network.Xmpp.Concurrent.IQ showsPrec :: Int -> IQRequestError -> ShowS # show :: IQRequestError -> String # showList :: [IQRequestError] -> ShowS # |
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,
type IQRequestHandler a = a -> IO (Either StanzaError (IQResponseType a)) Source #
runIQHandler :: IQRequestClass a => IQRequestHandler a -> Session -> IO () Source #
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
runConnectionClosedHandler :: Session -> XmppFailure -> IO () Source #
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 #
= (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 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 | |
|
Instances
Show Annotation Source # | |
Defined in Network.Xmpp.Concurrent.Types showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # |
type Annotated a = (a, [Annotation]) Source #
getAnnotation :: Typeable b => Annotated a -> Maybe b Source #
Retrieve the first matching annotation
Plugin' | |
|
= (XmppElement -> IO (Either XmppFailure ())) | pass stanza to next plugin |
-> ExceptT XmppFailure IO Plugin' |
type RosterPushCallback = Roster -> RosterUpdate -> IO () Source #
data SessionConfiguration Source #
Configuration for the Session
object.
SessionConfiguration | |
|
Instances
data EventHandlers Source #
Handlers to be run when the Xmpp session ends and when the Xmpp connection is closed.
Interrupt is used to signal to the reader thread that it should stop. Th contained semphore signals the reader to resume it's work.
Instances
Exception Interrupt Source # | |
Defined in Network.Xmpp.Concurrent.Types toException :: Interrupt -> SomeException # fromException :: SomeException -> Maybe Interrupt # displayException :: Interrupt -> String # | |
Show Interrupt Source # | |
type WriteSemaphore = TMVar (ByteString -> IO (Either XmppFailure ())) Source #
The Session object represents a single session with an XMPP server. You can
use session
to establish a session
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
IQRequestTicket | |
|
data IQSendError Source #
Error that can occur during sendIQ'
Instances
Exception IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types | |
Show IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types showsPrec :: Int -> IQSendError -> ShowS # show :: IQSendError -> String # showList :: [IQSendError] -> ShowS # | |
Eq IQSendError Source # | |
Defined in Network.Xmpp.Concurrent.Types (==) :: IQSendError -> IQSendError -> Bool # (/=) :: IQSendError -> IQSendError -> Bool # |
data MessageBody Source #
data MessageThread Source #
data InstantMessage Source #
The instant message (IM) specific part of a message.
InstantMessage | |
|
Instances
Default InstantMessage Source # | |
Defined in Network.Xmpp.IM.Message 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.
imToElements :: InstantMessage -> [Element] Source #
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.
xpMessageSubject :: PU [Element] [MessageSubject] Source #
xpMessageBody :: PU [Element] [MessageBody] Source #
xpMessageThread :: PU [Element] (Maybe MessageThread) Source #
data ShowStatus Source #
Instances
Read ShowStatus Source # | |
Defined in Network.Xmpp.IM.Presence readsPrec :: Int -> ReadS ShowStatus # readList :: ReadS [ShowStatus] # readPrec :: ReadPrec ShowStatus # readListPrec :: ReadPrec [ShowStatus] # | |
Show ShowStatus Source # | |
Defined in Network.Xmpp.IM.Presence showsPrec :: Int -> ShowStatus -> ShowS # show :: ShowStatus -> String # showList :: [ShowStatus] -> ShowS # | |
Eq ShowStatus Source # | |
Defined in Network.Xmpp.IM.Presence (==) :: ShowStatus -> ShowStatus -> Bool # (/=) :: ShowStatus -> ShowStatus -> Bool # |
data IMPresence Source #
IMP | |
|
Instances
Show IMPresence Source # | |
Defined in Network.Xmpp.IM.Presence showsPrec :: Int -> IMPresence -> ShowS # show :: IMPresence -> String # showList :: [IMPresence] -> ShowS # | |
Default IMPresence Source # | |
Defined in Network.Xmpp.IM.Presence def :: IMPresence # | |
Eq IMPresence Source # | |
Defined in Network.Xmpp.IM.Presence (==) :: IMPresence -> IMPresence -> Bool # (/=) :: IMPresence -> IMPresence -> Bool # |
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.
withIMPresence :: IMPresence -> Presence -> Presence Source #
xpIMPresence :: PU [Element] IMPresence Source #
:: 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.
initRoster :: Session -> IO () Source #
Get the initial roster or refresh the roster. You don't need to call this on your own.
handleRoster :: Maybe Jid -> TVar Roster -> RosterPushCallback -> StanzaHandler Source #
data Subscription Source #
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 |
Instances
Read Subscription Source # | |
Defined in Network.Xmpp.IM.Roster.Types readsPrec :: Int -> ReadS Subscription # readList :: ReadS [Subscription] # | |
Show Subscription Source # | |
Defined in Network.Xmpp.IM.Roster.Types showsPrec :: Int -> Subscription -> ShowS # show :: Subscription -> String # showList :: [Subscription] -> ShowS # | |
Eq Subscription Source # | |
Defined in Network.Xmpp.IM.Roster.Types (==) :: Subscription -> Subscription -> Bool # (/=) :: Subscription -> Subscription -> Bool # |
Roster Items
Item | |
|
data RosterUpdate Source #
RosterUpdateRemove Jid | |
RosterUpdateAdd Item | New or updated item |
Instances
Show RosterUpdate Source # | |
Defined in Network.Xmpp.IM.Roster.Types showsPrec :: Int -> RosterUpdate -> ShowS # show :: RosterUpdate -> String # showList :: [RosterUpdate] -> ShowS # |
xpStreamStanza :: PU [Node] (Either StreamErrorInfo Stanza) Source #
xpStanzaError :: PU [Node] StanzaError Source #
xpMessageError :: PU [Node] MessageError Source #
unpickleElem :: PU [Node] a -> Element -> Either UnpickleError a Source #
:: [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.
:: Username | Authentication identity (authcid or username) |
-> Maybe AuthZID | Authorization identity (authzid) |
-> Password | Password |
-> SaslHandler |
:: Username | username |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
:: 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.
makeNonce :: IO ByteString Source #
xpSaslElement :: PU [Node] SaslElement Source #
Pickler for SaslElement.
quote :: ByteString -> ByteString Source #
Add quotationmarks around a byte string.
saslInit :: Text -> Maybe ByteString -> ExceptT AuthFailure (StateT StreamState IO) () Source #
pullSaslElement :: ExceptT AuthFailure (StateT StreamState IO) SaslElement Source #
Pull the next element.
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
:: Username | Authentication identity (authcid or username) |
-> Maybe AuthZID | Authorization identity (authzid) |
-> Password | Password |
-> SaslHandler |
:: Username | username |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
:: Username | authentication ID (username) |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
:: Username | Authentication identity (authcid or username) |
-> Maybe AuthZID | Authorization identity (authzid) |
-> Password | Password |
-> SaslHandler |
:: 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
:: Hash ctx hash | |
=> hash | Dummy argument to determine the hash to use; you
can safely pass undefined or a |
-> 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.
:: Username | username |
-> Maybe AuthZID | authorization ID |
-> Password | password |
-> SaslHandler |
nonAsciiSpaces :: Set Char Source #
data SaslElement Source #
type Pairs = [(ByteString, ByteString)] Source #
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.
:: 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
FeatureNotImplemented
:Cancel
orModify
(returnsCancel
)PolicyViolation
:Modify
orWait
(Modify
)RemoteServerTimeout
:Wait
or unspecified other (Wait
)UndefinedCondition
: Any condition (Cancel
)
type StreamSink a = ConduitM Event Void (ExceptT XmppFailure IO) a Source #
connect :: HostName -> StreamConfiguration -> ExceptT XmppFailure IO (Maybe StreamHandle) Source #
elements :: MonadError XmppFailure m => ConduitT Event Element m () Source #
streamUnpickleElem :: PU [Node] a -> Element -> StreamSink a Source #
startStream :: StateT StreamState IO (Either XmppFailure ()) Source #
pushXmlDecl :: StateT StreamState IO (Either XmppFailure ()) Source #
pushOpenElement :: Element -> StateT StreamState IO (Either XmppFailure ()) Source #
runEventsSink :: ConduitT Event Void (ExceptT XmppFailure IO) b -> StateT StreamState IO (Either XmppFailure b) Source #
streamS :: Maybe Jid -> StreamSink (Either Element (Text, Maybe Jid, Maybe Jid, Maybe Text, Maybe LangTag, StreamFeatures)) Source #
pushElement :: Element -> StateT StreamState IO (Either XmppFailure ()) Source #
closeStreams' :: StateT StreamState IO () Source #
restartStream :: StateT StreamState IO (Either XmppFailure ()) Source #
sourceStreamHandle :: (MonadIO m, MonadError XmppFailure m) => StreamHandle -> ConduitM i ByteString m () Source #
bufferSrc :: ConduitT () o (ExceptT XmppFailure IO) () -> IO (ConduitM i o (ExceptT XmppFailure IO) ()) Source #
sourceStreamHandleRaw :: (MonadIO m, MonadError XmppFailure m) => StreamHandle -> ConduitM i ByteString m () Source #
logInput :: MonadIO m => ConduitM ByteString ByteString m () Source #
zeroSource :: ConduitT () a (ExceptT XmppFailure IO) () Source #
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 #
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
.
debugOut :: MonadIO m => ByteString -> m () Source #
wrapIOException :: MonadIO m => String -> IO a -> m (Either XmppFailure a) Source #
pushStanza :: Stanza -> Stream -> IO (Either XmppFailure ()) Source #
Encode and send stanza
withStream' :: StateT StreamState IO a -> Stream -> IO a Source #
pullUnpickle :: PU [Node] a -> StateT StreamState IO (Either XmppFailure a) Source #
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.
resolveAndConnectTcp :: HostName -> PortNumber -> IO (Maybe Handle) Source #
connectSrv :: ResolvConf -> String -> ExceptT XmppFailure IO (Maybe Handle) Source #
resolvSrvsAndConnectTcp :: [(HostName, PortNumber)] -> IO (Maybe Handle) Source #
fixDnsResult :: Either e a -> Maybe a Source #
rethrowErrorCall :: IO a -> IO a Source #
killStream :: Stream -> IO (Either XmppFailure ()) Source #
Close the connection and updates the XmppConMonad Stream state. Does not send the stream end tag.
pushIQ :: Text -> Maybe Jid -> IQRequestType -> Maybe LangTag -> Element -> Stream -> IO (Either XmppFailure (Either IQError IQResult)) Source #
mkBackend :: StreamHandle -> Backend Source #
tls :: Stream -> IO (Either XmppFailure ()) Source #
Checks for TLS support and run starttls procedure if applicable
tlsinit :: (MonadIO m, MonadIO m1) => ClientParams -> Backend -> m (ConduitT () ByteString m1 (), ConduitT ByteString Void m1 (), ByteString -> IO (), Int -> m1 ByteString, Context) Source #
mkReadBuffer :: IO ByteString -> IO (Int -> IO ByteString) Source #
:: 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) |
-> 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.
wrapExceptions :: IO a -> IO (Either XmppFailure a) Source #
newtype NonemptyText Source #
Type of Texts that contain at least on non-space character
Instances
IsString NonemptyText Source # | |
Defined in Network.Xmpp.Types fromString :: String -> NonemptyText # | |
Read NonemptyText Source # | |
Defined in Network.Xmpp.Types readsPrec :: Int -> ReadS NonemptyText # readList :: ReadS [NonemptyText] # | |
Show NonemptyText Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> NonemptyText -> ShowS # show :: NonemptyText -> String # showList :: [NonemptyText] -> ShowS # | |
Eq NonemptyText Source # | |
Defined in Network.Xmpp.Types (==) :: NonemptyText -> NonemptyText -> Bool # (/=) :: NonemptyText -> NonemptyText -> Bool # | |
Ord NonemptyText Source # | |
Defined in Network.Xmpp.Types compare :: NonemptyText -> NonemptyText -> Ordering # (<) :: NonemptyText -> NonemptyText -> Bool # (<=) :: NonemptyText -> NonemptyText -> Bool # (>) :: NonemptyText -> NonemptyText -> Bool # (>=) :: NonemptyText -> NonemptyText -> Bool # max :: NonemptyText -> NonemptyText -> NonemptyText # min :: NonemptyText -> NonemptyText -> NonemptyText # |
nonEmpty :: Text -> Maybe NonemptyText Source #
Check that Text contains at least one non-space character and wrap it
text :: NonemptyText -> Text Source #
Same as fromNonempty
The answer to an IQ request that generated an error.
IQError | |
|
Instances
A "request" Info/Query (IQ) stanza is one with either "get" or "set" as type. It always contains an xml payload.
IQRequest | |
|
Instances
data IQRequestType Source #
The type of IQ request that is made.
Instances
data IQResponse Source #
Instances
Show IQResponse Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> IQResponse -> ShowS # show :: IQResponse -> String # showList :: [IQResponse] -> ShowS # | |
Eq IQResponse Source # | |
Defined in Network.Xmpp.Types (==) :: IQResponse -> IQResponse -> Bool # (/=) :: IQResponse -> IQResponse -> Bool # |
The (non-error) answer to an IQ request.
IQResult | |
|
Instances
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).
LangTag | |
|
langTagFromText :: Text -> Maybe LangTag Source #
Parses, validates, and possibly constructs a LangTag object.
langTagToText :: LangTag -> Text Source #
parseLangTag :: String -> LangTag Source #
type ExtendedAttribute = (Name, Text) Source #
The message stanza. Used for push type communication.
Message | |
|
Instances
An empty message
message = Message { messageID = Nothing , messageFrom = Nothing , messageTo = Nothing , messageLangTag = Nothing , messageType = Normal , messagePayload = [] }
data MessageError Source #
An error stanza generated in response to a Message
.
MessageError | |
|
Instances
data MessageType Source #
The type of a Message being sent (http://xmpp.org/rfcs/rfc6121.html#message-syntax-type)
Chat | The message is sent in the context of a one-to-one chat session. Typically an interactive client will present a message of type chat in an interface that enables one-to-one chat between the two parties, including an appropriate conversation history. |
GroupChat | The message is sent in the context of a multi-user chat
environment (similar to that of |
Headline | The message provides an alert, a notification, or other transient information to which no reply is expected (e.g., news headlines, sports updates, near-real-time market data, or syndicated content). Because no reply to the message is expected, typically a receiving client will present a message of type headline in an interface that appropriately differentiates the message from standalone messages, chat messages, and groupchat messages (e.g., by not providing the recipient with the ability to reply). |
Normal | The message is a standalone message that is sent outside the context of a one-to-one conversation or groupchat, and to which it is expected that the recipient will reply. Typically a receiving client will present a message of type normal in an interface that enables the recipient to reply, but without a conversation history. This is the default value. |
Instances
The presence stanza. Used for communicating status updates.
Presence | |
|
Instances
data PresenceError Source #
An error stanza generated in response to a Presence
.
PresenceError | |
|
Instances
data PresenceType Source #
PresenceType
holds Xmpp presence types. The "error" message type is left
out as errors are using PresenceError
.
Subscribe | Sender wants to subscribe to presence |
Subscribed | Sender has approved the subscription |
Unsubscribe | Sender is unsubscribing from presence |
Unsubscribed | Sender has denied or cancelled a subscription |
Probe | Sender requests current presence; should only be used by servers |
Available | Sender wants to express availability (no type attribute is defined) |
Unavailable |
Instances
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
Generic SaslError Source # | |
Read SaslError Source # | |
Show SaslError Source # | |
Eq SaslError Source # | |
type Rep SaslError Source # | |
Defined in Network.Xmpp.Types type Rep SaslError = D1 ('MetaData "SaslError" "Network.Xmpp.Types" "pontarius-xmpp-0.5.7.0-DbzZSn5T7Dd7LRE5dQXSyx" '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
Generic SaslFailure Source # | |
Defined in Network.Xmpp.Types type Rep SaslFailure :: Type -> Type # from :: SaslFailure -> Rep SaslFailure x # to :: Rep SaslFailure x -> SaslFailure # | |
Show SaslFailure Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> SaslFailure -> ShowS # show :: SaslFailure -> String # showList :: [SaslFailure] -> ShowS # | |
Eq SaslFailure Source # | |
Defined in Network.Xmpp.Types (==) :: SaslFailure -> SaslFailure -> Bool # (/=) :: SaslFailure -> SaslFailure -> Bool # | |
type Rep SaslFailure Source # | |
Defined in Network.Xmpp.Types type Rep SaslFailure = D1 ('MetaData "SaslFailure" "Network.Xmpp.Types" "pontarius-xmpp-0.5.7.0-DbzZSn5T7Dd7LRE5dQXSyx" '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 #
StreamFeatures | |
|
Instances
Monoid StreamFeatures Source # | |
Defined in Network.Xmpp.Types mappend :: StreamFeatures -> StreamFeatures -> StreamFeatures # mconcat :: [StreamFeatures] -> StreamFeatures # | |
Semigroup StreamFeatures Source # | |
Defined in Network.Xmpp.Types (<>) :: StreamFeatures -> StreamFeatures -> StreamFeatures # sconcat :: NonEmpty StreamFeatures -> StreamFeatures # stimes :: Integral b => b -> StreamFeatures -> StreamFeatures # | |
Show StreamFeatures Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> StreamFeatures -> ShowS # show :: StreamFeatures -> String # showList :: [StreamFeatures] -> ShowS # | |
Eq StreamFeatures Source # | |
Defined in Network.Xmpp.Types (==) :: StreamFeatures -> StreamFeatures -> Bool # (/=) :: StreamFeatures -> StreamFeatures -> Bool # |
The Xmpp communication primitives (Message, Presence and Info/Query) are called stanzas.
IQRequestS !IQRequest | |
IQResultS !IQResult | |
IQErrorS !IQError | |
MessageS !Message | |
MessageErrorS !MessageError | |
PresenceS !Presence | |
PresenceErrorS !PresenceError |
Instances
data XmppElement Source #
Instances
Show XmppElement Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> XmppElement -> ShowS # show :: XmppElement -> String # showList :: [XmppElement] -> ShowS # | |
Eq XmppElement Source # | |
Defined in Network.Xmpp.Types (==) :: XmppElement -> XmppElement -> Bool # (/=) :: XmppElement -> XmppElement -> Bool # |
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
data StanzaErrorCondition Source #
Stanza errors are accommodated with one of the error conditions listed below.
BadRequest | Malformed XML. |
Conflict | Resource or session with name already exists. |
FeatureNotImplemented | |
Forbidden | Insufficient permissions. |
Gone (Maybe NonemptyText) | Entity can no longer be contacted at this address. |
InternalServerError | |
ItemNotFound | |
JidMalformed | |
NotAcceptable | Does not meet policy criteria. |
NotAllowed | No entity may perform this action. |
NotAuthorized | Must provide proper credentials. |
PolicyViolation | The entity has violated some local service policy (e.g., a message contains words that are prohibited by the service) |
RecipientUnavailable | Temporarily unavailable. |
Redirect (Maybe NonemptyText) | Redirecting to other entity, usually temporarily. |
RegistrationRequired | |
RemoteServerNotFound | |
RemoteServerTimeout | |
ResourceConstraint | Entity lacks the necessary system resources. |
ServiceUnavailable | |
SubscriptionRequired | |
UndefinedCondition | Application-specific condition. |
UnexpectedRequest | Badly timed request. |
Instances
data StanzaErrorType Source #
StanzaError
s always have one of these types.
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
data XmppFailure Source #
Signals an XMPP stream error or another unpredicted stream-related situation. This error is fatal, and closes the XMPP stream.
StreamErrorFailure StreamErrorInfo | An error XML stream element has been encountered. |
StreamEndFailure | The stream has been closed.
This exception is caught by the
concurrent implementation, and
will thus not be visible
through use of |
StreamCloseError ([Element], XmppFailure) | When an XmppFailure is encountered in closeStreams, this constructor wraps the elements collected so far. |
TcpConnectionFailure | All attempts to TCP connect to the server failed. |
XmppIllegalTcpDetails | The TCP details provided did not validate. |
TlsError XmppTlsError | An error occurred in the TLS layer |
TlsNoServerSupport | The server does not support the use of TLS |
XmppNoStream | An action that required an active
stream were performed when the
|
XmppAuthFailure AuthFailure | Authentication with the server failed (unrecoverably) |
TlsStreamSecured | Connection already secured |
XmppOtherFailure | Undefined condition. More information should be available in the log. |
XmppIOException IOException | An |
XmppInvalidXml String | Received data is not valid XML |
Instances
data XmppTlsError Source #
Instances
data StreamErrorCondition Source #
StreamBadFormat | The entity has sent XML that cannot be processed. |
StreamBadNamespacePrefix | The entity has sent a namespace prefix that is unsupported, or has sent no namespace prefix on an element that needs such a prefix |
StreamConflict | The server either (1) is closing the existing stream for this entity because a new stream has been initiated that conflicts with the existing stream, or (2) is refusing a new stream for this entity because allowing the new stream would conflict with an existing stream (e.g., because the server allows only a certain number of connections from the same IP address or allows only one server-to-server stream for a given domain pair as a way of helping to ensure in-order processing |
StreamConnectionTimeout | One party is closing the stream because it has reason to believe that the other party has permanently lost the ability to communicate over the stream. |
StreamHostGone | The value of the |
StreamHostUnknown | The value of the |
StreamImproperAddressing | A stanza sent between two servers lacks a
|
StreamInternalServerError | The server has experienced a misconfiguration or other internal error that prevents it from servicing the stream. |
StreamInvalidFrom | The data provided in a |
StreamInvalidNamespace | The stream namespace name is something other than "http:/etherx.jabber.orgstreams" (see Section 11.2) or the content namespace declared as the default namespace is not supported (e.g., something other than "jabber:client" or "jabber:server"). |
StreamInvalidXml | The entity has sent invalid XML over the stream to a server that performs validation |
StreamNotAuthorized | The entity has attempted to send XML stanzas or other outbound data before the stream has been authenticated, or otherwise is not authorized to perform an action related to stream negotiation; the receiving entity MUST NOT process the offending data before sending the stream error. |
StreamNotWellFormed | The initiating entity has sent XML that violates the well-formedness rules of [XML] or [XML‑NAMES]. |
StreamPolicyViolation | The entity has violated some local service policy (e.g., a stanza exceeds a configured size limit); the server MAY choose to specify the policy in the <text/> element or in an application-specific condition element. |
StreamRemoteConnectionFailed | The server is unable to properly connect to a remote entity that is needed for authentication or authorization (e.g., in certain scenarios related to Server Dialback [XEP‑0220]); this condition is not to be used when the cause of the error is within the administrative domain of the XMPP service provider, in which case the <internal-server-error /> condition is more appropriate. |
StreamReset | The server is closing the stream because it has new (typically security-critical) features to offer, because the keys or certificates used to establish a secure context for the stream have expired or have been revoked during the life of the stream , because the TLS sequence number has wrapped, etc. The reset applies to the stream and to any security context established for that stream (e.g., via TLS and SASL), which means that encryption and authentication need to be negotiated again for the new stream (e.g., TLS session resumption cannot be used) |
StreamResourceConstraint | The server lacks the system resources necessary to service the stream. |
StreamRestrictedXml | he entity has attempted to send restricted XML features such as a comment, processing instruction, DTD subset, or XML entity reference |
StreamSeeOtherHost | The server will not provide service to the initiating entity but is redirecting traffic to another host under the administrative control of the same service provider. |
StreamSystemShutdown | The server is being shut down and all active streams are being closed. |
StreamUndefinedCondition | The error condition is not one of those defined by the other conditions in this list |
StreamUnsupportedEncoding | The initiating entity has encoded the stream in an encoding that is not supported by the server or has otherwise improperly encoded the stream (e.g., by violating the rules of the [UTF‑8] encoding). |
StreamUnsupportedFeature | The receiving entity has advertised a mandatory-to-negotiate stream feature that the initiating entity does not support, and has offered no other mandatory-to-negotiate feature alongside the unsupported feature. |
StreamUnsupportedStanzaType | The initiating entity has sent a first-level child of the stream that is not supported by the server, either because the receiving entity does not understand the namespace or because the receiving entity does not understand the element name for the applicable namespace (which might be the content namespace declared as the default namespace) |
StreamUnsupportedVersion | The |
Instances
XMPP version number. Displayed as "<major>.<minor>". 2.4 is lesser than 2.13, which in turn is lesser than 12.3.
Version | |
|
Instances
Generic Version Source # | |
Read Version Source # | |
Show Version Source # | |
Eq Version Source # | |
Ord Version Source # | |
type Rep Version Source # | |
Defined in Network.Xmpp.Types type Rep Version = D1 ('MetaData "Version" "Network.Xmpp.Types" "pontarius-xmpp-0.5.7.0-DbzZSn5T7Dd7LRE5dQXSyx" '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.
StreamHandle | |
|
data StreamState Source #
StreamState | |
|
data ConnectionState Source #
Signals the state of the stream connection.
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
data StreamErrorInfo Source #
Encapsulates information about an XMPP stream error.
StreamErrorInfo | |
|
Instances
data ConnectionDetails Source #
Specify the method with which the connection is (re-)established
UseRealm | Use realm to resolv host. This is the default. |
UseSrv HostName | Use this hostname for a SRV lookup |
UseHost HostName 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 |
data StreamConfiguration Source #
Configuration settings related to the stream.
StreamConfiguration | |
|
Instances
Default StreamConfiguration Source # | |
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
A JID is XMPP's native format for addressing entities in the network. It is somewhat similar to an e-mail address but contains three parts instead of two: localpart, domainpart, and resourcepart.
The localpart
of a JID is an optional identifier placed
before the domainpart and separated from the latter by a
'@' character. Typically a localpart uniquely identifies
the entity requesting and using network access provided by a
server (i.e., a local account), although it can also
represent other kinds of entities (e.g., a chat room
associated with a multi-user chat service). The entity
represented by an XMPP localpart is addressed within the
context of a specific domain (i.e.,
localpart@domainpart
).
The domainpart typically identifies the home server to which clients connect for XML routing and data management functionality. However, it is not necessary for an XMPP domainpart to identify an entity that provides core XMPP server functionality (e.g., a domainpart can identify an entity such as a multi-user chat service, a publish-subscribe service, or a user directory).
The resourcepart of a JID is an optional identifier placed
after the domainpart and separated from the latter by the
'/' character. A resourcepart can modify either a
localpart@domainpart
address or a mere domainpart
address. Typically a resourcepart uniquely identifies a
specific connection (e.g., a device or location) or object
(e.g., an occupant in a multi-user chat room) belonging to
the entity associated with an XMPP localpart at a domain
(i.e., localpart@domainpart/resourcepart
).
For more details see RFC 6122 http://xmpp.org/rfcs/rfc6122.html
Jid | |
|
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
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.
jidToTexts :: Jid -> (Maybe Text, Text, Maybe Text) Source #
Converts a JID to up to three Text values: (the optional) localpart, the domainpart, and (the optional) resourcepart.
>>>
jidToTexts [jid|foo@bar/quux|]
(Just "foo","bar",Just "quux")
>>>
jidToTexts [jid|bar/quux|]
(Nothing,"bar",Just "quux")
>>>
jidToTexts [jid|foo@bar|]
(Just "foo","bar",Nothing)
jidToTexts j == (localpart j, domainpart j, resourcepart j)
Returns the Jid
without the resourcepart (if any).
>>>
toBare [jid|foo@bar/quux|] == [jid|foo@bar|]
True
localpart :: Jid -> Maybe Text Source #
Returns the localpart of the Jid
(if any).
>>>
localpart [jid|foo@bar/quux|]
Just "foo"
domainpart :: Jid -> Text Source #
Returns the domainpart of the Jid
.
>>>
domainpart [jid|foo@bar/quux|]
"bar"
resourcepart :: Jid -> Maybe Text Source #
Returns the resourcepart of the Jid
(if any).
>>>
resourcepart [jid|foo@bar/quux|]
Just "quux"
parseJid :: String -> Jid Source #
Parses a JID string.
Note: This function is only meant to be used to reverse Jid
Show
operations; it will produce an undefined
value if the JID does not
validate; please refer to jidFromText
for a safe equivalent.
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. |
Instances
Generic TlsBehaviour Source # | |
Defined in Network.Xmpp.Types type Rep TlsBehaviour :: Type -> Type # from :: TlsBehaviour -> Rep TlsBehaviour x # to :: Rep TlsBehaviour x -> TlsBehaviour # | |
Show TlsBehaviour Source # | |
Defined in Network.Xmpp.Types showsPrec :: Int -> TlsBehaviour -> ShowS # show :: TlsBehaviour -> String # showList :: [TlsBehaviour] -> ShowS # | |
Eq TlsBehaviour Source # | |
Defined in Network.Xmpp.Types (==) :: TlsBehaviour -> TlsBehaviour -> Bool # (/=) :: TlsBehaviour -> TlsBehaviour -> Bool # | |
type Rep TlsBehaviour Source # | |
Defined in Network.Xmpp.Types type Rep TlsBehaviour = D1 ('MetaData "TlsBehaviour" "Network.Xmpp.Types" "pontarius-xmpp-0.5.7.0-DbzZSn5T7Dd7LRE5dQXSyx" '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.
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
openElementToEvents :: Element -> [Event] Source #
renderElement :: Element -> ByteString Source #