{-# 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.APIGatewayManagementAPI.PostToConnection
-- 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 the provided data to the specified connection.
module Amazonka.APIGatewayManagementAPI.PostToConnection
  ( -- * Creating a Request
    PostToConnection (..),
    newPostToConnection,

    -- * Request Lenses
    postToConnection_connectionId,
    postToConnection_data,

    -- * Destructuring the Response
    PostToConnectionResponse (..),
    newPostToConnectionResponse,
  )
where

import Amazonka.APIGatewayManagementAPI.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:/ 'newPostToConnection' smart constructor.
data PostToConnection = PostToConnection'
  { -- | The identifier of the connection that a specific client is using.
    PostToConnection -> Text
connectionId :: Prelude.Text,
    -- | The data to be sent to the client specified by its connection id.
    PostToConnection -> ByteString
data' :: Prelude.ByteString
  }
  deriving (PostToConnection -> PostToConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostToConnection -> PostToConnection -> Bool
$c/= :: PostToConnection -> PostToConnection -> Bool
== :: PostToConnection -> PostToConnection -> Bool
$c== :: PostToConnection -> PostToConnection -> Bool
Prelude.Eq, ReadPrec [PostToConnection]
ReadPrec PostToConnection
Int -> ReadS PostToConnection
ReadS [PostToConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostToConnection]
$creadListPrec :: ReadPrec [PostToConnection]
readPrec :: ReadPrec PostToConnection
$creadPrec :: ReadPrec PostToConnection
readList :: ReadS [PostToConnection]
$creadList :: ReadS [PostToConnection]
readsPrec :: Int -> ReadS PostToConnection
$creadsPrec :: Int -> ReadS PostToConnection
Prelude.Read, Int -> PostToConnection -> ShowS
[PostToConnection] -> ShowS
PostToConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostToConnection] -> ShowS
$cshowList :: [PostToConnection] -> ShowS
show :: PostToConnection -> String
$cshow :: PostToConnection -> String
showsPrec :: Int -> PostToConnection -> ShowS
$cshowsPrec :: Int -> PostToConnection -> ShowS
Prelude.Show, forall x. Rep PostToConnection x -> PostToConnection
forall x. PostToConnection -> Rep PostToConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostToConnection x -> PostToConnection
$cfrom :: forall x. PostToConnection -> Rep PostToConnection x
Prelude.Generic)

-- |
-- Create a value of 'PostToConnection' 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:
--
-- 'connectionId', 'postToConnection_connectionId' - The identifier of the connection that a specific client is using.
--
-- 'data'', 'postToConnection_data' - The data to be sent to the client specified by its connection id.
newPostToConnection ::
  -- | 'connectionId'
  Prelude.Text ->
  -- | 'data''
  Prelude.ByteString ->
  PostToConnection
newPostToConnection :: Text -> ByteString -> PostToConnection
newPostToConnection Text
pConnectionId_ ByteString
pData_ =
  PostToConnection'
    { $sel:connectionId:PostToConnection' :: Text
connectionId = Text
pConnectionId_,
      $sel:data':PostToConnection' :: ByteString
data' = ByteString
pData_
    }

-- | The identifier of the connection that a specific client is using.
postToConnection_connectionId :: Lens.Lens' PostToConnection Prelude.Text
postToConnection_connectionId :: Lens' PostToConnection Text
postToConnection_connectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostToConnection' {Text
connectionId :: Text
$sel:connectionId:PostToConnection' :: PostToConnection -> Text
connectionId} -> Text
connectionId) (\s :: PostToConnection
s@PostToConnection' {} Text
a -> PostToConnection
s {$sel:connectionId:PostToConnection' :: Text
connectionId = Text
a} :: PostToConnection)

-- | The data to be sent to the client specified by its connection id.
postToConnection_data :: Lens.Lens' PostToConnection Prelude.ByteString
postToConnection_data :: Lens' PostToConnection ByteString
postToConnection_data = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PostToConnection' {ByteString
data' :: ByteString
$sel:data':PostToConnection' :: PostToConnection -> ByteString
data'} -> ByteString
data') (\s :: PostToConnection
s@PostToConnection' {} ByteString
a -> PostToConnection
s {$sel:data':PostToConnection' :: ByteString
data' = ByteString
a} :: PostToConnection)

instance Core.AWSRequest PostToConnection where
  type
    AWSResponse PostToConnection =
      PostToConnectionResponse
  request :: (Service -> Service)
-> PostToConnection -> Request PostToConnection
request Service -> Service
overrides =
    forall a. (ToRequest a, ToBody a) => Service -> a -> Request a
Request.postBody (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PostToConnection
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PostToConnection)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PostToConnectionResponse
PostToConnectionResponse'

instance Prelude.Hashable PostToConnection where
  hashWithSalt :: Int -> PostToConnection -> Int
hashWithSalt Int
_salt PostToConnection' {ByteString
Text
data' :: ByteString
connectionId :: Text
$sel:data':PostToConnection' :: PostToConnection -> ByteString
$sel:connectionId:PostToConnection' :: PostToConnection -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ByteString
data'

instance Prelude.NFData PostToConnection where
  rnf :: PostToConnection -> ()
rnf PostToConnection' {ByteString
Text
data' :: ByteString
connectionId :: Text
$sel:data':PostToConnection' :: PostToConnection -> ByteString
$sel:connectionId:PostToConnection' :: PostToConnection -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
connectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ByteString
data'

instance Data.ToBody PostToConnection where
  toBody :: PostToConnection -> RequestBody
toBody PostToConnection' {ByteString
Text
data' :: ByteString
connectionId :: Text
$sel:data':PostToConnection' :: PostToConnection -> ByteString
$sel:connectionId:PostToConnection' :: PostToConnection -> Text
..} = forall a. ToBody a => a -> RequestBody
Data.toBody ByteString
data'

instance Data.ToHeaders PostToConnection where
  toHeaders :: PostToConnection -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath PostToConnection where
  toPath :: PostToConnection -> ByteString
toPath PostToConnection' {ByteString
Text
data' :: ByteString
connectionId :: Text
$sel:data':PostToConnection' :: PostToConnection -> ByteString
$sel:connectionId:PostToConnection' :: PostToConnection -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/@connections/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
connectionId]

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

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

-- |
-- Create a value of 'PostToConnectionResponse' 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.
newPostToConnectionResponse ::
  PostToConnectionResponse
newPostToConnectionResponse :: PostToConnectionResponse
newPostToConnectionResponse =
  PostToConnectionResponse
PostToConnectionResponse'

instance Prelude.NFData PostToConnectionResponse where
  rnf :: PostToConnectionResponse -> ()
rnf PostToConnectionResponse
_ = ()