{-# 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.Omics.ListAnnotationImportJobs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list of annotation import jobs.
--
-- This operation returns paginated results.
module Amazonka.Omics.ListAnnotationImportJobs
  ( -- * Creating a Request
    ListAnnotationImportJobs (..),
    newListAnnotationImportJobs,

    -- * Request Lenses
    listAnnotationImportJobs_filter,
    listAnnotationImportJobs_ids,
    listAnnotationImportJobs_maxResults,
    listAnnotationImportJobs_nextToken,

    -- * Destructuring the Response
    ListAnnotationImportJobsResponse (..),
    newListAnnotationImportJobsResponse,

    -- * Response Lenses
    listAnnotationImportJobsResponse_annotationImportJobs,
    listAnnotationImportJobsResponse_nextToken,
    listAnnotationImportJobsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAnnotationImportJobs' smart constructor.
data ListAnnotationImportJobs = ListAnnotationImportJobs'
  { -- | A filter to apply to the list.
    ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
filter' :: Prelude.Maybe ListAnnotationImportJobsFilter,
    -- | IDs of annotation import jobs to retrieve.
    ListAnnotationImportJobs -> Maybe (NonEmpty Text)
ids :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The maximum number of jobs to return in one page of results.
    ListAnnotationImportJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specify the pagination token from a previous request to retrieve the
    -- next page of results.
    ListAnnotationImportJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListAnnotationImportJobs -> ListAnnotationImportJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnnotationImportJobs -> ListAnnotationImportJobs -> Bool
$c/= :: ListAnnotationImportJobs -> ListAnnotationImportJobs -> Bool
== :: ListAnnotationImportJobs -> ListAnnotationImportJobs -> Bool
$c== :: ListAnnotationImportJobs -> ListAnnotationImportJobs -> Bool
Prelude.Eq, ReadPrec [ListAnnotationImportJobs]
ReadPrec ListAnnotationImportJobs
Int -> ReadS ListAnnotationImportJobs
ReadS [ListAnnotationImportJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnnotationImportJobs]
$creadListPrec :: ReadPrec [ListAnnotationImportJobs]
readPrec :: ReadPrec ListAnnotationImportJobs
$creadPrec :: ReadPrec ListAnnotationImportJobs
readList :: ReadS [ListAnnotationImportJobs]
$creadList :: ReadS [ListAnnotationImportJobs]
readsPrec :: Int -> ReadS ListAnnotationImportJobs
$creadsPrec :: Int -> ReadS ListAnnotationImportJobs
Prelude.Read, Int -> ListAnnotationImportJobs -> ShowS
[ListAnnotationImportJobs] -> ShowS
ListAnnotationImportJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnnotationImportJobs] -> ShowS
$cshowList :: [ListAnnotationImportJobs] -> ShowS
show :: ListAnnotationImportJobs -> String
$cshow :: ListAnnotationImportJobs -> String
showsPrec :: Int -> ListAnnotationImportJobs -> ShowS
$cshowsPrec :: Int -> ListAnnotationImportJobs -> ShowS
Prelude.Show, forall x.
Rep ListAnnotationImportJobs x -> ListAnnotationImportJobs
forall x.
ListAnnotationImportJobs -> Rep ListAnnotationImportJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAnnotationImportJobs x -> ListAnnotationImportJobs
$cfrom :: forall x.
ListAnnotationImportJobs -> Rep ListAnnotationImportJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListAnnotationImportJobs' 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:
--
-- 'filter'', 'listAnnotationImportJobs_filter' - A filter to apply to the list.
--
-- 'ids', 'listAnnotationImportJobs_ids' - IDs of annotation import jobs to retrieve.
--
-- 'maxResults', 'listAnnotationImportJobs_maxResults' - The maximum number of jobs to return in one page of results.
--
-- 'nextToken', 'listAnnotationImportJobs_nextToken' - Specify the pagination token from a previous request to retrieve the
-- next page of results.
newListAnnotationImportJobs ::
  ListAnnotationImportJobs
newListAnnotationImportJobs :: ListAnnotationImportJobs
newListAnnotationImportJobs =
  ListAnnotationImportJobs'
    { $sel:filter':ListAnnotationImportJobs' :: Maybe ListAnnotationImportJobsFilter
filter' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ids:ListAnnotationImportJobs' :: Maybe (NonEmpty Text)
ids = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListAnnotationImportJobs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAnnotationImportJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | A filter to apply to the list.
listAnnotationImportJobs_filter :: Lens.Lens' ListAnnotationImportJobs (Prelude.Maybe ListAnnotationImportJobsFilter)
listAnnotationImportJobs_filter :: Lens'
  ListAnnotationImportJobs (Maybe ListAnnotationImportJobsFilter)
listAnnotationImportJobs_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobs' {Maybe ListAnnotationImportJobsFilter
filter' :: Maybe ListAnnotationImportJobsFilter
$sel:filter':ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
filter'} -> Maybe ListAnnotationImportJobsFilter
filter') (\s :: ListAnnotationImportJobs
s@ListAnnotationImportJobs' {} Maybe ListAnnotationImportJobsFilter
a -> ListAnnotationImportJobs
s {$sel:filter':ListAnnotationImportJobs' :: Maybe ListAnnotationImportJobsFilter
filter' = Maybe ListAnnotationImportJobsFilter
a} :: ListAnnotationImportJobs)

-- | IDs of annotation import jobs to retrieve.
listAnnotationImportJobs_ids :: Lens.Lens' ListAnnotationImportJobs (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
listAnnotationImportJobs_ids :: Lens' ListAnnotationImportJobs (Maybe (NonEmpty Text))
listAnnotationImportJobs_ids = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobs' {Maybe (NonEmpty Text)
ids :: Maybe (NonEmpty Text)
$sel:ids:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe (NonEmpty Text)
ids} -> Maybe (NonEmpty Text)
ids) (\s :: ListAnnotationImportJobs
s@ListAnnotationImportJobs' {} Maybe (NonEmpty Text)
a -> ListAnnotationImportJobs
s {$sel:ids:ListAnnotationImportJobs' :: Maybe (NonEmpty Text)
ids = Maybe (NonEmpty Text)
a} :: ListAnnotationImportJobs) 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 maximum number of jobs to return in one page of results.
listAnnotationImportJobs_maxResults :: Lens.Lens' ListAnnotationImportJobs (Prelude.Maybe Prelude.Natural)
listAnnotationImportJobs_maxResults :: Lens' ListAnnotationImportJobs (Maybe Natural)
listAnnotationImportJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAnnotationImportJobs
s@ListAnnotationImportJobs' {} Maybe Natural
a -> ListAnnotationImportJobs
s {$sel:maxResults:ListAnnotationImportJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAnnotationImportJobs)

-- | Specify the pagination token from a previous request to retrieve the
-- next page of results.
listAnnotationImportJobs_nextToken :: Lens.Lens' ListAnnotationImportJobs (Prelude.Maybe Prelude.Text)
listAnnotationImportJobs_nextToken :: Lens' ListAnnotationImportJobs (Maybe Text)
listAnnotationImportJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnnotationImportJobs
s@ListAnnotationImportJobs' {} Maybe Text
a -> ListAnnotationImportJobs
s {$sel:nextToken:ListAnnotationImportJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnnotationImportJobs)

instance Core.AWSPager ListAnnotationImportJobs where
  page :: ListAnnotationImportJobs
-> AWSResponse ListAnnotationImportJobs
-> Maybe ListAnnotationImportJobs
page ListAnnotationImportJobs
rq AWSResponse ListAnnotationImportJobs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAnnotationImportJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAnnotationImportJobsResponse (Maybe Text)
listAnnotationImportJobsResponse_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 ListAnnotationImportJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListAnnotationImportJobsResponse (Maybe [AnnotationImportJobItem])
listAnnotationImportJobsResponse_annotationImportJobs
            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.$ ListAnnotationImportJobs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAnnotationImportJobs (Maybe Text)
listAnnotationImportJobs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAnnotationImportJobs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAnnotationImportJobsResponse (Maybe Text)
listAnnotationImportJobsResponse_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 ListAnnotationImportJobs where
  type
    AWSResponse ListAnnotationImportJobs =
      ListAnnotationImportJobsResponse
  request :: (Service -> Service)
-> ListAnnotationImportJobs -> Request ListAnnotationImportJobs
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 ListAnnotationImportJobs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListAnnotationImportJobs)))
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 [AnnotationImportJobItem]
-> Maybe Text -> Int -> ListAnnotationImportJobsResponse
ListAnnotationImportJobsResponse'
            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
"annotationImportJobs"
                            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 ListAnnotationImportJobs where
  hashWithSalt :: Int -> ListAnnotationImportJobs -> Int
hashWithSalt Int
_salt ListAnnotationImportJobs' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe ListAnnotationImportJobsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
ids :: Maybe (NonEmpty Text)
filter' :: Maybe ListAnnotationImportJobsFilter
$sel:nextToken:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Text
$sel:maxResults:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Natural
$sel:ids:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe (NonEmpty Text)
$sel:filter':ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListAnnotationImportJobsFilter
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
ids
      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 ListAnnotationImportJobs where
  rnf :: ListAnnotationImportJobs -> ()
rnf ListAnnotationImportJobs' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe ListAnnotationImportJobsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
ids :: Maybe (NonEmpty Text)
filter' :: Maybe ListAnnotationImportJobsFilter
$sel:nextToken:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Text
$sel:maxResults:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Natural
$sel:ids:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe (NonEmpty Text)
$sel:filter':ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ListAnnotationImportJobsFilter
filter'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
ids
      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 ListAnnotationImportJobs where
  toHeaders :: ListAnnotationImportJobs -> 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.ToJSON ListAnnotationImportJobs where
  toJSON :: ListAnnotationImportJobs -> Value
toJSON ListAnnotationImportJobs' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe ListAnnotationImportJobsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
ids :: Maybe (NonEmpty Text)
filter' :: Maybe ListAnnotationImportJobsFilter
$sel:nextToken:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Text
$sel:maxResults:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Natural
$sel:ids:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe (NonEmpty Text)
$sel:filter':ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"filter" 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 ListAnnotationImportJobsFilter
filter',
            (Key
"ids" 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 (NonEmpty Text)
ids
          ]
      )

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

instance Data.ToQuery ListAnnotationImportJobs where
  toQuery :: ListAnnotationImportJobs -> QueryString
toQuery ListAnnotationImportJobs' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe ListAnnotationImportJobsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
ids :: Maybe (NonEmpty Text)
filter' :: Maybe ListAnnotationImportJobsFilter
$sel:nextToken:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Text
$sel:maxResults:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe Natural
$sel:ids:ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe (NonEmpty Text)
$sel:filter':ListAnnotationImportJobs' :: ListAnnotationImportJobs -> Maybe ListAnnotationImportJobsFilter
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ 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:/ 'newListAnnotationImportJobsResponse' smart constructor.
data ListAnnotationImportJobsResponse = ListAnnotationImportJobsResponse'
  { -- | A list of jobs.
    ListAnnotationImportJobsResponse -> Maybe [AnnotationImportJobItem]
annotationImportJobs :: Prelude.Maybe [AnnotationImportJobItem],
    -- | A pagination token that\'s included if more results are available.
    ListAnnotationImportJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAnnotationImportJobsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAnnotationImportJobsResponse
-> ListAnnotationImportJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnnotationImportJobsResponse
-> ListAnnotationImportJobsResponse -> Bool
$c/= :: ListAnnotationImportJobsResponse
-> ListAnnotationImportJobsResponse -> Bool
== :: ListAnnotationImportJobsResponse
-> ListAnnotationImportJobsResponse -> Bool
$c== :: ListAnnotationImportJobsResponse
-> ListAnnotationImportJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListAnnotationImportJobsResponse]
ReadPrec ListAnnotationImportJobsResponse
Int -> ReadS ListAnnotationImportJobsResponse
ReadS [ListAnnotationImportJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnnotationImportJobsResponse]
$creadListPrec :: ReadPrec [ListAnnotationImportJobsResponse]
readPrec :: ReadPrec ListAnnotationImportJobsResponse
$creadPrec :: ReadPrec ListAnnotationImportJobsResponse
readList :: ReadS [ListAnnotationImportJobsResponse]
$creadList :: ReadS [ListAnnotationImportJobsResponse]
readsPrec :: Int -> ReadS ListAnnotationImportJobsResponse
$creadsPrec :: Int -> ReadS ListAnnotationImportJobsResponse
Prelude.Read, Int -> ListAnnotationImportJobsResponse -> ShowS
[ListAnnotationImportJobsResponse] -> ShowS
ListAnnotationImportJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnnotationImportJobsResponse] -> ShowS
$cshowList :: [ListAnnotationImportJobsResponse] -> ShowS
show :: ListAnnotationImportJobsResponse -> String
$cshow :: ListAnnotationImportJobsResponse -> String
showsPrec :: Int -> ListAnnotationImportJobsResponse -> ShowS
$cshowsPrec :: Int -> ListAnnotationImportJobsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAnnotationImportJobsResponse x
-> ListAnnotationImportJobsResponse
forall x.
ListAnnotationImportJobsResponse
-> Rep ListAnnotationImportJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAnnotationImportJobsResponse x
-> ListAnnotationImportJobsResponse
$cfrom :: forall x.
ListAnnotationImportJobsResponse
-> Rep ListAnnotationImportJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAnnotationImportJobsResponse' 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:
--
-- 'annotationImportJobs', 'listAnnotationImportJobsResponse_annotationImportJobs' - A list of jobs.
--
-- 'nextToken', 'listAnnotationImportJobsResponse_nextToken' - A pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'listAnnotationImportJobsResponse_httpStatus' - The response's http status code.
newListAnnotationImportJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAnnotationImportJobsResponse
newListAnnotationImportJobsResponse :: Int -> ListAnnotationImportJobsResponse
newListAnnotationImportJobsResponse Int
pHttpStatus_ =
  ListAnnotationImportJobsResponse'
    { $sel:annotationImportJobs:ListAnnotationImportJobsResponse' :: Maybe [AnnotationImportJobItem]
annotationImportJobs =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAnnotationImportJobsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAnnotationImportJobsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of jobs.
listAnnotationImportJobsResponse_annotationImportJobs :: Lens.Lens' ListAnnotationImportJobsResponse (Prelude.Maybe [AnnotationImportJobItem])
listAnnotationImportJobsResponse_annotationImportJobs :: Lens'
  ListAnnotationImportJobsResponse (Maybe [AnnotationImportJobItem])
listAnnotationImportJobsResponse_annotationImportJobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobsResponse' {Maybe [AnnotationImportJobItem]
annotationImportJobs :: Maybe [AnnotationImportJobItem]
$sel:annotationImportJobs:ListAnnotationImportJobsResponse' :: ListAnnotationImportJobsResponse -> Maybe [AnnotationImportJobItem]
annotationImportJobs} -> Maybe [AnnotationImportJobItem]
annotationImportJobs) (\s :: ListAnnotationImportJobsResponse
s@ListAnnotationImportJobsResponse' {} Maybe [AnnotationImportJobItem]
a -> ListAnnotationImportJobsResponse
s {$sel:annotationImportJobs:ListAnnotationImportJobsResponse' :: Maybe [AnnotationImportJobItem]
annotationImportJobs = Maybe [AnnotationImportJobItem]
a} :: ListAnnotationImportJobsResponse) 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

-- | A pagination token that\'s included if more results are available.
listAnnotationImportJobsResponse_nextToken :: Lens.Lens' ListAnnotationImportJobsResponse (Prelude.Maybe Prelude.Text)
listAnnotationImportJobsResponse_nextToken :: Lens' ListAnnotationImportJobsResponse (Maybe Text)
listAnnotationImportJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnnotationImportJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnnotationImportJobsResponse' :: ListAnnotationImportJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnnotationImportJobsResponse
s@ListAnnotationImportJobsResponse' {} Maybe Text
a -> ListAnnotationImportJobsResponse
s {$sel:nextToken:ListAnnotationImportJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnnotationImportJobsResponse)

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

instance
  Prelude.NFData
    ListAnnotationImportJobsResponse
  where
  rnf :: ListAnnotationImportJobsResponse -> ()
rnf ListAnnotationImportJobsResponse' {Int
Maybe [AnnotationImportJobItem]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
annotationImportJobs :: Maybe [AnnotationImportJobItem]
$sel:httpStatus:ListAnnotationImportJobsResponse' :: ListAnnotationImportJobsResponse -> Int
$sel:nextToken:ListAnnotationImportJobsResponse' :: ListAnnotationImportJobsResponse -> Maybe Text
$sel:annotationImportJobs:ListAnnotationImportJobsResponse' :: ListAnnotationImportJobsResponse -> Maybe [AnnotationImportJobItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AnnotationImportJobItem]
annotationImportJobs
      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