{-# 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.Config.DeleteAggregationAuthorization
-- 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 the authorization granted to the specified configuration
-- aggregator account in a specified region.
module Amazonka.Config.DeleteAggregationAuthorization
  ( -- * Creating a Request
    DeleteAggregationAuthorization (..),
    newDeleteAggregationAuthorization,

    -- * Request Lenses
    deleteAggregationAuthorization_authorizedAccountId,
    deleteAggregationAuthorization_authorizedAwsRegion,

    -- * Destructuring the Response
    DeleteAggregationAuthorizationResponse (..),
    newDeleteAggregationAuthorizationResponse,
  )
where

import Amazonka.Config.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:/ 'newDeleteAggregationAuthorization' smart constructor.
data DeleteAggregationAuthorization = DeleteAggregationAuthorization'
  { -- | The 12-digit account ID of the account authorized to aggregate data.
    DeleteAggregationAuthorization -> Text
authorizedAccountId :: Prelude.Text,
    -- | The region authorized to collect aggregated data.
    DeleteAggregationAuthorization -> Text
authorizedAwsRegion :: Prelude.Text
  }
  deriving (DeleteAggregationAuthorization
-> DeleteAggregationAuthorization -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAggregationAuthorization
-> DeleteAggregationAuthorization -> Bool
$c/= :: DeleteAggregationAuthorization
-> DeleteAggregationAuthorization -> Bool
== :: DeleteAggregationAuthorization
-> DeleteAggregationAuthorization -> Bool
$c== :: DeleteAggregationAuthorization
-> DeleteAggregationAuthorization -> Bool
Prelude.Eq, ReadPrec [DeleteAggregationAuthorization]
ReadPrec DeleteAggregationAuthorization
Int -> ReadS DeleteAggregationAuthorization
ReadS [DeleteAggregationAuthorization]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAggregationAuthorization]
$creadListPrec :: ReadPrec [DeleteAggregationAuthorization]
readPrec :: ReadPrec DeleteAggregationAuthorization
$creadPrec :: ReadPrec DeleteAggregationAuthorization
readList :: ReadS [DeleteAggregationAuthorization]
$creadList :: ReadS [DeleteAggregationAuthorization]
readsPrec :: Int -> ReadS DeleteAggregationAuthorization
$creadsPrec :: Int -> ReadS DeleteAggregationAuthorization
Prelude.Read, Int -> DeleteAggregationAuthorization -> ShowS
[DeleteAggregationAuthorization] -> ShowS
DeleteAggregationAuthorization -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAggregationAuthorization] -> ShowS
$cshowList :: [DeleteAggregationAuthorization] -> ShowS
show :: DeleteAggregationAuthorization -> String
$cshow :: DeleteAggregationAuthorization -> String
showsPrec :: Int -> DeleteAggregationAuthorization -> ShowS
$cshowsPrec :: Int -> DeleteAggregationAuthorization -> ShowS
Prelude.Show, forall x.
Rep DeleteAggregationAuthorization x
-> DeleteAggregationAuthorization
forall x.
DeleteAggregationAuthorization
-> Rep DeleteAggregationAuthorization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAggregationAuthorization x
-> DeleteAggregationAuthorization
$cfrom :: forall x.
DeleteAggregationAuthorization
-> Rep DeleteAggregationAuthorization x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAggregationAuthorization' 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:
--
-- 'authorizedAccountId', 'deleteAggregationAuthorization_authorizedAccountId' - The 12-digit account ID of the account authorized to aggregate data.
--
-- 'authorizedAwsRegion', 'deleteAggregationAuthorization_authorizedAwsRegion' - The region authorized to collect aggregated data.
newDeleteAggregationAuthorization ::
  -- | 'authorizedAccountId'
  Prelude.Text ->
  -- | 'authorizedAwsRegion'
  Prelude.Text ->
  DeleteAggregationAuthorization
newDeleteAggregationAuthorization :: Text -> Text -> DeleteAggregationAuthorization
newDeleteAggregationAuthorization
  Text
pAuthorizedAccountId_
  Text
pAuthorizedAwsRegion_ =
    DeleteAggregationAuthorization'
      { $sel:authorizedAccountId:DeleteAggregationAuthorization' :: Text
authorizedAccountId =
          Text
pAuthorizedAccountId_,
        $sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: Text
authorizedAwsRegion = Text
pAuthorizedAwsRegion_
      }

-- | The 12-digit account ID of the account authorized to aggregate data.
deleteAggregationAuthorization_authorizedAccountId :: Lens.Lens' DeleteAggregationAuthorization Prelude.Text
deleteAggregationAuthorization_authorizedAccountId :: Lens' DeleteAggregationAuthorization Text
deleteAggregationAuthorization_authorizedAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAggregationAuthorization' {Text
authorizedAccountId :: Text
$sel:authorizedAccountId:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
authorizedAccountId} -> Text
authorizedAccountId) (\s :: DeleteAggregationAuthorization
s@DeleteAggregationAuthorization' {} Text
a -> DeleteAggregationAuthorization
s {$sel:authorizedAccountId:DeleteAggregationAuthorization' :: Text
authorizedAccountId = Text
a} :: DeleteAggregationAuthorization)

-- | The region authorized to collect aggregated data.
deleteAggregationAuthorization_authorizedAwsRegion :: Lens.Lens' DeleteAggregationAuthorization Prelude.Text
deleteAggregationAuthorization_authorizedAwsRegion :: Lens' DeleteAggregationAuthorization Text
deleteAggregationAuthorization_authorizedAwsRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAggregationAuthorization' {Text
authorizedAwsRegion :: Text
$sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
authorizedAwsRegion} -> Text
authorizedAwsRegion) (\s :: DeleteAggregationAuthorization
s@DeleteAggregationAuthorization' {} Text
a -> DeleteAggregationAuthorization
s {$sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: Text
authorizedAwsRegion = Text
a} :: DeleteAggregationAuthorization)

instance
  Core.AWSRequest
    DeleteAggregationAuthorization
  where
  type
    AWSResponse DeleteAggregationAuthorization =
      DeleteAggregationAuthorizationResponse
  request :: (Service -> Service)
-> DeleteAggregationAuthorization
-> Request DeleteAggregationAuthorization
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteAggregationAuthorization
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteAggregationAuthorization)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteAggregationAuthorizationResponse
DeleteAggregationAuthorizationResponse'

instance
  Prelude.Hashable
    DeleteAggregationAuthorization
  where
  hashWithSalt :: Int -> DeleteAggregationAuthorization -> Int
hashWithSalt
    Int
_salt
    DeleteAggregationAuthorization' {Text
authorizedAwsRegion :: Text
authorizedAccountId :: Text
$sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
$sel:authorizedAccountId:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authorizedAccountId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authorizedAwsRegion

instance
  Prelude.NFData
    DeleteAggregationAuthorization
  where
  rnf :: DeleteAggregationAuthorization -> ()
rnf DeleteAggregationAuthorization' {Text
authorizedAwsRegion :: Text
authorizedAccountId :: Text
$sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
$sel:authorizedAccountId:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
authorizedAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
authorizedAwsRegion

instance
  Data.ToHeaders
    DeleteAggregationAuthorization
  where
  toHeaders :: DeleteAggregationAuthorization -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"StarlingDoveService.DeleteAggregationAuthorization" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteAggregationAuthorization where
  toJSON :: DeleteAggregationAuthorization -> Value
toJSON DeleteAggregationAuthorization' {Text
authorizedAwsRegion :: Text
authorizedAccountId :: Text
$sel:authorizedAwsRegion:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
$sel:authorizedAccountId:DeleteAggregationAuthorization' :: DeleteAggregationAuthorization -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"AuthorizedAccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
authorizedAccountId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AuthorizedAwsRegion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
authorizedAwsRegion)
          ]
      )

instance Data.ToPath DeleteAggregationAuthorization where
  toPath :: DeleteAggregationAuthorization -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDeleteAggregationAuthorizationResponse' smart constructor.
data DeleteAggregationAuthorizationResponse = DeleteAggregationAuthorizationResponse'
  {
  }
  deriving (DeleteAggregationAuthorizationResponse
-> DeleteAggregationAuthorizationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAggregationAuthorizationResponse
-> DeleteAggregationAuthorizationResponse -> Bool
$c/= :: DeleteAggregationAuthorizationResponse
-> DeleteAggregationAuthorizationResponse -> Bool
== :: DeleteAggregationAuthorizationResponse
-> DeleteAggregationAuthorizationResponse -> Bool
$c== :: DeleteAggregationAuthorizationResponse
-> DeleteAggregationAuthorizationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteAggregationAuthorizationResponse]
ReadPrec DeleteAggregationAuthorizationResponse
Int -> ReadS DeleteAggregationAuthorizationResponse
ReadS [DeleteAggregationAuthorizationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAggregationAuthorizationResponse]
$creadListPrec :: ReadPrec [DeleteAggregationAuthorizationResponse]
readPrec :: ReadPrec DeleteAggregationAuthorizationResponse
$creadPrec :: ReadPrec DeleteAggregationAuthorizationResponse
readList :: ReadS [DeleteAggregationAuthorizationResponse]
$creadList :: ReadS [DeleteAggregationAuthorizationResponse]
readsPrec :: Int -> ReadS DeleteAggregationAuthorizationResponse
$creadsPrec :: Int -> ReadS DeleteAggregationAuthorizationResponse
Prelude.Read, Int -> DeleteAggregationAuthorizationResponse -> ShowS
[DeleteAggregationAuthorizationResponse] -> ShowS
DeleteAggregationAuthorizationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAggregationAuthorizationResponse] -> ShowS
$cshowList :: [DeleteAggregationAuthorizationResponse] -> ShowS
show :: DeleteAggregationAuthorizationResponse -> String
$cshow :: DeleteAggregationAuthorizationResponse -> String
showsPrec :: Int -> DeleteAggregationAuthorizationResponse -> ShowS
$cshowsPrec :: Int -> DeleteAggregationAuthorizationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteAggregationAuthorizationResponse x
-> DeleteAggregationAuthorizationResponse
forall x.
DeleteAggregationAuthorizationResponse
-> Rep DeleteAggregationAuthorizationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteAggregationAuthorizationResponse x
-> DeleteAggregationAuthorizationResponse
$cfrom :: forall x.
DeleteAggregationAuthorizationResponse
-> Rep DeleteAggregationAuthorizationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAggregationAuthorizationResponse' 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.
newDeleteAggregationAuthorizationResponse ::
  DeleteAggregationAuthorizationResponse
newDeleteAggregationAuthorizationResponse :: DeleteAggregationAuthorizationResponse
newDeleteAggregationAuthorizationResponse =
  DeleteAggregationAuthorizationResponse
DeleteAggregationAuthorizationResponse'

instance
  Prelude.NFData
    DeleteAggregationAuthorizationResponse
  where
  rnf :: DeleteAggregationAuthorizationResponse -> ()
rnf DeleteAggregationAuthorizationResponse
_ = ()