| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Ext.Cypher.Features
Description
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.
Synopsis
- data CypherFeatures = CypherFeatures {
- cypherFeaturesArithmetic :: ArithmeticFeatures
- cypherFeaturesAtom :: AtomFeatures
- cypherFeaturesComparison :: ComparisonFeatures
- cypherFeaturesDelete :: DeleteFeatures
- cypherFeaturesFunction :: FunctionFeatures
- cypherFeaturesList :: ListFeatures
- cypherFeaturesLiteral :: LiteralFeatures
- cypherFeaturesLogical :: LogicalFeatures
- cypherFeaturesMatch :: MatchFeatures
- cypherFeaturesMerge :: MergeFeatures
- cypherFeaturesNodePattern :: NodePatternFeatures
- cypherFeaturesNull :: NullFeatures
- cypherFeaturesPath :: PathFeatures
- cypherFeaturesProcedureCall :: ProcedureCallFeatures
- cypherFeaturesProjection :: ProjectionFeatures
- cypherFeaturesQuantifier :: QuantifierFeatures
- cypherFeaturesRangeLiteral :: RangeLiteralFeatures
- cypherFeaturesReading :: ReadingFeatures
- cypherFeaturesRelationshipDirection :: RelationshipDirectionFeatures
- cypherFeaturesRelationshipPattern :: RelationshipPatternFeatures
- cypherFeaturesRemove :: RemoveFeatures
- cypherFeaturesSet :: SetFeatures
- cypherFeaturesString :: StringFeatures
- cypherFeaturesUpdating :: UpdatingFeatures
- _CypherFeatures :: Name
- _CypherFeatures_arithmetic :: Name
- _CypherFeatures_atom :: Name
- _CypherFeatures_comparison :: Name
- _CypherFeatures_delete :: Name
- _CypherFeatures_function :: Name
- _CypherFeatures_list :: Name
- _CypherFeatures_literal :: Name
- _CypherFeatures_logical :: Name
- _CypherFeatures_match :: Name
- _CypherFeatures_merge :: Name
- _CypherFeatures_nodePattern :: Name
- _CypherFeatures_null :: Name
- _CypherFeatures_path :: Name
- _CypherFeatures_procedureCall :: Name
- _CypherFeatures_projection :: Name
- _CypherFeatures_quantifier :: Name
- _CypherFeatures_rangeLiteral :: Name
- _CypherFeatures_reading :: Name
- _CypherFeatures_relationshipDirection :: Name
- _CypherFeatures_relationshipPattern :: Name
- _CypherFeatures_remove :: Name
- _CypherFeatures_set :: Name
- _CypherFeatures_string :: Name
- _CypherFeatures_updating :: 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 {}
- _AtomFeatures :: Name
- _AtomFeatures_caseExpression :: Name
- _AtomFeatures_count :: Name
- _AtomFeatures_existentialSubquery :: Name
- _AtomFeatures_functionInvocation :: Name
- _AtomFeatures_parameter :: Name
- _AtomFeatures_patternComprehension :: Name
- _AtomFeatures_patternPredicate :: 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
- data DeleteFeatures = DeleteFeatures {}
- _DeleteFeatures :: Name
- _DeleteFeatures_delete :: Name
- _DeleteFeatures_detachDelete :: Name
- data FunctionFeatures = FunctionFeatures {
- functionFeaturesAggregateFunction :: AggregateFunctionFeatures
- functionFeaturesDatabaseFunction :: DatabaseFunctionFeatures
- functionFeaturesGenAIFunction :: GenAIFunctionFeatures
- functionFeaturesGraphFunction :: GraphFunctionFeatures
- functionFeaturesListFunction :: ListFunctionFeatures
- functionFeaturesLoadCSVFunction :: LoadCSVFunctionFeatures
- functionFeaturesLogarithmicFunction :: LogarithmicFunctionFeatures
- functionFeaturesNumericFunction :: NumericFunctionFeatures
- functionFeaturesPredicateFunction :: PredicateFunctionFeatures
- functionFeaturesScalarFunction :: ScalarFunctionFeatures
- functionFeaturesSpatialFunction :: SpatialFunctionFeatures
- functionFeaturesStringFunction :: StringFunctionFeatures
- functionFeaturesTemporalDurationFunction :: TemporalDurationFunctionFeatures
- functionFeaturesTemporalInstantFunction :: TemporalInstantFunctionFeatures
- functionFeaturesTrigonometricFunction :: TrigonometricFunctionFeatures
- functionFeaturesVectorFunction :: VectorFunctionFeatures
- _FunctionFeatures :: Name
- _FunctionFeatures_aggregateFunction :: Name
- _FunctionFeatures_databaseFunction :: Name
- _FunctionFeatures_genAIFunction :: Name
- _FunctionFeatures_graphFunction :: Name
- _FunctionFeatures_listFunction :: Name
- _FunctionFeatures_loadCSVFunction :: Name
- _FunctionFeatures_logarithmicFunction :: Name
- _FunctionFeatures_numericFunction :: Name
- _FunctionFeatures_predicateFunction :: Name
- _FunctionFeatures_scalarFunction :: Name
- _FunctionFeatures_spatialFunction :: Name
- _FunctionFeatures_stringFunction :: Name
- _FunctionFeatures_temporalDurationFunction :: Name
- _FunctionFeatures_temporalInstantFunction :: Name
- _FunctionFeatures_trigonometricFunction :: Name
- _FunctionFeatures_vectorFunction :: Name
- data AggregateFunctionFeatures = AggregateFunctionFeatures {
- aggregateFunctionFeaturesAvg :: Bool
- aggregateFunctionFeaturesCollect :: Bool
- aggregateFunctionFeaturesCount :: Bool
- aggregateFunctionFeaturesMax :: Bool
- aggregateFunctionFeaturesMin :: Bool
- aggregateFunctionFeaturesPercentileCont :: Bool
- aggregateFunctionFeaturesPercentileDisc :: Bool
- aggregateFunctionFeaturesStdev :: Bool
- aggregateFunctionFeaturesStdevp :: Bool
- aggregateFunctionFeaturesSum :: Bool
- _AggregateFunctionFeatures :: Name
- _AggregateFunctionFeatures_avg :: Name
- _AggregateFunctionFeatures_collect :: Name
- _AggregateFunctionFeatures_count :: Name
- _AggregateFunctionFeatures_max :: Name
- _AggregateFunctionFeatures_min :: Name
- _AggregateFunctionFeatures_percentileCont :: Name
- _AggregateFunctionFeatures_percentileDisc :: Name
- _AggregateFunctionFeatures_stdev :: Name
- _AggregateFunctionFeatures_stdevp :: Name
- _AggregateFunctionFeatures_sum :: Name
- data DatabaseFunctionFeatures = DatabaseFunctionFeatures {}
- _DatabaseFunctionFeatures :: Name
- _DatabaseFunctionFeatures_db_nameFromElementId :: Name
- data GenAIFunctionFeatures = GenAIFunctionFeatures {}
- _GenAIFunctionFeatures :: Name
- _GenAIFunctionFeatures_genai_vector_encode :: Name
- data GraphFunctionFeatures = GraphFunctionFeatures {}
- _GraphFunctionFeatures :: Name
- _GraphFunctionFeatures_graph_byElementId :: Name
- _GraphFunctionFeatures_graph_byName :: Name
- _GraphFunctionFeatures_graph_names :: Name
- _GraphFunctionFeatures_graph_propertiesByName :: Name
- data ListFunctionFeatures = ListFunctionFeatures {
- listFunctionFeaturesKeys :: Bool
- listFunctionFeaturesLabels :: Bool
- listFunctionFeaturesNodes :: Bool
- listFunctionFeaturesRange :: Bool
- listFunctionFeaturesReduce :: Bool
- listFunctionFeaturesRelationships :: Bool
- listFunctionFeaturesReverse :: Bool
- listFunctionFeaturesTail :: Bool
- listFunctionFeaturesToBooleanList :: Bool
- listFunctionFeaturesToFloatList :: Bool
- listFunctionFeaturesToIntegerList :: Bool
- listFunctionFeaturesToStringList :: Bool
- _ListFunctionFeatures :: Name
- _ListFunctionFeatures_keys :: Name
- _ListFunctionFeatures_labels :: Name
- _ListFunctionFeatures_nodes :: Name
- _ListFunctionFeatures_range :: Name
- _ListFunctionFeatures_reduce :: Name
- _ListFunctionFeatures_relationships :: Name
- _ListFunctionFeatures_reverse :: Name
- _ListFunctionFeatures_tail :: Name
- _ListFunctionFeatures_toBooleanList :: Name
- _ListFunctionFeatures_toFloatList :: Name
- _ListFunctionFeatures_toIntegerList :: Name
- _ListFunctionFeatures_toStringList :: Name
- data LoadCSVFunctionFeatures = LoadCSVFunctionFeatures {}
- _LoadCSVFunctionFeatures :: Name
- _LoadCSVFunctionFeatures_file :: Name
- _LoadCSVFunctionFeatures_linenumber :: Name
- data LogarithmicFunctionFeatures = LogarithmicFunctionFeatures {}
- _LogarithmicFunctionFeatures :: Name
- _LogarithmicFunctionFeatures_e :: Name
- _LogarithmicFunctionFeatures_exp :: Name
- _LogarithmicFunctionFeatures_log :: Name
- _LogarithmicFunctionFeatures_log10 :: Name
- _LogarithmicFunctionFeatures_sqrt :: Name
- data NumericFunctionFeatures = NumericFunctionFeatures {}
- _NumericFunctionFeatures :: Name
- _NumericFunctionFeatures_abs :: Name
- _NumericFunctionFeatures_ceil :: Name
- _NumericFunctionFeatures_floor :: Name
- _NumericFunctionFeatures_isNaN :: Name
- _NumericFunctionFeatures_rand :: Name
- _NumericFunctionFeatures_round :: Name
- _NumericFunctionFeatures_sign :: Name
- data PredicateFunctionFeatures = PredicateFunctionFeatures {}
- _PredicateFunctionFeatures :: Name
- _PredicateFunctionFeatures_all :: Name
- _PredicateFunctionFeatures_any :: Name
- _PredicateFunctionFeatures_exists :: Name
- _PredicateFunctionFeatures_isEmpty :: Name
- _PredicateFunctionFeatures_none :: Name
- _PredicateFunctionFeatures_single :: Name
- data ScalarFunctionFeatures = ScalarFunctionFeatures {
- scalarFunctionFeaturesChar_length :: Bool
- scalarFunctionFeaturesCharacter_length :: Bool
- scalarFunctionFeaturesCoalesce :: Bool
- scalarFunctionFeaturesElementId :: Bool
- scalarFunctionFeaturesEndNode :: Bool
- scalarFunctionFeaturesHead :: Bool
- scalarFunctionFeaturesId :: Bool
- scalarFunctionFeaturesLast :: Bool
- scalarFunctionFeaturesLength :: Bool
- scalarFunctionFeaturesNullIf :: Bool
- scalarFunctionFeaturesProperties :: Bool
- scalarFunctionFeaturesRandomUUID :: Bool
- scalarFunctionFeaturesSize :: Bool
- scalarFunctionFeaturesStartNode :: Bool
- scalarFunctionFeaturesToBoolean :: Bool
- scalarFunctionFeaturesToBooleanOrNull :: Bool
- scalarFunctionFeaturesToFloat :: Bool
- scalarFunctionFeaturesToFloatOrNull :: Bool
- scalarFunctionFeaturesToInteger :: Bool
- scalarFunctionFeaturesToIntegerOrNull :: Bool
- scalarFunctionFeaturesType :: Bool
- scalarFunctionFeaturesValueType :: Bool
- _ScalarFunctionFeatures :: Name
- _ScalarFunctionFeatures_char_length :: Name
- _ScalarFunctionFeatures_character_length :: Name
- _ScalarFunctionFeatures_coalesce :: Name
- _ScalarFunctionFeatures_elementId :: Name
- _ScalarFunctionFeatures_endNode :: Name
- _ScalarFunctionFeatures_head :: Name
- _ScalarFunctionFeatures_id :: Name
- _ScalarFunctionFeatures_last :: Name
- _ScalarFunctionFeatures_length :: Name
- _ScalarFunctionFeatures_nullIf :: Name
- _ScalarFunctionFeatures_properties :: Name
- _ScalarFunctionFeatures_randomUUID :: Name
- _ScalarFunctionFeatures_size :: Name
- _ScalarFunctionFeatures_startNode :: Name
- _ScalarFunctionFeatures_toBoolean :: Name
- _ScalarFunctionFeatures_toBooleanOrNull :: Name
- _ScalarFunctionFeatures_toFloat :: Name
- _ScalarFunctionFeatures_toFloatOrNull :: Name
- _ScalarFunctionFeatures_toInteger :: Name
- _ScalarFunctionFeatures_toIntegerOrNull :: Name
- _ScalarFunctionFeatures_type :: Name
- _ScalarFunctionFeatures_valueType :: Name
- data SpatialFunctionFeatures = SpatialFunctionFeatures {}
- _SpatialFunctionFeatures :: Name
- _SpatialFunctionFeatures_point_distance :: Name
- _SpatialFunctionFeatures_point :: Name
- _SpatialFunctionFeatures_point_withinBBox :: Name
- data StringFunctionFeatures = StringFunctionFeatures {
- stringFunctionFeaturesBtrim :: Bool
- stringFunctionFeaturesLeft :: Bool
- stringFunctionFeaturesLower :: Bool
- stringFunctionFeaturesLtrim :: Bool
- stringFunctionFeaturesNormalize :: Bool
- stringFunctionFeaturesReplace :: Bool
- stringFunctionFeaturesReverse :: Bool
- stringFunctionFeaturesRight :: Bool
- stringFunctionFeaturesRtrim :: Bool
- stringFunctionFeaturesSplit :: Bool
- stringFunctionFeaturesSubstring :: Bool
- stringFunctionFeaturesToLower :: Bool
- stringFunctionFeaturesToString :: Bool
- stringFunctionFeaturesToStringOrNull :: Bool
- stringFunctionFeaturesToUpper :: Bool
- stringFunctionFeaturesTrim :: Bool
- stringFunctionFeaturesUpper :: Bool
- _StringFunctionFeatures :: Name
- _StringFunctionFeatures_btrim :: Name
- _StringFunctionFeatures_left :: Name
- _StringFunctionFeatures_lower :: Name
- _StringFunctionFeatures_ltrim :: Name
- _StringFunctionFeatures_normalize :: Name
- _StringFunctionFeatures_replace :: Name
- _StringFunctionFeatures_reverse :: Name
- _StringFunctionFeatures_right :: Name
- _StringFunctionFeatures_rtrim :: Name
- _StringFunctionFeatures_split :: Name
- _StringFunctionFeatures_substring :: Name
- _StringFunctionFeatures_toLower :: Name
- _StringFunctionFeatures_toString :: Name
- _StringFunctionFeatures_toStringOrNull :: Name
- _StringFunctionFeatures_toUpper :: Name
- _StringFunctionFeatures_trim :: Name
- _StringFunctionFeatures_upper :: Name
- data TemporalDurationFunctionFeatures = TemporalDurationFunctionFeatures {}
- _TemporalDurationFunctionFeatures :: Name
- _TemporalDurationFunctionFeatures_duration :: Name
- _TemporalDurationFunctionFeatures_duration_between :: Name
- _TemporalDurationFunctionFeatures_duration_inDays :: Name
- _TemporalDurationFunctionFeatures_duration_inMonths :: Name
- _TemporalDurationFunctionFeatures_duration_inSeconds :: Name
- data TemporalInstantFunctionFeatures = TemporalInstantFunctionFeatures {
- temporalInstantFunctionFeaturesDate :: Bool
- temporalInstantFunctionFeaturesDate_realtime :: Bool
- temporalInstantFunctionFeaturesDate_statement :: Bool
- temporalInstantFunctionFeaturesDate_transaction :: Bool
- temporalInstantFunctionFeaturesDate_truncate :: Bool
- temporalInstantFunctionFeaturesDatetime :: Bool
- temporalInstantFunctionFeaturesDatetime_fromepoch :: Bool
- temporalInstantFunctionFeaturesDatetime_fromepochmillis :: Bool
- temporalInstantFunctionFeaturesDatetime_realtime :: Bool
- temporalInstantFunctionFeaturesDatetime_statement :: Bool
- temporalInstantFunctionFeaturesDatetime_transaction :: Bool
- temporalInstantFunctionFeaturesDatetime_truncate :: Bool
- temporalInstantFunctionFeaturesLocaldatetime :: Bool
- temporalInstantFunctionFeaturesLocaldatetime_realtime :: Bool
- temporalInstantFunctionFeaturesLocaldatetime_statement :: Bool
- temporalInstantFunctionFeaturesLocaldatetime_transaction :: Bool
- temporalInstantFunctionFeaturesLocaldatetime_truncate :: Bool
- temporalInstantFunctionFeaturesLocaltime :: Bool
- temporalInstantFunctionFeaturesLocaltime_realtime :: Bool
- temporalInstantFunctionFeaturesLocaltime_statement :: Bool
- temporalInstantFunctionFeaturesLocaltime_transaction :: Bool
- temporalInstantFunctionFeaturesLocaltime_truncate :: Bool
- temporalInstantFunctionFeaturesTime :: Bool
- temporalInstantFunctionFeaturesTime_realtime :: Bool
- temporalInstantFunctionFeaturesTime_statement :: Bool
- temporalInstantFunctionFeaturesTime_transaction :: Bool
- temporalInstantFunctionFeaturesTime_truncate :: Bool
- _TemporalInstantFunctionFeatures :: Name
- _TemporalInstantFunctionFeatures_date :: Name
- _TemporalInstantFunctionFeatures_date_realtime :: Name
- _TemporalInstantFunctionFeatures_date_statement :: Name
- _TemporalInstantFunctionFeatures_date_transaction :: Name
- _TemporalInstantFunctionFeatures_date_truncate :: Name
- _TemporalInstantFunctionFeatures_datetime :: Name
- _TemporalInstantFunctionFeatures_datetime_fromepoch :: Name
- _TemporalInstantFunctionFeatures_datetime_fromepochmillis :: Name
- _TemporalInstantFunctionFeatures_datetime_realtime :: Name
- _TemporalInstantFunctionFeatures_datetime_statement :: Name
- _TemporalInstantFunctionFeatures_datetime_transaction :: Name
- _TemporalInstantFunctionFeatures_datetime_truncate :: Name
- _TemporalInstantFunctionFeatures_localdatetime :: Name
- _TemporalInstantFunctionFeatures_localdatetime_realtime :: Name
- _TemporalInstantFunctionFeatures_localdatetime_statement :: Name
- _TemporalInstantFunctionFeatures_localdatetime_transaction :: Name
- _TemporalInstantFunctionFeatures_localdatetime_truncate :: Name
- _TemporalInstantFunctionFeatures_localtime :: Name
- _TemporalInstantFunctionFeatures_localtime_realtime :: Name
- _TemporalInstantFunctionFeatures_localtime_statement :: Name
- _TemporalInstantFunctionFeatures_localtime_transaction :: Name
- _TemporalInstantFunctionFeatures_localtime_truncate :: Name
- _TemporalInstantFunctionFeatures_time :: Name
- _TemporalInstantFunctionFeatures_time_realtime :: Name
- _TemporalInstantFunctionFeatures_time_statement :: Name
- _TemporalInstantFunctionFeatures_time_transaction :: Name
- _TemporalInstantFunctionFeatures_time_truncate :: Name
- data TrigonometricFunctionFeatures = TrigonometricFunctionFeatures {
- trigonometricFunctionFeaturesAcos :: Bool
- trigonometricFunctionFeaturesAsin :: Bool
- trigonometricFunctionFeaturesAtan :: Bool
- trigonometricFunctionFeaturesAtan2 :: Bool
- trigonometricFunctionFeaturesCos :: Bool
- trigonometricFunctionFeaturesCot :: Bool
- trigonometricFunctionFeaturesDegrees :: Bool
- trigonometricFunctionFeaturesHaversin :: Bool
- trigonometricFunctionFeaturesPi :: Bool
- trigonometricFunctionFeaturesRadians :: Bool
- trigonometricFunctionFeaturesSin :: Bool
- trigonometricFunctionFeaturesTan :: Bool
- _TrigonometricFunctionFeatures :: Name
- _TrigonometricFunctionFeatures_acos :: Name
- _TrigonometricFunctionFeatures_asin :: Name
- _TrigonometricFunctionFeatures_atan :: Name
- _TrigonometricFunctionFeatures_atan2 :: Name
- _TrigonometricFunctionFeatures_cos :: Name
- _TrigonometricFunctionFeatures_cot :: Name
- _TrigonometricFunctionFeatures_degrees :: Name
- _TrigonometricFunctionFeatures_haversin :: Name
- _TrigonometricFunctionFeatures_pi :: Name
- _TrigonometricFunctionFeatures_radians :: Name
- _TrigonometricFunctionFeatures_sin :: Name
- _TrigonometricFunctionFeatures_tan :: Name
- data VectorFunctionFeatures = VectorFunctionFeatures {}
- _VectorFunctionFeatures :: Name
- _VectorFunctionFeatures_vector_similarity_cosine :: Name
- _VectorFunctionFeatures_vector_similarity_euclidean :: Name
- data ListFeatures = ListFeatures {}
- _ListFeatures :: Name
- _ListFeatures_listComprehension :: Name
- _ListFeatures_listRange :: 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 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 PathFeatures = PathFeatures {}
- _PathFeatures :: 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_none :: Name
- _QuantifierFeatures_single :: 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 SetFeatures = SetFeatures {}
- _SetFeatures :: Name
- _SetFeatures_propertyEquals :: Name
- _SetFeatures_variableEquals :: Name
- _SetFeatures_variablePlusEquals :: Name
- _SetFeatures_variableWithNodeLabels :: Name
- data StringFeatures = StringFeatures {}
- _StringFeatures :: Name
- _StringFeatures_contains :: Name
- _StringFeatures_endsWith :: Name
- _StringFeatures_in :: Name
- _StringFeatures_startsWith :: Name
- data UpdatingFeatures = UpdatingFeatures {}
- _UpdatingFeatures :: Name
- _UpdatingFeatures_create :: Name
- _UpdatingFeatures_set :: Name
- _UpdatingFeatures_with :: Name
Documentation
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
Instances
| Read CypherFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS CypherFeatures # readList :: ReadS [CypherFeatures] # | |
| Show CypherFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> CypherFeatures -> ShowS # show :: CypherFeatures -> String # showList :: [CypherFeatures] -> ShowS # | |
| Eq CypherFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: CypherFeatures -> CypherFeatures -> Bool # (/=) :: CypherFeatures -> CypherFeatures -> Bool # | |
| Ord CypherFeatures Source # | |
Defined in Hydra.Ext.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 ArithmeticFeatures Source #
Arithmetic operations
Constructors
| ArithmeticFeatures | |
Fields
| |
Instances
data AtomFeatures Source #
Various kinds of atomic expressions
Constructors
| AtomFeatures | |
Fields
| |
Instances
| Read AtomFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS AtomFeatures # readList :: ReadS [AtomFeatures] # | |
| Show AtomFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> AtomFeatures -> ShowS # show :: AtomFeatures -> String # showList :: [AtomFeatures] -> ShowS # | |
| Eq AtomFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features | |
| Ord AtomFeatures Source # | |
Defined in Hydra.Ext.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 #
Comparison operators and functions
Constructors
| ComparisonFeatures | |
Fields
| |
Instances
data DeleteFeatures Source #
Delete operations
Constructors
| DeleteFeatures | |
Fields
| |
Instances
| Read DeleteFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS DeleteFeatures # readList :: ReadS [DeleteFeatures] # | |
| Show DeleteFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> DeleteFeatures -> ShowS # show :: DeleteFeatures -> String # showList :: [DeleteFeatures] -> ShowS # | |
| Eq DeleteFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: DeleteFeatures -> DeleteFeatures -> Bool # (/=) :: DeleteFeatures -> DeleteFeatures -> Bool # | |
| Ord DeleteFeatures Source # | |
Defined in Hydra.Ext.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 FunctionFeatures Source #
Standard Cypher functions
Constructors
Instances
data AggregateFunctionFeatures Source #
Aggregate functions
Constructors
| AggregateFunctionFeatures | |
Fields
| |
Instances
data DatabaseFunctionFeatures Source #
Database functions
Constructors
| DatabaseFunctionFeatures | |
Fields
| |
Instances
data GenAIFunctionFeatures Source #
GenAI functions
Constructors
| GenAIFunctionFeatures | |
Fields
| |
Instances
data GraphFunctionFeatures Source #
Graph functions
Constructors
| GraphFunctionFeatures | |
Fields
| |
Instances
data ListFunctionFeatures Source #
List functions
Constructors
| ListFunctionFeatures | |
Fields
| |
Instances
data LoadCSVFunctionFeatures Source #
Load CSV functions
Constructors
| LoadCSVFunctionFeatures | |
Fields
| |
Instances
data LogarithmicFunctionFeatures Source #
Logarithmic functions
Constructors
| LogarithmicFunctionFeatures | |
Fields
| |
Instances
data NumericFunctionFeatures Source #
Numeric functions
Constructors
| NumericFunctionFeatures | |
Fields
| |
Instances
data PredicateFunctionFeatures Source #
Predicate functions
Constructors
| PredicateFunctionFeatures | |
Fields
| |
Instances
data ScalarFunctionFeatures Source #
Scalar functions
Constructors
| ScalarFunctionFeatures | |
Fields
| |
Instances
data SpatialFunctionFeatures Source #
Spatial functions
Constructors
| SpatialFunctionFeatures | |
Fields
| |
Instances
data StringFunctionFeatures Source #
String functions
Constructors
| StringFunctionFeatures | |
Fields
| |
Instances
data TemporalDurationFunctionFeatures Source #
Temporal duration functions
Constructors
| TemporalDurationFunctionFeatures | |
Fields
| |
Instances
data TemporalInstantFunctionFeatures Source #
Temporal instant functions
Constructors
| TemporalInstantFunctionFeatures | |
Fields
| |
Instances
data TrigonometricFunctionFeatures Source #
Trigonometric functions
Constructors
| TrigonometricFunctionFeatures | |
Fields
| |
Instances
data VectorFunctionFeatures Source #
Vector functions
Constructors
| VectorFunctionFeatures | |
Fields
| |
Instances
data ListFeatures Source #
List functionality
Constructors
| ListFeatures | |
Fields
| |
Instances
| Read ListFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS ListFeatures # readList :: ReadS [ListFeatures] # | |
| Show ListFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> ListFeatures -> ShowS # show :: ListFeatures -> String # showList :: [ListFeatures] -> ShowS # | |
| Eq ListFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features | |
| Ord ListFeatures Source # | |
Defined in Hydra.Ext.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 #
Various types of literal values
Constructors
| LiteralFeatures | |
Fields
| |
Instances
| Read LiteralFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS LiteralFeatures # readList :: ReadS [LiteralFeatures] # | |
| Show LiteralFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> LiteralFeatures -> ShowS # show :: LiteralFeatures -> String # showList :: [LiteralFeatures] -> ShowS # | |
| Eq LiteralFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: LiteralFeatures -> LiteralFeatures -> Bool # (/=) :: LiteralFeatures -> LiteralFeatures -> Bool # | |
| Ord LiteralFeatures Source # | |
Defined in Hydra.Ext.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 #
Logical operations
Constructors
| LogicalFeatures | |
Fields
| |
Instances
| Read LogicalFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS LogicalFeatures # readList :: ReadS [LogicalFeatures] # | |
| Show LogicalFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> LogicalFeatures -> ShowS # show :: LogicalFeatures -> String # showList :: [LogicalFeatures] -> ShowS # | |
| Eq LogicalFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: LogicalFeatures -> LogicalFeatures -> Bool # (/=) :: LogicalFeatures -> LogicalFeatures -> Bool # | |
| Ord LogicalFeatures Source # | |
Defined in Hydra.Ext.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 MatchFeatures Source #
Match queries
Constructors
| MatchFeatures | |
Fields
| |
Instances
| Read MatchFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS MatchFeatures # readList :: ReadS [MatchFeatures] # | |
| Show MatchFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> MatchFeatures -> ShowS # show :: MatchFeatures -> String # showList :: [MatchFeatures] -> ShowS # | |
| Eq MatchFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: MatchFeatures -> MatchFeatures -> Bool # (/=) :: MatchFeatures -> MatchFeatures -> Bool # | |
| Ord MatchFeatures Source # | |
Defined in Hydra.Ext.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 #
Merge operations
Constructors
| MergeFeatures | |
Fields
| |
Instances
| Read MergeFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS MergeFeatures # readList :: ReadS [MergeFeatures] # | |
| Show MergeFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> MergeFeatures -> ShowS # show :: MergeFeatures -> String # showList :: [MergeFeatures] -> ShowS # | |
| Eq MergeFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: MergeFeatures -> MergeFeatures -> Bool # (/=) :: MergeFeatures -> MergeFeatures -> Bool # | |
| Ord MergeFeatures Source # | |
Defined in Hydra.Ext.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 #
Node patterns
Constructors
| NodePatternFeatures | |
Fields
| |
Instances
data NullFeatures Source #
IS NULL / IS NOT NULL checks
Constructors
| NullFeatures | |
Fields
| |
Instances
| Read NullFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS NullFeatures # readList :: ReadS [NullFeatures] # | |
| Show NullFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> NullFeatures -> ShowS # show :: NullFeatures -> String # showList :: [NullFeatures] -> ShowS # | |
| Eq NullFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features | |
| Ord NullFeatures Source # | |
Defined in Hydra.Ext.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 PathFeatures Source #
Path functions only found in OpenCypher
Constructors
| PathFeatures | |
Fields
| |
Instances
| Read PathFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS PathFeatures # readList :: ReadS [PathFeatures] # | |
| Show PathFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> PathFeatures -> ShowS # show :: PathFeatures -> String # showList :: [PathFeatures] -> ShowS # | |
| Eq PathFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features | |
| Ord PathFeatures Source # | |
Defined in Hydra.Ext.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 #
Procedure calls
Constructors
| ProcedureCallFeatures | |
Fields
| |
Instances
data ProjectionFeatures Source #
Projections
Constructors
| ProjectionFeatures | |
Fields
| |
Instances
data QuantifierFeatures Source #
Quantifier expressions
Constructors
| QuantifierFeatures | |
Fields
| |
Instances
data RangeLiteralFeatures Source #
Range literals within relationship patterns
Constructors
| RangeLiteralFeatures | |
Fields
| |
Instances
data ReadingFeatures Source #
Specific syntax related to reading data from the graph.
Constructors
| ReadingFeatures | |
Fields
| |
Instances
| Read ReadingFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS ReadingFeatures # readList :: ReadS [ReadingFeatures] # | |
| Show ReadingFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> ReadingFeatures -> ShowS # show :: ReadingFeatures -> String # showList :: [ReadingFeatures] -> ShowS # | |
| Eq ReadingFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: ReadingFeatures -> ReadingFeatures -> Bool # (/=) :: ReadingFeatures -> ReadingFeatures -> Bool # | |
| Ord ReadingFeatures Source # | |
Defined in Hydra.Ext.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 #
Relationship directions / arrow patterns
Constructors
| RelationshipDirectionFeatures | |
Fields
| |
Instances
data RelationshipPatternFeatures Source #
Relationship patterns
Constructors
| RelationshipPatternFeatures | |
Fields
| |
Instances
data RemoveFeatures Source #
REMOVE operations
Constructors
| RemoveFeatures | |
Fields
| |
Instances
| Read RemoveFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS RemoveFeatures # readList :: ReadS [RemoveFeatures] # | |
| Show RemoveFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> RemoveFeatures -> ShowS # show :: RemoveFeatures -> String # showList :: [RemoveFeatures] -> ShowS # | |
| Eq RemoveFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: RemoveFeatures -> RemoveFeatures -> Bool # (/=) :: RemoveFeatures -> RemoveFeatures -> Bool # | |
| Ord RemoveFeatures Source # | |
Defined in Hydra.Ext.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 SetFeatures Source #
Set definitions
Constructors
| SetFeatures | |
Fields
| |
Instances
| Read SetFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS SetFeatures # readList :: ReadS [SetFeatures] # readPrec :: ReadPrec SetFeatures # readListPrec :: ReadPrec [SetFeatures] # | |
| Show SetFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> SetFeatures -> ShowS # show :: SetFeatures -> String # showList :: [SetFeatures] -> ShowS # | |
| Eq SetFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features | |
| Ord SetFeatures Source # | |
Defined in Hydra.Ext.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 #
String functions/keywords only found in OpenCypher
Constructors
| StringFeatures | |
Fields
| |
Instances
| Read StringFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods readsPrec :: Int -> ReadS StringFeatures # readList :: ReadS [StringFeatures] # | |
| Show StringFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods showsPrec :: Int -> StringFeatures -> ShowS # show :: StringFeatures -> String # showList :: [StringFeatures] -> ShowS # | |
| Eq StringFeatures Source # | |
Defined in Hydra.Ext.Cypher.Features Methods (==) :: StringFeatures -> StringFeatures -> Bool # (/=) :: StringFeatures -> StringFeatures -> Bool # | |
| Ord StringFeatures Source # | |
Defined in Hydra.Ext.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 #
Specific syntax related to updating data in the graph
Constructors
| UpdatingFeatures | |
Fields
| |