Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Langs.Cypher.Features
Description
A model for characterizing OpenCypher queries and implementations in terms of included features.
Synopsis
- data AggregateFeatures = AggregateFeatures {}
- _AggregateFeatures :: Name
- _AggregateFeatures_avg :: Name
- _AggregateFeatures_collect :: Name
- _AggregateFeatures_count :: Name
- _AggregateFeatures_max :: Name
- _AggregateFeatures_min :: Name
- _AggregateFeatures_percentileCont :: Name
- _AggregateFeatures_percentileDisc :: Name
- _AggregateFeatures_stdev :: Name
- _AggregateFeatures_sum :: Name
- data ArithmeticFeatures = ArithmeticFeatures {}
- _ArithmeticFeatures :: Name
- _ArithmeticFeatures_plus :: Name
- _ArithmeticFeatures_minus :: Name
- _ArithmeticFeatures_multiply :: Name
- _ArithmeticFeatures_divide :: Name
- _ArithmeticFeatures_modulus :: Name
- _ArithmeticFeatures_powerOf :: Name
- data AtomFeatures = AtomFeatures {
- atomFeaturesCaseExpression :: Bool
- atomFeaturesCount :: Bool
- atomFeaturesExistentialSubquery :: Bool
- atomFeaturesFunctionInvocation :: Bool
- atomFeaturesList :: Maybe ListFeatures
- atomFeaturesLiteral :: Maybe LiteralFeatures
- atomFeaturesParameter :: Bool
- atomFeaturesPatternComprehension :: Bool
- atomFeaturesPatternPredicate :: Bool
- atomFeaturesQuantifier :: Maybe QuantifierFeatures
- atomFeaturesVariable :: Bool
- _AtomFeatures :: Name
- _AtomFeatures_caseExpression :: Name
- _AtomFeatures_count :: Name
- _AtomFeatures_existentialSubquery :: Name
- _AtomFeatures_functionInvocation :: Name
- _AtomFeatures_list :: Name
- _AtomFeatures_literal :: Name
- _AtomFeatures_parameter :: Name
- _AtomFeatures_patternComprehension :: Name
- _AtomFeatures_patternPredicate :: Name
- _AtomFeatures_quantifier :: Name
- _AtomFeatures_variable :: Name
- data ComparisonFeatures = ComparisonFeatures {}
- _ComparisonFeatures :: Name
- _ComparisonFeatures_equal :: Name
- _ComparisonFeatures_greaterThan :: Name
- _ComparisonFeatures_greaterThanOrEqual :: Name
- _ComparisonFeatures_lessThan :: Name
- _ComparisonFeatures_lessThanOrEqual :: Name
- _ComparisonFeatures_notEqual :: Name
- _ComparisonFeatures_nullIf :: Name
- data CypherFeatures = CypherFeatures {
- cypherFeaturesAggregate :: Maybe AggregateFeatures
- cypherFeaturesArithmetic :: Maybe ArithmeticFeatures
- cypherFeaturesAtom :: Maybe AtomFeatures
- cypherFeaturesComparison :: Maybe ComparisonFeatures
- cypherFeaturesDelete :: Maybe DeleteFeatures
- cypherFeaturesElement :: Maybe ElementFeatures
- cypherFeaturesLogical :: Maybe LogicalFeatures
- cypherFeaturesMap :: Maybe MapFeatures
- cypherFeaturesMatch :: Maybe MatchFeatures
- cypherFeaturesMerge :: Maybe MergeFeatures
- cypherFeaturesNodePattern :: Maybe NodePatternFeatures
- cypherFeaturesNull :: Maybe NullFeatures
- cypherFeaturesNumeric :: Maybe NumericFeatures
- cypherFeaturesPath :: Maybe PathFeatures
- cypherFeaturesProcedureCall :: Maybe ProcedureCallFeatures
- cypherFeaturesProjection :: Maybe ProjectionFeatures
- cypherFeaturesRandomness :: Maybe RandomnessFeatures
- cypherFeaturesRangeLiteral :: Maybe RangeLiteralFeatures
- cypherFeaturesReading :: Maybe ReadingFeatures
- cypherFeaturesRelationshipDirection :: Maybe RelationshipDirectionFeatures
- cypherFeaturesRelationshipPattern :: Maybe RelationshipPatternFeatures
- cypherFeaturesRemove :: Maybe RemoveFeatures
- cypherFeaturesSchema :: Maybe SchemaFeatures
- cypherFeaturesSet :: Maybe SetFeatures
- cypherFeaturesString :: Maybe StringFeatures
- cypherFeaturesUpdating :: Maybe UpdatingFeatures
- _CypherFeatures :: Name
- _CypherFeatures_aggregate :: Name
- _CypherFeatures_arithmetic :: Name
- _CypherFeatures_atom :: Name
- _CypherFeatures_comparison :: Name
- _CypherFeatures_delete :: Name
- _CypherFeatures_element :: Name
- _CypherFeatures_logical :: Name
- _CypherFeatures_map :: Name
- _CypherFeatures_match :: Name
- _CypherFeatures_merge :: Name
- _CypherFeatures_nodePattern :: Name
- _CypherFeatures_null :: Name
- _CypherFeatures_numeric :: Name
- _CypherFeatures_path :: Name
- _CypherFeatures_procedureCall :: Name
- _CypherFeatures_projection :: Name
- _CypherFeatures_randomness :: Name
- _CypherFeatures_rangeLiteral :: Name
- _CypherFeatures_reading :: Name
- _CypherFeatures_relationshipDirection :: Name
- _CypherFeatures_relationshipPattern :: Name
- _CypherFeatures_remove :: Name
- _CypherFeatures_schema :: Name
- _CypherFeatures_set :: Name
- _CypherFeatures_string :: Name
- _CypherFeatures_updating :: Name
- data DeleteFeatures = DeleteFeatures {}
- _DeleteFeatures :: Name
- _DeleteFeatures_delete :: Name
- _DeleteFeatures_detachDelete :: Name
- data ElementFeatures = ElementFeatures {}
- _ElementFeatures :: Name
- _ElementFeatures_elementId :: Name
- _ElementFeatures_endNode :: Name
- _ElementFeatures_labels :: Name
- _ElementFeatures_properties :: Name
- _ElementFeatures_startNode :: Name
- data ListFeatures = ListFeatures {
- listFeaturesAll :: Bool
- listFeaturesAny :: Bool
- listFeaturesCoalesce :: Bool
- listFeaturesIsEmpty :: Bool
- listFeaturesHead :: Bool
- listFeaturesLast :: Bool
- listFeaturesListComprehension :: Bool
- listFeaturesListRange :: Bool
- listFeaturesNone :: Bool
- listFeaturesReduce :: Bool
- listFeaturesReverse :: Bool
- listFeaturesSingle :: Bool
- listFeaturesSize :: Bool
- listFeaturesTail :: Bool
- listFeaturesToBooleanList :: Bool
- listFeaturesToFloatList :: Bool
- listFeaturesToIntegerList :: Bool
- listFeaturesToStringList :: Bool
- _ListFeatures :: Name
- _ListFeatures_all :: Name
- _ListFeatures_any :: Name
- _ListFeatures_coalesce :: Name
- _ListFeatures_isEmpty :: Name
- _ListFeatures_head :: Name
- _ListFeatures_last :: Name
- _ListFeatures_listComprehension :: Name
- _ListFeatures_listRange :: Name
- _ListFeatures_none :: Name
- _ListFeatures_reduce :: Name
- _ListFeatures_reverse :: Name
- _ListFeatures_single :: Name
- _ListFeatures_size :: Name
- _ListFeatures_tail :: Name
- _ListFeatures_toBooleanList :: Name
- _ListFeatures_toFloatList :: Name
- _ListFeatures_toIntegerList :: Name
- _ListFeatures_toStringList :: Name
- data LiteralFeatures = LiteralFeatures {}
- _LiteralFeatures :: Name
- _LiteralFeatures_boolean :: Name
- _LiteralFeatures_double :: Name
- _LiteralFeatures_integer :: Name
- _LiteralFeatures_list :: Name
- _LiteralFeatures_map :: Name
- _LiteralFeatures_null :: Name
- _LiteralFeatures_string :: Name
- data LogicalFeatures = LogicalFeatures {}
- _LogicalFeatures :: Name
- _LogicalFeatures_and :: Name
- _LogicalFeatures_not :: Name
- _LogicalFeatures_or :: Name
- _LogicalFeatures_xor :: Name
- data MapFeatures = MapFeatures {}
- _MapFeatures :: Name
- _MapFeatures_keys :: Name
- data MatchFeatures = MatchFeatures {}
- _MatchFeatures :: Name
- _MatchFeatures_match :: Name
- _MatchFeatures_optionalMatch :: Name
- data MergeFeatures = MergeFeatures {}
- _MergeFeatures :: Name
- _MergeFeatures_merge :: Name
- _MergeFeatures_mergeOnCreate :: Name
- _MergeFeatures_mergeOnMatch :: Name
- data NodePatternFeatures = NodePatternFeatures {}
- _NodePatternFeatures :: Name
- _NodePatternFeatures_multipleLabels :: Name
- _NodePatternFeatures_parameter :: Name
- _NodePatternFeatures_propertyMap :: Name
- _NodePatternFeatures_variableNode :: Name
- _NodePatternFeatures_wildcardLabel :: Name
- data NullFeatures = NullFeatures {}
- _NullFeatures :: Name
- _NullFeatures_isNull :: Name
- _NullFeatures_isNotNull :: Name
- data NumericFeatures = NumericFeatures {
- numericFeaturesAbs :: Bool
- numericFeaturesCeil :: Bool
- numericFeaturesE :: Bool
- numericFeaturesExp :: Bool
- numericFeaturesFloor :: Bool
- numericFeaturesIsNaN :: Bool
- numericFeaturesLog :: Bool
- numericFeaturesLog10 :: Bool
- numericFeaturesRange :: Bool
- numericFeaturesRound :: Bool
- numericFeaturesSign :: Bool
- numericFeaturesSqrt :: Bool
- _NumericFeatures :: Name
- _NumericFeatures_abs :: Name
- _NumericFeatures_ceil :: Name
- _NumericFeatures_e :: Name
- _NumericFeatures_exp :: Name
- _NumericFeatures_floor :: Name
- _NumericFeatures_isNaN :: Name
- _NumericFeatures_log :: Name
- _NumericFeatures_log10 :: Name
- _NumericFeatures_range :: Name
- _NumericFeatures_round :: Name
- _NumericFeatures_sign :: Name
- _NumericFeatures_sqrt :: Name
- data PathFeatures = PathFeatures {}
- _PathFeatures :: Name
- _PathFeatures_length :: Name
- _PathFeatures_nodes :: Name
- _PathFeatures_relationships :: Name
- _PathFeatures_shortestPath :: Name
- data ProcedureCallFeatures = ProcedureCallFeatures {}
- _ProcedureCallFeatures :: Name
- _ProcedureCallFeatures_inQueryCall :: Name
- _ProcedureCallFeatures_standaloneCall :: Name
- _ProcedureCallFeatures_yield :: Name
- data ProjectionFeatures = ProjectionFeatures {}
- _ProjectionFeatures :: Name
- _ProjectionFeatures_limit :: Name
- _ProjectionFeatures_orderBy :: Name
- _ProjectionFeatures_projectDistinct :: Name
- _ProjectionFeatures_projectAll :: Name
- _ProjectionFeatures_projectAs :: Name
- _ProjectionFeatures_skip :: Name
- _ProjectionFeatures_sortOrder :: Name
- data QuantifierFeatures = QuantifierFeatures {}
- _QuantifierFeatures :: Name
- _QuantifierFeatures_all :: Name
- _QuantifierFeatures_any :: Name
- _QuantifierFeatures_exists :: Name
- _QuantifierFeatures_none :: Name
- _QuantifierFeatures_single :: Name
- data RandomnessFeatures = RandomnessFeatures {}
- _RandomnessFeatures :: Name
- _RandomnessFeatures_rand :: Name
- _RandomnessFeatures_randomUUID :: Name
- data RangeLiteralFeatures = RangeLiteralFeatures {}
- _RangeLiteralFeatures :: Name
- _RangeLiteralFeatures_bounds :: Name
- _RangeLiteralFeatures_exactRange :: Name
- _RangeLiteralFeatures_lowerBound :: Name
- _RangeLiteralFeatures_starRange :: Name
- _RangeLiteralFeatures_upperBound :: Name
- data ReadingFeatures = ReadingFeatures {}
- _ReadingFeatures :: Name
- _ReadingFeatures_union :: Name
- _ReadingFeatures_unionAll :: Name
- _ReadingFeatures_unwind :: Name
- data RelationshipDirectionFeatures = RelationshipDirectionFeatures {}
- _RelationshipDirectionFeatures :: Name
- _RelationshipDirectionFeatures_both :: Name
- _RelationshipDirectionFeatures_left :: Name
- _RelationshipDirectionFeatures_neither :: Name
- _RelationshipDirectionFeatures_right :: Name
- data RelationshipPatternFeatures = RelationshipPatternFeatures {}
- _RelationshipPatternFeatures :: Name
- _RelationshipPatternFeatures_multipleTypes :: Name
- _RelationshipPatternFeatures_variableRelationship :: Name
- _RelationshipPatternFeatures_wildcardType :: Name
- data RemoveFeatures = RemoveFeatures {}
- _RemoveFeatures :: Name
- _RemoveFeatures_byLabel :: Name
- _RemoveFeatures_byProperty :: Name
- data SchemaFeatures = SchemaFeatures {}
- _SchemaFeatures :: Name
- _SchemaFeatures_type :: Name
- _SchemaFeatures_valueType :: Name
- data SetFeatures = SetFeatures {}
- _SetFeatures :: Name
- _SetFeatures_propertyEquals :: Name
- _SetFeatures_variableEquals :: Name
- _SetFeatures_variablePlusEquals :: Name
- _SetFeatures_variableWithNodeLabels :: Name
- data StringFeatures = StringFeatures {
- stringFeaturesChar_length :: Bool
- stringFeaturesCharacter_length :: Bool
- stringFeaturesContains :: Bool
- stringFeaturesEndsWith :: Bool
- stringFeaturesIn :: Bool
- stringFeaturesStartsWith :: Bool
- stringFeaturesToBoolean :: Bool
- stringFeaturesToBooleanOrNull :: Bool
- stringFeaturesToFloat :: Bool
- stringFeaturesToFloatOrNull :: Bool
- stringFeaturesToInteger :: Bool
- stringFeaturesToIntegerOrNull :: Bool
- _StringFeatures :: Name
- _StringFeatures_char_length :: Name
- _StringFeatures_character_length :: Name
- _StringFeatures_contains :: Name
- _StringFeatures_endsWith :: Name
- _StringFeatures_in :: Name
- _StringFeatures_startsWith :: Name
- _StringFeatures_toBoolean :: Name
- _StringFeatures_toBooleanOrNull :: Name
- _StringFeatures_toFloat :: Name
- _StringFeatures_toFloatOrNull :: Name
- _StringFeatures_toInteger :: Name
- _StringFeatures_toIntegerOrNull :: Name
- data UpdatingFeatures = UpdatingFeatures {}
- _UpdatingFeatures :: Name
- _UpdatingFeatures_create :: Name
- _UpdatingFeatures_set :: Name
- _UpdatingFeatures_with :: Name
Documentation
data AggregateFeatures Source #
A set of features for aggregation functions.
Constructors
AggregateFeatures | |
Fields
|
Instances
data ArithmeticFeatures Source #
A set of features for arithmetic operations.
Constructors
ArithmeticFeatures | |
Fields
|
Instances
data AtomFeatures Source #
A set of features for various kinds of atomic expressions.
Constructors
AtomFeatures | |
Fields
|
Instances
Read AtomFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS AtomFeatures # readList :: ReadS [AtomFeatures] # | |
Show AtomFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> AtomFeatures -> ShowS # show :: AtomFeatures -> String # showList :: [AtomFeatures] -> ShowS # | |
Eq AtomFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord AtomFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: AtomFeatures -> AtomFeatures -> Ordering # (<) :: AtomFeatures -> AtomFeatures -> Bool # (<=) :: AtomFeatures -> AtomFeatures -> Bool # (>) :: AtomFeatures -> AtomFeatures -> Bool # (>=) :: AtomFeatures -> AtomFeatures -> Bool # max :: AtomFeatures -> AtomFeatures -> AtomFeatures # min :: AtomFeatures -> AtomFeatures -> AtomFeatures # |
_AtomFeatures :: Name Source #
data ComparisonFeatures Source #
A set of features for comparison operators and functions.
Constructors
ComparisonFeatures | |
Fields
|
Instances
data CypherFeatures Source #
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.
Constructors
CypherFeatures | |
Fields
|
Instances
Read CypherFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS CypherFeatures # readList :: ReadS [CypherFeatures] # | |
Show CypherFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> CypherFeatures -> ShowS # show :: CypherFeatures -> String # showList :: [CypherFeatures] -> ShowS # | |
Eq CypherFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: CypherFeatures -> CypherFeatures -> Bool # (/=) :: CypherFeatures -> CypherFeatures -> Bool # | |
Ord CypherFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: CypherFeatures -> CypherFeatures -> Ordering # (<) :: CypherFeatures -> CypherFeatures -> Bool # (<=) :: CypherFeatures -> CypherFeatures -> Bool # (>) :: CypherFeatures -> CypherFeatures -> Bool # (>=) :: CypherFeatures -> CypherFeatures -> Bool # max :: CypherFeatures -> CypherFeatures -> CypherFeatures # min :: CypherFeatures -> CypherFeatures -> CypherFeatures # |
data DeleteFeatures Source #
A set of features for delete operations.
Constructors
DeleteFeatures | |
Fields
|
Instances
Read DeleteFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS DeleteFeatures # readList :: ReadS [DeleteFeatures] # | |
Show DeleteFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> DeleteFeatures -> ShowS # show :: DeleteFeatures -> String # showList :: [DeleteFeatures] -> ShowS # | |
Eq DeleteFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: DeleteFeatures -> DeleteFeatures -> Bool # (/=) :: DeleteFeatures -> DeleteFeatures -> Bool # | |
Ord DeleteFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: DeleteFeatures -> DeleteFeatures -> Ordering # (<) :: DeleteFeatures -> DeleteFeatures -> Bool # (<=) :: DeleteFeatures -> DeleteFeatures -> Bool # (>) :: DeleteFeatures -> DeleteFeatures -> Bool # (>=) :: DeleteFeatures -> DeleteFeatures -> Bool # max :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures # min :: DeleteFeatures -> DeleteFeatures -> DeleteFeatures # |
data ElementFeatures Source #
A set of features for element functions.
Constructors
ElementFeatures | |
Fields
|
Instances
Read ElementFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS ElementFeatures # readList :: ReadS [ElementFeatures] # | |
Show ElementFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> ElementFeatures -> ShowS # show :: ElementFeatures -> String # showList :: [ElementFeatures] -> ShowS # | |
Eq ElementFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: ElementFeatures -> ElementFeatures -> Bool # (/=) :: ElementFeatures -> ElementFeatures -> Bool # | |
Ord ElementFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: ElementFeatures -> ElementFeatures -> Ordering # (<) :: ElementFeatures -> ElementFeatures -> Bool # (<=) :: ElementFeatures -> ElementFeatures -> Bool # (>) :: ElementFeatures -> ElementFeatures -> Bool # (>=) :: ElementFeatures -> ElementFeatures -> Bool # max :: ElementFeatures -> ElementFeatures -> ElementFeatures # min :: ElementFeatures -> ElementFeatures -> ElementFeatures # |
data ListFeatures Source #
A set of features for list functionality.
Constructors
ListFeatures | |
Fields
|
Instances
Read ListFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS ListFeatures # readList :: ReadS [ListFeatures] # | |
Show ListFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> ListFeatures -> ShowS # show :: ListFeatures -> String # showList :: [ListFeatures] -> ShowS # | |
Eq ListFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord ListFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: ListFeatures -> ListFeatures -> Ordering # (<) :: ListFeatures -> ListFeatures -> Bool # (<=) :: ListFeatures -> ListFeatures -> Bool # (>) :: ListFeatures -> ListFeatures -> Bool # (>=) :: ListFeatures -> ListFeatures -> Bool # max :: ListFeatures -> ListFeatures -> ListFeatures # min :: ListFeatures -> ListFeatures -> ListFeatures # |
_ListFeatures :: Name Source #
data LiteralFeatures Source #
A set of features for various types of literal values.
Constructors
LiteralFeatures | |
Fields
|
Instances
Read LiteralFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS LiteralFeatures # readList :: ReadS [LiteralFeatures] # | |
Show LiteralFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> LiteralFeatures -> ShowS # show :: LiteralFeatures -> String # showList :: [LiteralFeatures] -> ShowS # | |
Eq LiteralFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: LiteralFeatures -> LiteralFeatures -> Bool # (/=) :: LiteralFeatures -> LiteralFeatures -> Bool # | |
Ord LiteralFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: LiteralFeatures -> LiteralFeatures -> Ordering # (<) :: LiteralFeatures -> LiteralFeatures -> Bool # (<=) :: LiteralFeatures -> LiteralFeatures -> Bool # (>) :: LiteralFeatures -> LiteralFeatures -> Bool # (>=) :: LiteralFeatures -> LiteralFeatures -> Bool # max :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures # min :: LiteralFeatures -> LiteralFeatures -> LiteralFeatures # |
data LogicalFeatures Source #
A set of features for logical operations.
Constructors
LogicalFeatures | |
Fields
|
Instances
Read LogicalFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS LogicalFeatures # readList :: ReadS [LogicalFeatures] # | |
Show LogicalFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> LogicalFeatures -> ShowS # show :: LogicalFeatures -> String # showList :: [LogicalFeatures] -> ShowS # | |
Eq LogicalFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: LogicalFeatures -> LogicalFeatures -> Bool # (/=) :: LogicalFeatures -> LogicalFeatures -> Bool # | |
Ord LogicalFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: LogicalFeatures -> LogicalFeatures -> Ordering # (<) :: LogicalFeatures -> LogicalFeatures -> Bool # (<=) :: LogicalFeatures -> LogicalFeatures -> Bool # (>) :: LogicalFeatures -> LogicalFeatures -> Bool # (>=) :: LogicalFeatures -> LogicalFeatures -> Bool # max :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures # min :: LogicalFeatures -> LogicalFeatures -> LogicalFeatures # |
data MapFeatures Source #
A set of features for property map functions.
Constructors
MapFeatures | |
Fields
|
Instances
Read MapFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS MapFeatures # readList :: ReadS [MapFeatures] # readPrec :: ReadPrec MapFeatures # readListPrec :: ReadPrec [MapFeatures] # | |
Show MapFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> MapFeatures -> ShowS # show :: MapFeatures -> String # showList :: [MapFeatures] -> ShowS # | |
Eq MapFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord MapFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: MapFeatures -> MapFeatures -> Ordering # (<) :: MapFeatures -> MapFeatures -> Bool # (<=) :: MapFeatures -> MapFeatures -> Bool # (>) :: MapFeatures -> MapFeatures -> Bool # (>=) :: MapFeatures -> MapFeatures -> Bool # max :: MapFeatures -> MapFeatures -> MapFeatures # min :: MapFeatures -> MapFeatures -> MapFeatures # |
_MapFeatures :: Name Source #
data MatchFeatures Source #
A set of features for match queries.
Constructors
MatchFeatures | |
Fields
|
Instances
Read MatchFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS MatchFeatures # readList :: ReadS [MatchFeatures] # | |
Show MatchFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> MatchFeatures -> ShowS # show :: MatchFeatures -> String # showList :: [MatchFeatures] -> ShowS # | |
Eq MatchFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: MatchFeatures -> MatchFeatures -> Bool # (/=) :: MatchFeatures -> MatchFeatures -> Bool # | |
Ord MatchFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: MatchFeatures -> MatchFeatures -> Ordering # (<) :: MatchFeatures -> MatchFeatures -> Bool # (<=) :: MatchFeatures -> MatchFeatures -> Bool # (>) :: MatchFeatures -> MatchFeatures -> Bool # (>=) :: MatchFeatures -> MatchFeatures -> Bool # max :: MatchFeatures -> MatchFeatures -> MatchFeatures # min :: MatchFeatures -> MatchFeatures -> MatchFeatures # |
data MergeFeatures Source #
A set of features for merge operations.
Constructors
MergeFeatures | |
Fields
|
Instances
Read MergeFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS MergeFeatures # readList :: ReadS [MergeFeatures] # | |
Show MergeFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> MergeFeatures -> ShowS # show :: MergeFeatures -> String # showList :: [MergeFeatures] -> ShowS # | |
Eq MergeFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: MergeFeatures -> MergeFeatures -> Bool # (/=) :: MergeFeatures -> MergeFeatures -> Bool # | |
Ord MergeFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: MergeFeatures -> MergeFeatures -> Ordering # (<) :: MergeFeatures -> MergeFeatures -> Bool # (<=) :: MergeFeatures -> MergeFeatures -> Bool # (>) :: MergeFeatures -> MergeFeatures -> Bool # (>=) :: MergeFeatures -> MergeFeatures -> Bool # max :: MergeFeatures -> MergeFeatures -> MergeFeatures # min :: MergeFeatures -> MergeFeatures -> MergeFeatures # |
data NodePatternFeatures Source #
A set of features for node patterns.
Constructors
NodePatternFeatures | |
Fields
|
Instances
data NullFeatures Source #
A set of features for IS NULL / IS NOT NULL checks.
Constructors
NullFeatures | |
Fields
|
Instances
Read NullFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS NullFeatures # readList :: ReadS [NullFeatures] # | |
Show NullFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> NullFeatures -> ShowS # show :: NullFeatures -> String # showList :: [NullFeatures] -> ShowS # | |
Eq NullFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord NullFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: NullFeatures -> NullFeatures -> Ordering # (<) :: NullFeatures -> NullFeatures -> Bool # (<=) :: NullFeatures -> NullFeatures -> Bool # (>) :: NullFeatures -> NullFeatures -> Bool # (>=) :: NullFeatures -> NullFeatures -> Bool # max :: NullFeatures -> NullFeatures -> NullFeatures # min :: NullFeatures -> NullFeatures -> NullFeatures # |
_NullFeatures :: Name Source #
data NumericFeatures Source #
A set of features for numeric functions.
Constructors
NumericFeatures | |
Fields
|
Instances
Read NumericFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS NumericFeatures # readList :: ReadS [NumericFeatures] # | |
Show NumericFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> NumericFeatures -> ShowS # show :: NumericFeatures -> String # showList :: [NumericFeatures] -> ShowS # | |
Eq NumericFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: NumericFeatures -> NumericFeatures -> Bool # (/=) :: NumericFeatures -> NumericFeatures -> Bool # | |
Ord NumericFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: NumericFeatures -> NumericFeatures -> Ordering # (<) :: NumericFeatures -> NumericFeatures -> Bool # (<=) :: NumericFeatures -> NumericFeatures -> Bool # (>) :: NumericFeatures -> NumericFeatures -> Bool # (>=) :: NumericFeatures -> NumericFeatures -> Bool # max :: NumericFeatures -> NumericFeatures -> NumericFeatures # min :: NumericFeatures -> NumericFeatures -> NumericFeatures # |
data PathFeatures Source #
A set of features for path functions.
Constructors
PathFeatures | |
Fields
|
Instances
Read PathFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS PathFeatures # readList :: ReadS [PathFeatures] # | |
Show PathFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> PathFeatures -> ShowS # show :: PathFeatures -> String # showList :: [PathFeatures] -> ShowS # | |
Eq PathFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord PathFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: PathFeatures -> PathFeatures -> Ordering # (<) :: PathFeatures -> PathFeatures -> Bool # (<=) :: PathFeatures -> PathFeatures -> Bool # (>) :: PathFeatures -> PathFeatures -> Bool # (>=) :: PathFeatures -> PathFeatures -> Bool # max :: PathFeatures -> PathFeatures -> PathFeatures # min :: PathFeatures -> PathFeatures -> PathFeatures # |
_PathFeatures :: Name Source #
data ProcedureCallFeatures Source #
A set of features for procedure calls.
Constructors
ProcedureCallFeatures | |
Fields
|
Instances
data ProjectionFeatures Source #
A set of features for projections.
Constructors
ProjectionFeatures | |
Fields
|
Instances
data QuantifierFeatures Source #
A set of features for quantifier expressions.
Constructors
QuantifierFeatures | |
Fields
|
Instances
data RandomnessFeatures Source #
A set of features for random value generation.
Constructors
RandomnessFeatures | |
Fields
|
Instances
data RangeLiteralFeatures Source #
A set of features for range literals within relationship patterns.
Constructors
RangeLiteralFeatures | |
Fields
|
Instances
data ReadingFeatures Source #
A set of features for specific syntax related to reading data from the graph..
Constructors
ReadingFeatures | |
Fields
|
Instances
Read ReadingFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS ReadingFeatures # readList :: ReadS [ReadingFeatures] # | |
Show ReadingFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> ReadingFeatures -> ShowS # show :: ReadingFeatures -> String # showList :: [ReadingFeatures] -> ShowS # | |
Eq ReadingFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: ReadingFeatures -> ReadingFeatures -> Bool # (/=) :: ReadingFeatures -> ReadingFeatures -> Bool # | |
Ord ReadingFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: ReadingFeatures -> ReadingFeatures -> Ordering # (<) :: ReadingFeatures -> ReadingFeatures -> Bool # (<=) :: ReadingFeatures -> ReadingFeatures -> Bool # (>) :: ReadingFeatures -> ReadingFeatures -> Bool # (>=) :: ReadingFeatures -> ReadingFeatures -> Bool # max :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures # min :: ReadingFeatures -> ReadingFeatures -> ReadingFeatures # |
data RelationshipDirectionFeatures Source #
A set of features for relationship directions / arrow patterns.
Constructors
RelationshipDirectionFeatures | |
Fields
|
Instances
data RelationshipPatternFeatures Source #
A set of features for relationship patterns.
Constructors
RelationshipPatternFeatures | |
Fields
|
Instances
data RemoveFeatures Source #
A set of features for REMOVE operations.
Constructors
RemoveFeatures | |
Fields
|
Instances
Read RemoveFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS RemoveFeatures # readList :: ReadS [RemoveFeatures] # | |
Show RemoveFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> RemoveFeatures -> ShowS # show :: RemoveFeatures -> String # showList :: [RemoveFeatures] -> ShowS # | |
Eq RemoveFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: RemoveFeatures -> RemoveFeatures -> Bool # (/=) :: RemoveFeatures -> RemoveFeatures -> Bool # | |
Ord RemoveFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: RemoveFeatures -> RemoveFeatures -> Ordering # (<) :: RemoveFeatures -> RemoveFeatures -> Bool # (<=) :: RemoveFeatures -> RemoveFeatures -> Bool # (>) :: RemoveFeatures -> RemoveFeatures -> Bool # (>=) :: RemoveFeatures -> RemoveFeatures -> Bool # max :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures # min :: RemoveFeatures -> RemoveFeatures -> RemoveFeatures # |
data SchemaFeatures Source #
A set of features for schema functions.
Constructors
SchemaFeatures | |
Fields
|
Instances
Read SchemaFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS SchemaFeatures # readList :: ReadS [SchemaFeatures] # | |
Show SchemaFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> SchemaFeatures -> ShowS # show :: SchemaFeatures -> String # showList :: [SchemaFeatures] -> ShowS # | |
Eq SchemaFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: SchemaFeatures -> SchemaFeatures -> Bool # (/=) :: SchemaFeatures -> SchemaFeatures -> Bool # | |
Ord SchemaFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: SchemaFeatures -> SchemaFeatures -> Ordering # (<) :: SchemaFeatures -> SchemaFeatures -> Bool # (<=) :: SchemaFeatures -> SchemaFeatures -> Bool # (>) :: SchemaFeatures -> SchemaFeatures -> Bool # (>=) :: SchemaFeatures -> SchemaFeatures -> Bool # max :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures # min :: SchemaFeatures -> SchemaFeatures -> SchemaFeatures # |
data SetFeatures Source #
A set of features for set definitions.
Constructors
SetFeatures | |
Fields
|
Instances
Read SetFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS SetFeatures # readList :: ReadS [SetFeatures] # readPrec :: ReadPrec SetFeatures # readListPrec :: ReadPrec [SetFeatures] # | |
Show SetFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> SetFeatures -> ShowS # show :: SetFeatures -> String # showList :: [SetFeatures] -> ShowS # | |
Eq SetFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features | |
Ord SetFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: SetFeatures -> SetFeatures -> Ordering # (<) :: SetFeatures -> SetFeatures -> Bool # (<=) :: SetFeatures -> SetFeatures -> Bool # (>) :: SetFeatures -> SetFeatures -> Bool # (>=) :: SetFeatures -> SetFeatures -> Bool # max :: SetFeatures -> SetFeatures -> SetFeatures # min :: SetFeatures -> SetFeatures -> SetFeatures # |
_SetFeatures :: Name Source #
data StringFeatures Source #
A set of features for string functions.
Constructors
StringFeatures | |
Fields
|
Instances
Read StringFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods readsPrec :: Int -> ReadS StringFeatures # readList :: ReadS [StringFeatures] # | |
Show StringFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods showsPrec :: Int -> StringFeatures -> ShowS # show :: StringFeatures -> String # showList :: [StringFeatures] -> ShowS # | |
Eq StringFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods (==) :: StringFeatures -> StringFeatures -> Bool # (/=) :: StringFeatures -> StringFeatures -> Bool # | |
Ord StringFeatures Source # | |
Defined in Hydra.Langs.Cypher.Features Methods compare :: StringFeatures -> StringFeatures -> Ordering # (<) :: StringFeatures -> StringFeatures -> Bool # (<=) :: StringFeatures -> StringFeatures -> Bool # (>) :: StringFeatures -> StringFeatures -> Bool # (>=) :: StringFeatures -> StringFeatures -> Bool # max :: StringFeatures -> StringFeatures -> StringFeatures # min :: StringFeatures -> StringFeatures -> StringFeatures # |
data UpdatingFeatures Source #
A set of features for specific syntax related to updating data in the graph.
Constructors
UpdatingFeatures | |
Fields
|