{-# 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.Connect.StopContactRecording
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops recording a call when a contact is being recorded.
-- StopContactRecording is a one-time action. If you use
-- StopContactRecording to stop recording an ongoing call, you can\'t use
-- StartContactRecording to restart it. For scenarios where the recording
-- has started and you want to suspend it for sensitive information (for
-- example, to collect a credit card number), and then restart it, use
-- SuspendContactRecording and ResumeContactRecording.
--
-- Only voice recordings are supported at this time.
module Amazonka.Connect.StopContactRecording
  ( -- * Creating a Request
    StopContactRecording (..),
    newStopContactRecording,

    -- * Request Lenses
    stopContactRecording_instanceId,
    stopContactRecording_contactId,
    stopContactRecording_initialContactId,

    -- * Destructuring the Response
    StopContactRecordingResponse (..),
    newStopContactRecordingResponse,

    -- * Response Lenses
    stopContactRecordingResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStopContactRecording' smart constructor.
data StopContactRecording = StopContactRecording'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    StopContactRecording -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the contact.
    StopContactRecording -> Text
contactId :: Prelude.Text,
    -- | The identifier of the contact. This is the identifier of the contact
    -- associated with the first interaction with the contact center.
    StopContactRecording -> Text
initialContactId :: Prelude.Text
  }
  deriving (StopContactRecording -> StopContactRecording -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopContactRecording -> StopContactRecording -> Bool
$c/= :: StopContactRecording -> StopContactRecording -> Bool
== :: StopContactRecording -> StopContactRecording -> Bool
$c== :: StopContactRecording -> StopContactRecording -> Bool
Prelude.Eq, ReadPrec [StopContactRecording]
ReadPrec StopContactRecording
Int -> ReadS StopContactRecording
ReadS [StopContactRecording]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopContactRecording]
$creadListPrec :: ReadPrec [StopContactRecording]
readPrec :: ReadPrec StopContactRecording
$creadPrec :: ReadPrec StopContactRecording
readList :: ReadS [StopContactRecording]
$creadList :: ReadS [StopContactRecording]
readsPrec :: Int -> ReadS StopContactRecording
$creadsPrec :: Int -> ReadS StopContactRecording
Prelude.Read, Int -> StopContactRecording -> ShowS
[StopContactRecording] -> ShowS
StopContactRecording -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopContactRecording] -> ShowS
$cshowList :: [StopContactRecording] -> ShowS
show :: StopContactRecording -> String
$cshow :: StopContactRecording -> String
showsPrec :: Int -> StopContactRecording -> ShowS
$cshowsPrec :: Int -> StopContactRecording -> ShowS
Prelude.Show, forall x. Rep StopContactRecording x -> StopContactRecording
forall x. StopContactRecording -> Rep StopContactRecording x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopContactRecording x -> StopContactRecording
$cfrom :: forall x. StopContactRecording -> Rep StopContactRecording x
Prelude.Generic)

-- |
-- Create a value of 'StopContactRecording' 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:
--
-- 'instanceId', 'stopContactRecording_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'contactId', 'stopContactRecording_contactId' - The identifier of the contact.
--
-- 'initialContactId', 'stopContactRecording_initialContactId' - The identifier of the contact. This is the identifier of the contact
-- associated with the first interaction with the contact center.
newStopContactRecording ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactId'
  Prelude.Text ->
  -- | 'initialContactId'
  Prelude.Text ->
  StopContactRecording
newStopContactRecording :: Text -> Text -> Text -> StopContactRecording
newStopContactRecording
  Text
pInstanceId_
  Text
pContactId_
  Text
pInitialContactId_ =
    StopContactRecording'
      { $sel:instanceId:StopContactRecording' :: Text
instanceId = Text
pInstanceId_,
        $sel:contactId:StopContactRecording' :: Text
contactId = Text
pContactId_,
        $sel:initialContactId:StopContactRecording' :: Text
initialContactId = Text
pInitialContactId_
      }

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
stopContactRecording_instanceId :: Lens.Lens' StopContactRecording Prelude.Text
stopContactRecording_instanceId :: Lens' StopContactRecording Text
stopContactRecording_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopContactRecording' {Text
instanceId :: Text
$sel:instanceId:StopContactRecording' :: StopContactRecording -> Text
instanceId} -> Text
instanceId) (\s :: StopContactRecording
s@StopContactRecording' {} Text
a -> StopContactRecording
s {$sel:instanceId:StopContactRecording' :: Text
instanceId = Text
a} :: StopContactRecording)

-- | The identifier of the contact.
stopContactRecording_contactId :: Lens.Lens' StopContactRecording Prelude.Text
stopContactRecording_contactId :: Lens' StopContactRecording Text
stopContactRecording_contactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopContactRecording' {Text
contactId :: Text
$sel:contactId:StopContactRecording' :: StopContactRecording -> Text
contactId} -> Text
contactId) (\s :: StopContactRecording
s@StopContactRecording' {} Text
a -> StopContactRecording
s {$sel:contactId:StopContactRecording' :: Text
contactId = Text
a} :: StopContactRecording)

-- | The identifier of the contact. This is the identifier of the contact
-- associated with the first interaction with the contact center.
stopContactRecording_initialContactId :: Lens.Lens' StopContactRecording Prelude.Text
stopContactRecording_initialContactId :: Lens' StopContactRecording Text
stopContactRecording_initialContactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopContactRecording' {Text
initialContactId :: Text
$sel:initialContactId:StopContactRecording' :: StopContactRecording -> Text
initialContactId} -> Text
initialContactId) (\s :: StopContactRecording
s@StopContactRecording' {} Text
a -> StopContactRecording
s {$sel:initialContactId:StopContactRecording' :: Text
initialContactId = Text
a} :: StopContactRecording)

instance Core.AWSRequest StopContactRecording where
  type
    AWSResponse StopContactRecording =
      StopContactRecordingResponse
  request :: (Service -> Service)
-> StopContactRecording -> Request StopContactRecording
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 StopContactRecording
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopContactRecording)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> StopContactRecordingResponse
StopContactRecordingResponse'
            forall (f :: * -> *) a b. Functor 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 StopContactRecording where
  hashWithSalt :: Int -> StopContactRecording -> Int
hashWithSalt Int
_salt StopContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:StopContactRecording' :: StopContactRecording -> Text
$sel:contactId:StopContactRecording' :: StopContactRecording -> Text
$sel:instanceId:StopContactRecording' :: StopContactRecording -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
contactId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
initialContactId

instance Prelude.NFData StopContactRecording where
  rnf :: StopContactRecording -> ()
rnf StopContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:StopContactRecording' :: StopContactRecording -> Text
$sel:contactId:StopContactRecording' :: StopContactRecording -> Text
$sel:instanceId:StopContactRecording' :: StopContactRecording -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
contactId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
initialContactId

instance Data.ToHeaders StopContactRecording where
  toHeaders :: StopContactRecording -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StopContactRecording where
  toJSON :: StopContactRecording -> Value
toJSON StopContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:StopContactRecording' :: StopContactRecording -> Text
$sel:contactId:StopContactRecording' :: StopContactRecording -> Text
$sel:instanceId:StopContactRecording' :: StopContactRecording -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ContactId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
contactId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"InitialContactId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
initialContactId)
          ]
      )

instance Data.ToPath StopContactRecording where
  toPath :: StopContactRecording -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/contact/stop-recording"

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

-- | /See:/ 'newStopContactRecordingResponse' smart constructor.
data StopContactRecordingResponse = StopContactRecordingResponse'
  { -- | The response's http status code.
    StopContactRecordingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopContactRecordingResponse
-> StopContactRecordingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopContactRecordingResponse
-> StopContactRecordingResponse -> Bool
$c/= :: StopContactRecordingResponse
-> StopContactRecordingResponse -> Bool
== :: StopContactRecordingResponse
-> StopContactRecordingResponse -> Bool
$c== :: StopContactRecordingResponse
-> StopContactRecordingResponse -> Bool
Prelude.Eq, ReadPrec [StopContactRecordingResponse]
ReadPrec StopContactRecordingResponse
Int -> ReadS StopContactRecordingResponse
ReadS [StopContactRecordingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopContactRecordingResponse]
$creadListPrec :: ReadPrec [StopContactRecordingResponse]
readPrec :: ReadPrec StopContactRecordingResponse
$creadPrec :: ReadPrec StopContactRecordingResponse
readList :: ReadS [StopContactRecordingResponse]
$creadList :: ReadS [StopContactRecordingResponse]
readsPrec :: Int -> ReadS StopContactRecordingResponse
$creadsPrec :: Int -> ReadS StopContactRecordingResponse
Prelude.Read, Int -> StopContactRecordingResponse -> ShowS
[StopContactRecordingResponse] -> ShowS
StopContactRecordingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopContactRecordingResponse] -> ShowS
$cshowList :: [StopContactRecordingResponse] -> ShowS
show :: StopContactRecordingResponse -> String
$cshow :: StopContactRecordingResponse -> String
showsPrec :: Int -> StopContactRecordingResponse -> ShowS
$cshowsPrec :: Int -> StopContactRecordingResponse -> ShowS
Prelude.Show, forall x.
Rep StopContactRecordingResponse x -> StopContactRecordingResponse
forall x.
StopContactRecordingResponse -> Rep StopContactRecordingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopContactRecordingResponse x -> StopContactRecordingResponse
$cfrom :: forall x.
StopContactRecordingResponse -> Rep StopContactRecordingResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopContactRecordingResponse' 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:
--
-- 'httpStatus', 'stopContactRecordingResponse_httpStatus' - The response's http status code.
newStopContactRecordingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopContactRecordingResponse
newStopContactRecordingResponse :: Int -> StopContactRecordingResponse
newStopContactRecordingResponse Int
pHttpStatus_ =
  StopContactRecordingResponse'
    { $sel:httpStatus:StopContactRecordingResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData StopContactRecordingResponse where
  rnf :: StopContactRecordingResponse -> ()
rnf StopContactRecordingResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopContactRecordingResponse' :: StopContactRecordingResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus