{-# 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.M2.UpdateEnvironment
-- 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 the configuration details for a specific runtime environment.
module Amazonka.M2.UpdateEnvironment
  ( -- * Creating a Request
    UpdateEnvironment (..),
    newUpdateEnvironment,

    -- * Request Lenses
    updateEnvironment_applyDuringMaintenanceWindow,
    updateEnvironment_desiredCapacity,
    updateEnvironment_engineVersion,
    updateEnvironment_instanceType,
    updateEnvironment_preferredMaintenanceWindow,
    updateEnvironment_environmentId,

    -- * Destructuring the Response
    UpdateEnvironmentResponse (..),
    newUpdateEnvironmentResponse,

    -- * Response Lenses
    updateEnvironmentResponse_httpStatus,
    updateEnvironmentResponse_environmentId,
  )
where

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

-- | /See:/ 'newUpdateEnvironment' smart constructor.
data UpdateEnvironment = UpdateEnvironment'
  { -- | Indicates whether to update the runtime environment during the
    -- maintenance window. The default is false. Currently, Amazon Web Services
    -- Mainframe Modernization accepts the @engineVersion@ parameter only if
    -- @applyDuringMaintenanceWindow@ is true. If any parameter other than
    -- @engineVersion@ is provided in @UpdateEnvironmentRequest@, it will fail
    -- if @applyDuringMaintenanceWindow@ is set to true.
    UpdateEnvironment -> Maybe Bool
applyDuringMaintenanceWindow :: Prelude.Maybe Prelude.Bool,
    -- | The desired capacity for the runtime environment to update.
    UpdateEnvironment -> Maybe Natural
desiredCapacity :: Prelude.Maybe Prelude.Natural,
    -- | The version of the runtime engine for the runtime environment.
    UpdateEnvironment -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The instance type for the runtime environment to update.
    UpdateEnvironment -> Maybe Text
instanceType :: Prelude.Maybe Prelude.Text,
    -- | Configures the maintenance window you want for the runtime environment.
    -- If you do not provide a value, a random system-generated value will be
    -- assigned.
    UpdateEnvironment -> Maybe Text
preferredMaintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the runtime environment that you want to
    -- update.
    UpdateEnvironment -> Text
environmentId :: Prelude.Text
  }
  deriving (UpdateEnvironment -> UpdateEnvironment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEnvironment -> UpdateEnvironment -> Bool
$c/= :: UpdateEnvironment -> UpdateEnvironment -> Bool
== :: UpdateEnvironment -> UpdateEnvironment -> Bool
$c== :: UpdateEnvironment -> UpdateEnvironment -> Bool
Prelude.Eq, ReadPrec [UpdateEnvironment]
ReadPrec UpdateEnvironment
Int -> ReadS UpdateEnvironment
ReadS [UpdateEnvironment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEnvironment]
$creadListPrec :: ReadPrec [UpdateEnvironment]
readPrec :: ReadPrec UpdateEnvironment
$creadPrec :: ReadPrec UpdateEnvironment
readList :: ReadS [UpdateEnvironment]
$creadList :: ReadS [UpdateEnvironment]
readsPrec :: Int -> ReadS UpdateEnvironment
$creadsPrec :: Int -> ReadS UpdateEnvironment
Prelude.Read, Int -> UpdateEnvironment -> ShowS
[UpdateEnvironment] -> ShowS
UpdateEnvironment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEnvironment] -> ShowS
$cshowList :: [UpdateEnvironment] -> ShowS
show :: UpdateEnvironment -> String
$cshow :: UpdateEnvironment -> String
showsPrec :: Int -> UpdateEnvironment -> ShowS
$cshowsPrec :: Int -> UpdateEnvironment -> ShowS
Prelude.Show, forall x. Rep UpdateEnvironment x -> UpdateEnvironment
forall x. UpdateEnvironment -> Rep UpdateEnvironment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEnvironment x -> UpdateEnvironment
$cfrom :: forall x. UpdateEnvironment -> Rep UpdateEnvironment x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEnvironment' 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:
--
-- 'applyDuringMaintenanceWindow', 'updateEnvironment_applyDuringMaintenanceWindow' - Indicates whether to update the runtime environment during the
-- maintenance window. The default is false. Currently, Amazon Web Services
-- Mainframe Modernization accepts the @engineVersion@ parameter only if
-- @applyDuringMaintenanceWindow@ is true. If any parameter other than
-- @engineVersion@ is provided in @UpdateEnvironmentRequest@, it will fail
-- if @applyDuringMaintenanceWindow@ is set to true.
--
-- 'desiredCapacity', 'updateEnvironment_desiredCapacity' - The desired capacity for the runtime environment to update.
--
-- 'engineVersion', 'updateEnvironment_engineVersion' - The version of the runtime engine for the runtime environment.
--
-- 'instanceType', 'updateEnvironment_instanceType' - The instance type for the runtime environment to update.
--
-- 'preferredMaintenanceWindow', 'updateEnvironment_preferredMaintenanceWindow' - Configures the maintenance window you want for the runtime environment.
-- If you do not provide a value, a random system-generated value will be
-- assigned.
--
-- 'environmentId', 'updateEnvironment_environmentId' - The unique identifier of the runtime environment that you want to
-- update.
newUpdateEnvironment ::
  -- | 'environmentId'
  Prelude.Text ->
  UpdateEnvironment
newUpdateEnvironment :: Text -> UpdateEnvironment
newUpdateEnvironment Text
pEnvironmentId_ =
  UpdateEnvironment'
    { $sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: Maybe Bool
applyDuringMaintenanceWindow =
        forall a. Maybe a
Prelude.Nothing,
      $sel:desiredCapacity:UpdateEnvironment' :: Maybe Natural
desiredCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:UpdateEnvironment' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:UpdateEnvironment' :: Maybe Text
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredMaintenanceWindow:UpdateEnvironment' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:UpdateEnvironment' :: Text
environmentId = Text
pEnvironmentId_
    }

-- | Indicates whether to update the runtime environment during the
-- maintenance window. The default is false. Currently, Amazon Web Services
-- Mainframe Modernization accepts the @engineVersion@ parameter only if
-- @applyDuringMaintenanceWindow@ is true. If any parameter other than
-- @engineVersion@ is provided in @UpdateEnvironmentRequest@, it will fail
-- if @applyDuringMaintenanceWindow@ is set to true.
updateEnvironment_applyDuringMaintenanceWindow :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Bool)
updateEnvironment_applyDuringMaintenanceWindow :: Lens' UpdateEnvironment (Maybe Bool)
updateEnvironment_applyDuringMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Bool
applyDuringMaintenanceWindow :: Maybe Bool
$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Bool
applyDuringMaintenanceWindow} -> Maybe Bool
applyDuringMaintenanceWindow) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Bool
a -> UpdateEnvironment
s {$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: Maybe Bool
applyDuringMaintenanceWindow = Maybe Bool
a} :: UpdateEnvironment)

-- | The desired capacity for the runtime environment to update.
updateEnvironment_desiredCapacity :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Natural)
updateEnvironment_desiredCapacity :: Lens' UpdateEnvironment (Maybe Natural)
updateEnvironment_desiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Natural
desiredCapacity :: Maybe Natural
$sel:desiredCapacity:UpdateEnvironment' :: UpdateEnvironment -> Maybe Natural
desiredCapacity} -> Maybe Natural
desiredCapacity) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Natural
a -> UpdateEnvironment
s {$sel:desiredCapacity:UpdateEnvironment' :: Maybe Natural
desiredCapacity = Maybe Natural
a} :: UpdateEnvironment)

-- | The version of the runtime engine for the runtime environment.
updateEnvironment_engineVersion :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_engineVersion :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:engineVersion:UpdateEnvironment' :: Maybe Text
engineVersion = Maybe Text
a} :: UpdateEnvironment)

-- | The instance type for the runtime environment to update.
updateEnvironment_instanceType :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_instanceType :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
instanceType :: Maybe Text
$sel:instanceType:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
instanceType} -> Maybe Text
instanceType) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:instanceType:UpdateEnvironment' :: Maybe Text
instanceType = Maybe Text
a} :: UpdateEnvironment)

-- | Configures the maintenance window you want for the runtime environment.
-- If you do not provide a value, a random system-generated value will be
-- assigned.
updateEnvironment_preferredMaintenanceWindow :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_preferredMaintenanceWindow :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:preferredMaintenanceWindow:UpdateEnvironment' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: UpdateEnvironment)

-- | The unique identifier of the runtime environment that you want to
-- update.
updateEnvironment_environmentId :: Lens.Lens' UpdateEnvironment Prelude.Text
updateEnvironment_environmentId :: Lens' UpdateEnvironment Text
updateEnvironment_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Text
environmentId :: Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
environmentId} -> Text
environmentId) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Text
a -> UpdateEnvironment
s {$sel:environmentId:UpdateEnvironment' :: Text
environmentId = Text
a} :: UpdateEnvironment)

instance Core.AWSRequest UpdateEnvironment where
  type
    AWSResponse UpdateEnvironment =
      UpdateEnvironmentResponse
  request :: (Service -> Service)
-> UpdateEnvironment -> Request UpdateEnvironment
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateEnvironment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateEnvironment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> Text -> UpdateEnvironmentResponse
UpdateEnvironmentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"environmentId")
      )

instance Prelude.Hashable UpdateEnvironment where
  hashWithSalt :: Int -> UpdateEnvironment -> Int
hashWithSalt Int
_salt UpdateEnvironment' {Maybe Bool
Maybe Natural
Maybe Text
Text
environmentId :: Text
preferredMaintenanceWindow :: Maybe Text
instanceType :: Maybe Text
engineVersion :: Maybe Text
desiredCapacity :: Maybe Natural
applyDuringMaintenanceWindow :: Maybe Bool
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:preferredMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:instanceType:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:engineVersion:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:desiredCapacity:UpdateEnvironment' :: UpdateEnvironment -> Maybe Natural
$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
applyDuringMaintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
desiredCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredMaintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentId

instance Prelude.NFData UpdateEnvironment where
  rnf :: UpdateEnvironment -> ()
rnf UpdateEnvironment' {Maybe Bool
Maybe Natural
Maybe Text
Text
environmentId :: Text
preferredMaintenanceWindow :: Maybe Text
instanceType :: Maybe Text
engineVersion :: Maybe Text
desiredCapacity :: Maybe Natural
applyDuringMaintenanceWindow :: Maybe Bool
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:preferredMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:instanceType:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:engineVersion:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:desiredCapacity:UpdateEnvironment' :: UpdateEnvironment -> Maybe Natural
$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
applyDuringMaintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
desiredCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
preferredMaintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentId

instance Data.ToHeaders UpdateEnvironment where
  toHeaders :: UpdateEnvironment -> 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 UpdateEnvironment where
  toJSON :: UpdateEnvironment -> Value
toJSON UpdateEnvironment' {Maybe Bool
Maybe Natural
Maybe Text
Text
environmentId :: Text
preferredMaintenanceWindow :: Maybe Text
instanceType :: Maybe Text
engineVersion :: Maybe Text
desiredCapacity :: Maybe Natural
applyDuringMaintenanceWindow :: Maybe Bool
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:preferredMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:instanceType:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:engineVersion:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:desiredCapacity:UpdateEnvironment' :: UpdateEnvironment -> Maybe Natural
$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"applyDuringMaintenanceWindow" 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 Bool
applyDuringMaintenanceWindow,
            (Key
"desiredCapacity" 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 Natural
desiredCapacity,
            (Key
"engineVersion" 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
engineVersion,
            (Key
"instanceType" 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
instanceType,
            (Key
"preferredMaintenanceWindow" 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
preferredMaintenanceWindow
          ]
      )

instance Data.ToPath UpdateEnvironment where
  toPath :: UpdateEnvironment -> ByteString
toPath UpdateEnvironment' {Maybe Bool
Maybe Natural
Maybe Text
Text
environmentId :: Text
preferredMaintenanceWindow :: Maybe Text
instanceType :: Maybe Text
engineVersion :: Maybe Text
desiredCapacity :: Maybe Natural
applyDuringMaintenanceWindow :: Maybe Bool
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:preferredMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:instanceType:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:engineVersion:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:desiredCapacity:UpdateEnvironment' :: UpdateEnvironment -> Maybe Natural
$sel:applyDuringMaintenanceWindow:UpdateEnvironment' :: UpdateEnvironment -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/environments/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentId]

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

-- | /See:/ 'newUpdateEnvironmentResponse' smart constructor.
data UpdateEnvironmentResponse = UpdateEnvironmentResponse'
  { -- | The response's http status code.
    UpdateEnvironmentResponse -> Int
httpStatus :: Prelude.Int,
    -- | The unique identifier of the runtime environment that was updated.
    UpdateEnvironmentResponse -> Text
environmentId :: Prelude.Text
  }
  deriving (UpdateEnvironmentResponse -> UpdateEnvironmentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEnvironmentResponse -> UpdateEnvironmentResponse -> Bool
$c/= :: UpdateEnvironmentResponse -> UpdateEnvironmentResponse -> Bool
== :: UpdateEnvironmentResponse -> UpdateEnvironmentResponse -> Bool
$c== :: UpdateEnvironmentResponse -> UpdateEnvironmentResponse -> Bool
Prelude.Eq, ReadPrec [UpdateEnvironmentResponse]
ReadPrec UpdateEnvironmentResponse
Int -> ReadS UpdateEnvironmentResponse
ReadS [UpdateEnvironmentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEnvironmentResponse]
$creadListPrec :: ReadPrec [UpdateEnvironmentResponse]
readPrec :: ReadPrec UpdateEnvironmentResponse
$creadPrec :: ReadPrec UpdateEnvironmentResponse
readList :: ReadS [UpdateEnvironmentResponse]
$creadList :: ReadS [UpdateEnvironmentResponse]
readsPrec :: Int -> ReadS UpdateEnvironmentResponse
$creadsPrec :: Int -> ReadS UpdateEnvironmentResponse
Prelude.Read, Int -> UpdateEnvironmentResponse -> ShowS
[UpdateEnvironmentResponse] -> ShowS
UpdateEnvironmentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEnvironmentResponse] -> ShowS
$cshowList :: [UpdateEnvironmentResponse] -> ShowS
show :: UpdateEnvironmentResponse -> String
$cshow :: UpdateEnvironmentResponse -> String
showsPrec :: Int -> UpdateEnvironmentResponse -> ShowS
$cshowsPrec :: Int -> UpdateEnvironmentResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateEnvironmentResponse x -> UpdateEnvironmentResponse
forall x.
UpdateEnvironmentResponse -> Rep UpdateEnvironmentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateEnvironmentResponse x -> UpdateEnvironmentResponse
$cfrom :: forall x.
UpdateEnvironmentResponse -> Rep UpdateEnvironmentResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEnvironmentResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'updateEnvironmentResponse_httpStatus' - The response's http status code.
--
-- 'environmentId', 'updateEnvironmentResponse_environmentId' - The unique identifier of the runtime environment that was updated.
newUpdateEnvironmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'environmentId'
  Prelude.Text ->
  UpdateEnvironmentResponse
newUpdateEnvironmentResponse :: Int -> Text -> UpdateEnvironmentResponse
newUpdateEnvironmentResponse
  Int
pHttpStatus_
  Text
pEnvironmentId_ =
    UpdateEnvironmentResponse'
      { $sel:httpStatus:UpdateEnvironmentResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:environmentId:UpdateEnvironmentResponse' :: Text
environmentId = Text
pEnvironmentId_
      }

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

-- | The unique identifier of the runtime environment that was updated.
updateEnvironmentResponse_environmentId :: Lens.Lens' UpdateEnvironmentResponse Prelude.Text
updateEnvironmentResponse_environmentId :: Lens' UpdateEnvironmentResponse Text
updateEnvironmentResponse_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironmentResponse' {Text
environmentId :: Text
$sel:environmentId:UpdateEnvironmentResponse' :: UpdateEnvironmentResponse -> Text
environmentId} -> Text
environmentId) (\s :: UpdateEnvironmentResponse
s@UpdateEnvironmentResponse' {} Text
a -> UpdateEnvironmentResponse
s {$sel:environmentId:UpdateEnvironmentResponse' :: Text
environmentId = Text
a} :: UpdateEnvironmentResponse)

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