{-# 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.Redshift.DescribeStorage
-- 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 account level backups storage size and provisional storage.
module Amazonka.Redshift.DescribeStorage
  ( -- * Creating a Request
    DescribeStorage (..),
    newDescribeStorage,

    -- * Destructuring the Response
    DescribeStorageResponse (..),
    newDescribeStorageResponse,

    -- * Response Lenses
    describeStorageResponse_totalBackupSizeInMegaBytes,
    describeStorageResponse_totalProvisionedStorageInMegaBytes,
    describeStorageResponse_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.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'DescribeStorage' 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.
newDescribeStorage ::
  DescribeStorage
newDescribeStorage :: DescribeStorage
newDescribeStorage = DescribeStorage
DescribeStorage'

instance Core.AWSRequest DescribeStorage where
  type
    AWSResponse DescribeStorage =
      DescribeStorageResponse
  request :: (Service -> Service) -> DescribeStorage -> Request DescribeStorage
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 DescribeStorage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeStorage)))
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
"DescribeStorageResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Double -> Maybe Double -> Int -> DescribeStorageResponse
DescribeStorageResponse'
            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
"TotalBackupSizeInMegaBytes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TotalProvisionedStorageInMegaBytes")
            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 DescribeStorage where
  hashWithSalt :: Int -> DescribeStorage -> Int
hashWithSalt Int
_salt DescribeStorage
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData DescribeStorage where
  rnf :: DescribeStorage -> ()
rnf DescribeStorage
_ = ()

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

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

instance Data.ToQuery DescribeStorage where
  toQuery :: DescribeStorage -> QueryString
toQuery =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ ByteString
"Action"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeStorage" :: Prelude.ByteString),
            ByteString
"Version"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString)
          ]
      )

-- | /See:/ 'newDescribeStorageResponse' smart constructor.
data DescribeStorageResponse = DescribeStorageResponse'
  { -- | The total amount of storage currently used for snapshots.
    DescribeStorageResponse -> Maybe Double
totalBackupSizeInMegaBytes :: Prelude.Maybe Prelude.Double,
    -- | The total amount of storage currently provisioned.
    DescribeStorageResponse -> Maybe Double
totalProvisionedStorageInMegaBytes :: Prelude.Maybe Prelude.Double,
    -- | The response's http status code.
    DescribeStorageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeStorageResponse -> DescribeStorageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStorageResponse -> DescribeStorageResponse -> Bool
$c/= :: DescribeStorageResponse -> DescribeStorageResponse -> Bool
== :: DescribeStorageResponse -> DescribeStorageResponse -> Bool
$c== :: DescribeStorageResponse -> DescribeStorageResponse -> Bool
Prelude.Eq, ReadPrec [DescribeStorageResponse]
ReadPrec DescribeStorageResponse
Int -> ReadS DescribeStorageResponse
ReadS [DescribeStorageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStorageResponse]
$creadListPrec :: ReadPrec [DescribeStorageResponse]
readPrec :: ReadPrec DescribeStorageResponse
$creadPrec :: ReadPrec DescribeStorageResponse
readList :: ReadS [DescribeStorageResponse]
$creadList :: ReadS [DescribeStorageResponse]
readsPrec :: Int -> ReadS DescribeStorageResponse
$creadsPrec :: Int -> ReadS DescribeStorageResponse
Prelude.Read, Int -> DescribeStorageResponse -> ShowS
[DescribeStorageResponse] -> ShowS
DescribeStorageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStorageResponse] -> ShowS
$cshowList :: [DescribeStorageResponse] -> ShowS
show :: DescribeStorageResponse -> String
$cshow :: DescribeStorageResponse -> String
showsPrec :: Int -> DescribeStorageResponse -> ShowS
$cshowsPrec :: Int -> DescribeStorageResponse -> ShowS
Prelude.Show, forall x. Rep DescribeStorageResponse x -> DescribeStorageResponse
forall x. DescribeStorageResponse -> Rep DescribeStorageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStorageResponse x -> DescribeStorageResponse
$cfrom :: forall x. DescribeStorageResponse -> Rep DescribeStorageResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStorageResponse' 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:
--
-- 'totalBackupSizeInMegaBytes', 'describeStorageResponse_totalBackupSizeInMegaBytes' - The total amount of storage currently used for snapshots.
--
-- 'totalProvisionedStorageInMegaBytes', 'describeStorageResponse_totalProvisionedStorageInMegaBytes' - The total amount of storage currently provisioned.
--
-- 'httpStatus', 'describeStorageResponse_httpStatus' - The response's http status code.
newDescribeStorageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeStorageResponse
newDescribeStorageResponse :: Int -> DescribeStorageResponse
newDescribeStorageResponse Int
pHttpStatus_ =
  DescribeStorageResponse'
    { $sel:totalBackupSizeInMegaBytes:DescribeStorageResponse' :: Maybe Double
totalBackupSizeInMegaBytes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:totalProvisionedStorageInMegaBytes:DescribeStorageResponse' :: Maybe Double
totalProvisionedStorageInMegaBytes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeStorageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The total amount of storage currently used for snapshots.
describeStorageResponse_totalBackupSizeInMegaBytes :: Lens.Lens' DescribeStorageResponse (Prelude.Maybe Prelude.Double)
describeStorageResponse_totalBackupSizeInMegaBytes :: Lens' DescribeStorageResponse (Maybe Double)
describeStorageResponse_totalBackupSizeInMegaBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStorageResponse' {Maybe Double
totalBackupSizeInMegaBytes :: Maybe Double
$sel:totalBackupSizeInMegaBytes:DescribeStorageResponse' :: DescribeStorageResponse -> Maybe Double
totalBackupSizeInMegaBytes} -> Maybe Double
totalBackupSizeInMegaBytes) (\s :: DescribeStorageResponse
s@DescribeStorageResponse' {} Maybe Double
a -> DescribeStorageResponse
s {$sel:totalBackupSizeInMegaBytes:DescribeStorageResponse' :: Maybe Double
totalBackupSizeInMegaBytes = Maybe Double
a} :: DescribeStorageResponse)

-- | The total amount of storage currently provisioned.
describeStorageResponse_totalProvisionedStorageInMegaBytes :: Lens.Lens' DescribeStorageResponse (Prelude.Maybe Prelude.Double)
describeStorageResponse_totalProvisionedStorageInMegaBytes :: Lens' DescribeStorageResponse (Maybe Double)
describeStorageResponse_totalProvisionedStorageInMegaBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStorageResponse' {Maybe Double
totalProvisionedStorageInMegaBytes :: Maybe Double
$sel:totalProvisionedStorageInMegaBytes:DescribeStorageResponse' :: DescribeStorageResponse -> Maybe Double
totalProvisionedStorageInMegaBytes} -> Maybe Double
totalProvisionedStorageInMegaBytes) (\s :: DescribeStorageResponse
s@DescribeStorageResponse' {} Maybe Double
a -> DescribeStorageResponse
s {$sel:totalProvisionedStorageInMegaBytes:DescribeStorageResponse' :: Maybe Double
totalProvisionedStorageInMegaBytes = Maybe Double
a} :: DescribeStorageResponse)

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

instance Prelude.NFData DescribeStorageResponse where
  rnf :: DescribeStorageResponse -> ()
rnf DescribeStorageResponse' {Int
Maybe Double
httpStatus :: Int
totalProvisionedStorageInMegaBytes :: Maybe Double
totalBackupSizeInMegaBytes :: Maybe Double
$sel:httpStatus:DescribeStorageResponse' :: DescribeStorageResponse -> Int
$sel:totalProvisionedStorageInMegaBytes:DescribeStorageResponse' :: DescribeStorageResponse -> Maybe Double
$sel:totalBackupSizeInMegaBytes:DescribeStorageResponse' :: DescribeStorageResponse -> Maybe Double
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
totalBackupSizeInMegaBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
totalProvisionedStorageInMegaBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus