{-# 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.Redshift.CreateClusterParameterGroup
-- 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 an Amazon Redshift parameter group.
--
-- Creating parameter groups is independent of creating clusters. You can
-- associate a cluster with a parameter group when you create the cluster.
-- You can also associate an existing cluster with a parameter group after
-- the cluster is created by using ModifyCluster.
--
-- Parameters in the parameter group define specific behavior that applies
-- to the databases you create on the cluster. For more information about
-- parameters and parameter groups, go to
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/working-with-parameter-groups.html Amazon Redshift Parameter Groups>
-- in the /Amazon Redshift Cluster Management Guide/.
module Amazonka.Redshift.CreateClusterParameterGroup
  ( -- * Creating a Request
    CreateClusterParameterGroup (..),
    newCreateClusterParameterGroup,

    -- * Request Lenses
    createClusterParameterGroup_tags,
    createClusterParameterGroup_parameterGroupName,
    createClusterParameterGroup_parameterGroupFamily,
    createClusterParameterGroup_description,

    -- * Destructuring the Response
    CreateClusterParameterGroupResponse (..),
    newCreateClusterParameterGroupResponse,

    -- * Response Lenses
    createClusterParameterGroupResponse_clusterParameterGroup,
    createClusterParameterGroupResponse_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.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newCreateClusterParameterGroup' smart constructor.
data CreateClusterParameterGroup = CreateClusterParameterGroup'
  { -- | A list of tag instances.
    CreateClusterParameterGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the cluster parameter group.
    --
    -- Constraints:
    --
    -- -   Must be 1 to 255 alphanumeric characters or hyphens
    --
    -- -   First character must be a letter.
    --
    -- -   Cannot end with a hyphen or contain two consecutive hyphens.
    --
    -- -   Must be unique withing your Amazon Web Services account.
    --
    -- This value is stored as a lower-case string.
    CreateClusterParameterGroup -> Text
parameterGroupName :: Prelude.Text,
    -- | The Amazon Redshift engine version to which the cluster parameter group
    -- applies. The cluster engine version determines the set of parameters.
    --
    -- To get a list of valid parameter group family names, you can call
    -- DescribeClusterParameterGroups. By default, Amazon Redshift returns a
    -- list of all the parameter groups that are owned by your Amazon Web
    -- Services account, including the default parameter groups for each Amazon
    -- Redshift engine version. The parameter group family names associated
    -- with the default parameter groups provide you the valid values. For
    -- example, a valid family name is \"redshift-1.0\".
    CreateClusterParameterGroup -> Text
parameterGroupFamily :: Prelude.Text,
    -- | A description of the parameter group.
    CreateClusterParameterGroup -> Text
description :: Prelude.Text
  }
  deriving (CreateClusterParameterGroup -> CreateClusterParameterGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClusterParameterGroup -> CreateClusterParameterGroup -> Bool
$c/= :: CreateClusterParameterGroup -> CreateClusterParameterGroup -> Bool
== :: CreateClusterParameterGroup -> CreateClusterParameterGroup -> Bool
$c== :: CreateClusterParameterGroup -> CreateClusterParameterGroup -> Bool
Prelude.Eq, ReadPrec [CreateClusterParameterGroup]
ReadPrec CreateClusterParameterGroup
Int -> ReadS CreateClusterParameterGroup
ReadS [CreateClusterParameterGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClusterParameterGroup]
$creadListPrec :: ReadPrec [CreateClusterParameterGroup]
readPrec :: ReadPrec CreateClusterParameterGroup
$creadPrec :: ReadPrec CreateClusterParameterGroup
readList :: ReadS [CreateClusterParameterGroup]
$creadList :: ReadS [CreateClusterParameterGroup]
readsPrec :: Int -> ReadS CreateClusterParameterGroup
$creadsPrec :: Int -> ReadS CreateClusterParameterGroup
Prelude.Read, Int -> CreateClusterParameterGroup -> ShowS
[CreateClusterParameterGroup] -> ShowS
CreateClusterParameterGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClusterParameterGroup] -> ShowS
$cshowList :: [CreateClusterParameterGroup] -> ShowS
show :: CreateClusterParameterGroup -> String
$cshow :: CreateClusterParameterGroup -> String
showsPrec :: Int -> CreateClusterParameterGroup -> ShowS
$cshowsPrec :: Int -> CreateClusterParameterGroup -> ShowS
Prelude.Show, forall x.
Rep CreateClusterParameterGroup x -> CreateClusterParameterGroup
forall x.
CreateClusterParameterGroup -> Rep CreateClusterParameterGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateClusterParameterGroup x -> CreateClusterParameterGroup
$cfrom :: forall x.
CreateClusterParameterGroup -> Rep CreateClusterParameterGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateClusterParameterGroup' 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', 'createClusterParameterGroup_tags' - A list of tag instances.
--
-- 'parameterGroupName', 'createClusterParameterGroup_parameterGroupName' - The name of the cluster parameter group.
--
-- Constraints:
--
-- -   Must be 1 to 255 alphanumeric characters or hyphens
--
-- -   First character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- -   Must be unique withing your Amazon Web Services account.
--
-- This value is stored as a lower-case string.
--
-- 'parameterGroupFamily', 'createClusterParameterGroup_parameterGroupFamily' - The Amazon Redshift engine version to which the cluster parameter group
-- applies. The cluster engine version determines the set of parameters.
--
-- To get a list of valid parameter group family names, you can call
-- DescribeClusterParameterGroups. By default, Amazon Redshift returns a
-- list of all the parameter groups that are owned by your Amazon Web
-- Services account, including the default parameter groups for each Amazon
-- Redshift engine version. The parameter group family names associated
-- with the default parameter groups provide you the valid values. For
-- example, a valid family name is \"redshift-1.0\".
--
-- 'description', 'createClusterParameterGroup_description' - A description of the parameter group.
newCreateClusterParameterGroup ::
  -- | 'parameterGroupName'
  Prelude.Text ->
  -- | 'parameterGroupFamily'
  Prelude.Text ->
  -- | 'description'
  Prelude.Text ->
  CreateClusterParameterGroup
newCreateClusterParameterGroup :: Text -> Text -> Text -> CreateClusterParameterGroup
newCreateClusterParameterGroup
  Text
pParameterGroupName_
  Text
pParameterGroupFamily_
  Text
pDescription_ =
    CreateClusterParameterGroup'
      { $sel:tags:CreateClusterParameterGroup' :: Maybe [Tag]
tags =
          forall a. Maybe a
Prelude.Nothing,
        $sel:parameterGroupName:CreateClusterParameterGroup' :: Text
parameterGroupName = Text
pParameterGroupName_,
        $sel:parameterGroupFamily:CreateClusterParameterGroup' :: Text
parameterGroupFamily = Text
pParameterGroupFamily_,
        $sel:description:CreateClusterParameterGroup' :: Text
description = Text
pDescription_
      }

-- | A list of tag instances.
createClusterParameterGroup_tags :: Lens.Lens' CreateClusterParameterGroup (Prelude.Maybe [Tag])
createClusterParameterGroup_tags :: Lens' CreateClusterParameterGroup (Maybe [Tag])
createClusterParameterGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterParameterGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateClusterParameterGroup
s@CreateClusterParameterGroup' {} Maybe [Tag]
a -> CreateClusterParameterGroup
s {$sel:tags:CreateClusterParameterGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateClusterParameterGroup) 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 cluster parameter group.
--
-- Constraints:
--
-- -   Must be 1 to 255 alphanumeric characters or hyphens
--
-- -   First character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- -   Must be unique withing your Amazon Web Services account.
--
-- This value is stored as a lower-case string.
createClusterParameterGroup_parameterGroupName :: Lens.Lens' CreateClusterParameterGroup Prelude.Text
createClusterParameterGroup_parameterGroupName :: Lens' CreateClusterParameterGroup Text
createClusterParameterGroup_parameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterParameterGroup' {Text
parameterGroupName :: Text
$sel:parameterGroupName:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
parameterGroupName} -> Text
parameterGroupName) (\s :: CreateClusterParameterGroup
s@CreateClusterParameterGroup' {} Text
a -> CreateClusterParameterGroup
s {$sel:parameterGroupName:CreateClusterParameterGroup' :: Text
parameterGroupName = Text
a} :: CreateClusterParameterGroup)

-- | The Amazon Redshift engine version to which the cluster parameter group
-- applies. The cluster engine version determines the set of parameters.
--
-- To get a list of valid parameter group family names, you can call
-- DescribeClusterParameterGroups. By default, Amazon Redshift returns a
-- list of all the parameter groups that are owned by your Amazon Web
-- Services account, including the default parameter groups for each Amazon
-- Redshift engine version. The parameter group family names associated
-- with the default parameter groups provide you the valid values. For
-- example, a valid family name is \"redshift-1.0\".
createClusterParameterGroup_parameterGroupFamily :: Lens.Lens' CreateClusterParameterGroup Prelude.Text
createClusterParameterGroup_parameterGroupFamily :: Lens' CreateClusterParameterGroup Text
createClusterParameterGroup_parameterGroupFamily = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterParameterGroup' {Text
parameterGroupFamily :: Text
$sel:parameterGroupFamily:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
parameterGroupFamily} -> Text
parameterGroupFamily) (\s :: CreateClusterParameterGroup
s@CreateClusterParameterGroup' {} Text
a -> CreateClusterParameterGroup
s {$sel:parameterGroupFamily:CreateClusterParameterGroup' :: Text
parameterGroupFamily = Text
a} :: CreateClusterParameterGroup)

-- | A description of the parameter group.
createClusterParameterGroup_description :: Lens.Lens' CreateClusterParameterGroup Prelude.Text
createClusterParameterGroup_description :: Lens' CreateClusterParameterGroup Text
createClusterParameterGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterParameterGroup' {Text
description :: Text
$sel:description:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
description} -> Text
description) (\s :: CreateClusterParameterGroup
s@CreateClusterParameterGroup' {} Text
a -> CreateClusterParameterGroup
s {$sel:description:CreateClusterParameterGroup' :: Text
description = Text
a} :: CreateClusterParameterGroup)

instance Core.AWSRequest CreateClusterParameterGroup where
  type
    AWSResponse CreateClusterParameterGroup =
      CreateClusterParameterGroupResponse
  request :: (Service -> Service)
-> CreateClusterParameterGroup
-> Request CreateClusterParameterGroup
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 CreateClusterParameterGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateClusterParameterGroup)))
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
"CreateClusterParameterGroupResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ClusterParameterGroup
-> Int -> CreateClusterParameterGroupResponse
CreateClusterParameterGroupResponse'
            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
"ClusterParameterGroup")
            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 CreateClusterParameterGroup where
  hashWithSalt :: Int -> CreateClusterParameterGroup -> Int
hashWithSalt Int
_salt CreateClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
parameterGroupFamily :: Text
parameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupFamily:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupName:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:tags:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> 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
parameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
parameterGroupFamily
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description

instance Prelude.NFData CreateClusterParameterGroup where
  rnf :: CreateClusterParameterGroup -> ()
rnf CreateClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
parameterGroupFamily :: Text
parameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupFamily:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupName:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:tags:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> 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
parameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
parameterGroupFamily
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description

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

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

instance Data.ToQuery CreateClusterParameterGroup where
  toQuery :: CreateClusterParameterGroup -> QueryString
toQuery CreateClusterParameterGroup' {Maybe [Tag]
Text
description :: Text
parameterGroupFamily :: Text
parameterGroupName :: Text
tags :: Maybe [Tag]
$sel:description:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupFamily:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:parameterGroupName:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Text
$sel:tags:CreateClusterParameterGroup' :: CreateClusterParameterGroup -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CreateClusterParameterGroup" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: 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
"ParameterGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
parameterGroupName,
        ByteString
"ParameterGroupFamily" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
parameterGroupFamily,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
description
      ]

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

-- |
-- Create a value of 'CreateClusterParameterGroupResponse' 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:
--
-- 'clusterParameterGroup', 'createClusterParameterGroupResponse_clusterParameterGroup' - Undocumented member.
--
-- 'httpStatus', 'createClusterParameterGroupResponse_httpStatus' - The response's http status code.
newCreateClusterParameterGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateClusterParameterGroupResponse
newCreateClusterParameterGroupResponse :: Int -> CreateClusterParameterGroupResponse
newCreateClusterParameterGroupResponse Int
pHttpStatus_ =
  CreateClusterParameterGroupResponse'
    { $sel:clusterParameterGroup:CreateClusterParameterGroupResponse' :: Maybe ClusterParameterGroup
clusterParameterGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateClusterParameterGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createClusterParameterGroupResponse_clusterParameterGroup :: Lens.Lens' CreateClusterParameterGroupResponse (Prelude.Maybe ClusterParameterGroup)
createClusterParameterGroupResponse_clusterParameterGroup :: Lens'
  CreateClusterParameterGroupResponse (Maybe ClusterParameterGroup)
createClusterParameterGroupResponse_clusterParameterGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterParameterGroupResponse' {Maybe ClusterParameterGroup
clusterParameterGroup :: Maybe ClusterParameterGroup
$sel:clusterParameterGroup:CreateClusterParameterGroupResponse' :: CreateClusterParameterGroupResponse -> Maybe ClusterParameterGroup
clusterParameterGroup} -> Maybe ClusterParameterGroup
clusterParameterGroup) (\s :: CreateClusterParameterGroupResponse
s@CreateClusterParameterGroupResponse' {} Maybe ClusterParameterGroup
a -> CreateClusterParameterGroupResponse
s {$sel:clusterParameterGroup:CreateClusterParameterGroupResponse' :: Maybe ClusterParameterGroup
clusterParameterGroup = Maybe ClusterParameterGroup
a} :: CreateClusterParameterGroupResponse)

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

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