module Hydra.Ext.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 CypherFeatures =
CypherFeatures {
CypherFeatures -> ArithmeticFeatures
cypherFeaturesArithmetic :: ArithmeticFeatures,
CypherFeatures -> AtomFeatures
cypherFeaturesAtom :: AtomFeatures,
CypherFeatures -> ComparisonFeatures
cypherFeaturesComparison :: ComparisonFeatures,
CypherFeatures -> DeleteFeatures
cypherFeaturesDelete :: DeleteFeatures,
CypherFeatures -> FunctionFeatures
cypherFeaturesFunction :: FunctionFeatures,
CypherFeatures -> ListFeatures
cypherFeaturesList :: ListFeatures,
CypherFeatures -> LiteralFeatures
cypherFeaturesLiteral :: LiteralFeatures,
CypherFeatures -> LogicalFeatures
cypherFeaturesLogical :: LogicalFeatures,
CypherFeatures -> MatchFeatures
cypherFeaturesMatch :: MatchFeatures,
CypherFeatures -> MergeFeatures
cypherFeaturesMerge :: MergeFeatures,
CypherFeatures -> NodePatternFeatures
cypherFeaturesNodePattern :: NodePatternFeatures,
CypherFeatures -> NullFeatures
cypherFeaturesNull :: NullFeatures,
CypherFeatures -> PathFeatures
cypherFeaturesPath :: PathFeatures,
CypherFeatures -> ProcedureCallFeatures
cypherFeaturesProcedureCall :: ProcedureCallFeatures,
CypherFeatures -> ProjectionFeatures
cypherFeaturesProjection :: ProjectionFeatures,
CypherFeatures -> QuantifierFeatures
cypherFeaturesQuantifier :: QuantifierFeatures,
CypherFeatures -> RangeLiteralFeatures
cypherFeaturesRangeLiteral :: RangeLiteralFeatures,
CypherFeatures -> ReadingFeatures
cypherFeaturesReading :: ReadingFeatures,
CypherFeatures -> RelationshipDirectionFeatures
cypherFeaturesRelationshipDirection :: RelationshipDirectionFeatures,
CypherFeatures -> RelationshipPatternFeatures
cypherFeaturesRelationshipPattern :: RelationshipPatternFeatures,
CypherFeatures -> RemoveFeatures
cypherFeaturesRemove :: RemoveFeatures,
CypherFeatures -> SetFeatures
cypherFeaturesSet :: SetFeatures,
CypherFeatures -> StringFeatures
cypherFeaturesString :: StringFeatures,
CypherFeatures -> UpdatingFeatures
cypherFeaturesUpdating :: 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/ext/cypher/features.CypherFeatures")
_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_function :: Name
_CypherFeatures_function = (String -> Name
Core.Name String
"function")
_CypherFeatures_list :: Name
_CypherFeatures_list = (String -> Name
Core.Name String
"list")
_CypherFeatures_literal :: Name
_CypherFeatures_literal = (String -> Name
Core.Name String
"literal")
_CypherFeatures_logical :: Name
_CypherFeatures_logical = (String -> Name
Core.Name String
"logical")
_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_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_quantifier :: Name
_CypherFeatures_quantifier = (String -> Name
Core.Name String
"quantifier")
_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_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 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/ext/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 -> Bool
atomFeaturesParameter :: Bool,
AtomFeatures -> Bool
atomFeaturesPatternComprehension :: Bool,
AtomFeatures -> Bool
atomFeaturesPatternPredicate :: Bool,
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/ext/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_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_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}
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/ext/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")
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/ext/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 FunctionFeatures =
FunctionFeatures {
FunctionFeatures -> AggregateFunctionFeatures
functionFeaturesAggregateFunction :: AggregateFunctionFeatures,
FunctionFeatures -> DatabaseFunctionFeatures
functionFeaturesDatabaseFunction :: DatabaseFunctionFeatures,
FunctionFeatures -> GenAIFunctionFeatures
functionFeaturesGenAIFunction :: GenAIFunctionFeatures,
FunctionFeatures -> GraphFunctionFeatures
functionFeaturesGraphFunction :: GraphFunctionFeatures,
FunctionFeatures -> ListFunctionFeatures
functionFeaturesListFunction :: ListFunctionFeatures,
FunctionFeatures -> LoadCSVFunctionFeatures
functionFeaturesLoadCSVFunction :: LoadCSVFunctionFeatures,
FunctionFeatures -> LogarithmicFunctionFeatures
functionFeaturesLogarithmicFunction :: LogarithmicFunctionFeatures,
FunctionFeatures -> NumericFunctionFeatures
functionFeaturesNumericFunction :: NumericFunctionFeatures,
FunctionFeatures -> PredicateFunctionFeatures
functionFeaturesPredicateFunction :: PredicateFunctionFeatures,
FunctionFeatures -> ScalarFunctionFeatures
functionFeaturesScalarFunction :: ScalarFunctionFeatures,
FunctionFeatures -> SpatialFunctionFeatures
functionFeaturesSpatialFunction :: SpatialFunctionFeatures,
FunctionFeatures -> StringFunctionFeatures
functionFeaturesStringFunction :: StringFunctionFeatures,
FunctionFeatures -> TemporalDurationFunctionFeatures
functionFeaturesTemporalDurationFunction :: TemporalDurationFunctionFeatures,
FunctionFeatures -> TemporalInstantFunctionFeatures
functionFeaturesTemporalInstantFunction :: TemporalInstantFunctionFeatures,
FunctionFeatures -> TrigonometricFunctionFeatures
functionFeaturesTrigonometricFunction :: TrigonometricFunctionFeatures,
FunctionFeatures -> VectorFunctionFeatures
functionFeaturesVectorFunction :: VectorFunctionFeatures}
deriving (FunctionFeatures -> FunctionFeatures -> Bool
(FunctionFeatures -> FunctionFeatures -> Bool)
-> (FunctionFeatures -> FunctionFeatures -> Bool)
-> Eq FunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionFeatures -> FunctionFeatures -> Bool
== :: FunctionFeatures -> FunctionFeatures -> Bool
$c/= :: FunctionFeatures -> FunctionFeatures -> Bool
/= :: FunctionFeatures -> FunctionFeatures -> Bool
Eq, Eq FunctionFeatures
Eq FunctionFeatures =>
(FunctionFeatures -> FunctionFeatures -> Ordering)
-> (FunctionFeatures -> FunctionFeatures -> Bool)
-> (FunctionFeatures -> FunctionFeatures -> Bool)
-> (FunctionFeatures -> FunctionFeatures -> Bool)
-> (FunctionFeatures -> FunctionFeatures -> Bool)
-> (FunctionFeatures -> FunctionFeatures -> FunctionFeatures)
-> (FunctionFeatures -> FunctionFeatures -> FunctionFeatures)
-> Ord FunctionFeatures
FunctionFeatures -> FunctionFeatures -> Bool
FunctionFeatures -> FunctionFeatures -> Ordering
FunctionFeatures -> FunctionFeatures -> FunctionFeatures
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 :: FunctionFeatures -> FunctionFeatures -> Ordering
compare :: FunctionFeatures -> FunctionFeatures -> Ordering
$c< :: FunctionFeatures -> FunctionFeatures -> Bool
< :: FunctionFeatures -> FunctionFeatures -> Bool
$c<= :: FunctionFeatures -> FunctionFeatures -> Bool
<= :: FunctionFeatures -> FunctionFeatures -> Bool
$c> :: FunctionFeatures -> FunctionFeatures -> Bool
> :: FunctionFeatures -> FunctionFeatures -> Bool
$c>= :: FunctionFeatures -> FunctionFeatures -> Bool
>= :: FunctionFeatures -> FunctionFeatures -> Bool
$cmax :: FunctionFeatures -> FunctionFeatures -> FunctionFeatures
max :: FunctionFeatures -> FunctionFeatures -> FunctionFeatures
$cmin :: FunctionFeatures -> FunctionFeatures -> FunctionFeatures
min :: FunctionFeatures -> FunctionFeatures -> FunctionFeatures
Ord, ReadPrec [FunctionFeatures]
ReadPrec FunctionFeatures
Int -> ReadS FunctionFeatures
ReadS [FunctionFeatures]
(Int -> ReadS FunctionFeatures)
-> ReadS [FunctionFeatures]
-> ReadPrec FunctionFeatures
-> ReadPrec [FunctionFeatures]
-> Read FunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionFeatures
readsPrec :: Int -> ReadS FunctionFeatures
$creadList :: ReadS [FunctionFeatures]
readList :: ReadS [FunctionFeatures]
$creadPrec :: ReadPrec FunctionFeatures
readPrec :: ReadPrec FunctionFeatures
$creadListPrec :: ReadPrec [FunctionFeatures]
readListPrec :: ReadPrec [FunctionFeatures]
Read, Int -> FunctionFeatures -> ShowS
[FunctionFeatures] -> ShowS
FunctionFeatures -> String
(Int -> FunctionFeatures -> ShowS)
-> (FunctionFeatures -> String)
-> ([FunctionFeatures] -> ShowS)
-> Show FunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionFeatures -> ShowS
showsPrec :: Int -> FunctionFeatures -> ShowS
$cshow :: FunctionFeatures -> String
show :: FunctionFeatures -> String
$cshowList :: [FunctionFeatures] -> ShowS
showList :: [FunctionFeatures] -> ShowS
Show)
_FunctionFeatures :: Name
_FunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.FunctionFeatures")
_FunctionFeatures_aggregateFunction :: Name
_FunctionFeatures_aggregateFunction = (String -> Name
Core.Name String
"aggregateFunction")
_FunctionFeatures_databaseFunction :: Name
_FunctionFeatures_databaseFunction = (String -> Name
Core.Name String
"databaseFunction")
_FunctionFeatures_genAIFunction :: Name
_FunctionFeatures_genAIFunction = (String -> Name
Core.Name String
"genAIFunction")
_FunctionFeatures_graphFunction :: Name
_FunctionFeatures_graphFunction = (String -> Name
Core.Name String
"graphFunction")
_FunctionFeatures_listFunction :: Name
_FunctionFeatures_listFunction = (String -> Name
Core.Name String
"listFunction")
_FunctionFeatures_loadCSVFunction :: Name
_FunctionFeatures_loadCSVFunction = (String -> Name
Core.Name String
"loadCSVFunction")
_FunctionFeatures_logarithmicFunction :: Name
_FunctionFeatures_logarithmicFunction = (String -> Name
Core.Name String
"logarithmicFunction")
_FunctionFeatures_numericFunction :: Name
_FunctionFeatures_numericFunction = (String -> Name
Core.Name String
"numericFunction")
_FunctionFeatures_predicateFunction :: Name
_FunctionFeatures_predicateFunction = (String -> Name
Core.Name String
"predicateFunction")
_FunctionFeatures_scalarFunction :: Name
_FunctionFeatures_scalarFunction = (String -> Name
Core.Name String
"scalarFunction")
_FunctionFeatures_spatialFunction :: Name
_FunctionFeatures_spatialFunction = (String -> Name
Core.Name String
"spatialFunction")
_FunctionFeatures_stringFunction :: Name
_FunctionFeatures_stringFunction = (String -> Name
Core.Name String
"stringFunction")
_FunctionFeatures_temporalDurationFunction :: Name
_FunctionFeatures_temporalDurationFunction = (String -> Name
Core.Name String
"temporalDurationFunction")
_FunctionFeatures_temporalInstantFunction :: Name
_FunctionFeatures_temporalInstantFunction = (String -> Name
Core.Name String
"temporalInstantFunction")
_FunctionFeatures_trigonometricFunction :: Name
_FunctionFeatures_trigonometricFunction = (String -> Name
Core.Name String
"trigonometricFunction")
_FunctionFeatures_vectorFunction :: Name
_FunctionFeatures_vectorFunction = (String -> Name
Core.Name String
"vectorFunction")
data AggregateFunctionFeatures =
AggregateFunctionFeatures {
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesAvg :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesCollect :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesCount :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesMax :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesMin :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesPercentileCont :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesPercentileDisc :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesStdev :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesStdevp :: Bool,
AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesSum :: Bool}
deriving (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
(AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> Eq AggregateFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
== :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
$c/= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
/= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
Eq, Eq AggregateFunctionFeatures
Eq AggregateFunctionFeatures =>
(AggregateFunctionFeatures
-> AggregateFunctionFeatures -> Ordering)
-> (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> (AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool)
-> (AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures)
-> (AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures)
-> Ord AggregateFunctionFeatures
AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
AggregateFunctionFeatures -> AggregateFunctionFeatures -> Ordering
AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures
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 :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Ordering
compare :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Ordering
$c< :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
< :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
$c<= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
<= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
$c> :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
> :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
$c>= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
>= :: AggregateFunctionFeatures -> AggregateFunctionFeatures -> Bool
$cmax :: AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures
max :: AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures
$cmin :: AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures
min :: AggregateFunctionFeatures
-> AggregateFunctionFeatures -> AggregateFunctionFeatures
Ord, ReadPrec [AggregateFunctionFeatures]
ReadPrec AggregateFunctionFeatures
Int -> ReadS AggregateFunctionFeatures
ReadS [AggregateFunctionFeatures]
(Int -> ReadS AggregateFunctionFeatures)
-> ReadS [AggregateFunctionFeatures]
-> ReadPrec AggregateFunctionFeatures
-> ReadPrec [AggregateFunctionFeatures]
-> Read AggregateFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AggregateFunctionFeatures
readsPrec :: Int -> ReadS AggregateFunctionFeatures
$creadList :: ReadS [AggregateFunctionFeatures]
readList :: ReadS [AggregateFunctionFeatures]
$creadPrec :: ReadPrec AggregateFunctionFeatures
readPrec :: ReadPrec AggregateFunctionFeatures
$creadListPrec :: ReadPrec [AggregateFunctionFeatures]
readListPrec :: ReadPrec [AggregateFunctionFeatures]
Read, Int -> AggregateFunctionFeatures -> ShowS
[AggregateFunctionFeatures] -> ShowS
AggregateFunctionFeatures -> String
(Int -> AggregateFunctionFeatures -> ShowS)
-> (AggregateFunctionFeatures -> String)
-> ([AggregateFunctionFeatures] -> ShowS)
-> Show AggregateFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AggregateFunctionFeatures -> ShowS
showsPrec :: Int -> AggregateFunctionFeatures -> ShowS
$cshow :: AggregateFunctionFeatures -> String
show :: AggregateFunctionFeatures -> String
$cshowList :: [AggregateFunctionFeatures] -> ShowS
showList :: [AggregateFunctionFeatures] -> ShowS
Show)
_AggregateFunctionFeatures :: Name
_AggregateFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.AggregateFunctionFeatures")
_AggregateFunctionFeatures_avg :: Name
_AggregateFunctionFeatures_avg = (String -> Name
Core.Name String
"avg")
_AggregateFunctionFeatures_collect :: Name
_AggregateFunctionFeatures_collect = (String -> Name
Core.Name String
"collect")
_AggregateFunctionFeatures_count :: Name
_AggregateFunctionFeatures_count = (String -> Name
Core.Name String
"count")
_AggregateFunctionFeatures_max :: Name
_AggregateFunctionFeatures_max = (String -> Name
Core.Name String
"max")
_AggregateFunctionFeatures_min :: Name
_AggregateFunctionFeatures_min = (String -> Name
Core.Name String
"min")
_AggregateFunctionFeatures_percentileCont :: Name
_AggregateFunctionFeatures_percentileCont = (String -> Name
Core.Name String
"percentileCont")
_AggregateFunctionFeatures_percentileDisc :: Name
_AggregateFunctionFeatures_percentileDisc = (String -> Name
Core.Name String
"percentileDisc")
_AggregateFunctionFeatures_stdev :: Name
_AggregateFunctionFeatures_stdev = (String -> Name
Core.Name String
"stdev")
_AggregateFunctionFeatures_stdevp :: Name
_AggregateFunctionFeatures_stdevp = (String -> Name
Core.Name String
"stdevp")
_AggregateFunctionFeatures_sum :: Name
_AggregateFunctionFeatures_sum = (String -> Name
Core.Name String
"sum")
data DatabaseFunctionFeatures =
DatabaseFunctionFeatures {
DatabaseFunctionFeatures -> Bool
databaseFunctionFeaturesDb_nameFromElementId :: Bool}
deriving (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
(DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> Eq DatabaseFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
== :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
$c/= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
/= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
Eq, Eq DatabaseFunctionFeatures
Eq DatabaseFunctionFeatures =>
(DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Ordering)
-> (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> (DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool)
-> (DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures)
-> (DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures)
-> Ord DatabaseFunctionFeatures
DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Ordering
DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures
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 :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Ordering
compare :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Ordering
$c< :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
< :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
$c<= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
<= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
$c> :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
> :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
$c>= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
>= :: DatabaseFunctionFeatures -> DatabaseFunctionFeatures -> Bool
$cmax :: DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures
max :: DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures
$cmin :: DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures
min :: DatabaseFunctionFeatures
-> DatabaseFunctionFeatures -> DatabaseFunctionFeatures
Ord, ReadPrec [DatabaseFunctionFeatures]
ReadPrec DatabaseFunctionFeatures
Int -> ReadS DatabaseFunctionFeatures
ReadS [DatabaseFunctionFeatures]
(Int -> ReadS DatabaseFunctionFeatures)
-> ReadS [DatabaseFunctionFeatures]
-> ReadPrec DatabaseFunctionFeatures
-> ReadPrec [DatabaseFunctionFeatures]
-> Read DatabaseFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DatabaseFunctionFeatures
readsPrec :: Int -> ReadS DatabaseFunctionFeatures
$creadList :: ReadS [DatabaseFunctionFeatures]
readList :: ReadS [DatabaseFunctionFeatures]
$creadPrec :: ReadPrec DatabaseFunctionFeatures
readPrec :: ReadPrec DatabaseFunctionFeatures
$creadListPrec :: ReadPrec [DatabaseFunctionFeatures]
readListPrec :: ReadPrec [DatabaseFunctionFeatures]
Read, Int -> DatabaseFunctionFeatures -> ShowS
[DatabaseFunctionFeatures] -> ShowS
DatabaseFunctionFeatures -> String
(Int -> DatabaseFunctionFeatures -> ShowS)
-> (DatabaseFunctionFeatures -> String)
-> ([DatabaseFunctionFeatures] -> ShowS)
-> Show DatabaseFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatabaseFunctionFeatures -> ShowS
showsPrec :: Int -> DatabaseFunctionFeatures -> ShowS
$cshow :: DatabaseFunctionFeatures -> String
show :: DatabaseFunctionFeatures -> String
$cshowList :: [DatabaseFunctionFeatures] -> ShowS
showList :: [DatabaseFunctionFeatures] -> ShowS
Show)
_DatabaseFunctionFeatures :: Name
_DatabaseFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.DatabaseFunctionFeatures")
_DatabaseFunctionFeatures_db_nameFromElementId :: Name
_DatabaseFunctionFeatures_db_nameFromElementId = (String -> Name
Core.Name String
"db.nameFromElementId")
data GenAIFunctionFeatures =
GenAIFunctionFeatures {
GenAIFunctionFeatures -> Bool
genAIFunctionFeaturesGenai_vector_encode :: Bool}
deriving (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
(GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> Eq GenAIFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
== :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
$c/= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
/= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
Eq, Eq GenAIFunctionFeatures
Eq GenAIFunctionFeatures =>
(GenAIFunctionFeatures -> GenAIFunctionFeatures -> Ordering)
-> (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> (GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool)
-> (GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures)
-> (GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures)
-> Ord GenAIFunctionFeatures
GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
GenAIFunctionFeatures -> GenAIFunctionFeatures -> Ordering
GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures
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 :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Ordering
compare :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Ordering
$c< :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
< :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
$c<= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
<= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
$c> :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
> :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
$c>= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
>= :: GenAIFunctionFeatures -> GenAIFunctionFeatures -> Bool
$cmax :: GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures
max :: GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures
$cmin :: GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures
min :: GenAIFunctionFeatures
-> GenAIFunctionFeatures -> GenAIFunctionFeatures
Ord, ReadPrec [GenAIFunctionFeatures]
ReadPrec GenAIFunctionFeatures
Int -> ReadS GenAIFunctionFeatures
ReadS [GenAIFunctionFeatures]
(Int -> ReadS GenAIFunctionFeatures)
-> ReadS [GenAIFunctionFeatures]
-> ReadPrec GenAIFunctionFeatures
-> ReadPrec [GenAIFunctionFeatures]
-> Read GenAIFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GenAIFunctionFeatures
readsPrec :: Int -> ReadS GenAIFunctionFeatures
$creadList :: ReadS [GenAIFunctionFeatures]
readList :: ReadS [GenAIFunctionFeatures]
$creadPrec :: ReadPrec GenAIFunctionFeatures
readPrec :: ReadPrec GenAIFunctionFeatures
$creadListPrec :: ReadPrec [GenAIFunctionFeatures]
readListPrec :: ReadPrec [GenAIFunctionFeatures]
Read, Int -> GenAIFunctionFeatures -> ShowS
[GenAIFunctionFeatures] -> ShowS
GenAIFunctionFeatures -> String
(Int -> GenAIFunctionFeatures -> ShowS)
-> (GenAIFunctionFeatures -> String)
-> ([GenAIFunctionFeatures] -> ShowS)
-> Show GenAIFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenAIFunctionFeatures -> ShowS
showsPrec :: Int -> GenAIFunctionFeatures -> ShowS
$cshow :: GenAIFunctionFeatures -> String
show :: GenAIFunctionFeatures -> String
$cshowList :: [GenAIFunctionFeatures] -> ShowS
showList :: [GenAIFunctionFeatures] -> ShowS
Show)
_GenAIFunctionFeatures :: Name
_GenAIFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.GenAIFunctionFeatures")
_GenAIFunctionFeatures_genai_vector_encode :: Name
_GenAIFunctionFeatures_genai_vector_encode = (String -> Name
Core.Name String
"genai.vector.encode")
data GraphFunctionFeatures =
GraphFunctionFeatures {
GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_byElementId :: Bool,
GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_byName :: Bool,
GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_names :: Bool,
GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_propertiesByName :: Bool}
deriving (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
(GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> Eq GraphFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
== :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
$c/= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
/= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
Eq, Eq GraphFunctionFeatures
Eq GraphFunctionFeatures =>
(GraphFunctionFeatures -> GraphFunctionFeatures -> Ordering)
-> (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> (GraphFunctionFeatures -> GraphFunctionFeatures -> Bool)
-> (GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures)
-> (GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures)
-> Ord GraphFunctionFeatures
GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
GraphFunctionFeatures -> GraphFunctionFeatures -> Ordering
GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures
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 :: GraphFunctionFeatures -> GraphFunctionFeatures -> Ordering
compare :: GraphFunctionFeatures -> GraphFunctionFeatures -> Ordering
$c< :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
< :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
$c<= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
<= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
$c> :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
> :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
$c>= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
>= :: GraphFunctionFeatures -> GraphFunctionFeatures -> Bool
$cmax :: GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures
max :: GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures
$cmin :: GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures
min :: GraphFunctionFeatures
-> GraphFunctionFeatures -> GraphFunctionFeatures
Ord, ReadPrec [GraphFunctionFeatures]
ReadPrec GraphFunctionFeatures
Int -> ReadS GraphFunctionFeatures
ReadS [GraphFunctionFeatures]
(Int -> ReadS GraphFunctionFeatures)
-> ReadS [GraphFunctionFeatures]
-> ReadPrec GraphFunctionFeatures
-> ReadPrec [GraphFunctionFeatures]
-> Read GraphFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GraphFunctionFeatures
readsPrec :: Int -> ReadS GraphFunctionFeatures
$creadList :: ReadS [GraphFunctionFeatures]
readList :: ReadS [GraphFunctionFeatures]
$creadPrec :: ReadPrec GraphFunctionFeatures
readPrec :: ReadPrec GraphFunctionFeatures
$creadListPrec :: ReadPrec [GraphFunctionFeatures]
readListPrec :: ReadPrec [GraphFunctionFeatures]
Read, Int -> GraphFunctionFeatures -> ShowS
[GraphFunctionFeatures] -> ShowS
GraphFunctionFeatures -> String
(Int -> GraphFunctionFeatures -> ShowS)
-> (GraphFunctionFeatures -> String)
-> ([GraphFunctionFeatures] -> ShowS)
-> Show GraphFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GraphFunctionFeatures -> ShowS
showsPrec :: Int -> GraphFunctionFeatures -> ShowS
$cshow :: GraphFunctionFeatures -> String
show :: GraphFunctionFeatures -> String
$cshowList :: [GraphFunctionFeatures] -> ShowS
showList :: [GraphFunctionFeatures] -> ShowS
Show)
_GraphFunctionFeatures :: Name
_GraphFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.GraphFunctionFeatures")
_GraphFunctionFeatures_graph_byElementId :: Name
_GraphFunctionFeatures_graph_byElementId = (String -> Name
Core.Name String
"graph.byElementId")
_GraphFunctionFeatures_graph_byName :: Name
_GraphFunctionFeatures_graph_byName = (String -> Name
Core.Name String
"graph.byName")
_GraphFunctionFeatures_graph_names :: Name
_GraphFunctionFeatures_graph_names = (String -> Name
Core.Name String
"graph.names")
_GraphFunctionFeatures_graph_propertiesByName :: Name
_GraphFunctionFeatures_graph_propertiesByName = (String -> Name
Core.Name String
"graph.propertiesByName")
data ListFunctionFeatures =
ListFunctionFeatures {
ListFunctionFeatures -> Bool
listFunctionFeaturesKeys :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesLabels :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesNodes :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesRange :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesReduce :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesRelationships :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesReverse :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesTail :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesToBooleanList :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesToFloatList :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesToIntegerList :: Bool,
ListFunctionFeatures -> Bool
listFunctionFeaturesToStringList :: Bool}
deriving (ListFunctionFeatures -> ListFunctionFeatures -> Bool
(ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> (ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> Eq ListFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
== :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
$c/= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
/= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
Eq, Eq ListFunctionFeatures
Eq ListFunctionFeatures =>
(ListFunctionFeatures -> ListFunctionFeatures -> Ordering)
-> (ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> (ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> (ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> (ListFunctionFeatures -> ListFunctionFeatures -> Bool)
-> (ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures)
-> (ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures)
-> Ord ListFunctionFeatures
ListFunctionFeatures -> ListFunctionFeatures -> Bool
ListFunctionFeatures -> ListFunctionFeatures -> Ordering
ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures
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 :: ListFunctionFeatures -> ListFunctionFeatures -> Ordering
compare :: ListFunctionFeatures -> ListFunctionFeatures -> Ordering
$c< :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
< :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
$c<= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
<= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
$c> :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
> :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
$c>= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
>= :: ListFunctionFeatures -> ListFunctionFeatures -> Bool
$cmax :: ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures
max :: ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures
$cmin :: ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures
min :: ListFunctionFeatures
-> ListFunctionFeatures -> ListFunctionFeatures
Ord, ReadPrec [ListFunctionFeatures]
ReadPrec ListFunctionFeatures
Int -> ReadS ListFunctionFeatures
ReadS [ListFunctionFeatures]
(Int -> ReadS ListFunctionFeatures)
-> ReadS [ListFunctionFeatures]
-> ReadPrec ListFunctionFeatures
-> ReadPrec [ListFunctionFeatures]
-> Read ListFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListFunctionFeatures
readsPrec :: Int -> ReadS ListFunctionFeatures
$creadList :: ReadS [ListFunctionFeatures]
readList :: ReadS [ListFunctionFeatures]
$creadPrec :: ReadPrec ListFunctionFeatures
readPrec :: ReadPrec ListFunctionFeatures
$creadListPrec :: ReadPrec [ListFunctionFeatures]
readListPrec :: ReadPrec [ListFunctionFeatures]
Read, Int -> ListFunctionFeatures -> ShowS
[ListFunctionFeatures] -> ShowS
ListFunctionFeatures -> String
(Int -> ListFunctionFeatures -> ShowS)
-> (ListFunctionFeatures -> String)
-> ([ListFunctionFeatures] -> ShowS)
-> Show ListFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListFunctionFeatures -> ShowS
showsPrec :: Int -> ListFunctionFeatures -> ShowS
$cshow :: ListFunctionFeatures -> String
show :: ListFunctionFeatures -> String
$cshowList :: [ListFunctionFeatures] -> ShowS
showList :: [ListFunctionFeatures] -> ShowS
Show)
_ListFunctionFeatures :: Name
_ListFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.ListFunctionFeatures")
_ListFunctionFeatures_keys :: Name
_ListFunctionFeatures_keys = (String -> Name
Core.Name String
"keys")
_ListFunctionFeatures_labels :: Name
_ListFunctionFeatures_labels = (String -> Name
Core.Name String
"labels")
_ListFunctionFeatures_nodes :: Name
_ListFunctionFeatures_nodes = (String -> Name
Core.Name String
"nodes")
_ListFunctionFeatures_range :: Name
_ListFunctionFeatures_range = (String -> Name
Core.Name String
"range")
_ListFunctionFeatures_reduce :: Name
_ListFunctionFeatures_reduce = (String -> Name
Core.Name String
"reduce")
_ListFunctionFeatures_relationships :: Name
_ListFunctionFeatures_relationships = (String -> Name
Core.Name String
"relationships")
_ListFunctionFeatures_reverse :: Name
_ListFunctionFeatures_reverse = (String -> Name
Core.Name String
"reverse")
_ListFunctionFeatures_tail :: Name
_ListFunctionFeatures_tail = (String -> Name
Core.Name String
"tail")
_ListFunctionFeatures_toBooleanList :: Name
_ListFunctionFeatures_toBooleanList = (String -> Name
Core.Name String
"toBooleanList")
_ListFunctionFeatures_toFloatList :: Name
_ListFunctionFeatures_toFloatList = (String -> Name
Core.Name String
"toFloatList")
_ListFunctionFeatures_toIntegerList :: Name
_ListFunctionFeatures_toIntegerList = (String -> Name
Core.Name String
"toIntegerList")
_ListFunctionFeatures_toStringList :: Name
_ListFunctionFeatures_toStringList = (String -> Name
Core.Name String
"toStringList")
data LoadCSVFunctionFeatures =
LoadCSVFunctionFeatures {
LoadCSVFunctionFeatures -> Bool
loadCSVFunctionFeaturesFile :: Bool,
LoadCSVFunctionFeatures -> Bool
loadCSVFunctionFeaturesLinenumber :: Bool}
deriving (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
(LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> Eq LoadCSVFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
== :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
$c/= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
/= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
Eq, Eq LoadCSVFunctionFeatures
Eq LoadCSVFunctionFeatures =>
(LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Ordering)
-> (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> (LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool)
-> (LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures)
-> (LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures)
-> Ord LoadCSVFunctionFeatures
LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Ordering
LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures
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 :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Ordering
compare :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Ordering
$c< :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
< :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
$c<= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
<= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
$c> :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
> :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
$c>= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
>= :: LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures -> Bool
$cmax :: LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures
max :: LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures
$cmin :: LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures
min :: LoadCSVFunctionFeatures
-> LoadCSVFunctionFeatures -> LoadCSVFunctionFeatures
Ord, ReadPrec [LoadCSVFunctionFeatures]
ReadPrec LoadCSVFunctionFeatures
Int -> ReadS LoadCSVFunctionFeatures
ReadS [LoadCSVFunctionFeatures]
(Int -> ReadS LoadCSVFunctionFeatures)
-> ReadS [LoadCSVFunctionFeatures]
-> ReadPrec LoadCSVFunctionFeatures
-> ReadPrec [LoadCSVFunctionFeatures]
-> Read LoadCSVFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LoadCSVFunctionFeatures
readsPrec :: Int -> ReadS LoadCSVFunctionFeatures
$creadList :: ReadS [LoadCSVFunctionFeatures]
readList :: ReadS [LoadCSVFunctionFeatures]
$creadPrec :: ReadPrec LoadCSVFunctionFeatures
readPrec :: ReadPrec LoadCSVFunctionFeatures
$creadListPrec :: ReadPrec [LoadCSVFunctionFeatures]
readListPrec :: ReadPrec [LoadCSVFunctionFeatures]
Read, Int -> LoadCSVFunctionFeatures -> ShowS
[LoadCSVFunctionFeatures] -> ShowS
LoadCSVFunctionFeatures -> String
(Int -> LoadCSVFunctionFeatures -> ShowS)
-> (LoadCSVFunctionFeatures -> String)
-> ([LoadCSVFunctionFeatures] -> ShowS)
-> Show LoadCSVFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LoadCSVFunctionFeatures -> ShowS
showsPrec :: Int -> LoadCSVFunctionFeatures -> ShowS
$cshow :: LoadCSVFunctionFeatures -> String
show :: LoadCSVFunctionFeatures -> String
$cshowList :: [LoadCSVFunctionFeatures] -> ShowS
showList :: [LoadCSVFunctionFeatures] -> ShowS
Show)
_LoadCSVFunctionFeatures :: Name
_LoadCSVFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.LoadCSVFunctionFeatures")
_LoadCSVFunctionFeatures_file :: Name
_LoadCSVFunctionFeatures_file = (String -> Name
Core.Name String
"file")
_LoadCSVFunctionFeatures_linenumber :: Name
_LoadCSVFunctionFeatures_linenumber = (String -> Name
Core.Name String
"linenumber")
data LogarithmicFunctionFeatures =
LogarithmicFunctionFeatures {
LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesE :: Bool,
LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesExp :: Bool,
LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesLog :: Bool,
LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesLog10 :: Bool,
LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesSqrt :: Bool}
deriving (LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
(LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> Eq LogarithmicFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
== :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
$c/= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
/= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
Eq, Eq LogarithmicFunctionFeatures
Eq LogarithmicFunctionFeatures =>
(LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Ordering)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Bool)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures)
-> (LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures)
-> Ord LogarithmicFunctionFeatures
LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Ordering
LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures
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 :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Ordering
compare :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> Ordering
$c< :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
< :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
$c<= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
<= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
$c> :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
> :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
$c>= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
>= :: LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures -> Bool
$cmax :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures
max :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures
$cmin :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures
min :: LogarithmicFunctionFeatures
-> LogarithmicFunctionFeatures -> LogarithmicFunctionFeatures
Ord, ReadPrec [LogarithmicFunctionFeatures]
ReadPrec LogarithmicFunctionFeatures
Int -> ReadS LogarithmicFunctionFeatures
ReadS [LogarithmicFunctionFeatures]
(Int -> ReadS LogarithmicFunctionFeatures)
-> ReadS [LogarithmicFunctionFeatures]
-> ReadPrec LogarithmicFunctionFeatures
-> ReadPrec [LogarithmicFunctionFeatures]
-> Read LogarithmicFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LogarithmicFunctionFeatures
readsPrec :: Int -> ReadS LogarithmicFunctionFeatures
$creadList :: ReadS [LogarithmicFunctionFeatures]
readList :: ReadS [LogarithmicFunctionFeatures]
$creadPrec :: ReadPrec LogarithmicFunctionFeatures
readPrec :: ReadPrec LogarithmicFunctionFeatures
$creadListPrec :: ReadPrec [LogarithmicFunctionFeatures]
readListPrec :: ReadPrec [LogarithmicFunctionFeatures]
Read, Int -> LogarithmicFunctionFeatures -> ShowS
[LogarithmicFunctionFeatures] -> ShowS
LogarithmicFunctionFeatures -> String
(Int -> LogarithmicFunctionFeatures -> ShowS)
-> (LogarithmicFunctionFeatures -> String)
-> ([LogarithmicFunctionFeatures] -> ShowS)
-> Show LogarithmicFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogarithmicFunctionFeatures -> ShowS
showsPrec :: Int -> LogarithmicFunctionFeatures -> ShowS
$cshow :: LogarithmicFunctionFeatures -> String
show :: LogarithmicFunctionFeatures -> String
$cshowList :: [LogarithmicFunctionFeatures] -> ShowS
showList :: [LogarithmicFunctionFeatures] -> ShowS
Show)
_LogarithmicFunctionFeatures :: Name
_LogarithmicFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.LogarithmicFunctionFeatures")
_LogarithmicFunctionFeatures_e :: Name
_LogarithmicFunctionFeatures_e = (String -> Name
Core.Name String
"e")
_LogarithmicFunctionFeatures_exp :: Name
_LogarithmicFunctionFeatures_exp = (String -> Name
Core.Name String
"exp")
_LogarithmicFunctionFeatures_log :: Name
_LogarithmicFunctionFeatures_log = (String -> Name
Core.Name String
"log")
_LogarithmicFunctionFeatures_log10 :: Name
_LogarithmicFunctionFeatures_log10 = (String -> Name
Core.Name String
"log10")
_LogarithmicFunctionFeatures_sqrt :: Name
_LogarithmicFunctionFeatures_sqrt = (String -> Name
Core.Name String
"sqrt")
data NumericFunctionFeatures =
NumericFunctionFeatures {
NumericFunctionFeatures -> Bool
numericFunctionFeaturesAbs :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesCeil :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesFloor :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesIsNaN :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesRand :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesRound :: Bool,
NumericFunctionFeatures -> Bool
numericFunctionFeaturesSign :: Bool}
deriving (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
(NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> Eq NumericFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
== :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
$c/= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
/= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
Eq, Eq NumericFunctionFeatures
Eq NumericFunctionFeatures =>
(NumericFunctionFeatures -> NumericFunctionFeatures -> Ordering)
-> (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> (NumericFunctionFeatures -> NumericFunctionFeatures -> Bool)
-> (NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures)
-> (NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures)
-> Ord NumericFunctionFeatures
NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
NumericFunctionFeatures -> NumericFunctionFeatures -> Ordering
NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures
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 :: NumericFunctionFeatures -> NumericFunctionFeatures -> Ordering
compare :: NumericFunctionFeatures -> NumericFunctionFeatures -> Ordering
$c< :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
< :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
$c<= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
<= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
$c> :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
> :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
$c>= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
>= :: NumericFunctionFeatures -> NumericFunctionFeatures -> Bool
$cmax :: NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures
max :: NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures
$cmin :: NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures
min :: NumericFunctionFeatures
-> NumericFunctionFeatures -> NumericFunctionFeatures
Ord, ReadPrec [NumericFunctionFeatures]
ReadPrec NumericFunctionFeatures
Int -> ReadS NumericFunctionFeatures
ReadS [NumericFunctionFeatures]
(Int -> ReadS NumericFunctionFeatures)
-> ReadS [NumericFunctionFeatures]
-> ReadPrec NumericFunctionFeatures
-> ReadPrec [NumericFunctionFeatures]
-> Read NumericFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NumericFunctionFeatures
readsPrec :: Int -> ReadS NumericFunctionFeatures
$creadList :: ReadS [NumericFunctionFeatures]
readList :: ReadS [NumericFunctionFeatures]
$creadPrec :: ReadPrec NumericFunctionFeatures
readPrec :: ReadPrec NumericFunctionFeatures
$creadListPrec :: ReadPrec [NumericFunctionFeatures]
readListPrec :: ReadPrec [NumericFunctionFeatures]
Read, Int -> NumericFunctionFeatures -> ShowS
[NumericFunctionFeatures] -> ShowS
NumericFunctionFeatures -> String
(Int -> NumericFunctionFeatures -> ShowS)
-> (NumericFunctionFeatures -> String)
-> ([NumericFunctionFeatures] -> ShowS)
-> Show NumericFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumericFunctionFeatures -> ShowS
showsPrec :: Int -> NumericFunctionFeatures -> ShowS
$cshow :: NumericFunctionFeatures -> String
show :: NumericFunctionFeatures -> String
$cshowList :: [NumericFunctionFeatures] -> ShowS
showList :: [NumericFunctionFeatures] -> ShowS
Show)
_NumericFunctionFeatures :: Name
_NumericFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.NumericFunctionFeatures")
_NumericFunctionFeatures_abs :: Name
_NumericFunctionFeatures_abs = (String -> Name
Core.Name String
"abs")
_NumericFunctionFeatures_ceil :: Name
_NumericFunctionFeatures_ceil = (String -> Name
Core.Name String
"ceil")
_NumericFunctionFeatures_floor :: Name
_NumericFunctionFeatures_floor = (String -> Name
Core.Name String
"floor")
_NumericFunctionFeatures_isNaN :: Name
_NumericFunctionFeatures_isNaN = (String -> Name
Core.Name String
"isNaN")
_NumericFunctionFeatures_rand :: Name
_NumericFunctionFeatures_rand = (String -> Name
Core.Name String
"rand")
_NumericFunctionFeatures_round :: Name
_NumericFunctionFeatures_round = (String -> Name
Core.Name String
"round")
_NumericFunctionFeatures_sign :: Name
_NumericFunctionFeatures_sign = (String -> Name
Core.Name String
"sign")
data PredicateFunctionFeatures =
PredicateFunctionFeatures {
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesAll :: Bool,
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesAny :: Bool,
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesExists :: Bool,
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesIsEmpty :: Bool,
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesNone :: Bool,
PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesSingle :: Bool}
deriving (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
(PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> Eq PredicateFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
== :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
$c/= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
/= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
Eq, Eq PredicateFunctionFeatures
Eq PredicateFunctionFeatures =>
(PredicateFunctionFeatures
-> PredicateFunctionFeatures -> Ordering)
-> (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> (PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool)
-> (PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures)
-> (PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures)
-> Ord PredicateFunctionFeatures
PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
PredicateFunctionFeatures -> PredicateFunctionFeatures -> Ordering
PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures
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 :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Ordering
compare :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Ordering
$c< :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
< :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
$c<= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
<= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
$c> :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
> :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
$c>= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
>= :: PredicateFunctionFeatures -> PredicateFunctionFeatures -> Bool
$cmax :: PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures
max :: PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures
$cmin :: PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures
min :: PredicateFunctionFeatures
-> PredicateFunctionFeatures -> PredicateFunctionFeatures
Ord, ReadPrec [PredicateFunctionFeatures]
ReadPrec PredicateFunctionFeatures
Int -> ReadS PredicateFunctionFeatures
ReadS [PredicateFunctionFeatures]
(Int -> ReadS PredicateFunctionFeatures)
-> ReadS [PredicateFunctionFeatures]
-> ReadPrec PredicateFunctionFeatures
-> ReadPrec [PredicateFunctionFeatures]
-> Read PredicateFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PredicateFunctionFeatures
readsPrec :: Int -> ReadS PredicateFunctionFeatures
$creadList :: ReadS [PredicateFunctionFeatures]
readList :: ReadS [PredicateFunctionFeatures]
$creadPrec :: ReadPrec PredicateFunctionFeatures
readPrec :: ReadPrec PredicateFunctionFeatures
$creadListPrec :: ReadPrec [PredicateFunctionFeatures]
readListPrec :: ReadPrec [PredicateFunctionFeatures]
Read, Int -> PredicateFunctionFeatures -> ShowS
[PredicateFunctionFeatures] -> ShowS
PredicateFunctionFeatures -> String
(Int -> PredicateFunctionFeatures -> ShowS)
-> (PredicateFunctionFeatures -> String)
-> ([PredicateFunctionFeatures] -> ShowS)
-> Show PredicateFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PredicateFunctionFeatures -> ShowS
showsPrec :: Int -> PredicateFunctionFeatures -> ShowS
$cshow :: PredicateFunctionFeatures -> String
show :: PredicateFunctionFeatures -> String
$cshowList :: [PredicateFunctionFeatures] -> ShowS
showList :: [PredicateFunctionFeatures] -> ShowS
Show)
_PredicateFunctionFeatures :: Name
_PredicateFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.PredicateFunctionFeatures")
_PredicateFunctionFeatures_all :: Name
_PredicateFunctionFeatures_all = (String -> Name
Core.Name String
"all")
_PredicateFunctionFeatures_any :: Name
_PredicateFunctionFeatures_any = (String -> Name
Core.Name String
"any")
_PredicateFunctionFeatures_exists :: Name
_PredicateFunctionFeatures_exists = (String -> Name
Core.Name String
"exists")
_PredicateFunctionFeatures_isEmpty :: Name
_PredicateFunctionFeatures_isEmpty = (String -> Name
Core.Name String
"isEmpty")
_PredicateFunctionFeatures_none :: Name
_PredicateFunctionFeatures_none = (String -> Name
Core.Name String
"none")
_PredicateFunctionFeatures_single :: Name
_PredicateFunctionFeatures_single = (String -> Name
Core.Name String
"single")
data ScalarFunctionFeatures =
ScalarFunctionFeatures {
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesChar_length :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesCharacter_length :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesCoalesce :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesElementId :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesEndNode :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesHead :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesId :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesLast :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesLength :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesNullIf :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesProperties :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesRandomUUID :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesSize :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesStartNode :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToBoolean :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToBooleanOrNull :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToFloat :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToFloatOrNull :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToInteger :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToIntegerOrNull :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesType :: Bool,
ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesValueType :: Bool}
deriving (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
(ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> Eq ScalarFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
== :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
$c/= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
/= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
Eq, Eq ScalarFunctionFeatures
Eq ScalarFunctionFeatures =>
(ScalarFunctionFeatures -> ScalarFunctionFeatures -> Ordering)
-> (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> (ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool)
-> (ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures)
-> (ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures)
-> Ord ScalarFunctionFeatures
ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
ScalarFunctionFeatures -> ScalarFunctionFeatures -> Ordering
ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures
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 :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Ordering
compare :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Ordering
$c< :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
< :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
$c<= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
<= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
$c> :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
> :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
$c>= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
>= :: ScalarFunctionFeatures -> ScalarFunctionFeatures -> Bool
$cmax :: ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures
max :: ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures
$cmin :: ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures
min :: ScalarFunctionFeatures
-> ScalarFunctionFeatures -> ScalarFunctionFeatures
Ord, ReadPrec [ScalarFunctionFeatures]
ReadPrec ScalarFunctionFeatures
Int -> ReadS ScalarFunctionFeatures
ReadS [ScalarFunctionFeatures]
(Int -> ReadS ScalarFunctionFeatures)
-> ReadS [ScalarFunctionFeatures]
-> ReadPrec ScalarFunctionFeatures
-> ReadPrec [ScalarFunctionFeatures]
-> Read ScalarFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScalarFunctionFeatures
readsPrec :: Int -> ReadS ScalarFunctionFeatures
$creadList :: ReadS [ScalarFunctionFeatures]
readList :: ReadS [ScalarFunctionFeatures]
$creadPrec :: ReadPrec ScalarFunctionFeatures
readPrec :: ReadPrec ScalarFunctionFeatures
$creadListPrec :: ReadPrec [ScalarFunctionFeatures]
readListPrec :: ReadPrec [ScalarFunctionFeatures]
Read, Int -> ScalarFunctionFeatures -> ShowS
[ScalarFunctionFeatures] -> ShowS
ScalarFunctionFeatures -> String
(Int -> ScalarFunctionFeatures -> ShowS)
-> (ScalarFunctionFeatures -> String)
-> ([ScalarFunctionFeatures] -> ShowS)
-> Show ScalarFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScalarFunctionFeatures -> ShowS
showsPrec :: Int -> ScalarFunctionFeatures -> ShowS
$cshow :: ScalarFunctionFeatures -> String
show :: ScalarFunctionFeatures -> String
$cshowList :: [ScalarFunctionFeatures] -> ShowS
showList :: [ScalarFunctionFeatures] -> ShowS
Show)
_ScalarFunctionFeatures :: Name
_ScalarFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.ScalarFunctionFeatures")
_ScalarFunctionFeatures_char_length :: Name
_ScalarFunctionFeatures_char_length = (String -> Name
Core.Name String
"char_length")
_ScalarFunctionFeatures_character_length :: Name
_ScalarFunctionFeatures_character_length = (String -> Name
Core.Name String
"character_length")
_ScalarFunctionFeatures_coalesce :: Name
_ScalarFunctionFeatures_coalesce = (String -> Name
Core.Name String
"coalesce")
_ScalarFunctionFeatures_elementId :: Name
_ScalarFunctionFeatures_elementId = (String -> Name
Core.Name String
"elementId")
_ScalarFunctionFeatures_endNode :: Name
_ScalarFunctionFeatures_endNode = (String -> Name
Core.Name String
"endNode")
_ScalarFunctionFeatures_head :: Name
_ScalarFunctionFeatures_head = (String -> Name
Core.Name String
"head")
_ScalarFunctionFeatures_id :: Name
_ScalarFunctionFeatures_id = (String -> Name
Core.Name String
"id")
_ScalarFunctionFeatures_last :: Name
_ScalarFunctionFeatures_last = (String -> Name
Core.Name String
"last")
_ScalarFunctionFeatures_length :: Name
_ScalarFunctionFeatures_length = (String -> Name
Core.Name String
"length")
_ScalarFunctionFeatures_nullIf :: Name
_ScalarFunctionFeatures_nullIf = (String -> Name
Core.Name String
"nullIf")
_ScalarFunctionFeatures_properties :: Name
_ScalarFunctionFeatures_properties = (String -> Name
Core.Name String
"properties")
_ScalarFunctionFeatures_randomUUID :: Name
_ScalarFunctionFeatures_randomUUID = (String -> Name
Core.Name String
"randomUUID")
_ScalarFunctionFeatures_size :: Name
_ScalarFunctionFeatures_size = (String -> Name
Core.Name String
"size")
_ScalarFunctionFeatures_startNode :: Name
_ScalarFunctionFeatures_startNode = (String -> Name
Core.Name String
"startNode")
_ScalarFunctionFeatures_toBoolean :: Name
_ScalarFunctionFeatures_toBoolean = (String -> Name
Core.Name String
"toBoolean")
_ScalarFunctionFeatures_toBooleanOrNull :: Name
_ScalarFunctionFeatures_toBooleanOrNull = (String -> Name
Core.Name String
"toBooleanOrNull")
_ScalarFunctionFeatures_toFloat :: Name
_ScalarFunctionFeatures_toFloat = (String -> Name
Core.Name String
"toFloat")
_ScalarFunctionFeatures_toFloatOrNull :: Name
_ScalarFunctionFeatures_toFloatOrNull = (String -> Name
Core.Name String
"toFloatOrNull")
_ScalarFunctionFeatures_toInteger :: Name
_ScalarFunctionFeatures_toInteger = (String -> Name
Core.Name String
"toInteger")
_ScalarFunctionFeatures_toIntegerOrNull :: Name
_ScalarFunctionFeatures_toIntegerOrNull = (String -> Name
Core.Name String
"toIntegerOrNull")
_ScalarFunctionFeatures_type :: Name
_ScalarFunctionFeatures_type = (String -> Name
Core.Name String
"type")
_ScalarFunctionFeatures_valueType :: Name
_ScalarFunctionFeatures_valueType = (String -> Name
Core.Name String
"valueType")
data SpatialFunctionFeatures =
SpatialFunctionFeatures {
SpatialFunctionFeatures -> Bool
spatialFunctionFeaturesPoint_distance :: Bool,
SpatialFunctionFeatures -> Bool
spatialFunctionFeaturesPoint :: Bool,
SpatialFunctionFeatures -> Bool
spatialFunctionFeaturesPoint_withinBBox :: Bool}
deriving (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
(SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> Eq SpatialFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
== :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
$c/= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
/= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
Eq, Eq SpatialFunctionFeatures
Eq SpatialFunctionFeatures =>
(SpatialFunctionFeatures -> SpatialFunctionFeatures -> Ordering)
-> (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> (SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool)
-> (SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures)
-> (SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures)
-> Ord SpatialFunctionFeatures
SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
SpatialFunctionFeatures -> SpatialFunctionFeatures -> Ordering
SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures
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 :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Ordering
compare :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Ordering
$c< :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
< :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
$c<= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
<= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
$c> :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
> :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
$c>= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
>= :: SpatialFunctionFeatures -> SpatialFunctionFeatures -> Bool
$cmax :: SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures
max :: SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures
$cmin :: SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures
min :: SpatialFunctionFeatures
-> SpatialFunctionFeatures -> SpatialFunctionFeatures
Ord, ReadPrec [SpatialFunctionFeatures]
ReadPrec SpatialFunctionFeatures
Int -> ReadS SpatialFunctionFeatures
ReadS [SpatialFunctionFeatures]
(Int -> ReadS SpatialFunctionFeatures)
-> ReadS [SpatialFunctionFeatures]
-> ReadPrec SpatialFunctionFeatures
-> ReadPrec [SpatialFunctionFeatures]
-> Read SpatialFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SpatialFunctionFeatures
readsPrec :: Int -> ReadS SpatialFunctionFeatures
$creadList :: ReadS [SpatialFunctionFeatures]
readList :: ReadS [SpatialFunctionFeatures]
$creadPrec :: ReadPrec SpatialFunctionFeatures
readPrec :: ReadPrec SpatialFunctionFeatures
$creadListPrec :: ReadPrec [SpatialFunctionFeatures]
readListPrec :: ReadPrec [SpatialFunctionFeatures]
Read, Int -> SpatialFunctionFeatures -> ShowS
[SpatialFunctionFeatures] -> ShowS
SpatialFunctionFeatures -> String
(Int -> SpatialFunctionFeatures -> ShowS)
-> (SpatialFunctionFeatures -> String)
-> ([SpatialFunctionFeatures] -> ShowS)
-> Show SpatialFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SpatialFunctionFeatures -> ShowS
showsPrec :: Int -> SpatialFunctionFeatures -> ShowS
$cshow :: SpatialFunctionFeatures -> String
show :: SpatialFunctionFeatures -> String
$cshowList :: [SpatialFunctionFeatures] -> ShowS
showList :: [SpatialFunctionFeatures] -> ShowS
Show)
_SpatialFunctionFeatures :: Name
_SpatialFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.SpatialFunctionFeatures")
_SpatialFunctionFeatures_point_distance :: Name
_SpatialFunctionFeatures_point_distance = (String -> Name
Core.Name String
"point.distance")
_SpatialFunctionFeatures_point :: Name
_SpatialFunctionFeatures_point = (String -> Name
Core.Name String
"point")
_SpatialFunctionFeatures_point_withinBBox :: Name
_SpatialFunctionFeatures_point_withinBBox = (String -> Name
Core.Name String
"point.withinBBox")
data StringFunctionFeatures =
StringFunctionFeatures {
StringFunctionFeatures -> Bool
stringFunctionFeaturesBtrim :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesLeft :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesLower :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesLtrim :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesNormalize :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesReplace :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesReverse :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesRight :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesRtrim :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesSplit :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesSubstring :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesToLower :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesToString :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesToStringOrNull :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesToUpper :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesTrim :: Bool,
StringFunctionFeatures -> Bool
stringFunctionFeaturesUpper :: Bool}
deriving (StringFunctionFeatures -> StringFunctionFeatures -> Bool
(StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> (StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> Eq StringFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
== :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
$c/= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
/= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
Eq, Eq StringFunctionFeatures
Eq StringFunctionFeatures =>
(StringFunctionFeatures -> StringFunctionFeatures -> Ordering)
-> (StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> (StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> (StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> (StringFunctionFeatures -> StringFunctionFeatures -> Bool)
-> (StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures)
-> (StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures)
-> Ord StringFunctionFeatures
StringFunctionFeatures -> StringFunctionFeatures -> Bool
StringFunctionFeatures -> StringFunctionFeatures -> Ordering
StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures
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 :: StringFunctionFeatures -> StringFunctionFeatures -> Ordering
compare :: StringFunctionFeatures -> StringFunctionFeatures -> Ordering
$c< :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
< :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
$c<= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
<= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
$c> :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
> :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
$c>= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
>= :: StringFunctionFeatures -> StringFunctionFeatures -> Bool
$cmax :: StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures
max :: StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures
$cmin :: StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures
min :: StringFunctionFeatures
-> StringFunctionFeatures -> StringFunctionFeatures
Ord, ReadPrec [StringFunctionFeatures]
ReadPrec StringFunctionFeatures
Int -> ReadS StringFunctionFeatures
ReadS [StringFunctionFeatures]
(Int -> ReadS StringFunctionFeatures)
-> ReadS [StringFunctionFeatures]
-> ReadPrec StringFunctionFeatures
-> ReadPrec [StringFunctionFeatures]
-> Read StringFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StringFunctionFeatures
readsPrec :: Int -> ReadS StringFunctionFeatures
$creadList :: ReadS [StringFunctionFeatures]
readList :: ReadS [StringFunctionFeatures]
$creadPrec :: ReadPrec StringFunctionFeatures
readPrec :: ReadPrec StringFunctionFeatures
$creadListPrec :: ReadPrec [StringFunctionFeatures]
readListPrec :: ReadPrec [StringFunctionFeatures]
Read, Int -> StringFunctionFeatures -> ShowS
[StringFunctionFeatures] -> ShowS
StringFunctionFeatures -> String
(Int -> StringFunctionFeatures -> ShowS)
-> (StringFunctionFeatures -> String)
-> ([StringFunctionFeatures] -> ShowS)
-> Show StringFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StringFunctionFeatures -> ShowS
showsPrec :: Int -> StringFunctionFeatures -> ShowS
$cshow :: StringFunctionFeatures -> String
show :: StringFunctionFeatures -> String
$cshowList :: [StringFunctionFeatures] -> ShowS
showList :: [StringFunctionFeatures] -> ShowS
Show)
_StringFunctionFeatures :: Name
_StringFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.StringFunctionFeatures")
_StringFunctionFeatures_btrim :: Name
_StringFunctionFeatures_btrim = (String -> Name
Core.Name String
"btrim")
_StringFunctionFeatures_left :: Name
_StringFunctionFeatures_left = (String -> Name
Core.Name String
"left")
_StringFunctionFeatures_lower :: Name
_StringFunctionFeatures_lower = (String -> Name
Core.Name String
"lower")
_StringFunctionFeatures_ltrim :: Name
_StringFunctionFeatures_ltrim = (String -> Name
Core.Name String
"ltrim")
_StringFunctionFeatures_normalize :: Name
_StringFunctionFeatures_normalize = (String -> Name
Core.Name String
"normalize")
_StringFunctionFeatures_replace :: Name
_StringFunctionFeatures_replace = (String -> Name
Core.Name String
"replace")
_StringFunctionFeatures_reverse :: Name
_StringFunctionFeatures_reverse = (String -> Name
Core.Name String
"reverse")
_StringFunctionFeatures_right :: Name
_StringFunctionFeatures_right = (String -> Name
Core.Name String
"right")
_StringFunctionFeatures_rtrim :: Name
_StringFunctionFeatures_rtrim = (String -> Name
Core.Name String
"rtrim")
_StringFunctionFeatures_split :: Name
_StringFunctionFeatures_split = (String -> Name
Core.Name String
"split")
_StringFunctionFeatures_substring :: Name
_StringFunctionFeatures_substring = (String -> Name
Core.Name String
"substring")
_StringFunctionFeatures_toLower :: Name
_StringFunctionFeatures_toLower = (String -> Name
Core.Name String
"toLower")
_StringFunctionFeatures_toString :: Name
_StringFunctionFeatures_toString = (String -> Name
Core.Name String
"toString")
_StringFunctionFeatures_toStringOrNull :: Name
_StringFunctionFeatures_toStringOrNull = (String -> Name
Core.Name String
"toStringOrNull")
_StringFunctionFeatures_toUpper :: Name
_StringFunctionFeatures_toUpper = (String -> Name
Core.Name String
"toUpper")
_StringFunctionFeatures_trim :: Name
_StringFunctionFeatures_trim = (String -> Name
Core.Name String
"trim")
_StringFunctionFeatures_upper :: Name
_StringFunctionFeatures_upper = (String -> Name
Core.Name String
"upper")
data TemporalDurationFunctionFeatures =
TemporalDurationFunctionFeatures {
TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration :: Bool,
TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_between :: Bool,
TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_inDays :: Bool,
TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_inMonths :: Bool,
TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_inSeconds :: Bool}
deriving (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
(TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> Eq TemporalDurationFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
== :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
$c/= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
/= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
Eq, Eq TemporalDurationFunctionFeatures
Eq TemporalDurationFunctionFeatures =>
(TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Ordering)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures)
-> (TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures)
-> Ord TemporalDurationFunctionFeatures
TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Ordering
TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
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 :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Ordering
compare :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Ordering
$c< :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
< :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
$c<= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
<= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
$c> :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
> :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
$c>= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
>= :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures -> Bool
$cmax :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
max :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
$cmin :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
min :: TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
-> TemporalDurationFunctionFeatures
Ord, ReadPrec [TemporalDurationFunctionFeatures]
ReadPrec TemporalDurationFunctionFeatures
Int -> ReadS TemporalDurationFunctionFeatures
ReadS [TemporalDurationFunctionFeatures]
(Int -> ReadS TemporalDurationFunctionFeatures)
-> ReadS [TemporalDurationFunctionFeatures]
-> ReadPrec TemporalDurationFunctionFeatures
-> ReadPrec [TemporalDurationFunctionFeatures]
-> Read TemporalDurationFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TemporalDurationFunctionFeatures
readsPrec :: Int -> ReadS TemporalDurationFunctionFeatures
$creadList :: ReadS [TemporalDurationFunctionFeatures]
readList :: ReadS [TemporalDurationFunctionFeatures]
$creadPrec :: ReadPrec TemporalDurationFunctionFeatures
readPrec :: ReadPrec TemporalDurationFunctionFeatures
$creadListPrec :: ReadPrec [TemporalDurationFunctionFeatures]
readListPrec :: ReadPrec [TemporalDurationFunctionFeatures]
Read, Int -> TemporalDurationFunctionFeatures -> ShowS
[TemporalDurationFunctionFeatures] -> ShowS
TemporalDurationFunctionFeatures -> String
(Int -> TemporalDurationFunctionFeatures -> ShowS)
-> (TemporalDurationFunctionFeatures -> String)
-> ([TemporalDurationFunctionFeatures] -> ShowS)
-> Show TemporalDurationFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TemporalDurationFunctionFeatures -> ShowS
showsPrec :: Int -> TemporalDurationFunctionFeatures -> ShowS
$cshow :: TemporalDurationFunctionFeatures -> String
show :: TemporalDurationFunctionFeatures -> String
$cshowList :: [TemporalDurationFunctionFeatures] -> ShowS
showList :: [TemporalDurationFunctionFeatures] -> ShowS
Show)
_TemporalDurationFunctionFeatures :: Name
_TemporalDurationFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.TemporalDurationFunctionFeatures")
_TemporalDurationFunctionFeatures_duration :: Name
_TemporalDurationFunctionFeatures_duration = (String -> Name
Core.Name String
"duration")
_TemporalDurationFunctionFeatures_duration_between :: Name
_TemporalDurationFunctionFeatures_duration_between = (String -> Name
Core.Name String
"duration.between")
_TemporalDurationFunctionFeatures_duration_inDays :: Name
_TemporalDurationFunctionFeatures_duration_inDays = (String -> Name
Core.Name String
"duration.inDays")
_TemporalDurationFunctionFeatures_duration_inMonths :: Name
_TemporalDurationFunctionFeatures_duration_inMonths = (String -> Name
Core.Name String
"duration.inMonths")
_TemporalDurationFunctionFeatures_duration_inSeconds :: Name
_TemporalDurationFunctionFeatures_duration_inSeconds = (String -> Name
Core.Name String
"duration.inSeconds")
data TemporalInstantFunctionFeatures =
TemporalInstantFunctionFeatures {
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_realtime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_statement :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_transaction :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_truncate :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_fromepoch :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_fromepochmillis :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_realtime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_statement :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_transaction :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_truncate :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_realtime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_statement :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_transaction :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_truncate :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_realtime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_statement :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_transaction :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_truncate :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_realtime :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_statement :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_transaction :: Bool,
TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_truncate :: Bool}
deriving (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
(TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> Eq TemporalInstantFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
== :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
$c/= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
/= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
Eq, Eq TemporalInstantFunctionFeatures
Eq TemporalInstantFunctionFeatures =>
(TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Ordering)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures)
-> (TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures)
-> Ord TemporalInstantFunctionFeatures
TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Ordering
TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
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 :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Ordering
compare :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Ordering
$c< :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
< :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
$c<= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
<= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
$c> :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
> :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
$c>= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
>= :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures -> Bool
$cmax :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
max :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
$cmin :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
min :: TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
-> TemporalInstantFunctionFeatures
Ord, ReadPrec [TemporalInstantFunctionFeatures]
ReadPrec TemporalInstantFunctionFeatures
Int -> ReadS TemporalInstantFunctionFeatures
ReadS [TemporalInstantFunctionFeatures]
(Int -> ReadS TemporalInstantFunctionFeatures)
-> ReadS [TemporalInstantFunctionFeatures]
-> ReadPrec TemporalInstantFunctionFeatures
-> ReadPrec [TemporalInstantFunctionFeatures]
-> Read TemporalInstantFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TemporalInstantFunctionFeatures
readsPrec :: Int -> ReadS TemporalInstantFunctionFeatures
$creadList :: ReadS [TemporalInstantFunctionFeatures]
readList :: ReadS [TemporalInstantFunctionFeatures]
$creadPrec :: ReadPrec TemporalInstantFunctionFeatures
readPrec :: ReadPrec TemporalInstantFunctionFeatures
$creadListPrec :: ReadPrec [TemporalInstantFunctionFeatures]
readListPrec :: ReadPrec [TemporalInstantFunctionFeatures]
Read, Int -> TemporalInstantFunctionFeatures -> ShowS
[TemporalInstantFunctionFeatures] -> ShowS
TemporalInstantFunctionFeatures -> String
(Int -> TemporalInstantFunctionFeatures -> ShowS)
-> (TemporalInstantFunctionFeatures -> String)
-> ([TemporalInstantFunctionFeatures] -> ShowS)
-> Show TemporalInstantFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TemporalInstantFunctionFeatures -> ShowS
showsPrec :: Int -> TemporalInstantFunctionFeatures -> ShowS
$cshow :: TemporalInstantFunctionFeatures -> String
show :: TemporalInstantFunctionFeatures -> String
$cshowList :: [TemporalInstantFunctionFeatures] -> ShowS
showList :: [TemporalInstantFunctionFeatures] -> ShowS
Show)
_TemporalInstantFunctionFeatures :: Name
_TemporalInstantFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.TemporalInstantFunctionFeatures")
_TemporalInstantFunctionFeatures_date :: Name
_TemporalInstantFunctionFeatures_date = (String -> Name
Core.Name String
"date")
_TemporalInstantFunctionFeatures_date_realtime :: Name
_TemporalInstantFunctionFeatures_date_realtime = (String -> Name
Core.Name String
"date.realtime")
_TemporalInstantFunctionFeatures_date_statement :: Name
_TemporalInstantFunctionFeatures_date_statement = (String -> Name
Core.Name String
"date.statement")
_TemporalInstantFunctionFeatures_date_transaction :: Name
_TemporalInstantFunctionFeatures_date_transaction = (String -> Name
Core.Name String
"date.transaction")
_TemporalInstantFunctionFeatures_date_truncate :: Name
_TemporalInstantFunctionFeatures_date_truncate = (String -> Name
Core.Name String
"date.truncate")
_TemporalInstantFunctionFeatures_datetime :: Name
_TemporalInstantFunctionFeatures_datetime = (String -> Name
Core.Name String
"datetime")
_TemporalInstantFunctionFeatures_datetime_fromepoch :: Name
_TemporalInstantFunctionFeatures_datetime_fromepoch = (String -> Name
Core.Name String
"datetime.fromepoch")
_TemporalInstantFunctionFeatures_datetime_fromepochmillis :: Name
_TemporalInstantFunctionFeatures_datetime_fromepochmillis = (String -> Name
Core.Name String
"datetime.fromepochmillis")
_TemporalInstantFunctionFeatures_datetime_realtime :: Name
_TemporalInstantFunctionFeatures_datetime_realtime = (String -> Name
Core.Name String
"datetime.realtime")
_TemporalInstantFunctionFeatures_datetime_statement :: Name
_TemporalInstantFunctionFeatures_datetime_statement = (String -> Name
Core.Name String
"datetime.statement")
_TemporalInstantFunctionFeatures_datetime_transaction :: Name
_TemporalInstantFunctionFeatures_datetime_transaction = (String -> Name
Core.Name String
"datetime.transaction")
_TemporalInstantFunctionFeatures_datetime_truncate :: Name
_TemporalInstantFunctionFeatures_datetime_truncate = (String -> Name
Core.Name String
"datetime.truncate")
_TemporalInstantFunctionFeatures_localdatetime :: Name
_TemporalInstantFunctionFeatures_localdatetime = (String -> Name
Core.Name String
"localdatetime")
_TemporalInstantFunctionFeatures_localdatetime_realtime :: Name
_TemporalInstantFunctionFeatures_localdatetime_realtime = (String -> Name
Core.Name String
"localdatetime.realtime")
_TemporalInstantFunctionFeatures_localdatetime_statement :: Name
_TemporalInstantFunctionFeatures_localdatetime_statement = (String -> Name
Core.Name String
"localdatetime.statement")
_TemporalInstantFunctionFeatures_localdatetime_transaction :: Name
_TemporalInstantFunctionFeatures_localdatetime_transaction = (String -> Name
Core.Name String
"localdatetime.transaction")
_TemporalInstantFunctionFeatures_localdatetime_truncate :: Name
_TemporalInstantFunctionFeatures_localdatetime_truncate = (String -> Name
Core.Name String
"localdatetime.truncate")
_TemporalInstantFunctionFeatures_localtime :: Name
_TemporalInstantFunctionFeatures_localtime = (String -> Name
Core.Name String
"localtime")
_TemporalInstantFunctionFeatures_localtime_realtime :: Name
_TemporalInstantFunctionFeatures_localtime_realtime = (String -> Name
Core.Name String
"localtime.realtime")
_TemporalInstantFunctionFeatures_localtime_statement :: Name
_TemporalInstantFunctionFeatures_localtime_statement = (String -> Name
Core.Name String
"localtime.statement")
_TemporalInstantFunctionFeatures_localtime_transaction :: Name
_TemporalInstantFunctionFeatures_localtime_transaction = (String -> Name
Core.Name String
"localtime.transaction")
_TemporalInstantFunctionFeatures_localtime_truncate :: Name
_TemporalInstantFunctionFeatures_localtime_truncate = (String -> Name
Core.Name String
"localtime.truncate")
_TemporalInstantFunctionFeatures_time :: Name
_TemporalInstantFunctionFeatures_time = (String -> Name
Core.Name String
"time")
_TemporalInstantFunctionFeatures_time_realtime :: Name
_TemporalInstantFunctionFeatures_time_realtime = (String -> Name
Core.Name String
"time.realtime")
_TemporalInstantFunctionFeatures_time_statement :: Name
_TemporalInstantFunctionFeatures_time_statement = (String -> Name
Core.Name String
"time.statement")
_TemporalInstantFunctionFeatures_time_transaction :: Name
_TemporalInstantFunctionFeatures_time_transaction = (String -> Name
Core.Name String
"time.transaction")
_TemporalInstantFunctionFeatures_time_truncate :: Name
_TemporalInstantFunctionFeatures_time_truncate = (String -> Name
Core.Name String
"time.truncate")
data TrigonometricFunctionFeatures =
TrigonometricFunctionFeatures {
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAcos :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAsin :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAtan :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAtan2 :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesCos :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesCot :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesDegrees :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesHaversin :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesPi :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesRadians :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesSin :: Bool,
TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesTan :: Bool}
deriving (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
(TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> Eq TrigonometricFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
== :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
$c/= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
/= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
Eq, Eq TrigonometricFunctionFeatures
Eq TrigonometricFunctionFeatures =>
(TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Ordering)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures)
-> (TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures)
-> Ord TrigonometricFunctionFeatures
TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Ordering
TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures
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 :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Ordering
compare :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Ordering
$c< :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
< :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
$c<= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
<= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
$c> :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
> :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
$c>= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
>= :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> Bool
$cmax :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures
max :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures
$cmin :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures
min :: TrigonometricFunctionFeatures
-> TrigonometricFunctionFeatures -> TrigonometricFunctionFeatures
Ord, ReadPrec [TrigonometricFunctionFeatures]
ReadPrec TrigonometricFunctionFeatures
Int -> ReadS TrigonometricFunctionFeatures
ReadS [TrigonometricFunctionFeatures]
(Int -> ReadS TrigonometricFunctionFeatures)
-> ReadS [TrigonometricFunctionFeatures]
-> ReadPrec TrigonometricFunctionFeatures
-> ReadPrec [TrigonometricFunctionFeatures]
-> Read TrigonometricFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TrigonometricFunctionFeatures
readsPrec :: Int -> ReadS TrigonometricFunctionFeatures
$creadList :: ReadS [TrigonometricFunctionFeatures]
readList :: ReadS [TrigonometricFunctionFeatures]
$creadPrec :: ReadPrec TrigonometricFunctionFeatures
readPrec :: ReadPrec TrigonometricFunctionFeatures
$creadListPrec :: ReadPrec [TrigonometricFunctionFeatures]
readListPrec :: ReadPrec [TrigonometricFunctionFeatures]
Read, Int -> TrigonometricFunctionFeatures -> ShowS
[TrigonometricFunctionFeatures] -> ShowS
TrigonometricFunctionFeatures -> String
(Int -> TrigonometricFunctionFeatures -> ShowS)
-> (TrigonometricFunctionFeatures -> String)
-> ([TrigonometricFunctionFeatures] -> ShowS)
-> Show TrigonometricFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrigonometricFunctionFeatures -> ShowS
showsPrec :: Int -> TrigonometricFunctionFeatures -> ShowS
$cshow :: TrigonometricFunctionFeatures -> String
show :: TrigonometricFunctionFeatures -> String
$cshowList :: [TrigonometricFunctionFeatures] -> ShowS
showList :: [TrigonometricFunctionFeatures] -> ShowS
Show)
_TrigonometricFunctionFeatures :: Name
_TrigonometricFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.TrigonometricFunctionFeatures")
_TrigonometricFunctionFeatures_acos :: Name
_TrigonometricFunctionFeatures_acos = (String -> Name
Core.Name String
"acos")
_TrigonometricFunctionFeatures_asin :: Name
_TrigonometricFunctionFeatures_asin = (String -> Name
Core.Name String
"asin")
_TrigonometricFunctionFeatures_atan :: Name
_TrigonometricFunctionFeatures_atan = (String -> Name
Core.Name String
"atan")
_TrigonometricFunctionFeatures_atan2 :: Name
_TrigonometricFunctionFeatures_atan2 = (String -> Name
Core.Name String
"atan2")
_TrigonometricFunctionFeatures_cos :: Name
_TrigonometricFunctionFeatures_cos = (String -> Name
Core.Name String
"cos")
_TrigonometricFunctionFeatures_cot :: Name
_TrigonometricFunctionFeatures_cot = (String -> Name
Core.Name String
"cot")
_TrigonometricFunctionFeatures_degrees :: Name
_TrigonometricFunctionFeatures_degrees = (String -> Name
Core.Name String
"degrees")
_TrigonometricFunctionFeatures_haversin :: Name
_TrigonometricFunctionFeatures_haversin = (String -> Name
Core.Name String
"haversin")
_TrigonometricFunctionFeatures_pi :: Name
_TrigonometricFunctionFeatures_pi = (String -> Name
Core.Name String
"pi")
_TrigonometricFunctionFeatures_radians :: Name
_TrigonometricFunctionFeatures_radians = (String -> Name
Core.Name String
"radians")
_TrigonometricFunctionFeatures_sin :: Name
_TrigonometricFunctionFeatures_sin = (String -> Name
Core.Name String
"sin")
_TrigonometricFunctionFeatures_tan :: Name
_TrigonometricFunctionFeatures_tan = (String -> Name
Core.Name String
"tan")
data VectorFunctionFeatures =
VectorFunctionFeatures {
VectorFunctionFeatures -> Bool
vectorFunctionFeaturesVector_similarity_cosine :: Bool,
VectorFunctionFeatures -> Bool
vectorFunctionFeaturesVector_similarity_euclidean :: Bool}
deriving (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
(VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> Eq VectorFunctionFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
== :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
$c/= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
/= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
Eq, Eq VectorFunctionFeatures
Eq VectorFunctionFeatures =>
(VectorFunctionFeatures -> VectorFunctionFeatures -> Ordering)
-> (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> (VectorFunctionFeatures -> VectorFunctionFeatures -> Bool)
-> (VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures)
-> (VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures)
-> Ord VectorFunctionFeatures
VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
VectorFunctionFeatures -> VectorFunctionFeatures -> Ordering
VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures
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 :: VectorFunctionFeatures -> VectorFunctionFeatures -> Ordering
compare :: VectorFunctionFeatures -> VectorFunctionFeatures -> Ordering
$c< :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
< :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
$c<= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
<= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
$c> :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
> :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
$c>= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
>= :: VectorFunctionFeatures -> VectorFunctionFeatures -> Bool
$cmax :: VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures
max :: VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures
$cmin :: VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures
min :: VectorFunctionFeatures
-> VectorFunctionFeatures -> VectorFunctionFeatures
Ord, ReadPrec [VectorFunctionFeatures]
ReadPrec VectorFunctionFeatures
Int -> ReadS VectorFunctionFeatures
ReadS [VectorFunctionFeatures]
(Int -> ReadS VectorFunctionFeatures)
-> ReadS [VectorFunctionFeatures]
-> ReadPrec VectorFunctionFeatures
-> ReadPrec [VectorFunctionFeatures]
-> Read VectorFunctionFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VectorFunctionFeatures
readsPrec :: Int -> ReadS VectorFunctionFeatures
$creadList :: ReadS [VectorFunctionFeatures]
readList :: ReadS [VectorFunctionFeatures]
$creadPrec :: ReadPrec VectorFunctionFeatures
readPrec :: ReadPrec VectorFunctionFeatures
$creadListPrec :: ReadPrec [VectorFunctionFeatures]
readListPrec :: ReadPrec [VectorFunctionFeatures]
Read, Int -> VectorFunctionFeatures -> ShowS
[VectorFunctionFeatures] -> ShowS
VectorFunctionFeatures -> String
(Int -> VectorFunctionFeatures -> ShowS)
-> (VectorFunctionFeatures -> String)
-> ([VectorFunctionFeatures] -> ShowS)
-> Show VectorFunctionFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VectorFunctionFeatures -> ShowS
showsPrec :: Int -> VectorFunctionFeatures -> ShowS
$cshow :: VectorFunctionFeatures -> String
show :: VectorFunctionFeatures -> String
$cshowList :: [VectorFunctionFeatures] -> ShowS
showList :: [VectorFunctionFeatures] -> ShowS
Show)
_VectorFunctionFeatures :: Name
_VectorFunctionFeatures = (String -> Name
Core.Name String
"hydra/ext/cypher/features.VectorFunctionFeatures")
_VectorFunctionFeatures_vector_similarity_cosine :: Name
_VectorFunctionFeatures_vector_similarity_cosine = (String -> Name
Core.Name String
"vector.similarity.cosine")
_VectorFunctionFeatures_vector_similarity_euclidean :: Name
_VectorFunctionFeatures_vector_similarity_euclidean = (String -> Name
Core.Name String
"vector.similarity.euclidean")
data ListFeatures =
ListFeatures {
ListFeatures -> Bool
listFeaturesListComprehension :: Bool,
ListFeatures -> Bool
listFeaturesListRange :: 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/ext/cypher/features.ListFeatures")
_ListFeatures_listComprehension :: Name
_ListFeatures_listComprehension = (String -> Name
Core.Name String
"listComprehension")
_ListFeatures_listRange :: Name
_ListFeatures_listRange = (String -> Name
Core.Name String
"listRange")
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/ext/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/ext/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 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/ext/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/ext/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/ext/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/ext/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 PathFeatures =
PathFeatures {
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/ext/cypher/features.PathFeatures")
_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/ext/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/ext/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
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/ext/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_none :: Name
_QuantifierFeatures_none = (String -> Name
Core.Name String
"none")
_QuantifierFeatures_single :: Name
_QuantifierFeatures_single = (String -> Name
Core.Name String
"single")
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/ext/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/ext/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/ext/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/ext/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/ext/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 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/ext/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
stringFeaturesContains :: Bool,
StringFeatures -> Bool
stringFeaturesEndsWith :: Bool,
StringFeatures -> Bool
stringFeaturesIn :: Bool,
StringFeatures -> Bool
stringFeaturesStartsWith :: 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/ext/cypher/features.StringFeatures")
_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")
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/ext/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")