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

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

-- |
-- Module      : Amazonka.IoTData.GetRetainedMessage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the details of a single retained message for the specified topic.
--
-- This action returns the message payload of the retained message, which
-- can incur messaging costs. To list only the topic names of the retained
-- messages, call
-- </iot/latest/developerguide/API_iotdata_ListRetainedMessages.html ListRetainedMessages>.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiotfleethubfordevicemanagement.html#awsiotfleethubfordevicemanagement-actions-as-permissions GetRetainedMessage>
-- action.
--
-- For more information about messaging costs, see
-- <http://aws.amazon.com/iot-core/pricing/#Messaging Amazon Web Services IoT Core pricing - Messaging>.
module Amazonka.IoTData.GetRetainedMessage
  ( -- * Creating a Request
    GetRetainedMessage (..),
    newGetRetainedMessage,

    -- * Request Lenses
    getRetainedMessage_topic,

    -- * Destructuring the Response
    GetRetainedMessageResponse (..),
    newGetRetainedMessageResponse,

    -- * Response Lenses
    getRetainedMessageResponse_lastModifiedTime,
    getRetainedMessageResponse_payload,
    getRetainedMessageResponse_qos,
    getRetainedMessageResponse_topic,
    getRetainedMessageResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTData.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The input for the GetRetainedMessage operation.
--
-- /See:/ 'newGetRetainedMessage' smart constructor.
data GetRetainedMessage = GetRetainedMessage'
  { -- | The topic name of the retained message to retrieve.
    GetRetainedMessage -> Text
topic :: Prelude.Text
  }
  deriving (GetRetainedMessage -> GetRetainedMessage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRetainedMessage -> GetRetainedMessage -> Bool
$c/= :: GetRetainedMessage -> GetRetainedMessage -> Bool
== :: GetRetainedMessage -> GetRetainedMessage -> Bool
$c== :: GetRetainedMessage -> GetRetainedMessage -> Bool
Prelude.Eq, ReadPrec [GetRetainedMessage]
ReadPrec GetRetainedMessage
Int -> ReadS GetRetainedMessage
ReadS [GetRetainedMessage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRetainedMessage]
$creadListPrec :: ReadPrec [GetRetainedMessage]
readPrec :: ReadPrec GetRetainedMessage
$creadPrec :: ReadPrec GetRetainedMessage
readList :: ReadS [GetRetainedMessage]
$creadList :: ReadS [GetRetainedMessage]
readsPrec :: Int -> ReadS GetRetainedMessage
$creadsPrec :: Int -> ReadS GetRetainedMessage
Prelude.Read, Int -> GetRetainedMessage -> ShowS
[GetRetainedMessage] -> ShowS
GetRetainedMessage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRetainedMessage] -> ShowS
$cshowList :: [GetRetainedMessage] -> ShowS
show :: GetRetainedMessage -> String
$cshow :: GetRetainedMessage -> String
showsPrec :: Int -> GetRetainedMessage -> ShowS
$cshowsPrec :: Int -> GetRetainedMessage -> ShowS
Prelude.Show, forall x. Rep GetRetainedMessage x -> GetRetainedMessage
forall x. GetRetainedMessage -> Rep GetRetainedMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRetainedMessage x -> GetRetainedMessage
$cfrom :: forall x. GetRetainedMessage -> Rep GetRetainedMessage x
Prelude.Generic)

-- |
-- Create a value of 'GetRetainedMessage' 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:
--
-- 'topic', 'getRetainedMessage_topic' - The topic name of the retained message to retrieve.
newGetRetainedMessage ::
  -- | 'topic'
  Prelude.Text ->
  GetRetainedMessage
newGetRetainedMessage :: Text -> GetRetainedMessage
newGetRetainedMessage Text
pTopic_ =
  GetRetainedMessage' {$sel:topic:GetRetainedMessage' :: Text
topic = Text
pTopic_}

-- | The topic name of the retained message to retrieve.
getRetainedMessage_topic :: Lens.Lens' GetRetainedMessage Prelude.Text
getRetainedMessage_topic :: Lens' GetRetainedMessage Text
getRetainedMessage_topic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessage' {Text
topic :: Text
$sel:topic:GetRetainedMessage' :: GetRetainedMessage -> Text
topic} -> Text
topic) (\s :: GetRetainedMessage
s@GetRetainedMessage' {} Text
a -> GetRetainedMessage
s {$sel:topic:GetRetainedMessage' :: Text
topic = Text
a} :: GetRetainedMessage)

instance Core.AWSRequest GetRetainedMessage where
  type
    AWSResponse GetRetainedMessage =
      GetRetainedMessageResponse
  request :: (Service -> Service)
-> GetRetainedMessage -> Request GetRetainedMessage
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetRetainedMessage
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetRetainedMessage)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Integer
-> Maybe Base64
-> Maybe Natural
-> Maybe Text
-> Int
-> GetRetainedMessageResponse
GetRetainedMessageResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"lastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"payload")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"qos")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"topic")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetRetainedMessage where
  hashWithSalt :: Int -> GetRetainedMessage -> Int
hashWithSalt Int
_salt GetRetainedMessage' {Text
topic :: Text
$sel:topic:GetRetainedMessage' :: GetRetainedMessage -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
topic

instance Prelude.NFData GetRetainedMessage where
  rnf :: GetRetainedMessage -> ()
rnf GetRetainedMessage' {Text
topic :: Text
$sel:topic:GetRetainedMessage' :: GetRetainedMessage -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
topic

instance Data.ToHeaders GetRetainedMessage where
  toHeaders :: GetRetainedMessage -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetRetainedMessage where
  toPath :: GetRetainedMessage -> ByteString
toPath GetRetainedMessage' {Text
topic :: Text
$sel:topic:GetRetainedMessage' :: GetRetainedMessage -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/retainedMessage/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
topic]

instance Data.ToQuery GetRetainedMessage where
  toQuery :: GetRetainedMessage -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | The output from the GetRetainedMessage operation.
--
-- /See:/ 'newGetRetainedMessageResponse' smart constructor.
data GetRetainedMessageResponse = GetRetainedMessageResponse'
  { -- | The Epoch date and time, in milliseconds, when the retained message was
    -- stored by IoT.
    GetRetainedMessageResponse -> Maybe Integer
lastModifiedTime :: Prelude.Maybe Prelude.Integer,
    -- | The Base64-encoded message payload of the retained message body.
    GetRetainedMessageResponse -> Maybe Base64
payload :: Prelude.Maybe Data.Base64,
    -- | The quality of service (QoS) level used to publish the retained message.
    GetRetainedMessageResponse -> Maybe Natural
qos :: Prelude.Maybe Prelude.Natural,
    -- | The topic name to which the retained message was published.
    GetRetainedMessageResponse -> Maybe Text
topic :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetRetainedMessageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRetainedMessageResponse -> GetRetainedMessageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRetainedMessageResponse -> GetRetainedMessageResponse -> Bool
$c/= :: GetRetainedMessageResponse -> GetRetainedMessageResponse -> Bool
== :: GetRetainedMessageResponse -> GetRetainedMessageResponse -> Bool
$c== :: GetRetainedMessageResponse -> GetRetainedMessageResponse -> Bool
Prelude.Eq, ReadPrec [GetRetainedMessageResponse]
ReadPrec GetRetainedMessageResponse
Int -> ReadS GetRetainedMessageResponse
ReadS [GetRetainedMessageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRetainedMessageResponse]
$creadListPrec :: ReadPrec [GetRetainedMessageResponse]
readPrec :: ReadPrec GetRetainedMessageResponse
$creadPrec :: ReadPrec GetRetainedMessageResponse
readList :: ReadS [GetRetainedMessageResponse]
$creadList :: ReadS [GetRetainedMessageResponse]
readsPrec :: Int -> ReadS GetRetainedMessageResponse
$creadsPrec :: Int -> ReadS GetRetainedMessageResponse
Prelude.Read, Int -> GetRetainedMessageResponse -> ShowS
[GetRetainedMessageResponse] -> ShowS
GetRetainedMessageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRetainedMessageResponse] -> ShowS
$cshowList :: [GetRetainedMessageResponse] -> ShowS
show :: GetRetainedMessageResponse -> String
$cshow :: GetRetainedMessageResponse -> String
showsPrec :: Int -> GetRetainedMessageResponse -> ShowS
$cshowsPrec :: Int -> GetRetainedMessageResponse -> ShowS
Prelude.Show, forall x.
Rep GetRetainedMessageResponse x -> GetRetainedMessageResponse
forall x.
GetRetainedMessageResponse -> Rep GetRetainedMessageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRetainedMessageResponse x -> GetRetainedMessageResponse
$cfrom :: forall x.
GetRetainedMessageResponse -> Rep GetRetainedMessageResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRetainedMessageResponse' 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:
--
-- 'lastModifiedTime', 'getRetainedMessageResponse_lastModifiedTime' - The Epoch date and time, in milliseconds, when the retained message was
-- stored by IoT.
--
-- 'payload', 'getRetainedMessageResponse_payload' - The Base64-encoded message payload of the retained message body.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
--
-- 'qos', 'getRetainedMessageResponse_qos' - The quality of service (QoS) level used to publish the retained message.
--
-- 'topic', 'getRetainedMessageResponse_topic' - The topic name to which the retained message was published.
--
-- 'httpStatus', 'getRetainedMessageResponse_httpStatus' - The response's http status code.
newGetRetainedMessageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRetainedMessageResponse
newGetRetainedMessageResponse :: Int -> GetRetainedMessageResponse
newGetRetainedMessageResponse Int
pHttpStatus_ =
  GetRetainedMessageResponse'
    { $sel:lastModifiedTime:GetRetainedMessageResponse' :: Maybe Integer
lastModifiedTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:payload:GetRetainedMessageResponse' :: Maybe Base64
payload = forall a. Maybe a
Prelude.Nothing,
      $sel:qos:GetRetainedMessageResponse' :: Maybe Natural
qos = forall a. Maybe a
Prelude.Nothing,
      $sel:topic:GetRetainedMessageResponse' :: Maybe Text
topic = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRetainedMessageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Epoch date and time, in milliseconds, when the retained message was
-- stored by IoT.
getRetainedMessageResponse_lastModifiedTime :: Lens.Lens' GetRetainedMessageResponse (Prelude.Maybe Prelude.Integer)
getRetainedMessageResponse_lastModifiedTime :: Lens' GetRetainedMessageResponse (Maybe Integer)
getRetainedMessageResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessageResponse' {Maybe Integer
lastModifiedTime :: Maybe Integer
$sel:lastModifiedTime:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Integer
lastModifiedTime} -> Maybe Integer
lastModifiedTime) (\s :: GetRetainedMessageResponse
s@GetRetainedMessageResponse' {} Maybe Integer
a -> GetRetainedMessageResponse
s {$sel:lastModifiedTime:GetRetainedMessageResponse' :: Maybe Integer
lastModifiedTime = Maybe Integer
a} :: GetRetainedMessageResponse)

-- | The Base64-encoded message payload of the retained message body.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
getRetainedMessageResponse_payload :: Lens.Lens' GetRetainedMessageResponse (Prelude.Maybe Prelude.ByteString)
getRetainedMessageResponse_payload :: Lens' GetRetainedMessageResponse (Maybe ByteString)
getRetainedMessageResponse_payload = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessageResponse' {Maybe Base64
payload :: Maybe Base64
$sel:payload:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Base64
payload} -> Maybe Base64
payload) (\s :: GetRetainedMessageResponse
s@GetRetainedMessageResponse' {} Maybe Base64
a -> GetRetainedMessageResponse
s {$sel:payload:GetRetainedMessageResponse' :: Maybe Base64
payload = Maybe Base64
a} :: GetRetainedMessageResponse) 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 Iso' Base64 ByteString
Data._Base64

-- | The quality of service (QoS) level used to publish the retained message.
getRetainedMessageResponse_qos :: Lens.Lens' GetRetainedMessageResponse (Prelude.Maybe Prelude.Natural)
getRetainedMessageResponse_qos :: Lens' GetRetainedMessageResponse (Maybe Natural)
getRetainedMessageResponse_qos = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessageResponse' {Maybe Natural
qos :: Maybe Natural
$sel:qos:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Natural
qos} -> Maybe Natural
qos) (\s :: GetRetainedMessageResponse
s@GetRetainedMessageResponse' {} Maybe Natural
a -> GetRetainedMessageResponse
s {$sel:qos:GetRetainedMessageResponse' :: Maybe Natural
qos = Maybe Natural
a} :: GetRetainedMessageResponse)

-- | The topic name to which the retained message was published.
getRetainedMessageResponse_topic :: Lens.Lens' GetRetainedMessageResponse (Prelude.Maybe Prelude.Text)
getRetainedMessageResponse_topic :: Lens' GetRetainedMessageResponse (Maybe Text)
getRetainedMessageResponse_topic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessageResponse' {Maybe Text
topic :: Maybe Text
$sel:topic:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Text
topic} -> Maybe Text
topic) (\s :: GetRetainedMessageResponse
s@GetRetainedMessageResponse' {} Maybe Text
a -> GetRetainedMessageResponse
s {$sel:topic:GetRetainedMessageResponse' :: Maybe Text
topic = Maybe Text
a} :: GetRetainedMessageResponse)

-- | The response's http status code.
getRetainedMessageResponse_httpStatus :: Lens.Lens' GetRetainedMessageResponse Prelude.Int
getRetainedMessageResponse_httpStatus :: Lens' GetRetainedMessageResponse Int
getRetainedMessageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRetainedMessageResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRetainedMessageResponse
s@GetRetainedMessageResponse' {} Int
a -> GetRetainedMessageResponse
s {$sel:httpStatus:GetRetainedMessageResponse' :: Int
httpStatus = Int
a} :: GetRetainedMessageResponse)

instance Prelude.NFData GetRetainedMessageResponse where
  rnf :: GetRetainedMessageResponse -> ()
rnf GetRetainedMessageResponse' {Int
Maybe Integer
Maybe Natural
Maybe Text
Maybe Base64
httpStatus :: Int
topic :: Maybe Text
qos :: Maybe Natural
payload :: Maybe Base64
lastModifiedTime :: Maybe Integer
$sel:httpStatus:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Int
$sel:topic:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Text
$sel:qos:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Natural
$sel:payload:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Base64
$sel:lastModifiedTime:GetRetainedMessageResponse' :: GetRetainedMessageResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Base64
payload
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
qos
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
topic
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus