{-# 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.Transcribe.GetCallAnalyticsJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides information about the specified Call Analytics job.
--
-- To view the job\'s status, refer to @CallAnalyticsJobStatus@. If the
-- status is @COMPLETED@, the job is finished. You can find your completed
-- transcript at the URI specified in @TranscriptFileUri@. If the status is
-- @FAILED@, @FailureReason@ provides details on why your transcription job
-- failed.
--
-- If you enabled personally identifiable information (PII) redaction, the
-- redacted transcript appears at the location specified in
-- @RedactedTranscriptFileUri@.
--
-- If you chose to redact the audio in your media file, you can find your
-- redacted media file at the location specified in @RedactedMediaFileUri@.
--
-- To get a list of your Call Analytics jobs, use the operation.
module Amazonka.Transcribe.GetCallAnalyticsJob
  ( -- * Creating a Request
    GetCallAnalyticsJob (..),
    newGetCallAnalyticsJob,

    -- * Request Lenses
    getCallAnalyticsJob_callAnalyticsJobName,

    -- * Destructuring the Response
    GetCallAnalyticsJobResponse (..),
    newGetCallAnalyticsJobResponse,

    -- * Response Lenses
    getCallAnalyticsJobResponse_callAnalyticsJob,
    getCallAnalyticsJobResponse_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.Transcribe.Types

-- | /See:/ 'newGetCallAnalyticsJob' smart constructor.
data GetCallAnalyticsJob = GetCallAnalyticsJob'
  { -- | The name of the Call Analytics job you want information about. Job names
    -- are case sensitive.
    GetCallAnalyticsJob -> Text
callAnalyticsJobName :: Prelude.Text
  }
  deriving (GetCallAnalyticsJob -> GetCallAnalyticsJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCallAnalyticsJob -> GetCallAnalyticsJob -> Bool
$c/= :: GetCallAnalyticsJob -> GetCallAnalyticsJob -> Bool
== :: GetCallAnalyticsJob -> GetCallAnalyticsJob -> Bool
$c== :: GetCallAnalyticsJob -> GetCallAnalyticsJob -> Bool
Prelude.Eq, ReadPrec [GetCallAnalyticsJob]
ReadPrec GetCallAnalyticsJob
Int -> ReadS GetCallAnalyticsJob
ReadS [GetCallAnalyticsJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCallAnalyticsJob]
$creadListPrec :: ReadPrec [GetCallAnalyticsJob]
readPrec :: ReadPrec GetCallAnalyticsJob
$creadPrec :: ReadPrec GetCallAnalyticsJob
readList :: ReadS [GetCallAnalyticsJob]
$creadList :: ReadS [GetCallAnalyticsJob]
readsPrec :: Int -> ReadS GetCallAnalyticsJob
$creadsPrec :: Int -> ReadS GetCallAnalyticsJob
Prelude.Read, Int -> GetCallAnalyticsJob -> ShowS
[GetCallAnalyticsJob] -> ShowS
GetCallAnalyticsJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCallAnalyticsJob] -> ShowS
$cshowList :: [GetCallAnalyticsJob] -> ShowS
show :: GetCallAnalyticsJob -> String
$cshow :: GetCallAnalyticsJob -> String
showsPrec :: Int -> GetCallAnalyticsJob -> ShowS
$cshowsPrec :: Int -> GetCallAnalyticsJob -> ShowS
Prelude.Show, forall x. Rep GetCallAnalyticsJob x -> GetCallAnalyticsJob
forall x. GetCallAnalyticsJob -> Rep GetCallAnalyticsJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCallAnalyticsJob x -> GetCallAnalyticsJob
$cfrom :: forall x. GetCallAnalyticsJob -> Rep GetCallAnalyticsJob x
Prelude.Generic)

-- |
-- Create a value of 'GetCallAnalyticsJob' 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:
--
-- 'callAnalyticsJobName', 'getCallAnalyticsJob_callAnalyticsJobName' - The name of the Call Analytics job you want information about. Job names
-- are case sensitive.
newGetCallAnalyticsJob ::
  -- | 'callAnalyticsJobName'
  Prelude.Text ->
  GetCallAnalyticsJob
newGetCallAnalyticsJob :: Text -> GetCallAnalyticsJob
newGetCallAnalyticsJob Text
pCallAnalyticsJobName_ =
  GetCallAnalyticsJob'
    { $sel:callAnalyticsJobName:GetCallAnalyticsJob' :: Text
callAnalyticsJobName =
        Text
pCallAnalyticsJobName_
    }

-- | The name of the Call Analytics job you want information about. Job names
-- are case sensitive.
getCallAnalyticsJob_callAnalyticsJobName :: Lens.Lens' GetCallAnalyticsJob Prelude.Text
getCallAnalyticsJob_callAnalyticsJobName :: Lens' GetCallAnalyticsJob Text
getCallAnalyticsJob_callAnalyticsJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallAnalyticsJob' {Text
callAnalyticsJobName :: Text
$sel:callAnalyticsJobName:GetCallAnalyticsJob' :: GetCallAnalyticsJob -> Text
callAnalyticsJobName} -> Text
callAnalyticsJobName) (\s :: GetCallAnalyticsJob
s@GetCallAnalyticsJob' {} Text
a -> GetCallAnalyticsJob
s {$sel:callAnalyticsJobName:GetCallAnalyticsJob' :: Text
callAnalyticsJobName = Text
a} :: GetCallAnalyticsJob)

instance Core.AWSRequest GetCallAnalyticsJob where
  type
    AWSResponse GetCallAnalyticsJob =
      GetCallAnalyticsJobResponse
  request :: (Service -> Service)
-> GetCallAnalyticsJob -> Request GetCallAnalyticsJob
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 GetCallAnalyticsJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetCallAnalyticsJob)))
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 CallAnalyticsJob -> Int -> GetCallAnalyticsJobResponse
GetCallAnalyticsJobResponse'
            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
"CallAnalyticsJob")
            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 GetCallAnalyticsJob where
  hashWithSalt :: Int -> GetCallAnalyticsJob -> Int
hashWithSalt Int
_salt GetCallAnalyticsJob' {Text
callAnalyticsJobName :: Text
$sel:callAnalyticsJobName:GetCallAnalyticsJob' :: GetCallAnalyticsJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
callAnalyticsJobName

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

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

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

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

-- | /See:/ 'newGetCallAnalyticsJobResponse' smart constructor.
data GetCallAnalyticsJobResponse = GetCallAnalyticsJobResponse'
  { -- | Provides detailed information about the specified Call Analytics job,
    -- including job status and, if applicable, failure reason.
    GetCallAnalyticsJobResponse -> Maybe CallAnalyticsJob
callAnalyticsJob :: Prelude.Maybe CallAnalyticsJob,
    -- | The response's http status code.
    GetCallAnalyticsJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCallAnalyticsJobResponse -> GetCallAnalyticsJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCallAnalyticsJobResponse -> GetCallAnalyticsJobResponse -> Bool
$c/= :: GetCallAnalyticsJobResponse -> GetCallAnalyticsJobResponse -> Bool
== :: GetCallAnalyticsJobResponse -> GetCallAnalyticsJobResponse -> Bool
$c== :: GetCallAnalyticsJobResponse -> GetCallAnalyticsJobResponse -> Bool
Prelude.Eq, ReadPrec [GetCallAnalyticsJobResponse]
ReadPrec GetCallAnalyticsJobResponse
Int -> ReadS GetCallAnalyticsJobResponse
ReadS [GetCallAnalyticsJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCallAnalyticsJobResponse]
$creadListPrec :: ReadPrec [GetCallAnalyticsJobResponse]
readPrec :: ReadPrec GetCallAnalyticsJobResponse
$creadPrec :: ReadPrec GetCallAnalyticsJobResponse
readList :: ReadS [GetCallAnalyticsJobResponse]
$creadList :: ReadS [GetCallAnalyticsJobResponse]
readsPrec :: Int -> ReadS GetCallAnalyticsJobResponse
$creadsPrec :: Int -> ReadS GetCallAnalyticsJobResponse
Prelude.Read, Int -> GetCallAnalyticsJobResponse -> ShowS
[GetCallAnalyticsJobResponse] -> ShowS
GetCallAnalyticsJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCallAnalyticsJobResponse] -> ShowS
$cshowList :: [GetCallAnalyticsJobResponse] -> ShowS
show :: GetCallAnalyticsJobResponse -> String
$cshow :: GetCallAnalyticsJobResponse -> String
showsPrec :: Int -> GetCallAnalyticsJobResponse -> ShowS
$cshowsPrec :: Int -> GetCallAnalyticsJobResponse -> ShowS
Prelude.Show, forall x.
Rep GetCallAnalyticsJobResponse x -> GetCallAnalyticsJobResponse
forall x.
GetCallAnalyticsJobResponse -> Rep GetCallAnalyticsJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetCallAnalyticsJobResponse x -> GetCallAnalyticsJobResponse
$cfrom :: forall x.
GetCallAnalyticsJobResponse -> Rep GetCallAnalyticsJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCallAnalyticsJobResponse' 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:
--
-- 'callAnalyticsJob', 'getCallAnalyticsJobResponse_callAnalyticsJob' - Provides detailed information about the specified Call Analytics job,
-- including job status and, if applicable, failure reason.
--
-- 'httpStatus', 'getCallAnalyticsJobResponse_httpStatus' - The response's http status code.
newGetCallAnalyticsJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCallAnalyticsJobResponse
newGetCallAnalyticsJobResponse :: Int -> GetCallAnalyticsJobResponse
newGetCallAnalyticsJobResponse Int
pHttpStatus_ =
  GetCallAnalyticsJobResponse'
    { $sel:callAnalyticsJob:GetCallAnalyticsJobResponse' :: Maybe CallAnalyticsJob
callAnalyticsJob =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCallAnalyticsJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Provides detailed information about the specified Call Analytics job,
-- including job status and, if applicable, failure reason.
getCallAnalyticsJobResponse_callAnalyticsJob :: Lens.Lens' GetCallAnalyticsJobResponse (Prelude.Maybe CallAnalyticsJob)
getCallAnalyticsJobResponse_callAnalyticsJob :: Lens' GetCallAnalyticsJobResponse (Maybe CallAnalyticsJob)
getCallAnalyticsJobResponse_callAnalyticsJob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCallAnalyticsJobResponse' {Maybe CallAnalyticsJob
callAnalyticsJob :: Maybe CallAnalyticsJob
$sel:callAnalyticsJob:GetCallAnalyticsJobResponse' :: GetCallAnalyticsJobResponse -> Maybe CallAnalyticsJob
callAnalyticsJob} -> Maybe CallAnalyticsJob
callAnalyticsJob) (\s :: GetCallAnalyticsJobResponse
s@GetCallAnalyticsJobResponse' {} Maybe CallAnalyticsJob
a -> GetCallAnalyticsJobResponse
s {$sel:callAnalyticsJob:GetCallAnalyticsJobResponse' :: Maybe CallAnalyticsJob
callAnalyticsJob = Maybe CallAnalyticsJob
a} :: GetCallAnalyticsJobResponse)

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

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