{-# 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.GenerateCredentialReport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Generates a credential report for the Amazon Web Services account. For
-- more information about the credential report, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/credential-reports.html Getting credential reports>
-- in the /IAM User Guide/.
module Amazonka.IAM.GenerateCredentialReport
  ( -- * Creating a Request
    GenerateCredentialReport (..),
    newGenerateCredentialReport,

    -- * Destructuring the Response
    GenerateCredentialReportResponse (..),
    newGenerateCredentialReportResponse,

    -- * Response Lenses
    generateCredentialReportResponse_description,
    generateCredentialReportResponse_state,
    generateCredentialReportResponse_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:/ 'newGenerateCredentialReport' smart constructor.
data GenerateCredentialReport = GenerateCredentialReport'
  {
  }
  deriving (GenerateCredentialReport -> GenerateCredentialReport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenerateCredentialReport -> GenerateCredentialReport -> Bool
$c/= :: GenerateCredentialReport -> GenerateCredentialReport -> Bool
== :: GenerateCredentialReport -> GenerateCredentialReport -> Bool
$c== :: GenerateCredentialReport -> GenerateCredentialReport -> Bool
Prelude.Eq, ReadPrec [GenerateCredentialReport]
ReadPrec GenerateCredentialReport
Int -> ReadS GenerateCredentialReport
ReadS [GenerateCredentialReport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GenerateCredentialReport]
$creadListPrec :: ReadPrec [GenerateCredentialReport]
readPrec :: ReadPrec GenerateCredentialReport
$creadPrec :: ReadPrec GenerateCredentialReport
readList :: ReadS [GenerateCredentialReport]
$creadList :: ReadS [GenerateCredentialReport]
readsPrec :: Int -> ReadS GenerateCredentialReport
$creadsPrec :: Int -> ReadS GenerateCredentialReport
Prelude.Read, Int -> GenerateCredentialReport -> ShowS
[GenerateCredentialReport] -> ShowS
GenerateCredentialReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenerateCredentialReport] -> ShowS
$cshowList :: [GenerateCredentialReport] -> ShowS
show :: GenerateCredentialReport -> String
$cshow :: GenerateCredentialReport -> String
showsPrec :: Int -> GenerateCredentialReport -> ShowS
$cshowsPrec :: Int -> GenerateCredentialReport -> ShowS
Prelude.Show, forall x.
Rep GenerateCredentialReport x -> GenerateCredentialReport
forall x.
GenerateCredentialReport -> Rep GenerateCredentialReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GenerateCredentialReport x -> GenerateCredentialReport
$cfrom :: forall x.
GenerateCredentialReport -> Rep GenerateCredentialReport x
Prelude.Generic)

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

instance Core.AWSRequest GenerateCredentialReport where
  type
    AWSResponse GenerateCredentialReport =
      GenerateCredentialReportResponse
  request :: (Service -> Service)
-> GenerateCredentialReport -> Request GenerateCredentialReport
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 GenerateCredentialReport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GenerateCredentialReport)))
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
"GenerateCredentialReportResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe ReportStateType -> Int -> GenerateCredentialReportResponse
GenerateCredentialReportResponse'
            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
"Description")
            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
"State")
            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 GenerateCredentialReport where
  hashWithSalt :: Int -> GenerateCredentialReport -> Int
hashWithSalt Int
_salt GenerateCredentialReport
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

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

-- | Contains the response to a successful GenerateCredentialReport request.
--
-- /See:/ 'newGenerateCredentialReportResponse' smart constructor.
data GenerateCredentialReportResponse = GenerateCredentialReportResponse'
  { -- | Information about the credential report.
    GenerateCredentialReportResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Information about the state of the credential report.
    GenerateCredentialReportResponse -> Maybe ReportStateType
state :: Prelude.Maybe ReportStateType,
    -- | The response's http status code.
    GenerateCredentialReportResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GenerateCredentialReportResponse
-> GenerateCredentialReportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenerateCredentialReportResponse
-> GenerateCredentialReportResponse -> Bool
$c/= :: GenerateCredentialReportResponse
-> GenerateCredentialReportResponse -> Bool
== :: GenerateCredentialReportResponse
-> GenerateCredentialReportResponse -> Bool
$c== :: GenerateCredentialReportResponse
-> GenerateCredentialReportResponse -> Bool
Prelude.Eq, ReadPrec [GenerateCredentialReportResponse]
ReadPrec GenerateCredentialReportResponse
Int -> ReadS GenerateCredentialReportResponse
ReadS [GenerateCredentialReportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GenerateCredentialReportResponse]
$creadListPrec :: ReadPrec [GenerateCredentialReportResponse]
readPrec :: ReadPrec GenerateCredentialReportResponse
$creadPrec :: ReadPrec GenerateCredentialReportResponse
readList :: ReadS [GenerateCredentialReportResponse]
$creadList :: ReadS [GenerateCredentialReportResponse]
readsPrec :: Int -> ReadS GenerateCredentialReportResponse
$creadsPrec :: Int -> ReadS GenerateCredentialReportResponse
Prelude.Read, Int -> GenerateCredentialReportResponse -> ShowS
[GenerateCredentialReportResponse] -> ShowS
GenerateCredentialReportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenerateCredentialReportResponse] -> ShowS
$cshowList :: [GenerateCredentialReportResponse] -> ShowS
show :: GenerateCredentialReportResponse -> String
$cshow :: GenerateCredentialReportResponse -> String
showsPrec :: Int -> GenerateCredentialReportResponse -> ShowS
$cshowsPrec :: Int -> GenerateCredentialReportResponse -> ShowS
Prelude.Show, forall x.
Rep GenerateCredentialReportResponse x
-> GenerateCredentialReportResponse
forall x.
GenerateCredentialReportResponse
-> Rep GenerateCredentialReportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GenerateCredentialReportResponse x
-> GenerateCredentialReportResponse
$cfrom :: forall x.
GenerateCredentialReportResponse
-> Rep GenerateCredentialReportResponse x
Prelude.Generic)

-- |
-- Create a value of 'GenerateCredentialReportResponse' 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:
--
-- 'description', 'generateCredentialReportResponse_description' - Information about the credential report.
--
-- 'state', 'generateCredentialReportResponse_state' - Information about the state of the credential report.
--
-- 'httpStatus', 'generateCredentialReportResponse_httpStatus' - The response's http status code.
newGenerateCredentialReportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GenerateCredentialReportResponse
newGenerateCredentialReportResponse :: Int -> GenerateCredentialReportResponse
newGenerateCredentialReportResponse Int
pHttpStatus_ =
  GenerateCredentialReportResponse'
    { $sel:description:GenerateCredentialReportResponse' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:state:GenerateCredentialReportResponse' :: Maybe ReportStateType
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GenerateCredentialReportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the credential report.
generateCredentialReportResponse_description :: Lens.Lens' GenerateCredentialReportResponse (Prelude.Maybe Prelude.Text)
generateCredentialReportResponse_description :: Lens' GenerateCredentialReportResponse (Maybe Text)
generateCredentialReportResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GenerateCredentialReportResponse' {Maybe Text
description :: Maybe Text
$sel:description:GenerateCredentialReportResponse' :: GenerateCredentialReportResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GenerateCredentialReportResponse
s@GenerateCredentialReportResponse' {} Maybe Text
a -> GenerateCredentialReportResponse
s {$sel:description:GenerateCredentialReportResponse' :: Maybe Text
description = Maybe Text
a} :: GenerateCredentialReportResponse)

-- | Information about the state of the credential report.
generateCredentialReportResponse_state :: Lens.Lens' GenerateCredentialReportResponse (Prelude.Maybe ReportStateType)
generateCredentialReportResponse_state :: Lens' GenerateCredentialReportResponse (Maybe ReportStateType)
generateCredentialReportResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GenerateCredentialReportResponse' {Maybe ReportStateType
state :: Maybe ReportStateType
$sel:state:GenerateCredentialReportResponse' :: GenerateCredentialReportResponse -> Maybe ReportStateType
state} -> Maybe ReportStateType
state) (\s :: GenerateCredentialReportResponse
s@GenerateCredentialReportResponse' {} Maybe ReportStateType
a -> GenerateCredentialReportResponse
s {$sel:state:GenerateCredentialReportResponse' :: Maybe ReportStateType
state = Maybe ReportStateType
a} :: GenerateCredentialReportResponse)

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

instance
  Prelude.NFData
    GenerateCredentialReportResponse
  where
  rnf :: GenerateCredentialReportResponse -> ()
rnf GenerateCredentialReportResponse' {Int
Maybe Text
Maybe ReportStateType
httpStatus :: Int
state :: Maybe ReportStateType
description :: Maybe Text
$sel:httpStatus:GenerateCredentialReportResponse' :: GenerateCredentialReportResponse -> Int
$sel:state:GenerateCredentialReportResponse' :: GenerateCredentialReportResponse -> Maybe ReportStateType
$sel:description:GenerateCredentialReportResponse' :: GenerateCredentialReportResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportStateType
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus