{-# 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.ComprehendMedical.DescribeSNOMEDCTInferenceJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the properties associated with an InferSNOMEDCT job. Use this
-- operation to get the status of an inference job.
module Amazonka.ComprehendMedical.DescribeSNOMEDCTInferenceJob
  ( -- * Creating a Request
    DescribeSNOMEDCTInferenceJob (..),
    newDescribeSNOMEDCTInferenceJob,

    -- * Request Lenses
    describeSNOMEDCTInferenceJob_jobId,

    -- * Destructuring the Response
    DescribeSNOMEDCTInferenceJobResponse (..),
    newDescribeSNOMEDCTInferenceJobResponse,

    -- * Response Lenses
    describeSNOMEDCTInferenceJobResponse_comprehendMedicalAsyncJobProperties,
    describeSNOMEDCTInferenceJobResponse_httpStatus,
  )
where

import Amazonka.ComprehendMedical.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeSNOMEDCTInferenceJob' smart constructor.
data DescribeSNOMEDCTInferenceJob = DescribeSNOMEDCTInferenceJob'
  { -- | The identifier that Amazon Comprehend Medical generated for the job. The
    -- StartSNOMEDCTInferenceJob operation returns this identifier in its
    -- response.
    DescribeSNOMEDCTInferenceJob -> Text
jobId :: Prelude.Text
  }
  deriving (DescribeSNOMEDCTInferenceJob
-> DescribeSNOMEDCTInferenceJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSNOMEDCTInferenceJob
-> DescribeSNOMEDCTInferenceJob -> Bool
$c/= :: DescribeSNOMEDCTInferenceJob
-> DescribeSNOMEDCTInferenceJob -> Bool
== :: DescribeSNOMEDCTInferenceJob
-> DescribeSNOMEDCTInferenceJob -> Bool
$c== :: DescribeSNOMEDCTInferenceJob
-> DescribeSNOMEDCTInferenceJob -> Bool
Prelude.Eq, ReadPrec [DescribeSNOMEDCTInferenceJob]
ReadPrec DescribeSNOMEDCTInferenceJob
Int -> ReadS DescribeSNOMEDCTInferenceJob
ReadS [DescribeSNOMEDCTInferenceJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSNOMEDCTInferenceJob]
$creadListPrec :: ReadPrec [DescribeSNOMEDCTInferenceJob]
readPrec :: ReadPrec DescribeSNOMEDCTInferenceJob
$creadPrec :: ReadPrec DescribeSNOMEDCTInferenceJob
readList :: ReadS [DescribeSNOMEDCTInferenceJob]
$creadList :: ReadS [DescribeSNOMEDCTInferenceJob]
readsPrec :: Int -> ReadS DescribeSNOMEDCTInferenceJob
$creadsPrec :: Int -> ReadS DescribeSNOMEDCTInferenceJob
Prelude.Read, Int -> DescribeSNOMEDCTInferenceJob -> ShowS
[DescribeSNOMEDCTInferenceJob] -> ShowS
DescribeSNOMEDCTInferenceJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSNOMEDCTInferenceJob] -> ShowS
$cshowList :: [DescribeSNOMEDCTInferenceJob] -> ShowS
show :: DescribeSNOMEDCTInferenceJob -> String
$cshow :: DescribeSNOMEDCTInferenceJob -> String
showsPrec :: Int -> DescribeSNOMEDCTInferenceJob -> ShowS
$cshowsPrec :: Int -> DescribeSNOMEDCTInferenceJob -> ShowS
Prelude.Show, forall x.
Rep DescribeSNOMEDCTInferenceJob x -> DescribeSNOMEDCTInferenceJob
forall x.
DescribeSNOMEDCTInferenceJob -> Rep DescribeSNOMEDCTInferenceJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSNOMEDCTInferenceJob x -> DescribeSNOMEDCTInferenceJob
$cfrom :: forall x.
DescribeSNOMEDCTInferenceJob -> Rep DescribeSNOMEDCTInferenceJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSNOMEDCTInferenceJob' 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:
--
-- 'jobId', 'describeSNOMEDCTInferenceJob_jobId' - The identifier that Amazon Comprehend Medical generated for the job. The
-- StartSNOMEDCTInferenceJob operation returns this identifier in its
-- response.
newDescribeSNOMEDCTInferenceJob ::
  -- | 'jobId'
  Prelude.Text ->
  DescribeSNOMEDCTInferenceJob
newDescribeSNOMEDCTInferenceJob :: Text -> DescribeSNOMEDCTInferenceJob
newDescribeSNOMEDCTInferenceJob Text
pJobId_ =
  DescribeSNOMEDCTInferenceJob' {$sel:jobId:DescribeSNOMEDCTInferenceJob' :: Text
jobId = Text
pJobId_}

-- | The identifier that Amazon Comprehend Medical generated for the job. The
-- StartSNOMEDCTInferenceJob operation returns this identifier in its
-- response.
describeSNOMEDCTInferenceJob_jobId :: Lens.Lens' DescribeSNOMEDCTInferenceJob Prelude.Text
describeSNOMEDCTInferenceJob_jobId :: Lens' DescribeSNOMEDCTInferenceJob Text
describeSNOMEDCTInferenceJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSNOMEDCTInferenceJob' {Text
jobId :: Text
$sel:jobId:DescribeSNOMEDCTInferenceJob' :: DescribeSNOMEDCTInferenceJob -> Text
jobId} -> Text
jobId) (\s :: DescribeSNOMEDCTInferenceJob
s@DescribeSNOMEDCTInferenceJob' {} Text
a -> DescribeSNOMEDCTInferenceJob
s {$sel:jobId:DescribeSNOMEDCTInferenceJob' :: Text
jobId = Text
a} :: DescribeSNOMEDCTInferenceJob)

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

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

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

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

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

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

-- |
-- Create a value of 'DescribeSNOMEDCTInferenceJobResponse' 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:
--
-- 'comprehendMedicalAsyncJobProperties', 'describeSNOMEDCTInferenceJobResponse_comprehendMedicalAsyncJobProperties' - Undocumented member.
--
-- 'httpStatus', 'describeSNOMEDCTInferenceJobResponse_httpStatus' - The response's http status code.
newDescribeSNOMEDCTInferenceJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSNOMEDCTInferenceJobResponse
newDescribeSNOMEDCTInferenceJobResponse :: Int -> DescribeSNOMEDCTInferenceJobResponse
newDescribeSNOMEDCTInferenceJobResponse Int
pHttpStatus_ =
  DescribeSNOMEDCTInferenceJobResponse'
    { $sel:comprehendMedicalAsyncJobProperties:DescribeSNOMEDCTInferenceJobResponse' :: Maybe ComprehendMedicalAsyncJobProperties
comprehendMedicalAsyncJobProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSNOMEDCTInferenceJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
describeSNOMEDCTInferenceJobResponse_comprehendMedicalAsyncJobProperties :: Lens.Lens' DescribeSNOMEDCTInferenceJobResponse (Prelude.Maybe ComprehendMedicalAsyncJobProperties)
describeSNOMEDCTInferenceJobResponse_comprehendMedicalAsyncJobProperties :: Lens'
  DescribeSNOMEDCTInferenceJobResponse
  (Maybe ComprehendMedicalAsyncJobProperties)
describeSNOMEDCTInferenceJobResponse_comprehendMedicalAsyncJobProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSNOMEDCTInferenceJobResponse' {Maybe ComprehendMedicalAsyncJobProperties
comprehendMedicalAsyncJobProperties :: Maybe ComprehendMedicalAsyncJobProperties
$sel:comprehendMedicalAsyncJobProperties:DescribeSNOMEDCTInferenceJobResponse' :: DescribeSNOMEDCTInferenceJobResponse
-> Maybe ComprehendMedicalAsyncJobProperties
comprehendMedicalAsyncJobProperties} -> Maybe ComprehendMedicalAsyncJobProperties
comprehendMedicalAsyncJobProperties) (\s :: DescribeSNOMEDCTInferenceJobResponse
s@DescribeSNOMEDCTInferenceJobResponse' {} Maybe ComprehendMedicalAsyncJobProperties
a -> DescribeSNOMEDCTInferenceJobResponse
s {$sel:comprehendMedicalAsyncJobProperties:DescribeSNOMEDCTInferenceJobResponse' :: Maybe ComprehendMedicalAsyncJobProperties
comprehendMedicalAsyncJobProperties = Maybe ComprehendMedicalAsyncJobProperties
a} :: DescribeSNOMEDCTInferenceJobResponse)

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

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