module Hydra.Langs.Cypher.Features where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data AggregateFeatures =
AggregateFeatures {
AggregateFeatures -> Bool
aggregateFeaturesAvg :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesCollect :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesCount :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesMax :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesMin :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesPercentileCont :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesPercentileDisc :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesStdev :: Bool,
AggregateFeatures -> Bool
aggregateFeaturesSum :: Bool}
deriving (AggregateFeatures -> AggregateFeatures -> Bool
(AggregateFeatures -> AggregateFeatures -> Bool)
-> (AggregateFeatures -> AggregateFeatures -> Bool)
-> Eq AggregateFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AggregateFeatures -> AggregateFeatures -> Bool
== :: AggregateFeatures -> AggregateFeatures -> Bool
$c/= :: AggregateFeatures -> AggregateFeatures -> Bool
/= :: AggregateFeatures -> AggregateFeatures -> Bool
Eq, Eq AggregateFeatures
Eq AggregateFeatures =>
(AggregateFeatures -> AggregateFeatures -> Ordering)
-> (AggregateFeatures -> AggregateFeatures -> Bool)
-> (AggregateFeatures -> AggregateFeatures -> Bool)
-> (AggregateFeatures -> AggregateFeatures -> Bool)
-> (AggregateFeatures -> AggregateFeatures -> Bool)
-> (AggregateFeatures -> AggregateFeatures -> AggregateFeatures)
-> (AggregateFeatures -> AggregateFeatures -> AggregateFeatures)
-> Ord AggregateFeatures
AggregateFeatures -> AggregateFeatures -> Bool
AggregateFeatures -> AggregateFeatures -> Ordering
AggregateFeatures -> AggregateFeatures -> AggregateFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AggregateFeatures -> AggregateFeatures -> Ordering
compare :: AggregateFeatures -> AggregateFeatures -> Ordering
$c< :: AggregateFeatures -> AggregateFeatures -> Bool
< :: AggregateFeatures -> AggregateFeatures -> Bool
$c<= :: AggregateFeatures -> AggregateFeatures -> Bool
<= :: AggregateFeatures -> AggregateFeatures -> Bool
$c> :: AggregateFeatures -> AggregateFeatures -> Bool
> :: AggregateFeatures -> AggregateFeatures -> Bool
$c>= :: AggregateFeatures -> AggregateFeatures -> Bool
>= :: AggregateFeatures -> AggregateFeatures -> Bool
$cmax :: AggregateFeatures -> AggregateFeatures -> AggregateFeatures
max :: AggregateFeatures -> AggregateFeatures -> AggregateFeatures
$cmin :: AggregateFeatures -> AggregateFeatures -> AggregateFeatures
min :: AggregateFeatures -> AggregateFeatures -> AggregateFeatures
Ord, ReadPrec [AggregateFeatures]
ReadPrec AggregateFeatures
Int -> ReadS AggregateFeatures
ReadS [AggregateFeatures]
(Int -> ReadS AggregateFeatures)
-> ReadS [AggregateFeatures]
-> ReadPrec AggregateFeatures
-> ReadPrec [AggregateFeatures]
-> Read AggregateFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AggregateFeatures
readsPrec :: Int -> ReadS AggregateFeatures
$creadList :: ReadS [AggregateFeatures]
readList :: ReadS [AggregateFeatures]
$creadPrec :: ReadPrec AggregateFeatures
readPrec :: ReadPrec AggregateFeatures
$creadListPrec :: ReadPrec [AggregateFeatures]
readListPrec :: ReadPrec [AggregateFeatures]
Read, Int -> AggregateFeatures -> ShowS
[AggregateFeatures] -> ShowS
AggregateFeatures -> String
(Int -> AggregateFeatures -> ShowS)
-> (AggregateFeatures -> String)
-> ([AggregateFeatures] -> ShowS)
-> Show AggregateFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AggregateFeatures -> ShowS
showsPrec :: Int -> AggregateFeatures -> ShowS
$cshow :: AggregateFeatures -> String
show :: AggregateFeatures -> String
$cshowList :: [AggregateFeatures] -> ShowS
showList :: [AggregateFeatures] -> ShowS
Show)
_AggregateFeatures :: Name
_AggregateFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.AggregateFeatures")
_AggregateFeatures_avg :: Name
_AggregateFeatures_avg = (String -> Name
Core.Name String
"avg")
_AggregateFeatures_collect :: Name
_AggregateFeatures_collect = (String -> Name
Core.Name String
"collect")
_AggregateFeatures_count :: Name
_AggregateFeatures_count = (String -> Name
Core.Name String
"count")
_AggregateFeatures_max :: Name
_AggregateFeatures_max = (String -> Name
Core.Name String
"max")
_AggregateFeatures_min :: Name
_AggregateFeatures_min = (String -> Name
Core.Name String
"min")
_AggregateFeatures_percentileCont :: Name
_AggregateFeatures_percentileCont = (String -> Name
Core.Name String
"percentileCont")
_AggregateFeatures_percentileDisc :: Name
_AggregateFeatures_percentileDisc = (String -> Name
Core.Name String
"percentileDisc")
_AggregateFeatures_stdev :: Name
_AggregateFeatures_stdev = (String -> Name
Core.Name String
"stdev")
_AggregateFeatures_sum :: Name
_AggregateFeatures_sum = (String -> Name
Core.Name String
"sum")
data ArithmeticFeatures =
ArithmeticFeatures {
ArithmeticFeatures -> Bool
arithmeticFeaturesPlus :: Bool,
ArithmeticFeatures -> Bool
arithmeticFeaturesMinus :: Bool,
ArithmeticFeatures -> Bool
arithmeticFeaturesMultiply :: Bool,
ArithmeticFeatures -> Bool
arithmeticFeaturesDivide :: Bool,
ArithmeticFeatures -> Bool
arithmeticFeaturesModulus :: Bool,
ArithmeticFeatures -> Bool
arithmeticFeaturesPowerOf :: Bool}
deriving (ArithmeticFeatures -> ArithmeticFeatures -> Bool
(ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> (ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> Eq ArithmeticFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
== :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
$c/= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
/= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
Eq, Eq ArithmeticFeatures
Eq ArithmeticFeatures =>
(ArithmeticFeatures -> ArithmeticFeatures -> Ordering)
-> (ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> (ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> (ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> (ArithmeticFeatures -> ArithmeticFeatures -> Bool)
-> (ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures)
-> (ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures)
-> Ord ArithmeticFeatures
ArithmeticFeatures -> ArithmeticFeatures -> Bool
ArithmeticFeatures -> ArithmeticFeatures -> Ordering
ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ArithmeticFeatures -> ArithmeticFeatures -> Ordering
compare :: ArithmeticFeatures -> ArithmeticFeatures -> Ordering
$c< :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
< :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
$c<= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
<= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
$c> :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
> :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
$c>= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
>= :: ArithmeticFeatures -> ArithmeticFeatures -> Bool
$cmax :: ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures
max :: ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures
$cmin :: ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures
min :: ArithmeticFeatures -> ArithmeticFeatures -> ArithmeticFeatures
Ord, ReadPrec [ArithmeticFeatures]
ReadPrec ArithmeticFeatures
Int -> ReadS ArithmeticFeatures
ReadS [ArithmeticFeatures]
(Int -> ReadS ArithmeticFeatures)
-> ReadS [ArithmeticFeatures]
-> ReadPrec ArithmeticFeatures
-> ReadPrec [ArithmeticFeatures]
-> Read ArithmeticFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ArithmeticFeatures
readsPrec :: Int -> ReadS ArithmeticFeatures
$creadList :: ReadS [ArithmeticFeatures]
readList :: ReadS [ArithmeticFeatures]
$creadPrec :: ReadPrec ArithmeticFeatures
readPrec :: ReadPrec ArithmeticFeatures
$creadListPrec :: ReadPrec [ArithmeticFeatures]
readListPrec :: ReadPrec [ArithmeticFeatures]
Read, Int -> ArithmeticFeatures -> ShowS
[ArithmeticFeatures] -> ShowS
ArithmeticFeatures -> String
(Int -> ArithmeticFeatures -> ShowS)
-> (ArithmeticFeatures -> String)
-> ([ArithmeticFeatures] -> ShowS)
-> Show ArithmeticFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ArithmeticFeatures -> ShowS
showsPrec :: Int -> ArithmeticFeatures -> ShowS
$cshow :: ArithmeticFeatures -> String
show :: ArithmeticFeatures -> String
$cshowList :: [ArithmeticFeatures] -> ShowS
showList :: [ArithmeticFeatures] -> ShowS
Show)
_ArithmeticFeatures :: Name
_ArithmeticFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ArithmeticFeatures")
_ArithmeticFeatures_plus :: Name
_ArithmeticFeatures_plus = (String -> Name
Core.Name String
"plus")
_ArithmeticFeatures_minus :: Name
_ArithmeticFeatures_minus = (String -> Name
Core.Name String
"minus")
_ArithmeticFeatures_multiply :: Name
_ArithmeticFeatures_multiply = (String -> Name
Core.Name String
"multiply")
_ArithmeticFeatures_divide :: Name
_ArithmeticFeatures_divide = (String -> Name
Core.Name String
"divide")
_ArithmeticFeatures_modulus :: Name
_ArithmeticFeatures_modulus = (String -> Name
Core.Name String
"modulus")
_ArithmeticFeatures_powerOf :: Name
_ArithmeticFeatures_powerOf = (String -> Name
Core.Name String
"powerOf")
data AtomFeatures =
AtomFeatures {
AtomFeatures -> Bool
atomFeaturesCaseExpression :: Bool,
AtomFeatures -> Bool
atomFeaturesCount :: Bool,
AtomFeatures -> Bool
atomFeaturesExistentialSubquery :: Bool,
AtomFeatures -> Bool
atomFeaturesFunctionInvocation :: Bool,
AtomFeatures -> Maybe ListFeatures
atomFeaturesList :: (Maybe ListFeatures),
AtomFeatures -> Maybe LiteralFeatures
atomFeaturesLiteral :: (Maybe LiteralFeatures),
AtomFeatures -> Bool
atomFeaturesParameter :: Bool,
AtomFeatures -> Bool
atomFeaturesPatternComprehension :: Bool,
AtomFeatures -> Bool
atomFeaturesPatternPredicate :: Bool,
AtomFeatures -> Maybe QuantifierFeatures
atomFeaturesQuantifier :: (Maybe QuantifierFeatures),
AtomFeatures -> Bool
atomFeaturesVariable :: Bool}
deriving (AtomFeatures -> AtomFeatures -> Bool
(AtomFeatures -> AtomFeatures -> Bool)
-> (AtomFeatures -> AtomFeatures -> Bool) -> Eq AtomFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AtomFeatures -> AtomFeatures -> Bool
== :: AtomFeatures -> AtomFeatures -> Bool
$c/= :: AtomFeatures -> AtomFeatures -> Bool
/= :: AtomFeatures -> AtomFeatures -> Bool
Eq, Eq AtomFeatures
Eq AtomFeatures =>
(AtomFeatures -> AtomFeatures -> Ordering)
-> (AtomFeatures -> AtomFeatures -> Bool)
-> (AtomFeatures -> AtomFeatures -> Bool)
-> (AtomFeatures -> AtomFeatures -> Bool)
-> (AtomFeatures -> AtomFeatures -> Bool)
-> (AtomFeatures -> AtomFeatures -> AtomFeatures)
-> (AtomFeatures -> AtomFeatures -> AtomFeatures)
-> Ord AtomFeatures
AtomFeatures -> AtomFeatures -> Bool
AtomFeatures -> AtomFeatures -> Ordering
AtomFeatures -> AtomFeatures -> AtomFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AtomFeatures -> AtomFeatures -> Ordering
compare :: AtomFeatures -> AtomFeatures -> Ordering
$c< :: AtomFeatures -> AtomFeatures -> Bool
< :: AtomFeatures -> AtomFeatures -> Bool
$c<= :: AtomFeatures -> AtomFeatures -> Bool
<= :: AtomFeatures -> AtomFeatures -> Bool
$c> :: AtomFeatures -> AtomFeatures -> Bool
> :: AtomFeatures -> AtomFeatures -> Bool
$c>= :: AtomFeatures -> AtomFeatures -> Bool
>= :: AtomFeatures -> AtomFeatures -> Bool
$cmax :: AtomFeatures -> AtomFeatures -> AtomFeatures
max :: AtomFeatures -> AtomFeatures -> AtomFeatures
$cmin :: AtomFeatures -> AtomFeatures -> AtomFeatures
min :: AtomFeatures -> AtomFeatures -> AtomFeatures
Ord, ReadPrec [AtomFeatures]
ReadPrec AtomFeatures
Int -> ReadS AtomFeatures
ReadS [AtomFeatures]
(Int -> ReadS AtomFeatures)
-> ReadS [AtomFeatures]
-> ReadPrec AtomFeatures
-> ReadPrec [AtomFeatures]
-> Read AtomFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AtomFeatures
readsPrec :: Int -> ReadS AtomFeatures
$creadList :: ReadS [AtomFeatures]
readList :: ReadS [AtomFeatures]
$creadPrec :: ReadPrec AtomFeatures
readPrec :: ReadPrec AtomFeatures
$creadListPrec :: ReadPrec [AtomFeatures]
readListPrec :: ReadPrec [AtomFeatures]
Read, Int -> AtomFeatures -> ShowS
[AtomFeatures] -> ShowS
AtomFeatures -> String
(Int -> AtomFeatures -> ShowS)
-> (AtomFeatures -> String)
-> ([AtomFeatures] -> ShowS)
-> Show AtomFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AtomFeatures -> ShowS
showsPrec :: Int -> AtomFeatures -> ShowS
$cshow :: AtomFeatures -> String
show :: AtomFeatures -> String
$cshowList :: [AtomFeatures] -> ShowS
showList :: [AtomFeatures] -> ShowS
Show)
_AtomFeatures :: Name
_AtomFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.AtomFeatures")
_AtomFeatures_caseExpression :: Name
_AtomFeatures_caseExpression = (String -> Name
Core.Name String
"caseExpression")
_AtomFeatures_count :: Name
_AtomFeatures_count = (String -> Name
Core.Name String
"count")
_AtomFeatures_existentialSubquery :: Name
_AtomFeatures_existentialSubquery = (String -> Name
Core.Name String
"existentialSubquery")
_AtomFeatures_functionInvocation :: Name
_AtomFeatures_functionInvocation = (String -> Name
Core.Name String
"functionInvocation")
_AtomFeatures_list :: Name
_AtomFeatures_list = (String -> Name
Core.Name String
"list")
_AtomFeatures_literal :: Name
_AtomFeatures_literal = (String -> Name
Core.Name String
"literal")
_AtomFeatures_parameter :: Name
_AtomFeatures_parameter = (String -> Name
Core.Name String
"parameter")
_AtomFeatures_patternComprehension :: Name
_AtomFeatures_patternComprehension = (String -> Name
Core.Name String
"patternComprehension")
_AtomFeatures_patternPredicate :: Name
_AtomFeatures_patternPredicate = (String -> Name
Core.Name String
"patternPredicate")
_AtomFeatures_quantifier :: Name
_AtomFeatures_quantifier = (String -> Name
Core.Name String
"quantifier")
_AtomFeatures_variable :: Name
_AtomFeatures_variable = (String -> Name
Core.Name String
"variable")
data ComparisonFeatures =
ComparisonFeatures {
ComparisonFeatures -> Bool
comparisonFeaturesEqual :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesGreaterThan :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesGreaterThanOrEqual :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesLessThan :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesLessThanOrEqual :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesNotEqual :: Bool,
ComparisonFeatures -> Bool
comparisonFeaturesNullIf :: Bool}
deriving (ComparisonFeatures -> ComparisonFeatures -> Bool
(ComparisonFeatures -> ComparisonFeatures -> Bool)
-> (ComparisonFeatures -> ComparisonFeatures -> Bool)
-> Eq ComparisonFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComparisonFeatures -> ComparisonFeatures -> Bool
== :: ComparisonFeatures -> ComparisonFeatures -> Bool
$c/= :: ComparisonFeatures -> ComparisonFeatures -> Bool
/= :: ComparisonFeatures -> ComparisonFeatures -> Bool
Eq, Eq ComparisonFeatures
Eq ComparisonFeatures =>
(ComparisonFeatures -> ComparisonFeatures -> Ordering)
-> (ComparisonFeatures -> ComparisonFeatures -> Bool)
-> (ComparisonFeatures -> ComparisonFeatures -> Bool)
-> (ComparisonFeatures -> ComparisonFeatures -> Bool)
-> (ComparisonFeatures -> ComparisonFeatures -> Bool)
-> (ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures)
-> (ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures)
-> Ord ComparisonFeatures
ComparisonFeatures -> ComparisonFeatures -> Bool
ComparisonFeatures -> ComparisonFeatures -> Ordering
ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ComparisonFeatures -> ComparisonFeatures -> Ordering
compare :: ComparisonFeatures -> ComparisonFeatures -> Ordering
$c< :: ComparisonFeatures -> ComparisonFeatures -> Bool
< :: ComparisonFeatures -> ComparisonFeatures -> Bool
$c<= :: ComparisonFeatures -> ComparisonFeatures -> Bool
<= :: ComparisonFeatures -> ComparisonFeatures -> Bool
$c> :: ComparisonFeatures -> ComparisonFeatures -> Bool
> :: ComparisonFeatures -> ComparisonFeatures -> Bool
$c>= :: ComparisonFeatures -> ComparisonFeatures -> Bool
>= :: ComparisonFeatures -> ComparisonFeatures -> Bool
$cmax :: ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures
max :: ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures
$cmin :: ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures
min :: ComparisonFeatures -> ComparisonFeatures -> ComparisonFeatures
Ord, ReadPrec [ComparisonFeatures]
ReadPrec ComparisonFeatures
Int -> ReadS ComparisonFeatures
ReadS [ComparisonFeatures]
(Int -> ReadS ComparisonFeatures)
-> ReadS [ComparisonFeatures]
-> ReadPrec ComparisonFeatures
-> ReadPrec [ComparisonFeatures]
-> Read ComparisonFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ComparisonFeatures
readsPrec :: Int -> ReadS ComparisonFeatures
$creadList :: ReadS [ComparisonFeatures]
readList :: ReadS [ComparisonFeatures]
$creadPrec :: ReadPrec ComparisonFeatures
readPrec :: ReadPrec ComparisonFeatures
$creadListPrec :: ReadPrec [ComparisonFeatures]
readListPrec :: ReadPrec [ComparisonFeatures]
Read, Int -> ComparisonFeatures -> ShowS
[ComparisonFeatures] -> ShowS
ComparisonFeatures -> String
(Int -> ComparisonFeatures -> ShowS)
-> (ComparisonFeatures -> String)
-> ([ComparisonFeatures] -> ShowS)
-> Show ComparisonFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComparisonFeatures -> ShowS
showsPrec :: Int -> ComparisonFeatures -> ShowS
$cshow :: ComparisonFeatures -> String
show :: ComparisonFeatures -> String
$cshowList :: [ComparisonFeatures] -> ShowS
showList :: [ComparisonFeatures] -> ShowS
Show)
_ComparisonFeatures :: Name
_ComparisonFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ComparisonFeatures")
_ComparisonFeatures_equal :: Name
_ComparisonFeatures_equal = (String -> Name
Core.Name String
"equal")
_ComparisonFeatures_greaterThan :: Name
_ComparisonFeatures_greaterThan = (String -> Name
Core.Name String
"greaterThan")
_ComparisonFeatures_greaterThanOrEqual :: Name
_ComparisonFeatures_greaterThanOrEqual = (String -> Name
Core.Name String
"greaterThanOrEqual")
_ComparisonFeatures_lessThan :: Name
_ComparisonFeatures_lessThan = (String -> Name
Core.Name String
"lessThan")
_ComparisonFeatures_lessThanOrEqual :: Name
_ComparisonFeatures_lessThanOrEqual = (String -> Name
Core.Name String
"lessThanOrEqual")
_ComparisonFeatures_notEqual :: Name
_ComparisonFeatures_notEqual = (String -> Name
Core.Name String
"notEqual")
_ComparisonFeatures_nullIf :: Name
_ComparisonFeatures_nullIf = (String -> Name
Core.Name String
"nullIf")
data CypherFeatures =
CypherFeatures {
CypherFeatures -> Maybe AggregateFeatures
cypherFeaturesAggregate :: (Maybe AggregateFeatures),
CypherFeatures -> Maybe ArithmeticFeatures
cypherFeaturesArithmetic :: (Maybe ArithmeticFeatures),
CypherFeatures -> Maybe AtomFeatures
cypherFeaturesAtom :: (Maybe AtomFeatures),
CypherFeatures -> Maybe ComparisonFeatures
cypherFeaturesComparison :: (Maybe ComparisonFeatures),
CypherFeatures -> Maybe DeleteFeatures
cypherFeaturesDelete :: (Maybe DeleteFeatures),
CypherFeatures -> Maybe ElementFeatures
cypherFeaturesElement :: (Maybe ElementFeatures),
CypherFeatures -> Maybe LogicalFeatures
cypherFeaturesLogical :: (Maybe LogicalFeatures),
CypherFeatures -> Maybe MapFeatures
cypherFeaturesMap :: (Maybe MapFeatures),
CypherFeatures -> Maybe MatchFeatures
cypherFeaturesMatch :: (Maybe MatchFeatures),
CypherFeatures -> Maybe MergeFeatures
cypherFeaturesMerge :: (Maybe MergeFeatures),
CypherFeatures -> Maybe NodePatternFeatures
cypherFeaturesNodePattern :: (Maybe NodePatternFeatures),
CypherFeatures -> Maybe NullFeatures
cypherFeaturesNull :: (Maybe NullFeatures),
CypherFeatures -> Maybe NumericFeatures
cypherFeaturesNumeric :: (Maybe NumericFeatures),
CypherFeatures -> Maybe PathFeatures
cypherFeaturesPath :: (Maybe PathFeatures),
CypherFeatures -> Maybe ProcedureCallFeatures
cypherFeaturesProcedureCall :: (Maybe ProcedureCallFeatures),
CypherFeatures -> Maybe ProjectionFeatures
cypherFeaturesProjection :: (Maybe ProjectionFeatures),
CypherFeatures -> Maybe RandomnessFeatures
cypherFeaturesRandomness :: (Maybe RandomnessFeatures),
CypherFeatures -> Maybe RangeLiteralFeatures
cypherFeaturesRangeLiteral :: (Maybe RangeLiteralFeatures),
CypherFeatures -> Maybe ReadingFeatures
cypherFeaturesReading :: (Maybe ReadingFeatures),
CypherFeatures -> Maybe RelationshipDirectionFeatures
cypherFeaturesRelationshipDirection :: (Maybe RelationshipDirectionFeatures),
CypherFeatures -> Maybe RelationshipPatternFeatures
cypherFeaturesRelationshipPattern :: (Maybe RelationshipPatternFeatures),
CypherFeatures -> Maybe RemoveFeatures
cypherFeaturesRemove :: (Maybe RemoveFeatures),
CypherFeatures -> Maybe SchemaFeatures
cypherFeaturesSchema :: (Maybe SchemaFeatures),
CypherFeatures -> Maybe SetFeatures
cypherFeaturesSet :: (Maybe SetFeatures),
CypherFeatures -> Maybe StringFeatures
cypherFeaturesString :: (Maybe StringFeatures),
CypherFeatures -> Maybe UpdatingFeatures
cypherFeaturesUpdating :: (Maybe UpdatingFeatures)}
deriving (CypherFeatures -> CypherFeatures -> Bool
(CypherFeatures -> CypherFeatures -> Bool)
-> (CypherFeatures -> CypherFeatures -> Bool) -> Eq CypherFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CypherFeatures -> CypherFeatures -> Bool
== :: CypherFeatures -> CypherFeatures -> Bool
$c/= :: CypherFeatures -> CypherFeatures -> Bool
/= :: CypherFeatures -> CypherFeatures -> Bool
Eq, Eq CypherFeatures
Eq CypherFeatures =>
(CypherFeatures -> CypherFeatures -> Ordering)
-> (CypherFeatures -> CypherFeatures -> Bool)
-> (CypherFeatures -> CypherFeatures -> Bool)
-> (CypherFeatures -> CypherFeatures -> Bool)
-> (CypherFeatures -> CypherFeatures -> Bool)
-> (CypherFeatures -> CypherFeatures -> CypherFeatures)
-> (CypherFeatures -> CypherFeatures -> CypherFeatures)
-> Ord CypherFeatures
CypherFeatures -> CypherFeatures -> Bool
CypherFeatures -> CypherFeatures -> Ordering
CypherFeatures -> CypherFeatures -> CypherFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CypherFeatures -> CypherFeatures -> Ordering
compare :: CypherFeatures -> CypherFeatures -> Ordering
$c< :: CypherFeatures -> CypherFeatures -> Bool
< :: CypherFeatures -> CypherFeatures -> Bool
$c<= :: CypherFeatures -> CypherFeatures -> Bool
<= :: CypherFeatures -> CypherFeatures -> Bool
$c> :: CypherFeatures -> CypherFeatures -> Bool
> :: CypherFeatures -> CypherFeatures -> Bool
$c>= :: CypherFeatures -> CypherFeatures -> Bool
>= :: CypherFeatures -> CypherFeatures -> Bool
$cmax :: CypherFeatures -> CypherFeatures -> CypherFeatures
max :: CypherFeatures -> CypherFeatures -> CypherFeatures
$cmin :: CypherFeatures -> CypherFeatures -> CypherFeatures
min :: CypherFeatures -> CypherFeatures -> CypherFeatures
Ord, ReadPrec [CypherFeatures]
ReadPrec CypherFeatures
Int -> ReadS CypherFeatures
ReadS [CypherFeatures]
(Int -> ReadS CypherFeatures)
-> ReadS [CypherFeatures]
-> ReadPrec CypherFeatures
-> ReadPrec [CypherFeatures]
-> Read CypherFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CypherFeatures
readsPrec :: Int -> ReadS CypherFeatures
$creadList :: ReadS [CypherFeatures]
readList :: ReadS [CypherFeatures]
$creadPrec :: ReadPrec CypherFeatures
readPrec :: ReadPrec CypherFeatures
$creadListPrec :: ReadPrec [CypherFeatures]
readListPrec :: ReadPrec [CypherFeatures]
Read, Int -> CypherFeatures -> ShowS
[CypherFeatures] -> ShowS
CypherFeatures -> String
(Int -> CypherFeatures -> ShowS)
-> (CypherFeatures -> String)
-> ([CypherFeatures] -> ShowS)
-> Show CypherFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CypherFeatures -> ShowS
showsPrec :: Int -> CypherFeatures -> ShowS
$cshow :: CypherFeatures -> String
show :: CypherFeatures -> String
$cshowList :: [CypherFeatures] -> ShowS
showList :: [CypherFeatures] -> ShowS
Show)
_CypherFeatures :: Name
_CypherFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.CypherFeatures")
_CypherFeatures_aggregate :: Name
_CypherFeatures_aggregate = (String -> Name
Core.Name String
"aggregate")
_CypherFeatures_arithmetic :: Name
_CypherFeatures_arithmetic = (String -> Name
Core.Name String
"arithmetic")
_CypherFeatures_atom :: Name
_CypherFeatures_atom = (String -> Name
Core.Name String
"atom")
_CypherFeatures_comparison :: Name
_CypherFeatures_comparison = (String -> Name
Core.Name String
"comparison")
_CypherFeatures_delete :: Name
_CypherFeatures_delete = (String -> Name
Core.Name String
"delete")
_CypherFeatures_element :: Name
_CypherFeatures_element = (String -> Name
Core.Name String
"element")
_CypherFeatures_logical :: Name
_CypherFeatures_logical = (String -> Name
Core.Name String
"logical")
_CypherFeatures_map :: Name
_CypherFeatures_map = (String -> Name
Core.Name String
"map")
_CypherFeatures_match :: Name
_CypherFeatures_match = (String -> Name
Core.Name String
"match")
_CypherFeatures_merge :: Name
_CypherFeatures_merge = (String -> Name
Core.Name String
"merge")
_CypherFeatures_nodePattern :: Name
_CypherFeatures_nodePattern = (String -> Name
Core.Name String
"nodePattern")
_CypherFeatures_null :: Name
_CypherFeatures_null = (String -> Name
Core.Name String
"null")
_CypherFeatures_numeric :: Name
_CypherFeatures_numeric = (String -> Name
Core.Name String
"numeric")
_CypherFeatures_path :: Name
_CypherFeatures_path = (String -> Name
Core.Name String
"path")
_CypherFeatures_procedureCall :: Name
_CypherFeatures_procedureCall = (String -> Name
Core.Name String
"procedureCall")
_CypherFeatures_projection :: Name
_CypherFeatures_projection = (String -> Name
Core.Name String
"projection")
_CypherFeatures_randomness :: Name
_CypherFeatures_randomness = (String -> Name
Core.Name String
"randomness")
_CypherFeatures_rangeLiteral :: Name
_CypherFeatures_rangeLiteral = (String -> Name
Core.Name String
"rangeLiteral")
_CypherFeatures_reading :: Name
_CypherFeatures_reading = (String -> Name
Core.Name String
"reading")
_CypherFeatures_relationshipDirection :: Name
_CypherFeatures_relationshipDirection = (String -> Name
Core.Name String
"relationshipDirection")
_CypherFeatures_relationshipPattern :: Name
_CypherFeatures_relationshipPattern = (String -> Name
Core.Name String
"relationshipPattern")
_CypherFeatures_remove :: Name
_CypherFeatures_remove = (String -> Name
Core.Name String
"remove")
_CypherFeatures_schema :: Name
_CypherFeatures_schema = (String -> Name
Core.Name String
"schema")
_CypherFeatures_set :: Name
_CypherFeatures_set = (String -> Name
Core.Name String
"set")
_CypherFeatures_string :: Name
_CypherFeatures_string = (String -> Name
Core.Name String
"string")
_CypherFeatures_updating :: Name
_CypherFeatures_updating = (String -> Name
Core.Name String
"updating")
data DeleteFeatures =
DeleteFeatures {
DeleteFeatures -> Bool
deleteFeaturesDelete :: Bool,
DeleteFeatures -> Bool
deleteFeaturesDetachDelete :: Bool}
deriving (DeleteFeatures -> DeleteFeatures -> Bool
(DeleteFeatures -> DeleteFeatures -> Bool)
-> (DeleteFeatures -> DeleteFeatures -> Bool) -> Eq DeleteFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeleteFeatures -> DeleteFeatures -> Bool
== :: DeleteFeatures -> DeleteFeatures -> Bool
$c/= :: DeleteFeatures -> DeleteFeatures -> Bool
/= :: DeleteFeatures -> DeleteFeatures -> Bool
Eq, Eq DeleteFeatures
Eq DeleteFeatures =>
(DeleteFeatures -> DeleteFeatures -> Ordering)
-> (DeleteFeatures -> DeleteFeatures -> Bool)
-> (DeleteFeatures -> DeleteFeatures -> Bool)
-> (DeleteFeatures -> DeleteFeatures -> Bool)
-> (DeleteFeatures -> DeleteFeatures -> Bool)
-> (DeleteFeatures -> DeleteFeatures -> DeleteFeatures)
-> (DeleteFeatures -> DeleteFeatures -> DeleteFeatures)
-> Ord DeleteFeatures
DeleteFeatures -> DeleteFeatures -> Bool
DeleteFeatures -> DeleteFeatures -> Ordering
DeleteFeatures -> DeleteFeatures -> DeleteFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DeleteFeatures -> DeleteFeatures -> Ordering
compare :: DeleteFeatures -> DeleteFeatures -> Ordering
$c< :: DeleteFeatures -> DeleteFeatures -> Bool
< :: DeleteFeatures -> DeleteFeatures -> Bool
$c<= :: DeleteFeatures -> DeleteFeatures -> Bool
<= :: DeleteFeatures -> DeleteFeatures -> Bool
$c> :: DeleteFeatures -> DeleteFeatures -> Bool
> :: DeleteFeatures -> DeleteFeatures -> Bool
$c>= :: DeleteFeatures -> DeleteFeatures -> Bool
>= :: DeleteFeatures -> DeleteFeatures -> Bool
$cmax :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures
max :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures
$cmin :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures
min :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures
Ord, ReadPrec [DeleteFeatures]
ReadPrec DeleteFeatures
Int -> ReadS DeleteFeatures
ReadS [DeleteFeatures]
(Int -> ReadS DeleteFeatures)
-> ReadS [DeleteFeatures]
-> ReadPrec DeleteFeatures
-> ReadPrec [DeleteFeatures]
-> Read DeleteFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DeleteFeatures
readsPrec :: Int -> ReadS DeleteFeatures
$creadList :: ReadS [DeleteFeatures]
readList :: ReadS [DeleteFeatures]
$creadPrec :: ReadPrec DeleteFeatures
readPrec :: ReadPrec DeleteFeatures
$creadListPrec :: ReadPrec [DeleteFeatures]
readListPrec :: ReadPrec [DeleteFeatures]
Read, Int -> DeleteFeatures -> ShowS
[DeleteFeatures] -> ShowS
DeleteFeatures -> String
(Int -> DeleteFeatures -> ShowS)
-> (DeleteFeatures -> String)
-> ([DeleteFeatures] -> ShowS)
-> Show DeleteFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DeleteFeatures -> ShowS
showsPrec :: Int -> DeleteFeatures -> ShowS
$cshow :: DeleteFeatures -> String
show :: DeleteFeatures -> String
$cshowList :: [DeleteFeatures] -> ShowS
showList :: [DeleteFeatures] -> ShowS
Show)
_DeleteFeatures :: Name
_DeleteFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.DeleteFeatures")
_DeleteFeatures_delete :: Name
_DeleteFeatures_delete = (String -> Name
Core.Name String
"delete")
_DeleteFeatures_detachDelete :: Name
_DeleteFeatures_detachDelete = (String -> Name
Core.Name String
"detachDelete")
data ElementFeatures =
ElementFeatures {
ElementFeatures -> Bool
elementFeaturesElementId :: Bool,
ElementFeatures -> Bool
elementFeaturesEndNode :: Bool,
ElementFeatures -> Bool
elementFeaturesLabels :: Bool,
ElementFeatures -> Bool
elementFeaturesProperties :: Bool,
ElementFeatures -> Bool
elementFeaturesStartNode :: Bool}
deriving (ElementFeatures -> ElementFeatures -> Bool
(ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> Eq ElementFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElementFeatures -> ElementFeatures -> Bool
== :: ElementFeatures -> ElementFeatures -> Bool
$c/= :: ElementFeatures -> ElementFeatures -> Bool
/= :: ElementFeatures -> ElementFeatures -> Bool
Eq, Eq ElementFeatures
Eq ElementFeatures =>
(ElementFeatures -> ElementFeatures -> Ordering)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> ElementFeatures)
-> (ElementFeatures -> ElementFeatures -> ElementFeatures)
-> Ord ElementFeatures
ElementFeatures -> ElementFeatures -> Bool
ElementFeatures -> ElementFeatures -> Ordering
ElementFeatures -> ElementFeatures -> ElementFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ElementFeatures -> ElementFeatures -> Ordering
compare :: ElementFeatures -> ElementFeatures -> Ordering
$c< :: ElementFeatures -> ElementFeatures -> Bool
< :: ElementFeatures -> ElementFeatures -> Bool
$c<= :: ElementFeatures -> ElementFeatures -> Bool
<= :: ElementFeatures -> ElementFeatures -> Bool
$c> :: ElementFeatures -> ElementFeatures -> Bool
> :: ElementFeatures -> ElementFeatures -> Bool
$c>= :: ElementFeatures -> ElementFeatures -> Bool
>= :: ElementFeatures -> ElementFeatures -> Bool
$cmax :: ElementFeatures -> ElementFeatures -> ElementFeatures
max :: ElementFeatures -> ElementFeatures -> ElementFeatures
$cmin :: ElementFeatures -> ElementFeatures -> ElementFeatures
min :: ElementFeatures -> ElementFeatures -> ElementFeatures
Ord, ReadPrec [ElementFeatures]
ReadPrec ElementFeatures
Int -> ReadS ElementFeatures
ReadS [ElementFeatures]
(Int -> ReadS ElementFeatures)
-> ReadS [ElementFeatures]
-> ReadPrec ElementFeatures
-> ReadPrec [ElementFeatures]
-> Read ElementFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ElementFeatures
readsPrec :: Int -> ReadS ElementFeatures
$creadList :: ReadS [ElementFeatures]
readList :: ReadS [ElementFeatures]
$creadPrec :: ReadPrec ElementFeatures
readPrec :: ReadPrec ElementFeatures
$creadListPrec :: ReadPrec [ElementFeatures]
readListPrec :: ReadPrec [ElementFeatures]
Read, Int -> ElementFeatures -> ShowS
[ElementFeatures] -> ShowS
ElementFeatures -> String
(Int -> ElementFeatures -> ShowS)
-> (ElementFeatures -> String)
-> ([ElementFeatures] -> ShowS)
-> Show ElementFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElementFeatures -> ShowS
showsPrec :: Int -> ElementFeatures -> ShowS
$cshow :: ElementFeatures -> String
show :: ElementFeatures -> String
$cshowList :: [ElementFeatures] -> ShowS
showList :: [ElementFeatures] -> ShowS
Show)
_ElementFeatures :: Name
_ElementFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ElementFeatures")
_ElementFeatures_elementId :: Name
_ElementFeatures_elementId = (String -> Name
Core.Name String
"elementId")
_ElementFeatures_endNode :: Name
_ElementFeatures_endNode = (String -> Name
Core.Name String
"endNode")
_ElementFeatures_labels :: Name
_ElementFeatures_labels = (String -> Name
Core.Name String
"labels")
_ElementFeatures_properties :: Name
_ElementFeatures_properties = (String -> Name
Core.Name String
"properties")
_ElementFeatures_startNode :: Name
_ElementFeatures_startNode = (String -> Name
Core.Name String
"startNode")
data ListFeatures =
ListFeatures {
ListFeatures -> Bool
listFeaturesAll :: Bool,
ListFeatures -> Bool
listFeaturesAny :: Bool,
ListFeatures -> Bool
listFeaturesCoalesce :: Bool,
ListFeatures -> Bool
listFeaturesIsEmpty :: Bool,
ListFeatures -> Bool
listFeaturesHead :: Bool,
ListFeatures -> Bool
listFeaturesLast :: Bool,
ListFeatures -> Bool
listFeaturesListComprehension :: Bool,
ListFeatures -> Bool
listFeaturesListRange :: Bool,
ListFeatures -> Bool
listFeaturesNone :: Bool,
ListFeatures -> Bool
listFeaturesReduce :: Bool,
ListFeatures -> Bool
listFeaturesReverse :: Bool,
ListFeatures -> Bool
listFeaturesSingle :: Bool,
ListFeatures -> Bool
listFeaturesSize :: Bool,
ListFeatures -> Bool
listFeaturesTail :: Bool,
ListFeatures -> Bool
listFeaturesToBooleanList :: Bool,
ListFeatures -> Bool
listFeaturesToFloatList :: Bool,
ListFeatures -> Bool
listFeaturesToIntegerList :: Bool,
ListFeatures -> Bool
listFeaturesToStringList :: Bool}
deriving (ListFeatures -> ListFeatures -> Bool
(ListFeatures -> ListFeatures -> Bool)
-> (ListFeatures -> ListFeatures -> Bool) -> Eq ListFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListFeatures -> ListFeatures -> Bool
== :: ListFeatures -> ListFeatures -> Bool
$c/= :: ListFeatures -> ListFeatures -> Bool
/= :: ListFeatures -> ListFeatures -> Bool
Eq, Eq ListFeatures
Eq ListFeatures =>
(ListFeatures -> ListFeatures -> Ordering)
-> (ListFeatures -> ListFeatures -> Bool)
-> (ListFeatures -> ListFeatures -> Bool)
-> (ListFeatures -> ListFeatures -> Bool)
-> (ListFeatures -> ListFeatures -> Bool)
-> (ListFeatures -> ListFeatures -> ListFeatures)
-> (ListFeatures -> ListFeatures -> ListFeatures)
-> Ord ListFeatures
ListFeatures -> ListFeatures -> Bool
ListFeatures -> ListFeatures -> Ordering
ListFeatures -> ListFeatures -> ListFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ListFeatures -> ListFeatures -> Ordering
compare :: ListFeatures -> ListFeatures -> Ordering
$c< :: ListFeatures -> ListFeatures -> Bool
< :: ListFeatures -> ListFeatures -> Bool
$c<= :: ListFeatures -> ListFeatures -> Bool
<= :: ListFeatures -> ListFeatures -> Bool
$c> :: ListFeatures -> ListFeatures -> Bool
> :: ListFeatures -> ListFeatures -> Bool
$c>= :: ListFeatures -> ListFeatures -> Bool
>= :: ListFeatures -> ListFeatures -> Bool
$cmax :: ListFeatures -> ListFeatures -> ListFeatures
max :: ListFeatures -> ListFeatures -> ListFeatures
$cmin :: ListFeatures -> ListFeatures -> ListFeatures
min :: ListFeatures -> ListFeatures -> ListFeatures
Ord, ReadPrec [ListFeatures]
ReadPrec ListFeatures
Int -> ReadS ListFeatures
ReadS [ListFeatures]
(Int -> ReadS ListFeatures)
-> ReadS [ListFeatures]
-> ReadPrec ListFeatures
-> ReadPrec [ListFeatures]
-> Read ListFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListFeatures
readsPrec :: Int -> ReadS ListFeatures
$creadList :: ReadS [ListFeatures]
readList :: ReadS [ListFeatures]
$creadPrec :: ReadPrec ListFeatures
readPrec :: ReadPrec ListFeatures
$creadListPrec :: ReadPrec [ListFeatures]
readListPrec :: ReadPrec [ListFeatures]
Read, Int -> ListFeatures -> ShowS
[ListFeatures] -> ShowS
ListFeatures -> String
(Int -> ListFeatures -> ShowS)
-> (ListFeatures -> String)
-> ([ListFeatures] -> ShowS)
-> Show ListFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListFeatures -> ShowS
showsPrec :: Int -> ListFeatures -> ShowS
$cshow :: ListFeatures -> String
show :: ListFeatures -> String
$cshowList :: [ListFeatures] -> ShowS
showList :: [ListFeatures] -> ShowS
Show)
_ListFeatures :: Name
_ListFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ListFeatures")
_ListFeatures_all :: Name
_ListFeatures_all = (String -> Name
Core.Name String
"all")
_ListFeatures_any :: Name
_ListFeatures_any = (String -> Name
Core.Name String
"any")
_ListFeatures_coalesce :: Name
_ListFeatures_coalesce = (String -> Name
Core.Name String
"coalesce")
_ListFeatures_isEmpty :: Name
_ListFeatures_isEmpty = (String -> Name
Core.Name String
"isEmpty")
_ListFeatures_head :: Name
_ListFeatures_head = (String -> Name
Core.Name String
"head")
_ListFeatures_last :: Name
_ListFeatures_last = (String -> Name
Core.Name String
"last")
_ListFeatures_listComprehension :: Name
_ListFeatures_listComprehension = (String -> Name
Core.Name String
"listComprehension")
_ListFeatures_listRange :: Name
_ListFeatures_listRange = (String -> Name
Core.Name String
"listRange")
_ListFeatures_none :: Name
_ListFeatures_none = (String -> Name
Core.Name String
"none")
_ListFeatures_reduce :: Name
_ListFeatures_reduce = (String -> Name
Core.Name String
"reduce")
_ListFeatures_reverse :: Name
_ListFeatures_reverse = (String -> Name
Core.Name String
"reverse")
_ListFeatures_single :: Name
_ListFeatures_single = (String -> Name
Core.Name String
"single")
_ListFeatures_size :: Name
_ListFeatures_size = (String -> Name
Core.Name String
"size")
_ListFeatures_tail :: Name
_ListFeatures_tail = (String -> Name
Core.Name String
"tail")
_ListFeatures_toBooleanList :: Name
_ListFeatures_toBooleanList = (String -> Name
Core.Name String
"toBooleanList")
_ListFeatures_toFloatList :: Name
_ListFeatures_toFloatList = (String -> Name
Core.Name String
"toFloatList")
_ListFeatures_toIntegerList :: Name
_ListFeatures_toIntegerList = (String -> Name
Core.Name String
"toIntegerList")
_ListFeatures_toStringList :: Name
_ListFeatures_toStringList = (String -> Name
Core.Name String
"toStringList")
data LiteralFeatures =
LiteralFeatures {
LiteralFeatures -> Bool
literalFeaturesBoolean :: Bool,
LiteralFeatures -> Bool
literalFeaturesDouble :: Bool,
LiteralFeatures -> Bool
literalFeaturesInteger :: Bool,
LiteralFeatures -> Bool
literalFeaturesList :: Bool,
LiteralFeatures -> Bool
literalFeaturesMap :: Bool,
LiteralFeatures -> Bool
literalFeaturesNull :: Bool,
LiteralFeatures -> Bool
literalFeaturesString :: Bool}
deriving (LiteralFeatures -> LiteralFeatures -> Bool
(LiteralFeatures -> LiteralFeatures -> Bool)
-> (LiteralFeatures -> LiteralFeatures -> Bool)
-> Eq LiteralFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LiteralFeatures -> LiteralFeatures -> Bool
== :: LiteralFeatures -> LiteralFeatures -> Bool
$c/= :: LiteralFeatures -> LiteralFeatures -> Bool
/= :: LiteralFeatures -> LiteralFeatures -> Bool
Eq, Eq LiteralFeatures
Eq LiteralFeatures =>
(LiteralFeatures -> LiteralFeatures -> Ordering)
-> (LiteralFeatures -> LiteralFeatures -> Bool)
-> (LiteralFeatures -> LiteralFeatures -> Bool)
-> (LiteralFeatures -> LiteralFeatures -> Bool)
-> (LiteralFeatures -> LiteralFeatures -> Bool)
-> (LiteralFeatures -> LiteralFeatures -> LiteralFeatures)
-> (LiteralFeatures -> LiteralFeatures -> LiteralFeatures)
-> Ord LiteralFeatures
LiteralFeatures -> LiteralFeatures -> Bool
LiteralFeatures -> LiteralFeatures -> Ordering
LiteralFeatures -> LiteralFeatures -> LiteralFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LiteralFeatures -> LiteralFeatures -> Ordering
compare :: LiteralFeatures -> LiteralFeatures -> Ordering
$c< :: LiteralFeatures -> LiteralFeatures -> Bool
< :: LiteralFeatures -> LiteralFeatures -> Bool
$c<= :: LiteralFeatures -> LiteralFeatures -> Bool
<= :: LiteralFeatures -> LiteralFeatures -> Bool
$c> :: LiteralFeatures -> LiteralFeatures -> Bool
> :: LiteralFeatures -> LiteralFeatures -> Bool
$c>= :: LiteralFeatures -> LiteralFeatures -> Bool
>= :: LiteralFeatures -> LiteralFeatures -> Bool
$cmax :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures
max :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures
$cmin :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures
min :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures
Ord, ReadPrec [LiteralFeatures]
ReadPrec LiteralFeatures
Int -> ReadS LiteralFeatures
ReadS [LiteralFeatures]
(Int -> ReadS LiteralFeatures)
-> ReadS [LiteralFeatures]
-> ReadPrec LiteralFeatures
-> ReadPrec [LiteralFeatures]
-> Read LiteralFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LiteralFeatures
readsPrec :: Int -> ReadS LiteralFeatures
$creadList :: ReadS [LiteralFeatures]
readList :: ReadS [LiteralFeatures]
$creadPrec :: ReadPrec LiteralFeatures
readPrec :: ReadPrec LiteralFeatures
$creadListPrec :: ReadPrec [LiteralFeatures]
readListPrec :: ReadPrec [LiteralFeatures]
Read, Int -> LiteralFeatures -> ShowS
[LiteralFeatures] -> ShowS
LiteralFeatures -> String
(Int -> LiteralFeatures -> ShowS)
-> (LiteralFeatures -> String)
-> ([LiteralFeatures] -> ShowS)
-> Show LiteralFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LiteralFeatures -> ShowS
showsPrec :: Int -> LiteralFeatures -> ShowS
$cshow :: LiteralFeatures -> String
show :: LiteralFeatures -> String
$cshowList :: [LiteralFeatures] -> ShowS
showList :: [LiteralFeatures] -> ShowS
Show)
_LiteralFeatures :: Name
_LiteralFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.LiteralFeatures")
_LiteralFeatures_boolean :: Name
_LiteralFeatures_boolean = (String -> Name
Core.Name String
"boolean")
_LiteralFeatures_double :: Name
_LiteralFeatures_double = (String -> Name
Core.Name String
"double")
_LiteralFeatures_integer :: Name
_LiteralFeatures_integer = (String -> Name
Core.Name String
"integer")
_LiteralFeatures_list :: Name
_LiteralFeatures_list = (String -> Name
Core.Name String
"list")
_LiteralFeatures_map :: Name
_LiteralFeatures_map = (String -> Name
Core.Name String
"map")
_LiteralFeatures_null :: Name
_LiteralFeatures_null = (String -> Name
Core.Name String
"null")
_LiteralFeatures_string :: Name
_LiteralFeatures_string = (String -> Name
Core.Name String
"string")
data LogicalFeatures =
LogicalFeatures {
LogicalFeatures -> Bool
logicalFeaturesAnd :: Bool,
LogicalFeatures -> Bool
logicalFeaturesNot :: Bool,
LogicalFeatures -> Bool
logicalFeaturesOr :: Bool,
LogicalFeatures -> Bool
logicalFeaturesXor :: Bool}
deriving (LogicalFeatures -> LogicalFeatures -> Bool
(LogicalFeatures -> LogicalFeatures -> Bool)
-> (LogicalFeatures -> LogicalFeatures -> Bool)
-> Eq LogicalFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogicalFeatures -> LogicalFeatures -> Bool
== :: LogicalFeatures -> LogicalFeatures -> Bool
$c/= :: LogicalFeatures -> LogicalFeatures -> Bool
/= :: LogicalFeatures -> LogicalFeatures -> Bool
Eq, Eq LogicalFeatures
Eq LogicalFeatures =>
(LogicalFeatures -> LogicalFeatures -> Ordering)
-> (LogicalFeatures -> LogicalFeatures -> Bool)
-> (LogicalFeatures -> LogicalFeatures -> Bool)
-> (LogicalFeatures -> LogicalFeatures -> Bool)
-> (LogicalFeatures -> LogicalFeatures -> Bool)
-> (LogicalFeatures -> LogicalFeatures -> LogicalFeatures)
-> (LogicalFeatures -> LogicalFeatures -> LogicalFeatures)
-> Ord LogicalFeatures
LogicalFeatures -> LogicalFeatures -> Bool
LogicalFeatures -> LogicalFeatures -> Ordering
LogicalFeatures -> LogicalFeatures -> LogicalFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LogicalFeatures -> LogicalFeatures -> Ordering
compare :: LogicalFeatures -> LogicalFeatures -> Ordering
$c< :: LogicalFeatures -> LogicalFeatures -> Bool
< :: LogicalFeatures -> LogicalFeatures -> Bool
$c<= :: LogicalFeatures -> LogicalFeatures -> Bool
<= :: LogicalFeatures -> LogicalFeatures -> Bool
$c> :: LogicalFeatures -> LogicalFeatures -> Bool
> :: LogicalFeatures -> LogicalFeatures -> Bool
$c>= :: LogicalFeatures -> LogicalFeatures -> Bool
>= :: LogicalFeatures -> LogicalFeatures -> Bool
$cmax :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures
max :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures
$cmin :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures
min :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures
Ord, ReadPrec [LogicalFeatures]
ReadPrec LogicalFeatures
Int -> ReadS LogicalFeatures
ReadS [LogicalFeatures]
(Int -> ReadS LogicalFeatures)
-> ReadS [LogicalFeatures]
-> ReadPrec LogicalFeatures
-> ReadPrec [LogicalFeatures]
-> Read LogicalFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LogicalFeatures
readsPrec :: Int -> ReadS LogicalFeatures
$creadList :: ReadS [LogicalFeatures]
readList :: ReadS [LogicalFeatures]
$creadPrec :: ReadPrec LogicalFeatures
readPrec :: ReadPrec LogicalFeatures
$creadListPrec :: ReadPrec [LogicalFeatures]
readListPrec :: ReadPrec [LogicalFeatures]
Read, Int -> LogicalFeatures -> ShowS
[LogicalFeatures] -> ShowS
LogicalFeatures -> String
(Int -> LogicalFeatures -> ShowS)
-> (LogicalFeatures -> String)
-> ([LogicalFeatures] -> ShowS)
-> Show LogicalFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogicalFeatures -> ShowS
showsPrec :: Int -> LogicalFeatures -> ShowS
$cshow :: LogicalFeatures -> String
show :: LogicalFeatures -> String
$cshowList :: [LogicalFeatures] -> ShowS
showList :: [LogicalFeatures] -> ShowS
Show)
_LogicalFeatures :: Name
_LogicalFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.LogicalFeatures")
_LogicalFeatures_and :: Name
_LogicalFeatures_and = (String -> Name
Core.Name String
"and")
_LogicalFeatures_not :: Name
_LogicalFeatures_not = (String -> Name
Core.Name String
"not")
_LogicalFeatures_or :: Name
_LogicalFeatures_or = (String -> Name
Core.Name String
"or")
_LogicalFeatures_xor :: Name
_LogicalFeatures_xor = (String -> Name
Core.Name String
"xor")
data MapFeatures =
MapFeatures {
MapFeatures -> Bool
mapFeaturesKeys :: Bool}
deriving (MapFeatures -> MapFeatures -> Bool
(MapFeatures -> MapFeatures -> Bool)
-> (MapFeatures -> MapFeatures -> Bool) -> Eq MapFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MapFeatures -> MapFeatures -> Bool
== :: MapFeatures -> MapFeatures -> Bool
$c/= :: MapFeatures -> MapFeatures -> Bool
/= :: MapFeatures -> MapFeatures -> Bool
Eq, Eq MapFeatures
Eq MapFeatures =>
(MapFeatures -> MapFeatures -> Ordering)
-> (MapFeatures -> MapFeatures -> Bool)
-> (MapFeatures -> MapFeatures -> Bool)
-> (MapFeatures -> MapFeatures -> Bool)
-> (MapFeatures -> MapFeatures -> Bool)
-> (MapFeatures -> MapFeatures -> MapFeatures)
-> (MapFeatures -> MapFeatures -> MapFeatures)
-> Ord MapFeatures
MapFeatures -> MapFeatures -> Bool
MapFeatures -> MapFeatures -> Ordering
MapFeatures -> MapFeatures -> MapFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MapFeatures -> MapFeatures -> Ordering
compare :: MapFeatures -> MapFeatures -> Ordering
$c< :: MapFeatures -> MapFeatures -> Bool
< :: MapFeatures -> MapFeatures -> Bool
$c<= :: MapFeatures -> MapFeatures -> Bool
<= :: MapFeatures -> MapFeatures -> Bool
$c> :: MapFeatures -> MapFeatures -> Bool
> :: MapFeatures -> MapFeatures -> Bool
$c>= :: MapFeatures -> MapFeatures -> Bool
>= :: MapFeatures -> MapFeatures -> Bool
$cmax :: MapFeatures -> MapFeatures -> MapFeatures
max :: MapFeatures -> MapFeatures -> MapFeatures
$cmin :: MapFeatures -> MapFeatures -> MapFeatures
min :: MapFeatures -> MapFeatures -> MapFeatures
Ord, ReadPrec [MapFeatures]
ReadPrec MapFeatures
Int -> ReadS MapFeatures
ReadS [MapFeatures]
(Int -> ReadS MapFeatures)
-> ReadS [MapFeatures]
-> ReadPrec MapFeatures
-> ReadPrec [MapFeatures]
-> Read MapFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MapFeatures
readsPrec :: Int -> ReadS MapFeatures
$creadList :: ReadS [MapFeatures]
readList :: ReadS [MapFeatures]
$creadPrec :: ReadPrec MapFeatures
readPrec :: ReadPrec MapFeatures
$creadListPrec :: ReadPrec [MapFeatures]
readListPrec :: ReadPrec [MapFeatures]
Read, Int -> MapFeatures -> ShowS
[MapFeatures] -> ShowS
MapFeatures -> String
(Int -> MapFeatures -> ShowS)
-> (MapFeatures -> String)
-> ([MapFeatures] -> ShowS)
-> Show MapFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MapFeatures -> ShowS
showsPrec :: Int -> MapFeatures -> ShowS
$cshow :: MapFeatures -> String
show :: MapFeatures -> String
$cshowList :: [MapFeatures] -> ShowS
showList :: [MapFeatures] -> ShowS
Show)
_MapFeatures :: Name
_MapFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.MapFeatures")
_MapFeatures_keys :: Name
_MapFeatures_keys = (String -> Name
Core.Name String
"keys")
data MatchFeatures =
MatchFeatures {
MatchFeatures -> Bool
matchFeaturesMatch :: Bool,
MatchFeatures -> Bool
matchFeaturesOptionalMatch :: Bool}
deriving (MatchFeatures -> MatchFeatures -> Bool
(MatchFeatures -> MatchFeatures -> Bool)
-> (MatchFeatures -> MatchFeatures -> Bool) -> Eq MatchFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MatchFeatures -> MatchFeatures -> Bool
== :: MatchFeatures -> MatchFeatures -> Bool
$c/= :: MatchFeatures -> MatchFeatures -> Bool
/= :: MatchFeatures -> MatchFeatures -> Bool
Eq, Eq MatchFeatures
Eq MatchFeatures =>
(MatchFeatures -> MatchFeatures -> Ordering)
-> (MatchFeatures -> MatchFeatures -> Bool)
-> (MatchFeatures -> MatchFeatures -> Bool)
-> (MatchFeatures -> MatchFeatures -> Bool)
-> (MatchFeatures -> MatchFeatures -> Bool)
-> (MatchFeatures -> MatchFeatures -> MatchFeatures)
-> (MatchFeatures -> MatchFeatures -> MatchFeatures)
-> Ord MatchFeatures
MatchFeatures -> MatchFeatures -> Bool
MatchFeatures -> MatchFeatures -> Ordering
MatchFeatures -> MatchFeatures -> MatchFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MatchFeatures -> MatchFeatures -> Ordering
compare :: MatchFeatures -> MatchFeatures -> Ordering
$c< :: MatchFeatures -> MatchFeatures -> Bool
< :: MatchFeatures -> MatchFeatures -> Bool
$c<= :: MatchFeatures -> MatchFeatures -> Bool
<= :: MatchFeatures -> MatchFeatures -> Bool
$c> :: MatchFeatures -> MatchFeatures -> Bool
> :: MatchFeatures -> MatchFeatures -> Bool
$c>= :: MatchFeatures -> MatchFeatures -> Bool
>= :: MatchFeatures -> MatchFeatures -> Bool
$cmax :: MatchFeatures -> MatchFeatures -> MatchFeatures
max :: MatchFeatures -> MatchFeatures -> MatchFeatures
$cmin :: MatchFeatures -> MatchFeatures -> MatchFeatures
min :: MatchFeatures -> MatchFeatures -> MatchFeatures
Ord, ReadPrec [MatchFeatures]
ReadPrec MatchFeatures
Int -> ReadS MatchFeatures
ReadS [MatchFeatures]
(Int -> ReadS MatchFeatures)
-> ReadS [MatchFeatures]
-> ReadPrec MatchFeatures
-> ReadPrec [MatchFeatures]
-> Read MatchFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MatchFeatures
readsPrec :: Int -> ReadS MatchFeatures
$creadList :: ReadS [MatchFeatures]
readList :: ReadS [MatchFeatures]
$creadPrec :: ReadPrec MatchFeatures
readPrec :: ReadPrec MatchFeatures
$creadListPrec :: ReadPrec [MatchFeatures]
readListPrec :: ReadPrec [MatchFeatures]
Read, Int -> MatchFeatures -> ShowS
[MatchFeatures] -> ShowS
MatchFeatures -> String
(Int -> MatchFeatures -> ShowS)
-> (MatchFeatures -> String)
-> ([MatchFeatures] -> ShowS)
-> Show MatchFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MatchFeatures -> ShowS
showsPrec :: Int -> MatchFeatures -> ShowS
$cshow :: MatchFeatures -> String
show :: MatchFeatures -> String
$cshowList :: [MatchFeatures] -> ShowS
showList :: [MatchFeatures] -> ShowS
Show)
_MatchFeatures :: Name
_MatchFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.MatchFeatures")
_MatchFeatures_match :: Name
_MatchFeatures_match = (String -> Name
Core.Name String
"match")
_MatchFeatures_optionalMatch :: Name
_MatchFeatures_optionalMatch = (String -> Name
Core.Name String
"optionalMatch")
data MergeFeatures =
MergeFeatures {
MergeFeatures -> Bool
mergeFeaturesMerge :: Bool,
MergeFeatures -> Bool
mergeFeaturesMergeOnCreate :: Bool,
MergeFeatures -> Bool
mergeFeaturesMergeOnMatch :: Bool}
deriving (MergeFeatures -> MergeFeatures -> Bool
(MergeFeatures -> MergeFeatures -> Bool)
-> (MergeFeatures -> MergeFeatures -> Bool) -> Eq MergeFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MergeFeatures -> MergeFeatures -> Bool
== :: MergeFeatures -> MergeFeatures -> Bool
$c/= :: MergeFeatures -> MergeFeatures -> Bool
/= :: MergeFeatures -> MergeFeatures -> Bool
Eq, Eq MergeFeatures
Eq MergeFeatures =>
(MergeFeatures -> MergeFeatures -> Ordering)
-> (MergeFeatures -> MergeFeatures -> Bool)
-> (MergeFeatures -> MergeFeatures -> Bool)
-> (MergeFeatures -> MergeFeatures -> Bool)
-> (MergeFeatures -> MergeFeatures -> Bool)
-> (MergeFeatures -> MergeFeatures -> MergeFeatures)
-> (MergeFeatures -> MergeFeatures -> MergeFeatures)
-> Ord MergeFeatures
MergeFeatures -> MergeFeatures -> Bool
MergeFeatures -> MergeFeatures -> Ordering
MergeFeatures -> MergeFeatures -> MergeFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MergeFeatures -> MergeFeatures -> Ordering
compare :: MergeFeatures -> MergeFeatures -> Ordering
$c< :: MergeFeatures -> MergeFeatures -> Bool
< :: MergeFeatures -> MergeFeatures -> Bool
$c<= :: MergeFeatures -> MergeFeatures -> Bool
<= :: MergeFeatures -> MergeFeatures -> Bool
$c> :: MergeFeatures -> MergeFeatures -> Bool
> :: MergeFeatures -> MergeFeatures -> Bool
$c>= :: MergeFeatures -> MergeFeatures -> Bool
>= :: MergeFeatures -> MergeFeatures -> Bool
$cmax :: MergeFeatures -> MergeFeatures -> MergeFeatures
max :: MergeFeatures -> MergeFeatures -> MergeFeatures
$cmin :: MergeFeatures -> MergeFeatures -> MergeFeatures
min :: MergeFeatures -> MergeFeatures -> MergeFeatures
Ord, ReadPrec [MergeFeatures]
ReadPrec MergeFeatures
Int -> ReadS MergeFeatures
ReadS [MergeFeatures]
(Int -> ReadS MergeFeatures)
-> ReadS [MergeFeatures]
-> ReadPrec MergeFeatures
-> ReadPrec [MergeFeatures]
-> Read MergeFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MergeFeatures
readsPrec :: Int -> ReadS MergeFeatures
$creadList :: ReadS [MergeFeatures]
readList :: ReadS [MergeFeatures]
$creadPrec :: ReadPrec MergeFeatures
readPrec :: ReadPrec MergeFeatures
$creadListPrec :: ReadPrec [MergeFeatures]
readListPrec :: ReadPrec [MergeFeatures]
Read, Int -> MergeFeatures -> ShowS
[MergeFeatures] -> ShowS
MergeFeatures -> String
(Int -> MergeFeatures -> ShowS)
-> (MergeFeatures -> String)
-> ([MergeFeatures] -> ShowS)
-> Show MergeFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MergeFeatures -> ShowS
showsPrec :: Int -> MergeFeatures -> ShowS
$cshow :: MergeFeatures -> String
show :: MergeFeatures -> String
$cshowList :: [MergeFeatures] -> ShowS
showList :: [MergeFeatures] -> ShowS
Show)
_MergeFeatures :: Name
_MergeFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.MergeFeatures")
_MergeFeatures_merge :: Name
_MergeFeatures_merge = (String -> Name
Core.Name String
"merge")
_MergeFeatures_mergeOnCreate :: Name
_MergeFeatures_mergeOnCreate = (String -> Name
Core.Name String
"mergeOnCreate")
_MergeFeatures_mergeOnMatch :: Name
_MergeFeatures_mergeOnMatch = (String -> Name
Core.Name String
"mergeOnMatch")
data NodePatternFeatures =
NodePatternFeatures {
NodePatternFeatures -> Bool
nodePatternFeaturesMultipleLabels :: Bool,
NodePatternFeatures -> Bool
nodePatternFeaturesParameter :: Bool,
NodePatternFeatures -> Bool
nodePatternFeaturesPropertyMap :: Bool,
NodePatternFeatures -> Bool
nodePatternFeaturesVariableNode :: Bool,
NodePatternFeatures -> Bool
nodePatternFeaturesWildcardLabel :: Bool}
deriving (NodePatternFeatures -> NodePatternFeatures -> Bool
(NodePatternFeatures -> NodePatternFeatures -> Bool)
-> (NodePatternFeatures -> NodePatternFeatures -> Bool)
-> Eq NodePatternFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodePatternFeatures -> NodePatternFeatures -> Bool
== :: NodePatternFeatures -> NodePatternFeatures -> Bool
$c/= :: NodePatternFeatures -> NodePatternFeatures -> Bool
/= :: NodePatternFeatures -> NodePatternFeatures -> Bool
Eq, Eq NodePatternFeatures
Eq NodePatternFeatures =>
(NodePatternFeatures -> NodePatternFeatures -> Ordering)
-> (NodePatternFeatures -> NodePatternFeatures -> Bool)
-> (NodePatternFeatures -> NodePatternFeatures -> Bool)
-> (NodePatternFeatures -> NodePatternFeatures -> Bool)
-> (NodePatternFeatures -> NodePatternFeatures -> Bool)
-> (NodePatternFeatures
-> NodePatternFeatures -> NodePatternFeatures)
-> (NodePatternFeatures
-> NodePatternFeatures -> NodePatternFeatures)
-> Ord NodePatternFeatures
NodePatternFeatures -> NodePatternFeatures -> Bool
NodePatternFeatures -> NodePatternFeatures -> Ordering
NodePatternFeatures -> NodePatternFeatures -> NodePatternFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NodePatternFeatures -> NodePatternFeatures -> Ordering
compare :: NodePatternFeatures -> NodePatternFeatures -> Ordering
$c< :: NodePatternFeatures -> NodePatternFeatures -> Bool
< :: NodePatternFeatures -> NodePatternFeatures -> Bool
$c<= :: NodePatternFeatures -> NodePatternFeatures -> Bool
<= :: NodePatternFeatures -> NodePatternFeatures -> Bool
$c> :: NodePatternFeatures -> NodePatternFeatures -> Bool
> :: NodePatternFeatures -> NodePatternFeatures -> Bool
$c>= :: NodePatternFeatures -> NodePatternFeatures -> Bool
>= :: NodePatternFeatures -> NodePatternFeatures -> Bool
$cmax :: NodePatternFeatures -> NodePatternFeatures -> NodePatternFeatures
max :: NodePatternFeatures -> NodePatternFeatures -> NodePatternFeatures
$cmin :: NodePatternFeatures -> NodePatternFeatures -> NodePatternFeatures
min :: NodePatternFeatures -> NodePatternFeatures -> NodePatternFeatures
Ord, ReadPrec [NodePatternFeatures]
ReadPrec NodePatternFeatures
Int -> ReadS NodePatternFeatures
ReadS [NodePatternFeatures]
(Int -> ReadS NodePatternFeatures)
-> ReadS [NodePatternFeatures]
-> ReadPrec NodePatternFeatures
-> ReadPrec [NodePatternFeatures]
-> Read NodePatternFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NodePatternFeatures
readsPrec :: Int -> ReadS NodePatternFeatures
$creadList :: ReadS [NodePatternFeatures]
readList :: ReadS [NodePatternFeatures]
$creadPrec :: ReadPrec NodePatternFeatures
readPrec :: ReadPrec NodePatternFeatures
$creadListPrec :: ReadPrec [NodePatternFeatures]
readListPrec :: ReadPrec [NodePatternFeatures]
Read, Int -> NodePatternFeatures -> ShowS
[NodePatternFeatures] -> ShowS
NodePatternFeatures -> String
(Int -> NodePatternFeatures -> ShowS)
-> (NodePatternFeatures -> String)
-> ([NodePatternFeatures] -> ShowS)
-> Show NodePatternFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodePatternFeatures -> ShowS
showsPrec :: Int -> NodePatternFeatures -> ShowS
$cshow :: NodePatternFeatures -> String
show :: NodePatternFeatures -> String
$cshowList :: [NodePatternFeatures] -> ShowS
showList :: [NodePatternFeatures] -> ShowS
Show)
_NodePatternFeatures :: Name
_NodePatternFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.NodePatternFeatures")
_NodePatternFeatures_multipleLabels :: Name
_NodePatternFeatures_multipleLabels = (String -> Name
Core.Name String
"multipleLabels")
_NodePatternFeatures_parameter :: Name
_NodePatternFeatures_parameter = (String -> Name
Core.Name String
"parameter")
_NodePatternFeatures_propertyMap :: Name
_NodePatternFeatures_propertyMap = (String -> Name
Core.Name String
"propertyMap")
_NodePatternFeatures_variableNode :: Name
_NodePatternFeatures_variableNode = (String -> Name
Core.Name String
"variableNode")
_NodePatternFeatures_wildcardLabel :: Name
_NodePatternFeatures_wildcardLabel = (String -> Name
Core.Name String
"wildcardLabel")
data NullFeatures =
NullFeatures {
NullFeatures -> Bool
nullFeaturesIsNull :: Bool,
NullFeatures -> Bool
nullFeaturesIsNotNull :: Bool}
deriving (NullFeatures -> NullFeatures -> Bool
(NullFeatures -> NullFeatures -> Bool)
-> (NullFeatures -> NullFeatures -> Bool) -> Eq NullFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NullFeatures -> NullFeatures -> Bool
== :: NullFeatures -> NullFeatures -> Bool
$c/= :: NullFeatures -> NullFeatures -> Bool
/= :: NullFeatures -> NullFeatures -> Bool
Eq, Eq NullFeatures
Eq NullFeatures =>
(NullFeatures -> NullFeatures -> Ordering)
-> (NullFeatures -> NullFeatures -> Bool)
-> (NullFeatures -> NullFeatures -> Bool)
-> (NullFeatures -> NullFeatures -> Bool)
-> (NullFeatures -> NullFeatures -> Bool)
-> (NullFeatures -> NullFeatures -> NullFeatures)
-> (NullFeatures -> NullFeatures -> NullFeatures)
-> Ord NullFeatures
NullFeatures -> NullFeatures -> Bool
NullFeatures -> NullFeatures -> Ordering
NullFeatures -> NullFeatures -> NullFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NullFeatures -> NullFeatures -> Ordering
compare :: NullFeatures -> NullFeatures -> Ordering
$c< :: NullFeatures -> NullFeatures -> Bool
< :: NullFeatures -> NullFeatures -> Bool
$c<= :: NullFeatures -> NullFeatures -> Bool
<= :: NullFeatures -> NullFeatures -> Bool
$c> :: NullFeatures -> NullFeatures -> Bool
> :: NullFeatures -> NullFeatures -> Bool
$c>= :: NullFeatures -> NullFeatures -> Bool
>= :: NullFeatures -> NullFeatures -> Bool
$cmax :: NullFeatures -> NullFeatures -> NullFeatures
max :: NullFeatures -> NullFeatures -> NullFeatures
$cmin :: NullFeatures -> NullFeatures -> NullFeatures
min :: NullFeatures -> NullFeatures -> NullFeatures
Ord, ReadPrec [NullFeatures]
ReadPrec NullFeatures
Int -> ReadS NullFeatures
ReadS [NullFeatures]
(Int -> ReadS NullFeatures)
-> ReadS [NullFeatures]
-> ReadPrec NullFeatures
-> ReadPrec [NullFeatures]
-> Read NullFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NullFeatures
readsPrec :: Int -> ReadS NullFeatures
$creadList :: ReadS [NullFeatures]
readList :: ReadS [NullFeatures]
$creadPrec :: ReadPrec NullFeatures
readPrec :: ReadPrec NullFeatures
$creadListPrec :: ReadPrec [NullFeatures]
readListPrec :: ReadPrec [NullFeatures]
Read, Int -> NullFeatures -> ShowS
[NullFeatures] -> ShowS
NullFeatures -> String
(Int -> NullFeatures -> ShowS)
-> (NullFeatures -> String)
-> ([NullFeatures] -> ShowS)
-> Show NullFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NullFeatures -> ShowS
showsPrec :: Int -> NullFeatures -> ShowS
$cshow :: NullFeatures -> String
show :: NullFeatures -> String
$cshowList :: [NullFeatures] -> ShowS
showList :: [NullFeatures] -> ShowS
Show)
_NullFeatures :: Name
_NullFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.NullFeatures")
_NullFeatures_isNull :: Name
_NullFeatures_isNull = (String -> Name
Core.Name String
"isNull")
_NullFeatures_isNotNull :: Name
_NullFeatures_isNotNull = (String -> Name
Core.Name String
"isNotNull")
data NumericFeatures =
NumericFeatures {
NumericFeatures -> Bool
numericFeaturesAbs :: Bool,
NumericFeatures -> Bool
numericFeaturesCeil :: Bool,
NumericFeatures -> Bool
numericFeaturesE :: Bool,
NumericFeatures -> Bool
numericFeaturesExp :: Bool,
NumericFeatures -> Bool
numericFeaturesFloor :: Bool,
NumericFeatures -> Bool
numericFeaturesIsNaN :: Bool,
NumericFeatures -> Bool
numericFeaturesLog :: Bool,
NumericFeatures -> Bool
numericFeaturesLog10 :: Bool,
NumericFeatures -> Bool
numericFeaturesRange :: Bool,
NumericFeatures -> Bool
numericFeaturesRound :: Bool,
NumericFeatures -> Bool
numericFeaturesSign :: Bool,
NumericFeatures -> Bool
numericFeaturesSqrt :: Bool}
deriving (NumericFeatures -> NumericFeatures -> Bool
(NumericFeatures -> NumericFeatures -> Bool)
-> (NumericFeatures -> NumericFeatures -> Bool)
-> Eq NumericFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumericFeatures -> NumericFeatures -> Bool
== :: NumericFeatures -> NumericFeatures -> Bool
$c/= :: NumericFeatures -> NumericFeatures -> Bool
/= :: NumericFeatures -> NumericFeatures -> Bool
Eq, Eq NumericFeatures
Eq NumericFeatures =>
(NumericFeatures -> NumericFeatures -> Ordering)
-> (NumericFeatures -> NumericFeatures -> Bool)
-> (NumericFeatures -> NumericFeatures -> Bool)
-> (NumericFeatures -> NumericFeatures -> Bool)
-> (NumericFeatures -> NumericFeatures -> Bool)
-> (NumericFeatures -> NumericFeatures -> NumericFeatures)
-> (NumericFeatures -> NumericFeatures -> NumericFeatures)
-> Ord NumericFeatures
NumericFeatures -> NumericFeatures -> Bool
NumericFeatures -> NumericFeatures -> Ordering
NumericFeatures -> NumericFeatures -> NumericFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NumericFeatures -> NumericFeatures -> Ordering
compare :: NumericFeatures -> NumericFeatures -> Ordering
$c< :: NumericFeatures -> NumericFeatures -> Bool
< :: NumericFeatures -> NumericFeatures -> Bool
$c<= :: NumericFeatures -> NumericFeatures -> Bool
<= :: NumericFeatures -> NumericFeatures -> Bool
$c> :: NumericFeatures -> NumericFeatures -> Bool
> :: NumericFeatures -> NumericFeatures -> Bool
$c>= :: NumericFeatures -> NumericFeatures -> Bool
>= :: NumericFeatures -> NumericFeatures -> Bool
$cmax :: NumericFeatures -> NumericFeatures -> NumericFeatures
max :: NumericFeatures -> NumericFeatures -> NumericFeatures
$cmin :: NumericFeatures -> NumericFeatures -> NumericFeatures
min :: NumericFeatures -> NumericFeatures -> NumericFeatures
Ord, ReadPrec [NumericFeatures]
ReadPrec NumericFeatures
Int -> ReadS NumericFeatures
ReadS [NumericFeatures]
(Int -> ReadS NumericFeatures)
-> ReadS [NumericFeatures]
-> ReadPrec NumericFeatures
-> ReadPrec [NumericFeatures]
-> Read NumericFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NumericFeatures
readsPrec :: Int -> ReadS NumericFeatures
$creadList :: ReadS [NumericFeatures]
readList :: ReadS [NumericFeatures]
$creadPrec :: ReadPrec NumericFeatures
readPrec :: ReadPrec NumericFeatures
$creadListPrec :: ReadPrec [NumericFeatures]
readListPrec :: ReadPrec [NumericFeatures]
Read, Int -> NumericFeatures -> ShowS
[NumericFeatures] -> ShowS
NumericFeatures -> String
(Int -> NumericFeatures -> ShowS)
-> (NumericFeatures -> String)
-> ([NumericFeatures] -> ShowS)
-> Show NumericFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumericFeatures -> ShowS
showsPrec :: Int -> NumericFeatures -> ShowS
$cshow :: NumericFeatures -> String
show :: NumericFeatures -> String
$cshowList :: [NumericFeatures] -> ShowS
showList :: [NumericFeatures] -> ShowS
Show)
_NumericFeatures :: Name
_NumericFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.NumericFeatures")
_NumericFeatures_abs :: Name
_NumericFeatures_abs = (String -> Name
Core.Name String
"abs")
_NumericFeatures_ceil :: Name
_NumericFeatures_ceil = (String -> Name
Core.Name String
"ceil")
_NumericFeatures_e :: Name
_NumericFeatures_e = (String -> Name
Core.Name String
"e")
_NumericFeatures_exp :: Name
_NumericFeatures_exp = (String -> Name
Core.Name String
"exp")
_NumericFeatures_floor :: Name
_NumericFeatures_floor = (String -> Name
Core.Name String
"floor")
_NumericFeatures_isNaN :: Name
_NumericFeatures_isNaN = (String -> Name
Core.Name String
"isNaN")
_NumericFeatures_log :: Name
_NumericFeatures_log = (String -> Name
Core.Name String
"log")
_NumericFeatures_log10 :: Name
_NumericFeatures_log10 = (String -> Name
Core.Name String
"log10")
_NumericFeatures_range :: Name
_NumericFeatures_range = (String -> Name
Core.Name String
"range")
_NumericFeatures_round :: Name
_NumericFeatures_round = (String -> Name
Core.Name String
"round")
_NumericFeatures_sign :: Name
_NumericFeatures_sign = (String -> Name
Core.Name String
"sign")
_NumericFeatures_sqrt :: Name
_NumericFeatures_sqrt = (String -> Name
Core.Name String
"sqrt")
data PathFeatures =
PathFeatures {
PathFeatures -> Bool
pathFeaturesLength :: Bool,
PathFeatures -> Bool
pathFeaturesNodes :: Bool,
PathFeatures -> Bool
pathFeaturesRelationships :: Bool,
PathFeatures -> Bool
pathFeaturesShortestPath :: Bool}
deriving (PathFeatures -> PathFeatures -> Bool
(PathFeatures -> PathFeatures -> Bool)
-> (PathFeatures -> PathFeatures -> Bool) -> Eq PathFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathFeatures -> PathFeatures -> Bool
== :: PathFeatures -> PathFeatures -> Bool
$c/= :: PathFeatures -> PathFeatures -> Bool
/= :: PathFeatures -> PathFeatures -> Bool
Eq, Eq PathFeatures
Eq PathFeatures =>
(PathFeatures -> PathFeatures -> Ordering)
-> (PathFeatures -> PathFeatures -> Bool)
-> (PathFeatures -> PathFeatures -> Bool)
-> (PathFeatures -> PathFeatures -> Bool)
-> (PathFeatures -> PathFeatures -> Bool)
-> (PathFeatures -> PathFeatures -> PathFeatures)
-> (PathFeatures -> PathFeatures -> PathFeatures)
-> Ord PathFeatures
PathFeatures -> PathFeatures -> Bool
PathFeatures -> PathFeatures -> Ordering
PathFeatures -> PathFeatures -> PathFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PathFeatures -> PathFeatures -> Ordering
compare :: PathFeatures -> PathFeatures -> Ordering
$c< :: PathFeatures -> PathFeatures -> Bool
< :: PathFeatures -> PathFeatures -> Bool
$c<= :: PathFeatures -> PathFeatures -> Bool
<= :: PathFeatures -> PathFeatures -> Bool
$c> :: PathFeatures -> PathFeatures -> Bool
> :: PathFeatures -> PathFeatures -> Bool
$c>= :: PathFeatures -> PathFeatures -> Bool
>= :: PathFeatures -> PathFeatures -> Bool
$cmax :: PathFeatures -> PathFeatures -> PathFeatures
max :: PathFeatures -> PathFeatures -> PathFeatures
$cmin :: PathFeatures -> PathFeatures -> PathFeatures
min :: PathFeatures -> PathFeatures -> PathFeatures
Ord, ReadPrec [PathFeatures]
ReadPrec PathFeatures
Int -> ReadS PathFeatures
ReadS [PathFeatures]
(Int -> ReadS PathFeatures)
-> ReadS [PathFeatures]
-> ReadPrec PathFeatures
-> ReadPrec [PathFeatures]
-> Read PathFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PathFeatures
readsPrec :: Int -> ReadS PathFeatures
$creadList :: ReadS [PathFeatures]
readList :: ReadS [PathFeatures]
$creadPrec :: ReadPrec PathFeatures
readPrec :: ReadPrec PathFeatures
$creadListPrec :: ReadPrec [PathFeatures]
readListPrec :: ReadPrec [PathFeatures]
Read, Int -> PathFeatures -> ShowS
[PathFeatures] -> ShowS
PathFeatures -> String
(Int -> PathFeatures -> ShowS)
-> (PathFeatures -> String)
-> ([PathFeatures] -> ShowS)
-> Show PathFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathFeatures -> ShowS
showsPrec :: Int -> PathFeatures -> ShowS
$cshow :: PathFeatures -> String
show :: PathFeatures -> String
$cshowList :: [PathFeatures] -> ShowS
showList :: [PathFeatures] -> ShowS
Show)
_PathFeatures :: Name
_PathFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.PathFeatures")
_PathFeatures_length :: Name
_PathFeatures_length = (String -> Name
Core.Name String
"length")
_PathFeatures_nodes :: Name
_PathFeatures_nodes = (String -> Name
Core.Name String
"nodes")
_PathFeatures_relationships :: Name
_PathFeatures_relationships = (String -> Name
Core.Name String
"relationships")
_PathFeatures_shortestPath :: Name
_PathFeatures_shortestPath = (String -> Name
Core.Name String
"shortestPath")
data ProcedureCallFeatures =
ProcedureCallFeatures {
ProcedureCallFeatures -> Bool
procedureCallFeaturesInQueryCall :: Bool,
ProcedureCallFeatures -> Bool
procedureCallFeaturesStandaloneCall :: Bool,
ProcedureCallFeatures -> Bool
procedureCallFeaturesYield :: Bool}
deriving (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
(ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> Eq ProcedureCallFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
== :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
$c/= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
/= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
Eq, Eq ProcedureCallFeatures
Eq ProcedureCallFeatures =>
(ProcedureCallFeatures -> ProcedureCallFeatures -> Ordering)
-> (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> (ProcedureCallFeatures -> ProcedureCallFeatures -> Bool)
-> (ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures)
-> (ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures)
-> Ord ProcedureCallFeatures
ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
ProcedureCallFeatures -> ProcedureCallFeatures -> Ordering
ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ProcedureCallFeatures -> ProcedureCallFeatures -> Ordering
compare :: ProcedureCallFeatures -> ProcedureCallFeatures -> Ordering
$c< :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
< :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
$c<= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
<= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
$c> :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
> :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
$c>= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
>= :: ProcedureCallFeatures -> ProcedureCallFeatures -> Bool
$cmax :: ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures
max :: ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures
$cmin :: ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures
min :: ProcedureCallFeatures
-> ProcedureCallFeatures -> ProcedureCallFeatures
Ord, ReadPrec [ProcedureCallFeatures]
ReadPrec ProcedureCallFeatures
Int -> ReadS ProcedureCallFeatures
ReadS [ProcedureCallFeatures]
(Int -> ReadS ProcedureCallFeatures)
-> ReadS [ProcedureCallFeatures]
-> ReadPrec ProcedureCallFeatures
-> ReadPrec [ProcedureCallFeatures]
-> Read ProcedureCallFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ProcedureCallFeatures
readsPrec :: Int -> ReadS ProcedureCallFeatures
$creadList :: ReadS [ProcedureCallFeatures]
readList :: ReadS [ProcedureCallFeatures]
$creadPrec :: ReadPrec ProcedureCallFeatures
readPrec :: ReadPrec ProcedureCallFeatures
$creadListPrec :: ReadPrec [ProcedureCallFeatures]
readListPrec :: ReadPrec [ProcedureCallFeatures]
Read, Int -> ProcedureCallFeatures -> ShowS
[ProcedureCallFeatures] -> ShowS
ProcedureCallFeatures -> String
(Int -> ProcedureCallFeatures -> ShowS)
-> (ProcedureCallFeatures -> String)
-> ([ProcedureCallFeatures] -> ShowS)
-> Show ProcedureCallFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProcedureCallFeatures -> ShowS
showsPrec :: Int -> ProcedureCallFeatures -> ShowS
$cshow :: ProcedureCallFeatures -> String
show :: ProcedureCallFeatures -> String
$cshowList :: [ProcedureCallFeatures] -> ShowS
showList :: [ProcedureCallFeatures] -> ShowS
Show)
_ProcedureCallFeatures :: Name
_ProcedureCallFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ProcedureCallFeatures")
_ProcedureCallFeatures_inQueryCall :: Name
_ProcedureCallFeatures_inQueryCall = (String -> Name
Core.Name String
"inQueryCall")
_ProcedureCallFeatures_standaloneCall :: Name
_ProcedureCallFeatures_standaloneCall = (String -> Name
Core.Name String
"standaloneCall")
_ProcedureCallFeatures_yield :: Name
_ProcedureCallFeatures_yield = (String -> Name
Core.Name String
"yield")
data ProjectionFeatures =
ProjectionFeatures {
ProjectionFeatures -> Bool
projectionFeaturesLimit :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesOrderBy :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesProjectDistinct :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesProjectAll :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesProjectAs :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesSkip :: Bool,
ProjectionFeatures -> Bool
projectionFeaturesSortOrder :: Bool}
deriving (ProjectionFeatures -> ProjectionFeatures -> Bool
(ProjectionFeatures -> ProjectionFeatures -> Bool)
-> (ProjectionFeatures -> ProjectionFeatures -> Bool)
-> Eq ProjectionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProjectionFeatures -> ProjectionFeatures -> Bool
== :: ProjectionFeatures -> ProjectionFeatures -> Bool
$c/= :: ProjectionFeatures -> ProjectionFeatures -> Bool
/= :: ProjectionFeatures -> ProjectionFeatures -> Bool
Eq, Eq ProjectionFeatures
Eq ProjectionFeatures =>
(ProjectionFeatures -> ProjectionFeatures -> Ordering)
-> (ProjectionFeatures -> ProjectionFeatures -> Bool)
-> (ProjectionFeatures -> ProjectionFeatures -> Bool)
-> (ProjectionFeatures -> ProjectionFeatures -> Bool)
-> (ProjectionFeatures -> ProjectionFeatures -> Bool)
-> (ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures)
-> (ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures)
-> Ord ProjectionFeatures
ProjectionFeatures -> ProjectionFeatures -> Bool
ProjectionFeatures -> ProjectionFeatures -> Ordering
ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ProjectionFeatures -> ProjectionFeatures -> Ordering
compare :: ProjectionFeatures -> ProjectionFeatures -> Ordering
$c< :: ProjectionFeatures -> ProjectionFeatures -> Bool
< :: ProjectionFeatures -> ProjectionFeatures -> Bool
$c<= :: ProjectionFeatures -> ProjectionFeatures -> Bool
<= :: ProjectionFeatures -> ProjectionFeatures -> Bool
$c> :: ProjectionFeatures -> ProjectionFeatures -> Bool
> :: ProjectionFeatures -> ProjectionFeatures -> Bool
$c>= :: ProjectionFeatures -> ProjectionFeatures -> Bool
>= :: ProjectionFeatures -> ProjectionFeatures -> Bool
$cmax :: ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures
max :: ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures
$cmin :: ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures
min :: ProjectionFeatures -> ProjectionFeatures -> ProjectionFeatures
Ord, ReadPrec [ProjectionFeatures]
ReadPrec ProjectionFeatures
Int -> ReadS ProjectionFeatures
ReadS [ProjectionFeatures]
(Int -> ReadS ProjectionFeatures)
-> ReadS [ProjectionFeatures]
-> ReadPrec ProjectionFeatures
-> ReadPrec [ProjectionFeatures]
-> Read ProjectionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ProjectionFeatures
readsPrec :: Int -> ReadS ProjectionFeatures
$creadList :: ReadS [ProjectionFeatures]
readList :: ReadS [ProjectionFeatures]
$creadPrec :: ReadPrec ProjectionFeatures
readPrec :: ReadPrec ProjectionFeatures
$creadListPrec :: ReadPrec [ProjectionFeatures]
readListPrec :: ReadPrec [ProjectionFeatures]
Read, Int -> ProjectionFeatures -> ShowS
[ProjectionFeatures] -> ShowS
ProjectionFeatures -> String
(Int -> ProjectionFeatures -> ShowS)
-> (ProjectionFeatures -> String)
-> ([ProjectionFeatures] -> ShowS)
-> Show ProjectionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProjectionFeatures -> ShowS
showsPrec :: Int -> ProjectionFeatures -> ShowS
$cshow :: ProjectionFeatures -> String
show :: ProjectionFeatures -> String
$cshowList :: [ProjectionFeatures] -> ShowS
showList :: [ProjectionFeatures] -> ShowS
Show)
_ProjectionFeatures :: Name
_ProjectionFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ProjectionFeatures")
_ProjectionFeatures_limit :: Name
_ProjectionFeatures_limit = (String -> Name
Core.Name String
"limit")
_ProjectionFeatures_orderBy :: Name
_ProjectionFeatures_orderBy = (String -> Name
Core.Name String
"orderBy")
_ProjectionFeatures_projectDistinct :: Name
_ProjectionFeatures_projectDistinct = (String -> Name
Core.Name String
"projectDistinct")
_ProjectionFeatures_projectAll :: Name
_ProjectionFeatures_projectAll = (String -> Name
Core.Name String
"projectAll")
_ProjectionFeatures_projectAs :: Name
_ProjectionFeatures_projectAs = (String -> Name
Core.Name String
"projectAs")
_ProjectionFeatures_skip :: Name
_ProjectionFeatures_skip = (String -> Name
Core.Name String
"skip")
_ProjectionFeatures_sortOrder :: Name
_ProjectionFeatures_sortOrder = (String -> Name
Core.Name String
"sortOrder")
data QuantifierFeatures =
QuantifierFeatures {
QuantifierFeatures -> Bool
quantifierFeaturesAll :: Bool,
QuantifierFeatures -> Bool
quantifierFeaturesAny :: Bool,
QuantifierFeatures -> Bool
quantifierFeaturesExists :: Bool,
QuantifierFeatures -> Bool
quantifierFeaturesNone :: Bool,
QuantifierFeatures -> Bool
quantifierFeaturesSingle :: Bool}
deriving (QuantifierFeatures -> QuantifierFeatures -> Bool
(QuantifierFeatures -> QuantifierFeatures -> Bool)
-> (QuantifierFeatures -> QuantifierFeatures -> Bool)
-> Eq QuantifierFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuantifierFeatures -> QuantifierFeatures -> Bool
== :: QuantifierFeatures -> QuantifierFeatures -> Bool
$c/= :: QuantifierFeatures -> QuantifierFeatures -> Bool
/= :: QuantifierFeatures -> QuantifierFeatures -> Bool
Eq, Eq QuantifierFeatures
Eq QuantifierFeatures =>
(QuantifierFeatures -> QuantifierFeatures -> Ordering)
-> (QuantifierFeatures -> QuantifierFeatures -> Bool)
-> (QuantifierFeatures -> QuantifierFeatures -> Bool)
-> (QuantifierFeatures -> QuantifierFeatures -> Bool)
-> (QuantifierFeatures -> QuantifierFeatures -> Bool)
-> (QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures)
-> (QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures)
-> Ord QuantifierFeatures
QuantifierFeatures -> QuantifierFeatures -> Bool
QuantifierFeatures -> QuantifierFeatures -> Ordering
QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuantifierFeatures -> QuantifierFeatures -> Ordering
compare :: QuantifierFeatures -> QuantifierFeatures -> Ordering
$c< :: QuantifierFeatures -> QuantifierFeatures -> Bool
< :: QuantifierFeatures -> QuantifierFeatures -> Bool
$c<= :: QuantifierFeatures -> QuantifierFeatures -> Bool
<= :: QuantifierFeatures -> QuantifierFeatures -> Bool
$c> :: QuantifierFeatures -> QuantifierFeatures -> Bool
> :: QuantifierFeatures -> QuantifierFeatures -> Bool
$c>= :: QuantifierFeatures -> QuantifierFeatures -> Bool
>= :: QuantifierFeatures -> QuantifierFeatures -> Bool
$cmax :: QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures
max :: QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures
$cmin :: QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures
min :: QuantifierFeatures -> QuantifierFeatures -> QuantifierFeatures
Ord, ReadPrec [QuantifierFeatures]
ReadPrec QuantifierFeatures
Int -> ReadS QuantifierFeatures
ReadS [QuantifierFeatures]
(Int -> ReadS QuantifierFeatures)
-> ReadS [QuantifierFeatures]
-> ReadPrec QuantifierFeatures
-> ReadPrec [QuantifierFeatures]
-> Read QuantifierFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS QuantifierFeatures
readsPrec :: Int -> ReadS QuantifierFeatures
$creadList :: ReadS [QuantifierFeatures]
readList :: ReadS [QuantifierFeatures]
$creadPrec :: ReadPrec QuantifierFeatures
readPrec :: ReadPrec QuantifierFeatures
$creadListPrec :: ReadPrec [QuantifierFeatures]
readListPrec :: ReadPrec [QuantifierFeatures]
Read, Int -> QuantifierFeatures -> ShowS
[QuantifierFeatures] -> ShowS
QuantifierFeatures -> String
(Int -> QuantifierFeatures -> ShowS)
-> (QuantifierFeatures -> String)
-> ([QuantifierFeatures] -> ShowS)
-> Show QuantifierFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QuantifierFeatures -> ShowS
showsPrec :: Int -> QuantifierFeatures -> ShowS
$cshow :: QuantifierFeatures -> String
show :: QuantifierFeatures -> String
$cshowList :: [QuantifierFeatures] -> ShowS
showList :: [QuantifierFeatures] -> ShowS
Show)
_QuantifierFeatures :: Name
_QuantifierFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.QuantifierFeatures")
_QuantifierFeatures_all :: Name
_QuantifierFeatures_all = (String -> Name
Core.Name String
"all")
_QuantifierFeatures_any :: Name
_QuantifierFeatures_any = (String -> Name
Core.Name String
"any")
_QuantifierFeatures_exists :: Name
_QuantifierFeatures_exists = (String -> Name
Core.Name String
"exists")
_QuantifierFeatures_none :: Name
_QuantifierFeatures_none = (String -> Name
Core.Name String
"none")
_QuantifierFeatures_single :: Name
_QuantifierFeatures_single = (String -> Name
Core.Name String
"single")
data RandomnessFeatures =
RandomnessFeatures {
RandomnessFeatures -> Bool
randomnessFeaturesRand :: Bool,
RandomnessFeatures -> Bool
randomnessFeaturesRandomUUID :: Bool}
deriving (RandomnessFeatures -> RandomnessFeatures -> Bool
(RandomnessFeatures -> RandomnessFeatures -> Bool)
-> (RandomnessFeatures -> RandomnessFeatures -> Bool)
-> Eq RandomnessFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RandomnessFeatures -> RandomnessFeatures -> Bool
== :: RandomnessFeatures -> RandomnessFeatures -> Bool
$c/= :: RandomnessFeatures -> RandomnessFeatures -> Bool
/= :: RandomnessFeatures -> RandomnessFeatures -> Bool
Eq, Eq RandomnessFeatures
Eq RandomnessFeatures =>
(RandomnessFeatures -> RandomnessFeatures -> Ordering)
-> (RandomnessFeatures -> RandomnessFeatures -> Bool)
-> (RandomnessFeatures -> RandomnessFeatures -> Bool)
-> (RandomnessFeatures -> RandomnessFeatures -> Bool)
-> (RandomnessFeatures -> RandomnessFeatures -> Bool)
-> (RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures)
-> (RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures)
-> Ord RandomnessFeatures
RandomnessFeatures -> RandomnessFeatures -> Bool
RandomnessFeatures -> RandomnessFeatures -> Ordering
RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RandomnessFeatures -> RandomnessFeatures -> Ordering
compare :: RandomnessFeatures -> RandomnessFeatures -> Ordering
$c< :: RandomnessFeatures -> RandomnessFeatures -> Bool
< :: RandomnessFeatures -> RandomnessFeatures -> Bool
$c<= :: RandomnessFeatures -> RandomnessFeatures -> Bool
<= :: RandomnessFeatures -> RandomnessFeatures -> Bool
$c> :: RandomnessFeatures -> RandomnessFeatures -> Bool
> :: RandomnessFeatures -> RandomnessFeatures -> Bool
$c>= :: RandomnessFeatures -> RandomnessFeatures -> Bool
>= :: RandomnessFeatures -> RandomnessFeatures -> Bool
$cmax :: RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures
max :: RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures
$cmin :: RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures
min :: RandomnessFeatures -> RandomnessFeatures -> RandomnessFeatures
Ord, ReadPrec [RandomnessFeatures]
ReadPrec RandomnessFeatures
Int -> ReadS RandomnessFeatures
ReadS [RandomnessFeatures]
(Int -> ReadS RandomnessFeatures)
-> ReadS [RandomnessFeatures]
-> ReadPrec RandomnessFeatures
-> ReadPrec [RandomnessFeatures]
-> Read RandomnessFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RandomnessFeatures
readsPrec :: Int -> ReadS RandomnessFeatures
$creadList :: ReadS [RandomnessFeatures]
readList :: ReadS [RandomnessFeatures]
$creadPrec :: ReadPrec RandomnessFeatures
readPrec :: ReadPrec RandomnessFeatures
$creadListPrec :: ReadPrec [RandomnessFeatures]
readListPrec :: ReadPrec [RandomnessFeatures]
Read, Int -> RandomnessFeatures -> ShowS
[RandomnessFeatures] -> ShowS
RandomnessFeatures -> String
(Int -> RandomnessFeatures -> ShowS)
-> (RandomnessFeatures -> String)
-> ([RandomnessFeatures] -> ShowS)
-> Show RandomnessFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RandomnessFeatures -> ShowS
showsPrec :: Int -> RandomnessFeatures -> ShowS
$cshow :: RandomnessFeatures -> String
show :: RandomnessFeatures -> String
$cshowList :: [RandomnessFeatures] -> ShowS
showList :: [RandomnessFeatures] -> ShowS
Show)
_RandomnessFeatures :: Name
_RandomnessFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.RandomnessFeatures")
_RandomnessFeatures_rand :: Name
_RandomnessFeatures_rand = (String -> Name
Core.Name String
"rand")
_RandomnessFeatures_randomUUID :: Name
_RandomnessFeatures_randomUUID = (String -> Name
Core.Name String
"randomUUID")
data RangeLiteralFeatures =
RangeLiteralFeatures {
RangeLiteralFeatures -> Bool
rangeLiteralFeaturesBounds :: Bool,
RangeLiteralFeatures -> Bool
rangeLiteralFeaturesExactRange :: Bool,
RangeLiteralFeatures -> Bool
rangeLiteralFeaturesLowerBound :: Bool,
RangeLiteralFeatures -> Bool
rangeLiteralFeaturesStarRange :: Bool,
RangeLiteralFeatures -> Bool
rangeLiteralFeaturesUpperBound :: Bool}
deriving (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
(RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> Eq RangeLiteralFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
== :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
$c/= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
/= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
Eq, Eq RangeLiteralFeatures
Eq RangeLiteralFeatures =>
(RangeLiteralFeatures -> RangeLiteralFeatures -> Ordering)
-> (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> (RangeLiteralFeatures -> RangeLiteralFeatures -> Bool)
-> (RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures)
-> (RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures)
-> Ord RangeLiteralFeatures
RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
RangeLiteralFeatures -> RangeLiteralFeatures -> Ordering
RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RangeLiteralFeatures -> RangeLiteralFeatures -> Ordering
compare :: RangeLiteralFeatures -> RangeLiteralFeatures -> Ordering
$c< :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
< :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
$c<= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
<= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
$c> :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
> :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
$c>= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
>= :: RangeLiteralFeatures -> RangeLiteralFeatures -> Bool
$cmax :: RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures
max :: RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures
$cmin :: RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures
min :: RangeLiteralFeatures
-> RangeLiteralFeatures -> RangeLiteralFeatures
Ord, ReadPrec [RangeLiteralFeatures]
ReadPrec RangeLiteralFeatures
Int -> ReadS RangeLiteralFeatures
ReadS [RangeLiteralFeatures]
(Int -> ReadS RangeLiteralFeatures)
-> ReadS [RangeLiteralFeatures]
-> ReadPrec RangeLiteralFeatures
-> ReadPrec [RangeLiteralFeatures]
-> Read RangeLiteralFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RangeLiteralFeatures
readsPrec :: Int -> ReadS RangeLiteralFeatures
$creadList :: ReadS [RangeLiteralFeatures]
readList :: ReadS [RangeLiteralFeatures]
$creadPrec :: ReadPrec RangeLiteralFeatures
readPrec :: ReadPrec RangeLiteralFeatures
$creadListPrec :: ReadPrec [RangeLiteralFeatures]
readListPrec :: ReadPrec [RangeLiteralFeatures]
Read, Int -> RangeLiteralFeatures -> ShowS
[RangeLiteralFeatures] -> ShowS
RangeLiteralFeatures -> String
(Int -> RangeLiteralFeatures -> ShowS)
-> (RangeLiteralFeatures -> String)
-> ([RangeLiteralFeatures] -> ShowS)
-> Show RangeLiteralFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RangeLiteralFeatures -> ShowS
showsPrec :: Int -> RangeLiteralFeatures -> ShowS
$cshow :: RangeLiteralFeatures -> String
show :: RangeLiteralFeatures -> String
$cshowList :: [RangeLiteralFeatures] -> ShowS
showList :: [RangeLiteralFeatures] -> ShowS
Show)
_RangeLiteralFeatures :: Name
_RangeLiteralFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.RangeLiteralFeatures")
_RangeLiteralFeatures_bounds :: Name
_RangeLiteralFeatures_bounds = (String -> Name
Core.Name String
"bounds")
_RangeLiteralFeatures_exactRange :: Name
_RangeLiteralFeatures_exactRange = (String -> Name
Core.Name String
"exactRange")
_RangeLiteralFeatures_lowerBound :: Name
_RangeLiteralFeatures_lowerBound = (String -> Name
Core.Name String
"lowerBound")
_RangeLiteralFeatures_starRange :: Name
_RangeLiteralFeatures_starRange = (String -> Name
Core.Name String
"starRange")
_RangeLiteralFeatures_upperBound :: Name
_RangeLiteralFeatures_upperBound = (String -> Name
Core.Name String
"upperBound")
data ReadingFeatures =
ReadingFeatures {
ReadingFeatures -> Bool
readingFeaturesUnion :: Bool,
ReadingFeatures -> Bool
readingFeaturesUnionAll :: Bool,
ReadingFeatures -> Bool
readingFeaturesUnwind :: Bool}
deriving (ReadingFeatures -> ReadingFeatures -> Bool
(ReadingFeatures -> ReadingFeatures -> Bool)
-> (ReadingFeatures -> ReadingFeatures -> Bool)
-> Eq ReadingFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReadingFeatures -> ReadingFeatures -> Bool
== :: ReadingFeatures -> ReadingFeatures -> Bool
$c/= :: ReadingFeatures -> ReadingFeatures -> Bool
/= :: ReadingFeatures -> ReadingFeatures -> Bool
Eq, Eq ReadingFeatures
Eq ReadingFeatures =>
(ReadingFeatures -> ReadingFeatures -> Ordering)
-> (ReadingFeatures -> ReadingFeatures -> Bool)
-> (ReadingFeatures -> ReadingFeatures -> Bool)
-> (ReadingFeatures -> ReadingFeatures -> Bool)
-> (ReadingFeatures -> ReadingFeatures -> Bool)
-> (ReadingFeatures -> ReadingFeatures -> ReadingFeatures)
-> (ReadingFeatures -> ReadingFeatures -> ReadingFeatures)
-> Ord ReadingFeatures
ReadingFeatures -> ReadingFeatures -> Bool
ReadingFeatures -> ReadingFeatures -> Ordering
ReadingFeatures -> ReadingFeatures -> ReadingFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ReadingFeatures -> ReadingFeatures -> Ordering
compare :: ReadingFeatures -> ReadingFeatures -> Ordering
$c< :: ReadingFeatures -> ReadingFeatures -> Bool
< :: ReadingFeatures -> ReadingFeatures -> Bool
$c<= :: ReadingFeatures -> ReadingFeatures -> Bool
<= :: ReadingFeatures -> ReadingFeatures -> Bool
$c> :: ReadingFeatures -> ReadingFeatures -> Bool
> :: ReadingFeatures -> ReadingFeatures -> Bool
$c>= :: ReadingFeatures -> ReadingFeatures -> Bool
>= :: ReadingFeatures -> ReadingFeatures -> Bool
$cmax :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures
max :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures
$cmin :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures
min :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures
Ord, ReadPrec [ReadingFeatures]
ReadPrec ReadingFeatures
Int -> ReadS ReadingFeatures
ReadS [ReadingFeatures]
(Int -> ReadS ReadingFeatures)
-> ReadS [ReadingFeatures]
-> ReadPrec ReadingFeatures
-> ReadPrec [ReadingFeatures]
-> Read ReadingFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ReadingFeatures
readsPrec :: Int -> ReadS ReadingFeatures
$creadList :: ReadS [ReadingFeatures]
readList :: ReadS [ReadingFeatures]
$creadPrec :: ReadPrec ReadingFeatures
readPrec :: ReadPrec ReadingFeatures
$creadListPrec :: ReadPrec [ReadingFeatures]
readListPrec :: ReadPrec [ReadingFeatures]
Read, Int -> ReadingFeatures -> ShowS
[ReadingFeatures] -> ShowS
ReadingFeatures -> String
(Int -> ReadingFeatures -> ShowS)
-> (ReadingFeatures -> String)
-> ([ReadingFeatures] -> ShowS)
-> Show ReadingFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReadingFeatures -> ShowS
showsPrec :: Int -> ReadingFeatures -> ShowS
$cshow :: ReadingFeatures -> String
show :: ReadingFeatures -> String
$cshowList :: [ReadingFeatures] -> ShowS
showList :: [ReadingFeatures] -> ShowS
Show)
_ReadingFeatures :: Name
_ReadingFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.ReadingFeatures")
_ReadingFeatures_union :: Name
_ReadingFeatures_union = (String -> Name
Core.Name String
"union")
_ReadingFeatures_unionAll :: Name
_ReadingFeatures_unionAll = (String -> Name
Core.Name String
"unionAll")
_ReadingFeatures_unwind :: Name
_ReadingFeatures_unwind = (String -> Name
Core.Name String
"unwind")
data RelationshipDirectionFeatures =
RelationshipDirectionFeatures {
RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesBoth :: Bool,
RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesLeft :: Bool,
RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesNeither :: Bool,
RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesRight :: Bool}
deriving (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
(RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> Eq RelationshipDirectionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
== :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
$c/= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
/= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
Eq, Eq RelationshipDirectionFeatures
Eq RelationshipDirectionFeatures =>
(RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Ordering)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures)
-> (RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures)
-> Ord RelationshipDirectionFeatures
RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Ordering
RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Ordering
compare :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Ordering
$c< :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
< :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
$c<= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
<= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
$c> :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
> :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
$c>= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
>= :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> Bool
$cmax :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures
max :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures
$cmin :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures
min :: RelationshipDirectionFeatures
-> RelationshipDirectionFeatures -> RelationshipDirectionFeatures
Ord, ReadPrec [RelationshipDirectionFeatures]
ReadPrec RelationshipDirectionFeatures
Int -> ReadS RelationshipDirectionFeatures
ReadS [RelationshipDirectionFeatures]
(Int -> ReadS RelationshipDirectionFeatures)
-> ReadS [RelationshipDirectionFeatures]
-> ReadPrec RelationshipDirectionFeatures
-> ReadPrec [RelationshipDirectionFeatures]
-> Read RelationshipDirectionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationshipDirectionFeatures
readsPrec :: Int -> ReadS RelationshipDirectionFeatures
$creadList :: ReadS [RelationshipDirectionFeatures]
readList :: ReadS [RelationshipDirectionFeatures]
$creadPrec :: ReadPrec RelationshipDirectionFeatures
readPrec :: ReadPrec RelationshipDirectionFeatures
$creadListPrec :: ReadPrec [RelationshipDirectionFeatures]
readListPrec :: ReadPrec [RelationshipDirectionFeatures]
Read, Int -> RelationshipDirectionFeatures -> ShowS
[RelationshipDirectionFeatures] -> ShowS
RelationshipDirectionFeatures -> String
(Int -> RelationshipDirectionFeatures -> ShowS)
-> (RelationshipDirectionFeatures -> String)
-> ([RelationshipDirectionFeatures] -> ShowS)
-> Show RelationshipDirectionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RelationshipDirectionFeatures -> ShowS
showsPrec :: Int -> RelationshipDirectionFeatures -> ShowS
$cshow :: RelationshipDirectionFeatures -> String
show :: RelationshipDirectionFeatures -> String
$cshowList :: [RelationshipDirectionFeatures] -> ShowS
showList :: [RelationshipDirectionFeatures] -> ShowS
Show)
_RelationshipDirectionFeatures :: Name
_RelationshipDirectionFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.RelationshipDirectionFeatures")
_RelationshipDirectionFeatures_both :: Name
_RelationshipDirectionFeatures_both = (String -> Name
Core.Name String
"both")
_RelationshipDirectionFeatures_left :: Name
_RelationshipDirectionFeatures_left = (String -> Name
Core.Name String
"left")
_RelationshipDirectionFeatures_neither :: Name
_RelationshipDirectionFeatures_neither = (String -> Name
Core.Name String
"neither")
_RelationshipDirectionFeatures_right :: Name
_RelationshipDirectionFeatures_right = (String -> Name
Core.Name String
"right")
data RelationshipPatternFeatures =
RelationshipPatternFeatures {
RelationshipPatternFeatures -> Bool
relationshipPatternFeaturesMultipleTypes :: Bool,
RelationshipPatternFeatures -> Bool
relationshipPatternFeaturesVariableRelationship :: Bool,
RelationshipPatternFeatures -> Bool
relationshipPatternFeaturesWildcardType :: Bool}
deriving (RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
(RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> Eq RelationshipPatternFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
== :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
$c/= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
/= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
Eq, Eq RelationshipPatternFeatures
Eq RelationshipPatternFeatures =>
(RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Ordering)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Bool)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures)
-> (RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures)
-> Ord RelationshipPatternFeatures
RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Ordering
RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Ordering
compare :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> Ordering
$c< :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
< :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
$c<= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
<= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
$c> :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
> :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
$c>= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
>= :: RelationshipPatternFeatures -> RelationshipPatternFeatures -> Bool
$cmax :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures
max :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures
$cmin :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures
min :: RelationshipPatternFeatures
-> RelationshipPatternFeatures -> RelationshipPatternFeatures
Ord, ReadPrec [RelationshipPatternFeatures]
ReadPrec RelationshipPatternFeatures
Int -> ReadS RelationshipPatternFeatures
ReadS [RelationshipPatternFeatures]
(Int -> ReadS RelationshipPatternFeatures)
-> ReadS [RelationshipPatternFeatures]
-> ReadPrec RelationshipPatternFeatures
-> ReadPrec [RelationshipPatternFeatures]
-> Read RelationshipPatternFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationshipPatternFeatures
readsPrec :: Int -> ReadS RelationshipPatternFeatures
$creadList :: ReadS [RelationshipPatternFeatures]
readList :: ReadS [RelationshipPatternFeatures]
$creadPrec :: ReadPrec RelationshipPatternFeatures
readPrec :: ReadPrec RelationshipPatternFeatures
$creadListPrec :: ReadPrec [RelationshipPatternFeatures]
readListPrec :: ReadPrec [RelationshipPatternFeatures]
Read, Int -> RelationshipPatternFeatures -> ShowS
[RelationshipPatternFeatures] -> ShowS
RelationshipPatternFeatures -> String
(Int -> RelationshipPatternFeatures -> ShowS)
-> (RelationshipPatternFeatures -> String)
-> ([RelationshipPatternFeatures] -> ShowS)
-> Show RelationshipPatternFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RelationshipPatternFeatures -> ShowS
showsPrec :: Int -> RelationshipPatternFeatures -> ShowS
$cshow :: RelationshipPatternFeatures -> String
show :: RelationshipPatternFeatures -> String
$cshowList :: [RelationshipPatternFeatures] -> ShowS
showList :: [RelationshipPatternFeatures] -> ShowS
Show)
_RelationshipPatternFeatures :: Name
_RelationshipPatternFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.RelationshipPatternFeatures")
_RelationshipPatternFeatures_multipleTypes :: Name
_RelationshipPatternFeatures_multipleTypes = (String -> Name
Core.Name String
"multipleTypes")
_RelationshipPatternFeatures_variableRelationship :: Name
_RelationshipPatternFeatures_variableRelationship = (String -> Name
Core.Name String
"variableRelationship")
_RelationshipPatternFeatures_wildcardType :: Name
_RelationshipPatternFeatures_wildcardType = (String -> Name
Core.Name String
"wildcardType")
data RemoveFeatures =
RemoveFeatures {
RemoveFeatures -> Bool
removeFeaturesByLabel :: Bool,
RemoveFeatures -> Bool
removeFeaturesByProperty :: Bool}
deriving (RemoveFeatures -> RemoveFeatures -> Bool
(RemoveFeatures -> RemoveFeatures -> Bool)
-> (RemoveFeatures -> RemoveFeatures -> Bool) -> Eq RemoveFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RemoveFeatures -> RemoveFeatures -> Bool
== :: RemoveFeatures -> RemoveFeatures -> Bool
$c/= :: RemoveFeatures -> RemoveFeatures -> Bool
/= :: RemoveFeatures -> RemoveFeatures -> Bool
Eq, Eq RemoveFeatures
Eq RemoveFeatures =>
(RemoveFeatures -> RemoveFeatures -> Ordering)
-> (RemoveFeatures -> RemoveFeatures -> Bool)
-> (RemoveFeatures -> RemoveFeatures -> Bool)
-> (RemoveFeatures -> RemoveFeatures -> Bool)
-> (RemoveFeatures -> RemoveFeatures -> Bool)
-> (RemoveFeatures -> RemoveFeatures -> RemoveFeatures)
-> (RemoveFeatures -> RemoveFeatures -> RemoveFeatures)
-> Ord RemoveFeatures
RemoveFeatures -> RemoveFeatures -> Bool
RemoveFeatures -> RemoveFeatures -> Ordering
RemoveFeatures -> RemoveFeatures -> RemoveFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RemoveFeatures -> RemoveFeatures -> Ordering
compare :: RemoveFeatures -> RemoveFeatures -> Ordering
$c< :: RemoveFeatures -> RemoveFeatures -> Bool
< :: RemoveFeatures -> RemoveFeatures -> Bool
$c<= :: RemoveFeatures -> RemoveFeatures -> Bool
<= :: RemoveFeatures -> RemoveFeatures -> Bool
$c> :: RemoveFeatures -> RemoveFeatures -> Bool
> :: RemoveFeatures -> RemoveFeatures -> Bool
$c>= :: RemoveFeatures -> RemoveFeatures -> Bool
>= :: RemoveFeatures -> RemoveFeatures -> Bool
$cmax :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures
max :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures
$cmin :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures
min :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures
Ord, ReadPrec [RemoveFeatures]
ReadPrec RemoveFeatures
Int -> ReadS RemoveFeatures
ReadS [RemoveFeatures]
(Int -> ReadS RemoveFeatures)
-> ReadS [RemoveFeatures]
-> ReadPrec RemoveFeatures
-> ReadPrec [RemoveFeatures]
-> Read RemoveFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RemoveFeatures
readsPrec :: Int -> ReadS RemoveFeatures
$creadList :: ReadS [RemoveFeatures]
readList :: ReadS [RemoveFeatures]
$creadPrec :: ReadPrec RemoveFeatures
readPrec :: ReadPrec RemoveFeatures
$creadListPrec :: ReadPrec [RemoveFeatures]
readListPrec :: ReadPrec [RemoveFeatures]
Read, Int -> RemoveFeatures -> ShowS
[RemoveFeatures] -> ShowS
RemoveFeatures -> String
(Int -> RemoveFeatures -> ShowS)
-> (RemoveFeatures -> String)
-> ([RemoveFeatures] -> ShowS)
-> Show RemoveFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RemoveFeatures -> ShowS
showsPrec :: Int -> RemoveFeatures -> ShowS
$cshow :: RemoveFeatures -> String
show :: RemoveFeatures -> String
$cshowList :: [RemoveFeatures] -> ShowS
showList :: [RemoveFeatures] -> ShowS
Show)
_RemoveFeatures :: Name
_RemoveFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.RemoveFeatures")
_RemoveFeatures_byLabel :: Name
_RemoveFeatures_byLabel = (String -> Name
Core.Name String
"byLabel")
_RemoveFeatures_byProperty :: Name
_RemoveFeatures_byProperty = (String -> Name
Core.Name String
"byProperty")
data SchemaFeatures =
SchemaFeatures {
SchemaFeatures -> Bool
schemaFeaturesType :: Bool,
SchemaFeatures -> Bool
schemaFeaturesValueType :: Bool}
deriving (SchemaFeatures -> SchemaFeatures -> Bool
(SchemaFeatures -> SchemaFeatures -> Bool)
-> (SchemaFeatures -> SchemaFeatures -> Bool) -> Eq SchemaFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaFeatures -> SchemaFeatures -> Bool
== :: SchemaFeatures -> SchemaFeatures -> Bool
$c/= :: SchemaFeatures -> SchemaFeatures -> Bool
/= :: SchemaFeatures -> SchemaFeatures -> Bool
Eq, Eq SchemaFeatures
Eq SchemaFeatures =>
(SchemaFeatures -> SchemaFeatures -> Ordering)
-> (SchemaFeatures -> SchemaFeatures -> Bool)
-> (SchemaFeatures -> SchemaFeatures -> Bool)
-> (SchemaFeatures -> SchemaFeatures -> Bool)
-> (SchemaFeatures -> SchemaFeatures -> Bool)
-> (SchemaFeatures -> SchemaFeatures -> SchemaFeatures)
-> (SchemaFeatures -> SchemaFeatures -> SchemaFeatures)
-> Ord SchemaFeatures
SchemaFeatures -> SchemaFeatures -> Bool
SchemaFeatures -> SchemaFeatures -> Ordering
SchemaFeatures -> SchemaFeatures -> SchemaFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SchemaFeatures -> SchemaFeatures -> Ordering
compare :: SchemaFeatures -> SchemaFeatures -> Ordering
$c< :: SchemaFeatures -> SchemaFeatures -> Bool
< :: SchemaFeatures -> SchemaFeatures -> Bool
$c<= :: SchemaFeatures -> SchemaFeatures -> Bool
<= :: SchemaFeatures -> SchemaFeatures -> Bool
$c> :: SchemaFeatures -> SchemaFeatures -> Bool
> :: SchemaFeatures -> SchemaFeatures -> Bool
$c>= :: SchemaFeatures -> SchemaFeatures -> Bool
>= :: SchemaFeatures -> SchemaFeatures -> Bool
$cmax :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures
max :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures
$cmin :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures
min :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures
Ord, ReadPrec [SchemaFeatures]
ReadPrec SchemaFeatures
Int -> ReadS SchemaFeatures
ReadS [SchemaFeatures]
(Int -> ReadS SchemaFeatures)
-> ReadS [SchemaFeatures]
-> ReadPrec SchemaFeatures
-> ReadPrec [SchemaFeatures]
-> Read SchemaFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaFeatures
readsPrec :: Int -> ReadS SchemaFeatures
$creadList :: ReadS [SchemaFeatures]
readList :: ReadS [SchemaFeatures]
$creadPrec :: ReadPrec SchemaFeatures
readPrec :: ReadPrec SchemaFeatures
$creadListPrec :: ReadPrec [SchemaFeatures]
readListPrec :: ReadPrec [SchemaFeatures]
Read, Int -> SchemaFeatures -> ShowS
[SchemaFeatures] -> ShowS
SchemaFeatures -> String
(Int -> SchemaFeatures -> ShowS)
-> (SchemaFeatures -> String)
-> ([SchemaFeatures] -> ShowS)
-> Show SchemaFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchemaFeatures -> ShowS
showsPrec :: Int -> SchemaFeatures -> ShowS
$cshow :: SchemaFeatures -> String
show :: SchemaFeatures -> String
$cshowList :: [SchemaFeatures] -> ShowS
showList :: [SchemaFeatures] -> ShowS
Show)
_SchemaFeatures :: Name
_SchemaFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.SchemaFeatures")
_SchemaFeatures_type :: Name
_SchemaFeatures_type = (String -> Name
Core.Name String
"type")
_SchemaFeatures_valueType :: Name
_SchemaFeatures_valueType = (String -> Name
Core.Name String
"valueType")
data SetFeatures =
SetFeatures {
SetFeatures -> Bool
setFeaturesPropertyEquals :: Bool,
SetFeatures -> Bool
setFeaturesVariableEquals :: Bool,
SetFeatures -> Bool
setFeaturesVariablePlusEquals :: Bool,
SetFeatures -> Bool
setFeaturesVariableWithNodeLabels :: Bool}
deriving (SetFeatures -> SetFeatures -> Bool
(SetFeatures -> SetFeatures -> Bool)
-> (SetFeatures -> SetFeatures -> Bool) -> Eq SetFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetFeatures -> SetFeatures -> Bool
== :: SetFeatures -> SetFeatures -> Bool
$c/= :: SetFeatures -> SetFeatures -> Bool
/= :: SetFeatures -> SetFeatures -> Bool
Eq, Eq SetFeatures
Eq SetFeatures =>
(SetFeatures -> SetFeatures -> Ordering)
-> (SetFeatures -> SetFeatures -> Bool)
-> (SetFeatures -> SetFeatures -> Bool)
-> (SetFeatures -> SetFeatures -> Bool)
-> (SetFeatures -> SetFeatures -> Bool)
-> (SetFeatures -> SetFeatures -> SetFeatures)
-> (SetFeatures -> SetFeatures -> SetFeatures)
-> Ord SetFeatures
SetFeatures -> SetFeatures -> Bool
SetFeatures -> SetFeatures -> Ordering
SetFeatures -> SetFeatures -> SetFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SetFeatures -> SetFeatures -> Ordering
compare :: SetFeatures -> SetFeatures -> Ordering
$c< :: SetFeatures -> SetFeatures -> Bool
< :: SetFeatures -> SetFeatures -> Bool
$c<= :: SetFeatures -> SetFeatures -> Bool
<= :: SetFeatures -> SetFeatures -> Bool
$c> :: SetFeatures -> SetFeatures -> Bool
> :: SetFeatures -> SetFeatures -> Bool
$c>= :: SetFeatures -> SetFeatures -> Bool
>= :: SetFeatures -> SetFeatures -> Bool
$cmax :: SetFeatures -> SetFeatures -> SetFeatures
max :: SetFeatures -> SetFeatures -> SetFeatures
$cmin :: SetFeatures -> SetFeatures -> SetFeatures
min :: SetFeatures -> SetFeatures -> SetFeatures
Ord, ReadPrec [SetFeatures]
ReadPrec SetFeatures
Int -> ReadS SetFeatures
ReadS [SetFeatures]
(Int -> ReadS SetFeatures)
-> ReadS [SetFeatures]
-> ReadPrec SetFeatures
-> ReadPrec [SetFeatures]
-> Read SetFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SetFeatures
readsPrec :: Int -> ReadS SetFeatures
$creadList :: ReadS [SetFeatures]
readList :: ReadS [SetFeatures]
$creadPrec :: ReadPrec SetFeatures
readPrec :: ReadPrec SetFeatures
$creadListPrec :: ReadPrec [SetFeatures]
readListPrec :: ReadPrec [SetFeatures]
Read, Int -> SetFeatures -> ShowS
[SetFeatures] -> ShowS
SetFeatures -> String
(Int -> SetFeatures -> ShowS)
-> (SetFeatures -> String)
-> ([SetFeatures] -> ShowS)
-> Show SetFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetFeatures -> ShowS
showsPrec :: Int -> SetFeatures -> ShowS
$cshow :: SetFeatures -> String
show :: SetFeatures -> String
$cshowList :: [SetFeatures] -> ShowS
showList :: [SetFeatures] -> ShowS
Show)
_SetFeatures :: Name
_SetFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.SetFeatures")
_SetFeatures_propertyEquals :: Name
_SetFeatures_propertyEquals = (String -> Name
Core.Name String
"propertyEquals")
_SetFeatures_variableEquals :: Name
_SetFeatures_variableEquals = (String -> Name
Core.Name String
"variableEquals")
_SetFeatures_variablePlusEquals :: Name
_SetFeatures_variablePlusEquals = (String -> Name
Core.Name String
"variablePlusEquals")
_SetFeatures_variableWithNodeLabels :: Name
_SetFeatures_variableWithNodeLabels = (String -> Name
Core.Name String
"variableWithNodeLabels")
data StringFeatures =
StringFeatures {
StringFeatures -> Bool
stringFeaturesChar_length :: Bool,
StringFeatures -> Bool
stringFeaturesCharacter_length :: Bool,
StringFeatures -> Bool
stringFeaturesContains :: Bool,
StringFeatures -> Bool
stringFeaturesEndsWith :: Bool,
StringFeatures -> Bool
stringFeaturesIn :: Bool,
StringFeatures -> Bool
stringFeaturesStartsWith :: Bool,
StringFeatures -> Bool
stringFeaturesToBoolean :: Bool,
StringFeatures -> Bool
stringFeaturesToBooleanOrNull :: Bool,
StringFeatures -> Bool
stringFeaturesToFloat :: Bool,
StringFeatures -> Bool
stringFeaturesToFloatOrNull :: Bool,
StringFeatures -> Bool
stringFeaturesToInteger :: Bool,
StringFeatures -> Bool
stringFeaturesToIntegerOrNull :: Bool}
deriving (StringFeatures -> StringFeatures -> Bool
(StringFeatures -> StringFeatures -> Bool)
-> (StringFeatures -> StringFeatures -> Bool) -> Eq StringFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StringFeatures -> StringFeatures -> Bool
== :: StringFeatures -> StringFeatures -> Bool
$c/= :: StringFeatures -> StringFeatures -> Bool
/= :: StringFeatures -> StringFeatures -> Bool
Eq, Eq StringFeatures
Eq StringFeatures =>
(StringFeatures -> StringFeatures -> Ordering)
-> (StringFeatures -> StringFeatures -> Bool)
-> (StringFeatures -> StringFeatures -> Bool)
-> (StringFeatures -> StringFeatures -> Bool)
-> (StringFeatures -> StringFeatures -> Bool)
-> (StringFeatures -> StringFeatures -> StringFeatures)
-> (StringFeatures -> StringFeatures -> StringFeatures)
-> Ord StringFeatures
StringFeatures -> StringFeatures -> Bool
StringFeatures -> StringFeatures -> Ordering
StringFeatures -> StringFeatures -> StringFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StringFeatures -> StringFeatures -> Ordering
compare :: StringFeatures -> StringFeatures -> Ordering
$c< :: StringFeatures -> StringFeatures -> Bool
< :: StringFeatures -> StringFeatures -> Bool
$c<= :: StringFeatures -> StringFeatures -> Bool
<= :: StringFeatures -> StringFeatures -> Bool
$c> :: StringFeatures -> StringFeatures -> Bool
> :: StringFeatures -> StringFeatures -> Bool
$c>= :: StringFeatures -> StringFeatures -> Bool
>= :: StringFeatures -> StringFeatures -> Bool
$cmax :: StringFeatures -> StringFeatures -> StringFeatures
max :: StringFeatures -> StringFeatures -> StringFeatures
$cmin :: StringFeatures -> StringFeatures -> StringFeatures
min :: StringFeatures -> StringFeatures -> StringFeatures
Ord, ReadPrec [StringFeatures]
ReadPrec StringFeatures
Int -> ReadS StringFeatures
ReadS [StringFeatures]
(Int -> ReadS StringFeatures)
-> ReadS [StringFeatures]
-> ReadPrec StringFeatures
-> ReadPrec [StringFeatures]
-> Read StringFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StringFeatures
readsPrec :: Int -> ReadS StringFeatures
$creadList :: ReadS [StringFeatures]
readList :: ReadS [StringFeatures]
$creadPrec :: ReadPrec StringFeatures
readPrec :: ReadPrec StringFeatures
$creadListPrec :: ReadPrec [StringFeatures]
readListPrec :: ReadPrec [StringFeatures]
Read, Int -> StringFeatures -> ShowS
[StringFeatures] -> ShowS
StringFeatures -> String
(Int -> StringFeatures -> ShowS)
-> (StringFeatures -> String)
-> ([StringFeatures] -> ShowS)
-> Show StringFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StringFeatures -> ShowS
showsPrec :: Int -> StringFeatures -> ShowS
$cshow :: StringFeatures -> String
show :: StringFeatures -> String
$cshowList :: [StringFeatures] -> ShowS
showList :: [StringFeatures] -> ShowS
Show)
_StringFeatures :: Name
_StringFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.StringFeatures")
_StringFeatures_char_length :: Name
_StringFeatures_char_length = (String -> Name
Core.Name String
"char_length")
_StringFeatures_character_length :: Name
_StringFeatures_character_length = (String -> Name
Core.Name String
"character_length")
_StringFeatures_contains :: Name
_StringFeatures_contains = (String -> Name
Core.Name String
"contains")
_StringFeatures_endsWith :: Name
_StringFeatures_endsWith = (String -> Name
Core.Name String
"endsWith")
_StringFeatures_in :: Name
_StringFeatures_in = (String -> Name
Core.Name String
"in")
_StringFeatures_startsWith :: Name
_StringFeatures_startsWith = (String -> Name
Core.Name String
"startsWith")
_StringFeatures_toBoolean :: Name
_StringFeatures_toBoolean = (String -> Name
Core.Name String
"toBoolean")
_StringFeatures_toBooleanOrNull :: Name
_StringFeatures_toBooleanOrNull = (String -> Name
Core.Name String
"toBooleanOrNull")
_StringFeatures_toFloat :: Name
_StringFeatures_toFloat = (String -> Name
Core.Name String
"toFloat")
_StringFeatures_toFloatOrNull :: Name
_StringFeatures_toFloatOrNull = (String -> Name
Core.Name String
"toFloatOrNull")
_StringFeatures_toInteger :: Name
_StringFeatures_toInteger = (String -> Name
Core.Name String
"toInteger")
_StringFeatures_toIntegerOrNull :: Name
_StringFeatures_toIntegerOrNull = (String -> Name
Core.Name String
"toIntegerOrNull")
data UpdatingFeatures =
UpdatingFeatures {
UpdatingFeatures -> Bool
updatingFeaturesCreate :: Bool,
UpdatingFeatures -> Bool
updatingFeaturesSet :: Bool,
UpdatingFeatures -> Bool
updatingFeaturesWith :: Bool}
deriving (UpdatingFeatures -> UpdatingFeatures -> Bool
(UpdatingFeatures -> UpdatingFeatures -> Bool)
-> (UpdatingFeatures -> UpdatingFeatures -> Bool)
-> Eq UpdatingFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdatingFeatures -> UpdatingFeatures -> Bool
== :: UpdatingFeatures -> UpdatingFeatures -> Bool
$c/= :: UpdatingFeatures -> UpdatingFeatures -> Bool
/= :: UpdatingFeatures -> UpdatingFeatures -> Bool
Eq, Eq UpdatingFeatures
Eq UpdatingFeatures =>
(UpdatingFeatures -> UpdatingFeatures -> Ordering)
-> (UpdatingFeatures -> UpdatingFeatures -> Bool)
-> (UpdatingFeatures -> UpdatingFeatures -> Bool)
-> (UpdatingFeatures -> UpdatingFeatures -> Bool)
-> (UpdatingFeatures -> UpdatingFeatures -> Bool)
-> (UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures)
-> (UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures)
-> Ord UpdatingFeatures
UpdatingFeatures -> UpdatingFeatures -> Bool
UpdatingFeatures -> UpdatingFeatures -> Ordering
UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UpdatingFeatures -> UpdatingFeatures -> Ordering
compare :: UpdatingFeatures -> UpdatingFeatures -> Ordering
$c< :: UpdatingFeatures -> UpdatingFeatures -> Bool
< :: UpdatingFeatures -> UpdatingFeatures -> Bool
$c<= :: UpdatingFeatures -> UpdatingFeatures -> Bool
<= :: UpdatingFeatures -> UpdatingFeatures -> Bool
$c> :: UpdatingFeatures -> UpdatingFeatures -> Bool
> :: UpdatingFeatures -> UpdatingFeatures -> Bool
$c>= :: UpdatingFeatures -> UpdatingFeatures -> Bool
>= :: UpdatingFeatures -> UpdatingFeatures -> Bool
$cmax :: UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures
max :: UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures
$cmin :: UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures
min :: UpdatingFeatures -> UpdatingFeatures -> UpdatingFeatures
Ord, ReadPrec [UpdatingFeatures]
ReadPrec UpdatingFeatures
Int -> ReadS UpdatingFeatures
ReadS [UpdatingFeatures]
(Int -> ReadS UpdatingFeatures)
-> ReadS [UpdatingFeatures]
-> ReadPrec UpdatingFeatures
-> ReadPrec [UpdatingFeatures]
-> Read UpdatingFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UpdatingFeatures
readsPrec :: Int -> ReadS UpdatingFeatures
$creadList :: ReadS [UpdatingFeatures]
readList :: ReadS [UpdatingFeatures]
$creadPrec :: ReadPrec UpdatingFeatures
readPrec :: ReadPrec UpdatingFeatures
$creadListPrec :: ReadPrec [UpdatingFeatures]
readListPrec :: ReadPrec [UpdatingFeatures]
Read, Int -> UpdatingFeatures -> ShowS
[UpdatingFeatures] -> ShowS
UpdatingFeatures -> String
(Int -> UpdatingFeatures -> ShowS)
-> (UpdatingFeatures -> String)
-> ([UpdatingFeatures] -> ShowS)
-> Show UpdatingFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdatingFeatures -> ShowS
showsPrec :: Int -> UpdatingFeatures -> ShowS
$cshow :: UpdatingFeatures -> String
show :: UpdatingFeatures -> String
$cshowList :: [UpdatingFeatures] -> ShowS
showList :: [UpdatingFeatures] -> ShowS
Show)
_UpdatingFeatures :: Name
_UpdatingFeatures = (String -> Name
Core.Name String
"hydra/langs/cypher/features.UpdatingFeatures")
_UpdatingFeatures_create :: Name
_UpdatingFeatures_create = (String -> Name
Core.Name String
"create")
_UpdatingFeatures_set :: Name
_UpdatingFeatures_set = (String -> Name
Core.Name String
"set")
_UpdatingFeatures_with :: Name
_UpdatingFeatures_with = (String -> Name
Core.Name String
"with")