{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.IoT.Types.MqttHeaders
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.IoT.Types.MqttHeaders where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types.UserProperty
import qualified Amazonka.Prelude as Prelude

-- | Specifies MQTT Version 5.0 headers information. For more information,
-- see
-- <https://docs.aws.amazon.com/iot/latest/developerguide/mqtt.html MQTT>
-- from Amazon Web Services IoT Core Developer Guide.
--
-- /See:/ 'newMqttHeaders' smart constructor.
data MqttHeaders = MqttHeaders'
  { -- | A UTF-8 encoded string that describes the content of the publishing
    -- message.
    --
    -- For more information, see
    -- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901118 Content Type>
    -- from the MQTT Version 5.0 specification.
    --
    -- Supports
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
    MqttHeaders -> Maybe Text
contentType :: Prelude.Maybe Prelude.Text,
    -- | The base64-encoded binary data used by the sender of the request message
    -- to identify which request the response message is for when it\'s
    -- received.
    --
    -- For more information, see
    -- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901115 Correlation Data>
    -- from the MQTT Version 5.0 specification.
    --
    -- This binary data must be based64-encoded.
    --
    -- Supports
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
    MqttHeaders -> Maybe Text
correlationData :: Prelude.Maybe Prelude.Text,
    -- | A user-defined integer value that will persist a message at the message
    -- broker for a specified amount of time to ensure that the message will
    -- expire if it\'s no longer relevant to the subscriber. The value of
    -- @messageExpiry@ represents the number of seconds before it expires. For
    -- more information about the limits of @messageExpiry@, see
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/mqtt.html Amazon Web Services IoT Core message broker and protocol limits and quotas>
    -- from the Amazon Web Services Reference Guide.
    --
    -- Supports
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
    MqttHeaders -> Maybe Text
messageExpiry :: Prelude.Maybe Prelude.Text,
    -- | An @Enum@ string value that indicates whether the payload is formatted
    -- as UTF-8.
    --
    -- Valid values are @UNSPECIFIED_BYTES@ and @UTF8_DATA@.
    --
    -- For more information, see
    -- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901111 Payload Format Indicator>
    -- from the MQTT Version 5.0 specification.
    --
    -- Supports
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
    MqttHeaders -> Maybe Text
payloadFormatIndicator :: Prelude.Maybe Prelude.Text,
    -- | A UTF-8 encoded string that\'s used as the topic name for a response
    -- message. The response topic is used to describe the topic which the
    -- receiver should publish to as part of the request-response flow. The
    -- topic must not contain wildcard characters.
    --
    -- For more information, see
    -- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901114 Response Topic>
    -- from the MQTT Version 5.0 specification.
    --
    -- Supports
    -- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
    MqttHeaders -> Maybe Text
responseTopic :: Prelude.Maybe Prelude.Text,
    -- | An array of key-value pairs that you define in the MQTT5 header.
    MqttHeaders -> Maybe (NonEmpty UserProperty)
userProperties :: Prelude.Maybe (Prelude.NonEmpty UserProperty)
  }
  deriving (MqttHeaders -> MqttHeaders -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MqttHeaders -> MqttHeaders -> Bool
$c/= :: MqttHeaders -> MqttHeaders -> Bool
== :: MqttHeaders -> MqttHeaders -> Bool
$c== :: MqttHeaders -> MqttHeaders -> Bool
Prelude.Eq, ReadPrec [MqttHeaders]
ReadPrec MqttHeaders
Int -> ReadS MqttHeaders
ReadS [MqttHeaders]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MqttHeaders]
$creadListPrec :: ReadPrec [MqttHeaders]
readPrec :: ReadPrec MqttHeaders
$creadPrec :: ReadPrec MqttHeaders
readList :: ReadS [MqttHeaders]
$creadList :: ReadS [MqttHeaders]
readsPrec :: Int -> ReadS MqttHeaders
$creadsPrec :: Int -> ReadS MqttHeaders
Prelude.Read, Int -> MqttHeaders -> ShowS
[MqttHeaders] -> ShowS
MqttHeaders -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MqttHeaders] -> ShowS
$cshowList :: [MqttHeaders] -> ShowS
show :: MqttHeaders -> String
$cshow :: MqttHeaders -> String
showsPrec :: Int -> MqttHeaders -> ShowS
$cshowsPrec :: Int -> MqttHeaders -> ShowS
Prelude.Show, forall x. Rep MqttHeaders x -> MqttHeaders
forall x. MqttHeaders -> Rep MqttHeaders x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MqttHeaders x -> MqttHeaders
$cfrom :: forall x. MqttHeaders -> Rep MqttHeaders x
Prelude.Generic)

-- |
-- Create a value of 'MqttHeaders' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'contentType', 'mqttHeaders_contentType' - A UTF-8 encoded string that describes the content of the publishing
-- message.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901118 Content Type>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
--
-- 'correlationData', 'mqttHeaders_correlationData' - The base64-encoded binary data used by the sender of the request message
-- to identify which request the response message is for when it\'s
-- received.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901115 Correlation Data>
-- from the MQTT Version 5.0 specification.
--
-- This binary data must be based64-encoded.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
--
-- 'messageExpiry', 'mqttHeaders_messageExpiry' - A user-defined integer value that will persist a message at the message
-- broker for a specified amount of time to ensure that the message will
-- expire if it\'s no longer relevant to the subscriber. The value of
-- @messageExpiry@ represents the number of seconds before it expires. For
-- more information about the limits of @messageExpiry@, see
-- <https://docs.aws.amazon.com/iot/latest/developerguide/mqtt.html Amazon Web Services IoT Core message broker and protocol limits and quotas>
-- from the Amazon Web Services Reference Guide.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
--
-- 'payloadFormatIndicator', 'mqttHeaders_payloadFormatIndicator' - An @Enum@ string value that indicates whether the payload is formatted
-- as UTF-8.
--
-- Valid values are @UNSPECIFIED_BYTES@ and @UTF8_DATA@.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901111 Payload Format Indicator>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
--
-- 'responseTopic', 'mqttHeaders_responseTopic' - A UTF-8 encoded string that\'s used as the topic name for a response
-- message. The response topic is used to describe the topic which the
-- receiver should publish to as part of the request-response flow. The
-- topic must not contain wildcard characters.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901114 Response Topic>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
--
-- 'userProperties', 'mqttHeaders_userProperties' - An array of key-value pairs that you define in the MQTT5 header.
newMqttHeaders ::
  MqttHeaders
newMqttHeaders :: MqttHeaders
newMqttHeaders =
  MqttHeaders'
    { $sel:contentType:MqttHeaders' :: Maybe Text
contentType = forall a. Maybe a
Prelude.Nothing,
      $sel:correlationData:MqttHeaders' :: Maybe Text
correlationData = forall a. Maybe a
Prelude.Nothing,
      $sel:messageExpiry:MqttHeaders' :: Maybe Text
messageExpiry = forall a. Maybe a
Prelude.Nothing,
      $sel:payloadFormatIndicator:MqttHeaders' :: Maybe Text
payloadFormatIndicator = forall a. Maybe a
Prelude.Nothing,
      $sel:responseTopic:MqttHeaders' :: Maybe Text
responseTopic = forall a. Maybe a
Prelude.Nothing,
      $sel:userProperties:MqttHeaders' :: Maybe (NonEmpty UserProperty)
userProperties = forall a. Maybe a
Prelude.Nothing
    }

-- | A UTF-8 encoded string that describes the content of the publishing
-- message.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901118 Content Type>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
mqttHeaders_contentType :: Lens.Lens' MqttHeaders (Prelude.Maybe Prelude.Text)
mqttHeaders_contentType :: Lens' MqttHeaders (Maybe Text)
mqttHeaders_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe Text
contentType :: Maybe Text
$sel:contentType:MqttHeaders' :: MqttHeaders -> Maybe Text
contentType} -> Maybe Text
contentType) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe Text
a -> MqttHeaders
s {$sel:contentType:MqttHeaders' :: Maybe Text
contentType = Maybe Text
a} :: MqttHeaders)

-- | The base64-encoded binary data used by the sender of the request message
-- to identify which request the response message is for when it\'s
-- received.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901115 Correlation Data>
-- from the MQTT Version 5.0 specification.
--
-- This binary data must be based64-encoded.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
mqttHeaders_correlationData :: Lens.Lens' MqttHeaders (Prelude.Maybe Prelude.Text)
mqttHeaders_correlationData :: Lens' MqttHeaders (Maybe Text)
mqttHeaders_correlationData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe Text
correlationData :: Maybe Text
$sel:correlationData:MqttHeaders' :: MqttHeaders -> Maybe Text
correlationData} -> Maybe Text
correlationData) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe Text
a -> MqttHeaders
s {$sel:correlationData:MqttHeaders' :: Maybe Text
correlationData = Maybe Text
a} :: MqttHeaders)

-- | A user-defined integer value that will persist a message at the message
-- broker for a specified amount of time to ensure that the message will
-- expire if it\'s no longer relevant to the subscriber. The value of
-- @messageExpiry@ represents the number of seconds before it expires. For
-- more information about the limits of @messageExpiry@, see
-- <https://docs.aws.amazon.com/iot/latest/developerguide/mqtt.html Amazon Web Services IoT Core message broker and protocol limits and quotas>
-- from the Amazon Web Services Reference Guide.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
mqttHeaders_messageExpiry :: Lens.Lens' MqttHeaders (Prelude.Maybe Prelude.Text)
mqttHeaders_messageExpiry :: Lens' MqttHeaders (Maybe Text)
mqttHeaders_messageExpiry = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe Text
messageExpiry :: Maybe Text
$sel:messageExpiry:MqttHeaders' :: MqttHeaders -> Maybe Text
messageExpiry} -> Maybe Text
messageExpiry) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe Text
a -> MqttHeaders
s {$sel:messageExpiry:MqttHeaders' :: Maybe Text
messageExpiry = Maybe Text
a} :: MqttHeaders)

-- | An @Enum@ string value that indicates whether the payload is formatted
-- as UTF-8.
--
-- Valid values are @UNSPECIFIED_BYTES@ and @UTF8_DATA@.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901111 Payload Format Indicator>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
mqttHeaders_payloadFormatIndicator :: Lens.Lens' MqttHeaders (Prelude.Maybe Prelude.Text)
mqttHeaders_payloadFormatIndicator :: Lens' MqttHeaders (Maybe Text)
mqttHeaders_payloadFormatIndicator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe Text
payloadFormatIndicator :: Maybe Text
$sel:payloadFormatIndicator:MqttHeaders' :: MqttHeaders -> Maybe Text
payloadFormatIndicator} -> Maybe Text
payloadFormatIndicator) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe Text
a -> MqttHeaders
s {$sel:payloadFormatIndicator:MqttHeaders' :: Maybe Text
payloadFormatIndicator = Maybe Text
a} :: MqttHeaders)

-- | A UTF-8 encoded string that\'s used as the topic name for a response
-- message. The response topic is used to describe the topic which the
-- receiver should publish to as part of the request-response flow. The
-- topic must not contain wildcard characters.
--
-- For more information, see
-- <https://docs.oasis-open.org/mqtt/mqtt/v5.0/os/mqtt-v5.0-os.html#_Toc3901114 Response Topic>
-- from the MQTT Version 5.0 specification.
--
-- Supports
-- <https://docs.aws.amazon.com/iot/latest/developerguide/iot-substitution-templates.html substitution templates>.
mqttHeaders_responseTopic :: Lens.Lens' MqttHeaders (Prelude.Maybe Prelude.Text)
mqttHeaders_responseTopic :: Lens' MqttHeaders (Maybe Text)
mqttHeaders_responseTopic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe Text
responseTopic :: Maybe Text
$sel:responseTopic:MqttHeaders' :: MqttHeaders -> Maybe Text
responseTopic} -> Maybe Text
responseTopic) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe Text
a -> MqttHeaders
s {$sel:responseTopic:MqttHeaders' :: Maybe Text
responseTopic = Maybe Text
a} :: MqttHeaders)

-- | An array of key-value pairs that you define in the MQTT5 header.
mqttHeaders_userProperties :: Lens.Lens' MqttHeaders (Prelude.Maybe (Prelude.NonEmpty UserProperty))
mqttHeaders_userProperties :: Lens' MqttHeaders (Maybe (NonEmpty UserProperty))
mqttHeaders_userProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MqttHeaders' {Maybe (NonEmpty UserProperty)
userProperties :: Maybe (NonEmpty UserProperty)
$sel:userProperties:MqttHeaders' :: MqttHeaders -> Maybe (NonEmpty UserProperty)
userProperties} -> Maybe (NonEmpty UserProperty)
userProperties) (\s :: MqttHeaders
s@MqttHeaders' {} Maybe (NonEmpty UserProperty)
a -> MqttHeaders
s {$sel:userProperties:MqttHeaders' :: Maybe (NonEmpty UserProperty)
userProperties = Maybe (NonEmpty UserProperty)
a} :: MqttHeaders) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Data.FromJSON MqttHeaders where
  parseJSON :: Value -> Parser MqttHeaders
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MqttHeaders"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty UserProperty)
-> MqttHeaders
MqttHeaders'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"contentType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"correlationData")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"messageExpiry")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"payloadFormatIndicator")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"responseTopic")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"userProperties")
      )

instance Prelude.Hashable MqttHeaders where
  hashWithSalt :: Int -> MqttHeaders -> Int
hashWithSalt Int
_salt MqttHeaders' {Maybe (NonEmpty UserProperty)
Maybe Text
userProperties :: Maybe (NonEmpty UserProperty)
responseTopic :: Maybe Text
payloadFormatIndicator :: Maybe Text
messageExpiry :: Maybe Text
correlationData :: Maybe Text
contentType :: Maybe Text
$sel:userProperties:MqttHeaders' :: MqttHeaders -> Maybe (NonEmpty UserProperty)
$sel:responseTopic:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:payloadFormatIndicator:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:messageExpiry:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:correlationData:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:contentType:MqttHeaders' :: MqttHeaders -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
correlationData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
messageExpiry
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
payloadFormatIndicator
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
responseTopic
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty UserProperty)
userProperties

instance Prelude.NFData MqttHeaders where
  rnf :: MqttHeaders -> ()
rnf MqttHeaders' {Maybe (NonEmpty UserProperty)
Maybe Text
userProperties :: Maybe (NonEmpty UserProperty)
responseTopic :: Maybe Text
payloadFormatIndicator :: Maybe Text
messageExpiry :: Maybe Text
correlationData :: Maybe Text
contentType :: Maybe Text
$sel:userProperties:MqttHeaders' :: MqttHeaders -> Maybe (NonEmpty UserProperty)
$sel:responseTopic:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:payloadFormatIndicator:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:messageExpiry:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:correlationData:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:contentType:MqttHeaders' :: MqttHeaders -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
correlationData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
messageExpiry
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
payloadFormatIndicator
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
responseTopic
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty UserProperty)
userProperties

instance Data.ToJSON MqttHeaders where
  toJSON :: MqttHeaders -> Value
toJSON MqttHeaders' {Maybe (NonEmpty UserProperty)
Maybe Text
userProperties :: Maybe (NonEmpty UserProperty)
responseTopic :: Maybe Text
payloadFormatIndicator :: Maybe Text
messageExpiry :: Maybe Text
correlationData :: Maybe Text
contentType :: Maybe Text
$sel:userProperties:MqttHeaders' :: MqttHeaders -> Maybe (NonEmpty UserProperty)
$sel:responseTopic:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:payloadFormatIndicator:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:messageExpiry:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:correlationData:MqttHeaders' :: MqttHeaders -> Maybe Text
$sel:contentType:MqttHeaders' :: MqttHeaders -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"contentType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
contentType,
            (Key
"correlationData" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
correlationData,
            (Key
"messageExpiry" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
messageExpiry,
            (Key
"payloadFormatIndicator" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
payloadFormatIndicator,
            (Key
"responseTopic" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
responseTopic,
            (Key
"userProperties" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty UserProperty)
userProperties
          ]
      )