{-# 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.IAM.GetAccountSummary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about IAM entity usage and IAM quotas in the
-- Amazon Web Services account.
--
-- For information about IAM quotas, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_iam-quotas.html IAM and STS quotas>
-- in the /IAM User Guide/.
module Amazonka.IAM.GetAccountSummary
  ( -- * Creating a Request
    GetAccountSummary (..),
    newGetAccountSummary,

    -- * Destructuring the Response
    GetAccountSummaryResponse (..),
    newGetAccountSummaryResponse,

    -- * Response Lenses
    getAccountSummaryResponse_summaryMap,
    getAccountSummaryResponse_httpStatus,
  )
where

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

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

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

instance Core.AWSRequest GetAccountSummary where
  type
    AWSResponse GetAccountSummary =
      GetAccountSummaryResponse
  request :: (Service -> Service)
-> GetAccountSummary -> Request GetAccountSummary
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 GetAccountSummary
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAccountSummary)))
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
"GetAccountSummaryResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe (HashMap SummaryKeyType Int)
-> Int -> GetAccountSummaryResponse
GetAccountSummaryResponse'
            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
"SummaryMap"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall k v.
(Eq k, Hashable k, FromText k, FromXML v) =>
Text -> Text -> Text -> [Node] -> Either String (HashMap k v)
Data.parseXMLMap Text
"entry" Text
"key" Text
"value")
                        )
            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 GetAccountSummary where
  hashWithSalt :: Int -> GetAccountSummary -> Int
hashWithSalt Int
_salt GetAccountSummary
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

instance Data.ToQuery GetAccountSummary where
  toQuery :: GetAccountSummary -> 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
"GetAccountSummary" :: Prelude.ByteString),
            ByteString
"Version"
              forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString)
          ]
      )

-- | Contains the response to a successful GetAccountSummary request.
--
-- /See:/ 'newGetAccountSummaryResponse' smart constructor.
data GetAccountSummaryResponse = GetAccountSummaryResponse'
  { -- | A set of key–value pairs containing information about IAM entity usage
    -- and IAM quotas.
    GetAccountSummaryResponse -> Maybe (HashMap SummaryKeyType Int)
summaryMap :: Prelude.Maybe (Prelude.HashMap SummaryKeyType Prelude.Int),
    -- | The response's http status code.
    GetAccountSummaryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAccountSummaryResponse -> GetAccountSummaryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAccountSummaryResponse -> GetAccountSummaryResponse -> Bool
$c/= :: GetAccountSummaryResponse -> GetAccountSummaryResponse -> Bool
== :: GetAccountSummaryResponse -> GetAccountSummaryResponse -> Bool
$c== :: GetAccountSummaryResponse -> GetAccountSummaryResponse -> Bool
Prelude.Eq, ReadPrec [GetAccountSummaryResponse]
ReadPrec GetAccountSummaryResponse
Int -> ReadS GetAccountSummaryResponse
ReadS [GetAccountSummaryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAccountSummaryResponse]
$creadListPrec :: ReadPrec [GetAccountSummaryResponse]
readPrec :: ReadPrec GetAccountSummaryResponse
$creadPrec :: ReadPrec GetAccountSummaryResponse
readList :: ReadS [GetAccountSummaryResponse]
$creadList :: ReadS [GetAccountSummaryResponse]
readsPrec :: Int -> ReadS GetAccountSummaryResponse
$creadsPrec :: Int -> ReadS GetAccountSummaryResponse
Prelude.Read, Int -> GetAccountSummaryResponse -> ShowS
[GetAccountSummaryResponse] -> ShowS
GetAccountSummaryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAccountSummaryResponse] -> ShowS
$cshowList :: [GetAccountSummaryResponse] -> ShowS
show :: GetAccountSummaryResponse -> String
$cshow :: GetAccountSummaryResponse -> String
showsPrec :: Int -> GetAccountSummaryResponse -> ShowS
$cshowsPrec :: Int -> GetAccountSummaryResponse -> ShowS
Prelude.Show, forall x.
Rep GetAccountSummaryResponse x -> GetAccountSummaryResponse
forall x.
GetAccountSummaryResponse -> Rep GetAccountSummaryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAccountSummaryResponse x -> GetAccountSummaryResponse
$cfrom :: forall x.
GetAccountSummaryResponse -> Rep GetAccountSummaryResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAccountSummaryResponse' 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:
--
-- 'summaryMap', 'getAccountSummaryResponse_summaryMap' - A set of key–value pairs containing information about IAM entity usage
-- and IAM quotas.
--
-- 'httpStatus', 'getAccountSummaryResponse_httpStatus' - The response's http status code.
newGetAccountSummaryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAccountSummaryResponse
newGetAccountSummaryResponse :: Int -> GetAccountSummaryResponse
newGetAccountSummaryResponse Int
pHttpStatus_ =
  GetAccountSummaryResponse'
    { $sel:summaryMap:GetAccountSummaryResponse' :: Maybe (HashMap SummaryKeyType Int)
summaryMap =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAccountSummaryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A set of key–value pairs containing information about IAM entity usage
-- and IAM quotas.
getAccountSummaryResponse_summaryMap :: Lens.Lens' GetAccountSummaryResponse (Prelude.Maybe (Prelude.HashMap SummaryKeyType Prelude.Int))
getAccountSummaryResponse_summaryMap :: Lens'
  GetAccountSummaryResponse (Maybe (HashMap SummaryKeyType Int))
getAccountSummaryResponse_summaryMap = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAccountSummaryResponse' {Maybe (HashMap SummaryKeyType Int)
summaryMap :: Maybe (HashMap SummaryKeyType Int)
$sel:summaryMap:GetAccountSummaryResponse' :: GetAccountSummaryResponse -> Maybe (HashMap SummaryKeyType Int)
summaryMap} -> Maybe (HashMap SummaryKeyType Int)
summaryMap) (\s :: GetAccountSummaryResponse
s@GetAccountSummaryResponse' {} Maybe (HashMap SummaryKeyType Int)
a -> GetAccountSummaryResponse
s {$sel:summaryMap:GetAccountSummaryResponse' :: Maybe (HashMap SummaryKeyType Int)
summaryMap = Maybe (HashMap SummaryKeyType Int)
a} :: GetAccountSummaryResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetAccountSummaryResponse where
  rnf :: GetAccountSummaryResponse -> ()
rnf GetAccountSummaryResponse' {Int
Maybe (HashMap SummaryKeyType Int)
httpStatus :: Int
summaryMap :: Maybe (HashMap SummaryKeyType Int)
$sel:httpStatus:GetAccountSummaryResponse' :: GetAccountSummaryResponse -> Int
$sel:summaryMap:GetAccountSummaryResponse' :: GetAccountSummaryResponse -> Maybe (HashMap SummaryKeyType Int)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap SummaryKeyType Int)
summaryMap
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus