{-# 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.GetExpenseAnalysis
-- 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
-- analyzes invoices and receipts. Amazon Textract finds contact
-- information, items purchased, and vendor name, from input invoices and
-- receipts.
--
-- You start asynchronous invoice\/receipt analysis by calling
-- StartExpenseAnalysis, which returns a job identifier (@JobId@). Upon
-- completion of the invoice\/receipt analysis, Amazon Textract publishes
-- the completion status to the Amazon Simple Notification Service (Amazon
-- SNS) topic. This topic must be registered in the initial call to
-- @StartExpenseAnalysis@. To get the results of the invoice\/receipt
-- analysis operation, first ensure that the status value published to the
-- Amazon SNS topic is @SUCCEEDED@. If so, call @GetExpenseAnalysis@, and
-- pass the job identifier (@JobId@) from the initial call to
-- @StartExpenseAnalysis@.
--
-- 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 @GetExpenseAnalysis@, and populate the @NextToken@ request
-- parameter with the token value that\'s returned from the previous call
-- to @GetExpenseAnalysis@.
--
-- For more information, see
-- <https://docs.aws.amazon.com/textract/latest/dg/invoices-receipts.html Analyzing Invoices and Receipts>.
module Amazonka.Textract.GetExpenseAnalysis
  ( -- * Creating a Request
    GetExpenseAnalysis (..),
    newGetExpenseAnalysis,

    -- * Request Lenses
    getExpenseAnalysis_maxResults,
    getExpenseAnalysis_nextToken,
    getExpenseAnalysis_jobId,

    -- * Destructuring the Response
    GetExpenseAnalysisResponse (..),
    newGetExpenseAnalysisResponse,

    -- * Response Lenses
    getExpenseAnalysisResponse_analyzeExpenseModelVersion,
    getExpenseAnalysisResponse_documentMetadata,
    getExpenseAnalysisResponse_expenseDocuments,
    getExpenseAnalysisResponse_jobStatus,
    getExpenseAnalysisResponse_nextToken,
    getExpenseAnalysisResponse_statusMessage,
    getExpenseAnalysisResponse_warnings,
    getExpenseAnalysisResponse_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:/ 'newGetExpenseAnalysis' smart constructor.
data GetExpenseAnalysis = GetExpenseAnalysis'
  { -- | The maximum number of results to return per paginated call. The largest
    -- value you can specify is 20. If you specify a value greater than 20, a
    -- maximum of 20 results is returned. The default value is 20.
    GetExpenseAnalysis -> 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.
    GetExpenseAnalysis -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the text detection job. The @JobId@ is returned
    -- from @StartExpenseAnalysis@. A @JobId@ value is only valid for 7 days.
    GetExpenseAnalysis -> Text
jobId :: Prelude.Text
  }
  deriving (GetExpenseAnalysis -> GetExpenseAnalysis -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetExpenseAnalysis -> GetExpenseAnalysis -> Bool
$c/= :: GetExpenseAnalysis -> GetExpenseAnalysis -> Bool
== :: GetExpenseAnalysis -> GetExpenseAnalysis -> Bool
$c== :: GetExpenseAnalysis -> GetExpenseAnalysis -> Bool
Prelude.Eq, ReadPrec [GetExpenseAnalysis]
ReadPrec GetExpenseAnalysis
Int -> ReadS GetExpenseAnalysis
ReadS [GetExpenseAnalysis]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetExpenseAnalysis]
$creadListPrec :: ReadPrec [GetExpenseAnalysis]
readPrec :: ReadPrec GetExpenseAnalysis
$creadPrec :: ReadPrec GetExpenseAnalysis
readList :: ReadS [GetExpenseAnalysis]
$creadList :: ReadS [GetExpenseAnalysis]
readsPrec :: Int -> ReadS GetExpenseAnalysis
$creadsPrec :: Int -> ReadS GetExpenseAnalysis
Prelude.Read, Int -> GetExpenseAnalysis -> ShowS
[GetExpenseAnalysis] -> ShowS
GetExpenseAnalysis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetExpenseAnalysis] -> ShowS
$cshowList :: [GetExpenseAnalysis] -> ShowS
show :: GetExpenseAnalysis -> String
$cshow :: GetExpenseAnalysis -> String
showsPrec :: Int -> GetExpenseAnalysis -> ShowS
$cshowsPrec :: Int -> GetExpenseAnalysis -> ShowS
Prelude.Show, forall x. Rep GetExpenseAnalysis x -> GetExpenseAnalysis
forall x. GetExpenseAnalysis -> Rep GetExpenseAnalysis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetExpenseAnalysis x -> GetExpenseAnalysis
$cfrom :: forall x. GetExpenseAnalysis -> Rep GetExpenseAnalysis x
Prelude.Generic)

-- |
-- Create a value of 'GetExpenseAnalysis' 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', 'getExpenseAnalysis_maxResults' - The maximum number of results to return per paginated call. The largest
-- value you can specify is 20. If you specify a value greater than 20, a
-- maximum of 20 results is returned. The default value is 20.
--
-- 'nextToken', 'getExpenseAnalysis_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', 'getExpenseAnalysis_jobId' - A unique identifier for the text detection job. The @JobId@ is returned
-- from @StartExpenseAnalysis@. A @JobId@ value is only valid for 7 days.
newGetExpenseAnalysis ::
  -- | 'jobId'
  Prelude.Text ->
  GetExpenseAnalysis
newGetExpenseAnalysis :: Text -> GetExpenseAnalysis
newGetExpenseAnalysis Text
pJobId_ =
  GetExpenseAnalysis'
    { $sel:maxResults:GetExpenseAnalysis' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetExpenseAnalysis' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:GetExpenseAnalysis' :: Text
jobId = Text
pJobId_
    }

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

-- | 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.
getExpenseAnalysis_nextToken :: Lens.Lens' GetExpenseAnalysis (Prelude.Maybe Prelude.Text)
getExpenseAnalysis_nextToken :: Lens' GetExpenseAnalysis (Maybe Text)
getExpenseAnalysis_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExpenseAnalysis' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetExpenseAnalysis' :: GetExpenseAnalysis -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetExpenseAnalysis
s@GetExpenseAnalysis' {} Maybe Text
a -> GetExpenseAnalysis
s {$sel:nextToken:GetExpenseAnalysis' :: Maybe Text
nextToken = Maybe Text
a} :: GetExpenseAnalysis)

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

instance Core.AWSRequest GetExpenseAnalysis where
  type
    AWSResponse GetExpenseAnalysis =
      GetExpenseAnalysisResponse
  request :: (Service -> Service)
-> GetExpenseAnalysis -> Request GetExpenseAnalysis
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 GetExpenseAnalysis
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetExpenseAnalysis)))
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 Text
-> Maybe DocumentMetadata
-> Maybe [ExpenseDocument]
-> Maybe JobStatus
-> Maybe Text
-> Maybe Text
-> Maybe [Warning]
-> Int
-> GetExpenseAnalysisResponse
GetExpenseAnalysisResponse'
            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
"AnalyzeExpenseModelVersion")
            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
"ExpenseDocuments"
                            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
"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 GetExpenseAnalysis where
  hashWithSalt :: Int -> GetExpenseAnalysis -> Int
hashWithSalt Int
_salt GetExpenseAnalysis' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetExpenseAnalysis' :: GetExpenseAnalysis -> Text
$sel:nextToken:GetExpenseAnalysis' :: GetExpenseAnalysis -> Maybe Text
$sel:maxResults:GetExpenseAnalysis' :: GetExpenseAnalysis -> 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 GetExpenseAnalysis where
  rnf :: GetExpenseAnalysis -> ()
rnf GetExpenseAnalysis' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetExpenseAnalysis' :: GetExpenseAnalysis -> Text
$sel:nextToken:GetExpenseAnalysis' :: GetExpenseAnalysis -> Maybe Text
$sel:maxResults:GetExpenseAnalysis' :: GetExpenseAnalysis -> 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 GetExpenseAnalysis where
  toHeaders :: GetExpenseAnalysis -> 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.GetExpenseAnalysis" ::
                          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 GetExpenseAnalysis where
  toJSON :: GetExpenseAnalysis -> Value
toJSON GetExpenseAnalysis' {Maybe Natural
Maybe Text
Text
jobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:jobId:GetExpenseAnalysis' :: GetExpenseAnalysis -> Text
$sel:nextToken:GetExpenseAnalysis' :: GetExpenseAnalysis -> Maybe Text
$sel:maxResults:GetExpenseAnalysis' :: GetExpenseAnalysis -> 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 GetExpenseAnalysis where
  toPath :: GetExpenseAnalysis -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetExpenseAnalysisResponse' smart constructor.
data GetExpenseAnalysisResponse = GetExpenseAnalysisResponse'
  { -- | The current model version of AnalyzeExpense.
    GetExpenseAnalysisResponse -> Maybe Text
analyzeExpenseModelVersion :: 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 operation.
    GetExpenseAnalysisResponse -> Maybe DocumentMetadata
documentMetadata :: Prelude.Maybe DocumentMetadata,
    -- | The expenses detected by Amazon Textract.
    GetExpenseAnalysisResponse -> Maybe [ExpenseDocument]
expenseDocuments :: Prelude.Maybe [ExpenseDocument],
    -- | The current status of the text detection job.
    GetExpenseAnalysisResponse -> 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.
    GetExpenseAnalysisResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Returns if the detection job could not be completed. Contains
    -- explanation for what error occured.
    GetExpenseAnalysisResponse -> Maybe Text
statusMessage :: Prelude.Maybe Prelude.Text,
    -- | A list of warnings that occurred during the text-detection operation for
    -- the document.
    GetExpenseAnalysisResponse -> Maybe [Warning]
warnings :: Prelude.Maybe [Warning],
    -- | The response's http status code.
    GetExpenseAnalysisResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetExpenseAnalysisResponse -> GetExpenseAnalysisResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetExpenseAnalysisResponse -> GetExpenseAnalysisResponse -> Bool
$c/= :: GetExpenseAnalysisResponse -> GetExpenseAnalysisResponse -> Bool
== :: GetExpenseAnalysisResponse -> GetExpenseAnalysisResponse -> Bool
$c== :: GetExpenseAnalysisResponse -> GetExpenseAnalysisResponse -> Bool
Prelude.Eq, ReadPrec [GetExpenseAnalysisResponse]
ReadPrec GetExpenseAnalysisResponse
Int -> ReadS GetExpenseAnalysisResponse
ReadS [GetExpenseAnalysisResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetExpenseAnalysisResponse]
$creadListPrec :: ReadPrec [GetExpenseAnalysisResponse]
readPrec :: ReadPrec GetExpenseAnalysisResponse
$creadPrec :: ReadPrec GetExpenseAnalysisResponse
readList :: ReadS [GetExpenseAnalysisResponse]
$creadList :: ReadS [GetExpenseAnalysisResponse]
readsPrec :: Int -> ReadS GetExpenseAnalysisResponse
$creadsPrec :: Int -> ReadS GetExpenseAnalysisResponse
Prelude.Read, Int -> GetExpenseAnalysisResponse -> ShowS
[GetExpenseAnalysisResponse] -> ShowS
GetExpenseAnalysisResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetExpenseAnalysisResponse] -> ShowS
$cshowList :: [GetExpenseAnalysisResponse] -> ShowS
show :: GetExpenseAnalysisResponse -> String
$cshow :: GetExpenseAnalysisResponse -> String
showsPrec :: Int -> GetExpenseAnalysisResponse -> ShowS
$cshowsPrec :: Int -> GetExpenseAnalysisResponse -> ShowS
Prelude.Show, forall x.
Rep GetExpenseAnalysisResponse x -> GetExpenseAnalysisResponse
forall x.
GetExpenseAnalysisResponse -> Rep GetExpenseAnalysisResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetExpenseAnalysisResponse x -> GetExpenseAnalysisResponse
$cfrom :: forall x.
GetExpenseAnalysisResponse -> Rep GetExpenseAnalysisResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetExpenseAnalysisResponse' 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:
--
-- 'analyzeExpenseModelVersion', 'getExpenseAnalysisResponse_analyzeExpenseModelVersion' - The current model version of AnalyzeExpense.
--
-- 'documentMetadata', 'getExpenseAnalysisResponse_documentMetadata' - Information about a document that Amazon Textract processed.
-- @DocumentMetadata@ is returned in every page of paginated responses from
-- an Amazon Textract operation.
--
-- 'expenseDocuments', 'getExpenseAnalysisResponse_expenseDocuments' - The expenses detected by Amazon Textract.
--
-- 'jobStatus', 'getExpenseAnalysisResponse_jobStatus' - The current status of the text detection job.
--
-- 'nextToken', 'getExpenseAnalysisResponse_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', 'getExpenseAnalysisResponse_statusMessage' - Returns if the detection job could not be completed. Contains
-- explanation for what error occured.
--
-- 'warnings', 'getExpenseAnalysisResponse_warnings' - A list of warnings that occurred during the text-detection operation for
-- the document.
--
-- 'httpStatus', 'getExpenseAnalysisResponse_httpStatus' - The response's http status code.
newGetExpenseAnalysisResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetExpenseAnalysisResponse
newGetExpenseAnalysisResponse :: Int -> GetExpenseAnalysisResponse
newGetExpenseAnalysisResponse Int
pHttpStatus_ =
  GetExpenseAnalysisResponse'
    { $sel:analyzeExpenseModelVersion:GetExpenseAnalysisResponse' :: Maybe Text
analyzeExpenseModelVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:documentMetadata:GetExpenseAnalysisResponse' :: Maybe DocumentMetadata
documentMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:expenseDocuments:GetExpenseAnalysisResponse' :: Maybe [ExpenseDocument]
expenseDocuments = forall a. Maybe a
Prelude.Nothing,
      $sel:jobStatus:GetExpenseAnalysisResponse' :: Maybe JobStatus
jobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetExpenseAnalysisResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:GetExpenseAnalysisResponse' :: Maybe Text
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:GetExpenseAnalysisResponse' :: Maybe [Warning]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetExpenseAnalysisResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The current model version of AnalyzeExpense.
getExpenseAnalysisResponse_analyzeExpenseModelVersion :: Lens.Lens' GetExpenseAnalysisResponse (Prelude.Maybe Prelude.Text)
getExpenseAnalysisResponse_analyzeExpenseModelVersion :: Lens' GetExpenseAnalysisResponse (Maybe Text)
getExpenseAnalysisResponse_analyzeExpenseModelVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExpenseAnalysisResponse' {Maybe Text
analyzeExpenseModelVersion :: Maybe Text
$sel:analyzeExpenseModelVersion:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe Text
analyzeExpenseModelVersion} -> Maybe Text
analyzeExpenseModelVersion) (\s :: GetExpenseAnalysisResponse
s@GetExpenseAnalysisResponse' {} Maybe Text
a -> GetExpenseAnalysisResponse
s {$sel:analyzeExpenseModelVersion:GetExpenseAnalysisResponse' :: Maybe Text
analyzeExpenseModelVersion = Maybe Text
a} :: GetExpenseAnalysisResponse)

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

-- | The expenses detected by Amazon Textract.
getExpenseAnalysisResponse_expenseDocuments :: Lens.Lens' GetExpenseAnalysisResponse (Prelude.Maybe [ExpenseDocument])
getExpenseAnalysisResponse_expenseDocuments :: Lens' GetExpenseAnalysisResponse (Maybe [ExpenseDocument])
getExpenseAnalysisResponse_expenseDocuments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExpenseAnalysisResponse' {Maybe [ExpenseDocument]
expenseDocuments :: Maybe [ExpenseDocument]
$sel:expenseDocuments:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe [ExpenseDocument]
expenseDocuments} -> Maybe [ExpenseDocument]
expenseDocuments) (\s :: GetExpenseAnalysisResponse
s@GetExpenseAnalysisResponse' {} Maybe [ExpenseDocument]
a -> GetExpenseAnalysisResponse
s {$sel:expenseDocuments:GetExpenseAnalysisResponse' :: Maybe [ExpenseDocument]
expenseDocuments = Maybe [ExpenseDocument]
a} :: GetExpenseAnalysisResponse) 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 current status of the text detection job.
getExpenseAnalysisResponse_jobStatus :: Lens.Lens' GetExpenseAnalysisResponse (Prelude.Maybe JobStatus)
getExpenseAnalysisResponse_jobStatus :: Lens' GetExpenseAnalysisResponse (Maybe JobStatus)
getExpenseAnalysisResponse_jobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExpenseAnalysisResponse' {Maybe JobStatus
jobStatus :: Maybe JobStatus
$sel:jobStatus:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe JobStatus
jobStatus} -> Maybe JobStatus
jobStatus) (\s :: GetExpenseAnalysisResponse
s@GetExpenseAnalysisResponse' {} Maybe JobStatus
a -> GetExpenseAnalysisResponse
s {$sel:jobStatus:GetExpenseAnalysisResponse' :: Maybe JobStatus
jobStatus = Maybe JobStatus
a} :: GetExpenseAnalysisResponse)

-- | 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.
getExpenseAnalysisResponse_nextToken :: Lens.Lens' GetExpenseAnalysisResponse (Prelude.Maybe Prelude.Text)
getExpenseAnalysisResponse_nextToken :: Lens' GetExpenseAnalysisResponse (Maybe Text)
getExpenseAnalysisResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetExpenseAnalysisResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetExpenseAnalysisResponse
s@GetExpenseAnalysisResponse' {} Maybe Text
a -> GetExpenseAnalysisResponse
s {$sel:nextToken:GetExpenseAnalysisResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetExpenseAnalysisResponse)

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

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

instance Prelude.NFData GetExpenseAnalysisResponse where
  rnf :: GetExpenseAnalysisResponse -> ()
rnf GetExpenseAnalysisResponse' {Int
Maybe [ExpenseDocument]
Maybe [Warning]
Maybe Text
Maybe DocumentMetadata
Maybe JobStatus
httpStatus :: Int
warnings :: Maybe [Warning]
statusMessage :: Maybe Text
nextToken :: Maybe Text
jobStatus :: Maybe JobStatus
expenseDocuments :: Maybe [ExpenseDocument]
documentMetadata :: Maybe DocumentMetadata
analyzeExpenseModelVersion :: Maybe Text
$sel:httpStatus:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Int
$sel:warnings:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe [Warning]
$sel:statusMessage:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe Text
$sel:nextToken:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe Text
$sel:jobStatus:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe JobStatus
$sel:expenseDocuments:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe [ExpenseDocument]
$sel:documentMetadata:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe DocumentMetadata
$sel:analyzeExpenseModelVersion:GetExpenseAnalysisResponse' :: GetExpenseAnalysisResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
analyzeExpenseModelVersion
      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 [ExpenseDocument]
expenseDocuments
      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