{-# 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.UpdateRobotApplication
-- 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 robot application.
module Amazonka.RobOMaker.UpdateRobotApplication
  ( -- * Creating a Request
    UpdateRobotApplication (..),
    newUpdateRobotApplication,

    -- * Request Lenses
    updateRobotApplication_currentRevisionId,
    updateRobotApplication_environment,
    updateRobotApplication_sources,
    updateRobotApplication_application,
    updateRobotApplication_robotSoftwareSuite,

    -- * Destructuring the Response
    UpdateRobotApplicationResponse (..),
    newUpdateRobotApplicationResponse,

    -- * Response Lenses
    updateRobotApplicationResponse_arn,
    updateRobotApplicationResponse_environment,
    updateRobotApplicationResponse_lastUpdatedAt,
    updateRobotApplicationResponse_name,
    updateRobotApplicationResponse_revisionId,
    updateRobotApplicationResponse_robotSoftwareSuite,
    updateRobotApplicationResponse_sources,
    updateRobotApplicationResponse_version,
    updateRobotApplicationResponse_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:/ 'newUpdateRobotApplication' smart constructor.
data UpdateRobotApplication = UpdateRobotApplication'
  { -- | The revision id for the robot application.
    UpdateRobotApplication -> Maybe Text
currentRevisionId :: Prelude.Maybe Prelude.Text,
    -- | The object that contains the Docker image URI for your robot
    -- application.
    UpdateRobotApplication -> Maybe Environment
environment :: Prelude.Maybe Environment,
    -- | The sources of the robot application.
    UpdateRobotApplication -> Maybe [SourceConfig]
sources :: Prelude.Maybe [SourceConfig],
    -- | The application information for the robot application.
    UpdateRobotApplication -> Text
application :: Prelude.Text,
    -- | The robot software suite (ROS distribution) used by the robot
    -- application.
    UpdateRobotApplication -> RobotSoftwareSuite
robotSoftwareSuite :: RobotSoftwareSuite
  }
  deriving (UpdateRobotApplication -> UpdateRobotApplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRobotApplication -> UpdateRobotApplication -> Bool
$c/= :: UpdateRobotApplication -> UpdateRobotApplication -> Bool
== :: UpdateRobotApplication -> UpdateRobotApplication -> Bool
$c== :: UpdateRobotApplication -> UpdateRobotApplication -> Bool
Prelude.Eq, ReadPrec [UpdateRobotApplication]
ReadPrec UpdateRobotApplication
Int -> ReadS UpdateRobotApplication
ReadS [UpdateRobotApplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRobotApplication]
$creadListPrec :: ReadPrec [UpdateRobotApplication]
readPrec :: ReadPrec UpdateRobotApplication
$creadPrec :: ReadPrec UpdateRobotApplication
readList :: ReadS [UpdateRobotApplication]
$creadList :: ReadS [UpdateRobotApplication]
readsPrec :: Int -> ReadS UpdateRobotApplication
$creadsPrec :: Int -> ReadS UpdateRobotApplication
Prelude.Read, Int -> UpdateRobotApplication -> ShowS
[UpdateRobotApplication] -> ShowS
UpdateRobotApplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRobotApplication] -> ShowS
$cshowList :: [UpdateRobotApplication] -> ShowS
show :: UpdateRobotApplication -> String
$cshow :: UpdateRobotApplication -> String
showsPrec :: Int -> UpdateRobotApplication -> ShowS
$cshowsPrec :: Int -> UpdateRobotApplication -> ShowS
Prelude.Show, forall x. Rep UpdateRobotApplication x -> UpdateRobotApplication
forall x. UpdateRobotApplication -> Rep UpdateRobotApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRobotApplication x -> UpdateRobotApplication
$cfrom :: forall x. UpdateRobotApplication -> Rep UpdateRobotApplication x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRobotApplication' 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', 'updateRobotApplication_currentRevisionId' - The revision id for the robot application.
--
-- 'environment', 'updateRobotApplication_environment' - The object that contains the Docker image URI for your robot
-- application.
--
-- 'sources', 'updateRobotApplication_sources' - The sources of the robot application.
--
-- 'application', 'updateRobotApplication_application' - The application information for the robot application.
--
-- 'robotSoftwareSuite', 'updateRobotApplication_robotSoftwareSuite' - The robot software suite (ROS distribution) used by the robot
-- application.
newUpdateRobotApplication ::
  -- | 'application'
  Prelude.Text ->
  -- | 'robotSoftwareSuite'
  RobotSoftwareSuite ->
  UpdateRobotApplication
newUpdateRobotApplication :: Text -> RobotSoftwareSuite -> UpdateRobotApplication
newUpdateRobotApplication
  Text
pApplication_
  RobotSoftwareSuite
pRobotSoftwareSuite_ =
    UpdateRobotApplication'
      { $sel:currentRevisionId:UpdateRobotApplication' :: Maybe Text
currentRevisionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:environment:UpdateRobotApplication' :: Maybe Environment
environment = forall a. Maybe a
Prelude.Nothing,
        $sel:sources:UpdateRobotApplication' :: Maybe [SourceConfig]
sources = forall a. Maybe a
Prelude.Nothing,
        $sel:application:UpdateRobotApplication' :: Text
application = Text
pApplication_,
        $sel:robotSoftwareSuite:UpdateRobotApplication' :: RobotSoftwareSuite
robotSoftwareSuite = RobotSoftwareSuite
pRobotSoftwareSuite_
      }

-- | The revision id for the robot application.
updateRobotApplication_currentRevisionId :: Lens.Lens' UpdateRobotApplication (Prelude.Maybe Prelude.Text)
updateRobotApplication_currentRevisionId :: Lens' UpdateRobotApplication (Maybe Text)
updateRobotApplication_currentRevisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRobotApplication' {Maybe Text
currentRevisionId :: Maybe Text
$sel:currentRevisionId:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe Text
currentRevisionId} -> Maybe Text
currentRevisionId) (\s :: UpdateRobotApplication
s@UpdateRobotApplication' {} Maybe Text
a -> UpdateRobotApplication
s {$sel:currentRevisionId:UpdateRobotApplication' :: Maybe Text
currentRevisionId = Maybe Text
a} :: UpdateRobotApplication)

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

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

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

instance Core.AWSRequest UpdateRobotApplication where
  type
    AWSResponse UpdateRobotApplication =
      UpdateRobotApplicationResponse
  request :: (Service -> Service)
-> UpdateRobotApplication -> Request UpdateRobotApplication
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 UpdateRobotApplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateRobotApplication)))
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
-> UpdateRobotApplicationResponse
UpdateRobotApplicationResponse'
            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 UpdateRobotApplication where
  hashWithSalt :: Int -> UpdateRobotApplication -> Int
hashWithSalt Int
_salt UpdateRobotApplication' {Maybe [SourceConfig]
Maybe Text
Maybe Environment
Text
RobotSoftwareSuite
robotSoftwareSuite :: RobotSoftwareSuite
application :: Text
sources :: Maybe [SourceConfig]
environment :: Maybe Environment
currentRevisionId :: Maybe Text
$sel:robotSoftwareSuite:UpdateRobotApplication' :: UpdateRobotApplication -> RobotSoftwareSuite
$sel:application:UpdateRobotApplication' :: UpdateRobotApplication -> Text
$sel:sources:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe [SourceConfig]
$sel:environment:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe Environment
$sel:currentRevisionId:UpdateRobotApplication' :: UpdateRobotApplication -> 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 Environment
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SourceConfig]
sources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
application
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RobotSoftwareSuite
robotSoftwareSuite

instance Prelude.NFData UpdateRobotApplication where
  rnf :: UpdateRobotApplication -> ()
rnf UpdateRobotApplication' {Maybe [SourceConfig]
Maybe Text
Maybe Environment
Text
RobotSoftwareSuite
robotSoftwareSuite :: RobotSoftwareSuite
application :: Text
sources :: Maybe [SourceConfig]
environment :: Maybe Environment
currentRevisionId :: Maybe Text
$sel:robotSoftwareSuite:UpdateRobotApplication' :: UpdateRobotApplication -> RobotSoftwareSuite
$sel:application:UpdateRobotApplication' :: UpdateRobotApplication -> Text
$sel:sources:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe [SourceConfig]
$sel:environment:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe Environment
$sel:currentRevisionId:UpdateRobotApplication' :: UpdateRobotApplication -> 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 Environment
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SourceConfig]
sources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
application
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RobotSoftwareSuite
robotSoftwareSuite

instance Data.ToHeaders UpdateRobotApplication where
  toHeaders :: UpdateRobotApplication -> 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 UpdateRobotApplication where
  toJSON :: UpdateRobotApplication -> Value
toJSON UpdateRobotApplication' {Maybe [SourceConfig]
Maybe Text
Maybe Environment
Text
RobotSoftwareSuite
robotSoftwareSuite :: RobotSoftwareSuite
application :: Text
sources :: Maybe [SourceConfig]
environment :: Maybe Environment
currentRevisionId :: Maybe Text
$sel:robotSoftwareSuite:UpdateRobotApplication' :: UpdateRobotApplication -> RobotSoftwareSuite
$sel:application:UpdateRobotApplication' :: UpdateRobotApplication -> Text
$sel:sources:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe [SourceConfig]
$sel:environment:UpdateRobotApplication' :: UpdateRobotApplication -> Maybe Environment
$sel:currentRevisionId:UpdateRobotApplication' :: UpdateRobotApplication -> 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
"environment" 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 Environment
environment,
            (Key
"sources" 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 [SourceConfig]
sources,
            forall a. a -> Maybe a
Prelude.Just (Key
"application" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
application),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"robotSoftwareSuite" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RobotSoftwareSuite
robotSoftwareSuite)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateRobotApplicationResponse' 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', 'updateRobotApplicationResponse_arn' - The Amazon Resource Name (ARN) of the updated robot application.
--
-- 'environment', 'updateRobotApplicationResponse_environment' - The object that contains the Docker image URI for your robot
-- application.
--
-- 'lastUpdatedAt', 'updateRobotApplicationResponse_lastUpdatedAt' - The time, in milliseconds since the epoch, when the robot application
-- was last updated.
--
-- 'name', 'updateRobotApplicationResponse_name' - The name of the robot application.
--
-- 'revisionId', 'updateRobotApplicationResponse_revisionId' - The revision id of the robot application.
--
-- 'robotSoftwareSuite', 'updateRobotApplicationResponse_robotSoftwareSuite' - The robot software suite (ROS distribution) used by the robot
-- application.
--
-- 'sources', 'updateRobotApplicationResponse_sources' - The sources of the robot application.
--
-- 'version', 'updateRobotApplicationResponse_version' - The version of the robot application.
--
-- 'httpStatus', 'updateRobotApplicationResponse_httpStatus' - The response's http status code.
newUpdateRobotApplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRobotApplicationResponse
newUpdateRobotApplicationResponse :: Int -> UpdateRobotApplicationResponse
newUpdateRobotApplicationResponse Int
pHttpStatus_ =
  UpdateRobotApplicationResponse'
    { $sel:arn:UpdateRobotApplicationResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:environment:UpdateRobotApplicationResponse' :: Maybe Environment
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:UpdateRobotApplicationResponse' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateRobotApplicationResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionId:UpdateRobotApplicationResponse' :: Maybe Text
revisionId = forall a. Maybe a
Prelude.Nothing,
      $sel:robotSoftwareSuite:UpdateRobotApplicationResponse' :: Maybe RobotSoftwareSuite
robotSoftwareSuite = forall a. Maybe a
Prelude.Nothing,
      $sel:sources:UpdateRobotApplicationResponse' :: Maybe [Source]
sources = forall a. Maybe a
Prelude.Nothing,
      $sel:version:UpdateRobotApplicationResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRobotApplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | The time, in milliseconds since the epoch, when the robot application
-- was last updated.
updateRobotApplicationResponse_lastUpdatedAt :: Lens.Lens' UpdateRobotApplicationResponse (Prelude.Maybe Prelude.UTCTime)
updateRobotApplicationResponse_lastUpdatedAt :: Lens' UpdateRobotApplicationResponse (Maybe UTCTime)
updateRobotApplicationResponse_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRobotApplicationResponse' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: UpdateRobotApplicationResponse
s@UpdateRobotApplicationResponse' {} Maybe POSIX
a -> UpdateRobotApplicationResponse
s {$sel:lastUpdatedAt:UpdateRobotApplicationResponse' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: UpdateRobotApplicationResponse) 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.
updateRobotApplicationResponse_name :: Lens.Lens' UpdateRobotApplicationResponse (Prelude.Maybe Prelude.Text)
updateRobotApplicationResponse_name :: Lens' UpdateRobotApplicationResponse (Maybe Text)
updateRobotApplicationResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRobotApplicationResponse' {Maybe Text
name :: Maybe Text
$sel:name:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateRobotApplicationResponse
s@UpdateRobotApplicationResponse' {} Maybe Text
a -> UpdateRobotApplicationResponse
s {$sel:name:UpdateRobotApplicationResponse' :: Maybe Text
name = Maybe Text
a} :: UpdateRobotApplicationResponse)

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

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

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

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

instance
  Prelude.NFData
    UpdateRobotApplicationResponse
  where
  rnf :: UpdateRobotApplicationResponse -> ()
rnf UpdateRobotApplicationResponse' {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:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Int
$sel:version:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe Text
$sel:sources:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe [Source]
$sel:robotSoftwareSuite:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe RobotSoftwareSuite
$sel:revisionId:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe Text
$sel:name:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe Text
$sel:lastUpdatedAt:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe POSIX
$sel:environment:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> Maybe Environment
$sel:arn:UpdateRobotApplicationResponse' :: UpdateRobotApplicationResponse -> 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