{-# 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.AppConfig.UpdateConfigurationProfile
-- 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 a configuration profile.
module Amazonka.AppConfig.UpdateConfigurationProfile
  ( -- * Creating a Request
    UpdateConfigurationProfile (..),
    newUpdateConfigurationProfile,

    -- * Request Lenses
    updateConfigurationProfile_description,
    updateConfigurationProfile_name,
    updateConfigurationProfile_retrievalRoleArn,
    updateConfigurationProfile_validators,
    updateConfigurationProfile_applicationId,
    updateConfigurationProfile_configurationProfileId,

    -- * Destructuring the Response
    ConfigurationProfile (..),
    newConfigurationProfile,

    -- * Response Lenses
    configurationProfile_applicationId,
    configurationProfile_description,
    configurationProfile_id,
    configurationProfile_locationUri,
    configurationProfile_name,
    configurationProfile_retrievalRoleArn,
    configurationProfile_type,
    configurationProfile_validators,
  )
where

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

-- | /See:/ 'newUpdateConfigurationProfile' smart constructor.
data UpdateConfigurationProfile = UpdateConfigurationProfile'
  { -- | A description of the configuration profile.
    UpdateConfigurationProfile -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the configuration profile.
    UpdateConfigurationProfile -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ARN of an IAM role with permission to access the configuration at
    -- the specified @LocationUri@.
    UpdateConfigurationProfile -> Maybe Text
retrievalRoleArn :: Prelude.Maybe Prelude.Text,
    -- | A list of methods for validating the configuration.
    UpdateConfigurationProfile -> Maybe [Validator]
validators :: Prelude.Maybe [Validator],
    -- | The application ID.
    UpdateConfigurationProfile -> Text
applicationId :: Prelude.Text,
    -- | The ID of the configuration profile.
    UpdateConfigurationProfile -> Text
configurationProfileId :: Prelude.Text
  }
  deriving (UpdateConfigurationProfile -> UpdateConfigurationProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConfigurationProfile -> UpdateConfigurationProfile -> Bool
$c/= :: UpdateConfigurationProfile -> UpdateConfigurationProfile -> Bool
== :: UpdateConfigurationProfile -> UpdateConfigurationProfile -> Bool
$c== :: UpdateConfigurationProfile -> UpdateConfigurationProfile -> Bool
Prelude.Eq, Int -> UpdateConfigurationProfile -> ShowS
[UpdateConfigurationProfile] -> ShowS
UpdateConfigurationProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConfigurationProfile] -> ShowS
$cshowList :: [UpdateConfigurationProfile] -> ShowS
show :: UpdateConfigurationProfile -> String
$cshow :: UpdateConfigurationProfile -> String
showsPrec :: Int -> UpdateConfigurationProfile -> ShowS
$cshowsPrec :: Int -> UpdateConfigurationProfile -> ShowS
Prelude.Show, forall x.
Rep UpdateConfigurationProfile x -> UpdateConfigurationProfile
forall x.
UpdateConfigurationProfile -> Rep UpdateConfigurationProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConfigurationProfile x -> UpdateConfigurationProfile
$cfrom :: forall x.
UpdateConfigurationProfile -> Rep UpdateConfigurationProfile x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConfigurationProfile' 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', 'updateConfigurationProfile_description' - A description of the configuration profile.
--
-- 'name', 'updateConfigurationProfile_name' - The name of the configuration profile.
--
-- 'retrievalRoleArn', 'updateConfigurationProfile_retrievalRoleArn' - The ARN of an IAM role with permission to access the configuration at
-- the specified @LocationUri@.
--
-- 'validators', 'updateConfigurationProfile_validators' - A list of methods for validating the configuration.
--
-- 'applicationId', 'updateConfigurationProfile_applicationId' - The application ID.
--
-- 'configurationProfileId', 'updateConfigurationProfile_configurationProfileId' - The ID of the configuration profile.
newUpdateConfigurationProfile ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'configurationProfileId'
  Prelude.Text ->
  UpdateConfigurationProfile
newUpdateConfigurationProfile :: Text -> Text -> UpdateConfigurationProfile
newUpdateConfigurationProfile
  Text
pApplicationId_
  Text
pConfigurationProfileId_ =
    UpdateConfigurationProfile'
      { $sel:description:UpdateConfigurationProfile' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:name:UpdateConfigurationProfile' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:retrievalRoleArn:UpdateConfigurationProfile' :: Maybe Text
retrievalRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:validators:UpdateConfigurationProfile' :: Maybe [Validator]
validators = forall a. Maybe a
Prelude.Nothing,
        $sel:applicationId:UpdateConfigurationProfile' :: Text
applicationId = Text
pApplicationId_,
        $sel:configurationProfileId:UpdateConfigurationProfile' :: Text
configurationProfileId =
          Text
pConfigurationProfileId_
      }

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

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

-- | The ARN of an IAM role with permission to access the configuration at
-- the specified @LocationUri@.
updateConfigurationProfile_retrievalRoleArn :: Lens.Lens' UpdateConfigurationProfile (Prelude.Maybe Prelude.Text)
updateConfigurationProfile_retrievalRoleArn :: Lens' UpdateConfigurationProfile (Maybe Text)
updateConfigurationProfile_retrievalRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationProfile' {Maybe Text
retrievalRoleArn :: Maybe Text
$sel:retrievalRoleArn:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
retrievalRoleArn} -> Maybe Text
retrievalRoleArn) (\s :: UpdateConfigurationProfile
s@UpdateConfigurationProfile' {} Maybe Text
a -> UpdateConfigurationProfile
s {$sel:retrievalRoleArn:UpdateConfigurationProfile' :: Maybe Text
retrievalRoleArn = Maybe Text
a} :: UpdateConfigurationProfile)

-- | A list of methods for validating the configuration.
updateConfigurationProfile_validators :: Lens.Lens' UpdateConfigurationProfile (Prelude.Maybe [Validator])
updateConfigurationProfile_validators :: Lens' UpdateConfigurationProfile (Maybe [Validator])
updateConfigurationProfile_validators = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationProfile' {Maybe [Validator]
validators :: Maybe [Validator]
$sel:validators:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe [Validator]
validators} -> Maybe [Validator]
validators) (\s :: UpdateConfigurationProfile
s@UpdateConfigurationProfile' {} Maybe [Validator]
a -> UpdateConfigurationProfile
s {$sel:validators:UpdateConfigurationProfile' :: Maybe [Validator]
validators = Maybe [Validator]
a} :: UpdateConfigurationProfile) 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 application ID.
updateConfigurationProfile_applicationId :: Lens.Lens' UpdateConfigurationProfile Prelude.Text
updateConfigurationProfile_applicationId :: Lens' UpdateConfigurationProfile Text
updateConfigurationProfile_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationProfile' {Text
applicationId :: Text
$sel:applicationId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
applicationId} -> Text
applicationId) (\s :: UpdateConfigurationProfile
s@UpdateConfigurationProfile' {} Text
a -> UpdateConfigurationProfile
s {$sel:applicationId:UpdateConfigurationProfile' :: Text
applicationId = Text
a} :: UpdateConfigurationProfile)

-- | The ID of the configuration profile.
updateConfigurationProfile_configurationProfileId :: Lens.Lens' UpdateConfigurationProfile Prelude.Text
updateConfigurationProfile_configurationProfileId :: Lens' UpdateConfigurationProfile Text
updateConfigurationProfile_configurationProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConfigurationProfile' {Text
configurationProfileId :: Text
$sel:configurationProfileId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
configurationProfileId} -> Text
configurationProfileId) (\s :: UpdateConfigurationProfile
s@UpdateConfigurationProfile' {} Text
a -> UpdateConfigurationProfile
s {$sel:configurationProfileId:UpdateConfigurationProfile' :: Text
configurationProfileId = Text
a} :: UpdateConfigurationProfile)

instance Core.AWSRequest UpdateConfigurationProfile where
  type
    AWSResponse UpdateConfigurationProfile =
      ConfigurationProfile
  request :: (Service -> Service)
-> UpdateConfigurationProfile -> Request UpdateConfigurationProfile
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateConfigurationProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateConfigurationProfile)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable UpdateConfigurationProfile where
  hashWithSalt :: Int -> UpdateConfigurationProfile -> Int
hashWithSalt Int
_salt UpdateConfigurationProfile' {Maybe [Validator]
Maybe Text
Text
configurationProfileId :: Text
applicationId :: Text
validators :: Maybe [Validator]
retrievalRoleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:configurationProfileId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:applicationId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:validators:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe [Validator]
$sel:retrievalRoleArn:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:name:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:description:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> 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
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
retrievalRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Validator]
validators
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationProfileId

instance Prelude.NFData UpdateConfigurationProfile where
  rnf :: UpdateConfigurationProfile -> ()
rnf UpdateConfigurationProfile' {Maybe [Validator]
Maybe Text
Text
configurationProfileId :: Text
applicationId :: Text
validators :: Maybe [Validator]
retrievalRoleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:configurationProfileId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:applicationId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:validators:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe [Validator]
$sel:retrievalRoleArn:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:name:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:description:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> 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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
retrievalRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Validator]
validators
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configurationProfileId

instance Data.ToHeaders UpdateConfigurationProfile where
  toHeaders :: UpdateConfigurationProfile -> 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 UpdateConfigurationProfile where
  toJSON :: UpdateConfigurationProfile -> Value
toJSON UpdateConfigurationProfile' {Maybe [Validator]
Maybe Text
Text
configurationProfileId :: Text
applicationId :: Text
validators :: Maybe [Validator]
retrievalRoleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:configurationProfileId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:applicationId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:validators:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe [Validator]
$sel:retrievalRoleArn:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:name:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:description:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> 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
"Name" 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
name,
            (Key
"RetrievalRoleArn" 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
retrievalRoleArn,
            (Key
"Validators" 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 [Validator]
validators
          ]
      )

instance Data.ToPath UpdateConfigurationProfile where
  toPath :: UpdateConfigurationProfile -> ByteString
toPath UpdateConfigurationProfile' {Maybe [Validator]
Maybe Text
Text
configurationProfileId :: Text
applicationId :: Text
validators :: Maybe [Validator]
retrievalRoleArn :: Maybe Text
name :: Maybe Text
description :: Maybe Text
$sel:configurationProfileId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:applicationId:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Text
$sel:validators:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe [Validator]
$sel:retrievalRoleArn:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:name:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
$sel:description:UpdateConfigurationProfile' :: UpdateConfigurationProfile -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/configurationprofiles/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
configurationProfileId
      ]

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