{-# 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.UpdateSecurityProfile
-- 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 security profile.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions UpdateSecurityProfile>
-- action.
module Amazonka.IoT.UpdateSecurityProfile
  ( -- * Creating a Request
    UpdateSecurityProfile (..),
    newUpdateSecurityProfile,

    -- * Request Lenses
    updateSecurityProfile_additionalMetricsToRetain,
    updateSecurityProfile_additionalMetricsToRetainV2,
    updateSecurityProfile_alertTargets,
    updateSecurityProfile_behaviors,
    updateSecurityProfile_deleteAdditionalMetricsToRetain,
    updateSecurityProfile_deleteAlertTargets,
    updateSecurityProfile_deleteBehaviors,
    updateSecurityProfile_expectedVersion,
    updateSecurityProfile_securityProfileDescription,
    updateSecurityProfile_securityProfileName,

    -- * Destructuring the Response
    UpdateSecurityProfileResponse (..),
    newUpdateSecurityProfileResponse,

    -- * Response Lenses
    updateSecurityProfileResponse_additionalMetricsToRetain,
    updateSecurityProfileResponse_additionalMetricsToRetainV2,
    updateSecurityProfileResponse_alertTargets,
    updateSecurityProfileResponse_behaviors,
    updateSecurityProfileResponse_creationDate,
    updateSecurityProfileResponse_lastModifiedDate,
    updateSecurityProfileResponse_securityProfileArn,
    updateSecurityProfileResponse_securityProfileDescription,
    updateSecurityProfileResponse_securityProfileName,
    updateSecurityProfileResponse_version,
    updateSecurityProfileResponse_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:/ 'newUpdateSecurityProfile' smart constructor.
data UpdateSecurityProfile = UpdateSecurityProfile'
  { -- | /Please use UpdateSecurityProfileRequest$additionalMetricsToRetainV2
    -- instead./
    --
    -- A list of metrics whose data is retained (stored). By default, data is
    -- retained for any metric used in the profile\'s @behaviors@, but it is
    -- also retained for any metric specified here. Can be used with custom
    -- metrics; cannot be used with dimensions.
    UpdateSecurityProfile -> Maybe [Text]
additionalMetricsToRetain :: Prelude.Maybe [Prelude.Text],
    -- | A list of metrics whose data is retained (stored). By default, data is
    -- retained for any metric used in the profile\'s behaviors, but it is also
    -- retained for any metric specified here. Can be used with custom metrics;
    -- cannot be used with dimensions.
    UpdateSecurityProfile -> Maybe [MetricToRetain]
additionalMetricsToRetainV2 :: Prelude.Maybe [MetricToRetain],
    -- | Where the alerts are sent. (Alerts are always sent to the console.)
    UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets :: Prelude.Maybe (Prelude.HashMap AlertTargetType AlertTarget),
    -- | Specifies the behaviors that, when violated by a device (thing), cause
    -- an alert.
    UpdateSecurityProfile -> Maybe [Behavior]
behaviors :: Prelude.Maybe [Behavior],
    -- | If true, delete all @additionalMetricsToRetain@ defined for this
    -- security profile. If any @additionalMetricsToRetain@ are defined in the
    -- current invocation, an exception occurs.
    UpdateSecurityProfile -> Maybe Bool
deleteAdditionalMetricsToRetain :: Prelude.Maybe Prelude.Bool,
    -- | If true, delete all @alertTargets@ defined for this security profile. If
    -- any @alertTargets@ are defined in the current invocation, an exception
    -- occurs.
    UpdateSecurityProfile -> Maybe Bool
deleteAlertTargets :: Prelude.Maybe Prelude.Bool,
    -- | If true, delete all @behaviors@ defined for this security profile. If
    -- any @behaviors@ are defined in the current invocation, an exception
    -- occurs.
    UpdateSecurityProfile -> Maybe Bool
deleteBehaviors :: Prelude.Maybe Prelude.Bool,
    -- | The expected version of the security profile. A new version is generated
    -- whenever the security profile is updated. If you specify a value that is
    -- different from the actual version, a @VersionConflictException@ is
    -- thrown.
    UpdateSecurityProfile -> Maybe Integer
expectedVersion :: Prelude.Maybe Prelude.Integer,
    -- | A description of the security profile.
    UpdateSecurityProfile -> Maybe Text
securityProfileDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the security profile you want to update.
    UpdateSecurityProfile -> Text
securityProfileName :: Prelude.Text
  }
  deriving (UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
$c/= :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
== :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
$c== :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityProfile]
ReadPrec UpdateSecurityProfile
Int -> ReadS UpdateSecurityProfile
ReadS [UpdateSecurityProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityProfile]
$creadListPrec :: ReadPrec [UpdateSecurityProfile]
readPrec :: ReadPrec UpdateSecurityProfile
$creadPrec :: ReadPrec UpdateSecurityProfile
readList :: ReadS [UpdateSecurityProfile]
$creadList :: ReadS [UpdateSecurityProfile]
readsPrec :: Int -> ReadS UpdateSecurityProfile
$creadsPrec :: Int -> ReadS UpdateSecurityProfile
Prelude.Read, Int -> UpdateSecurityProfile -> ShowS
[UpdateSecurityProfile] -> ShowS
UpdateSecurityProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityProfile] -> ShowS
$cshowList :: [UpdateSecurityProfile] -> ShowS
show :: UpdateSecurityProfile -> String
$cshow :: UpdateSecurityProfile -> String
showsPrec :: Int -> UpdateSecurityProfile -> ShowS
$cshowsPrec :: Int -> UpdateSecurityProfile -> ShowS
Prelude.Show, forall x. Rep UpdateSecurityProfile x -> UpdateSecurityProfile
forall x. UpdateSecurityProfile -> Rep UpdateSecurityProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSecurityProfile x -> UpdateSecurityProfile
$cfrom :: forall x. UpdateSecurityProfile -> Rep UpdateSecurityProfile x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityProfile' 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:
--
-- 'additionalMetricsToRetain', 'updateSecurityProfile_additionalMetricsToRetain' - /Please use UpdateSecurityProfileRequest$additionalMetricsToRetainV2
-- instead./
--
-- A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s @behaviors@, but it is
-- also retained for any metric specified here. Can be used with custom
-- metrics; cannot be used with dimensions.
--
-- 'additionalMetricsToRetainV2', 'updateSecurityProfile_additionalMetricsToRetainV2' - A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s behaviors, but it is also
-- retained for any metric specified here. Can be used with custom metrics;
-- cannot be used with dimensions.
--
-- 'alertTargets', 'updateSecurityProfile_alertTargets' - Where the alerts are sent. (Alerts are always sent to the console.)
--
-- 'behaviors', 'updateSecurityProfile_behaviors' - Specifies the behaviors that, when violated by a device (thing), cause
-- an alert.
--
-- 'deleteAdditionalMetricsToRetain', 'updateSecurityProfile_deleteAdditionalMetricsToRetain' - If true, delete all @additionalMetricsToRetain@ defined for this
-- security profile. If any @additionalMetricsToRetain@ are defined in the
-- current invocation, an exception occurs.
--
-- 'deleteAlertTargets', 'updateSecurityProfile_deleteAlertTargets' - If true, delete all @alertTargets@ defined for this security profile. If
-- any @alertTargets@ are defined in the current invocation, an exception
-- occurs.
--
-- 'deleteBehaviors', 'updateSecurityProfile_deleteBehaviors' - If true, delete all @behaviors@ defined for this security profile. If
-- any @behaviors@ are defined in the current invocation, an exception
-- occurs.
--
-- 'expectedVersion', 'updateSecurityProfile_expectedVersion' - The expected version of the security profile. A new version is generated
-- whenever the security profile is updated. If you specify a value that is
-- different from the actual version, a @VersionConflictException@ is
-- thrown.
--
-- 'securityProfileDescription', 'updateSecurityProfile_securityProfileDescription' - A description of the security profile.
--
-- 'securityProfileName', 'updateSecurityProfile_securityProfileName' - The name of the security profile you want to update.
newUpdateSecurityProfile ::
  -- | 'securityProfileName'
  Prelude.Text ->
  UpdateSecurityProfile
newUpdateSecurityProfile :: Text -> UpdateSecurityProfile
newUpdateSecurityProfile Text
pSecurityProfileName_ =
  UpdateSecurityProfile'
    { $sel:additionalMetricsToRetain:UpdateSecurityProfile' :: Maybe [Text]
additionalMetricsToRetain =
        forall a. Maybe a
Prelude.Nothing,
      $sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: Maybe [MetricToRetain]
additionalMetricsToRetainV2 = forall a. Maybe a
Prelude.Nothing,
      $sel:alertTargets:UpdateSecurityProfile' :: Maybe (HashMap AlertTargetType AlertTarget)
alertTargets = forall a. Maybe a
Prelude.Nothing,
      $sel:behaviors:UpdateSecurityProfile' :: Maybe [Behavior]
behaviors = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: Maybe Bool
deleteAdditionalMetricsToRetain = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteAlertTargets:UpdateSecurityProfile' :: Maybe Bool
deleteAlertTargets = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteBehaviors:UpdateSecurityProfile' :: Maybe Bool
deleteBehaviors = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedVersion:UpdateSecurityProfile' :: Maybe Integer
expectedVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfileDescription:UpdateSecurityProfile' :: Maybe Text
securityProfileDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfileName:UpdateSecurityProfile' :: Text
securityProfileName = Text
pSecurityProfileName_
    }

-- | /Please use UpdateSecurityProfileRequest$additionalMetricsToRetainV2
-- instead./
--
-- A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s @behaviors@, but it is
-- also retained for any metric specified here. Can be used with custom
-- metrics; cannot be used with dimensions.
updateSecurityProfile_additionalMetricsToRetain :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe [Prelude.Text])
updateSecurityProfile_additionalMetricsToRetain :: Lens' UpdateSecurityProfile (Maybe [Text])
updateSecurityProfile_additionalMetricsToRetain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe [Text]
additionalMetricsToRetain :: Maybe [Text]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
additionalMetricsToRetain} -> Maybe [Text]
additionalMetricsToRetain) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe [Text]
a -> UpdateSecurityProfile
s {$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: Maybe [Text]
additionalMetricsToRetain = Maybe [Text]
a} :: UpdateSecurityProfile) 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

-- | A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s behaviors, but it is also
-- retained for any metric specified here. Can be used with custom metrics;
-- cannot be used with dimensions.
updateSecurityProfile_additionalMetricsToRetainV2 :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe [MetricToRetain])
updateSecurityProfile_additionalMetricsToRetainV2 :: Lens' UpdateSecurityProfile (Maybe [MetricToRetain])
updateSecurityProfile_additionalMetricsToRetainV2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe [MetricToRetain]
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
additionalMetricsToRetainV2} -> Maybe [MetricToRetain]
additionalMetricsToRetainV2) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe [MetricToRetain]
a -> UpdateSecurityProfile
s {$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: Maybe [MetricToRetain]
additionalMetricsToRetainV2 = Maybe [MetricToRetain]
a} :: UpdateSecurityProfile) 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

-- | Where the alerts are sent. (Alerts are always sent to the console.)
updateSecurityProfile_alertTargets :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe (Prelude.HashMap AlertTargetType AlertTarget))
updateSecurityProfile_alertTargets :: Lens'
  UpdateSecurityProfile (Maybe (HashMap AlertTargetType AlertTarget))
updateSecurityProfile_alertTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe (HashMap AlertTargetType AlertTarget)
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets} -> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe (HashMap AlertTargetType AlertTarget)
a -> UpdateSecurityProfile
s {$sel:alertTargets:UpdateSecurityProfile' :: Maybe (HashMap AlertTargetType AlertTarget)
alertTargets = Maybe (HashMap AlertTargetType AlertTarget)
a} :: UpdateSecurityProfile) 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

-- | Specifies the behaviors that, when violated by a device (thing), cause
-- an alert.
updateSecurityProfile_behaviors :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe [Behavior])
updateSecurityProfile_behaviors :: Lens' UpdateSecurityProfile (Maybe [Behavior])
updateSecurityProfile_behaviors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe [Behavior]
behaviors :: Maybe [Behavior]
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
behaviors} -> Maybe [Behavior]
behaviors) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe [Behavior]
a -> UpdateSecurityProfile
s {$sel:behaviors:UpdateSecurityProfile' :: Maybe [Behavior]
behaviors = Maybe [Behavior]
a} :: UpdateSecurityProfile) 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

-- | If true, delete all @additionalMetricsToRetain@ defined for this
-- security profile. If any @additionalMetricsToRetain@ are defined in the
-- current invocation, an exception occurs.
updateSecurityProfile_deleteAdditionalMetricsToRetain :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Bool)
updateSecurityProfile_deleteAdditionalMetricsToRetain :: Lens' UpdateSecurityProfile (Maybe Bool)
updateSecurityProfile_deleteAdditionalMetricsToRetain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
deleteAdditionalMetricsToRetain} -> Maybe Bool
deleteAdditionalMetricsToRetain) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Bool
a -> UpdateSecurityProfile
s {$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: Maybe Bool
deleteAdditionalMetricsToRetain = Maybe Bool
a} :: UpdateSecurityProfile)

-- | If true, delete all @alertTargets@ defined for this security profile. If
-- any @alertTargets@ are defined in the current invocation, an exception
-- occurs.
updateSecurityProfile_deleteAlertTargets :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Bool)
updateSecurityProfile_deleteAlertTargets :: Lens' UpdateSecurityProfile (Maybe Bool)
updateSecurityProfile_deleteAlertTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Bool
deleteAlertTargets :: Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
deleteAlertTargets} -> Maybe Bool
deleteAlertTargets) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Bool
a -> UpdateSecurityProfile
s {$sel:deleteAlertTargets:UpdateSecurityProfile' :: Maybe Bool
deleteAlertTargets = Maybe Bool
a} :: UpdateSecurityProfile)

-- | If true, delete all @behaviors@ defined for this security profile. If
-- any @behaviors@ are defined in the current invocation, an exception
-- occurs.
updateSecurityProfile_deleteBehaviors :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Bool)
updateSecurityProfile_deleteBehaviors :: Lens' UpdateSecurityProfile (Maybe Bool)
updateSecurityProfile_deleteBehaviors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Bool
deleteBehaviors :: Maybe Bool
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
deleteBehaviors} -> Maybe Bool
deleteBehaviors) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Bool
a -> UpdateSecurityProfile
s {$sel:deleteBehaviors:UpdateSecurityProfile' :: Maybe Bool
deleteBehaviors = Maybe Bool
a} :: UpdateSecurityProfile)

-- | The expected version of the security profile. A new version is generated
-- whenever the security profile is updated. If you specify a value that is
-- different from the actual version, a @VersionConflictException@ is
-- thrown.
updateSecurityProfile_expectedVersion :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Integer)
updateSecurityProfile_expectedVersion :: Lens' UpdateSecurityProfile (Maybe Integer)
updateSecurityProfile_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Integer
a -> UpdateSecurityProfile
s {$sel:expectedVersion:UpdateSecurityProfile' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: UpdateSecurityProfile)

-- | A description of the security profile.
updateSecurityProfile_securityProfileDescription :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Text)
updateSecurityProfile_securityProfileDescription :: Lens' UpdateSecurityProfile (Maybe Text)
updateSecurityProfile_securityProfileDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Text
securityProfileDescription :: Maybe Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
securityProfileDescription} -> Maybe Text
securityProfileDescription) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Text
a -> UpdateSecurityProfile
s {$sel:securityProfileDescription:UpdateSecurityProfile' :: Maybe Text
securityProfileDescription = Maybe Text
a} :: UpdateSecurityProfile)

-- | The name of the security profile you want to update.
updateSecurityProfile_securityProfileName :: Lens.Lens' UpdateSecurityProfile Prelude.Text
updateSecurityProfile_securityProfileName :: Lens' UpdateSecurityProfile Text
updateSecurityProfile_securityProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Text
securityProfileName :: Text
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
securityProfileName} -> Text
securityProfileName) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Text
a -> UpdateSecurityProfile
s {$sel:securityProfileName:UpdateSecurityProfile' :: Text
securityProfileName = Text
a} :: UpdateSecurityProfile)

instance Core.AWSRequest UpdateSecurityProfile where
  type
    AWSResponse UpdateSecurityProfile =
      UpdateSecurityProfileResponse
  request :: (Service -> Service)
-> UpdateSecurityProfile -> Request UpdateSecurityProfile
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 UpdateSecurityProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSecurityProfile)))
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 ->
          Maybe [Text]
-> Maybe [MetricToRetain]
-> Maybe (HashMap AlertTargetType AlertTarget)
-> Maybe [Behavior]
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Integer
-> Int
-> UpdateSecurityProfileResponse
UpdateSecurityProfileResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"additionalMetricsToRetain"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"additionalMetricsToRetainV2"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"alertTargets" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"behaviors" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"creationDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"lastModifiedDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"securityProfileArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"securityProfileDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"securityProfileName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"version")
            forall (f :: * -> *) a b. Applicative f => 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 UpdateSecurityProfile where
  hashWithSalt :: Int -> UpdateSecurityProfile -> Int
hashWithSalt Int
_salt UpdateSecurityProfile' {Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Text
securityProfileName :: Text
securityProfileDescription :: Maybe Text
expectedVersion :: Maybe Integer
deleteBehaviors :: Maybe Bool
deleteAlertTargets :: Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
additionalMetricsToRetain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MetricToRetain]
additionalMetricsToRetainV2
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap AlertTargetType AlertTarget)
alertTargets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Behavior]
behaviors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteAdditionalMetricsToRetain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteAlertTargets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteBehaviors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
expectedVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
securityProfileDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
securityProfileName

instance Prelude.NFData UpdateSecurityProfile where
  rnf :: UpdateSecurityProfile -> ()
rnf UpdateSecurityProfile' {Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Text
securityProfileName :: Text
securityProfileDescription :: Maybe Text
expectedVersion :: Maybe Integer
deleteBehaviors :: Maybe Bool
deleteAlertTargets :: Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
additionalMetricsToRetain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MetricToRetain]
additionalMetricsToRetainV2
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap AlertTargetType AlertTarget)
alertTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Behavior]
behaviors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteAdditionalMetricsToRetain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteAlertTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteBehaviors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
expectedVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityProfileDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
securityProfileName

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

instance Data.ToJSON UpdateSecurityProfile where
  toJSON :: UpdateSecurityProfile -> Value
toJSON UpdateSecurityProfile' {Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Text
securityProfileName :: Text
securityProfileDescription :: Maybe Text
expectedVersion :: Maybe Integer
deleteBehaviors :: Maybe Bool
deleteAlertTargets :: Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"additionalMetricsToRetain" 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]
additionalMetricsToRetain,
            (Key
"additionalMetricsToRetainV2" 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 [MetricToRetain]
additionalMetricsToRetainV2,
            (Key
"alertTargets" 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 (HashMap AlertTargetType AlertTarget)
alertTargets,
            (Key
"behaviors" 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 [Behavior]
behaviors,
            (Key
"deleteAdditionalMetricsToRetain" 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
deleteAdditionalMetricsToRetain,
            (Key
"deleteAlertTargets" 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
deleteAlertTargets,
            (Key
"deleteBehaviors" 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
deleteBehaviors,
            (Key
"securityProfileDescription" 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
securityProfileDescription
          ]
      )

instance Data.ToPath UpdateSecurityProfile where
  toPath :: UpdateSecurityProfile -> ByteString
toPath UpdateSecurityProfile' {Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Text
securityProfileName :: Text
securityProfileDescription :: Maybe Text
expectedVersion :: Maybe Integer
deleteBehaviors :: Maybe Bool
deleteAlertTargets :: Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/security-profiles/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
securityProfileName
      ]

instance Data.ToQuery UpdateSecurityProfile where
  toQuery :: UpdateSecurityProfile -> QueryString
toQuery UpdateSecurityProfile' {Maybe Bool
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Text
securityProfileName :: Text
securityProfileDescription :: Maybe Text
expectedVersion :: Maybe Integer
deleteBehaviors :: Maybe Bool
deleteAlertTargets :: Maybe Bool
deleteAdditionalMetricsToRetain :: Maybe Bool
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:securityProfileName:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileDescription:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:expectedVersion:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Integer
$sel:deleteBehaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAlertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:deleteAdditionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Bool
$sel:behaviors:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfile' :: UpdateSecurityProfile
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"expectedVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Integer
expectedVersion]

-- | /See:/ 'newUpdateSecurityProfileResponse' smart constructor.
data UpdateSecurityProfileResponse = UpdateSecurityProfileResponse'
  { -- | /Please use UpdateSecurityProfileResponse$additionalMetricsToRetainV2
    -- instead./
    --
    -- A list of metrics whose data is retained (stored). By default, data is
    -- retained for any metric used in the security profile\'s @behaviors@, but
    -- it is also retained for any metric specified here.
    UpdateSecurityProfileResponse -> Maybe [Text]
additionalMetricsToRetain :: Prelude.Maybe [Prelude.Text],
    -- | A list of metrics whose data is retained (stored). By default, data is
    -- retained for any metric used in the profile\'s behaviors, but it is also
    -- retained for any metric specified here. Can be used with custom metrics;
    -- cannot be used with dimensions.
    UpdateSecurityProfileResponse -> Maybe [MetricToRetain]
additionalMetricsToRetainV2 :: Prelude.Maybe [MetricToRetain],
    -- | Where the alerts are sent. (Alerts are always sent to the console.)
    UpdateSecurityProfileResponse
-> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets :: Prelude.Maybe (Prelude.HashMap AlertTargetType AlertTarget),
    -- | Specifies the behaviors that, when violated by a device (thing), cause
    -- an alert.
    UpdateSecurityProfileResponse -> Maybe [Behavior]
behaviors :: Prelude.Maybe [Behavior],
    -- | The time the security profile was created.
    UpdateSecurityProfileResponse -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | The time the security profile was last modified.
    UpdateSecurityProfileResponse -> Maybe POSIX
lastModifiedDate :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the security profile that was updated.
    UpdateSecurityProfileResponse -> Maybe Text
securityProfileArn :: Prelude.Maybe Prelude.Text,
    -- | The description of the security profile.
    UpdateSecurityProfileResponse -> Maybe Text
securityProfileDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the security profile that was updated.
    UpdateSecurityProfileResponse -> Maybe Text
securityProfileName :: Prelude.Maybe Prelude.Text,
    -- | The updated version of the security profile.
    UpdateSecurityProfileResponse -> Maybe Integer
version :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    UpdateSecurityProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
$c/= :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
== :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
$c== :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityProfileResponse]
ReadPrec UpdateSecurityProfileResponse
Int -> ReadS UpdateSecurityProfileResponse
ReadS [UpdateSecurityProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityProfileResponse]
$creadListPrec :: ReadPrec [UpdateSecurityProfileResponse]
readPrec :: ReadPrec UpdateSecurityProfileResponse
$creadPrec :: ReadPrec UpdateSecurityProfileResponse
readList :: ReadS [UpdateSecurityProfileResponse]
$creadList :: ReadS [UpdateSecurityProfileResponse]
readsPrec :: Int -> ReadS UpdateSecurityProfileResponse
$creadsPrec :: Int -> ReadS UpdateSecurityProfileResponse
Prelude.Read, Int -> UpdateSecurityProfileResponse -> ShowS
[UpdateSecurityProfileResponse] -> ShowS
UpdateSecurityProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityProfileResponse] -> ShowS
$cshowList :: [UpdateSecurityProfileResponse] -> ShowS
show :: UpdateSecurityProfileResponse -> String
$cshow :: UpdateSecurityProfileResponse -> String
showsPrec :: Int -> UpdateSecurityProfileResponse -> ShowS
$cshowsPrec :: Int -> UpdateSecurityProfileResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateSecurityProfileResponse x
-> UpdateSecurityProfileResponse
forall x.
UpdateSecurityProfileResponse
-> Rep UpdateSecurityProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSecurityProfileResponse x
-> UpdateSecurityProfileResponse
$cfrom :: forall x.
UpdateSecurityProfileResponse
-> Rep UpdateSecurityProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityProfileResponse' 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:
--
-- 'additionalMetricsToRetain', 'updateSecurityProfileResponse_additionalMetricsToRetain' - /Please use UpdateSecurityProfileResponse$additionalMetricsToRetainV2
-- instead./
--
-- A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the security profile\'s @behaviors@, but
-- it is also retained for any metric specified here.
--
-- 'additionalMetricsToRetainV2', 'updateSecurityProfileResponse_additionalMetricsToRetainV2' - A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s behaviors, but it is also
-- retained for any metric specified here. Can be used with custom metrics;
-- cannot be used with dimensions.
--
-- 'alertTargets', 'updateSecurityProfileResponse_alertTargets' - Where the alerts are sent. (Alerts are always sent to the console.)
--
-- 'behaviors', 'updateSecurityProfileResponse_behaviors' - Specifies the behaviors that, when violated by a device (thing), cause
-- an alert.
--
-- 'creationDate', 'updateSecurityProfileResponse_creationDate' - The time the security profile was created.
--
-- 'lastModifiedDate', 'updateSecurityProfileResponse_lastModifiedDate' - The time the security profile was last modified.
--
-- 'securityProfileArn', 'updateSecurityProfileResponse_securityProfileArn' - The ARN of the security profile that was updated.
--
-- 'securityProfileDescription', 'updateSecurityProfileResponse_securityProfileDescription' - The description of the security profile.
--
-- 'securityProfileName', 'updateSecurityProfileResponse_securityProfileName' - The name of the security profile that was updated.
--
-- 'version', 'updateSecurityProfileResponse_version' - The updated version of the security profile.
--
-- 'httpStatus', 'updateSecurityProfileResponse_httpStatus' - The response's http status code.
newUpdateSecurityProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSecurityProfileResponse
newUpdateSecurityProfileResponse :: Int -> UpdateSecurityProfileResponse
newUpdateSecurityProfileResponse Int
pHttpStatus_ =
  UpdateSecurityProfileResponse'
    { $sel:additionalMetricsToRetain:UpdateSecurityProfileResponse' :: Maybe [Text]
additionalMetricsToRetain =
        forall a. Maybe a
Prelude.Nothing,
      $sel:additionalMetricsToRetainV2:UpdateSecurityProfileResponse' :: Maybe [MetricToRetain]
additionalMetricsToRetainV2 =
        forall a. Maybe a
Prelude.Nothing,
      $sel:alertTargets:UpdateSecurityProfileResponse' :: Maybe (HashMap AlertTargetType AlertTarget)
alertTargets = forall a. Maybe a
Prelude.Nothing,
      $sel:behaviors:UpdateSecurityProfileResponse' :: Maybe [Behavior]
behaviors = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:UpdateSecurityProfileResponse' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedDate:UpdateSecurityProfileResponse' :: Maybe POSIX
lastModifiedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfileArn:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileArn = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfileDescription:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfileName:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileName = forall a. Maybe a
Prelude.Nothing,
      $sel:version:UpdateSecurityProfileResponse' :: Maybe Integer
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSecurityProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | /Please use UpdateSecurityProfileResponse$additionalMetricsToRetainV2
-- instead./
--
-- A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the security profile\'s @behaviors@, but
-- it is also retained for any metric specified here.
updateSecurityProfileResponse_additionalMetricsToRetain :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe [Prelude.Text])
updateSecurityProfileResponse_additionalMetricsToRetain :: Lens' UpdateSecurityProfileResponse (Maybe [Text])
updateSecurityProfileResponse_additionalMetricsToRetain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe [Text]
additionalMetricsToRetain :: Maybe [Text]
$sel:additionalMetricsToRetain:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [Text]
additionalMetricsToRetain} -> Maybe [Text]
additionalMetricsToRetain) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe [Text]
a -> UpdateSecurityProfileResponse
s {$sel:additionalMetricsToRetain:UpdateSecurityProfileResponse' :: Maybe [Text]
additionalMetricsToRetain = Maybe [Text]
a} :: UpdateSecurityProfileResponse) 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

-- | A list of metrics whose data is retained (stored). By default, data is
-- retained for any metric used in the profile\'s behaviors, but it is also
-- retained for any metric specified here. Can be used with custom metrics;
-- cannot be used with dimensions.
updateSecurityProfileResponse_additionalMetricsToRetainV2 :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe [MetricToRetain])
updateSecurityProfileResponse_additionalMetricsToRetainV2 :: Lens' UpdateSecurityProfileResponse (Maybe [MetricToRetain])
updateSecurityProfileResponse_additionalMetricsToRetainV2 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe [MetricToRetain]
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
$sel:additionalMetricsToRetainV2:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [MetricToRetain]
additionalMetricsToRetainV2} -> Maybe [MetricToRetain]
additionalMetricsToRetainV2) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe [MetricToRetain]
a -> UpdateSecurityProfileResponse
s {$sel:additionalMetricsToRetainV2:UpdateSecurityProfileResponse' :: Maybe [MetricToRetain]
additionalMetricsToRetainV2 = Maybe [MetricToRetain]
a} :: UpdateSecurityProfileResponse) 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

-- | Where the alerts are sent. (Alerts are always sent to the console.)
updateSecurityProfileResponse_alertTargets :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe (Prelude.HashMap AlertTargetType AlertTarget))
updateSecurityProfileResponse_alertTargets :: Lens'
  UpdateSecurityProfileResponse
  (Maybe (HashMap AlertTargetType AlertTarget))
updateSecurityProfileResponse_alertTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe (HashMap AlertTargetType AlertTarget)
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
$sel:alertTargets:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse
-> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets} -> Maybe (HashMap AlertTargetType AlertTarget)
alertTargets) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe (HashMap AlertTargetType AlertTarget)
a -> UpdateSecurityProfileResponse
s {$sel:alertTargets:UpdateSecurityProfileResponse' :: Maybe (HashMap AlertTargetType AlertTarget)
alertTargets = Maybe (HashMap AlertTargetType AlertTarget)
a} :: UpdateSecurityProfileResponse) 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

-- | Specifies the behaviors that, when violated by a device (thing), cause
-- an alert.
updateSecurityProfileResponse_behaviors :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe [Behavior])
updateSecurityProfileResponse_behaviors :: Lens' UpdateSecurityProfileResponse (Maybe [Behavior])
updateSecurityProfileResponse_behaviors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe [Behavior]
behaviors :: Maybe [Behavior]
$sel:behaviors:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [Behavior]
behaviors} -> Maybe [Behavior]
behaviors) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe [Behavior]
a -> UpdateSecurityProfileResponse
s {$sel:behaviors:UpdateSecurityProfileResponse' :: Maybe [Behavior]
behaviors = Maybe [Behavior]
a} :: UpdateSecurityProfileResponse) 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 the security profile was created.
updateSecurityProfileResponse_creationDate :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.UTCTime)
updateSecurityProfileResponse_creationDate :: Lens' UpdateSecurityProfileResponse (Maybe UTCTime)
updateSecurityProfileResponse_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe POSIX
a -> UpdateSecurityProfileResponse
s {$sel:creationDate:UpdateSecurityProfileResponse' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: UpdateSecurityProfileResponse) 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

-- | The time the security profile was last modified.
updateSecurityProfileResponse_lastModifiedDate :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.UTCTime)
updateSecurityProfileResponse_lastModifiedDate :: Lens' UpdateSecurityProfileResponse (Maybe UTCTime)
updateSecurityProfileResponse_lastModifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe POSIX
lastModifiedDate :: Maybe POSIX
$sel:lastModifiedDate:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe POSIX
lastModifiedDate} -> Maybe POSIX
lastModifiedDate) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe POSIX
a -> UpdateSecurityProfileResponse
s {$sel:lastModifiedDate:UpdateSecurityProfileResponse' :: Maybe POSIX
lastModifiedDate = Maybe POSIX
a} :: UpdateSecurityProfileResponse) 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

-- | The ARN of the security profile that was updated.
updateSecurityProfileResponse_securityProfileArn :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.Text)
updateSecurityProfileResponse_securityProfileArn :: Lens' UpdateSecurityProfileResponse (Maybe Text)
updateSecurityProfileResponse_securityProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe Text
securityProfileArn :: Maybe Text
$sel:securityProfileArn:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
securityProfileArn} -> Maybe Text
securityProfileArn) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe Text
a -> UpdateSecurityProfileResponse
s {$sel:securityProfileArn:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileArn = Maybe Text
a} :: UpdateSecurityProfileResponse)

-- | The description of the security profile.
updateSecurityProfileResponse_securityProfileDescription :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.Text)
updateSecurityProfileResponse_securityProfileDescription :: Lens' UpdateSecurityProfileResponse (Maybe Text)
updateSecurityProfileResponse_securityProfileDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe Text
securityProfileDescription :: Maybe Text
$sel:securityProfileDescription:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
securityProfileDescription} -> Maybe Text
securityProfileDescription) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe Text
a -> UpdateSecurityProfileResponse
s {$sel:securityProfileDescription:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileDescription = Maybe Text
a} :: UpdateSecurityProfileResponse)

-- | The name of the security profile that was updated.
updateSecurityProfileResponse_securityProfileName :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.Text)
updateSecurityProfileResponse_securityProfileName :: Lens' UpdateSecurityProfileResponse (Maybe Text)
updateSecurityProfileResponse_securityProfileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe Text
securityProfileName :: Maybe Text
$sel:securityProfileName:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
securityProfileName} -> Maybe Text
securityProfileName) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe Text
a -> UpdateSecurityProfileResponse
s {$sel:securityProfileName:UpdateSecurityProfileResponse' :: Maybe Text
securityProfileName = Maybe Text
a} :: UpdateSecurityProfileResponse)

-- | The updated version of the security profile.
updateSecurityProfileResponse_version :: Lens.Lens' UpdateSecurityProfileResponse (Prelude.Maybe Prelude.Integer)
updateSecurityProfileResponse_version :: Lens' UpdateSecurityProfileResponse (Maybe Integer)
updateSecurityProfileResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfileResponse' {Maybe Integer
version :: Maybe Integer
$sel:version:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Integer
version} -> Maybe Integer
version) (\s :: UpdateSecurityProfileResponse
s@UpdateSecurityProfileResponse' {} Maybe Integer
a -> UpdateSecurityProfileResponse
s {$sel:version:UpdateSecurityProfileResponse' :: Maybe Integer
version = Maybe Integer
a} :: UpdateSecurityProfileResponse)

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

instance Prelude.NFData UpdateSecurityProfileResponse where
  rnf :: UpdateSecurityProfileResponse -> ()
rnf UpdateSecurityProfileResponse' {Int
Maybe Integer
Maybe [Text]
Maybe [MetricToRetain]
Maybe [Behavior]
Maybe Text
Maybe (HashMap AlertTargetType AlertTarget)
Maybe POSIX
httpStatus :: Int
version :: Maybe Integer
securityProfileName :: Maybe Text
securityProfileDescription :: Maybe Text
securityProfileArn :: Maybe Text
lastModifiedDate :: Maybe POSIX
creationDate :: Maybe POSIX
behaviors :: Maybe [Behavior]
alertTargets :: Maybe (HashMap AlertTargetType AlertTarget)
additionalMetricsToRetainV2 :: Maybe [MetricToRetain]
additionalMetricsToRetain :: Maybe [Text]
$sel:httpStatus:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Int
$sel:version:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Integer
$sel:securityProfileName:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
$sel:securityProfileDescription:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
$sel:securityProfileArn:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe Text
$sel:lastModifiedDate:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe POSIX
$sel:creationDate:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe POSIX
$sel:behaviors:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [Behavior]
$sel:alertTargets:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse
-> Maybe (HashMap AlertTargetType AlertTarget)
$sel:additionalMetricsToRetainV2:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [MetricToRetain]
$sel:additionalMetricsToRetain:UpdateSecurityProfileResponse' :: UpdateSecurityProfileResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
additionalMetricsToRetain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MetricToRetain]
additionalMetricsToRetainV2
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap AlertTargetType AlertTarget)
alertTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Behavior]
behaviors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityProfileArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityProfileDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus