{-# 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.Chime.UpdateRoom
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates room details, such as the room name, for a room in an Amazon
-- Chime Enterprise account.
module Amazonka.Chime.UpdateRoom
  ( -- * Creating a Request
    UpdateRoom (..),
    newUpdateRoom,

    -- * Request Lenses
    updateRoom_name,
    updateRoom_accountId,
    updateRoom_roomId,

    -- * Destructuring the Response
    UpdateRoomResponse (..),
    newUpdateRoomResponse,

    -- * Response Lenses
    updateRoomResponse_room,
    updateRoomResponse_httpStatus,
  )
where

import Amazonka.Chime.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:/ 'newUpdateRoom' smart constructor.
data UpdateRoom = UpdateRoom'
  { -- | The room name.
    UpdateRoom -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The Amazon Chime account ID.
    UpdateRoom -> Text
accountId :: Prelude.Text,
    -- | The room ID.
    UpdateRoom -> Text
roomId :: Prelude.Text
  }
  deriving (UpdateRoom -> UpdateRoom -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRoom -> UpdateRoom -> Bool
$c/= :: UpdateRoom -> UpdateRoom -> Bool
== :: UpdateRoom -> UpdateRoom -> Bool
$c== :: UpdateRoom -> UpdateRoom -> Bool
Prelude.Eq, Int -> UpdateRoom -> ShowS
[UpdateRoom] -> ShowS
UpdateRoom -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRoom] -> ShowS
$cshowList :: [UpdateRoom] -> ShowS
show :: UpdateRoom -> String
$cshow :: UpdateRoom -> String
showsPrec :: Int -> UpdateRoom -> ShowS
$cshowsPrec :: Int -> UpdateRoom -> ShowS
Prelude.Show, forall x. Rep UpdateRoom x -> UpdateRoom
forall x. UpdateRoom -> Rep UpdateRoom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRoom x -> UpdateRoom
$cfrom :: forall x. UpdateRoom -> Rep UpdateRoom x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRoom' 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:
--
-- 'name', 'updateRoom_name' - The room name.
--
-- 'accountId', 'updateRoom_accountId' - The Amazon Chime account ID.
--
-- 'roomId', 'updateRoom_roomId' - The room ID.
newUpdateRoom ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'roomId'
  Prelude.Text ->
  UpdateRoom
newUpdateRoom :: Text -> Text -> UpdateRoom
newUpdateRoom Text
pAccountId_ Text
pRoomId_ =
  UpdateRoom'
    { $sel:name:UpdateRoom' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
      $sel:accountId:UpdateRoom' :: Text
accountId = Text
pAccountId_,
      $sel:roomId:UpdateRoom' :: Text
roomId = Text
pRoomId_
    }

-- | The room name.
updateRoom_name :: Lens.Lens' UpdateRoom (Prelude.Maybe Prelude.Text)
updateRoom_name :: Lens' UpdateRoom (Maybe Text)
updateRoom_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoom' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:UpdateRoom' :: UpdateRoom -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: UpdateRoom
s@UpdateRoom' {} Maybe (Sensitive Text)
a -> UpdateRoom
s {$sel:name:UpdateRoom' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: UpdateRoom) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The Amazon Chime account ID.
updateRoom_accountId :: Lens.Lens' UpdateRoom Prelude.Text
updateRoom_accountId :: Lens' UpdateRoom Text
updateRoom_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoom' {Text
accountId :: Text
$sel:accountId:UpdateRoom' :: UpdateRoom -> Text
accountId} -> Text
accountId) (\s :: UpdateRoom
s@UpdateRoom' {} Text
a -> UpdateRoom
s {$sel:accountId:UpdateRoom' :: Text
accountId = Text
a} :: UpdateRoom)

-- | The room ID.
updateRoom_roomId :: Lens.Lens' UpdateRoom Prelude.Text
updateRoom_roomId :: Lens' UpdateRoom Text
updateRoom_roomId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoom' {Text
roomId :: Text
$sel:roomId:UpdateRoom' :: UpdateRoom -> Text
roomId} -> Text
roomId) (\s :: UpdateRoom
s@UpdateRoom' {} Text
a -> UpdateRoom
s {$sel:roomId:UpdateRoom' :: Text
roomId = Text
a} :: UpdateRoom)

instance Core.AWSRequest UpdateRoom where
  type AWSResponse UpdateRoom = UpdateRoomResponse
  request :: (Service -> Service) -> UpdateRoom -> Request UpdateRoom
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 UpdateRoom
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateRoom)))
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 Room -> Int -> UpdateRoomResponse
UpdateRoomResponse'
            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
"Room")
            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 UpdateRoom where
  hashWithSalt :: Int -> UpdateRoom -> Int
hashWithSalt Int
_salt UpdateRoom' {Maybe (Sensitive Text)
Text
roomId :: Text
accountId :: Text
name :: Maybe (Sensitive Text)
$sel:roomId:UpdateRoom' :: UpdateRoom -> Text
$sel:accountId:UpdateRoom' :: UpdateRoom -> Text
$sel:name:UpdateRoom' :: UpdateRoom -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roomId

instance Prelude.NFData UpdateRoom where
  rnf :: UpdateRoom -> ()
rnf UpdateRoom' {Maybe (Sensitive Text)
Text
roomId :: Text
accountId :: Text
name :: Maybe (Sensitive Text)
$sel:roomId:UpdateRoom' :: UpdateRoom -> Text
$sel:accountId:UpdateRoom' :: UpdateRoom -> Text
$sel:name:UpdateRoom' :: UpdateRoom -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roomId

instance Data.ToHeaders UpdateRoom where
  toHeaders :: UpdateRoom -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON UpdateRoom where
  toJSON :: UpdateRoom -> Value
toJSON UpdateRoom' {Maybe (Sensitive Text)
Text
roomId :: Text
accountId :: Text
name :: Maybe (Sensitive Text)
$sel:roomId:UpdateRoom' :: UpdateRoom -> Text
$sel:accountId:UpdateRoom' :: UpdateRoom -> Text
$sel:name:UpdateRoom' :: UpdateRoom -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"Name" 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 (Sensitive Text)
name]
      )

instance Data.ToPath UpdateRoom where
  toPath :: UpdateRoom -> ByteString
toPath UpdateRoom' {Maybe (Sensitive Text)
Text
roomId :: Text
accountId :: Text
name :: Maybe (Sensitive Text)
$sel:roomId:UpdateRoom' :: UpdateRoom -> Text
$sel:accountId:UpdateRoom' :: UpdateRoom -> Text
$sel:name:UpdateRoom' :: UpdateRoom -> Maybe (Sensitive Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/accounts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId,
        ByteString
"/rooms/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
roomId
      ]

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

-- | /See:/ 'newUpdateRoomResponse' smart constructor.
data UpdateRoomResponse = UpdateRoomResponse'
  { -- | The room details.
    UpdateRoomResponse -> Maybe Room
room :: Prelude.Maybe Room,
    -- | The response's http status code.
    UpdateRoomResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRoomResponse -> UpdateRoomResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRoomResponse -> UpdateRoomResponse -> Bool
$c/= :: UpdateRoomResponse -> UpdateRoomResponse -> Bool
== :: UpdateRoomResponse -> UpdateRoomResponse -> Bool
$c== :: UpdateRoomResponse -> UpdateRoomResponse -> Bool
Prelude.Eq, Int -> UpdateRoomResponse -> ShowS
[UpdateRoomResponse] -> ShowS
UpdateRoomResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRoomResponse] -> ShowS
$cshowList :: [UpdateRoomResponse] -> ShowS
show :: UpdateRoomResponse -> String
$cshow :: UpdateRoomResponse -> String
showsPrec :: Int -> UpdateRoomResponse -> ShowS
$cshowsPrec :: Int -> UpdateRoomResponse -> ShowS
Prelude.Show, forall x. Rep UpdateRoomResponse x -> UpdateRoomResponse
forall x. UpdateRoomResponse -> Rep UpdateRoomResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRoomResponse x -> UpdateRoomResponse
$cfrom :: forall x. UpdateRoomResponse -> Rep UpdateRoomResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRoomResponse' 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:
--
-- 'room', 'updateRoomResponse_room' - The room details.
--
-- 'httpStatus', 'updateRoomResponse_httpStatus' - The response's http status code.
newUpdateRoomResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRoomResponse
newUpdateRoomResponse :: Int -> UpdateRoomResponse
newUpdateRoomResponse Int
pHttpStatus_ =
  UpdateRoomResponse'
    { $sel:room:UpdateRoomResponse' :: Maybe Room
room = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRoomResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The room details.
updateRoomResponse_room :: Lens.Lens' UpdateRoomResponse (Prelude.Maybe Room)
updateRoomResponse_room :: Lens' UpdateRoomResponse (Maybe Room)
updateRoomResponse_room = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoomResponse' {Maybe Room
room :: Maybe Room
$sel:room:UpdateRoomResponse' :: UpdateRoomResponse -> Maybe Room
room} -> Maybe Room
room) (\s :: UpdateRoomResponse
s@UpdateRoomResponse' {} Maybe Room
a -> UpdateRoomResponse
s {$sel:room:UpdateRoomResponse' :: Maybe Room
room = Maybe Room
a} :: UpdateRoomResponse)

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

instance Prelude.NFData UpdateRoomResponse where
  rnf :: UpdateRoomResponse -> ()
rnf UpdateRoomResponse' {Int
Maybe Room
httpStatus :: Int
room :: Maybe Room
$sel:httpStatus:UpdateRoomResponse' :: UpdateRoomResponse -> Int
$sel:room:UpdateRoomResponse' :: UpdateRoomResponse -> Maybe Room
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Room
room
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus