{-# 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.IVSChat.DisconnectUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disconnects all connections using a specified user ID from a room. This
-- replicates the
-- <https://docs.aws.amazon.com/ivs/latest/chatmsgapireference/actions-disconnectuser-publish.html DisconnectUser>
-- WebSocket operation in the Amazon IVS Chat Messaging API.
module Amazonka.IVSChat.DisconnectUser
  ( -- * Creating a Request
    DisconnectUser (..),
    newDisconnectUser,

    -- * Request Lenses
    disconnectUser_reason,
    disconnectUser_roomIdentifier,
    disconnectUser_userId,

    -- * Destructuring the Response
    DisconnectUserResponse (..),
    newDisconnectUserResponse,

    -- * Response Lenses
    disconnectUserResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IVSChat.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDisconnectUser' smart constructor.
data DisconnectUser = DisconnectUser'
  { -- | Reason for disconnecting the user.
    DisconnectUser -> Maybe Text
reason :: Prelude.Maybe Prelude.Text,
    -- | Identifier of the room from which the user\'s clients should be
    -- disconnected. Currently this must be an ARN.
    DisconnectUser -> Text
roomIdentifier :: Prelude.Text,
    -- | ID of the user (connection) to disconnect from the room.
    DisconnectUser -> Text
userId :: Prelude.Text
  }
  deriving (DisconnectUser -> DisconnectUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisconnectUser -> DisconnectUser -> Bool
$c/= :: DisconnectUser -> DisconnectUser -> Bool
== :: DisconnectUser -> DisconnectUser -> Bool
$c== :: DisconnectUser -> DisconnectUser -> Bool
Prelude.Eq, ReadPrec [DisconnectUser]
ReadPrec DisconnectUser
Int -> ReadS DisconnectUser
ReadS [DisconnectUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisconnectUser]
$creadListPrec :: ReadPrec [DisconnectUser]
readPrec :: ReadPrec DisconnectUser
$creadPrec :: ReadPrec DisconnectUser
readList :: ReadS [DisconnectUser]
$creadList :: ReadS [DisconnectUser]
readsPrec :: Int -> ReadS DisconnectUser
$creadsPrec :: Int -> ReadS DisconnectUser
Prelude.Read, Int -> DisconnectUser -> ShowS
[DisconnectUser] -> ShowS
DisconnectUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisconnectUser] -> ShowS
$cshowList :: [DisconnectUser] -> ShowS
show :: DisconnectUser -> String
$cshow :: DisconnectUser -> String
showsPrec :: Int -> DisconnectUser -> ShowS
$cshowsPrec :: Int -> DisconnectUser -> ShowS
Prelude.Show, forall x. Rep DisconnectUser x -> DisconnectUser
forall x. DisconnectUser -> Rep DisconnectUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisconnectUser x -> DisconnectUser
$cfrom :: forall x. DisconnectUser -> Rep DisconnectUser x
Prelude.Generic)

-- |
-- Create a value of 'DisconnectUser' 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:
--
-- 'reason', 'disconnectUser_reason' - Reason for disconnecting the user.
--
-- 'roomIdentifier', 'disconnectUser_roomIdentifier' - Identifier of the room from which the user\'s clients should be
-- disconnected. Currently this must be an ARN.
--
-- 'userId', 'disconnectUser_userId' - ID of the user (connection) to disconnect from the room.
newDisconnectUser ::
  -- | 'roomIdentifier'
  Prelude.Text ->
  -- | 'userId'
  Prelude.Text ->
  DisconnectUser
newDisconnectUser :: Text -> Text -> DisconnectUser
newDisconnectUser Text
pRoomIdentifier_ Text
pUserId_ =
  DisconnectUser'
    { $sel:reason:DisconnectUser' :: Maybe Text
reason = forall a. Maybe a
Prelude.Nothing,
      $sel:roomIdentifier:DisconnectUser' :: Text
roomIdentifier = Text
pRoomIdentifier_,
      $sel:userId:DisconnectUser' :: Text
userId = Text
pUserId_
    }

-- | Reason for disconnecting the user.
disconnectUser_reason :: Lens.Lens' DisconnectUser (Prelude.Maybe Prelude.Text)
disconnectUser_reason :: Lens' DisconnectUser (Maybe Text)
disconnectUser_reason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisconnectUser' {Maybe Text
reason :: Maybe Text
$sel:reason:DisconnectUser' :: DisconnectUser -> Maybe Text
reason} -> Maybe Text
reason) (\s :: DisconnectUser
s@DisconnectUser' {} Maybe Text
a -> DisconnectUser
s {$sel:reason:DisconnectUser' :: Maybe Text
reason = Maybe Text
a} :: DisconnectUser)

-- | Identifier of the room from which the user\'s clients should be
-- disconnected. Currently this must be an ARN.
disconnectUser_roomIdentifier :: Lens.Lens' DisconnectUser Prelude.Text
disconnectUser_roomIdentifier :: Lens' DisconnectUser Text
disconnectUser_roomIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisconnectUser' {Text
roomIdentifier :: Text
$sel:roomIdentifier:DisconnectUser' :: DisconnectUser -> Text
roomIdentifier} -> Text
roomIdentifier) (\s :: DisconnectUser
s@DisconnectUser' {} Text
a -> DisconnectUser
s {$sel:roomIdentifier:DisconnectUser' :: Text
roomIdentifier = Text
a} :: DisconnectUser)

-- | ID of the user (connection) to disconnect from the room.
disconnectUser_userId :: Lens.Lens' DisconnectUser Prelude.Text
disconnectUser_userId :: Lens' DisconnectUser Text
disconnectUser_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisconnectUser' {Text
userId :: Text
$sel:userId:DisconnectUser' :: DisconnectUser -> Text
userId} -> Text
userId) (\s :: DisconnectUser
s@DisconnectUser' {} Text
a -> DisconnectUser
s {$sel:userId:DisconnectUser' :: Text
userId = Text
a} :: DisconnectUser)

instance Core.AWSRequest DisconnectUser where
  type
    AWSResponse DisconnectUser =
      DisconnectUserResponse
  request :: (Service -> Service) -> DisconnectUser -> Request DisconnectUser
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 DisconnectUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DisconnectUser)))
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 -> DisconnectUserResponse
DisconnectUserResponse'
            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 DisconnectUser where
  hashWithSalt :: Int -> DisconnectUser -> Int
hashWithSalt Int
_salt DisconnectUser' {Maybe Text
Text
userId :: Text
roomIdentifier :: Text
reason :: Maybe Text
$sel:userId:DisconnectUser' :: DisconnectUser -> Text
$sel:roomIdentifier:DisconnectUser' :: DisconnectUser -> Text
$sel:reason:DisconnectUser' :: DisconnectUser -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roomIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userId

instance Prelude.NFData DisconnectUser where
  rnf :: DisconnectUser -> ()
rnf DisconnectUser' {Maybe Text
Text
userId :: Text
roomIdentifier :: Text
reason :: Maybe Text
$sel:userId:DisconnectUser' :: DisconnectUser -> Text
$sel:roomIdentifier:DisconnectUser' :: DisconnectUser -> Text
$sel:reason:DisconnectUser' :: DisconnectUser -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roomIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userId

instance Data.ToHeaders DisconnectUser where
  toHeaders :: DisconnectUser -> 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 DisconnectUser where
  toJSON :: DisconnectUser -> Value
toJSON DisconnectUser' {Maybe Text
Text
userId :: Text
roomIdentifier :: Text
reason :: Maybe Text
$sel:userId:DisconnectUser' :: DisconnectUser -> Text
$sel:roomIdentifier:DisconnectUser' :: DisconnectUser -> Text
$sel:reason:DisconnectUser' :: DisconnectUser -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"reason" 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
reason,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"roomIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roomIdentifier),
            forall a. a -> Maybe a
Prelude.Just (Key
"userId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userId)
          ]
      )

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

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

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

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

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

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