{-# 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.ListReportJobs
-- 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 details about your report jobs.
module Amazonka.Backup.ListReportJobs
  ( -- * Creating a Request
    ListReportJobs (..),
    newListReportJobs,

    -- * Request Lenses
    listReportJobs_byCreationAfter,
    listReportJobs_byCreationBefore,
    listReportJobs_byReportPlanName,
    listReportJobs_byStatus,
    listReportJobs_maxResults,
    listReportJobs_nextToken,

    -- * Destructuring the Response
    ListReportJobsResponse (..),
    newListReportJobsResponse,

    -- * Response Lenses
    listReportJobsResponse_nextToken,
    listReportJobsResponse_reportJobs,
    listReportJobsResponse_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:/ 'newListReportJobs' smart constructor.
data ListReportJobs = ListReportJobs'
  { -- | Returns only report jobs that were created after the date and time
    -- specified in Unix format and Coordinated Universal Time (UTC). For
    -- example, the value 1516925490 represents Friday, January 26, 2018
    -- 12:11:30 AM.
    ListReportJobs -> Maybe POSIX
byCreationAfter :: Prelude.Maybe Data.POSIX,
    -- | Returns only report jobs that were created before the date and time
    -- specified in Unix format and Coordinated Universal Time (UTC). For
    -- example, the value 1516925490 represents Friday, January 26, 2018
    -- 12:11:30 AM.
    ListReportJobs -> Maybe POSIX
byCreationBefore :: Prelude.Maybe Data.POSIX,
    -- | Returns only report jobs with the specified report plan name.
    ListReportJobs -> Maybe Text
byReportPlanName :: Prelude.Maybe Prelude.Text,
    -- | Returns only report jobs that are in the specified status. The statuses
    -- are:
    --
    -- @CREATED | RUNNING | COMPLETED | FAILED@
    ListReportJobs -> Maybe Text
byStatus :: Prelude.Maybe Prelude.Text,
    -- | The number of desired results from 1 to 1000. Optional. If unspecified,
    -- the query will return 1 MB of data.
    ListReportJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | An identifier that was returned from the previous call to this
    -- operation, which can be used to return the next set of items in the
    -- list.
    ListReportJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListReportJobs -> ListReportJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListReportJobs -> ListReportJobs -> Bool
$c/= :: ListReportJobs -> ListReportJobs -> Bool
== :: ListReportJobs -> ListReportJobs -> Bool
$c== :: ListReportJobs -> ListReportJobs -> Bool
Prelude.Eq, ReadPrec [ListReportJobs]
ReadPrec ListReportJobs
Int -> ReadS ListReportJobs
ReadS [ListReportJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListReportJobs]
$creadListPrec :: ReadPrec [ListReportJobs]
readPrec :: ReadPrec ListReportJobs
$creadPrec :: ReadPrec ListReportJobs
readList :: ReadS [ListReportJobs]
$creadList :: ReadS [ListReportJobs]
readsPrec :: Int -> ReadS ListReportJobs
$creadsPrec :: Int -> ReadS ListReportJobs
Prelude.Read, Int -> ListReportJobs -> ShowS
[ListReportJobs] -> ShowS
ListReportJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListReportJobs] -> ShowS
$cshowList :: [ListReportJobs] -> ShowS
show :: ListReportJobs -> String
$cshow :: ListReportJobs -> String
showsPrec :: Int -> ListReportJobs -> ShowS
$cshowsPrec :: Int -> ListReportJobs -> ShowS
Prelude.Show, forall x. Rep ListReportJobs x -> ListReportJobs
forall x. ListReportJobs -> Rep ListReportJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListReportJobs x -> ListReportJobs
$cfrom :: forall x. ListReportJobs -> Rep ListReportJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListReportJobs' 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:
--
-- 'byCreationAfter', 'listReportJobs_byCreationAfter' - Returns only report jobs that were created after the date and time
-- specified in Unix format and Coordinated Universal Time (UTC). For
-- example, the value 1516925490 represents Friday, January 26, 2018
-- 12:11:30 AM.
--
-- 'byCreationBefore', 'listReportJobs_byCreationBefore' - Returns only report jobs that were created before the date and time
-- specified in Unix format and Coordinated Universal Time (UTC). For
-- example, the value 1516925490 represents Friday, January 26, 2018
-- 12:11:30 AM.
--
-- 'byReportPlanName', 'listReportJobs_byReportPlanName' - Returns only report jobs with the specified report plan name.
--
-- 'byStatus', 'listReportJobs_byStatus' - Returns only report jobs that are in the specified status. The statuses
-- are:
--
-- @CREATED | RUNNING | COMPLETED | FAILED@
--
-- 'maxResults', 'listReportJobs_maxResults' - The number of desired results from 1 to 1000. Optional. If unspecified,
-- the query will return 1 MB of data.
--
-- 'nextToken', 'listReportJobs_nextToken' - An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
newListReportJobs ::
  ListReportJobs
newListReportJobs :: ListReportJobs
newListReportJobs =
  ListReportJobs'
    { $sel:byCreationAfter:ListReportJobs' :: Maybe POSIX
byCreationAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:byCreationBefore:ListReportJobs' :: Maybe POSIX
byCreationBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:byReportPlanName:ListReportJobs' :: Maybe Text
byReportPlanName = forall a. Maybe a
Prelude.Nothing,
      $sel:byStatus:ListReportJobs' :: Maybe Text
byStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListReportJobs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListReportJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Returns only report jobs that were created after the date and time
-- specified in Unix format and Coordinated Universal Time (UTC). For
-- example, the value 1516925490 represents Friday, January 26, 2018
-- 12:11:30 AM.
listReportJobs_byCreationAfter :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.UTCTime)
listReportJobs_byCreationAfter :: Lens' ListReportJobs (Maybe UTCTime)
listReportJobs_byCreationAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe POSIX
byCreationAfter :: Maybe POSIX
$sel:byCreationAfter:ListReportJobs' :: ListReportJobs -> Maybe POSIX
byCreationAfter} -> Maybe POSIX
byCreationAfter) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe POSIX
a -> ListReportJobs
s {$sel:byCreationAfter:ListReportJobs' :: Maybe POSIX
byCreationAfter = Maybe POSIX
a} :: ListReportJobs) 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 report jobs that were created before the date and time
-- specified in Unix format and Coordinated Universal Time (UTC). For
-- example, the value 1516925490 represents Friday, January 26, 2018
-- 12:11:30 AM.
listReportJobs_byCreationBefore :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.UTCTime)
listReportJobs_byCreationBefore :: Lens' ListReportJobs (Maybe UTCTime)
listReportJobs_byCreationBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe POSIX
byCreationBefore :: Maybe POSIX
$sel:byCreationBefore:ListReportJobs' :: ListReportJobs -> Maybe POSIX
byCreationBefore} -> Maybe POSIX
byCreationBefore) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe POSIX
a -> ListReportJobs
s {$sel:byCreationBefore:ListReportJobs' :: Maybe POSIX
byCreationBefore = Maybe POSIX
a} :: ListReportJobs) 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 report jobs with the specified report plan name.
listReportJobs_byReportPlanName :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.Text)
listReportJobs_byReportPlanName :: Lens' ListReportJobs (Maybe Text)
listReportJobs_byReportPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe Text
byReportPlanName :: Maybe Text
$sel:byReportPlanName:ListReportJobs' :: ListReportJobs -> Maybe Text
byReportPlanName} -> Maybe Text
byReportPlanName) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe Text
a -> ListReportJobs
s {$sel:byReportPlanName:ListReportJobs' :: Maybe Text
byReportPlanName = Maybe Text
a} :: ListReportJobs)

-- | Returns only report jobs that are in the specified status. The statuses
-- are:
--
-- @CREATED | RUNNING | COMPLETED | FAILED@
listReportJobs_byStatus :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.Text)
listReportJobs_byStatus :: Lens' ListReportJobs (Maybe Text)
listReportJobs_byStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe Text
byStatus :: Maybe Text
$sel:byStatus:ListReportJobs' :: ListReportJobs -> Maybe Text
byStatus} -> Maybe Text
byStatus) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe Text
a -> ListReportJobs
s {$sel:byStatus:ListReportJobs' :: Maybe Text
byStatus = Maybe Text
a} :: ListReportJobs)

-- | The number of desired results from 1 to 1000. Optional. If unspecified,
-- the query will return 1 MB of data.
listReportJobs_maxResults :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.Natural)
listReportJobs_maxResults :: Lens' ListReportJobs (Maybe Natural)
listReportJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListReportJobs' :: ListReportJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe Natural
a -> ListReportJobs
s {$sel:maxResults:ListReportJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListReportJobs)

-- | An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
listReportJobs_nextToken :: Lens.Lens' ListReportJobs (Prelude.Maybe Prelude.Text)
listReportJobs_nextToken :: Lens' ListReportJobs (Maybe Text)
listReportJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListReportJobs' :: ListReportJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListReportJobs
s@ListReportJobs' {} Maybe Text
a -> ListReportJobs
s {$sel:nextToken:ListReportJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListReportJobs)

instance Core.AWSRequest ListReportJobs where
  type
    AWSResponse ListReportJobs =
      ListReportJobsResponse
  request :: (Service -> Service) -> ListReportJobs -> Request ListReportJobs
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 ListReportJobs
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListReportJobs)))
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 [ReportJob] -> Int -> ListReportJobsResponse
ListReportJobsResponse'
            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
"ReportJobs" 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 ListReportJobs where
  hashWithSalt :: Int -> ListReportJobs -> Int
hashWithSalt Int
_salt ListReportJobs' {Maybe Natural
Maybe Text
Maybe POSIX
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe Text
byReportPlanName :: Maybe Text
byCreationBefore :: Maybe POSIX
byCreationAfter :: Maybe POSIX
$sel:nextToken:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:maxResults:ListReportJobs' :: ListReportJobs -> Maybe Natural
$sel:byStatus:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byReportPlanName:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byCreationBefore:ListReportJobs' :: ListReportJobs -> Maybe POSIX
$sel:byCreationAfter:ListReportJobs' :: ListReportJobs -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCreationAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
byCreationBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
byReportPlanName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
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 ListReportJobs where
  rnf :: ListReportJobs -> ()
rnf ListReportJobs' {Maybe Natural
Maybe Text
Maybe POSIX
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe Text
byReportPlanName :: Maybe Text
byCreationBefore :: Maybe POSIX
byCreationAfter :: Maybe POSIX
$sel:nextToken:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:maxResults:ListReportJobs' :: ListReportJobs -> Maybe Natural
$sel:byStatus:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byReportPlanName:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byCreationBefore:ListReportJobs' :: ListReportJobs -> Maybe POSIX
$sel:byCreationAfter:ListReportJobs' :: ListReportJobs -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCreationAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
byCreationBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
byReportPlanName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
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 ListReportJobs where
  toHeaders :: ListReportJobs -> 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 ListReportJobs where
  toPath :: ListReportJobs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/audit/report-jobs"

instance Data.ToQuery ListReportJobs where
  toQuery :: ListReportJobs -> QueryString
toQuery ListReportJobs' {Maybe Natural
Maybe Text
Maybe POSIX
nextToken :: Maybe Text
maxResults :: Maybe Natural
byStatus :: Maybe Text
byReportPlanName :: Maybe Text
byCreationBefore :: Maybe POSIX
byCreationAfter :: Maybe POSIX
$sel:nextToken:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:maxResults:ListReportJobs' :: ListReportJobs -> Maybe Natural
$sel:byStatus:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byReportPlanName:ListReportJobs' :: ListReportJobs -> Maybe Text
$sel:byCreationBefore:ListReportJobs' :: ListReportJobs -> Maybe POSIX
$sel:byCreationAfter:ListReportJobs' :: ListReportJobs -> Maybe POSIX
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"CreationAfter" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCreationAfter,
        ByteString
"CreationBefore" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
byCreationBefore,
        ByteString
"ReportPlanName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
byReportPlanName,
        ByteString
"Status" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
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:/ 'newListReportJobsResponse' smart constructor.
data ListReportJobsResponse = ListReportJobsResponse'
  { -- | An identifier that was returned from the previous call to this
    -- operation, which can be used to return the next set of items in the
    -- list.
    ListReportJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Details about your report jobs in JSON format.
    ListReportJobsResponse -> Maybe [ReportJob]
reportJobs :: Prelude.Maybe [ReportJob],
    -- | The response's http status code.
    ListReportJobsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListReportJobsResponse -> ListReportJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListReportJobsResponse -> ListReportJobsResponse -> Bool
$c/= :: ListReportJobsResponse -> ListReportJobsResponse -> Bool
== :: ListReportJobsResponse -> ListReportJobsResponse -> Bool
$c== :: ListReportJobsResponse -> ListReportJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListReportJobsResponse]
ReadPrec ListReportJobsResponse
Int -> ReadS ListReportJobsResponse
ReadS [ListReportJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListReportJobsResponse]
$creadListPrec :: ReadPrec [ListReportJobsResponse]
readPrec :: ReadPrec ListReportJobsResponse
$creadPrec :: ReadPrec ListReportJobsResponse
readList :: ReadS [ListReportJobsResponse]
$creadList :: ReadS [ListReportJobsResponse]
readsPrec :: Int -> ReadS ListReportJobsResponse
$creadsPrec :: Int -> ReadS ListReportJobsResponse
Prelude.Read, Int -> ListReportJobsResponse -> ShowS
[ListReportJobsResponse] -> ShowS
ListReportJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListReportJobsResponse] -> ShowS
$cshowList :: [ListReportJobsResponse] -> ShowS
show :: ListReportJobsResponse -> String
$cshow :: ListReportJobsResponse -> String
showsPrec :: Int -> ListReportJobsResponse -> ShowS
$cshowsPrec :: Int -> ListReportJobsResponse -> ShowS
Prelude.Show, forall x. Rep ListReportJobsResponse x -> ListReportJobsResponse
forall x. ListReportJobsResponse -> Rep ListReportJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListReportJobsResponse x -> ListReportJobsResponse
$cfrom :: forall x. ListReportJobsResponse -> Rep ListReportJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListReportJobsResponse' 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', 'listReportJobsResponse_nextToken' - An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
--
-- 'reportJobs', 'listReportJobsResponse_reportJobs' - Details about your report jobs in JSON format.
--
-- 'httpStatus', 'listReportJobsResponse_httpStatus' - The response's http status code.
newListReportJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListReportJobsResponse
newListReportJobsResponse :: Int -> ListReportJobsResponse
newListReportJobsResponse Int
pHttpStatus_ =
  ListReportJobsResponse'
    { $sel:nextToken:ListReportJobsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:reportJobs:ListReportJobsResponse' :: Maybe [ReportJob]
reportJobs = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListReportJobsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
listReportJobsResponse_nextToken :: Lens.Lens' ListReportJobsResponse (Prelude.Maybe Prelude.Text)
listReportJobsResponse_nextToken :: Lens' ListReportJobsResponse (Maybe Text)
listReportJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListReportJobsResponse' :: ListReportJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListReportJobsResponse
s@ListReportJobsResponse' {} Maybe Text
a -> ListReportJobsResponse
s {$sel:nextToken:ListReportJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListReportJobsResponse)

-- | Details about your report jobs in JSON format.
listReportJobsResponse_reportJobs :: Lens.Lens' ListReportJobsResponse (Prelude.Maybe [ReportJob])
listReportJobsResponse_reportJobs :: Lens' ListReportJobsResponse (Maybe [ReportJob])
listReportJobsResponse_reportJobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobsResponse' {Maybe [ReportJob]
reportJobs :: Maybe [ReportJob]
$sel:reportJobs:ListReportJobsResponse' :: ListReportJobsResponse -> Maybe [ReportJob]
reportJobs} -> Maybe [ReportJob]
reportJobs) (\s :: ListReportJobsResponse
s@ListReportJobsResponse' {} Maybe [ReportJob]
a -> ListReportJobsResponse
s {$sel:reportJobs:ListReportJobsResponse' :: Maybe [ReportJob]
reportJobs = Maybe [ReportJob]
a} :: ListReportJobsResponse) 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.
listReportJobsResponse_httpStatus :: Lens.Lens' ListReportJobsResponse Prelude.Int
listReportJobsResponse_httpStatus :: Lens' ListReportJobsResponse Int
listReportJobsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReportJobsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListReportJobsResponse' :: ListReportJobsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListReportJobsResponse
s@ListReportJobsResponse' {} Int
a -> ListReportJobsResponse
s {$sel:httpStatus:ListReportJobsResponse' :: Int
httpStatus = Int
a} :: ListReportJobsResponse)

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