{-# 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.Route53RecoveryControlConfig.Types.GatingRule
-- 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.Route53RecoveryControlConfig.Types.GatingRule 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.Route53RecoveryControlConfig.Types.RuleConfig
import Amazonka.Route53RecoveryControlConfig.Types.Status

-- | A gating rule verifies that a gating routing control or set of gating
-- routing controls, evaluates as true, based on a rule configuration that
-- you specify, which allows a set of routing control state changes to
-- complete.
--
-- For example, if you specify one gating routing control and you set the
-- Type in the rule configuration to OR, that indicates that you must set
-- the gating routing control to On for the rule to evaluate as true; that
-- is, for the gating control \"switch\" to be \"On\". When you do that,
-- then you can update the routing control states for the target routing
-- controls that you specify in the gating rule.
--
-- /See:/ 'newGatingRule' smart constructor.
data GatingRule = GatingRule'
  { -- | The deployment status of a gating rule. Status can be one of the
    -- following: PENDING, DEPLOYED, PENDING_DELETION.
    GatingRule -> Status
status :: Status,
    -- | An array of target routing control Amazon Resource Names (ARNs) for
    -- which the states can only be updated if the rule configuration that you
    -- specify evaluates to true for the gating routing control. As a simple
    -- example, if you have a single gating control, it acts as an overall
    -- \"on\/off\" switch for a set of target routing controls. You can use
    -- this to manually override automated failover, for example.
    GatingRule -> [Text]
targetControls :: [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the control panel.
    GatingRule -> Text
controlPanelArn :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the gating rule.
    GatingRule -> Text
safetyRuleArn :: Prelude.Text,
    -- | An array of gating routing control Amazon Resource Names (ARNs). For a
    -- simple \"on\/off\" switch, specify the ARN for one routing control. The
    -- gating routing controls are evaluated by the rule configuration that you
    -- specify to determine if the target routing control states can be
    -- changed.
    GatingRule -> [Text]
gatingControls :: [Prelude.Text],
    -- | The criteria that you set for gating routing controls that designate how
    -- many of the routing control states must be ON to allow you to update
    -- target routing control states.
    GatingRule -> RuleConfig
ruleConfig :: RuleConfig,
    -- | An evaluation period, in milliseconds (ms), during which any request
    -- against the target routing controls will fail. This helps prevent
    -- \"flapping\" of state. The wait period is 5000 ms by default, but you
    -- can choose a custom value.
    GatingRule -> Int
waitPeriodMs :: Prelude.Int,
    -- | The name for the gating rule. You can use any non-white space character
    -- in the name.
    GatingRule -> Text
name :: Prelude.Text
  }
  deriving (GatingRule -> GatingRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GatingRule -> GatingRule -> Bool
$c/= :: GatingRule -> GatingRule -> Bool
== :: GatingRule -> GatingRule -> Bool
$c== :: GatingRule -> GatingRule -> Bool
Prelude.Eq, ReadPrec [GatingRule]
ReadPrec GatingRule
Int -> ReadS GatingRule
ReadS [GatingRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GatingRule]
$creadListPrec :: ReadPrec [GatingRule]
readPrec :: ReadPrec GatingRule
$creadPrec :: ReadPrec GatingRule
readList :: ReadS [GatingRule]
$creadList :: ReadS [GatingRule]
readsPrec :: Int -> ReadS GatingRule
$creadsPrec :: Int -> ReadS GatingRule
Prelude.Read, Int -> GatingRule -> ShowS
[GatingRule] -> ShowS
GatingRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GatingRule] -> ShowS
$cshowList :: [GatingRule] -> ShowS
show :: GatingRule -> String
$cshow :: GatingRule -> String
showsPrec :: Int -> GatingRule -> ShowS
$cshowsPrec :: Int -> GatingRule -> ShowS
Prelude.Show, forall x. Rep GatingRule x -> GatingRule
forall x. GatingRule -> Rep GatingRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GatingRule x -> GatingRule
$cfrom :: forall x. GatingRule -> Rep GatingRule x
Prelude.Generic)

-- |
-- Create a value of 'GatingRule' 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:
--
-- 'status', 'gatingRule_status' - The deployment status of a gating rule. Status can be one of the
-- following: PENDING, DEPLOYED, PENDING_DELETION.
--
-- 'targetControls', 'gatingRule_targetControls' - An array of target routing control Amazon Resource Names (ARNs) for
-- which the states can only be updated if the rule configuration that you
-- specify evaluates to true for the gating routing control. As a simple
-- example, if you have a single gating control, it acts as an overall
-- \"on\/off\" switch for a set of target routing controls. You can use
-- this to manually override automated failover, for example.
--
-- 'controlPanelArn', 'gatingRule_controlPanelArn' - The Amazon Resource Name (ARN) of the control panel.
--
-- 'safetyRuleArn', 'gatingRule_safetyRuleArn' - The Amazon Resource Name (ARN) of the gating rule.
--
-- 'gatingControls', 'gatingRule_gatingControls' - An array of gating routing control Amazon Resource Names (ARNs). For a
-- simple \"on\/off\" switch, specify the ARN for one routing control. The
-- gating routing controls are evaluated by the rule configuration that you
-- specify to determine if the target routing control states can be
-- changed.
--
-- 'ruleConfig', 'gatingRule_ruleConfig' - The criteria that you set for gating routing controls that designate how
-- many of the routing control states must be ON to allow you to update
-- target routing control states.
--
-- 'waitPeriodMs', 'gatingRule_waitPeriodMs' - An evaluation period, in milliseconds (ms), during which any request
-- against the target routing controls will fail. This helps prevent
-- \"flapping\" of state. The wait period is 5000 ms by default, but you
-- can choose a custom value.
--
-- 'name', 'gatingRule_name' - The name for the gating rule. You can use any non-white space character
-- in the name.
newGatingRule ::
  -- | 'status'
  Status ->
  -- | 'controlPanelArn'
  Prelude.Text ->
  -- | 'safetyRuleArn'
  Prelude.Text ->
  -- | 'ruleConfig'
  RuleConfig ->
  -- | 'waitPeriodMs'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  GatingRule
newGatingRule :: Status -> Text -> Text -> RuleConfig -> Int -> Text -> GatingRule
newGatingRule
  Status
pStatus_
  Text
pControlPanelArn_
  Text
pSafetyRuleArn_
  RuleConfig
pRuleConfig_
  Int
pWaitPeriodMs_
  Text
pName_ =
    GatingRule'
      { $sel:status:GatingRule' :: Status
status = Status
pStatus_,
        $sel:targetControls:GatingRule' :: [Text]
targetControls = forall a. Monoid a => a
Prelude.mempty,
        $sel:controlPanelArn:GatingRule' :: Text
controlPanelArn = Text
pControlPanelArn_,
        $sel:safetyRuleArn:GatingRule' :: Text
safetyRuleArn = Text
pSafetyRuleArn_,
        $sel:gatingControls:GatingRule' :: [Text]
gatingControls = forall a. Monoid a => a
Prelude.mempty,
        $sel:ruleConfig:GatingRule' :: RuleConfig
ruleConfig = RuleConfig
pRuleConfig_,
        $sel:waitPeriodMs:GatingRule' :: Int
waitPeriodMs = Int
pWaitPeriodMs_,
        $sel:name:GatingRule' :: Text
name = Text
pName_
      }

-- | The deployment status of a gating rule. Status can be one of the
-- following: PENDING, DEPLOYED, PENDING_DELETION.
gatingRule_status :: Lens.Lens' GatingRule Status
gatingRule_status :: Lens' GatingRule Status
gatingRule_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {Status
status :: Status
$sel:status:GatingRule' :: GatingRule -> Status
status} -> Status
status) (\s :: GatingRule
s@GatingRule' {} Status
a -> GatingRule
s {$sel:status:GatingRule' :: Status
status = Status
a} :: GatingRule)

-- | An array of target routing control Amazon Resource Names (ARNs) for
-- which the states can only be updated if the rule configuration that you
-- specify evaluates to true for the gating routing control. As a simple
-- example, if you have a single gating control, it acts as an overall
-- \"on\/off\" switch for a set of target routing controls. You can use
-- this to manually override automated failover, for example.
gatingRule_targetControls :: Lens.Lens' GatingRule [Prelude.Text]
gatingRule_targetControls :: Lens' GatingRule [Text]
gatingRule_targetControls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {[Text]
targetControls :: [Text]
$sel:targetControls:GatingRule' :: GatingRule -> [Text]
targetControls} -> [Text]
targetControls) (\s :: GatingRule
s@GatingRule' {} [Text]
a -> GatingRule
s {$sel:targetControls:GatingRule' :: [Text]
targetControls = [Text]
a} :: GatingRule) 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 Amazon Resource Name (ARN) of the control panel.
gatingRule_controlPanelArn :: Lens.Lens' GatingRule Prelude.Text
gatingRule_controlPanelArn :: Lens' GatingRule Text
gatingRule_controlPanelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {Text
controlPanelArn :: Text
$sel:controlPanelArn:GatingRule' :: GatingRule -> Text
controlPanelArn} -> Text
controlPanelArn) (\s :: GatingRule
s@GatingRule' {} Text
a -> GatingRule
s {$sel:controlPanelArn:GatingRule' :: Text
controlPanelArn = Text
a} :: GatingRule)

-- | The Amazon Resource Name (ARN) of the gating rule.
gatingRule_safetyRuleArn :: Lens.Lens' GatingRule Prelude.Text
gatingRule_safetyRuleArn :: Lens' GatingRule Text
gatingRule_safetyRuleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {Text
safetyRuleArn :: Text
$sel:safetyRuleArn:GatingRule' :: GatingRule -> Text
safetyRuleArn} -> Text
safetyRuleArn) (\s :: GatingRule
s@GatingRule' {} Text
a -> GatingRule
s {$sel:safetyRuleArn:GatingRule' :: Text
safetyRuleArn = Text
a} :: GatingRule)

-- | An array of gating routing control Amazon Resource Names (ARNs). For a
-- simple \"on\/off\" switch, specify the ARN for one routing control. The
-- gating routing controls are evaluated by the rule configuration that you
-- specify to determine if the target routing control states can be
-- changed.
gatingRule_gatingControls :: Lens.Lens' GatingRule [Prelude.Text]
gatingRule_gatingControls :: Lens' GatingRule [Text]
gatingRule_gatingControls = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {[Text]
gatingControls :: [Text]
$sel:gatingControls:GatingRule' :: GatingRule -> [Text]
gatingControls} -> [Text]
gatingControls) (\s :: GatingRule
s@GatingRule' {} [Text]
a -> GatingRule
s {$sel:gatingControls:GatingRule' :: [Text]
gatingControls = [Text]
a} :: GatingRule) 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 criteria that you set for gating routing controls that designate how
-- many of the routing control states must be ON to allow you to update
-- target routing control states.
gatingRule_ruleConfig :: Lens.Lens' GatingRule RuleConfig
gatingRule_ruleConfig :: Lens' GatingRule RuleConfig
gatingRule_ruleConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {RuleConfig
ruleConfig :: RuleConfig
$sel:ruleConfig:GatingRule' :: GatingRule -> RuleConfig
ruleConfig} -> RuleConfig
ruleConfig) (\s :: GatingRule
s@GatingRule' {} RuleConfig
a -> GatingRule
s {$sel:ruleConfig:GatingRule' :: RuleConfig
ruleConfig = RuleConfig
a} :: GatingRule)

-- | An evaluation period, in milliseconds (ms), during which any request
-- against the target routing controls will fail. This helps prevent
-- \"flapping\" of state. The wait period is 5000 ms by default, but you
-- can choose a custom value.
gatingRule_waitPeriodMs :: Lens.Lens' GatingRule Prelude.Int
gatingRule_waitPeriodMs :: Lens' GatingRule Int
gatingRule_waitPeriodMs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {Int
waitPeriodMs :: Int
$sel:waitPeriodMs:GatingRule' :: GatingRule -> Int
waitPeriodMs} -> Int
waitPeriodMs) (\s :: GatingRule
s@GatingRule' {} Int
a -> GatingRule
s {$sel:waitPeriodMs:GatingRule' :: Int
waitPeriodMs = Int
a} :: GatingRule)

-- | The name for the gating rule. You can use any non-white space character
-- in the name.
gatingRule_name :: Lens.Lens' GatingRule Prelude.Text
gatingRule_name :: Lens' GatingRule Text
gatingRule_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GatingRule' {Text
name :: Text
$sel:name:GatingRule' :: GatingRule -> Text
name} -> Text
name) (\s :: GatingRule
s@GatingRule' {} Text
a -> GatingRule
s {$sel:name:GatingRule' :: Text
name = Text
a} :: GatingRule)

instance Data.FromJSON GatingRule where
  parseJSON :: Value -> Parser GatingRule
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"GatingRule"
      ( \Object
x ->
          Status
-> [Text]
-> Text
-> Text
-> [Text]
-> RuleConfig
-> Int
-> Text
-> GatingRule
GatingRule'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Status")
            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
"TargetControls" 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 a
Data..: Key
"ControlPanelArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SafetyRuleArn")
            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
"GatingControls" 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 a
Data..: Key
"RuleConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"WaitPeriodMs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Name")
      )

instance Prelude.Hashable GatingRule where
  hashWithSalt :: Int -> GatingRule -> Int
hashWithSalt Int
_salt GatingRule' {Int
[Text]
Text
RuleConfig
Status
name :: Text
waitPeriodMs :: Int
ruleConfig :: RuleConfig
gatingControls :: [Text]
safetyRuleArn :: Text
controlPanelArn :: Text
targetControls :: [Text]
status :: Status
$sel:name:GatingRule' :: GatingRule -> Text
$sel:waitPeriodMs:GatingRule' :: GatingRule -> Int
$sel:ruleConfig:GatingRule' :: GatingRule -> RuleConfig
$sel:gatingControls:GatingRule' :: GatingRule -> [Text]
$sel:safetyRuleArn:GatingRule' :: GatingRule -> Text
$sel:controlPanelArn:GatingRule' :: GatingRule -> Text
$sel:targetControls:GatingRule' :: GatingRule -> [Text]
$sel:status:GatingRule' :: GatingRule -> Status
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Status
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
targetControls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
controlPanelArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
safetyRuleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
gatingControls
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RuleConfig
ruleConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
waitPeriodMs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData GatingRule where
  rnf :: GatingRule -> ()
rnf GatingRule' {Int
[Text]
Text
RuleConfig
Status
name :: Text
waitPeriodMs :: Int
ruleConfig :: RuleConfig
gatingControls :: [Text]
safetyRuleArn :: Text
controlPanelArn :: Text
targetControls :: [Text]
status :: Status
$sel:name:GatingRule' :: GatingRule -> Text
$sel:waitPeriodMs:GatingRule' :: GatingRule -> Int
$sel:ruleConfig:GatingRule' :: GatingRule -> RuleConfig
$sel:gatingControls:GatingRule' :: GatingRule -> [Text]
$sel:safetyRuleArn:GatingRule' :: GatingRule -> Text
$sel:controlPanelArn:GatingRule' :: GatingRule -> Text
$sel:targetControls:GatingRule' :: GatingRule -> [Text]
$sel:status:GatingRule' :: GatingRule -> Status
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Status
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
targetControls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
controlPanelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
safetyRuleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
gatingControls
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleConfig
ruleConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
waitPeriodMs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name