{-# 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.Kafka.DescribeCluster
-- 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 a description of the MSK cluster whose Amazon Resource Name
-- (ARN) is specified in the request.
module Amazonka.Kafka.DescribeCluster
  ( -- * Creating a Request
    DescribeCluster (..),
    newDescribeCluster,

    -- * Request Lenses
    describeCluster_clusterArn,

    -- * Destructuring the Response
    DescribeClusterResponse (..),
    newDescribeClusterResponse,

    -- * Response Lenses
    describeClusterResponse_clusterInfo,
    describeClusterResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeCluster' smart constructor.
data DescribeCluster = DescribeCluster'
  { -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    DescribeCluster -> Text
clusterArn :: Prelude.Text
  }
  deriving (DescribeCluster -> DescribeCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCluster -> DescribeCluster -> Bool
$c/= :: DescribeCluster -> DescribeCluster -> Bool
== :: DescribeCluster -> DescribeCluster -> Bool
$c== :: DescribeCluster -> DescribeCluster -> Bool
Prelude.Eq, ReadPrec [DescribeCluster]
ReadPrec DescribeCluster
Int -> ReadS DescribeCluster
ReadS [DescribeCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCluster]
$creadListPrec :: ReadPrec [DescribeCluster]
readPrec :: ReadPrec DescribeCluster
$creadPrec :: ReadPrec DescribeCluster
readList :: ReadS [DescribeCluster]
$creadList :: ReadS [DescribeCluster]
readsPrec :: Int -> ReadS DescribeCluster
$creadsPrec :: Int -> ReadS DescribeCluster
Prelude.Read, Int -> DescribeCluster -> ShowS
[DescribeCluster] -> ShowS
DescribeCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCluster] -> ShowS
$cshowList :: [DescribeCluster] -> ShowS
show :: DescribeCluster -> String
$cshow :: DescribeCluster -> String
showsPrec :: Int -> DescribeCluster -> ShowS
$cshowsPrec :: Int -> DescribeCluster -> ShowS
Prelude.Show, forall x. Rep DescribeCluster x -> DescribeCluster
forall x. DescribeCluster -> Rep DescribeCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeCluster x -> DescribeCluster
$cfrom :: forall x. DescribeCluster -> Rep DescribeCluster x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCluster' 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', 'describeCluster_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
newDescribeCluster ::
  -- | 'clusterArn'
  Prelude.Text ->
  DescribeCluster
newDescribeCluster :: Text -> DescribeCluster
newDescribeCluster Text
pClusterArn_ =
  DescribeCluster' {$sel:clusterArn:DescribeCluster' :: Text
clusterArn = Text
pClusterArn_}

-- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
describeCluster_clusterArn :: Lens.Lens' DescribeCluster Prelude.Text
describeCluster_clusterArn :: Lens' DescribeCluster Text
describeCluster_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCluster' {Text
clusterArn :: Text
$sel:clusterArn:DescribeCluster' :: DescribeCluster -> Text
clusterArn} -> Text
clusterArn) (\s :: DescribeCluster
s@DescribeCluster' {} Text
a -> DescribeCluster
s {$sel:clusterArn:DescribeCluster' :: Text
clusterArn = Text
a} :: DescribeCluster)

instance Core.AWSRequest DescribeCluster where
  type
    AWSResponse DescribeCluster =
      DescribeClusterResponse
  request :: (Service -> Service) -> DescribeCluster -> Request DescribeCluster
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 DescribeCluster
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeCluster)))
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 ClusterInfo -> Int -> DescribeClusterResponse
DescribeClusterResponse'
            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
"clusterInfo")
            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 DescribeCluster where
  hashWithSalt :: Int -> DescribeCluster -> Int
hashWithSalt Int
_salt DescribeCluster' {Text
clusterArn :: Text
$sel:clusterArn:DescribeCluster' :: DescribeCluster -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn

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

instance Data.ToHeaders DescribeCluster where
  toHeaders :: DescribeCluster -> 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 DescribeCluster where
  toPath :: DescribeCluster -> ByteString
toPath DescribeCluster' {Text
clusterArn :: Text
$sel:clusterArn:DescribeCluster' :: DescribeCluster -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/clusters/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn]

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

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

-- |
-- Create a value of 'DescribeClusterResponse' 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:
--
-- 'clusterInfo', 'describeClusterResponse_clusterInfo' - The cluster information.
--
-- 'httpStatus', 'describeClusterResponse_httpStatus' - The response's http status code.
newDescribeClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeClusterResponse
newDescribeClusterResponse :: Int -> DescribeClusterResponse
newDescribeClusterResponse Int
pHttpStatus_ =
  DescribeClusterResponse'
    { $sel:clusterInfo:DescribeClusterResponse' :: Maybe ClusterInfo
clusterInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The cluster information.
describeClusterResponse_clusterInfo :: Lens.Lens' DescribeClusterResponse (Prelude.Maybe ClusterInfo)
describeClusterResponse_clusterInfo :: Lens' DescribeClusterResponse (Maybe ClusterInfo)
describeClusterResponse_clusterInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClusterResponse' {Maybe ClusterInfo
clusterInfo :: Maybe ClusterInfo
$sel:clusterInfo:DescribeClusterResponse' :: DescribeClusterResponse -> Maybe ClusterInfo
clusterInfo} -> Maybe ClusterInfo
clusterInfo) (\s :: DescribeClusterResponse
s@DescribeClusterResponse' {} Maybe ClusterInfo
a -> DescribeClusterResponse
s {$sel:clusterInfo:DescribeClusterResponse' :: Maybe ClusterInfo
clusterInfo = Maybe ClusterInfo
a} :: DescribeClusterResponse)

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

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