{-# 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.RDS.CreateDBClusterParameterGroup
-- 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 DB cluster parameter group.
--
-- Parameters in a DB cluster parameter group apply to all of the instances
-- in a DB cluster.
--
-- A DB cluster parameter group is initially created with the default
-- parameters for the database engine used by instances in the DB cluster.
-- To provide custom values for any of the parameters, you must modify the
-- group after creating it using @ModifyDBClusterParameterGroup@. Once
-- you\'ve created a DB cluster parameter group, you need to associate it
-- with your DB cluster using @ModifyDBCluster@.
--
-- When you associate a new DB cluster parameter group with a running
-- Aurora DB cluster, reboot the DB instances in the DB cluster without
-- failover for the new DB cluster parameter group and associated settings
-- to take effect.
--
-- When you associate a new DB cluster parameter group with a running
-- Multi-AZ DB cluster, reboot the DB cluster without failover for the new
-- DB cluster parameter group and associated settings to take effect.
--
-- After you create a DB cluster parameter group, you should wait at least
-- 5 minutes before creating your first DB cluster that uses that DB
-- cluster parameter group as the default parameter group. This allows
-- Amazon RDS to fully complete the create action before the DB cluster
-- parameter group is used as the default for a new DB cluster. This is
-- especially important for parameters that are critical when creating the
-- default database for a DB cluster, such as the character set for the
-- default database defined by the @character_set_database@ parameter. You
-- can use the /Parameter Groups/ option of the
-- <https://console.aws.amazon.com/rds/ Amazon RDS console> or the
-- @DescribeDBClusterParameters@ operation to verify that your DB cluster
-- parameter group has been created or modified.
--
-- For more information on Amazon Aurora, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/CHAP_AuroraOverview.html What is Amazon Aurora?>
-- in the /Amazon Aurora User Guide/.
--
-- For more information on Multi-AZ DB clusters, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/multi-az-db-clusters-concepts.html Multi-AZ deployments with two readable standby DB instances>
-- in the /Amazon RDS User Guide/.
module Amazonka.RDS.CreateDBClusterParameterGroup
  ( -- * Creating a Request
    CreateDBClusterParameterGroup (..),
    newCreateDBClusterParameterGroup,

    -- * Request Lenses
    createDBClusterParameterGroup_tags,
    createDBClusterParameterGroup_dbClusterParameterGroupName,
    createDBClusterParameterGroup_dbParameterGroupFamily,
    createDBClusterParameterGroup_description,

    -- * Destructuring the Response
    CreateDBClusterParameterGroupResponse (..),
    newCreateDBClusterParameterGroupResponse,

    -- * Response Lenses
    createDBClusterParameterGroupResponse_dbClusterParameterGroup,
    createDBClusterParameterGroupResponse_httpStatus,
  )
where

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 Amazonka.RDS.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newCreateDBClusterParameterGroup' smart constructor.
data CreateDBClusterParameterGroup = CreateDBClusterParameterGroup'
  { -- | Tags to assign to the DB cluster parameter group.
    CreateDBClusterParameterGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the DB cluster parameter group.
    --
    -- Constraints:
    --
    -- -   Must not match the name of an existing DB cluster parameter group.
    --
    -- This value is stored as a lowercase string.
    CreateDBClusterParameterGroup -> Text
dbClusterParameterGroupName :: Prelude.Text,
    -- | The DB cluster parameter group family name. A DB cluster parameter group
    -- can be associated with one and only one DB cluster parameter group
    -- family, and can be applied only to a DB cluster running a database
    -- engine and engine version compatible with that DB cluster parameter
    -- group family.
    --
    -- __Aurora MySQL__
    --
    -- Example: @aurora5.6@, @aurora-mysql5.7@, @aurora-mysql8.0@
    --
    -- __Aurora PostgreSQL__
    --
    -- Example: @aurora-postgresql9.6@
    --
    -- __RDS for MySQL__
    --
    -- Example: @mysql8.0@
    --
    -- __RDS for PostgreSQL__
    --
    -- Example: @postgres12@
    --
    -- To list all of the available parameter group families for a DB engine,
    -- use the following command:
    --
    -- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine \<engine>@
    --
    -- For example, to list all of the available parameter group families for
    -- the Aurora PostgreSQL DB engine, use the following command:
    --
    -- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine aurora-postgresql@
    --
    -- The output contains duplicates.
    --
    -- The following are the valid DB engine values:
    --
    -- -   @aurora@ (for MySQL 5.6-compatible Aurora)
    --
    -- -   @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
    --     Aurora)
    --
    -- -   @aurora-postgresql@
    --
    -- -   @mysql@
    --
    -- -   @postgres@
    CreateDBClusterParameterGroup -> Text
dbParameterGroupFamily :: Prelude.Text,
    -- | The description for the DB cluster parameter group.
    CreateDBClusterParameterGroup -> Text
description :: Prelude.Text
  }
  deriving (CreateDBClusterParameterGroup
-> CreateDBClusterParameterGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDBClusterParameterGroup
-> CreateDBClusterParameterGroup -> Bool
$c/= :: CreateDBClusterParameterGroup
-> CreateDBClusterParameterGroup -> Bool
== :: CreateDBClusterParameterGroup
-> CreateDBClusterParameterGroup -> Bool
$c== :: CreateDBClusterParameterGroup
-> CreateDBClusterParameterGroup -> Bool
Prelude.Eq, ReadPrec [CreateDBClusterParameterGroup]
ReadPrec CreateDBClusterParameterGroup
Int -> ReadS CreateDBClusterParameterGroup
ReadS [CreateDBClusterParameterGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDBClusterParameterGroup]
$creadListPrec :: ReadPrec [CreateDBClusterParameterGroup]
readPrec :: ReadPrec CreateDBClusterParameterGroup
$creadPrec :: ReadPrec CreateDBClusterParameterGroup
readList :: ReadS [CreateDBClusterParameterGroup]
$creadList :: ReadS [CreateDBClusterParameterGroup]
readsPrec :: Int -> ReadS CreateDBClusterParameterGroup
$creadsPrec :: Int -> ReadS CreateDBClusterParameterGroup
Prelude.Read, Int -> CreateDBClusterParameterGroup -> ShowS
[CreateDBClusterParameterGroup] -> ShowS
CreateDBClusterParameterGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDBClusterParameterGroup] -> ShowS
$cshowList :: [CreateDBClusterParameterGroup] -> ShowS
show :: CreateDBClusterParameterGroup -> String
$cshow :: CreateDBClusterParameterGroup -> String
showsPrec :: Int -> CreateDBClusterParameterGroup -> ShowS
$cshowsPrec :: Int -> CreateDBClusterParameterGroup -> ShowS
Prelude.Show, forall x.
Rep CreateDBClusterParameterGroup x
-> CreateDBClusterParameterGroup
forall x.
CreateDBClusterParameterGroup
-> Rep CreateDBClusterParameterGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDBClusterParameterGroup x
-> CreateDBClusterParameterGroup
$cfrom :: forall x.
CreateDBClusterParameterGroup
-> Rep CreateDBClusterParameterGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateDBClusterParameterGroup' 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:
--
-- 'tags', 'createDBClusterParameterGroup_tags' - Tags to assign to the DB cluster parameter group.
--
-- 'dbClusterParameterGroupName', 'createDBClusterParameterGroup_dbClusterParameterGroupName' - The name of the DB cluster parameter group.
--
-- Constraints:
--
-- -   Must not match the name of an existing DB cluster parameter group.
--
-- This value is stored as a lowercase string.
--
-- 'dbParameterGroupFamily', 'createDBClusterParameterGroup_dbParameterGroupFamily' - The DB cluster parameter group family name. A DB cluster parameter group
-- can be associated with one and only one DB cluster parameter group
-- family, and can be applied only to a DB cluster running a database
-- engine and engine version compatible with that DB cluster parameter
-- group family.
--
-- __Aurora MySQL__
--
-- Example: @aurora5.6@, @aurora-mysql5.7@, @aurora-mysql8.0@
--
-- __Aurora PostgreSQL__
--
-- Example: @aurora-postgresql9.6@
--
-- __RDS for MySQL__
--
-- Example: @mysql8.0@
--
-- __RDS for PostgreSQL__
--
-- Example: @postgres12@
--
-- To list all of the available parameter group families for a DB engine,
-- use the following command:
--
-- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine \<engine>@
--
-- For example, to list all of the available parameter group families for
-- the Aurora PostgreSQL DB engine, use the following command:
--
-- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine aurora-postgresql@
--
-- The output contains duplicates.
--
-- The following are the valid DB engine values:
--
-- -   @aurora@ (for MySQL 5.6-compatible Aurora)
--
-- -   @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
--     Aurora)
--
-- -   @aurora-postgresql@
--
-- -   @mysql@
--
-- -   @postgres@
--
-- 'description', 'createDBClusterParameterGroup_description' - The description for the DB cluster parameter group.
newCreateDBClusterParameterGroup ::
  -- | 'dbClusterParameterGroupName'
  Prelude.Text ->
  -- | 'dbParameterGroupFamily'
  Prelude.Text ->
  -- | 'description'
  Prelude.Text ->
  CreateDBClusterParameterGroup
newCreateDBClusterParameterGroup :: Text -> Text -> Text -> CreateDBClusterParameterGroup
newCreateDBClusterParameterGroup
  Text
pDBClusterParameterGroupName_
  Text
pDBParameterGroupFamily_
  Text
pDescription_ =
    CreateDBClusterParameterGroup'
      { $sel:tags:CreateDBClusterParameterGroup' :: Maybe [Tag]
tags =
          forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: Text
dbClusterParameterGroupName =
          Text
pDBClusterParameterGroupName_,
        $sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: Text
dbParameterGroupFamily =
          Text
pDBParameterGroupFamily_,
        $sel:description:CreateDBClusterParameterGroup' :: Text
description = Text
pDescription_
      }

-- | Tags to assign to the DB cluster parameter group.
createDBClusterParameterGroup_tags :: Lens.Lens' CreateDBClusterParameterGroup (Prelude.Maybe [Tag])
createDBClusterParameterGroup_tags :: Lens' CreateDBClusterParameterGroup (Maybe [Tag])
createDBClusterParameterGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterParameterGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateDBClusterParameterGroup
s@CreateDBClusterParameterGroup' {} Maybe [Tag]
a -> CreateDBClusterParameterGroup
s {$sel:tags:CreateDBClusterParameterGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateDBClusterParameterGroup) 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 name of the DB cluster parameter group.
--
-- Constraints:
--
-- -   Must not match the name of an existing DB cluster parameter group.
--
-- This value is stored as a lowercase string.
createDBClusterParameterGroup_dbClusterParameterGroupName :: Lens.Lens' CreateDBClusterParameterGroup Prelude.Text
createDBClusterParameterGroup_dbClusterParameterGroupName :: Lens' CreateDBClusterParameterGroup Text
createDBClusterParameterGroup_dbClusterParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterParameterGroup' {Text
dbClusterParameterGroupName :: Text
$sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
dbClusterParameterGroupName} -> Text
dbClusterParameterGroupName) (\s :: CreateDBClusterParameterGroup
s@CreateDBClusterParameterGroup' {} Text
a -> CreateDBClusterParameterGroup
s {$sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: Text
dbClusterParameterGroupName = Text
a} :: CreateDBClusterParameterGroup)

-- | The DB cluster parameter group family name. A DB cluster parameter group
-- can be associated with one and only one DB cluster parameter group
-- family, and can be applied only to a DB cluster running a database
-- engine and engine version compatible with that DB cluster parameter
-- group family.
--
-- __Aurora MySQL__
--
-- Example: @aurora5.6@, @aurora-mysql5.7@, @aurora-mysql8.0@
--
-- __Aurora PostgreSQL__
--
-- Example: @aurora-postgresql9.6@
--
-- __RDS for MySQL__
--
-- Example: @mysql8.0@
--
-- __RDS for PostgreSQL__
--
-- Example: @postgres12@
--
-- To list all of the available parameter group families for a DB engine,
-- use the following command:
--
-- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine \<engine>@
--
-- For example, to list all of the available parameter group families for
-- the Aurora PostgreSQL DB engine, use the following command:
--
-- @aws rds describe-db-engine-versions --query \"DBEngineVersions[].DBParameterGroupFamily\" --engine aurora-postgresql@
--
-- The output contains duplicates.
--
-- The following are the valid DB engine values:
--
-- -   @aurora@ (for MySQL 5.6-compatible Aurora)
--
-- -   @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
--     Aurora)
--
-- -   @aurora-postgresql@
--
-- -   @mysql@
--
-- -   @postgres@
createDBClusterParameterGroup_dbParameterGroupFamily :: Lens.Lens' CreateDBClusterParameterGroup Prelude.Text
createDBClusterParameterGroup_dbParameterGroupFamily :: Lens' CreateDBClusterParameterGroup Text
createDBClusterParameterGroup_dbParameterGroupFamily = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterParameterGroup' {Text
dbParameterGroupFamily :: Text
$sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
dbParameterGroupFamily} -> Text
dbParameterGroupFamily) (\s :: CreateDBClusterParameterGroup
s@CreateDBClusterParameterGroup' {} Text
a -> CreateDBClusterParameterGroup
s {$sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: Text
dbParameterGroupFamily = Text
a} :: CreateDBClusterParameterGroup)

-- | The description for the DB cluster parameter group.
createDBClusterParameterGroup_description :: Lens.Lens' CreateDBClusterParameterGroup Prelude.Text
createDBClusterParameterGroup_description :: Lens' CreateDBClusterParameterGroup Text
createDBClusterParameterGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterParameterGroup' {Text
description :: Text
$sel:description:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
description} -> Text
description) (\s :: CreateDBClusterParameterGroup
s@CreateDBClusterParameterGroup' {} Text
a -> CreateDBClusterParameterGroup
s {$sel:description:CreateDBClusterParameterGroup' :: Text
description = Text
a} :: CreateDBClusterParameterGroup)

instance
  Core.AWSRequest
    CreateDBClusterParameterGroup
  where
  type
    AWSResponse CreateDBClusterParameterGroup =
      CreateDBClusterParameterGroupResponse
  request :: (Service -> Service)
-> CreateDBClusterParameterGroup
-> Request CreateDBClusterParameterGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateDBClusterParameterGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDBClusterParameterGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"CreateDBClusterParameterGroupResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBClusterParameterGroup
-> Int -> CreateDBClusterParameterGroupResponse
CreateDBClusterParameterGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBClusterParameterGroup")
            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
    CreateDBClusterParameterGroup
  where
  hashWithSalt :: Int -> CreateDBClusterParameterGroup -> Int
hashWithSalt Int
_salt CreateDBClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
dbParameterGroupFamily :: Text
dbClusterParameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:tags:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbClusterParameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbParameterGroupFamily
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description

instance Prelude.NFData CreateDBClusterParameterGroup where
  rnf :: CreateDBClusterParameterGroup -> ()
rnf CreateDBClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
dbParameterGroupFamily :: Text
dbClusterParameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:tags:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbClusterParameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbParameterGroupFamily
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description

instance Data.ToHeaders CreateDBClusterParameterGroup where
  toHeaders :: CreateDBClusterParameterGroup -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery CreateDBClusterParameterGroup where
  toQuery :: CreateDBClusterParameterGroup -> QueryString
toQuery CreateDBClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
dbParameterGroupFamily :: Text
dbClusterParameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbParameterGroupFamily:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:dbClusterParameterGroupName:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Text
$sel:tags:CreateDBClusterParameterGroup' :: CreateDBClusterParameterGroup -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CreateDBClusterParameterGroup" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"DBClusterParameterGroupName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterParameterGroupName,
        ByteString
"DBParameterGroupFamily"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbParameterGroupFamily,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
description
      ]

-- | /See:/ 'newCreateDBClusterParameterGroupResponse' smart constructor.
data CreateDBClusterParameterGroupResponse = CreateDBClusterParameterGroupResponse'
  { CreateDBClusterParameterGroupResponse
-> Maybe DBClusterParameterGroup
dbClusterParameterGroup :: Prelude.Maybe DBClusterParameterGroup,
    -- | The response's http status code.
    CreateDBClusterParameterGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDBClusterParameterGroupResponse
-> CreateDBClusterParameterGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDBClusterParameterGroupResponse
-> CreateDBClusterParameterGroupResponse -> Bool
$c/= :: CreateDBClusterParameterGroupResponse
-> CreateDBClusterParameterGroupResponse -> Bool
== :: CreateDBClusterParameterGroupResponse
-> CreateDBClusterParameterGroupResponse -> Bool
$c== :: CreateDBClusterParameterGroupResponse
-> CreateDBClusterParameterGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateDBClusterParameterGroupResponse]
ReadPrec CreateDBClusterParameterGroupResponse
Int -> ReadS CreateDBClusterParameterGroupResponse
ReadS [CreateDBClusterParameterGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDBClusterParameterGroupResponse]
$creadListPrec :: ReadPrec [CreateDBClusterParameterGroupResponse]
readPrec :: ReadPrec CreateDBClusterParameterGroupResponse
$creadPrec :: ReadPrec CreateDBClusterParameterGroupResponse
readList :: ReadS [CreateDBClusterParameterGroupResponse]
$creadList :: ReadS [CreateDBClusterParameterGroupResponse]
readsPrec :: Int -> ReadS CreateDBClusterParameterGroupResponse
$creadsPrec :: Int -> ReadS CreateDBClusterParameterGroupResponse
Prelude.Read, Int -> CreateDBClusterParameterGroupResponse -> ShowS
[CreateDBClusterParameterGroupResponse] -> ShowS
CreateDBClusterParameterGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDBClusterParameterGroupResponse] -> ShowS
$cshowList :: [CreateDBClusterParameterGroupResponse] -> ShowS
show :: CreateDBClusterParameterGroupResponse -> String
$cshow :: CreateDBClusterParameterGroupResponse -> String
showsPrec :: Int -> CreateDBClusterParameterGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateDBClusterParameterGroupResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDBClusterParameterGroupResponse x
-> CreateDBClusterParameterGroupResponse
forall x.
CreateDBClusterParameterGroupResponse
-> Rep CreateDBClusterParameterGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDBClusterParameterGroupResponse x
-> CreateDBClusterParameterGroupResponse
$cfrom :: forall x.
CreateDBClusterParameterGroupResponse
-> Rep CreateDBClusterParameterGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDBClusterParameterGroupResponse' 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:
--
-- 'dbClusterParameterGroup', 'createDBClusterParameterGroupResponse_dbClusterParameterGroup' - Undocumented member.
--
-- 'httpStatus', 'createDBClusterParameterGroupResponse_httpStatus' - The response's http status code.
newCreateDBClusterParameterGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDBClusterParameterGroupResponse
newCreateDBClusterParameterGroupResponse :: Int -> CreateDBClusterParameterGroupResponse
newCreateDBClusterParameterGroupResponse Int
pHttpStatus_ =
  CreateDBClusterParameterGroupResponse'
    { $sel:dbClusterParameterGroup:CreateDBClusterParameterGroupResponse' :: Maybe DBClusterParameterGroup
dbClusterParameterGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDBClusterParameterGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createDBClusterParameterGroupResponse_dbClusterParameterGroup :: Lens.Lens' CreateDBClusterParameterGroupResponse (Prelude.Maybe DBClusterParameterGroup)
createDBClusterParameterGroupResponse_dbClusterParameterGroup :: Lens'
  CreateDBClusterParameterGroupResponse
  (Maybe DBClusterParameterGroup)
createDBClusterParameterGroupResponse_dbClusterParameterGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterParameterGroupResponse' {Maybe DBClusterParameterGroup
dbClusterParameterGroup :: Maybe DBClusterParameterGroup
$sel:dbClusterParameterGroup:CreateDBClusterParameterGroupResponse' :: CreateDBClusterParameterGroupResponse
-> Maybe DBClusterParameterGroup
dbClusterParameterGroup} -> Maybe DBClusterParameterGroup
dbClusterParameterGroup) (\s :: CreateDBClusterParameterGroupResponse
s@CreateDBClusterParameterGroupResponse' {} Maybe DBClusterParameterGroup
a -> CreateDBClusterParameterGroupResponse
s {$sel:dbClusterParameterGroup:CreateDBClusterParameterGroupResponse' :: Maybe DBClusterParameterGroup
dbClusterParameterGroup = Maybe DBClusterParameterGroup
a} :: CreateDBClusterParameterGroupResponse)

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

instance
  Prelude.NFData
    CreateDBClusterParameterGroupResponse
  where
  rnf :: CreateDBClusterParameterGroupResponse -> ()
rnf CreateDBClusterParameterGroupResponse' {Int
Maybe DBClusterParameterGroup
httpStatus :: Int
dbClusterParameterGroup :: Maybe DBClusterParameterGroup
$sel:httpStatus:CreateDBClusterParameterGroupResponse' :: CreateDBClusterParameterGroupResponse -> Int
$sel:dbClusterParameterGroup:CreateDBClusterParameterGroupResponse' :: CreateDBClusterParameterGroupResponse
-> Maybe DBClusterParameterGroup
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DBClusterParameterGroup
dbClusterParameterGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus