| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Query
Description
A model for language-agnostic graph pattern queries
Synopsis
- data ComparisonConstraint
- _ComparisonConstraint :: Name
- _ComparisonConstraint_equal :: Name
- _ComparisonConstraint_notEqual :: Name
- _ComparisonConstraint_lessThan :: Name
- _ComparisonConstraint_greaterThan :: Name
- _ComparisonConstraint_lessThanOrEqual :: Name
- _ComparisonConstraint_greaterThanOrEqual :: Name
- data Edge = Edge {}
- _Edge :: Name
- _Edge_type :: Name
- _Edge_out :: Name
- _Edge_in :: Name
- data GraphPattern = GraphPattern {}
- _GraphPattern :: Name
- _GraphPattern_graph :: Name
- _GraphPattern_patterns :: Name
- data Node
- _Node :: Name
- _Node_term :: Name
- _Node_variable :: Name
- _Node_wildcard :: Name
- data Path
- _Path :: Name
- _Path_step :: Name
- _Path_regex :: Name
- _Path_inverse :: Name
- data Pattern
- _Pattern :: Name
- _Pattern_triple :: Name
- _Pattern_negation :: Name
- _Pattern_conjunction :: Name
- _Pattern_disjunction :: Name
- _Pattern_graph :: Name
- data Query = Query {
- queryVariables :: [Variable]
- queryPatterns :: [Pattern]
- _Query :: Name
- _Query_variables :: Name
- _Query_patterns :: Name
- data Range = Range {}
- _Range :: Name
- _Range_min :: Name
- _Range_max :: Name
- data RegexQuantifier
- _RegexQuantifier :: Name
- _RegexQuantifier_one :: Name
- _RegexQuantifier_zeroOrOne :: Name
- _RegexQuantifier_zeroOrMore :: Name
- _RegexQuantifier_oneOrMore :: Name
- _RegexQuantifier_exactly :: Name
- _RegexQuantifier_atLeast :: Name
- _RegexQuantifier_range :: Name
- data RegexSequence = RegexSequence {}
- _RegexSequence :: Name
- _RegexSequence_path :: Name
- _RegexSequence_quantifier :: Name
- data Step
- _Step :: Name
- _Step_edge :: Name
- _Step_project :: Name
- _Step_compare :: Name
- data TriplePattern = TriplePattern {}
- _TriplePattern :: Name
- _TriplePattern_subject :: Name
- _TriplePattern_predicate :: Name
- _TriplePattern_object :: Name
- newtype Variable = Variable {
- unVariable :: String
- _Variable :: Name
Documentation
data ComparisonConstraint Source #
One of several comparison operators
Constructors
| ComparisonConstraintEqual | |
| ComparisonConstraintNotEqual | |
| ComparisonConstraintLessThan | |
| ComparisonConstraintGreaterThan | |
| ComparisonConstraintLessThanOrEqual | |
| ComparisonConstraintGreaterThanOrEqual |
Instances
An abstract edge based on a record type
Constructors
| Edge | |
_Edge_type :: Name Source #
data GraphPattern Source #
A query pattern which matches within a designated component subgraph
Constructors
| GraphPattern | |
Fields
| |
Instances
| Read GraphPattern Source # | |
Defined in Hydra.Query Methods readsPrec :: Int -> ReadS GraphPattern # readList :: ReadS [GraphPattern] # | |
| Show GraphPattern Source # | |
Defined in Hydra.Query Methods showsPrec :: Int -> GraphPattern -> ShowS # show :: GraphPattern -> String # showList :: [GraphPattern] -> ShowS # | |
| Eq GraphPattern Source # | |
Defined in Hydra.Query | |
| Ord GraphPattern Source # | |
Defined in Hydra.Query Methods compare :: GraphPattern -> GraphPattern -> Ordering # (<) :: GraphPattern -> GraphPattern -> Bool # (<=) :: GraphPattern -> GraphPattern -> Bool # (>) :: GraphPattern -> GraphPattern -> Bool # (>=) :: GraphPattern -> GraphPattern -> Bool # max :: GraphPattern -> GraphPattern -> GraphPattern # min :: GraphPattern -> GraphPattern -> GraphPattern # | |
_GraphPattern :: Name Source #
A node in a query expression; it may be a term, a variable, or a wildcard
Constructors
| NodeTerm Term | A graph term; an expression which is valid in the graph being matched |
| NodeVariable Variable | A query variable, not to be confused with a variable term |
| NodeWildcard | An anonymous variable which we do not care to join across patterns |
_Node_term :: Name Source #
A query path
Constructors
| PathStep Step | A path given by a single step |
| PathRegex RegexSequence | A path given by a regular expression quantifier applied to another path |
| PathInverse Path | A path given by the inverse of another path |
_Path_step :: Name Source #
_Path_regex :: Name Source #
_Path_inverse :: Name Source #
A query pattern
Constructors
| PatternTriple TriplePattern | A subjectpredicateobject pattern |
| PatternNegation Pattern | The negation of another pattern |
| PatternConjunction [Pattern] | The conjunction ( |
| PatternDisjunction [Pattern] | The disjunction (inclusive |
| PatternGraph GraphPattern | A pattern which matches within a named subgraph |
A SELECT-style graph pattern matching query
Constructors
| Query | |
Fields
| |
A range from min to max, inclusive
_Range_min :: Name Source #
_Range_max :: Name Source #
data RegexQuantifier Source #
A regular expression quantifier
Constructors
| RegexQuantifierOne | No quantifier; matches a single occurrence |
| RegexQuantifierZeroOrOne | The ? quanifier; matches zero or one occurrence |
| RegexQuantifierZeroOrMore | The * quantifier; matches any number of occurrences |
| RegexQuantifierOneOrMore | The + quantifier; matches one or more occurrences |
| RegexQuantifierExactly Int | The {n} quantifier; matches exactly n occurrences |
| RegexQuantifierAtLeast Int | The {n,} quantifier; matches at least n occurrences |
| RegexQuantifierRange Range | The {n, m} quantifier; matches between n and m (inclusive) occurrences |
Instances
| Read RegexQuantifier Source # | |
Defined in Hydra.Query Methods readsPrec :: Int -> ReadS RegexQuantifier # readList :: ReadS [RegexQuantifier] # | |
| Show RegexQuantifier Source # | |
Defined in Hydra.Query Methods showsPrec :: Int -> RegexQuantifier -> ShowS # show :: RegexQuantifier -> String # showList :: [RegexQuantifier] -> ShowS # | |
| Eq RegexQuantifier Source # | |
Defined in Hydra.Query Methods (==) :: RegexQuantifier -> RegexQuantifier -> Bool # (/=) :: RegexQuantifier -> RegexQuantifier -> Bool # | |
| Ord RegexQuantifier Source # | |
Defined in Hydra.Query Methods compare :: RegexQuantifier -> RegexQuantifier -> Ordering # (<) :: RegexQuantifier -> RegexQuantifier -> Bool # (<=) :: RegexQuantifier -> RegexQuantifier -> Bool # (>) :: RegexQuantifier -> RegexQuantifier -> Bool # (>=) :: RegexQuantifier -> RegexQuantifier -> Bool # max :: RegexQuantifier -> RegexQuantifier -> RegexQuantifier # min :: RegexQuantifier -> RegexQuantifier -> RegexQuantifier # | |
data RegexSequence Source #
A path with a regex quantifier
Constructors
| RegexSequence | |
Fields | |
Instances
| Read RegexSequence Source # | |
Defined in Hydra.Query Methods readsPrec :: Int -> ReadS RegexSequence # readList :: ReadS [RegexSequence] # | |
| Show RegexSequence Source # | |
Defined in Hydra.Query Methods showsPrec :: Int -> RegexSequence -> ShowS # show :: RegexSequence -> String # showList :: [RegexSequence] -> ShowS # | |
| Eq RegexSequence Source # | |
Defined in Hydra.Query Methods (==) :: RegexSequence -> RegexSequence -> Bool # (/=) :: RegexSequence -> RegexSequence -> Bool # | |
| Ord RegexSequence Source # | |
Defined in Hydra.Query Methods compare :: RegexSequence -> RegexSequence -> Ordering # (<) :: RegexSequence -> RegexSequence -> Bool # (<=) :: RegexSequence -> RegexSequence -> Bool # (>) :: RegexSequence -> RegexSequence -> Bool # (>=) :: RegexSequence -> RegexSequence -> Bool # max :: RegexSequence -> RegexSequence -> RegexSequence # min :: RegexSequence -> RegexSequence -> RegexSequence # | |
An atomic function as part of a query. When applied to a graph, steps are typed by function types.
Constructors
| StepEdge Edge | An out-to-in traversal of an abstract edge |
| StepProject Projection | A projection from a record through one of its fields |
| StepCompare ComparisonConstraint | A comparison of two terms |
_Step_edge :: Name Source #
_Step_project :: Name Source #
_Step_compare :: Name Source #
data TriplePattern Source #
A subjectpredicateobject pattern
Constructors
| TriplePattern | |
Fields | |
Instances
| Read TriplePattern Source # | |
Defined in Hydra.Query Methods readsPrec :: Int -> ReadS TriplePattern # readList :: ReadS [TriplePattern] # | |
| Show TriplePattern Source # | |
Defined in Hydra.Query Methods showsPrec :: Int -> TriplePattern -> ShowS # show :: TriplePattern -> String # showList :: [TriplePattern] -> ShowS # | |
| Eq TriplePattern Source # | |
Defined in Hydra.Query Methods (==) :: TriplePattern -> TriplePattern -> Bool # (/=) :: TriplePattern -> TriplePattern -> Bool # | |
| Ord TriplePattern Source # | |
Defined in Hydra.Query Methods compare :: TriplePattern -> TriplePattern -> Ordering # (<) :: TriplePattern -> TriplePattern -> Bool # (<=) :: TriplePattern -> TriplePattern -> Bool # (>) :: TriplePattern -> TriplePattern -> Bool # (>=) :: TriplePattern -> TriplePattern -> Bool # max :: TriplePattern -> TriplePattern -> TriplePattern # min :: TriplePattern -> TriplePattern -> TriplePattern # | |