{-# 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.SES.SetIdentityHeadersInNotificationsEnabled
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Given an identity (an email address or a domain), sets whether Amazon
-- SES includes the original email headers in the Amazon Simple
-- Notification Service (Amazon SNS) notifications of a specified type.
--
-- You can execute this operation no more than once per second.
--
-- For more information about using notifications with Amazon SES, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/notifications.html Amazon SES Developer Guide>.
module Amazonka.SES.SetIdentityHeadersInNotificationsEnabled
  ( -- * Creating a Request
    SetIdentityHeadersInNotificationsEnabled (..),
    newSetIdentityHeadersInNotificationsEnabled,

    -- * Request Lenses
    setIdentityHeadersInNotificationsEnabled_identity,
    setIdentityHeadersInNotificationsEnabled_notificationType,
    setIdentityHeadersInNotificationsEnabled_enabled,

    -- * Destructuring the Response
    SetIdentityHeadersInNotificationsEnabledResponse (..),
    newSetIdentityHeadersInNotificationsEnabledResponse,

    -- * Response Lenses
    setIdentityHeadersInNotificationsEnabledResponse_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.SES.Types

-- | Represents a request to set whether Amazon SES includes the original
-- email headers in the Amazon SNS notifications of a specified type. For
-- information about notifications, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/notifications-via-sns.html Amazon SES Developer Guide>.
--
-- /See:/ 'newSetIdentityHeadersInNotificationsEnabled' smart constructor.
data SetIdentityHeadersInNotificationsEnabled = SetIdentityHeadersInNotificationsEnabled'
  { -- | The identity for which to enable or disable headers in notifications.
    -- Examples: @user\@example.com@, @example.com@.
    SetIdentityHeadersInNotificationsEnabled -> Text
identity :: Prelude.Text,
    -- | The notification type for which to enable or disable headers in
    -- notifications.
    SetIdentityHeadersInNotificationsEnabled -> NotificationType
notificationType :: NotificationType,
    -- | Sets whether Amazon SES includes the original email headers in Amazon
    -- SNS notifications of the specified notification type. A value of @true@
    -- specifies that Amazon SES will include headers in notifications, and a
    -- value of @false@ specifies that Amazon SES will not include headers in
    -- notifications.
    --
    -- This value can only be set when @NotificationType@ is already set to use
    -- a particular Amazon SNS topic.
    SetIdentityHeadersInNotificationsEnabled -> Bool
enabled :: Prelude.Bool
  }
  deriving (SetIdentityHeadersInNotificationsEnabled
-> SetIdentityHeadersInNotificationsEnabled -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetIdentityHeadersInNotificationsEnabled
-> SetIdentityHeadersInNotificationsEnabled -> Bool
$c/= :: SetIdentityHeadersInNotificationsEnabled
-> SetIdentityHeadersInNotificationsEnabled -> Bool
== :: SetIdentityHeadersInNotificationsEnabled
-> SetIdentityHeadersInNotificationsEnabled -> Bool
$c== :: SetIdentityHeadersInNotificationsEnabled
-> SetIdentityHeadersInNotificationsEnabled -> Bool
Prelude.Eq, ReadPrec [SetIdentityHeadersInNotificationsEnabled]
ReadPrec SetIdentityHeadersInNotificationsEnabled
Int -> ReadS SetIdentityHeadersInNotificationsEnabled
ReadS [SetIdentityHeadersInNotificationsEnabled]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetIdentityHeadersInNotificationsEnabled]
$creadListPrec :: ReadPrec [SetIdentityHeadersInNotificationsEnabled]
readPrec :: ReadPrec SetIdentityHeadersInNotificationsEnabled
$creadPrec :: ReadPrec SetIdentityHeadersInNotificationsEnabled
readList :: ReadS [SetIdentityHeadersInNotificationsEnabled]
$creadList :: ReadS [SetIdentityHeadersInNotificationsEnabled]
readsPrec :: Int -> ReadS SetIdentityHeadersInNotificationsEnabled
$creadsPrec :: Int -> ReadS SetIdentityHeadersInNotificationsEnabled
Prelude.Read, Int -> SetIdentityHeadersInNotificationsEnabled -> ShowS
[SetIdentityHeadersInNotificationsEnabled] -> ShowS
SetIdentityHeadersInNotificationsEnabled -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetIdentityHeadersInNotificationsEnabled] -> ShowS
$cshowList :: [SetIdentityHeadersInNotificationsEnabled] -> ShowS
show :: SetIdentityHeadersInNotificationsEnabled -> String
$cshow :: SetIdentityHeadersInNotificationsEnabled -> String
showsPrec :: Int -> SetIdentityHeadersInNotificationsEnabled -> ShowS
$cshowsPrec :: Int -> SetIdentityHeadersInNotificationsEnabled -> ShowS
Prelude.Show, forall x.
Rep SetIdentityHeadersInNotificationsEnabled x
-> SetIdentityHeadersInNotificationsEnabled
forall x.
SetIdentityHeadersInNotificationsEnabled
-> Rep SetIdentityHeadersInNotificationsEnabled x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetIdentityHeadersInNotificationsEnabled x
-> SetIdentityHeadersInNotificationsEnabled
$cfrom :: forall x.
SetIdentityHeadersInNotificationsEnabled
-> Rep SetIdentityHeadersInNotificationsEnabled x
Prelude.Generic)

-- |
-- Create a value of 'SetIdentityHeadersInNotificationsEnabled' 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:
--
-- 'identity', 'setIdentityHeadersInNotificationsEnabled_identity' - The identity for which to enable or disable headers in notifications.
-- Examples: @user\@example.com@, @example.com@.
--
-- 'notificationType', 'setIdentityHeadersInNotificationsEnabled_notificationType' - The notification type for which to enable or disable headers in
-- notifications.
--
-- 'enabled', 'setIdentityHeadersInNotificationsEnabled_enabled' - Sets whether Amazon SES includes the original email headers in Amazon
-- SNS notifications of the specified notification type. A value of @true@
-- specifies that Amazon SES will include headers in notifications, and a
-- value of @false@ specifies that Amazon SES will not include headers in
-- notifications.
--
-- This value can only be set when @NotificationType@ is already set to use
-- a particular Amazon SNS topic.
newSetIdentityHeadersInNotificationsEnabled ::
  -- | 'identity'
  Prelude.Text ->
  -- | 'notificationType'
  NotificationType ->
  -- | 'enabled'
  Prelude.Bool ->
  SetIdentityHeadersInNotificationsEnabled
newSetIdentityHeadersInNotificationsEnabled :: Text
-> NotificationType
-> Bool
-> SetIdentityHeadersInNotificationsEnabled
newSetIdentityHeadersInNotificationsEnabled
  Text
pIdentity_
  NotificationType
pNotificationType_
  Bool
pEnabled_ =
    SetIdentityHeadersInNotificationsEnabled'
      { $sel:identity:SetIdentityHeadersInNotificationsEnabled' :: Text
identity =
          Text
pIdentity_,
        $sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: NotificationType
notificationType =
          NotificationType
pNotificationType_,
        $sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: Bool
enabled = Bool
pEnabled_
      }

-- | The identity for which to enable or disable headers in notifications.
-- Examples: @user\@example.com@, @example.com@.
setIdentityHeadersInNotificationsEnabled_identity :: Lens.Lens' SetIdentityHeadersInNotificationsEnabled Prelude.Text
setIdentityHeadersInNotificationsEnabled_identity :: Lens' SetIdentityHeadersInNotificationsEnabled Text
setIdentityHeadersInNotificationsEnabled_identity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetIdentityHeadersInNotificationsEnabled' {Text
identity :: Text
$sel:identity:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Text
identity} -> Text
identity) (\s :: SetIdentityHeadersInNotificationsEnabled
s@SetIdentityHeadersInNotificationsEnabled' {} Text
a -> SetIdentityHeadersInNotificationsEnabled
s {$sel:identity:SetIdentityHeadersInNotificationsEnabled' :: Text
identity = Text
a} :: SetIdentityHeadersInNotificationsEnabled)

-- | The notification type for which to enable or disable headers in
-- notifications.
setIdentityHeadersInNotificationsEnabled_notificationType :: Lens.Lens' SetIdentityHeadersInNotificationsEnabled NotificationType
setIdentityHeadersInNotificationsEnabled_notificationType :: Lens' SetIdentityHeadersInNotificationsEnabled NotificationType
setIdentityHeadersInNotificationsEnabled_notificationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetIdentityHeadersInNotificationsEnabled' {NotificationType
notificationType :: NotificationType
$sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> NotificationType
notificationType} -> NotificationType
notificationType) (\s :: SetIdentityHeadersInNotificationsEnabled
s@SetIdentityHeadersInNotificationsEnabled' {} NotificationType
a -> SetIdentityHeadersInNotificationsEnabled
s {$sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: NotificationType
notificationType = NotificationType
a} :: SetIdentityHeadersInNotificationsEnabled)

-- | Sets whether Amazon SES includes the original email headers in Amazon
-- SNS notifications of the specified notification type. A value of @true@
-- specifies that Amazon SES will include headers in notifications, and a
-- value of @false@ specifies that Amazon SES will not include headers in
-- notifications.
--
-- This value can only be set when @NotificationType@ is already set to use
-- a particular Amazon SNS topic.
setIdentityHeadersInNotificationsEnabled_enabled :: Lens.Lens' SetIdentityHeadersInNotificationsEnabled Prelude.Bool
setIdentityHeadersInNotificationsEnabled_enabled :: Lens' SetIdentityHeadersInNotificationsEnabled Bool
setIdentityHeadersInNotificationsEnabled_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetIdentityHeadersInNotificationsEnabled' {Bool
enabled :: Bool
$sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Bool
enabled} -> Bool
enabled) (\s :: SetIdentityHeadersInNotificationsEnabled
s@SetIdentityHeadersInNotificationsEnabled' {} Bool
a -> SetIdentityHeadersInNotificationsEnabled
s {$sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: Bool
enabled = Bool
a} :: SetIdentityHeadersInNotificationsEnabled)

instance
  Core.AWSRequest
    SetIdentityHeadersInNotificationsEnabled
  where
  type
    AWSResponse
      SetIdentityHeadersInNotificationsEnabled =
      SetIdentityHeadersInNotificationsEnabledResponse
  request :: (Service -> Service)
-> SetIdentityHeadersInNotificationsEnabled
-> Request SetIdentityHeadersInNotificationsEnabled
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy SetIdentityHeadersInNotificationsEnabled
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse SetIdentityHeadersInNotificationsEnabled)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"SetIdentityHeadersInNotificationsEnabledResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> SetIdentityHeadersInNotificationsEnabledResponse
SetIdentityHeadersInNotificationsEnabledResponse'
            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
    SetIdentityHeadersInNotificationsEnabled
  where
  hashWithSalt :: Int -> SetIdentityHeadersInNotificationsEnabled -> Int
hashWithSalt
    Int
_salt
    SetIdentityHeadersInNotificationsEnabled' {Bool
Text
NotificationType
enabled :: Bool
notificationType :: NotificationType
identity :: Text
$sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Bool
$sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> NotificationType
$sel:identity:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identity
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NotificationType
notificationType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
enabled

instance
  Prelude.NFData
    SetIdentityHeadersInNotificationsEnabled
  where
  rnf :: SetIdentityHeadersInNotificationsEnabled -> ()
rnf SetIdentityHeadersInNotificationsEnabled' {Bool
Text
NotificationType
enabled :: Bool
notificationType :: NotificationType
identity :: Text
$sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Bool
$sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> NotificationType
$sel:identity:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NotificationType
notificationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
enabled

instance
  Data.ToHeaders
    SetIdentityHeadersInNotificationsEnabled
  where
  toHeaders :: SetIdentityHeadersInNotificationsEnabled -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    SetIdentityHeadersInNotificationsEnabled
  where
  toQuery :: SetIdentityHeadersInNotificationsEnabled -> QueryString
toQuery SetIdentityHeadersInNotificationsEnabled' {Bool
Text
NotificationType
enabled :: Bool
notificationType :: NotificationType
identity :: Text
$sel:enabled:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Bool
$sel:notificationType:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> NotificationType
$sel:identity:SetIdentityHeadersInNotificationsEnabled' :: SetIdentityHeadersInNotificationsEnabled -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"SetIdentityHeadersInNotificationsEnabled" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"Identity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
identity,
        ByteString
"NotificationType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: NotificationType
notificationType,
        ByteString
"Enabled" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
enabled
      ]

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

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

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

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