{-# 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.DeleteAccountSubscription
-- 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 @DeleteAccountSubscription@ operation to delete an Amazon
-- QuickSight account. This operation will result in an error message if
-- you have configured your account termination protection settings to
-- @True@. To change this setting and delete your account, call the
-- @UpdateAccountSettings@ API and set the value of the
-- @TerminationProtectionEnabled@ parameter to @False@, then make another
-- call to the @DeleteAccountSubscription@ API.
module Amazonka.QuickSight.DeleteAccountSubscription
  ( -- * Creating a Request
    DeleteAccountSubscription (..),
    newDeleteAccountSubscription,

    -- * Request Lenses
    deleteAccountSubscription_awsAccountId,

    -- * Destructuring the Response
    DeleteAccountSubscriptionResponse (..),
    newDeleteAccountSubscriptionResponse,

    -- * Response Lenses
    deleteAccountSubscriptionResponse_requestId,
    deleteAccountSubscriptionResponse_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:/ 'newDeleteAccountSubscription' smart constructor.
data DeleteAccountSubscription = DeleteAccountSubscription'
  { -- | The Amazon Web Services account ID of the account that you want to
    -- delete.
    DeleteAccountSubscription -> Text
awsAccountId :: Prelude.Text
  }
  deriving (DeleteAccountSubscription -> DeleteAccountSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccountSubscription -> DeleteAccountSubscription -> Bool
$c/= :: DeleteAccountSubscription -> DeleteAccountSubscription -> Bool
== :: DeleteAccountSubscription -> DeleteAccountSubscription -> Bool
$c== :: DeleteAccountSubscription -> DeleteAccountSubscription -> Bool
Prelude.Eq, ReadPrec [DeleteAccountSubscription]
ReadPrec DeleteAccountSubscription
Int -> ReadS DeleteAccountSubscription
ReadS [DeleteAccountSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAccountSubscription]
$creadListPrec :: ReadPrec [DeleteAccountSubscription]
readPrec :: ReadPrec DeleteAccountSubscription
$creadPrec :: ReadPrec DeleteAccountSubscription
readList :: ReadS [DeleteAccountSubscription]
$creadList :: ReadS [DeleteAccountSubscription]
readsPrec :: Int -> ReadS DeleteAccountSubscription
$creadsPrec :: Int -> ReadS DeleteAccountSubscription
Prelude.Read, Int -> DeleteAccountSubscription -> ShowS
[DeleteAccountSubscription] -> ShowS
DeleteAccountSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccountSubscription] -> ShowS
$cshowList :: [DeleteAccountSubscription] -> ShowS
show :: DeleteAccountSubscription -> String
$cshow :: DeleteAccountSubscription -> String
showsPrec :: Int -> DeleteAccountSubscription -> ShowS
$cshowsPrec :: Int -> DeleteAccountSubscription -> ShowS
Prelude.Show, forall x.
Rep DeleteAccountSubscription x -> DeleteAccountSubscription
forall x.
DeleteAccountSubscription -> Rep DeleteAccountSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAccountSubscription x -> DeleteAccountSubscription
$cfrom :: forall x.
DeleteAccountSubscription -> Rep DeleteAccountSubscription x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAccountSubscription' 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', 'deleteAccountSubscription_awsAccountId' - The Amazon Web Services account ID of the account that you want to
-- delete.
newDeleteAccountSubscription ::
  -- | 'awsAccountId'
  Prelude.Text ->
  DeleteAccountSubscription
newDeleteAccountSubscription :: Text -> DeleteAccountSubscription
newDeleteAccountSubscription Text
pAwsAccountId_ =
  DeleteAccountSubscription'
    { $sel:awsAccountId:DeleteAccountSubscription' :: Text
awsAccountId =
        Text
pAwsAccountId_
    }

-- | The Amazon Web Services account ID of the account that you want to
-- delete.
deleteAccountSubscription_awsAccountId :: Lens.Lens' DeleteAccountSubscription Prelude.Text
deleteAccountSubscription_awsAccountId :: Lens' DeleteAccountSubscription Text
deleteAccountSubscription_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAccountSubscription' {Text
awsAccountId :: Text
$sel:awsAccountId:DeleteAccountSubscription' :: DeleteAccountSubscription -> Text
awsAccountId} -> Text
awsAccountId) (\s :: DeleteAccountSubscription
s@DeleteAccountSubscription' {} Text
a -> DeleteAccountSubscription
s {$sel:awsAccountId:DeleteAccountSubscription' :: Text
awsAccountId = Text
a} :: DeleteAccountSubscription)

instance Core.AWSRequest DeleteAccountSubscription where
  type
    AWSResponse DeleteAccountSubscription =
      DeleteAccountSubscriptionResponse
  request :: (Service -> Service)
-> DeleteAccountSubscription -> Request DeleteAccountSubscription
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteAccountSubscription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteAccountSubscription)))
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 Text -> Int -> DeleteAccountSubscriptionResponse
DeleteAccountSubscriptionResponse'
            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
"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 DeleteAccountSubscription where
  hashWithSalt :: Int -> DeleteAccountSubscription -> Int
hashWithSalt Int
_salt DeleteAccountSubscription' {Text
awsAccountId :: Text
$sel:awsAccountId:DeleteAccountSubscription' :: DeleteAccountSubscription -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
awsAccountId

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

instance Data.ToHeaders DeleteAccountSubscription where
  toHeaders :: DeleteAccountSubscription -> 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 DeleteAccountSubscription where
  toPath :: DeleteAccountSubscription -> ByteString
toPath DeleteAccountSubscription' {Text
awsAccountId :: Text
$sel:awsAccountId:DeleteAccountSubscription' :: DeleteAccountSubscription -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/account/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
awsAccountId]

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

-- | /See:/ 'newDeleteAccountSubscriptionResponse' smart constructor.
data DeleteAccountSubscriptionResponse = DeleteAccountSubscriptionResponse'
  { -- | The Amazon Web Services request ID for this operation.
    DeleteAccountSubscriptionResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The HTTP status of the request.
    DeleteAccountSubscriptionResponse -> Int
status :: Prelude.Int
  }
  deriving (DeleteAccountSubscriptionResponse
-> DeleteAccountSubscriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccountSubscriptionResponse
-> DeleteAccountSubscriptionResponse -> Bool
$c/= :: DeleteAccountSubscriptionResponse
-> DeleteAccountSubscriptionResponse -> Bool
== :: DeleteAccountSubscriptionResponse
-> DeleteAccountSubscriptionResponse -> Bool
$c== :: DeleteAccountSubscriptionResponse
-> DeleteAccountSubscriptionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAccountSubscriptionResponse]
ReadPrec DeleteAccountSubscriptionResponse
Int -> ReadS DeleteAccountSubscriptionResponse
ReadS [DeleteAccountSubscriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAccountSubscriptionResponse]
$creadListPrec :: ReadPrec [DeleteAccountSubscriptionResponse]
readPrec :: ReadPrec DeleteAccountSubscriptionResponse
$creadPrec :: ReadPrec DeleteAccountSubscriptionResponse
readList :: ReadS [DeleteAccountSubscriptionResponse]
$creadList :: ReadS [DeleteAccountSubscriptionResponse]
readsPrec :: Int -> ReadS DeleteAccountSubscriptionResponse
$creadsPrec :: Int -> ReadS DeleteAccountSubscriptionResponse
Prelude.Read, Int -> DeleteAccountSubscriptionResponse -> ShowS
[DeleteAccountSubscriptionResponse] -> ShowS
DeleteAccountSubscriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccountSubscriptionResponse] -> ShowS
$cshowList :: [DeleteAccountSubscriptionResponse] -> ShowS
show :: DeleteAccountSubscriptionResponse -> String
$cshow :: DeleteAccountSubscriptionResponse -> String
showsPrec :: Int -> DeleteAccountSubscriptionResponse -> ShowS
$cshowsPrec :: Int -> DeleteAccountSubscriptionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteAccountSubscriptionResponse x
-> DeleteAccountSubscriptionResponse
forall x.
DeleteAccountSubscriptionResponse
-> Rep DeleteAccountSubscriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAccountSubscriptionResponse x
-> DeleteAccountSubscriptionResponse
$cfrom :: forall x.
DeleteAccountSubscriptionResponse
-> Rep DeleteAccountSubscriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAccountSubscriptionResponse' 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:
--
-- 'requestId', 'deleteAccountSubscriptionResponse_requestId' - The Amazon Web Services request ID for this operation.
--
-- 'status', 'deleteAccountSubscriptionResponse_status' - The HTTP status of the request.
newDeleteAccountSubscriptionResponse ::
  -- | 'status'
  Prelude.Int ->
  DeleteAccountSubscriptionResponse
newDeleteAccountSubscriptionResponse :: Int -> DeleteAccountSubscriptionResponse
newDeleteAccountSubscriptionResponse Int
pStatus_ =
  DeleteAccountSubscriptionResponse'
    { $sel:requestId:DeleteAccountSubscriptionResponse' :: Maybe Text
requestId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:status:DeleteAccountSubscriptionResponse' :: Int
status = Int
pStatus_
    }

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

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

instance
  Prelude.NFData
    DeleteAccountSubscriptionResponse
  where
  rnf :: DeleteAccountSubscriptionResponse -> ()
rnf DeleteAccountSubscriptionResponse' {Int
Maybe Text
status :: Int
requestId :: Maybe Text
$sel:status:DeleteAccountSubscriptionResponse' :: DeleteAccountSubscriptionResponse -> Int
$sel:requestId:DeleteAccountSubscriptionResponse' :: DeleteAccountSubscriptionResponse -> Maybe Text
..} =
    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