{-# 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.GetAccount
-- 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 account, such as
-- account type and supported licenses.
module Amazonka.Chime.GetAccount
  ( -- * Creating a Request
    GetAccount (..),
    newGetAccount,

    -- * Request Lenses
    getAccount_accountId,

    -- * Destructuring the Response
    GetAccountResponse (..),
    newGetAccountResponse,

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

-- |
-- Create a value of 'GetAccount' 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', 'getAccount_accountId' - The Amazon Chime account ID.
newGetAccount ::
  -- | 'accountId'
  Prelude.Text ->
  GetAccount
newGetAccount :: Text -> GetAccount
newGetAccount Text
pAccountId_ =
  GetAccount' {$sel:accountId:GetAccount' :: Text
accountId = Text
pAccountId_}

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

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

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

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

instance Data.ToPath GetAccount where
  toPath :: GetAccount -> ByteString
toPath GetAccount' {Text
accountId :: Text
$sel:accountId:GetAccount' :: GetAccount -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/accounts/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId]

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

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

-- |
-- Create a value of 'GetAccountResponse' 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:
--
-- 'account', 'getAccountResponse_account' - The Amazon Chime account details.
--
-- 'httpStatus', 'getAccountResponse_httpStatus' - The response's http status code.
newGetAccountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAccountResponse
newGetAccountResponse :: Int -> GetAccountResponse
newGetAccountResponse Int
pHttpStatus_ =
  GetAccountResponse'
    { $sel:account:GetAccountResponse' :: Maybe Account
account = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAccountResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Chime account details.
getAccountResponse_account :: Lens.Lens' GetAccountResponse (Prelude.Maybe Account)
getAccountResponse_account :: Lens' GetAccountResponse (Maybe Account)
getAccountResponse_account = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAccountResponse' {Maybe Account
account :: Maybe Account
$sel:account:GetAccountResponse' :: GetAccountResponse -> Maybe Account
account} -> Maybe Account
account) (\s :: GetAccountResponse
s@GetAccountResponse' {} Maybe Account
a -> GetAccountResponse
s {$sel:account:GetAccountResponse' :: Maybe Account
account = Maybe Account
a} :: GetAccountResponse)

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

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