{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Inspector.Types.FindingFilter
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Inspector.Types.FindingFilter where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Inspector.Types.Attribute
import Amazonka.Inspector.Types.Severity
import Amazonka.Inspector.Types.TimestampRange
import qualified Amazonka.Prelude as Prelude

-- | This data type is used as a request parameter in the ListFindings
-- action.
--
-- /See:/ 'newFindingFilter' smart constructor.
data FindingFilter = FindingFilter'
  { -- | For a record to match a filter, one of the values that is specified for
    -- this data type property must be the exact match of the value of the
    -- __agentId__ property of the Finding data type.
    FindingFilter -> Maybe [Text]
agentIds :: Prelude.Maybe [Prelude.Text],
    -- | For a record to match a filter, the list of values that are specified
    -- for this data type property must be contained in the list of values of
    -- the __attributes__ property of the Finding data type.
    FindingFilter -> Maybe [Attribute]
attributes :: Prelude.Maybe [Attribute],
    -- | For a record to match a filter, one of the values that is specified for
    -- this data type property must be the exact match of the value of the
    -- __autoScalingGroup__ property of the Finding data type.
    FindingFilter -> Maybe [Text]
autoScalingGroups :: Prelude.Maybe [Prelude.Text],
    -- | The time range during which the finding is generated.
    FindingFilter -> Maybe TimestampRange
creationTimeRange :: Prelude.Maybe TimestampRange,
    -- | For a record to match a filter, one of the values that is specified for
    -- this data type property must be the exact match of the value of the
    -- __ruleName__ property of the Finding data type.
    FindingFilter -> Maybe [Text]
ruleNames :: Prelude.Maybe [Prelude.Text],
    -- | For a record to match a filter, one of the values that is specified for
    -- this data type property must be the exact match of the value of the
    -- __rulesPackageArn__ property of the Finding data type.
    FindingFilter -> Maybe [Text]
rulesPackageArns :: Prelude.Maybe [Prelude.Text],
    -- | For a record to match a filter, one of the values that is specified for
    -- this data type property must be the exact match of the value of the
    -- __severity__ property of the Finding data type.
    FindingFilter -> Maybe [Severity]
severities :: Prelude.Maybe [Severity],
    -- | For a record to match a filter, the value that is specified for this
    -- data type property must be contained in the list of values of the
    -- __userAttributes__ property of the Finding data type.
    FindingFilter -> Maybe [Attribute]
userAttributes :: Prelude.Maybe [Attribute]
  }
  deriving (FindingFilter -> FindingFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FindingFilter -> FindingFilter -> Bool
$c/= :: FindingFilter -> FindingFilter -> Bool
== :: FindingFilter -> FindingFilter -> Bool
$c== :: FindingFilter -> FindingFilter -> Bool
Prelude.Eq, ReadPrec [FindingFilter]
ReadPrec FindingFilter
Int -> ReadS FindingFilter
ReadS [FindingFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FindingFilter]
$creadListPrec :: ReadPrec [FindingFilter]
readPrec :: ReadPrec FindingFilter
$creadPrec :: ReadPrec FindingFilter
readList :: ReadS [FindingFilter]
$creadList :: ReadS [FindingFilter]
readsPrec :: Int -> ReadS FindingFilter
$creadsPrec :: Int -> ReadS FindingFilter
Prelude.Read, Int -> FindingFilter -> ShowS
[FindingFilter] -> ShowS
FindingFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FindingFilter] -> ShowS
$cshowList :: [FindingFilter] -> ShowS
show :: FindingFilter -> String
$cshow :: FindingFilter -> String
showsPrec :: Int -> FindingFilter -> ShowS
$cshowsPrec :: Int -> FindingFilter -> ShowS
Prelude.Show, forall x. Rep FindingFilter x -> FindingFilter
forall x. FindingFilter -> Rep FindingFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FindingFilter x -> FindingFilter
$cfrom :: forall x. FindingFilter -> Rep FindingFilter x
Prelude.Generic)

-- |
-- Create a value of 'FindingFilter' 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:
--
-- 'agentIds', 'findingFilter_agentIds' - For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __agentId__ property of the Finding data type.
--
-- 'attributes', 'findingFilter_attributes' - For a record to match a filter, the list of values that are specified
-- for this data type property must be contained in the list of values of
-- the __attributes__ property of the Finding data type.
--
-- 'autoScalingGroups', 'findingFilter_autoScalingGroups' - For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __autoScalingGroup__ property of the Finding data type.
--
-- 'creationTimeRange', 'findingFilter_creationTimeRange' - The time range during which the finding is generated.
--
-- 'ruleNames', 'findingFilter_ruleNames' - For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __ruleName__ property of the Finding data type.
--
-- 'rulesPackageArns', 'findingFilter_rulesPackageArns' - For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __rulesPackageArn__ property of the Finding data type.
--
-- 'severities', 'findingFilter_severities' - For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __severity__ property of the Finding data type.
--
-- 'userAttributes', 'findingFilter_userAttributes' - For a record to match a filter, the value that is specified for this
-- data type property must be contained in the list of values of the
-- __userAttributes__ property of the Finding data type.
newFindingFilter ::
  FindingFilter
newFindingFilter :: FindingFilter
newFindingFilter =
  FindingFilter'
    { $sel:agentIds:FindingFilter' :: Maybe [Text]
agentIds = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:FindingFilter' :: Maybe [Attribute]
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroups:FindingFilter' :: Maybe [Text]
autoScalingGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimeRange:FindingFilter' :: Maybe TimestampRange
creationTimeRange = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleNames:FindingFilter' :: Maybe [Text]
ruleNames = forall a. Maybe a
Prelude.Nothing,
      $sel:rulesPackageArns:FindingFilter' :: Maybe [Text]
rulesPackageArns = forall a. Maybe a
Prelude.Nothing,
      $sel:severities:FindingFilter' :: Maybe [Severity]
severities = forall a. Maybe a
Prelude.Nothing,
      $sel:userAttributes:FindingFilter' :: Maybe [Attribute]
userAttributes = forall a. Maybe a
Prelude.Nothing
    }

-- | For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __agentId__ property of the Finding data type.
findingFilter_agentIds :: Lens.Lens' FindingFilter (Prelude.Maybe [Prelude.Text])
findingFilter_agentIds :: Lens' FindingFilter (Maybe [Text])
findingFilter_agentIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Text]
agentIds :: Maybe [Text]
$sel:agentIds:FindingFilter' :: FindingFilter -> Maybe [Text]
agentIds} -> Maybe [Text]
agentIds) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Text]
a -> FindingFilter
s {$sel:agentIds:FindingFilter' :: Maybe [Text]
agentIds = Maybe [Text]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | For a record to match a filter, the list of values that are specified
-- for this data type property must be contained in the list of values of
-- the __attributes__ property of the Finding data type.
findingFilter_attributes :: Lens.Lens' FindingFilter (Prelude.Maybe [Attribute])
findingFilter_attributes :: Lens' FindingFilter (Maybe [Attribute])
findingFilter_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Attribute]
attributes :: Maybe [Attribute]
$sel:attributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
attributes} -> Maybe [Attribute]
attributes) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Attribute]
a -> FindingFilter
s {$sel:attributes:FindingFilter' :: Maybe [Attribute]
attributes = Maybe [Attribute]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __autoScalingGroup__ property of the Finding data type.
findingFilter_autoScalingGroups :: Lens.Lens' FindingFilter (Prelude.Maybe [Prelude.Text])
findingFilter_autoScalingGroups :: Lens' FindingFilter (Maybe [Text])
findingFilter_autoScalingGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Text]
autoScalingGroups :: Maybe [Text]
$sel:autoScalingGroups:FindingFilter' :: FindingFilter -> Maybe [Text]
autoScalingGroups} -> Maybe [Text]
autoScalingGroups) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Text]
a -> FindingFilter
s {$sel:autoScalingGroups:FindingFilter' :: Maybe [Text]
autoScalingGroups = Maybe [Text]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The time range during which the finding is generated.
findingFilter_creationTimeRange :: Lens.Lens' FindingFilter (Prelude.Maybe TimestampRange)
findingFilter_creationTimeRange :: Lens' FindingFilter (Maybe TimestampRange)
findingFilter_creationTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe TimestampRange
creationTimeRange :: Maybe TimestampRange
$sel:creationTimeRange:FindingFilter' :: FindingFilter -> Maybe TimestampRange
creationTimeRange} -> Maybe TimestampRange
creationTimeRange) (\s :: FindingFilter
s@FindingFilter' {} Maybe TimestampRange
a -> FindingFilter
s {$sel:creationTimeRange:FindingFilter' :: Maybe TimestampRange
creationTimeRange = Maybe TimestampRange
a} :: FindingFilter)

-- | For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __ruleName__ property of the Finding data type.
findingFilter_ruleNames :: Lens.Lens' FindingFilter (Prelude.Maybe [Prelude.Text])
findingFilter_ruleNames :: Lens' FindingFilter (Maybe [Text])
findingFilter_ruleNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Text]
ruleNames :: Maybe [Text]
$sel:ruleNames:FindingFilter' :: FindingFilter -> Maybe [Text]
ruleNames} -> Maybe [Text]
ruleNames) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Text]
a -> FindingFilter
s {$sel:ruleNames:FindingFilter' :: Maybe [Text]
ruleNames = Maybe [Text]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __rulesPackageArn__ property of the Finding data type.
findingFilter_rulesPackageArns :: Lens.Lens' FindingFilter (Prelude.Maybe [Prelude.Text])
findingFilter_rulesPackageArns :: Lens' FindingFilter (Maybe [Text])
findingFilter_rulesPackageArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Text]
rulesPackageArns :: Maybe [Text]
$sel:rulesPackageArns:FindingFilter' :: FindingFilter -> Maybe [Text]
rulesPackageArns} -> Maybe [Text]
rulesPackageArns) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Text]
a -> FindingFilter
s {$sel:rulesPackageArns:FindingFilter' :: Maybe [Text]
rulesPackageArns = Maybe [Text]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | For a record to match a filter, one of the values that is specified for
-- this data type property must be the exact match of the value of the
-- __severity__ property of the Finding data type.
findingFilter_severities :: Lens.Lens' FindingFilter (Prelude.Maybe [Severity])
findingFilter_severities :: Lens' FindingFilter (Maybe [Severity])
findingFilter_severities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Severity]
severities :: Maybe [Severity]
$sel:severities:FindingFilter' :: FindingFilter -> Maybe [Severity]
severities} -> Maybe [Severity]
severities) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Severity]
a -> FindingFilter
s {$sel:severities:FindingFilter' :: Maybe [Severity]
severities = Maybe [Severity]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | For a record to match a filter, the value that is specified for this
-- data type property must be contained in the list of values of the
-- __userAttributes__ property of the Finding data type.
findingFilter_userAttributes :: Lens.Lens' FindingFilter (Prelude.Maybe [Attribute])
findingFilter_userAttributes :: Lens' FindingFilter (Maybe [Attribute])
findingFilter_userAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindingFilter' {Maybe [Attribute]
userAttributes :: Maybe [Attribute]
$sel:userAttributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
userAttributes} -> Maybe [Attribute]
userAttributes) (\s :: FindingFilter
s@FindingFilter' {} Maybe [Attribute]
a -> FindingFilter
s {$sel:userAttributes:FindingFilter' :: Maybe [Attribute]
userAttributes = Maybe [Attribute]
a} :: FindingFilter) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.Hashable FindingFilter where
  hashWithSalt :: Int -> FindingFilter -> Int
hashWithSalt Int
_salt FindingFilter' {Maybe [Text]
Maybe [Attribute]
Maybe [Severity]
Maybe TimestampRange
userAttributes :: Maybe [Attribute]
severities :: Maybe [Severity]
rulesPackageArns :: Maybe [Text]
ruleNames :: Maybe [Text]
creationTimeRange :: Maybe TimestampRange
autoScalingGroups :: Maybe [Text]
attributes :: Maybe [Attribute]
agentIds :: Maybe [Text]
$sel:userAttributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:severities:FindingFilter' :: FindingFilter -> Maybe [Severity]
$sel:rulesPackageArns:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:ruleNames:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:creationTimeRange:FindingFilter' :: FindingFilter -> Maybe TimestampRange
$sel:autoScalingGroups:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:attributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:agentIds:FindingFilter' :: FindingFilter -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
agentIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Attribute]
attributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
autoScalingGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TimestampRange
creationTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
ruleNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
rulesPackageArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Severity]
severities
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Attribute]
userAttributes

instance Prelude.NFData FindingFilter where
  rnf :: FindingFilter -> ()
rnf FindingFilter' {Maybe [Text]
Maybe [Attribute]
Maybe [Severity]
Maybe TimestampRange
userAttributes :: Maybe [Attribute]
severities :: Maybe [Severity]
rulesPackageArns :: Maybe [Text]
ruleNames :: Maybe [Text]
creationTimeRange :: Maybe TimestampRange
autoScalingGroups :: Maybe [Text]
attributes :: Maybe [Attribute]
agentIds :: Maybe [Text]
$sel:userAttributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:severities:FindingFilter' :: FindingFilter -> Maybe [Severity]
$sel:rulesPackageArns:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:ruleNames:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:creationTimeRange:FindingFilter' :: FindingFilter -> Maybe TimestampRange
$sel:autoScalingGroups:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:attributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:agentIds:FindingFilter' :: FindingFilter -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
agentIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Attribute]
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
autoScalingGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TimestampRange
creationTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
ruleNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
rulesPackageArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Severity]
severities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Attribute]
userAttributes

instance Data.ToJSON FindingFilter where
  toJSON :: FindingFilter -> Value
toJSON FindingFilter' {Maybe [Text]
Maybe [Attribute]
Maybe [Severity]
Maybe TimestampRange
userAttributes :: Maybe [Attribute]
severities :: Maybe [Severity]
rulesPackageArns :: Maybe [Text]
ruleNames :: Maybe [Text]
creationTimeRange :: Maybe TimestampRange
autoScalingGroups :: Maybe [Text]
attributes :: Maybe [Attribute]
agentIds :: Maybe [Text]
$sel:userAttributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:severities:FindingFilter' :: FindingFilter -> Maybe [Severity]
$sel:rulesPackageArns:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:ruleNames:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:creationTimeRange:FindingFilter' :: FindingFilter -> Maybe TimestampRange
$sel:autoScalingGroups:FindingFilter' :: FindingFilter -> Maybe [Text]
$sel:attributes:FindingFilter' :: FindingFilter -> Maybe [Attribute]
$sel:agentIds:FindingFilter' :: FindingFilter -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"agentIds" 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]
agentIds,
            (Key
"attributes" 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 [Attribute]
attributes,
            (Key
"autoScalingGroups" 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]
autoScalingGroups,
            (Key
"creationTimeRange" 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 TimestampRange
creationTimeRange,
            (Key
"ruleNames" 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]
ruleNames,
            (Key
"rulesPackageArns" 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]
rulesPackageArns,
            (Key
"severities" 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 [Severity]
severities,
            (Key
"userAttributes" 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 [Attribute]
userAttributes
          ]
      )