{-# 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.LookoutVision.StartModelPackagingJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts an Amazon Lookout for Vision model packaging job. A model
-- packaging job creates an AWS IoT Greengrass component for a Lookout for
-- Vision model. You can use the component to deploy your model to an edge
-- device managed by Greengrass.
--
-- Use the DescribeModelPackagingJob API to determine the current status of
-- the job. The model packaging job is complete if the value of @Status@ is
-- @SUCCEEDED@.
--
-- To deploy the component to the target device, use the component name and
-- component version with the AWS IoT Greengrass
-- <https://docs.aws.amazon.com/greengrass/v2/APIReference/API_CreateDeployment.html CreateDeployment>
-- API.
--
-- This operation requires the following permissions:
--
-- -   @lookoutvision:StartModelPackagingJob@
--
-- -   @s3:PutObject@
--
-- -   @s3:GetBucketLocation@
--
-- -   @kms:GenerateDataKey@
--
-- -   @greengrass:CreateComponentVersion@
--
-- -   @greengrass:DescribeComponent@
--
-- -   (Optional) @greengrass:TagResource@. Only required if you want to
--     tag the component.
--
-- For more information, see /Using your Amazon Lookout for Vision model on
-- an edge device/ in the Amazon Lookout for Vision Developer Guide.
module Amazonka.LookoutVision.StartModelPackagingJob
  ( -- * Creating a Request
    StartModelPackagingJob (..),
    newStartModelPackagingJob,

    -- * Request Lenses
    startModelPackagingJob_clientToken,
    startModelPackagingJob_description,
    startModelPackagingJob_jobName,
    startModelPackagingJob_projectName,
    startModelPackagingJob_modelVersion,
    startModelPackagingJob_configuration,

    -- * Destructuring the Response
    StartModelPackagingJobResponse (..),
    newStartModelPackagingJobResponse,

    -- * Response Lenses
    startModelPackagingJobResponse_jobName,
    startModelPackagingJobResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartModelPackagingJob' smart constructor.
data StartModelPackagingJob = StartModelPackagingJob'
  { -- | ClientToken is an idempotency token that ensures a call to
    -- @StartModelPackagingJob@ completes only once. You choose the value to
    -- pass. For example, An issue might prevent you from getting a response
    -- from @StartModelPackagingJob@. In this case, safely retry your call to
    -- @StartModelPackagingJob@ by using the same @ClientToken@ parameter
    -- value.
    --
    -- If you don\'t supply a value for @ClientToken@, the AWS SDK you are
    -- using inserts a value for you. This prevents retries after a network
    -- error from making multiple dataset creation requests. You\'ll need to
    -- provide your own value for other use cases.
    --
    -- An error occurs if the other input parameters are not the same as in the
    -- first request. Using a different value for @ClientToken@ is considered a
    -- new call to @StartModelPackagingJob@. An idempotency token is active for
    -- 8 hours.
    StartModelPackagingJob -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description for the model packaging job.
    StartModelPackagingJob -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A name for the model packaging job. If you don\'t supply a value, the
    -- service creates a job name for you.
    StartModelPackagingJob -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The name of the project which contains the version of the model that you
    -- want to package.
    StartModelPackagingJob -> Text
projectName :: Prelude.Text,
    -- | The version of the model within the project that you want to package.
    StartModelPackagingJob -> Text
modelVersion :: Prelude.Text,
    -- | The configuration for the model packaging job.
    StartModelPackagingJob -> ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
  }
  deriving (StartModelPackagingJob -> StartModelPackagingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartModelPackagingJob -> StartModelPackagingJob -> Bool
$c/= :: StartModelPackagingJob -> StartModelPackagingJob -> Bool
== :: StartModelPackagingJob -> StartModelPackagingJob -> Bool
$c== :: StartModelPackagingJob -> StartModelPackagingJob -> Bool
Prelude.Eq, ReadPrec [StartModelPackagingJob]
ReadPrec StartModelPackagingJob
Int -> ReadS StartModelPackagingJob
ReadS [StartModelPackagingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartModelPackagingJob]
$creadListPrec :: ReadPrec [StartModelPackagingJob]
readPrec :: ReadPrec StartModelPackagingJob
$creadPrec :: ReadPrec StartModelPackagingJob
readList :: ReadS [StartModelPackagingJob]
$creadList :: ReadS [StartModelPackagingJob]
readsPrec :: Int -> ReadS StartModelPackagingJob
$creadsPrec :: Int -> ReadS StartModelPackagingJob
Prelude.Read, Int -> StartModelPackagingJob -> ShowS
[StartModelPackagingJob] -> ShowS
StartModelPackagingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartModelPackagingJob] -> ShowS
$cshowList :: [StartModelPackagingJob] -> ShowS
show :: StartModelPackagingJob -> String
$cshow :: StartModelPackagingJob -> String
showsPrec :: Int -> StartModelPackagingJob -> ShowS
$cshowsPrec :: Int -> StartModelPackagingJob -> ShowS
Prelude.Show, forall x. Rep StartModelPackagingJob x -> StartModelPackagingJob
forall x. StartModelPackagingJob -> Rep StartModelPackagingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartModelPackagingJob x -> StartModelPackagingJob
$cfrom :: forall x. StartModelPackagingJob -> Rep StartModelPackagingJob x
Prelude.Generic)

-- |
-- Create a value of 'StartModelPackagingJob' 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:
--
-- 'clientToken', 'startModelPackagingJob_clientToken' - ClientToken is an idempotency token that ensures a call to
-- @StartModelPackagingJob@ completes only once. You choose the value to
-- pass. For example, An issue might prevent you from getting a response
-- from @StartModelPackagingJob@. In this case, safely retry your call to
-- @StartModelPackagingJob@ by using the same @ClientToken@ parameter
-- value.
--
-- If you don\'t supply a value for @ClientToken@, the AWS SDK you are
-- using inserts a value for you. This prevents retries after a network
-- error from making multiple dataset creation requests. You\'ll need to
-- provide your own value for other use cases.
--
-- An error occurs if the other input parameters are not the same as in the
-- first request. Using a different value for @ClientToken@ is considered a
-- new call to @StartModelPackagingJob@. An idempotency token is active for
-- 8 hours.
--
-- 'description', 'startModelPackagingJob_description' - A description for the model packaging job.
--
-- 'jobName', 'startModelPackagingJob_jobName' - A name for the model packaging job. If you don\'t supply a value, the
-- service creates a job name for you.
--
-- 'projectName', 'startModelPackagingJob_projectName' - The name of the project which contains the version of the model that you
-- want to package.
--
-- 'modelVersion', 'startModelPackagingJob_modelVersion' - The version of the model within the project that you want to package.
--
-- 'configuration', 'startModelPackagingJob_configuration' - The configuration for the model packaging job.
newStartModelPackagingJob ::
  -- | 'projectName'
  Prelude.Text ->
  -- | 'modelVersion'
  Prelude.Text ->
  -- | 'configuration'
  ModelPackagingConfiguration ->
  StartModelPackagingJob
newStartModelPackagingJob :: Text
-> Text -> ModelPackagingConfiguration -> StartModelPackagingJob
newStartModelPackagingJob
  Text
pProjectName_
  Text
pModelVersion_
  ModelPackagingConfiguration
pConfiguration_ =
    StartModelPackagingJob'
      { $sel:clientToken:StartModelPackagingJob' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:StartModelPackagingJob' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:jobName:StartModelPackagingJob' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
        $sel:projectName:StartModelPackagingJob' :: Text
projectName = Text
pProjectName_,
        $sel:modelVersion:StartModelPackagingJob' :: Text
modelVersion = Text
pModelVersion_,
        $sel:configuration:StartModelPackagingJob' :: ModelPackagingConfiguration
configuration = ModelPackagingConfiguration
pConfiguration_
      }

-- | ClientToken is an idempotency token that ensures a call to
-- @StartModelPackagingJob@ completes only once. You choose the value to
-- pass. For example, An issue might prevent you from getting a response
-- from @StartModelPackagingJob@. In this case, safely retry your call to
-- @StartModelPackagingJob@ by using the same @ClientToken@ parameter
-- value.
--
-- If you don\'t supply a value for @ClientToken@, the AWS SDK you are
-- using inserts a value for you. This prevents retries after a network
-- error from making multiple dataset creation requests. You\'ll need to
-- provide your own value for other use cases.
--
-- An error occurs if the other input parameters are not the same as in the
-- first request. Using a different value for @ClientToken@ is considered a
-- new call to @StartModelPackagingJob@. An idempotency token is active for
-- 8 hours.
startModelPackagingJob_clientToken :: Lens.Lens' StartModelPackagingJob (Prelude.Maybe Prelude.Text)
startModelPackagingJob_clientToken :: Lens' StartModelPackagingJob (Maybe Text)
startModelPackagingJob_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} Maybe Text
a -> StartModelPackagingJob
s {$sel:clientToken:StartModelPackagingJob' :: Maybe Text
clientToken = Maybe Text
a} :: StartModelPackagingJob)

-- | A description for the model packaging job.
startModelPackagingJob_description :: Lens.Lens' StartModelPackagingJob (Prelude.Maybe Prelude.Text)
startModelPackagingJob_description :: Lens' StartModelPackagingJob (Maybe Text)
startModelPackagingJob_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {Maybe Text
description :: Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
description} -> Maybe Text
description) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} Maybe Text
a -> StartModelPackagingJob
s {$sel:description:StartModelPackagingJob' :: Maybe Text
description = Maybe Text
a} :: StartModelPackagingJob)

-- | A name for the model packaging job. If you don\'t supply a value, the
-- service creates a job name for you.
startModelPackagingJob_jobName :: Lens.Lens' StartModelPackagingJob (Prelude.Maybe Prelude.Text)
startModelPackagingJob_jobName :: Lens' StartModelPackagingJob (Maybe Text)
startModelPackagingJob_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {Maybe Text
jobName :: Maybe Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} Maybe Text
a -> StartModelPackagingJob
s {$sel:jobName:StartModelPackagingJob' :: Maybe Text
jobName = Maybe Text
a} :: StartModelPackagingJob)

-- | The name of the project which contains the version of the model that you
-- want to package.
startModelPackagingJob_projectName :: Lens.Lens' StartModelPackagingJob Prelude.Text
startModelPackagingJob_projectName :: Lens' StartModelPackagingJob Text
startModelPackagingJob_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {Text
projectName :: Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
projectName} -> Text
projectName) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} Text
a -> StartModelPackagingJob
s {$sel:projectName:StartModelPackagingJob' :: Text
projectName = Text
a} :: StartModelPackagingJob)

-- | The version of the model within the project that you want to package.
startModelPackagingJob_modelVersion :: Lens.Lens' StartModelPackagingJob Prelude.Text
startModelPackagingJob_modelVersion :: Lens' StartModelPackagingJob Text
startModelPackagingJob_modelVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {Text
modelVersion :: Text
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
modelVersion} -> Text
modelVersion) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} Text
a -> StartModelPackagingJob
s {$sel:modelVersion:StartModelPackagingJob' :: Text
modelVersion = Text
a} :: StartModelPackagingJob)

-- | The configuration for the model packaging job.
startModelPackagingJob_configuration :: Lens.Lens' StartModelPackagingJob ModelPackagingConfiguration
startModelPackagingJob_configuration :: Lens' StartModelPackagingJob ModelPackagingConfiguration
startModelPackagingJob_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJob' {ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
configuration} -> ModelPackagingConfiguration
configuration) (\s :: StartModelPackagingJob
s@StartModelPackagingJob' {} ModelPackagingConfiguration
a -> StartModelPackagingJob
s {$sel:configuration:StartModelPackagingJob' :: ModelPackagingConfiguration
configuration = ModelPackagingConfiguration
a} :: StartModelPackagingJob)

instance Core.AWSRequest StartModelPackagingJob where
  type
    AWSResponse StartModelPackagingJob =
      StartModelPackagingJobResponse
  request :: (Service -> Service)
-> StartModelPackagingJob -> Request StartModelPackagingJob
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 StartModelPackagingJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartModelPackagingJob)))
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 Text -> Int -> StartModelPackagingJobResponse
StartModelPackagingJobResponse'
            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
"JobName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable StartModelPackagingJob where
  hashWithSalt :: Int -> StartModelPackagingJob -> Int
hashWithSalt Int
_salt StartModelPackagingJob' {Maybe Text
Text
ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
modelVersion :: Text
projectName :: Text
jobName :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
modelVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ModelPackagingConfiguration
configuration

instance Prelude.NFData StartModelPackagingJob where
  rnf :: StartModelPackagingJob -> ()
rnf StartModelPackagingJob' {Maybe Text
Text
ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
modelVersion :: Text
projectName :: Text
jobName :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
modelVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ModelPackagingConfiguration
configuration

instance Data.ToHeaders StartModelPackagingJob where
  toHeaders :: StartModelPackagingJob -> ResponseHeaders
toHeaders StartModelPackagingJob' {Maybe Text
Text
ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
modelVersion :: Text
projectName :: Text
jobName :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amzn-Client-Token" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
clientToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON StartModelPackagingJob where
  toJSON :: StartModelPackagingJob -> Value
toJSON StartModelPackagingJob' {Maybe Text
Text
ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
modelVersion :: Text
projectName :: Text
jobName :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (Key
"JobName" 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
jobName,
            forall a. a -> Maybe a
Prelude.Just (Key
"ModelVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
modelVersion),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"Configuration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ModelPackagingConfiguration
configuration)
          ]
      )

instance Data.ToPath StartModelPackagingJob where
  toPath :: StartModelPackagingJob -> ByteString
toPath StartModelPackagingJob' {Maybe Text
Text
ModelPackagingConfiguration
configuration :: ModelPackagingConfiguration
modelVersion :: Text
projectName :: Text
jobName :: Maybe Text
description :: Maybe Text
clientToken :: Maybe Text
$sel:configuration:StartModelPackagingJob' :: StartModelPackagingJob -> ModelPackagingConfiguration
$sel:modelVersion:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:projectName:StartModelPackagingJob' :: StartModelPackagingJob -> Text
$sel:jobName:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:description:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
$sel:clientToken:StartModelPackagingJob' :: StartModelPackagingJob -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-11-20/projects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
projectName,
        ByteString
"/modelpackagingjobs"
      ]

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

-- | /See:/ 'newStartModelPackagingJobResponse' smart constructor.
data StartModelPackagingJobResponse = StartModelPackagingJobResponse'
  { -- | The job name for the model packaging job. If you don\'t supply a job
    -- name in the @JobName@ input parameter, the service creates a job name
    -- for you.
    StartModelPackagingJobResponse -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartModelPackagingJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartModelPackagingJobResponse
-> StartModelPackagingJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartModelPackagingJobResponse
-> StartModelPackagingJobResponse -> Bool
$c/= :: StartModelPackagingJobResponse
-> StartModelPackagingJobResponse -> Bool
== :: StartModelPackagingJobResponse
-> StartModelPackagingJobResponse -> Bool
$c== :: StartModelPackagingJobResponse
-> StartModelPackagingJobResponse -> Bool
Prelude.Eq, ReadPrec [StartModelPackagingJobResponse]
ReadPrec StartModelPackagingJobResponse
Int -> ReadS StartModelPackagingJobResponse
ReadS [StartModelPackagingJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartModelPackagingJobResponse]
$creadListPrec :: ReadPrec [StartModelPackagingJobResponse]
readPrec :: ReadPrec StartModelPackagingJobResponse
$creadPrec :: ReadPrec StartModelPackagingJobResponse
readList :: ReadS [StartModelPackagingJobResponse]
$creadList :: ReadS [StartModelPackagingJobResponse]
readsPrec :: Int -> ReadS StartModelPackagingJobResponse
$creadsPrec :: Int -> ReadS StartModelPackagingJobResponse
Prelude.Read, Int -> StartModelPackagingJobResponse -> ShowS
[StartModelPackagingJobResponse] -> ShowS
StartModelPackagingJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartModelPackagingJobResponse] -> ShowS
$cshowList :: [StartModelPackagingJobResponse] -> ShowS
show :: StartModelPackagingJobResponse -> String
$cshow :: StartModelPackagingJobResponse -> String
showsPrec :: Int -> StartModelPackagingJobResponse -> ShowS
$cshowsPrec :: Int -> StartModelPackagingJobResponse -> ShowS
Prelude.Show, forall x.
Rep StartModelPackagingJobResponse x
-> StartModelPackagingJobResponse
forall x.
StartModelPackagingJobResponse
-> Rep StartModelPackagingJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartModelPackagingJobResponse x
-> StartModelPackagingJobResponse
$cfrom :: forall x.
StartModelPackagingJobResponse
-> Rep StartModelPackagingJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartModelPackagingJobResponse' 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:
--
-- 'jobName', 'startModelPackagingJobResponse_jobName' - The job name for the model packaging job. If you don\'t supply a job
-- name in the @JobName@ input parameter, the service creates a job name
-- for you.
--
-- 'httpStatus', 'startModelPackagingJobResponse_httpStatus' - The response's http status code.
newStartModelPackagingJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartModelPackagingJobResponse
newStartModelPackagingJobResponse :: Int -> StartModelPackagingJobResponse
newStartModelPackagingJobResponse Int
pHttpStatus_ =
  StartModelPackagingJobResponse'
    { $sel:jobName:StartModelPackagingJobResponse' :: Maybe Text
jobName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartModelPackagingJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The job name for the model packaging job. If you don\'t supply a job
-- name in the @JobName@ input parameter, the service creates a job name
-- for you.
startModelPackagingJobResponse_jobName :: Lens.Lens' StartModelPackagingJobResponse (Prelude.Maybe Prelude.Text)
startModelPackagingJobResponse_jobName :: Lens' StartModelPackagingJobResponse (Maybe Text)
startModelPackagingJobResponse_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartModelPackagingJobResponse' {Maybe Text
jobName :: Maybe Text
$sel:jobName:StartModelPackagingJobResponse' :: StartModelPackagingJobResponse -> Maybe Text
jobName} -> Maybe Text
jobName) (\s :: StartModelPackagingJobResponse
s@StartModelPackagingJobResponse' {} Maybe Text
a -> StartModelPackagingJobResponse
s {$sel:jobName:StartModelPackagingJobResponse' :: Maybe Text
jobName = Maybe Text
a} :: StartModelPackagingJobResponse)

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

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