{-# 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.BatchGetCrawlers
-- 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 resource metadata for a given list of crawler names.
-- After calling the @ListCrawlers@ operation, you can call this operation
-- to access the data to which you have been granted permissions. This
-- operation supports all IAM permissions, including permission conditions
-- that uses tags.
module Amazonka.Glue.BatchGetCrawlers
  ( -- * Creating a Request
    BatchGetCrawlers (..),
    newBatchGetCrawlers,

    -- * Request Lenses
    batchGetCrawlers_crawlerNames,

    -- * Destructuring the Response
    BatchGetCrawlersResponse (..),
    newBatchGetCrawlersResponse,

    -- * Response Lenses
    batchGetCrawlersResponse_crawlers,
    batchGetCrawlersResponse_crawlersNotFound,
    batchGetCrawlersResponse_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:/ 'newBatchGetCrawlers' smart constructor.
data BatchGetCrawlers = BatchGetCrawlers'
  { -- | A list of crawler names, which might be the names returned from the
    -- @ListCrawlers@ operation.
    BatchGetCrawlers -> [Text]
crawlerNames :: [Prelude.Text]
  }
  deriving (BatchGetCrawlers -> BatchGetCrawlers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetCrawlers -> BatchGetCrawlers -> Bool
$c/= :: BatchGetCrawlers -> BatchGetCrawlers -> Bool
== :: BatchGetCrawlers -> BatchGetCrawlers -> Bool
$c== :: BatchGetCrawlers -> BatchGetCrawlers -> Bool
Prelude.Eq, ReadPrec [BatchGetCrawlers]
ReadPrec BatchGetCrawlers
Int -> ReadS BatchGetCrawlers
ReadS [BatchGetCrawlers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetCrawlers]
$creadListPrec :: ReadPrec [BatchGetCrawlers]
readPrec :: ReadPrec BatchGetCrawlers
$creadPrec :: ReadPrec BatchGetCrawlers
readList :: ReadS [BatchGetCrawlers]
$creadList :: ReadS [BatchGetCrawlers]
readsPrec :: Int -> ReadS BatchGetCrawlers
$creadsPrec :: Int -> ReadS BatchGetCrawlers
Prelude.Read, Int -> BatchGetCrawlers -> ShowS
[BatchGetCrawlers] -> ShowS
BatchGetCrawlers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetCrawlers] -> ShowS
$cshowList :: [BatchGetCrawlers] -> ShowS
show :: BatchGetCrawlers -> String
$cshow :: BatchGetCrawlers -> String
showsPrec :: Int -> BatchGetCrawlers -> ShowS
$cshowsPrec :: Int -> BatchGetCrawlers -> ShowS
Prelude.Show, forall x. Rep BatchGetCrawlers x -> BatchGetCrawlers
forall x. BatchGetCrawlers -> Rep BatchGetCrawlers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchGetCrawlers x -> BatchGetCrawlers
$cfrom :: forall x. BatchGetCrawlers -> Rep BatchGetCrawlers x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetCrawlers' 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:
--
-- 'crawlerNames', 'batchGetCrawlers_crawlerNames' - A list of crawler names, which might be the names returned from the
-- @ListCrawlers@ operation.
newBatchGetCrawlers ::
  BatchGetCrawlers
newBatchGetCrawlers :: BatchGetCrawlers
newBatchGetCrawlers =
  BatchGetCrawlers' {$sel:crawlerNames:BatchGetCrawlers' :: [Text]
crawlerNames = forall a. Monoid a => a
Prelude.mempty}

-- | A list of crawler names, which might be the names returned from the
-- @ListCrawlers@ operation.
batchGetCrawlers_crawlerNames :: Lens.Lens' BatchGetCrawlers [Prelude.Text]
batchGetCrawlers_crawlerNames :: Lens' BatchGetCrawlers [Text]
batchGetCrawlers_crawlerNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetCrawlers' {[Text]
crawlerNames :: [Text]
$sel:crawlerNames:BatchGetCrawlers' :: BatchGetCrawlers -> [Text]
crawlerNames} -> [Text]
crawlerNames) (\s :: BatchGetCrawlers
s@BatchGetCrawlers' {} [Text]
a -> BatchGetCrawlers
s {$sel:crawlerNames:BatchGetCrawlers' :: [Text]
crawlerNames = [Text]
a} :: BatchGetCrawlers) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchGetCrawlers where
  type
    AWSResponse BatchGetCrawlers =
      BatchGetCrawlersResponse
  request :: (Service -> Service)
-> BatchGetCrawlers -> Request BatchGetCrawlers
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 BatchGetCrawlers
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse BatchGetCrawlers)))
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 [Crawler] -> Maybe [Text] -> Int -> BatchGetCrawlersResponse
BatchGetCrawlersResponse'
            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
"Crawlers" 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
"CrawlersNotFound"
                            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 BatchGetCrawlers where
  hashWithSalt :: Int -> BatchGetCrawlers -> Int
hashWithSalt Int
_salt BatchGetCrawlers' {[Text]
crawlerNames :: [Text]
$sel:crawlerNames:BatchGetCrawlers' :: BatchGetCrawlers -> [Text]
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
crawlerNames

instance Prelude.NFData BatchGetCrawlers where
  rnf :: BatchGetCrawlers -> ()
rnf BatchGetCrawlers' {[Text]
crawlerNames :: [Text]
$sel:crawlerNames:BatchGetCrawlers' :: BatchGetCrawlers -> [Text]
..} = forall a. NFData a => a -> ()
Prelude.rnf [Text]
crawlerNames

instance Data.ToHeaders BatchGetCrawlers where
  toHeaders :: BatchGetCrawlers -> 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.BatchGetCrawlers" :: 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 BatchGetCrawlers where
  toJSON :: BatchGetCrawlers -> Value
toJSON BatchGetCrawlers' {[Text]
crawlerNames :: [Text]
$sel:crawlerNames:BatchGetCrawlers' :: BatchGetCrawlers -> [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"CrawlerNames" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
crawlerNames)]
      )

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

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

-- | /See:/ 'newBatchGetCrawlersResponse' smart constructor.
data BatchGetCrawlersResponse = BatchGetCrawlersResponse'
  { -- | A list of crawler definitions.
    BatchGetCrawlersResponse -> Maybe [Crawler]
crawlers :: Prelude.Maybe [Crawler],
    -- | A list of names of crawlers that were not found.
    BatchGetCrawlersResponse -> Maybe [Text]
crawlersNotFound :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    BatchGetCrawlersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchGetCrawlersResponse -> BatchGetCrawlersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetCrawlersResponse -> BatchGetCrawlersResponse -> Bool
$c/= :: BatchGetCrawlersResponse -> BatchGetCrawlersResponse -> Bool
== :: BatchGetCrawlersResponse -> BatchGetCrawlersResponse -> Bool
$c== :: BatchGetCrawlersResponse -> BatchGetCrawlersResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetCrawlersResponse]
ReadPrec BatchGetCrawlersResponse
Int -> ReadS BatchGetCrawlersResponse
ReadS [BatchGetCrawlersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetCrawlersResponse]
$creadListPrec :: ReadPrec [BatchGetCrawlersResponse]
readPrec :: ReadPrec BatchGetCrawlersResponse
$creadPrec :: ReadPrec BatchGetCrawlersResponse
readList :: ReadS [BatchGetCrawlersResponse]
$creadList :: ReadS [BatchGetCrawlersResponse]
readsPrec :: Int -> ReadS BatchGetCrawlersResponse
$creadsPrec :: Int -> ReadS BatchGetCrawlersResponse
Prelude.Read, Int -> BatchGetCrawlersResponse -> ShowS
[BatchGetCrawlersResponse] -> ShowS
BatchGetCrawlersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetCrawlersResponse] -> ShowS
$cshowList :: [BatchGetCrawlersResponse] -> ShowS
show :: BatchGetCrawlersResponse -> String
$cshow :: BatchGetCrawlersResponse -> String
showsPrec :: Int -> BatchGetCrawlersResponse -> ShowS
$cshowsPrec :: Int -> BatchGetCrawlersResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetCrawlersResponse x -> BatchGetCrawlersResponse
forall x.
BatchGetCrawlersResponse -> Rep BatchGetCrawlersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetCrawlersResponse x -> BatchGetCrawlersResponse
$cfrom :: forall x.
BatchGetCrawlersResponse -> Rep BatchGetCrawlersResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetCrawlersResponse' 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:
--
-- 'crawlers', 'batchGetCrawlersResponse_crawlers' - A list of crawler definitions.
--
-- 'crawlersNotFound', 'batchGetCrawlersResponse_crawlersNotFound' - A list of names of crawlers that were not found.
--
-- 'httpStatus', 'batchGetCrawlersResponse_httpStatus' - The response's http status code.
newBatchGetCrawlersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetCrawlersResponse
newBatchGetCrawlersResponse :: Int -> BatchGetCrawlersResponse
newBatchGetCrawlersResponse Int
pHttpStatus_ =
  BatchGetCrawlersResponse'
    { $sel:crawlers:BatchGetCrawlersResponse' :: Maybe [Crawler]
crawlers =
        forall a. Maybe a
Prelude.Nothing,
      $sel:crawlersNotFound:BatchGetCrawlersResponse' :: Maybe [Text]
crawlersNotFound = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchGetCrawlersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of crawler definitions.
batchGetCrawlersResponse_crawlers :: Lens.Lens' BatchGetCrawlersResponse (Prelude.Maybe [Crawler])
batchGetCrawlersResponse_crawlers :: Lens' BatchGetCrawlersResponse (Maybe [Crawler])
batchGetCrawlersResponse_crawlers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetCrawlersResponse' {Maybe [Crawler]
crawlers :: Maybe [Crawler]
$sel:crawlers:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Maybe [Crawler]
crawlers} -> Maybe [Crawler]
crawlers) (\s :: BatchGetCrawlersResponse
s@BatchGetCrawlersResponse' {} Maybe [Crawler]
a -> BatchGetCrawlersResponse
s {$sel:crawlers:BatchGetCrawlersResponse' :: Maybe [Crawler]
crawlers = Maybe [Crawler]
a} :: BatchGetCrawlersResponse) 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 list of names of crawlers that were not found.
batchGetCrawlersResponse_crawlersNotFound :: Lens.Lens' BatchGetCrawlersResponse (Prelude.Maybe [Prelude.Text])
batchGetCrawlersResponse_crawlersNotFound :: Lens' BatchGetCrawlersResponse (Maybe [Text])
batchGetCrawlersResponse_crawlersNotFound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetCrawlersResponse' {Maybe [Text]
crawlersNotFound :: Maybe [Text]
$sel:crawlersNotFound:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Maybe [Text]
crawlersNotFound} -> Maybe [Text]
crawlersNotFound) (\s :: BatchGetCrawlersResponse
s@BatchGetCrawlersResponse' {} Maybe [Text]
a -> BatchGetCrawlersResponse
s {$sel:crawlersNotFound:BatchGetCrawlersResponse' :: Maybe [Text]
crawlersNotFound = Maybe [Text]
a} :: BatchGetCrawlersResponse) 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.
batchGetCrawlersResponse_httpStatus :: Lens.Lens' BatchGetCrawlersResponse Prelude.Int
batchGetCrawlersResponse_httpStatus :: Lens' BatchGetCrawlersResponse Int
batchGetCrawlersResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetCrawlersResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchGetCrawlersResponse
s@BatchGetCrawlersResponse' {} Int
a -> BatchGetCrawlersResponse
s {$sel:httpStatus:BatchGetCrawlersResponse' :: Int
httpStatus = Int
a} :: BatchGetCrawlersResponse)

instance Prelude.NFData BatchGetCrawlersResponse where
  rnf :: BatchGetCrawlersResponse -> ()
rnf BatchGetCrawlersResponse' {Int
Maybe [Text]
Maybe [Crawler]
httpStatus :: Int
crawlersNotFound :: Maybe [Text]
crawlers :: Maybe [Crawler]
$sel:httpStatus:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Int
$sel:crawlersNotFound:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Maybe [Text]
$sel:crawlers:BatchGetCrawlersResponse' :: BatchGetCrawlersResponse -> Maybe [Crawler]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Crawler]
crawlers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
crawlersNotFound
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus