{-# 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.MQ.DescribeConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the specified configuration.
module Amazonka.MQ.DescribeConfiguration
  ( -- * Creating a Request
    DescribeConfiguration (..),
    newDescribeConfiguration,

    -- * Request Lenses
    describeConfiguration_configurationId,

    -- * Destructuring the Response
    DescribeConfigurationResponse (..),
    newDescribeConfigurationResponse,

    -- * Response Lenses
    describeConfigurationResponse_arn,
    describeConfigurationResponse_authenticationStrategy,
    describeConfigurationResponse_created,
    describeConfigurationResponse_description,
    describeConfigurationResponse_engineType,
    describeConfigurationResponse_engineVersion,
    describeConfigurationResponse_id,
    describeConfigurationResponse_latestRevision,
    describeConfigurationResponse_name,
    describeConfigurationResponse_tags,
    describeConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeConfiguration' smart constructor.
data DescribeConfiguration = DescribeConfiguration'
  { -- | The unique ID that Amazon MQ generates for the configuration.
    DescribeConfiguration -> Text
configurationId :: Prelude.Text
  }
  deriving (DescribeConfiguration -> DescribeConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfiguration -> DescribeConfiguration -> Bool
$c/= :: DescribeConfiguration -> DescribeConfiguration -> Bool
== :: DescribeConfiguration -> DescribeConfiguration -> Bool
$c== :: DescribeConfiguration -> DescribeConfiguration -> Bool
Prelude.Eq, ReadPrec [DescribeConfiguration]
ReadPrec DescribeConfiguration
Int -> ReadS DescribeConfiguration
ReadS [DescribeConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfiguration]
$creadListPrec :: ReadPrec [DescribeConfiguration]
readPrec :: ReadPrec DescribeConfiguration
$creadPrec :: ReadPrec DescribeConfiguration
readList :: ReadS [DescribeConfiguration]
$creadList :: ReadS [DescribeConfiguration]
readsPrec :: Int -> ReadS DescribeConfiguration
$creadsPrec :: Int -> ReadS DescribeConfiguration
Prelude.Read, Int -> DescribeConfiguration -> ShowS
[DescribeConfiguration] -> ShowS
DescribeConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfiguration] -> ShowS
$cshowList :: [DescribeConfiguration] -> ShowS
show :: DescribeConfiguration -> String
$cshow :: DescribeConfiguration -> String
showsPrec :: Int -> DescribeConfiguration -> ShowS
$cshowsPrec :: Int -> DescribeConfiguration -> ShowS
Prelude.Show, forall x. Rep DescribeConfiguration x -> DescribeConfiguration
forall x. DescribeConfiguration -> Rep DescribeConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeConfiguration x -> DescribeConfiguration
$cfrom :: forall x. DescribeConfiguration -> Rep DescribeConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfiguration' 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:
--
-- 'configurationId', 'describeConfiguration_configurationId' - The unique ID that Amazon MQ generates for the configuration.
newDescribeConfiguration ::
  -- | 'configurationId'
  Prelude.Text ->
  DescribeConfiguration
newDescribeConfiguration :: Text -> DescribeConfiguration
newDescribeConfiguration Text
pConfigurationId_ =
  DescribeConfiguration'
    { $sel:configurationId:DescribeConfiguration' :: Text
configurationId =
        Text
pConfigurationId_
    }

-- | The unique ID that Amazon MQ generates for the configuration.
describeConfiguration_configurationId :: Lens.Lens' DescribeConfiguration Prelude.Text
describeConfiguration_configurationId :: Lens' DescribeConfiguration Text
describeConfiguration_configurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfiguration' {Text
configurationId :: Text
$sel:configurationId:DescribeConfiguration' :: DescribeConfiguration -> Text
configurationId} -> Text
configurationId) (\s :: DescribeConfiguration
s@DescribeConfiguration' {} Text
a -> DescribeConfiguration
s {$sel:configurationId:DescribeConfiguration' :: Text
configurationId = Text
a} :: DescribeConfiguration)

instance Core.AWSRequest DescribeConfiguration where
  type
    AWSResponse DescribeConfiguration =
      DescribeConfigurationResponse
  request :: (Service -> Service)
-> DescribeConfiguration -> Request DescribeConfiguration
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 DescribeConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeConfiguration)))
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 Text
-> Maybe AuthenticationStrategy
-> Maybe ISO8601
-> Maybe Text
-> Maybe EngineType
-> Maybe Text
-> Maybe Text
-> Maybe ConfigurationRevision
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Int
-> DescribeConfigurationResponse
DescribeConfigurationResponse'
            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
"arn")
            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
"authenticationStrategy")
            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
"created")
            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
"description")
            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
"engineType")
            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
"engineVersion")
            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
"id")
            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
"latestRevision")
            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
"name")
            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
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DescribeConfiguration where
  hashWithSalt :: Int -> DescribeConfiguration -> Int
hashWithSalt Int
_salt DescribeConfiguration' {Text
configurationId :: Text
$sel:configurationId:DescribeConfiguration' :: DescribeConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationId

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

instance Data.ToHeaders DescribeConfiguration where
  toHeaders :: DescribeConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

-- | /See:/ 'newDescribeConfigurationResponse' smart constructor.
data DescribeConfigurationResponse = DescribeConfigurationResponse'
  { -- | Required. The ARN of the configuration.
    DescribeConfigurationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Optional. The authentication strategy associated with the configuration.
    -- The default is SIMPLE.
    DescribeConfigurationResponse -> Maybe AuthenticationStrategy
authenticationStrategy :: Prelude.Maybe AuthenticationStrategy,
    -- | Required. The date and time of the configuration revision.
    DescribeConfigurationResponse -> Maybe ISO8601
created :: Prelude.Maybe Data.ISO8601,
    -- | Required. The description of the configuration.
    DescribeConfigurationResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Required. The type of broker engine. Currently, Amazon MQ supports
    -- ACTIVEMQ and RABBITMQ.
    DescribeConfigurationResponse -> Maybe EngineType
engineType :: Prelude.Maybe EngineType,
    -- | Required. The broker engine\'s version. For a list of supported engine
    -- versions, see,
    -- <https://docs.aws.amazon.com//amazon-mq/latest/developer-guide/broker-engine.html Supported engines>.
    DescribeConfigurationResponse -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | Required. The unique ID that Amazon MQ generates for the configuration.
    DescribeConfigurationResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | Required. The latest revision of the configuration.
    DescribeConfigurationResponse -> Maybe ConfigurationRevision
latestRevision :: Prelude.Maybe ConfigurationRevision,
    -- | Required. The name of the configuration. This value can contain only
    -- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
    -- ~). This value must be 1-150 characters long.
    DescribeConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The list of all tags associated with this configuration.
    DescribeConfigurationResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    DescribeConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConfigurationResponse
-> DescribeConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfigurationResponse
-> DescribeConfigurationResponse -> Bool
$c/= :: DescribeConfigurationResponse
-> DescribeConfigurationResponse -> Bool
== :: DescribeConfigurationResponse
-> DescribeConfigurationResponse -> Bool
$c== :: DescribeConfigurationResponse
-> DescribeConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConfigurationResponse]
ReadPrec DescribeConfigurationResponse
Int -> ReadS DescribeConfigurationResponse
ReadS [DescribeConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfigurationResponse]
$creadListPrec :: ReadPrec [DescribeConfigurationResponse]
readPrec :: ReadPrec DescribeConfigurationResponse
$creadPrec :: ReadPrec DescribeConfigurationResponse
readList :: ReadS [DescribeConfigurationResponse]
$creadList :: ReadS [DescribeConfigurationResponse]
readsPrec :: Int -> ReadS DescribeConfigurationResponse
$creadsPrec :: Int -> ReadS DescribeConfigurationResponse
Prelude.Read, Int -> DescribeConfigurationResponse -> ShowS
[DescribeConfigurationResponse] -> ShowS
DescribeConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfigurationResponse] -> ShowS
$cshowList :: [DescribeConfigurationResponse] -> ShowS
show :: DescribeConfigurationResponse -> String
$cshow :: DescribeConfigurationResponse -> String
showsPrec :: Int -> DescribeConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DescribeConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConfigurationResponse x
-> DescribeConfigurationResponse
forall x.
DescribeConfigurationResponse
-> Rep DescribeConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConfigurationResponse x
-> DescribeConfigurationResponse
$cfrom :: forall x.
DescribeConfigurationResponse
-> Rep DescribeConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfigurationResponse' 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:
--
-- 'arn', 'describeConfigurationResponse_arn' - Required. The ARN of the configuration.
--
-- 'authenticationStrategy', 'describeConfigurationResponse_authenticationStrategy' - Optional. The authentication strategy associated with the configuration.
-- The default is SIMPLE.
--
-- 'created', 'describeConfigurationResponse_created' - Required. The date and time of the configuration revision.
--
-- 'description', 'describeConfigurationResponse_description' - Required. The description of the configuration.
--
-- 'engineType', 'describeConfigurationResponse_engineType' - Required. The type of broker engine. Currently, Amazon MQ supports
-- ACTIVEMQ and RABBITMQ.
--
-- 'engineVersion', 'describeConfigurationResponse_engineVersion' - Required. The broker engine\'s version. For a list of supported engine
-- versions, see,
-- <https://docs.aws.amazon.com//amazon-mq/latest/developer-guide/broker-engine.html Supported engines>.
--
-- 'id', 'describeConfigurationResponse_id' - Required. The unique ID that Amazon MQ generates for the configuration.
--
-- 'latestRevision', 'describeConfigurationResponse_latestRevision' - Required. The latest revision of the configuration.
--
-- 'name', 'describeConfigurationResponse_name' - Required. The name of the configuration. This value can contain only
-- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
-- ~). This value must be 1-150 characters long.
--
-- 'tags', 'describeConfigurationResponse_tags' - The list of all tags associated with this configuration.
--
-- 'httpStatus', 'describeConfigurationResponse_httpStatus' - The response's http status code.
newDescribeConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConfigurationResponse
newDescribeConfigurationResponse :: Int -> DescribeConfigurationResponse
newDescribeConfigurationResponse Int
pHttpStatus_ =
  DescribeConfigurationResponse'
    { $sel:arn:DescribeConfigurationResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationStrategy:DescribeConfigurationResponse' :: Maybe AuthenticationStrategy
authenticationStrategy = forall a. Maybe a
Prelude.Nothing,
      $sel:created:DescribeConfigurationResponse' :: Maybe ISO8601
created = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeConfigurationResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:engineType:DescribeConfigurationResponse' :: Maybe EngineType
engineType = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:DescribeConfigurationResponse' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DescribeConfigurationResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:latestRevision:DescribeConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeConfigurationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:DescribeConfigurationResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Required. The ARN of the configuration.
describeConfigurationResponse_arn :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.Text)
describeConfigurationResponse_arn :: Lens' DescribeConfigurationResponse (Maybe Text)
describeConfigurationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe Text
a -> DescribeConfigurationResponse
s {$sel:arn:DescribeConfigurationResponse' :: Maybe Text
arn = Maybe Text
a} :: DescribeConfigurationResponse)

-- | Optional. The authentication strategy associated with the configuration.
-- The default is SIMPLE.
describeConfigurationResponse_authenticationStrategy :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe AuthenticationStrategy)
describeConfigurationResponse_authenticationStrategy :: Lens' DescribeConfigurationResponse (Maybe AuthenticationStrategy)
describeConfigurationResponse_authenticationStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe AuthenticationStrategy
authenticationStrategy :: Maybe AuthenticationStrategy
$sel:authenticationStrategy:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe AuthenticationStrategy
authenticationStrategy} -> Maybe AuthenticationStrategy
authenticationStrategy) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe AuthenticationStrategy
a -> DescribeConfigurationResponse
s {$sel:authenticationStrategy:DescribeConfigurationResponse' :: Maybe AuthenticationStrategy
authenticationStrategy = Maybe AuthenticationStrategy
a} :: DescribeConfigurationResponse)

-- | Required. The date and time of the configuration revision.
describeConfigurationResponse_created :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.UTCTime)
describeConfigurationResponse_created :: Lens' DescribeConfigurationResponse (Maybe UTCTime)
describeConfigurationResponse_created = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe ISO8601
created :: Maybe ISO8601
$sel:created:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe ISO8601
created} -> Maybe ISO8601
created) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe ISO8601
a -> DescribeConfigurationResponse
s {$sel:created:DescribeConfigurationResponse' :: Maybe ISO8601
created = Maybe ISO8601
a} :: DescribeConfigurationResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Required. The description of the configuration.
describeConfigurationResponse_description :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.Text)
describeConfigurationResponse_description :: Lens' DescribeConfigurationResponse (Maybe Text)
describeConfigurationResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe Text
a -> DescribeConfigurationResponse
s {$sel:description:DescribeConfigurationResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeConfigurationResponse)

-- | Required. The type of broker engine. Currently, Amazon MQ supports
-- ACTIVEMQ and RABBITMQ.
describeConfigurationResponse_engineType :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe EngineType)
describeConfigurationResponse_engineType :: Lens' DescribeConfigurationResponse (Maybe EngineType)
describeConfigurationResponse_engineType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe EngineType
engineType :: Maybe EngineType
$sel:engineType:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe EngineType
engineType} -> Maybe EngineType
engineType) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe EngineType
a -> DescribeConfigurationResponse
s {$sel:engineType:DescribeConfigurationResponse' :: Maybe EngineType
engineType = Maybe EngineType
a} :: DescribeConfigurationResponse)

-- | Required. The broker engine\'s version. For a list of supported engine
-- versions, see,
-- <https://docs.aws.amazon.com//amazon-mq/latest/developer-guide/broker-engine.html Supported engines>.
describeConfigurationResponse_engineVersion :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.Text)
describeConfigurationResponse_engineVersion :: Lens' DescribeConfigurationResponse (Maybe Text)
describeConfigurationResponse_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe Text
a -> DescribeConfigurationResponse
s {$sel:engineVersion:DescribeConfigurationResponse' :: Maybe Text
engineVersion = Maybe Text
a} :: DescribeConfigurationResponse)

-- | Required. The unique ID that Amazon MQ generates for the configuration.
describeConfigurationResponse_id :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.Text)
describeConfigurationResponse_id :: Lens' DescribeConfigurationResponse (Maybe Text)
describeConfigurationResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe Text
id :: Maybe Text
$sel:id:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe Text
a -> DescribeConfigurationResponse
s {$sel:id:DescribeConfigurationResponse' :: Maybe Text
id = Maybe Text
a} :: DescribeConfigurationResponse)

-- | Required. The latest revision of the configuration.
describeConfigurationResponse_latestRevision :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe ConfigurationRevision)
describeConfigurationResponse_latestRevision :: Lens' DescribeConfigurationResponse (Maybe ConfigurationRevision)
describeConfigurationResponse_latestRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe ConfigurationRevision
latestRevision :: Maybe ConfigurationRevision
$sel:latestRevision:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe ConfigurationRevision
latestRevision} -> Maybe ConfigurationRevision
latestRevision) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe ConfigurationRevision
a -> DescribeConfigurationResponse
s {$sel:latestRevision:DescribeConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = Maybe ConfigurationRevision
a} :: DescribeConfigurationResponse)

-- | Required. The name of the configuration. This value can contain only
-- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
-- ~). This value must be 1-150 characters long.
describeConfigurationResponse_name :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe Prelude.Text)
describeConfigurationResponse_name :: Lens' DescribeConfigurationResponse (Maybe Text)
describeConfigurationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe Text
name :: Maybe Text
$sel:name:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe Text
a -> DescribeConfigurationResponse
s {$sel:name:DescribeConfigurationResponse' :: Maybe Text
name = Maybe Text
a} :: DescribeConfigurationResponse)

-- | The list of all tags associated with this configuration.
describeConfigurationResponse_tags :: Lens.Lens' DescribeConfigurationResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeConfigurationResponse_tags :: Lens' DescribeConfigurationResponse (Maybe (HashMap Text Text))
describeConfigurationResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: DescribeConfigurationResponse
s@DescribeConfigurationResponse' {} Maybe (HashMap Text Text)
a -> DescribeConfigurationResponse
s {$sel:tags:DescribeConfigurationResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: DescribeConfigurationResponse) 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

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

instance Prelude.NFData DescribeConfigurationResponse where
  rnf :: DescribeConfigurationResponse -> ()
rnf DescribeConfigurationResponse' {Int
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
Maybe AuthenticationStrategy
Maybe ConfigurationRevision
Maybe EngineType
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
latestRevision :: Maybe ConfigurationRevision
id :: Maybe Text
engineVersion :: Maybe Text
engineType :: Maybe EngineType
description :: Maybe Text
created :: Maybe ISO8601
authenticationStrategy :: Maybe AuthenticationStrategy
arn :: Maybe Text
$sel:httpStatus:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Int
$sel:tags:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe (HashMap Text Text)
$sel:name:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
$sel:latestRevision:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe ConfigurationRevision
$sel:id:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
$sel:engineVersion:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
$sel:engineType:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe EngineType
$sel:description:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
$sel:created:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe ISO8601
$sel:authenticationStrategy:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe AuthenticationStrategy
$sel:arn:DescribeConfigurationResponse' :: DescribeConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationStrategy
authenticationStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
created
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EngineType
engineType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfigurationRevision
latestRevision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus