{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier0.Query where
import qualified Data.List as L
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Maybe as Y
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import qualified Hydra.Dsl.Terms as Terms
import Hydra.Dsl.Types as Types
import Hydra.Sources.Core
hydraQueryModule :: Module
hydraQueryModule :: Module
hydraQueryModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
hydraCoreModule] [Module
hydraCoreModule] (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"A model for language-agnostic graph pattern queries"
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/query"
core :: String -> Type
core = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
hydraCoreModule
query :: String -> Type
query = Namespace -> String -> Type
typeref Namespace
ns
def :: String -> Type -> Element
def = Namespace -> String -> Type -> Element
datatype Namespace
ns
elements :: [Element]
elements = [
String -> Type -> Element
def String
"ComparisonConstraint" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"One of several comparison operators" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"equal", String
"notEqual", String
"lessThan", String
"greaterThan", String
"lessThanOrEqual", String
"greaterThanOrEqual"],
String -> Type -> Element
def String
"Edge" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An abstract edge based on a record type" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"type"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of a record type, for which the edge also specifies an out- and an in- projection" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"out"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The field representing the out-projection of the edge. Defaults to 'out'." (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Name",
String
"in"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The field representing the in-projection of the edge. Defaults to 'in'." (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
core String
"Name"],
String -> Type -> Element
def String
"GraphPattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A query pattern which matches within a designated component subgraph" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"graph"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The name of the component graph" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Name",
String
"patterns"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The patterns to match within the subgraph" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (String -> Type
query String
"Pattern")],
String -> Type -> Element
def String
"Node" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A node in a query expression; it may be a term, a variable, or a wildcard" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"term"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A graph term; an expression which is valid in the graph being matched" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Term",
String
"variable"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A query variable, not to be confused with a variable term" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"Variable",
String
"wildcard"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An anonymous variable which we do not care to join across patterns" Type
unit],
String -> Type -> Element
def String
"Path" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A query path" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"step"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A path given by a single step" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"Step",
String
"regex"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A path given by a regular expression quantifier applied to another path" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"RegexSequence",
String
"inverse"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A path given by the inverse of another path" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"Path"],
String -> Type -> Element
def String
"Pattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A query pattern" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"triple"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A subject/predicate/object pattern" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"TriplePattern",
String
"negation"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The negation of another pattern" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"Pattern",
String
"conjunction"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The conjunction ('and') of several other patterns" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (String -> Type
query String
"Pattern"),
String
"disjunction"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The disjunction (inclusive 'or') of several other patterns" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (String -> Type
query String
"Pattern"),
String
"graph"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A pattern which matches within a named subgraph" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"GraphPattern"],
String -> Type -> Element
def String
"Query" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A SELECT-style graph pattern matching query" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"variables"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The variables selected by the query" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
query String
"Variable",
String
"patterns"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"The patterns to be matched" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (String -> Type
query String
"Pattern")],
String -> Type -> Element
def String
"Range" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A range from min to max, inclusive" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"min"String -> Type -> FieldType
>: Type
int32,
String
"max"String -> Type -> FieldType
>: Type
int32],
String -> Type -> Element
def String
"RegexQuantifier" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A regular expression quantifier" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"one"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"No quantifier; matches a single occurrence" Type
unit,
String
"zeroOrOne"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The ? quanifier; matches zero or one occurrence" Type
unit,
String
"zeroOrMore"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The * quantifier; matches any number of occurrences" Type
unit,
String
"oneOrMore"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The + quantifier; matches one or more occurrences" Type
unit,
String
"exactly"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The {n} quantifier; matches exactly n occurrences" Type
int32,
String
"atLeast"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The {n,} quantifier; matches at least n occurrences" Type
int32,
String
"range"String -> Type -> FieldType
>: String -> Type -> Type
doc String
"The {n, m} quantifier; matches between n and m (inclusive) occurrences" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
query String
"Range"],
String -> Type -> Element
def String
"RegexSequence" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A path with a regex quantifier" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"path"String -> Type -> FieldType
>: String -> Type
query String
"Path",
String
"quantifier"String -> Type -> FieldType
>: String -> Type
query String
"RegexQuantifier"],
String -> Type -> Element
def String
"Step" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"An atomic function as part of a query. When applied to a graph, steps are typed by function types." (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"edge"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"An out-to-in traversal of an abstract edge" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"Edge",
String
"project"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A projection from a record through one of its fields" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
core String
"Projection",
String
"compare"String -> Type -> FieldType
>:
String -> Type -> Type
doc String
"A comparison of two terms" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
String -> Type
query String
"ComparisonConstraint"],
String -> Type -> Element
def String
"TriplePattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A subject/predicate/object pattern" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"subject"String -> Type -> FieldType
>: String -> Type
query String
"Node",
String
"predicate"String -> Type -> FieldType
>: String -> Type
query String
"Path",
String
"object"String -> Type -> FieldType
>: String -> Type
query String
"Node"],
String -> Type -> Element
def String
"Variable" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
String -> Type -> Type
doc String
"A query variable"
Type
string]