{-# 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.SuspendContactRecording
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- When a contact is being recorded, this API suspends recording the call.
-- For example, you might suspend the call recording while collecting
-- sensitive information, such as a credit card number. Then use
-- ResumeContactRecording to restart recording.
--
-- The period of time that the recording is suspended is filled with
-- silence in the final recording.
--
-- Only voice recordings are supported at this time.
module Amazonka.Connect.SuspendContactRecording
  ( -- * Creating a Request
    SuspendContactRecording (..),
    newSuspendContactRecording,

    -- * Request Lenses
    suspendContactRecording_instanceId,
    suspendContactRecording_contactId,
    suspendContactRecording_initialContactId,

    -- * Destructuring the Response
    SuspendContactRecordingResponse (..),
    newSuspendContactRecordingResponse,

    -- * Response Lenses
    suspendContactRecordingResponse_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:/ 'newSuspendContactRecording' smart constructor.
data SuspendContactRecording = SuspendContactRecording'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    SuspendContactRecording -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the contact.
    SuspendContactRecording -> 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.
    SuspendContactRecording -> Text
initialContactId :: Prelude.Text
  }
  deriving (SuspendContactRecording -> SuspendContactRecording -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SuspendContactRecording -> SuspendContactRecording -> Bool
$c/= :: SuspendContactRecording -> SuspendContactRecording -> Bool
== :: SuspendContactRecording -> SuspendContactRecording -> Bool
$c== :: SuspendContactRecording -> SuspendContactRecording -> Bool
Prelude.Eq, ReadPrec [SuspendContactRecording]
ReadPrec SuspendContactRecording
Int -> ReadS SuspendContactRecording
ReadS [SuspendContactRecording]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SuspendContactRecording]
$creadListPrec :: ReadPrec [SuspendContactRecording]
readPrec :: ReadPrec SuspendContactRecording
$creadPrec :: ReadPrec SuspendContactRecording
readList :: ReadS [SuspendContactRecording]
$creadList :: ReadS [SuspendContactRecording]
readsPrec :: Int -> ReadS SuspendContactRecording
$creadsPrec :: Int -> ReadS SuspendContactRecording
Prelude.Read, Int -> SuspendContactRecording -> ShowS
[SuspendContactRecording] -> ShowS
SuspendContactRecording -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SuspendContactRecording] -> ShowS
$cshowList :: [SuspendContactRecording] -> ShowS
show :: SuspendContactRecording -> String
$cshow :: SuspendContactRecording -> String
showsPrec :: Int -> SuspendContactRecording -> ShowS
$cshowsPrec :: Int -> SuspendContactRecording -> ShowS
Prelude.Show, forall x. Rep SuspendContactRecording x -> SuspendContactRecording
forall x. SuspendContactRecording -> Rep SuspendContactRecording x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SuspendContactRecording x -> SuspendContactRecording
$cfrom :: forall x. SuspendContactRecording -> Rep SuspendContactRecording x
Prelude.Generic)

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

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

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

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

instance Core.AWSRequest SuspendContactRecording where
  type
    AWSResponse SuspendContactRecording =
      SuspendContactRecordingResponse
  request :: (Service -> Service)
-> SuspendContactRecording -> Request SuspendContactRecording
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 SuspendContactRecording
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SuspendContactRecording)))
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 -> SuspendContactRecordingResponse
SuspendContactRecordingResponse'
            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 SuspendContactRecording where
  hashWithSalt :: Int -> SuspendContactRecording -> Int
hashWithSalt Int
_salt SuspendContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:contactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:instanceId:SuspendContactRecording' :: SuspendContactRecording -> 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 SuspendContactRecording where
  rnf :: SuspendContactRecording -> ()
rnf SuspendContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:contactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:instanceId:SuspendContactRecording' :: SuspendContactRecording -> 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 SuspendContactRecording where
  toHeaders :: SuspendContactRecording -> 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 SuspendContactRecording where
  toJSON :: SuspendContactRecording -> Value
toJSON SuspendContactRecording' {Text
initialContactId :: Text
contactId :: Text
instanceId :: Text
$sel:initialContactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:contactId:SuspendContactRecording' :: SuspendContactRecording -> Text
$sel:instanceId:SuspendContactRecording' :: SuspendContactRecording -> 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 SuspendContactRecording where
  toPath :: SuspendContactRecording -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/contact/suspend-recording"

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

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

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

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

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