{-# 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.StartExpenseAnalysis
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts the asynchronous analysis of invoices or receipts for data like
-- contact information, items purchased, and vendor names.
--
-- @StartExpenseAnalysis@ can analyze text in documents that are in JPEG,
-- PNG, and PDF format. The documents must be stored in an Amazon S3
-- bucket. Use the DocumentLocation parameter to specify the name of your
-- S3 bucket and the name of the document in that bucket.
--
-- @StartExpenseAnalysis@ returns a job identifier (@JobId@) that you will
-- provide to @GetExpenseAnalysis@ to retrieve the results of the
-- operation. When the analysis of the input invoices\/receipts is
-- finished, Amazon Textract publishes a completion status to the Amazon
-- Simple Notification Service (Amazon SNS) topic that you provide to the
-- @NotificationChannel@. To obtain the results of the invoice and receipt
-- analysis operation, ensure that the status value published to the Amazon
-- SNS topic is @SUCCEEDED@. If so, call GetExpenseAnalysis, and pass the
-- job identifier (@JobId@) that was returned by your call to
-- @StartExpenseAnalysis@.
--
-- For more information, see
-- <https://docs.aws.amazon.com/textract/latest/dg/invoice-receipts.html Analyzing Invoices and Receipts>.
module Amazonka.Textract.StartExpenseAnalysis
  ( -- * Creating a Request
    StartExpenseAnalysis (..),
    newStartExpenseAnalysis,

    -- * Request Lenses
    startExpenseAnalysis_clientRequestToken,
    startExpenseAnalysis_jobTag,
    startExpenseAnalysis_kmsKeyId,
    startExpenseAnalysis_notificationChannel,
    startExpenseAnalysis_outputConfig,
    startExpenseAnalysis_documentLocation,

    -- * Destructuring the Response
    StartExpenseAnalysisResponse (..),
    newStartExpenseAnalysisResponse,

    -- * Response Lenses
    startExpenseAnalysisResponse_jobId,
    startExpenseAnalysisResponse_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:/ 'newStartExpenseAnalysis' smart constructor.
data StartExpenseAnalysis = StartExpenseAnalysis'
  { -- | The idempotent token that\'s used to identify the start request. If you
    -- use the same token with multiple @StartDocumentTextDetection@ requests,
    -- the same @JobId@ is returned. Use @ClientRequestToken@ to prevent the
    -- same job from being accidentally started more than once. For more
    -- information, see
    -- <https://docs.aws.amazon.com/textract/latest/dg/api-async.html Calling Amazon Textract Asynchronous Operations>
    StartExpenseAnalysis -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | An identifier you specify that\'s included in the completion
    -- notification published to the Amazon SNS topic. For example, you can use
    -- @JobTag@ to identify the type of document that the completion
    -- notification corresponds to (such as a tax form or a receipt).
    StartExpenseAnalysis -> Maybe Text
jobTag :: Prelude.Maybe Prelude.Text,
    -- | The KMS key used to encrypt the inference results. This can be in either
    -- Key ID or Key Alias format. When a KMS key is provided, the KMS key will
    -- be used for server-side encryption of the objects in the customer
    -- bucket. When this parameter is not enabled, the result will be encrypted
    -- server side,using SSE-S3.
    StartExpenseAnalysis -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon SNS topic ARN that you want Amazon Textract to publish the
    -- completion status of the operation to.
    StartExpenseAnalysis -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    -- | Sets if the output will go to a customer defined bucket. By default,
    -- Amazon Textract will save the results internally to be accessed by the
    -- @GetExpenseAnalysis@ operation.
    StartExpenseAnalysis -> Maybe OutputConfig
outputConfig :: Prelude.Maybe OutputConfig,
    -- | The location of the document to be processed.
    StartExpenseAnalysis -> DocumentLocation
documentLocation :: DocumentLocation
  }
  deriving (StartExpenseAnalysis -> StartExpenseAnalysis -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartExpenseAnalysis -> StartExpenseAnalysis -> Bool
$c/= :: StartExpenseAnalysis -> StartExpenseAnalysis -> Bool
== :: StartExpenseAnalysis -> StartExpenseAnalysis -> Bool
$c== :: StartExpenseAnalysis -> StartExpenseAnalysis -> Bool
Prelude.Eq, ReadPrec [StartExpenseAnalysis]
ReadPrec StartExpenseAnalysis
Int -> ReadS StartExpenseAnalysis
ReadS [StartExpenseAnalysis]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartExpenseAnalysis]
$creadListPrec :: ReadPrec [StartExpenseAnalysis]
readPrec :: ReadPrec StartExpenseAnalysis
$creadPrec :: ReadPrec StartExpenseAnalysis
readList :: ReadS [StartExpenseAnalysis]
$creadList :: ReadS [StartExpenseAnalysis]
readsPrec :: Int -> ReadS StartExpenseAnalysis
$creadsPrec :: Int -> ReadS StartExpenseAnalysis
Prelude.Read, Int -> StartExpenseAnalysis -> ShowS
[StartExpenseAnalysis] -> ShowS
StartExpenseAnalysis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartExpenseAnalysis] -> ShowS
$cshowList :: [StartExpenseAnalysis] -> ShowS
show :: StartExpenseAnalysis -> String
$cshow :: StartExpenseAnalysis -> String
showsPrec :: Int -> StartExpenseAnalysis -> ShowS
$cshowsPrec :: Int -> StartExpenseAnalysis -> ShowS
Prelude.Show, forall x. Rep StartExpenseAnalysis x -> StartExpenseAnalysis
forall x. StartExpenseAnalysis -> Rep StartExpenseAnalysis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartExpenseAnalysis x -> StartExpenseAnalysis
$cfrom :: forall x. StartExpenseAnalysis -> Rep StartExpenseAnalysis x
Prelude.Generic)

-- |
-- Create a value of 'StartExpenseAnalysis' 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:
--
-- 'clientRequestToken', 'startExpenseAnalysis_clientRequestToken' - The idempotent token that\'s used to identify the start request. If you
-- use the same token with multiple @StartDocumentTextDetection@ requests,
-- the same @JobId@ is returned. Use @ClientRequestToken@ to prevent the
-- same job from being accidentally started more than once. For more
-- information, see
-- <https://docs.aws.amazon.com/textract/latest/dg/api-async.html Calling Amazon Textract Asynchronous Operations>
--
-- 'jobTag', 'startExpenseAnalysis_jobTag' - An identifier you specify that\'s included in the completion
-- notification published to the Amazon SNS topic. For example, you can use
-- @JobTag@ to identify the type of document that the completion
-- notification corresponds to (such as a tax form or a receipt).
--
-- 'kmsKeyId', 'startExpenseAnalysis_kmsKeyId' - The KMS key used to encrypt the inference results. This can be in either
-- Key ID or Key Alias format. When a KMS key is provided, the KMS key will
-- be used for server-side encryption of the objects in the customer
-- bucket. When this parameter is not enabled, the result will be encrypted
-- server side,using SSE-S3.
--
-- 'notificationChannel', 'startExpenseAnalysis_notificationChannel' - The Amazon SNS topic ARN that you want Amazon Textract to publish the
-- completion status of the operation to.
--
-- 'outputConfig', 'startExpenseAnalysis_outputConfig' - Sets if the output will go to a customer defined bucket. By default,
-- Amazon Textract will save the results internally to be accessed by the
-- @GetExpenseAnalysis@ operation.
--
-- 'documentLocation', 'startExpenseAnalysis_documentLocation' - The location of the document to be processed.
newStartExpenseAnalysis ::
  -- | 'documentLocation'
  DocumentLocation ->
  StartExpenseAnalysis
newStartExpenseAnalysis :: DocumentLocation -> StartExpenseAnalysis
newStartExpenseAnalysis DocumentLocation
pDocumentLocation_ =
  StartExpenseAnalysis'
    { $sel:clientRequestToken:StartExpenseAnalysis' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartExpenseAnalysis' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:StartExpenseAnalysis' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartExpenseAnalysis' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:outputConfig:StartExpenseAnalysis' :: Maybe OutputConfig
outputConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:documentLocation:StartExpenseAnalysis' :: DocumentLocation
documentLocation = DocumentLocation
pDocumentLocation_
    }

-- | The idempotent token that\'s used to identify the start request. If you
-- use the same token with multiple @StartDocumentTextDetection@ requests,
-- the same @JobId@ is returned. Use @ClientRequestToken@ to prevent the
-- same job from being accidentally started more than once. For more
-- information, see
-- <https://docs.aws.amazon.com/textract/latest/dg/api-async.html Calling Amazon Textract Asynchronous Operations>
startExpenseAnalysis_clientRequestToken :: Lens.Lens' StartExpenseAnalysis (Prelude.Maybe Prelude.Text)
startExpenseAnalysis_clientRequestToken :: Lens' StartExpenseAnalysis (Maybe Text)
startExpenseAnalysis_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} Maybe Text
a -> StartExpenseAnalysis
s {$sel:clientRequestToken:StartExpenseAnalysis' :: Maybe Text
clientRequestToken = Maybe Text
a} :: StartExpenseAnalysis)

-- | An identifier you specify that\'s included in the completion
-- notification published to the Amazon SNS topic. For example, you can use
-- @JobTag@ to identify the type of document that the completion
-- notification corresponds to (such as a tax form or a receipt).
startExpenseAnalysis_jobTag :: Lens.Lens' StartExpenseAnalysis (Prelude.Maybe Prelude.Text)
startExpenseAnalysis_jobTag :: Lens' StartExpenseAnalysis (Maybe Text)
startExpenseAnalysis_jobTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {Maybe Text
jobTag :: Maybe Text
$sel:jobTag:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
jobTag} -> Maybe Text
jobTag) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} Maybe Text
a -> StartExpenseAnalysis
s {$sel:jobTag:StartExpenseAnalysis' :: Maybe Text
jobTag = Maybe Text
a} :: StartExpenseAnalysis)

-- | The KMS key used to encrypt the inference results. This can be in either
-- Key ID or Key Alias format. When a KMS key is provided, the KMS key will
-- be used for server-side encryption of the objects in the customer
-- bucket. When this parameter is not enabled, the result will be encrypted
-- server side,using SSE-S3.
startExpenseAnalysis_kmsKeyId :: Lens.Lens' StartExpenseAnalysis (Prelude.Maybe Prelude.Text)
startExpenseAnalysis_kmsKeyId :: Lens' StartExpenseAnalysis (Maybe Text)
startExpenseAnalysis_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} Maybe Text
a -> StartExpenseAnalysis
s {$sel:kmsKeyId:StartExpenseAnalysis' :: Maybe Text
kmsKeyId = Maybe Text
a} :: StartExpenseAnalysis)

-- | The Amazon SNS topic ARN that you want Amazon Textract to publish the
-- completion status of the operation to.
startExpenseAnalysis_notificationChannel :: Lens.Lens' StartExpenseAnalysis (Prelude.Maybe NotificationChannel)
startExpenseAnalysis_notificationChannel :: Lens' StartExpenseAnalysis (Maybe NotificationChannel)
startExpenseAnalysis_notificationChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {Maybe NotificationChannel
notificationChannel :: Maybe NotificationChannel
$sel:notificationChannel:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe NotificationChannel
notificationChannel} -> Maybe NotificationChannel
notificationChannel) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} Maybe NotificationChannel
a -> StartExpenseAnalysis
s {$sel:notificationChannel:StartExpenseAnalysis' :: Maybe NotificationChannel
notificationChannel = Maybe NotificationChannel
a} :: StartExpenseAnalysis)

-- | Sets if the output will go to a customer defined bucket. By default,
-- Amazon Textract will save the results internally to be accessed by the
-- @GetExpenseAnalysis@ operation.
startExpenseAnalysis_outputConfig :: Lens.Lens' StartExpenseAnalysis (Prelude.Maybe OutputConfig)
startExpenseAnalysis_outputConfig :: Lens' StartExpenseAnalysis (Maybe OutputConfig)
startExpenseAnalysis_outputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {Maybe OutputConfig
outputConfig :: Maybe OutputConfig
$sel:outputConfig:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe OutputConfig
outputConfig} -> Maybe OutputConfig
outputConfig) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} Maybe OutputConfig
a -> StartExpenseAnalysis
s {$sel:outputConfig:StartExpenseAnalysis' :: Maybe OutputConfig
outputConfig = Maybe OutputConfig
a} :: StartExpenseAnalysis)

-- | The location of the document to be processed.
startExpenseAnalysis_documentLocation :: Lens.Lens' StartExpenseAnalysis DocumentLocation
startExpenseAnalysis_documentLocation :: Lens' StartExpenseAnalysis DocumentLocation
startExpenseAnalysis_documentLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExpenseAnalysis' {DocumentLocation
documentLocation :: DocumentLocation
$sel:documentLocation:StartExpenseAnalysis' :: StartExpenseAnalysis -> DocumentLocation
documentLocation} -> DocumentLocation
documentLocation) (\s :: StartExpenseAnalysis
s@StartExpenseAnalysis' {} DocumentLocation
a -> StartExpenseAnalysis
s {$sel:documentLocation:StartExpenseAnalysis' :: DocumentLocation
documentLocation = DocumentLocation
a} :: StartExpenseAnalysis)

instance Core.AWSRequest StartExpenseAnalysis where
  type
    AWSResponse StartExpenseAnalysis =
      StartExpenseAnalysisResponse
  request :: (Service -> Service)
-> StartExpenseAnalysis -> Request StartExpenseAnalysis
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 StartExpenseAnalysis
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartExpenseAnalysis)))
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 -> Int -> StartExpenseAnalysisResponse
StartExpenseAnalysisResponse'
            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
"JobId")
            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 StartExpenseAnalysis where
  hashWithSalt :: Int -> StartExpenseAnalysis -> Int
hashWithSalt Int
_salt StartExpenseAnalysis' {Maybe Text
Maybe NotificationChannel
Maybe OutputConfig
DocumentLocation
documentLocation :: DocumentLocation
outputConfig :: Maybe OutputConfig
notificationChannel :: Maybe NotificationChannel
kmsKeyId :: Maybe Text
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:documentLocation:StartExpenseAnalysis' :: StartExpenseAnalysis -> DocumentLocation
$sel:outputConfig:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe OutputConfig
$sel:notificationChannel:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe NotificationChannel
$sel:kmsKeyId:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:jobTag:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:clientRequestToken:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobTag
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationChannel
notificationChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputConfig
outputConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DocumentLocation
documentLocation

instance Prelude.NFData StartExpenseAnalysis where
  rnf :: StartExpenseAnalysis -> ()
rnf StartExpenseAnalysis' {Maybe Text
Maybe NotificationChannel
Maybe OutputConfig
DocumentLocation
documentLocation :: DocumentLocation
outputConfig :: Maybe OutputConfig
notificationChannel :: Maybe NotificationChannel
kmsKeyId :: Maybe Text
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:documentLocation:StartExpenseAnalysis' :: StartExpenseAnalysis -> DocumentLocation
$sel:outputConfig:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe OutputConfig
$sel:notificationChannel:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe NotificationChannel
$sel:kmsKeyId:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:jobTag:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:clientRequestToken:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NotificationChannel
notificationChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputConfig
outputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DocumentLocation
documentLocation

instance Data.ToHeaders StartExpenseAnalysis where
  toHeaders :: StartExpenseAnalysis -> 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.StartExpenseAnalysis" ::
                          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 StartExpenseAnalysis where
  toJSON :: StartExpenseAnalysis -> Value
toJSON StartExpenseAnalysis' {Maybe Text
Maybe NotificationChannel
Maybe OutputConfig
DocumentLocation
documentLocation :: DocumentLocation
outputConfig :: Maybe OutputConfig
notificationChannel :: Maybe NotificationChannel
kmsKeyId :: Maybe Text
jobTag :: Maybe Text
clientRequestToken :: Maybe Text
$sel:documentLocation:StartExpenseAnalysis' :: StartExpenseAnalysis -> DocumentLocation
$sel:outputConfig:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe OutputConfig
$sel:notificationChannel:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe NotificationChannel
$sel:kmsKeyId:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:jobTag:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
$sel:clientRequestToken:StartExpenseAnalysis' :: StartExpenseAnalysis -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            (Key
"JobTag" 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
jobTag,
            (Key
"KMSKeyId" 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
kmsKeyId,
            (Key
"NotificationChannel" 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 NotificationChannel
notificationChannel,
            (Key
"OutputConfig" 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 OutputConfig
outputConfig,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"DocumentLocation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= DocumentLocation
documentLocation)
          ]
      )

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

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

-- | /See:/ 'newStartExpenseAnalysisResponse' smart constructor.
data StartExpenseAnalysisResponse = StartExpenseAnalysisResponse'
  { -- | A unique identifier for the text detection job. The @JobId@ is returned
    -- from @StartExpenseAnalysis@. A @JobId@ value is only valid for 7 days.
    StartExpenseAnalysisResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartExpenseAnalysisResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartExpenseAnalysisResponse
-> StartExpenseAnalysisResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartExpenseAnalysisResponse
-> StartExpenseAnalysisResponse -> Bool
$c/= :: StartExpenseAnalysisResponse
-> StartExpenseAnalysisResponse -> Bool
== :: StartExpenseAnalysisResponse
-> StartExpenseAnalysisResponse -> Bool
$c== :: StartExpenseAnalysisResponse
-> StartExpenseAnalysisResponse -> Bool
Prelude.Eq, ReadPrec [StartExpenseAnalysisResponse]
ReadPrec StartExpenseAnalysisResponse
Int -> ReadS StartExpenseAnalysisResponse
ReadS [StartExpenseAnalysisResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartExpenseAnalysisResponse]
$creadListPrec :: ReadPrec [StartExpenseAnalysisResponse]
readPrec :: ReadPrec StartExpenseAnalysisResponse
$creadPrec :: ReadPrec StartExpenseAnalysisResponse
readList :: ReadS [StartExpenseAnalysisResponse]
$creadList :: ReadS [StartExpenseAnalysisResponse]
readsPrec :: Int -> ReadS StartExpenseAnalysisResponse
$creadsPrec :: Int -> ReadS StartExpenseAnalysisResponse
Prelude.Read, Int -> StartExpenseAnalysisResponse -> ShowS
[StartExpenseAnalysisResponse] -> ShowS
StartExpenseAnalysisResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartExpenseAnalysisResponse] -> ShowS
$cshowList :: [StartExpenseAnalysisResponse] -> ShowS
show :: StartExpenseAnalysisResponse -> String
$cshow :: StartExpenseAnalysisResponse -> String
showsPrec :: Int -> StartExpenseAnalysisResponse -> ShowS
$cshowsPrec :: Int -> StartExpenseAnalysisResponse -> ShowS
Prelude.Show, forall x.
Rep StartExpenseAnalysisResponse x -> StartExpenseAnalysisResponse
forall x.
StartExpenseAnalysisResponse -> Rep StartExpenseAnalysisResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartExpenseAnalysisResponse x -> StartExpenseAnalysisResponse
$cfrom :: forall x.
StartExpenseAnalysisResponse -> Rep StartExpenseAnalysisResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartExpenseAnalysisResponse' 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:
--
-- 'jobId', 'startExpenseAnalysisResponse_jobId' - A unique identifier for the text detection job. The @JobId@ is returned
-- from @StartExpenseAnalysis@. A @JobId@ value is only valid for 7 days.
--
-- 'httpStatus', 'startExpenseAnalysisResponse_httpStatus' - The response's http status code.
newStartExpenseAnalysisResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartExpenseAnalysisResponse
newStartExpenseAnalysisResponse :: Int -> StartExpenseAnalysisResponse
newStartExpenseAnalysisResponse Int
pHttpStatus_ =
  StartExpenseAnalysisResponse'
    { $sel:jobId:StartExpenseAnalysisResponse' :: Maybe Text
jobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartExpenseAnalysisResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData StartExpenseAnalysisResponse where
  rnf :: StartExpenseAnalysisResponse -> ()
rnf StartExpenseAnalysisResponse' {Int
Maybe Text
httpStatus :: Int
jobId :: Maybe Text
$sel:httpStatus:StartExpenseAnalysisResponse' :: StartExpenseAnalysisResponse -> Int
$sel:jobId:StartExpenseAnalysisResponse' :: StartExpenseAnalysisResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus