{-# 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.GetHIT
-- 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 @GetHIT@ operation retrieves the details of the specified HIT.
module Amazonka.MechanicalTurk.GetHIT
  ( -- * Creating a Request
    GetHIT (..),
    newGetHIT,

    -- * Request Lenses
    getHIT_hITId,

    -- * Destructuring the Response
    GetHITResponse (..),
    newGetHITResponse,

    -- * Response Lenses
    getHITResponse_hit,
    getHITResponse_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:/ 'newGetHIT' smart constructor.
data GetHIT = GetHIT'
  { -- | The ID of the HIT to be retrieved.
    GetHIT -> Text
hITId :: Prelude.Text
  }
  deriving (GetHIT -> GetHIT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHIT -> GetHIT -> Bool
$c/= :: GetHIT -> GetHIT -> Bool
== :: GetHIT -> GetHIT -> Bool
$c== :: GetHIT -> GetHIT -> Bool
Prelude.Eq, ReadPrec [GetHIT]
ReadPrec GetHIT
Int -> ReadS GetHIT
ReadS [GetHIT]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHIT]
$creadListPrec :: ReadPrec [GetHIT]
readPrec :: ReadPrec GetHIT
$creadPrec :: ReadPrec GetHIT
readList :: ReadS [GetHIT]
$creadList :: ReadS [GetHIT]
readsPrec :: Int -> ReadS GetHIT
$creadsPrec :: Int -> ReadS GetHIT
Prelude.Read, Int -> GetHIT -> ShowS
[GetHIT] -> ShowS
GetHIT -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHIT] -> ShowS
$cshowList :: [GetHIT] -> ShowS
show :: GetHIT -> String
$cshow :: GetHIT -> String
showsPrec :: Int -> GetHIT -> ShowS
$cshowsPrec :: Int -> GetHIT -> ShowS
Prelude.Show, forall x. Rep GetHIT x -> GetHIT
forall x. GetHIT -> Rep GetHIT x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetHIT x -> GetHIT
$cfrom :: forall x. GetHIT -> Rep GetHIT x
Prelude.Generic)

-- |
-- Create a value of 'GetHIT' 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:
--
-- 'hITId', 'getHIT_hITId' - The ID of the HIT to be retrieved.
newGetHIT ::
  -- | 'hITId'
  Prelude.Text ->
  GetHIT
newGetHIT :: Text -> GetHIT
newGetHIT Text
pHITId_ = GetHIT' {$sel:hITId:GetHIT' :: Text
hITId = Text
pHITId_}

-- | The ID of the HIT to be retrieved.
getHIT_hITId :: Lens.Lens' GetHIT Prelude.Text
getHIT_hITId :: Lens' GetHIT Text
getHIT_hITId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHIT' {Text
hITId :: Text
$sel:hITId:GetHIT' :: GetHIT -> Text
hITId} -> Text
hITId) (\s :: GetHIT
s@GetHIT' {} Text
a -> GetHIT
s {$sel:hITId:GetHIT' :: Text
hITId = Text
a} :: GetHIT)

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

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

instance Data.ToHeaders GetHIT where
  toHeaders :: GetHIT -> 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.GetHIT" ::
                          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 GetHIT where
  toJSON :: GetHIT -> Value
toJSON GetHIT' {Text
hITId :: Text
$sel:hITId:GetHIT' :: GetHIT -> 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 GetHIT where
  toPath :: GetHIT -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'GetHITResponse' 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:
--
-- 'hit', 'getHITResponse_hit' - Contains the requested HIT data.
--
-- 'httpStatus', 'getHITResponse_httpStatus' - The response's http status code.
newGetHITResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetHITResponse
newGetHITResponse :: Int -> GetHITResponse
newGetHITResponse Int
pHttpStatus_ =
  GetHITResponse'
    { $sel:hit:GetHITResponse' :: Maybe HIT
hit = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetHITResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the requested HIT data.
getHITResponse_hit :: Lens.Lens' GetHITResponse (Prelude.Maybe HIT)
getHITResponse_hit :: Lens' GetHITResponse (Maybe HIT)
getHITResponse_hit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHITResponse' {Maybe HIT
hit :: Maybe HIT
$sel:hit:GetHITResponse' :: GetHITResponse -> Maybe HIT
hit} -> Maybe HIT
hit) (\s :: GetHITResponse
s@GetHITResponse' {} Maybe HIT
a -> GetHITResponse
s {$sel:hit:GetHITResponse' :: Maybe HIT
hit = Maybe HIT
a} :: GetHITResponse)

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

instance Prelude.NFData GetHITResponse where
  rnf :: GetHITResponse -> ()
rnf GetHITResponse' {Int
Maybe HIT
httpStatus :: Int
hit :: Maybe HIT
$sel:httpStatus:GetHITResponse' :: GetHITResponse -> Int
$sel:hit:GetHITResponse' :: GetHITResponse -> Maybe HIT
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe HIT
hit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus