{-# 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.CustomerProfiles.ListIdentityResolutionJobs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists all of the Identity Resolution Jobs in your domain. The response
-- sorts the list by @JobStartTime@.
module Amazonka.CustomerProfiles.ListIdentityResolutionJobs
  ( -- * Creating a Request
    ListIdentityResolutionJobs (..),
    newListIdentityResolutionJobs,

    -- * Request Lenses
    listIdentityResolutionJobs_maxResults,
    listIdentityResolutionJobs_nextToken,
    listIdentityResolutionJobs_domainName,

    -- * Destructuring the Response
    ListIdentityResolutionJobsResponse (..),
    newListIdentityResolutionJobsResponse,

    -- * Response Lenses
    listIdentityResolutionJobsResponse_identityResolutionJobsList,
    listIdentityResolutionJobsResponse_nextToken,
    listIdentityResolutionJobsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListIdentityResolutionJobs' smart constructor.
data ListIdentityResolutionJobs = ListIdentityResolutionJobs'
  { -- | The maximum number of results to return per page.
    ListIdentityResolutionJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of results. Use the value returned in the
    -- previous response in the next request to retrieve the next set of
    -- results.
    ListIdentityResolutionJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The unique name of the domain.
    ListIdentityResolutionJobs -> Text
domainName :: Prelude.Text
  }
  deriving (ListIdentityResolutionJobs -> ListIdentityResolutionJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIdentityResolutionJobs -> ListIdentityResolutionJobs -> Bool
$c/= :: ListIdentityResolutionJobs -> ListIdentityResolutionJobs -> Bool
== :: ListIdentityResolutionJobs -> ListIdentityResolutionJobs -> Bool
$c== :: ListIdentityResolutionJobs -> ListIdentityResolutionJobs -> Bool
Prelude.Eq, ReadPrec [ListIdentityResolutionJobs]
ReadPrec ListIdentityResolutionJobs
Int -> ReadS ListIdentityResolutionJobs
ReadS [ListIdentityResolutionJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIdentityResolutionJobs]
$creadListPrec :: ReadPrec [ListIdentityResolutionJobs]
readPrec :: ReadPrec ListIdentityResolutionJobs
$creadPrec :: ReadPrec ListIdentityResolutionJobs
readList :: ReadS [ListIdentityResolutionJobs]
$creadList :: ReadS [ListIdentityResolutionJobs]
readsPrec :: Int -> ReadS ListIdentityResolutionJobs
$creadsPrec :: Int -> ReadS ListIdentityResolutionJobs
Prelude.Read, Int -> ListIdentityResolutionJobs -> ShowS
[ListIdentityResolutionJobs] -> ShowS
ListIdentityResolutionJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIdentityResolutionJobs] -> ShowS
$cshowList :: [ListIdentityResolutionJobs] -> ShowS
show :: ListIdentityResolutionJobs -> String
$cshow :: ListIdentityResolutionJobs -> String
showsPrec :: Int -> ListIdentityResolutionJobs -> ShowS
$cshowsPrec :: Int -> ListIdentityResolutionJobs -> ShowS
Prelude.Show, forall x.
Rep ListIdentityResolutionJobs x -> ListIdentityResolutionJobs
forall x.
ListIdentityResolutionJobs -> Rep ListIdentityResolutionJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListIdentityResolutionJobs x -> ListIdentityResolutionJobs
$cfrom :: forall x.
ListIdentityResolutionJobs -> Rep ListIdentityResolutionJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListIdentityResolutionJobs' 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:
--
-- 'maxResults', 'listIdentityResolutionJobs_maxResults' - The maximum number of results to return per page.
--
-- 'nextToken', 'listIdentityResolutionJobs_nextToken' - The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
--
-- 'domainName', 'listIdentityResolutionJobs_domainName' - The unique name of the domain.
newListIdentityResolutionJobs ::
  -- | 'domainName'
  Prelude.Text ->
  ListIdentityResolutionJobs
newListIdentityResolutionJobs :: Text -> ListIdentityResolutionJobs
newListIdentityResolutionJobs Text
pDomainName_ =
  ListIdentityResolutionJobs'
    { $sel:maxResults:ListIdentityResolutionJobs' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIdentityResolutionJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:ListIdentityResolutionJobs' :: Text
domainName = Text
pDomainName_
    }

-- | The maximum number of results to return per page.
listIdentityResolutionJobs_maxResults :: Lens.Lens' ListIdentityResolutionJobs (Prelude.Maybe Prelude.Natural)
listIdentityResolutionJobs_maxResults :: Lens' ListIdentityResolutionJobs (Maybe Natural)
listIdentityResolutionJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityResolutionJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListIdentityResolutionJobs
s@ListIdentityResolutionJobs' {} Maybe Natural
a -> ListIdentityResolutionJobs
s {$sel:maxResults:ListIdentityResolutionJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListIdentityResolutionJobs)

-- | The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
listIdentityResolutionJobs_nextToken :: Lens.Lens' ListIdentityResolutionJobs (Prelude.Maybe Prelude.Text)
listIdentityResolutionJobs_nextToken :: Lens' ListIdentityResolutionJobs (Maybe Text)
listIdentityResolutionJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityResolutionJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIdentityResolutionJobs
s@ListIdentityResolutionJobs' {} Maybe Text
a -> ListIdentityResolutionJobs
s {$sel:nextToken:ListIdentityResolutionJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListIdentityResolutionJobs)

-- | The unique name of the domain.
listIdentityResolutionJobs_domainName :: Lens.Lens' ListIdentityResolutionJobs Prelude.Text
listIdentityResolutionJobs_domainName :: Lens' ListIdentityResolutionJobs Text
listIdentityResolutionJobs_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityResolutionJobs' {Text
domainName :: Text
$sel:domainName:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Text
domainName} -> Text
domainName) (\s :: ListIdentityResolutionJobs
s@ListIdentityResolutionJobs' {} Text
a -> ListIdentityResolutionJobs
s {$sel:domainName:ListIdentityResolutionJobs' :: Text
domainName = Text
a} :: ListIdentityResolutionJobs)

instance Core.AWSRequest ListIdentityResolutionJobs where
  type
    AWSResponse ListIdentityResolutionJobs =
      ListIdentityResolutionJobsResponse
  request :: (Service -> Service)
-> ListIdentityResolutionJobs -> Request ListIdentityResolutionJobs
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListIdentityResolutionJobs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListIdentityResolutionJobs)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [IdentityResolutionJob]
-> Maybe Text -> Int -> ListIdentityResolutionJobsResponse
ListIdentityResolutionJobsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IdentityResolutionJobsList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            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 ListIdentityResolutionJobs where
  hashWithSalt :: Int -> ListIdentityResolutionJobs -> Int
hashWithSalt Int
_salt ListIdentityResolutionJobs' {Maybe Natural
Maybe Text
Text
domainName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:domainName:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Text
$sel:nextToken:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Text
$sel:maxResults:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

instance Prelude.NFData ListIdentityResolutionJobs where
  rnf :: ListIdentityResolutionJobs -> ()
rnf ListIdentityResolutionJobs' {Maybe Natural
Maybe Text
Text
domainName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:domainName:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Text
$sel:nextToken:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Text
$sel:maxResults:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

instance Data.ToHeaders ListIdentityResolutionJobs where
  toHeaders :: ListIdentityResolutionJobs -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath ListIdentityResolutionJobs where
  toPath :: ListIdentityResolutionJobs -> ByteString
toPath ListIdentityResolutionJobs' {Maybe Natural
Maybe Text
Text
domainName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:domainName:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Text
$sel:nextToken:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Text
$sel:maxResults:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/domains/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainName,
        ByteString
"/identity-resolution-jobs"
      ]

instance Data.ToQuery ListIdentityResolutionJobs where
  toQuery :: ListIdentityResolutionJobs -> QueryString
toQuery ListIdentityResolutionJobs' {Maybe Natural
Maybe Text
Text
domainName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:domainName:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Text
$sel:nextToken:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Text
$sel:maxResults:ListIdentityResolutionJobs' :: ListIdentityResolutionJobs -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"max-results" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"next-token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListIdentityResolutionJobsResponse' smart constructor.
data ListIdentityResolutionJobsResponse = ListIdentityResolutionJobsResponse'
  { -- | A list of Identity Resolution Jobs.
    ListIdentityResolutionJobsResponse -> Maybe [IdentityResolutionJob]
identityResolutionJobsList :: Prelude.Maybe [IdentityResolutionJob],
    -- | If there are additional results, this is the token for the next set of
    -- results.
    ListIdentityResolutionJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListIdentityResolutionJobsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListIdentityResolutionJobsResponse
-> ListIdentityResolutionJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIdentityResolutionJobsResponse
-> ListIdentityResolutionJobsResponse -> Bool
$c/= :: ListIdentityResolutionJobsResponse
-> ListIdentityResolutionJobsResponse -> Bool
== :: ListIdentityResolutionJobsResponse
-> ListIdentityResolutionJobsResponse -> Bool
$c== :: ListIdentityResolutionJobsResponse
-> ListIdentityResolutionJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListIdentityResolutionJobsResponse]
ReadPrec ListIdentityResolutionJobsResponse
Int -> ReadS ListIdentityResolutionJobsResponse
ReadS [ListIdentityResolutionJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIdentityResolutionJobsResponse]
$creadListPrec :: ReadPrec [ListIdentityResolutionJobsResponse]
readPrec :: ReadPrec ListIdentityResolutionJobsResponse
$creadPrec :: ReadPrec ListIdentityResolutionJobsResponse
readList :: ReadS [ListIdentityResolutionJobsResponse]
$creadList :: ReadS [ListIdentityResolutionJobsResponse]
readsPrec :: Int -> ReadS ListIdentityResolutionJobsResponse
$creadsPrec :: Int -> ReadS ListIdentityResolutionJobsResponse
Prelude.Read, Int -> ListIdentityResolutionJobsResponse -> ShowS
[ListIdentityResolutionJobsResponse] -> ShowS
ListIdentityResolutionJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIdentityResolutionJobsResponse] -> ShowS
$cshowList :: [ListIdentityResolutionJobsResponse] -> ShowS
show :: ListIdentityResolutionJobsResponse -> String
$cshow :: ListIdentityResolutionJobsResponse -> String
showsPrec :: Int -> ListIdentityResolutionJobsResponse -> ShowS
$cshowsPrec :: Int -> ListIdentityResolutionJobsResponse -> ShowS
Prelude.Show, forall x.
Rep ListIdentityResolutionJobsResponse x
-> ListIdentityResolutionJobsResponse
forall x.
ListIdentityResolutionJobsResponse
-> Rep ListIdentityResolutionJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListIdentityResolutionJobsResponse x
-> ListIdentityResolutionJobsResponse
$cfrom :: forall x.
ListIdentityResolutionJobsResponse
-> Rep ListIdentityResolutionJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListIdentityResolutionJobsResponse' 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:
--
-- 'identityResolutionJobsList', 'listIdentityResolutionJobsResponse_identityResolutionJobsList' - A list of Identity Resolution Jobs.
--
-- 'nextToken', 'listIdentityResolutionJobsResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'httpStatus', 'listIdentityResolutionJobsResponse_httpStatus' - The response's http status code.
newListIdentityResolutionJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListIdentityResolutionJobsResponse
newListIdentityResolutionJobsResponse :: Int -> ListIdentityResolutionJobsResponse
newListIdentityResolutionJobsResponse Int
pHttpStatus_ =
  ListIdentityResolutionJobsResponse'
    { $sel:identityResolutionJobsList:ListIdentityResolutionJobsResponse' :: Maybe [IdentityResolutionJob]
identityResolutionJobsList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIdentityResolutionJobsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListIdentityResolutionJobsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of Identity Resolution Jobs.
listIdentityResolutionJobsResponse_identityResolutionJobsList :: Lens.Lens' ListIdentityResolutionJobsResponse (Prelude.Maybe [IdentityResolutionJob])
listIdentityResolutionJobsResponse_identityResolutionJobsList :: Lens'
  ListIdentityResolutionJobsResponse (Maybe [IdentityResolutionJob])
listIdentityResolutionJobsResponse_identityResolutionJobsList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityResolutionJobsResponse' {Maybe [IdentityResolutionJob]
identityResolutionJobsList :: Maybe [IdentityResolutionJob]
$sel:identityResolutionJobsList:ListIdentityResolutionJobsResponse' :: ListIdentityResolutionJobsResponse -> Maybe [IdentityResolutionJob]
identityResolutionJobsList} -> Maybe [IdentityResolutionJob]
identityResolutionJobsList) (\s :: ListIdentityResolutionJobsResponse
s@ListIdentityResolutionJobsResponse' {} Maybe [IdentityResolutionJob]
a -> ListIdentityResolutionJobsResponse
s {$sel:identityResolutionJobsList:ListIdentityResolutionJobsResponse' :: Maybe [IdentityResolutionJob]
identityResolutionJobsList = Maybe [IdentityResolutionJob]
a} :: ListIdentityResolutionJobsResponse) 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

-- | If there are additional results, this is the token for the next set of
-- results.
listIdentityResolutionJobsResponse_nextToken :: Lens.Lens' ListIdentityResolutionJobsResponse (Prelude.Maybe Prelude.Text)
listIdentityResolutionJobsResponse_nextToken :: Lens' ListIdentityResolutionJobsResponse (Maybe Text)
listIdentityResolutionJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityResolutionJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIdentityResolutionJobsResponse' :: ListIdentityResolutionJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIdentityResolutionJobsResponse
s@ListIdentityResolutionJobsResponse' {} Maybe Text
a -> ListIdentityResolutionJobsResponse
s {$sel:nextToken:ListIdentityResolutionJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListIdentityResolutionJobsResponse)

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

instance
  Prelude.NFData
    ListIdentityResolutionJobsResponse
  where
  rnf :: ListIdentityResolutionJobsResponse -> ()
rnf ListIdentityResolutionJobsResponse' {Int
Maybe [IdentityResolutionJob]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
identityResolutionJobsList :: Maybe [IdentityResolutionJob]
$sel:httpStatus:ListIdentityResolutionJobsResponse' :: ListIdentityResolutionJobsResponse -> Int
$sel:nextToken:ListIdentityResolutionJobsResponse' :: ListIdentityResolutionJobsResponse -> Maybe Text
$sel:identityResolutionJobsList:ListIdentityResolutionJobsResponse' :: ListIdentityResolutionJobsResponse -> Maybe [IdentityResolutionJob]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [IdentityResolutionJob]
identityResolutionJobsList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus