{-# 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.DocumentDB.StartDBCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Restarts the stopped cluster that is specified by @DBClusterIdentifier@.
-- For more information, see
-- <https://docs.aws.amazon.com/documentdb/latest/developerguide/db-cluster-stop-start.html Stopping and Starting an Amazon DocumentDB Cluster>.
module Amazonka.DocumentDB.StartDBCluster
  ( -- * Creating a Request
    StartDBCluster (..),
    newStartDBCluster,

    -- * Request Lenses
    startDBCluster_dbClusterIdentifier,

    -- * Destructuring the Response
    StartDBClusterResponse (..),
    newStartDBClusterResponse,

    -- * Response Lenses
    startDBClusterResponse_dbCluster,
    startDBClusterResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DocumentDB.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartDBCluster' smart constructor.
data StartDBCluster = StartDBCluster'
  { -- | The identifier of the cluster to restart. Example:
    -- @docdb-2019-05-28-15-24-52@
    StartDBCluster -> Text
dbClusterIdentifier :: Prelude.Text
  }
  deriving (StartDBCluster -> StartDBCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartDBCluster -> StartDBCluster -> Bool
$c/= :: StartDBCluster -> StartDBCluster -> Bool
== :: StartDBCluster -> StartDBCluster -> Bool
$c== :: StartDBCluster -> StartDBCluster -> Bool
Prelude.Eq, ReadPrec [StartDBCluster]
ReadPrec StartDBCluster
Int -> ReadS StartDBCluster
ReadS [StartDBCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartDBCluster]
$creadListPrec :: ReadPrec [StartDBCluster]
readPrec :: ReadPrec StartDBCluster
$creadPrec :: ReadPrec StartDBCluster
readList :: ReadS [StartDBCluster]
$creadList :: ReadS [StartDBCluster]
readsPrec :: Int -> ReadS StartDBCluster
$creadsPrec :: Int -> ReadS StartDBCluster
Prelude.Read, Int -> StartDBCluster -> ShowS
[StartDBCluster] -> ShowS
StartDBCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartDBCluster] -> ShowS
$cshowList :: [StartDBCluster] -> ShowS
show :: StartDBCluster -> String
$cshow :: StartDBCluster -> String
showsPrec :: Int -> StartDBCluster -> ShowS
$cshowsPrec :: Int -> StartDBCluster -> ShowS
Prelude.Show, forall x. Rep StartDBCluster x -> StartDBCluster
forall x. StartDBCluster -> Rep StartDBCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartDBCluster x -> StartDBCluster
$cfrom :: forall x. StartDBCluster -> Rep StartDBCluster x
Prelude.Generic)

-- |
-- Create a value of 'StartDBCluster' 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:
--
-- 'dbClusterIdentifier', 'startDBCluster_dbClusterIdentifier' - The identifier of the cluster to restart. Example:
-- @docdb-2019-05-28-15-24-52@
newStartDBCluster ::
  -- | 'dbClusterIdentifier'
  Prelude.Text ->
  StartDBCluster
newStartDBCluster :: Text -> StartDBCluster
newStartDBCluster Text
pDBClusterIdentifier_ =
  StartDBCluster'
    { $sel:dbClusterIdentifier:StartDBCluster' :: Text
dbClusterIdentifier =
        Text
pDBClusterIdentifier_
    }

-- | The identifier of the cluster to restart. Example:
-- @docdb-2019-05-28-15-24-52@
startDBCluster_dbClusterIdentifier :: Lens.Lens' StartDBCluster Prelude.Text
startDBCluster_dbClusterIdentifier :: Lens' StartDBCluster Text
startDBCluster_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDBCluster' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:StartDBCluster' :: StartDBCluster -> Text
dbClusterIdentifier} -> Text
dbClusterIdentifier) (\s :: StartDBCluster
s@StartDBCluster' {} Text
a -> StartDBCluster
s {$sel:dbClusterIdentifier:StartDBCluster' :: Text
dbClusterIdentifier = Text
a} :: StartDBCluster)

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

instance Prelude.NFData StartDBCluster where
  rnf :: StartDBCluster -> ()
rnf StartDBCluster' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:StartDBCluster' :: StartDBCluster -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
dbClusterIdentifier

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

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

instance Data.ToQuery StartDBCluster where
  toQuery :: StartDBCluster -> QueryString
toQuery StartDBCluster' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:StartDBCluster' :: StartDBCluster -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"StartDBCluster" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"DBClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterIdentifier
      ]

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

-- |
-- Create a value of 'StartDBClusterResponse' 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:
--
-- 'dbCluster', 'startDBClusterResponse_dbCluster' - Undocumented member.
--
-- 'httpStatus', 'startDBClusterResponse_httpStatus' - The response's http status code.
newStartDBClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartDBClusterResponse
newStartDBClusterResponse :: Int -> StartDBClusterResponse
newStartDBClusterResponse Int
pHttpStatus_ =
  StartDBClusterResponse'
    { $sel:dbCluster:StartDBClusterResponse' :: Maybe DBCluster
dbCluster =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartDBClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
startDBClusterResponse_dbCluster :: Lens.Lens' StartDBClusterResponse (Prelude.Maybe DBCluster)
startDBClusterResponse_dbCluster :: Lens' StartDBClusterResponse (Maybe DBCluster)
startDBClusterResponse_dbCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartDBClusterResponse' {Maybe DBCluster
dbCluster :: Maybe DBCluster
$sel:dbCluster:StartDBClusterResponse' :: StartDBClusterResponse -> Maybe DBCluster
dbCluster} -> Maybe DBCluster
dbCluster) (\s :: StartDBClusterResponse
s@StartDBClusterResponse' {} Maybe DBCluster
a -> StartDBClusterResponse
s {$sel:dbCluster:StartDBClusterResponse' :: Maybe DBCluster
dbCluster = Maybe DBCluster
a} :: StartDBClusterResponse)

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

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