{-# 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.GuardDuty.UpdateFilter
-- 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 filter specified by the filter name.
module Amazonka.GuardDuty.UpdateFilter
  ( -- * Creating a Request
    UpdateFilter (..),
    newUpdateFilter,

    -- * Request Lenses
    updateFilter_action,
    updateFilter_description,
    updateFilter_findingCriteria,
    updateFilter_rank,
    updateFilter_detectorId,
    updateFilter_filterName,

    -- * Destructuring the Response
    UpdateFilterResponse (..),
    newUpdateFilterResponse,

    -- * Response Lenses
    updateFilterResponse_httpStatus,
    updateFilterResponse_name,
  )
where

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

-- | /See:/ 'newUpdateFilter' smart constructor.
data UpdateFilter = UpdateFilter'
  { -- | Specifies the action that is to be applied to the findings that match
    -- the filter.
    UpdateFilter -> Maybe FilterAction
action :: Prelude.Maybe FilterAction,
    -- | The description of the filter. Valid special characters include period
    -- (.), underscore (_), dash (-), and whitespace. The new line character is
    -- considered to be an invalid input for description.
    UpdateFilter -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Represents the criteria to be used in the filter for querying findings.
    UpdateFilter -> Maybe FindingCriteria
findingCriteria :: Prelude.Maybe FindingCriteria,
    -- | Specifies the position of the filter in the list of current filters.
    -- Also specifies the order in which this filter is applied to the
    -- findings.
    UpdateFilter -> Maybe Natural
rank :: Prelude.Maybe Prelude.Natural,
    -- | The unique ID of the detector that specifies the GuardDuty service where
    -- you want to update a filter.
    UpdateFilter -> Text
detectorId :: Prelude.Text,
    -- | The name of the filter.
    UpdateFilter -> Text
filterName :: Prelude.Text
  }
  deriving (UpdateFilter -> UpdateFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFilter -> UpdateFilter -> Bool
$c/= :: UpdateFilter -> UpdateFilter -> Bool
== :: UpdateFilter -> UpdateFilter -> Bool
$c== :: UpdateFilter -> UpdateFilter -> Bool
Prelude.Eq, ReadPrec [UpdateFilter]
ReadPrec UpdateFilter
Int -> ReadS UpdateFilter
ReadS [UpdateFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFilter]
$creadListPrec :: ReadPrec [UpdateFilter]
readPrec :: ReadPrec UpdateFilter
$creadPrec :: ReadPrec UpdateFilter
readList :: ReadS [UpdateFilter]
$creadList :: ReadS [UpdateFilter]
readsPrec :: Int -> ReadS UpdateFilter
$creadsPrec :: Int -> ReadS UpdateFilter
Prelude.Read, Int -> UpdateFilter -> ShowS
[UpdateFilter] -> ShowS
UpdateFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFilter] -> ShowS
$cshowList :: [UpdateFilter] -> ShowS
show :: UpdateFilter -> String
$cshow :: UpdateFilter -> String
showsPrec :: Int -> UpdateFilter -> ShowS
$cshowsPrec :: Int -> UpdateFilter -> ShowS
Prelude.Show, forall x. Rep UpdateFilter x -> UpdateFilter
forall x. UpdateFilter -> Rep UpdateFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFilter x -> UpdateFilter
$cfrom :: forall x. UpdateFilter -> Rep UpdateFilter x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFilter' 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:
--
-- 'action', 'updateFilter_action' - Specifies the action that is to be applied to the findings that match
-- the filter.
--
-- 'description', 'updateFilter_description' - The description of the filter. Valid special characters include period
-- (.), underscore (_), dash (-), and whitespace. The new line character is
-- considered to be an invalid input for description.
--
-- 'findingCriteria', 'updateFilter_findingCriteria' - Represents the criteria to be used in the filter for querying findings.
--
-- 'rank', 'updateFilter_rank' - Specifies the position of the filter in the list of current filters.
-- Also specifies the order in which this filter is applied to the
-- findings.
--
-- 'detectorId', 'updateFilter_detectorId' - The unique ID of the detector that specifies the GuardDuty service where
-- you want to update a filter.
--
-- 'filterName', 'updateFilter_filterName' - The name of the filter.
newUpdateFilter ::
  -- | 'detectorId'
  Prelude.Text ->
  -- | 'filterName'
  Prelude.Text ->
  UpdateFilter
newUpdateFilter :: Text -> Text -> UpdateFilter
newUpdateFilter Text
pDetectorId_ Text
pFilterName_ =
  UpdateFilter'
    { $sel:action:UpdateFilter' :: Maybe FilterAction
action = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateFilter' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:findingCriteria:UpdateFilter' :: Maybe FindingCriteria
findingCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:rank:UpdateFilter' :: Maybe Natural
rank = forall a. Maybe a
Prelude.Nothing,
      $sel:detectorId:UpdateFilter' :: Text
detectorId = Text
pDetectorId_,
      $sel:filterName:UpdateFilter' :: Text
filterName = Text
pFilterName_
    }

-- | Specifies the action that is to be applied to the findings that match
-- the filter.
updateFilter_action :: Lens.Lens' UpdateFilter (Prelude.Maybe FilterAction)
updateFilter_action :: Lens' UpdateFilter (Maybe FilterAction)
updateFilter_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Maybe FilterAction
action :: Maybe FilterAction
$sel:action:UpdateFilter' :: UpdateFilter -> Maybe FilterAction
action} -> Maybe FilterAction
action) (\s :: UpdateFilter
s@UpdateFilter' {} Maybe FilterAction
a -> UpdateFilter
s {$sel:action:UpdateFilter' :: Maybe FilterAction
action = Maybe FilterAction
a} :: UpdateFilter)

-- | The description of the filter. Valid special characters include period
-- (.), underscore (_), dash (-), and whitespace. The new line character is
-- considered to be an invalid input for description.
updateFilter_description :: Lens.Lens' UpdateFilter (Prelude.Maybe Prelude.Text)
updateFilter_description :: Lens' UpdateFilter (Maybe Text)
updateFilter_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Maybe Text
description :: Maybe Text
$sel:description:UpdateFilter' :: UpdateFilter -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateFilter
s@UpdateFilter' {} Maybe Text
a -> UpdateFilter
s {$sel:description:UpdateFilter' :: Maybe Text
description = Maybe Text
a} :: UpdateFilter)

-- | Represents the criteria to be used in the filter for querying findings.
updateFilter_findingCriteria :: Lens.Lens' UpdateFilter (Prelude.Maybe FindingCriteria)
updateFilter_findingCriteria :: Lens' UpdateFilter (Maybe FindingCriteria)
updateFilter_findingCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Maybe FindingCriteria
findingCriteria :: Maybe FindingCriteria
$sel:findingCriteria:UpdateFilter' :: UpdateFilter -> Maybe FindingCriteria
findingCriteria} -> Maybe FindingCriteria
findingCriteria) (\s :: UpdateFilter
s@UpdateFilter' {} Maybe FindingCriteria
a -> UpdateFilter
s {$sel:findingCriteria:UpdateFilter' :: Maybe FindingCriteria
findingCriteria = Maybe FindingCriteria
a} :: UpdateFilter)

-- | Specifies the position of the filter in the list of current filters.
-- Also specifies the order in which this filter is applied to the
-- findings.
updateFilter_rank :: Lens.Lens' UpdateFilter (Prelude.Maybe Prelude.Natural)
updateFilter_rank :: Lens' UpdateFilter (Maybe Natural)
updateFilter_rank = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Maybe Natural
rank :: Maybe Natural
$sel:rank:UpdateFilter' :: UpdateFilter -> Maybe Natural
rank} -> Maybe Natural
rank) (\s :: UpdateFilter
s@UpdateFilter' {} Maybe Natural
a -> UpdateFilter
s {$sel:rank:UpdateFilter' :: Maybe Natural
rank = Maybe Natural
a} :: UpdateFilter)

-- | The unique ID of the detector that specifies the GuardDuty service where
-- you want to update a filter.
updateFilter_detectorId :: Lens.Lens' UpdateFilter Prelude.Text
updateFilter_detectorId :: Lens' UpdateFilter Text
updateFilter_detectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Text
detectorId :: Text
$sel:detectorId:UpdateFilter' :: UpdateFilter -> Text
detectorId} -> Text
detectorId) (\s :: UpdateFilter
s@UpdateFilter' {} Text
a -> UpdateFilter
s {$sel:detectorId:UpdateFilter' :: Text
detectorId = Text
a} :: UpdateFilter)

-- | The name of the filter.
updateFilter_filterName :: Lens.Lens' UpdateFilter Prelude.Text
updateFilter_filterName :: Lens' UpdateFilter Text
updateFilter_filterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFilter' {Text
filterName :: Text
$sel:filterName:UpdateFilter' :: UpdateFilter -> Text
filterName} -> Text
filterName) (\s :: UpdateFilter
s@UpdateFilter' {} Text
a -> UpdateFilter
s {$sel:filterName:UpdateFilter' :: Text
filterName = Text
a} :: UpdateFilter)

instance Core.AWSRequest UpdateFilter where
  type AWSResponse UpdateFilter = UpdateFilterResponse
  request :: (Service -> Service) -> UpdateFilter -> Request UpdateFilter
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 UpdateFilter
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateFilter)))
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 -> UpdateFilterResponse
UpdateFilterResponse'
            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
"name")
      )

instance Prelude.Hashable UpdateFilter where
  hashWithSalt :: Int -> UpdateFilter -> Int
hashWithSalt Int
_salt UpdateFilter' {Maybe Natural
Maybe Text
Maybe FilterAction
Maybe FindingCriteria
Text
filterName :: Text
detectorId :: Text
rank :: Maybe Natural
findingCriteria :: Maybe FindingCriteria
description :: Maybe Text
action :: Maybe FilterAction
$sel:filterName:UpdateFilter' :: UpdateFilter -> Text
$sel:detectorId:UpdateFilter' :: UpdateFilter -> Text
$sel:rank:UpdateFilter' :: UpdateFilter -> Maybe Natural
$sel:findingCriteria:UpdateFilter' :: UpdateFilter -> Maybe FindingCriteria
$sel:description:UpdateFilter' :: UpdateFilter -> Maybe Text
$sel:action:UpdateFilter' :: UpdateFilter -> Maybe FilterAction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FilterAction
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FindingCriteria
findingCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
rank
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
detectorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
filterName

instance Prelude.NFData UpdateFilter where
  rnf :: UpdateFilter -> ()
rnf UpdateFilter' {Maybe Natural
Maybe Text
Maybe FilterAction
Maybe FindingCriteria
Text
filterName :: Text
detectorId :: Text
rank :: Maybe Natural
findingCriteria :: Maybe FindingCriteria
description :: Maybe Text
action :: Maybe FilterAction
$sel:filterName:UpdateFilter' :: UpdateFilter -> Text
$sel:detectorId:UpdateFilter' :: UpdateFilter -> Text
$sel:rank:UpdateFilter' :: UpdateFilter -> Maybe Natural
$sel:findingCriteria:UpdateFilter' :: UpdateFilter -> Maybe FindingCriteria
$sel:description:UpdateFilter' :: UpdateFilter -> Maybe Text
$sel:action:UpdateFilter' :: UpdateFilter -> Maybe FilterAction
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FilterAction
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 FindingCriteria
findingCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
rank
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
detectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
filterName

instance Data.ToHeaders UpdateFilter where
  toHeaders :: UpdateFilter -> 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 UpdateFilter where
  toJSON :: UpdateFilter -> Value
toJSON UpdateFilter' {Maybe Natural
Maybe Text
Maybe FilterAction
Maybe FindingCriteria
Text
filterName :: Text
detectorId :: Text
rank :: Maybe Natural
findingCriteria :: Maybe FindingCriteria
description :: Maybe Text
action :: Maybe FilterAction
$sel:filterName:UpdateFilter' :: UpdateFilter -> Text
$sel:detectorId:UpdateFilter' :: UpdateFilter -> Text
$sel:rank:UpdateFilter' :: UpdateFilter -> Maybe Natural
$sel:findingCriteria:UpdateFilter' :: UpdateFilter -> Maybe FindingCriteria
$sel:description:UpdateFilter' :: UpdateFilter -> Maybe Text
$sel:action:UpdateFilter' :: UpdateFilter -> Maybe FilterAction
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"action" 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 FilterAction
action,
            (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
"findingCriteria" 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 FindingCriteria
findingCriteria,
            (Key
"rank" 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
rank
          ]
      )

instance Data.ToPath UpdateFilter where
  toPath :: UpdateFilter -> ByteString
toPath UpdateFilter' {Maybe Natural
Maybe Text
Maybe FilterAction
Maybe FindingCriteria
Text
filterName :: Text
detectorId :: Text
rank :: Maybe Natural
findingCriteria :: Maybe FindingCriteria
description :: Maybe Text
action :: Maybe FilterAction
$sel:filterName:UpdateFilter' :: UpdateFilter -> Text
$sel:detectorId:UpdateFilter' :: UpdateFilter -> Text
$sel:rank:UpdateFilter' :: UpdateFilter -> Maybe Natural
$sel:findingCriteria:UpdateFilter' :: UpdateFilter -> Maybe FindingCriteria
$sel:description:UpdateFilter' :: UpdateFilter -> Maybe Text
$sel:action:UpdateFilter' :: UpdateFilter -> Maybe FilterAction
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/detector/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
detectorId,
        ByteString
"/filter/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
filterName
      ]

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

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

-- |
-- Create a value of 'UpdateFilterResponse' 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', 'updateFilterResponse_httpStatus' - The response's http status code.
--
-- 'name', 'updateFilterResponse_name' - The name of the filter.
newUpdateFilterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  UpdateFilterResponse
newUpdateFilterResponse :: Int -> Text -> UpdateFilterResponse
newUpdateFilterResponse Int
pHttpStatus_ Text
pName_ =
  UpdateFilterResponse'
    { $sel:httpStatus:UpdateFilterResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:name:UpdateFilterResponse' :: Text
name = Text
pName_
    }

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

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

instance Prelude.NFData UpdateFilterResponse where
  rnf :: UpdateFilterResponse -> ()
rnf UpdateFilterResponse' {Int
Text
name :: Text
httpStatus :: Int
$sel:name:UpdateFilterResponse' :: UpdateFilterResponse -> Text
$sel:httpStatus:UpdateFilterResponse' :: UpdateFilterResponse -> 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
name