{-# 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 #-}
module Amazonka.MechanicalTurk.DeleteHIT
(
DeleteHIT (..),
newDeleteHIT,
deleteHIT_hITId,
DeleteHITResponse (..),
newDeleteHITResponse,
deleteHITResponse_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
data DeleteHIT = DeleteHIT'
{
DeleteHIT -> Text
hITId :: Prelude.Text
}
deriving (DeleteHIT -> DeleteHIT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteHIT -> DeleteHIT -> Bool
$c/= :: DeleteHIT -> DeleteHIT -> Bool
== :: DeleteHIT -> DeleteHIT -> Bool
$c== :: DeleteHIT -> DeleteHIT -> Bool
Prelude.Eq, ReadPrec [DeleteHIT]
ReadPrec DeleteHIT
Int -> ReadS DeleteHIT
ReadS [DeleteHIT]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteHIT]
$creadListPrec :: ReadPrec [DeleteHIT]
readPrec :: ReadPrec DeleteHIT
$creadPrec :: ReadPrec DeleteHIT
readList :: ReadS [DeleteHIT]
$creadList :: ReadS [DeleteHIT]
readsPrec :: Int -> ReadS DeleteHIT
$creadsPrec :: Int -> ReadS DeleteHIT
Prelude.Read, Int -> DeleteHIT -> ShowS
[DeleteHIT] -> ShowS
DeleteHIT -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteHIT] -> ShowS
$cshowList :: [DeleteHIT] -> ShowS
show :: DeleteHIT -> String
$cshow :: DeleteHIT -> String
showsPrec :: Int -> DeleteHIT -> ShowS
$cshowsPrec :: Int -> DeleteHIT -> ShowS
Prelude.Show, forall x. Rep DeleteHIT x -> DeleteHIT
forall x. DeleteHIT -> Rep DeleteHIT x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteHIT x -> DeleteHIT
$cfrom :: forall x. DeleteHIT -> Rep DeleteHIT x
Prelude.Generic)
newDeleteHIT ::
Prelude.Text ->
DeleteHIT
newDeleteHIT :: Text -> DeleteHIT
newDeleteHIT Text
pHITId_ = DeleteHIT' {$sel:hITId:DeleteHIT' :: Text
hITId = Text
pHITId_}
deleteHIT_hITId :: Lens.Lens' DeleteHIT Prelude.Text
deleteHIT_hITId :: Lens' DeleteHIT Text
deleteHIT_hITId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteHIT' {Text
hITId :: Text
$sel:hITId:DeleteHIT' :: DeleteHIT -> Text
hITId} -> Text
hITId) (\s :: DeleteHIT
s@DeleteHIT' {} Text
a -> DeleteHIT
s {$sel:hITId:DeleteHIT' :: Text
hITId = Text
a} :: DeleteHIT)
instance Core.AWSRequest DeleteHIT where
type AWSResponse DeleteHIT = DeleteHITResponse
request :: (Service -> Service) -> DeleteHIT -> Request DeleteHIT
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 DeleteHIT
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteHIT)))
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 -> DeleteHITResponse
DeleteHITResponse'
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 DeleteHIT where
hashWithSalt :: Int -> DeleteHIT -> Int
hashWithSalt Int
_salt DeleteHIT' {Text
hITId :: Text
$sel:hITId:DeleteHIT' :: DeleteHIT -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
hITId
instance Prelude.NFData DeleteHIT where
rnf :: DeleteHIT -> ()
rnf DeleteHIT' {Text
hITId :: Text
$sel:hITId:DeleteHIT' :: DeleteHIT -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
hITId
instance Data.ToHeaders DeleteHIT where
toHeaders :: DeleteHIT -> 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.DeleteHIT" ::
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 DeleteHIT where
toJSON :: DeleteHIT -> Value
toJSON DeleteHIT' {Text
hITId :: Text
$sel:hITId:DeleteHIT' :: DeleteHIT -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"HITId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
hITId)]
)
instance Data.ToPath DeleteHIT where
toPath :: DeleteHIT -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DeleteHIT where
toQuery :: DeleteHIT -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteHITResponse = DeleteHITResponse'
{
DeleteHITResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteHITResponse -> DeleteHITResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteHITResponse -> DeleteHITResponse -> Bool
$c/= :: DeleteHITResponse -> DeleteHITResponse -> Bool
== :: DeleteHITResponse -> DeleteHITResponse -> Bool
$c== :: DeleteHITResponse -> DeleteHITResponse -> Bool
Prelude.Eq, ReadPrec [DeleteHITResponse]
ReadPrec DeleteHITResponse
Int -> ReadS DeleteHITResponse
ReadS [DeleteHITResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteHITResponse]
$creadListPrec :: ReadPrec [DeleteHITResponse]
readPrec :: ReadPrec DeleteHITResponse
$creadPrec :: ReadPrec DeleteHITResponse
readList :: ReadS [DeleteHITResponse]
$creadList :: ReadS [DeleteHITResponse]
readsPrec :: Int -> ReadS DeleteHITResponse
$creadsPrec :: Int -> ReadS DeleteHITResponse
Prelude.Read, Int -> DeleteHITResponse -> ShowS
[DeleteHITResponse] -> ShowS
DeleteHITResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteHITResponse] -> ShowS
$cshowList :: [DeleteHITResponse] -> ShowS
show :: DeleteHITResponse -> String
$cshow :: DeleteHITResponse -> String
showsPrec :: Int -> DeleteHITResponse -> ShowS
$cshowsPrec :: Int -> DeleteHITResponse -> ShowS
Prelude.Show, forall x. Rep DeleteHITResponse x -> DeleteHITResponse
forall x. DeleteHITResponse -> Rep DeleteHITResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteHITResponse x -> DeleteHITResponse
$cfrom :: forall x. DeleteHITResponse -> Rep DeleteHITResponse x
Prelude.Generic)
newDeleteHITResponse ::
Prelude.Int ->
DeleteHITResponse
newDeleteHITResponse :: Int -> DeleteHITResponse
newDeleteHITResponse Int
pHttpStatus_ =
DeleteHITResponse' {$sel:httpStatus:DeleteHITResponse' :: Int
httpStatus = Int
pHttpStatus_}
deleteHITResponse_httpStatus :: Lens.Lens' DeleteHITResponse Prelude.Int
deleteHITResponse_httpStatus :: Lens' DeleteHITResponse Int
deleteHITResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteHITResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteHITResponse' :: DeleteHITResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteHITResponse
s@DeleteHITResponse' {} Int
a -> DeleteHITResponse
s {$sel:httpStatus:DeleteHITResponse' :: Int
httpStatus = Int
a} :: DeleteHITResponse)
instance Prelude.NFData DeleteHITResponse where
rnf :: DeleteHITResponse -> ()
rnf DeleteHITResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteHITResponse' :: DeleteHITResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus