{-# 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.MacieV2.DeleteAllowList
-- 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 an allow list.
module Amazonka.MacieV2.DeleteAllowList
  ( -- * Creating a Request
    DeleteAllowList (..),
    newDeleteAllowList,

    -- * Request Lenses
    deleteAllowList_ignoreJobChecks,
    deleteAllowList_id,

    -- * Destructuring the Response
    DeleteAllowListResponse (..),
    newDeleteAllowListResponse,

    -- * Response Lenses
    deleteAllowListResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MacieV2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteAllowList' smart constructor.
data DeleteAllowList = DeleteAllowList'
  { -- | Specifies whether to force deletion of the allow list, even if active
    -- classification jobs are configured to use the list.
    --
    -- When you try to delete an allow list, Amazon Macie checks for
    -- classification jobs that use the list and have a status other than
    -- COMPLETE or CANCELLED. By default, Macie rejects your request if any
    -- jobs meet these criteria. To skip these checks and delete the list, set
    -- this value to true. To delete the list only if no active jobs are
    -- configured to use it, set this value to false.
    DeleteAllowList -> Maybe Text
ignoreJobChecks :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the Amazon Macie resource that the request
    -- applies to.
    DeleteAllowList -> Text
id :: Prelude.Text
  }
  deriving (DeleteAllowList -> DeleteAllowList -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAllowList -> DeleteAllowList -> Bool
$c/= :: DeleteAllowList -> DeleteAllowList -> Bool
== :: DeleteAllowList -> DeleteAllowList -> Bool
$c== :: DeleteAllowList -> DeleteAllowList -> Bool
Prelude.Eq, ReadPrec [DeleteAllowList]
ReadPrec DeleteAllowList
Int -> ReadS DeleteAllowList
ReadS [DeleteAllowList]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAllowList]
$creadListPrec :: ReadPrec [DeleteAllowList]
readPrec :: ReadPrec DeleteAllowList
$creadPrec :: ReadPrec DeleteAllowList
readList :: ReadS [DeleteAllowList]
$creadList :: ReadS [DeleteAllowList]
readsPrec :: Int -> ReadS DeleteAllowList
$creadsPrec :: Int -> ReadS DeleteAllowList
Prelude.Read, Int -> DeleteAllowList -> ShowS
[DeleteAllowList] -> ShowS
DeleteAllowList -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAllowList] -> ShowS
$cshowList :: [DeleteAllowList] -> ShowS
show :: DeleteAllowList -> String
$cshow :: DeleteAllowList -> String
showsPrec :: Int -> DeleteAllowList -> ShowS
$cshowsPrec :: Int -> DeleteAllowList -> ShowS
Prelude.Show, forall x. Rep DeleteAllowList x -> DeleteAllowList
forall x. DeleteAllowList -> Rep DeleteAllowList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAllowList x -> DeleteAllowList
$cfrom :: forall x. DeleteAllowList -> Rep DeleteAllowList x
Prelude.Generic)

-- |
-- Create a value of 'DeleteAllowList' 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:
--
-- 'ignoreJobChecks', 'deleteAllowList_ignoreJobChecks' - Specifies whether to force deletion of the allow list, even if active
-- classification jobs are configured to use the list.
--
-- When you try to delete an allow list, Amazon Macie checks for
-- classification jobs that use the list and have a status other than
-- COMPLETE or CANCELLED. By default, Macie rejects your request if any
-- jobs meet these criteria. To skip these checks and delete the list, set
-- this value to true. To delete the list only if no active jobs are
-- configured to use it, set this value to false.
--
-- 'id', 'deleteAllowList_id' - The unique identifier for the Amazon Macie resource that the request
-- applies to.
newDeleteAllowList ::
  -- | 'id'
  Prelude.Text ->
  DeleteAllowList
newDeleteAllowList :: Text -> DeleteAllowList
newDeleteAllowList Text
pId_ =
  DeleteAllowList'
    { $sel:ignoreJobChecks:DeleteAllowList' :: Maybe Text
ignoreJobChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DeleteAllowList' :: Text
id = Text
pId_
    }

-- | Specifies whether to force deletion of the allow list, even if active
-- classification jobs are configured to use the list.
--
-- When you try to delete an allow list, Amazon Macie checks for
-- classification jobs that use the list and have a status other than
-- COMPLETE or CANCELLED. By default, Macie rejects your request if any
-- jobs meet these criteria. To skip these checks and delete the list, set
-- this value to true. To delete the list only if no active jobs are
-- configured to use it, set this value to false.
deleteAllowList_ignoreJobChecks :: Lens.Lens' DeleteAllowList (Prelude.Maybe Prelude.Text)
deleteAllowList_ignoreJobChecks :: Lens' DeleteAllowList (Maybe Text)
deleteAllowList_ignoreJobChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAllowList' {Maybe Text
ignoreJobChecks :: Maybe Text
$sel:ignoreJobChecks:DeleteAllowList' :: DeleteAllowList -> Maybe Text
ignoreJobChecks} -> Maybe Text
ignoreJobChecks) (\s :: DeleteAllowList
s@DeleteAllowList' {} Maybe Text
a -> DeleteAllowList
s {$sel:ignoreJobChecks:DeleteAllowList' :: Maybe Text
ignoreJobChecks = Maybe Text
a} :: DeleteAllowList)

-- | The unique identifier for the Amazon Macie resource that the request
-- applies to.
deleteAllowList_id :: Lens.Lens' DeleteAllowList Prelude.Text
deleteAllowList_id :: Lens' DeleteAllowList Text
deleteAllowList_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAllowList' {Text
id :: Text
$sel:id:DeleteAllowList' :: DeleteAllowList -> Text
id} -> Text
id) (\s :: DeleteAllowList
s@DeleteAllowList' {} Text
a -> DeleteAllowList
s {$sel:id:DeleteAllowList' :: Text
id = Text
a} :: DeleteAllowList)

instance Core.AWSRequest DeleteAllowList where
  type
    AWSResponse DeleteAllowList =
      DeleteAllowListResponse
  request :: (Service -> Service) -> DeleteAllowList -> Request DeleteAllowList
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 DeleteAllowList
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteAllowList)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteAllowListResponse
DeleteAllowListResponse'
            forall (f :: * -> *) a b. Functor 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 DeleteAllowList where
  hashWithSalt :: Int -> DeleteAllowList -> Int
hashWithSalt Int
_salt DeleteAllowList' {Maybe Text
Text
id :: Text
ignoreJobChecks :: Maybe Text
$sel:id:DeleteAllowList' :: DeleteAllowList -> Text
$sel:ignoreJobChecks:DeleteAllowList' :: DeleteAllowList -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ignoreJobChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

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

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

instance Data.ToPath DeleteAllowList where
  toPath :: DeleteAllowList -> ByteString
toPath DeleteAllowList' {Maybe Text
Text
id :: Text
ignoreJobChecks :: Maybe Text
$sel:id:DeleteAllowList' :: DeleteAllowList -> Text
$sel:ignoreJobChecks:DeleteAllowList' :: DeleteAllowList -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/allow-lists/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

-- |
-- Create a value of 'DeleteAllowListResponse' 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:
--
-- 'httpStatus', 'deleteAllowListResponse_httpStatus' - The response's http status code.
newDeleteAllowListResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteAllowListResponse
newDeleteAllowListResponse :: Int -> DeleteAllowListResponse
newDeleteAllowListResponse Int
pHttpStatus_ =
  DeleteAllowListResponse' {$sel:httpStatus:DeleteAllowListResponse' :: Int
httpStatus = Int
pHttpStatus_}

-- | The response's http status code.
deleteAllowListResponse_httpStatus :: Lens.Lens' DeleteAllowListResponse Prelude.Int
deleteAllowListResponse_httpStatus :: Lens' DeleteAllowListResponse Int
deleteAllowListResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteAllowListResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteAllowListResponse' :: DeleteAllowListResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteAllowListResponse
s@DeleteAllowListResponse' {} Int
a -> DeleteAllowListResponse
s {$sel:httpStatus:DeleteAllowListResponse' :: Int
httpStatus = Int
a} :: DeleteAllowListResponse)

instance Prelude.NFData DeleteAllowListResponse where
  rnf :: DeleteAllowListResponse -> ()
rnf DeleteAllowListResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteAllowListResponse' :: DeleteAllowListResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus