{-# 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.UpdateModelPackage
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a versioned model.
module Amazonka.SageMaker.UpdateModelPackage
  ( -- * Creating a Request
    UpdateModelPackage (..),
    newUpdateModelPackage,

    -- * Request Lenses
    updateModelPackage_additionalInferenceSpecificationsToAdd,
    updateModelPackage_approvalDescription,
    updateModelPackage_customerMetadataProperties,
    updateModelPackage_customerMetadataPropertiesToRemove,
    updateModelPackage_modelApprovalStatus,
    updateModelPackage_modelPackageArn,

    -- * Destructuring the Response
    UpdateModelPackageResponse (..),
    newUpdateModelPackageResponse,

    -- * Response Lenses
    updateModelPackageResponse_httpStatus,
    updateModelPackageResponse_modelPackageArn,
  )
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:/ 'newUpdateModelPackage' smart constructor.
data UpdateModelPackage = UpdateModelPackage'
  { -- | An array of additional Inference Specification objects to be added to
    -- the existing array additional Inference Specification. Total number of
    -- additional Inference Specifications can not exceed 15. 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.
    UpdateModelPackage
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd :: Prelude.Maybe (Prelude.NonEmpty AdditionalInferenceSpecificationDefinition),
    -- | A description for the approval status of the model.
    UpdateModelPackage -> Maybe Text
approvalDescription :: Prelude.Maybe Prelude.Text,
    -- | The metadata properties associated with the model package versions.
    UpdateModelPackage -> Maybe (HashMap Text Text)
customerMetadataProperties :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The metadata properties associated with the model package versions to
    -- remove.
    UpdateModelPackage -> Maybe [Text]
customerMetadataPropertiesToRemove :: Prelude.Maybe [Prelude.Text],
    -- | The approval status of the model.
    UpdateModelPackage -> Maybe ModelApprovalStatus
modelApprovalStatus :: Prelude.Maybe ModelApprovalStatus,
    -- | The Amazon Resource Name (ARN) of the model package.
    UpdateModelPackage -> Text
modelPackageArn :: Prelude.Text
  }
  deriving (UpdateModelPackage -> UpdateModelPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateModelPackage -> UpdateModelPackage -> Bool
$c/= :: UpdateModelPackage -> UpdateModelPackage -> Bool
== :: UpdateModelPackage -> UpdateModelPackage -> Bool
$c== :: UpdateModelPackage -> UpdateModelPackage -> Bool
Prelude.Eq, ReadPrec [UpdateModelPackage]
ReadPrec UpdateModelPackage
Int -> ReadS UpdateModelPackage
ReadS [UpdateModelPackage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateModelPackage]
$creadListPrec :: ReadPrec [UpdateModelPackage]
readPrec :: ReadPrec UpdateModelPackage
$creadPrec :: ReadPrec UpdateModelPackage
readList :: ReadS [UpdateModelPackage]
$creadList :: ReadS [UpdateModelPackage]
readsPrec :: Int -> ReadS UpdateModelPackage
$creadsPrec :: Int -> ReadS UpdateModelPackage
Prelude.Read, Int -> UpdateModelPackage -> ShowS
[UpdateModelPackage] -> ShowS
UpdateModelPackage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateModelPackage] -> ShowS
$cshowList :: [UpdateModelPackage] -> ShowS
show :: UpdateModelPackage -> String
$cshow :: UpdateModelPackage -> String
showsPrec :: Int -> UpdateModelPackage -> ShowS
$cshowsPrec :: Int -> UpdateModelPackage -> ShowS
Prelude.Show, forall x. Rep UpdateModelPackage x -> UpdateModelPackage
forall x. UpdateModelPackage -> Rep UpdateModelPackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateModelPackage x -> UpdateModelPackage
$cfrom :: forall x. UpdateModelPackage -> Rep UpdateModelPackage x
Prelude.Generic)

-- |
-- Create a value of 'UpdateModelPackage' 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:
--
-- 'additionalInferenceSpecificationsToAdd', 'updateModelPackage_additionalInferenceSpecificationsToAdd' - An array of additional Inference Specification objects to be added to
-- the existing array additional Inference Specification. Total number of
-- additional Inference Specifications can not exceed 15. 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', 'updateModelPackage_approvalDescription' - A description for the approval status of the model.
--
-- 'customerMetadataProperties', 'updateModelPackage_customerMetadataProperties' - The metadata properties associated with the model package versions.
--
-- 'customerMetadataPropertiesToRemove', 'updateModelPackage_customerMetadataPropertiesToRemove' - The metadata properties associated with the model package versions to
-- remove.
--
-- 'modelApprovalStatus', 'updateModelPackage_modelApprovalStatus' - The approval status of the model.
--
-- 'modelPackageArn', 'updateModelPackage_modelPackageArn' - The Amazon Resource Name (ARN) of the model package.
newUpdateModelPackage ::
  -- | 'modelPackageArn'
  Prelude.Text ->
  UpdateModelPackage
newUpdateModelPackage :: Text -> UpdateModelPackage
newUpdateModelPackage Text
pModelPackageArn_ =
  UpdateModelPackage'
    { $sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd =
        forall a. Maybe a
Prelude.Nothing,
      $sel:approvalDescription:UpdateModelPackage' :: Maybe Text
approvalDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:customerMetadataProperties:UpdateModelPackage' :: Maybe (HashMap Text Text)
customerMetadataProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: Maybe [Text]
customerMetadataPropertiesToRemove = forall a. Maybe a
Prelude.Nothing,
      $sel:modelApprovalStatus:UpdateModelPackage' :: Maybe ModelApprovalStatus
modelApprovalStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:modelPackageArn:UpdateModelPackage' :: Text
modelPackageArn = Text
pModelPackageArn_
    }

-- | An array of additional Inference Specification objects to be added to
-- the existing array additional Inference Specification. Total number of
-- additional Inference Specifications can not exceed 15. 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.
updateModelPackage_additionalInferenceSpecificationsToAdd :: Lens.Lens' UpdateModelPackage (Prelude.Maybe (Prelude.NonEmpty AdditionalInferenceSpecificationDefinition))
updateModelPackage_additionalInferenceSpecificationsToAdd :: Lens'
  UpdateModelPackage
  (Maybe (NonEmpty AdditionalInferenceSpecificationDefinition))
updateModelPackage_additionalInferenceSpecificationsToAdd = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateModelPackage' {Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: UpdateModelPackage
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd} -> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd) (\s :: UpdateModelPackage
s@UpdateModelPackage' {} Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
a -> UpdateModelPackage
s {$sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd = Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
a} :: UpdateModelPackage) 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 for the approval status of the model.
updateModelPackage_approvalDescription :: Lens.Lens' UpdateModelPackage (Prelude.Maybe Prelude.Text)
updateModelPackage_approvalDescription :: Lens' UpdateModelPackage (Maybe Text)
updateModelPackage_approvalDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateModelPackage' {Maybe Text
approvalDescription :: Maybe Text
$sel:approvalDescription:UpdateModelPackage' :: UpdateModelPackage -> Maybe Text
approvalDescription} -> Maybe Text
approvalDescription) (\s :: UpdateModelPackage
s@UpdateModelPackage' {} Maybe Text
a -> UpdateModelPackage
s {$sel:approvalDescription:UpdateModelPackage' :: Maybe Text
approvalDescription = Maybe Text
a} :: UpdateModelPackage)

-- | The metadata properties associated with the model package versions.
updateModelPackage_customerMetadataProperties :: Lens.Lens' UpdateModelPackage (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateModelPackage_customerMetadataProperties :: Lens' UpdateModelPackage (Maybe (HashMap Text Text))
updateModelPackage_customerMetadataProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateModelPackage' {Maybe (HashMap Text Text)
customerMetadataProperties :: Maybe (HashMap Text Text)
$sel:customerMetadataProperties:UpdateModelPackage' :: UpdateModelPackage -> Maybe (HashMap Text Text)
customerMetadataProperties} -> Maybe (HashMap Text Text)
customerMetadataProperties) (\s :: UpdateModelPackage
s@UpdateModelPackage' {} Maybe (HashMap Text Text)
a -> UpdateModelPackage
s {$sel:customerMetadataProperties:UpdateModelPackage' :: Maybe (HashMap Text Text)
customerMetadataProperties = Maybe (HashMap Text Text)
a} :: UpdateModelPackage) 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 metadata properties associated with the model package versions to
-- remove.
updateModelPackage_customerMetadataPropertiesToRemove :: Lens.Lens' UpdateModelPackage (Prelude.Maybe [Prelude.Text])
updateModelPackage_customerMetadataPropertiesToRemove :: Lens' UpdateModelPackage (Maybe [Text])
updateModelPackage_customerMetadataPropertiesToRemove = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateModelPackage' {Maybe [Text]
customerMetadataPropertiesToRemove :: Maybe [Text]
$sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: UpdateModelPackage -> Maybe [Text]
customerMetadataPropertiesToRemove} -> Maybe [Text]
customerMetadataPropertiesToRemove) (\s :: UpdateModelPackage
s@UpdateModelPackage' {} Maybe [Text]
a -> UpdateModelPackage
s {$sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: Maybe [Text]
customerMetadataPropertiesToRemove = Maybe [Text]
a} :: UpdateModelPackage) 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 approval status of the model.
updateModelPackage_modelApprovalStatus :: Lens.Lens' UpdateModelPackage (Prelude.Maybe ModelApprovalStatus)
updateModelPackage_modelApprovalStatus :: Lens' UpdateModelPackage (Maybe ModelApprovalStatus)
updateModelPackage_modelApprovalStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateModelPackage' {Maybe ModelApprovalStatus
modelApprovalStatus :: Maybe ModelApprovalStatus
$sel:modelApprovalStatus:UpdateModelPackage' :: UpdateModelPackage -> Maybe ModelApprovalStatus
modelApprovalStatus} -> Maybe ModelApprovalStatus
modelApprovalStatus) (\s :: UpdateModelPackage
s@UpdateModelPackage' {} Maybe ModelApprovalStatus
a -> UpdateModelPackage
s {$sel:modelApprovalStatus:UpdateModelPackage' :: Maybe ModelApprovalStatus
modelApprovalStatus = Maybe ModelApprovalStatus
a} :: UpdateModelPackage)

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

instance Core.AWSRequest UpdateModelPackage where
  type
    AWSResponse UpdateModelPackage =
      UpdateModelPackageResponse
  request :: (Service -> Service)
-> UpdateModelPackage -> Request UpdateModelPackage
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 UpdateModelPackage
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateModelPackage)))
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 ->
          Int -> Text -> UpdateModelPackageResponse
UpdateModelPackageResponse'
            forall (f :: * -> *) a b. Functor 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
"ModelPackageArn")
      )

instance Prelude.Hashable UpdateModelPackage where
  hashWithSalt :: Int -> UpdateModelPackage -> Int
hashWithSalt Int
_salt UpdateModelPackage' {Maybe [Text]
Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
Maybe Text
Maybe (HashMap Text Text)
Maybe ModelApprovalStatus
Text
modelPackageArn :: Text
modelApprovalStatus :: Maybe ModelApprovalStatus
customerMetadataPropertiesToRemove :: Maybe [Text]
customerMetadataProperties :: Maybe (HashMap Text Text)
approvalDescription :: Maybe Text
additionalInferenceSpecificationsToAdd :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:modelPackageArn:UpdateModelPackage' :: UpdateModelPackage -> Text
$sel:modelApprovalStatus:UpdateModelPackage' :: UpdateModelPackage -> Maybe ModelApprovalStatus
$sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: UpdateModelPackage -> Maybe [Text]
$sel:customerMetadataProperties:UpdateModelPackage' :: UpdateModelPackage -> Maybe (HashMap Text Text)
$sel:approvalDescription:UpdateModelPackage' :: UpdateModelPackage -> Maybe Text
$sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: UpdateModelPackage
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
approvalDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
customerMetadataProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
customerMetadataPropertiesToRemove
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelApprovalStatus
modelApprovalStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
modelPackageArn

instance Prelude.NFData UpdateModelPackage where
  rnf :: UpdateModelPackage -> ()
rnf UpdateModelPackage' {Maybe [Text]
Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
Maybe Text
Maybe (HashMap Text Text)
Maybe ModelApprovalStatus
Text
modelPackageArn :: Text
modelApprovalStatus :: Maybe ModelApprovalStatus
customerMetadataPropertiesToRemove :: Maybe [Text]
customerMetadataProperties :: Maybe (HashMap Text Text)
approvalDescription :: Maybe Text
additionalInferenceSpecificationsToAdd :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:modelPackageArn:UpdateModelPackage' :: UpdateModelPackage -> Text
$sel:modelApprovalStatus:UpdateModelPackage' :: UpdateModelPackage -> Maybe ModelApprovalStatus
$sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: UpdateModelPackage -> Maybe [Text]
$sel:customerMetadataProperties:UpdateModelPackage' :: UpdateModelPackage -> Maybe (HashMap Text Text)
$sel:approvalDescription:UpdateModelPackage' :: UpdateModelPackage -> Maybe Text
$sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: UpdateModelPackage
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd
      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 (HashMap Text Text)
customerMetadataProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
customerMetadataPropertiesToRemove
      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 Text
modelPackageArn

instance Data.ToHeaders UpdateModelPackage where
  toHeaders :: UpdateModelPackage -> 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.UpdateModelPackage" ::
                          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 UpdateModelPackage where
  toJSON :: UpdateModelPackage -> Value
toJSON UpdateModelPackage' {Maybe [Text]
Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
Maybe Text
Maybe (HashMap Text Text)
Maybe ModelApprovalStatus
Text
modelPackageArn :: Text
modelApprovalStatus :: Maybe ModelApprovalStatus
customerMetadataPropertiesToRemove :: Maybe [Text]
customerMetadataProperties :: Maybe (HashMap Text Text)
approvalDescription :: Maybe Text
additionalInferenceSpecificationsToAdd :: Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
$sel:modelPackageArn:UpdateModelPackage' :: UpdateModelPackage -> Text
$sel:modelApprovalStatus:UpdateModelPackage' :: UpdateModelPackage -> Maybe ModelApprovalStatus
$sel:customerMetadataPropertiesToRemove:UpdateModelPackage' :: UpdateModelPackage -> Maybe [Text]
$sel:customerMetadataProperties:UpdateModelPackage' :: UpdateModelPackage -> Maybe (HashMap Text Text)
$sel:approvalDescription:UpdateModelPackage' :: UpdateModelPackage -> Maybe Text
$sel:additionalInferenceSpecificationsToAdd:UpdateModelPackage' :: UpdateModelPackage
-> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AdditionalInferenceSpecificationsToAdd" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty AdditionalInferenceSpecificationDefinition)
additionalInferenceSpecificationsToAdd,
            (Key
"ApprovalDescription" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
approvalDescription,
            (Key
"CustomerMetadataProperties" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
customerMetadataProperties,
            (Key
"CustomerMetadataPropertiesToRemove" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
customerMetadataPropertiesToRemove,
            (Key
"ModelApprovalStatus" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ModelApprovalStatus
modelApprovalStatus,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ModelPackageArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
modelPackageArn)
          ]
      )

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

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

-- | /See:/ 'newUpdateModelPackageResponse' smart constructor.
data UpdateModelPackageResponse = UpdateModelPackageResponse'
  { -- | The response's http status code.
    UpdateModelPackageResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the model.
    UpdateModelPackageResponse -> Text
modelPackageArn :: Prelude.Text
  }
  deriving (UpdateModelPackageResponse -> UpdateModelPackageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateModelPackageResponse -> UpdateModelPackageResponse -> Bool
$c/= :: UpdateModelPackageResponse -> UpdateModelPackageResponse -> Bool
== :: UpdateModelPackageResponse -> UpdateModelPackageResponse -> Bool
$c== :: UpdateModelPackageResponse -> UpdateModelPackageResponse -> Bool
Prelude.Eq, ReadPrec [UpdateModelPackageResponse]
ReadPrec UpdateModelPackageResponse
Int -> ReadS UpdateModelPackageResponse
ReadS [UpdateModelPackageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateModelPackageResponse]
$creadListPrec :: ReadPrec [UpdateModelPackageResponse]
readPrec :: ReadPrec UpdateModelPackageResponse
$creadPrec :: ReadPrec UpdateModelPackageResponse
readList :: ReadS [UpdateModelPackageResponse]
$creadList :: ReadS [UpdateModelPackageResponse]
readsPrec :: Int -> ReadS UpdateModelPackageResponse
$creadsPrec :: Int -> ReadS UpdateModelPackageResponse
Prelude.Read, Int -> UpdateModelPackageResponse -> ShowS
[UpdateModelPackageResponse] -> ShowS
UpdateModelPackageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateModelPackageResponse] -> ShowS
$cshowList :: [UpdateModelPackageResponse] -> ShowS
show :: UpdateModelPackageResponse -> String
$cshow :: UpdateModelPackageResponse -> String
showsPrec :: Int -> UpdateModelPackageResponse -> ShowS
$cshowsPrec :: Int -> UpdateModelPackageResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateModelPackageResponse x -> UpdateModelPackageResponse
forall x.
UpdateModelPackageResponse -> Rep UpdateModelPackageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateModelPackageResponse x -> UpdateModelPackageResponse
$cfrom :: forall x.
UpdateModelPackageResponse -> Rep UpdateModelPackageResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateModelPackageResponse' 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:
--
-- 'httpStatus', 'updateModelPackageResponse_httpStatus' - The response's http status code.
--
-- 'modelPackageArn', 'updateModelPackageResponse_modelPackageArn' - The Amazon Resource Name (ARN) of the model.
newUpdateModelPackageResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'modelPackageArn'
  Prelude.Text ->
  UpdateModelPackageResponse
newUpdateModelPackageResponse :: Int -> Text -> UpdateModelPackageResponse
newUpdateModelPackageResponse
  Int
pHttpStatus_
  Text
pModelPackageArn_ =
    UpdateModelPackageResponse'
      { $sel:httpStatus:UpdateModelPackageResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:modelPackageArn:UpdateModelPackageResponse' :: Text
modelPackageArn = Text
pModelPackageArn_
      }

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

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

instance Prelude.NFData UpdateModelPackageResponse where
  rnf :: UpdateModelPackageResponse -> ()
rnf UpdateModelPackageResponse' {Int
Text
modelPackageArn :: Text
httpStatus :: Int
$sel:modelPackageArn:UpdateModelPackageResponse' :: UpdateModelPackageResponse -> Text
$sel:httpStatus:UpdateModelPackageResponse' :: UpdateModelPackageResponse -> Int
..} =
    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
modelPackageArn