{-# 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.Forecast.ListPredictorBacktestExportJobs
-- 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 predictor backtest export jobs created using the
-- CreatePredictorBacktestExportJob operation. This operation returns a
-- summary for each backtest export job. You can filter the list using an
-- array of Filter objects.
--
-- To retrieve the complete set of properties for a particular backtest
-- export job, use the ARN with the DescribePredictorBacktestExportJob
-- operation.
--
-- This operation returns paginated results.
module Amazonka.Forecast.ListPredictorBacktestExportJobs
  ( -- * Creating a Request
    ListPredictorBacktestExportJobs (..),
    newListPredictorBacktestExportJobs,

    -- * Request Lenses
    listPredictorBacktestExportJobs_filters,
    listPredictorBacktestExportJobs_maxResults,
    listPredictorBacktestExportJobs_nextToken,

    -- * Destructuring the Response
    ListPredictorBacktestExportJobsResponse (..),
    newListPredictorBacktestExportJobsResponse,

    -- * Response Lenses
    listPredictorBacktestExportJobsResponse_nextToken,
    listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs,
    listPredictorBacktestExportJobsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListPredictorBacktestExportJobs' smart constructor.
data ListPredictorBacktestExportJobs = ListPredictorBacktestExportJobs'
  { -- | An array of filters. For each filter, provide a condition and a match
    -- statement. The condition is either @IS@ or @IS_NOT@, which specifies
    -- whether to include or exclude the predictor backtest export jobs that
    -- match the statement from the list. The match statement consists of a key
    -- and a value.
    --
    -- __Filter properties__
    --
    -- -   @Condition@ - The condition to apply. Valid values are @IS@ and
    --     @IS_NOT@. To include the predictor backtest export jobs that match
    --     the statement, specify @IS@. To exclude matching predictor backtest
    --     export jobs, specify @IS_NOT@.
    --
    -- -   @Key@ - The name of the parameter to filter on. Valid values are
    --     @PredictorArn@ and @Status@.
    --
    -- -   @Value@ - The value to match.
    ListPredictorBacktestExportJobs -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The number of items to return in the response.
    ListPredictorBacktestExportJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the result of the previous request was truncated, the response
    -- includes a NextToken. To retrieve the next set of results, use the token
    -- in the next request. Tokens expire after 24 hours.
    ListPredictorBacktestExportJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListPredictorBacktestExportJobs
-> ListPredictorBacktestExportJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPredictorBacktestExportJobs
-> ListPredictorBacktestExportJobs -> Bool
$c/= :: ListPredictorBacktestExportJobs
-> ListPredictorBacktestExportJobs -> Bool
== :: ListPredictorBacktestExportJobs
-> ListPredictorBacktestExportJobs -> Bool
$c== :: ListPredictorBacktestExportJobs
-> ListPredictorBacktestExportJobs -> Bool
Prelude.Eq, ReadPrec [ListPredictorBacktestExportJobs]
ReadPrec ListPredictorBacktestExportJobs
Int -> ReadS ListPredictorBacktestExportJobs
ReadS [ListPredictorBacktestExportJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPredictorBacktestExportJobs]
$creadListPrec :: ReadPrec [ListPredictorBacktestExportJobs]
readPrec :: ReadPrec ListPredictorBacktestExportJobs
$creadPrec :: ReadPrec ListPredictorBacktestExportJobs
readList :: ReadS [ListPredictorBacktestExportJobs]
$creadList :: ReadS [ListPredictorBacktestExportJobs]
readsPrec :: Int -> ReadS ListPredictorBacktestExportJobs
$creadsPrec :: Int -> ReadS ListPredictorBacktestExportJobs
Prelude.Read, Int -> ListPredictorBacktestExportJobs -> ShowS
[ListPredictorBacktestExportJobs] -> ShowS
ListPredictorBacktestExportJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPredictorBacktestExportJobs] -> ShowS
$cshowList :: [ListPredictorBacktestExportJobs] -> ShowS
show :: ListPredictorBacktestExportJobs -> String
$cshow :: ListPredictorBacktestExportJobs -> String
showsPrec :: Int -> ListPredictorBacktestExportJobs -> ShowS
$cshowsPrec :: Int -> ListPredictorBacktestExportJobs -> ShowS
Prelude.Show, forall x.
Rep ListPredictorBacktestExportJobs x
-> ListPredictorBacktestExportJobs
forall x.
ListPredictorBacktestExportJobs
-> Rep ListPredictorBacktestExportJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPredictorBacktestExportJobs x
-> ListPredictorBacktestExportJobs
$cfrom :: forall x.
ListPredictorBacktestExportJobs
-> Rep ListPredictorBacktestExportJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListPredictorBacktestExportJobs' 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:
--
-- 'filters', 'listPredictorBacktestExportJobs_filters' - An array of filters. For each filter, provide a condition and a match
-- statement. The condition is either @IS@ or @IS_NOT@, which specifies
-- whether to include or exclude the predictor backtest export jobs that
-- match the statement from the list. The match statement consists of a key
-- and a value.
--
-- __Filter properties__
--
-- -   @Condition@ - The condition to apply. Valid values are @IS@ and
--     @IS_NOT@. To include the predictor backtest export jobs that match
--     the statement, specify @IS@. To exclude matching predictor backtest
--     export jobs, specify @IS_NOT@.
--
-- -   @Key@ - The name of the parameter to filter on. Valid values are
--     @PredictorArn@ and @Status@.
--
-- -   @Value@ - The value to match.
--
-- 'maxResults', 'listPredictorBacktestExportJobs_maxResults' - The number of items to return in the response.
--
-- 'nextToken', 'listPredictorBacktestExportJobs_nextToken' - If the result of the previous request was truncated, the response
-- includes a NextToken. To retrieve the next set of results, use the token
-- in the next request. Tokens expire after 24 hours.
newListPredictorBacktestExportJobs ::
  ListPredictorBacktestExportJobs
newListPredictorBacktestExportJobs :: ListPredictorBacktestExportJobs
newListPredictorBacktestExportJobs =
  ListPredictorBacktestExportJobs'
    { $sel:filters:ListPredictorBacktestExportJobs' :: Maybe [Filter]
filters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListPredictorBacktestExportJobs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPredictorBacktestExportJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | An array of filters. For each filter, provide a condition and a match
-- statement. The condition is either @IS@ or @IS_NOT@, which specifies
-- whether to include or exclude the predictor backtest export jobs that
-- match the statement from the list. The match statement consists of a key
-- and a value.
--
-- __Filter properties__
--
-- -   @Condition@ - The condition to apply. Valid values are @IS@ and
--     @IS_NOT@. To include the predictor backtest export jobs that match
--     the statement, specify @IS@. To exclude matching predictor backtest
--     export jobs, specify @IS_NOT@.
--
-- -   @Key@ - The name of the parameter to filter on. Valid values are
--     @PredictorArn@ and @Status@.
--
-- -   @Value@ - The value to match.
listPredictorBacktestExportJobs_filters :: Lens.Lens' ListPredictorBacktestExportJobs (Prelude.Maybe [Filter])
listPredictorBacktestExportJobs_filters :: Lens' ListPredictorBacktestExportJobs (Maybe [Filter])
listPredictorBacktestExportJobs_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobs' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListPredictorBacktestExportJobs
s@ListPredictorBacktestExportJobs' {} Maybe [Filter]
a -> ListPredictorBacktestExportJobs
s {$sel:filters:ListPredictorBacktestExportJobs' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListPredictorBacktestExportJobs) 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 number of items to return in the response.
listPredictorBacktestExportJobs_maxResults :: Lens.Lens' ListPredictorBacktestExportJobs (Prelude.Maybe Prelude.Natural)
listPredictorBacktestExportJobs_maxResults :: Lens' ListPredictorBacktestExportJobs (Maybe Natural)
listPredictorBacktestExportJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPredictorBacktestExportJobs
s@ListPredictorBacktestExportJobs' {} Maybe Natural
a -> ListPredictorBacktestExportJobs
s {$sel:maxResults:ListPredictorBacktestExportJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPredictorBacktestExportJobs)

-- | If the result of the previous request was truncated, the response
-- includes a NextToken. To retrieve the next set of results, use the token
-- in the next request. Tokens expire after 24 hours.
listPredictorBacktestExportJobs_nextToken :: Lens.Lens' ListPredictorBacktestExportJobs (Prelude.Maybe Prelude.Text)
listPredictorBacktestExportJobs_nextToken :: Lens' ListPredictorBacktestExportJobs (Maybe Text)
listPredictorBacktestExportJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPredictorBacktestExportJobs
s@ListPredictorBacktestExportJobs' {} Maybe Text
a -> ListPredictorBacktestExportJobs
s {$sel:nextToken:ListPredictorBacktestExportJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListPredictorBacktestExportJobs)

instance
  Core.AWSPager
    ListPredictorBacktestExportJobs
  where
  page :: ListPredictorBacktestExportJobs
-> AWSResponse ListPredictorBacktestExportJobs
-> Maybe ListPredictorBacktestExportJobs
page ListPredictorBacktestExportJobs
rq AWSResponse ListPredictorBacktestExportJobs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPredictorBacktestExportJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPredictorBacktestExportJobsResponse (Maybe Text)
listPredictorBacktestExportJobsResponse_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 ListPredictorBacktestExportJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListPredictorBacktestExportJobsResponse
  (Maybe [PredictorBacktestExportJobSummary])
listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs
            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.$ ListPredictorBacktestExportJobs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPredictorBacktestExportJobs (Maybe Text)
listPredictorBacktestExportJobs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPredictorBacktestExportJobs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPredictorBacktestExportJobsResponse (Maybe Text)
listPredictorBacktestExportJobsResponse_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
    ListPredictorBacktestExportJobs
  where
  type
    AWSResponse ListPredictorBacktestExportJobs =
      ListPredictorBacktestExportJobsResponse
  request :: (Service -> Service)
-> ListPredictorBacktestExportJobs
-> Request ListPredictorBacktestExportJobs
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListPredictorBacktestExportJobs
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListPredictorBacktestExportJobs)))
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 [PredictorBacktestExportJobSummary]
-> Int
-> ListPredictorBacktestExportJobsResponse
ListPredictorBacktestExportJobsResponse'
            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
"PredictorBacktestExportJobs"
                            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
    ListPredictorBacktestExportJobs
  where
  hashWithSalt :: Int -> ListPredictorBacktestExportJobs -> Int
hashWithSalt
    Int
_salt
    ListPredictorBacktestExportJobs' {Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:nextToken:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Text
$sel:maxResults:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Natural
$sel:filters:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe [Filter]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
        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
    ListPredictorBacktestExportJobs
  where
  rnf :: ListPredictorBacktestExportJobs -> ()
rnf ListPredictorBacktestExportJobs' {Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:nextToken:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Text
$sel:maxResults:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Natural
$sel:filters:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      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
    ListPredictorBacktestExportJobs
  where
  toHeaders :: ListPredictorBacktestExportJobs -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonForecast.ListPredictorBacktestExportJobs" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListPredictorBacktestExportJobs where
  toJSON :: ListPredictorBacktestExportJobs -> Value
toJSON ListPredictorBacktestExportJobs' {Maybe Natural
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
$sel:nextToken:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Text
$sel:maxResults:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe Natural
$sel:filters:ListPredictorBacktestExportJobs' :: ListPredictorBacktestExportJobs -> Maybe [Filter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken
          ]
      )

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

instance Data.ToQuery ListPredictorBacktestExportJobs where
  toQuery :: ListPredictorBacktestExportJobs -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListPredictorBacktestExportJobsResponse' smart constructor.
data ListPredictorBacktestExportJobsResponse = ListPredictorBacktestExportJobsResponse'
  { -- | Returns this token if the response is truncated. To retrieve the next
    -- set of results, use the token in the next request.
    ListPredictorBacktestExportJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that summarize the properties of each predictor
    -- backtest export job.
    ListPredictorBacktestExportJobsResponse
-> Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs :: Prelude.Maybe [PredictorBacktestExportJobSummary],
    -- | The response's http status code.
    ListPredictorBacktestExportJobsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPredictorBacktestExportJobsResponse
-> ListPredictorBacktestExportJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPredictorBacktestExportJobsResponse
-> ListPredictorBacktestExportJobsResponse -> Bool
$c/= :: ListPredictorBacktestExportJobsResponse
-> ListPredictorBacktestExportJobsResponse -> Bool
== :: ListPredictorBacktestExportJobsResponse
-> ListPredictorBacktestExportJobsResponse -> Bool
$c== :: ListPredictorBacktestExportJobsResponse
-> ListPredictorBacktestExportJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListPredictorBacktestExportJobsResponse]
ReadPrec ListPredictorBacktestExportJobsResponse
Int -> ReadS ListPredictorBacktestExportJobsResponse
ReadS [ListPredictorBacktestExportJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPredictorBacktestExportJobsResponse]
$creadListPrec :: ReadPrec [ListPredictorBacktestExportJobsResponse]
readPrec :: ReadPrec ListPredictorBacktestExportJobsResponse
$creadPrec :: ReadPrec ListPredictorBacktestExportJobsResponse
readList :: ReadS [ListPredictorBacktestExportJobsResponse]
$creadList :: ReadS [ListPredictorBacktestExportJobsResponse]
readsPrec :: Int -> ReadS ListPredictorBacktestExportJobsResponse
$creadsPrec :: Int -> ReadS ListPredictorBacktestExportJobsResponse
Prelude.Read, Int -> ListPredictorBacktestExportJobsResponse -> ShowS
[ListPredictorBacktestExportJobsResponse] -> ShowS
ListPredictorBacktestExportJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPredictorBacktestExportJobsResponse] -> ShowS
$cshowList :: [ListPredictorBacktestExportJobsResponse] -> ShowS
show :: ListPredictorBacktestExportJobsResponse -> String
$cshow :: ListPredictorBacktestExportJobsResponse -> String
showsPrec :: Int -> ListPredictorBacktestExportJobsResponse -> ShowS
$cshowsPrec :: Int -> ListPredictorBacktestExportJobsResponse -> ShowS
Prelude.Show, forall x.
Rep ListPredictorBacktestExportJobsResponse x
-> ListPredictorBacktestExportJobsResponse
forall x.
ListPredictorBacktestExportJobsResponse
-> Rep ListPredictorBacktestExportJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPredictorBacktestExportJobsResponse x
-> ListPredictorBacktestExportJobsResponse
$cfrom :: forall x.
ListPredictorBacktestExportJobsResponse
-> Rep ListPredictorBacktestExportJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPredictorBacktestExportJobsResponse' 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', 'listPredictorBacktestExportJobsResponse_nextToken' - Returns this token if the response is truncated. To retrieve the next
-- set of results, use the token in the next request.
--
-- 'predictorBacktestExportJobs', 'listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs' - An array of objects that summarize the properties of each predictor
-- backtest export job.
--
-- 'httpStatus', 'listPredictorBacktestExportJobsResponse_httpStatus' - The response's http status code.
newListPredictorBacktestExportJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPredictorBacktestExportJobsResponse
newListPredictorBacktestExportJobsResponse :: Int -> ListPredictorBacktestExportJobsResponse
newListPredictorBacktestExportJobsResponse
  Int
pHttpStatus_ =
    ListPredictorBacktestExportJobsResponse'
      { $sel:nextToken:ListPredictorBacktestExportJobsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:predictorBacktestExportJobs:ListPredictorBacktestExportJobsResponse' :: Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListPredictorBacktestExportJobsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Returns this token if the response is truncated. To retrieve the next
-- set of results, use the token in the next request.
listPredictorBacktestExportJobsResponse_nextToken :: Lens.Lens' ListPredictorBacktestExportJobsResponse (Prelude.Maybe Prelude.Text)
listPredictorBacktestExportJobsResponse_nextToken :: Lens' ListPredictorBacktestExportJobsResponse (Maybe Text)
listPredictorBacktestExportJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPredictorBacktestExportJobsResponse' :: ListPredictorBacktestExportJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPredictorBacktestExportJobsResponse
s@ListPredictorBacktestExportJobsResponse' {} Maybe Text
a -> ListPredictorBacktestExportJobsResponse
s {$sel:nextToken:ListPredictorBacktestExportJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPredictorBacktestExportJobsResponse)

-- | An array of objects that summarize the properties of each predictor
-- backtest export job.
listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs :: Lens.Lens' ListPredictorBacktestExportJobsResponse (Prelude.Maybe [PredictorBacktestExportJobSummary])
listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs :: Lens'
  ListPredictorBacktestExportJobsResponse
  (Maybe [PredictorBacktestExportJobSummary])
listPredictorBacktestExportJobsResponse_predictorBacktestExportJobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobsResponse' {Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs :: Maybe [PredictorBacktestExportJobSummary]
$sel:predictorBacktestExportJobs:ListPredictorBacktestExportJobsResponse' :: ListPredictorBacktestExportJobsResponse
-> Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs} -> Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs) (\s :: ListPredictorBacktestExportJobsResponse
s@ListPredictorBacktestExportJobsResponse' {} Maybe [PredictorBacktestExportJobSummary]
a -> ListPredictorBacktestExportJobsResponse
s {$sel:predictorBacktestExportJobs:ListPredictorBacktestExportJobsResponse' :: Maybe [PredictorBacktestExportJobSummary]
predictorBacktestExportJobs = Maybe [PredictorBacktestExportJobSummary]
a} :: ListPredictorBacktestExportJobsResponse) 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.
listPredictorBacktestExportJobsResponse_httpStatus :: Lens.Lens' ListPredictorBacktestExportJobsResponse Prelude.Int
listPredictorBacktestExportJobsResponse_httpStatus :: Lens' ListPredictorBacktestExportJobsResponse Int
listPredictorBacktestExportJobsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPredictorBacktestExportJobsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPredictorBacktestExportJobsResponse' :: ListPredictorBacktestExportJobsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPredictorBacktestExportJobsResponse
s@ListPredictorBacktestExportJobsResponse' {} Int
a -> ListPredictorBacktestExportJobsResponse
s {$sel:httpStatus:ListPredictorBacktestExportJobsResponse' :: Int
httpStatus = Int
a} :: ListPredictorBacktestExportJobsResponse)

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