net-mqtt-0.8.1.0: An MQTT Protocol Implementation.
Copyright(c) Dustin Sallings 2019
LicenseBSD3
Maintainerdustin@spy.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.MQTT.Client

Description

An MQTT protocol client

Both MQTT 3.1.1 and MQTT 5.0 are supported over plain TCP, TLS, WebSockets and Secure WebSockets.

Synopsis

Configuring the client.

data MQTTConfig Source #

Configuration for setting up an MQTT client.

Constructors

MQTTConfig 

Fields

data MQTTClient Source #

The MQTT client.

See connectURI for the most straightforward example.

data QoS Source #

QoS values for publishing and subscribing.

Constructors

QoS0 
QoS1 
QoS2 

Instances

Instances details
Bounded QoS Source # 
Instance details

Defined in Network.MQTT.Types

Methods

minBound :: QoS #

maxBound :: QoS #

Enum QoS Source # 
Instance details

Defined in Network.MQTT.Types

Methods

succ :: QoS -> QoS #

pred :: QoS -> QoS #

toEnum :: Int -> QoS #

fromEnum :: QoS -> Int #

enumFrom :: QoS -> [QoS] #

enumFromThen :: QoS -> QoS -> [QoS] #

enumFromTo :: QoS -> QoS -> [QoS] #

enumFromThenTo :: QoS -> QoS -> QoS -> [QoS] #

Eq QoS Source # 
Instance details

Defined in Network.MQTT.Types

Methods

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

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

Ord QoS Source # 
Instance details

Defined in Network.MQTT.Types

Methods

compare :: QoS -> QoS -> Ordering #

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

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

(>) :: QoS -> QoS -> Bool #

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

max :: QoS -> QoS -> QoS #

min :: QoS -> QoS -> QoS #

Show QoS Source # 
Instance details

Defined in Network.MQTT.Types

Methods

showsPrec :: Int -> QoS -> ShowS #

show :: QoS -> String #

showList :: [QoS] -> ShowS #

Arbitrary QoS Source # 
Instance details

Defined in Network.MQTT.Arbitrary

Methods

arbitrary :: Gen QoS #

shrink :: QoS -> [QoS] #

data Topic Source #

An MQTT topic.

Instances

Instances details
Eq Topic Source # 
Instance details

Defined in Network.MQTT.Topic

Methods

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

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

Ord Topic Source # 
Instance details

Defined in Network.MQTT.Topic

Methods

compare :: Topic -> Topic -> Ordering #

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

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

(>) :: Topic -> Topic -> Bool #

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

max :: Topic -> Topic -> Topic #

min :: Topic -> Topic -> Topic #

Show Topic Source # 
Instance details

Defined in Network.MQTT.Topic

Methods

showsPrec :: Int -> Topic -> ShowS #

show :: Topic -> String #

showList :: [Topic] -> ShowS #

IsString Topic Source # 
Instance details

Defined in Network.MQTT.Topic

Methods

fromString :: String -> Topic #

Semigroup Topic Source # 
Instance details

Defined in Network.MQTT.Topic

Methods

(<>) :: Topic -> Topic -> Topic #

sconcat :: NonEmpty Topic -> Topic #

stimes :: Integral b => b -> Topic -> Topic #

Arbitrary Topic Source # 
Instance details

Defined in Network.MQTT.Arbitrary

Methods

arbitrary :: Gen Topic #

shrink :: Topic -> [Topic] #

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.

data LastWill Source #

An MQTT Will message.

Instances

Instances details
Eq LastWill Source # 
Instance details

Defined in Network.MQTT.Types

Show LastWill Source # 
Instance details

Defined in Network.MQTT.Types

Arbitrary LastWill Source # 
Instance details

Defined in Network.MQTT.Arbitrary

data ProtocolLevel Source #

MQTT Protocol Levels

Constructors

Protocol311

MQTT 3.1.1

Protocol50

MQTT 5.0

data Property Source #

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.

Instances

Instances details
Eq Property Source # 
Instance details

Defined in Network.MQTT.Types

Show Property Source # 
Instance details

Defined in Network.MQTT.Types

Arbitrary Property Source # 
Instance details

Defined in Network.MQTT.Arbitrary

ByteMe Property Source # 
Instance details

Defined in Network.MQTT.Types

data SubOptions Source #

Options used at subscribe time to define how to handle incoming messages.

Constructors

SubOptions 

Fields

Instances

Instances details
Eq SubOptions Source # 
Instance details

Defined in Network.MQTT.Types

Show SubOptions Source # 
Instance details

Defined in Network.MQTT.Types

Arbitrary SubOptions Source # 
Instance details

Defined in Network.MQTT.Arbitrary

ByteMe SubOptions Source # 
Instance details

Defined in Network.MQTT.Types

subOptions :: SubOptions Source #

Reasonable subscription option defaults at QoS0.

data MessageCallback Source #

Callback invoked on each incoming subscribed message.

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 #

Subscribe to a list of topic filters with their respective QoSes. The accepted QoSes are returned in the same order as requested.

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.

publish Source #

Arguments

:: MQTTClient 
-> Topic

Topic

-> ByteString

Message body

-> Bool

Retain flag

-> IO () 

Publish a message (QoS 0).

publishq Source #

Arguments

:: MQTTClient 
-> Topic

Topic

-> ByteString

Message body

-> Bool

Retain flag

-> QoS

QoS

-> [Property]

Properties

-> IO () 

Publish a message with the specified QoS and Properties list.

pubAliased Source #

Arguments

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

Low-level bits

runMQTTConduit Source #

Arguments

:: ((MQTTConduit -> IO ()) -> IO ())

an action providing an MQTTConduit in an execution context

-> MQTTConfig

the MQTTConfig

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