{-# 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.BatchGetDataQualityResult
-- 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 data quality results for the specified result IDs.
module Amazonka.Glue.BatchGetDataQualityResult
  ( -- * Creating a Request
    BatchGetDataQualityResult (..),
    newBatchGetDataQualityResult,

    -- * Request Lenses
    batchGetDataQualityResult_resultIds,

    -- * Destructuring the Response
    BatchGetDataQualityResultResponse (..),
    newBatchGetDataQualityResultResponse,

    -- * Response Lenses
    batchGetDataQualityResultResponse_resultsNotFound,
    batchGetDataQualityResultResponse_httpStatus,
    batchGetDataQualityResultResponse_results,
  )
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:/ 'newBatchGetDataQualityResult' smart constructor.
data BatchGetDataQualityResult = BatchGetDataQualityResult'
  { -- | A list of unique result IDs for the data quality results.
    BatchGetDataQualityResult -> NonEmpty Text
resultIds :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchGetDataQualityResult -> BatchGetDataQualityResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetDataQualityResult -> BatchGetDataQualityResult -> Bool
$c/= :: BatchGetDataQualityResult -> BatchGetDataQualityResult -> Bool
== :: BatchGetDataQualityResult -> BatchGetDataQualityResult -> Bool
$c== :: BatchGetDataQualityResult -> BatchGetDataQualityResult -> Bool
Prelude.Eq, ReadPrec [BatchGetDataQualityResult]
ReadPrec BatchGetDataQualityResult
Int -> ReadS BatchGetDataQualityResult
ReadS [BatchGetDataQualityResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetDataQualityResult]
$creadListPrec :: ReadPrec [BatchGetDataQualityResult]
readPrec :: ReadPrec BatchGetDataQualityResult
$creadPrec :: ReadPrec BatchGetDataQualityResult
readList :: ReadS [BatchGetDataQualityResult]
$creadList :: ReadS [BatchGetDataQualityResult]
readsPrec :: Int -> ReadS BatchGetDataQualityResult
$creadsPrec :: Int -> ReadS BatchGetDataQualityResult
Prelude.Read, Int -> BatchGetDataQualityResult -> ShowS
[BatchGetDataQualityResult] -> ShowS
BatchGetDataQualityResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetDataQualityResult] -> ShowS
$cshowList :: [BatchGetDataQualityResult] -> ShowS
show :: BatchGetDataQualityResult -> String
$cshow :: BatchGetDataQualityResult -> String
showsPrec :: Int -> BatchGetDataQualityResult -> ShowS
$cshowsPrec :: Int -> BatchGetDataQualityResult -> ShowS
Prelude.Show, forall x.
Rep BatchGetDataQualityResult x -> BatchGetDataQualityResult
forall x.
BatchGetDataQualityResult -> Rep BatchGetDataQualityResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetDataQualityResult x -> BatchGetDataQualityResult
$cfrom :: forall x.
BatchGetDataQualityResult -> Rep BatchGetDataQualityResult x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetDataQualityResult' 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:
--
-- 'resultIds', 'batchGetDataQualityResult_resultIds' - A list of unique result IDs for the data quality results.
newBatchGetDataQualityResult ::
  -- | 'resultIds'
  Prelude.NonEmpty Prelude.Text ->
  BatchGetDataQualityResult
newBatchGetDataQualityResult :: NonEmpty Text -> BatchGetDataQualityResult
newBatchGetDataQualityResult NonEmpty Text
pResultIds_ =
  BatchGetDataQualityResult'
    { $sel:resultIds:BatchGetDataQualityResult' :: NonEmpty Text
resultIds =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pResultIds_
    }

-- | A list of unique result IDs for the data quality results.
batchGetDataQualityResult_resultIds :: Lens.Lens' BatchGetDataQualityResult (Prelude.NonEmpty Prelude.Text)
batchGetDataQualityResult_resultIds :: Lens' BatchGetDataQualityResult (NonEmpty Text)
batchGetDataQualityResult_resultIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDataQualityResult' {NonEmpty Text
resultIds :: NonEmpty Text
$sel:resultIds:BatchGetDataQualityResult' :: BatchGetDataQualityResult -> NonEmpty Text
resultIds} -> NonEmpty Text
resultIds) (\s :: BatchGetDataQualityResult
s@BatchGetDataQualityResult' {} NonEmpty Text
a -> BatchGetDataQualityResult
s {$sel:resultIds:BatchGetDataQualityResult' :: NonEmpty Text
resultIds = NonEmpty Text
a} :: BatchGetDataQualityResult) 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 BatchGetDataQualityResult where
  type
    AWSResponse BatchGetDataQualityResult =
      BatchGetDataQualityResultResponse
  request :: (Service -> Service)
-> BatchGetDataQualityResult -> Request BatchGetDataQualityResult
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 BatchGetDataQualityResult
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchGetDataQualityResult)))
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 (NonEmpty Text)
-> Int -> [DataQualityResult] -> BatchGetDataQualityResultResponse
BatchGetDataQualityResultResponse'
            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
"ResultsNotFound")
            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))
            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
"Results" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable BatchGetDataQualityResult where
  hashWithSalt :: Int -> BatchGetDataQualityResult -> Int
hashWithSalt Int
_salt BatchGetDataQualityResult' {NonEmpty Text
resultIds :: NonEmpty Text
$sel:resultIds:BatchGetDataQualityResult' :: BatchGetDataQualityResult -> NonEmpty Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
resultIds

instance Prelude.NFData BatchGetDataQualityResult where
  rnf :: BatchGetDataQualityResult -> ()
rnf BatchGetDataQualityResult' {NonEmpty Text
resultIds :: NonEmpty Text
$sel:resultIds:BatchGetDataQualityResult' :: BatchGetDataQualityResult -> NonEmpty Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
resultIds

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

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

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

-- | /See:/ 'newBatchGetDataQualityResultResponse' smart constructor.
data BatchGetDataQualityResultResponse = BatchGetDataQualityResultResponse'
  { -- | A list of result IDs for which results were not found.
    BatchGetDataQualityResultResponse -> Maybe (NonEmpty Text)
resultsNotFound :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The response's http status code.
    BatchGetDataQualityResultResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of @DataQualityResult@ objects representing the data quality
    -- results.
    BatchGetDataQualityResultResponse -> [DataQualityResult]
results :: [DataQualityResult]
  }
  deriving (BatchGetDataQualityResultResponse
-> BatchGetDataQualityResultResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetDataQualityResultResponse
-> BatchGetDataQualityResultResponse -> Bool
$c/= :: BatchGetDataQualityResultResponse
-> BatchGetDataQualityResultResponse -> Bool
== :: BatchGetDataQualityResultResponse
-> BatchGetDataQualityResultResponse -> Bool
$c== :: BatchGetDataQualityResultResponse
-> BatchGetDataQualityResultResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetDataQualityResultResponse]
ReadPrec BatchGetDataQualityResultResponse
Int -> ReadS BatchGetDataQualityResultResponse
ReadS [BatchGetDataQualityResultResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetDataQualityResultResponse]
$creadListPrec :: ReadPrec [BatchGetDataQualityResultResponse]
readPrec :: ReadPrec BatchGetDataQualityResultResponse
$creadPrec :: ReadPrec BatchGetDataQualityResultResponse
readList :: ReadS [BatchGetDataQualityResultResponse]
$creadList :: ReadS [BatchGetDataQualityResultResponse]
readsPrec :: Int -> ReadS BatchGetDataQualityResultResponse
$creadsPrec :: Int -> ReadS BatchGetDataQualityResultResponse
Prelude.Read, Int -> BatchGetDataQualityResultResponse -> ShowS
[BatchGetDataQualityResultResponse] -> ShowS
BatchGetDataQualityResultResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetDataQualityResultResponse] -> ShowS
$cshowList :: [BatchGetDataQualityResultResponse] -> ShowS
show :: BatchGetDataQualityResultResponse -> String
$cshow :: BatchGetDataQualityResultResponse -> String
showsPrec :: Int -> BatchGetDataQualityResultResponse -> ShowS
$cshowsPrec :: Int -> BatchGetDataQualityResultResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetDataQualityResultResponse x
-> BatchGetDataQualityResultResponse
forall x.
BatchGetDataQualityResultResponse
-> Rep BatchGetDataQualityResultResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetDataQualityResultResponse x
-> BatchGetDataQualityResultResponse
$cfrom :: forall x.
BatchGetDataQualityResultResponse
-> Rep BatchGetDataQualityResultResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetDataQualityResultResponse' 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:
--
-- 'resultsNotFound', 'batchGetDataQualityResultResponse_resultsNotFound' - A list of result IDs for which results were not found.
--
-- 'httpStatus', 'batchGetDataQualityResultResponse_httpStatus' - The response's http status code.
--
-- 'results', 'batchGetDataQualityResultResponse_results' - A list of @DataQualityResult@ objects representing the data quality
-- results.
newBatchGetDataQualityResultResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetDataQualityResultResponse
newBatchGetDataQualityResultResponse :: Int -> BatchGetDataQualityResultResponse
newBatchGetDataQualityResultResponse Int
pHttpStatus_ =
  BatchGetDataQualityResultResponse'
    { $sel:resultsNotFound:BatchGetDataQualityResultResponse' :: Maybe (NonEmpty Text)
resultsNotFound =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchGetDataQualityResultResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:results:BatchGetDataQualityResultResponse' :: [DataQualityResult]
results = forall a. Monoid a => a
Prelude.mempty
    }

-- | A list of result IDs for which results were not found.
batchGetDataQualityResultResponse_resultsNotFound :: Lens.Lens' BatchGetDataQualityResultResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
batchGetDataQualityResultResponse_resultsNotFound :: Lens' BatchGetDataQualityResultResponse (Maybe (NonEmpty Text))
batchGetDataQualityResultResponse_resultsNotFound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDataQualityResultResponse' {Maybe (NonEmpty Text)
resultsNotFound :: Maybe (NonEmpty Text)
$sel:resultsNotFound:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> Maybe (NonEmpty Text)
resultsNotFound} -> Maybe (NonEmpty Text)
resultsNotFound) (\s :: BatchGetDataQualityResultResponse
s@BatchGetDataQualityResultResponse' {} Maybe (NonEmpty Text)
a -> BatchGetDataQualityResultResponse
s {$sel:resultsNotFound:BatchGetDataQualityResultResponse' :: Maybe (NonEmpty Text)
resultsNotFound = Maybe (NonEmpty Text)
a} :: BatchGetDataQualityResultResponse) 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.
batchGetDataQualityResultResponse_httpStatus :: Lens.Lens' BatchGetDataQualityResultResponse Prelude.Int
batchGetDataQualityResultResponse_httpStatus :: Lens' BatchGetDataQualityResultResponse Int
batchGetDataQualityResultResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDataQualityResultResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchGetDataQualityResultResponse
s@BatchGetDataQualityResultResponse' {} Int
a -> BatchGetDataQualityResultResponse
s {$sel:httpStatus:BatchGetDataQualityResultResponse' :: Int
httpStatus = Int
a} :: BatchGetDataQualityResultResponse)

-- | A list of @DataQualityResult@ objects representing the data quality
-- results.
batchGetDataQualityResultResponse_results :: Lens.Lens' BatchGetDataQualityResultResponse [DataQualityResult]
batchGetDataQualityResultResponse_results :: Lens' BatchGetDataQualityResultResponse [DataQualityResult]
batchGetDataQualityResultResponse_results = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetDataQualityResultResponse' {[DataQualityResult]
results :: [DataQualityResult]
$sel:results:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> [DataQualityResult]
results} -> [DataQualityResult]
results) (\s :: BatchGetDataQualityResultResponse
s@BatchGetDataQualityResultResponse' {} [DataQualityResult]
a -> BatchGetDataQualityResultResponse
s {$sel:results:BatchGetDataQualityResultResponse' :: [DataQualityResult]
results = [DataQualityResult]
a} :: BatchGetDataQualityResultResponse) 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
  Prelude.NFData
    BatchGetDataQualityResultResponse
  where
  rnf :: BatchGetDataQualityResultResponse -> ()
rnf BatchGetDataQualityResultResponse' {Int
[DataQualityResult]
Maybe (NonEmpty Text)
results :: [DataQualityResult]
httpStatus :: Int
resultsNotFound :: Maybe (NonEmpty Text)
$sel:results:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> [DataQualityResult]
$sel:httpStatus:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> Int
$sel:resultsNotFound:BatchGetDataQualityResultResponse' :: BatchGetDataQualityResultResponse -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
resultsNotFound
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DataQualityResult]
results