{-# 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.Textract.GetDocumentTextDetection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the results for an Amazon Textract asynchronous operation that
-- detects text in a document. Amazon Textract can detect lines of text and
-- the words that make up a line of text.
--
-- You start asynchronous text detection by calling
-- StartDocumentTextDetection, which returns a job identifier (@JobId@).
-- When the text detection operation finishes, Amazon Textract publishes a
-- completion status to the Amazon Simple Notification Service (Amazon SNS)
-- topic that\'s registered in the initial call to
-- @StartDocumentTextDetection@. To get the results of the text-detection
-- operation, first check that the status value published to the Amazon SNS
-- topic is @SUCCEEDED@. If so, call @GetDocumentTextDetection@, and pass
-- the job identifier (@JobId@) from the initial call to
-- @StartDocumentTextDetection@.
--
-- @GetDocumentTextDetection@ returns an array of Block objects.
--
-- Each document page has as an associated @Block@ of type PAGE. Each PAGE
-- @Block@ object is the parent of LINE @Block@ objects that represent the
-- lines of detected text on a page. A LINE @Block@ object is a parent for
-- each word that makes up the line. Words are represented by @Block@
-- objects of type WORD.
--
-- Use the MaxResults parameter to limit the number of blocks that are
-- returned. If there are more results than specified in @MaxResults@, the
-- value of @NextToken@ in the operation response contains a pagination
-- token for getting the next set of results. To get the next page of
-- results, call @GetDocumentTextDetection@, and populate the @NextToken@
-- request parameter with the token value that\'s returned from the
-- previous call to @GetDocumentTextDetection@.
--
-- For more information, see
-- <https://docs.aws.amazon.com/textract/latest/dg/how-it-works-detecting.html Document Text Detection>.
module Amazonka.Textract.GetDocumentTextDetection
  ( -- * Creating a Request
    GetDocumentTextDetection (..),
    newGetDocumentTextDetection,

    -- * Request Lenses
    getDocumentTextDetection_maxResults,
    getDocumentTextDetection_nextToken,
    getDocumentTextDetection_jobId,

    -- * Destructuring the Response
    GetDocumentTextDetectionResponse (..),
    newGetDocumentTextDetectionResponse,

    -- * Response Lenses
    getDocumentTextDetectionResponse_blocks,
    getDocumentTextDetectionResponse_detectDocumentTextModelVersion,
    getDocumentTextDetectionResponse_documentMetadata,
    getDocumentTextDetectionResponse_jobStatus,
    getDocumentTextDetectionResponse_nextToken,
    getDocumentTextDetectionResponse_statusMessage,
    getDocumentTextDetectionResponse_warnings,
    getDocumentTextDetectionResponse_httpStatus,
  )
where

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
import Amazonka.Textract.Types

-- | /See:/ 'newGetDocumentTextDetection' smart constructor.
data GetDocumentTextDetection = GetDocumentTextDetection'
  { -- | The maximum number of results to return per paginated call. The largest
    -- value you can specify is 1,000. If you specify a value greater than
    -- 1,000, a maximum of 1,000 results is returned. The default value is
    -- 1,000.
    GetDocumentTextDetection -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there are more blocks
    -- to retrieve), Amazon Textract returns a pagination token in the
    -- response. You can use this pagination token to retrieve the next set of
    -- blocks.
    GetDocumentTextDetection -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the text detection job. The @JobId@ is returned
    -- from @StartDocumentTextDetection@. A @JobId@ value is only valid for 7
    -- days.
    GetDocumentTextDetection -> Text
jobId :: Prelude.Text
  }
  deriving (GetDocumentTextDetection -> GetDocumentTextDetection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDocumentTextDetection -> GetDocumentTextDetection -> Bool
$c/= :: GetDocumentTextDetection -> GetDocumentTextDetection -> Bool
== :: GetDocumentTextDetection -> GetDocumentTextDetection -> Bool
$c== :: GetDocumentTextDetection -> GetDocumentTextDetection -> Bool
Prelude.Eq, ReadPrec [GetDocumentTextDetection]
ReadPrec GetDocumentTextDetection
Int -> ReadS GetDocumentTextDetection
ReadS [GetDocumentTextDetection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDocumentTextDetection]
$creadListPrec :: ReadPrec [GetDocumentTextDetection]
readPrec :: ReadPrec GetDocumentTextDetection
$creadPrec :: ReadPrec GetDocumentTextDetection
readList :: ReadS [GetDocumentTextDetection]
$creadList :: ReadS [GetDocumentTextDetection]
readsPrec :: Int -> ReadS GetDocumentTextDetection
$creadsPrec :: Int -> ReadS GetDocumentTextDetection
Prelude.Read, Int -> GetDocumentTextDetection -> ShowS
[GetDocumentTextDetection] -> ShowS
GetDocumentTextDetection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDocumentTextDetection] -> ShowS
$cshowList :: [GetDocumentTextDetection] -> ShowS
show :: GetDocumentTextDetection -> String
$cshow :: GetDocumentTextDetection -> String
showsPrec :: Int -> GetDocumentTextDetection -> ShowS
$cshowsPrec :: Int -> GetDocumentTextDetection -> ShowS
Prelude.Show, forall x.
Rep GetDocumentTextDetection x -> GetDocumentTextDetection
forall x.
GetDocumentTextDetection -> Rep GetDocumentTextDetection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDocumentTextDetection x -> GetDocumentTextDetection
$cfrom :: forall x.
GetDocumentTextDetection -> Rep GetDocumentTextDetection x
Prelude.Generic)

-- |
-- Create a value of 'GetDocumentTextDetection' 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:
--
-- 'maxResults', 'getDocumentTextDetection_maxResults' - The maximum number of results to return per paginated call. The largest
-- value you can specify is 1,000. If you specify a value greater than
-- 1,000, a maximum of 1,000 results is returned. The default value is
-- 1,000.
--
-- 'nextToken', 'getDocumentTextDetection_nextToken' - If the previous response was incomplete (because there are more blocks
-- to retrieve), Amazon Textract returns a pagination token in the
-- response. You can use this pagination token to retrieve the next set of
-- blocks.
--
-- 'jobId', 'getDocumentTextDetection_jobId' - A unique identifier for the text detection job. The @JobId@ is returned
-- from @StartDocumentTextDetection@. A @JobId@ value is only valid for 7
-- days.
newGetDocumentTextDetection ::
  -- | 'jobId'
  Prelude.Text ->
  GetDocumentTextDetection
newGetDocumentTextDetection :: Text -> GetDocumentTextDetection
newGetDocumentTextDetection Text
pJobId_ =
  GetDocumentTextDetection'
    { $sel:maxResults:GetDocumentTextDetection' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetDocumentTextDetection' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:GetDocumentTextDetection' :: Text
jobId = Text
pJobId_
    }

-- | The maximum number of results to return per paginated call. The largest
-- value you can specify is 1,000. If you specify a value greater than
-- 1,000, a maximum of 1,000 results is returned. The default value is
-- 1,000.
getDocumentTextDetection_maxResults :: Lens.Lens' GetDocumentTextDetection (Prelude.Maybe Prelude.Natural)
getDocumentTextDetection_maxResults :: Lens' GetDocumentTextDetection (Maybe Natural)
getDocumentTextDetection_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetection' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetDocumentTextDetection
s@GetDocumentTextDetection' {} Maybe Natural
a -> GetDocumentTextDetection
s {$sel:maxResults:GetDocumentTextDetection' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetDocumentTextDetection)

-- | If the previous response was incomplete (because there are more blocks
-- to retrieve), Amazon Textract returns a pagination token in the
-- response. You can use this pagination token to retrieve the next set of
-- blocks.
getDocumentTextDetection_nextToken :: Lens.Lens' GetDocumentTextDetection (Prelude.Maybe Prelude.Text)
getDocumentTextDetection_nextToken :: Lens' GetDocumentTextDetection (Maybe Text)
getDocumentTextDetection_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetection' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetDocumentTextDetection
s@GetDocumentTextDetection' {} Maybe Text
a -> GetDocumentTextDetection
s {$sel:nextToken:GetDocumentTextDetection' :: Maybe Text
nextToken = Maybe Text
a} :: GetDocumentTextDetection)

-- | A unique identifier for the text detection job. The @JobId@ is returned
-- from @StartDocumentTextDetection@. A @JobId@ value is only valid for 7
-- days.
getDocumentTextDetection_jobId :: Lens.Lens' GetDocumentTextDetection Prelude.Text
getDocumentTextDetection_jobId :: Lens' GetDocumentTextDetection Text
getDocumentTextDetection_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetection' {Text
jobId :: Text
$sel:jobId:GetDocumentTextDetection' :: GetDocumentTextDetection -> Text
jobId} -> Text
jobId) (\s :: GetDocumentTextDetection
s@GetDocumentTextDetection' {} Text
a -> GetDocumentTextDetection
s {$sel:jobId:GetDocumentTextDetection' :: Text
jobId = Text
a} :: GetDocumentTextDetection)

instance Core.AWSRequest GetDocumentTextDetection where
  type
    AWSResponse GetDocumentTextDetection =
      GetDocumentTextDetectionResponse
  request :: (Service -> Service)
-> GetDocumentTextDetection -> Request GetDocumentTextDetection
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 GetDocumentTextDetection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDocumentTextDetection)))
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 [Block]
-> Maybe Text
-> Maybe DocumentMetadata
-> Maybe JobStatus
-> Maybe Text
-> Maybe Text
-> Maybe [Warning]
-> Int
-> GetDocumentTextDetectionResponse
GetDocumentTextDetectionResponse'
            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
"Blocks" 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
"DetectDocumentTextModelVersion")
            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
"DocumentMetadata")
            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
"JobStatus")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StatusMessage")
            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
"Warnings" 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 GetDocumentTextDetection where
  hashWithSalt :: Int -> GetDocumentTextDetection -> Int
hashWithSalt Int
_salt GetDocumentTextDetection' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetDocumentTextDetection' :: GetDocumentTextDetection -> Text
$sel:nextToken:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Text
$sel:maxResults:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Natural
..} =
    Int
_salt
      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
jobId

instance Prelude.NFData GetDocumentTextDetection where
  rnf :: GetDocumentTextDetection -> ()
rnf GetDocumentTextDetection' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetDocumentTextDetection' :: GetDocumentTextDetection -> Text
$sel:nextToken:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Text
$sel:maxResults:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Natural
..} =
    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
jobId

instance Data.ToHeaders GetDocumentTextDetection where
  toHeaders :: GetDocumentTextDetection -> 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
"Textract.GetDocumentTextDetection" ::
                          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 GetDocumentTextDetection where
  toJSON :: GetDocumentTextDetection -> Value
toJSON GetDocumentTextDetection' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetDocumentTextDetection' :: GetDocumentTextDetection -> Text
$sel:nextToken:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Text
$sel:maxResults:GetDocumentTextDetection' :: GetDocumentTextDetection -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"JobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)
          ]
      )

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

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

-- | /See:/ 'newGetDocumentTextDetectionResponse' smart constructor.
data GetDocumentTextDetectionResponse = GetDocumentTextDetectionResponse'
  { -- | The results of the text-detection operation.
    GetDocumentTextDetectionResponse -> Maybe [Block]
blocks :: Prelude.Maybe [Block],
    GetDocumentTextDetectionResponse -> Maybe Text
detectDocumentTextModelVersion :: Prelude.Maybe Prelude.Text,
    -- | Information about a document that Amazon Textract processed.
    -- @DocumentMetadata@ is returned in every page of paginated responses from
    -- an Amazon Textract video operation.
    GetDocumentTextDetectionResponse -> Maybe DocumentMetadata
documentMetadata :: Prelude.Maybe DocumentMetadata,
    -- | The current status of the text detection job.
    GetDocumentTextDetectionResponse -> Maybe JobStatus
jobStatus :: Prelude.Maybe JobStatus,
    -- | If the response is truncated, Amazon Textract returns this token. You
    -- can use this token in the subsequent request to retrieve the next set of
    -- text-detection results.
    GetDocumentTextDetectionResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Returns if the detection job could not be completed. Contains
    -- explanation for what error occured.
    GetDocumentTextDetectionResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | A list of warnings that occurred during the text-detection operation for
    -- the document.
    GetDocumentTextDetectionResponse -> Maybe [Warning]
warnings :: Prelude.Maybe [Warning],
    -- | The response's http status code.
    GetDocumentTextDetectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDocumentTextDetectionResponse
-> GetDocumentTextDetectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDocumentTextDetectionResponse
-> GetDocumentTextDetectionResponse -> Bool
$c/= :: GetDocumentTextDetectionResponse
-> GetDocumentTextDetectionResponse -> Bool
== :: GetDocumentTextDetectionResponse
-> GetDocumentTextDetectionResponse -> Bool
$c== :: GetDocumentTextDetectionResponse
-> GetDocumentTextDetectionResponse -> Bool
Prelude.Eq, ReadPrec [GetDocumentTextDetectionResponse]
ReadPrec GetDocumentTextDetectionResponse
Int -> ReadS GetDocumentTextDetectionResponse
ReadS [GetDocumentTextDetectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDocumentTextDetectionResponse]
$creadListPrec :: ReadPrec [GetDocumentTextDetectionResponse]
readPrec :: ReadPrec GetDocumentTextDetectionResponse
$creadPrec :: ReadPrec GetDocumentTextDetectionResponse
readList :: ReadS [GetDocumentTextDetectionResponse]
$creadList :: ReadS [GetDocumentTextDetectionResponse]
readsPrec :: Int -> ReadS GetDocumentTextDetectionResponse
$creadsPrec :: Int -> ReadS GetDocumentTextDetectionResponse
Prelude.Read, Int -> GetDocumentTextDetectionResponse -> ShowS
[GetDocumentTextDetectionResponse] -> ShowS
GetDocumentTextDetectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDocumentTextDetectionResponse] -> ShowS
$cshowList :: [GetDocumentTextDetectionResponse] -> ShowS
show :: GetDocumentTextDetectionResponse -> String
$cshow :: GetDocumentTextDetectionResponse -> String
showsPrec :: Int -> GetDocumentTextDetectionResponse -> ShowS
$cshowsPrec :: Int -> GetDocumentTextDetectionResponse -> ShowS
Prelude.Show, forall x.
Rep GetDocumentTextDetectionResponse x
-> GetDocumentTextDetectionResponse
forall x.
GetDocumentTextDetectionResponse
-> Rep GetDocumentTextDetectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDocumentTextDetectionResponse x
-> GetDocumentTextDetectionResponse
$cfrom :: forall x.
GetDocumentTextDetectionResponse
-> Rep GetDocumentTextDetectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDocumentTextDetectionResponse' 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:
--
-- 'blocks', 'getDocumentTextDetectionResponse_blocks' - The results of the text-detection operation.
--
-- 'detectDocumentTextModelVersion', 'getDocumentTextDetectionResponse_detectDocumentTextModelVersion' -
--
-- 'documentMetadata', 'getDocumentTextDetectionResponse_documentMetadata' - Information about a document that Amazon Textract processed.
-- @DocumentMetadata@ is returned in every page of paginated responses from
-- an Amazon Textract video operation.
--
-- 'jobStatus', 'getDocumentTextDetectionResponse_jobStatus' - The current status of the text detection job.
--
-- 'nextToken', 'getDocumentTextDetectionResponse_nextToken' - If the response is truncated, Amazon Textract returns this token. You
-- can use this token in the subsequent request to retrieve the next set of
-- text-detection results.
--
-- 'statusMessage', 'getDocumentTextDetectionResponse_statusMessage' - Returns if the detection job could not be completed. Contains
-- explanation for what error occured.
--
-- 'warnings', 'getDocumentTextDetectionResponse_warnings' - A list of warnings that occurred during the text-detection operation for
-- the document.
--
-- 'httpStatus', 'getDocumentTextDetectionResponse_httpStatus' - The response's http status code.
newGetDocumentTextDetectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDocumentTextDetectionResponse
newGetDocumentTextDetectionResponse :: Int -> GetDocumentTextDetectionResponse
newGetDocumentTextDetectionResponse Int
pHttpStatus_ =
  GetDocumentTextDetectionResponse'
    { $sel:blocks:GetDocumentTextDetectionResponse' :: Maybe [Block]
blocks =
        forall a. Maybe a
Prelude.Nothing,
      $sel:detectDocumentTextModelVersion:GetDocumentTextDetectionResponse' :: Maybe Text
detectDocumentTextModelVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:documentMetadata:GetDocumentTextDetectionResponse' :: Maybe DocumentMetadata
documentMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:jobStatus:GetDocumentTextDetectionResponse' :: Maybe JobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetDocumentTextDetectionResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetDocumentTextDetectionResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:GetDocumentTextDetectionResponse' :: Maybe [Warning]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDocumentTextDetectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The results of the text-detection operation.
getDocumentTextDetectionResponse_blocks :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe [Block])
getDocumentTextDetectionResponse_blocks :: Lens' GetDocumentTextDetectionResponse (Maybe [Block])
getDocumentTextDetectionResponse_blocks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe [Block]
blocks :: Maybe [Block]
$sel:blocks:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe [Block]
blocks} -> Maybe [Block]
blocks) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe [Block]
a -> GetDocumentTextDetectionResponse
s {$sel:blocks:GetDocumentTextDetectionResponse' :: Maybe [Block]
blocks = Maybe [Block]
a} :: GetDocumentTextDetectionResponse) 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

getDocumentTextDetectionResponse_detectDocumentTextModelVersion :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe Prelude.Text)
getDocumentTextDetectionResponse_detectDocumentTextModelVersion :: Lens' GetDocumentTextDetectionResponse (Maybe Text)
getDocumentTextDetectionResponse_detectDocumentTextModelVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe Text
detectDocumentTextModelVersion :: Maybe Text
$sel:detectDocumentTextModelVersion:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
detectDocumentTextModelVersion} -> Maybe Text
detectDocumentTextModelVersion) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe Text
a -> GetDocumentTextDetectionResponse
s {$sel:detectDocumentTextModelVersion:GetDocumentTextDetectionResponse' :: Maybe Text
detectDocumentTextModelVersion = Maybe Text
a} :: GetDocumentTextDetectionResponse)

-- | Information about a document that Amazon Textract processed.
-- @DocumentMetadata@ is returned in every page of paginated responses from
-- an Amazon Textract video operation.
getDocumentTextDetectionResponse_documentMetadata :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe DocumentMetadata)
getDocumentTextDetectionResponse_documentMetadata :: Lens' GetDocumentTextDetectionResponse (Maybe DocumentMetadata)
getDocumentTextDetectionResponse_documentMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe DocumentMetadata
documentMetadata :: Maybe DocumentMetadata
$sel:documentMetadata:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe DocumentMetadata
documentMetadata} -> Maybe DocumentMetadata
documentMetadata) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe DocumentMetadata
a -> GetDocumentTextDetectionResponse
s {$sel:documentMetadata:GetDocumentTextDetectionResponse' :: Maybe DocumentMetadata
documentMetadata = Maybe DocumentMetadata
a} :: GetDocumentTextDetectionResponse)

-- | The current status of the text detection job.
getDocumentTextDetectionResponse_jobStatus :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe JobStatus)
getDocumentTextDetectionResponse_jobStatus :: Lens' GetDocumentTextDetectionResponse (Maybe JobStatus)
getDocumentTextDetectionResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe JobStatus
jobStatus :: Maybe JobStatus
$sel:jobStatus:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe JobStatus
jobStatus} -> Maybe JobStatus
jobStatus) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe JobStatus
a -> GetDocumentTextDetectionResponse
s {$sel:jobStatus:GetDocumentTextDetectionResponse' :: Maybe JobStatus
jobStatus = Maybe JobStatus
a} :: GetDocumentTextDetectionResponse)

-- | If the response is truncated, Amazon Textract returns this token. You
-- can use this token in the subsequent request to retrieve the next set of
-- text-detection results.
getDocumentTextDetectionResponse_nextToken :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe Prelude.Text)
getDocumentTextDetectionResponse_nextToken :: Lens' GetDocumentTextDetectionResponse (Maybe Text)
getDocumentTextDetectionResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe Text
a -> GetDocumentTextDetectionResponse
s {$sel:nextToken:GetDocumentTextDetectionResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetDocumentTextDetectionResponse)

-- | Returns if the detection job could not be completed. Contains
-- explanation for what error occured.
getDocumentTextDetectionResponse_statusMessage :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe Prelude.Text)
getDocumentTextDetectionResponse_statusMessage :: Lens' GetDocumentTextDetectionResponse (Maybe Text)
getDocumentTextDetectionResponse_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe Text
statusMessage :: Maybe Text
$sel:statusMessage:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
statusMessage} -> Maybe Text
statusMessage) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe Text
a -> GetDocumentTextDetectionResponse
s {$sel:statusMessage:GetDocumentTextDetectionResponse' :: Maybe Text
statusMessage = Maybe Text
a} :: GetDocumentTextDetectionResponse)

-- | A list of warnings that occurred during the text-detection operation for
-- the document.
getDocumentTextDetectionResponse_warnings :: Lens.Lens' GetDocumentTextDetectionResponse (Prelude.Maybe [Warning])
getDocumentTextDetectionResponse_warnings :: Lens' GetDocumentTextDetectionResponse (Maybe [Warning])
getDocumentTextDetectionResponse_warnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Maybe [Warning]
warnings :: Maybe [Warning]
$sel:warnings:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe [Warning]
warnings} -> Maybe [Warning]
warnings) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Maybe [Warning]
a -> GetDocumentTextDetectionResponse
s {$sel:warnings:GetDocumentTextDetectionResponse' :: Maybe [Warning]
warnings = Maybe [Warning]
a} :: GetDocumentTextDetectionResponse) 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.
getDocumentTextDetectionResponse_httpStatus :: Lens.Lens' GetDocumentTextDetectionResponse Prelude.Int
getDocumentTextDetectionResponse_httpStatus :: Lens' GetDocumentTextDetectionResponse Int
getDocumentTextDetectionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDocumentTextDetectionResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetDocumentTextDetectionResponse
s@GetDocumentTextDetectionResponse' {} Int
a -> GetDocumentTextDetectionResponse
s {$sel:httpStatus:GetDocumentTextDetectionResponse' :: Int
httpStatus = Int
a} :: GetDocumentTextDetectionResponse)

instance
  Prelude.NFData
    GetDocumentTextDetectionResponse
  where
  rnf :: GetDocumentTextDetectionResponse -> ()
rnf GetDocumentTextDetectionResponse' {Int
Maybe [Block]
Maybe [Warning]
Maybe Text
Maybe DocumentMetadata
Maybe JobStatus
httpStatus :: Int
warnings :: Maybe [Warning]
statusMessage :: Maybe Text
nextToken :: Maybe Text
jobStatus :: Maybe JobStatus
documentMetadata :: Maybe DocumentMetadata
detectDocumentTextModelVersion :: Maybe Text
blocks :: Maybe [Block]
$sel:httpStatus:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Int
$sel:warnings:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe [Warning]
$sel:statusMessage:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
$sel:nextToken:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
$sel:jobStatus:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe JobStatus
$sel:documentMetadata:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe DocumentMetadata
$sel:detectDocumentTextModelVersion:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe Text
$sel:blocks:GetDocumentTextDetectionResponse' :: GetDocumentTextDetectionResponse -> Maybe [Block]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Block]
blocks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
detectDocumentTextModelVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentMetadata
documentMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobStatus
jobStatus
      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 Maybe Text
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Warning]
warnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus