{-# 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.CognitoSync.DescribeIdentityPoolUsage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets usage details (for example, data storage) about a particular
-- identity pool.
--
-- This API can only be called with developer credentials. You cannot call
-- this API with the temporary user credentials provided by Cognito
-- Identity.
module Amazonka.CognitoSync.DescribeIdentityPoolUsage
  ( -- * Creating a Request
    DescribeIdentityPoolUsage (..),
    newDescribeIdentityPoolUsage,

    -- * Request Lenses
    describeIdentityPoolUsage_identityPoolId,

    -- * Destructuring the Response
    DescribeIdentityPoolUsageResponse (..),
    newDescribeIdentityPoolUsageResponse,

    -- * Response Lenses
    describeIdentityPoolUsageResponse_identityPoolUsage,
    describeIdentityPoolUsageResponse_httpStatus,
  )
where

import Amazonka.CognitoSync.Types
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

-- | A request for usage information about the identity pool.
--
-- /See:/ 'newDescribeIdentityPoolUsage' smart constructor.
data DescribeIdentityPoolUsage = DescribeIdentityPoolUsage'
  { -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. GUID generation is unique within a region.
    DescribeIdentityPoolUsage -> Text
identityPoolId :: Prelude.Text
  }
  deriving (DescribeIdentityPoolUsage -> DescribeIdentityPoolUsage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeIdentityPoolUsage -> DescribeIdentityPoolUsage -> Bool
$c/= :: DescribeIdentityPoolUsage -> DescribeIdentityPoolUsage -> Bool
== :: DescribeIdentityPoolUsage -> DescribeIdentityPoolUsage -> Bool
$c== :: DescribeIdentityPoolUsage -> DescribeIdentityPoolUsage -> Bool
Prelude.Eq, ReadPrec [DescribeIdentityPoolUsage]
ReadPrec DescribeIdentityPoolUsage
Int -> ReadS DescribeIdentityPoolUsage
ReadS [DescribeIdentityPoolUsage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeIdentityPoolUsage]
$creadListPrec :: ReadPrec [DescribeIdentityPoolUsage]
readPrec :: ReadPrec DescribeIdentityPoolUsage
$creadPrec :: ReadPrec DescribeIdentityPoolUsage
readList :: ReadS [DescribeIdentityPoolUsage]
$creadList :: ReadS [DescribeIdentityPoolUsage]
readsPrec :: Int -> ReadS DescribeIdentityPoolUsage
$creadsPrec :: Int -> ReadS DescribeIdentityPoolUsage
Prelude.Read, Int -> DescribeIdentityPoolUsage -> ShowS
[DescribeIdentityPoolUsage] -> ShowS
DescribeIdentityPoolUsage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeIdentityPoolUsage] -> ShowS
$cshowList :: [DescribeIdentityPoolUsage] -> ShowS
show :: DescribeIdentityPoolUsage -> String
$cshow :: DescribeIdentityPoolUsage -> String
showsPrec :: Int -> DescribeIdentityPoolUsage -> ShowS
$cshowsPrec :: Int -> DescribeIdentityPoolUsage -> ShowS
Prelude.Show, forall x.
Rep DescribeIdentityPoolUsage x -> DescribeIdentityPoolUsage
forall x.
DescribeIdentityPoolUsage -> Rep DescribeIdentityPoolUsage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeIdentityPoolUsage x -> DescribeIdentityPoolUsage
$cfrom :: forall x.
DescribeIdentityPoolUsage -> Rep DescribeIdentityPoolUsage x
Prelude.Generic)

-- |
-- Create a value of 'DescribeIdentityPoolUsage' 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:
--
-- 'identityPoolId', 'describeIdentityPoolUsage_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
newDescribeIdentityPoolUsage ::
  -- | 'identityPoolId'
  Prelude.Text ->
  DescribeIdentityPoolUsage
newDescribeIdentityPoolUsage :: Text -> DescribeIdentityPoolUsage
newDescribeIdentityPoolUsage Text
pIdentityPoolId_ =
  DescribeIdentityPoolUsage'
    { $sel:identityPoolId:DescribeIdentityPoolUsage' :: Text
identityPoolId =
        Text
pIdentityPoolId_
    }

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
describeIdentityPoolUsage_identityPoolId :: Lens.Lens' DescribeIdentityPoolUsage Prelude.Text
describeIdentityPoolUsage_identityPoolId :: Lens' DescribeIdentityPoolUsage Text
describeIdentityPoolUsage_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIdentityPoolUsage' {Text
identityPoolId :: Text
$sel:identityPoolId:DescribeIdentityPoolUsage' :: DescribeIdentityPoolUsage -> Text
identityPoolId} -> Text
identityPoolId) (\s :: DescribeIdentityPoolUsage
s@DescribeIdentityPoolUsage' {} Text
a -> DescribeIdentityPoolUsage
s {$sel:identityPoolId:DescribeIdentityPoolUsage' :: Text
identityPoolId = Text
a} :: DescribeIdentityPoolUsage)

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

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

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

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

-- | Response to a successful DescribeIdentityPoolUsage request.
--
-- /See:/ 'newDescribeIdentityPoolUsageResponse' smart constructor.
data DescribeIdentityPoolUsageResponse = DescribeIdentityPoolUsageResponse'
  { -- | Information about the usage of the identity pool.
    DescribeIdentityPoolUsageResponse -> Maybe IdentityPoolUsage
identityPoolUsage :: Prelude.Maybe IdentityPoolUsage,
    -- | The response's http status code.
    DescribeIdentityPoolUsageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeIdentityPoolUsageResponse
-> DescribeIdentityPoolUsageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeIdentityPoolUsageResponse
-> DescribeIdentityPoolUsageResponse -> Bool
$c/= :: DescribeIdentityPoolUsageResponse
-> DescribeIdentityPoolUsageResponse -> Bool
== :: DescribeIdentityPoolUsageResponse
-> DescribeIdentityPoolUsageResponse -> Bool
$c== :: DescribeIdentityPoolUsageResponse
-> DescribeIdentityPoolUsageResponse -> Bool
Prelude.Eq, ReadPrec [DescribeIdentityPoolUsageResponse]
ReadPrec DescribeIdentityPoolUsageResponse
Int -> ReadS DescribeIdentityPoolUsageResponse
ReadS [DescribeIdentityPoolUsageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeIdentityPoolUsageResponse]
$creadListPrec :: ReadPrec [DescribeIdentityPoolUsageResponse]
readPrec :: ReadPrec DescribeIdentityPoolUsageResponse
$creadPrec :: ReadPrec DescribeIdentityPoolUsageResponse
readList :: ReadS [DescribeIdentityPoolUsageResponse]
$creadList :: ReadS [DescribeIdentityPoolUsageResponse]
readsPrec :: Int -> ReadS DescribeIdentityPoolUsageResponse
$creadsPrec :: Int -> ReadS DescribeIdentityPoolUsageResponse
Prelude.Read, Int -> DescribeIdentityPoolUsageResponse -> ShowS
[DescribeIdentityPoolUsageResponse] -> ShowS
DescribeIdentityPoolUsageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeIdentityPoolUsageResponse] -> ShowS
$cshowList :: [DescribeIdentityPoolUsageResponse] -> ShowS
show :: DescribeIdentityPoolUsageResponse -> String
$cshow :: DescribeIdentityPoolUsageResponse -> String
showsPrec :: Int -> DescribeIdentityPoolUsageResponse -> ShowS
$cshowsPrec :: Int -> DescribeIdentityPoolUsageResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeIdentityPoolUsageResponse x
-> DescribeIdentityPoolUsageResponse
forall x.
DescribeIdentityPoolUsageResponse
-> Rep DescribeIdentityPoolUsageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeIdentityPoolUsageResponse x
-> DescribeIdentityPoolUsageResponse
$cfrom :: forall x.
DescribeIdentityPoolUsageResponse
-> Rep DescribeIdentityPoolUsageResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeIdentityPoolUsageResponse' 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:
--
-- 'identityPoolUsage', 'describeIdentityPoolUsageResponse_identityPoolUsage' - Information about the usage of the identity pool.
--
-- 'httpStatus', 'describeIdentityPoolUsageResponse_httpStatus' - The response's http status code.
newDescribeIdentityPoolUsageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeIdentityPoolUsageResponse
newDescribeIdentityPoolUsageResponse :: Int -> DescribeIdentityPoolUsageResponse
newDescribeIdentityPoolUsageResponse Int
pHttpStatus_ =
  DescribeIdentityPoolUsageResponse'
    { $sel:identityPoolUsage:DescribeIdentityPoolUsageResponse' :: Maybe IdentityPoolUsage
identityPoolUsage =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeIdentityPoolUsageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the usage of the identity pool.
describeIdentityPoolUsageResponse_identityPoolUsage :: Lens.Lens' DescribeIdentityPoolUsageResponse (Prelude.Maybe IdentityPoolUsage)
describeIdentityPoolUsageResponse_identityPoolUsage :: Lens' DescribeIdentityPoolUsageResponse (Maybe IdentityPoolUsage)
describeIdentityPoolUsageResponse_identityPoolUsage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIdentityPoolUsageResponse' {Maybe IdentityPoolUsage
identityPoolUsage :: Maybe IdentityPoolUsage
$sel:identityPoolUsage:DescribeIdentityPoolUsageResponse' :: DescribeIdentityPoolUsageResponse -> Maybe IdentityPoolUsage
identityPoolUsage} -> Maybe IdentityPoolUsage
identityPoolUsage) (\s :: DescribeIdentityPoolUsageResponse
s@DescribeIdentityPoolUsageResponse' {} Maybe IdentityPoolUsage
a -> DescribeIdentityPoolUsageResponse
s {$sel:identityPoolUsage:DescribeIdentityPoolUsageResponse' :: Maybe IdentityPoolUsage
identityPoolUsage = Maybe IdentityPoolUsage
a} :: DescribeIdentityPoolUsageResponse)

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

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