{-# 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.QuickSight.DescribeAccountSubscription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use the DescribeAccountSubscription operation to receive a description
-- of an Amazon QuickSight account\'s subscription. A successful API call
-- returns an @AccountInfo@ object that includes an account\'s name,
-- subscription status, authentication type, edition, and notification
-- email address.
module Amazonka.QuickSight.DescribeAccountSubscription
  ( -- * Creating a Request
    DescribeAccountSubscription (..),
    newDescribeAccountSubscription,

    -- * Request Lenses
    describeAccountSubscription_awsAccountId,

    -- * Destructuring the Response
    DescribeAccountSubscriptionResponse (..),
    newDescribeAccountSubscriptionResponse,

    -- * Response Lenses
    describeAccountSubscriptionResponse_accountInfo,
    describeAccountSubscriptionResponse_requestId,
    describeAccountSubscriptionResponse_status,
  )
where

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 Amazonka.QuickSight.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeAccountSubscription' smart constructor.
data DescribeAccountSubscription = DescribeAccountSubscription'
  { -- | The Amazon Web Services account ID associated with your Amazon
    -- QuickSight account.
    DescribeAccountSubscription -> Text
awsAccountId :: Prelude.Text
  }
  deriving (DescribeAccountSubscription -> DescribeAccountSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAccountSubscription -> DescribeAccountSubscription -> Bool
$c/= :: DescribeAccountSubscription -> DescribeAccountSubscription -> Bool
== :: DescribeAccountSubscription -> DescribeAccountSubscription -> Bool
$c== :: DescribeAccountSubscription -> DescribeAccountSubscription -> Bool
Prelude.Eq, ReadPrec [DescribeAccountSubscription]
ReadPrec DescribeAccountSubscription
Int -> ReadS DescribeAccountSubscription
ReadS [DescribeAccountSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAccountSubscription]
$creadListPrec :: ReadPrec [DescribeAccountSubscription]
readPrec :: ReadPrec DescribeAccountSubscription
$creadPrec :: ReadPrec DescribeAccountSubscription
readList :: ReadS [DescribeAccountSubscription]
$creadList :: ReadS [DescribeAccountSubscription]
readsPrec :: Int -> ReadS DescribeAccountSubscription
$creadsPrec :: Int -> ReadS DescribeAccountSubscription
Prelude.Read, Int -> DescribeAccountSubscription -> ShowS
[DescribeAccountSubscription] -> ShowS
DescribeAccountSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAccountSubscription] -> ShowS
$cshowList :: [DescribeAccountSubscription] -> ShowS
show :: DescribeAccountSubscription -> String
$cshow :: DescribeAccountSubscription -> String
showsPrec :: Int -> DescribeAccountSubscription -> ShowS
$cshowsPrec :: Int -> DescribeAccountSubscription -> ShowS
Prelude.Show, forall x.
Rep DescribeAccountSubscription x -> DescribeAccountSubscription
forall x.
DescribeAccountSubscription -> Rep DescribeAccountSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAccountSubscription x -> DescribeAccountSubscription
$cfrom :: forall x.
DescribeAccountSubscription -> Rep DescribeAccountSubscription x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAccountSubscription' 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:
--
-- 'awsAccountId', 'describeAccountSubscription_awsAccountId' - The Amazon Web Services account ID associated with your Amazon
-- QuickSight account.
newDescribeAccountSubscription ::
  -- | 'awsAccountId'
  Prelude.Text ->
  DescribeAccountSubscription
newDescribeAccountSubscription :: Text -> DescribeAccountSubscription
newDescribeAccountSubscription Text
pAwsAccountId_ =
  DescribeAccountSubscription'
    { $sel:awsAccountId:DescribeAccountSubscription' :: Text
awsAccountId =
        Text
pAwsAccountId_
    }

-- | The Amazon Web Services account ID associated with your Amazon
-- QuickSight account.
describeAccountSubscription_awsAccountId :: Lens.Lens' DescribeAccountSubscription Prelude.Text
describeAccountSubscription_awsAccountId :: Lens' DescribeAccountSubscription Text
describeAccountSubscription_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccountSubscription' {Text
awsAccountId :: Text
$sel:awsAccountId:DescribeAccountSubscription' :: DescribeAccountSubscription -> Text
awsAccountId} -> Text
awsAccountId) (\s :: DescribeAccountSubscription
s@DescribeAccountSubscription' {} Text
a -> DescribeAccountSubscription
s {$sel:awsAccountId:DescribeAccountSubscription' :: Text
awsAccountId = Text
a} :: DescribeAccountSubscription)

instance Core.AWSRequest DescribeAccountSubscription where
  type
    AWSResponse DescribeAccountSubscription =
      DescribeAccountSubscriptionResponse
  request :: (Service -> Service)
-> DescribeAccountSubscription
-> Request DescribeAccountSubscription
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 DescribeAccountSubscription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAccountSubscription)))
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 AccountInfo
-> Maybe Text -> Int -> DescribeAccountSubscriptionResponse
DescribeAccountSubscriptionResponse'
            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
"AccountInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RequestId")
            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 DescribeAccountSubscription where
  hashWithSalt :: Int -> DescribeAccountSubscription -> Int
hashWithSalt Int
_salt DescribeAccountSubscription' {Text
awsAccountId :: Text
$sel:awsAccountId:DescribeAccountSubscription' :: DescribeAccountSubscription -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
awsAccountId

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

instance Data.ToHeaders DescribeAccountSubscription where
  toHeaders :: DescribeAccountSubscription -> 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.0" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

-- | /See:/ 'newDescribeAccountSubscriptionResponse' smart constructor.
data DescribeAccountSubscriptionResponse = DescribeAccountSubscriptionResponse'
  { -- | A structure that contains the following elements:
    --
    -- -   Your Amazon QuickSight account name.
    --
    -- -   The edition of Amazon QuickSight that your account is using.
    --
    -- -   The notification email address that is associated with the Amazon
    --     QuickSight account.
    --
    -- -   The authentication type of the Amazon QuickSight account.
    --
    -- -   The status of the Amazon QuickSight account\'s subscription.
    DescribeAccountSubscriptionResponse -> Maybe AccountInfo
accountInfo :: Prelude.Maybe AccountInfo,
    -- | The Amazon Web Services request ID for this operation.
    DescribeAccountSubscriptionResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The HTTP status of the request.
    DescribeAccountSubscriptionResponse -> Int
status :: Prelude.Int
  }
  deriving (DescribeAccountSubscriptionResponse
-> DescribeAccountSubscriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAccountSubscriptionResponse
-> DescribeAccountSubscriptionResponse -> Bool
$c/= :: DescribeAccountSubscriptionResponse
-> DescribeAccountSubscriptionResponse -> Bool
== :: DescribeAccountSubscriptionResponse
-> DescribeAccountSubscriptionResponse -> Bool
$c== :: DescribeAccountSubscriptionResponse
-> DescribeAccountSubscriptionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAccountSubscriptionResponse]
ReadPrec DescribeAccountSubscriptionResponse
Int -> ReadS DescribeAccountSubscriptionResponse
ReadS [DescribeAccountSubscriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAccountSubscriptionResponse]
$creadListPrec :: ReadPrec [DescribeAccountSubscriptionResponse]
readPrec :: ReadPrec DescribeAccountSubscriptionResponse
$creadPrec :: ReadPrec DescribeAccountSubscriptionResponse
readList :: ReadS [DescribeAccountSubscriptionResponse]
$creadList :: ReadS [DescribeAccountSubscriptionResponse]
readsPrec :: Int -> ReadS DescribeAccountSubscriptionResponse
$creadsPrec :: Int -> ReadS DescribeAccountSubscriptionResponse
Prelude.Read, Int -> DescribeAccountSubscriptionResponse -> ShowS
[DescribeAccountSubscriptionResponse] -> ShowS
DescribeAccountSubscriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAccountSubscriptionResponse] -> ShowS
$cshowList :: [DescribeAccountSubscriptionResponse] -> ShowS
show :: DescribeAccountSubscriptionResponse -> String
$cshow :: DescribeAccountSubscriptionResponse -> String
showsPrec :: Int -> DescribeAccountSubscriptionResponse -> ShowS
$cshowsPrec :: Int -> DescribeAccountSubscriptionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAccountSubscriptionResponse x
-> DescribeAccountSubscriptionResponse
forall x.
DescribeAccountSubscriptionResponse
-> Rep DescribeAccountSubscriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAccountSubscriptionResponse x
-> DescribeAccountSubscriptionResponse
$cfrom :: forall x.
DescribeAccountSubscriptionResponse
-> Rep DescribeAccountSubscriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAccountSubscriptionResponse' 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:
--
-- 'accountInfo', 'describeAccountSubscriptionResponse_accountInfo' - A structure that contains the following elements:
--
-- -   Your Amazon QuickSight account name.
--
-- -   The edition of Amazon QuickSight that your account is using.
--
-- -   The notification email address that is associated with the Amazon
--     QuickSight account.
--
-- -   The authentication type of the Amazon QuickSight account.
--
-- -   The status of the Amazon QuickSight account\'s subscription.
--
-- 'requestId', 'describeAccountSubscriptionResponse_requestId' - The Amazon Web Services request ID for this operation.
--
-- 'status', 'describeAccountSubscriptionResponse_status' - The HTTP status of the request.
newDescribeAccountSubscriptionResponse ::
  -- | 'status'
  Prelude.Int ->
  DescribeAccountSubscriptionResponse
newDescribeAccountSubscriptionResponse :: Int -> DescribeAccountSubscriptionResponse
newDescribeAccountSubscriptionResponse Int
pStatus_ =
  DescribeAccountSubscriptionResponse'
    { $sel:accountInfo:DescribeAccountSubscriptionResponse' :: Maybe AccountInfo
accountInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requestId:DescribeAccountSubscriptionResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeAccountSubscriptionResponse' :: Int
status = Int
pStatus_
    }

-- | A structure that contains the following elements:
--
-- -   Your Amazon QuickSight account name.
--
-- -   The edition of Amazon QuickSight that your account is using.
--
-- -   The notification email address that is associated with the Amazon
--     QuickSight account.
--
-- -   The authentication type of the Amazon QuickSight account.
--
-- -   The status of the Amazon QuickSight account\'s subscription.
describeAccountSubscriptionResponse_accountInfo :: Lens.Lens' DescribeAccountSubscriptionResponse (Prelude.Maybe AccountInfo)
describeAccountSubscriptionResponse_accountInfo :: Lens' DescribeAccountSubscriptionResponse (Maybe AccountInfo)
describeAccountSubscriptionResponse_accountInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccountSubscriptionResponse' {Maybe AccountInfo
accountInfo :: Maybe AccountInfo
$sel:accountInfo:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Maybe AccountInfo
accountInfo} -> Maybe AccountInfo
accountInfo) (\s :: DescribeAccountSubscriptionResponse
s@DescribeAccountSubscriptionResponse' {} Maybe AccountInfo
a -> DescribeAccountSubscriptionResponse
s {$sel:accountInfo:DescribeAccountSubscriptionResponse' :: Maybe AccountInfo
accountInfo = Maybe AccountInfo
a} :: DescribeAccountSubscriptionResponse)

-- | The Amazon Web Services request ID for this operation.
describeAccountSubscriptionResponse_requestId :: Lens.Lens' DescribeAccountSubscriptionResponse (Prelude.Maybe Prelude.Text)
describeAccountSubscriptionResponse_requestId :: Lens' DescribeAccountSubscriptionResponse (Maybe Text)
describeAccountSubscriptionResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccountSubscriptionResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: DescribeAccountSubscriptionResponse
s@DescribeAccountSubscriptionResponse' {} Maybe Text
a -> DescribeAccountSubscriptionResponse
s {$sel:requestId:DescribeAccountSubscriptionResponse' :: Maybe Text
requestId = Maybe Text
a} :: DescribeAccountSubscriptionResponse)

-- | The HTTP status of the request.
describeAccountSubscriptionResponse_status :: Lens.Lens' DescribeAccountSubscriptionResponse Prelude.Int
describeAccountSubscriptionResponse_status :: Lens' DescribeAccountSubscriptionResponse Int
describeAccountSubscriptionResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccountSubscriptionResponse' {Int
status :: Int
$sel:status:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Int
status} -> Int
status) (\s :: DescribeAccountSubscriptionResponse
s@DescribeAccountSubscriptionResponse' {} Int
a -> DescribeAccountSubscriptionResponse
s {$sel:status:DescribeAccountSubscriptionResponse' :: Int
status = Int
a} :: DescribeAccountSubscriptionResponse)

instance
  Prelude.NFData
    DescribeAccountSubscriptionResponse
  where
  rnf :: DescribeAccountSubscriptionResponse -> ()
rnf DescribeAccountSubscriptionResponse' {Int
Maybe Text
Maybe AccountInfo
status :: Int
requestId :: Maybe Text
accountInfo :: Maybe AccountInfo
$sel:status:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Int
$sel:requestId:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Maybe Text
$sel:accountInfo:DescribeAccountSubscriptionResponse' :: DescribeAccountSubscriptionResponse -> Maybe AccountInfo
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AccountInfo
accountInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
status