{-# 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.StartContactStreaming
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Initiates real-time message streaming for a new chat contact.
--
-- For more information about message streaming, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/chat-message-streaming.html Enable real-time chat message streaming>
-- in the /Amazon Connect Administrator Guide/.
module Amazonka.Connect.StartContactStreaming
  ( -- * Creating a Request
    StartContactStreaming (..),
    newStartContactStreaming,

    -- * Request Lenses
    startContactStreaming_instanceId,
    startContactStreaming_contactId,
    startContactStreaming_chatStreamingConfiguration,
    startContactStreaming_clientToken,

    -- * Destructuring the Response
    StartContactStreamingResponse (..),
    newStartContactStreamingResponse,

    -- * Response Lenses
    startContactStreamingResponse_httpStatus,
    startContactStreamingResponse_streamingId,
  )
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:/ 'newStartContactStreaming' smart constructor.
data StartContactStreaming = StartContactStreaming'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    StartContactStreaming -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the contact. This is the identifier of the contact
    -- associated with the first interaction with the contact center.
    StartContactStreaming -> Text
contactId :: Prelude.Text,
    -- | The streaming configuration, such as the Amazon SNS streaming endpoint.
    StartContactStreaming -> ChatStreamingConfiguration
chatStreamingConfiguration :: ChatStreamingConfiguration,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. If not provided, the Amazon Web Services SDK
    -- populates this field. For more information about idempotency, see
    -- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
    StartContactStreaming -> Text
clientToken :: Prelude.Text
  }
  deriving (StartContactStreaming -> StartContactStreaming -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartContactStreaming -> StartContactStreaming -> Bool
$c/= :: StartContactStreaming -> StartContactStreaming -> Bool
== :: StartContactStreaming -> StartContactStreaming -> Bool
$c== :: StartContactStreaming -> StartContactStreaming -> Bool
Prelude.Eq, ReadPrec [StartContactStreaming]
ReadPrec StartContactStreaming
Int -> ReadS StartContactStreaming
ReadS [StartContactStreaming]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartContactStreaming]
$creadListPrec :: ReadPrec [StartContactStreaming]
readPrec :: ReadPrec StartContactStreaming
$creadPrec :: ReadPrec StartContactStreaming
readList :: ReadS [StartContactStreaming]
$creadList :: ReadS [StartContactStreaming]
readsPrec :: Int -> ReadS StartContactStreaming
$creadsPrec :: Int -> ReadS StartContactStreaming
Prelude.Read, Int -> StartContactStreaming -> ShowS
[StartContactStreaming] -> ShowS
StartContactStreaming -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartContactStreaming] -> ShowS
$cshowList :: [StartContactStreaming] -> ShowS
show :: StartContactStreaming -> String
$cshow :: StartContactStreaming -> String
showsPrec :: Int -> StartContactStreaming -> ShowS
$cshowsPrec :: Int -> StartContactStreaming -> ShowS
Prelude.Show, forall x. Rep StartContactStreaming x -> StartContactStreaming
forall x. StartContactStreaming -> Rep StartContactStreaming x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartContactStreaming x -> StartContactStreaming
$cfrom :: forall x. StartContactStreaming -> Rep StartContactStreaming x
Prelude.Generic)

-- |
-- Create a value of 'StartContactStreaming' 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', 'startContactStreaming_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'contactId', 'startContactStreaming_contactId' - The identifier of the contact. This is the identifier of the contact
-- associated with the first interaction with the contact center.
--
-- 'chatStreamingConfiguration', 'startContactStreaming_chatStreamingConfiguration' - The streaming configuration, such as the Amazon SNS streaming endpoint.
--
-- 'clientToken', 'startContactStreaming_clientToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
newStartContactStreaming ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactId'
  Prelude.Text ->
  -- | 'chatStreamingConfiguration'
  ChatStreamingConfiguration ->
  -- | 'clientToken'
  Prelude.Text ->
  StartContactStreaming
newStartContactStreaming :: Text
-> Text
-> ChatStreamingConfiguration
-> Text
-> StartContactStreaming
newStartContactStreaming
  Text
pInstanceId_
  Text
pContactId_
  ChatStreamingConfiguration
pChatStreamingConfiguration_
  Text
pClientToken_ =
    StartContactStreaming'
      { $sel:instanceId:StartContactStreaming' :: Text
instanceId = Text
pInstanceId_,
        $sel:contactId:StartContactStreaming' :: Text
contactId = Text
pContactId_,
        $sel:chatStreamingConfiguration:StartContactStreaming' :: ChatStreamingConfiguration
chatStreamingConfiguration =
          ChatStreamingConfiguration
pChatStreamingConfiguration_,
        $sel:clientToken:StartContactStreaming' :: Text
clientToken = Text
pClientToken_
      }

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

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

-- | The streaming configuration, such as the Amazon SNS streaming endpoint.
startContactStreaming_chatStreamingConfiguration :: Lens.Lens' StartContactStreaming ChatStreamingConfiguration
startContactStreaming_chatStreamingConfiguration :: Lens' StartContactStreaming ChatStreamingConfiguration
startContactStreaming_chatStreamingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartContactStreaming' {ChatStreamingConfiguration
chatStreamingConfiguration :: ChatStreamingConfiguration
$sel:chatStreamingConfiguration:StartContactStreaming' :: StartContactStreaming -> ChatStreamingConfiguration
chatStreamingConfiguration} -> ChatStreamingConfiguration
chatStreamingConfiguration) (\s :: StartContactStreaming
s@StartContactStreaming' {} ChatStreamingConfiguration
a -> StartContactStreaming
s {$sel:chatStreamingConfiguration:StartContactStreaming' :: ChatStreamingConfiguration
chatStreamingConfiguration = ChatStreamingConfiguration
a} :: StartContactStreaming)

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
startContactStreaming_clientToken :: Lens.Lens' StartContactStreaming Prelude.Text
startContactStreaming_clientToken :: Lens' StartContactStreaming Text
startContactStreaming_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartContactStreaming' {Text
clientToken :: Text
$sel:clientToken:StartContactStreaming' :: StartContactStreaming -> Text
clientToken} -> Text
clientToken) (\s :: StartContactStreaming
s@StartContactStreaming' {} Text
a -> StartContactStreaming
s {$sel:clientToken:StartContactStreaming' :: Text
clientToken = Text
a} :: StartContactStreaming)

instance Core.AWSRequest StartContactStreaming where
  type
    AWSResponse StartContactStreaming =
      StartContactStreamingResponse
  request :: (Service -> Service)
-> StartContactStreaming -> Request StartContactStreaming
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 StartContactStreaming
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartContactStreaming)))
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 ->
          Int -> Text -> StartContactStreamingResponse
StartContactStreamingResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"StreamingId")
      )

instance Prelude.Hashable StartContactStreaming where
  hashWithSalt :: Int -> StartContactStreaming -> Int
hashWithSalt Int
_salt StartContactStreaming' {Text
ChatStreamingConfiguration
clientToken :: Text
chatStreamingConfiguration :: ChatStreamingConfiguration
contactId :: Text
instanceId :: Text
$sel:clientToken:StartContactStreaming' :: StartContactStreaming -> Text
$sel:chatStreamingConfiguration:StartContactStreaming' :: StartContactStreaming -> ChatStreamingConfiguration
$sel:contactId:StartContactStreaming' :: StartContactStreaming -> Text
$sel:instanceId:StartContactStreaming' :: StartContactStreaming -> 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` ChatStreamingConfiguration
chatStreamingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken

instance Prelude.NFData StartContactStreaming where
  rnf :: StartContactStreaming -> ()
rnf StartContactStreaming' {Text
ChatStreamingConfiguration
clientToken :: Text
chatStreamingConfiguration :: ChatStreamingConfiguration
contactId :: Text
instanceId :: Text
$sel:clientToken:StartContactStreaming' :: StartContactStreaming -> Text
$sel:chatStreamingConfiguration:StartContactStreaming' :: StartContactStreaming -> ChatStreamingConfiguration
$sel:contactId:StartContactStreaming' :: StartContactStreaming -> Text
$sel:instanceId:StartContactStreaming' :: StartContactStreaming -> 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 ChatStreamingConfiguration
chatStreamingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken

instance Data.ToHeaders StartContactStreaming where
  toHeaders :: StartContactStreaming -> 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 StartContactStreaming where
  toJSON :: StartContactStreaming -> Value
toJSON StartContactStreaming' {Text
ChatStreamingConfiguration
clientToken :: Text
chatStreamingConfiguration :: ChatStreamingConfiguration
contactId :: Text
instanceId :: Text
$sel:clientToken:StartContactStreaming' :: StartContactStreaming -> Text
$sel:chatStreamingConfiguration:StartContactStreaming' :: StartContactStreaming -> ChatStreamingConfiguration
$sel:contactId:StartContactStreaming' :: StartContactStreaming -> Text
$sel:instanceId:StartContactStreaming' :: StartContactStreaming -> 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
"ChatStreamingConfiguration"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ChatStreamingConfiguration
chatStreamingConfiguration
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"ClientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientToken)
          ]
      )

instance Data.ToPath StartContactStreaming where
  toPath :: StartContactStreaming -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/contact/start-streaming"

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

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

-- |
-- Create a value of 'StartContactStreamingResponse' 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', 'startContactStreamingResponse_httpStatus' - The response's http status code.
--
-- 'streamingId', 'startContactStreamingResponse_streamingId' - The identifier of the streaming configuration enabled.
newStartContactStreamingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'streamingId'
  Prelude.Text ->
  StartContactStreamingResponse
newStartContactStreamingResponse :: Int -> Text -> StartContactStreamingResponse
newStartContactStreamingResponse
  Int
pHttpStatus_
  Text
pStreamingId_ =
    StartContactStreamingResponse'
      { $sel:httpStatus:StartContactStreamingResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:streamingId:StartContactStreamingResponse' :: Text
streamingId = Text
pStreamingId_
      }

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

-- | The identifier of the streaming configuration enabled.
startContactStreamingResponse_streamingId :: Lens.Lens' StartContactStreamingResponse Prelude.Text
startContactStreamingResponse_streamingId :: Lens' StartContactStreamingResponse Text
startContactStreamingResponse_streamingId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartContactStreamingResponse' {Text
streamingId :: Text
$sel:streamingId:StartContactStreamingResponse' :: StartContactStreamingResponse -> Text
streamingId} -> Text
streamingId) (\s :: StartContactStreamingResponse
s@StartContactStreamingResponse' {} Text
a -> StartContactStreamingResponse
s {$sel:streamingId:StartContactStreamingResponse' :: Text
streamingId = Text
a} :: StartContactStreamingResponse)

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