{-# 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.DeleteOrganizationConformancePack
-- 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 specified organization conformance pack and all of the
-- Config rules and remediation actions from all member accounts in that
-- organization.
--
-- Only a management account or a delegated administrator account can
-- delete an organization conformance pack. When calling this API with a
-- delegated administrator, you must ensure Organizations
-- @ListDelegatedAdministrator@ permissions are added.
--
-- Config sets the state of a conformance pack to DELETE_IN_PROGRESS until
-- the deletion is complete. You cannot update a conformance pack while it
-- is in this state.
module Amazonka.Config.DeleteOrganizationConformancePack
  ( -- * Creating a Request
    DeleteOrganizationConformancePack (..),
    newDeleteOrganizationConformancePack,

    -- * Request Lenses
    deleteOrganizationConformancePack_organizationConformancePackName,

    -- * Destructuring the Response
    DeleteOrganizationConformancePackResponse (..),
    newDeleteOrganizationConformancePackResponse,
  )
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:/ 'newDeleteOrganizationConformancePack' smart constructor.
data DeleteOrganizationConformancePack = DeleteOrganizationConformancePack'
  { -- | The name of organization conformance pack that you want to delete.
    DeleteOrganizationConformancePack -> Text
organizationConformancePackName :: Prelude.Text
  }
  deriving (DeleteOrganizationConformancePack
-> DeleteOrganizationConformancePack -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOrganizationConformancePack
-> DeleteOrganizationConformancePack -> Bool
$c/= :: DeleteOrganizationConformancePack
-> DeleteOrganizationConformancePack -> Bool
== :: DeleteOrganizationConformancePack
-> DeleteOrganizationConformancePack -> Bool
$c== :: DeleteOrganizationConformancePack
-> DeleteOrganizationConformancePack -> Bool
Prelude.Eq, ReadPrec [DeleteOrganizationConformancePack]
ReadPrec DeleteOrganizationConformancePack
Int -> ReadS DeleteOrganizationConformancePack
ReadS [DeleteOrganizationConformancePack]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOrganizationConformancePack]
$creadListPrec :: ReadPrec [DeleteOrganizationConformancePack]
readPrec :: ReadPrec DeleteOrganizationConformancePack
$creadPrec :: ReadPrec DeleteOrganizationConformancePack
readList :: ReadS [DeleteOrganizationConformancePack]
$creadList :: ReadS [DeleteOrganizationConformancePack]
readsPrec :: Int -> ReadS DeleteOrganizationConformancePack
$creadsPrec :: Int -> ReadS DeleteOrganizationConformancePack
Prelude.Read, Int -> DeleteOrganizationConformancePack -> ShowS
[DeleteOrganizationConformancePack] -> ShowS
DeleteOrganizationConformancePack -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOrganizationConformancePack] -> ShowS
$cshowList :: [DeleteOrganizationConformancePack] -> ShowS
show :: DeleteOrganizationConformancePack -> String
$cshow :: DeleteOrganizationConformancePack -> String
showsPrec :: Int -> DeleteOrganizationConformancePack -> ShowS
$cshowsPrec :: Int -> DeleteOrganizationConformancePack -> ShowS
Prelude.Show, forall x.
Rep DeleteOrganizationConformancePack x
-> DeleteOrganizationConformancePack
forall x.
DeleteOrganizationConformancePack
-> Rep DeleteOrganizationConformancePack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOrganizationConformancePack x
-> DeleteOrganizationConformancePack
$cfrom :: forall x.
DeleteOrganizationConformancePack
-> Rep DeleteOrganizationConformancePack x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOrganizationConformancePack' 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:
--
-- 'organizationConformancePackName', 'deleteOrganizationConformancePack_organizationConformancePackName' - The name of organization conformance pack that you want to delete.
newDeleteOrganizationConformancePack ::
  -- | 'organizationConformancePackName'
  Prelude.Text ->
  DeleteOrganizationConformancePack
newDeleteOrganizationConformancePack :: Text -> DeleteOrganizationConformancePack
newDeleteOrganizationConformancePack
  Text
pOrganizationConformancePackName_ =
    DeleteOrganizationConformancePack'
      { $sel:organizationConformancePackName:DeleteOrganizationConformancePack' :: Text
organizationConformancePackName =
          Text
pOrganizationConformancePackName_
      }

-- | The name of organization conformance pack that you want to delete.
deleteOrganizationConformancePack_organizationConformancePackName :: Lens.Lens' DeleteOrganizationConformancePack Prelude.Text
deleteOrganizationConformancePack_organizationConformancePackName :: Lens' DeleteOrganizationConformancePack Text
deleteOrganizationConformancePack_organizationConformancePackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOrganizationConformancePack' {Text
organizationConformancePackName :: Text
$sel:organizationConformancePackName:DeleteOrganizationConformancePack' :: DeleteOrganizationConformancePack -> Text
organizationConformancePackName} -> Text
organizationConformancePackName) (\s :: DeleteOrganizationConformancePack
s@DeleteOrganizationConformancePack' {} Text
a -> DeleteOrganizationConformancePack
s {$sel:organizationConformancePackName:DeleteOrganizationConformancePack' :: Text
organizationConformancePackName = Text
a} :: DeleteOrganizationConformancePack)

instance
  Core.AWSRequest
    DeleteOrganizationConformancePack
  where
  type
    AWSResponse DeleteOrganizationConformancePack =
      DeleteOrganizationConformancePackResponse
  request :: (Service -> Service)
-> DeleteOrganizationConformancePack
-> Request DeleteOrganizationConformancePack
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 DeleteOrganizationConformancePack
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteOrganizationConformancePack)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteOrganizationConformancePackResponse
DeleteOrganizationConformancePackResponse'

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

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

instance
  Data.ToHeaders
    DeleteOrganizationConformancePack
  where
  toHeaders :: DeleteOrganizationConformancePack -> [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.DeleteOrganizationConformancePack" ::
                          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
    DeleteOrganizationConformancePack
  where
  toJSON :: DeleteOrganizationConformancePack -> Value
toJSON DeleteOrganizationConformancePack' {Text
organizationConformancePackName :: Text
$sel:organizationConformancePackName:DeleteOrganizationConformancePack' :: DeleteOrganizationConformancePack -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"OrganizationConformancePackName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationConformancePackName
              )
          ]
      )

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

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

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

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

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