{-# 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.DescribeModelPackage
-- 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 a description of the specified model package, which is used to
-- create SageMaker models or list them on Amazon Web Services Marketplace.
--
-- To create models in SageMaker, buyers can subscribe to model packages
-- listed on Amazon Web Services Marketplace.
module Amazonka.SageMaker.DescribeModelPackage
  ( -- * Creating a Request
    DescribeModelPackage (..),
    newDescribeModelPackage,

    -- * Request Lenses
    describeModelPackage_modelPackageName,

    -- * Destructuring the Response
    DescribeModelPackageResponse (..),
    newDescribeModelPackageResponse,

    -- * Response Lenses
    describeModelPackageResponse_additionalInferenceSpecifications,
    describeModelPackageResponse_approvalDescription,
    describeModelPackageResponse_certifyForMarketplace,
    describeModelPackageResponse_createdBy,
    describeModelPackageResponse_customerMetadataProperties,
    describeModelPackageResponse_domain,
    describeModelPackageResponse_driftCheckBaselines,
    describeModelPackageResponse_inferenceSpecification,
    describeModelPackageResponse_lastModifiedBy,
    describeModelPackageResponse_lastModifiedTime,
    describeModelPackageResponse_metadataProperties,
    describeModelPackageResponse_modelApprovalStatus,
    describeModelPackageResponse_modelMetrics,
    describeModelPackageResponse_modelPackageDescription,
    describeModelPackageResponse_modelPackageGroupName,
    describeModelPackageResponse_modelPackageVersion,
    describeModelPackageResponse_samplePayloadUrl,
    describeModelPackageResponse_sourceAlgorithmSpecification,
    describeModelPackageResponse_task,
    describeModelPackageResponse_validationSpecification,
    describeModelPackageResponse_httpStatus,
    describeModelPackageResponse_modelPackageName,
    describeModelPackageResponse_modelPackageArn,
    describeModelPackageResponse_creationTime,
    describeModelPackageResponse_modelPackageStatus,
    describeModelPackageResponse_modelPackageStatusDetails,
  )
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:/ 'newDescribeModelPackage' smart constructor.
data DescribeModelPackage = DescribeModelPackage'
  { -- | The name or Amazon Resource Name (ARN) of the model package to describe.
    --
    -- When you specify a name, the name must have 1 to 63 characters. Valid
    -- characters are a-z, A-Z, 0-9, and - (hyphen).
    DescribeModelPackage -> Text
modelPackageName :: Prelude.Text
  }
  deriving (DescribeModelPackage -> DescribeModelPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeModelPackage -> DescribeModelPackage -> Bool
$c/= :: DescribeModelPackage -> DescribeModelPackage -> Bool
== :: DescribeModelPackage -> DescribeModelPackage -> Bool
$c== :: DescribeModelPackage -> DescribeModelPackage -> Bool
Prelude.Eq, ReadPrec [DescribeModelPackage]
ReadPrec DescribeModelPackage
Int -> ReadS DescribeModelPackage
ReadS [DescribeModelPackage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeModelPackage]
$creadListPrec :: ReadPrec [DescribeModelPackage]
readPrec :: ReadPrec DescribeModelPackage
$creadPrec :: ReadPrec DescribeModelPackage
readList :: ReadS [DescribeModelPackage]
$creadList :: ReadS [DescribeModelPackage]
readsPrec :: Int -> ReadS DescribeModelPackage
$creadsPrec :: Int -> ReadS DescribeModelPackage
Prelude.Read, Int -> DescribeModelPackage -> ShowS
[DescribeModelPackage] -> ShowS
DescribeModelPackage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeModelPackage] -> ShowS
$cshowList :: [DescribeModelPackage] -> ShowS
show :: DescribeModelPackage -> String
$cshow :: DescribeModelPackage -> String
showsPrec :: Int -> DescribeModelPackage -> ShowS
$cshowsPrec :: Int -> DescribeModelPackage -> ShowS
Prelude.Show, forall x. Rep DescribeModelPackage x -> DescribeModelPackage
forall x. DescribeModelPackage -> Rep DescribeModelPackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeModelPackage x -> DescribeModelPackage
$cfrom :: forall x. DescribeModelPackage -> Rep DescribeModelPackage x
Prelude.Generic)

-- |
-- Create a value of 'DescribeModelPackage' 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:
--
-- 'modelPackageName', 'describeModelPackage_modelPackageName' - The name or Amazon Resource Name (ARN) of the model package to describe.
--
-- When you specify a name, the name must have 1 to 63 characters. Valid
-- characters are a-z, A-Z, 0-9, and - (hyphen).
newDescribeModelPackage ::
  -- | 'modelPackageName'
  Prelude.Text ->
  DescribeModelPackage
newDescribeModelPackage :: Text -> DescribeModelPackage
newDescribeModelPackage Text
pModelPackageName_ =
  DescribeModelPackage'
    { $sel:modelPackageName:DescribeModelPackage' :: Text
modelPackageName =
        Text
pModelPackageName_
    }

-- | The name or Amazon Resource Name (ARN) of the model package to describe.
--
-- When you specify a name, the name must have 1 to 63 characters. Valid
-- characters are a-z, A-Z, 0-9, and - (hyphen).
describeModelPackage_modelPackageName :: Lens.Lens' DescribeModelPackage Prelude.Text
describeModelPackage_modelPackageName :: Lens' DescribeModelPackage Text
describeModelPackage_modelPackageName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackage' {Text
modelPackageName :: Text
$sel:modelPackageName:DescribeModelPackage' :: DescribeModelPackage -> Text
modelPackageName} -> Text
modelPackageName) (\s :: DescribeModelPackage
s@DescribeModelPackage' {} Text
a -> DescribeModelPackage
s {$sel:modelPackageName:DescribeModelPackage' :: Text
modelPackageName = Text
a} :: DescribeModelPackage)

instance Core.AWSRequest DescribeModelPackage where
  type
    AWSResponse DescribeModelPackage =
      DescribeModelPackageResponse
  request :: (Service -> Service)
-> DescribeModelPackage -> Request DescribeModelPackage
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 DescribeModelPackage
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeModelPackage)))
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 (NonEmpty AdditionalInferenceSpecificationDefinition)
-> Maybe Text
-> Maybe Bool
-> Maybe UserContext
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe DriftCheckBaselines
-> Maybe InferenceSpecification
-> Maybe UserContext
-> Maybe POSIX
-> Maybe MetadataProperties
-> Maybe ModelApprovalStatus
-> Maybe ModelMetrics
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe SourceAlgorithmSpecification
-> Maybe Text
-> Maybe ModelPackageValidationSpecification
-> Int
-> Text
-> Text
-> POSIX
-> ModelPackageStatus
-> ModelPackageStatusDetails
-> DescribeModelPackageResponse
DescribeModelPackageResponse'
            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
"AdditionalInferenceSpecifications")
            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
"ApprovalDescription")
            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
"CertifyForMarketplace")
            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
"CreatedBy")
            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
"CustomerMetadataProperties"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Domain")
            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
"DriftCheckBaselines")
            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
"InferenceSpecification")
            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
"LastModifiedBy")
            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
"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 (Maybe a)
Data..?> Key
"MetadataProperties")
            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
"ModelApprovalStatus")
            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
"ModelMetrics")
            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
"ModelPackageDescription")
            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
"ModelPackageGroupName")
            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
"ModelPackageVersion")
            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
"SamplePayloadUrl")
            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
"SourceAlgorithmSpecification")
            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
"Task")
            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
"ValidationSpecification")
            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
"ModelPackageName")
            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
"ModelPackageArn")
            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
"ModelPackageStatus")
            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
"ModelPackageStatusDetails")
      )

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

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

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

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

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

-- | /See:/ 'newDescribeModelPackageResponse' smart constructor.
data DescribeModelPackageResponse = DescribeModelPackageResponse'
  { -- | An array of additional Inference Specification objects. Each additional
    -- Inference Specification specifies artifacts based on this model package
    -- that can be used on inference endpoints. Generally used with SageMaker
    -- Neo to store the compiled artifacts.
    DescribeModelPackageResponse
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications :: Prelude.Maybe (Prelude.NonEmpty AdditionalInferenceSpecificationDefinition),
    -- | A description provided for the model approval.
    DescribeModelPackageResponse -> Maybe Text
approvalDescription :: Prelude.Maybe Prelude.Text,
    -- | Whether the model package is certified for listing on Amazon Web
    -- Services Marketplace.
    DescribeModelPackageResponse -> Maybe Bool
certifyForMarketplace :: Prelude.Maybe Prelude.Bool,
    DescribeModelPackageResponse -> Maybe UserContext
createdBy :: Prelude.Maybe UserContext,
    -- | The metadata properties associated with the model package versions.
    DescribeModelPackageResponse -> Maybe (HashMap Text Text)
customerMetadataProperties :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The machine learning domain of the model package you specified. Common
    -- machine learning domains include computer vision and natural language
    -- processing.
    DescribeModelPackageResponse -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | Represents the drift check baselines that can be used when the model
    -- monitor is set using the model package. For more information, see the
    -- topic on
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/pipelines-quality-clarify-baseline-lifecycle.html#pipelines-quality-clarify-baseline-drift-detection Drift Detection against Previous Baselines in SageMaker Pipelines>
    -- in the /Amazon SageMaker Developer Guide/.
    DescribeModelPackageResponse -> Maybe DriftCheckBaselines
driftCheckBaselines :: Prelude.Maybe DriftCheckBaselines,
    -- | Details about inference jobs that can be run with models based on this
    -- model package.
    DescribeModelPackageResponse -> Maybe InferenceSpecification
inferenceSpecification :: Prelude.Maybe InferenceSpecification,
    DescribeModelPackageResponse -> Maybe UserContext
lastModifiedBy :: Prelude.Maybe UserContext,
    -- | The last time that the model package was modified.
    DescribeModelPackageResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    DescribeModelPackageResponse -> Maybe MetadataProperties
metadataProperties :: Prelude.Maybe MetadataProperties,
    -- | The approval status of the model package.
    DescribeModelPackageResponse -> Maybe ModelApprovalStatus
modelApprovalStatus :: Prelude.Maybe ModelApprovalStatus,
    -- | Metrics for the model.
    DescribeModelPackageResponse -> Maybe ModelMetrics
modelMetrics :: Prelude.Maybe ModelMetrics,
    -- | A brief summary of the model package.
    DescribeModelPackageResponse -> Maybe Text
modelPackageDescription :: Prelude.Maybe Prelude.Text,
    -- | If the model is a versioned model, the name of the model group that the
    -- versioned model belongs to.
    DescribeModelPackageResponse -> Maybe Text
modelPackageGroupName :: Prelude.Maybe Prelude.Text,
    -- | The version of the model package.
    DescribeModelPackageResponse -> Maybe Natural
modelPackageVersion :: Prelude.Maybe Prelude.Natural,
    -- | The Amazon Simple Storage Service (Amazon S3) path where the sample
    -- payload are stored. This path points to a single gzip compressed tar
    -- archive (.tar.gz suffix).
    DescribeModelPackageResponse -> Maybe Text
samplePayloadUrl :: Prelude.Maybe Prelude.Text,
    -- | Details about the algorithm that was used to create the model package.
    DescribeModelPackageResponse -> Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification :: Prelude.Maybe SourceAlgorithmSpecification,
    -- | The machine learning task you specified that your model package
    -- accomplishes. Common machine learning tasks include object detection and
    -- image classification.
    DescribeModelPackageResponse -> Maybe Text
task :: Prelude.Maybe Prelude.Text,
    -- | Configurations for one or more transform jobs that SageMaker runs to
    -- test the model package.
    DescribeModelPackageResponse
-> Maybe ModelPackageValidationSpecification
validationSpecification :: Prelude.Maybe ModelPackageValidationSpecification,
    -- | The response's http status code.
    DescribeModelPackageResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the model package being described.
    DescribeModelPackageResponse -> Text
modelPackageName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the model package.
    DescribeModelPackageResponse -> Text
modelPackageArn :: Prelude.Text,
    -- | A timestamp specifying when the model package was created.
    DescribeModelPackageResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The current status of the model package.
    DescribeModelPackageResponse -> ModelPackageStatus
modelPackageStatus :: ModelPackageStatus,
    -- | Details about the current status of the model package.
    DescribeModelPackageResponse -> ModelPackageStatusDetails
modelPackageStatusDetails :: ModelPackageStatusDetails
  }
  deriving (DescribeModelPackageResponse
-> DescribeModelPackageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeModelPackageResponse
-> DescribeModelPackageResponse -> Bool
$c/= :: DescribeModelPackageResponse
-> DescribeModelPackageResponse -> Bool
== :: DescribeModelPackageResponse
-> DescribeModelPackageResponse -> Bool
$c== :: DescribeModelPackageResponse
-> DescribeModelPackageResponse -> Bool
Prelude.Eq, ReadPrec [DescribeModelPackageResponse]
ReadPrec DescribeModelPackageResponse
Int -> ReadS DescribeModelPackageResponse
ReadS [DescribeModelPackageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeModelPackageResponse]
$creadListPrec :: ReadPrec [DescribeModelPackageResponse]
readPrec :: ReadPrec DescribeModelPackageResponse
$creadPrec :: ReadPrec DescribeModelPackageResponse
readList :: ReadS [DescribeModelPackageResponse]
$creadList :: ReadS [DescribeModelPackageResponse]
readsPrec :: Int -> ReadS DescribeModelPackageResponse
$creadsPrec :: Int -> ReadS DescribeModelPackageResponse
Prelude.Read, Int -> DescribeModelPackageResponse -> ShowS
[DescribeModelPackageResponse] -> ShowS
DescribeModelPackageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeModelPackageResponse] -> ShowS
$cshowList :: [DescribeModelPackageResponse] -> ShowS
show :: DescribeModelPackageResponse -> String
$cshow :: DescribeModelPackageResponse -> String
showsPrec :: Int -> DescribeModelPackageResponse -> ShowS
$cshowsPrec :: Int -> DescribeModelPackageResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeModelPackageResponse x -> DescribeModelPackageResponse
forall x.
DescribeModelPackageResponse -> Rep DescribeModelPackageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeModelPackageResponse x -> DescribeModelPackageResponse
$cfrom :: forall x.
DescribeModelPackageResponse -> Rep DescribeModelPackageResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeModelPackageResponse' 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:
--
-- 'additionalInferenceSpecifications', 'describeModelPackageResponse_additionalInferenceSpecifications' - An array of additional Inference Specification objects. Each additional
-- Inference Specification specifies artifacts based on this model package
-- that can be used on inference endpoints. Generally used with SageMaker
-- Neo to store the compiled artifacts.
--
-- 'approvalDescription', 'describeModelPackageResponse_approvalDescription' - A description provided for the model approval.
--
-- 'certifyForMarketplace', 'describeModelPackageResponse_certifyForMarketplace' - Whether the model package is certified for listing on Amazon Web
-- Services Marketplace.
--
-- 'createdBy', 'describeModelPackageResponse_createdBy' - Undocumented member.
--
-- 'customerMetadataProperties', 'describeModelPackageResponse_customerMetadataProperties' - The metadata properties associated with the model package versions.
--
-- 'domain', 'describeModelPackageResponse_domain' - The machine learning domain of the model package you specified. Common
-- machine learning domains include computer vision and natural language
-- processing.
--
-- 'driftCheckBaselines', 'describeModelPackageResponse_driftCheckBaselines' - Represents the drift check baselines that can be used when the model
-- monitor is set using the model package. For more information, see the
-- topic on
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/pipelines-quality-clarify-baseline-lifecycle.html#pipelines-quality-clarify-baseline-drift-detection Drift Detection against Previous Baselines in SageMaker Pipelines>
-- in the /Amazon SageMaker Developer Guide/.
--
-- 'inferenceSpecification', 'describeModelPackageResponse_inferenceSpecification' - Details about inference jobs that can be run with models based on this
-- model package.
--
-- 'lastModifiedBy', 'describeModelPackageResponse_lastModifiedBy' - Undocumented member.
--
-- 'lastModifiedTime', 'describeModelPackageResponse_lastModifiedTime' - The last time that the model package was modified.
--
-- 'metadataProperties', 'describeModelPackageResponse_metadataProperties' - Undocumented member.
--
-- 'modelApprovalStatus', 'describeModelPackageResponse_modelApprovalStatus' - The approval status of the model package.
--
-- 'modelMetrics', 'describeModelPackageResponse_modelMetrics' - Metrics for the model.
--
-- 'modelPackageDescription', 'describeModelPackageResponse_modelPackageDescription' - A brief summary of the model package.
--
-- 'modelPackageGroupName', 'describeModelPackageResponse_modelPackageGroupName' - If the model is a versioned model, the name of the model group that the
-- versioned model belongs to.
--
-- 'modelPackageVersion', 'describeModelPackageResponse_modelPackageVersion' - The version of the model package.
--
-- 'samplePayloadUrl', 'describeModelPackageResponse_samplePayloadUrl' - The Amazon Simple Storage Service (Amazon S3) path where the sample
-- payload are stored. This path points to a single gzip compressed tar
-- archive (.tar.gz suffix).
--
-- 'sourceAlgorithmSpecification', 'describeModelPackageResponse_sourceAlgorithmSpecification' - Details about the algorithm that was used to create the model package.
--
-- 'task', 'describeModelPackageResponse_task' - The machine learning task you specified that your model package
-- accomplishes. Common machine learning tasks include object detection and
-- image classification.
--
-- 'validationSpecification', 'describeModelPackageResponse_validationSpecification' - Configurations for one or more transform jobs that SageMaker runs to
-- test the model package.
--
-- 'httpStatus', 'describeModelPackageResponse_httpStatus' - The response's http status code.
--
-- 'modelPackageName', 'describeModelPackageResponse_modelPackageName' - The name of the model package being described.
--
-- 'modelPackageArn', 'describeModelPackageResponse_modelPackageArn' - The Amazon Resource Name (ARN) of the model package.
--
-- 'creationTime', 'describeModelPackageResponse_creationTime' - A timestamp specifying when the model package was created.
--
-- 'modelPackageStatus', 'describeModelPackageResponse_modelPackageStatus' - The current status of the model package.
--
-- 'modelPackageStatusDetails', 'describeModelPackageResponse_modelPackageStatusDetails' - Details about the current status of the model package.
newDescribeModelPackageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'modelPackageName'
  Prelude.Text ->
  -- | 'modelPackageArn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'modelPackageStatus'
  ModelPackageStatus ->
  -- | 'modelPackageStatusDetails'
  ModelPackageStatusDetails ->
  DescribeModelPackageResponse
newDescribeModelPackageResponse :: Int
-> Text
-> Text
-> UTCTime
-> ModelPackageStatus
-> ModelPackageStatusDetails
-> DescribeModelPackageResponse
newDescribeModelPackageResponse
  Int
pHttpStatus_
  Text
pModelPackageName_
  Text
pModelPackageArn_
  UTCTime
pCreationTime_
  ModelPackageStatus
pModelPackageStatus_
  ModelPackageStatusDetails
pModelPackageStatusDetails_ =
    DescribeModelPackageResponse'
      { $sel:additionalInferenceSpecifications:DescribeModelPackageResponse' :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications =
          forall a. Maybe a
Prelude.Nothing,
        $sel:approvalDescription:DescribeModelPackageResponse' :: Maybe Text
approvalDescription = forall a. Maybe a
Prelude.Nothing,
        $sel:certifyForMarketplace:DescribeModelPackageResponse' :: Maybe Bool
certifyForMarketplace = forall a. Maybe a
Prelude.Nothing,
        $sel:createdBy:DescribeModelPackageResponse' :: Maybe UserContext
createdBy = forall a. Maybe a
Prelude.Nothing,
        $sel:customerMetadataProperties:DescribeModelPackageResponse' :: Maybe (HashMap Text Text)
customerMetadataProperties = forall a. Maybe a
Prelude.Nothing,
        $sel:domain:DescribeModelPackageResponse' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
        $sel:driftCheckBaselines:DescribeModelPackageResponse' :: Maybe DriftCheckBaselines
driftCheckBaselines = forall a. Maybe a
Prelude.Nothing,
        $sel:inferenceSpecification:DescribeModelPackageResponse' :: Maybe InferenceSpecification
inferenceSpecification = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedBy:DescribeModelPackageResponse' :: Maybe UserContext
lastModifiedBy = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedTime:DescribeModelPackageResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:metadataProperties:DescribeModelPackageResponse' :: Maybe MetadataProperties
metadataProperties = forall a. Maybe a
Prelude.Nothing,
        $sel:modelApprovalStatus:DescribeModelPackageResponse' :: Maybe ModelApprovalStatus
modelApprovalStatus = forall a. Maybe a
Prelude.Nothing,
        $sel:modelMetrics:DescribeModelPackageResponse' :: Maybe ModelMetrics
modelMetrics = forall a. Maybe a
Prelude.Nothing,
        $sel:modelPackageDescription:DescribeModelPackageResponse' :: Maybe Text
modelPackageDescription = forall a. Maybe a
Prelude.Nothing,
        $sel:modelPackageGroupName:DescribeModelPackageResponse' :: Maybe Text
modelPackageGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:modelPackageVersion:DescribeModelPackageResponse' :: Maybe Natural
modelPackageVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:samplePayloadUrl:DescribeModelPackageResponse' :: Maybe Text
samplePayloadUrl = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceAlgorithmSpecification:DescribeModelPackageResponse' :: Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification =
          forall a. Maybe a
Prelude.Nothing,
        $sel:task:DescribeModelPackageResponse' :: Maybe Text
task = forall a. Maybe a
Prelude.Nothing,
        $sel:validationSpecification:DescribeModelPackageResponse' :: Maybe ModelPackageValidationSpecification
validationSpecification = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeModelPackageResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:modelPackageName:DescribeModelPackageResponse' :: Text
modelPackageName = Text
pModelPackageName_,
        $sel:modelPackageArn:DescribeModelPackageResponse' :: Text
modelPackageArn = Text
pModelPackageArn_,
        $sel:creationTime:DescribeModelPackageResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:modelPackageStatus:DescribeModelPackageResponse' :: ModelPackageStatus
modelPackageStatus = ModelPackageStatus
pModelPackageStatus_,
        $sel:modelPackageStatusDetails:DescribeModelPackageResponse' :: ModelPackageStatusDetails
modelPackageStatusDetails =
          ModelPackageStatusDetails
pModelPackageStatusDetails_
      }

-- | An array of additional Inference Specification objects. Each additional
-- Inference Specification specifies artifacts based on this model package
-- that can be used on inference endpoints. Generally used with SageMaker
-- Neo to store the compiled artifacts.
describeModelPackageResponse_additionalInferenceSpecifications :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe (Prelude.NonEmpty AdditionalInferenceSpecificationDefinition))
describeModelPackageResponse_additionalInferenceSpecifications :: Lens'
  DescribeModelPackageResponse
  (Maybe (NonEmpty AdditionalInferenceSpecificationDefinition))
describeModelPackageResponse_additionalInferenceSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:additionalInferenceSpecifications:DescribeModelPackageResponse' :: DescribeModelPackageResponse
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications} -> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
a -> DescribeModelPackageResponse
s {$sel:additionalInferenceSpecifications:DescribeModelPackageResponse' :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications = Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
a} :: DescribeModelPackageResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A description provided for the model approval.
describeModelPackageResponse_approvalDescription :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_approvalDescription :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_approvalDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
approvalDescription :: Maybe Text
$sel:approvalDescription:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
approvalDescription} -> Maybe Text
approvalDescription) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:approvalDescription:DescribeModelPackageResponse' :: Maybe Text
approvalDescription = Maybe Text
a} :: DescribeModelPackageResponse)

-- | Whether the model package is certified for listing on Amazon Web
-- Services Marketplace.
describeModelPackageResponse_certifyForMarketplace :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Bool)
describeModelPackageResponse_certifyForMarketplace :: Lens' DescribeModelPackageResponse (Maybe Bool)
describeModelPackageResponse_certifyForMarketplace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Bool
certifyForMarketplace :: Maybe Bool
$sel:certifyForMarketplace:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Bool
certifyForMarketplace} -> Maybe Bool
certifyForMarketplace) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Bool
a -> DescribeModelPackageResponse
s {$sel:certifyForMarketplace:DescribeModelPackageResponse' :: Maybe Bool
certifyForMarketplace = Maybe Bool
a} :: DescribeModelPackageResponse)

-- | Undocumented member.
describeModelPackageResponse_createdBy :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe UserContext)
describeModelPackageResponse_createdBy :: Lens' DescribeModelPackageResponse (Maybe UserContext)
describeModelPackageResponse_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe UserContext
createdBy :: Maybe UserContext
$sel:createdBy:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe UserContext
createdBy} -> Maybe UserContext
createdBy) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe UserContext
a -> DescribeModelPackageResponse
s {$sel:createdBy:DescribeModelPackageResponse' :: Maybe UserContext
createdBy = Maybe UserContext
a} :: DescribeModelPackageResponse)

-- | The metadata properties associated with the model package versions.
describeModelPackageResponse_customerMetadataProperties :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeModelPackageResponse_customerMetadataProperties :: Lens' DescribeModelPackageResponse (Maybe (HashMap Text Text))
describeModelPackageResponse_customerMetadataProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe (HashMap Text Text)
customerMetadataProperties :: Maybe (HashMap Text Text)
$sel:customerMetadataProperties:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe (HashMap Text Text)
customerMetadataProperties} -> Maybe (HashMap Text Text)
customerMetadataProperties) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe (HashMap Text Text)
a -> DescribeModelPackageResponse
s {$sel:customerMetadataProperties:DescribeModelPackageResponse' :: Maybe (HashMap Text Text)
customerMetadataProperties = Maybe (HashMap Text Text)
a} :: DescribeModelPackageResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The machine learning domain of the model package you specified. Common
-- machine learning domains include computer vision and natural language
-- processing.
describeModelPackageResponse_domain :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_domain :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
domain :: Maybe Text
$sel:domain:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
domain} -> Maybe Text
domain) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:domain:DescribeModelPackageResponse' :: Maybe Text
domain = Maybe Text
a} :: DescribeModelPackageResponse)

-- | Represents the drift check baselines that can be used when the model
-- monitor is set using the model package. For more information, see the
-- topic on
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/pipelines-quality-clarify-baseline-lifecycle.html#pipelines-quality-clarify-baseline-drift-detection Drift Detection against Previous Baselines in SageMaker Pipelines>
-- in the /Amazon SageMaker Developer Guide/.
describeModelPackageResponse_driftCheckBaselines :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe DriftCheckBaselines)
describeModelPackageResponse_driftCheckBaselines :: Lens' DescribeModelPackageResponse (Maybe DriftCheckBaselines)
describeModelPackageResponse_driftCheckBaselines = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe DriftCheckBaselines
driftCheckBaselines :: Maybe DriftCheckBaselines
$sel:driftCheckBaselines:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe DriftCheckBaselines
driftCheckBaselines} -> Maybe DriftCheckBaselines
driftCheckBaselines) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe DriftCheckBaselines
a -> DescribeModelPackageResponse
s {$sel:driftCheckBaselines:DescribeModelPackageResponse' :: Maybe DriftCheckBaselines
driftCheckBaselines = Maybe DriftCheckBaselines
a} :: DescribeModelPackageResponse)

-- | Details about inference jobs that can be run with models based on this
-- model package.
describeModelPackageResponse_inferenceSpecification :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe InferenceSpecification)
describeModelPackageResponse_inferenceSpecification :: Lens' DescribeModelPackageResponse (Maybe InferenceSpecification)
describeModelPackageResponse_inferenceSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe InferenceSpecification
inferenceSpecification :: Maybe InferenceSpecification
$sel:inferenceSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe InferenceSpecification
inferenceSpecification} -> Maybe InferenceSpecification
inferenceSpecification) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe InferenceSpecification
a -> DescribeModelPackageResponse
s {$sel:inferenceSpecification:DescribeModelPackageResponse' :: Maybe InferenceSpecification
inferenceSpecification = Maybe InferenceSpecification
a} :: DescribeModelPackageResponse)

-- | Undocumented member.
describeModelPackageResponse_lastModifiedBy :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe UserContext)
describeModelPackageResponse_lastModifiedBy :: Lens' DescribeModelPackageResponse (Maybe UserContext)
describeModelPackageResponse_lastModifiedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe UserContext
lastModifiedBy :: Maybe UserContext
$sel:lastModifiedBy:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe UserContext
lastModifiedBy} -> Maybe UserContext
lastModifiedBy) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe UserContext
a -> DescribeModelPackageResponse
s {$sel:lastModifiedBy:DescribeModelPackageResponse' :: Maybe UserContext
lastModifiedBy = Maybe UserContext
a} :: DescribeModelPackageResponse)

-- | The last time that the model package was modified.
describeModelPackageResponse_lastModifiedTime :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.UTCTime)
describeModelPackageResponse_lastModifiedTime :: Lens' DescribeModelPackageResponse (Maybe UTCTime)
describeModelPackageResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe POSIX
a -> DescribeModelPackageResponse
s {$sel:lastModifiedTime:DescribeModelPackageResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DescribeModelPackageResponse) 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

-- | Undocumented member.
describeModelPackageResponse_metadataProperties :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe MetadataProperties)
describeModelPackageResponse_metadataProperties :: Lens' DescribeModelPackageResponse (Maybe MetadataProperties)
describeModelPackageResponse_metadataProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe MetadataProperties
metadataProperties :: Maybe MetadataProperties
$sel:metadataProperties:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe MetadataProperties
metadataProperties} -> Maybe MetadataProperties
metadataProperties) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe MetadataProperties
a -> DescribeModelPackageResponse
s {$sel:metadataProperties:DescribeModelPackageResponse' :: Maybe MetadataProperties
metadataProperties = Maybe MetadataProperties
a} :: DescribeModelPackageResponse)

-- | The approval status of the model package.
describeModelPackageResponse_modelApprovalStatus :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe ModelApprovalStatus)
describeModelPackageResponse_modelApprovalStatus :: Lens' DescribeModelPackageResponse (Maybe ModelApprovalStatus)
describeModelPackageResponse_modelApprovalStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe ModelApprovalStatus
modelApprovalStatus :: Maybe ModelApprovalStatus
$sel:modelApprovalStatus:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe ModelApprovalStatus
modelApprovalStatus} -> Maybe ModelApprovalStatus
modelApprovalStatus) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe ModelApprovalStatus
a -> DescribeModelPackageResponse
s {$sel:modelApprovalStatus:DescribeModelPackageResponse' :: Maybe ModelApprovalStatus
modelApprovalStatus = Maybe ModelApprovalStatus
a} :: DescribeModelPackageResponse)

-- | Metrics for the model.
describeModelPackageResponse_modelMetrics :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe ModelMetrics)
describeModelPackageResponse_modelMetrics :: Lens' DescribeModelPackageResponse (Maybe ModelMetrics)
describeModelPackageResponse_modelMetrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe ModelMetrics
modelMetrics :: Maybe ModelMetrics
$sel:modelMetrics:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe ModelMetrics
modelMetrics} -> Maybe ModelMetrics
modelMetrics) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe ModelMetrics
a -> DescribeModelPackageResponse
s {$sel:modelMetrics:DescribeModelPackageResponse' :: Maybe ModelMetrics
modelMetrics = Maybe ModelMetrics
a} :: DescribeModelPackageResponse)

-- | A brief summary of the model package.
describeModelPackageResponse_modelPackageDescription :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_modelPackageDescription :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_modelPackageDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
modelPackageDescription :: Maybe Text
$sel:modelPackageDescription:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
modelPackageDescription} -> Maybe Text
modelPackageDescription) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:modelPackageDescription:DescribeModelPackageResponse' :: Maybe Text
modelPackageDescription = Maybe Text
a} :: DescribeModelPackageResponse)

-- | If the model is a versioned model, the name of the model group that the
-- versioned model belongs to.
describeModelPackageResponse_modelPackageGroupName :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_modelPackageGroupName :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_modelPackageGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
modelPackageGroupName :: Maybe Text
$sel:modelPackageGroupName:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
modelPackageGroupName} -> Maybe Text
modelPackageGroupName) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:modelPackageGroupName:DescribeModelPackageResponse' :: Maybe Text
modelPackageGroupName = Maybe Text
a} :: DescribeModelPackageResponse)

-- | The version of the model package.
describeModelPackageResponse_modelPackageVersion :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Natural)
describeModelPackageResponse_modelPackageVersion :: Lens' DescribeModelPackageResponse (Maybe Natural)
describeModelPackageResponse_modelPackageVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Natural
modelPackageVersion :: Maybe Natural
$sel:modelPackageVersion:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Natural
modelPackageVersion} -> Maybe Natural
modelPackageVersion) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Natural
a -> DescribeModelPackageResponse
s {$sel:modelPackageVersion:DescribeModelPackageResponse' :: Maybe Natural
modelPackageVersion = Maybe Natural
a} :: DescribeModelPackageResponse)

-- | The Amazon Simple Storage Service (Amazon S3) path where the sample
-- payload are stored. This path points to a single gzip compressed tar
-- archive (.tar.gz suffix).
describeModelPackageResponse_samplePayloadUrl :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_samplePayloadUrl :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_samplePayloadUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
samplePayloadUrl :: Maybe Text
$sel:samplePayloadUrl:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
samplePayloadUrl} -> Maybe Text
samplePayloadUrl) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:samplePayloadUrl:DescribeModelPackageResponse' :: Maybe Text
samplePayloadUrl = Maybe Text
a} :: DescribeModelPackageResponse)

-- | Details about the algorithm that was used to create the model package.
describeModelPackageResponse_sourceAlgorithmSpecification :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe SourceAlgorithmSpecification)
describeModelPackageResponse_sourceAlgorithmSpecification :: Lens'
  DescribeModelPackageResponse (Maybe SourceAlgorithmSpecification)
describeModelPackageResponse_sourceAlgorithmSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification :: Maybe SourceAlgorithmSpecification
$sel:sourceAlgorithmSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification} -> Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe SourceAlgorithmSpecification
a -> DescribeModelPackageResponse
s {$sel:sourceAlgorithmSpecification:DescribeModelPackageResponse' :: Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification = Maybe SourceAlgorithmSpecification
a} :: DescribeModelPackageResponse)

-- | The machine learning task you specified that your model package
-- accomplishes. Common machine learning tasks include object detection and
-- image classification.
describeModelPackageResponse_task :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe Prelude.Text)
describeModelPackageResponse_task :: Lens' DescribeModelPackageResponse (Maybe Text)
describeModelPackageResponse_task = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe Text
task :: Maybe Text
$sel:task:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
task} -> Maybe Text
task) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe Text
a -> DescribeModelPackageResponse
s {$sel:task:DescribeModelPackageResponse' :: Maybe Text
task = Maybe Text
a} :: DescribeModelPackageResponse)

-- | Configurations for one or more transform jobs that SageMaker runs to
-- test the model package.
describeModelPackageResponse_validationSpecification :: Lens.Lens' DescribeModelPackageResponse (Prelude.Maybe ModelPackageValidationSpecification)
describeModelPackageResponse_validationSpecification :: Lens'
  DescribeModelPackageResponse
  (Maybe ModelPackageValidationSpecification)
describeModelPackageResponse_validationSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Maybe ModelPackageValidationSpecification
validationSpecification :: Maybe ModelPackageValidationSpecification
$sel:validationSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse
-> Maybe ModelPackageValidationSpecification
validationSpecification} -> Maybe ModelPackageValidationSpecification
validationSpecification) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Maybe ModelPackageValidationSpecification
a -> DescribeModelPackageResponse
s {$sel:validationSpecification:DescribeModelPackageResponse' :: Maybe ModelPackageValidationSpecification
validationSpecification = Maybe ModelPackageValidationSpecification
a} :: DescribeModelPackageResponse)

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

-- | The name of the model package being described.
describeModelPackageResponse_modelPackageName :: Lens.Lens' DescribeModelPackageResponse Prelude.Text
describeModelPackageResponse_modelPackageName :: Lens' DescribeModelPackageResponse Text
describeModelPackageResponse_modelPackageName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Text
modelPackageName :: Text
$sel:modelPackageName:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Text
modelPackageName} -> Text
modelPackageName) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Text
a -> DescribeModelPackageResponse
s {$sel:modelPackageName:DescribeModelPackageResponse' :: Text
modelPackageName = Text
a} :: DescribeModelPackageResponse)

-- | The Amazon Resource Name (ARN) of the model package.
describeModelPackageResponse_modelPackageArn :: Lens.Lens' DescribeModelPackageResponse Prelude.Text
describeModelPackageResponse_modelPackageArn :: Lens' DescribeModelPackageResponse Text
describeModelPackageResponse_modelPackageArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {Text
modelPackageArn :: Text
$sel:modelPackageArn:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Text
modelPackageArn} -> Text
modelPackageArn) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} Text
a -> DescribeModelPackageResponse
s {$sel:modelPackageArn:DescribeModelPackageResponse' :: Text
modelPackageArn = Text
a} :: DescribeModelPackageResponse)

-- | A timestamp specifying when the model package was created.
describeModelPackageResponse_creationTime :: Lens.Lens' DescribeModelPackageResponse Prelude.UTCTime
describeModelPackageResponse_creationTime :: Lens' DescribeModelPackageResponse UTCTime
describeModelPackageResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} POSIX
a -> DescribeModelPackageResponse
s {$sel:creationTime:DescribeModelPackageResponse' :: POSIX
creationTime = POSIX
a} :: DescribeModelPackageResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current status of the model package.
describeModelPackageResponse_modelPackageStatus :: Lens.Lens' DescribeModelPackageResponse ModelPackageStatus
describeModelPackageResponse_modelPackageStatus :: Lens' DescribeModelPackageResponse ModelPackageStatus
describeModelPackageResponse_modelPackageStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {ModelPackageStatus
modelPackageStatus :: ModelPackageStatus
$sel:modelPackageStatus:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> ModelPackageStatus
modelPackageStatus} -> ModelPackageStatus
modelPackageStatus) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} ModelPackageStatus
a -> DescribeModelPackageResponse
s {$sel:modelPackageStatus:DescribeModelPackageResponse' :: ModelPackageStatus
modelPackageStatus = ModelPackageStatus
a} :: DescribeModelPackageResponse)

-- | Details about the current status of the model package.
describeModelPackageResponse_modelPackageStatusDetails :: Lens.Lens' DescribeModelPackageResponse ModelPackageStatusDetails
describeModelPackageResponse_modelPackageStatusDetails :: Lens' DescribeModelPackageResponse ModelPackageStatusDetails
describeModelPackageResponse_modelPackageStatusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeModelPackageResponse' {ModelPackageStatusDetails
modelPackageStatusDetails :: ModelPackageStatusDetails
$sel:modelPackageStatusDetails:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> ModelPackageStatusDetails
modelPackageStatusDetails} -> ModelPackageStatusDetails
modelPackageStatusDetails) (\s :: DescribeModelPackageResponse
s@DescribeModelPackageResponse' {} ModelPackageStatusDetails
a -> DescribeModelPackageResponse
s {$sel:modelPackageStatusDetails:DescribeModelPackageResponse' :: ModelPackageStatusDetails
modelPackageStatusDetails = ModelPackageStatusDetails
a} :: DescribeModelPackageResponse)

instance Prelude.NFData DescribeModelPackageResponse where
  rnf :: DescribeModelPackageResponse -> ()
rnf DescribeModelPackageResponse' {Int
Maybe Bool
Maybe Natural
Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe MetadataProperties
Maybe DriftCheckBaselines
Maybe ModelApprovalStatus
Maybe ModelMetrics
Maybe SourceAlgorithmSpecification
Maybe InferenceSpecification
Maybe ModelPackageValidationSpecification
Maybe UserContext
Text
POSIX
ModelPackageStatus
ModelPackageStatusDetails
modelPackageStatusDetails :: ModelPackageStatusDetails
modelPackageStatus :: ModelPackageStatus
creationTime :: POSIX
modelPackageArn :: Text
modelPackageName :: Text
httpStatus :: Int
validationSpecification :: Maybe ModelPackageValidationSpecification
task :: Maybe Text
sourceAlgorithmSpecification :: Maybe SourceAlgorithmSpecification
samplePayloadUrl :: Maybe Text
modelPackageVersion :: Maybe Natural
modelPackageGroupName :: Maybe Text
modelPackageDescription :: Maybe Text
modelMetrics :: Maybe ModelMetrics
modelApprovalStatus :: Maybe ModelApprovalStatus
metadataProperties :: Maybe MetadataProperties
lastModifiedTime :: Maybe POSIX
lastModifiedBy :: Maybe UserContext
inferenceSpecification :: Maybe InferenceSpecification
driftCheckBaselines :: Maybe DriftCheckBaselines
domain :: Maybe Text
customerMetadataProperties :: Maybe (HashMap Text Text)
createdBy :: Maybe UserContext
certifyForMarketplace :: Maybe Bool
approvalDescription :: Maybe Text
additionalInferenceSpecifications :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:modelPackageStatusDetails:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> ModelPackageStatusDetails
$sel:modelPackageStatus:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> ModelPackageStatus
$sel:creationTime:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> POSIX
$sel:modelPackageArn:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Text
$sel:modelPackageName:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Text
$sel:httpStatus:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Int
$sel:validationSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse
-> Maybe ModelPackageValidationSpecification
$sel:task:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:sourceAlgorithmSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe SourceAlgorithmSpecification
$sel:samplePayloadUrl:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:modelPackageVersion:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Natural
$sel:modelPackageGroupName:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:modelPackageDescription:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:modelMetrics:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe ModelMetrics
$sel:modelApprovalStatus:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe ModelApprovalStatus
$sel:metadataProperties:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe MetadataProperties
$sel:lastModifiedTime:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe POSIX
$sel:lastModifiedBy:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe UserContext
$sel:inferenceSpecification:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe InferenceSpecification
$sel:driftCheckBaselines:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe DriftCheckBaselines
$sel:domain:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:customerMetadataProperties:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe (HashMap Text Text)
$sel:createdBy:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe UserContext
$sel:certifyForMarketplace:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Bool
$sel:approvalDescription:DescribeModelPackageResponse' :: DescribeModelPackageResponse -> Maybe Text
$sel:additionalInferenceSpecifications:DescribeModelPackageResponse' :: DescribeModelPackageResponse
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
approvalDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
certifyForMarketplace
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserContext
createdBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
customerMetadataProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DriftCheckBaselines
driftCheckBaselines
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InferenceSpecification
inferenceSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserContext
lastModifiedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MetadataProperties
metadataProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelApprovalStatus
modelApprovalStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelMetrics
modelMetrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelPackageDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelPackageGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
modelPackageVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
samplePayloadUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe SourceAlgorithmSpecification
sourceAlgorithmSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
task
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ModelPackageValidationSpecification
validationSpecification
      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
modelPackageName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
modelPackageArn
      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
        ModelPackageStatus
modelPackageStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        ModelPackageStatusDetails
modelPackageStatusDetails