Copyright | (c) Dustin Sallings 2019 |
---|---|
License | BSD3 |
Maintainer | dustin@spy.net |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
An MQTT protocol client
Both MQTT 3.1.1 and MQTT 5.0 are supported over plain TCP, TLS, WebSockets and Secure WebSockets.
Synopsis
- data MQTTConfig = MQTTConfig {
- _cleanSession :: Bool
- _lwt :: Maybe LastWill
- _msgCB :: MessageCallback
- _protocol :: ProtocolLevel
- _connProps :: [Property]
- _hostname :: String
- _port :: Int
- _connID :: String
- _username :: Maybe String
- _password :: Maybe String
- _connectTimeout :: Int
- _tlsSettings :: TLSSettings
- data MQTTClient
- data QoS
- type Topic = Text
- mqttConfig :: MQTTConfig
- mkLWT :: Topic -> ByteString -> Bool -> LastWill
- data LastWill = LastWill {
- _willRetain :: Bool
- _willQoS :: QoS
- _willTopic :: ByteString
- _willMsg :: ByteString
- _willProps :: [Property]
- data ProtocolLevel
- data Property
- = PropPayloadFormatIndicator Word8
- | PropMessageExpiryInterval Word32
- | PropContentType ByteString
- | PropResponseTopic ByteString
- | PropCorrelationData ByteString
- | PropSubscriptionIdentifier Int
- | PropSessionExpiryInterval Word32
- | PropAssignedClientIdentifier ByteString
- | PropServerKeepAlive Word16
- | PropAuthenticationMethod ByteString
- | PropAuthenticationData ByteString
- | PropRequestProblemInformation Word8
- | PropWillDelayInterval Word32
- | PropRequestResponseInformation Word8
- | PropResponseInformation ByteString
- | PropServerReference ByteString
- | PropReasonString ByteString
- | PropReceiveMaximum Word16
- | PropTopicAliasMaximum Word16
- | PropTopicAlias Word16
- | PropMaximumQoS Word8
- | PropRetainAvailable Word8
- | PropUserProperty ByteString ByteString
- | PropMaximumPacketSize Word32
- | PropWildcardSubscriptionAvailable Word8
- | PropSubscriptionIdentifierAvailable Word8
- | PropSharedSubscriptionAvailable Word8
- data SubOptions = SubOptions {}
- subOptions :: SubOptions
- data MessageCallback
- = NoCallback
- | SimpleCallback (MQTTClient -> Topic -> ByteString -> [Property] -> IO ())
- | LowLevelCallback (MQTTClient -> PublishRequest -> IO ())
- waitForClient :: MQTTClient -> IO ()
- connectURI :: MQTTConfig -> URI -> IO MQTTClient
- isConnected :: MQTTClient -> IO Bool
- disconnect :: MQTTClient -> DiscoReason -> [Property] -> IO ()
- normalDisconnect :: MQTTClient -> IO ()
- subscribe :: MQTTClient -> [(Filter, SubOptions)] -> [Property] -> IO ([Either SubErr QoS], [Property])
- unsubscribe :: MQTTClient -> [Filter] -> [Property] -> IO ([UnsubStatus], [Property])
- publish :: MQTTClient -> Topic -> ByteString -> Bool -> IO ()
- publishq :: MQTTClient -> Topic -> ByteString -> Bool -> QoS -> [Property] -> IO ()
- pubAliased :: MQTTClient -> Topic -> ByteString -> Bool -> QoS -> [Property] -> IO ()
- svrProps :: MQTTClient -> IO [Property]
- connACK :: MQTTClient -> IO ConnACKFlags
- data MQTTException
- runMQTTConduit :: ((MQTTConduit -> IO ()) -> IO ()) -> MQTTConfig -> IO MQTTClient
- type MQTTConduit = (ConduitT () ByteString IO (), ConduitT ByteString Void IO ())
- isConnectedSTM :: MQTTClient -> STM Bool
- connACKSTM :: MQTTClient -> STM ConnACKFlags
- registerCorrelated :: MQTTClient -> ByteString -> MessageCallback -> STM ()
- unregisterCorrelated :: MQTTClient -> ByteString -> STM ()
Configuring the client.
data MQTTConfig Source #
Configuration for setting up an MQTT client.
MQTTConfig | |
|
data MQTTClient Source #
The MQTT client.
See connectURI
for the most straightforward example.
QoS values for publishing and subscribing.
mqttConfig :: MQTTConfig Source #
A default MQTTConfig
. A _connID
may be required depending on
your broker (or if you just want an identifiable/resumable
connection). In MQTTv5, an empty connection ID may be sent and the
server may assign an identifier for you and return it in the
PropAssignedClientIdentifier
Property
.
mkLWT :: Topic -> ByteString -> Bool -> LastWill Source #
A convenience method for creating a LastWill
.
An MQTT Will message.
LastWill | |
|
data ProtocolLevel Source #
MQTT Protocol Levels
Protocol311 | MQTT 3.1.1 |
Protocol50 | MQTT 5.0 |
Instances
Property represents the various MQTT Properties that may sent or received along with packets in MQTT 5. For detailed use on when and where to use them, consult with the MQTT 5.0 spec.
data SubOptions Source #
Options used at subscribe time to define how to handle incoming messages.
SubOptions | |
|
Instances
Eq SubOptions Source # | |
Defined in Network.MQTT.Types (==) :: SubOptions -> SubOptions -> Bool # (/=) :: SubOptions -> SubOptions -> Bool # | |
Show SubOptions Source # | |
Defined in Network.MQTT.Types showsPrec :: Int -> SubOptions -> ShowS # show :: SubOptions -> String # showList :: [SubOptions] -> ShowS # | |
Arbitrary SubOptions Source # | |
Defined in Network.MQTT.Arbitrary arbitrary :: Gen SubOptions # shrink :: SubOptions -> [SubOptions] # | |
ByteMe SubOptions Source # | |
Defined in Network.MQTT.Types toBytes :: ProtocolLevel -> SubOptions -> [Word8] toByteString :: ProtocolLevel -> SubOptions -> ByteString Source # |
subOptions :: SubOptions Source #
Reasonable subscription option defaults at QoS0
.
data MessageCallback Source #
Callback invoked on each incoming subscribed message.
NoCallback | |
SimpleCallback (MQTTClient -> Topic -> ByteString -> [Property] -> IO ()) | |
LowLevelCallback (MQTTClient -> PublishRequest -> IO ()) |
Running and waiting for the client.
waitForClient :: MQTTClient -> IO () Source #
Wait for a client to terminate its connection. An exception is thrown if the client didn't terminate expectedly.
connectURI :: MQTTConfig -> URI -> IO MQTTClient Source #
Connect to an MQTT server by URI.
mqtt://
, mqtts://
, ws://
, and wss://
URLs are supported.
The host, port, username, and password will be derived from the URI
and the values supplied in the config will be ignored.
main :: IO main = do let (Just uri) = parseURI "mqtt://test.mosquitto.org" mc <- connectURI mqttConfig{} uri publish mc "tmp/topic" "hello!" False
isConnected :: MQTTClient -> IO Bool Source #
True if we're currently in a normally connected state (in the IO monad).
disconnect :: MQTTClient -> DiscoReason -> [Property] -> IO () Source #
Disconnect from the MQTT server.
normalDisconnect :: MQTTClient -> IO () Source #
Disconnect with DiscoNormalDisconnection
and no properties.
General client interactions.
subscribe :: MQTTClient -> [(Filter, SubOptions)] -> [Property] -> IO ([Either SubErr QoS], [Property]) Source #
unsubscribe :: MQTTClient -> [Filter] -> [Property] -> IO ([UnsubStatus], [Property]) Source #
Unsubscribe from a list of topic filters.
In MQTT 3.1.1, there is no body to an unsubscribe response, so it can be ignored. If this returns, you were unsubscribed. In MQTT 5, you'll get a list of unsub status values corresponding to your request filters, and whatever properties the server thought you should know about.
:: MQTTClient | |
-> Topic | Topic |
-> ByteString | Message body |
-> Bool | Retain flag |
-> IO () |
Publish a message (QoS 0).
:: MQTTClient | |
-> Topic | Topic |
-> ByteString | Message body |
-> Bool | Retain flag |
-> QoS | QoS |
-> [Property] | Properties |
-> IO () |
Publish a message with the specified QoS and Properties list.
:: MQTTClient | |
-> Topic | Topic |
-> ByteString | Message body |
-> Bool | Retain flag |
-> QoS | QoS |
-> [Property] | Properties |
-> IO () |
Publish a message with the specified QoS
and Property
list. If
possible, use an alias to shorten the message length. The alias
list is managed by the client in a first-come, first-served basis,
so if you use this with more properties than the broker allows,
only the first N (up to TopicAliasMaximum, as specified by the
broker at connect time) will be aliased.
This is safe to use as a general publish mechanism, as it will default to not aliasing whenver there's not already an alias and we can't create any more.
svrProps :: MQTTClient -> IO [Property] Source #
Get the list of properties that were sent from the broker at connect time.
connACK :: MQTTClient -> IO ConnACKFlags Source #
Get the complete connection aCK packet from the beginning of this session.
data MQTTException Source #
Instances
Eq MQTTException Source # | |
Defined in Network.MQTT.Client (==) :: MQTTException -> MQTTException -> Bool # (/=) :: MQTTException -> MQTTException -> Bool # | |
Show MQTTException Source # | |
Defined in Network.MQTT.Client showsPrec :: Int -> MQTTException -> ShowS # show :: MQTTException -> String # showList :: [MQTTException] -> ShowS # | |
Exception MQTTException Source # | |
Defined in Network.MQTT.Client |
Low-level bits
:: ((MQTTConduit -> IO ()) -> IO ()) | an action providing an |
-> MQTTConfig | the |
-> IO MQTTClient |
Set up and run a client with a conduit context function.
The provided action calls another IO action with a MQTTConduit
as a
parameter. It is expected that this action will manage the
lifecycle of the conduit source/sink on behalf of the client.
type MQTTConduit = (ConduitT () ByteString IO (), ConduitT ByteString Void IO ()) Source #
MQTTConduit provides a source and sink for data as used by runMQTTConduit
.
isConnectedSTM :: MQTTClient -> STM Bool Source #
True if we're currently in a normally connected state (in the STM monad).
connACKSTM :: MQTTClient -> STM ConnACKFlags Source #
Get the complete connection ACK packet from the beginning of this session.
registerCorrelated :: MQTTClient -> ByteString -> MessageCallback -> STM () Source #
Register a callback handler for a message with the given correlated data identifier.
This registration will remain in place until unregisterCorrelated is called to remove it.
unregisterCorrelated :: MQTTClient -> ByteString -> STM () Source #
Unregister a callback handler for the given correlated data identifier.