{-# 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.DeleteAccountCustomization
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes all Amazon QuickSight customizations in this Amazon Web Services
-- Region for the specified Amazon Web Services account and Amazon
-- QuickSight namespace.
module Amazonka.QuickSight.DeleteAccountCustomization
  ( -- * Creating a Request
    DeleteAccountCustomization (..),
    newDeleteAccountCustomization,

    -- * Request Lenses
    deleteAccountCustomization_namespace,
    deleteAccountCustomization_awsAccountId,

    -- * Destructuring the Response
    DeleteAccountCustomizationResponse (..),
    newDeleteAccountCustomizationResponse,

    -- * Response Lenses
    deleteAccountCustomizationResponse_requestId,
    deleteAccountCustomizationResponse_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:/ 'newDeleteAccountCustomization' smart constructor.
data DeleteAccountCustomization = DeleteAccountCustomization'
  { -- | The Amazon QuickSight namespace that you\'re deleting the customizations
    -- from.
    DeleteAccountCustomization -> Maybe Text
namespace :: Prelude.Maybe Prelude.Text,
    -- | The ID for the Amazon Web Services account that you want to delete
    -- Amazon QuickSight customizations from in this Amazon Web Services
    -- Region.
    DeleteAccountCustomization -> Text
awsAccountId :: Prelude.Text
  }
  deriving (DeleteAccountCustomization -> DeleteAccountCustomization -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccountCustomization -> DeleteAccountCustomization -> Bool
$c/= :: DeleteAccountCustomization -> DeleteAccountCustomization -> Bool
== :: DeleteAccountCustomization -> DeleteAccountCustomization -> Bool
$c== :: DeleteAccountCustomization -> DeleteAccountCustomization -> Bool
Prelude.Eq, ReadPrec [DeleteAccountCustomization]
ReadPrec DeleteAccountCustomization
Int -> ReadS DeleteAccountCustomization
ReadS [DeleteAccountCustomization]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAccountCustomization]
$creadListPrec :: ReadPrec [DeleteAccountCustomization]
readPrec :: ReadPrec DeleteAccountCustomization
$creadPrec :: ReadPrec DeleteAccountCustomization
readList :: ReadS [DeleteAccountCustomization]
$creadList :: ReadS [DeleteAccountCustomization]
readsPrec :: Int -> ReadS DeleteAccountCustomization
$creadsPrec :: Int -> ReadS DeleteAccountCustomization
Prelude.Read, Int -> DeleteAccountCustomization -> ShowS
[DeleteAccountCustomization] -> ShowS
DeleteAccountCustomization -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccountCustomization] -> ShowS
$cshowList :: [DeleteAccountCustomization] -> ShowS
show :: DeleteAccountCustomization -> String
$cshow :: DeleteAccountCustomization -> String
showsPrec :: Int -> DeleteAccountCustomization -> ShowS
$cshowsPrec :: Int -> DeleteAccountCustomization -> ShowS
Prelude.Show, forall x.
Rep DeleteAccountCustomization x -> DeleteAccountCustomization
forall x.
DeleteAccountCustomization -> Rep DeleteAccountCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAccountCustomization x -> DeleteAccountCustomization
$cfrom :: forall x.
DeleteAccountCustomization -> Rep DeleteAccountCustomization x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAccountCustomization' 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:
--
-- 'namespace', 'deleteAccountCustomization_namespace' - The Amazon QuickSight namespace that you\'re deleting the customizations
-- from.
--
-- 'awsAccountId', 'deleteAccountCustomization_awsAccountId' - The ID for the Amazon Web Services account that you want to delete
-- Amazon QuickSight customizations from in this Amazon Web Services
-- Region.
newDeleteAccountCustomization ::
  -- | 'awsAccountId'
  Prelude.Text ->
  DeleteAccountCustomization
newDeleteAccountCustomization :: Text -> DeleteAccountCustomization
newDeleteAccountCustomization Text
pAwsAccountId_ =
  DeleteAccountCustomization'
    { $sel:namespace:DeleteAccountCustomization' :: Maybe Text
namespace =
        forall a. Maybe a
Prelude.Nothing,
      $sel:awsAccountId:DeleteAccountCustomization' :: Text
awsAccountId = Text
pAwsAccountId_
    }

-- | The Amazon QuickSight namespace that you\'re deleting the customizations
-- from.
deleteAccountCustomization_namespace :: Lens.Lens' DeleteAccountCustomization (Prelude.Maybe Prelude.Text)
deleteAccountCustomization_namespace :: Lens' DeleteAccountCustomization (Maybe Text)
deleteAccountCustomization_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAccountCustomization' {Maybe Text
namespace :: Maybe Text
$sel:namespace:DeleteAccountCustomization' :: DeleteAccountCustomization -> Maybe Text
namespace} -> Maybe Text
namespace) (\s :: DeleteAccountCustomization
s@DeleteAccountCustomization' {} Maybe Text
a -> DeleteAccountCustomization
s {$sel:namespace:DeleteAccountCustomization' :: Maybe Text
namespace = Maybe Text
a} :: DeleteAccountCustomization)

-- | The ID for the Amazon Web Services account that you want to delete
-- Amazon QuickSight customizations from in this Amazon Web Services
-- Region.
deleteAccountCustomization_awsAccountId :: Lens.Lens' DeleteAccountCustomization Prelude.Text
deleteAccountCustomization_awsAccountId :: Lens' DeleteAccountCustomization Text
deleteAccountCustomization_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAccountCustomization' {Text
awsAccountId :: Text
$sel:awsAccountId:DeleteAccountCustomization' :: DeleteAccountCustomization -> Text
awsAccountId} -> Text
awsAccountId) (\s :: DeleteAccountCustomization
s@DeleteAccountCustomization' {} Text
a -> DeleteAccountCustomization
s {$sel:awsAccountId:DeleteAccountCustomization' :: Text
awsAccountId = Text
a} :: DeleteAccountCustomization)

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

instance Prelude.NFData DeleteAccountCustomization where
  rnf :: DeleteAccountCustomization -> ()
rnf DeleteAccountCustomization' {Maybe Text
Text
awsAccountId :: Text
namespace :: Maybe Text
$sel:awsAccountId:DeleteAccountCustomization' :: DeleteAccountCustomization -> Text
$sel:namespace:DeleteAccountCustomization' :: DeleteAccountCustomization -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
namespace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
awsAccountId

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

instance Data.ToQuery DeleteAccountCustomization where
  toQuery :: DeleteAccountCustomization -> QueryString
toQuery DeleteAccountCustomization' {Maybe Text
Text
awsAccountId :: Text
namespace :: Maybe Text
$sel:awsAccountId:DeleteAccountCustomization' :: DeleteAccountCustomization -> Text
$sel:namespace:DeleteAccountCustomization' :: DeleteAccountCustomization -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"namespace" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
namespace]

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

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

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

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

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