{-# 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.CreateConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new configuration for the specified configuration name. Amazon
-- MQ uses the default configuration (the engine type and version).
module Amazonka.MQ.CreateConfiguration
  ( -- * Creating a Request
    CreateConfiguration (..),
    newCreateConfiguration,

    -- * Request Lenses
    createConfiguration_authenticationStrategy,
    createConfiguration_tags,
    createConfiguration_engineVersion,
    createConfiguration_engineType,
    createConfiguration_name,

    -- * Destructuring the Response
    CreateConfigurationResponse (..),
    newCreateConfigurationResponse,

    -- * Response Lenses
    createConfigurationResponse_arn,
    createConfigurationResponse_authenticationStrategy,
    createConfigurationResponse_created,
    createConfigurationResponse_id,
    createConfigurationResponse_latestRevision,
    createConfigurationResponse_name,
    createConfigurationResponse_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

-- | Creates a new configuration for the specified configuration name. Amazon
-- MQ uses the default configuration (the engine type and version).
--
-- /See:/ 'newCreateConfiguration' smart constructor.
data CreateConfiguration = CreateConfiguration'
  { -- | Optional. The authentication strategy associated with the configuration.
    -- The default is SIMPLE.
    CreateConfiguration -> Maybe AuthenticationStrategy
authenticationStrategy :: Prelude.Maybe AuthenticationStrategy,
    -- | Create tags when creating the configuration.
    CreateConfiguration -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | 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>.
    CreateConfiguration -> Text
engineVersion :: Prelude.Text,
    -- | Required. The type of broker engine. Currently, Amazon MQ supports
    -- ACTIVEMQ and RABBITMQ.
    CreateConfiguration -> EngineType
engineType :: EngineType,
    -- | 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.
    CreateConfiguration -> Text
name :: Prelude.Text
  }
  deriving (CreateConfiguration -> CreateConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConfiguration -> CreateConfiguration -> Bool
$c/= :: CreateConfiguration -> CreateConfiguration -> Bool
== :: CreateConfiguration -> CreateConfiguration -> Bool
$c== :: CreateConfiguration -> CreateConfiguration -> Bool
Prelude.Eq, ReadPrec [CreateConfiguration]
ReadPrec CreateConfiguration
Int -> ReadS CreateConfiguration
ReadS [CreateConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConfiguration]
$creadListPrec :: ReadPrec [CreateConfiguration]
readPrec :: ReadPrec CreateConfiguration
$creadPrec :: ReadPrec CreateConfiguration
readList :: ReadS [CreateConfiguration]
$creadList :: ReadS [CreateConfiguration]
readsPrec :: Int -> ReadS CreateConfiguration
$creadsPrec :: Int -> ReadS CreateConfiguration
Prelude.Read, Int -> CreateConfiguration -> ShowS
[CreateConfiguration] -> ShowS
CreateConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConfiguration] -> ShowS
$cshowList :: [CreateConfiguration] -> ShowS
show :: CreateConfiguration -> String
$cshow :: CreateConfiguration -> String
showsPrec :: Int -> CreateConfiguration -> ShowS
$cshowsPrec :: Int -> CreateConfiguration -> ShowS
Prelude.Show, forall x. Rep CreateConfiguration x -> CreateConfiguration
forall x. CreateConfiguration -> Rep CreateConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateConfiguration x -> CreateConfiguration
$cfrom :: forall x. CreateConfiguration -> Rep CreateConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'CreateConfiguration' 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:
--
-- 'authenticationStrategy', 'createConfiguration_authenticationStrategy' - Optional. The authentication strategy associated with the configuration.
-- The default is SIMPLE.
--
-- 'tags', 'createConfiguration_tags' - Create tags when creating the configuration.
--
-- 'engineVersion', 'createConfiguration_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>.
--
-- 'engineType', 'createConfiguration_engineType' - Required. The type of broker engine. Currently, Amazon MQ supports
-- ACTIVEMQ and RABBITMQ.
--
-- 'name', 'createConfiguration_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.
newCreateConfiguration ::
  -- | 'engineVersion'
  Prelude.Text ->
  -- | 'engineType'
  EngineType ->
  -- | 'name'
  Prelude.Text ->
  CreateConfiguration
newCreateConfiguration :: Text -> EngineType -> Text -> CreateConfiguration
newCreateConfiguration
  Text
pEngineVersion_
  EngineType
pEngineType_
  Text
pName_ =
    CreateConfiguration'
      { $sel:authenticationStrategy:CreateConfiguration' :: Maybe AuthenticationStrategy
authenticationStrategy =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateConfiguration' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:engineVersion:CreateConfiguration' :: Text
engineVersion = Text
pEngineVersion_,
        $sel:engineType:CreateConfiguration' :: EngineType
engineType = EngineType
pEngineType_,
        $sel:name:CreateConfiguration' :: Text
name = Text
pName_
      }

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

-- | Create tags when creating the configuration.
createConfiguration_tags :: Lens.Lens' CreateConfiguration (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createConfiguration_tags :: Lens' CreateConfiguration (Maybe (HashMap Text Text))
createConfiguration_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfiguration' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateConfiguration' :: CreateConfiguration -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateConfiguration
s@CreateConfiguration' {} Maybe (HashMap Text Text)
a -> CreateConfiguration
s {$sel:tags:CreateConfiguration' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateConfiguration) 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

-- | 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>.
createConfiguration_engineVersion :: Lens.Lens' CreateConfiguration Prelude.Text
createConfiguration_engineVersion :: Lens' CreateConfiguration Text
createConfiguration_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfiguration' {Text
engineVersion :: Text
$sel:engineVersion:CreateConfiguration' :: CreateConfiguration -> Text
engineVersion} -> Text
engineVersion) (\s :: CreateConfiguration
s@CreateConfiguration' {} Text
a -> CreateConfiguration
s {$sel:engineVersion:CreateConfiguration' :: Text
engineVersion = Text
a} :: CreateConfiguration)

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

-- | 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.
createConfiguration_name :: Lens.Lens' CreateConfiguration Prelude.Text
createConfiguration_name :: Lens' CreateConfiguration Text
createConfiguration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfiguration' {Text
name :: Text
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
name} -> Text
name) (\s :: CreateConfiguration
s@CreateConfiguration' {} Text
a -> CreateConfiguration
s {$sel:name:CreateConfiguration' :: Text
name = Text
a} :: CreateConfiguration)

instance Core.AWSRequest CreateConfiguration where
  type
    AWSResponse CreateConfiguration =
      CreateConfigurationResponse
  request :: (Service -> Service)
-> CreateConfiguration -> Request CreateConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateConfiguration)))
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 ConfigurationRevision
-> Maybe Text
-> Int
-> CreateConfigurationResponse
CreateConfigurationResponse'
            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
"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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateConfiguration where
  hashWithSalt :: Int -> CreateConfiguration -> Int
hashWithSalt Int
_salt CreateConfiguration' {Maybe (HashMap Text Text)
Maybe AuthenticationStrategy
Text
EngineType
name :: Text
engineType :: EngineType
engineVersion :: Text
tags :: Maybe (HashMap Text Text)
authenticationStrategy :: Maybe AuthenticationStrategy
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:engineType:CreateConfiguration' :: CreateConfiguration -> EngineType
$sel:engineVersion:CreateConfiguration' :: CreateConfiguration -> Text
$sel:tags:CreateConfiguration' :: CreateConfiguration -> Maybe (HashMap Text Text)
$sel:authenticationStrategy:CreateConfiguration' :: CreateConfiguration -> Maybe AuthenticationStrategy
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationStrategy
authenticationStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EngineType
engineType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateConfiguration where
  rnf :: CreateConfiguration -> ()
rnf CreateConfiguration' {Maybe (HashMap Text Text)
Maybe AuthenticationStrategy
Text
EngineType
name :: Text
engineType :: EngineType
engineVersion :: Text
tags :: Maybe (HashMap Text Text)
authenticationStrategy :: Maybe AuthenticationStrategy
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:engineType:CreateConfiguration' :: CreateConfiguration -> EngineType
$sel:engineVersion:CreateConfiguration' :: CreateConfiguration -> Text
$sel:tags:CreateConfiguration' :: CreateConfiguration -> Maybe (HashMap Text Text)
$sel:authenticationStrategy:CreateConfiguration' :: CreateConfiguration -> Maybe AuthenticationStrategy
..} =
    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 (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EngineType
engineType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateConfiguration where
  toHeaders :: CreateConfiguration -> 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.ToJSON CreateConfiguration where
  toJSON :: CreateConfiguration -> Value
toJSON CreateConfiguration' {Maybe (HashMap Text Text)
Maybe AuthenticationStrategy
Text
EngineType
name :: Text
engineType :: EngineType
engineVersion :: Text
tags :: Maybe (HashMap Text Text)
authenticationStrategy :: Maybe AuthenticationStrategy
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:engineType:CreateConfiguration' :: CreateConfiguration -> EngineType
$sel:engineVersion:CreateConfiguration' :: CreateConfiguration -> Text
$sel:tags:CreateConfiguration' :: CreateConfiguration -> Maybe (HashMap Text Text)
$sel:authenticationStrategy:CreateConfiguration' :: CreateConfiguration -> Maybe AuthenticationStrategy
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"authenticationStrategy" 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 AuthenticationStrategy
authenticationStrategy,
            (Key
"tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"engineVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
engineVersion),
            forall a. a -> Maybe a
Prelude.Just (Key
"engineType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= EngineType
engineType),
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

instance Data.ToPath CreateConfiguration where
  toPath :: CreateConfiguration -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/configurations"

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

-- | /See:/ 'newCreateConfigurationResponse' smart constructor.
data CreateConfigurationResponse = CreateConfigurationResponse'
  { -- | Required. The Amazon Resource Name (ARN) of the configuration.
    CreateConfigurationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Optional. The authentication strategy associated with the configuration.
    -- The default is SIMPLE.
    CreateConfigurationResponse -> Maybe AuthenticationStrategy
authenticationStrategy :: Prelude.Maybe AuthenticationStrategy,
    -- | Required. The date and time of the configuration.
    CreateConfigurationResponse -> Maybe ISO8601
created :: Prelude.Maybe Data.ISO8601,
    -- | Required. The unique ID that Amazon MQ generates for the configuration.
    CreateConfigurationResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The latest revision of the configuration.
    CreateConfigurationResponse -> 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.
    CreateConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateConfigurationResponse -> CreateConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConfigurationResponse -> CreateConfigurationResponse -> Bool
$c/= :: CreateConfigurationResponse -> CreateConfigurationResponse -> Bool
== :: CreateConfigurationResponse -> CreateConfigurationResponse -> Bool
$c== :: CreateConfigurationResponse -> CreateConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [CreateConfigurationResponse]
ReadPrec CreateConfigurationResponse
Int -> ReadS CreateConfigurationResponse
ReadS [CreateConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConfigurationResponse]
$creadListPrec :: ReadPrec [CreateConfigurationResponse]
readPrec :: ReadPrec CreateConfigurationResponse
$creadPrec :: ReadPrec CreateConfigurationResponse
readList :: ReadS [CreateConfigurationResponse]
$creadList :: ReadS [CreateConfigurationResponse]
readsPrec :: Int -> ReadS CreateConfigurationResponse
$creadsPrec :: Int -> ReadS CreateConfigurationResponse
Prelude.Read, Int -> CreateConfigurationResponse -> ShowS
[CreateConfigurationResponse] -> ShowS
CreateConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConfigurationResponse] -> ShowS
$cshowList :: [CreateConfigurationResponse] -> ShowS
show :: CreateConfigurationResponse -> String
$cshow :: CreateConfigurationResponse -> String
showsPrec :: Int -> CreateConfigurationResponse -> ShowS
$cshowsPrec :: Int -> CreateConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateConfigurationResponse x -> CreateConfigurationResponse
forall x.
CreateConfigurationResponse -> Rep CreateConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateConfigurationResponse x -> CreateConfigurationResponse
$cfrom :: forall x.
CreateConfigurationResponse -> Rep CreateConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateConfigurationResponse' 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', 'createConfigurationResponse_arn' - Required. The Amazon Resource Name (ARN) of the configuration.
--
-- 'authenticationStrategy', 'createConfigurationResponse_authenticationStrategy' - Optional. The authentication strategy associated with the configuration.
-- The default is SIMPLE.
--
-- 'created', 'createConfigurationResponse_created' - Required. The date and time of the configuration.
--
-- 'id', 'createConfigurationResponse_id' - Required. The unique ID that Amazon MQ generates for the configuration.
--
-- 'latestRevision', 'createConfigurationResponse_latestRevision' - The latest revision of the configuration.
--
-- 'name', 'createConfigurationResponse_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.
--
-- 'httpStatus', 'createConfigurationResponse_httpStatus' - The response's http status code.
newCreateConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateConfigurationResponse
newCreateConfigurationResponse :: Int -> CreateConfigurationResponse
newCreateConfigurationResponse Int
pHttpStatus_ =
  CreateConfigurationResponse'
    { $sel:arn:CreateConfigurationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationStrategy:CreateConfigurationResponse' :: Maybe AuthenticationStrategy
authenticationStrategy = forall a. Maybe a
Prelude.Nothing,
      $sel:created:CreateConfigurationResponse' :: Maybe ISO8601
created = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateConfigurationResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:latestRevision:CreateConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateConfigurationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | Required. The date and time of the configuration.
createConfigurationResponse_created :: Lens.Lens' CreateConfigurationResponse (Prelude.Maybe Prelude.UTCTime)
createConfigurationResponse_created :: Lens' CreateConfigurationResponse (Maybe UTCTime)
createConfigurationResponse_created = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationResponse' {Maybe ISO8601
created :: Maybe ISO8601
$sel:created:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ISO8601
created} -> Maybe ISO8601
created) (\s :: CreateConfigurationResponse
s@CreateConfigurationResponse' {} Maybe ISO8601
a -> CreateConfigurationResponse
s {$sel:created:CreateConfigurationResponse' :: Maybe ISO8601
created = Maybe ISO8601
a} :: CreateConfigurationResponse) 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 unique ID that Amazon MQ generates for the configuration.
createConfigurationResponse_id :: Lens.Lens' CreateConfigurationResponse (Prelude.Maybe Prelude.Text)
createConfigurationResponse_id :: Lens' CreateConfigurationResponse (Maybe Text)
createConfigurationResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateConfigurationResponse
s@CreateConfigurationResponse' {} Maybe Text
a -> CreateConfigurationResponse
s {$sel:id:CreateConfigurationResponse' :: Maybe Text
id = Maybe Text
a} :: CreateConfigurationResponse)

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

-- | 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.
createConfigurationResponse_name :: Lens.Lens' CreateConfigurationResponse (Prelude.Maybe Prelude.Text)
createConfigurationResponse_name :: Lens' CreateConfigurationResponse (Maybe Text)
createConfigurationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateConfigurationResponse
s@CreateConfigurationResponse' {} Maybe Text
a -> CreateConfigurationResponse
s {$sel:name:CreateConfigurationResponse' :: Maybe Text
name = Maybe Text
a} :: CreateConfigurationResponse)

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

instance Prelude.NFData CreateConfigurationResponse where
  rnf :: CreateConfigurationResponse -> ()
rnf CreateConfigurationResponse' {Int
Maybe Text
Maybe ISO8601
Maybe AuthenticationStrategy
Maybe ConfigurationRevision
httpStatus :: Int
name :: Maybe Text
latestRevision :: Maybe ConfigurationRevision
id :: Maybe Text
created :: Maybe ISO8601
authenticationStrategy :: Maybe AuthenticationStrategy
arn :: Maybe Text
$sel:httpStatus:CreateConfigurationResponse' :: CreateConfigurationResponse -> Int
$sel:name:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe Text
$sel:latestRevision:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ConfigurationRevision
$sel:id:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe Text
$sel:created:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ISO8601
$sel:authenticationStrategy:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe AuthenticationStrategy
$sel:arn:CreateConfigurationResponse' :: CreateConfigurationResponse -> 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
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 Int
httpStatus