module Stratosphere.ElasticLoadBalancingV2.ListenerRule.RuleConditionProperty (
        module Exports, RuleConditionProperty(..), mkRuleConditionProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.HostHeaderConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.HttpHeaderConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.HttpRequestMethodConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.PathPatternConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.QueryStringConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.ElasticLoadBalancingV2.ListenerRule.SourceIpConfigProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RuleConditionProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html>
    RuleConditionProperty {RuleConditionProperty -> ()
haddock_workaround_ :: (),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-field>
                           RuleConditionProperty -> Maybe (Value Text)
field :: (Prelude.Maybe (Value Prelude.Text)),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-hostheaderconfig>
                           RuleConditionProperty -> Maybe HostHeaderConfigProperty
hostHeaderConfig :: (Prelude.Maybe HostHeaderConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-httpheaderconfig>
                           RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpHeaderConfig :: (Prelude.Maybe HttpHeaderConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-httprequestmethodconfig>
                           RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
httpRequestMethodConfig :: (Prelude.Maybe HttpRequestMethodConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-pathpatternconfig>
                           RuleConditionProperty -> Maybe PathPatternConfigProperty
pathPatternConfig :: (Prelude.Maybe PathPatternConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-querystringconfig>
                           RuleConditionProperty -> Maybe QueryStringConfigProperty
queryStringConfig :: (Prelude.Maybe QueryStringConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-regexvalues>
                           RuleConditionProperty -> Maybe (ValueList Text)
regexValues :: (Prelude.Maybe (ValueList Prelude.Text)),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-sourceipconfig>
                           RuleConditionProperty -> Maybe SourceIpConfigProperty
sourceIpConfig :: (Prelude.Maybe SourceIpConfigProperty),
                           -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-elasticloadbalancingv2-listenerrule-rulecondition.html#cfn-elasticloadbalancingv2-listenerrule-rulecondition-values>
                           RuleConditionProperty -> Maybe (ValueList Text)
values :: (Prelude.Maybe (ValueList Prelude.Text))}
  deriving stock (RuleConditionProperty -> RuleConditionProperty -> Bool
(RuleConditionProperty -> RuleConditionProperty -> Bool)
-> (RuleConditionProperty -> RuleConditionProperty -> Bool)
-> Eq RuleConditionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleConditionProperty -> RuleConditionProperty -> Bool
== :: RuleConditionProperty -> RuleConditionProperty -> Bool
$c/= :: RuleConditionProperty -> RuleConditionProperty -> Bool
/= :: RuleConditionProperty -> RuleConditionProperty -> Bool
Prelude.Eq, Int -> RuleConditionProperty -> ShowS
[RuleConditionProperty] -> ShowS
RuleConditionProperty -> String
(Int -> RuleConditionProperty -> ShowS)
-> (RuleConditionProperty -> String)
-> ([RuleConditionProperty] -> ShowS)
-> Show RuleConditionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleConditionProperty -> ShowS
showsPrec :: Int -> RuleConditionProperty -> ShowS
$cshow :: RuleConditionProperty -> String
show :: RuleConditionProperty -> String
$cshowList :: [RuleConditionProperty] -> ShowS
showList :: [RuleConditionProperty] -> ShowS
Prelude.Show)
mkRuleConditionProperty :: RuleConditionProperty
mkRuleConditionProperty :: RuleConditionProperty
mkRuleConditionProperty
  = RuleConditionProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), field :: Maybe (Value Text)
field = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       hostHeaderConfig :: Maybe HostHeaderConfigProperty
hostHeaderConfig = Maybe HostHeaderConfigProperty
forall a. Maybe a
Prelude.Nothing,
       httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpHeaderConfig = Maybe HttpHeaderConfigProperty
forall a. Maybe a
Prelude.Nothing,
       httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
httpRequestMethodConfig = Maybe HttpRequestMethodConfigProperty
forall a. Maybe a
Prelude.Nothing,
       pathPatternConfig :: Maybe PathPatternConfigProperty
pathPatternConfig = Maybe PathPatternConfigProperty
forall a. Maybe a
Prelude.Nothing,
       queryStringConfig :: Maybe QueryStringConfigProperty
queryStringConfig = Maybe QueryStringConfigProperty
forall a. Maybe a
Prelude.Nothing, regexValues :: Maybe (ValueList Text)
regexValues = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       sourceIpConfig :: Maybe SourceIpConfigProperty
sourceIpConfig = Maybe SourceIpConfigProperty
forall a. Maybe a
Prelude.Nothing, values :: Maybe (ValueList Text)
values = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RuleConditionProperty where
  toResourceProperties :: RuleConditionProperty -> ResourceProperties
toResourceProperties RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::ElasticLoadBalancingV2::ListenerRule.RuleCondition",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                           [Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Field" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
field,
                            Key -> HostHeaderConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HostHeaderConfig" (HostHeaderConfigProperty -> (Key, Value))
-> Maybe HostHeaderConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HostHeaderConfigProperty
hostHeaderConfig,
                            Key -> HttpHeaderConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HttpHeaderConfig" (HttpHeaderConfigProperty -> (Key, Value))
-> Maybe HttpHeaderConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpHeaderConfigProperty
httpHeaderConfig,
                            Key -> HttpRequestMethodConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HttpRequestMethodConfig"
                              (HttpRequestMethodConfigProperty -> (Key, Value))
-> Maybe HttpRequestMethodConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpRequestMethodConfigProperty
httpRequestMethodConfig,
                            Key -> PathPatternConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PathPatternConfig" (PathPatternConfigProperty -> (Key, Value))
-> Maybe PathPatternConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathPatternConfigProperty
pathPatternConfig,
                            Key -> QueryStringConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QueryStringConfig" (QueryStringConfigProperty -> (Key, Value))
-> Maybe QueryStringConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QueryStringConfigProperty
queryStringConfig,
                            Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RegexValues" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
regexValues,
                            Key -> SourceIpConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SourceIpConfig" (SourceIpConfigProperty -> (Key, Value))
-> Maybe SourceIpConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SourceIpConfigProperty
sourceIpConfig,
                            Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Values" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
values])}
instance JSON.ToJSON RuleConditionProperty where
  toJSON :: RuleConditionProperty -> Value
toJSON RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
              [Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Field" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
field,
               Key -> HostHeaderConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HostHeaderConfig" (HostHeaderConfigProperty -> (Key, Value))
-> Maybe HostHeaderConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HostHeaderConfigProperty
hostHeaderConfig,
               Key -> HttpHeaderConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HttpHeaderConfig" (HttpHeaderConfigProperty -> (Key, Value))
-> Maybe HttpHeaderConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpHeaderConfigProperty
httpHeaderConfig,
               Key -> HttpRequestMethodConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HttpRequestMethodConfig"
                 (HttpRequestMethodConfigProperty -> (Key, Value))
-> Maybe HttpRequestMethodConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HttpRequestMethodConfigProperty
httpRequestMethodConfig,
               Key -> PathPatternConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PathPatternConfig" (PathPatternConfigProperty -> (Key, Value))
-> Maybe PathPatternConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathPatternConfigProperty
pathPatternConfig,
               Key -> QueryStringConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"QueryStringConfig" (QueryStringConfigProperty -> (Key, Value))
-> Maybe QueryStringConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe QueryStringConfigProperty
queryStringConfig,
               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RegexValues" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
regexValues,
               Key -> SourceIpConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SourceIpConfig" (SourceIpConfigProperty -> (Key, Value))
-> Maybe SourceIpConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SourceIpConfigProperty
sourceIpConfig,
               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Values" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
values]))
instance Property "Field" RuleConditionProperty where
  type PropertyType "Field" RuleConditionProperty = Value Prelude.Text
  set :: PropertyType "Field" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "Field" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty {field :: Maybe (Value Text)
field = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Field" RuleConditionProperty
Value Text
newValue, Maybe (ValueList Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "HostHeaderConfig" RuleConditionProperty where
  type PropertyType "HostHeaderConfig" RuleConditionProperty = HostHeaderConfigProperty
  set :: PropertyType "HostHeaderConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "HostHeaderConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {hostHeaderConfig :: Maybe HostHeaderConfigProperty
hostHeaderConfig = HostHeaderConfigProperty -> Maybe HostHeaderConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostHeaderConfig" RuleConditionProperty
HostHeaderConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "HttpHeaderConfig" RuleConditionProperty where
  type PropertyType "HttpHeaderConfig" RuleConditionProperty = HttpHeaderConfigProperty
  set :: PropertyType "HttpHeaderConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "HttpHeaderConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpHeaderConfig = HttpHeaderConfigProperty -> Maybe HttpHeaderConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HttpHeaderConfig" RuleConditionProperty
HttpHeaderConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "HttpRequestMethodConfig" RuleConditionProperty where
  type PropertyType "HttpRequestMethodConfig" RuleConditionProperty = HttpRequestMethodConfigProperty
  set :: PropertyType "HttpRequestMethodConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "HttpRequestMethodConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
httpRequestMethodConfig = HttpRequestMethodConfigProperty
-> Maybe HttpRequestMethodConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HttpRequestMethodConfig" RuleConditionProperty
HttpRequestMethodConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "PathPatternConfig" RuleConditionProperty where
  type PropertyType "PathPatternConfig" RuleConditionProperty = PathPatternConfigProperty
  set :: PropertyType "PathPatternConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "PathPatternConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {pathPatternConfig :: Maybe PathPatternConfigProperty
pathPatternConfig = PathPatternConfigProperty -> Maybe PathPatternConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PathPatternConfig" RuleConditionProperty
PathPatternConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "QueryStringConfig" RuleConditionProperty where
  type PropertyType "QueryStringConfig" RuleConditionProperty = QueryStringConfigProperty
  set :: PropertyType "QueryStringConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "QueryStringConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {queryStringConfig :: Maybe QueryStringConfigProperty
queryStringConfig = QueryStringConfigProperty -> Maybe QueryStringConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "QueryStringConfig" RuleConditionProperty
QueryStringConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "RegexValues" RuleConditionProperty where
  type PropertyType "RegexValues" RuleConditionProperty = ValueList Prelude.Text
  set :: PropertyType "RegexValues" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "RegexValues" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty {regexValues :: Maybe (ValueList Text)
regexValues = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RegexValues" RuleConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
instance Property "SourceIpConfig" RuleConditionProperty where
  type PropertyType "SourceIpConfig" RuleConditionProperty = SourceIpConfigProperty
  set :: PropertyType "SourceIpConfig" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "SourceIpConfig" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty
        {sourceIpConfig :: Maybe SourceIpConfigProperty
sourceIpConfig = SourceIpConfigProperty -> Maybe SourceIpConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SourceIpConfig" RuleConditionProperty
SourceIpConfigProperty
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
values :: Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
values :: Maybe (ValueList Text)
..}
instance Property "Values" RuleConditionProperty where
  type PropertyType "Values" RuleConditionProperty = ValueList Prelude.Text
  set :: PropertyType "Values" RuleConditionProperty
-> RuleConditionProperty -> RuleConditionProperty
set PropertyType "Values" RuleConditionProperty
newValue RuleConditionProperty {Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: RuleConditionProperty -> ()
field :: RuleConditionProperty -> Maybe (Value Text)
hostHeaderConfig :: RuleConditionProperty -> Maybe HostHeaderConfigProperty
httpHeaderConfig :: RuleConditionProperty -> Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: RuleConditionProperty -> Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: RuleConditionProperty -> Maybe PathPatternConfigProperty
queryStringConfig :: RuleConditionProperty -> Maybe QueryStringConfigProperty
regexValues :: RuleConditionProperty -> Maybe (ValueList Text)
sourceIpConfig :: RuleConditionProperty -> Maybe SourceIpConfigProperty
values :: RuleConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
values :: Maybe (ValueList Text)
..}
    = RuleConditionProperty {values :: Maybe (ValueList Text)
values = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Values" RuleConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Text)
Maybe HostHeaderConfigProperty
Maybe HttpHeaderConfigProperty
Maybe HttpRequestMethodConfigProperty
Maybe PathPatternConfigProperty
Maybe QueryStringConfigProperty
Maybe SourceIpConfigProperty
()
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
haddock_workaround_ :: ()
field :: Maybe (Value Text)
hostHeaderConfig :: Maybe HostHeaderConfigProperty
httpHeaderConfig :: Maybe HttpHeaderConfigProperty
httpRequestMethodConfig :: Maybe HttpRequestMethodConfigProperty
pathPatternConfig :: Maybe PathPatternConfigProperty
queryStringConfig :: Maybe QueryStringConfigProperty
regexValues :: Maybe (ValueList Text)
sourceIpConfig :: Maybe SourceIpConfigProperty
..}