{-# 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.CreateParameterGroup
-- 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 parameter group. A parameter group is a collection of
-- parameters that you apply to all of the nodes in a DAX cluster.
module Amazonka.DAX.CreateParameterGroup
  ( -- * Creating a Request
    CreateParameterGroup (..),
    newCreateParameterGroup,

    -- * Request Lenses
    createParameterGroup_description,
    createParameterGroup_parameterGroupName,

    -- * Destructuring the Response
    CreateParameterGroupResponse (..),
    newCreateParameterGroupResponse,

    -- * Response Lenses
    createParameterGroupResponse_parameterGroup,
    createParameterGroupResponse_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:/ 'newCreateParameterGroup' smart constructor.
data CreateParameterGroup = CreateParameterGroup'
  { -- | A description of the parameter group.
    CreateParameterGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the parameter group to apply to all of the clusters in this
    -- replication group.
    CreateParameterGroup -> Text
parameterGroupName :: Prelude.Text
  }
  deriving (CreateParameterGroup -> CreateParameterGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateParameterGroup -> CreateParameterGroup -> Bool
$c/= :: CreateParameterGroup -> CreateParameterGroup -> Bool
== :: CreateParameterGroup -> CreateParameterGroup -> Bool
$c== :: CreateParameterGroup -> CreateParameterGroup -> Bool
Prelude.Eq, ReadPrec [CreateParameterGroup]
ReadPrec CreateParameterGroup
Int -> ReadS CreateParameterGroup
ReadS [CreateParameterGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateParameterGroup]
$creadListPrec :: ReadPrec [CreateParameterGroup]
readPrec :: ReadPrec CreateParameterGroup
$creadPrec :: ReadPrec CreateParameterGroup
readList :: ReadS [CreateParameterGroup]
$creadList :: ReadS [CreateParameterGroup]
readsPrec :: Int -> ReadS CreateParameterGroup
$creadsPrec :: Int -> ReadS CreateParameterGroup
Prelude.Read, Int -> CreateParameterGroup -> ShowS
[CreateParameterGroup] -> ShowS
CreateParameterGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateParameterGroup] -> ShowS
$cshowList :: [CreateParameterGroup] -> ShowS
show :: CreateParameterGroup -> String
$cshow :: CreateParameterGroup -> String
showsPrec :: Int -> CreateParameterGroup -> ShowS
$cshowsPrec :: Int -> CreateParameterGroup -> ShowS
Prelude.Show, forall x. Rep CreateParameterGroup x -> CreateParameterGroup
forall x. CreateParameterGroup -> Rep CreateParameterGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateParameterGroup x -> CreateParameterGroup
$cfrom :: forall x. CreateParameterGroup -> Rep CreateParameterGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateParameterGroup' 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', 'createParameterGroup_description' - A description of the parameter group.
--
-- 'parameterGroupName', 'createParameterGroup_parameterGroupName' - The name of the parameter group to apply to all of the clusters in this
-- replication group.
newCreateParameterGroup ::
  -- | 'parameterGroupName'
  Prelude.Text ->
  CreateParameterGroup
newCreateParameterGroup :: Text -> CreateParameterGroup
newCreateParameterGroup Text
pParameterGroupName_ =
  CreateParameterGroup'
    { $sel:description:CreateParameterGroup' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:parameterGroupName:CreateParameterGroup' :: Text
parameterGroupName = Text
pParameterGroupName_
    }

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

-- | The name of the parameter group to apply to all of the clusters in this
-- replication group.
createParameterGroup_parameterGroupName :: Lens.Lens' CreateParameterGroup Prelude.Text
createParameterGroup_parameterGroupName :: Lens' CreateParameterGroup Text
createParameterGroup_parameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateParameterGroup' {Text
parameterGroupName :: Text
$sel:parameterGroupName:CreateParameterGroup' :: CreateParameterGroup -> Text
parameterGroupName} -> Text
parameterGroupName) (\s :: CreateParameterGroup
s@CreateParameterGroup' {} Text
a -> CreateParameterGroup
s {$sel:parameterGroupName:CreateParameterGroup' :: Text
parameterGroupName = Text
a} :: CreateParameterGroup)

instance Core.AWSRequest CreateParameterGroup where
  type
    AWSResponse CreateParameterGroup =
      CreateParameterGroupResponse
  request :: (Service -> Service)
-> CreateParameterGroup -> Request CreateParameterGroup
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 CreateParameterGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateParameterGroup)))
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 ParameterGroup -> Int -> CreateParameterGroupResponse
CreateParameterGroupResponse'
            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
"ParameterGroup")
            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 CreateParameterGroup where
  hashWithSalt :: Int -> CreateParameterGroup -> Int
hashWithSalt Int
_salt CreateParameterGroup' {Maybe Text
Text
parameterGroupName :: Text
description :: Maybe Text
$sel:parameterGroupName:CreateParameterGroup' :: CreateParameterGroup -> Text
$sel:description:CreateParameterGroup' :: CreateParameterGroup -> 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
parameterGroupName

instance Prelude.NFData CreateParameterGroup where
  rnf :: CreateParameterGroup -> ()
rnf CreateParameterGroup' {Maybe Text
Text
parameterGroupName :: Text
description :: Maybe Text
$sel:parameterGroupName:CreateParameterGroup' :: CreateParameterGroup -> Text
$sel:description:CreateParameterGroup' :: CreateParameterGroup -> 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
parameterGroupName

instance Data.ToHeaders CreateParameterGroup where
  toHeaders :: CreateParameterGroup -> 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.CreateParameterGroup" ::
                          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 CreateParameterGroup where
  toJSON :: CreateParameterGroup -> Value
toJSON CreateParameterGroup' {Maybe Text
Text
parameterGroupName :: Text
description :: Maybe Text
$sel:parameterGroupName:CreateParameterGroup' :: CreateParameterGroup -> Text
$sel:description:CreateParameterGroup' :: CreateParameterGroup -> 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
"ParameterGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
parameterGroupName)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateParameterGroupResponse' 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:
--
-- 'parameterGroup', 'createParameterGroupResponse_parameterGroup' - Represents the output of a /CreateParameterGroup/ action.
--
-- 'httpStatus', 'createParameterGroupResponse_httpStatus' - The response's http status code.
newCreateParameterGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateParameterGroupResponse
newCreateParameterGroupResponse :: Int -> CreateParameterGroupResponse
newCreateParameterGroupResponse Int
pHttpStatus_ =
  CreateParameterGroupResponse'
    { $sel:parameterGroup:CreateParameterGroupResponse' :: Maybe ParameterGroup
parameterGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateParameterGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the output of a /CreateParameterGroup/ action.
createParameterGroupResponse_parameterGroup :: Lens.Lens' CreateParameterGroupResponse (Prelude.Maybe ParameterGroup)
createParameterGroupResponse_parameterGroup :: Lens' CreateParameterGroupResponse (Maybe ParameterGroup)
createParameterGroupResponse_parameterGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateParameterGroupResponse' {Maybe ParameterGroup
parameterGroup :: Maybe ParameterGroup
$sel:parameterGroup:CreateParameterGroupResponse' :: CreateParameterGroupResponse -> Maybe ParameterGroup
parameterGroup} -> Maybe ParameterGroup
parameterGroup) (\s :: CreateParameterGroupResponse
s@CreateParameterGroupResponse' {} Maybe ParameterGroup
a -> CreateParameterGroupResponse
s {$sel:parameterGroup:CreateParameterGroupResponse' :: Maybe ParameterGroup
parameterGroup = Maybe ParameterGroup
a} :: CreateParameterGroupResponse)

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

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