{-# 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.RobOMaker.CreateRobotApplicationVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a version of a robot application.
module Amazonka.RobOMaker.CreateRobotApplicationVersion
  ( -- * Creating a Request
    CreateRobotApplicationVersion (..),
    newCreateRobotApplicationVersion,

    -- * Request Lenses
    createRobotApplicationVersion_currentRevisionId,
    createRobotApplicationVersion_imageDigest,
    createRobotApplicationVersion_s3Etags,
    createRobotApplicationVersion_application,

    -- * Destructuring the Response
    CreateRobotApplicationVersionResponse (..),
    newCreateRobotApplicationVersionResponse,

    -- * Response Lenses
    createRobotApplicationVersionResponse_arn,
    createRobotApplicationVersionResponse_environment,
    createRobotApplicationVersionResponse_lastUpdatedAt,
    createRobotApplicationVersionResponse_name,
    createRobotApplicationVersionResponse_revisionId,
    createRobotApplicationVersionResponse_robotSoftwareSuite,
    createRobotApplicationVersionResponse_sources,
    createRobotApplicationVersionResponse_version,
    createRobotApplicationVersionResponse_httpStatus,
  )
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.RobOMaker.Types

-- | /See:/ 'newCreateRobotApplicationVersion' smart constructor.
data CreateRobotApplicationVersion = CreateRobotApplicationVersion'
  { -- | The current revision id for the robot application. If you provide a
    -- value and it matches the latest revision ID, a new version will be
    -- created.
    CreateRobotApplicationVersion -> Maybe Text
currentRevisionId :: Prelude.Maybe Prelude.Text,
    -- | A SHA256 identifier for the Docker image that you use for your robot
    -- application.
    CreateRobotApplicationVersion -> Maybe Text
imageDigest :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 identifier for the zip file bundle that you use for your
    -- robot application.
    CreateRobotApplicationVersion -> Maybe [Text]
s3Etags :: Prelude.Maybe [Prelude.Text],
    -- | The application information for the robot application.
    CreateRobotApplicationVersion -> Text
application :: Prelude.Text
  }
  deriving (CreateRobotApplicationVersion
-> CreateRobotApplicationVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRobotApplicationVersion
-> CreateRobotApplicationVersion -> Bool
$c/= :: CreateRobotApplicationVersion
-> CreateRobotApplicationVersion -> Bool
== :: CreateRobotApplicationVersion
-> CreateRobotApplicationVersion -> Bool
$c== :: CreateRobotApplicationVersion
-> CreateRobotApplicationVersion -> Bool
Prelude.Eq, ReadPrec [CreateRobotApplicationVersion]
ReadPrec CreateRobotApplicationVersion
Int -> ReadS CreateRobotApplicationVersion
ReadS [CreateRobotApplicationVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRobotApplicationVersion]
$creadListPrec :: ReadPrec [CreateRobotApplicationVersion]
readPrec :: ReadPrec CreateRobotApplicationVersion
$creadPrec :: ReadPrec CreateRobotApplicationVersion
readList :: ReadS [CreateRobotApplicationVersion]
$creadList :: ReadS [CreateRobotApplicationVersion]
readsPrec :: Int -> ReadS CreateRobotApplicationVersion
$creadsPrec :: Int -> ReadS CreateRobotApplicationVersion
Prelude.Read, Int -> CreateRobotApplicationVersion -> ShowS
[CreateRobotApplicationVersion] -> ShowS
CreateRobotApplicationVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRobotApplicationVersion] -> ShowS
$cshowList :: [CreateRobotApplicationVersion] -> ShowS
show :: CreateRobotApplicationVersion -> String
$cshow :: CreateRobotApplicationVersion -> String
showsPrec :: Int -> CreateRobotApplicationVersion -> ShowS
$cshowsPrec :: Int -> CreateRobotApplicationVersion -> ShowS
Prelude.Show, forall x.
Rep CreateRobotApplicationVersion x
-> CreateRobotApplicationVersion
forall x.
CreateRobotApplicationVersion
-> Rep CreateRobotApplicationVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateRobotApplicationVersion x
-> CreateRobotApplicationVersion
$cfrom :: forall x.
CreateRobotApplicationVersion
-> Rep CreateRobotApplicationVersion x
Prelude.Generic)

-- |
-- Create a value of 'CreateRobotApplicationVersion' 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:
--
-- 'currentRevisionId', 'createRobotApplicationVersion_currentRevisionId' - The current revision id for the robot application. If you provide a
-- value and it matches the latest revision ID, a new version will be
-- created.
--
-- 'imageDigest', 'createRobotApplicationVersion_imageDigest' - A SHA256 identifier for the Docker image that you use for your robot
-- application.
--
-- 's3Etags', 'createRobotApplicationVersion_s3Etags' - The Amazon S3 identifier for the zip file bundle that you use for your
-- robot application.
--
-- 'application', 'createRobotApplicationVersion_application' - The application information for the robot application.
newCreateRobotApplicationVersion ::
  -- | 'application'
  Prelude.Text ->
  CreateRobotApplicationVersion
newCreateRobotApplicationVersion :: Text -> CreateRobotApplicationVersion
newCreateRobotApplicationVersion Text
pApplication_ =
  CreateRobotApplicationVersion'
    { $sel:currentRevisionId:CreateRobotApplicationVersion' :: Maybe Text
currentRevisionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:imageDigest:CreateRobotApplicationVersion' :: Maybe Text
imageDigest = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Etags:CreateRobotApplicationVersion' :: Maybe [Text]
s3Etags = forall a. Maybe a
Prelude.Nothing,
      $sel:application:CreateRobotApplicationVersion' :: Text
application = Text
pApplication_
    }

-- | The current revision id for the robot application. If you provide a
-- value and it matches the latest revision ID, a new version will be
-- created.
createRobotApplicationVersion_currentRevisionId :: Lens.Lens' CreateRobotApplicationVersion (Prelude.Maybe Prelude.Text)
createRobotApplicationVersion_currentRevisionId :: Lens' CreateRobotApplicationVersion (Maybe Text)
createRobotApplicationVersion_currentRevisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersion' {Maybe Text
currentRevisionId :: Maybe Text
$sel:currentRevisionId:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
currentRevisionId} -> Maybe Text
currentRevisionId) (\s :: CreateRobotApplicationVersion
s@CreateRobotApplicationVersion' {} Maybe Text
a -> CreateRobotApplicationVersion
s {$sel:currentRevisionId:CreateRobotApplicationVersion' :: Maybe Text
currentRevisionId = Maybe Text
a} :: CreateRobotApplicationVersion)

-- | A SHA256 identifier for the Docker image that you use for your robot
-- application.
createRobotApplicationVersion_imageDigest :: Lens.Lens' CreateRobotApplicationVersion (Prelude.Maybe Prelude.Text)
createRobotApplicationVersion_imageDigest :: Lens' CreateRobotApplicationVersion (Maybe Text)
createRobotApplicationVersion_imageDigest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersion' {Maybe Text
imageDigest :: Maybe Text
$sel:imageDigest:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
imageDigest} -> Maybe Text
imageDigest) (\s :: CreateRobotApplicationVersion
s@CreateRobotApplicationVersion' {} Maybe Text
a -> CreateRobotApplicationVersion
s {$sel:imageDigest:CreateRobotApplicationVersion' :: Maybe Text
imageDigest = Maybe Text
a} :: CreateRobotApplicationVersion)

-- | The Amazon S3 identifier for the zip file bundle that you use for your
-- robot application.
createRobotApplicationVersion_s3Etags :: Lens.Lens' CreateRobotApplicationVersion (Prelude.Maybe [Prelude.Text])
createRobotApplicationVersion_s3Etags :: Lens' CreateRobotApplicationVersion (Maybe [Text])
createRobotApplicationVersion_s3Etags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersion' {Maybe [Text]
s3Etags :: Maybe [Text]
$sel:s3Etags:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe [Text]
s3Etags} -> Maybe [Text]
s3Etags) (\s :: CreateRobotApplicationVersion
s@CreateRobotApplicationVersion' {} Maybe [Text]
a -> CreateRobotApplicationVersion
s {$sel:s3Etags:CreateRobotApplicationVersion' :: Maybe [Text]
s3Etags = Maybe [Text]
a} :: CreateRobotApplicationVersion) 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 application information for the robot application.
createRobotApplicationVersion_application :: Lens.Lens' CreateRobotApplicationVersion Prelude.Text
createRobotApplicationVersion_application :: Lens' CreateRobotApplicationVersion Text
createRobotApplicationVersion_application = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersion' {Text
application :: Text
$sel:application:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Text
application} -> Text
application) (\s :: CreateRobotApplicationVersion
s@CreateRobotApplicationVersion' {} Text
a -> CreateRobotApplicationVersion
s {$sel:application:CreateRobotApplicationVersion' :: Text
application = Text
a} :: CreateRobotApplicationVersion)

instance
  Core.AWSRequest
    CreateRobotApplicationVersion
  where
  type
    AWSResponse CreateRobotApplicationVersion =
      CreateRobotApplicationVersionResponse
  request :: (Service -> Service)
-> CreateRobotApplicationVersion
-> Request CreateRobotApplicationVersion
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 CreateRobotApplicationVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateRobotApplicationVersion)))
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
-> Maybe Environment
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe RobotSoftwareSuite
-> Maybe [Source]
-> Maybe Text
-> Int
-> CreateRobotApplicationVersionResponse
CreateRobotApplicationVersionResponse'
            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
"arn")
            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
"environment")
            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
"lastUpdatedAt")
            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
"name")
            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
"revisionId")
            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
"robotSoftwareSuite")
            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
"sources" 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
"version")
            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
    CreateRobotApplicationVersion
  where
  hashWithSalt :: Int -> CreateRobotApplicationVersion -> Int
hashWithSalt Int
_salt CreateRobotApplicationVersion' {Maybe [Text]
Maybe Text
Text
application :: Text
s3Etags :: Maybe [Text]
imageDigest :: Maybe Text
currentRevisionId :: Maybe Text
$sel:application:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Text
$sel:s3Etags:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe [Text]
$sel:imageDigest:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
$sel:currentRevisionId:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentRevisionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
imageDigest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
s3Etags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
application

instance Prelude.NFData CreateRobotApplicationVersion where
  rnf :: CreateRobotApplicationVersion -> ()
rnf CreateRobotApplicationVersion' {Maybe [Text]
Maybe Text
Text
application :: Text
s3Etags :: Maybe [Text]
imageDigest :: Maybe Text
currentRevisionId :: Maybe Text
$sel:application:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Text
$sel:s3Etags:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe [Text]
$sel:imageDigest:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
$sel:currentRevisionId:CreateRobotApplicationVersion' :: CreateRobotApplicationVersion -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
currentRevisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
imageDigest
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
s3Etags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
application

instance Data.ToHeaders CreateRobotApplicationVersion where
  toHeaders :: CreateRobotApplicationVersion -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | /See:/ 'newCreateRobotApplicationVersionResponse' smart constructor.
data CreateRobotApplicationVersionResponse = CreateRobotApplicationVersionResponse'
  { -- | The Amazon Resource Name (ARN) of the robot application.
    CreateRobotApplicationVersionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The object that contains the Docker image URI used to create your robot
    -- application.
    CreateRobotApplicationVersionResponse -> Maybe Environment
environment :: Prelude.Maybe Environment,
    -- | The time, in milliseconds since the epoch, when the robot application
    -- was last updated.
    CreateRobotApplicationVersionResponse -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | The name of the robot application.
    CreateRobotApplicationVersionResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The revision id of the robot application.
    CreateRobotApplicationVersionResponse -> Maybe Text
revisionId :: Prelude.Maybe Prelude.Text,
    -- | The robot software suite (ROS distribution) used by the robot
    -- application.
    CreateRobotApplicationVersionResponse -> Maybe RobotSoftwareSuite
robotSoftwareSuite :: Prelude.Maybe RobotSoftwareSuite,
    -- | The sources of the robot application.
    CreateRobotApplicationVersionResponse -> Maybe [Source]
sources :: Prelude.Maybe [Source],
    -- | The version of the robot application.
    CreateRobotApplicationVersionResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateRobotApplicationVersionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateRobotApplicationVersionResponse
-> CreateRobotApplicationVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRobotApplicationVersionResponse
-> CreateRobotApplicationVersionResponse -> Bool
$c/= :: CreateRobotApplicationVersionResponse
-> CreateRobotApplicationVersionResponse -> Bool
== :: CreateRobotApplicationVersionResponse
-> CreateRobotApplicationVersionResponse -> Bool
$c== :: CreateRobotApplicationVersionResponse
-> CreateRobotApplicationVersionResponse -> Bool
Prelude.Eq, ReadPrec [CreateRobotApplicationVersionResponse]
ReadPrec CreateRobotApplicationVersionResponse
Int -> ReadS CreateRobotApplicationVersionResponse
ReadS [CreateRobotApplicationVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRobotApplicationVersionResponse]
$creadListPrec :: ReadPrec [CreateRobotApplicationVersionResponse]
readPrec :: ReadPrec CreateRobotApplicationVersionResponse
$creadPrec :: ReadPrec CreateRobotApplicationVersionResponse
readList :: ReadS [CreateRobotApplicationVersionResponse]
$creadList :: ReadS [CreateRobotApplicationVersionResponse]
readsPrec :: Int -> ReadS CreateRobotApplicationVersionResponse
$creadsPrec :: Int -> ReadS CreateRobotApplicationVersionResponse
Prelude.Read, Int -> CreateRobotApplicationVersionResponse -> ShowS
[CreateRobotApplicationVersionResponse] -> ShowS
CreateRobotApplicationVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRobotApplicationVersionResponse] -> ShowS
$cshowList :: [CreateRobotApplicationVersionResponse] -> ShowS
show :: CreateRobotApplicationVersionResponse -> String
$cshow :: CreateRobotApplicationVersionResponse -> String
showsPrec :: Int -> CreateRobotApplicationVersionResponse -> ShowS
$cshowsPrec :: Int -> CreateRobotApplicationVersionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateRobotApplicationVersionResponse x
-> CreateRobotApplicationVersionResponse
forall x.
CreateRobotApplicationVersionResponse
-> Rep CreateRobotApplicationVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateRobotApplicationVersionResponse x
-> CreateRobotApplicationVersionResponse
$cfrom :: forall x.
CreateRobotApplicationVersionResponse
-> Rep CreateRobotApplicationVersionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRobotApplicationVersionResponse' 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:
--
-- 'arn', 'createRobotApplicationVersionResponse_arn' - The Amazon Resource Name (ARN) of the robot application.
--
-- 'environment', 'createRobotApplicationVersionResponse_environment' - The object that contains the Docker image URI used to create your robot
-- application.
--
-- 'lastUpdatedAt', 'createRobotApplicationVersionResponse_lastUpdatedAt' - The time, in milliseconds since the epoch, when the robot application
-- was last updated.
--
-- 'name', 'createRobotApplicationVersionResponse_name' - The name of the robot application.
--
-- 'revisionId', 'createRobotApplicationVersionResponse_revisionId' - The revision id of the robot application.
--
-- 'robotSoftwareSuite', 'createRobotApplicationVersionResponse_robotSoftwareSuite' - The robot software suite (ROS distribution) used by the robot
-- application.
--
-- 'sources', 'createRobotApplicationVersionResponse_sources' - The sources of the robot application.
--
-- 'version', 'createRobotApplicationVersionResponse_version' - The version of the robot application.
--
-- 'httpStatus', 'createRobotApplicationVersionResponse_httpStatus' - The response's http status code.
newCreateRobotApplicationVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRobotApplicationVersionResponse
newCreateRobotApplicationVersionResponse :: Int -> CreateRobotApplicationVersionResponse
newCreateRobotApplicationVersionResponse Int
pHttpStatus_ =
  CreateRobotApplicationVersionResponse'
    { $sel:arn:CreateRobotApplicationVersionResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:environment:CreateRobotApplicationVersionResponse' :: Maybe Environment
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:CreateRobotApplicationVersionResponse' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateRobotApplicationVersionResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionId:CreateRobotApplicationVersionResponse' :: Maybe Text
revisionId = forall a. Maybe a
Prelude.Nothing,
      $sel:robotSoftwareSuite:CreateRobotApplicationVersionResponse' :: Maybe RobotSoftwareSuite
robotSoftwareSuite = forall a. Maybe a
Prelude.Nothing,
      $sel:sources:CreateRobotApplicationVersionResponse' :: Maybe [Source]
sources = forall a. Maybe a
Prelude.Nothing,
      $sel:version:CreateRobotApplicationVersionResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRobotApplicationVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the robot application.
createRobotApplicationVersionResponse_arn :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Prelude.Text)
createRobotApplicationVersionResponse_arn :: Lens' CreateRobotApplicationVersionResponse (Maybe Text)
createRobotApplicationVersionResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe Text
a -> CreateRobotApplicationVersionResponse
s {$sel:arn:CreateRobotApplicationVersionResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateRobotApplicationVersionResponse)

-- | The object that contains the Docker image URI used to create your robot
-- application.
createRobotApplicationVersionResponse_environment :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Environment)
createRobotApplicationVersionResponse_environment :: Lens' CreateRobotApplicationVersionResponse (Maybe Environment)
createRobotApplicationVersionResponse_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe Environment
environment :: Maybe Environment
$sel:environment:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Environment
environment} -> Maybe Environment
environment) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe Environment
a -> CreateRobotApplicationVersionResponse
s {$sel:environment:CreateRobotApplicationVersionResponse' :: Maybe Environment
environment = Maybe Environment
a} :: CreateRobotApplicationVersionResponse)

-- | The time, in milliseconds since the epoch, when the robot application
-- was last updated.
createRobotApplicationVersionResponse_lastUpdatedAt :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Prelude.UTCTime)
createRobotApplicationVersionResponse_lastUpdatedAt :: Lens' CreateRobotApplicationVersionResponse (Maybe UTCTime)
createRobotApplicationVersionResponse_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe POSIX
a -> CreateRobotApplicationVersionResponse
s {$sel:lastUpdatedAt:CreateRobotApplicationVersionResponse' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: CreateRobotApplicationVersionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of the robot application.
createRobotApplicationVersionResponse_name :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Prelude.Text)
createRobotApplicationVersionResponse_name :: Lens' CreateRobotApplicationVersionResponse (Maybe Text)
createRobotApplicationVersionResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe Text
a -> CreateRobotApplicationVersionResponse
s {$sel:name:CreateRobotApplicationVersionResponse' :: Maybe Text
name = Maybe Text
a} :: CreateRobotApplicationVersionResponse)

-- | The revision id of the robot application.
createRobotApplicationVersionResponse_revisionId :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Prelude.Text)
createRobotApplicationVersionResponse_revisionId :: Lens' CreateRobotApplicationVersionResponse (Maybe Text)
createRobotApplicationVersionResponse_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe Text
revisionId :: Maybe Text
$sel:revisionId:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
revisionId} -> Maybe Text
revisionId) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe Text
a -> CreateRobotApplicationVersionResponse
s {$sel:revisionId:CreateRobotApplicationVersionResponse' :: Maybe Text
revisionId = Maybe Text
a} :: CreateRobotApplicationVersionResponse)

-- | The robot software suite (ROS distribution) used by the robot
-- application.
createRobotApplicationVersionResponse_robotSoftwareSuite :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe RobotSoftwareSuite)
createRobotApplicationVersionResponse_robotSoftwareSuite :: Lens'
  CreateRobotApplicationVersionResponse (Maybe RobotSoftwareSuite)
createRobotApplicationVersionResponse_robotSoftwareSuite = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe RobotSoftwareSuite
robotSoftwareSuite :: Maybe RobotSoftwareSuite
$sel:robotSoftwareSuite:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe RobotSoftwareSuite
robotSoftwareSuite} -> Maybe RobotSoftwareSuite
robotSoftwareSuite) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe RobotSoftwareSuite
a -> CreateRobotApplicationVersionResponse
s {$sel:robotSoftwareSuite:CreateRobotApplicationVersionResponse' :: Maybe RobotSoftwareSuite
robotSoftwareSuite = Maybe RobotSoftwareSuite
a} :: CreateRobotApplicationVersionResponse)

-- | The sources of the robot application.
createRobotApplicationVersionResponse_sources :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe [Source])
createRobotApplicationVersionResponse_sources :: Lens' CreateRobotApplicationVersionResponse (Maybe [Source])
createRobotApplicationVersionResponse_sources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe [Source]
sources :: Maybe [Source]
$sel:sources:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe [Source]
sources} -> Maybe [Source]
sources) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe [Source]
a -> CreateRobotApplicationVersionResponse
s {$sel:sources:CreateRobotApplicationVersionResponse' :: Maybe [Source]
sources = Maybe [Source]
a} :: CreateRobotApplicationVersionResponse) 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 version of the robot application.
createRobotApplicationVersionResponse_version :: Lens.Lens' CreateRobotApplicationVersionResponse (Prelude.Maybe Prelude.Text)
createRobotApplicationVersionResponse_version :: Lens' CreateRobotApplicationVersionResponse (Maybe Text)
createRobotApplicationVersionResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRobotApplicationVersionResponse' {Maybe Text
version :: Maybe Text
$sel:version:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: CreateRobotApplicationVersionResponse
s@CreateRobotApplicationVersionResponse' {} Maybe Text
a -> CreateRobotApplicationVersionResponse
s {$sel:version:CreateRobotApplicationVersionResponse' :: Maybe Text
version = Maybe Text
a} :: CreateRobotApplicationVersionResponse)

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

instance
  Prelude.NFData
    CreateRobotApplicationVersionResponse
  where
  rnf :: CreateRobotApplicationVersionResponse -> ()
rnf CreateRobotApplicationVersionResponse' {Int
Maybe [Source]
Maybe Text
Maybe POSIX
Maybe Environment
Maybe RobotSoftwareSuite
httpStatus :: Int
version :: Maybe Text
sources :: Maybe [Source]
robotSoftwareSuite :: Maybe RobotSoftwareSuite
revisionId :: Maybe Text
name :: Maybe Text
lastUpdatedAt :: Maybe POSIX
environment :: Maybe Environment
arn :: Maybe Text
$sel:httpStatus:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Int
$sel:version:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
$sel:sources:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe [Source]
$sel:robotSoftwareSuite:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe RobotSoftwareSuite
$sel:revisionId:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
$sel:name:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
$sel:lastUpdatedAt:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe POSIX
$sel:environment:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Environment
$sel:arn:CreateRobotApplicationVersionResponse' :: CreateRobotApplicationVersionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Environment
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
revisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RobotSoftwareSuite
robotSoftwareSuite
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Source]
sources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus