{-# 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.RebootDBInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- You might need to reboot your DB instance, usually for maintenance
-- reasons. For example, if you make certain modifications, or if you
-- change the DB parameter group associated with the DB instance, you must
-- reboot the instance for the changes to take effect.
--
-- Rebooting a DB instance restarts the database engine service. Rebooting
-- a DB instance results in a momentary outage, during which the DB
-- instance status is set to rebooting.
--
-- For more information about rebooting, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_RebootInstance.html Rebooting a DB Instance>
-- in the /Amazon RDS User Guide./
--
-- This command doesn\'t apply to RDS Custom.
--
-- If your DB instance is part of a Multi-AZ DB cluster, you can reboot the
-- DB cluster with the @RebootDBCluster@ operation.
module Amazonka.RDS.RebootDBInstance
  ( -- * Creating a Request
    RebootDBInstance (..),
    newRebootDBInstance,

    -- * Request Lenses
    rebootDBInstance_forceFailover,
    rebootDBInstance_dbInstanceIdentifier,

    -- * Destructuring the Response
    RebootDBInstanceResponse (..),
    newRebootDBInstanceResponse,

    -- * Response Lenses
    rebootDBInstanceResponse_dbInstance,
    rebootDBInstanceResponse_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.RDS.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newRebootDBInstance' smart constructor.
data RebootDBInstance = RebootDBInstance'
  { -- | A value that indicates whether the reboot is conducted through a
    -- Multi-AZ failover.
    --
    -- Constraint: You can\'t enable force failover if the instance isn\'t
    -- configured for Multi-AZ.
    RebootDBInstance -> Maybe Bool
forceFailover :: Prelude.Maybe Prelude.Bool,
    -- | The DB instance identifier. This parameter is stored as a lowercase
    -- string.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing DBInstance.
    RebootDBInstance -> Text
dbInstanceIdentifier :: Prelude.Text
  }
  deriving (RebootDBInstance -> RebootDBInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RebootDBInstance -> RebootDBInstance -> Bool
$c/= :: RebootDBInstance -> RebootDBInstance -> Bool
== :: RebootDBInstance -> RebootDBInstance -> Bool
$c== :: RebootDBInstance -> RebootDBInstance -> Bool
Prelude.Eq, ReadPrec [RebootDBInstance]
ReadPrec RebootDBInstance
Int -> ReadS RebootDBInstance
ReadS [RebootDBInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RebootDBInstance]
$creadListPrec :: ReadPrec [RebootDBInstance]
readPrec :: ReadPrec RebootDBInstance
$creadPrec :: ReadPrec RebootDBInstance
readList :: ReadS [RebootDBInstance]
$creadList :: ReadS [RebootDBInstance]
readsPrec :: Int -> ReadS RebootDBInstance
$creadsPrec :: Int -> ReadS RebootDBInstance
Prelude.Read, Int -> RebootDBInstance -> ShowS
[RebootDBInstance] -> ShowS
RebootDBInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RebootDBInstance] -> ShowS
$cshowList :: [RebootDBInstance] -> ShowS
show :: RebootDBInstance -> String
$cshow :: RebootDBInstance -> String
showsPrec :: Int -> RebootDBInstance -> ShowS
$cshowsPrec :: Int -> RebootDBInstance -> ShowS
Prelude.Show, forall x. Rep RebootDBInstance x -> RebootDBInstance
forall x. RebootDBInstance -> Rep RebootDBInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RebootDBInstance x -> RebootDBInstance
$cfrom :: forall x. RebootDBInstance -> Rep RebootDBInstance x
Prelude.Generic)

-- |
-- Create a value of 'RebootDBInstance' 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:
--
-- 'forceFailover', 'rebootDBInstance_forceFailover' - A value that indicates whether the reboot is conducted through a
-- Multi-AZ failover.
--
-- Constraint: You can\'t enable force failover if the instance isn\'t
-- configured for Multi-AZ.
--
-- 'dbInstanceIdentifier', 'rebootDBInstance_dbInstanceIdentifier' - The DB instance identifier. This parameter is stored as a lowercase
-- string.
--
-- Constraints:
--
-- -   Must match the identifier of an existing DBInstance.
newRebootDBInstance ::
  -- | 'dbInstanceIdentifier'
  Prelude.Text ->
  RebootDBInstance
newRebootDBInstance :: Text -> RebootDBInstance
newRebootDBInstance Text
pDBInstanceIdentifier_ =
  RebootDBInstance'
    { $sel:forceFailover:RebootDBInstance' :: Maybe Bool
forceFailover = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceIdentifier:RebootDBInstance' :: Text
dbInstanceIdentifier = Text
pDBInstanceIdentifier_
    }

-- | A value that indicates whether the reboot is conducted through a
-- Multi-AZ failover.
--
-- Constraint: You can\'t enable force failover if the instance isn\'t
-- configured for Multi-AZ.
rebootDBInstance_forceFailover :: Lens.Lens' RebootDBInstance (Prelude.Maybe Prelude.Bool)
rebootDBInstance_forceFailover :: Lens' RebootDBInstance (Maybe Bool)
rebootDBInstance_forceFailover = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RebootDBInstance' {Maybe Bool
forceFailover :: Maybe Bool
$sel:forceFailover:RebootDBInstance' :: RebootDBInstance -> Maybe Bool
forceFailover} -> Maybe Bool
forceFailover) (\s :: RebootDBInstance
s@RebootDBInstance' {} Maybe Bool
a -> RebootDBInstance
s {$sel:forceFailover:RebootDBInstance' :: Maybe Bool
forceFailover = Maybe Bool
a} :: RebootDBInstance)

-- | The DB instance identifier. This parameter is stored as a lowercase
-- string.
--
-- Constraints:
--
-- -   Must match the identifier of an existing DBInstance.
rebootDBInstance_dbInstanceIdentifier :: Lens.Lens' RebootDBInstance Prelude.Text
rebootDBInstance_dbInstanceIdentifier :: Lens' RebootDBInstance Text
rebootDBInstance_dbInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RebootDBInstance' {Text
dbInstanceIdentifier :: Text
$sel:dbInstanceIdentifier:RebootDBInstance' :: RebootDBInstance -> Text
dbInstanceIdentifier} -> Text
dbInstanceIdentifier) (\s :: RebootDBInstance
s@RebootDBInstance' {} Text
a -> RebootDBInstance
s {$sel:dbInstanceIdentifier:RebootDBInstance' :: Text
dbInstanceIdentifier = Text
a} :: RebootDBInstance)

instance Core.AWSRequest RebootDBInstance where
  type
    AWSResponse RebootDBInstance =
      RebootDBInstanceResponse
  request :: (Service -> Service)
-> RebootDBInstance -> Request RebootDBInstance
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 RebootDBInstance
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RebootDBInstance)))
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
"RebootDBInstanceResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBInstance -> Int -> RebootDBInstanceResponse
RebootDBInstanceResponse'
            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
"DBInstance")
            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 RebootDBInstance where
  hashWithSalt :: Int -> RebootDBInstance -> Int
hashWithSalt Int
_salt RebootDBInstance' {Maybe Bool
Text
dbInstanceIdentifier :: Text
forceFailover :: Maybe Bool
$sel:dbInstanceIdentifier:RebootDBInstance' :: RebootDBInstance -> Text
$sel:forceFailover:RebootDBInstance' :: RebootDBInstance -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
forceFailover
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbInstanceIdentifier

instance Prelude.NFData RebootDBInstance where
  rnf :: RebootDBInstance -> ()
rnf RebootDBInstance' {Maybe Bool
Text
dbInstanceIdentifier :: Text
forceFailover :: Maybe Bool
$sel:dbInstanceIdentifier:RebootDBInstance' :: RebootDBInstance -> Text
$sel:forceFailover:RebootDBInstance' :: RebootDBInstance -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
forceFailover
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbInstanceIdentifier

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

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

instance Data.ToQuery RebootDBInstance where
  toQuery :: RebootDBInstance -> QueryString
toQuery RebootDBInstance' {Maybe Bool
Text
dbInstanceIdentifier :: Text
forceFailover :: Maybe Bool
$sel:dbInstanceIdentifier:RebootDBInstance' :: RebootDBInstance -> Text
$sel:forceFailover:RebootDBInstance' :: RebootDBInstance -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RebootDBInstance" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"ForceFailover" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
forceFailover,
        ByteString
"DBInstanceIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbInstanceIdentifier
      ]

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

-- |
-- Create a value of 'RebootDBInstanceResponse' 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:
--
-- 'dbInstance', 'rebootDBInstanceResponse_dbInstance' - Undocumented member.
--
-- 'httpStatus', 'rebootDBInstanceResponse_httpStatus' - The response's http status code.
newRebootDBInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RebootDBInstanceResponse
newRebootDBInstanceResponse :: Int -> RebootDBInstanceResponse
newRebootDBInstanceResponse Int
pHttpStatus_ =
  RebootDBInstanceResponse'
    { $sel:dbInstance:RebootDBInstanceResponse' :: Maybe DBInstance
dbInstance =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RebootDBInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
rebootDBInstanceResponse_dbInstance :: Lens.Lens' RebootDBInstanceResponse (Prelude.Maybe DBInstance)
rebootDBInstanceResponse_dbInstance :: Lens' RebootDBInstanceResponse (Maybe DBInstance)
rebootDBInstanceResponse_dbInstance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RebootDBInstanceResponse' {Maybe DBInstance
dbInstance :: Maybe DBInstance
$sel:dbInstance:RebootDBInstanceResponse' :: RebootDBInstanceResponse -> Maybe DBInstance
dbInstance} -> Maybe DBInstance
dbInstance) (\s :: RebootDBInstanceResponse
s@RebootDBInstanceResponse' {} Maybe DBInstance
a -> RebootDBInstanceResponse
s {$sel:dbInstance:RebootDBInstanceResponse' :: Maybe DBInstance
dbInstance = Maybe DBInstance
a} :: RebootDBInstanceResponse)

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

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