{-# 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.DAX.CreateSubnetGroup
-- 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 subnet group.
module Amazonka.DAX.CreateSubnetGroup
  ( -- * Creating a Request
    CreateSubnetGroup (..),
    newCreateSubnetGroup,

    -- * Request Lenses
    createSubnetGroup_description,
    createSubnetGroup_subnetGroupName,
    createSubnetGroup_subnetIds,

    -- * Destructuring the Response
    CreateSubnetGroupResponse (..),
    newCreateSubnetGroupResponse,

    -- * Response Lenses
    createSubnetGroupResponse_subnetGroup,
    createSubnetGroupResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.DAX.Types
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:/ 'newCreateSubnetGroup' smart constructor.
data CreateSubnetGroup = CreateSubnetGroup'
  { -- | A description for the subnet group
    CreateSubnetGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A name for the subnet group. This value is stored as a lowercase string.
    CreateSubnetGroup -> Text
subnetGroupName :: Prelude.Text,
    -- | A list of VPC subnet IDs for the subnet group.
    CreateSubnetGroup -> [Text]
subnetIds :: [Prelude.Text]
  }
  deriving (CreateSubnetGroup -> CreateSubnetGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSubnetGroup -> CreateSubnetGroup -> Bool
$c/= :: CreateSubnetGroup -> CreateSubnetGroup -> Bool
== :: CreateSubnetGroup -> CreateSubnetGroup -> Bool
$c== :: CreateSubnetGroup -> CreateSubnetGroup -> Bool
Prelude.Eq, ReadPrec [CreateSubnetGroup]
ReadPrec CreateSubnetGroup
Int -> ReadS CreateSubnetGroup
ReadS [CreateSubnetGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSubnetGroup]
$creadListPrec :: ReadPrec [CreateSubnetGroup]
readPrec :: ReadPrec CreateSubnetGroup
$creadPrec :: ReadPrec CreateSubnetGroup
readList :: ReadS [CreateSubnetGroup]
$creadList :: ReadS [CreateSubnetGroup]
readsPrec :: Int -> ReadS CreateSubnetGroup
$creadsPrec :: Int -> ReadS CreateSubnetGroup
Prelude.Read, Int -> CreateSubnetGroup -> ShowS
[CreateSubnetGroup] -> ShowS
CreateSubnetGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSubnetGroup] -> ShowS
$cshowList :: [CreateSubnetGroup] -> ShowS
show :: CreateSubnetGroup -> String
$cshow :: CreateSubnetGroup -> String
showsPrec :: Int -> CreateSubnetGroup -> ShowS
$cshowsPrec :: Int -> CreateSubnetGroup -> ShowS
Prelude.Show, forall x. Rep CreateSubnetGroup x -> CreateSubnetGroup
forall x. CreateSubnetGroup -> Rep CreateSubnetGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSubnetGroup x -> CreateSubnetGroup
$cfrom :: forall x. CreateSubnetGroup -> Rep CreateSubnetGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateSubnetGroup' 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', 'createSubnetGroup_description' - A description for the subnet group
--
-- 'subnetGroupName', 'createSubnetGroup_subnetGroupName' - A name for the subnet group. This value is stored as a lowercase string.
--
-- 'subnetIds', 'createSubnetGroup_subnetIds' - A list of VPC subnet IDs for the subnet group.
newCreateSubnetGroup ::
  -- | 'subnetGroupName'
  Prelude.Text ->
  CreateSubnetGroup
newCreateSubnetGroup :: Text -> CreateSubnetGroup
newCreateSubnetGroup Text
pSubnetGroupName_ =
  CreateSubnetGroup'
    { $sel:description:CreateSubnetGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetGroupName:CreateSubnetGroup' :: Text
subnetGroupName = Text
pSubnetGroupName_,
      $sel:subnetIds:CreateSubnetGroup' :: [Text]
subnetIds = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A name for the subnet group. This value is stored as a lowercase string.
createSubnetGroup_subnetGroupName :: Lens.Lens' CreateSubnetGroup Prelude.Text
createSubnetGroup_subnetGroupName :: Lens' CreateSubnetGroup Text
createSubnetGroup_subnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSubnetGroup' {Text
subnetGroupName :: Text
$sel:subnetGroupName:CreateSubnetGroup' :: CreateSubnetGroup -> Text
subnetGroupName} -> Text
subnetGroupName) (\s :: CreateSubnetGroup
s@CreateSubnetGroup' {} Text
a -> CreateSubnetGroup
s {$sel:subnetGroupName:CreateSubnetGroup' :: Text
subnetGroupName = Text
a} :: CreateSubnetGroup)

-- | A list of VPC subnet IDs for the subnet group.
createSubnetGroup_subnetIds :: Lens.Lens' CreateSubnetGroup [Prelude.Text]
createSubnetGroup_subnetIds :: Lens' CreateSubnetGroup [Text]
createSubnetGroup_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSubnetGroup' {[Text]
subnetIds :: [Text]
$sel:subnetIds:CreateSubnetGroup' :: CreateSubnetGroup -> [Text]
subnetIds} -> [Text]
subnetIds) (\s :: CreateSubnetGroup
s@CreateSubnetGroup' {} [Text]
a -> CreateSubnetGroup
s {$sel:subnetIds:CreateSubnetGroup' :: [Text]
subnetIds = [Text]
a} :: CreateSubnetGroup) 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 CreateSubnetGroup where
  type
    AWSResponse CreateSubnetGroup =
      CreateSubnetGroupResponse
  request :: (Service -> Service)
-> CreateSubnetGroup -> Request CreateSubnetGroup
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 CreateSubnetGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSubnetGroup)))
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 ->
          Maybe SubnetGroup -> Int -> CreateSubnetGroupResponse
CreateSubnetGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SubnetGroup")
            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 CreateSubnetGroup where
  hashWithSalt :: Int -> CreateSubnetGroup -> Int
hashWithSalt Int
_salt CreateSubnetGroup' {[Text]
Maybe Text
Text
subnetIds :: [Text]
subnetGroupName :: Text
description :: Maybe Text
$sel:subnetIds:CreateSubnetGroup' :: CreateSubnetGroup -> [Text]
$sel:subnetGroupName:CreateSubnetGroup' :: CreateSubnetGroup -> Text
$sel:description:CreateSubnetGroup' :: CreateSubnetGroup -> 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` Text
subnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
subnetIds

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

instance Data.ToHeaders CreateSubnetGroup where
  toHeaders :: CreateSubnetGroup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonDAXV3.CreateSubnetGroup" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateSubnetGroup where
  toJSON :: CreateSubnetGroup -> Value
toJSON CreateSubnetGroup' {[Text]
Maybe Text
Text
subnetIds :: [Text]
subnetGroupName :: Text
description :: Maybe Text
$sel:subnetIds:CreateSubnetGroup' :: CreateSubnetGroup -> [Text]
$sel:subnetGroupName:CreateSubnetGroup' :: CreateSubnetGroup -> Text
$sel:description:CreateSubnetGroup' :: CreateSubnetGroup -> 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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SubnetGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
subnetGroupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"SubnetIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
subnetIds)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateSubnetGroupResponse' 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:
--
-- 'subnetGroup', 'createSubnetGroupResponse_subnetGroup' - Represents the output of a /CreateSubnetGroup/ operation.
--
-- 'httpStatus', 'createSubnetGroupResponse_httpStatus' - The response's http status code.
newCreateSubnetGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSubnetGroupResponse
newCreateSubnetGroupResponse :: Int -> CreateSubnetGroupResponse
newCreateSubnetGroupResponse Int
pHttpStatus_ =
  CreateSubnetGroupResponse'
    { $sel:subnetGroup:CreateSubnetGroupResponse' :: Maybe SubnetGroup
subnetGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSubnetGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the output of a /CreateSubnetGroup/ operation.
createSubnetGroupResponse_subnetGroup :: Lens.Lens' CreateSubnetGroupResponse (Prelude.Maybe SubnetGroup)
createSubnetGroupResponse_subnetGroup :: Lens' CreateSubnetGroupResponse (Maybe SubnetGroup)
createSubnetGroupResponse_subnetGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSubnetGroupResponse' {Maybe SubnetGroup
subnetGroup :: Maybe SubnetGroup
$sel:subnetGroup:CreateSubnetGroupResponse' :: CreateSubnetGroupResponse -> Maybe SubnetGroup
subnetGroup} -> Maybe SubnetGroup
subnetGroup) (\s :: CreateSubnetGroupResponse
s@CreateSubnetGroupResponse' {} Maybe SubnetGroup
a -> CreateSubnetGroupResponse
s {$sel:subnetGroup:CreateSubnetGroupResponse' :: Maybe SubnetGroup
subnetGroup = Maybe SubnetGroup
a} :: CreateSubnetGroupResponse)

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

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