{-# 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.Kafka.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 MSK configuration.
module Amazonka.Kafka.CreateConfiguration
  ( -- * Creating a Request
    CreateConfiguration (..),
    newCreateConfiguration,

    -- * Request Lenses
    createConfiguration_description,
    createConfiguration_kafkaVersions,
    createConfiguration_serverProperties,
    createConfiguration_name,

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

    -- * Response Lenses
    createConfigurationResponse_arn,
    createConfigurationResponse_creationTime,
    createConfigurationResponse_latestRevision,
    createConfigurationResponse_name,
    createConfigurationResponse_state,
    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.Kafka.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateConfiguration' smart constructor.
data CreateConfiguration = CreateConfiguration'
  { -- | The description of the configuration.
    CreateConfiguration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The versions of Apache Kafka with which you can use this MSK
    -- configuration.
    CreateConfiguration -> Maybe [Text]
kafkaVersions :: Prelude.Maybe [Prelude.Text],
    -- | Contents of the server.properties file. When using the API, you must
    -- ensure that the contents of the file are base64 encoded. When using the
    -- AWS Management Console, the SDK, or the AWS CLI, the contents of
    -- server.properties can be in plaintext.
    CreateConfiguration -> Base64
serverProperties :: Data.Base64,
    -- | The name of the configuration.
    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:
--
-- 'description', 'createConfiguration_description' - The description of the configuration.
--
-- 'kafkaVersions', 'createConfiguration_kafkaVersions' - The versions of Apache Kafka with which you can use this MSK
-- configuration.
--
-- 'serverProperties', 'createConfiguration_serverProperties' - Contents of the server.properties file. When using the API, you must
-- ensure that the contents of the file are base64 encoded. When using the
-- AWS Management Console, the SDK, or the AWS CLI, the contents of
-- server.properties can be in plaintext.--
-- -- /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.
--
-- 'name', 'createConfiguration_name' - The name of the configuration.
newCreateConfiguration ::
  -- | 'serverProperties'
  Prelude.ByteString ->
  -- | 'name'
  Prelude.Text ->
  CreateConfiguration
newCreateConfiguration :: ByteString -> Text -> CreateConfiguration
newCreateConfiguration ByteString
pServerProperties_ Text
pName_ =
  CreateConfiguration'
    { $sel:description:CreateConfiguration' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:kafkaVersions:CreateConfiguration' :: Maybe [Text]
kafkaVersions = forall a. Maybe a
Prelude.Nothing,
      $sel:serverProperties:CreateConfiguration' :: Base64
serverProperties =
        Iso' Base64 ByteString
Data._Base64 forall t b. AReview t b -> b -> t
Lens.# ByteString
pServerProperties_,
      $sel:name:CreateConfiguration' :: Text
name = Text
pName_
    }

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

-- | The versions of Apache Kafka with which you can use this MSK
-- configuration.
createConfiguration_kafkaVersions :: Lens.Lens' CreateConfiguration (Prelude.Maybe [Prelude.Text])
createConfiguration_kafkaVersions :: Lens' CreateConfiguration (Maybe [Text])
createConfiguration_kafkaVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfiguration' {Maybe [Text]
kafkaVersions :: Maybe [Text]
$sel:kafkaVersions:CreateConfiguration' :: CreateConfiguration -> Maybe [Text]
kafkaVersions} -> Maybe [Text]
kafkaVersions) (\s :: CreateConfiguration
s@CreateConfiguration' {} Maybe [Text]
a -> CreateConfiguration
s {$sel:kafkaVersions:CreateConfiguration' :: Maybe [Text]
kafkaVersions = Maybe [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

-- | Contents of the server.properties file. When using the API, you must
-- ensure that the contents of the file are base64 encoded. When using the
-- AWS Management Console, the SDK, or the AWS CLI, the contents of
-- server.properties can be in plaintext.--
-- -- /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.
createConfiguration_serverProperties :: Lens.Lens' CreateConfiguration Prelude.ByteString
createConfiguration_serverProperties :: Lens' CreateConfiguration ByteString
createConfiguration_serverProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfiguration' {Base64
serverProperties :: Base64
$sel:serverProperties:CreateConfiguration' :: CreateConfiguration -> Base64
serverProperties} -> Base64
serverProperties) (\s :: CreateConfiguration
s@CreateConfiguration' {} Base64
a -> CreateConfiguration
s {$sel:serverProperties:CreateConfiguration' :: Base64
serverProperties = Base64
a} :: CreateConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

-- | The name of the configuration.
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 ISO8601
-> Maybe ConfigurationRevision
-> Maybe Text
-> Maybe ConfigurationState
-> 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
"creationTime")
            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
"state")
            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 [Text]
Maybe Text
Text
Base64
name :: Text
serverProperties :: Base64
kafkaVersions :: Maybe [Text]
description :: Maybe Text
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:serverProperties:CreateConfiguration' :: CreateConfiguration -> Base64
$sel:kafkaVersions:CreateConfiguration' :: CreateConfiguration -> Maybe [Text]
$sel:description:CreateConfiguration' :: CreateConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
kafkaVersions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Base64
serverProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateConfiguration where
  rnf :: CreateConfiguration -> ()
rnf CreateConfiguration' {Maybe [Text]
Maybe Text
Text
Base64
name :: Text
serverProperties :: Base64
kafkaVersions :: Maybe [Text]
description :: Maybe Text
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:serverProperties:CreateConfiguration' :: CreateConfiguration -> Base64
$sel:kafkaVersions:CreateConfiguration' :: CreateConfiguration -> Maybe [Text]
$sel:description:CreateConfiguration' :: CreateConfiguration -> Maybe Text
..} =
    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 [Text]
kafkaVersions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Base64
serverProperties
      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 [Text]
Maybe Text
Text
Base64
name :: Text
serverProperties :: Base64
kafkaVersions :: Maybe [Text]
description :: Maybe Text
$sel:name:CreateConfiguration' :: CreateConfiguration -> Text
$sel:serverProperties:CreateConfiguration' :: CreateConfiguration -> Base64
$sel:kafkaVersions:CreateConfiguration' :: CreateConfiguration -> Maybe [Text]
$sel:description:CreateConfiguration' :: CreateConfiguration -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            (Key
"kafkaVersions" 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]
kafkaVersions,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"serverProperties" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Base64
serverProperties),
            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'
  { -- | The Amazon Resource Name (ARN) of the configuration.
    CreateConfigurationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time when the configuration was created.
    CreateConfigurationResponse -> Maybe ISO8601
creationTime :: Prelude.Maybe Data.ISO8601,
    -- | Latest revision of the configuration.
    CreateConfigurationResponse -> Maybe ConfigurationRevision
latestRevision :: Prelude.Maybe ConfigurationRevision,
    -- | The name of the configuration.
    CreateConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The state of the configuration. The possible states are ACTIVE,
    -- DELETING, and DELETE_FAILED.
    CreateConfigurationResponse -> Maybe ConfigurationState
state :: Prelude.Maybe ConfigurationState,
    -- | 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' - The Amazon Resource Name (ARN) of the configuration.
--
-- 'creationTime', 'createConfigurationResponse_creationTime' - The time when the configuration was created.
--
-- 'latestRevision', 'createConfigurationResponse_latestRevision' - Latest revision of the configuration.
--
-- 'name', 'createConfigurationResponse_name' - The name of the configuration.
--
-- 'state', 'createConfigurationResponse_state' - The state of the configuration. The possible states are ACTIVE,
-- DELETING, and DELETE_FAILED.
--
-- '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:creationTime:CreateConfigurationResponse' :: Maybe ISO8601
creationTime = 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:state:CreateConfigurationResponse' :: Maybe ConfigurationState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The time when the configuration was created.
createConfigurationResponse_creationTime :: Lens.Lens' CreateConfigurationResponse (Prelude.Maybe Prelude.UTCTime)
createConfigurationResponse_creationTime :: Lens' CreateConfigurationResponse (Maybe UTCTime)
createConfigurationResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationResponse' {Maybe ISO8601
creationTime :: Maybe ISO8601
$sel:creationTime:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ISO8601
creationTime} -> Maybe ISO8601
creationTime) (\s :: CreateConfigurationResponse
s@CreateConfigurationResponse' {} Maybe ISO8601
a -> CreateConfigurationResponse
s {$sel:creationTime:CreateConfigurationResponse' :: Maybe ISO8601
creationTime = 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

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

-- | The name of the configuration.
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 state of the configuration. The possible states are ACTIVE,
-- DELETING, and DELETE_FAILED.
createConfigurationResponse_state :: Lens.Lens' CreateConfigurationResponse (Prelude.Maybe ConfigurationState)
createConfigurationResponse_state :: Lens' CreateConfigurationResponse (Maybe ConfigurationState)
createConfigurationResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationResponse' {Maybe ConfigurationState
state :: Maybe ConfigurationState
$sel:state:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ConfigurationState
state} -> Maybe ConfigurationState
state) (\s :: CreateConfigurationResponse
s@CreateConfigurationResponse' {} Maybe ConfigurationState
a -> CreateConfigurationResponse
s {$sel:state:CreateConfigurationResponse' :: Maybe ConfigurationState
state = Maybe ConfigurationState
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 ConfigurationRevision
Maybe ConfigurationState
httpStatus :: Int
state :: Maybe ConfigurationState
name :: Maybe Text
latestRevision :: Maybe ConfigurationRevision
creationTime :: Maybe ISO8601
arn :: Maybe Text
$sel:httpStatus:CreateConfigurationResponse' :: CreateConfigurationResponse -> Int
$sel:state:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ConfigurationState
$sel:name:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe Text
$sel:latestRevision:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ConfigurationRevision
$sel:creationTime:CreateConfigurationResponse' :: CreateConfigurationResponse -> Maybe ISO8601
$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 ISO8601
creationTime
      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 ConfigurationState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus