-- | A model for characterizing OpenCypher queries and implementations in terms of included features.Based on the OpenCypher grammar and the list of standard Cypher functions at https://neo4j.com/docs/cypher-manual/current/functions. Current as of August 2024.

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

-- | A set of features which characterize an OpenCypher query or implementation. Any features which are omitted from the set are assumed to be unsupported or nonrequired.
data CypherFeatures = 
  CypherFeatures {
    -- | Arithmetic operations
    CypherFeatures -> ArithmeticFeatures
cypherFeaturesArithmetic :: ArithmeticFeatures,
    -- | Various kinds of atomic expressions
    CypherFeatures -> AtomFeatures
cypherFeaturesAtom :: AtomFeatures,
    -- | Comparison operators and functions
    CypherFeatures -> ComparisonFeatures
cypherFeaturesComparison :: ComparisonFeatures,
    -- | Delete operations
    CypherFeatures -> DeleteFeatures
cypherFeaturesDelete :: DeleteFeatures,
    -- | Standard Cypher functions
    CypherFeatures -> FunctionFeatures
cypherFeaturesFunction :: FunctionFeatures,
    -- | List functionality
    CypherFeatures -> ListFeatures
cypherFeaturesList :: ListFeatures,
    -- | Various types of literal values
    CypherFeatures -> LiteralFeatures
cypherFeaturesLiteral :: LiteralFeatures,
    -- | Logical operations
    CypherFeatures -> LogicalFeatures
cypherFeaturesLogical :: LogicalFeatures,
    -- | Match queries
    CypherFeatures -> MatchFeatures
cypherFeaturesMatch :: MatchFeatures,
    -- | Merge operations
    CypherFeatures -> MergeFeatures
cypherFeaturesMerge :: MergeFeatures,
    -- | Node patterns
    CypherFeatures -> NodePatternFeatures
cypherFeaturesNodePattern :: NodePatternFeatures,
    -- | IS NULL / IS NOT NULL checks
    CypherFeatures -> NullFeatures
cypherFeaturesNull :: NullFeatures,
    -- | Path functions only found in OpenCypher
    CypherFeatures -> PathFeatures
cypherFeaturesPath :: PathFeatures,
    -- | Procedure calls
    CypherFeatures -> ProcedureCallFeatures
cypherFeaturesProcedureCall :: ProcedureCallFeatures,
    -- | Projections
    CypherFeatures -> ProjectionFeatures
cypherFeaturesProjection :: ProjectionFeatures,
    -- | Quantifier expressions
    CypherFeatures -> QuantifierFeatures
cypherFeaturesQuantifier :: QuantifierFeatures,
    -- | Range literals within relationship patterns
    CypherFeatures -> RangeLiteralFeatures
cypherFeaturesRangeLiteral :: RangeLiteralFeatures,
    -- | Specific syntax related to reading data from the graph.
    CypherFeatures -> ReadingFeatures
cypherFeaturesReading :: ReadingFeatures,
    -- | Relationship directions / arrow patterns
    CypherFeatures -> RelationshipDirectionFeatures
cypherFeaturesRelationshipDirection :: RelationshipDirectionFeatures,
    -- | Relationship patterns
    CypherFeatures -> RelationshipPatternFeatures
cypherFeaturesRelationshipPattern :: RelationshipPatternFeatures,
    -- | REMOVE operations
    CypherFeatures -> RemoveFeatures
cypherFeaturesRemove :: RemoveFeatures,
    -- | Set definitions
    CypherFeatures -> SetFeatures
cypherFeaturesSet :: SetFeatures,
    -- | String functions/keywords only found in OpenCypher
    CypherFeatures -> StringFeatures
cypherFeaturesString :: StringFeatures,
    -- | Specific syntax related to updating data in the graph
    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")

-- | Arithmetic operations
data ArithmeticFeatures = 
  ArithmeticFeatures {
    -- | The + operator
    ArithmeticFeatures -> Bool
arithmeticFeaturesPlus :: Bool,
    -- | The - operator
    ArithmeticFeatures -> Bool
arithmeticFeaturesMinus :: Bool,
    -- | The * operator
    ArithmeticFeatures -> Bool
arithmeticFeaturesMultiply :: Bool,
    -- | The / operator
    ArithmeticFeatures -> Bool
arithmeticFeaturesDivide :: Bool,
    -- | The % operator
    ArithmeticFeatures -> Bool
arithmeticFeaturesModulus :: Bool,
    -- | The ^ operator
    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")

-- | Various kinds of atomic expressions
data AtomFeatures = 
  AtomFeatures {
    -- | CASE expressions
    AtomFeatures -> Bool
atomFeaturesCaseExpression :: Bool,
    -- | The COUNT (*) expression
    AtomFeatures -> Bool
atomFeaturesCount :: Bool,
    -- | Existential subqueries
    AtomFeatures -> Bool
atomFeaturesExistentialSubquery :: Bool,
    -- | Function invocation
    AtomFeatures -> Bool
atomFeaturesFunctionInvocation :: Bool,
    -- | Parameter expressions
    AtomFeatures -> Bool
atomFeaturesParameter :: Bool,
    -- | Pattern comprehensions
    AtomFeatures -> Bool
atomFeaturesPatternComprehension :: Bool,
    -- | Relationship patterns as subexpressions
    AtomFeatures -> Bool
atomFeaturesPatternPredicate :: Bool,
    -- | Variable expressions (note: included by most if not all implementations).
    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")

-- | Comparison operators and functions
data ComparisonFeatures = 
  ComparisonFeatures {
    -- | The = comparison operator
    ComparisonFeatures -> Bool
comparisonFeaturesEqual :: Bool,
    -- | The > comparison operator
    ComparisonFeatures -> Bool
comparisonFeaturesGreaterThan :: Bool,
    -- | The >= comparison operator
    ComparisonFeatures -> Bool
comparisonFeaturesGreaterThanOrEqual :: Bool,
    -- | The < comparison operator
    ComparisonFeatures -> Bool
comparisonFeaturesLessThan :: Bool,
    -- | The <= comparison operator
    ComparisonFeatures -> Bool
comparisonFeaturesLessThanOrEqual :: Bool,
    -- | The <> comparison operator
    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")

-- | Delete operations
data DeleteFeatures = 
  DeleteFeatures {
    -- | The basic DELETE clause
    DeleteFeatures -> Bool
deleteFeaturesDelete :: Bool,
    -- | The DETACH DELETE clause
    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")

-- | Standard Cypher functions
data FunctionFeatures = 
  FunctionFeatures {
    -- | Aggregate functions
    FunctionFeatures -> AggregateFunctionFeatures
functionFeaturesAggregateFunction :: AggregateFunctionFeatures,
    -- | Database functions
    FunctionFeatures -> DatabaseFunctionFeatures
functionFeaturesDatabaseFunction :: DatabaseFunctionFeatures,
    -- | GenAI functions
    FunctionFeatures -> GenAIFunctionFeatures
functionFeaturesGenAIFunction :: GenAIFunctionFeatures,
    -- | Graph functions
    FunctionFeatures -> GraphFunctionFeatures
functionFeaturesGraphFunction :: GraphFunctionFeatures,
    -- | List functions
    FunctionFeatures -> ListFunctionFeatures
functionFeaturesListFunction :: ListFunctionFeatures,
    -- | Load CSV functions
    FunctionFeatures -> LoadCSVFunctionFeatures
functionFeaturesLoadCSVFunction :: LoadCSVFunctionFeatures,
    -- | Logarithmic functions
    FunctionFeatures -> LogarithmicFunctionFeatures
functionFeaturesLogarithmicFunction :: LogarithmicFunctionFeatures,
    -- | Numeric functions
    FunctionFeatures -> NumericFunctionFeatures
functionFeaturesNumericFunction :: NumericFunctionFeatures,
    -- | Predicate functions
    FunctionFeatures -> PredicateFunctionFeatures
functionFeaturesPredicateFunction :: PredicateFunctionFeatures,
    -- | Scalar functions
    FunctionFeatures -> ScalarFunctionFeatures
functionFeaturesScalarFunction :: ScalarFunctionFeatures,
    -- | Spatial functions
    FunctionFeatures -> SpatialFunctionFeatures
functionFeaturesSpatialFunction :: SpatialFunctionFeatures,
    -- | String functions
    FunctionFeatures -> StringFunctionFeatures
functionFeaturesStringFunction :: StringFunctionFeatures,
    -- | Temporal duration functions
    FunctionFeatures -> TemporalDurationFunctionFeatures
functionFeaturesTemporalDurationFunction :: TemporalDurationFunctionFeatures,
    -- | Temporal instant functions
    FunctionFeatures -> TemporalInstantFunctionFeatures
functionFeaturesTemporalInstantFunction :: TemporalInstantFunctionFeatures,
    -- | Trigonometric functions
    FunctionFeatures -> TrigonometricFunctionFeatures
functionFeaturesTrigonometricFunction :: TrigonometricFunctionFeatures,
    -- | Vector functions
    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")

-- | Aggregate functions
data AggregateFunctionFeatures = 
  AggregateFunctionFeatures {
    -- | The avg() function / AVG. Returns the average of a set of DURATION values.; Returns the average of a set of FLOAT values.; Returns the average of a set of INTEGER values.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesAvg :: Bool,
    -- | The collect() function / COLLECT. Returns a list containing the values returned by an expression.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesCollect :: Bool,
    -- | The count() function / COUNT. Returns the number of values or rows.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesCount :: Bool,
    -- | The max() function / MAX. Returns the maximum value in a set of values.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesMax :: Bool,
    -- | The min() function / MIN. Returns the minimum value in a set of values.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesMin :: Bool,
    -- | The percentileCont() function. Returns the percentile of a value over a group using linear interpolation.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesPercentileCont :: Bool,
    -- | The percentileDisc() function. Returns the nearest FLOAT value to the given percentile over a group using a rounding method.; Returns the nearest INTEGER value to the given percentile over a group using a rounding method.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesPercentileDisc :: Bool,
    -- | The stdev() function. Returns the standard deviation for the given value over a group for a sample of a population.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesStdev :: Bool,
    -- | The stdevp() function. Returns the standard deviation for the given value over a group for an entire population.
    AggregateFunctionFeatures -> Bool
aggregateFunctionFeaturesStdevp :: Bool,
    -- | The sum() function / SUM. Returns the sum of a set of DURATION values.; Returns the sum of a set of FLOAT values.; Returns the sum of a set of INTEGER values.
    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")

-- | Database functions
data DatabaseFunctionFeatures = 
  DatabaseFunctionFeatures {
    -- | The db.nameFromElementId() function. Resolves the database name from the given element id. Introduced in 5.12.
    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")

-- | GenAI functions
data GenAIFunctionFeatures = 
  GenAIFunctionFeatures {
    -- | The genai.vector.encode() function. Encode a given resource as a vector using the named provider. Introduced in 5.17.
    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")

-- | Graph functions
data GraphFunctionFeatures = 
  GraphFunctionFeatures {
    -- | The graph.byElementId() function. Resolves the constituent graph to which a given element id belongs. Introduced in 5.13.
    GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_byElementId :: Bool,
    -- | The graph.byName() function. Resolves a constituent graph by name.
    GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_byName :: Bool,
    -- | The graph.names() function. Returns a list containing the names of all graphs in the current composite database.
    GraphFunctionFeatures -> Bool
graphFunctionFeaturesGraph_names :: Bool,
    -- | The graph.propertiesByName() function. Returns a map containing the properties associated with the given graph.
    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")

-- | List functions
data ListFunctionFeatures = 
  ListFunctionFeatures {
    -- | The keys() function. Returns a LIST<STRING> containing the STRING representations for all the property names of a MAP.; Returns a LIST<STRING> containing the STRING representations for all the property names of a NODE.; Returns a LIST<STRING> containing the STRING representations for all the property names of a RELATIONSHIP.
    ListFunctionFeatures -> Bool
listFunctionFeaturesKeys :: Bool,
    -- | The labels() function. Returns a LIST<STRING> containing the STRING representations for all the labels of a NODE.
    ListFunctionFeatures -> Bool
listFunctionFeaturesLabels :: Bool,
    -- | The nodes() function. Returns a LIST<NODE> containing all the NODE values in a PATH.
    ListFunctionFeatures -> Bool
listFunctionFeaturesNodes :: Bool,
    -- | The range() function. Returns a LIST<INTEGER> comprising all INTEGER values within a specified range.; Returns a LIST<INTEGER> comprising all INTEGER values within a specified range created with step length.
    ListFunctionFeatures -> Bool
listFunctionFeaturesRange :: Bool,
    -- | The reduce() function. Runs an expression against individual elements of a LIST<ANY>, storing the result of the expression in an accumulator.
    ListFunctionFeatures -> Bool
listFunctionFeaturesReduce :: Bool,
    -- | The relationships() function. Returns a LIST<RELATIONSHIP> containing all the RELATIONSHIP values in a PATH.
    ListFunctionFeatures -> Bool
listFunctionFeaturesRelationships :: Bool,
    -- | The reverse() function. Returns a LIST<ANY> in which the order of all elements in the given LIST<ANY> have been reversed.
    ListFunctionFeatures -> Bool
listFunctionFeaturesReverse :: Bool,
    -- | The tail() function. Returns all but the first element in a LIST<ANY>.
    ListFunctionFeatures -> Bool
listFunctionFeaturesTail :: Bool,
    -- | The toBooleanList() function. Converts a LIST<ANY> of values to a LIST<BOOLEAN> values. If any values are not convertible to BOOLEAN they will be null in the LIST<BOOLEAN> returned.
    ListFunctionFeatures -> Bool
listFunctionFeaturesToBooleanList :: Bool,
    -- | The toFloatList() function. Converts a LIST<ANY> to a LIST<FLOAT> values. If any values are not convertible to FLOAT they will be null in the LIST<FLOAT> returned.
    ListFunctionFeatures -> Bool
listFunctionFeaturesToFloatList :: Bool,
    -- | The toIntegerList() function. Converts a LIST<ANY> to a LIST<INTEGER> values. If any values are not convertible to INTEGER they will be null in the LIST<INTEGER> returned.
    ListFunctionFeatures -> Bool
listFunctionFeaturesToIntegerList :: Bool,
    -- | The toStringList() function. Converts a LIST<ANY> to a LIST<STRING> values. If any values are not convertible to STRING they will be null in the LIST<STRING> returned.
    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")

-- | Load CSV functions
data LoadCSVFunctionFeatures = 
  LoadCSVFunctionFeatures {
    -- | The file() function. Returns the absolute path of the file that LOAD CSV is using.
    LoadCSVFunctionFeatures -> Bool
loadCSVFunctionFeaturesFile :: Bool,
    -- | The linenumber() function. Returns the line number that LOAD CSV is currently using.
    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")

-- | Logarithmic functions
data LogarithmicFunctionFeatures = 
  LogarithmicFunctionFeatures {
    -- | The e() function. Returns the base of the natural logarithm, e.
    LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesE :: Bool,
    -- | The exp() function. Returns e^n, where e is the base of the natural logarithm, and n is the value of the argument expression.
    LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesExp :: Bool,
    -- | The log() function. Returns the natural logarithm of a FLOAT.
    LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesLog :: Bool,
    -- | The log10() function. Returns the common logarithm (base 10) of a FLOAT.
    LogarithmicFunctionFeatures -> Bool
logarithmicFunctionFeaturesLog10 :: Bool,
    -- | The sqrt() function. Returns the square root of a FLOAT.
    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")

-- | Numeric functions
data NumericFunctionFeatures = 
  NumericFunctionFeatures {
    -- | The abs() function. Returns the absolute value of a FLOAT.; Returns the absolute value of an INTEGER.
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesAbs :: Bool,
    -- | The ceil() function. Returns the smallest FLOAT that is greater than or equal to a number and equal to an INTEGER.
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesCeil :: Bool,
    -- | The floor() function. Returns the largest FLOAT that is less than or equal to a number and equal to an INTEGER.
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesFloor :: Bool,
    -- | The isNaN() function. Returns true if the floating point number is NaN.; Returns true if the integer number is NaN.
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesIsNaN :: Bool,
    -- | The rand() function. Returns a random FLOAT in the range from 0 (inclusive) to 1 (exclusive).
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesRand :: Bool,
    -- | The round() function. Returns the value of a number rounded to the nearest INTEGER.; Returns the value of a number rounded to the specified precision using rounding mode HALF_UP.; Returns the value of a number rounded to the specified precision with the specified rounding mode.
    NumericFunctionFeatures -> Bool
numericFunctionFeaturesRound :: Bool,
    -- | The sign() function. Returns the signum of a FLOAT: 0 if the number is 0, -1 for any negative number, and 1 for any positive number.; Returns the signum of an INTEGER: 0 if the number is 0, -1 for any negative number, and 1 for any positive number.
    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")

-- | Predicate functions
data PredicateFunctionFeatures = 
  PredicateFunctionFeatures {
    -- | The all() function. Returns true if the predicate holds for all elements in the given LIST<ANY>.
    PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesAll :: Bool,
    -- | The any() function. Returns true if the predicate holds for at least one element in the given LIST<ANY>.
    PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesAny :: Bool,
    -- | The exists() function. Returns true if a match for the pattern exists in the graph.
    PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesExists :: Bool,
    -- | The isEmpty() function. Checks whether a LIST<ANY> is empty.; Checks whether a MAP is empty.; Checks whether a STRING is empty.
    PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesIsEmpty :: Bool,
    -- | The none() function. Returns true if the predicate holds for no element in the given LIST<ANY>.
    PredicateFunctionFeatures -> Bool
predicateFunctionFeaturesNone :: Bool,
    -- | The single() function. Returns true if the predicate holds for exactly one of the elements in the given LIST<ANY>.
    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")

-- | Scalar functions
data ScalarFunctionFeatures = 
  ScalarFunctionFeatures {
    -- | The char_length() function. Returns the number of Unicode characters in a STRING.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesChar_length :: Bool,
    -- | The character_length() function. Returns the number of Unicode characters in a STRING.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesCharacter_length :: Bool,
    -- | The coalesce() function. Returns the first non-null value in a list of expressions.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesCoalesce :: Bool,
    -- | The elementId() function. Returns a node identifier, unique within a specific transaction and DBMS.; Returns a relationship identifier, unique within a specific transaction and DBMS.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesElementId :: Bool,
    -- | The endNode() function. Returns a relationship identifier, unique within a specific transaction and DBMS.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesEndNode :: Bool,
    -- | The head() function. Returns the first element in a LIST<ANY>.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesHead :: Bool,
    -- | The id() function. [Deprecated] Returns the id of a NODE. Replaced by elementId().; [Deprecated] Returns the id of a RELATIONSHIP. Replaced by elementId().
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesId :: Bool,
    -- | The last() function. Returns the last element in a LIST<ANY>.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesLast :: Bool,
    -- | The length() function. Returns the length of a PATH.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesLength :: Bool,
    -- | The nullIf() function. Returns null if the two given parameters are equivalent, otherwise returns the value of the first parameter.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesNullIf :: Bool,
    -- | The properties() function. Returns a MAP containing all the properties of a MAP.; Returns a MAP containing all the properties of a NODE.; Returns a MAP containing all the properties of a RELATIONSHIP.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesProperties :: Bool,
    -- | The randomUUID() function. Generates a random UUID.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesRandomUUID :: Bool,
    -- | The size() function. Returns the number of items in a LIST<ANY>.; Returns the number of Unicode characters in a STRING.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesSize :: Bool,
    -- | The startNode() function. Returns the start NODE of a RELATIONSHIP.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesStartNode :: Bool,
    -- | The toBoolean() function. Converts a STRING value to a BOOLEAN value.; Converts a BOOLEAN value to a BOOLEAN value.; Converts an INTEGER value to a BOOLEAN value.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToBoolean :: Bool,
    -- | The toBooleanOrNull() function. Converts a value to a BOOLEAN value, or null if the value cannot be converted.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToBooleanOrNull :: Bool,
    -- | The toFloat() function. Converts an INTEGER value to a FLOAT value.; Converts a STRING value to a FLOAT value.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToFloat :: Bool,
    -- | The toFloatOrNull() function. Converts a value to a FLOAT value, or null if the value cannot be converted.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToFloatOrNull :: Bool,
    -- | The toInteger() function. Converts a FLOAT value to an INTEGER value.; Converts a BOOLEAN value to an INTEGER value.; Converts a STRING value to an INTEGER value.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToInteger :: Bool,
    -- | The toIntegerOrNull() function. Converts a value to an INTEGER value, or null if the value cannot be converted.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesToIntegerOrNull :: Bool,
    -- | The type() function. Returns a STRING representation of the RELATIONSHIP type.
    ScalarFunctionFeatures -> Bool
scalarFunctionFeaturesType :: Bool,
    -- | The valueType() function. Returns a STRING representation of the most precise value type that the given expression evaluates to.
    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")

-- | Spatial functions
data SpatialFunctionFeatures = 
  SpatialFunctionFeatures {
    -- | The point.distance() function. Returns a FLOAT representing the geodesic distance between any two points in the same CRS.
    SpatialFunctionFeatures -> Bool
spatialFunctionFeaturesPoint_distance :: Bool,
    -- | The point() function. Returns a 2D point object, given two coordinate values in the Cartesian coordinate system.; Returns a 3D point object, given three coordinate values in the Cartesian coordinate system.; Returns a 2D point object, given two coordinate values in the WGS 84 geographic coordinate system.; Returns a 3D point object, given three coordinate values in the WGS 84 geographic coordinate system.
    SpatialFunctionFeatures -> Bool
spatialFunctionFeaturesPoint :: Bool,
    -- | The point.withinBBox() function. Returns true if the provided point is within the bounding box defined by the two provided points, lowerLeft and upperRight.
    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")

-- | String functions
data StringFunctionFeatures = 
  StringFunctionFeatures {
    -- | The btrim() function. Returns the given STRING with leading and trailing whitespace removed.; Returns the given STRING with leading and trailing trimCharacterString characters removed. Introduced in 5.20.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesBtrim :: Bool,
    -- | The left() function. Returns a STRING containing the specified number (INTEGER) of leftmost characters in the given STRING.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesLeft :: Bool,
    -- | The lower() function. Returns the given STRING in lowercase. This function is an alias to the toLower() function, and it was introduced as part of Cypher's GQL conformance. Introduced in 5.21.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesLower :: Bool,
    -- | The ltrim() function. Returns the given STRING with leading whitespace removed.; Returns the given STRING with leading trimCharacterString characters removed. Introduced in 5.20.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesLtrim :: Bool,
    -- | The normalize() function. Returns the given STRING normalized according to the normalization CypherFunctionForm NFC. Introduced in 5.17.; Returns the given STRING normalized according to the specified normalization CypherFunctionForm. Introduced in 5.17.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesNormalize :: Bool,
    -- | The replace() function. Returns a STRING in which all occurrences of a specified search STRING in the given STRING have been replaced by another (specified) replacement STRING.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesReplace :: Bool,
    -- | The reverse() function. Returns a STRING in which the order of all characters in the given STRING have been reversed.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesReverse :: Bool,
    -- | The right() function. Returns a STRING containing the specified number of rightmost characters in the given STRING.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesRight :: Bool,
    -- | The rtrim() function. Returns the given STRING with trailing whitespace removed.; Returns the given STRING with trailing trimCharacterString characters removed. Introduced in 5.20.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesRtrim :: Bool,
    -- | The split() function. Returns a LIST<STRING> resulting from the splitting of the given STRING around matches of the given delimiter.; Returns a LIST<STRING> resulting from the splitting of the given STRING around matches of any of the given delimiters.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesSplit :: Bool,
    -- | The substring() function. Returns a substring of the given STRING, beginning with a 0-based index start.; Returns a substring of a given length from the given STRING, beginning with a 0-based index start.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesSubstring :: Bool,
    -- | The toLower() function. Returns the given STRING in lowercase.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesToLower :: Bool,
    -- | The toString() function. Converts an INTEGER, FLOAT, BOOLEAN, POINT or temporal type (i.e. DATE, ZONED TIME, LOCAL TIME, ZONED DATETIME, LOCAL DATETIME or DURATION) value to a STRING.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesToString :: Bool,
    -- | The toStringOrNull() function. Converts an INTEGER, FLOAT, BOOLEAN, POINT or temporal type (i.e. DATE, ZONED TIME, LOCAL TIME, ZONED DATETIME, LOCAL DATETIME or DURATION) value to a STRING, or null if the value cannot be converted.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesToStringOrNull :: Bool,
    -- | The toUpper() function. Returns the given STRING in uppercase.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesToUpper :: Bool,
    -- | The trim() function. Returns the given STRING with leading and trailing whitespace removed.; Returns the given STRING with the leading and/or trailing trimCharacterString character removed. Introduced in 5.20.
    StringFunctionFeatures -> Bool
stringFunctionFeaturesTrim :: Bool,
    -- | The upper() function. Returns the given STRING in uppercase. This function is an alias to the toUpper() function, and it was introduced as part of Cypher's GQL conformance. Introduced in 5.21.
    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")

-- | Temporal duration functions
data TemporalDurationFunctionFeatures = 
  TemporalDurationFunctionFeatures {
    -- | The duration() function. Constructs a DURATION value.
    TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration :: Bool,
    -- | The duration.between() function. Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in logical units.
    TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_between :: Bool,
    -- | The duration.inDays() function. Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in days.
    TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_inDays :: Bool,
    -- | The duration.inMonths() function. Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in months.
    TemporalDurationFunctionFeatures -> Bool
temporalDurationFunctionFeaturesDuration_inMonths :: Bool,
    -- | The duration.inSeconds() function. Computes the DURATION between the from instant (inclusive) and the to instant (exclusive) in seconds.
    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")

-- | Temporal instant functions
data TemporalInstantFunctionFeatures = 
  TemporalInstantFunctionFeatures {
    -- | The date() function. Creates a DATE instant.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate :: Bool,
    -- | The date.realtime() function. Returns the current DATE instant using the realtime clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_realtime :: Bool,
    -- | The date.statement() function. Returns the current DATE instant using the statement clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_statement :: Bool,
    -- | The date.transaction() function. Returns the current DATE instant using the transaction clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_transaction :: Bool,
    -- | The date.truncate() function. Truncates the given temporal value to a DATE instant using the specified unit.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDate_truncate :: Bool,
    -- | The datetime() function. Creates a ZONED DATETIME instant.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime :: Bool,
    -- | The datetime.fromepoch() function. Creates a ZONED DATETIME given the seconds and nanoseconds since the start of the epoch.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_fromepoch :: Bool,
    -- | The datetime.fromepochmillis() function. Creates a ZONED DATETIME given the milliseconds since the start of the epoch.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_fromepochmillis :: Bool,
    -- | The datetime.realtime() function. Returns the current ZONED DATETIME instant using the realtime clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_realtime :: Bool,
    -- | The datetime.statement() function. Returns the current ZONED DATETIME instant using the statement clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_statement :: Bool,
    -- | The datetime.transaction() function. Returns the current ZONED DATETIME instant using the transaction clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_transaction :: Bool,
    -- | The datetime.truncate() function. Truncates the given temporal value to a ZONED DATETIME instant using the specified unit.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesDatetime_truncate :: Bool,
    -- | The localdatetime() function. Creates a LOCAL DATETIME instant.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime :: Bool,
    -- | The localdatetime.realtime() function. Returns the current LOCAL DATETIME instant using the realtime clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_realtime :: Bool,
    -- | The localdatetime.statement() function. Returns the current LOCAL DATETIME instant using the statement clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_statement :: Bool,
    -- | The localdatetime.transaction() function. Returns the current LOCAL DATETIME instant using the transaction clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_transaction :: Bool,
    -- | The localdatetime.truncate() function. Truncates the given temporal value to a LOCAL DATETIME instant using the specified unit.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaldatetime_truncate :: Bool,
    -- | The localtime() function. Creates a LOCAL TIME instant.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime :: Bool,
    -- | The localtime.realtime() function. Returns the current LOCAL TIME instant using the realtime clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_realtime :: Bool,
    -- | The localtime.statement() function. Returns the current LOCAL TIME instant using the statement clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_statement :: Bool,
    -- | The localtime.transaction() function. Returns the current LOCAL TIME instant using the transaction clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_transaction :: Bool,
    -- | The localtime.truncate() function. Truncates the given temporal value to a LOCAL TIME instant using the specified unit.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesLocaltime_truncate :: Bool,
    -- | The time() function. Creates a ZONED TIME instant.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime :: Bool,
    -- | The time.realtime() function. Returns the current ZONED TIME instant using the realtime clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_realtime :: Bool,
    -- | The time.statement() function. Returns the current ZONED TIME instant using the statement clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_statement :: Bool,
    -- | The time.transaction() function. Returns the current ZONED TIME instant using the transaction clock.
    TemporalInstantFunctionFeatures -> Bool
temporalInstantFunctionFeaturesTime_transaction :: Bool,
    -- | The time.truncate() function. Truncates the given temporal value to a ZONED TIME instant using the specified unit.
    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")

-- | Trigonometric functions
data TrigonometricFunctionFeatures = 
  TrigonometricFunctionFeatures {
    -- | The acos() function. Returns the arccosine of a FLOAT in radians.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAcos :: Bool,
    -- | The asin() function. Returns the arcsine of a FLOAT in radians.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAsin :: Bool,
    -- | The atan() function. Returns the arctangent of a FLOAT in radians.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAtan :: Bool,
    -- | The atan2() function. Returns the arctangent2 of a set of coordinates in radians.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesAtan2 :: Bool,
    -- | The cos() function. Returns the cosine of a FLOAT.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesCos :: Bool,
    -- | The cot() function. Returns the cotangent of a FLOAT.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesCot :: Bool,
    -- | The degrees() function. Converts radians to degrees.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesDegrees :: Bool,
    -- | The haversin() function. Returns half the versine of a number.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesHaversin :: Bool,
    -- | The pi() function. Returns the mathematical constant pi.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesPi :: Bool,
    -- | The radians() function. Converts degrees to radians.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesRadians :: Bool,
    -- | The sin() function. Returns the sine of a FLOAT.
    TrigonometricFunctionFeatures -> Bool
trigonometricFunctionFeaturesSin :: Bool,
    -- | The tan() function. Returns the tangent of a FLOAT.
    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")

-- | Vector functions
data VectorFunctionFeatures = 
  VectorFunctionFeatures {
    -- | The vector.similarity.cosine() function. Returns a FLOAT representing the similarity between the argument vectors based on their cosine.
    VectorFunctionFeatures -> Bool
vectorFunctionFeaturesVector_similarity_cosine :: Bool,
    -- | The vector.similarity.euclidean() function. Returns a FLOAT representing the similarity between the argument vectors based on their Euclidean distance.
    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")

-- | List functionality
data ListFeatures = 
  ListFeatures {
    -- | Basic list comprehensions
    ListFeatures -> Bool
listFeaturesListComprehension :: Bool,
    -- | List range comprehensions (e.g. [1..10])
    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")

-- | Various types of literal values
data LiteralFeatures = 
  LiteralFeatures {
    -- | Boolean literals (note: included by most if not all implementations).
    LiteralFeatures -> Bool
literalFeaturesBoolean :: Bool,
    -- | Double-precision floating-point literals
    LiteralFeatures -> Bool
literalFeaturesDouble :: Bool,
    -- | Integer literals
    LiteralFeatures -> Bool
literalFeaturesInteger :: Bool,
    -- | List literals
    LiteralFeatures -> Bool
literalFeaturesList :: Bool,
    -- | Map literals
    LiteralFeatures -> Bool
literalFeaturesMap :: Bool,
    -- | The NULL literal
    LiteralFeatures -> Bool
literalFeaturesNull :: Bool,
    -- | String literals (note: included by most if not all implementations).
    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")

-- | Logical operations
data LogicalFeatures = 
  LogicalFeatures {
    -- | The AND operator
    LogicalFeatures -> Bool
logicalFeaturesAnd :: Bool,
    -- | The NOT operator
    LogicalFeatures -> Bool
logicalFeaturesNot :: Bool,
    -- | The OR operator
    LogicalFeatures -> Bool
logicalFeaturesOr :: Bool,
    -- | The XOR operator
    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")

-- | Match queries
data MatchFeatures = 
  MatchFeatures {
    -- | The basic (non-optional) MATCH clause
    MatchFeatures -> Bool
matchFeaturesMatch :: Bool,
    -- | OPTIONAL MATCH
    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")

-- | Merge operations
data MergeFeatures = 
  MergeFeatures {
    -- | The basic MERGE clause
    MergeFeatures -> Bool
mergeFeaturesMerge :: Bool,
    -- | MERGE with the ON CREATE action
    MergeFeatures -> Bool
mergeFeaturesMergeOnCreate :: Bool,
    -- | MERGE with the ON MATCH action
    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")

-- | Node patterns
data NodePatternFeatures = 
  NodePatternFeatures {
    -- | Specifying multiple labels in a node pattern
    NodePatternFeatures -> Bool
nodePatternFeaturesMultipleLabels :: Bool,
    -- | Specifying a parameter as part of a node pattern
    NodePatternFeatures -> Bool
nodePatternFeaturesParameter :: Bool,
    -- | Specifying a key/value map of properties in a node pattern
    NodePatternFeatures -> Bool
nodePatternFeaturesPropertyMap :: Bool,
    -- | Binding a variable to a node in a node pattern (note: included by most if not all implementations).
    NodePatternFeatures -> Bool
nodePatternFeaturesVariableNode :: Bool,
    -- | Omitting labels from a node pattern
    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")

-- | IS NULL / IS NOT NULL checks
data NullFeatures = 
  NullFeatures {
    -- | The IS NULL operator
    NullFeatures -> Bool
nullFeaturesIsNull :: Bool,
    -- | The IS NOT NULL operator
    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")

-- | Path functions only found in OpenCypher
data PathFeatures = 
  PathFeatures {
    -- | The shortestPath() function
    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")

-- | Procedure calls
data ProcedureCallFeatures = 
  ProcedureCallFeatures {
    -- | CALL within a query
    ProcedureCallFeatures -> Bool
procedureCallFeaturesInQueryCall :: Bool,
    -- | Standalone / top-level CALL
    ProcedureCallFeatures -> Bool
procedureCallFeaturesStandaloneCall :: Bool,
    -- | The YIELD clause in CALL
    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")

-- | Projections
data ProjectionFeatures = 
  ProjectionFeatures {
    -- | The LIMIT clause
    ProjectionFeatures -> Bool
projectionFeaturesLimit :: Bool,
    -- | The ORDER BY clause
    ProjectionFeatures -> Bool
projectionFeaturesOrderBy :: Bool,
    -- | The DISTINCT keyword
    ProjectionFeatures -> Bool
projectionFeaturesProjectDistinct :: Bool,
    -- | The * projection
    ProjectionFeatures -> Bool
projectionFeaturesProjectAll :: Bool,
    -- | The AS keyword
    ProjectionFeatures -> Bool
projectionFeaturesProjectAs :: Bool,
    -- | The SKIP clause
    ProjectionFeatures -> Bool
projectionFeaturesSkip :: Bool,
    -- | The ASC/ASCENDING and DESC/DESCENDING keywords
    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")

-- | Quantifier expressions
data QuantifierFeatures = 
  QuantifierFeatures {
    -- | The ALL quantifier
    QuantifierFeatures -> Bool
quantifierFeaturesAll :: Bool,
    -- | The ANY quantifier
    QuantifierFeatures -> Bool
quantifierFeaturesAny :: Bool,
    -- | The NONE quantifier
    QuantifierFeatures -> Bool
quantifierFeaturesNone :: Bool,
    -- | The SINGLE quantifier
    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")

-- | Range literals within relationship patterns
data RangeLiteralFeatures = 
  RangeLiteralFeatures {
    -- | Range literals with both lower and upper bounds
    RangeLiteralFeatures -> Bool
rangeLiteralFeaturesBounds :: Bool,
    -- | Range literals providing an exact number of repetitions
    RangeLiteralFeatures -> Bool
rangeLiteralFeaturesExactRange :: Bool,
    -- | Range literals with a lower bound (only)
    RangeLiteralFeatures -> Bool
rangeLiteralFeaturesLowerBound :: Bool,
    -- | The * range literal
    RangeLiteralFeatures -> Bool
rangeLiteralFeaturesStarRange :: Bool,
    -- | Range literals with an upper bound (only)
    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")

-- | Specific syntax related to reading data from the graph.
data ReadingFeatures = 
  ReadingFeatures {
    -- | The UNION operator
    ReadingFeatures -> Bool
readingFeaturesUnion :: Bool,
    -- | The UNION ALL operator
    ReadingFeatures -> Bool
readingFeaturesUnionAll :: Bool,
    -- | The UNWIND clause
    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")

-- | Relationship directions / arrow patterns
data RelationshipDirectionFeatures = 
  RelationshipDirectionFeatures {
    -- | The two-headed arrow (<-[]->) relationship direction
    RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesBoth :: Bool,
    -- | The left arrow (<-[]-) relationship direction
    RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesLeft :: Bool,
    -- | The headless arrow (-[]-) relationship direction
    RelationshipDirectionFeatures -> Bool
relationshipDirectionFeaturesNeither :: Bool,
    -- | The right arrow (-[]->) relationship direction
    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")

-- | Relationship patterns
data RelationshipPatternFeatures = 
  RelationshipPatternFeatures {
    -- | Specifying a disjunction of multiple types in a relationship pattern
    RelationshipPatternFeatures -> Bool
relationshipPatternFeaturesMultipleTypes :: Bool,
    -- | Binding a variable to a relationship in a relationship pattern (note: included by most if not all implementations).
    RelationshipPatternFeatures -> Bool
relationshipPatternFeaturesVariableRelationship :: Bool,
    -- | Omitting types from a relationship pattern
    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")

-- | REMOVE operations
data RemoveFeatures = 
  RemoveFeatures {
    -- | REMOVE Variable:NodeLabels
    RemoveFeatures -> Bool
removeFeaturesByLabel :: Bool,
    -- | REMOVE PropertyExpression
    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")

-- | Set definitions
data SetFeatures = 
  SetFeatures {
    -- | Defining a set using PropertyExpression = Expression
    SetFeatures -> Bool
setFeaturesPropertyEquals :: Bool,
    -- | Defining a set using Variable = Expression
    SetFeatures -> Bool
setFeaturesVariableEquals :: Bool,
    -- | Defining a set using Variable += Expression
    SetFeatures -> Bool
setFeaturesVariablePlusEquals :: Bool,
    -- | Defining a set using Variable:NodeLabels
    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")

-- | String functions/keywords only found in OpenCypher
data StringFeatures = 
  StringFeatures {
    -- | The contains() function / CONTAINS
    StringFeatures -> Bool
stringFeaturesContains :: Bool,
    -- | The endsWith() function / ENDS WITH
    StringFeatures -> Bool
stringFeaturesEndsWith :: Bool,
    -- | The in() function / IN
    StringFeatures -> Bool
stringFeaturesIn :: Bool,
    -- | The startsWith() function / STARTS WITH
    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")

-- | Specific syntax related to updating data in the graph
data UpdatingFeatures = 
  UpdatingFeatures {
    -- | The CREATE clause
    UpdatingFeatures -> Bool
updatingFeaturesCreate :: Bool,
    -- | The SET clause
    UpdatingFeatures -> Bool
updatingFeaturesSet :: Bool,
    -- | Multi-part queries using WITH
    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")