{-# 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.ResilienceHub.Types.ResiliencyPolicy
-- 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.ResilienceHub.Types.ResiliencyPolicy where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.ResilienceHub.Types.DataLocationConstraint
import Amazonka.ResilienceHub.Types.DisruptionType
import Amazonka.ResilienceHub.Types.EstimatedCostTier
import Amazonka.ResilienceHub.Types.FailurePolicy
import Amazonka.ResilienceHub.Types.ResiliencyPolicyTier

-- | Defines a resiliency policy.
--
-- /See:/ 'newResiliencyPolicy' smart constructor.
data ResiliencyPolicy = ResiliencyPolicy'
  { -- | The timestamp for when the resiliency policy was created.
    ResiliencyPolicy -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | Specifies a high-level geographical location constraint for where your
    -- resilience policy data can be stored.
    ResiliencyPolicy -> Maybe DataLocationConstraint
dataLocationConstraint :: Prelude.Maybe DataLocationConstraint,
    -- | Specifies the estimated cost tier of the resiliency policy.
    ResiliencyPolicy -> Maybe EstimatedCostTier
estimatedCostTier :: Prelude.Maybe EstimatedCostTier,
    -- | The resiliency policy.
    ResiliencyPolicy -> Maybe (HashMap DisruptionType FailurePolicy)
policy :: Prelude.Maybe (Prelude.HashMap DisruptionType FailurePolicy),
    -- | The Amazon Resource Name (ARN) of the resiliency policy. The format for
    -- this ARN is:
    -- arn:@partition@:resiliencehub:@region@:@account@:resiliency-policy\/@policy-id@.
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /AWS General Reference/.
    ResiliencyPolicy -> Maybe Text
policyArn :: Prelude.Maybe Prelude.Text,
    -- | The description for the policy.
    ResiliencyPolicy -> Maybe Text
policyDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the policy
    ResiliencyPolicy -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to the resource. A tag is a label that you assign to
    -- an Amazon Web Services resource. Each tag consists of a key\/value pair.
    ResiliencyPolicy -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The tier for this resiliency policy, ranging from the highest severity
    -- (@MissionCritical@) to lowest (@NonCritical@).
    ResiliencyPolicy -> Maybe ResiliencyPolicyTier
tier :: Prelude.Maybe ResiliencyPolicyTier
  }
  deriving (ResiliencyPolicy -> ResiliencyPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResiliencyPolicy -> ResiliencyPolicy -> Bool
$c/= :: ResiliencyPolicy -> ResiliencyPolicy -> Bool
== :: ResiliencyPolicy -> ResiliencyPolicy -> Bool
$c== :: ResiliencyPolicy -> ResiliencyPolicy -> Bool
Prelude.Eq, Int -> ResiliencyPolicy -> ShowS
[ResiliencyPolicy] -> ShowS
ResiliencyPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResiliencyPolicy] -> ShowS
$cshowList :: [ResiliencyPolicy] -> ShowS
show :: ResiliencyPolicy -> String
$cshow :: ResiliencyPolicy -> String
showsPrec :: Int -> ResiliencyPolicy -> ShowS
$cshowsPrec :: Int -> ResiliencyPolicy -> ShowS
Prelude.Show, forall x. Rep ResiliencyPolicy x -> ResiliencyPolicy
forall x. ResiliencyPolicy -> Rep ResiliencyPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResiliencyPolicy x -> ResiliencyPolicy
$cfrom :: forall x. ResiliencyPolicy -> Rep ResiliencyPolicy x
Prelude.Generic)

-- |
-- Create a value of 'ResiliencyPolicy' 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:
--
-- 'creationTime', 'resiliencyPolicy_creationTime' - The timestamp for when the resiliency policy was created.
--
-- 'dataLocationConstraint', 'resiliencyPolicy_dataLocationConstraint' - Specifies a high-level geographical location constraint for where your
-- resilience policy data can be stored.
--
-- 'estimatedCostTier', 'resiliencyPolicy_estimatedCostTier' - Specifies the estimated cost tier of the resiliency policy.
--
-- 'policy', 'resiliencyPolicy_policy' - The resiliency policy.
--
-- 'policyArn', 'resiliencyPolicy_policyArn' - The Amazon Resource Name (ARN) of the resiliency policy. The format for
-- this ARN is:
-- arn:@partition@:resiliencehub:@region@:@account@:resiliency-policy\/@policy-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
--
-- 'policyDescription', 'resiliencyPolicy_policyDescription' - The description for the policy.
--
-- 'policyName', 'resiliencyPolicy_policyName' - The name of the policy
--
-- 'tags', 'resiliencyPolicy_tags' - The tags assigned to the resource. A tag is a label that you assign to
-- an Amazon Web Services resource. Each tag consists of a key\/value pair.
--
-- 'tier', 'resiliencyPolicy_tier' - The tier for this resiliency policy, ranging from the highest severity
-- (@MissionCritical@) to lowest (@NonCritical@).
newResiliencyPolicy ::
  ResiliencyPolicy
newResiliencyPolicy :: ResiliencyPolicy
newResiliencyPolicy =
  ResiliencyPolicy'
    { $sel:creationTime:ResiliencyPolicy' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dataLocationConstraint:ResiliencyPolicy' :: Maybe DataLocationConstraint
dataLocationConstraint = forall a. Maybe a
Prelude.Nothing,
      $sel:estimatedCostTier:ResiliencyPolicy' :: Maybe EstimatedCostTier
estimatedCostTier = forall a. Maybe a
Prelude.Nothing,
      $sel:policy:ResiliencyPolicy' :: Maybe (HashMap DisruptionType FailurePolicy)
policy = forall a. Maybe a
Prelude.Nothing,
      $sel:policyArn:ResiliencyPolicy' :: Maybe Text
policyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:policyDescription:ResiliencyPolicy' :: Maybe Text
policyDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:ResiliencyPolicy' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ResiliencyPolicy' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tier:ResiliencyPolicy' :: Maybe ResiliencyPolicyTier
tier = forall a. Maybe a
Prelude.Nothing
    }

-- | The timestamp for when the resiliency policy was created.
resiliencyPolicy_creationTime :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe Prelude.UTCTime)
resiliencyPolicy_creationTime :: Lens' ResiliencyPolicy (Maybe UTCTime)
resiliencyPolicy_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe POSIX
a -> ResiliencyPolicy
s {$sel:creationTime:ResiliencyPolicy' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: ResiliencyPolicy) 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

-- | Specifies a high-level geographical location constraint for where your
-- resilience policy data can be stored.
resiliencyPolicy_dataLocationConstraint :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe DataLocationConstraint)
resiliencyPolicy_dataLocationConstraint :: Lens' ResiliencyPolicy (Maybe DataLocationConstraint)
resiliencyPolicy_dataLocationConstraint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe DataLocationConstraint
dataLocationConstraint :: Maybe DataLocationConstraint
$sel:dataLocationConstraint:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe DataLocationConstraint
dataLocationConstraint} -> Maybe DataLocationConstraint
dataLocationConstraint) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe DataLocationConstraint
a -> ResiliencyPolicy
s {$sel:dataLocationConstraint:ResiliencyPolicy' :: Maybe DataLocationConstraint
dataLocationConstraint = Maybe DataLocationConstraint
a} :: ResiliencyPolicy)

-- | Specifies the estimated cost tier of the resiliency policy.
resiliencyPolicy_estimatedCostTier :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe EstimatedCostTier)
resiliencyPolicy_estimatedCostTier :: Lens' ResiliencyPolicy (Maybe EstimatedCostTier)
resiliencyPolicy_estimatedCostTier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe EstimatedCostTier
estimatedCostTier :: Maybe EstimatedCostTier
$sel:estimatedCostTier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe EstimatedCostTier
estimatedCostTier} -> Maybe EstimatedCostTier
estimatedCostTier) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe EstimatedCostTier
a -> ResiliencyPolicy
s {$sel:estimatedCostTier:ResiliencyPolicy' :: Maybe EstimatedCostTier
estimatedCostTier = Maybe EstimatedCostTier
a} :: ResiliencyPolicy)

-- | The resiliency policy.
resiliencyPolicy_policy :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe (Prelude.HashMap DisruptionType FailurePolicy))
resiliencyPolicy_policy :: Lens'
  ResiliencyPolicy (Maybe (HashMap DisruptionType FailurePolicy))
resiliencyPolicy_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe (HashMap DisruptionType FailurePolicy)
policy :: Maybe (HashMap DisruptionType FailurePolicy)
$sel:policy:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (HashMap DisruptionType FailurePolicy)
policy} -> Maybe (HashMap DisruptionType FailurePolicy)
policy) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe (HashMap DisruptionType FailurePolicy)
a -> ResiliencyPolicy
s {$sel:policy:ResiliencyPolicy' :: Maybe (HashMap DisruptionType FailurePolicy)
policy = Maybe (HashMap DisruptionType FailurePolicy)
a} :: ResiliencyPolicy) 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 Amazon Resource Name (ARN) of the resiliency policy. The format for
-- this ARN is:
-- arn:@partition@:resiliencehub:@region@:@account@:resiliency-policy\/@policy-id@.
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /AWS General Reference/.
resiliencyPolicy_policyArn :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe Prelude.Text)
resiliencyPolicy_policyArn :: Lens' ResiliencyPolicy (Maybe Text)
resiliencyPolicy_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe Text
policyArn :: Maybe Text
$sel:policyArn:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
policyArn} -> Maybe Text
policyArn) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe Text
a -> ResiliencyPolicy
s {$sel:policyArn:ResiliencyPolicy' :: Maybe Text
policyArn = Maybe Text
a} :: ResiliencyPolicy)

-- | The description for the policy.
resiliencyPolicy_policyDescription :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe Prelude.Text)
resiliencyPolicy_policyDescription :: Lens' ResiliencyPolicy (Maybe Text)
resiliencyPolicy_policyDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe Text
policyDescription :: Maybe Text
$sel:policyDescription:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
policyDescription} -> Maybe Text
policyDescription) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe Text
a -> ResiliencyPolicy
s {$sel:policyDescription:ResiliencyPolicy' :: Maybe Text
policyDescription = Maybe Text
a} :: ResiliencyPolicy)

-- | The name of the policy
resiliencyPolicy_policyName :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe Prelude.Text)
resiliencyPolicy_policyName :: Lens' ResiliencyPolicy (Maybe Text)
resiliencyPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe Text
policyName :: Maybe Text
$sel:policyName:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe Text
a -> ResiliencyPolicy
s {$sel:policyName:ResiliencyPolicy' :: Maybe Text
policyName = Maybe Text
a} :: ResiliencyPolicy)

-- | The tags assigned to the resource. A tag is a label that you assign to
-- an Amazon Web Services resource. Each tag consists of a key\/value pair.
resiliencyPolicy_tags :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
resiliencyPolicy_tags :: Lens' ResiliencyPolicy (Maybe (HashMap Text Text))
resiliencyPolicy_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe (Sensitive (HashMap Text Text))
a -> ResiliencyPolicy
s {$sel:tags:ResiliencyPolicy' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: ResiliencyPolicy) 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. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The tier for this resiliency policy, ranging from the highest severity
-- (@MissionCritical@) to lowest (@NonCritical@).
resiliencyPolicy_tier :: Lens.Lens' ResiliencyPolicy (Prelude.Maybe ResiliencyPolicyTier)
resiliencyPolicy_tier :: Lens' ResiliencyPolicy (Maybe ResiliencyPolicyTier)
resiliencyPolicy_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResiliencyPolicy' {Maybe ResiliencyPolicyTier
tier :: Maybe ResiliencyPolicyTier
$sel:tier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe ResiliencyPolicyTier
tier} -> Maybe ResiliencyPolicyTier
tier) (\s :: ResiliencyPolicy
s@ResiliencyPolicy' {} Maybe ResiliencyPolicyTier
a -> ResiliencyPolicy
s {$sel:tier:ResiliencyPolicy' :: Maybe ResiliencyPolicyTier
tier = Maybe ResiliencyPolicyTier
a} :: ResiliencyPolicy)

instance Data.FromJSON ResiliencyPolicy where
  parseJSON :: Value -> Parser ResiliencyPolicy
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ResiliencyPolicy"
      ( \Object
x ->
          Maybe POSIX
-> Maybe DataLocationConstraint
-> Maybe EstimatedCostTier
-> Maybe (HashMap DisruptionType FailurePolicy)
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (Sensitive (HashMap Text Text))
-> Maybe ResiliencyPolicyTier
-> ResiliencyPolicy
ResiliencyPolicy'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"creationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"dataLocationConstraint")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"estimatedCostTier")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"policy" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"policyArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"policyDescription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"policyName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"tier")
      )

instance Prelude.Hashable ResiliencyPolicy where
  hashWithSalt :: Int -> ResiliencyPolicy -> Int
hashWithSalt Int
_salt ResiliencyPolicy' {Maybe Text
Maybe (HashMap DisruptionType FailurePolicy)
Maybe (Sensitive (HashMap Text Text))
Maybe POSIX
Maybe DataLocationConstraint
Maybe EstimatedCostTier
Maybe ResiliencyPolicyTier
tier :: Maybe ResiliencyPolicyTier
tags :: Maybe (Sensitive (HashMap Text Text))
policyName :: Maybe Text
policyDescription :: Maybe Text
policyArn :: Maybe Text
policy :: Maybe (HashMap DisruptionType FailurePolicy)
estimatedCostTier :: Maybe EstimatedCostTier
dataLocationConstraint :: Maybe DataLocationConstraint
creationTime :: Maybe POSIX
$sel:tier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe ResiliencyPolicyTier
$sel:tags:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (Sensitive (HashMap Text Text))
$sel:policyName:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policyDescription:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policyArn:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policy:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (HashMap DisruptionType FailurePolicy)
$sel:estimatedCostTier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe EstimatedCostTier
$sel:dataLocationConstraint:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe DataLocationConstraint
$sel:creationTime:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataLocationConstraint
dataLocationConstraint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EstimatedCostTier
estimatedCostTier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap DisruptionType FailurePolicy)
policy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResiliencyPolicyTier
tier

instance Prelude.NFData ResiliencyPolicy where
  rnf :: ResiliencyPolicy -> ()
rnf ResiliencyPolicy' {Maybe Text
Maybe (HashMap DisruptionType FailurePolicy)
Maybe (Sensitive (HashMap Text Text))
Maybe POSIX
Maybe DataLocationConstraint
Maybe EstimatedCostTier
Maybe ResiliencyPolicyTier
tier :: Maybe ResiliencyPolicyTier
tags :: Maybe (Sensitive (HashMap Text Text))
policyName :: Maybe Text
policyDescription :: Maybe Text
policyArn :: Maybe Text
policy :: Maybe (HashMap DisruptionType FailurePolicy)
estimatedCostTier :: Maybe EstimatedCostTier
dataLocationConstraint :: Maybe DataLocationConstraint
creationTime :: Maybe POSIX
$sel:tier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe ResiliencyPolicyTier
$sel:tags:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (Sensitive (HashMap Text Text))
$sel:policyName:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policyDescription:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policyArn:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe Text
$sel:policy:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe (HashMap DisruptionType FailurePolicy)
$sel:estimatedCostTier:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe EstimatedCostTier
$sel:dataLocationConstraint:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe DataLocationConstraint
$sel:creationTime:ResiliencyPolicy' :: ResiliencyPolicy -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataLocationConstraint
dataLocationConstraint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EstimatedCostTier
estimatedCostTier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap DisruptionType FailurePolicy)
policy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResiliencyPolicyTier
tier