{-# 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.CloudTrail.ListImports
-- 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 information on all imports, or a select set of imports by
-- @ImportStatus@ or @Destination@.
--
-- This operation returns paginated results.
module Amazonka.CloudTrail.ListImports
  ( -- * Creating a Request
    ListImports (..),
    newListImports,

    -- * Request Lenses
    listImports_destination,
    listImports_importStatus,
    listImports_maxResults,
    listImports_nextToken,

    -- * Destructuring the Response
    ListImportsResponse (..),
    newListImportsResponse,

    -- * Response Lenses
    listImportsResponse_imports,
    listImportsResponse_nextToken,
    listImportsResponse_httpStatus,
  )
where

import Amazonka.CloudTrail.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:/ 'newListImports' smart constructor.
data ListImports = ListImports'
  { -- | The ARN of the destination event data store.
    ListImports -> Maybe Text
destination :: Prelude.Maybe Prelude.Text,
    -- | The status of the import.
    ListImports -> Maybe ImportStatus
importStatus :: Prelude.Maybe ImportStatus,
    -- | The maximum number of imports to display on a single page.
    ListImports -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token you can use to get the next page of import results.
    ListImports -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListImports -> ListImports -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListImports -> ListImports -> Bool
$c/= :: ListImports -> ListImports -> Bool
== :: ListImports -> ListImports -> Bool
$c== :: ListImports -> ListImports -> Bool
Prelude.Eq, ReadPrec [ListImports]
ReadPrec ListImports
Int -> ReadS ListImports
ReadS [ListImports]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListImports]
$creadListPrec :: ReadPrec [ListImports]
readPrec :: ReadPrec ListImports
$creadPrec :: ReadPrec ListImports
readList :: ReadS [ListImports]
$creadList :: ReadS [ListImports]
readsPrec :: Int -> ReadS ListImports
$creadsPrec :: Int -> ReadS ListImports
Prelude.Read, Int -> ListImports -> ShowS
[ListImports] -> ShowS
ListImports -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListImports] -> ShowS
$cshowList :: [ListImports] -> ShowS
show :: ListImports -> String
$cshow :: ListImports -> String
showsPrec :: Int -> ListImports -> ShowS
$cshowsPrec :: Int -> ListImports -> ShowS
Prelude.Show, forall x. Rep ListImports x -> ListImports
forall x. ListImports -> Rep ListImports x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListImports x -> ListImports
$cfrom :: forall x. ListImports -> Rep ListImports x
Prelude.Generic)

-- |
-- Create a value of 'ListImports' 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:
--
-- 'destination', 'listImports_destination' - The ARN of the destination event data store.
--
-- 'importStatus', 'listImports_importStatus' - The status of the import.
--
-- 'maxResults', 'listImports_maxResults' - The maximum number of imports to display on a single page.
--
-- 'nextToken', 'listImports_nextToken' - A token you can use to get the next page of import results.
newListImports ::
  ListImports
newListImports :: ListImports
newListImports =
  ListImports'
    { $sel:destination:ListImports' :: Maybe Text
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:importStatus:ListImports' :: Maybe ImportStatus
importStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListImports' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListImports' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the destination event data store.
listImports_destination :: Lens.Lens' ListImports (Prelude.Maybe Prelude.Text)
listImports_destination :: Lens' ListImports (Maybe Text)
listImports_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImports' {Maybe Text
destination :: Maybe Text
$sel:destination:ListImports' :: ListImports -> Maybe Text
destination} -> Maybe Text
destination) (\s :: ListImports
s@ListImports' {} Maybe Text
a -> ListImports
s {$sel:destination:ListImports' :: Maybe Text
destination = Maybe Text
a} :: ListImports)

-- | The status of the import.
listImports_importStatus :: Lens.Lens' ListImports (Prelude.Maybe ImportStatus)
listImports_importStatus :: Lens' ListImports (Maybe ImportStatus)
listImports_importStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImports' {Maybe ImportStatus
importStatus :: Maybe ImportStatus
$sel:importStatus:ListImports' :: ListImports -> Maybe ImportStatus
importStatus} -> Maybe ImportStatus
importStatus) (\s :: ListImports
s@ListImports' {} Maybe ImportStatus
a -> ListImports
s {$sel:importStatus:ListImports' :: Maybe ImportStatus
importStatus = Maybe ImportStatus
a} :: ListImports)

-- | The maximum number of imports to display on a single page.
listImports_maxResults :: Lens.Lens' ListImports (Prelude.Maybe Prelude.Natural)
listImports_maxResults :: Lens' ListImports (Maybe Natural)
listImports_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImports' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListImports' :: ListImports -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListImports
s@ListImports' {} Maybe Natural
a -> ListImports
s {$sel:maxResults:ListImports' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListImports)

-- | A token you can use to get the next page of import results.
listImports_nextToken :: Lens.Lens' ListImports (Prelude.Maybe Prelude.Text)
listImports_nextToken :: Lens' ListImports (Maybe Text)
listImports_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImports' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListImports' :: ListImports -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListImports
s@ListImports' {} Maybe Text
a -> ListImports
s {$sel:nextToken:ListImports' :: Maybe Text
nextToken = Maybe Text
a} :: ListImports)

instance Core.AWSPager ListImports where
  page :: ListImports -> AWSResponse ListImports -> Maybe ListImports
page ListImports
rq AWSResponse ListImports
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListImports
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImportsResponse (Maybe Text)
listImportsResponse_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 ListImports
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImportsResponse (Maybe [ImportsListItem])
listImportsResponse_imports
            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.$ ListImports
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListImports (Maybe Text)
listImports_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListImports
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListImportsResponse (Maybe Text)
listImportsResponse_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 ListImports where
  type AWSResponse ListImports = ListImportsResponse
  request :: (Service -> Service) -> ListImports -> Request ListImports
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 ListImports
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListImports)))
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 [ImportsListItem] -> Maybe Text -> Int -> ListImportsResponse
ListImportsResponse'
            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
"Imports" 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 ListImports where
  hashWithSalt :: Int -> ListImports -> Int
hashWithSalt Int
_salt ListImports' {Maybe Natural
Maybe Text
Maybe ImportStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
importStatus :: Maybe ImportStatus
destination :: Maybe Text
$sel:nextToken:ListImports' :: ListImports -> Maybe Text
$sel:maxResults:ListImports' :: ListImports -> Maybe Natural
$sel:importStatus:ListImports' :: ListImports -> Maybe ImportStatus
$sel:destination:ListImports' :: ListImports -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImportStatus
importStatus
      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 ListImports where
  rnf :: ListImports -> ()
rnf ListImports' {Maybe Natural
Maybe Text
Maybe ImportStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
importStatus :: Maybe ImportStatus
destination :: Maybe Text
$sel:nextToken:ListImports' :: ListImports -> Maybe Text
$sel:maxResults:ListImports' :: ListImports -> Maybe Natural
$sel:importStatus:ListImports' :: ListImports -> Maybe ImportStatus
$sel:destination:ListImports' :: ListImports -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImportStatus
importStatus
      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 ListImports where
  toHeaders :: ListImports -> 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
"com.amazonaws.cloudtrail.v20131101.CloudTrail_20131101.ListImports" ::
                          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 ListImports where
  toJSON :: ListImports -> Value
toJSON ListImports' {Maybe Natural
Maybe Text
Maybe ImportStatus
nextToken :: Maybe Text
maxResults :: Maybe Natural
importStatus :: Maybe ImportStatus
destination :: Maybe Text
$sel:nextToken:ListImports' :: ListImports -> Maybe Text
$sel:maxResults:ListImports' :: ListImports -> Maybe Natural
$sel:importStatus:ListImports' :: ListImports -> Maybe ImportStatus
$sel:destination:ListImports' :: ListImports -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Destination" 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
destination,
            (Key
"ImportStatus" 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 ImportStatus
importStatus,
            (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 ListImports where
  toPath :: ListImports -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListImportsResponse' smart constructor.
data ListImportsResponse = ListImportsResponse'
  { -- | The list of returned imports.
    ListImportsResponse -> Maybe [ImportsListItem]
imports :: Prelude.Maybe [ImportsListItem],
    -- | A token you can use to get the next page of import results.
    ListImportsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListImportsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListImportsResponse -> ListImportsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListImportsResponse -> ListImportsResponse -> Bool
$c/= :: ListImportsResponse -> ListImportsResponse -> Bool
== :: ListImportsResponse -> ListImportsResponse -> Bool
$c== :: ListImportsResponse -> ListImportsResponse -> Bool
Prelude.Eq, ReadPrec [ListImportsResponse]
ReadPrec ListImportsResponse
Int -> ReadS ListImportsResponse
ReadS [ListImportsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListImportsResponse]
$creadListPrec :: ReadPrec [ListImportsResponse]
readPrec :: ReadPrec ListImportsResponse
$creadPrec :: ReadPrec ListImportsResponse
readList :: ReadS [ListImportsResponse]
$creadList :: ReadS [ListImportsResponse]
readsPrec :: Int -> ReadS ListImportsResponse
$creadsPrec :: Int -> ReadS ListImportsResponse
Prelude.Read, Int -> ListImportsResponse -> ShowS
[ListImportsResponse] -> ShowS
ListImportsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListImportsResponse] -> ShowS
$cshowList :: [ListImportsResponse] -> ShowS
show :: ListImportsResponse -> String
$cshow :: ListImportsResponse -> String
showsPrec :: Int -> ListImportsResponse -> ShowS
$cshowsPrec :: Int -> ListImportsResponse -> ShowS
Prelude.Show, forall x. Rep ListImportsResponse x -> ListImportsResponse
forall x. ListImportsResponse -> Rep ListImportsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListImportsResponse x -> ListImportsResponse
$cfrom :: forall x. ListImportsResponse -> Rep ListImportsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListImportsResponse' 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:
--
-- 'imports', 'listImportsResponse_imports' - The list of returned imports.
--
-- 'nextToken', 'listImportsResponse_nextToken' - A token you can use to get the next page of import results.
--
-- 'httpStatus', 'listImportsResponse_httpStatus' - The response's http status code.
newListImportsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListImportsResponse
newListImportsResponse :: Int -> ListImportsResponse
newListImportsResponse Int
pHttpStatus_ =
  ListImportsResponse'
    { $sel:imports:ListImportsResponse' :: Maybe [ImportsListItem]
imports = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListImportsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListImportsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of returned imports.
listImportsResponse_imports :: Lens.Lens' ListImportsResponse (Prelude.Maybe [ImportsListItem])
listImportsResponse_imports :: Lens' ListImportsResponse (Maybe [ImportsListItem])
listImportsResponse_imports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImportsResponse' {Maybe [ImportsListItem]
imports :: Maybe [ImportsListItem]
$sel:imports:ListImportsResponse' :: ListImportsResponse -> Maybe [ImportsListItem]
imports} -> Maybe [ImportsListItem]
imports) (\s :: ListImportsResponse
s@ListImportsResponse' {} Maybe [ImportsListItem]
a -> ListImportsResponse
s {$sel:imports:ListImportsResponse' :: Maybe [ImportsListItem]
imports = Maybe [ImportsListItem]
a} :: ListImportsResponse) 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 token you can use to get the next page of import results.
listImportsResponse_nextToken :: Lens.Lens' ListImportsResponse (Prelude.Maybe Prelude.Text)
listImportsResponse_nextToken :: Lens' ListImportsResponse (Maybe Text)
listImportsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListImportsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListImportsResponse' :: ListImportsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListImportsResponse
s@ListImportsResponse' {} Maybe Text
a -> ListImportsResponse
s {$sel:nextToken:ListImportsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListImportsResponse)

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

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