{-# 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.ConnectParticipant.SendMessage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sends a message.
--
-- @ConnectionToken@ is used for invoking this API instead of
-- @ParticipantToken@.
--
-- The Amazon Connect Participant Service APIs do not use
-- <https://docs.aws.amazon.com/general/latest/gr/signature-version-4.html Signature Version 4 authentication>.
module Amazonka.ConnectParticipant.SendMessage
  ( -- * Creating a Request
    SendMessage (..),
    newSendMessage,

    -- * Request Lenses
    sendMessage_clientToken,
    sendMessage_contentType,
    sendMessage_content,
    sendMessage_connectionToken,

    -- * Destructuring the Response
    SendMessageResponse (..),
    newSendMessageResponse,

    -- * Response Lenses
    sendMessageResponse_absoluteTime,
    sendMessageResponse_id,
    sendMessageResponse_httpStatus,
  )
where

import Amazonka.ConnectParticipant.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:/ 'newSendMessage' smart constructor.
data SendMessage = SendMessage'
  { -- | 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>.
    SendMessage -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The type of the content. Supported types are @text\/plain@,
    -- @text\/markdown@, and @application\/json@.
    SendMessage -> Text
contentType :: Prelude.Text,
    -- | The content of the message.
    --
    -- -   For @text\/plain@ and @text\/markdown@, the Length Constraints are
    --     Minimum of 1, Maximum of 1024.
    --
    -- -   For @application\/json@, the Length Constraints are Minimum of 1,
    --     Maximum of 12000.
    SendMessage -> Text
content :: Prelude.Text,
    -- | The authentication token associated with the connection.
    SendMessage -> Text
connectionToken :: Prelude.Text
  }
  deriving (SendMessage -> SendMessage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendMessage -> SendMessage -> Bool
$c/= :: SendMessage -> SendMessage -> Bool
== :: SendMessage -> SendMessage -> Bool
$c== :: SendMessage -> SendMessage -> Bool
Prelude.Eq, ReadPrec [SendMessage]
ReadPrec SendMessage
Int -> ReadS SendMessage
ReadS [SendMessage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendMessage]
$creadListPrec :: ReadPrec [SendMessage]
readPrec :: ReadPrec SendMessage
$creadPrec :: ReadPrec SendMessage
readList :: ReadS [SendMessage]
$creadList :: ReadS [SendMessage]
readsPrec :: Int -> ReadS SendMessage
$creadsPrec :: Int -> ReadS SendMessage
Prelude.Read, Int -> SendMessage -> ShowS
[SendMessage] -> ShowS
SendMessage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendMessage] -> ShowS
$cshowList :: [SendMessage] -> ShowS
show :: SendMessage -> String
$cshow :: SendMessage -> String
showsPrec :: Int -> SendMessage -> ShowS
$cshowsPrec :: Int -> SendMessage -> ShowS
Prelude.Show, forall x. Rep SendMessage x -> SendMessage
forall x. SendMessage -> Rep SendMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessage x -> SendMessage
$cfrom :: forall x. SendMessage -> Rep SendMessage x
Prelude.Generic)

-- |
-- Create a value of 'SendMessage' 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:
--
-- 'clientToken', 'sendMessage_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>.
--
-- 'contentType', 'sendMessage_contentType' - The type of the content. Supported types are @text\/plain@,
-- @text\/markdown@, and @application\/json@.
--
-- 'content', 'sendMessage_content' - The content of the message.
--
-- -   For @text\/plain@ and @text\/markdown@, the Length Constraints are
--     Minimum of 1, Maximum of 1024.
--
-- -   For @application\/json@, the Length Constraints are Minimum of 1,
--     Maximum of 12000.
--
-- 'connectionToken', 'sendMessage_connectionToken' - The authentication token associated with the connection.
newSendMessage ::
  -- | 'contentType'
  Prelude.Text ->
  -- | 'content'
  Prelude.Text ->
  -- | 'connectionToken'
  Prelude.Text ->
  SendMessage
newSendMessage :: Text -> Text -> Text -> SendMessage
newSendMessage
  Text
pContentType_
  Text
pContent_
  Text
pConnectionToken_ =
    SendMessage'
      { $sel:clientToken:SendMessage' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:contentType:SendMessage' :: Text
contentType = Text
pContentType_,
        $sel:content:SendMessage' :: Text
content = Text
pContent_,
        $sel:connectionToken:SendMessage' :: Text
connectionToken = Text
pConnectionToken_
      }

-- | 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>.
sendMessage_clientToken :: Lens.Lens' SendMessage (Prelude.Maybe Prelude.Text)
sendMessage_clientToken :: Lens' SendMessage (Maybe Text)
sendMessage_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessage' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:SendMessage' :: SendMessage -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: SendMessage
s@SendMessage' {} Maybe Text
a -> SendMessage
s {$sel:clientToken:SendMessage' :: Maybe Text
clientToken = Maybe Text
a} :: SendMessage)

-- | The type of the content. Supported types are @text\/plain@,
-- @text\/markdown@, and @application\/json@.
sendMessage_contentType :: Lens.Lens' SendMessage Prelude.Text
sendMessage_contentType :: Lens' SendMessage Text
sendMessage_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessage' {Text
contentType :: Text
$sel:contentType:SendMessage' :: SendMessage -> Text
contentType} -> Text
contentType) (\s :: SendMessage
s@SendMessage' {} Text
a -> SendMessage
s {$sel:contentType:SendMessage' :: Text
contentType = Text
a} :: SendMessage)

-- | The content of the message.
--
-- -   For @text\/plain@ and @text\/markdown@, the Length Constraints are
--     Minimum of 1, Maximum of 1024.
--
-- -   For @application\/json@, the Length Constraints are Minimum of 1,
--     Maximum of 12000.
sendMessage_content :: Lens.Lens' SendMessage Prelude.Text
sendMessage_content :: Lens' SendMessage Text
sendMessage_content = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessage' {Text
content :: Text
$sel:content:SendMessage' :: SendMessage -> Text
content} -> Text
content) (\s :: SendMessage
s@SendMessage' {} Text
a -> SendMessage
s {$sel:content:SendMessage' :: Text
content = Text
a} :: SendMessage)

-- | The authentication token associated with the connection.
sendMessage_connectionToken :: Lens.Lens' SendMessage Prelude.Text
sendMessage_connectionToken :: Lens' SendMessage Text
sendMessage_connectionToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessage' {Text
connectionToken :: Text
$sel:connectionToken:SendMessage' :: SendMessage -> Text
connectionToken} -> Text
connectionToken) (\s :: SendMessage
s@SendMessage' {} Text
a -> SendMessage
s {$sel:connectionToken:SendMessage' :: Text
connectionToken = Text
a} :: SendMessage)

instance Core.AWSRequest SendMessage where
  type AWSResponse SendMessage = SendMessageResponse
  request :: (Service -> Service) -> SendMessage -> Request SendMessage
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 SendMessage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SendMessage)))
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 -> Maybe Text -> Int -> SendMessageResponse
SendMessageResponse'
            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
"AbsoluteTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            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 SendMessage where
  hashWithSalt :: Int -> SendMessage -> Int
hashWithSalt Int
_salt SendMessage' {Maybe Text
Text
connectionToken :: Text
content :: Text
contentType :: Text
clientToken :: Maybe Text
$sel:connectionToken:SendMessage' :: SendMessage -> Text
$sel:content:SendMessage' :: SendMessage -> Text
$sel:contentType:SendMessage' :: SendMessage -> Text
$sel:clientToken:SendMessage' :: SendMessage -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
contentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
content
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionToken

instance Prelude.NFData SendMessage where
  rnf :: SendMessage -> ()
rnf SendMessage' {Maybe Text
Text
connectionToken :: Text
content :: Text
contentType :: Text
clientToken :: Maybe Text
$sel:connectionToken:SendMessage' :: SendMessage -> Text
$sel:content:SendMessage' :: SendMessage -> Text
$sel:contentType:SendMessage' :: SendMessage -> Text
$sel:clientToken:SendMessage' :: SendMessage -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
contentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
content
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionToken

instance Data.ToHeaders SendMessage where
  toHeaders :: SendMessage -> ResponseHeaders
toHeaders SendMessage' {Maybe Text
Text
connectionToken :: Text
content :: Text
contentType :: Text
clientToken :: Maybe Text
$sel:connectionToken:SendMessage' :: SendMessage -> Text
$sel:content:SendMessage' :: SendMessage -> Text
$sel:contentType:SendMessage' :: SendMessage -> Text
$sel:clientToken:SendMessage' :: SendMessage -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amz-Bearer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
connectionToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON SendMessage where
  toJSON :: SendMessage -> Value
toJSON SendMessage' {Maybe Text
Text
connectionToken :: Text
content :: Text
contentType :: Text
clientToken :: Maybe Text
$sel:connectionToken:SendMessage' :: SendMessage -> Text
$sel:content:SendMessage' :: SendMessage -> Text
$sel:contentType:SendMessage' :: SendMessage -> Text
$sel:clientToken:SendMessage' :: SendMessage -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientToken" 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
clientToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"ContentType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
contentType),
            forall a. a -> Maybe a
Prelude.Just (Key
"Content" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
content)
          ]
      )

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

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

-- | /See:/ 'newSendMessageResponse' smart constructor.
data SendMessageResponse = SendMessageResponse'
  { -- | The time when the message was sent.
    --
    -- It\'s specified in ISO 8601 format: yyyy-MM-ddThh:mm:ss.SSSZ. For
    -- example, 2019-11-08T02:41:28.172Z.
    SendMessageResponse -> Maybe Text
absoluteTime :: Prelude.Maybe Prelude.Text,
    -- | The ID of the message.
    SendMessageResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    SendMessageResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SendMessageResponse -> SendMessageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendMessageResponse -> SendMessageResponse -> Bool
$c/= :: SendMessageResponse -> SendMessageResponse -> Bool
== :: SendMessageResponse -> SendMessageResponse -> Bool
$c== :: SendMessageResponse -> SendMessageResponse -> Bool
Prelude.Eq, ReadPrec [SendMessageResponse]
ReadPrec SendMessageResponse
Int -> ReadS SendMessageResponse
ReadS [SendMessageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendMessageResponse]
$creadListPrec :: ReadPrec [SendMessageResponse]
readPrec :: ReadPrec SendMessageResponse
$creadPrec :: ReadPrec SendMessageResponse
readList :: ReadS [SendMessageResponse]
$creadList :: ReadS [SendMessageResponse]
readsPrec :: Int -> ReadS SendMessageResponse
$creadsPrec :: Int -> ReadS SendMessageResponse
Prelude.Read, Int -> SendMessageResponse -> ShowS
[SendMessageResponse] -> ShowS
SendMessageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendMessageResponse] -> ShowS
$cshowList :: [SendMessageResponse] -> ShowS
show :: SendMessageResponse -> String
$cshow :: SendMessageResponse -> String
showsPrec :: Int -> SendMessageResponse -> ShowS
$cshowsPrec :: Int -> SendMessageResponse -> ShowS
Prelude.Show, forall x. Rep SendMessageResponse x -> SendMessageResponse
forall x. SendMessageResponse -> Rep SendMessageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessageResponse x -> SendMessageResponse
$cfrom :: forall x. SendMessageResponse -> Rep SendMessageResponse x
Prelude.Generic)

-- |
-- Create a value of 'SendMessageResponse' 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:
--
-- 'absoluteTime', 'sendMessageResponse_absoluteTime' - The time when the message was sent.
--
-- It\'s specified in ISO 8601 format: yyyy-MM-ddThh:mm:ss.SSSZ. For
-- example, 2019-11-08T02:41:28.172Z.
--
-- 'id', 'sendMessageResponse_id' - The ID of the message.
--
-- 'httpStatus', 'sendMessageResponse_httpStatus' - The response's http status code.
newSendMessageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SendMessageResponse
newSendMessageResponse :: Int -> SendMessageResponse
newSendMessageResponse Int
pHttpStatus_ =
  SendMessageResponse'
    { $sel:absoluteTime:SendMessageResponse' :: Maybe Text
absoluteTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:id:SendMessageResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SendMessageResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The time when the message was sent.
--
-- It\'s specified in ISO 8601 format: yyyy-MM-ddThh:mm:ss.SSSZ. For
-- example, 2019-11-08T02:41:28.172Z.
sendMessageResponse_absoluteTime :: Lens.Lens' SendMessageResponse (Prelude.Maybe Prelude.Text)
sendMessageResponse_absoluteTime :: Lens' SendMessageResponse (Maybe Text)
sendMessageResponse_absoluteTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessageResponse' {Maybe Text
absoluteTime :: Maybe Text
$sel:absoluteTime:SendMessageResponse' :: SendMessageResponse -> Maybe Text
absoluteTime} -> Maybe Text
absoluteTime) (\s :: SendMessageResponse
s@SendMessageResponse' {} Maybe Text
a -> SendMessageResponse
s {$sel:absoluteTime:SendMessageResponse' :: Maybe Text
absoluteTime = Maybe Text
a} :: SendMessageResponse)

-- | The ID of the message.
sendMessageResponse_id :: Lens.Lens' SendMessageResponse (Prelude.Maybe Prelude.Text)
sendMessageResponse_id :: Lens' SendMessageResponse (Maybe Text)
sendMessageResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendMessageResponse' {Maybe Text
id :: Maybe Text
$sel:id:SendMessageResponse' :: SendMessageResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: SendMessageResponse
s@SendMessageResponse' {} Maybe Text
a -> SendMessageResponse
s {$sel:id:SendMessageResponse' :: Maybe Text
id = Maybe Text
a} :: SendMessageResponse)

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

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