{-# 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.Backup.ListRestoreJobs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of jobs that Backup initiated to restore a saved
-- resource, including details about the recovery process.
--
-- This operation returns paginated results.
module Amazonka.Backup.ListRestoreJobs
  ( -- * Creating a Request
    ListRestoreJobs (..),
    newListRestoreJobs,

    -- * Request Lenses
    listRestoreJobs_byAccountId,
    listRestoreJobs_byCompleteAfter,
    listRestoreJobs_byCompleteBefore,
    listRestoreJobs_byCreatedAfter,
    listRestoreJobs_byCreatedBefore,
    listRestoreJobs_byStatus,
    listRestoreJobs_maxResults,
    listRestoreJobs_nextToken,

    -- * Destructuring the Response
    ListRestoreJobsResponse (..),
    newListRestoreJobsResponse,

    -- * Response Lenses
    listRestoreJobsResponse_nextToken,
    listRestoreJobsResponse_restoreJobs,
    listRestoreJobsResponse_httpStatus,
  )
where

import Amazonka.Backup.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
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:/ 'newListRestoreJobs' smart constructor.
data ListRestoreJobs = ListRestoreJobs'
  { -- | The account ID to list the jobs from. Returns only restore jobs
    -- associated with the specified account ID.
    ListRestoreJobs -> Maybe Text
byAccountId :: Prelude.Maybe Prelude.Text,
    -- | Returns only copy jobs completed after a date expressed in Unix format
    -- and Coordinated Universal Time (UTC).
    ListRestoreJobs -> Maybe POSIX
byCompleteAfter :: Prelude.Maybe Data.POSIX,
    -- | Returns only copy jobs completed before a date expressed in Unix format
    -- and Coordinated Universal Time (UTC).
    ListRestoreJobs -> Maybe POSIX
byCompleteBefore :: Prelude.Maybe Data.POSIX,
    -- | Returns only restore jobs that were created after the specified date.
    ListRestoreJobs -> Maybe POSIX
byCreatedAfter :: Prelude.Maybe Data.POSIX,
    -- | Returns only restore jobs that were created before the specified date.
    ListRestoreJobs -> Maybe POSIX
byCreatedBefore :: Prelude.Maybe Data.POSIX,
    -- | Returns only restore jobs associated with the specified job status.
    ListRestoreJobs -> Maybe RestoreJobStatus
byStatus :: Prelude.Maybe RestoreJobStatus,
    -- | The maximum number of items to be returned.
    ListRestoreJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The next item following a partial list of returned items. For example,
    -- if a request is made to return @maxResults@ number of items, @NextToken@
    -- allows you to return more items in your list starting at the location
    -- pointed to by the next token.
    ListRestoreJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListRestoreJobs -> ListRestoreJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRestoreJobs -> ListRestoreJobs -> Bool
$c/= :: ListRestoreJobs -> ListRestoreJobs -> Bool
== :: ListRestoreJobs -> ListRestoreJobs -> Bool
$c== :: ListRestoreJobs -> ListRestoreJobs -> Bool
Prelude.Eq, ReadPrec [ListRestoreJobs]
ReadPrec ListRestoreJobs
Int -> ReadS ListRestoreJobs
ReadS [ListRestoreJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRestoreJobs]
$creadListPrec :: ReadPrec [ListRestoreJobs]
readPrec :: ReadPrec ListRestoreJobs
$creadPrec :: ReadPrec ListRestoreJobs
readList :: ReadS [ListRestoreJobs]
$creadList :: ReadS [ListRestoreJobs]
readsPrec :: Int -> ReadS ListRestoreJobs
$creadsPrec :: Int -> ReadS ListRestoreJobs
Prelude.Read, Int -> ListRestoreJobs -> ShowS
[ListRestoreJobs] -> ShowS
ListRestoreJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRestoreJobs] -> ShowS
$cshowList :: [ListRestoreJobs] -> ShowS
show :: ListRestoreJobs -> String
$cshow :: ListRestoreJobs -> String
showsPrec :: Int -> ListRestoreJobs -> ShowS
$cshowsPrec :: Int -> ListRestoreJobs -> ShowS
Prelude.Show, forall x. Rep ListRestoreJobs x -> ListRestoreJobs
forall x. ListRestoreJobs -> Rep ListRestoreJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRestoreJobs x -> ListRestoreJobs
$cfrom :: forall x. ListRestoreJobs -> Rep ListRestoreJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListRestoreJobs' 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:
--
-- 'byAccountId', 'listRestoreJobs_byAccountId' - The account ID to list the jobs from. Returns only restore jobs
-- associated with the specified account ID.
--
-- 'byCompleteAfter', 'listRestoreJobs_byCompleteAfter' - Returns only copy jobs completed after a date expressed in Unix format
-- and Coordinated Universal Time (UTC).
--
-- 'byCompleteBefore', 'listRestoreJobs_byCompleteBefore' - Returns only copy jobs completed before a date expressed in Unix format
-- and Coordinated Universal Time (UTC).
--
-- 'byCreatedAfter', 'listRestoreJobs_byCreatedAfter' - Returns only restore jobs that were created after the specified date.
--
-- 'byCreatedBefore', 'listRestoreJobs_byCreatedBefore' - Returns only restore jobs that were created before the specified date.
--
-- 'byStatus', 'listRestoreJobs_byStatus' - Returns only restore jobs associated with the specified job status.
--
-- 'maxResults', 'listRestoreJobs_maxResults' - The maximum number of items to be returned.
--
-- 'nextToken', 'listRestoreJobs_nextToken' - The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
newListRestoreJobs ::
  ListRestoreJobs
newListRestoreJobs :: ListRestoreJobs
newListRestoreJobs =
  ListRestoreJobs'
    { $sel:byAccountId:ListRestoreJobs' :: Maybe Text
byAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:byCompleteAfter:ListRestoreJobs' :: Maybe POSIX
byCompleteAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:byCompleteBefore:ListRestoreJobs' :: Maybe POSIX
byCompleteBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:byCreatedAfter:ListRestoreJobs' :: Maybe POSIX
byCreatedAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:byCreatedBefore:ListRestoreJobs' :: Maybe POSIX
byCreatedBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:byStatus:ListRestoreJobs' :: Maybe RestoreJobStatus
byStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListRestoreJobs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListRestoreJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The account ID to list the jobs from. Returns only restore jobs
-- associated with the specified account ID.
listRestoreJobs_byAccountId :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.Text)
listRestoreJobs_byAccountId :: Lens' ListRestoreJobs (Maybe Text)
listRestoreJobs_byAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe Text
byAccountId :: Maybe Text
$sel:byAccountId:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
byAccountId} -> Maybe Text
byAccountId) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe Text
a -> ListRestoreJobs
s {$sel:byAccountId:ListRestoreJobs' :: Maybe Text
byAccountId = Maybe Text
a} :: ListRestoreJobs)

-- | Returns only copy jobs completed after a date expressed in Unix format
-- and Coordinated Universal Time (UTC).
listRestoreJobs_byCompleteAfter :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.UTCTime)
listRestoreJobs_byCompleteAfter :: Lens' ListRestoreJobs (Maybe UTCTime)
listRestoreJobs_byCompleteAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe POSIX
byCompleteAfter :: Maybe POSIX
$sel:byCompleteAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
byCompleteAfter} -> Maybe POSIX
byCompleteAfter) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe POSIX
a -> ListRestoreJobs
s {$sel:byCompleteAfter:ListRestoreJobs' :: Maybe POSIX
byCompleteAfter = Maybe POSIX
a} :: ListRestoreJobs) 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

-- | Returns only copy jobs completed before a date expressed in Unix format
-- and Coordinated Universal Time (UTC).
listRestoreJobs_byCompleteBefore :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.UTCTime)
listRestoreJobs_byCompleteBefore :: Lens' ListRestoreJobs (Maybe UTCTime)
listRestoreJobs_byCompleteBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe POSIX
byCompleteBefore :: Maybe POSIX
$sel:byCompleteBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
byCompleteBefore} -> Maybe POSIX
byCompleteBefore) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe POSIX
a -> ListRestoreJobs
s {$sel:byCompleteBefore:ListRestoreJobs' :: Maybe POSIX
byCompleteBefore = Maybe POSIX
a} :: ListRestoreJobs) 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

-- | Returns only restore jobs that were created after the specified date.
listRestoreJobs_byCreatedAfter :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.UTCTime)
listRestoreJobs_byCreatedAfter :: Lens' ListRestoreJobs (Maybe UTCTime)
listRestoreJobs_byCreatedAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe POSIX
byCreatedAfter :: Maybe POSIX
$sel:byCreatedAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
byCreatedAfter} -> Maybe POSIX
byCreatedAfter) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe POSIX
a -> ListRestoreJobs
s {$sel:byCreatedAfter:ListRestoreJobs' :: Maybe POSIX
byCreatedAfter = Maybe POSIX
a} :: ListRestoreJobs) 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

-- | Returns only restore jobs that were created before the specified date.
listRestoreJobs_byCreatedBefore :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.UTCTime)
listRestoreJobs_byCreatedBefore :: Lens' ListRestoreJobs (Maybe UTCTime)
listRestoreJobs_byCreatedBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe POSIX
byCreatedBefore :: Maybe POSIX
$sel:byCreatedBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
byCreatedBefore} -> Maybe POSIX
byCreatedBefore) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe POSIX
a -> ListRestoreJobs
s {$sel:byCreatedBefore:ListRestoreJobs' :: Maybe POSIX
byCreatedBefore = Maybe POSIX
a} :: ListRestoreJobs) 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

-- | Returns only restore jobs associated with the specified job status.
listRestoreJobs_byStatus :: Lens.Lens' ListRestoreJobs (Prelude.Maybe RestoreJobStatus)
listRestoreJobs_byStatus :: Lens' ListRestoreJobs (Maybe RestoreJobStatus)
listRestoreJobs_byStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe RestoreJobStatus
byStatus :: Maybe RestoreJobStatus
$sel:byStatus:ListRestoreJobs' :: ListRestoreJobs -> Maybe RestoreJobStatus
byStatus} -> Maybe RestoreJobStatus
byStatus) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe RestoreJobStatus
a -> ListRestoreJobs
s {$sel:byStatus:ListRestoreJobs' :: Maybe RestoreJobStatus
byStatus = Maybe RestoreJobStatus
a} :: ListRestoreJobs)

-- | The maximum number of items to be returned.
listRestoreJobs_maxResults :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.Natural)
listRestoreJobs_maxResults :: Lens' ListRestoreJobs (Maybe Natural)
listRestoreJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListRestoreJobs' :: ListRestoreJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe Natural
a -> ListRestoreJobs
s {$sel:maxResults:ListRestoreJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListRestoreJobs)

-- | The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
listRestoreJobs_nextToken :: Lens.Lens' ListRestoreJobs (Prelude.Maybe Prelude.Text)
listRestoreJobs_nextToken :: Lens' ListRestoreJobs (Maybe Text)
listRestoreJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRestoreJobs
s@ListRestoreJobs' {} Maybe Text
a -> ListRestoreJobs
s {$sel:nextToken:ListRestoreJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListRestoreJobs)

instance Core.AWSPager ListRestoreJobs where
  page :: ListRestoreJobs
-> AWSResponse ListRestoreJobs -> Maybe ListRestoreJobs
page ListRestoreJobs
rq AWSResponse ListRestoreJobs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListRestoreJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRestoreJobsResponse (Maybe Text)
listRestoreJobsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListRestoreJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRestoreJobsResponse (Maybe [RestoreJobsListMember])
listRestoreJobsResponse_restoreJobs
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListRestoreJobs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListRestoreJobs (Maybe Text)
listRestoreJobs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListRestoreJobs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListRestoreJobsResponse (Maybe Text)
listRestoreJobsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListRestoreJobs where
  type
    AWSResponse ListRestoreJobs =
      ListRestoreJobsResponse
  request :: (Service -> Service) -> ListRestoreJobs -> Request ListRestoreJobs
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 ListRestoreJobs
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListRestoreJobs)))
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 Text
-> Maybe [RestoreJobsListMember] -> Int -> ListRestoreJobsResponse
ListRestoreJobsResponse'
            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
"NextToken")
            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
"RestoreJobs" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListRestoreJobs where
  hashWithSalt :: Int -> ListRestoreJobs -> Int
hashWithSalt Int
_salt ListRestoreJobs' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe RestoreJobStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe RestoreJobStatus
byCreatedBefore :: Maybe POSIX
byCreatedAfter :: Maybe POSIX
byCompleteBefore :: Maybe POSIX
byCompleteAfter :: Maybe POSIX
byAccountId :: Maybe Text
$sel:nextToken:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
$sel:maxResults:ListRestoreJobs' :: ListRestoreJobs -> Maybe Natural
$sel:byStatus:ListRestoreJobs' :: ListRestoreJobs -> Maybe RestoreJobStatus
$sel:byCreatedBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCreatedAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byAccountId:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
byAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCompleteAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCompleteBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCreatedAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCreatedBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RestoreJobStatus
byStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListRestoreJobs where
  rnf :: ListRestoreJobs -> ()
rnf ListRestoreJobs' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe RestoreJobStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe RestoreJobStatus
byCreatedBefore :: Maybe POSIX
byCreatedAfter :: Maybe POSIX
byCompleteBefore :: Maybe POSIX
byCompleteAfter :: Maybe POSIX
byAccountId :: Maybe Text
$sel:nextToken:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
$sel:maxResults:ListRestoreJobs' :: ListRestoreJobs -> Maybe Natural
$sel:byStatus:ListRestoreJobs' :: ListRestoreJobs -> Maybe RestoreJobStatus
$sel:byCreatedBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCreatedAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byAccountId:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
byAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCompleteAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCompleteBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCreatedAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCreatedBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RestoreJobStatus
byStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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

instance Data.ToHeaders ListRestoreJobs where
  toHeaders :: ListRestoreJobs -> 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 ListRestoreJobs where
  toPath :: ListRestoreJobs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/restore-jobs/"

instance Data.ToQuery ListRestoreJobs where
  toQuery :: ListRestoreJobs -> QueryString
toQuery ListRestoreJobs' {Maybe Natural
Maybe Text
Maybe POSIX
Maybe RestoreJobStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe RestoreJobStatus
byCreatedBefore :: Maybe POSIX
byCreatedAfter :: Maybe POSIX
byCompleteBefore :: Maybe POSIX
byCompleteAfter :: Maybe POSIX
byAccountId :: Maybe Text
$sel:nextToken:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
$sel:maxResults:ListRestoreJobs' :: ListRestoreJobs -> Maybe Natural
$sel:byStatus:ListRestoreJobs' :: ListRestoreJobs -> Maybe RestoreJobStatus
$sel:byCreatedBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCreatedAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteBefore:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byCompleteAfter:ListRestoreJobs' :: ListRestoreJobs -> Maybe POSIX
$sel:byAccountId:ListRestoreJobs' :: ListRestoreJobs -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"accountId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
byAccountId,
        ByteString
"completeAfter" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCompleteAfter,
        ByteString
"completeBefore" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCompleteBefore,
        ByteString
"createdAfter" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCreatedAfter,
        ByteString
"createdBefore" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCreatedBefore,
        ByteString
"status" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe RestoreJobStatus
byStatus,
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListRestoreJobsResponse' smart constructor.
data ListRestoreJobsResponse = ListRestoreJobsResponse'
  { -- | The next item following a partial list of returned items. For example,
    -- if a request is made to return @maxResults@ number of items, @NextToken@
    -- allows you to return more items in your list starting at the location
    -- pointed to by the next token.
    ListRestoreJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that contain detailed information about jobs to
    -- restore saved resources.
    ListRestoreJobsResponse -> Maybe [RestoreJobsListMember]
restoreJobs :: Prelude.Maybe [RestoreJobsListMember],
    -- | The response's http status code.
    ListRestoreJobsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListRestoreJobsResponse -> ListRestoreJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRestoreJobsResponse -> ListRestoreJobsResponse -> Bool
$c/= :: ListRestoreJobsResponse -> ListRestoreJobsResponse -> Bool
== :: ListRestoreJobsResponse -> ListRestoreJobsResponse -> Bool
$c== :: ListRestoreJobsResponse -> ListRestoreJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListRestoreJobsResponse]
ReadPrec ListRestoreJobsResponse
Int -> ReadS ListRestoreJobsResponse
ReadS [ListRestoreJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListRestoreJobsResponse]
$creadListPrec :: ReadPrec [ListRestoreJobsResponse]
readPrec :: ReadPrec ListRestoreJobsResponse
$creadPrec :: ReadPrec ListRestoreJobsResponse
readList :: ReadS [ListRestoreJobsResponse]
$creadList :: ReadS [ListRestoreJobsResponse]
readsPrec :: Int -> ReadS ListRestoreJobsResponse
$creadsPrec :: Int -> ReadS ListRestoreJobsResponse
Prelude.Read, Int -> ListRestoreJobsResponse -> ShowS
[ListRestoreJobsResponse] -> ShowS
ListRestoreJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRestoreJobsResponse] -> ShowS
$cshowList :: [ListRestoreJobsResponse] -> ShowS
show :: ListRestoreJobsResponse -> String
$cshow :: ListRestoreJobsResponse -> String
showsPrec :: Int -> ListRestoreJobsResponse -> ShowS
$cshowsPrec :: Int -> ListRestoreJobsResponse -> ShowS
Prelude.Show, forall x. Rep ListRestoreJobsResponse x -> ListRestoreJobsResponse
forall x. ListRestoreJobsResponse -> Rep ListRestoreJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListRestoreJobsResponse x -> ListRestoreJobsResponse
$cfrom :: forall x. ListRestoreJobsResponse -> Rep ListRestoreJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListRestoreJobsResponse' 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:
--
-- 'nextToken', 'listRestoreJobsResponse_nextToken' - The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
--
-- 'restoreJobs', 'listRestoreJobsResponse_restoreJobs' - An array of objects that contain detailed information about jobs to
-- restore saved resources.
--
-- 'httpStatus', 'listRestoreJobsResponse_httpStatus' - The response's http status code.
newListRestoreJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListRestoreJobsResponse
newListRestoreJobsResponse :: Int -> ListRestoreJobsResponse
newListRestoreJobsResponse Int
pHttpStatus_ =
  ListRestoreJobsResponse'
    { $sel:nextToken:ListRestoreJobsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:restoreJobs:ListRestoreJobsResponse' :: Maybe [RestoreJobsListMember]
restoreJobs = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListRestoreJobsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The next item following a partial list of returned items. For example,
-- if a request is made to return @maxResults@ number of items, @NextToken@
-- allows you to return more items in your list starting at the location
-- pointed to by the next token.
listRestoreJobsResponse_nextToken :: Lens.Lens' ListRestoreJobsResponse (Prelude.Maybe Prelude.Text)
listRestoreJobsResponse_nextToken :: Lens' ListRestoreJobsResponse (Maybe Text)
listRestoreJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListRestoreJobsResponse' :: ListRestoreJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListRestoreJobsResponse
s@ListRestoreJobsResponse' {} Maybe Text
a -> ListRestoreJobsResponse
s {$sel:nextToken:ListRestoreJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListRestoreJobsResponse)

-- | An array of objects that contain detailed information about jobs to
-- restore saved resources.
listRestoreJobsResponse_restoreJobs :: Lens.Lens' ListRestoreJobsResponse (Prelude.Maybe [RestoreJobsListMember])
listRestoreJobsResponse_restoreJobs :: Lens' ListRestoreJobsResponse (Maybe [RestoreJobsListMember])
listRestoreJobsResponse_restoreJobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListRestoreJobsResponse' {Maybe [RestoreJobsListMember]
restoreJobs :: Maybe [RestoreJobsListMember]
$sel:restoreJobs:ListRestoreJobsResponse' :: ListRestoreJobsResponse -> Maybe [RestoreJobsListMember]
restoreJobs} -> Maybe [RestoreJobsListMember]
restoreJobs) (\s :: ListRestoreJobsResponse
s@ListRestoreJobsResponse' {} Maybe [RestoreJobsListMember]
a -> ListRestoreJobsResponse
s {$sel:restoreJobs:ListRestoreJobsResponse' :: Maybe [RestoreJobsListMember]
restoreJobs = Maybe [RestoreJobsListMember]
a} :: ListRestoreJobsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData ListRestoreJobsResponse where
  rnf :: ListRestoreJobsResponse -> ()
rnf ListRestoreJobsResponse' {Int
Maybe [RestoreJobsListMember]
Maybe Text
httpStatus :: Int
restoreJobs :: Maybe [RestoreJobsListMember]
nextToken :: Maybe Text
$sel:httpStatus:ListRestoreJobsResponse' :: ListRestoreJobsResponse -> Int
$sel:restoreJobs:ListRestoreJobsResponse' :: ListRestoreJobsResponse -> Maybe [RestoreJobsListMember]
$sel:nextToken:ListRestoreJobsResponse' :: ListRestoreJobsResponse -> Maybe Text
..} =
    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 Maybe [RestoreJobsListMember]
restoreJobs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus