{-# 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.MechanicalTurk.DeleteQualificationType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The @DeleteQualificationType@ deletes a Qualification type and deletes
-- any HIT types that are associated with the Qualification type.
--
-- This operation does not revoke Qualifications already assigned to
-- Workers because the Qualifications might be needed for active HITs. If
-- there are any pending requests for the Qualification type, Amazon
-- Mechanical Turk rejects those requests. After you delete a Qualification
-- type, you can no longer use it to create HITs or HIT types.
--
-- DeleteQualificationType must wait for all the HITs that use the deleted
-- Qualification type to be deleted before completing. It may take up to 48
-- hours before DeleteQualificationType completes and the unique name of
-- the Qualification type is available for reuse with
-- CreateQualificationType.
module Amazonka.MechanicalTurk.DeleteQualificationType
  ( -- * Creating a Request
    DeleteQualificationType (..),
    newDeleteQualificationType,

    -- * Request Lenses
    deleteQualificationType_qualificationTypeId,

    -- * Destructuring the Response
    DeleteQualificationTypeResponse (..),
    newDeleteQualificationTypeResponse,

    -- * Response Lenses
    deleteQualificationTypeResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteQualificationType' 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:
--
-- 'qualificationTypeId', 'deleteQualificationType_qualificationTypeId' - The ID of the QualificationType to dispose.
newDeleteQualificationType ::
  -- | 'qualificationTypeId'
  Prelude.Text ->
  DeleteQualificationType
newDeleteQualificationType :: Text -> DeleteQualificationType
newDeleteQualificationType Text
pQualificationTypeId_ =
  DeleteQualificationType'
    { $sel:qualificationTypeId:DeleteQualificationType' :: Text
qualificationTypeId =
        Text
pQualificationTypeId_
    }

-- | The ID of the QualificationType to dispose.
deleteQualificationType_qualificationTypeId :: Lens.Lens' DeleteQualificationType Prelude.Text
deleteQualificationType_qualificationTypeId :: Lens' DeleteQualificationType Text
deleteQualificationType_qualificationTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteQualificationType' {Text
qualificationTypeId :: Text
$sel:qualificationTypeId:DeleteQualificationType' :: DeleteQualificationType -> Text
qualificationTypeId} -> Text
qualificationTypeId) (\s :: DeleteQualificationType
s@DeleteQualificationType' {} Text
a -> DeleteQualificationType
s {$sel:qualificationTypeId:DeleteQualificationType' :: Text
qualificationTypeId = Text
a} :: DeleteQualificationType)

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

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

instance Data.ToHeaders DeleteQualificationType where
  toHeaders :: DeleteQualificationType -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"MTurkRequesterServiceV20170117.DeleteQualificationType" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

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

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

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

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