{-# 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.CreateClusterSubnetGroup
-- 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 Amazon Redshift subnet group. You must provide a list of
-- one or more subnets in your existing Amazon Virtual Private Cloud
-- (Amazon VPC) when creating Amazon Redshift subnet group.
--
-- For information about subnet groups, go to
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/working-with-cluster-subnet-groups.html Amazon Redshift Cluster Subnet Groups>
-- in the /Amazon Redshift Cluster Management Guide/.
module Amazonka.Redshift.CreateClusterSubnetGroup
  ( -- * Creating a Request
    CreateClusterSubnetGroup (..),
    newCreateClusterSubnetGroup,

    -- * Request Lenses
    createClusterSubnetGroup_tags,
    createClusterSubnetGroup_clusterSubnetGroupName,
    createClusterSubnetGroup_description,
    createClusterSubnetGroup_subnetIds,

    -- * Destructuring the Response
    CreateClusterSubnetGroupResponse (..),
    newCreateClusterSubnetGroupResponse,

    -- * Response Lenses
    createClusterSubnetGroupResponse_clusterSubnetGroup,
    createClusterSubnetGroupResponse_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:/ 'newCreateClusterSubnetGroup' smart constructor.
data CreateClusterSubnetGroup = CreateClusterSubnetGroup'
  { -- | A list of tag instances.
    CreateClusterSubnetGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name for the subnet group. Amazon Redshift stores the value as a
    -- lowercase string.
    --
    -- Constraints:
    --
    -- -   Must contain no more than 255 alphanumeric characters or hyphens.
    --
    -- -   Must not be \"Default\".
    --
    -- -   Must be unique for all subnet groups that are created by your Amazon
    --     Web Services account.
    --
    -- Example: @examplesubnetgroup@
    CreateClusterSubnetGroup -> Text
clusterSubnetGroupName :: Prelude.Text,
    -- | A description for the subnet group.
    CreateClusterSubnetGroup -> Text
description :: Prelude.Text,
    -- | An array of VPC subnet IDs. A maximum of 20 subnets can be modified in a
    -- single request.
    CreateClusterSubnetGroup -> [Text]
subnetIds :: [Prelude.Text]
  }
  deriving (CreateClusterSubnetGroup -> CreateClusterSubnetGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateClusterSubnetGroup -> CreateClusterSubnetGroup -> Bool
$c/= :: CreateClusterSubnetGroup -> CreateClusterSubnetGroup -> Bool
== :: CreateClusterSubnetGroup -> CreateClusterSubnetGroup -> Bool
$c== :: CreateClusterSubnetGroup -> CreateClusterSubnetGroup -> Bool
Prelude.Eq, ReadPrec [CreateClusterSubnetGroup]
ReadPrec CreateClusterSubnetGroup
Int -> ReadS CreateClusterSubnetGroup
ReadS [CreateClusterSubnetGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateClusterSubnetGroup]
$creadListPrec :: ReadPrec [CreateClusterSubnetGroup]
readPrec :: ReadPrec CreateClusterSubnetGroup
$creadPrec :: ReadPrec CreateClusterSubnetGroup
readList :: ReadS [CreateClusterSubnetGroup]
$creadList :: ReadS [CreateClusterSubnetGroup]
readsPrec :: Int -> ReadS CreateClusterSubnetGroup
$creadsPrec :: Int -> ReadS CreateClusterSubnetGroup
Prelude.Read, Int -> CreateClusterSubnetGroup -> ShowS
[CreateClusterSubnetGroup] -> ShowS
CreateClusterSubnetGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateClusterSubnetGroup] -> ShowS
$cshowList :: [CreateClusterSubnetGroup] -> ShowS
show :: CreateClusterSubnetGroup -> String
$cshow :: CreateClusterSubnetGroup -> String
showsPrec :: Int -> CreateClusterSubnetGroup -> ShowS
$cshowsPrec :: Int -> CreateClusterSubnetGroup -> ShowS
Prelude.Show, forall x.
Rep CreateClusterSubnetGroup x -> CreateClusterSubnetGroup
forall x.
CreateClusterSubnetGroup -> Rep CreateClusterSubnetGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateClusterSubnetGroup x -> CreateClusterSubnetGroup
$cfrom :: forall x.
CreateClusterSubnetGroup -> Rep CreateClusterSubnetGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateClusterSubnetGroup' 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', 'createClusterSubnetGroup_tags' - A list of tag instances.
--
-- 'clusterSubnetGroupName', 'createClusterSubnetGroup_clusterSubnetGroupName' - The name for the subnet group. Amazon Redshift stores the value as a
-- lowercase string.
--
-- Constraints:
--
-- -   Must contain no more than 255 alphanumeric characters or hyphens.
--
-- -   Must not be \"Default\".
--
-- -   Must be unique for all subnet groups that are created by your Amazon
--     Web Services account.
--
-- Example: @examplesubnetgroup@
--
-- 'description', 'createClusterSubnetGroup_description' - A description for the subnet group.
--
-- 'subnetIds', 'createClusterSubnetGroup_subnetIds' - An array of VPC subnet IDs. A maximum of 20 subnets can be modified in a
-- single request.
newCreateClusterSubnetGroup ::
  -- | 'clusterSubnetGroupName'
  Prelude.Text ->
  -- | 'description'
  Prelude.Text ->
  CreateClusterSubnetGroup
newCreateClusterSubnetGroup :: Text -> Text -> CreateClusterSubnetGroup
newCreateClusterSubnetGroup
  Text
pClusterSubnetGroupName_
  Text
pDescription_ =
    CreateClusterSubnetGroup'
      { $sel:tags:CreateClusterSubnetGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:clusterSubnetGroupName:CreateClusterSubnetGroup' :: Text
clusterSubnetGroupName = Text
pClusterSubnetGroupName_,
        $sel:description:CreateClusterSubnetGroup' :: Text
description = Text
pDescription_,
        $sel:subnetIds:CreateClusterSubnetGroup' :: [Text]
subnetIds = forall a. Monoid a => a
Prelude.mempty
      }

-- | A list of tag instances.
createClusterSubnetGroup_tags :: Lens.Lens' CreateClusterSubnetGroup (Prelude.Maybe [Tag])
createClusterSubnetGroup_tags :: Lens' CreateClusterSubnetGroup (Maybe [Tag])
createClusterSubnetGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterSubnetGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateClusterSubnetGroup
s@CreateClusterSubnetGroup' {} Maybe [Tag]
a -> CreateClusterSubnetGroup
s {$sel:tags:CreateClusterSubnetGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateClusterSubnetGroup) 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 for the subnet group. Amazon Redshift stores the value as a
-- lowercase string.
--
-- Constraints:
--
-- -   Must contain no more than 255 alphanumeric characters or hyphens.
--
-- -   Must not be \"Default\".
--
-- -   Must be unique for all subnet groups that are created by your Amazon
--     Web Services account.
--
-- Example: @examplesubnetgroup@
createClusterSubnetGroup_clusterSubnetGroupName :: Lens.Lens' CreateClusterSubnetGroup Prelude.Text
createClusterSubnetGroup_clusterSubnetGroupName :: Lens' CreateClusterSubnetGroup Text
createClusterSubnetGroup_clusterSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterSubnetGroup' {Text
clusterSubnetGroupName :: Text
$sel:clusterSubnetGroupName:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Text
clusterSubnetGroupName} -> Text
clusterSubnetGroupName) (\s :: CreateClusterSubnetGroup
s@CreateClusterSubnetGroup' {} Text
a -> CreateClusterSubnetGroup
s {$sel:clusterSubnetGroupName:CreateClusterSubnetGroup' :: Text
clusterSubnetGroupName = Text
a} :: CreateClusterSubnetGroup)

-- | A description for the subnet group.
createClusterSubnetGroup_description :: Lens.Lens' CreateClusterSubnetGroup Prelude.Text
createClusterSubnetGroup_description :: Lens' CreateClusterSubnetGroup Text
createClusterSubnetGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterSubnetGroup' {Text
description :: Text
$sel:description:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Text
description} -> Text
description) (\s :: CreateClusterSubnetGroup
s@CreateClusterSubnetGroup' {} Text
a -> CreateClusterSubnetGroup
s {$sel:description:CreateClusterSubnetGroup' :: Text
description = Text
a} :: CreateClusterSubnetGroup)

-- | An array of VPC subnet IDs. A maximum of 20 subnets can be modified in a
-- single request.
createClusterSubnetGroup_subnetIds :: Lens.Lens' CreateClusterSubnetGroup [Prelude.Text]
createClusterSubnetGroup_subnetIds :: Lens' CreateClusterSubnetGroup [Text]
createClusterSubnetGroup_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterSubnetGroup' {[Text]
subnetIds :: [Text]
$sel:subnetIds:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> [Text]
subnetIds} -> [Text]
subnetIds) (\s :: CreateClusterSubnetGroup
s@CreateClusterSubnetGroup' {} [Text]
a -> CreateClusterSubnetGroup
s {$sel:subnetIds:CreateClusterSubnetGroup' :: [Text]
subnetIds = [Text]
a} :: CreateClusterSubnetGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

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

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

instance Data.ToQuery CreateClusterSubnetGroup where
  toQuery :: CreateClusterSubnetGroup -> QueryString
toQuery CreateClusterSubnetGroup' {[Text]
Maybe [Tag]
Text
subnetIds :: [Text]
description :: Text
clusterSubnetGroupName :: Text
tags :: Maybe [Tag]
$sel:subnetIds:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> [Text]
$sel:description:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Text
$sel:clusterSubnetGroupName:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Text
$sel:tags:CreateClusterSubnetGroup' :: CreateClusterSubnetGroup -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateClusterSubnetGroup" :: 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
"ClusterSubnetGroupName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clusterSubnetGroupName,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
description,
        ByteString
"SubnetIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SubnetIdentifier" [Text]
subnetIds
      ]

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

-- |
-- Create a value of 'CreateClusterSubnetGroupResponse' 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:
--
-- 'clusterSubnetGroup', 'createClusterSubnetGroupResponse_clusterSubnetGroup' - Undocumented member.
--
-- 'httpStatus', 'createClusterSubnetGroupResponse_httpStatus' - The response's http status code.
newCreateClusterSubnetGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateClusterSubnetGroupResponse
newCreateClusterSubnetGroupResponse :: Int -> CreateClusterSubnetGroupResponse
newCreateClusterSubnetGroupResponse Int
pHttpStatus_ =
  CreateClusterSubnetGroupResponse'
    { $sel:clusterSubnetGroup:CreateClusterSubnetGroupResponse' :: Maybe ClusterSubnetGroup
clusterSubnetGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateClusterSubnetGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createClusterSubnetGroupResponse_clusterSubnetGroup :: Lens.Lens' CreateClusterSubnetGroupResponse (Prelude.Maybe ClusterSubnetGroup)
createClusterSubnetGroupResponse_clusterSubnetGroup :: Lens' CreateClusterSubnetGroupResponse (Maybe ClusterSubnetGroup)
createClusterSubnetGroupResponse_clusterSubnetGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateClusterSubnetGroupResponse' {Maybe ClusterSubnetGroup
clusterSubnetGroup :: Maybe ClusterSubnetGroup
$sel:clusterSubnetGroup:CreateClusterSubnetGroupResponse' :: CreateClusterSubnetGroupResponse -> Maybe ClusterSubnetGroup
clusterSubnetGroup} -> Maybe ClusterSubnetGroup
clusterSubnetGroup) (\s :: CreateClusterSubnetGroupResponse
s@CreateClusterSubnetGroupResponse' {} Maybe ClusterSubnetGroup
a -> CreateClusterSubnetGroupResponse
s {$sel:clusterSubnetGroup:CreateClusterSubnetGroupResponse' :: Maybe ClusterSubnetGroup
clusterSubnetGroup = Maybe ClusterSubnetGroup
a} :: CreateClusterSubnetGroupResponse)

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

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