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

    -- * Request Lenses
    getAssignment_assignmentId,

    -- * Destructuring the Response
    GetAssignmentResponse (..),
    newGetAssignmentResponse,

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

-- |
-- Create a value of 'GetAssignment' 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:
--
-- 'assignmentId', 'getAssignment_assignmentId' - The ID of the Assignment to be retrieved.
newGetAssignment ::
  -- | 'assignmentId'
  Prelude.Text ->
  GetAssignment
newGetAssignment :: Text -> GetAssignment
newGetAssignment Text
pAssignmentId_ =
  GetAssignment' {$sel:assignmentId:GetAssignment' :: Text
assignmentId = Text
pAssignmentId_}

-- | The ID of the Assignment to be retrieved.
getAssignment_assignmentId :: Lens.Lens' GetAssignment Prelude.Text
getAssignment_assignmentId :: Lens' GetAssignment Text
getAssignment_assignmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssignment' {Text
assignmentId :: Text
$sel:assignmentId:GetAssignment' :: GetAssignment -> Text
assignmentId} -> Text
assignmentId) (\s :: GetAssignment
s@GetAssignment' {} Text
a -> GetAssignment
s {$sel:assignmentId:GetAssignment' :: Text
assignmentId = Text
a} :: GetAssignment)

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

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

instance Data.ToHeaders GetAssignment where
  toHeaders :: GetAssignment -> 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.GetAssignment" ::
                          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 GetAssignment where
  toJSON :: GetAssignment -> Value
toJSON GetAssignment' {Text
assignmentId :: Text
$sel:assignmentId:GetAssignment' :: GetAssignment -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"AssignmentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
assignmentId)]
      )

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

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

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

-- |
-- Create a value of 'GetAssignmentResponse' 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:
--
-- 'assignment', 'getAssignmentResponse_assignment' - The assignment. The response includes one Assignment element.
--
-- 'hit', 'getAssignmentResponse_hit' - The HIT associated with this assignment. The response includes one HIT
-- element.
--
-- 'httpStatus', 'getAssignmentResponse_httpStatus' - The response's http status code.
newGetAssignmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAssignmentResponse
newGetAssignmentResponse :: Int -> GetAssignmentResponse
newGetAssignmentResponse Int
pHttpStatus_ =
  GetAssignmentResponse'
    { $sel:assignment:GetAssignmentResponse' :: Maybe Assignment
assignment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:hit:GetAssignmentResponse' :: Maybe HIT
hit = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAssignmentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The assignment. The response includes one Assignment element.
getAssignmentResponse_assignment :: Lens.Lens' GetAssignmentResponse (Prelude.Maybe Assignment)
getAssignmentResponse_assignment :: Lens' GetAssignmentResponse (Maybe Assignment)
getAssignmentResponse_assignment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssignmentResponse' {Maybe Assignment
assignment :: Maybe Assignment
$sel:assignment:GetAssignmentResponse' :: GetAssignmentResponse -> Maybe Assignment
assignment} -> Maybe Assignment
assignment) (\s :: GetAssignmentResponse
s@GetAssignmentResponse' {} Maybe Assignment
a -> GetAssignmentResponse
s {$sel:assignment:GetAssignmentResponse' :: Maybe Assignment
assignment = Maybe Assignment
a} :: GetAssignmentResponse)

-- | The HIT associated with this assignment. The response includes one HIT
-- element.
getAssignmentResponse_hit :: Lens.Lens' GetAssignmentResponse (Prelude.Maybe HIT)
getAssignmentResponse_hit :: Lens' GetAssignmentResponse (Maybe HIT)
getAssignmentResponse_hit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssignmentResponse' {Maybe HIT
hit :: Maybe HIT
$sel:hit:GetAssignmentResponse' :: GetAssignmentResponse -> Maybe HIT
hit} -> Maybe HIT
hit) (\s :: GetAssignmentResponse
s@GetAssignmentResponse' {} Maybe HIT
a -> GetAssignmentResponse
s {$sel:hit:GetAssignmentResponse' :: Maybe HIT
hit = Maybe HIT
a} :: GetAssignmentResponse)

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

instance Prelude.NFData GetAssignmentResponse where
  rnf :: GetAssignmentResponse -> ()
rnf GetAssignmentResponse' {Int
Maybe Assignment
Maybe HIT
httpStatus :: Int
hit :: Maybe HIT
assignment :: Maybe Assignment
$sel:httpStatus:GetAssignmentResponse' :: GetAssignmentResponse -> Int
$sel:hit:GetAssignmentResponse' :: GetAssignmentResponse -> Maybe HIT
$sel:assignment:GetAssignmentResponse' :: GetAssignmentResponse -> Maybe Assignment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Assignment
assignment
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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