{-# 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.GetVoiceConnectorGroup
-- 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 details for the specified Amazon Chime Voice Connector group,
-- such as timestamps,name, and associated @VoiceConnectorItems@.
module Amazonka.Chime.GetVoiceConnectorGroup
  ( -- * Creating a Request
    GetVoiceConnectorGroup (..),
    newGetVoiceConnectorGroup,

    -- * Request Lenses
    getVoiceConnectorGroup_voiceConnectorGroupId,

    -- * Destructuring the Response
    GetVoiceConnectorGroupResponse (..),
    newGetVoiceConnectorGroupResponse,

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

-- |
-- Create a value of 'GetVoiceConnectorGroup' 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:
--
-- 'voiceConnectorGroupId', 'getVoiceConnectorGroup_voiceConnectorGroupId' - The Amazon Chime Voice Connector group ID.
newGetVoiceConnectorGroup ::
  -- | 'voiceConnectorGroupId'
  Prelude.Text ->
  GetVoiceConnectorGroup
newGetVoiceConnectorGroup :: Text -> GetVoiceConnectorGroup
newGetVoiceConnectorGroup Text
pVoiceConnectorGroupId_ =
  GetVoiceConnectorGroup'
    { $sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: Text
voiceConnectorGroupId =
        Text
pVoiceConnectorGroupId_
    }

-- | The Amazon Chime Voice Connector group ID.
getVoiceConnectorGroup_voiceConnectorGroupId :: Lens.Lens' GetVoiceConnectorGroup Prelude.Text
getVoiceConnectorGroup_voiceConnectorGroupId :: Lens' GetVoiceConnectorGroup Text
getVoiceConnectorGroup_voiceConnectorGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVoiceConnectorGroup' {Text
voiceConnectorGroupId :: Text
$sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: GetVoiceConnectorGroup -> Text
voiceConnectorGroupId} -> Text
voiceConnectorGroupId) (\s :: GetVoiceConnectorGroup
s@GetVoiceConnectorGroup' {} Text
a -> GetVoiceConnectorGroup
s {$sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: Text
voiceConnectorGroupId = Text
a} :: GetVoiceConnectorGroup)

instance Core.AWSRequest GetVoiceConnectorGroup where
  type
    AWSResponse GetVoiceConnectorGroup =
      GetVoiceConnectorGroupResponse
  request :: (Service -> Service)
-> GetVoiceConnectorGroup -> Request GetVoiceConnectorGroup
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 GetVoiceConnectorGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetVoiceConnectorGroup)))
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 VoiceConnectorGroup -> Int -> GetVoiceConnectorGroupResponse
GetVoiceConnectorGroupResponse'
            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
"VoiceConnectorGroup")
            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 GetVoiceConnectorGroup where
  hashWithSalt :: Int -> GetVoiceConnectorGroup -> Int
hashWithSalt Int
_salt GetVoiceConnectorGroup' {Text
voiceConnectorGroupId :: Text
$sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: GetVoiceConnectorGroup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
voiceConnectorGroupId

instance Prelude.NFData GetVoiceConnectorGroup where
  rnf :: GetVoiceConnectorGroup -> ()
rnf GetVoiceConnectorGroup' {Text
voiceConnectorGroupId :: Text
$sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: GetVoiceConnectorGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
voiceConnectorGroupId

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

instance Data.ToPath GetVoiceConnectorGroup where
  toPath :: GetVoiceConnectorGroup -> ByteString
toPath GetVoiceConnectorGroup' {Text
voiceConnectorGroupId :: Text
$sel:voiceConnectorGroupId:GetVoiceConnectorGroup' :: GetVoiceConnectorGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/voice-connector-groups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
voiceConnectorGroupId
      ]

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

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

-- |
-- Create a value of 'GetVoiceConnectorGroupResponse' 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:
--
-- 'voiceConnectorGroup', 'getVoiceConnectorGroupResponse_voiceConnectorGroup' - The Amazon Chime Voice Connector group details.
--
-- 'httpStatus', 'getVoiceConnectorGroupResponse_httpStatus' - The response's http status code.
newGetVoiceConnectorGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetVoiceConnectorGroupResponse
newGetVoiceConnectorGroupResponse :: Int -> GetVoiceConnectorGroupResponse
newGetVoiceConnectorGroupResponse Int
pHttpStatus_ =
  GetVoiceConnectorGroupResponse'
    { $sel:voiceConnectorGroup:GetVoiceConnectorGroupResponse' :: Maybe VoiceConnectorGroup
voiceConnectorGroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetVoiceConnectorGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Chime Voice Connector group details.
getVoiceConnectorGroupResponse_voiceConnectorGroup :: Lens.Lens' GetVoiceConnectorGroupResponse (Prelude.Maybe VoiceConnectorGroup)
getVoiceConnectorGroupResponse_voiceConnectorGroup :: Lens' GetVoiceConnectorGroupResponse (Maybe VoiceConnectorGroup)
getVoiceConnectorGroupResponse_voiceConnectorGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVoiceConnectorGroupResponse' {Maybe VoiceConnectorGroup
voiceConnectorGroup :: Maybe VoiceConnectorGroup
$sel:voiceConnectorGroup:GetVoiceConnectorGroupResponse' :: GetVoiceConnectorGroupResponse -> Maybe VoiceConnectorGroup
voiceConnectorGroup} -> Maybe VoiceConnectorGroup
voiceConnectorGroup) (\s :: GetVoiceConnectorGroupResponse
s@GetVoiceConnectorGroupResponse' {} Maybe VoiceConnectorGroup
a -> GetVoiceConnectorGroupResponse
s {$sel:voiceConnectorGroup:GetVoiceConnectorGroupResponse' :: Maybe VoiceConnectorGroup
voiceConnectorGroup = Maybe VoiceConnectorGroup
a} :: GetVoiceConnectorGroupResponse)

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

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