{-# 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.ListHITsForQualificationType
(
ListHITsForQualificationType (..),
newListHITsForQualificationType,
listHITsForQualificationType_maxResults,
listHITsForQualificationType_nextToken,
listHITsForQualificationType_qualificationTypeId,
ListHITsForQualificationTypeResponse (..),
newListHITsForQualificationTypeResponse,
listHITsForQualificationTypeResponse_hITs,
listHITsForQualificationTypeResponse_nextToken,
listHITsForQualificationTypeResponse_numResults,
listHITsForQualificationTypeResponse_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 ListHITsForQualificationType = ListHITsForQualificationType'
{
ListHITsForQualificationType -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListHITsForQualificationType -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListHITsForQualificationType -> Text
qualificationTypeId :: Prelude.Text
}
deriving (ListHITsForQualificationType
-> ListHITsForQualificationType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListHITsForQualificationType
-> ListHITsForQualificationType -> Bool
$c/= :: ListHITsForQualificationType
-> ListHITsForQualificationType -> Bool
== :: ListHITsForQualificationType
-> ListHITsForQualificationType -> Bool
$c== :: ListHITsForQualificationType
-> ListHITsForQualificationType -> Bool
Prelude.Eq, ReadPrec [ListHITsForQualificationType]
ReadPrec ListHITsForQualificationType
Int -> ReadS ListHITsForQualificationType
ReadS [ListHITsForQualificationType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListHITsForQualificationType]
$creadListPrec :: ReadPrec [ListHITsForQualificationType]
readPrec :: ReadPrec ListHITsForQualificationType
$creadPrec :: ReadPrec ListHITsForQualificationType
readList :: ReadS [ListHITsForQualificationType]
$creadList :: ReadS [ListHITsForQualificationType]
readsPrec :: Int -> ReadS ListHITsForQualificationType
$creadsPrec :: Int -> ReadS ListHITsForQualificationType
Prelude.Read, Int -> ListHITsForQualificationType -> ShowS
[ListHITsForQualificationType] -> ShowS
ListHITsForQualificationType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListHITsForQualificationType] -> ShowS
$cshowList :: [ListHITsForQualificationType] -> ShowS
show :: ListHITsForQualificationType -> String
$cshow :: ListHITsForQualificationType -> String
showsPrec :: Int -> ListHITsForQualificationType -> ShowS
$cshowsPrec :: Int -> ListHITsForQualificationType -> ShowS
Prelude.Show, forall x.
Rep ListHITsForQualificationType x -> ListHITsForQualificationType
forall x.
ListHITsForQualificationType -> Rep ListHITsForQualificationType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListHITsForQualificationType x -> ListHITsForQualificationType
$cfrom :: forall x.
ListHITsForQualificationType -> Rep ListHITsForQualificationType x
Prelude.Generic)
newListHITsForQualificationType ::
Prelude.Text ->
ListHITsForQualificationType
newListHITsForQualificationType :: Text -> ListHITsForQualificationType
newListHITsForQualificationType Text
pQualificationTypeId_ =
ListHITsForQualificationType'
{ $sel:maxResults:ListHITsForQualificationType' :: Maybe Natural
maxResults =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListHITsForQualificationType' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:qualificationTypeId:ListHITsForQualificationType' :: Text
qualificationTypeId = Text
pQualificationTypeId_
}
listHITsForQualificationType_maxResults :: Lens.Lens' ListHITsForQualificationType (Prelude.Maybe Prelude.Natural)
listHITsForQualificationType_maxResults :: Lens' ListHITsForQualificationType (Maybe Natural)
listHITsForQualificationType_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationType' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListHITsForQualificationType
s@ListHITsForQualificationType' {} Maybe Natural
a -> ListHITsForQualificationType
s {$sel:maxResults:ListHITsForQualificationType' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListHITsForQualificationType)
listHITsForQualificationType_nextToken :: Lens.Lens' ListHITsForQualificationType (Prelude.Maybe Prelude.Text)
listHITsForQualificationType_nextToken :: Lens' ListHITsForQualificationType (Maybe Text)
listHITsForQualificationType_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationType' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListHITsForQualificationType
s@ListHITsForQualificationType' {} Maybe Text
a -> ListHITsForQualificationType
s {$sel:nextToken:ListHITsForQualificationType' :: Maybe Text
nextToken = Maybe Text
a} :: ListHITsForQualificationType)
listHITsForQualificationType_qualificationTypeId :: Lens.Lens' ListHITsForQualificationType Prelude.Text
listHITsForQualificationType_qualificationTypeId :: Lens' ListHITsForQualificationType Text
listHITsForQualificationType_qualificationTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationType' {Text
qualificationTypeId :: Text
$sel:qualificationTypeId:ListHITsForQualificationType' :: ListHITsForQualificationType -> Text
qualificationTypeId} -> Text
qualificationTypeId) (\s :: ListHITsForQualificationType
s@ListHITsForQualificationType' {} Text
a -> ListHITsForQualificationType
s {$sel:qualificationTypeId:ListHITsForQualificationType' :: Text
qualificationTypeId = Text
a} :: ListHITsForQualificationType)
instance Core.AWSPager ListHITsForQualificationType where
page :: ListHITsForQualificationType
-> AWSResponse ListHITsForQualificationType
-> Maybe ListHITsForQualificationType
page ListHITsForQualificationType
rq AWSResponse ListHITsForQualificationType
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListHITsForQualificationType
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListHITsForQualificationTypeResponse (Maybe Text)
listHITsForQualificationTypeResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListHITsForQualificationType
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListHITsForQualificationTypeResponse (Maybe [HIT])
listHITsForQualificationTypeResponse_hITs
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ ListHITsForQualificationType
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListHITsForQualificationType (Maybe Text)
listHITsForQualificationType_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListHITsForQualificationType
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListHITsForQualificationTypeResponse (Maybe Text)
listHITsForQualificationTypeResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest ListHITsForQualificationType where
type
AWSResponse ListHITsForQualificationType =
ListHITsForQualificationTypeResponse
request :: (Service -> Service)
-> ListHITsForQualificationType
-> Request ListHITsForQualificationType
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 ListHITsForQualificationType
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ListHITsForQualificationType)))
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 [HIT]
-> Maybe Text
-> Maybe Int
-> Int
-> ListHITsForQualificationTypeResponse
ListHITsForQualificationTypeResponse'
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
"HITs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NumResults")
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
ListHITsForQualificationType
where
hashWithSalt :: Int -> ListHITsForQualificationType -> Int
hashWithSalt Int
_salt ListHITsForQualificationType' {Maybe Natural
Maybe Text
Text
qualificationTypeId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:qualificationTypeId:ListHITsForQualificationType' :: ListHITsForQualificationType -> Text
$sel:nextToken:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Text
$sel:maxResults:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Natural
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
qualificationTypeId
instance Prelude.NFData ListHITsForQualificationType where
rnf :: ListHITsForQualificationType -> ()
rnf ListHITsForQualificationType' {Maybe Natural
Maybe Text
Text
qualificationTypeId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:qualificationTypeId:ListHITsForQualificationType' :: ListHITsForQualificationType -> Text
$sel:nextToken:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Text
$sel:maxResults:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Natural
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
qualificationTypeId
instance Data.ToHeaders ListHITsForQualificationType where
toHeaders :: ListHITsForQualificationType -> 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.ListHITsForQualificationType" ::
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 ListHITsForQualificationType where
toJSON :: ListHITsForQualificationType -> Value
toJSON ListHITsForQualificationType' {Maybe Natural
Maybe Text
Text
qualificationTypeId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:qualificationTypeId:ListHITsForQualificationType' :: ListHITsForQualificationType -> Text
$sel:nextToken:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Text
$sel:maxResults:ListHITsForQualificationType' :: ListHITsForQualificationType -> Maybe Natural
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"MaxResults" 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 Natural
maxResults,
(Key
"NextToken" 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
nextToken,
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 ListHITsForQualificationType where
toPath :: ListHITsForQualificationType -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListHITsForQualificationType where
toQuery :: ListHITsForQualificationType -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListHITsForQualificationTypeResponse = ListHITsForQualificationTypeResponse'
{
ListHITsForQualificationTypeResponse -> Maybe [HIT]
hITs :: Prelude.Maybe [HIT],
ListHITsForQualificationTypeResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListHITsForQualificationTypeResponse -> Maybe Int
numResults :: Prelude.Maybe Prelude.Int,
ListHITsForQualificationTypeResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListHITsForQualificationTypeResponse
-> ListHITsForQualificationTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListHITsForQualificationTypeResponse
-> ListHITsForQualificationTypeResponse -> Bool
$c/= :: ListHITsForQualificationTypeResponse
-> ListHITsForQualificationTypeResponse -> Bool
== :: ListHITsForQualificationTypeResponse
-> ListHITsForQualificationTypeResponse -> Bool
$c== :: ListHITsForQualificationTypeResponse
-> ListHITsForQualificationTypeResponse -> Bool
Prelude.Eq, ReadPrec [ListHITsForQualificationTypeResponse]
ReadPrec ListHITsForQualificationTypeResponse
Int -> ReadS ListHITsForQualificationTypeResponse
ReadS [ListHITsForQualificationTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListHITsForQualificationTypeResponse]
$creadListPrec :: ReadPrec [ListHITsForQualificationTypeResponse]
readPrec :: ReadPrec ListHITsForQualificationTypeResponse
$creadPrec :: ReadPrec ListHITsForQualificationTypeResponse
readList :: ReadS [ListHITsForQualificationTypeResponse]
$creadList :: ReadS [ListHITsForQualificationTypeResponse]
readsPrec :: Int -> ReadS ListHITsForQualificationTypeResponse
$creadsPrec :: Int -> ReadS ListHITsForQualificationTypeResponse
Prelude.Read, Int -> ListHITsForQualificationTypeResponse -> ShowS
[ListHITsForQualificationTypeResponse] -> ShowS
ListHITsForQualificationTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListHITsForQualificationTypeResponse] -> ShowS
$cshowList :: [ListHITsForQualificationTypeResponse] -> ShowS
show :: ListHITsForQualificationTypeResponse -> String
$cshow :: ListHITsForQualificationTypeResponse -> String
showsPrec :: Int -> ListHITsForQualificationTypeResponse -> ShowS
$cshowsPrec :: Int -> ListHITsForQualificationTypeResponse -> ShowS
Prelude.Show, forall x.
Rep ListHITsForQualificationTypeResponse x
-> ListHITsForQualificationTypeResponse
forall x.
ListHITsForQualificationTypeResponse
-> Rep ListHITsForQualificationTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListHITsForQualificationTypeResponse x
-> ListHITsForQualificationTypeResponse
$cfrom :: forall x.
ListHITsForQualificationTypeResponse
-> Rep ListHITsForQualificationTypeResponse x
Prelude.Generic)
newListHITsForQualificationTypeResponse ::
Prelude.Int ->
ListHITsForQualificationTypeResponse
newListHITsForQualificationTypeResponse :: Int -> ListHITsForQualificationTypeResponse
newListHITsForQualificationTypeResponse Int
pHttpStatus_ =
ListHITsForQualificationTypeResponse'
{ $sel:hITs:ListHITsForQualificationTypeResponse' :: Maybe [HIT]
hITs =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListHITsForQualificationTypeResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:numResults:ListHITsForQualificationTypeResponse' :: Maybe Int
numResults = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListHITsForQualificationTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listHITsForQualificationTypeResponse_hITs :: Lens.Lens' ListHITsForQualificationTypeResponse (Prelude.Maybe [HIT])
listHITsForQualificationTypeResponse_hITs :: Lens' ListHITsForQualificationTypeResponse (Maybe [HIT])
listHITsForQualificationTypeResponse_hITs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationTypeResponse' {Maybe [HIT]
hITs :: Maybe [HIT]
$sel:hITs:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe [HIT]
hITs} -> Maybe [HIT]
hITs) (\s :: ListHITsForQualificationTypeResponse
s@ListHITsForQualificationTypeResponse' {} Maybe [HIT]
a -> ListHITsForQualificationTypeResponse
s {$sel:hITs:ListHITsForQualificationTypeResponse' :: Maybe [HIT]
hITs = Maybe [HIT]
a} :: ListHITsForQualificationTypeResponse) 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
listHITsForQualificationTypeResponse_nextToken :: Lens.Lens' ListHITsForQualificationTypeResponse (Prelude.Maybe Prelude.Text)
listHITsForQualificationTypeResponse_nextToken :: Lens' ListHITsForQualificationTypeResponse (Maybe Text)
listHITsForQualificationTypeResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationTypeResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListHITsForQualificationTypeResponse
s@ListHITsForQualificationTypeResponse' {} Maybe Text
a -> ListHITsForQualificationTypeResponse
s {$sel:nextToken:ListHITsForQualificationTypeResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListHITsForQualificationTypeResponse)
listHITsForQualificationTypeResponse_numResults :: Lens.Lens' ListHITsForQualificationTypeResponse (Prelude.Maybe Prelude.Int)
listHITsForQualificationTypeResponse_numResults :: Lens' ListHITsForQualificationTypeResponse (Maybe Int)
listHITsForQualificationTypeResponse_numResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationTypeResponse' {Maybe Int
numResults :: Maybe Int
$sel:numResults:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe Int
numResults} -> Maybe Int
numResults) (\s :: ListHITsForQualificationTypeResponse
s@ListHITsForQualificationTypeResponse' {} Maybe Int
a -> ListHITsForQualificationTypeResponse
s {$sel:numResults:ListHITsForQualificationTypeResponse' :: Maybe Int
numResults = Maybe Int
a} :: ListHITsForQualificationTypeResponse)
listHITsForQualificationTypeResponse_httpStatus :: Lens.Lens' ListHITsForQualificationTypeResponse Prelude.Int
listHITsForQualificationTypeResponse_httpStatus :: Lens' ListHITsForQualificationTypeResponse Int
listHITsForQualificationTypeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHITsForQualificationTypeResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListHITsForQualificationTypeResponse
s@ListHITsForQualificationTypeResponse' {} Int
a -> ListHITsForQualificationTypeResponse
s {$sel:httpStatus:ListHITsForQualificationTypeResponse' :: Int
httpStatus = Int
a} :: ListHITsForQualificationTypeResponse)
instance
Prelude.NFData
ListHITsForQualificationTypeResponse
where
rnf :: ListHITsForQualificationTypeResponse -> ()
rnf ListHITsForQualificationTypeResponse' {Int
Maybe Int
Maybe [HIT]
Maybe Text
httpStatus :: Int
numResults :: Maybe Int
nextToken :: Maybe Text
hITs :: Maybe [HIT]
$sel:httpStatus:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Int
$sel:numResults:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe Int
$sel:nextToken:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe Text
$sel:hITs:ListHITsForQualificationTypeResponse' :: ListHITsForQualificationTypeResponse -> Maybe [HIT]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [HIT]
hITs
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus