{-# 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 #-}
module Amazonka.WAFV2.Types.RuleAction 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.WAFV2.Types.AllowAction
import Amazonka.WAFV2.Types.BlockAction
import Amazonka.WAFV2.Types.CaptchaAction
import Amazonka.WAFV2.Types.ChallengeAction
import Amazonka.WAFV2.Types.CountAction
data RuleAction = RuleAction'
{
RuleAction -> Maybe AllowAction
allow :: Prelude.Maybe AllowAction,
RuleAction -> Maybe BlockAction
block :: Prelude.Maybe BlockAction,
RuleAction -> Maybe CaptchaAction
captcha :: Prelude.Maybe CaptchaAction,
RuleAction -> Maybe ChallengeAction
challenge :: Prelude.Maybe ChallengeAction,
RuleAction -> Maybe CountAction
count :: Prelude.Maybe CountAction
}
deriving (RuleAction -> RuleAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RuleAction -> RuleAction -> Bool
$c/= :: RuleAction -> RuleAction -> Bool
== :: RuleAction -> RuleAction -> Bool
$c== :: RuleAction -> RuleAction -> Bool
Prelude.Eq, ReadPrec [RuleAction]
ReadPrec RuleAction
Int -> ReadS RuleAction
ReadS [RuleAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RuleAction]
$creadListPrec :: ReadPrec [RuleAction]
readPrec :: ReadPrec RuleAction
$creadPrec :: ReadPrec RuleAction
readList :: ReadS [RuleAction]
$creadList :: ReadS [RuleAction]
readsPrec :: Int -> ReadS RuleAction
$creadsPrec :: Int -> ReadS RuleAction
Prelude.Read, Int -> RuleAction -> ShowS
[RuleAction] -> ShowS
RuleAction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RuleAction] -> ShowS
$cshowList :: [RuleAction] -> ShowS
show :: RuleAction -> String
$cshow :: RuleAction -> String
showsPrec :: Int -> RuleAction -> ShowS
$cshowsPrec :: Int -> RuleAction -> ShowS
Prelude.Show, forall x. Rep RuleAction x -> RuleAction
forall x. RuleAction -> Rep RuleAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RuleAction x -> RuleAction
$cfrom :: forall x. RuleAction -> Rep RuleAction x
Prelude.Generic)
newRuleAction ::
RuleAction
newRuleAction :: RuleAction
newRuleAction =
RuleAction'
{ $sel:allow:RuleAction' :: Maybe AllowAction
allow = forall a. Maybe a
Prelude.Nothing,
$sel:block:RuleAction' :: Maybe BlockAction
block = forall a. Maybe a
Prelude.Nothing,
$sel:captcha:RuleAction' :: Maybe CaptchaAction
captcha = forall a. Maybe a
Prelude.Nothing,
$sel:challenge:RuleAction' :: Maybe ChallengeAction
challenge = forall a. Maybe a
Prelude.Nothing,
$sel:count:RuleAction' :: Maybe CountAction
count = forall a. Maybe a
Prelude.Nothing
}
ruleAction_allow :: Lens.Lens' RuleAction (Prelude.Maybe AllowAction)
ruleAction_allow :: Lens' RuleAction (Maybe AllowAction)
ruleAction_allow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RuleAction' {Maybe AllowAction
allow :: Maybe AllowAction
$sel:allow:RuleAction' :: RuleAction -> Maybe AllowAction
allow} -> Maybe AllowAction
allow) (\s :: RuleAction
s@RuleAction' {} Maybe AllowAction
a -> RuleAction
s {$sel:allow:RuleAction' :: Maybe AllowAction
allow = Maybe AllowAction
a} :: RuleAction)
ruleAction_block :: Lens.Lens' RuleAction (Prelude.Maybe BlockAction)
ruleAction_block :: Lens' RuleAction (Maybe BlockAction)
ruleAction_block = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RuleAction' {Maybe BlockAction
block :: Maybe BlockAction
$sel:block:RuleAction' :: RuleAction -> Maybe BlockAction
block} -> Maybe BlockAction
block) (\s :: RuleAction
s@RuleAction' {} Maybe BlockAction
a -> RuleAction
s {$sel:block:RuleAction' :: Maybe BlockAction
block = Maybe BlockAction
a} :: RuleAction)
ruleAction_captcha :: Lens.Lens' RuleAction (Prelude.Maybe CaptchaAction)
ruleAction_captcha :: Lens' RuleAction (Maybe CaptchaAction)
ruleAction_captcha = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RuleAction' {Maybe CaptchaAction
captcha :: Maybe CaptchaAction
$sel:captcha:RuleAction' :: RuleAction -> Maybe CaptchaAction
captcha} -> Maybe CaptchaAction
captcha) (\s :: RuleAction
s@RuleAction' {} Maybe CaptchaAction
a -> RuleAction
s {$sel:captcha:RuleAction' :: Maybe CaptchaAction
captcha = Maybe CaptchaAction
a} :: RuleAction)
ruleAction_challenge :: Lens.Lens' RuleAction (Prelude.Maybe ChallengeAction)
ruleAction_challenge :: Lens' RuleAction (Maybe ChallengeAction)
ruleAction_challenge = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RuleAction' {Maybe ChallengeAction
challenge :: Maybe ChallengeAction
$sel:challenge:RuleAction' :: RuleAction -> Maybe ChallengeAction
challenge} -> Maybe ChallengeAction
challenge) (\s :: RuleAction
s@RuleAction' {} Maybe ChallengeAction
a -> RuleAction
s {$sel:challenge:RuleAction' :: Maybe ChallengeAction
challenge = Maybe ChallengeAction
a} :: RuleAction)
ruleAction_count :: Lens.Lens' RuleAction (Prelude.Maybe CountAction)
ruleAction_count :: Lens' RuleAction (Maybe CountAction)
ruleAction_count = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RuleAction' {Maybe CountAction
count :: Maybe CountAction
$sel:count:RuleAction' :: RuleAction -> Maybe CountAction
count} -> Maybe CountAction
count) (\s :: RuleAction
s@RuleAction' {} Maybe CountAction
a -> RuleAction
s {$sel:count:RuleAction' :: Maybe CountAction
count = Maybe CountAction
a} :: RuleAction)
instance Data.FromJSON RuleAction where
parseJSON :: Value -> Parser RuleAction
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"RuleAction"
( \Object
x ->
Maybe AllowAction
-> Maybe BlockAction
-> Maybe CaptchaAction
-> Maybe ChallengeAction
-> Maybe CountAction
-> RuleAction
RuleAction'
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
"Allow")
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
"Block")
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
"Captcha")
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
"Challenge")
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
"Count")
)
instance Prelude.Hashable RuleAction where
hashWithSalt :: Int -> RuleAction -> Int
hashWithSalt Int
_salt RuleAction' {Maybe CountAction
Maybe ChallengeAction
Maybe CaptchaAction
Maybe AllowAction
Maybe BlockAction
count :: Maybe CountAction
challenge :: Maybe ChallengeAction
captcha :: Maybe CaptchaAction
block :: Maybe BlockAction
allow :: Maybe AllowAction
$sel:count:RuleAction' :: RuleAction -> Maybe CountAction
$sel:challenge:RuleAction' :: RuleAction -> Maybe ChallengeAction
$sel:captcha:RuleAction' :: RuleAction -> Maybe CaptchaAction
$sel:block:RuleAction' :: RuleAction -> Maybe BlockAction
$sel:allow:RuleAction' :: RuleAction -> Maybe AllowAction
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AllowAction
allow
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BlockAction
block
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CaptchaAction
captcha
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChallengeAction
challenge
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CountAction
count
instance Prelude.NFData RuleAction where
rnf :: RuleAction -> ()
rnf RuleAction' {Maybe CountAction
Maybe ChallengeAction
Maybe CaptchaAction
Maybe AllowAction
Maybe BlockAction
count :: Maybe CountAction
challenge :: Maybe ChallengeAction
captcha :: Maybe CaptchaAction
block :: Maybe BlockAction
allow :: Maybe AllowAction
$sel:count:RuleAction' :: RuleAction -> Maybe CountAction
$sel:challenge:RuleAction' :: RuleAction -> Maybe ChallengeAction
$sel:captcha:RuleAction' :: RuleAction -> Maybe CaptchaAction
$sel:block:RuleAction' :: RuleAction -> Maybe BlockAction
$sel:allow:RuleAction' :: RuleAction -> Maybe AllowAction
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AllowAction
allow
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BlockAction
block
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CaptchaAction
captcha
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChallengeAction
challenge
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CountAction
count
instance Data.ToJSON RuleAction where
toJSON :: RuleAction -> Value
toJSON RuleAction' {Maybe CountAction
Maybe ChallengeAction
Maybe CaptchaAction
Maybe AllowAction
Maybe BlockAction
count :: Maybe CountAction
challenge :: Maybe ChallengeAction
captcha :: Maybe CaptchaAction
block :: Maybe BlockAction
allow :: Maybe AllowAction
$sel:count:RuleAction' :: RuleAction -> Maybe CountAction
$sel:challenge:RuleAction' :: RuleAction -> Maybe ChallengeAction
$sel:captcha:RuleAction' :: RuleAction -> Maybe CaptchaAction
$sel:block:RuleAction' :: RuleAction -> Maybe BlockAction
$sel:allow:RuleAction' :: RuleAction -> Maybe AllowAction
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"Allow" 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 AllowAction
allow,
(Key
"Block" 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 BlockAction
block,
(Key
"Captcha" 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 CaptchaAction
captcha,
(Key
"Challenge" 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 ChallengeAction
challenge,
(Key
"Count" 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 CountAction
count
]
)