{-# 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.GetServiceLastAccessedDetailsWithEntities
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- After you generate a group or policy report using the
-- @GenerateServiceLastAccessedDetails@ operation, you can use the @JobId@
-- parameter in @GetServiceLastAccessedDetailsWithEntities@. This operation
-- retrieves the status of your report job and a list of entities that
-- could have used group or policy permissions to access the specified
-- service.
--
-- -   __Group__ – For a group report, this operation returns a list of
--     users in the group that could have used the group’s policies in an
--     attempt to access the service.
--
-- -   __Policy__ – For a policy report, this operation returns a list of
--     entities (users or roles) that could have used the policy in an
--     attempt to access the service.
--
-- You can also use this operation for user or role reports to retrieve
-- details about those entities.
--
-- If the operation fails, the @GetServiceLastAccessedDetailsWithEntities@
-- operation returns the reason that it failed.
--
-- By default, the list of associated entities is sorted by date, with the
-- most recent access listed first.
module Amazonka.IAM.GetServiceLastAccessedDetailsWithEntities
  ( -- * Creating a Request
    GetServiceLastAccessedDetailsWithEntities (..),
    newGetServiceLastAccessedDetailsWithEntities,

    -- * Request Lenses
    getServiceLastAccessedDetailsWithEntities_marker,
    getServiceLastAccessedDetailsWithEntities_maxItems,
    getServiceLastAccessedDetailsWithEntities_jobId,
    getServiceLastAccessedDetailsWithEntities_serviceNamespace,

    -- * Destructuring the Response
    GetServiceLastAccessedDetailsWithEntitiesResponse (..),
    newGetServiceLastAccessedDetailsWithEntitiesResponse,

    -- * Response Lenses
    getServiceLastAccessedDetailsWithEntitiesResponse_error,
    getServiceLastAccessedDetailsWithEntitiesResponse_isTruncated,
    getServiceLastAccessedDetailsWithEntitiesResponse_marker,
    getServiceLastAccessedDetailsWithEntitiesResponse_httpStatus,
    getServiceLastAccessedDetailsWithEntitiesResponse_jobStatus,
    getServiceLastAccessedDetailsWithEntitiesResponse_jobCreationDate,
    getServiceLastAccessedDetailsWithEntitiesResponse_jobCompletionDate,
    getServiceLastAccessedDetailsWithEntitiesResponse_entityDetailsList,
  )
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:/ 'newGetServiceLastAccessedDetailsWithEntities' smart constructor.
data GetServiceLastAccessedDetailsWithEntities = GetServiceLastAccessedDetailsWithEntities'
  { -- | Use this parameter only when paginating results and only after you
    -- receive a response indicating that the results are truncated. Set it to
    -- the value of the @Marker@ element in the response that you received to
    -- indicate where the next call should start.
    GetServiceLastAccessedDetailsWithEntities -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | Use this only when paginating results to indicate the maximum number of
    -- items you want in the response. If additional items exist beyond the
    -- maximum you specify, the @IsTruncated@ response element is @true@.
    --
    -- If you do not include this parameter, the number of items defaults to
    -- 100. Note that IAM might return fewer results, even when there are more
    -- results available. In that case, the @IsTruncated@ response element
    -- returns @true@, and @Marker@ contains a value to include in the
    -- subsequent call that tells the service where to continue from.
    GetServiceLastAccessedDetailsWithEntities -> Maybe Natural
maxItems :: Prelude.Maybe Prelude.Natural,
    -- | The ID of the request generated by the
    -- @GenerateServiceLastAccessedDetails@ operation.
    GetServiceLastAccessedDetailsWithEntities -> Text
jobId :: Prelude.Text,
    -- | The service namespace for an Amazon Web Services service. Provide the
    -- service namespace to learn when the IAM entity last attempted to access
    -- the specified service.
    --
    -- To learn the service namespace for a service, see
    -- <https://docs.aws.amazon.com/service-authorization/latest/reference/reference_policies_actions-resources-contextkeys.html Actions, resources, and condition keys for Amazon Web Services services>
    -- in the /IAM User Guide/. Choose the name of the service to view details
    -- for that service. In the first paragraph, find the service prefix. For
    -- example, @(service prefix: a4b)@. For more information about service
    -- namespaces, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html#genref-aws-service-namespaces Amazon Web Services service namespaces>
    -- in the /Amazon Web Services General Reference/.
    GetServiceLastAccessedDetailsWithEntities -> Text
serviceNamespace :: Prelude.Text
  }
  deriving (GetServiceLastAccessedDetailsWithEntities
-> GetServiceLastAccessedDetailsWithEntities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceLastAccessedDetailsWithEntities
-> GetServiceLastAccessedDetailsWithEntities -> Bool
$c/= :: GetServiceLastAccessedDetailsWithEntities
-> GetServiceLastAccessedDetailsWithEntities -> Bool
== :: GetServiceLastAccessedDetailsWithEntities
-> GetServiceLastAccessedDetailsWithEntities -> Bool
$c== :: GetServiceLastAccessedDetailsWithEntities
-> GetServiceLastAccessedDetailsWithEntities -> Bool
Prelude.Eq, ReadPrec [GetServiceLastAccessedDetailsWithEntities]
ReadPrec GetServiceLastAccessedDetailsWithEntities
Int -> ReadS GetServiceLastAccessedDetailsWithEntities
ReadS [GetServiceLastAccessedDetailsWithEntities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceLastAccessedDetailsWithEntities]
$creadListPrec :: ReadPrec [GetServiceLastAccessedDetailsWithEntities]
readPrec :: ReadPrec GetServiceLastAccessedDetailsWithEntities
$creadPrec :: ReadPrec GetServiceLastAccessedDetailsWithEntities
readList :: ReadS [GetServiceLastAccessedDetailsWithEntities]
$creadList :: ReadS [GetServiceLastAccessedDetailsWithEntities]
readsPrec :: Int -> ReadS GetServiceLastAccessedDetailsWithEntities
$creadsPrec :: Int -> ReadS GetServiceLastAccessedDetailsWithEntities
Prelude.Read, Int -> GetServiceLastAccessedDetailsWithEntities -> ShowS
[GetServiceLastAccessedDetailsWithEntities] -> ShowS
GetServiceLastAccessedDetailsWithEntities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceLastAccessedDetailsWithEntities] -> ShowS
$cshowList :: [GetServiceLastAccessedDetailsWithEntities] -> ShowS
show :: GetServiceLastAccessedDetailsWithEntities -> String
$cshow :: GetServiceLastAccessedDetailsWithEntities -> String
showsPrec :: Int -> GetServiceLastAccessedDetailsWithEntities -> ShowS
$cshowsPrec :: Int -> GetServiceLastAccessedDetailsWithEntities -> ShowS
Prelude.Show, forall x.
Rep GetServiceLastAccessedDetailsWithEntities x
-> GetServiceLastAccessedDetailsWithEntities
forall x.
GetServiceLastAccessedDetailsWithEntities
-> Rep GetServiceLastAccessedDetailsWithEntities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetServiceLastAccessedDetailsWithEntities x
-> GetServiceLastAccessedDetailsWithEntities
$cfrom :: forall x.
GetServiceLastAccessedDetailsWithEntities
-> Rep GetServiceLastAccessedDetailsWithEntities x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceLastAccessedDetailsWithEntities' 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:
--
-- 'marker', 'getServiceLastAccessedDetailsWithEntities_marker' - Use this parameter only when paginating results and only after you
-- receive a response indicating that the results are truncated. Set it to
-- the value of the @Marker@ element in the response that you received to
-- indicate where the next call should start.
--
-- 'maxItems', 'getServiceLastAccessedDetailsWithEntities_maxItems' - Use this only when paginating results to indicate the maximum number of
-- items you want in the response. If additional items exist beyond the
-- maximum you specify, the @IsTruncated@ response element is @true@.
--
-- If you do not include this parameter, the number of items defaults to
-- 100. Note that IAM might return fewer results, even when there are more
-- results available. In that case, the @IsTruncated@ response element
-- returns @true@, and @Marker@ contains a value to include in the
-- subsequent call that tells the service where to continue from.
--
-- 'jobId', 'getServiceLastAccessedDetailsWithEntities_jobId' - The ID of the request generated by the
-- @GenerateServiceLastAccessedDetails@ operation.
--
-- 'serviceNamespace', 'getServiceLastAccessedDetailsWithEntities_serviceNamespace' - The service namespace for an Amazon Web Services service. Provide the
-- service namespace to learn when the IAM entity last attempted to access
-- the specified service.
--
-- To learn the service namespace for a service, see
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/reference_policies_actions-resources-contextkeys.html Actions, resources, and condition keys for Amazon Web Services services>
-- in the /IAM User Guide/. Choose the name of the service to view details
-- for that service. In the first paragraph, find the service prefix. For
-- example, @(service prefix: a4b)@. For more information about service
-- namespaces, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html#genref-aws-service-namespaces Amazon Web Services service namespaces>
-- in the /Amazon Web Services General Reference/.
newGetServiceLastAccessedDetailsWithEntities ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'serviceNamespace'
  Prelude.Text ->
  GetServiceLastAccessedDetailsWithEntities
newGetServiceLastAccessedDetailsWithEntities :: Text -> Text -> GetServiceLastAccessedDetailsWithEntities
newGetServiceLastAccessedDetailsWithEntities
  Text
pJobId_
  Text
pServiceNamespace_ =
    GetServiceLastAccessedDetailsWithEntities'
      { $sel:marker:GetServiceLastAccessedDetailsWithEntities' :: Maybe Text
marker =
          forall a. Maybe a
Prelude.Nothing,
        $sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: Maybe Natural
maxItems = forall a. Maybe a
Prelude.Nothing,
        $sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: Text
jobId = Text
pJobId_,
        $sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: Text
serviceNamespace =
          Text
pServiceNamespace_
      }

-- | Use this parameter only when paginating results and only after you
-- receive a response indicating that the results are truncated. Set it to
-- the value of the @Marker@ element in the response that you received to
-- indicate where the next call should start.
getServiceLastAccessedDetailsWithEntities_marker :: Lens.Lens' GetServiceLastAccessedDetailsWithEntities (Prelude.Maybe Prelude.Text)
getServiceLastAccessedDetailsWithEntities_marker :: Lens' GetServiceLastAccessedDetailsWithEntities (Maybe Text)
getServiceLastAccessedDetailsWithEntities_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntities' {Maybe Text
marker :: Maybe Text
$sel:marker:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Text
marker} -> Maybe Text
marker) (\s :: GetServiceLastAccessedDetailsWithEntities
s@GetServiceLastAccessedDetailsWithEntities' {} Maybe Text
a -> GetServiceLastAccessedDetailsWithEntities
s {$sel:marker:GetServiceLastAccessedDetailsWithEntities' :: Maybe Text
marker = Maybe Text
a} :: GetServiceLastAccessedDetailsWithEntities)

-- | Use this only when paginating results to indicate the maximum number of
-- items you want in the response. If additional items exist beyond the
-- maximum you specify, the @IsTruncated@ response element is @true@.
--
-- If you do not include this parameter, the number of items defaults to
-- 100. Note that IAM might return fewer results, even when there are more
-- results available. In that case, the @IsTruncated@ response element
-- returns @true@, and @Marker@ contains a value to include in the
-- subsequent call that tells the service where to continue from.
getServiceLastAccessedDetailsWithEntities_maxItems :: Lens.Lens' GetServiceLastAccessedDetailsWithEntities (Prelude.Maybe Prelude.Natural)
getServiceLastAccessedDetailsWithEntities_maxItems :: Lens' GetServiceLastAccessedDetailsWithEntities (Maybe Natural)
getServiceLastAccessedDetailsWithEntities_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntities' {Maybe Natural
maxItems :: Maybe Natural
$sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Natural
maxItems} -> Maybe Natural
maxItems) (\s :: GetServiceLastAccessedDetailsWithEntities
s@GetServiceLastAccessedDetailsWithEntities' {} Maybe Natural
a -> GetServiceLastAccessedDetailsWithEntities
s {$sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: Maybe Natural
maxItems = Maybe Natural
a} :: GetServiceLastAccessedDetailsWithEntities)

-- | The ID of the request generated by the
-- @GenerateServiceLastAccessedDetails@ operation.
getServiceLastAccessedDetailsWithEntities_jobId :: Lens.Lens' GetServiceLastAccessedDetailsWithEntities Prelude.Text
getServiceLastAccessedDetailsWithEntities_jobId :: Lens' GetServiceLastAccessedDetailsWithEntities Text
getServiceLastAccessedDetailsWithEntities_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntities' {Text
jobId :: Text
$sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
jobId} -> Text
jobId) (\s :: GetServiceLastAccessedDetailsWithEntities
s@GetServiceLastAccessedDetailsWithEntities' {} Text
a -> GetServiceLastAccessedDetailsWithEntities
s {$sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: Text
jobId = Text
a} :: GetServiceLastAccessedDetailsWithEntities)

-- | The service namespace for an Amazon Web Services service. Provide the
-- service namespace to learn when the IAM entity last attempted to access
-- the specified service.
--
-- To learn the service namespace for a service, see
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/reference_policies_actions-resources-contextkeys.html Actions, resources, and condition keys for Amazon Web Services services>
-- in the /IAM User Guide/. Choose the name of the service to view details
-- for that service. In the first paragraph, find the service prefix. For
-- example, @(service prefix: a4b)@. For more information about service
-- namespaces, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html#genref-aws-service-namespaces Amazon Web Services service namespaces>
-- in the /Amazon Web Services General Reference/.
getServiceLastAccessedDetailsWithEntities_serviceNamespace :: Lens.Lens' GetServiceLastAccessedDetailsWithEntities Prelude.Text
getServiceLastAccessedDetailsWithEntities_serviceNamespace :: Lens' GetServiceLastAccessedDetailsWithEntities Text
getServiceLastAccessedDetailsWithEntities_serviceNamespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntities' {Text
serviceNamespace :: Text
$sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
serviceNamespace} -> Text
serviceNamespace) (\s :: GetServiceLastAccessedDetailsWithEntities
s@GetServiceLastAccessedDetailsWithEntities' {} Text
a -> GetServiceLastAccessedDetailsWithEntities
s {$sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: Text
serviceNamespace = Text
a} :: GetServiceLastAccessedDetailsWithEntities)

instance
  Core.AWSRequest
    GetServiceLastAccessedDetailsWithEntities
  where
  type
    AWSResponse
      GetServiceLastAccessedDetailsWithEntities =
      GetServiceLastAccessedDetailsWithEntitiesResponse
  request :: (Service -> Service)
-> GetServiceLastAccessedDetailsWithEntities
-> Request GetServiceLastAccessedDetailsWithEntities
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 GetServiceLastAccessedDetailsWithEntities
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse GetServiceLastAccessedDetailsWithEntities)))
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
"GetServiceLastAccessedDetailsWithEntitiesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ErrorDetails
-> Maybe Bool
-> Maybe Text
-> Int
-> JobStatusType
-> ISO8601
-> ISO8601
-> [EntityDetails]
-> GetServiceLastAccessedDetailsWithEntitiesResponse
GetServiceLastAccessedDetailsWithEntitiesResponse'
            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
"Error")
            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
"IsTruncated")
            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
"Marker")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"JobStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"JobCreationDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"JobCompletionDate")
            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
"EntityDetailsList"
                            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 a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member"
                        )
      )

instance
  Prelude.Hashable
    GetServiceLastAccessedDetailsWithEntities
  where
  hashWithSalt :: Int -> GetServiceLastAccessedDetailsWithEntities -> Int
hashWithSalt
    Int
_salt
    GetServiceLastAccessedDetailsWithEntities' {Maybe Natural
Maybe Text
Text
serviceNamespace :: Text
jobId :: Text
maxItems :: Maybe Natural
marker :: Maybe Text
$sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Natural
$sel:marker:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxItems
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceNamespace

instance
  Prelude.NFData
    GetServiceLastAccessedDetailsWithEntities
  where
  rnf :: GetServiceLastAccessedDetailsWithEntities -> ()
rnf GetServiceLastAccessedDetailsWithEntities' {Maybe Natural
Maybe Text
Text
serviceNamespace :: Text
jobId :: Text
maxItems :: Maybe Natural
marker :: Maybe Text
$sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Natural
$sel:marker:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceNamespace

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

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

instance
  Data.ToQuery
    GetServiceLastAccessedDetailsWithEntities
  where
  toQuery :: GetServiceLastAccessedDetailsWithEntities -> QueryString
toQuery
    GetServiceLastAccessedDetailsWithEntities' {Maybe Natural
Maybe Text
Text
serviceNamespace :: Text
jobId :: Text
maxItems :: Maybe Natural
marker :: Maybe Text
$sel:serviceNamespace:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:jobId:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Text
$sel:maxItems:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Natural
$sel:marker:GetServiceLastAccessedDetailsWithEntities' :: GetServiceLastAccessedDetailsWithEntities -> Maybe Text
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"Action"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"GetServiceLastAccessedDetailsWithEntities" ::
                        Prelude.ByteString
                    ),
          ByteString
"Version"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
          ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
          ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxItems,
          ByteString
"JobId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
jobId,
          ByteString
"ServiceNamespace" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
serviceNamespace
        ]

-- | /See:/ 'newGetServiceLastAccessedDetailsWithEntitiesResponse' smart constructor.
data GetServiceLastAccessedDetailsWithEntitiesResponse = GetServiceLastAccessedDetailsWithEntitiesResponse'
  { -- | An object that contains details about the reason the operation failed.
    GetServiceLastAccessedDetailsWithEntitiesResponse
-> Maybe ErrorDetails
error :: Prelude.Maybe ErrorDetails,
    -- | A flag that indicates whether there are more items to return. If your
    -- results were truncated, you can make a subsequent pagination request
    -- using the @Marker@ request parameter to retrieve more items. Note that
    -- IAM might return fewer than the @MaxItems@ number of results even when
    -- there are more results available. We recommend that you check
    -- @IsTruncated@ after every call to ensure that you receive all your
    -- results.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Bool
isTruncated :: Prelude.Maybe Prelude.Bool,
    -- | When @IsTruncated@ is @true@, this element is present and contains the
    -- value to use for the @Marker@ parameter in a subsequent pagination
    -- request.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> Int
httpStatus :: Prelude.Int,
    -- | The status of the job.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> JobStatusType
jobStatus :: JobStatusType,
    -- | The date and time,
    -- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
    -- report job was created.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
jobCreationDate :: Data.ISO8601,
    -- | The date and time,
    -- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
    -- generated report job was completed or failed.
    --
    -- This field is null if the job is still in progress, as indicated by a
    -- job status value of @IN_PROGRESS@.
    GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
jobCompletionDate :: Data.ISO8601,
    -- | An @EntityDetailsList@ object that contains details about when an IAM
    -- entity (user or role) used group or policy permissions in an attempt to
    -- access the specified Amazon Web Services service.
    GetServiceLastAccessedDetailsWithEntitiesResponse
-> [EntityDetails]
entityDetailsList :: [EntityDetails]
  }
  deriving (GetServiceLastAccessedDetailsWithEntitiesResponse
-> GetServiceLastAccessedDetailsWithEntitiesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> GetServiceLastAccessedDetailsWithEntitiesResponse -> Bool
$c/= :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> GetServiceLastAccessedDetailsWithEntitiesResponse -> Bool
== :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> GetServiceLastAccessedDetailsWithEntitiesResponse -> Bool
$c== :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> GetServiceLastAccessedDetailsWithEntitiesResponse -> Bool
Prelude.Eq, ReadPrec [GetServiceLastAccessedDetailsWithEntitiesResponse]
ReadPrec GetServiceLastAccessedDetailsWithEntitiesResponse
Int -> ReadS GetServiceLastAccessedDetailsWithEntitiesResponse
ReadS [GetServiceLastAccessedDetailsWithEntitiesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceLastAccessedDetailsWithEntitiesResponse]
$creadListPrec :: ReadPrec [GetServiceLastAccessedDetailsWithEntitiesResponse]
readPrec :: ReadPrec GetServiceLastAccessedDetailsWithEntitiesResponse
$creadPrec :: ReadPrec GetServiceLastAccessedDetailsWithEntitiesResponse
readList :: ReadS [GetServiceLastAccessedDetailsWithEntitiesResponse]
$creadList :: ReadS [GetServiceLastAccessedDetailsWithEntitiesResponse]
readsPrec :: Int -> ReadS GetServiceLastAccessedDetailsWithEntitiesResponse
$creadsPrec :: Int -> ReadS GetServiceLastAccessedDetailsWithEntitiesResponse
Prelude.Read, Int -> GetServiceLastAccessedDetailsWithEntitiesResponse -> ShowS
[GetServiceLastAccessedDetailsWithEntitiesResponse] -> ShowS
GetServiceLastAccessedDetailsWithEntitiesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceLastAccessedDetailsWithEntitiesResponse] -> ShowS
$cshowList :: [GetServiceLastAccessedDetailsWithEntitiesResponse] -> ShowS
show :: GetServiceLastAccessedDetailsWithEntitiesResponse -> String
$cshow :: GetServiceLastAccessedDetailsWithEntitiesResponse -> String
showsPrec :: Int -> GetServiceLastAccessedDetailsWithEntitiesResponse -> ShowS
$cshowsPrec :: Int -> GetServiceLastAccessedDetailsWithEntitiesResponse -> ShowS
Prelude.Show, forall x.
Rep GetServiceLastAccessedDetailsWithEntitiesResponse x
-> GetServiceLastAccessedDetailsWithEntitiesResponse
forall x.
GetServiceLastAccessedDetailsWithEntitiesResponse
-> Rep GetServiceLastAccessedDetailsWithEntitiesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetServiceLastAccessedDetailsWithEntitiesResponse x
-> GetServiceLastAccessedDetailsWithEntitiesResponse
$cfrom :: forall x.
GetServiceLastAccessedDetailsWithEntitiesResponse
-> Rep GetServiceLastAccessedDetailsWithEntitiesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceLastAccessedDetailsWithEntitiesResponse' 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:
--
-- 'error', 'getServiceLastAccessedDetailsWithEntitiesResponse_error' - An object that contains details about the reason the operation failed.
--
-- 'isTruncated', 'getServiceLastAccessedDetailsWithEntitiesResponse_isTruncated' - A flag that indicates whether there are more items to return. If your
-- results were truncated, you can make a subsequent pagination request
-- using the @Marker@ request parameter to retrieve more items. Note that
-- IAM might return fewer than the @MaxItems@ number of results even when
-- there are more results available. We recommend that you check
-- @IsTruncated@ after every call to ensure that you receive all your
-- results.
--
-- 'marker', 'getServiceLastAccessedDetailsWithEntitiesResponse_marker' - When @IsTruncated@ is @true@, this element is present and contains the
-- value to use for the @Marker@ parameter in a subsequent pagination
-- request.
--
-- 'httpStatus', 'getServiceLastAccessedDetailsWithEntitiesResponse_httpStatus' - The response's http status code.
--
-- 'jobStatus', 'getServiceLastAccessedDetailsWithEntitiesResponse_jobStatus' - The status of the job.
--
-- 'jobCreationDate', 'getServiceLastAccessedDetailsWithEntitiesResponse_jobCreationDate' - The date and time,
-- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- report job was created.
--
-- 'jobCompletionDate', 'getServiceLastAccessedDetailsWithEntitiesResponse_jobCompletionDate' - The date and time,
-- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- generated report job was completed or failed.
--
-- This field is null if the job is still in progress, as indicated by a
-- job status value of @IN_PROGRESS@.
--
-- 'entityDetailsList', 'getServiceLastAccessedDetailsWithEntitiesResponse_entityDetailsList' - An @EntityDetailsList@ object that contains details about when an IAM
-- entity (user or role) used group or policy permissions in an attempt to
-- access the specified Amazon Web Services service.
newGetServiceLastAccessedDetailsWithEntitiesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'jobStatus'
  JobStatusType ->
  -- | 'jobCreationDate'
  Prelude.UTCTime ->
  -- | 'jobCompletionDate'
  Prelude.UTCTime ->
  GetServiceLastAccessedDetailsWithEntitiesResponse
newGetServiceLastAccessedDetailsWithEntitiesResponse :: Int
-> JobStatusType
-> UTCTime
-> UTCTime
-> GetServiceLastAccessedDetailsWithEntitiesResponse
newGetServiceLastAccessedDetailsWithEntitiesResponse
  Int
pHttpStatus_
  JobStatusType
pJobStatus_
  UTCTime
pJobCreationDate_
  UTCTime
pJobCompletionDate_ =
    GetServiceLastAccessedDetailsWithEntitiesResponse'
      { $sel:error:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe ErrorDetails
error =
          forall a. Maybe a
Prelude.Nothing,
        $sel:isTruncated:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe Bool
isTruncated =
          forall a. Maybe a
Prelude.Nothing,
        $sel:marker:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:jobStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: JobStatusType
jobStatus = JobStatusType
pJobStatus_,
        $sel:jobCreationDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: ISO8601
jobCreationDate =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
            forall t b. AReview t b -> b -> t
Lens.# UTCTime
pJobCreationDate_,
        $sel:jobCompletionDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: ISO8601
jobCompletionDate =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
            forall t b. AReview t b -> b -> t
Lens.# UTCTime
pJobCompletionDate_,
        $sel:entityDetailsList:GetServiceLastAccessedDetailsWithEntitiesResponse' :: [EntityDetails]
entityDetailsList =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | An object that contains details about the reason the operation failed.
getServiceLastAccessedDetailsWithEntitiesResponse_error :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse (Prelude.Maybe ErrorDetails)
getServiceLastAccessedDetailsWithEntitiesResponse_error :: Lens'
  GetServiceLastAccessedDetailsWithEntitiesResponse
  (Maybe ErrorDetails)
getServiceLastAccessedDetailsWithEntitiesResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {Maybe ErrorDetails
error :: Maybe ErrorDetails
$sel:error:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> Maybe ErrorDetails
error} -> Maybe ErrorDetails
error) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} Maybe ErrorDetails
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:error:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe ErrorDetails
error = Maybe ErrorDetails
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse)

-- | A flag that indicates whether there are more items to return. If your
-- results were truncated, you can make a subsequent pagination request
-- using the @Marker@ request parameter to retrieve more items. Note that
-- IAM might return fewer than the @MaxItems@ number of results even when
-- there are more results available. We recommend that you check
-- @IsTruncated@ after every call to ensure that you receive all your
-- results.
getServiceLastAccessedDetailsWithEntitiesResponse_isTruncated :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse (Prelude.Maybe Prelude.Bool)
getServiceLastAccessedDetailsWithEntitiesResponse_isTruncated :: Lens'
  GetServiceLastAccessedDetailsWithEntitiesResponse (Maybe Bool)
getServiceLastAccessedDetailsWithEntitiesResponse_isTruncated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {Maybe Bool
isTruncated :: Maybe Bool
$sel:isTruncated:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Bool
isTruncated} -> Maybe Bool
isTruncated) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} Maybe Bool
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:isTruncated:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe Bool
isTruncated = Maybe Bool
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse)

-- | When @IsTruncated@ is @true@, this element is present and contains the
-- value to use for the @Marker@ parameter in a subsequent pagination
-- request.
getServiceLastAccessedDetailsWithEntitiesResponse_marker :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse (Prelude.Maybe Prelude.Text)
getServiceLastAccessedDetailsWithEntitiesResponse_marker :: Lens'
  GetServiceLastAccessedDetailsWithEntitiesResponse (Maybe Text)
getServiceLastAccessedDetailsWithEntitiesResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} Maybe Text
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:marker:GetServiceLastAccessedDetailsWithEntitiesResponse' :: Maybe Text
marker = Maybe Text
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse)

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

-- | The status of the job.
getServiceLastAccessedDetailsWithEntitiesResponse_jobStatus :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse JobStatusType
getServiceLastAccessedDetailsWithEntitiesResponse_jobStatus :: Lens'
  GetServiceLastAccessedDetailsWithEntitiesResponse JobStatusType
getServiceLastAccessedDetailsWithEntitiesResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {JobStatusType
jobStatus :: JobStatusType
$sel:jobStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> JobStatusType
jobStatus} -> JobStatusType
jobStatus) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} JobStatusType
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:jobStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: JobStatusType
jobStatus = JobStatusType
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse)

-- | The date and time,
-- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- report job was created.
getServiceLastAccessedDetailsWithEntitiesResponse_jobCreationDate :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse Prelude.UTCTime
getServiceLastAccessedDetailsWithEntitiesResponse_jobCreationDate :: Lens' GetServiceLastAccessedDetailsWithEntitiesResponse UTCTime
getServiceLastAccessedDetailsWithEntitiesResponse_jobCreationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {ISO8601
jobCreationDate :: ISO8601
$sel:jobCreationDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
jobCreationDate} -> ISO8601
jobCreationDate) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} ISO8601
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:jobCreationDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: ISO8601
jobCreationDate = ISO8601
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date and time,
-- in <http://www.iso.org/iso/iso8601 ISO 8601 date-time format>, when the
-- generated report job was completed or failed.
--
-- This field is null if the job is still in progress, as indicated by a
-- job status value of @IN_PROGRESS@.
getServiceLastAccessedDetailsWithEntitiesResponse_jobCompletionDate :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse Prelude.UTCTime
getServiceLastAccessedDetailsWithEntitiesResponse_jobCompletionDate :: Lens' GetServiceLastAccessedDetailsWithEntitiesResponse UTCTime
getServiceLastAccessedDetailsWithEntitiesResponse_jobCompletionDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {ISO8601
jobCompletionDate :: ISO8601
$sel:jobCompletionDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
jobCompletionDate} -> ISO8601
jobCompletionDate) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} ISO8601
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:jobCompletionDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: ISO8601
jobCompletionDate = ISO8601
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | An @EntityDetailsList@ object that contains details about when an IAM
-- entity (user or role) used group or policy permissions in an attempt to
-- access the specified Amazon Web Services service.
getServiceLastAccessedDetailsWithEntitiesResponse_entityDetailsList :: Lens.Lens' GetServiceLastAccessedDetailsWithEntitiesResponse [EntityDetails]
getServiceLastAccessedDetailsWithEntitiesResponse_entityDetailsList :: Lens'
  GetServiceLastAccessedDetailsWithEntitiesResponse [EntityDetails]
getServiceLastAccessedDetailsWithEntitiesResponse_entityDetailsList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceLastAccessedDetailsWithEntitiesResponse' {[EntityDetails]
entityDetailsList :: [EntityDetails]
$sel:entityDetailsList:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> [EntityDetails]
entityDetailsList} -> [EntityDetails]
entityDetailsList) (\s :: GetServiceLastAccessedDetailsWithEntitiesResponse
s@GetServiceLastAccessedDetailsWithEntitiesResponse' {} [EntityDetails]
a -> GetServiceLastAccessedDetailsWithEntitiesResponse
s {$sel:entityDetailsList:GetServiceLastAccessedDetailsWithEntitiesResponse' :: [EntityDetails]
entityDetailsList = [EntityDetails]
a} :: GetServiceLastAccessedDetailsWithEntitiesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    GetServiceLastAccessedDetailsWithEntitiesResponse
  where
  rnf :: GetServiceLastAccessedDetailsWithEntitiesResponse -> ()
rnf
    GetServiceLastAccessedDetailsWithEntitiesResponse' {Int
[EntityDetails]
Maybe Bool
Maybe Text
Maybe ErrorDetails
ISO8601
JobStatusType
entityDetailsList :: [EntityDetails]
jobCompletionDate :: ISO8601
jobCreationDate :: ISO8601
jobStatus :: JobStatusType
httpStatus :: Int
marker :: Maybe Text
isTruncated :: Maybe Bool
error :: Maybe ErrorDetails
$sel:entityDetailsList:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> [EntityDetails]
$sel:jobCompletionDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
$sel:jobCreationDate:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> ISO8601
$sel:jobStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> JobStatusType
$sel:httpStatus:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> Int
$sel:marker:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Text
$sel:isTruncated:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse -> Maybe Bool
$sel:error:GetServiceLastAccessedDetailsWithEntitiesResponse' :: GetServiceLastAccessedDetailsWithEntitiesResponse
-> Maybe ErrorDetails
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorDetails
error
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isTruncated
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JobStatusType
jobStatus
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
jobCreationDate
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
jobCompletionDate
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [EntityDetails]
entityDetailsList