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

    -- * Request Lenses
    getRoom_accountId,
    getRoom_roomId,

    -- * Destructuring the Response
    GetRoomResponse (..),
    newGetRoomResponse,

    -- * Response Lenses
    getRoomResponse_room,
    getRoomResponse_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:/ 'newGetRoom' smart constructor.
data GetRoom = GetRoom'
  { -- | The Amazon Chime account ID.
    GetRoom -> Text
accountId :: Prelude.Text,
    -- | The room ID.
    GetRoom -> Text
roomId :: Prelude.Text
  }
  deriving (GetRoom -> GetRoom -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRoom -> GetRoom -> Bool
$c/= :: GetRoom -> GetRoom -> Bool
== :: GetRoom -> GetRoom -> Bool
$c== :: GetRoom -> GetRoom -> Bool
Prelude.Eq, ReadPrec [GetRoom]
ReadPrec GetRoom
Int -> ReadS GetRoom
ReadS [GetRoom]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRoom]
$creadListPrec :: ReadPrec [GetRoom]
readPrec :: ReadPrec GetRoom
$creadPrec :: ReadPrec GetRoom
readList :: ReadS [GetRoom]
$creadList :: ReadS [GetRoom]
readsPrec :: Int -> ReadS GetRoom
$creadsPrec :: Int -> ReadS GetRoom
Prelude.Read, Int -> GetRoom -> ShowS
[GetRoom] -> ShowS
GetRoom -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRoom] -> ShowS
$cshowList :: [GetRoom] -> ShowS
show :: GetRoom -> String
$cshow :: GetRoom -> String
showsPrec :: Int -> GetRoom -> ShowS
$cshowsPrec :: Int -> GetRoom -> ShowS
Prelude.Show, forall x. Rep GetRoom x -> GetRoom
forall x. GetRoom -> Rep GetRoom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRoom x -> GetRoom
$cfrom :: forall x. GetRoom -> Rep GetRoom x
Prelude.Generic)

-- |
-- Create a value of 'GetRoom' 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:
--
-- 'accountId', 'getRoom_accountId' - The Amazon Chime account ID.
--
-- 'roomId', 'getRoom_roomId' - The room ID.
newGetRoom ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'roomId'
  Prelude.Text ->
  GetRoom
newGetRoom :: Text -> Text -> GetRoom
newGetRoom Text
pAccountId_ Text
pRoomId_ =
  GetRoom'
    { $sel:accountId:GetRoom' :: Text
accountId = Text
pAccountId_,
      $sel:roomId:GetRoom' :: Text
roomId = Text
pRoomId_
    }

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

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

instance Core.AWSRequest GetRoom where
  type AWSResponse GetRoom = GetRoomResponse
  request :: (Service -> Service) -> GetRoom -> Request GetRoom
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetRoom
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRoom)))
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 -> GetRoomResponse
GetRoomResponse'
            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 GetRoom where
  hashWithSalt :: Int -> GetRoom -> Int
hashWithSalt Int
_salt GetRoom' {Text
roomId :: Text
accountId :: Text
$sel:roomId:GetRoom' :: GetRoom -> Text
$sel:accountId:GetRoom' :: GetRoom -> Text
..} =
    Int
_salt
      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 GetRoom where
  rnf :: GetRoom -> ()
rnf GetRoom' {Text
roomId :: Text
accountId :: Text
$sel:roomId:GetRoom' :: GetRoom -> Text
$sel:accountId:GetRoom' :: GetRoom -> Text
..} =
    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 GetRoom where
  toHeaders :: GetRoom -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetRoom where
  toPath :: GetRoom -> ByteString
toPath GetRoom' {Text
roomId :: Text
accountId :: Text
$sel:roomId:GetRoom' :: GetRoom -> Text
$sel:accountId:GetRoom' :: GetRoom -> 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 GetRoom where
  toQuery :: GetRoom -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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

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

instance Prelude.NFData GetRoomResponse where
  rnf :: GetRoomResponse -> ()
rnf GetRoomResponse' {Int
Maybe Room
httpStatus :: Int
room :: Maybe Room
$sel:httpStatus:GetRoomResponse' :: GetRoomResponse -> Int
$sel:room:GetRoomResponse' :: GetRoomResponse -> 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