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

    -- * Request Lenses
    updateConfiguration_description,
    updateConfiguration_configurationId,
    updateConfiguration_data,

    -- * Destructuring the Response
    UpdateConfigurationResponse (..),
    newUpdateConfigurationResponse,

    -- * Response Lenses
    updateConfigurationResponse_arn,
    updateConfigurationResponse_created,
    updateConfigurationResponse_id,
    updateConfigurationResponse_latestRevision,
    updateConfigurationResponse_name,
    updateConfigurationResponse_warnings,
    updateConfigurationResponse_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

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

-- |
-- Create a value of 'UpdateConfiguration' 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', 'updateConfiguration_description' - The description of the configuration.
--
-- 'configurationId', 'updateConfiguration_configurationId' - The unique ID that Amazon MQ generates for the configuration.
--
-- 'data'', 'updateConfiguration_data' - Required. The base64-encoded XML configuration.
newUpdateConfiguration ::
  -- | 'configurationId'
  Prelude.Text ->
  -- | 'data''
  Prelude.Text ->
  UpdateConfiguration
newUpdateConfiguration :: Text -> Text -> UpdateConfiguration
newUpdateConfiguration Text
pConfigurationId_ Text
pData_ =
  UpdateConfiguration'
    { $sel:description:UpdateConfiguration' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationId:UpdateConfiguration' :: Text
configurationId = Text
pConfigurationId_,
      $sel:data':UpdateConfiguration' :: Text
data' = Text
pData_
    }

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

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

-- | Required. The base64-encoded XML configuration.
updateConfiguration_data :: Lens.Lens' UpdateConfiguration Prelude.Text
updateConfiguration_data :: Lens' UpdateConfiguration Text
updateConfiguration_data = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfiguration' {Text
data' :: Text
$sel:data':UpdateConfiguration' :: UpdateConfiguration -> Text
data'} -> Text
data') (\s :: UpdateConfiguration
s@UpdateConfiguration' {} Text
a -> UpdateConfiguration
s {$sel:data':UpdateConfiguration' :: Text
data' = Text
a} :: UpdateConfiguration)

instance Core.AWSRequest UpdateConfiguration where
  type
    AWSResponse UpdateConfiguration =
      UpdateConfigurationResponse
  request :: (Service -> Service)
-> UpdateConfiguration -> Request UpdateConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateConfiguration)))
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 Text
-> Maybe ConfigurationRevision
-> Maybe Text
-> Maybe [SanitizationWarning]
-> Int
-> UpdateConfigurationResponse
UpdateConfigurationResponse'
            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
"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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"warnings" 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 UpdateConfiguration where
  hashWithSalt :: Int -> UpdateConfiguration -> Int
hashWithSalt Int
_salt UpdateConfiguration' {Maybe Text
Text
data' :: Text
configurationId :: Text
description :: Maybe Text
$sel:data':UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:configurationId:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> 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` Text
configurationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
data'

instance Prelude.NFData UpdateConfiguration where
  rnf :: UpdateConfiguration -> ()
rnf UpdateConfiguration' {Maybe Text
Text
data' :: Text
configurationId :: Text
description :: Maybe Text
$sel:data':UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:configurationId:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> 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 Text
configurationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
data'

instance Data.ToHeaders UpdateConfiguration where
  toHeaders :: UpdateConfiguration -> 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 UpdateConfiguration where
  toJSON :: UpdateConfiguration -> Value
toJSON UpdateConfiguration' {Maybe Text
Text
data' :: Text
configurationId :: Text
description :: Maybe Text
$sel:data':UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:configurationId:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> 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,
            forall a. a -> Maybe a
Prelude.Just (Key
"data" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
data')
          ]
      )

instance Data.ToPath UpdateConfiguration where
  toPath :: UpdateConfiguration -> ByteString
toPath UpdateConfiguration' {Maybe Text
Text
data' :: Text
configurationId :: Text
description :: Maybe Text
$sel:data':UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:configurationId:UpdateConfiguration' :: UpdateConfiguration -> Text
$sel:description:UpdateConfiguration' :: UpdateConfiguration -> Maybe 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 UpdateConfiguration where
  toQuery :: UpdateConfiguration -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateConfigurationResponse' smart constructor.
data UpdateConfigurationResponse = UpdateConfigurationResponse'
  { -- | Required. The Amazon Resource Name (ARN) of the configuration.
    UpdateConfigurationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Required. The date and time of the configuration.
    UpdateConfigurationResponse -> Maybe ISO8601
created :: Prelude.Maybe Data.ISO8601,
    -- | Required. The unique ID that Amazon MQ generates for the configuration.
    UpdateConfigurationResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The latest revision of the configuration.
    UpdateConfigurationResponse -> 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.
    UpdateConfigurationResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The list of the first 20 warnings about the configuration XML elements
    -- or attributes that were sanitized.
    UpdateConfigurationResponse -> Maybe [SanitizationWarning]
warnings :: Prelude.Maybe [SanitizationWarning],
    -- | The response's http status code.
    UpdateConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateConfigurationResponse -> UpdateConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConfigurationResponse -> UpdateConfigurationResponse -> Bool
$c/= :: UpdateConfigurationResponse -> UpdateConfigurationResponse -> Bool
== :: UpdateConfigurationResponse -> UpdateConfigurationResponse -> Bool
$c== :: UpdateConfigurationResponse -> UpdateConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConfigurationResponse]
ReadPrec UpdateConfigurationResponse
Int -> ReadS UpdateConfigurationResponse
ReadS [UpdateConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConfigurationResponse]
$creadListPrec :: ReadPrec [UpdateConfigurationResponse]
readPrec :: ReadPrec UpdateConfigurationResponse
$creadPrec :: ReadPrec UpdateConfigurationResponse
readList :: ReadS [UpdateConfigurationResponse]
$creadList :: ReadS [UpdateConfigurationResponse]
readsPrec :: Int -> ReadS UpdateConfigurationResponse
$creadsPrec :: Int -> ReadS UpdateConfigurationResponse
Prelude.Read, Int -> UpdateConfigurationResponse -> ShowS
[UpdateConfigurationResponse] -> ShowS
UpdateConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConfigurationResponse] -> ShowS
$cshowList :: [UpdateConfigurationResponse] -> ShowS
show :: UpdateConfigurationResponse -> String
$cshow :: UpdateConfigurationResponse -> String
showsPrec :: Int -> UpdateConfigurationResponse -> ShowS
$cshowsPrec :: Int -> UpdateConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConfigurationResponse x -> UpdateConfigurationResponse
forall x.
UpdateConfigurationResponse -> Rep UpdateConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConfigurationResponse x -> UpdateConfigurationResponse
$cfrom :: forall x.
UpdateConfigurationResponse -> Rep UpdateConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConfigurationResponse' 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', 'updateConfigurationResponse_arn' - Required. The Amazon Resource Name (ARN) of the configuration.
--
-- 'created', 'updateConfigurationResponse_created' - Required. The date and time of the configuration.
--
-- 'id', 'updateConfigurationResponse_id' - Required. The unique ID that Amazon MQ generates for the configuration.
--
-- 'latestRevision', 'updateConfigurationResponse_latestRevision' - The latest revision of the configuration.
--
-- 'name', 'updateConfigurationResponse_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.
--
-- 'warnings', 'updateConfigurationResponse_warnings' - The list of the first 20 warnings about the configuration XML elements
-- or attributes that were sanitized.
--
-- 'httpStatus', 'updateConfigurationResponse_httpStatus' - The response's http status code.
newUpdateConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConfigurationResponse
newUpdateConfigurationResponse :: Int -> UpdateConfigurationResponse
newUpdateConfigurationResponse Int
pHttpStatus_ =
  UpdateConfigurationResponse'
    { $sel:arn:UpdateConfigurationResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:created:UpdateConfigurationResponse' :: Maybe ISO8601
created = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateConfigurationResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:latestRevision:UpdateConfigurationResponse' :: Maybe ConfigurationRevision
latestRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateConfigurationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:UpdateConfigurationResponse' :: Maybe [SanitizationWarning]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Required. The date and time of the configuration.
updateConfigurationResponse_created :: Lens.Lens' UpdateConfigurationResponse (Prelude.Maybe Prelude.UTCTime)
updateConfigurationResponse_created :: Lens' UpdateConfigurationResponse (Maybe UTCTime)
updateConfigurationResponse_created = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationResponse' {Maybe ISO8601
created :: Maybe ISO8601
$sel:created:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe ISO8601
created} -> Maybe ISO8601
created) (\s :: UpdateConfigurationResponse
s@UpdateConfigurationResponse' {} Maybe ISO8601
a -> UpdateConfigurationResponse
s {$sel:created:UpdateConfigurationResponse' :: Maybe ISO8601
created = Maybe ISO8601
a} :: UpdateConfigurationResponse) 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.
updateConfigurationResponse_id :: Lens.Lens' UpdateConfigurationResponse (Prelude.Maybe Prelude.Text)
updateConfigurationResponse_id :: Lens' UpdateConfigurationResponse (Maybe Text)
updateConfigurationResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationResponse' {Maybe Text
id :: Maybe Text
$sel:id:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: UpdateConfigurationResponse
s@UpdateConfigurationResponse' {} Maybe Text
a -> UpdateConfigurationResponse
s {$sel:id:UpdateConfigurationResponse' :: Maybe Text
id = Maybe Text
a} :: UpdateConfigurationResponse)

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

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

-- | The list of the first 20 warnings about the configuration XML elements
-- or attributes that were sanitized.
updateConfigurationResponse_warnings :: Lens.Lens' UpdateConfigurationResponse (Prelude.Maybe [SanitizationWarning])
updateConfigurationResponse_warnings :: Lens' UpdateConfigurationResponse (Maybe [SanitizationWarning])
updateConfigurationResponse_warnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationResponse' {Maybe [SanitizationWarning]
warnings :: Maybe [SanitizationWarning]
$sel:warnings:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe [SanitizationWarning]
warnings} -> Maybe [SanitizationWarning]
warnings) (\s :: UpdateConfigurationResponse
s@UpdateConfigurationResponse' {} Maybe [SanitizationWarning]
a -> UpdateConfigurationResponse
s {$sel:warnings:UpdateConfigurationResponse' :: Maybe [SanitizationWarning]
warnings = Maybe [SanitizationWarning]
a} :: UpdateConfigurationResponse) 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.
updateConfigurationResponse_httpStatus :: Lens.Lens' UpdateConfigurationResponse Prelude.Int
updateConfigurationResponse_httpStatus :: Lens' UpdateConfigurationResponse Int
updateConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateConfigurationResponse
s@UpdateConfigurationResponse' {} Int
a -> UpdateConfigurationResponse
s {$sel:httpStatus:UpdateConfigurationResponse' :: Int
httpStatus = Int
a} :: UpdateConfigurationResponse)

instance Prelude.NFData UpdateConfigurationResponse where
  rnf :: UpdateConfigurationResponse -> ()
rnf UpdateConfigurationResponse' {Int
Maybe [SanitizationWarning]
Maybe Text
Maybe ISO8601
Maybe ConfigurationRevision
httpStatus :: Int
warnings :: Maybe [SanitizationWarning]
name :: Maybe Text
latestRevision :: Maybe ConfigurationRevision
id :: Maybe Text
created :: Maybe ISO8601
arn :: Maybe Text
$sel:httpStatus:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Int
$sel:warnings:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe [SanitizationWarning]
$sel:name:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe Text
$sel:latestRevision:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe ConfigurationRevision
$sel:id:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe Text
$sel:created:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> Maybe ISO8601
$sel:arn:UpdateConfigurationResponse' :: UpdateConfigurationResponse -> 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
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 Maybe [SanitizationWarning]
warnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus