{-# 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.IoT.UpdateAuditSuppression
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a Device Defender audit suppression.
module Amazonka.IoT.UpdateAuditSuppression
  ( -- * Creating a Request
    UpdateAuditSuppression (..),
    newUpdateAuditSuppression,

    -- * Request Lenses
    updateAuditSuppression_description,
    updateAuditSuppression_expirationDate,
    updateAuditSuppression_suppressIndefinitely,
    updateAuditSuppression_checkName,
    updateAuditSuppression_resourceIdentifier,

    -- * Destructuring the Response
    UpdateAuditSuppressionResponse (..),
    newUpdateAuditSuppressionResponse,

    -- * Response Lenses
    updateAuditSuppressionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateAuditSuppression' smart constructor.
data UpdateAuditSuppression = UpdateAuditSuppression'
  { -- | The description of the audit suppression.
    UpdateAuditSuppression -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The expiration date (epoch timestamp in seconds) that you want the
    -- suppression to adhere to.
    UpdateAuditSuppression -> Maybe POSIX
expirationDate :: Prelude.Maybe Data.POSIX,
    -- | Indicates whether a suppression should exist indefinitely or not.
    UpdateAuditSuppression -> Maybe Bool
suppressIndefinitely :: Prelude.Maybe Prelude.Bool,
    UpdateAuditSuppression -> Text
checkName :: Prelude.Text,
    UpdateAuditSuppression -> ResourceIdentifier
resourceIdentifier :: ResourceIdentifier
  }
  deriving (UpdateAuditSuppression -> UpdateAuditSuppression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAuditSuppression -> UpdateAuditSuppression -> Bool
$c/= :: UpdateAuditSuppression -> UpdateAuditSuppression -> Bool
== :: UpdateAuditSuppression -> UpdateAuditSuppression -> Bool
$c== :: UpdateAuditSuppression -> UpdateAuditSuppression -> Bool
Prelude.Eq, ReadPrec [UpdateAuditSuppression]
ReadPrec UpdateAuditSuppression
Int -> ReadS UpdateAuditSuppression
ReadS [UpdateAuditSuppression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAuditSuppression]
$creadListPrec :: ReadPrec [UpdateAuditSuppression]
readPrec :: ReadPrec UpdateAuditSuppression
$creadPrec :: ReadPrec UpdateAuditSuppression
readList :: ReadS [UpdateAuditSuppression]
$creadList :: ReadS [UpdateAuditSuppression]
readsPrec :: Int -> ReadS UpdateAuditSuppression
$creadsPrec :: Int -> ReadS UpdateAuditSuppression
Prelude.Read, Int -> UpdateAuditSuppression -> ShowS
[UpdateAuditSuppression] -> ShowS
UpdateAuditSuppression -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAuditSuppression] -> ShowS
$cshowList :: [UpdateAuditSuppression] -> ShowS
show :: UpdateAuditSuppression -> String
$cshow :: UpdateAuditSuppression -> String
showsPrec :: Int -> UpdateAuditSuppression -> ShowS
$cshowsPrec :: Int -> UpdateAuditSuppression -> ShowS
Prelude.Show, forall x. Rep UpdateAuditSuppression x -> UpdateAuditSuppression
forall x. UpdateAuditSuppression -> Rep UpdateAuditSuppression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateAuditSuppression x -> UpdateAuditSuppression
$cfrom :: forall x. UpdateAuditSuppression -> Rep UpdateAuditSuppression x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAuditSuppression' 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', 'updateAuditSuppression_description' - The description of the audit suppression.
--
-- 'expirationDate', 'updateAuditSuppression_expirationDate' - The expiration date (epoch timestamp in seconds) that you want the
-- suppression to adhere to.
--
-- 'suppressIndefinitely', 'updateAuditSuppression_suppressIndefinitely' - Indicates whether a suppression should exist indefinitely or not.
--
-- 'checkName', 'updateAuditSuppression_checkName' - Undocumented member.
--
-- 'resourceIdentifier', 'updateAuditSuppression_resourceIdentifier' - Undocumented member.
newUpdateAuditSuppression ::
  -- | 'checkName'
  Prelude.Text ->
  -- | 'resourceIdentifier'
  ResourceIdentifier ->
  UpdateAuditSuppression
newUpdateAuditSuppression :: Text -> ResourceIdentifier -> UpdateAuditSuppression
newUpdateAuditSuppression
  Text
pCheckName_
  ResourceIdentifier
pResourceIdentifier_ =
    UpdateAuditSuppression'
      { $sel:description:UpdateAuditSuppression' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:expirationDate:UpdateAuditSuppression' :: Maybe POSIX
expirationDate = forall a. Maybe a
Prelude.Nothing,
        $sel:suppressIndefinitely:UpdateAuditSuppression' :: Maybe Bool
suppressIndefinitely = forall a. Maybe a
Prelude.Nothing,
        $sel:checkName:UpdateAuditSuppression' :: Text
checkName = Text
pCheckName_,
        $sel:resourceIdentifier:UpdateAuditSuppression' :: ResourceIdentifier
resourceIdentifier = ResourceIdentifier
pResourceIdentifier_
      }

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

-- | The expiration date (epoch timestamp in seconds) that you want the
-- suppression to adhere to.
updateAuditSuppression_expirationDate :: Lens.Lens' UpdateAuditSuppression (Prelude.Maybe Prelude.UTCTime)
updateAuditSuppression_expirationDate :: Lens' UpdateAuditSuppression (Maybe UTCTime)
updateAuditSuppression_expirationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuditSuppression' {Maybe POSIX
expirationDate :: Maybe POSIX
$sel:expirationDate:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe POSIX
expirationDate} -> Maybe POSIX
expirationDate) (\s :: UpdateAuditSuppression
s@UpdateAuditSuppression' {} Maybe POSIX
a -> UpdateAuditSuppression
s {$sel:expirationDate:UpdateAuditSuppression' :: Maybe POSIX
expirationDate = Maybe POSIX
a} :: UpdateAuditSuppression) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Indicates whether a suppression should exist indefinitely or not.
updateAuditSuppression_suppressIndefinitely :: Lens.Lens' UpdateAuditSuppression (Prelude.Maybe Prelude.Bool)
updateAuditSuppression_suppressIndefinitely :: Lens' UpdateAuditSuppression (Maybe Bool)
updateAuditSuppression_suppressIndefinitely = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuditSuppression' {Maybe Bool
suppressIndefinitely :: Maybe Bool
$sel:suppressIndefinitely:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe Bool
suppressIndefinitely} -> Maybe Bool
suppressIndefinitely) (\s :: UpdateAuditSuppression
s@UpdateAuditSuppression' {} Maybe Bool
a -> UpdateAuditSuppression
s {$sel:suppressIndefinitely:UpdateAuditSuppression' :: Maybe Bool
suppressIndefinitely = Maybe Bool
a} :: UpdateAuditSuppression)

-- | Undocumented member.
updateAuditSuppression_checkName :: Lens.Lens' UpdateAuditSuppression Prelude.Text
updateAuditSuppression_checkName :: Lens' UpdateAuditSuppression Text
updateAuditSuppression_checkName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuditSuppression' {Text
checkName :: Text
$sel:checkName:UpdateAuditSuppression' :: UpdateAuditSuppression -> Text
checkName} -> Text
checkName) (\s :: UpdateAuditSuppression
s@UpdateAuditSuppression' {} Text
a -> UpdateAuditSuppression
s {$sel:checkName:UpdateAuditSuppression' :: Text
checkName = Text
a} :: UpdateAuditSuppression)

-- | Undocumented member.
updateAuditSuppression_resourceIdentifier :: Lens.Lens' UpdateAuditSuppression ResourceIdentifier
updateAuditSuppression_resourceIdentifier :: Lens' UpdateAuditSuppression ResourceIdentifier
updateAuditSuppression_resourceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuditSuppression' {ResourceIdentifier
resourceIdentifier :: ResourceIdentifier
$sel:resourceIdentifier:UpdateAuditSuppression' :: UpdateAuditSuppression -> ResourceIdentifier
resourceIdentifier} -> ResourceIdentifier
resourceIdentifier) (\s :: UpdateAuditSuppression
s@UpdateAuditSuppression' {} ResourceIdentifier
a -> UpdateAuditSuppression
s {$sel:resourceIdentifier:UpdateAuditSuppression' :: ResourceIdentifier
resourceIdentifier = ResourceIdentifier
a} :: UpdateAuditSuppression)

instance Core.AWSRequest UpdateAuditSuppression where
  type
    AWSResponse UpdateAuditSuppression =
      UpdateAuditSuppressionResponse
  request :: (Service -> Service)
-> UpdateAuditSuppression -> Request UpdateAuditSuppression
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 UpdateAuditSuppression
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateAuditSuppression)))
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 -> UpdateAuditSuppressionResponse
UpdateAuditSuppressionResponse'
            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 UpdateAuditSuppression where
  hashWithSalt :: Int -> UpdateAuditSuppression -> Int
hashWithSalt Int
_salt UpdateAuditSuppression' {Maybe Bool
Maybe Text
Maybe POSIX
Text
ResourceIdentifier
resourceIdentifier :: ResourceIdentifier
checkName :: Text
suppressIndefinitely :: Maybe Bool
expirationDate :: Maybe POSIX
description :: Maybe Text
$sel:resourceIdentifier:UpdateAuditSuppression' :: UpdateAuditSuppression -> ResourceIdentifier
$sel:checkName:UpdateAuditSuppression' :: UpdateAuditSuppression -> Text
$sel:suppressIndefinitely:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe Bool
$sel:expirationDate:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe POSIX
$sel:description:UpdateAuditSuppression' :: UpdateAuditSuppression -> 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 POSIX
expirationDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
suppressIndefinitely
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
checkName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceIdentifier
resourceIdentifier

instance Prelude.NFData UpdateAuditSuppression where
  rnf :: UpdateAuditSuppression -> ()
rnf UpdateAuditSuppression' {Maybe Bool
Maybe Text
Maybe POSIX
Text
ResourceIdentifier
resourceIdentifier :: ResourceIdentifier
checkName :: Text
suppressIndefinitely :: Maybe Bool
expirationDate :: Maybe POSIX
description :: Maybe Text
$sel:resourceIdentifier:UpdateAuditSuppression' :: UpdateAuditSuppression -> ResourceIdentifier
$sel:checkName:UpdateAuditSuppression' :: UpdateAuditSuppression -> Text
$sel:suppressIndefinitely:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe Bool
$sel:expirationDate:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe POSIX
$sel:description:UpdateAuditSuppression' :: UpdateAuditSuppression -> 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 POSIX
expirationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
suppressIndefinitely
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
checkName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ResourceIdentifier
resourceIdentifier

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

instance Data.ToJSON UpdateAuditSuppression where
  toJSON :: UpdateAuditSuppression -> Value
toJSON UpdateAuditSuppression' {Maybe Bool
Maybe Text
Maybe POSIX
Text
ResourceIdentifier
resourceIdentifier :: ResourceIdentifier
checkName :: Text
suppressIndefinitely :: Maybe Bool
expirationDate :: Maybe POSIX
description :: Maybe Text
$sel:resourceIdentifier:UpdateAuditSuppression' :: UpdateAuditSuppression -> ResourceIdentifier
$sel:checkName:UpdateAuditSuppression' :: UpdateAuditSuppression -> Text
$sel:suppressIndefinitely:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe Bool
$sel:expirationDate:UpdateAuditSuppression' :: UpdateAuditSuppression -> Maybe POSIX
$sel:description:UpdateAuditSuppression' :: UpdateAuditSuppression -> 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
"expirationDate" 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 POSIX
expirationDate,
            (Key
"suppressIndefinitely" 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
suppressIndefinitely,
            forall a. a -> Maybe a
Prelude.Just (Key
"checkName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
checkName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"resourceIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ResourceIdentifier
resourceIdentifier)
          ]
      )

instance Data.ToPath UpdateAuditSuppression where
  toPath :: UpdateAuditSuppression -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/audit/suppressions/update"

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

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

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

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

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