{-# 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.CreateConfigurationProfile
-- 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 configuration profile, which is information that enables
-- AppConfig to access the configuration source. Valid configuration
-- sources include the AppConfig hosted configuration store, Amazon Web
-- Services Systems Manager (SSM) documents, SSM Parameter Store
-- parameters, Amazon S3 objects, or any
-- <http://docs.aws.amazon.com/codepipeline/latest/userguide/integrations-action-type.html#integrations-source integration source action>
-- supported by CodePipeline. A configuration profile includes the
-- following information:
--
-- -   The URI location of the configuration data.
--
-- -   The Identity and Access Management (IAM) role that provides access
--     to the configuration data.
--
-- -   A validator for the configuration data. Available validators include
--     either a JSON Schema or an Amazon Web Services Lambda function.
--
-- For more information, see
-- <http://docs.aws.amazon.com/appconfig/latest/userguide/appconfig-creating-configuration-and-profile.html Create a Configuration and a Configuration Profile>
-- in the /AppConfig User Guide/.
module Amazonka.AppConfig.CreateConfigurationProfile
  ( -- * Creating a Request
    CreateConfigurationProfile (..),
    newCreateConfigurationProfile,

    -- * Request Lenses
    createConfigurationProfile_description,
    createConfigurationProfile_retrievalRoleArn,
    createConfigurationProfile_tags,
    createConfigurationProfile_type,
    createConfigurationProfile_validators,
    createConfigurationProfile_applicationId,
    createConfigurationProfile_name,
    createConfigurationProfile_locationUri,

    -- * 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:/ 'newCreateConfigurationProfile' smart constructor.
data CreateConfigurationProfile = CreateConfigurationProfile'
  { -- | A description of the configuration profile.
    CreateConfigurationProfile -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ARN of an IAM role with permission to access the configuration at
    -- the specified @LocationUri@.
    --
    -- A retrieval role ARN is not required for configurations stored in the
    -- AppConfig hosted configuration store. It is required for all other
    -- sources that store your configuration.
    CreateConfigurationProfile -> Maybe Text
retrievalRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Metadata to assign to the configuration profile. Tags help organize and
    -- categorize your AppConfig resources. Each tag consists of a key and an
    -- optional value, both of which you define.
    CreateConfigurationProfile -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The type of configurations contained in the profile. AppConfig supports
    -- @feature flags@ and @freeform@ configurations. We recommend you create
    -- feature flag configurations to enable or disable new features and
    -- freeform configurations to distribute configurations to an application.
    -- When calling this API, enter one of the following values for @Type@:
    --
    -- @AWS.AppConfig.FeatureFlags@
    --
    -- @AWS.Freeform@
    CreateConfigurationProfile -> Maybe Text
type' :: Prelude.Maybe Prelude.Text,
    -- | A list of methods for validating the configuration.
    CreateConfigurationProfile -> Maybe [Validator]
validators :: Prelude.Maybe [Validator],
    -- | The application ID.
    CreateConfigurationProfile -> Text
applicationId :: Prelude.Text,
    -- | A name for the configuration profile.
    CreateConfigurationProfile -> Text
name :: Prelude.Text,
    -- | A URI to locate the configuration. You can specify the AppConfig hosted
    -- configuration store, Systems Manager (SSM) document, an SSM Parameter
    -- Store parameter, or an Amazon S3 object. For the hosted configuration
    -- store and for feature flags, specify @hosted@. For an SSM document,
    -- specify either the document name in the format
    -- @ssm-document:\/\/\<Document_name>@ or the Amazon Resource Name (ARN).
    -- For a parameter, specify either the parameter name in the format
    -- @ssm-parameter:\/\/\<Parameter_name>@ or the ARN. For an Amazon S3
    -- object, specify the URI in the following format:
    -- @s3:\/\/\<bucket>\/\<objectKey> @. Here is an example:
    -- @s3:\/\/my-bucket\/my-app\/us-east-1\/my-config.json@
    CreateConfigurationProfile -> Text
locationUri :: Prelude.Text
  }
  deriving (CreateConfigurationProfile -> CreateConfigurationProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConfigurationProfile -> CreateConfigurationProfile -> Bool
$c/= :: CreateConfigurationProfile -> CreateConfigurationProfile -> Bool
== :: CreateConfigurationProfile -> CreateConfigurationProfile -> Bool
$c== :: CreateConfigurationProfile -> CreateConfigurationProfile -> Bool
Prelude.Eq, Int -> CreateConfigurationProfile -> ShowS
[CreateConfigurationProfile] -> ShowS
CreateConfigurationProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConfigurationProfile] -> ShowS
$cshowList :: [CreateConfigurationProfile] -> ShowS
show :: CreateConfigurationProfile -> String
$cshow :: CreateConfigurationProfile -> String
showsPrec :: Int -> CreateConfigurationProfile -> ShowS
$cshowsPrec :: Int -> CreateConfigurationProfile -> ShowS
Prelude.Show, forall x.
Rep CreateConfigurationProfile x -> CreateConfigurationProfile
forall x.
CreateConfigurationProfile -> Rep CreateConfigurationProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateConfigurationProfile x -> CreateConfigurationProfile
$cfrom :: forall x.
CreateConfigurationProfile -> Rep CreateConfigurationProfile x
Prelude.Generic)

-- |
-- Create a value of 'CreateConfigurationProfile' 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', 'createConfigurationProfile_description' - A description of the configuration profile.
--
-- 'retrievalRoleArn', 'createConfigurationProfile_retrievalRoleArn' - The ARN of an IAM role with permission to access the configuration at
-- the specified @LocationUri@.
--
-- A retrieval role ARN is not required for configurations stored in the
-- AppConfig hosted configuration store. It is required for all other
-- sources that store your configuration.
--
-- 'tags', 'createConfigurationProfile_tags' - Metadata to assign to the configuration profile. Tags help organize and
-- categorize your AppConfig resources. Each tag consists of a key and an
-- optional value, both of which you define.
--
-- 'type'', 'createConfigurationProfile_type' - The type of configurations contained in the profile. AppConfig supports
-- @feature flags@ and @freeform@ configurations. We recommend you create
-- feature flag configurations to enable or disable new features and
-- freeform configurations to distribute configurations to an application.
-- When calling this API, enter one of the following values for @Type@:
--
-- @AWS.AppConfig.FeatureFlags@
--
-- @AWS.Freeform@
--
-- 'validators', 'createConfigurationProfile_validators' - A list of methods for validating the configuration.
--
-- 'applicationId', 'createConfigurationProfile_applicationId' - The application ID.
--
-- 'name', 'createConfigurationProfile_name' - A name for the configuration profile.
--
-- 'locationUri', 'createConfigurationProfile_locationUri' - A URI to locate the configuration. You can specify the AppConfig hosted
-- configuration store, Systems Manager (SSM) document, an SSM Parameter
-- Store parameter, or an Amazon S3 object. For the hosted configuration
-- store and for feature flags, specify @hosted@. For an SSM document,
-- specify either the document name in the format
-- @ssm-document:\/\/\<Document_name>@ or the Amazon Resource Name (ARN).
-- For a parameter, specify either the parameter name in the format
-- @ssm-parameter:\/\/\<Parameter_name>@ or the ARN. For an Amazon S3
-- object, specify the URI in the following format:
-- @s3:\/\/\<bucket>\/\<objectKey> @. Here is an example:
-- @s3:\/\/my-bucket\/my-app\/us-east-1\/my-config.json@
newCreateConfigurationProfile ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'locationUri'
  Prelude.Text ->
  CreateConfigurationProfile
newCreateConfigurationProfile :: Text -> Text -> Text -> CreateConfigurationProfile
newCreateConfigurationProfile
  Text
pApplicationId_
  Text
pName_
  Text
pLocationUri_ =
    CreateConfigurationProfile'
      { $sel:description:CreateConfigurationProfile' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:retrievalRoleArn:CreateConfigurationProfile' :: Maybe Text
retrievalRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateConfigurationProfile' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:type':CreateConfigurationProfile' :: Maybe Text
type' = forall a. Maybe a
Prelude.Nothing,
        $sel:validators:CreateConfigurationProfile' :: Maybe [Validator]
validators = forall a. Maybe a
Prelude.Nothing,
        $sel:applicationId:CreateConfigurationProfile' :: Text
applicationId = Text
pApplicationId_,
        $sel:name:CreateConfigurationProfile' :: Text
name = Text
pName_,
        $sel:locationUri:CreateConfigurationProfile' :: Text
locationUri = Text
pLocationUri_
      }

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

-- | The ARN of an IAM role with permission to access the configuration at
-- the specified @LocationUri@.
--
-- A retrieval role ARN is not required for configurations stored in the
-- AppConfig hosted configuration store. It is required for all other
-- sources that store your configuration.
createConfigurationProfile_retrievalRoleArn :: Lens.Lens' CreateConfigurationProfile (Prelude.Maybe Prelude.Text)
createConfigurationProfile_retrievalRoleArn :: Lens' CreateConfigurationProfile (Maybe Text)
createConfigurationProfile_retrievalRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationProfile' {Maybe Text
retrievalRoleArn :: Maybe Text
$sel:retrievalRoleArn:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
retrievalRoleArn} -> Maybe Text
retrievalRoleArn) (\s :: CreateConfigurationProfile
s@CreateConfigurationProfile' {} Maybe Text
a -> CreateConfigurationProfile
s {$sel:retrievalRoleArn:CreateConfigurationProfile' :: Maybe Text
retrievalRoleArn = Maybe Text
a} :: CreateConfigurationProfile)

-- | Metadata to assign to the configuration profile. Tags help organize and
-- categorize your AppConfig resources. Each tag consists of a key and an
-- optional value, both of which you define.
createConfigurationProfile_tags :: Lens.Lens' CreateConfigurationProfile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createConfigurationProfile_tags :: Lens' CreateConfigurationProfile (Maybe (HashMap Text Text))
createConfigurationProfile_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationProfile' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateConfigurationProfile
s@CreateConfigurationProfile' {} Maybe (HashMap Text Text)
a -> CreateConfigurationProfile
s {$sel:tags:CreateConfigurationProfile' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateConfigurationProfile) 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 type of configurations contained in the profile. AppConfig supports
-- @feature flags@ and @freeform@ configurations. We recommend you create
-- feature flag configurations to enable or disable new features and
-- freeform configurations to distribute configurations to an application.
-- When calling this API, enter one of the following values for @Type@:
--
-- @AWS.AppConfig.FeatureFlags@
--
-- @AWS.Freeform@
createConfigurationProfile_type :: Lens.Lens' CreateConfigurationProfile (Prelude.Maybe Prelude.Text)
createConfigurationProfile_type :: Lens' CreateConfigurationProfile (Maybe Text)
createConfigurationProfile_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationProfile' {Maybe Text
type' :: Maybe Text
$sel:type':CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
type'} -> Maybe Text
type') (\s :: CreateConfigurationProfile
s@CreateConfigurationProfile' {} Maybe Text
a -> CreateConfigurationProfile
s {$sel:type':CreateConfigurationProfile' :: Maybe Text
type' = Maybe Text
a} :: CreateConfigurationProfile)

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

-- | A name for the configuration profile.
createConfigurationProfile_name :: Lens.Lens' CreateConfigurationProfile Prelude.Text
createConfigurationProfile_name :: Lens' CreateConfigurationProfile Text
createConfigurationProfile_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationProfile' {Text
name :: Text
$sel:name:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
name} -> Text
name) (\s :: CreateConfigurationProfile
s@CreateConfigurationProfile' {} Text
a -> CreateConfigurationProfile
s {$sel:name:CreateConfigurationProfile' :: Text
name = Text
a} :: CreateConfigurationProfile)

-- | A URI to locate the configuration. You can specify the AppConfig hosted
-- configuration store, Systems Manager (SSM) document, an SSM Parameter
-- Store parameter, or an Amazon S3 object. For the hosted configuration
-- store and for feature flags, specify @hosted@. For an SSM document,
-- specify either the document name in the format
-- @ssm-document:\/\/\<Document_name>@ or the Amazon Resource Name (ARN).
-- For a parameter, specify either the parameter name in the format
-- @ssm-parameter:\/\/\<Parameter_name>@ or the ARN. For an Amazon S3
-- object, specify the URI in the following format:
-- @s3:\/\/\<bucket>\/\<objectKey> @. Here is an example:
-- @s3:\/\/my-bucket\/my-app\/us-east-1\/my-config.json@
createConfigurationProfile_locationUri :: Lens.Lens' CreateConfigurationProfile Prelude.Text
createConfigurationProfile_locationUri :: Lens' CreateConfigurationProfile Text
createConfigurationProfile_locationUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConfigurationProfile' {Text
locationUri :: Text
$sel:locationUri:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
locationUri} -> Text
locationUri) (\s :: CreateConfigurationProfile
s@CreateConfigurationProfile' {} Text
a -> CreateConfigurationProfile
s {$sel:locationUri:CreateConfigurationProfile' :: Text
locationUri = Text
a} :: CreateConfigurationProfile)

instance Core.AWSRequest CreateConfigurationProfile where
  type
    AWSResponse CreateConfigurationProfile =
      ConfigurationProfile
  request :: (Service -> Service)
-> CreateConfigurationProfile -> Request CreateConfigurationProfile
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 CreateConfigurationProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateConfigurationProfile)))
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 CreateConfigurationProfile where
  hashWithSalt :: Int -> CreateConfigurationProfile -> Int
hashWithSalt Int
_salt CreateConfigurationProfile' {Maybe [Validator]
Maybe Text
Maybe (HashMap Text Text)
Text
locationUri :: Text
name :: Text
applicationId :: Text
validators :: Maybe [Validator]
type' :: Maybe Text
tags :: Maybe (HashMap Text Text)
retrievalRoleArn :: Maybe Text
description :: Maybe Text
$sel:locationUri:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:name:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:applicationId:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:validators:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe [Validator]
$sel:type':CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
$sel:tags:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe (HashMap Text Text)
$sel:retrievalRoleArn:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
$sel:description:CreateConfigurationProfile' :: CreateConfigurationProfile -> 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
retrievalRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
type'
      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
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
locationUri

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

instance Data.ToHeaders CreateConfigurationProfile where
  toHeaders :: CreateConfigurationProfile -> 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 CreateConfigurationProfile where
  toJSON :: CreateConfigurationProfile -> Value
toJSON CreateConfigurationProfile' {Maybe [Validator]
Maybe Text
Maybe (HashMap Text Text)
Text
locationUri :: Text
name :: Text
applicationId :: Text
validators :: Maybe [Validator]
type' :: Maybe Text
tags :: Maybe (HashMap Text Text)
retrievalRoleArn :: Maybe Text
description :: Maybe Text
$sel:locationUri:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:name:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:applicationId:CreateConfigurationProfile' :: CreateConfigurationProfile -> Text
$sel:validators:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe [Validator]
$sel:type':CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
$sel:tags:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe (HashMap Text Text)
$sel:retrievalRoleArn:CreateConfigurationProfile' :: CreateConfigurationProfile -> Maybe Text
$sel:description:CreateConfigurationProfile' :: CreateConfigurationProfile -> 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
"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
"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,
            (Key
"Type" 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
type',
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"LocationUri" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
locationUri)
          ]
      )

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

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