{-# 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.Glue.ListCrawls
-- 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 all the crawls of a specified crawler. Returns only the crawls
-- that have occurred since the launch date of the crawler history feature,
-- and only retains up to 12 months of crawls. Older crawls will not be
-- returned.
--
-- You may use this API to:
--
-- -   Retrive all the crawls of a specified crawler.
--
-- -   Retrieve all the crawls of a specified crawler within a limited
--     count.
--
-- -   Retrieve all the crawls of a specified crawler in a specific time
--     range.
--
-- -   Retrieve all the crawls of a specified crawler with a particular
--     state, crawl ID, or DPU hour value.
module Amazonka.Glue.ListCrawls
  ( -- * Creating a Request
    ListCrawls (..),
    newListCrawls,

    -- * Request Lenses
    listCrawls_filters,
    listCrawls_maxResults,
    listCrawls_nextToken,
    listCrawls_crawlerName,

    -- * Destructuring the Response
    ListCrawlsResponse (..),
    newListCrawlsResponse,

    -- * Response Lenses
    listCrawlsResponse_crawls,
    listCrawlsResponse_nextToken,
    listCrawlsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListCrawls' smart constructor.
data ListCrawls = ListCrawls'
  { -- | Filters the crawls by the criteria you specify in a list of
    -- @CrawlsFilter@ objects.
    ListCrawls -> Maybe [CrawlsFilter]
filters :: Prelude.Maybe [CrawlsFilter],
    -- | The maximum number of results to return. The default is 20, and maximum
    -- is 100.
    ListCrawls -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A continuation token, if this is a continuation call.
    ListCrawls -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the crawler whose runs you want to retrieve.
    ListCrawls -> Text
crawlerName :: Prelude.Text
  }
  deriving (ListCrawls -> ListCrawls -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCrawls -> ListCrawls -> Bool
$c/= :: ListCrawls -> ListCrawls -> Bool
== :: ListCrawls -> ListCrawls -> Bool
$c== :: ListCrawls -> ListCrawls -> Bool
Prelude.Eq, ReadPrec [ListCrawls]
ReadPrec ListCrawls
Int -> ReadS ListCrawls
ReadS [ListCrawls]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCrawls]
$creadListPrec :: ReadPrec [ListCrawls]
readPrec :: ReadPrec ListCrawls
$creadPrec :: ReadPrec ListCrawls
readList :: ReadS [ListCrawls]
$creadList :: ReadS [ListCrawls]
readsPrec :: Int -> ReadS ListCrawls
$creadsPrec :: Int -> ReadS ListCrawls
Prelude.Read, Int -> ListCrawls -> ShowS
[ListCrawls] -> ShowS
ListCrawls -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCrawls] -> ShowS
$cshowList :: [ListCrawls] -> ShowS
show :: ListCrawls -> String
$cshow :: ListCrawls -> String
showsPrec :: Int -> ListCrawls -> ShowS
$cshowsPrec :: Int -> ListCrawls -> ShowS
Prelude.Show, forall x. Rep ListCrawls x -> ListCrawls
forall x. ListCrawls -> Rep ListCrawls x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCrawls x -> ListCrawls
$cfrom :: forall x. ListCrawls -> Rep ListCrawls x
Prelude.Generic)

-- |
-- Create a value of 'ListCrawls' 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', 'listCrawls_filters' - Filters the crawls by the criteria you specify in a list of
-- @CrawlsFilter@ objects.
--
-- 'maxResults', 'listCrawls_maxResults' - The maximum number of results to return. The default is 20, and maximum
-- is 100.
--
-- 'nextToken', 'listCrawls_nextToken' - A continuation token, if this is a continuation call.
--
-- 'crawlerName', 'listCrawls_crawlerName' - The name of the crawler whose runs you want to retrieve.
newListCrawls ::
  -- | 'crawlerName'
  Prelude.Text ->
  ListCrawls
newListCrawls :: Text -> ListCrawls
newListCrawls Text
pCrawlerName_ =
  ListCrawls'
    { $sel:filters:ListCrawls' :: Maybe [CrawlsFilter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListCrawls' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCrawls' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:crawlerName:ListCrawls' :: Text
crawlerName = Text
pCrawlerName_
    }

-- | Filters the crawls by the criteria you specify in a list of
-- @CrawlsFilter@ objects.
listCrawls_filters :: Lens.Lens' ListCrawls (Prelude.Maybe [CrawlsFilter])
listCrawls_filters :: Lens' ListCrawls (Maybe [CrawlsFilter])
listCrawls_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawls' {Maybe [CrawlsFilter]
filters :: Maybe [CrawlsFilter]
$sel:filters:ListCrawls' :: ListCrawls -> Maybe [CrawlsFilter]
filters} -> Maybe [CrawlsFilter]
filters) (\s :: ListCrawls
s@ListCrawls' {} Maybe [CrawlsFilter]
a -> ListCrawls
s {$sel:filters:ListCrawls' :: Maybe [CrawlsFilter]
filters = Maybe [CrawlsFilter]
a} :: ListCrawls) 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 results to return. The default is 20, and maximum
-- is 100.
listCrawls_maxResults :: Lens.Lens' ListCrawls (Prelude.Maybe Prelude.Natural)
listCrawls_maxResults :: Lens' ListCrawls (Maybe Natural)
listCrawls_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawls' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListCrawls' :: ListCrawls -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListCrawls
s@ListCrawls' {} Maybe Natural
a -> ListCrawls
s {$sel:maxResults:ListCrawls' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListCrawls)

-- | A continuation token, if this is a continuation call.
listCrawls_nextToken :: Lens.Lens' ListCrawls (Prelude.Maybe Prelude.Text)
listCrawls_nextToken :: Lens' ListCrawls (Maybe Text)
listCrawls_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawls' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCrawls' :: ListCrawls -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCrawls
s@ListCrawls' {} Maybe Text
a -> ListCrawls
s {$sel:nextToken:ListCrawls' :: Maybe Text
nextToken = Maybe Text
a} :: ListCrawls)

-- | The name of the crawler whose runs you want to retrieve.
listCrawls_crawlerName :: Lens.Lens' ListCrawls Prelude.Text
listCrawls_crawlerName :: Lens' ListCrawls Text
listCrawls_crawlerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawls' {Text
crawlerName :: Text
$sel:crawlerName:ListCrawls' :: ListCrawls -> Text
crawlerName} -> Text
crawlerName) (\s :: ListCrawls
s@ListCrawls' {} Text
a -> ListCrawls
s {$sel:crawlerName:ListCrawls' :: Text
crawlerName = Text
a} :: ListCrawls)

instance Core.AWSRequest ListCrawls where
  type AWSResponse ListCrawls = ListCrawlsResponse
  request :: (Service -> Service) -> ListCrawls -> Request ListCrawls
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 ListCrawls
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListCrawls)))
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 [CrawlerHistory] -> Maybe Text -> Int -> ListCrawlsResponse
ListCrawlsResponse'
            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
"Crawls" 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 ListCrawls where
  hashWithSalt :: Int -> ListCrawls -> Int
hashWithSalt Int
_salt ListCrawls' {Maybe Natural
Maybe [CrawlsFilter]
Maybe Text
Text
crawlerName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [CrawlsFilter]
$sel:crawlerName:ListCrawls' :: ListCrawls -> Text
$sel:nextToken:ListCrawls' :: ListCrawls -> Maybe Text
$sel:maxResults:ListCrawls' :: ListCrawls -> Maybe Natural
$sel:filters:ListCrawls' :: ListCrawls -> Maybe [CrawlsFilter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CrawlsFilter]
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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
crawlerName

instance Prelude.NFData ListCrawls where
  rnf :: ListCrawls -> ()
rnf ListCrawls' {Maybe Natural
Maybe [CrawlsFilter]
Maybe Text
Text
crawlerName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [CrawlsFilter]
$sel:crawlerName:ListCrawls' :: ListCrawls -> Text
$sel:nextToken:ListCrawls' :: ListCrawls -> Maybe Text
$sel:maxResults:ListCrawls' :: ListCrawls -> Maybe Natural
$sel:filters:ListCrawls' :: ListCrawls -> Maybe [CrawlsFilter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CrawlsFilter]
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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
crawlerName

instance Data.ToHeaders ListCrawls where
  toHeaders :: ListCrawls -> 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
"AWSGlue.ListCrawls" :: 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 ListCrawls where
  toJSON :: ListCrawls -> Value
toJSON ListCrawls' {Maybe Natural
Maybe [CrawlsFilter]
Maybe Text
Text
crawlerName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [CrawlsFilter]
$sel:crawlerName:ListCrawls' :: ListCrawls -> Text
$sel:nextToken:ListCrawls' :: ListCrawls -> Maybe Text
$sel:maxResults:ListCrawls' :: ListCrawls -> Maybe Natural
$sel:filters:ListCrawls' :: ListCrawls -> Maybe [CrawlsFilter]
..} =
    [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 [CrawlsFilter]
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,
            forall a. a -> Maybe a
Prelude.Just (Key
"CrawlerName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
crawlerName)
          ]
      )

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

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

-- | /See:/ 'newListCrawlsResponse' smart constructor.
data ListCrawlsResponse = ListCrawlsResponse'
  { -- | A list of @CrawlerHistory@ objects representing the crawl runs that meet
    -- your criteria.
    ListCrawlsResponse -> Maybe [CrawlerHistory]
crawls :: Prelude.Maybe [CrawlerHistory],
    -- | A continuation token for paginating the returned list of tokens,
    -- returned if the current segment of the list is not the last.
    ListCrawlsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCrawlsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCrawlsResponse -> ListCrawlsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCrawlsResponse -> ListCrawlsResponse -> Bool
$c/= :: ListCrawlsResponse -> ListCrawlsResponse -> Bool
== :: ListCrawlsResponse -> ListCrawlsResponse -> Bool
$c== :: ListCrawlsResponse -> ListCrawlsResponse -> Bool
Prelude.Eq, ReadPrec [ListCrawlsResponse]
ReadPrec ListCrawlsResponse
Int -> ReadS ListCrawlsResponse
ReadS [ListCrawlsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCrawlsResponse]
$creadListPrec :: ReadPrec [ListCrawlsResponse]
readPrec :: ReadPrec ListCrawlsResponse
$creadPrec :: ReadPrec ListCrawlsResponse
readList :: ReadS [ListCrawlsResponse]
$creadList :: ReadS [ListCrawlsResponse]
readsPrec :: Int -> ReadS ListCrawlsResponse
$creadsPrec :: Int -> ReadS ListCrawlsResponse
Prelude.Read, Int -> ListCrawlsResponse -> ShowS
[ListCrawlsResponse] -> ShowS
ListCrawlsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCrawlsResponse] -> ShowS
$cshowList :: [ListCrawlsResponse] -> ShowS
show :: ListCrawlsResponse -> String
$cshow :: ListCrawlsResponse -> String
showsPrec :: Int -> ListCrawlsResponse -> ShowS
$cshowsPrec :: Int -> ListCrawlsResponse -> ShowS
Prelude.Show, forall x. Rep ListCrawlsResponse x -> ListCrawlsResponse
forall x. ListCrawlsResponse -> Rep ListCrawlsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCrawlsResponse x -> ListCrawlsResponse
$cfrom :: forall x. ListCrawlsResponse -> Rep ListCrawlsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCrawlsResponse' 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:
--
-- 'crawls', 'listCrawlsResponse_crawls' - A list of @CrawlerHistory@ objects representing the crawl runs that meet
-- your criteria.
--
-- 'nextToken', 'listCrawlsResponse_nextToken' - A continuation token for paginating the returned list of tokens,
-- returned if the current segment of the list is not the last.
--
-- 'httpStatus', 'listCrawlsResponse_httpStatus' - The response's http status code.
newListCrawlsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCrawlsResponse
newListCrawlsResponse :: Int -> ListCrawlsResponse
newListCrawlsResponse Int
pHttpStatus_ =
  ListCrawlsResponse'
    { $sel:crawls:ListCrawlsResponse' :: Maybe [CrawlerHistory]
crawls = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCrawlsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCrawlsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of @CrawlerHistory@ objects representing the crawl runs that meet
-- your criteria.
listCrawlsResponse_crawls :: Lens.Lens' ListCrawlsResponse (Prelude.Maybe [CrawlerHistory])
listCrawlsResponse_crawls :: Lens' ListCrawlsResponse (Maybe [CrawlerHistory])
listCrawlsResponse_crawls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawlsResponse' {Maybe [CrawlerHistory]
crawls :: Maybe [CrawlerHistory]
$sel:crawls:ListCrawlsResponse' :: ListCrawlsResponse -> Maybe [CrawlerHistory]
crawls} -> Maybe [CrawlerHistory]
crawls) (\s :: ListCrawlsResponse
s@ListCrawlsResponse' {} Maybe [CrawlerHistory]
a -> ListCrawlsResponse
s {$sel:crawls:ListCrawlsResponse' :: Maybe [CrawlerHistory]
crawls = Maybe [CrawlerHistory]
a} :: ListCrawlsResponse) 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 continuation token for paginating the returned list of tokens,
-- returned if the current segment of the list is not the last.
listCrawlsResponse_nextToken :: Lens.Lens' ListCrawlsResponse (Prelude.Maybe Prelude.Text)
listCrawlsResponse_nextToken :: Lens' ListCrawlsResponse (Maybe Text)
listCrawlsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCrawlsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCrawlsResponse' :: ListCrawlsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCrawlsResponse
s@ListCrawlsResponse' {} Maybe Text
a -> ListCrawlsResponse
s {$sel:nextToken:ListCrawlsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCrawlsResponse)

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

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