{-# 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.SageMaker.DescribeCompilationJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a model compilation job.
--
-- To create a model compilation job, use CreateCompilationJob. To get
-- information about multiple model compilation jobs, use
-- ListCompilationJobs.
module Amazonka.SageMaker.DescribeCompilationJob
  ( -- * Creating a Request
    DescribeCompilationJob (..),
    newDescribeCompilationJob,

    -- * Request Lenses
    describeCompilationJob_compilationJobName,

    -- * Destructuring the Response
    DescribeCompilationJobResponse (..),
    newDescribeCompilationJobResponse,

    -- * Response Lenses
    describeCompilationJobResponse_compilationEndTime,
    describeCompilationJobResponse_compilationStartTime,
    describeCompilationJobResponse_inferenceImage,
    describeCompilationJobResponse_modelDigests,
    describeCompilationJobResponse_modelPackageVersionArn,
    describeCompilationJobResponse_vpcConfig,
    describeCompilationJobResponse_httpStatus,
    describeCompilationJobResponse_compilationJobName,
    describeCompilationJobResponse_compilationJobArn,
    describeCompilationJobResponse_compilationJobStatus,
    describeCompilationJobResponse_stoppingCondition,
    describeCompilationJobResponse_creationTime,
    describeCompilationJobResponse_lastModifiedTime,
    describeCompilationJobResponse_failureReason,
    describeCompilationJobResponse_modelArtifacts,
    describeCompilationJobResponse_roleArn,
    describeCompilationJobResponse_inputConfig,
    describeCompilationJobResponse_outputConfig,
  )
where

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
import Amazonka.SageMaker.Types

-- | /See:/ 'newDescribeCompilationJob' smart constructor.
data DescribeCompilationJob = DescribeCompilationJob'
  { -- | The name of the model compilation job that you want information about.
    DescribeCompilationJob -> Text
compilationJobName :: Prelude.Text
  }
  deriving (DescribeCompilationJob -> DescribeCompilationJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCompilationJob -> DescribeCompilationJob -> Bool
$c/= :: DescribeCompilationJob -> DescribeCompilationJob -> Bool
== :: DescribeCompilationJob -> DescribeCompilationJob -> Bool
$c== :: DescribeCompilationJob -> DescribeCompilationJob -> Bool
Prelude.Eq, ReadPrec [DescribeCompilationJob]
ReadPrec DescribeCompilationJob
Int -> ReadS DescribeCompilationJob
ReadS [DescribeCompilationJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCompilationJob]
$creadListPrec :: ReadPrec [DescribeCompilationJob]
readPrec :: ReadPrec DescribeCompilationJob
$creadPrec :: ReadPrec DescribeCompilationJob
readList :: ReadS [DescribeCompilationJob]
$creadList :: ReadS [DescribeCompilationJob]
readsPrec :: Int -> ReadS DescribeCompilationJob
$creadsPrec :: Int -> ReadS DescribeCompilationJob
Prelude.Read, Int -> DescribeCompilationJob -> ShowS
[DescribeCompilationJob] -> ShowS
DescribeCompilationJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCompilationJob] -> ShowS
$cshowList :: [DescribeCompilationJob] -> ShowS
show :: DescribeCompilationJob -> String
$cshow :: DescribeCompilationJob -> String
showsPrec :: Int -> DescribeCompilationJob -> ShowS
$cshowsPrec :: Int -> DescribeCompilationJob -> ShowS
Prelude.Show, forall x. Rep DescribeCompilationJob x -> DescribeCompilationJob
forall x. DescribeCompilationJob -> Rep DescribeCompilationJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeCompilationJob x -> DescribeCompilationJob
$cfrom :: forall x. DescribeCompilationJob -> Rep DescribeCompilationJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCompilationJob' 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:
--
-- 'compilationJobName', 'describeCompilationJob_compilationJobName' - The name of the model compilation job that you want information about.
newDescribeCompilationJob ::
  -- | 'compilationJobName'
  Prelude.Text ->
  DescribeCompilationJob
newDescribeCompilationJob :: Text -> DescribeCompilationJob
newDescribeCompilationJob Text
pCompilationJobName_ =
  DescribeCompilationJob'
    { $sel:compilationJobName:DescribeCompilationJob' :: Text
compilationJobName =
        Text
pCompilationJobName_
    }

-- | The name of the model compilation job that you want information about.
describeCompilationJob_compilationJobName :: Lens.Lens' DescribeCompilationJob Prelude.Text
describeCompilationJob_compilationJobName :: Lens' DescribeCompilationJob Text
describeCompilationJob_compilationJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJob' {Text
compilationJobName :: Text
$sel:compilationJobName:DescribeCompilationJob' :: DescribeCompilationJob -> Text
compilationJobName} -> Text
compilationJobName) (\s :: DescribeCompilationJob
s@DescribeCompilationJob' {} Text
a -> DescribeCompilationJob
s {$sel:compilationJobName:DescribeCompilationJob' :: Text
compilationJobName = Text
a} :: DescribeCompilationJob)

instance Core.AWSRequest DescribeCompilationJob where
  type
    AWSResponse DescribeCompilationJob =
      DescribeCompilationJobResponse
  request :: (Service -> Service)
-> DescribeCompilationJob -> Request DescribeCompilationJob
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 DescribeCompilationJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeCompilationJob)))
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 POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe ModelDigests
-> Maybe Text
-> Maybe NeoVpcConfig
-> Int
-> Text
-> Text
-> CompilationJobStatus
-> StoppingCondition
-> POSIX
-> POSIX
-> Text
-> ModelArtifacts
-> Text
-> InputConfig
-> OutputConfig
-> DescribeCompilationJobResponse
DescribeCompilationJobResponse'
            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
"CompilationEndTime")
            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
"CompilationStartTime")
            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
"InferenceImage")
            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
"ModelDigests")
            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
"ModelPackageVersionArn")
            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
"VpcConfig")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CompilationJobName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CompilationJobArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CompilationJobStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"StoppingCondition")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"LastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"ModelArtifacts")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"InputConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"OutputConfig")
      )

instance Prelude.Hashable DescribeCompilationJob where
  hashWithSalt :: Int -> DescribeCompilationJob -> Int
hashWithSalt Int
_salt DescribeCompilationJob' {Text
compilationJobName :: Text
$sel:compilationJobName:DescribeCompilationJob' :: DescribeCompilationJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
compilationJobName

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

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

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

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

-- | /See:/ 'newDescribeCompilationJobResponse' smart constructor.
data DescribeCompilationJobResponse = DescribeCompilationJobResponse'
  { -- | The time when the model compilation job on a compilation job instance
    -- ended. For a successful or stopped job, this is when the job\'s model
    -- artifacts have finished uploading. For a failed job, this is when Amazon
    -- SageMaker detected that the job failed.
    DescribeCompilationJobResponse -> Maybe POSIX
compilationEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time when the model compilation job started the @CompilationJob@
    -- instances.
    --
    -- You are billed for the time between this timestamp and the timestamp in
    -- the DescribeCompilationJobResponse$CompilationEndTime field. In Amazon
    -- CloudWatch Logs, the start time might be later than this time. That\'s
    -- because it takes time to download the compilation job, which depends on
    -- the size of the compilation job container.
    DescribeCompilationJobResponse -> Maybe POSIX
compilationStartTime :: Prelude.Maybe Data.POSIX,
    -- | The inference image to use when compiling a model. Specify an image only
    -- if the target device is a cloud instance.
    DescribeCompilationJobResponse -> Maybe Text
inferenceImage :: Prelude.Maybe Prelude.Text,
    -- | Provides a BLAKE2 hash value that identifies the compiled model
    -- artifacts in Amazon S3.
    DescribeCompilationJobResponse -> Maybe ModelDigests
modelDigests :: Prelude.Maybe ModelDigests,
    -- | The Amazon Resource Name (ARN) of the versioned model package that was
    -- provided to SageMaker Neo when you initiated a compilation job.
    DescribeCompilationJobResponse -> Maybe Text
modelPackageVersionArn :: Prelude.Maybe Prelude.Text,
    -- | A VpcConfig object that specifies the VPC that you want your compilation
    -- job to connect to. Control access to your models by configuring the VPC.
    -- For more information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/neo-vpc.html Protect Compilation Jobs by Using an Amazon Virtual Private Cloud>.
    DescribeCompilationJobResponse -> Maybe NeoVpcConfig
vpcConfig :: Prelude.Maybe NeoVpcConfig,
    -- | The response's http status code.
    DescribeCompilationJobResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the model compilation job.
    DescribeCompilationJobResponse -> Text
compilationJobName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the model compilation job.
    DescribeCompilationJobResponse -> Text
compilationJobArn :: Prelude.Text,
    -- | The status of the model compilation job.
    DescribeCompilationJobResponse -> CompilationJobStatus
compilationJobStatus :: CompilationJobStatus,
    -- | Specifies a limit to how long a model compilation job can run. When the
    -- job reaches the time limit, Amazon SageMaker ends the compilation job.
    -- Use this API to cap model training costs.
    DescribeCompilationJobResponse -> StoppingCondition
stoppingCondition :: StoppingCondition,
    -- | The time that the model compilation job was created.
    DescribeCompilationJobResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The time that the status of the model compilation job was last modified.
    DescribeCompilationJobResponse -> POSIX
lastModifiedTime :: Data.POSIX,
    -- | If a model compilation job failed, the reason it failed.
    DescribeCompilationJobResponse -> Text
failureReason :: Prelude.Text,
    -- | Information about the location in Amazon S3 that has been configured for
    -- storing the model artifacts used in the compilation job.
    DescribeCompilationJobResponse -> ModelArtifacts
modelArtifacts :: ModelArtifacts,
    -- | The Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker
    -- assumes to perform the model compilation job.
    DescribeCompilationJobResponse -> Text
roleArn :: Prelude.Text,
    -- | Information about the location in Amazon S3 of the input model
    -- artifacts, the name and shape of the expected data inputs, and the
    -- framework in which the model was trained.
    DescribeCompilationJobResponse -> InputConfig
inputConfig :: InputConfig,
    -- | Information about the output location for the compiled model and the
    -- target device that the model runs on.
    DescribeCompilationJobResponse -> OutputConfig
outputConfig :: OutputConfig
  }
  deriving (DescribeCompilationJobResponse
-> DescribeCompilationJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCompilationJobResponse
-> DescribeCompilationJobResponse -> Bool
$c/= :: DescribeCompilationJobResponse
-> DescribeCompilationJobResponse -> Bool
== :: DescribeCompilationJobResponse
-> DescribeCompilationJobResponse -> Bool
$c== :: DescribeCompilationJobResponse
-> DescribeCompilationJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCompilationJobResponse]
ReadPrec DescribeCompilationJobResponse
Int -> ReadS DescribeCompilationJobResponse
ReadS [DescribeCompilationJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCompilationJobResponse]
$creadListPrec :: ReadPrec [DescribeCompilationJobResponse]
readPrec :: ReadPrec DescribeCompilationJobResponse
$creadPrec :: ReadPrec DescribeCompilationJobResponse
readList :: ReadS [DescribeCompilationJobResponse]
$creadList :: ReadS [DescribeCompilationJobResponse]
readsPrec :: Int -> ReadS DescribeCompilationJobResponse
$creadsPrec :: Int -> ReadS DescribeCompilationJobResponse
Prelude.Read, Int -> DescribeCompilationJobResponse -> ShowS
[DescribeCompilationJobResponse] -> ShowS
DescribeCompilationJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCompilationJobResponse] -> ShowS
$cshowList :: [DescribeCompilationJobResponse] -> ShowS
show :: DescribeCompilationJobResponse -> String
$cshow :: DescribeCompilationJobResponse -> String
showsPrec :: Int -> DescribeCompilationJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeCompilationJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCompilationJobResponse x
-> DescribeCompilationJobResponse
forall x.
DescribeCompilationJobResponse
-> Rep DescribeCompilationJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCompilationJobResponse x
-> DescribeCompilationJobResponse
$cfrom :: forall x.
DescribeCompilationJobResponse
-> Rep DescribeCompilationJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCompilationJobResponse' 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:
--
-- 'compilationEndTime', 'describeCompilationJobResponse_compilationEndTime' - The time when the model compilation job on a compilation job instance
-- ended. For a successful or stopped job, this is when the job\'s model
-- artifacts have finished uploading. For a failed job, this is when Amazon
-- SageMaker detected that the job failed.
--
-- 'compilationStartTime', 'describeCompilationJobResponse_compilationStartTime' - The time when the model compilation job started the @CompilationJob@
-- instances.
--
-- You are billed for the time between this timestamp and the timestamp in
-- the DescribeCompilationJobResponse$CompilationEndTime field. In Amazon
-- CloudWatch Logs, the start time might be later than this time. That\'s
-- because it takes time to download the compilation job, which depends on
-- the size of the compilation job container.
--
-- 'inferenceImage', 'describeCompilationJobResponse_inferenceImage' - The inference image to use when compiling a model. Specify an image only
-- if the target device is a cloud instance.
--
-- 'modelDigests', 'describeCompilationJobResponse_modelDigests' - Provides a BLAKE2 hash value that identifies the compiled model
-- artifacts in Amazon S3.
--
-- 'modelPackageVersionArn', 'describeCompilationJobResponse_modelPackageVersionArn' - The Amazon Resource Name (ARN) of the versioned model package that was
-- provided to SageMaker Neo when you initiated a compilation job.
--
-- 'vpcConfig', 'describeCompilationJobResponse_vpcConfig' - A VpcConfig object that specifies the VPC that you want your compilation
-- job to connect to. Control access to your models by configuring the VPC.
-- For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/neo-vpc.html Protect Compilation Jobs by Using an Amazon Virtual Private Cloud>.
--
-- 'httpStatus', 'describeCompilationJobResponse_httpStatus' - The response's http status code.
--
-- 'compilationJobName', 'describeCompilationJobResponse_compilationJobName' - The name of the model compilation job.
--
-- 'compilationJobArn', 'describeCompilationJobResponse_compilationJobArn' - The Amazon Resource Name (ARN) of the model compilation job.
--
-- 'compilationJobStatus', 'describeCompilationJobResponse_compilationJobStatus' - The status of the model compilation job.
--
-- 'stoppingCondition', 'describeCompilationJobResponse_stoppingCondition' - Specifies a limit to how long a model compilation job can run. When the
-- job reaches the time limit, Amazon SageMaker ends the compilation job.
-- Use this API to cap model training costs.
--
-- 'creationTime', 'describeCompilationJobResponse_creationTime' - The time that the model compilation job was created.
--
-- 'lastModifiedTime', 'describeCompilationJobResponse_lastModifiedTime' - The time that the status of the model compilation job was last modified.
--
-- 'failureReason', 'describeCompilationJobResponse_failureReason' - If a model compilation job failed, the reason it failed.
--
-- 'modelArtifacts', 'describeCompilationJobResponse_modelArtifacts' - Information about the location in Amazon S3 that has been configured for
-- storing the model artifacts used in the compilation job.
--
-- 'roleArn', 'describeCompilationJobResponse_roleArn' - The Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker
-- assumes to perform the model compilation job.
--
-- 'inputConfig', 'describeCompilationJobResponse_inputConfig' - Information about the location in Amazon S3 of the input model
-- artifacts, the name and shape of the expected data inputs, and the
-- framework in which the model was trained.
--
-- 'outputConfig', 'describeCompilationJobResponse_outputConfig' - Information about the output location for the compiled model and the
-- target device that the model runs on.
newDescribeCompilationJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'compilationJobName'
  Prelude.Text ->
  -- | 'compilationJobArn'
  Prelude.Text ->
  -- | 'compilationJobStatus'
  CompilationJobStatus ->
  -- | 'stoppingCondition'
  StoppingCondition ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  -- | 'failureReason'
  Prelude.Text ->
  -- | 'modelArtifacts'
  ModelArtifacts ->
  -- | 'roleArn'
  Prelude.Text ->
  -- | 'inputConfig'
  InputConfig ->
  -- | 'outputConfig'
  OutputConfig ->
  DescribeCompilationJobResponse
newDescribeCompilationJobResponse :: Int
-> Text
-> Text
-> CompilationJobStatus
-> StoppingCondition
-> UTCTime
-> UTCTime
-> Text
-> ModelArtifacts
-> Text
-> InputConfig
-> OutputConfig
-> DescribeCompilationJobResponse
newDescribeCompilationJobResponse
  Int
pHttpStatus_
  Text
pCompilationJobName_
  Text
pCompilationJobArn_
  CompilationJobStatus
pCompilationJobStatus_
  StoppingCondition
pStoppingCondition_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_
  Text
pFailureReason_
  ModelArtifacts
pModelArtifacts_
  Text
pRoleArn_
  InputConfig
pInputConfig_
  OutputConfig
pOutputConfig_ =
    DescribeCompilationJobResponse'
      { $sel:compilationEndTime:DescribeCompilationJobResponse' :: Maybe POSIX
compilationEndTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:compilationStartTime:DescribeCompilationJobResponse' :: Maybe POSIX
compilationStartTime = forall a. Maybe a
Prelude.Nothing,
        $sel:inferenceImage:DescribeCompilationJobResponse' :: Maybe Text
inferenceImage = forall a. Maybe a
Prelude.Nothing,
        $sel:modelDigests:DescribeCompilationJobResponse' :: Maybe ModelDigests
modelDigests = forall a. Maybe a
Prelude.Nothing,
        $sel:modelPackageVersionArn:DescribeCompilationJobResponse' :: Maybe Text
modelPackageVersionArn = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcConfig:DescribeCompilationJobResponse' :: Maybe NeoVpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeCompilationJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:compilationJobName:DescribeCompilationJobResponse' :: Text
compilationJobName = Text
pCompilationJobName_,
        $sel:compilationJobArn:DescribeCompilationJobResponse' :: Text
compilationJobArn = Text
pCompilationJobArn_,
        $sel:compilationJobStatus:DescribeCompilationJobResponse' :: CompilationJobStatus
compilationJobStatus =
          CompilationJobStatus
pCompilationJobStatus_,
        $sel:stoppingCondition:DescribeCompilationJobResponse' :: StoppingCondition
stoppingCondition = StoppingCondition
pStoppingCondition_,
        $sel:creationTime:DescribeCompilationJobResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:DescribeCompilationJobResponse' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_,
        $sel:failureReason:DescribeCompilationJobResponse' :: Text
failureReason = Text
pFailureReason_,
        $sel:modelArtifacts:DescribeCompilationJobResponse' :: ModelArtifacts
modelArtifacts = ModelArtifacts
pModelArtifacts_,
        $sel:roleArn:DescribeCompilationJobResponse' :: Text
roleArn = Text
pRoleArn_,
        $sel:inputConfig:DescribeCompilationJobResponse' :: InputConfig
inputConfig = InputConfig
pInputConfig_,
        $sel:outputConfig:DescribeCompilationJobResponse' :: OutputConfig
outputConfig = OutputConfig
pOutputConfig_
      }

-- | The time when the model compilation job on a compilation job instance
-- ended. For a successful or stopped job, this is when the job\'s model
-- artifacts have finished uploading. For a failed job, this is when Amazon
-- SageMaker detected that the job failed.
describeCompilationJobResponse_compilationEndTime :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe Prelude.UTCTime)
describeCompilationJobResponse_compilationEndTime :: Lens' DescribeCompilationJobResponse (Maybe UTCTime)
describeCompilationJobResponse_compilationEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe POSIX
compilationEndTime :: Maybe POSIX
$sel:compilationEndTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe POSIX
compilationEndTime} -> Maybe POSIX
compilationEndTime) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe POSIX
a -> DescribeCompilationJobResponse
s {$sel:compilationEndTime:DescribeCompilationJobResponse' :: Maybe POSIX
compilationEndTime = Maybe POSIX
a} :: DescribeCompilationJobResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time when the model compilation job started the @CompilationJob@
-- instances.
--
-- You are billed for the time between this timestamp and the timestamp in
-- the DescribeCompilationJobResponse$CompilationEndTime field. In Amazon
-- CloudWatch Logs, the start time might be later than this time. That\'s
-- because it takes time to download the compilation job, which depends on
-- the size of the compilation job container.
describeCompilationJobResponse_compilationStartTime :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe Prelude.UTCTime)
describeCompilationJobResponse_compilationStartTime :: Lens' DescribeCompilationJobResponse (Maybe UTCTime)
describeCompilationJobResponse_compilationStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe POSIX
compilationStartTime :: Maybe POSIX
$sel:compilationStartTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe POSIX
compilationStartTime} -> Maybe POSIX
compilationStartTime) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe POSIX
a -> DescribeCompilationJobResponse
s {$sel:compilationStartTime:DescribeCompilationJobResponse' :: Maybe POSIX
compilationStartTime = Maybe POSIX
a} :: DescribeCompilationJobResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The inference image to use when compiling a model. Specify an image only
-- if the target device is a cloud instance.
describeCompilationJobResponse_inferenceImage :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe Prelude.Text)
describeCompilationJobResponse_inferenceImage :: Lens' DescribeCompilationJobResponse (Maybe Text)
describeCompilationJobResponse_inferenceImage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe Text
inferenceImage :: Maybe Text
$sel:inferenceImage:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe Text
inferenceImage} -> Maybe Text
inferenceImage) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe Text
a -> DescribeCompilationJobResponse
s {$sel:inferenceImage:DescribeCompilationJobResponse' :: Maybe Text
inferenceImage = Maybe Text
a} :: DescribeCompilationJobResponse)

-- | Provides a BLAKE2 hash value that identifies the compiled model
-- artifacts in Amazon S3.
describeCompilationJobResponse_modelDigests :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe ModelDigests)
describeCompilationJobResponse_modelDigests :: Lens' DescribeCompilationJobResponse (Maybe ModelDigests)
describeCompilationJobResponse_modelDigests = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe ModelDigests
modelDigests :: Maybe ModelDigests
$sel:modelDigests:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe ModelDigests
modelDigests} -> Maybe ModelDigests
modelDigests) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe ModelDigests
a -> DescribeCompilationJobResponse
s {$sel:modelDigests:DescribeCompilationJobResponse' :: Maybe ModelDigests
modelDigests = Maybe ModelDigests
a} :: DescribeCompilationJobResponse)

-- | The Amazon Resource Name (ARN) of the versioned model package that was
-- provided to SageMaker Neo when you initiated a compilation job.
describeCompilationJobResponse_modelPackageVersionArn :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe Prelude.Text)
describeCompilationJobResponse_modelPackageVersionArn :: Lens' DescribeCompilationJobResponse (Maybe Text)
describeCompilationJobResponse_modelPackageVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe Text
modelPackageVersionArn :: Maybe Text
$sel:modelPackageVersionArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe Text
modelPackageVersionArn} -> Maybe Text
modelPackageVersionArn) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe Text
a -> DescribeCompilationJobResponse
s {$sel:modelPackageVersionArn:DescribeCompilationJobResponse' :: Maybe Text
modelPackageVersionArn = Maybe Text
a} :: DescribeCompilationJobResponse)

-- | A VpcConfig object that specifies the VPC that you want your compilation
-- job to connect to. Control access to your models by configuring the VPC.
-- For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/neo-vpc.html Protect Compilation Jobs by Using an Amazon Virtual Private Cloud>.
describeCompilationJobResponse_vpcConfig :: Lens.Lens' DescribeCompilationJobResponse (Prelude.Maybe NeoVpcConfig)
describeCompilationJobResponse_vpcConfig :: Lens' DescribeCompilationJobResponse (Maybe NeoVpcConfig)
describeCompilationJobResponse_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Maybe NeoVpcConfig
vpcConfig :: Maybe NeoVpcConfig
$sel:vpcConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe NeoVpcConfig
vpcConfig} -> Maybe NeoVpcConfig
vpcConfig) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Maybe NeoVpcConfig
a -> DescribeCompilationJobResponse
s {$sel:vpcConfig:DescribeCompilationJobResponse' :: Maybe NeoVpcConfig
vpcConfig = Maybe NeoVpcConfig
a} :: DescribeCompilationJobResponse)

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

-- | The name of the model compilation job.
describeCompilationJobResponse_compilationJobName :: Lens.Lens' DescribeCompilationJobResponse Prelude.Text
describeCompilationJobResponse_compilationJobName :: Lens' DescribeCompilationJobResponse Text
describeCompilationJobResponse_compilationJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Text
compilationJobName :: Text
$sel:compilationJobName:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
compilationJobName} -> Text
compilationJobName) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Text
a -> DescribeCompilationJobResponse
s {$sel:compilationJobName:DescribeCompilationJobResponse' :: Text
compilationJobName = Text
a} :: DescribeCompilationJobResponse)

-- | The Amazon Resource Name (ARN) of the model compilation job.
describeCompilationJobResponse_compilationJobArn :: Lens.Lens' DescribeCompilationJobResponse Prelude.Text
describeCompilationJobResponse_compilationJobArn :: Lens' DescribeCompilationJobResponse Text
describeCompilationJobResponse_compilationJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Text
compilationJobArn :: Text
$sel:compilationJobArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
compilationJobArn} -> Text
compilationJobArn) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Text
a -> DescribeCompilationJobResponse
s {$sel:compilationJobArn:DescribeCompilationJobResponse' :: Text
compilationJobArn = Text
a} :: DescribeCompilationJobResponse)

-- | The status of the model compilation job.
describeCompilationJobResponse_compilationJobStatus :: Lens.Lens' DescribeCompilationJobResponse CompilationJobStatus
describeCompilationJobResponse_compilationJobStatus :: Lens' DescribeCompilationJobResponse CompilationJobStatus
describeCompilationJobResponse_compilationJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {CompilationJobStatus
compilationJobStatus :: CompilationJobStatus
$sel:compilationJobStatus:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> CompilationJobStatus
compilationJobStatus} -> CompilationJobStatus
compilationJobStatus) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} CompilationJobStatus
a -> DescribeCompilationJobResponse
s {$sel:compilationJobStatus:DescribeCompilationJobResponse' :: CompilationJobStatus
compilationJobStatus = CompilationJobStatus
a} :: DescribeCompilationJobResponse)

-- | Specifies a limit to how long a model compilation job can run. When the
-- job reaches the time limit, Amazon SageMaker ends the compilation job.
-- Use this API to cap model training costs.
describeCompilationJobResponse_stoppingCondition :: Lens.Lens' DescribeCompilationJobResponse StoppingCondition
describeCompilationJobResponse_stoppingCondition :: Lens' DescribeCompilationJobResponse StoppingCondition
describeCompilationJobResponse_stoppingCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {StoppingCondition
stoppingCondition :: StoppingCondition
$sel:stoppingCondition:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> StoppingCondition
stoppingCondition} -> StoppingCondition
stoppingCondition) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} StoppingCondition
a -> DescribeCompilationJobResponse
s {$sel:stoppingCondition:DescribeCompilationJobResponse' :: StoppingCondition
stoppingCondition = StoppingCondition
a} :: DescribeCompilationJobResponse)

-- | The time that the model compilation job was created.
describeCompilationJobResponse_creationTime :: Lens.Lens' DescribeCompilationJobResponse Prelude.UTCTime
describeCompilationJobResponse_creationTime :: Lens' DescribeCompilationJobResponse UTCTime
describeCompilationJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} POSIX
a -> DescribeCompilationJobResponse
s {$sel:creationTime:DescribeCompilationJobResponse' :: POSIX
creationTime = POSIX
a} :: DescribeCompilationJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time that the status of the model compilation job was last modified.
describeCompilationJobResponse_lastModifiedTime :: Lens.Lens' DescribeCompilationJobResponse Prelude.UTCTime
describeCompilationJobResponse_lastModifiedTime :: Lens' DescribeCompilationJobResponse UTCTime
describeCompilationJobResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} POSIX
a -> DescribeCompilationJobResponse
s {$sel:lastModifiedTime:DescribeCompilationJobResponse' :: POSIX
lastModifiedTime = POSIX
a} :: DescribeCompilationJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | If a model compilation job failed, the reason it failed.
describeCompilationJobResponse_failureReason :: Lens.Lens' DescribeCompilationJobResponse Prelude.Text
describeCompilationJobResponse_failureReason :: Lens' DescribeCompilationJobResponse Text
describeCompilationJobResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Text
failureReason :: Text
$sel:failureReason:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
failureReason} -> Text
failureReason) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Text
a -> DescribeCompilationJobResponse
s {$sel:failureReason:DescribeCompilationJobResponse' :: Text
failureReason = Text
a} :: DescribeCompilationJobResponse)

-- | Information about the location in Amazon S3 that has been configured for
-- storing the model artifacts used in the compilation job.
describeCompilationJobResponse_modelArtifacts :: Lens.Lens' DescribeCompilationJobResponse ModelArtifacts
describeCompilationJobResponse_modelArtifacts :: Lens' DescribeCompilationJobResponse ModelArtifacts
describeCompilationJobResponse_modelArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {ModelArtifacts
modelArtifacts :: ModelArtifacts
$sel:modelArtifacts:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> ModelArtifacts
modelArtifacts} -> ModelArtifacts
modelArtifacts) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} ModelArtifacts
a -> DescribeCompilationJobResponse
s {$sel:modelArtifacts:DescribeCompilationJobResponse' :: ModelArtifacts
modelArtifacts = ModelArtifacts
a} :: DescribeCompilationJobResponse)

-- | The Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker
-- assumes to perform the model compilation job.
describeCompilationJobResponse_roleArn :: Lens.Lens' DescribeCompilationJobResponse Prelude.Text
describeCompilationJobResponse_roleArn :: Lens' DescribeCompilationJobResponse Text
describeCompilationJobResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {Text
roleArn :: Text
$sel:roleArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
roleArn} -> Text
roleArn) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} Text
a -> DescribeCompilationJobResponse
s {$sel:roleArn:DescribeCompilationJobResponse' :: Text
roleArn = Text
a} :: DescribeCompilationJobResponse)

-- | Information about the location in Amazon S3 of the input model
-- artifacts, the name and shape of the expected data inputs, and the
-- framework in which the model was trained.
describeCompilationJobResponse_inputConfig :: Lens.Lens' DescribeCompilationJobResponse InputConfig
describeCompilationJobResponse_inputConfig :: Lens' DescribeCompilationJobResponse InputConfig
describeCompilationJobResponse_inputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {InputConfig
inputConfig :: InputConfig
$sel:inputConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> InputConfig
inputConfig} -> InputConfig
inputConfig) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} InputConfig
a -> DescribeCompilationJobResponse
s {$sel:inputConfig:DescribeCompilationJobResponse' :: InputConfig
inputConfig = InputConfig
a} :: DescribeCompilationJobResponse)

-- | Information about the output location for the compiled model and the
-- target device that the model runs on.
describeCompilationJobResponse_outputConfig :: Lens.Lens' DescribeCompilationJobResponse OutputConfig
describeCompilationJobResponse_outputConfig :: Lens' DescribeCompilationJobResponse OutputConfig
describeCompilationJobResponse_outputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCompilationJobResponse' {OutputConfig
outputConfig :: OutputConfig
$sel:outputConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> OutputConfig
outputConfig} -> OutputConfig
outputConfig) (\s :: DescribeCompilationJobResponse
s@DescribeCompilationJobResponse' {} OutputConfig
a -> DescribeCompilationJobResponse
s {$sel:outputConfig:DescribeCompilationJobResponse' :: OutputConfig
outputConfig = OutputConfig
a} :: DescribeCompilationJobResponse)

instance
  Prelude.NFData
    DescribeCompilationJobResponse
  where
  rnf :: DescribeCompilationJobResponse -> ()
rnf DescribeCompilationJobResponse' {Int
Maybe Text
Maybe POSIX
Maybe ModelDigests
Maybe NeoVpcConfig
Text
POSIX
CompilationJobStatus
InputConfig
ModelArtifacts
StoppingCondition
OutputConfig
outputConfig :: OutputConfig
inputConfig :: InputConfig
roleArn :: Text
modelArtifacts :: ModelArtifacts
failureReason :: Text
lastModifiedTime :: POSIX
creationTime :: POSIX
stoppingCondition :: StoppingCondition
compilationJobStatus :: CompilationJobStatus
compilationJobArn :: Text
compilationJobName :: Text
httpStatus :: Int
vpcConfig :: Maybe NeoVpcConfig
modelPackageVersionArn :: Maybe Text
modelDigests :: Maybe ModelDigests
inferenceImage :: Maybe Text
compilationStartTime :: Maybe POSIX
compilationEndTime :: Maybe POSIX
$sel:outputConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> OutputConfig
$sel:inputConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> InputConfig
$sel:roleArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
$sel:modelArtifacts:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> ModelArtifacts
$sel:failureReason:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
$sel:lastModifiedTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> POSIX
$sel:creationTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> POSIX
$sel:stoppingCondition:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> StoppingCondition
$sel:compilationJobStatus:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> CompilationJobStatus
$sel:compilationJobArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
$sel:compilationJobName:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Text
$sel:httpStatus:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Int
$sel:vpcConfig:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe NeoVpcConfig
$sel:modelPackageVersionArn:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe Text
$sel:modelDigests:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe ModelDigests
$sel:inferenceImage:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe Text
$sel:compilationStartTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe POSIX
$sel:compilationEndTime:DescribeCompilationJobResponse' :: DescribeCompilationJobResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
compilationEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
compilationStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
inferenceImage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelDigests
modelDigests
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelPackageVersionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NeoVpcConfig
vpcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
compilationJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
compilationJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CompilationJobStatus
compilationJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf StoppingCondition
stoppingCondition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ModelArtifacts
modelArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf InputConfig
inputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf OutputConfig
outputConfig