{-# 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.Snowball.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 information about a specific cluster including shipping
-- information, cluster status, and other important metadata.
module Amazonka.Snowball.DescribeCluster
  ( -- * Creating a Request
    DescribeCluster (..),
    newDescribeCluster,

    -- * Request Lenses
    describeCluster_clusterId,

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

    -- * Response Lenses
    describeClusterResponse_clusterMetadata,
    describeClusterResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Snowball.Types

-- | /See:/ 'newDescribeCluster' smart constructor.
data DescribeCluster = DescribeCluster'
  { -- | The automatically generated ID for a cluster.
    DescribeCluster -> Text
clusterId :: 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:
--
-- 'clusterId', 'describeCluster_clusterId' - The automatically generated ID for a cluster.
newDescribeCluster ::
  -- | 'clusterId'
  Prelude.Text ->
  DescribeCluster
newDescribeCluster :: Text -> DescribeCluster
newDescribeCluster Text
pClusterId_ =
  DescribeCluster' {$sel:clusterId:DescribeCluster' :: Text
clusterId = Text
pClusterId_}

-- | The automatically generated ID for a cluster.
describeCluster_clusterId :: Lens.Lens' DescribeCluster Prelude.Text
describeCluster_clusterId :: Lens' DescribeCluster Text
describeCluster_clusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCluster' {Text
clusterId :: Text
$sel:clusterId:DescribeCluster' :: DescribeCluster -> Text
clusterId} -> Text
clusterId) (\s :: DescribeCluster
s@DescribeCluster' {} Text
a -> DescribeCluster
s {$sel:clusterId:DescribeCluster' :: Text
clusterId = 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, ToJSON a) => Service -> a -> Request a
Request.postJSON (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 ClusterMetadata -> 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
"ClusterMetadata")
            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
clusterId :: Text
$sel:clusterId:DescribeCluster' :: DescribeCluster -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterId

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

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
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSIESnowballJobManagementService.DescribeCluster" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeCluster where
  toJSON :: DescribeCluster -> Value
toJSON DescribeCluster' {Text
clusterId :: Text
$sel:clusterId:DescribeCluster' :: DescribeCluster -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ClusterId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterId)]
      )

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

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'
  { -- | Information about a specific cluster, including shipping information,
    -- cluster status, and other important metadata.
    DescribeClusterResponse -> Maybe ClusterMetadata
clusterMetadata :: Prelude.Maybe ClusterMetadata,
    -- | 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:
--
-- 'clusterMetadata', 'describeClusterResponse_clusterMetadata' - Information about a specific cluster, including shipping information,
-- cluster status, and other important metadata.
--
-- 'httpStatus', 'describeClusterResponse_httpStatus' - The response's http status code.
newDescribeClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeClusterResponse
newDescribeClusterResponse :: Int -> DescribeClusterResponse
newDescribeClusterResponse Int
pHttpStatus_ =
  DescribeClusterResponse'
    { $sel:clusterMetadata:DescribeClusterResponse' :: Maybe ClusterMetadata
clusterMetadata =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about a specific cluster, including shipping information,
-- cluster status, and other important metadata.
describeClusterResponse_clusterMetadata :: Lens.Lens' DescribeClusterResponse (Prelude.Maybe ClusterMetadata)
describeClusterResponse_clusterMetadata :: Lens' DescribeClusterResponse (Maybe ClusterMetadata)
describeClusterResponse_clusterMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeClusterResponse' {Maybe ClusterMetadata
clusterMetadata :: Maybe ClusterMetadata
$sel:clusterMetadata:DescribeClusterResponse' :: DescribeClusterResponse -> Maybe ClusterMetadata
clusterMetadata} -> Maybe ClusterMetadata
clusterMetadata) (\s :: DescribeClusterResponse
s@DescribeClusterResponse' {} Maybe ClusterMetadata
a -> DescribeClusterResponse
s {$sel:clusterMetadata:DescribeClusterResponse' :: Maybe ClusterMetadata
clusterMetadata = Maybe ClusterMetadata
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 ClusterMetadata
httpStatus :: Int
clusterMetadata :: Maybe ClusterMetadata
$sel:httpStatus:DescribeClusterResponse' :: DescribeClusterResponse -> Int
$sel:clusterMetadata:DescribeClusterResponse' :: DescribeClusterResponse -> Maybe ClusterMetadata
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterMetadata
clusterMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus