{-# 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.Rekognition.StartTextDetection
-- 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 asynchronous detection of text in a stored video.
--
-- Amazon Rekognition Video can detect text in a video stored in an Amazon
-- S3 bucket. Use Video to specify the bucket name and the filename of the
-- video. @StartTextDetection@ returns a job identifier (@JobId@) which you
-- use to get the results of the operation. When text detection is
-- finished, Amazon Rekognition Video publishes a completion status to the
-- Amazon Simple Notification Service topic that you specify in
-- @NotificationChannel@.
--
-- 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 GetTextDetection and pass the job identifier (@JobId@) from the
-- initial call to @StartTextDetection@.
module Amazonka.Rekognition.StartTextDetection
  ( -- * Creating a Request
    StartTextDetection (..),
    newStartTextDetection,

    -- * Request Lenses
    startTextDetection_clientRequestToken,
    startTextDetection_filters,
    startTextDetection_jobTag,
    startTextDetection_notificationChannel,
    startTextDetection_video,

    -- * Destructuring the Response
    StartTextDetectionResponse (..),
    newStartTextDetectionResponse,

    -- * Response Lenses
    startTextDetectionResponse_jobId,
    startTextDetectionResponse_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 Amazonka.Rekognition.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartTextDetection' smart constructor.
data StartTextDetection = StartTextDetection'
  { -- | Idempotent token used to identify the start request. If you use the same
    -- token with multiple @StartTextDetection@ requests, the same @JobId@ is
    -- returned. Use @ClientRequestToken@ to prevent the same job from being
    -- accidentaly started more than once.
    StartTextDetection -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | Optional parameters that let you set criteria the text must meet to be
    -- included in your response.
    StartTextDetection -> Maybe StartTextDetectionFilters
filters :: Prelude.Maybe StartTextDetectionFilters,
    -- | An identifier returned in the completion status published by your Amazon
    -- Simple Notification Service topic. For example, you can use @JobTag@ to
    -- group related jobs and identify them in the completion notification.
    StartTextDetection -> Maybe Text
jobTag :: Prelude.Maybe Prelude.Text,
    StartTextDetection -> Maybe NotificationChannel
notificationChannel :: Prelude.Maybe NotificationChannel,
    StartTextDetection -> Video
video :: Video
  }
  deriving (StartTextDetection -> StartTextDetection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartTextDetection -> StartTextDetection -> Bool
$c/= :: StartTextDetection -> StartTextDetection -> Bool
== :: StartTextDetection -> StartTextDetection -> Bool
$c== :: StartTextDetection -> StartTextDetection -> Bool
Prelude.Eq, ReadPrec [StartTextDetection]
ReadPrec StartTextDetection
Int -> ReadS StartTextDetection
ReadS [StartTextDetection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartTextDetection]
$creadListPrec :: ReadPrec [StartTextDetection]
readPrec :: ReadPrec StartTextDetection
$creadPrec :: ReadPrec StartTextDetection
readList :: ReadS [StartTextDetection]
$creadList :: ReadS [StartTextDetection]
readsPrec :: Int -> ReadS StartTextDetection
$creadsPrec :: Int -> ReadS StartTextDetection
Prelude.Read, Int -> StartTextDetection -> ShowS
[StartTextDetection] -> ShowS
StartTextDetection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartTextDetection] -> ShowS
$cshowList :: [StartTextDetection] -> ShowS
show :: StartTextDetection -> String
$cshow :: StartTextDetection -> String
showsPrec :: Int -> StartTextDetection -> ShowS
$cshowsPrec :: Int -> StartTextDetection -> ShowS
Prelude.Show, forall x. Rep StartTextDetection x -> StartTextDetection
forall x. StartTextDetection -> Rep StartTextDetection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartTextDetection x -> StartTextDetection
$cfrom :: forall x. StartTextDetection -> Rep StartTextDetection x
Prelude.Generic)

-- |
-- Create a value of 'StartTextDetection' 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', 'startTextDetection_clientRequestToken' - Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartTextDetection@ requests, the same @JobId@ is
-- returned. Use @ClientRequestToken@ to prevent the same job from being
-- accidentaly started more than once.
--
-- 'filters', 'startTextDetection_filters' - Optional parameters that let you set criteria the text must meet to be
-- included in your response.
--
-- 'jobTag', 'startTextDetection_jobTag' - An identifier returned in the completion status published by your Amazon
-- Simple Notification Service topic. For example, you can use @JobTag@ to
-- group related jobs and identify them in the completion notification.
--
-- 'notificationChannel', 'startTextDetection_notificationChannel' - Undocumented member.
--
-- 'video', 'startTextDetection_video' - Undocumented member.
newStartTextDetection ::
  -- | 'video'
  Video ->
  StartTextDetection
newStartTextDetection :: Video -> StartTextDetection
newStartTextDetection Video
pVideo_ =
  StartTextDetection'
    { $sel:clientRequestToken:StartTextDetection' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:filters:StartTextDetection' :: Maybe StartTextDetectionFilters
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTag:StartTextDetection' :: Maybe Text
jobTag = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationChannel:StartTextDetection' :: Maybe NotificationChannel
notificationChannel = forall a. Maybe a
Prelude.Nothing,
      $sel:video:StartTextDetection' :: Video
video = Video
pVideo_
    }

-- | Idempotent token used to identify the start request. If you use the same
-- token with multiple @StartTextDetection@ requests, the same @JobId@ is
-- returned. Use @ClientRequestToken@ to prevent the same job from being
-- accidentaly started more than once.
startTextDetection_clientRequestToken :: Lens.Lens' StartTextDetection (Prelude.Maybe Prelude.Text)
startTextDetection_clientRequestToken :: Lens' StartTextDetection (Maybe Text)
startTextDetection_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetection' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:StartTextDetection' :: StartTextDetection -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: StartTextDetection
s@StartTextDetection' {} Maybe Text
a -> StartTextDetection
s {$sel:clientRequestToken:StartTextDetection' :: Maybe Text
clientRequestToken = Maybe Text
a} :: StartTextDetection)

-- | Optional parameters that let you set criteria the text must meet to be
-- included in your response.
startTextDetection_filters :: Lens.Lens' StartTextDetection (Prelude.Maybe StartTextDetectionFilters)
startTextDetection_filters :: Lens' StartTextDetection (Maybe StartTextDetectionFilters)
startTextDetection_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetection' {Maybe StartTextDetectionFilters
filters :: Maybe StartTextDetectionFilters
$sel:filters:StartTextDetection' :: StartTextDetection -> Maybe StartTextDetectionFilters
filters} -> Maybe StartTextDetectionFilters
filters) (\s :: StartTextDetection
s@StartTextDetection' {} Maybe StartTextDetectionFilters
a -> StartTextDetection
s {$sel:filters:StartTextDetection' :: Maybe StartTextDetectionFilters
filters = Maybe StartTextDetectionFilters
a} :: StartTextDetection)

-- | An identifier returned in the completion status published by your Amazon
-- Simple Notification Service topic. For example, you can use @JobTag@ to
-- group related jobs and identify them in the completion notification.
startTextDetection_jobTag :: Lens.Lens' StartTextDetection (Prelude.Maybe Prelude.Text)
startTextDetection_jobTag :: Lens' StartTextDetection (Maybe Text)
startTextDetection_jobTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetection' {Maybe Text
jobTag :: Maybe Text
$sel:jobTag:StartTextDetection' :: StartTextDetection -> Maybe Text
jobTag} -> Maybe Text
jobTag) (\s :: StartTextDetection
s@StartTextDetection' {} Maybe Text
a -> StartTextDetection
s {$sel:jobTag:StartTextDetection' :: Maybe Text
jobTag = Maybe Text
a} :: StartTextDetection)

-- | Undocumented member.
startTextDetection_notificationChannel :: Lens.Lens' StartTextDetection (Prelude.Maybe NotificationChannel)
startTextDetection_notificationChannel :: Lens' StartTextDetection (Maybe NotificationChannel)
startTextDetection_notificationChannel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetection' {Maybe NotificationChannel
notificationChannel :: Maybe NotificationChannel
$sel:notificationChannel:StartTextDetection' :: StartTextDetection -> Maybe NotificationChannel
notificationChannel} -> Maybe NotificationChannel
notificationChannel) (\s :: StartTextDetection
s@StartTextDetection' {} Maybe NotificationChannel
a -> StartTextDetection
s {$sel:notificationChannel:StartTextDetection' :: Maybe NotificationChannel
notificationChannel = Maybe NotificationChannel
a} :: StartTextDetection)

-- | Undocumented member.
startTextDetection_video :: Lens.Lens' StartTextDetection Video
startTextDetection_video :: Lens' StartTextDetection Video
startTextDetection_video = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetection' {Video
video :: Video
$sel:video:StartTextDetection' :: StartTextDetection -> Video
video} -> Video
video) (\s :: StartTextDetection
s@StartTextDetection' {} Video
a -> StartTextDetection
s {$sel:video:StartTextDetection' :: Video
video = Video
a} :: StartTextDetection)

instance Core.AWSRequest StartTextDetection where
  type
    AWSResponse StartTextDetection =
      StartTextDetectionResponse
  request :: (Service -> Service)
-> StartTextDetection -> Request StartTextDetection
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 StartTextDetection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartTextDetection)))
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 -> StartTextDetectionResponse
StartTextDetectionResponse'
            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 StartTextDetection where
  hashWithSalt :: Int -> StartTextDetection -> Int
hashWithSalt Int
_salt StartTextDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartTextDetectionFilters
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartTextDetectionFilters
clientRequestToken :: Maybe Text
$sel:video:StartTextDetection' :: StartTextDetection -> Video
$sel:notificationChannel:StartTextDetection' :: StartTextDetection -> Maybe NotificationChannel
$sel:jobTag:StartTextDetection' :: StartTextDetection -> Maybe Text
$sel:filters:StartTextDetection' :: StartTextDetection -> Maybe StartTextDetectionFilters
$sel:clientRequestToken:StartTextDetection' :: StartTextDetection -> 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 StartTextDetectionFilters
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobTag
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationChannel
notificationChannel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Video
video

instance Prelude.NFData StartTextDetection where
  rnf :: StartTextDetection -> ()
rnf StartTextDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartTextDetectionFilters
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartTextDetectionFilters
clientRequestToken :: Maybe Text
$sel:video:StartTextDetection' :: StartTextDetection -> Video
$sel:notificationChannel:StartTextDetection' :: StartTextDetection -> Maybe NotificationChannel
$sel:jobTag:StartTextDetection' :: StartTextDetection -> Maybe Text
$sel:filters:StartTextDetection' :: StartTextDetection -> Maybe StartTextDetectionFilters
$sel:clientRequestToken:StartTextDetection' :: StartTextDetection -> 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 StartTextDetectionFilters
filters
      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 NotificationChannel
notificationChannel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Video
video

instance Data.ToHeaders StartTextDetection where
  toHeaders :: StartTextDetection -> 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
"RekognitionService.StartTextDetection" ::
                          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 StartTextDetection where
  toJSON :: StartTextDetection -> Value
toJSON StartTextDetection' {Maybe Text
Maybe NotificationChannel
Maybe StartTextDetectionFilters
Video
video :: Video
notificationChannel :: Maybe NotificationChannel
jobTag :: Maybe Text
filters :: Maybe StartTextDetectionFilters
clientRequestToken :: Maybe Text
$sel:video:StartTextDetection' :: StartTextDetection -> Video
$sel:notificationChannel:StartTextDetection' :: StartTextDetection -> Maybe NotificationChannel
$sel:jobTag:StartTextDetection' :: StartTextDetection -> Maybe Text
$sel:filters:StartTextDetection' :: StartTextDetection -> Maybe StartTextDetectionFilters
$sel:clientRequestToken:StartTextDetection' :: StartTextDetection -> 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
"Filters" 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 StartTextDetectionFilters
filters,
            (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
"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,
            forall a. a -> Maybe a
Prelude.Just (Key
"Video" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Video
video)
          ]
      )

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

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

-- | /See:/ 'newStartTextDetectionResponse' smart constructor.
data StartTextDetectionResponse = StartTextDetectionResponse'
  { -- | Identifier for the text detection job. Use @JobId@ to identify the job
    -- in a subsequent call to @GetTextDetection@.
    StartTextDetectionResponse -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartTextDetectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartTextDetectionResponse -> StartTextDetectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartTextDetectionResponse -> StartTextDetectionResponse -> Bool
$c/= :: StartTextDetectionResponse -> StartTextDetectionResponse -> Bool
== :: StartTextDetectionResponse -> StartTextDetectionResponse -> Bool
$c== :: StartTextDetectionResponse -> StartTextDetectionResponse -> Bool
Prelude.Eq, ReadPrec [StartTextDetectionResponse]
ReadPrec StartTextDetectionResponse
Int -> ReadS StartTextDetectionResponse
ReadS [StartTextDetectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartTextDetectionResponse]
$creadListPrec :: ReadPrec [StartTextDetectionResponse]
readPrec :: ReadPrec StartTextDetectionResponse
$creadPrec :: ReadPrec StartTextDetectionResponse
readList :: ReadS [StartTextDetectionResponse]
$creadList :: ReadS [StartTextDetectionResponse]
readsPrec :: Int -> ReadS StartTextDetectionResponse
$creadsPrec :: Int -> ReadS StartTextDetectionResponse
Prelude.Read, Int -> StartTextDetectionResponse -> ShowS
[StartTextDetectionResponse] -> ShowS
StartTextDetectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartTextDetectionResponse] -> ShowS
$cshowList :: [StartTextDetectionResponse] -> ShowS
show :: StartTextDetectionResponse -> String
$cshow :: StartTextDetectionResponse -> String
showsPrec :: Int -> StartTextDetectionResponse -> ShowS
$cshowsPrec :: Int -> StartTextDetectionResponse -> ShowS
Prelude.Show, forall x.
Rep StartTextDetectionResponse x -> StartTextDetectionResponse
forall x.
StartTextDetectionResponse -> Rep StartTextDetectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartTextDetectionResponse x -> StartTextDetectionResponse
$cfrom :: forall x.
StartTextDetectionResponse -> Rep StartTextDetectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartTextDetectionResponse' 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', 'startTextDetectionResponse_jobId' - Identifier for the text detection job. Use @JobId@ to identify the job
-- in a subsequent call to @GetTextDetection@.
--
-- 'httpStatus', 'startTextDetectionResponse_httpStatus' - The response's http status code.
newStartTextDetectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartTextDetectionResponse
newStartTextDetectionResponse :: Int -> StartTextDetectionResponse
newStartTextDetectionResponse Int
pHttpStatus_ =
  StartTextDetectionResponse'
    { $sel:jobId:StartTextDetectionResponse' :: Maybe Text
jobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartTextDetectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Identifier for the text detection job. Use @JobId@ to identify the job
-- in a subsequent call to @GetTextDetection@.
startTextDetectionResponse_jobId :: Lens.Lens' StartTextDetectionResponse (Prelude.Maybe Prelude.Text)
startTextDetectionResponse_jobId :: Lens' StartTextDetectionResponse (Maybe Text)
startTextDetectionResponse_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartTextDetectionResponse' {Maybe Text
jobId :: Maybe Text
$sel:jobId:StartTextDetectionResponse' :: StartTextDetectionResponse -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: StartTextDetectionResponse
s@StartTextDetectionResponse' {} Maybe Text
a -> StartTextDetectionResponse
s {$sel:jobId:StartTextDetectionResponse' :: Maybe Text
jobId = Maybe Text
a} :: StartTextDetectionResponse)

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

instance Prelude.NFData StartTextDetectionResponse where
  rnf :: StartTextDetectionResponse -> ()
rnf StartTextDetectionResponse' {Int
Maybe Text
httpStatus :: Int
jobId :: Maybe Text
$sel:httpStatus:StartTextDetectionResponse' :: StartTextDetectionResponse -> Int
$sel:jobId:StartTextDetectionResponse' :: StartTextDetectionResponse -> 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