{-# 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.WorkMail.UpdateImpersonationRole
-- 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 an impersonation role for the given WorkMail organization.
module Amazonka.WorkMail.UpdateImpersonationRole
  ( -- * Creating a Request
    UpdateImpersonationRole (..),
    newUpdateImpersonationRole,

    -- * Request Lenses
    updateImpersonationRole_description,
    updateImpersonationRole_organizationId,
    updateImpersonationRole_impersonationRoleId,
    updateImpersonationRole_name,
    updateImpersonationRole_type,
    updateImpersonationRole_rules,

    -- * Destructuring the Response
    UpdateImpersonationRoleResponse (..),
    newUpdateImpersonationRoleResponse,

    -- * Response Lenses
    updateImpersonationRoleResponse_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.WorkMail.Types

-- | /See:/ 'newUpdateImpersonationRole' smart constructor.
data UpdateImpersonationRole = UpdateImpersonationRole'
  { -- | The updated impersonation role description.
    UpdateImpersonationRole -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The WorkMail organization that contains the impersonation role to
    -- update.
    UpdateImpersonationRole -> Text
organizationId :: Prelude.Text,
    -- | The ID of the impersonation role to update.
    UpdateImpersonationRole -> Text
impersonationRoleId :: Prelude.Text,
    -- | The updated impersonation role name.
    UpdateImpersonationRole -> Text
name :: Prelude.Text,
    -- | The updated impersonation role type.
    UpdateImpersonationRole -> ImpersonationRoleType
type' :: ImpersonationRoleType,
    -- | The updated list of rules.
    UpdateImpersonationRole -> [ImpersonationRule]
rules :: [ImpersonationRule]
  }
  deriving (UpdateImpersonationRole -> UpdateImpersonationRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateImpersonationRole -> UpdateImpersonationRole -> Bool
$c/= :: UpdateImpersonationRole -> UpdateImpersonationRole -> Bool
== :: UpdateImpersonationRole -> UpdateImpersonationRole -> Bool
$c== :: UpdateImpersonationRole -> UpdateImpersonationRole -> Bool
Prelude.Eq, ReadPrec [UpdateImpersonationRole]
ReadPrec UpdateImpersonationRole
Int -> ReadS UpdateImpersonationRole
ReadS [UpdateImpersonationRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateImpersonationRole]
$creadListPrec :: ReadPrec [UpdateImpersonationRole]
readPrec :: ReadPrec UpdateImpersonationRole
$creadPrec :: ReadPrec UpdateImpersonationRole
readList :: ReadS [UpdateImpersonationRole]
$creadList :: ReadS [UpdateImpersonationRole]
readsPrec :: Int -> ReadS UpdateImpersonationRole
$creadsPrec :: Int -> ReadS UpdateImpersonationRole
Prelude.Read, Int -> UpdateImpersonationRole -> ShowS
[UpdateImpersonationRole] -> ShowS
UpdateImpersonationRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateImpersonationRole] -> ShowS
$cshowList :: [UpdateImpersonationRole] -> ShowS
show :: UpdateImpersonationRole -> String
$cshow :: UpdateImpersonationRole -> String
showsPrec :: Int -> UpdateImpersonationRole -> ShowS
$cshowsPrec :: Int -> UpdateImpersonationRole -> ShowS
Prelude.Show, forall x. Rep UpdateImpersonationRole x -> UpdateImpersonationRole
forall x. UpdateImpersonationRole -> Rep UpdateImpersonationRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateImpersonationRole x -> UpdateImpersonationRole
$cfrom :: forall x. UpdateImpersonationRole -> Rep UpdateImpersonationRole x
Prelude.Generic)

-- |
-- Create a value of 'UpdateImpersonationRole' 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', 'updateImpersonationRole_description' - The updated impersonation role description.
--
-- 'organizationId', 'updateImpersonationRole_organizationId' - The WorkMail organization that contains the impersonation role to
-- update.
--
-- 'impersonationRoleId', 'updateImpersonationRole_impersonationRoleId' - The ID of the impersonation role to update.
--
-- 'name', 'updateImpersonationRole_name' - The updated impersonation role name.
--
-- 'type'', 'updateImpersonationRole_type' - The updated impersonation role type.
--
-- 'rules', 'updateImpersonationRole_rules' - The updated list of rules.
newUpdateImpersonationRole ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'impersonationRoleId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'type''
  ImpersonationRoleType ->
  UpdateImpersonationRole
newUpdateImpersonationRole :: Text
-> Text -> Text -> ImpersonationRoleType -> UpdateImpersonationRole
newUpdateImpersonationRole
  Text
pOrganizationId_
  Text
pImpersonationRoleId_
  Text
pName_
  ImpersonationRoleType
pType_ =
    UpdateImpersonationRole'
      { $sel:description:UpdateImpersonationRole' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:organizationId:UpdateImpersonationRole' :: Text
organizationId = Text
pOrganizationId_,
        $sel:impersonationRoleId:UpdateImpersonationRole' :: Text
impersonationRoleId = Text
pImpersonationRoleId_,
        $sel:name:UpdateImpersonationRole' :: Text
name = Text
pName_,
        $sel:type':UpdateImpersonationRole' :: ImpersonationRoleType
type' = ImpersonationRoleType
pType_,
        $sel:rules:UpdateImpersonationRole' :: [ImpersonationRule]
rules = forall a. Monoid a => a
Prelude.mempty
      }

-- | The updated impersonation role description.
updateImpersonationRole_description :: Lens.Lens' UpdateImpersonationRole (Prelude.Maybe Prelude.Text)
updateImpersonationRole_description :: Lens' UpdateImpersonationRole (Maybe Text)
updateImpersonationRole_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {Maybe Text
description :: Maybe Text
$sel:description:UpdateImpersonationRole' :: UpdateImpersonationRole -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} Maybe Text
a -> UpdateImpersonationRole
s {$sel:description:UpdateImpersonationRole' :: Maybe Text
description = Maybe Text
a} :: UpdateImpersonationRole)

-- | The WorkMail organization that contains the impersonation role to
-- update.
updateImpersonationRole_organizationId :: Lens.Lens' UpdateImpersonationRole Prelude.Text
updateImpersonationRole_organizationId :: Lens' UpdateImpersonationRole Text
updateImpersonationRole_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {Text
organizationId :: Text
$sel:organizationId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
organizationId} -> Text
organizationId) (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} Text
a -> UpdateImpersonationRole
s {$sel:organizationId:UpdateImpersonationRole' :: Text
organizationId = Text
a} :: UpdateImpersonationRole)

-- | The ID of the impersonation role to update.
updateImpersonationRole_impersonationRoleId :: Lens.Lens' UpdateImpersonationRole Prelude.Text
updateImpersonationRole_impersonationRoleId :: Lens' UpdateImpersonationRole Text
updateImpersonationRole_impersonationRoleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {Text
impersonationRoleId :: Text
$sel:impersonationRoleId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
impersonationRoleId} -> Text
impersonationRoleId) (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} Text
a -> UpdateImpersonationRole
s {$sel:impersonationRoleId:UpdateImpersonationRole' :: Text
impersonationRoleId = Text
a} :: UpdateImpersonationRole)

-- | The updated impersonation role name.
updateImpersonationRole_name :: Lens.Lens' UpdateImpersonationRole Prelude.Text
updateImpersonationRole_name :: Lens' UpdateImpersonationRole Text
updateImpersonationRole_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {Text
name :: Text
$sel:name:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
name} -> Text
name) (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} Text
a -> UpdateImpersonationRole
s {$sel:name:UpdateImpersonationRole' :: Text
name = Text
a} :: UpdateImpersonationRole)

-- | The updated impersonation role type.
updateImpersonationRole_type :: Lens.Lens' UpdateImpersonationRole ImpersonationRoleType
updateImpersonationRole_type :: Lens' UpdateImpersonationRole ImpersonationRoleType
updateImpersonationRole_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {ImpersonationRoleType
type' :: ImpersonationRoleType
$sel:type':UpdateImpersonationRole' :: UpdateImpersonationRole -> ImpersonationRoleType
type'} -> ImpersonationRoleType
type') (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} ImpersonationRoleType
a -> UpdateImpersonationRole
s {$sel:type':UpdateImpersonationRole' :: ImpersonationRoleType
type' = ImpersonationRoleType
a} :: UpdateImpersonationRole)

-- | The updated list of rules.
updateImpersonationRole_rules :: Lens.Lens' UpdateImpersonationRole [ImpersonationRule]
updateImpersonationRole_rules :: Lens' UpdateImpersonationRole [ImpersonationRule]
updateImpersonationRole_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImpersonationRole' {[ImpersonationRule]
rules :: [ImpersonationRule]
$sel:rules:UpdateImpersonationRole' :: UpdateImpersonationRole -> [ImpersonationRule]
rules} -> [ImpersonationRule]
rules) (\s :: UpdateImpersonationRole
s@UpdateImpersonationRole' {} [ImpersonationRule]
a -> UpdateImpersonationRole
s {$sel:rules:UpdateImpersonationRole' :: [ImpersonationRule]
rules = [ImpersonationRule]
a} :: UpdateImpersonationRole) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest UpdateImpersonationRole where
  type
    AWSResponse UpdateImpersonationRole =
      UpdateImpersonationRoleResponse
  request :: (Service -> Service)
-> UpdateImpersonationRole -> Request UpdateImpersonationRole
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 UpdateImpersonationRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateImpersonationRole)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateImpersonationRoleResponse
UpdateImpersonationRoleResponse'
            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))
      )

instance Prelude.Hashable UpdateImpersonationRole where
  hashWithSalt :: Int -> UpdateImpersonationRole -> Int
hashWithSalt Int
_salt UpdateImpersonationRole' {[ImpersonationRule]
Maybe Text
Text
ImpersonationRoleType
rules :: [ImpersonationRule]
type' :: ImpersonationRoleType
name :: Text
impersonationRoleId :: Text
organizationId :: Text
description :: Maybe Text
$sel:rules:UpdateImpersonationRole' :: UpdateImpersonationRole -> [ImpersonationRule]
$sel:type':UpdateImpersonationRole' :: UpdateImpersonationRole -> ImpersonationRoleType
$sel:name:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:impersonationRoleId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:organizationId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:description:UpdateImpersonationRole' :: UpdateImpersonationRole -> 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` Text
organizationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
impersonationRoleId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ImpersonationRoleType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [ImpersonationRule]
rules

instance Prelude.NFData UpdateImpersonationRole where
  rnf :: UpdateImpersonationRole -> ()
rnf UpdateImpersonationRole' {[ImpersonationRule]
Maybe Text
Text
ImpersonationRoleType
rules :: [ImpersonationRule]
type' :: ImpersonationRoleType
name :: Text
impersonationRoleId :: Text
organizationId :: Text
description :: Maybe Text
$sel:rules:UpdateImpersonationRole' :: UpdateImpersonationRole -> [ImpersonationRule]
$sel:type':UpdateImpersonationRole' :: UpdateImpersonationRole -> ImpersonationRoleType
$sel:name:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:impersonationRoleId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:organizationId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:description:UpdateImpersonationRole' :: UpdateImpersonationRole -> 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 Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
impersonationRoleId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ImpersonationRoleType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ImpersonationRule]
rules

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

instance Data.ToJSON UpdateImpersonationRole where
  toJSON :: UpdateImpersonationRole -> Value
toJSON UpdateImpersonationRole' {[ImpersonationRule]
Maybe Text
Text
ImpersonationRoleType
rules :: [ImpersonationRule]
type' :: ImpersonationRoleType
name :: Text
impersonationRoleId :: Text
organizationId :: Text
description :: Maybe Text
$sel:rules:UpdateImpersonationRole' :: UpdateImpersonationRole -> [ImpersonationRule]
$sel:type':UpdateImpersonationRole' :: UpdateImpersonationRole -> ImpersonationRoleType
$sel:name:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:impersonationRoleId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:organizationId:UpdateImpersonationRole' :: UpdateImpersonationRole -> Text
$sel:description:UpdateImpersonationRole' :: UpdateImpersonationRole -> 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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ImpersonationRoleId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
impersonationRoleId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ImpersonationRoleType
type'),
            forall a. a -> Maybe a
Prelude.Just (Key
"Rules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [ImpersonationRule]
rules)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateImpersonationRoleResponse' 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', 'updateImpersonationRoleResponse_httpStatus' - The response's http status code.
newUpdateImpersonationRoleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateImpersonationRoleResponse
newUpdateImpersonationRoleResponse :: Int -> UpdateImpersonationRoleResponse
newUpdateImpersonationRoleResponse Int
pHttpStatus_ =
  UpdateImpersonationRoleResponse'
    { $sel:httpStatus:UpdateImpersonationRoleResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    UpdateImpersonationRoleResponse
  where
  rnf :: UpdateImpersonationRoleResponse -> ()
rnf UpdateImpersonationRoleResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateImpersonationRoleResponse' :: UpdateImpersonationRoleResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus