{-# 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.CreateHITType
(
CreateHITType (..),
newCreateHITType,
createHITType_autoApprovalDelayInSeconds,
createHITType_keywords,
createHITType_qualificationRequirements,
createHITType_assignmentDurationInSeconds,
createHITType_reward,
createHITType_title,
createHITType_description,
CreateHITTypeResponse (..),
newCreateHITTypeResponse,
createHITTypeResponse_hITTypeId,
createHITTypeResponse_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 CreateHITType = CreateHITType'
{
CreateHITType -> Maybe Integer
autoApprovalDelayInSeconds :: Prelude.Maybe Prelude.Integer,
CreateHITType -> Maybe Text
keywords :: Prelude.Maybe Prelude.Text,
CreateHITType -> Maybe [QualificationRequirement]
qualificationRequirements :: Prelude.Maybe [QualificationRequirement],
CreateHITType -> Integer
assignmentDurationInSeconds :: Prelude.Integer,
CreateHITType -> Text
reward :: Prelude.Text,
CreateHITType -> Text
title :: Prelude.Text,
CreateHITType -> Text
description :: Prelude.Text
}
deriving (CreateHITType -> CreateHITType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateHITType -> CreateHITType -> Bool
$c/= :: CreateHITType -> CreateHITType -> Bool
== :: CreateHITType -> CreateHITType -> Bool
$c== :: CreateHITType -> CreateHITType -> Bool
Prelude.Eq, ReadPrec [CreateHITType]
ReadPrec CreateHITType
Int -> ReadS CreateHITType
ReadS [CreateHITType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateHITType]
$creadListPrec :: ReadPrec [CreateHITType]
readPrec :: ReadPrec CreateHITType
$creadPrec :: ReadPrec CreateHITType
readList :: ReadS [CreateHITType]
$creadList :: ReadS [CreateHITType]
readsPrec :: Int -> ReadS CreateHITType
$creadsPrec :: Int -> ReadS CreateHITType
Prelude.Read, Int -> CreateHITType -> ShowS
[CreateHITType] -> ShowS
CreateHITType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateHITType] -> ShowS
$cshowList :: [CreateHITType] -> ShowS
show :: CreateHITType -> String
$cshow :: CreateHITType -> String
showsPrec :: Int -> CreateHITType -> ShowS
$cshowsPrec :: Int -> CreateHITType -> ShowS
Prelude.Show, forall x. Rep CreateHITType x -> CreateHITType
forall x. CreateHITType -> Rep CreateHITType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateHITType x -> CreateHITType
$cfrom :: forall x. CreateHITType -> Rep CreateHITType x
Prelude.Generic)
newCreateHITType ::
Prelude.Integer ->
Prelude.Text ->
Prelude.Text ->
Prelude.Text ->
CreateHITType
newCreateHITType :: Integer -> Text -> Text -> Text -> CreateHITType
newCreateHITType
Integer
pAssignmentDurationInSeconds_
Text
pReward_
Text
pTitle_
Text
pDescription_ =
CreateHITType'
{ $sel:autoApprovalDelayInSeconds:CreateHITType' :: Maybe Integer
autoApprovalDelayInSeconds =
forall a. Maybe a
Prelude.Nothing,
$sel:keywords:CreateHITType' :: Maybe Text
keywords = forall a. Maybe a
Prelude.Nothing,
$sel:qualificationRequirements:CreateHITType' :: Maybe [QualificationRequirement]
qualificationRequirements = forall a. Maybe a
Prelude.Nothing,
$sel:assignmentDurationInSeconds:CreateHITType' :: Integer
assignmentDurationInSeconds =
Integer
pAssignmentDurationInSeconds_,
$sel:reward:CreateHITType' :: Text
reward = Text
pReward_,
$sel:title:CreateHITType' :: Text
title = Text
pTitle_,
$sel:description:CreateHITType' :: Text
description = Text
pDescription_
}
createHITType_autoApprovalDelayInSeconds :: Lens.Lens' CreateHITType (Prelude.Maybe Prelude.Integer)
createHITType_autoApprovalDelayInSeconds :: Lens' CreateHITType (Maybe Integer)
createHITType_autoApprovalDelayInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Maybe Integer
autoApprovalDelayInSeconds :: Maybe Integer
$sel:autoApprovalDelayInSeconds:CreateHITType' :: CreateHITType -> Maybe Integer
autoApprovalDelayInSeconds} -> Maybe Integer
autoApprovalDelayInSeconds) (\s :: CreateHITType
s@CreateHITType' {} Maybe Integer
a -> CreateHITType
s {$sel:autoApprovalDelayInSeconds:CreateHITType' :: Maybe Integer
autoApprovalDelayInSeconds = Maybe Integer
a} :: CreateHITType)
createHITType_keywords :: Lens.Lens' CreateHITType (Prelude.Maybe Prelude.Text)
createHITType_keywords :: Lens' CreateHITType (Maybe Text)
createHITType_keywords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Maybe Text
keywords :: Maybe Text
$sel:keywords:CreateHITType' :: CreateHITType -> Maybe Text
keywords} -> Maybe Text
keywords) (\s :: CreateHITType
s@CreateHITType' {} Maybe Text
a -> CreateHITType
s {$sel:keywords:CreateHITType' :: Maybe Text
keywords = Maybe Text
a} :: CreateHITType)
createHITType_qualificationRequirements :: Lens.Lens' CreateHITType (Prelude.Maybe [QualificationRequirement])
createHITType_qualificationRequirements :: Lens' CreateHITType (Maybe [QualificationRequirement])
createHITType_qualificationRequirements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Maybe [QualificationRequirement]
qualificationRequirements :: Maybe [QualificationRequirement]
$sel:qualificationRequirements:CreateHITType' :: CreateHITType -> Maybe [QualificationRequirement]
qualificationRequirements} -> Maybe [QualificationRequirement]
qualificationRequirements) (\s :: CreateHITType
s@CreateHITType' {} Maybe [QualificationRequirement]
a -> CreateHITType
s {$sel:qualificationRequirements:CreateHITType' :: Maybe [QualificationRequirement]
qualificationRequirements = Maybe [QualificationRequirement]
a} :: CreateHITType) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
createHITType_assignmentDurationInSeconds :: Lens.Lens' CreateHITType Prelude.Integer
createHITType_assignmentDurationInSeconds :: Lens' CreateHITType Integer
createHITType_assignmentDurationInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Integer
assignmentDurationInSeconds :: Integer
$sel:assignmentDurationInSeconds:CreateHITType' :: CreateHITType -> Integer
assignmentDurationInSeconds} -> Integer
assignmentDurationInSeconds) (\s :: CreateHITType
s@CreateHITType' {} Integer
a -> CreateHITType
s {$sel:assignmentDurationInSeconds:CreateHITType' :: Integer
assignmentDurationInSeconds = Integer
a} :: CreateHITType)
createHITType_reward :: Lens.Lens' CreateHITType Prelude.Text
createHITType_reward :: Lens' CreateHITType Text
createHITType_reward = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Text
reward :: Text
$sel:reward:CreateHITType' :: CreateHITType -> Text
reward} -> Text
reward) (\s :: CreateHITType
s@CreateHITType' {} Text
a -> CreateHITType
s {$sel:reward:CreateHITType' :: Text
reward = Text
a} :: CreateHITType)
createHITType_title :: Lens.Lens' CreateHITType Prelude.Text
createHITType_title :: Lens' CreateHITType Text
createHITType_title = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Text
title :: Text
$sel:title:CreateHITType' :: CreateHITType -> Text
title} -> Text
title) (\s :: CreateHITType
s@CreateHITType' {} Text
a -> CreateHITType
s {$sel:title:CreateHITType' :: Text
title = Text
a} :: CreateHITType)
createHITType_description :: Lens.Lens' CreateHITType Prelude.Text
createHITType_description :: Lens' CreateHITType Text
createHITType_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITType' {Text
description :: Text
$sel:description:CreateHITType' :: CreateHITType -> Text
description} -> Text
description) (\s :: CreateHITType
s@CreateHITType' {} Text
a -> CreateHITType
s {$sel:description:CreateHITType' :: Text
description = Text
a} :: CreateHITType)
instance Core.AWSRequest CreateHITType where
type
AWSResponse CreateHITType =
CreateHITTypeResponse
request :: (Service -> Service) -> CreateHITType -> Request CreateHITType
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 CreateHITType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateHITType)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe Text -> Int -> CreateHITTypeResponse
CreateHITTypeResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"HITTypeId")
forall (f :: * -> *) a b. Applicative f => 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 CreateHITType where
hashWithSalt :: Int -> CreateHITType -> Int
hashWithSalt Int
_salt CreateHITType' {Integer
Maybe Integer
Maybe [QualificationRequirement]
Maybe Text
Text
description :: Text
title :: Text
reward :: Text
assignmentDurationInSeconds :: Integer
qualificationRequirements :: Maybe [QualificationRequirement]
keywords :: Maybe Text
autoApprovalDelayInSeconds :: Maybe Integer
$sel:description:CreateHITType' :: CreateHITType -> Text
$sel:title:CreateHITType' :: CreateHITType -> Text
$sel:reward:CreateHITType' :: CreateHITType -> Text
$sel:assignmentDurationInSeconds:CreateHITType' :: CreateHITType -> Integer
$sel:qualificationRequirements:CreateHITType' :: CreateHITType -> Maybe [QualificationRequirement]
$sel:keywords:CreateHITType' :: CreateHITType -> Maybe Text
$sel:autoApprovalDelayInSeconds:CreateHITType' :: CreateHITType -> Maybe Integer
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
autoApprovalDelayInSeconds
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keywords
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [QualificationRequirement]
qualificationRequirements
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
assignmentDurationInSeconds
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
reward
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
title
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description
instance Prelude.NFData CreateHITType where
rnf :: CreateHITType -> ()
rnf CreateHITType' {Integer
Maybe Integer
Maybe [QualificationRequirement]
Maybe Text
Text
description :: Text
title :: Text
reward :: Text
assignmentDurationInSeconds :: Integer
qualificationRequirements :: Maybe [QualificationRequirement]
keywords :: Maybe Text
autoApprovalDelayInSeconds :: Maybe Integer
$sel:description:CreateHITType' :: CreateHITType -> Text
$sel:title:CreateHITType' :: CreateHITType -> Text
$sel:reward:CreateHITType' :: CreateHITType -> Text
$sel:assignmentDurationInSeconds:CreateHITType' :: CreateHITType -> Integer
$sel:qualificationRequirements:CreateHITType' :: CreateHITType -> Maybe [QualificationRequirement]
$sel:keywords:CreateHITType' :: CreateHITType -> Maybe Text
$sel:autoApprovalDelayInSeconds:CreateHITType' :: CreateHITType -> Maybe Integer
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
autoApprovalDelayInSeconds
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keywords
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [QualificationRequirement]
qualificationRequirements
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
assignmentDurationInSeconds
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
reward
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
title
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description
instance Data.ToHeaders CreateHITType where
toHeaders :: CreateHITType -> 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.CreateHITType" ::
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 CreateHITType where
toJSON :: CreateHITType -> Value
toJSON CreateHITType' {Integer
Maybe Integer
Maybe [QualificationRequirement]
Maybe Text
Text
description :: Text
title :: Text
reward :: Text
assignmentDurationInSeconds :: Integer
qualificationRequirements :: Maybe [QualificationRequirement]
keywords :: Maybe Text
autoApprovalDelayInSeconds :: Maybe Integer
$sel:description:CreateHITType' :: CreateHITType -> Text
$sel:title:CreateHITType' :: CreateHITType -> Text
$sel:reward:CreateHITType' :: CreateHITType -> Text
$sel:assignmentDurationInSeconds:CreateHITType' :: CreateHITType -> Integer
$sel:qualificationRequirements:CreateHITType' :: CreateHITType -> Maybe [QualificationRequirement]
$sel:keywords:CreateHITType' :: CreateHITType -> Maybe Text
$sel:autoApprovalDelayInSeconds:CreateHITType' :: CreateHITType -> Maybe Integer
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"AutoApprovalDelayInSeconds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Integer
autoApprovalDelayInSeconds,
(Key
"Keywords" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
keywords,
(Key
"QualificationRequirements" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [QualificationRequirement]
qualificationRequirements,
forall a. a -> Maybe a
Prelude.Just
( Key
"AssignmentDurationInSeconds"
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Integer
assignmentDurationInSeconds
),
forall a. a -> Maybe a
Prelude.Just (Key
"Reward" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
reward),
forall a. a -> Maybe a
Prelude.Just (Key
"Title" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
title),
forall a. a -> Maybe a
Prelude.Just (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
description)
]
)
instance Data.ToPath CreateHITType where
toPath :: CreateHITType -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateHITType where
toQuery :: CreateHITType -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateHITTypeResponse = CreateHITTypeResponse'
{
CreateHITTypeResponse -> Maybe Text
hITTypeId :: Prelude.Maybe Prelude.Text,
CreateHITTypeResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateHITTypeResponse -> CreateHITTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateHITTypeResponse -> CreateHITTypeResponse -> Bool
$c/= :: CreateHITTypeResponse -> CreateHITTypeResponse -> Bool
== :: CreateHITTypeResponse -> CreateHITTypeResponse -> Bool
$c== :: CreateHITTypeResponse -> CreateHITTypeResponse -> Bool
Prelude.Eq, ReadPrec [CreateHITTypeResponse]
ReadPrec CreateHITTypeResponse
Int -> ReadS CreateHITTypeResponse
ReadS [CreateHITTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateHITTypeResponse]
$creadListPrec :: ReadPrec [CreateHITTypeResponse]
readPrec :: ReadPrec CreateHITTypeResponse
$creadPrec :: ReadPrec CreateHITTypeResponse
readList :: ReadS [CreateHITTypeResponse]
$creadList :: ReadS [CreateHITTypeResponse]
readsPrec :: Int -> ReadS CreateHITTypeResponse
$creadsPrec :: Int -> ReadS CreateHITTypeResponse
Prelude.Read, Int -> CreateHITTypeResponse -> ShowS
[CreateHITTypeResponse] -> ShowS
CreateHITTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateHITTypeResponse] -> ShowS
$cshowList :: [CreateHITTypeResponse] -> ShowS
show :: CreateHITTypeResponse -> String
$cshow :: CreateHITTypeResponse -> String
showsPrec :: Int -> CreateHITTypeResponse -> ShowS
$cshowsPrec :: Int -> CreateHITTypeResponse -> ShowS
Prelude.Show, forall x. Rep CreateHITTypeResponse x -> CreateHITTypeResponse
forall x. CreateHITTypeResponse -> Rep CreateHITTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateHITTypeResponse x -> CreateHITTypeResponse
$cfrom :: forall x. CreateHITTypeResponse -> Rep CreateHITTypeResponse x
Prelude.Generic)
newCreateHITTypeResponse ::
Prelude.Int ->
CreateHITTypeResponse
newCreateHITTypeResponse :: Int -> CreateHITTypeResponse
newCreateHITTypeResponse Int
pHttpStatus_ =
CreateHITTypeResponse'
{ $sel:hITTypeId:CreateHITTypeResponse' :: Maybe Text
hITTypeId = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateHITTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createHITTypeResponse_hITTypeId :: Lens.Lens' CreateHITTypeResponse (Prelude.Maybe Prelude.Text)
createHITTypeResponse_hITTypeId :: Lens' CreateHITTypeResponse (Maybe Text)
createHITTypeResponse_hITTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITTypeResponse' {Maybe Text
hITTypeId :: Maybe Text
$sel:hITTypeId:CreateHITTypeResponse' :: CreateHITTypeResponse -> Maybe Text
hITTypeId} -> Maybe Text
hITTypeId) (\s :: CreateHITTypeResponse
s@CreateHITTypeResponse' {} Maybe Text
a -> CreateHITTypeResponse
s {$sel:hITTypeId:CreateHITTypeResponse' :: Maybe Text
hITTypeId = Maybe Text
a} :: CreateHITTypeResponse)
createHITTypeResponse_httpStatus :: Lens.Lens' CreateHITTypeResponse Prelude.Int
createHITTypeResponse_httpStatus :: Lens' CreateHITTypeResponse Int
createHITTypeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateHITTypeResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateHITTypeResponse' :: CreateHITTypeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateHITTypeResponse
s@CreateHITTypeResponse' {} Int
a -> CreateHITTypeResponse
s {$sel:httpStatus:CreateHITTypeResponse' :: Int
httpStatus = Int
a} :: CreateHITTypeResponse)
instance Prelude.NFData CreateHITTypeResponse where
rnf :: CreateHITTypeResponse -> ()
rnf CreateHITTypeResponse' {Int
Maybe Text
httpStatus :: Int
hITTypeId :: Maybe Text
$sel:httpStatus:CreateHITTypeResponse' :: CreateHITTypeResponse -> Int
$sel:hITTypeId:CreateHITTypeResponse' :: CreateHITTypeResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hITTypeId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus