{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier4.Langs.Tinkerpop.Queries where
import Hydra.Sources.Tier3.All
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import Hydra.Dsl.Types as Types
import Hydra.Sources.Core
import Hydra.Sources.Tier4.Langs.Tinkerpop.PropertyGraph
propertyGraphQueriesModule :: Module
propertyGraphQueriesModule :: Module
propertyGraphQueriesModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module Namespace
ns [Element]
elements [Module
tinkerpopPropertyGraphModule] [Module]
tier0Modules (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just (String
"A common model for pattern-matching queries over property graphs")
where
ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/langs/tinkerpop/queries"
pg :: String -> Type
pg = Namespace -> String -> Type
typeref (Namespace -> String -> Type) -> Namespace -> String -> Type
forall a b. (a -> b) -> a -> b
$ Module -> Namespace
moduleNamespace Module
tinkerpopPropertyGraphModule
q :: String -> Type
q = 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
"AggregationQuery" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"count"String -> Type -> FieldType
>: Type
unit],
String -> Type -> Element
def String
"ApplicationQuery" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
Type -> Type
nonemptyList (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Query",
String -> Type -> Element
def String
"AssociativeExpression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"operator"String -> Type -> FieldType
>: String -> Type
q String
"BinaryOperator",
String
"operands"String -> Type -> FieldType
>: Type -> Type
nonemptyList (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Expression"],
String -> Type -> Element
def String
"BinaryExpression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"left"String -> Type -> FieldType
>: String -> Type
q String
"Expression",
String
"operator"String -> Type -> FieldType
>: String -> Type
q String
"BinaryOperator",
String
"right"String -> Type -> FieldType
>: String -> Type
q String
"Expression"],
String -> Type -> Element
def String
"BinaryBooleanOperator" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"and", String
"or", String
"xor"],
String -> Type -> Element
def String
"BinaryOperator" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"boolean"String -> Type -> FieldType
>: String -> Type
q String
"BinaryBooleanOperator",
String
"comparison"String -> Type -> FieldType
>: String -> Type
q String
"ComparisonOperator",
String
"power"String -> Type -> FieldType
>: Type
unit],
String -> Type -> Element
def String
"Binding" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"key"String -> Type -> FieldType
>: String -> Type
q String
"Variable",
String
"value"String -> Type -> FieldType
>: String -> Type
q String
"Query"],
String -> Type -> Element
def String
"ComparisonOperator" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"eq", String
"neq", String
"lt", String
"lte", String
"gt", String
"gte"],
String -> Type -> Element
def String
"EdgeProjectionPattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"direction"String -> Type -> FieldType
>: String -> Type
pg String
"Direction",
String
"label"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
pg String
"EdgeLabel",
String
"properties"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"PropertyPattern",
String
"vertex"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"VertexPattern"],
String -> Type -> Element
def String
"Expression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"associative"String -> Type -> FieldType
>: String -> Type
q String
"AssociativeExpression",
String
"binary"String -> Type -> FieldType
>: String -> Type
q String
"BinaryExpression",
String
"property"String -> Type -> FieldType
>: String -> Type
q String
"PropertyProjection",
String
"unary"String -> Type -> FieldType
>: String -> Type
q String
"UnaryExpression",
String
"variable"String -> Type -> FieldType
>: String -> Type
q String
"Variable",
String
"vertex"String -> Type -> FieldType
>: String -> Type
q String
"VertexPattern"],
String -> Type -> Element
def String
"LetQuery" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"bindings"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Binding",
String
"environment"String -> Type -> FieldType
>: String -> Type
q String
"Query"],
String -> Type -> Element
def String
"MatchQuery" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"optional"String -> Type -> FieldType
>: Type
boolean,
String
"pattern"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Projection",
String
"where"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Expression"],
String -> Type -> Element
def String
"Projection" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"value"String -> Type -> FieldType
>: String -> Type
q String
"Expression",
String
"as"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Variable"],
String -> Type -> Element
def String
"Projections" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"all"String -> Type -> FieldType
>: Type
boolean,
String
"explicit"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Projection"],
String -> Type -> Element
def String
"PropertyPattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"key"String -> Type -> FieldType
>: String -> Type
pg String
"PropertyKey",
String
"value"String -> Type -> FieldType
>: String -> Type
q String
"PropertyValuePattern"],
String -> Type -> Element
def String
"PropertyProjection" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"base"String -> Type -> FieldType
>: String -> Type
q String
"Expression",
String
"key"String -> Type -> FieldType
>: String -> Type
pg String
"PropertyKey"],
String -> Type -> Element
def String
"PropertyValue" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$ Type
string,
String -> Type -> Element
def String
"PropertyValuePattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"variable"String -> Type -> FieldType
>: String -> Type
pg String
"PropertyKey",
String
"value"String -> Type -> FieldType
>: Type
string],
String -> Type -> Element
def String
"Query" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
union [
String
"application"String -> Type -> FieldType
>: String -> Type
q String
"ApplicationQuery",
String
"aggregate"String -> Type -> FieldType
>: String -> Type
q String
"AggregationQuery",
String
"LetQuery"String -> Type -> FieldType
>: String -> Type
q String
"LetQuery",
String
"match"String -> Type -> FieldType
>: String -> Type
q String
"MatchQuery",
String
"select"String -> Type -> FieldType
>: String -> Type
q String
"SelectQuery",
String
"value"String -> Type -> FieldType
>: Type
string],
String -> Type -> Element
def String
"SelectQuery" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"distinct"String -> Type -> FieldType
>: Type
boolean,
String
"projection"String -> Type -> FieldType
>: String -> Type
q String
"Projections"],
String -> Type -> Element
def String
"UnaryExpression" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"operator"String -> Type -> FieldType
>: String -> Type
q String
"UnaryOperator",
String
"operand"String -> Type -> FieldType
>: String -> Type
q String
"Expression"],
String -> Type -> Element
def String
"UnaryOperator" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[String] -> Type
enum [String
"negate"],
String -> Type -> Element
def String
"Variable" Type
string,
String -> Type -> Element
def String
"VertexPattern" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
String
"variable"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"Variable",
String
"label"String -> Type -> FieldType
>: Type -> Type
optional (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
pg String
"VertexLabel",
String
"properties"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"PropertyPattern",
String
"edges"String -> Type -> FieldType
>: Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ String -> Type
q String
"EdgeProjectionPattern"]]