module Stratosphere.GuardDuty.Filter.ConditionProperty (
        ConditionProperty(..), mkConditionProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ConditionProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html>
    ConditionProperty {ConditionProperty -> ()
haddock_workaround_ :: (),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-eq>
                       ConditionProperty -> Maybe (ValueList Text)
eq :: (Prelude.Maybe (ValueList Prelude.Text)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-equals>
                       ConditionProperty -> Maybe (ValueList Text)
equals :: (Prelude.Maybe (ValueList Prelude.Text)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-greaterthan>
                       ConditionProperty -> Maybe (Value Integer)
greaterThan :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-greaterthanorequal>
                       ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-gt>
                       ConditionProperty -> Maybe (Value Integer)
gt :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-gte>
                       ConditionProperty -> Maybe (Value Integer)
gte :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-lessthan>
                       ConditionProperty -> Maybe (Value Integer)
lessThan :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-lessthanorequal>
                       ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-lt>
                       ConditionProperty -> Maybe (Value Integer)
lt :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-lte>
                       ConditionProperty -> Maybe (Value Integer)
lte :: (Prelude.Maybe (Value Prelude.Integer)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-neq>
                       ConditionProperty -> Maybe (ValueList Text)
neq :: (Prelude.Maybe (ValueList Prelude.Text)),
                       -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-guardduty-filter-condition.html#cfn-guardduty-filter-condition-notequals>
                       ConditionProperty -> Maybe (ValueList Text)
notEquals :: (Prelude.Maybe (ValueList Prelude.Text))}
  deriving stock (ConditionProperty -> ConditionProperty -> Bool
(ConditionProperty -> ConditionProperty -> Bool)
-> (ConditionProperty -> ConditionProperty -> Bool)
-> Eq ConditionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConditionProperty -> ConditionProperty -> Bool
== :: ConditionProperty -> ConditionProperty -> Bool
$c/= :: ConditionProperty -> ConditionProperty -> Bool
/= :: ConditionProperty -> ConditionProperty -> Bool
Prelude.Eq, Int -> ConditionProperty -> ShowS
[ConditionProperty] -> ShowS
ConditionProperty -> String
(Int -> ConditionProperty -> ShowS)
-> (ConditionProperty -> String)
-> ([ConditionProperty] -> ShowS)
-> Show ConditionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConditionProperty -> ShowS
showsPrec :: Int -> ConditionProperty -> ShowS
$cshow :: ConditionProperty -> String
show :: ConditionProperty -> String
$cshowList :: [ConditionProperty] -> ShowS
showList :: [ConditionProperty] -> ShowS
Prelude.Show)
mkConditionProperty :: ConditionProperty
mkConditionProperty :: ConditionProperty
mkConditionProperty
  = ConditionProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), eq :: Maybe (ValueList Text)
eq = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       equals :: Maybe (ValueList Text)
equals = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, greaterThan :: Maybe (Value Integer)
greaterThan = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       greaterThanOrEqual :: Maybe (Value Integer)
greaterThanOrEqual = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, gt :: Maybe (Value Integer)
gt = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       gte :: Maybe (Value Integer)
gte = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, lessThan :: Maybe (Value Integer)
lessThan = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       lessThanOrEqual :: Maybe (Value Integer)
lessThanOrEqual = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, lt :: Maybe (Value Integer)
lt = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       lte :: Maybe (Value Integer)
lte = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, neq :: Maybe (ValueList Text)
neq = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       notEquals :: Maybe (ValueList Text)
notEquals = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ConditionProperty where
  toResourceProperties :: ConditionProperty -> ResourceProperties
toResourceProperties ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::GuardDuty::Filter.Condition",
         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 -> 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
"Eq" (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)
eq,
                            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
"Equals" (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)
equals,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GreaterThan" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
greaterThan,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GreaterThanOrEqual" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
greaterThanOrEqual,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Gt" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
gt, Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Gte" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
gte,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LessThan" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lessThan,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LessThanOrEqual" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lessThanOrEqual,
                            Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Lt" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lt, Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Lte" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lte,
                            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
"Neq" (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)
neq,
                            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
"NotEquals" (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)
notEquals])}
instance JSON.ToJSON ConditionProperty where
  toJSON :: ConditionProperty -> Value
toJSON ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: 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 -> 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
"Eq" (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)
eq,
               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
"Equals" (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)
equals,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GreaterThan" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
greaterThan,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GreaterThanOrEqual" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
greaterThanOrEqual,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Gt" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
gt, Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Gte" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
gte,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LessThan" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lessThan,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LessThanOrEqual" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lessThanOrEqual,
               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Lt" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lt, Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Lte" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
lte,
               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
"Neq" (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)
neq,
               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
"NotEquals" (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)
notEquals]))
instance Property "Eq" ConditionProperty where
  type PropertyType "Eq" ConditionProperty = ValueList Prelude.Text
  set :: PropertyType "Eq" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Eq" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {eq :: Maybe (ValueList Text)
eq = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Eq" ConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Equals" ConditionProperty where
  type PropertyType "Equals" ConditionProperty = ValueList Prelude.Text
  set :: PropertyType "Equals" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Equals" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {equals :: Maybe (ValueList Text)
equals = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Equals" ConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "GreaterThan" ConditionProperty where
  type PropertyType "GreaterThan" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "GreaterThan" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "GreaterThan" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {greaterThan :: Maybe (Value Integer)
greaterThan = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GreaterThan" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "GreaterThanOrEqual" ConditionProperty where
  type PropertyType "GreaterThanOrEqual" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "GreaterThanOrEqual" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "GreaterThanOrEqual" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty
        {greaterThanOrEqual :: Maybe (Value Integer)
greaterThanOrEqual = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "GreaterThanOrEqual" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Gt" ConditionProperty where
  type PropertyType "Gt" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "Gt" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Gt" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {gt :: Maybe (Value Integer)
gt = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Gt" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Gte" ConditionProperty where
  type PropertyType "Gte" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "Gte" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Gte" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {gte :: Maybe (Value Integer)
gte = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Gte" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "LessThan" ConditionProperty where
  type PropertyType "LessThan" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "LessThan" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "LessThan" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {lessThan :: Maybe (Value Integer)
lessThan = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LessThan" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "LessThanOrEqual" ConditionProperty where
  type PropertyType "LessThanOrEqual" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "LessThanOrEqual" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "LessThanOrEqual" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {lessThanOrEqual :: Maybe (Value Integer)
lessThanOrEqual = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LessThanOrEqual" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Lt" ConditionProperty where
  type PropertyType "Lt" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "Lt" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Lt" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {lt :: Maybe (Value Integer)
lt = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Lt" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Lte" ConditionProperty where
  type PropertyType "Lte" ConditionProperty = Value Prelude.Integer
  set :: PropertyType "Lte" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Lte" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {lte :: Maybe (Value Integer)
lte = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Lte" ConditionProperty
Value Integer
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
instance Property "Neq" ConditionProperty where
  type PropertyType "Neq" ConditionProperty = ValueList Prelude.Text
  set :: PropertyType "Neq" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "Neq" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {neq :: Maybe (ValueList Text)
neq = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Neq" ConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
notEquals :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
notEquals :: Maybe (ValueList Text)
..}
instance Property "NotEquals" ConditionProperty where
  type PropertyType "NotEquals" ConditionProperty = ValueList Prelude.Text
  set :: PropertyType "NotEquals" ConditionProperty
-> ConditionProperty -> ConditionProperty
set PropertyType "NotEquals" ConditionProperty
newValue ConditionProperty {Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ConditionProperty -> ()
eq :: ConditionProperty -> Maybe (ValueList Text)
equals :: ConditionProperty -> Maybe (ValueList Text)
greaterThan :: ConditionProperty -> Maybe (Value Integer)
greaterThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
gt :: ConditionProperty -> Maybe (Value Integer)
gte :: ConditionProperty -> Maybe (Value Integer)
lessThan :: ConditionProperty -> Maybe (Value Integer)
lessThanOrEqual :: ConditionProperty -> Maybe (Value Integer)
lt :: ConditionProperty -> Maybe (Value Integer)
lte :: ConditionProperty -> Maybe (Value Integer)
neq :: ConditionProperty -> Maybe (ValueList Text)
notEquals :: ConditionProperty -> Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
notEquals :: Maybe (ValueList Text)
..}
    = ConditionProperty {notEquals :: Maybe (ValueList Text)
notEquals = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NotEquals" ConditionProperty
ValueList Text
newValue, Maybe (ValueList Text)
Maybe (Value Integer)
()
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
haddock_workaround_ :: ()
eq :: Maybe (ValueList Text)
equals :: Maybe (ValueList Text)
greaterThan :: Maybe (Value Integer)
greaterThanOrEqual :: Maybe (Value Integer)
gt :: Maybe (Value Integer)
gte :: Maybe (Value Integer)
lessThan :: Maybe (Value Integer)
lessThanOrEqual :: Maybe (Value Integer)
lt :: Maybe (Value Integer)
lte :: Maybe (Value Integer)
neq :: Maybe (ValueList Text)
..}