{-# 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.DocDbElastic.GetCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a specific Elastic DocumentDB cluster.
module Amazonka.DocDbElastic.GetCluster
  ( -- * Creating a Request
    GetCluster (..),
    newGetCluster,

    -- * Request Lenses
    getCluster_clusterArn,

    -- * Destructuring the Response
    GetClusterResponse (..),
    newGetClusterResponse,

    -- * Response Lenses
    getClusterResponse_httpStatus,
    getClusterResponse_cluster,
  )
where

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

-- | /See:/ 'newGetCluster' smart constructor.
data GetCluster = GetCluster'
  { -- | The arn of the Elastic DocumentDB cluster.
    GetCluster -> Text
clusterArn :: Prelude.Text
  }
  deriving (GetCluster -> GetCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCluster -> GetCluster -> Bool
$c/= :: GetCluster -> GetCluster -> Bool
== :: GetCluster -> GetCluster -> Bool
$c== :: GetCluster -> GetCluster -> Bool
Prelude.Eq, ReadPrec [GetCluster]
ReadPrec GetCluster
Int -> ReadS GetCluster
ReadS [GetCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCluster]
$creadListPrec :: ReadPrec [GetCluster]
readPrec :: ReadPrec GetCluster
$creadPrec :: ReadPrec GetCluster
readList :: ReadS [GetCluster]
$creadList :: ReadS [GetCluster]
readsPrec :: Int -> ReadS GetCluster
$creadsPrec :: Int -> ReadS GetCluster
Prelude.Read, Int -> GetCluster -> ShowS
[GetCluster] -> ShowS
GetCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCluster] -> ShowS
$cshowList :: [GetCluster] -> ShowS
show :: GetCluster -> String
$cshow :: GetCluster -> String
showsPrec :: Int -> GetCluster -> ShowS
$cshowsPrec :: Int -> GetCluster -> ShowS
Prelude.Show, forall x. Rep GetCluster x -> GetCluster
forall x. GetCluster -> Rep GetCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCluster x -> GetCluster
$cfrom :: forall x. GetCluster -> Rep GetCluster x
Prelude.Generic)

-- |
-- Create a value of 'GetCluster' 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:
--
-- 'clusterArn', 'getCluster_clusterArn' - The arn of the Elastic DocumentDB cluster.
newGetCluster ::
  -- | 'clusterArn'
  Prelude.Text ->
  GetCluster
newGetCluster :: Text -> GetCluster
newGetCluster Text
pClusterArn_ =
  GetCluster' {$sel:clusterArn:GetCluster' :: Text
clusterArn = Text
pClusterArn_}

-- | The arn of the Elastic DocumentDB cluster.
getCluster_clusterArn :: Lens.Lens' GetCluster Prelude.Text
getCluster_clusterArn :: Lens' GetCluster Text
getCluster_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCluster' {Text
clusterArn :: Text
$sel:clusterArn:GetCluster' :: GetCluster -> Text
clusterArn} -> Text
clusterArn) (\s :: GetCluster
s@GetCluster' {} Text
a -> GetCluster
s {$sel:clusterArn:GetCluster' :: Text
clusterArn = Text
a} :: GetCluster)

instance Core.AWSRequest GetCluster where
  type AWSResponse GetCluster = GetClusterResponse
  request :: (Service -> Service) -> GetCluster -> Request GetCluster
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetCluster
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCluster)))
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 ->
          Int -> Cluster -> GetClusterResponse
GetClusterResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"cluster")
      )

instance Prelude.Hashable GetCluster where
  hashWithSalt :: Int -> GetCluster -> Int
hashWithSalt Int
_salt GetCluster' {Text
clusterArn :: Text
$sel:clusterArn:GetCluster' :: GetCluster -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn

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

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

instance Data.ToPath GetCluster where
  toPath :: GetCluster -> ByteString
toPath GetCluster' {Text
clusterArn :: Text
$sel:clusterArn:GetCluster' :: GetCluster -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/cluster/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn]

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

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

-- |
-- Create a value of 'GetClusterResponse' 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:
--
-- 'httpStatus', 'getClusterResponse_httpStatus' - The response's http status code.
--
-- 'cluster', 'getClusterResponse_cluster' - Returns information about a specific Elastic DocumentDB cluster.
newGetClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'cluster'
  Cluster ->
  GetClusterResponse
newGetClusterResponse :: Int -> Cluster -> GetClusterResponse
newGetClusterResponse Int
pHttpStatus_ Cluster
pCluster_ =
  GetClusterResponse'
    { $sel:httpStatus:GetClusterResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:cluster:GetClusterResponse' :: Cluster
cluster = Cluster
pCluster_
    }

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

-- | Returns information about a specific Elastic DocumentDB cluster.
getClusterResponse_cluster :: Lens.Lens' GetClusterResponse Cluster
getClusterResponse_cluster :: Lens' GetClusterResponse Cluster
getClusterResponse_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetClusterResponse' {Cluster
cluster :: Cluster
$sel:cluster:GetClusterResponse' :: GetClusterResponse -> Cluster
cluster} -> Cluster
cluster) (\s :: GetClusterResponse
s@GetClusterResponse' {} Cluster
a -> GetClusterResponse
s {$sel:cluster:GetClusterResponse' :: Cluster
cluster = Cluster
a} :: GetClusterResponse)

instance Prelude.NFData GetClusterResponse where
  rnf :: GetClusterResponse -> ()
rnf GetClusterResponse' {Int
Cluster
cluster :: Cluster
httpStatus :: Int
$sel:cluster:GetClusterResponse' :: GetClusterResponse -> Cluster
$sel:httpStatus:GetClusterResponse' :: GetClusterResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Cluster
cluster