{-# 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.ResetDBParameterGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the parameters of a DB parameter group to the engine\/system
-- default value. To reset specific parameters, provide a list of the
-- following: @ParameterName@ and @ApplyMethod@. To reset the entire DB
-- parameter group, specify the @DBParameterGroup@ name and
-- @ResetAllParameters@ parameters. When resetting the entire group,
-- dynamic parameters are updated immediately and static parameters are set
-- to @pending-reboot@ to take effect on the next DB instance restart or
-- @RebootDBInstance@ request.
module Amazonka.RDS.ResetDBParameterGroup
  ( -- * Creating a Request
    ResetDBParameterGroup (..),
    newResetDBParameterGroup,

    -- * Request Lenses
    resetDBParameterGroup_parameters,
    resetDBParameterGroup_resetAllParameters,
    resetDBParameterGroup_dbParameterGroupName,

    -- * Destructuring the Response
    DBParameterGroupNameMessage (..),
    newDBParameterGroupNameMessage,

    -- * Response Lenses
    dbParameterGroupNameMessage_dbParameterGroupName,
  )
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:/ 'newResetDBParameterGroup' smart constructor.
data ResetDBParameterGroup = ResetDBParameterGroup'
  { -- | To reset the entire DB parameter group, specify the @DBParameterGroup@
    -- name and @ResetAllParameters@ parameters. To reset specific parameters,
    -- provide a list of the following: @ParameterName@ and @ApplyMethod@. A
    -- maximum of 20 parameters can be modified in a single request.
    --
    -- __MySQL__
    --
    -- Valid Values (for Apply method): @immediate@ | @pending-reboot@
    --
    -- You can use the immediate value with dynamic parameters only. You can
    -- use the @pending-reboot@ value for both dynamic and static parameters,
    -- and changes are applied when DB instance reboots.
    --
    -- __MariaDB__
    --
    -- Valid Values (for Apply method): @immediate@ | @pending-reboot@
    --
    -- You can use the immediate value with dynamic parameters only. You can
    -- use the @pending-reboot@ value for both dynamic and static parameters,
    -- and changes are applied when DB instance reboots.
    --
    -- __Oracle__
    --
    -- Valid Values (for Apply method): @pending-reboot@
    ResetDBParameterGroup -> Maybe [Parameter]
parameters :: Prelude.Maybe [Parameter],
    -- | A value that indicates whether to reset all parameters in the DB
    -- parameter group to default values. By default, all parameters in the DB
    -- parameter group are reset to default values.
    ResetDBParameterGroup -> Maybe Bool
resetAllParameters :: Prelude.Maybe Prelude.Bool,
    -- | The name of the DB parameter group.
    --
    -- Constraints:
    --
    -- -   Must match the name of an existing @DBParameterGroup@.
    ResetDBParameterGroup -> Text
dbParameterGroupName :: Prelude.Text
  }
  deriving (ResetDBParameterGroup -> ResetDBParameterGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetDBParameterGroup -> ResetDBParameterGroup -> Bool
$c/= :: ResetDBParameterGroup -> ResetDBParameterGroup -> Bool
== :: ResetDBParameterGroup -> ResetDBParameterGroup -> Bool
$c== :: ResetDBParameterGroup -> ResetDBParameterGroup -> Bool
Prelude.Eq, ReadPrec [ResetDBParameterGroup]
ReadPrec ResetDBParameterGroup
Int -> ReadS ResetDBParameterGroup
ReadS [ResetDBParameterGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResetDBParameterGroup]
$creadListPrec :: ReadPrec [ResetDBParameterGroup]
readPrec :: ReadPrec ResetDBParameterGroup
$creadPrec :: ReadPrec ResetDBParameterGroup
readList :: ReadS [ResetDBParameterGroup]
$creadList :: ReadS [ResetDBParameterGroup]
readsPrec :: Int -> ReadS ResetDBParameterGroup
$creadsPrec :: Int -> ReadS ResetDBParameterGroup
Prelude.Read, Int -> ResetDBParameterGroup -> ShowS
[ResetDBParameterGroup] -> ShowS
ResetDBParameterGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetDBParameterGroup] -> ShowS
$cshowList :: [ResetDBParameterGroup] -> ShowS
show :: ResetDBParameterGroup -> String
$cshow :: ResetDBParameterGroup -> String
showsPrec :: Int -> ResetDBParameterGroup -> ShowS
$cshowsPrec :: Int -> ResetDBParameterGroup -> ShowS
Prelude.Show, forall x. Rep ResetDBParameterGroup x -> ResetDBParameterGroup
forall x. ResetDBParameterGroup -> Rep ResetDBParameterGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetDBParameterGroup x -> ResetDBParameterGroup
$cfrom :: forall x. ResetDBParameterGroup -> Rep ResetDBParameterGroup x
Prelude.Generic)

-- |
-- Create a value of 'ResetDBParameterGroup' 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:
--
-- 'parameters', 'resetDBParameterGroup_parameters' - To reset the entire DB parameter group, specify the @DBParameterGroup@
-- name and @ResetAllParameters@ parameters. To reset specific parameters,
-- provide a list of the following: @ParameterName@ and @ApplyMethod@. A
-- maximum of 20 parameters can be modified in a single request.
--
-- __MySQL__
--
-- Valid Values (for Apply method): @immediate@ | @pending-reboot@
--
-- You can use the immediate value with dynamic parameters only. You can
-- use the @pending-reboot@ value for both dynamic and static parameters,
-- and changes are applied when DB instance reboots.
--
-- __MariaDB__
--
-- Valid Values (for Apply method): @immediate@ | @pending-reboot@
--
-- You can use the immediate value with dynamic parameters only. You can
-- use the @pending-reboot@ value for both dynamic and static parameters,
-- and changes are applied when DB instance reboots.
--
-- __Oracle__
--
-- Valid Values (for Apply method): @pending-reboot@
--
-- 'resetAllParameters', 'resetDBParameterGroup_resetAllParameters' - A value that indicates whether to reset all parameters in the DB
-- parameter group to default values. By default, all parameters in the DB
-- parameter group are reset to default values.
--
-- 'dbParameterGroupName', 'resetDBParameterGroup_dbParameterGroupName' - The name of the DB parameter group.
--
-- Constraints:
--
-- -   Must match the name of an existing @DBParameterGroup@.
newResetDBParameterGroup ::
  -- | 'dbParameterGroupName'
  Prelude.Text ->
  ResetDBParameterGroup
newResetDBParameterGroup :: Text -> ResetDBParameterGroup
newResetDBParameterGroup Text
pDBParameterGroupName_ =
  ResetDBParameterGroup'
    { $sel:parameters:ResetDBParameterGroup' :: Maybe [Parameter]
parameters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resetAllParameters:ResetDBParameterGroup' :: Maybe Bool
resetAllParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:dbParameterGroupName:ResetDBParameterGroup' :: Text
dbParameterGroupName = Text
pDBParameterGroupName_
    }

-- | To reset the entire DB parameter group, specify the @DBParameterGroup@
-- name and @ResetAllParameters@ parameters. To reset specific parameters,
-- provide a list of the following: @ParameterName@ and @ApplyMethod@. A
-- maximum of 20 parameters can be modified in a single request.
--
-- __MySQL__
--
-- Valid Values (for Apply method): @immediate@ | @pending-reboot@
--
-- You can use the immediate value with dynamic parameters only. You can
-- use the @pending-reboot@ value for both dynamic and static parameters,
-- and changes are applied when DB instance reboots.
--
-- __MariaDB__
--
-- Valid Values (for Apply method): @immediate@ | @pending-reboot@
--
-- You can use the immediate value with dynamic parameters only. You can
-- use the @pending-reboot@ value for both dynamic and static parameters,
-- and changes are applied when DB instance reboots.
--
-- __Oracle__
--
-- Valid Values (for Apply method): @pending-reboot@
resetDBParameterGroup_parameters :: Lens.Lens' ResetDBParameterGroup (Prelude.Maybe [Parameter])
resetDBParameterGroup_parameters :: Lens' ResetDBParameterGroup (Maybe [Parameter])
resetDBParameterGroup_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDBParameterGroup' {Maybe [Parameter]
parameters :: Maybe [Parameter]
$sel:parameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe [Parameter]
parameters} -> Maybe [Parameter]
parameters) (\s :: ResetDBParameterGroup
s@ResetDBParameterGroup' {} Maybe [Parameter]
a -> ResetDBParameterGroup
s {$sel:parameters:ResetDBParameterGroup' :: Maybe [Parameter]
parameters = Maybe [Parameter]
a} :: ResetDBParameterGroup) 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

-- | A value that indicates whether to reset all parameters in the DB
-- parameter group to default values. By default, all parameters in the DB
-- parameter group are reset to default values.
resetDBParameterGroup_resetAllParameters :: Lens.Lens' ResetDBParameterGroup (Prelude.Maybe Prelude.Bool)
resetDBParameterGroup_resetAllParameters :: Lens' ResetDBParameterGroup (Maybe Bool)
resetDBParameterGroup_resetAllParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDBParameterGroup' {Maybe Bool
resetAllParameters :: Maybe Bool
$sel:resetAllParameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe Bool
resetAllParameters} -> Maybe Bool
resetAllParameters) (\s :: ResetDBParameterGroup
s@ResetDBParameterGroup' {} Maybe Bool
a -> ResetDBParameterGroup
s {$sel:resetAllParameters:ResetDBParameterGroup' :: Maybe Bool
resetAllParameters = Maybe Bool
a} :: ResetDBParameterGroup)

-- | The name of the DB parameter group.
--
-- Constraints:
--
-- -   Must match the name of an existing @DBParameterGroup@.
resetDBParameterGroup_dbParameterGroupName :: Lens.Lens' ResetDBParameterGroup Prelude.Text
resetDBParameterGroup_dbParameterGroupName :: Lens' ResetDBParameterGroup Text
resetDBParameterGroup_dbParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResetDBParameterGroup' {Text
dbParameterGroupName :: Text
$sel:dbParameterGroupName:ResetDBParameterGroup' :: ResetDBParameterGroup -> Text
dbParameterGroupName} -> Text
dbParameterGroupName) (\s :: ResetDBParameterGroup
s@ResetDBParameterGroup' {} Text
a -> ResetDBParameterGroup
s {$sel:dbParameterGroupName:ResetDBParameterGroup' :: Text
dbParameterGroupName = Text
a} :: ResetDBParameterGroup)

instance Core.AWSRequest ResetDBParameterGroup where
  type
    AWSResponse ResetDBParameterGroup =
      DBParameterGroupNameMessage
  request :: (Service -> Service)
-> ResetDBParameterGroup -> Request ResetDBParameterGroup
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 ResetDBParameterGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ResetDBParameterGroup)))
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
"ResetDBParameterGroupResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable ResetDBParameterGroup where
  hashWithSalt :: Int -> ResetDBParameterGroup -> Int
hashWithSalt Int
_salt ResetDBParameterGroup' {Maybe Bool
Maybe [Parameter]
Text
dbParameterGroupName :: Text
resetAllParameters :: Maybe Bool
parameters :: Maybe [Parameter]
$sel:dbParameterGroupName:ResetDBParameterGroup' :: ResetDBParameterGroup -> Text
$sel:resetAllParameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe Bool
$sel:parameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe [Parameter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Parameter]
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
resetAllParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbParameterGroupName

instance Prelude.NFData ResetDBParameterGroup where
  rnf :: ResetDBParameterGroup -> ()
rnf ResetDBParameterGroup' {Maybe Bool
Maybe [Parameter]
Text
dbParameterGroupName :: Text
resetAllParameters :: Maybe Bool
parameters :: Maybe [Parameter]
$sel:dbParameterGroupName:ResetDBParameterGroup' :: ResetDBParameterGroup -> Text
$sel:resetAllParameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe Bool
$sel:parameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe [Parameter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Parameter]
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
resetAllParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbParameterGroupName

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

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

instance Data.ToQuery ResetDBParameterGroup where
  toQuery :: ResetDBParameterGroup -> QueryString
toQuery ResetDBParameterGroup' {Maybe Bool
Maybe [Parameter]
Text
dbParameterGroupName :: Text
resetAllParameters :: Maybe Bool
parameters :: Maybe [Parameter]
$sel:dbParameterGroupName:ResetDBParameterGroup' :: ResetDBParameterGroup -> Text
$sel:resetAllParameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe Bool
$sel:parameters:ResetDBParameterGroup' :: ResetDBParameterGroup -> Maybe [Parameter]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ResetDBParameterGroup" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"Parameters"
          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
"Parameter"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Parameter]
parameters
            ),
        ByteString
"ResetAllParameters" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
resetAllParameters,
        ByteString
"DBParameterGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbParameterGroupName
      ]