{-# 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.FinSpace.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)
--
-- Update your FinSpace environment.
module Amazonka.FinSpace.UpdateEnvironment
  ( -- * Creating a Request
    UpdateEnvironment (..),
    newUpdateEnvironment,

    -- * Request Lenses
    updateEnvironment_description,
    updateEnvironment_federationMode,
    updateEnvironment_federationParameters,
    updateEnvironment_name,
    updateEnvironment_environmentId,

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

    -- * Response Lenses
    updateEnvironmentResponse_environment,
    updateEnvironmentResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FinSpace.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'
  { -- | The description of the environment.
    UpdateEnvironment -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Authentication mode for the environment.
    --
    -- -   @FEDERATED@ - Users access FinSpace through Single Sign On (SSO) via
    --     your Identity provider.
    --
    -- -   @LOCAL@ - Users access FinSpace via email and password managed
    --     within the FinSpace environment.
    UpdateEnvironment -> Maybe FederationMode
federationMode :: Prelude.Maybe FederationMode,
    UpdateEnvironment -> Maybe FederationParameters
federationParameters :: Prelude.Maybe FederationParameters,
    -- | The name of the environment.
    UpdateEnvironment -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the FinSpace environment.
    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:
--
-- 'description', 'updateEnvironment_description' - The description of the environment.
--
-- 'federationMode', 'updateEnvironment_federationMode' - Authentication mode for the environment.
--
-- -   @FEDERATED@ - Users access FinSpace through Single Sign On (SSO) via
--     your Identity provider.
--
-- -   @LOCAL@ - Users access FinSpace via email and password managed
--     within the FinSpace environment.
--
-- 'federationParameters', 'updateEnvironment_federationParameters' - Undocumented member.
--
-- 'name', 'updateEnvironment_name' - The name of the environment.
--
-- 'environmentId', 'updateEnvironment_environmentId' - The identifier of the FinSpace environment.
newUpdateEnvironment ::
  -- | 'environmentId'
  Prelude.Text ->
  UpdateEnvironment
newUpdateEnvironment :: Text -> UpdateEnvironment
newUpdateEnvironment Text
pEnvironmentId_ =
  UpdateEnvironment'
    { $sel:description:UpdateEnvironment' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:federationMode:UpdateEnvironment' :: Maybe FederationMode
federationMode = forall a. Maybe a
Prelude.Nothing,
      $sel:federationParameters:UpdateEnvironment' :: Maybe FederationParameters
federationParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateEnvironment' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:UpdateEnvironment' :: Text
environmentId = Text
pEnvironmentId_
    }

-- | The description of the environment.
updateEnvironment_description :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_description :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
description :: Maybe Text
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:description:UpdateEnvironment' :: Maybe Text
description = Maybe Text
a} :: UpdateEnvironment)

-- | Authentication mode for the environment.
--
-- -   @FEDERATED@ - Users access FinSpace through Single Sign On (SSO) via
--     your Identity provider.
--
-- -   @LOCAL@ - Users access FinSpace via email and password managed
--     within the FinSpace environment.
updateEnvironment_federationMode :: Lens.Lens' UpdateEnvironment (Prelude.Maybe FederationMode)
updateEnvironment_federationMode :: Lens' UpdateEnvironment (Maybe FederationMode)
updateEnvironment_federationMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe FederationMode
federationMode :: Maybe FederationMode
$sel:federationMode:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationMode
federationMode} -> Maybe FederationMode
federationMode) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe FederationMode
a -> UpdateEnvironment
s {$sel:federationMode:UpdateEnvironment' :: Maybe FederationMode
federationMode = Maybe FederationMode
a} :: UpdateEnvironment)

-- | Undocumented member.
updateEnvironment_federationParameters :: Lens.Lens' UpdateEnvironment (Prelude.Maybe FederationParameters)
updateEnvironment_federationParameters :: Lens' UpdateEnvironment (Maybe FederationParameters)
updateEnvironment_federationParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe FederationParameters
federationParameters :: Maybe FederationParameters
$sel:federationParameters:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationParameters
federationParameters} -> Maybe FederationParameters
federationParameters) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe FederationParameters
a -> UpdateEnvironment
s {$sel:federationParameters:UpdateEnvironment' :: Maybe FederationParameters
federationParameters = Maybe FederationParameters
a} :: UpdateEnvironment)

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

-- | The identifier of the FinSpace environment.
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.putJSON (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 ->
          Maybe Environment -> Int -> UpdateEnvironmentResponse
UpdateEnvironmentResponse'
            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
"environment")
            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 UpdateEnvironment where
  hashWithSalt :: Int -> UpdateEnvironment -> Int
hashWithSalt Int
_salt UpdateEnvironment' {Maybe Text
Maybe FederationMode
Maybe FederationParameters
Text
environmentId :: Text
name :: Maybe Text
federationParameters :: Maybe FederationParameters
federationMode :: Maybe FederationMode
description :: Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:name:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:federationParameters:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationParameters
$sel:federationMode:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationMode
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FederationMode
federationMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FederationParameters
federationParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentId

instance Prelude.NFData UpdateEnvironment where
  rnf :: UpdateEnvironment -> ()
rnf UpdateEnvironment' {Maybe Text
Maybe FederationMode
Maybe FederationParameters
Text
environmentId :: Text
name :: Maybe Text
federationParameters :: Maybe FederationParameters
federationMode :: Maybe FederationMode
description :: Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:name:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:federationParameters:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationParameters
$sel:federationMode:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationMode
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FederationMode
federationMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FederationParameters
federationParameters
      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 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 Text
Maybe FederationMode
Maybe FederationParameters
Text
environmentId :: Text
name :: Maybe Text
federationParameters :: Maybe FederationParameters
federationMode :: Maybe FederationMode
description :: Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:name:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:federationParameters:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationParameters
$sel:federationMode:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationMode
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"federationMode" 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 FederationMode
federationMode,
            (Key
"federationParameters" 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 FederationParameters
federationParameters,
            (Key
"name" 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
name
          ]
      )

instance Data.ToPath UpdateEnvironment where
  toPath :: UpdateEnvironment -> ByteString
toPath UpdateEnvironment' {Maybe Text
Maybe FederationMode
Maybe FederationParameters
Text
environmentId :: Text
name :: Maybe Text
federationParameters :: Maybe FederationParameters
federationMode :: Maybe FederationMode
description :: Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Text
$sel:name:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:federationParameters:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationParameters
$sel:federationMode:UpdateEnvironment' :: UpdateEnvironment -> Maybe FederationMode
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/environment/", 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'
  { -- | Returns the FinSpace environment object.
    UpdateEnvironmentResponse -> Maybe Environment
environment :: Prelude.Maybe Environment,
    -- | The response's http status code.
    UpdateEnvironmentResponse -> Int
httpStatus :: Prelude.Int
  }
  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:
--
-- 'environment', 'updateEnvironmentResponse_environment' - Returns the FinSpace environment object.
--
-- 'httpStatus', 'updateEnvironmentResponse_httpStatus' - The response's http status code.
newUpdateEnvironmentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateEnvironmentResponse
newUpdateEnvironmentResponse :: Int -> UpdateEnvironmentResponse
newUpdateEnvironmentResponse Int
pHttpStatus_ =
  UpdateEnvironmentResponse'
    { $sel:environment:UpdateEnvironmentResponse' :: Maybe Environment
environment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateEnvironmentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns the FinSpace environment object.
updateEnvironmentResponse_environment :: Lens.Lens' UpdateEnvironmentResponse (Prelude.Maybe Environment)
updateEnvironmentResponse_environment :: Lens' UpdateEnvironmentResponse (Maybe Environment)
updateEnvironmentResponse_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironmentResponse' {Maybe Environment
environment :: Maybe Environment
$sel:environment:UpdateEnvironmentResponse' :: UpdateEnvironmentResponse -> Maybe Environment
environment} -> Maybe Environment
environment) (\s :: UpdateEnvironmentResponse
s@UpdateEnvironmentResponse' {} Maybe Environment
a -> UpdateEnvironmentResponse
s {$sel:environment:UpdateEnvironmentResponse' :: Maybe Environment
environment = Maybe Environment
a} :: UpdateEnvironmentResponse)

-- | 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)

instance Prelude.NFData UpdateEnvironmentResponse where
  rnf :: UpdateEnvironmentResponse -> ()
rnf UpdateEnvironmentResponse' {Int
Maybe Environment
httpStatus :: Int
environment :: Maybe Environment
$sel:httpStatus:UpdateEnvironmentResponse' :: UpdateEnvironmentResponse -> Int
$sel:environment:UpdateEnvironmentResponse' :: UpdateEnvironmentResponse -> Maybe Environment
..} =
    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 Int
httpStatus