{-# 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.GetCredentialReport
-- 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 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.GetCredentialReport
  ( -- * Creating a Request
    GetCredentialReport (..),
    newGetCredentialReport,

    -- * Destructuring the Response
    GetCredentialReportResponse (..),
    newGetCredentialReportResponse,

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

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

instance Core.AWSRequest GetCredentialReport where
  type
    AWSResponse GetCredentialReport =
      GetCredentialReportResponse
  request :: (Service -> Service)
-> GetCredentialReport -> Request GetCredentialReport
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 GetCredentialReport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCredentialReport)))
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
"GetCredentialReportResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Base64
-> Maybe ISO8601
-> Maybe ReportFormatType
-> Int
-> GetCredentialReportResponse
GetCredentialReportResponse'
            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
"Content")
            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
"GeneratedTime")
            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
"ReportFormat")
            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 GetCredentialReport where
  hashWithSalt :: Int -> GetCredentialReport -> Int
hashWithSalt Int
_salt GetCredentialReport
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

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

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

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

-- | Contains the response to a successful GetCredentialReport request.
--
-- /See:/ 'newGetCredentialReportResponse' smart constructor.
data GetCredentialReportResponse = GetCredentialReportResponse'
  { -- | Contains the credential report. The report is Base64-encoded.
    GetCredentialReportResponse -> Maybe Base64
content :: Prelude.Maybe Data.Base64,
    -- | The date and time when the credential report was created, in
    -- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>.
    GetCredentialReportResponse -> Maybe ISO8601
generatedTime :: Prelude.Maybe Data.ISO8601,
    -- | The format (MIME type) of the credential report.
    GetCredentialReportResponse -> Maybe ReportFormatType
reportFormat :: Prelude.Maybe ReportFormatType,
    -- | The response's http status code.
    GetCredentialReportResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCredentialReportResponse -> GetCredentialReportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCredentialReportResponse -> GetCredentialReportResponse -> Bool
$c/= :: GetCredentialReportResponse -> GetCredentialReportResponse -> Bool
== :: GetCredentialReportResponse -> GetCredentialReportResponse -> Bool
$c== :: GetCredentialReportResponse -> GetCredentialReportResponse -> Bool
Prelude.Eq, ReadPrec [GetCredentialReportResponse]
ReadPrec GetCredentialReportResponse
Int -> ReadS GetCredentialReportResponse
ReadS [GetCredentialReportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCredentialReportResponse]
$creadListPrec :: ReadPrec [GetCredentialReportResponse]
readPrec :: ReadPrec GetCredentialReportResponse
$creadPrec :: ReadPrec GetCredentialReportResponse
readList :: ReadS [GetCredentialReportResponse]
$creadList :: ReadS [GetCredentialReportResponse]
readsPrec :: Int -> ReadS GetCredentialReportResponse
$creadsPrec :: Int -> ReadS GetCredentialReportResponse
Prelude.Read, Int -> GetCredentialReportResponse -> ShowS
[GetCredentialReportResponse] -> ShowS
GetCredentialReportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCredentialReportResponse] -> ShowS
$cshowList :: [GetCredentialReportResponse] -> ShowS
show :: GetCredentialReportResponse -> String
$cshow :: GetCredentialReportResponse -> String
showsPrec :: Int -> GetCredentialReportResponse -> ShowS
$cshowsPrec :: Int -> GetCredentialReportResponse -> ShowS
Prelude.Show, forall x.
Rep GetCredentialReportResponse x -> GetCredentialReportResponse
forall x.
GetCredentialReportResponse -> Rep GetCredentialReportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCredentialReportResponse x -> GetCredentialReportResponse
$cfrom :: forall x.
GetCredentialReportResponse -> Rep GetCredentialReportResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCredentialReportResponse' 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:
--
-- 'content', 'getCredentialReportResponse_content' - Contains the credential report. The report is Base64-encoded.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
--
-- 'generatedTime', 'getCredentialReportResponse_generatedTime' - The date and time when the credential report was created, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>.
--
-- 'reportFormat', 'getCredentialReportResponse_reportFormat' - The format (MIME type) of the credential report.
--
-- 'httpStatus', 'getCredentialReportResponse_httpStatus' - The response's http status code.
newGetCredentialReportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCredentialReportResponse
newGetCredentialReportResponse :: Int -> GetCredentialReportResponse
newGetCredentialReportResponse Int
pHttpStatus_ =
  GetCredentialReportResponse'
    { $sel:content:GetCredentialReportResponse' :: Maybe Base64
content =
        forall a. Maybe a
Prelude.Nothing,
      $sel:generatedTime:GetCredentialReportResponse' :: Maybe ISO8601
generatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:reportFormat:GetCredentialReportResponse' :: Maybe ReportFormatType
reportFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCredentialReportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the credential report. The report is Base64-encoded.--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
getCredentialReportResponse_content :: Lens.Lens' GetCredentialReportResponse (Prelude.Maybe Prelude.ByteString)
getCredentialReportResponse_content :: Lens' GetCredentialReportResponse (Maybe ByteString)
getCredentialReportResponse_content = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCredentialReportResponse' {Maybe Base64
content :: Maybe Base64
$sel:content:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe Base64
content} -> Maybe Base64
content) (\s :: GetCredentialReportResponse
s@GetCredentialReportResponse' {} Maybe Base64
a -> GetCredentialReportResponse
s {$sel:content:GetCredentialReportResponse' :: Maybe Base64
content = Maybe Base64
a} :: GetCredentialReportResponse) 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 Iso' Base64 ByteString
Data._Base64

-- | The date and time when the credential report was created, in
-- <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>.
getCredentialReportResponse_generatedTime :: Lens.Lens' GetCredentialReportResponse (Prelude.Maybe Prelude.UTCTime)
getCredentialReportResponse_generatedTime :: Lens' GetCredentialReportResponse (Maybe UTCTime)
getCredentialReportResponse_generatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCredentialReportResponse' {Maybe ISO8601
generatedTime :: Maybe ISO8601
$sel:generatedTime:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe ISO8601
generatedTime} -> Maybe ISO8601
generatedTime) (\s :: GetCredentialReportResponse
s@GetCredentialReportResponse' {} Maybe ISO8601
a -> GetCredentialReportResponse
s {$sel:generatedTime:GetCredentialReportResponse' :: Maybe ISO8601
generatedTime = Maybe ISO8601
a} :: GetCredentialReportResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The format (MIME type) of the credential report.
getCredentialReportResponse_reportFormat :: Lens.Lens' GetCredentialReportResponse (Prelude.Maybe ReportFormatType)
getCredentialReportResponse_reportFormat :: Lens' GetCredentialReportResponse (Maybe ReportFormatType)
getCredentialReportResponse_reportFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCredentialReportResponse' {Maybe ReportFormatType
reportFormat :: Maybe ReportFormatType
$sel:reportFormat:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe ReportFormatType
reportFormat} -> Maybe ReportFormatType
reportFormat) (\s :: GetCredentialReportResponse
s@GetCredentialReportResponse' {} Maybe ReportFormatType
a -> GetCredentialReportResponse
s {$sel:reportFormat:GetCredentialReportResponse' :: Maybe ReportFormatType
reportFormat = Maybe ReportFormatType
a} :: GetCredentialReportResponse)

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

instance Prelude.NFData GetCredentialReportResponse where
  rnf :: GetCredentialReportResponse -> ()
rnf GetCredentialReportResponse' {Int
Maybe Base64
Maybe ISO8601
Maybe ReportFormatType
httpStatus :: Int
reportFormat :: Maybe ReportFormatType
generatedTime :: Maybe ISO8601
content :: Maybe Base64
$sel:httpStatus:GetCredentialReportResponse' :: GetCredentialReportResponse -> Int
$sel:reportFormat:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe ReportFormatType
$sel:generatedTime:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe ISO8601
$sel:content:GetCredentialReportResponse' :: GetCredentialReportResponse -> Maybe Base64
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Base64
content
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
generatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportFormatType
reportFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus