-- | A common model for pattern-matching queries over property graphs

module Hydra.Langs.Tinkerpop.Queries where

import qualified Hydra.Core as Core
import qualified Hydra.Langs.Tinkerpop.PropertyGraph as PropertyGraph
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S

data AggregationQuery = 
  AggregationQueryCount 
  deriving (AggregationQuery -> AggregationQuery -> Bool
(AggregationQuery -> AggregationQuery -> Bool)
-> (AggregationQuery -> AggregationQuery -> Bool)
-> Eq AggregationQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AggregationQuery -> AggregationQuery -> Bool
== :: AggregationQuery -> AggregationQuery -> Bool
$c/= :: AggregationQuery -> AggregationQuery -> Bool
/= :: AggregationQuery -> AggregationQuery -> Bool
Eq, Eq AggregationQuery
Eq AggregationQuery =>
(AggregationQuery -> AggregationQuery -> Ordering)
-> (AggregationQuery -> AggregationQuery -> Bool)
-> (AggregationQuery -> AggregationQuery -> Bool)
-> (AggregationQuery -> AggregationQuery -> Bool)
-> (AggregationQuery -> AggregationQuery -> Bool)
-> (AggregationQuery -> AggregationQuery -> AggregationQuery)
-> (AggregationQuery -> AggregationQuery -> AggregationQuery)
-> Ord AggregationQuery
AggregationQuery -> AggregationQuery -> Bool
AggregationQuery -> AggregationQuery -> Ordering
AggregationQuery -> AggregationQuery -> AggregationQuery
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AggregationQuery -> AggregationQuery -> Ordering
compare :: AggregationQuery -> AggregationQuery -> Ordering
$c< :: AggregationQuery -> AggregationQuery -> Bool
< :: AggregationQuery -> AggregationQuery -> Bool
$c<= :: AggregationQuery -> AggregationQuery -> Bool
<= :: AggregationQuery -> AggregationQuery -> Bool
$c> :: AggregationQuery -> AggregationQuery -> Bool
> :: AggregationQuery -> AggregationQuery -> Bool
$c>= :: AggregationQuery -> AggregationQuery -> Bool
>= :: AggregationQuery -> AggregationQuery -> Bool
$cmax :: AggregationQuery -> AggregationQuery -> AggregationQuery
max :: AggregationQuery -> AggregationQuery -> AggregationQuery
$cmin :: AggregationQuery -> AggregationQuery -> AggregationQuery
min :: AggregationQuery -> AggregationQuery -> AggregationQuery
Ord, ReadPrec [AggregationQuery]
ReadPrec AggregationQuery
Int -> ReadS AggregationQuery
ReadS [AggregationQuery]
(Int -> ReadS AggregationQuery)
-> ReadS [AggregationQuery]
-> ReadPrec AggregationQuery
-> ReadPrec [AggregationQuery]
-> Read AggregationQuery
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AggregationQuery
readsPrec :: Int -> ReadS AggregationQuery
$creadList :: ReadS [AggregationQuery]
readList :: ReadS [AggregationQuery]
$creadPrec :: ReadPrec AggregationQuery
readPrec :: ReadPrec AggregationQuery
$creadListPrec :: ReadPrec [AggregationQuery]
readListPrec :: ReadPrec [AggregationQuery]
Read, Int -> AggregationQuery -> ShowS
[AggregationQuery] -> ShowS
AggregationQuery -> String
(Int -> AggregationQuery -> ShowS)
-> (AggregationQuery -> String)
-> ([AggregationQuery] -> ShowS)
-> Show AggregationQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AggregationQuery -> ShowS
showsPrec :: Int -> AggregationQuery -> ShowS
$cshow :: AggregationQuery -> String
show :: AggregationQuery -> String
$cshowList :: [AggregationQuery] -> ShowS
showList :: [AggregationQuery] -> ShowS
Show)

_AggregationQuery :: Name
_AggregationQuery = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.AggregationQuery")

_AggregationQuery_count :: Name
_AggregationQuery_count = (String -> Name
Core.Name String
"count")

newtype ApplicationQuery = 
  ApplicationQuery {
    ApplicationQuery -> [Query]
unApplicationQuery :: [Query]}
  deriving (ApplicationQuery -> ApplicationQuery -> Bool
(ApplicationQuery -> ApplicationQuery -> Bool)
-> (ApplicationQuery -> ApplicationQuery -> Bool)
-> Eq ApplicationQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationQuery -> ApplicationQuery -> Bool
== :: ApplicationQuery -> ApplicationQuery -> Bool
$c/= :: ApplicationQuery -> ApplicationQuery -> Bool
/= :: ApplicationQuery -> ApplicationQuery -> Bool
Eq, Eq ApplicationQuery
Eq ApplicationQuery =>
(ApplicationQuery -> ApplicationQuery -> Ordering)
-> (ApplicationQuery -> ApplicationQuery -> Bool)
-> (ApplicationQuery -> ApplicationQuery -> Bool)
-> (ApplicationQuery -> ApplicationQuery -> Bool)
-> (ApplicationQuery -> ApplicationQuery -> Bool)
-> (ApplicationQuery -> ApplicationQuery -> ApplicationQuery)
-> (ApplicationQuery -> ApplicationQuery -> ApplicationQuery)
-> Ord ApplicationQuery
ApplicationQuery -> ApplicationQuery -> Bool
ApplicationQuery -> ApplicationQuery -> Ordering
ApplicationQuery -> ApplicationQuery -> ApplicationQuery
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ApplicationQuery -> ApplicationQuery -> Ordering
compare :: ApplicationQuery -> ApplicationQuery -> Ordering
$c< :: ApplicationQuery -> ApplicationQuery -> Bool
< :: ApplicationQuery -> ApplicationQuery -> Bool
$c<= :: ApplicationQuery -> ApplicationQuery -> Bool
<= :: ApplicationQuery -> ApplicationQuery -> Bool
$c> :: ApplicationQuery -> ApplicationQuery -> Bool
> :: ApplicationQuery -> ApplicationQuery -> Bool
$c>= :: ApplicationQuery -> ApplicationQuery -> Bool
>= :: ApplicationQuery -> ApplicationQuery -> Bool
$cmax :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery
max :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery
$cmin :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery
min :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery
Ord, ReadPrec [ApplicationQuery]
ReadPrec ApplicationQuery
Int -> ReadS ApplicationQuery
ReadS [ApplicationQuery]
(Int -> ReadS ApplicationQuery)
-> ReadS [ApplicationQuery]
-> ReadPrec ApplicationQuery
-> ReadPrec [ApplicationQuery]
-> Read ApplicationQuery
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ApplicationQuery
readsPrec :: Int -> ReadS ApplicationQuery
$creadList :: ReadS [ApplicationQuery]
readList :: ReadS [ApplicationQuery]
$creadPrec :: ReadPrec ApplicationQuery
readPrec :: ReadPrec ApplicationQuery
$creadListPrec :: ReadPrec [ApplicationQuery]
readListPrec :: ReadPrec [ApplicationQuery]
Read, Int -> ApplicationQuery -> ShowS
[ApplicationQuery] -> ShowS
ApplicationQuery -> String
(Int -> ApplicationQuery -> ShowS)
-> (ApplicationQuery -> String)
-> ([ApplicationQuery] -> ShowS)
-> Show ApplicationQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationQuery -> ShowS
showsPrec :: Int -> ApplicationQuery -> ShowS
$cshow :: ApplicationQuery -> String
show :: ApplicationQuery -> String
$cshowList :: [ApplicationQuery] -> ShowS
showList :: [ApplicationQuery] -> ShowS
Show)

_ApplicationQuery :: Name
_ApplicationQuery = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.ApplicationQuery")

data AssociativeExpression = 
  AssociativeExpression {
    AssociativeExpression -> BinaryOperator
associativeExpressionOperator :: BinaryOperator,
    AssociativeExpression -> [Expression]
associativeExpressionOperands :: [Expression]}
  deriving (AssociativeExpression -> AssociativeExpression -> Bool
(AssociativeExpression -> AssociativeExpression -> Bool)
-> (AssociativeExpression -> AssociativeExpression -> Bool)
-> Eq AssociativeExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssociativeExpression -> AssociativeExpression -> Bool
== :: AssociativeExpression -> AssociativeExpression -> Bool
$c/= :: AssociativeExpression -> AssociativeExpression -> Bool
/= :: AssociativeExpression -> AssociativeExpression -> Bool
Eq, Eq AssociativeExpression
Eq AssociativeExpression =>
(AssociativeExpression -> AssociativeExpression -> Ordering)
-> (AssociativeExpression -> AssociativeExpression -> Bool)
-> (AssociativeExpression -> AssociativeExpression -> Bool)
-> (AssociativeExpression -> AssociativeExpression -> Bool)
-> (AssociativeExpression -> AssociativeExpression -> Bool)
-> (AssociativeExpression
    -> AssociativeExpression -> AssociativeExpression)
-> (AssociativeExpression
    -> AssociativeExpression -> AssociativeExpression)
-> Ord AssociativeExpression
AssociativeExpression -> AssociativeExpression -> Bool
AssociativeExpression -> AssociativeExpression -> Ordering
AssociativeExpression
-> AssociativeExpression -> AssociativeExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AssociativeExpression -> AssociativeExpression -> Ordering
compare :: AssociativeExpression -> AssociativeExpression -> Ordering
$c< :: AssociativeExpression -> AssociativeExpression -> Bool
< :: AssociativeExpression -> AssociativeExpression -> Bool
$c<= :: AssociativeExpression -> AssociativeExpression -> Bool
<= :: AssociativeExpression -> AssociativeExpression -> Bool
$c> :: AssociativeExpression -> AssociativeExpression -> Bool
> :: AssociativeExpression -> AssociativeExpression -> Bool
$c>= :: AssociativeExpression -> AssociativeExpression -> Bool
>= :: AssociativeExpression -> AssociativeExpression -> Bool
$cmax :: AssociativeExpression
-> AssociativeExpression -> AssociativeExpression
max :: AssociativeExpression
-> AssociativeExpression -> AssociativeExpression
$cmin :: AssociativeExpression
-> AssociativeExpression -> AssociativeExpression
min :: AssociativeExpression
-> AssociativeExpression -> AssociativeExpression
Ord, ReadPrec [AssociativeExpression]
ReadPrec AssociativeExpression
Int -> ReadS AssociativeExpression
ReadS [AssociativeExpression]
(Int -> ReadS AssociativeExpression)
-> ReadS [AssociativeExpression]
-> ReadPrec AssociativeExpression
-> ReadPrec [AssociativeExpression]
-> Read AssociativeExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssociativeExpression
readsPrec :: Int -> ReadS AssociativeExpression
$creadList :: ReadS [AssociativeExpression]
readList :: ReadS [AssociativeExpression]
$creadPrec :: ReadPrec AssociativeExpression
readPrec :: ReadPrec AssociativeExpression
$creadListPrec :: ReadPrec [AssociativeExpression]
readListPrec :: ReadPrec [AssociativeExpression]
Read, Int -> AssociativeExpression -> ShowS
[AssociativeExpression] -> ShowS
AssociativeExpression -> String
(Int -> AssociativeExpression -> ShowS)
-> (AssociativeExpression -> String)
-> ([AssociativeExpression] -> ShowS)
-> Show AssociativeExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AssociativeExpression -> ShowS
showsPrec :: Int -> AssociativeExpression -> ShowS
$cshow :: AssociativeExpression -> String
show :: AssociativeExpression -> String
$cshowList :: [AssociativeExpression] -> ShowS
showList :: [AssociativeExpression] -> ShowS
Show)

_AssociativeExpression :: Name
_AssociativeExpression = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.AssociativeExpression")

_AssociativeExpression_operator :: Name
_AssociativeExpression_operator = (String -> Name
Core.Name String
"operator")

_AssociativeExpression_operands :: Name
_AssociativeExpression_operands = (String -> Name
Core.Name String
"operands")

data BinaryExpression = 
  BinaryExpression {
    BinaryExpression -> Expression
binaryExpressionLeft :: Expression,
    BinaryExpression -> BinaryOperator
binaryExpressionOperator :: BinaryOperator,
    BinaryExpression -> Expression
binaryExpressionRight :: Expression}
  deriving (BinaryExpression -> BinaryExpression -> Bool
(BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> Eq BinaryExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinaryExpression -> BinaryExpression -> Bool
== :: BinaryExpression -> BinaryExpression -> Bool
$c/= :: BinaryExpression -> BinaryExpression -> Bool
/= :: BinaryExpression -> BinaryExpression -> Bool
Eq, Eq BinaryExpression
Eq BinaryExpression =>
(BinaryExpression -> BinaryExpression -> Ordering)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> BinaryExpression)
-> (BinaryExpression -> BinaryExpression -> BinaryExpression)
-> Ord BinaryExpression
BinaryExpression -> BinaryExpression -> Bool
BinaryExpression -> BinaryExpression -> Ordering
BinaryExpression -> BinaryExpression -> BinaryExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinaryExpression -> BinaryExpression -> Ordering
compare :: BinaryExpression -> BinaryExpression -> Ordering
$c< :: BinaryExpression -> BinaryExpression -> Bool
< :: BinaryExpression -> BinaryExpression -> Bool
$c<= :: BinaryExpression -> BinaryExpression -> Bool
<= :: BinaryExpression -> BinaryExpression -> Bool
$c> :: BinaryExpression -> BinaryExpression -> Bool
> :: BinaryExpression -> BinaryExpression -> Bool
$c>= :: BinaryExpression -> BinaryExpression -> Bool
>= :: BinaryExpression -> BinaryExpression -> Bool
$cmax :: BinaryExpression -> BinaryExpression -> BinaryExpression
max :: BinaryExpression -> BinaryExpression -> BinaryExpression
$cmin :: BinaryExpression -> BinaryExpression -> BinaryExpression
min :: BinaryExpression -> BinaryExpression -> BinaryExpression
Ord, ReadPrec [BinaryExpression]
ReadPrec BinaryExpression
Int -> ReadS BinaryExpression
ReadS [BinaryExpression]
(Int -> ReadS BinaryExpression)
-> ReadS [BinaryExpression]
-> ReadPrec BinaryExpression
-> ReadPrec [BinaryExpression]
-> Read BinaryExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BinaryExpression
readsPrec :: Int -> ReadS BinaryExpression
$creadList :: ReadS [BinaryExpression]
readList :: ReadS [BinaryExpression]
$creadPrec :: ReadPrec BinaryExpression
readPrec :: ReadPrec BinaryExpression
$creadListPrec :: ReadPrec [BinaryExpression]
readListPrec :: ReadPrec [BinaryExpression]
Read, Int -> BinaryExpression -> ShowS
[BinaryExpression] -> ShowS
BinaryExpression -> String
(Int -> BinaryExpression -> ShowS)
-> (BinaryExpression -> String)
-> ([BinaryExpression] -> ShowS)
-> Show BinaryExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryExpression -> ShowS
showsPrec :: Int -> BinaryExpression -> ShowS
$cshow :: BinaryExpression -> String
show :: BinaryExpression -> String
$cshowList :: [BinaryExpression] -> ShowS
showList :: [BinaryExpression] -> ShowS
Show)

_BinaryExpression :: Name
_BinaryExpression = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.BinaryExpression")

_BinaryExpression_left :: Name
_BinaryExpression_left = (String -> Name
Core.Name String
"left")

_BinaryExpression_operator :: Name
_BinaryExpression_operator = (String -> Name
Core.Name String
"operator")

_BinaryExpression_right :: Name
_BinaryExpression_right = (String -> Name
Core.Name String
"right")

data BinaryBooleanOperator = 
  BinaryBooleanOperatorAnd  |
  BinaryBooleanOperatorOr  |
  BinaryBooleanOperatorXor 
  deriving (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
(BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> Eq BinaryBooleanOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
== :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
$c/= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
/= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
Eq, Eq BinaryBooleanOperator
Eq BinaryBooleanOperator =>
(BinaryBooleanOperator -> BinaryBooleanOperator -> Ordering)
-> (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> (BinaryBooleanOperator -> BinaryBooleanOperator -> Bool)
-> (BinaryBooleanOperator
    -> BinaryBooleanOperator -> BinaryBooleanOperator)
-> (BinaryBooleanOperator
    -> BinaryBooleanOperator -> BinaryBooleanOperator)
-> Ord BinaryBooleanOperator
BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
BinaryBooleanOperator -> BinaryBooleanOperator -> Ordering
BinaryBooleanOperator
-> BinaryBooleanOperator -> BinaryBooleanOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinaryBooleanOperator -> BinaryBooleanOperator -> Ordering
compare :: BinaryBooleanOperator -> BinaryBooleanOperator -> Ordering
$c< :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
< :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
$c<= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
<= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
$c> :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
> :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
$c>= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
>= :: BinaryBooleanOperator -> BinaryBooleanOperator -> Bool
$cmax :: BinaryBooleanOperator
-> BinaryBooleanOperator -> BinaryBooleanOperator
max :: BinaryBooleanOperator
-> BinaryBooleanOperator -> BinaryBooleanOperator
$cmin :: BinaryBooleanOperator
-> BinaryBooleanOperator -> BinaryBooleanOperator
min :: BinaryBooleanOperator
-> BinaryBooleanOperator -> BinaryBooleanOperator
Ord, ReadPrec [BinaryBooleanOperator]
ReadPrec BinaryBooleanOperator
Int -> ReadS BinaryBooleanOperator
ReadS [BinaryBooleanOperator]
(Int -> ReadS BinaryBooleanOperator)
-> ReadS [BinaryBooleanOperator]
-> ReadPrec BinaryBooleanOperator
-> ReadPrec [BinaryBooleanOperator]
-> Read BinaryBooleanOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BinaryBooleanOperator
readsPrec :: Int -> ReadS BinaryBooleanOperator
$creadList :: ReadS [BinaryBooleanOperator]
readList :: ReadS [BinaryBooleanOperator]
$creadPrec :: ReadPrec BinaryBooleanOperator
readPrec :: ReadPrec BinaryBooleanOperator
$creadListPrec :: ReadPrec [BinaryBooleanOperator]
readListPrec :: ReadPrec [BinaryBooleanOperator]
Read, Int -> BinaryBooleanOperator -> ShowS
[BinaryBooleanOperator] -> ShowS
BinaryBooleanOperator -> String
(Int -> BinaryBooleanOperator -> ShowS)
-> (BinaryBooleanOperator -> String)
-> ([BinaryBooleanOperator] -> ShowS)
-> Show BinaryBooleanOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryBooleanOperator -> ShowS
showsPrec :: Int -> BinaryBooleanOperator -> ShowS
$cshow :: BinaryBooleanOperator -> String
show :: BinaryBooleanOperator -> String
$cshowList :: [BinaryBooleanOperator] -> ShowS
showList :: [BinaryBooleanOperator] -> ShowS
Show)

_BinaryBooleanOperator :: Name
_BinaryBooleanOperator = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.BinaryBooleanOperator")

_BinaryBooleanOperator_and :: Name
_BinaryBooleanOperator_and = (String -> Name
Core.Name String
"and")

_BinaryBooleanOperator_or :: Name
_BinaryBooleanOperator_or = (String -> Name
Core.Name String
"or")

_BinaryBooleanOperator_xor :: Name
_BinaryBooleanOperator_xor = (String -> Name
Core.Name String
"xor")

data BinaryOperator = 
  BinaryOperatorBoolean BinaryBooleanOperator |
  BinaryOperatorComparison ComparisonOperator |
  BinaryOperatorPower 
  deriving (BinaryOperator -> BinaryOperator -> Bool
(BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool) -> Eq BinaryOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinaryOperator -> BinaryOperator -> Bool
== :: BinaryOperator -> BinaryOperator -> Bool
$c/= :: BinaryOperator -> BinaryOperator -> Bool
/= :: BinaryOperator -> BinaryOperator -> Bool
Eq, Eq BinaryOperator
Eq BinaryOperator =>
(BinaryOperator -> BinaryOperator -> Ordering)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> BinaryOperator)
-> (BinaryOperator -> BinaryOperator -> BinaryOperator)
-> Ord BinaryOperator
BinaryOperator -> BinaryOperator -> Bool
BinaryOperator -> BinaryOperator -> Ordering
BinaryOperator -> BinaryOperator -> BinaryOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinaryOperator -> BinaryOperator -> Ordering
compare :: BinaryOperator -> BinaryOperator -> Ordering
$c< :: BinaryOperator -> BinaryOperator -> Bool
< :: BinaryOperator -> BinaryOperator -> Bool
$c<= :: BinaryOperator -> BinaryOperator -> Bool
<= :: BinaryOperator -> BinaryOperator -> Bool
$c> :: BinaryOperator -> BinaryOperator -> Bool
> :: BinaryOperator -> BinaryOperator -> Bool
$c>= :: BinaryOperator -> BinaryOperator -> Bool
>= :: BinaryOperator -> BinaryOperator -> Bool
$cmax :: BinaryOperator -> BinaryOperator -> BinaryOperator
max :: BinaryOperator -> BinaryOperator -> BinaryOperator
$cmin :: BinaryOperator -> BinaryOperator -> BinaryOperator
min :: BinaryOperator -> BinaryOperator -> BinaryOperator
Ord, ReadPrec [BinaryOperator]
ReadPrec BinaryOperator
Int -> ReadS BinaryOperator
ReadS [BinaryOperator]
(Int -> ReadS BinaryOperator)
-> ReadS [BinaryOperator]
-> ReadPrec BinaryOperator
-> ReadPrec [BinaryOperator]
-> Read BinaryOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BinaryOperator
readsPrec :: Int -> ReadS BinaryOperator
$creadList :: ReadS [BinaryOperator]
readList :: ReadS [BinaryOperator]
$creadPrec :: ReadPrec BinaryOperator
readPrec :: ReadPrec BinaryOperator
$creadListPrec :: ReadPrec [BinaryOperator]
readListPrec :: ReadPrec [BinaryOperator]
Read, Int -> BinaryOperator -> ShowS
[BinaryOperator] -> ShowS
BinaryOperator -> String
(Int -> BinaryOperator -> ShowS)
-> (BinaryOperator -> String)
-> ([BinaryOperator] -> ShowS)
-> Show BinaryOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryOperator -> ShowS
showsPrec :: Int -> BinaryOperator -> ShowS
$cshow :: BinaryOperator -> String
show :: BinaryOperator -> String
$cshowList :: [BinaryOperator] -> ShowS
showList :: [BinaryOperator] -> ShowS
Show)

_BinaryOperator :: Name
_BinaryOperator = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.BinaryOperator")

_BinaryOperator_boolean :: Name
_BinaryOperator_boolean = (String -> Name
Core.Name String
"boolean")

_BinaryOperator_comparison :: Name
_BinaryOperator_comparison = (String -> Name
Core.Name String
"comparison")

_BinaryOperator_power :: Name
_BinaryOperator_power = (String -> Name
Core.Name String
"power")

data Binding = 
  Binding {
    Binding -> Variable
bindingKey :: Variable,
    Binding -> Query
bindingValue :: Query}
  deriving (Binding -> Binding -> Bool
(Binding -> Binding -> Bool)
-> (Binding -> Binding -> Bool) -> Eq Binding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Binding -> Binding -> Bool
== :: Binding -> Binding -> Bool
$c/= :: Binding -> Binding -> Bool
/= :: Binding -> Binding -> Bool
Eq, Eq Binding
Eq Binding =>
(Binding -> Binding -> Ordering)
-> (Binding -> Binding -> Bool)
-> (Binding -> Binding -> Bool)
-> (Binding -> Binding -> Bool)
-> (Binding -> Binding -> Bool)
-> (Binding -> Binding -> Binding)
-> (Binding -> Binding -> Binding)
-> Ord Binding
Binding -> Binding -> Bool
Binding -> Binding -> Ordering
Binding -> Binding -> Binding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Binding -> Binding -> Ordering
compare :: Binding -> Binding -> Ordering
$c< :: Binding -> Binding -> Bool
< :: Binding -> Binding -> Bool
$c<= :: Binding -> Binding -> Bool
<= :: Binding -> Binding -> Bool
$c> :: Binding -> Binding -> Bool
> :: Binding -> Binding -> Bool
$c>= :: Binding -> Binding -> Bool
>= :: Binding -> Binding -> Bool
$cmax :: Binding -> Binding -> Binding
max :: Binding -> Binding -> Binding
$cmin :: Binding -> Binding -> Binding
min :: Binding -> Binding -> Binding
Ord, ReadPrec [Binding]
ReadPrec Binding
Int -> ReadS Binding
ReadS [Binding]
(Int -> ReadS Binding)
-> ReadS [Binding]
-> ReadPrec Binding
-> ReadPrec [Binding]
-> Read Binding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Binding
readsPrec :: Int -> ReadS Binding
$creadList :: ReadS [Binding]
readList :: ReadS [Binding]
$creadPrec :: ReadPrec Binding
readPrec :: ReadPrec Binding
$creadListPrec :: ReadPrec [Binding]
readListPrec :: ReadPrec [Binding]
Read, Int -> Binding -> ShowS
[Binding] -> ShowS
Binding -> String
(Int -> Binding -> ShowS)
-> (Binding -> String) -> ([Binding] -> ShowS) -> Show Binding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Binding -> ShowS
showsPrec :: Int -> Binding -> ShowS
$cshow :: Binding -> String
show :: Binding -> String
$cshowList :: [Binding] -> ShowS
showList :: [Binding] -> ShowS
Show)

_Binding :: Name
_Binding = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Binding")

_Binding_key :: Name
_Binding_key = (String -> Name
Core.Name String
"key")

_Binding_value :: Name
_Binding_value = (String -> Name
Core.Name String
"value")

data ComparisonOperator = 
  ComparisonOperatorEq  |
  ComparisonOperatorNeq  |
  ComparisonOperatorLt  |
  ComparisonOperatorLte  |
  ComparisonOperatorGt  |
  ComparisonOperatorGte 
  deriving (ComparisonOperator -> ComparisonOperator -> Bool
(ComparisonOperator -> ComparisonOperator -> Bool)
-> (ComparisonOperator -> ComparisonOperator -> Bool)
-> Eq ComparisonOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComparisonOperator -> ComparisonOperator -> Bool
== :: ComparisonOperator -> ComparisonOperator -> Bool
$c/= :: ComparisonOperator -> ComparisonOperator -> Bool
/= :: ComparisonOperator -> ComparisonOperator -> Bool
Eq, Eq ComparisonOperator
Eq ComparisonOperator =>
(ComparisonOperator -> ComparisonOperator -> Ordering)
-> (ComparisonOperator -> ComparisonOperator -> Bool)
-> (ComparisonOperator -> ComparisonOperator -> Bool)
-> (ComparisonOperator -> ComparisonOperator -> Bool)
-> (ComparisonOperator -> ComparisonOperator -> Bool)
-> (ComparisonOperator -> ComparisonOperator -> ComparisonOperator)
-> (ComparisonOperator -> ComparisonOperator -> ComparisonOperator)
-> Ord ComparisonOperator
ComparisonOperator -> ComparisonOperator -> Bool
ComparisonOperator -> ComparisonOperator -> Ordering
ComparisonOperator -> ComparisonOperator -> ComparisonOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ComparisonOperator -> ComparisonOperator -> Ordering
compare :: ComparisonOperator -> ComparisonOperator -> Ordering
$c< :: ComparisonOperator -> ComparisonOperator -> Bool
< :: ComparisonOperator -> ComparisonOperator -> Bool
$c<= :: ComparisonOperator -> ComparisonOperator -> Bool
<= :: ComparisonOperator -> ComparisonOperator -> Bool
$c> :: ComparisonOperator -> ComparisonOperator -> Bool
> :: ComparisonOperator -> ComparisonOperator -> Bool
$c>= :: ComparisonOperator -> ComparisonOperator -> Bool
>= :: ComparisonOperator -> ComparisonOperator -> Bool
$cmax :: ComparisonOperator -> ComparisonOperator -> ComparisonOperator
max :: ComparisonOperator -> ComparisonOperator -> ComparisonOperator
$cmin :: ComparisonOperator -> ComparisonOperator -> ComparisonOperator
min :: ComparisonOperator -> ComparisonOperator -> ComparisonOperator
Ord, ReadPrec [ComparisonOperator]
ReadPrec ComparisonOperator
Int -> ReadS ComparisonOperator
ReadS [ComparisonOperator]
(Int -> ReadS ComparisonOperator)
-> ReadS [ComparisonOperator]
-> ReadPrec ComparisonOperator
-> ReadPrec [ComparisonOperator]
-> Read ComparisonOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ComparisonOperator
readsPrec :: Int -> ReadS ComparisonOperator
$creadList :: ReadS [ComparisonOperator]
readList :: ReadS [ComparisonOperator]
$creadPrec :: ReadPrec ComparisonOperator
readPrec :: ReadPrec ComparisonOperator
$creadListPrec :: ReadPrec [ComparisonOperator]
readListPrec :: ReadPrec [ComparisonOperator]
Read, Int -> ComparisonOperator -> ShowS
[ComparisonOperator] -> ShowS
ComparisonOperator -> String
(Int -> ComparisonOperator -> ShowS)
-> (ComparisonOperator -> String)
-> ([ComparisonOperator] -> ShowS)
-> Show ComparisonOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComparisonOperator -> ShowS
showsPrec :: Int -> ComparisonOperator -> ShowS
$cshow :: ComparisonOperator -> String
show :: ComparisonOperator -> String
$cshowList :: [ComparisonOperator] -> ShowS
showList :: [ComparisonOperator] -> ShowS
Show)

_ComparisonOperator :: Name
_ComparisonOperator = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.ComparisonOperator")

_ComparisonOperator_eq :: Name
_ComparisonOperator_eq = (String -> Name
Core.Name String
"eq")

_ComparisonOperator_neq :: Name
_ComparisonOperator_neq = (String -> Name
Core.Name String
"neq")

_ComparisonOperator_lt :: Name
_ComparisonOperator_lt = (String -> Name
Core.Name String
"lt")

_ComparisonOperator_lte :: Name
_ComparisonOperator_lte = (String -> Name
Core.Name String
"lte")

_ComparisonOperator_gt :: Name
_ComparisonOperator_gt = (String -> Name
Core.Name String
"gt")

_ComparisonOperator_gte :: Name
_ComparisonOperator_gte = (String -> Name
Core.Name String
"gte")

data EdgeProjectionPattern = 
  EdgeProjectionPattern {
    EdgeProjectionPattern -> Direction
edgeProjectionPatternDirection :: PropertyGraph.Direction,
    EdgeProjectionPattern -> Maybe EdgeLabel
edgeProjectionPatternLabel :: (Maybe PropertyGraph.EdgeLabel),
    EdgeProjectionPattern -> [PropertyPattern]
edgeProjectionPatternProperties :: [PropertyPattern],
    EdgeProjectionPattern -> Maybe VertexPattern
edgeProjectionPatternVertex :: (Maybe VertexPattern)}
  deriving (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
(EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> Eq EdgeProjectionPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
== :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
$c/= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
/= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
Eq, Eq EdgeProjectionPattern
Eq EdgeProjectionPattern =>
(EdgeProjectionPattern -> EdgeProjectionPattern -> Ordering)
-> (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> (EdgeProjectionPattern -> EdgeProjectionPattern -> Bool)
-> (EdgeProjectionPattern
    -> EdgeProjectionPattern -> EdgeProjectionPattern)
-> (EdgeProjectionPattern
    -> EdgeProjectionPattern -> EdgeProjectionPattern)
-> Ord EdgeProjectionPattern
EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
EdgeProjectionPattern -> EdgeProjectionPattern -> Ordering
EdgeProjectionPattern
-> EdgeProjectionPattern -> EdgeProjectionPattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EdgeProjectionPattern -> EdgeProjectionPattern -> Ordering
compare :: EdgeProjectionPattern -> EdgeProjectionPattern -> Ordering
$c< :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
< :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
$c<= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
<= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
$c> :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
> :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
$c>= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
>= :: EdgeProjectionPattern -> EdgeProjectionPattern -> Bool
$cmax :: EdgeProjectionPattern
-> EdgeProjectionPattern -> EdgeProjectionPattern
max :: EdgeProjectionPattern
-> EdgeProjectionPattern -> EdgeProjectionPattern
$cmin :: EdgeProjectionPattern
-> EdgeProjectionPattern -> EdgeProjectionPattern
min :: EdgeProjectionPattern
-> EdgeProjectionPattern -> EdgeProjectionPattern
Ord, ReadPrec [EdgeProjectionPattern]
ReadPrec EdgeProjectionPattern
Int -> ReadS EdgeProjectionPattern
ReadS [EdgeProjectionPattern]
(Int -> ReadS EdgeProjectionPattern)
-> ReadS [EdgeProjectionPattern]
-> ReadPrec EdgeProjectionPattern
-> ReadPrec [EdgeProjectionPattern]
-> Read EdgeProjectionPattern
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgeProjectionPattern
readsPrec :: Int -> ReadS EdgeProjectionPattern
$creadList :: ReadS [EdgeProjectionPattern]
readList :: ReadS [EdgeProjectionPattern]
$creadPrec :: ReadPrec EdgeProjectionPattern
readPrec :: ReadPrec EdgeProjectionPattern
$creadListPrec :: ReadPrec [EdgeProjectionPattern]
readListPrec :: ReadPrec [EdgeProjectionPattern]
Read, Int -> EdgeProjectionPattern -> ShowS
[EdgeProjectionPattern] -> ShowS
EdgeProjectionPattern -> String
(Int -> EdgeProjectionPattern -> ShowS)
-> (EdgeProjectionPattern -> String)
-> ([EdgeProjectionPattern] -> ShowS)
-> Show EdgeProjectionPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeProjectionPattern -> ShowS
showsPrec :: Int -> EdgeProjectionPattern -> ShowS
$cshow :: EdgeProjectionPattern -> String
show :: EdgeProjectionPattern -> String
$cshowList :: [EdgeProjectionPattern] -> ShowS
showList :: [EdgeProjectionPattern] -> ShowS
Show)

_EdgeProjectionPattern :: Name
_EdgeProjectionPattern = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.EdgeProjectionPattern")

_EdgeProjectionPattern_direction :: Name
_EdgeProjectionPattern_direction = (String -> Name
Core.Name String
"direction")

_EdgeProjectionPattern_label :: Name
_EdgeProjectionPattern_label = (String -> Name
Core.Name String
"label")

_EdgeProjectionPattern_properties :: Name
_EdgeProjectionPattern_properties = (String -> Name
Core.Name String
"properties")

_EdgeProjectionPattern_vertex :: Name
_EdgeProjectionPattern_vertex = (String -> Name
Core.Name String
"vertex")

data Expression = 
  ExpressionAssociative AssociativeExpression |
  ExpressionBinary BinaryExpression |
  ExpressionProperty PropertyProjection |
  ExpressionUnary UnaryExpression |
  ExpressionVariable Variable |
  ExpressionVertex VertexPattern
  deriving (Expression -> Expression -> Bool
(Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool) -> Eq Expression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
/= :: Expression -> Expression -> Bool
Eq, Eq Expression
Eq Expression =>
(Expression -> Expression -> Ordering)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Expression)
-> (Expression -> Expression -> Expression)
-> Ord Expression
Expression -> Expression -> Bool
Expression -> Expression -> Ordering
Expression -> Expression -> Expression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression -> Expression -> Ordering
compare :: Expression -> Expression -> Ordering
$c< :: Expression -> Expression -> Bool
< :: Expression -> Expression -> Bool
$c<= :: Expression -> Expression -> Bool
<= :: Expression -> Expression -> Bool
$c> :: Expression -> Expression -> Bool
> :: Expression -> Expression -> Bool
$c>= :: Expression -> Expression -> Bool
>= :: Expression -> Expression -> Bool
$cmax :: Expression -> Expression -> Expression
max :: Expression -> Expression -> Expression
$cmin :: Expression -> Expression -> Expression
min :: Expression -> Expression -> Expression
Ord, ReadPrec [Expression]
ReadPrec Expression
Int -> ReadS Expression
ReadS [Expression]
(Int -> ReadS Expression)
-> ReadS [Expression]
-> ReadPrec Expression
-> ReadPrec [Expression]
-> Read Expression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression
readsPrec :: Int -> ReadS Expression
$creadList :: ReadS [Expression]
readList :: ReadS [Expression]
$creadPrec :: ReadPrec Expression
readPrec :: ReadPrec Expression
$creadListPrec :: ReadPrec [Expression]
readListPrec :: ReadPrec [Expression]
Read, Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
(Int -> Expression -> ShowS)
-> (Expression -> String)
-> ([Expression] -> ShowS)
-> Show Expression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression -> ShowS
showsPrec :: Int -> Expression -> ShowS
$cshow :: Expression -> String
show :: Expression -> String
$cshowList :: [Expression] -> ShowS
showList :: [Expression] -> ShowS
Show)

_Expression :: Name
_Expression = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Expression")

_Expression_associative :: Name
_Expression_associative = (String -> Name
Core.Name String
"associative")

_Expression_binary :: Name
_Expression_binary = (String -> Name
Core.Name String
"binary")

_Expression_property :: Name
_Expression_property = (String -> Name
Core.Name String
"property")

_Expression_unary :: Name
_Expression_unary = (String -> Name
Core.Name String
"unary")

_Expression_variable :: Name
_Expression_variable = (String -> Name
Core.Name String
"variable")

_Expression_vertex :: Name
_Expression_vertex = (String -> Name
Core.Name String
"vertex")

data LetQuery = 
  LetQuery {
    LetQuery -> [Binding]
letQueryBindings :: [Binding],
    LetQuery -> Query
letQueryEnvironment :: Query}
  deriving (LetQuery -> LetQuery -> Bool
(LetQuery -> LetQuery -> Bool)
-> (LetQuery -> LetQuery -> Bool) -> Eq LetQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LetQuery -> LetQuery -> Bool
== :: LetQuery -> LetQuery -> Bool
$c/= :: LetQuery -> LetQuery -> Bool
/= :: LetQuery -> LetQuery -> Bool
Eq, Eq LetQuery
Eq LetQuery =>
(LetQuery -> LetQuery -> Ordering)
-> (LetQuery -> LetQuery -> Bool)
-> (LetQuery -> LetQuery -> Bool)
-> (LetQuery -> LetQuery -> Bool)
-> (LetQuery -> LetQuery -> Bool)
-> (LetQuery -> LetQuery -> LetQuery)
-> (LetQuery -> LetQuery -> LetQuery)
-> Ord LetQuery
LetQuery -> LetQuery -> Bool
LetQuery -> LetQuery -> Ordering
LetQuery -> LetQuery -> LetQuery
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LetQuery -> LetQuery -> Ordering
compare :: LetQuery -> LetQuery -> Ordering
$c< :: LetQuery -> LetQuery -> Bool
< :: LetQuery -> LetQuery -> Bool
$c<= :: LetQuery -> LetQuery -> Bool
<= :: LetQuery -> LetQuery -> Bool
$c> :: LetQuery -> LetQuery -> Bool
> :: LetQuery -> LetQuery -> Bool
$c>= :: LetQuery -> LetQuery -> Bool
>= :: LetQuery -> LetQuery -> Bool
$cmax :: LetQuery -> LetQuery -> LetQuery
max :: LetQuery -> LetQuery -> LetQuery
$cmin :: LetQuery -> LetQuery -> LetQuery
min :: LetQuery -> LetQuery -> LetQuery
Ord, ReadPrec [LetQuery]
ReadPrec LetQuery
Int -> ReadS LetQuery
ReadS [LetQuery]
(Int -> ReadS LetQuery)
-> ReadS [LetQuery]
-> ReadPrec LetQuery
-> ReadPrec [LetQuery]
-> Read LetQuery
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LetQuery
readsPrec :: Int -> ReadS LetQuery
$creadList :: ReadS [LetQuery]
readList :: ReadS [LetQuery]
$creadPrec :: ReadPrec LetQuery
readPrec :: ReadPrec LetQuery
$creadListPrec :: ReadPrec [LetQuery]
readListPrec :: ReadPrec [LetQuery]
Read, Int -> LetQuery -> ShowS
[LetQuery] -> ShowS
LetQuery -> String
(Int -> LetQuery -> ShowS)
-> (LetQuery -> String) -> ([LetQuery] -> ShowS) -> Show LetQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LetQuery -> ShowS
showsPrec :: Int -> LetQuery -> ShowS
$cshow :: LetQuery -> String
show :: LetQuery -> String
$cshowList :: [LetQuery] -> ShowS
showList :: [LetQuery] -> ShowS
Show)

_LetQuery :: Name
_LetQuery = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.LetQuery")

_LetQuery_bindings :: Name
_LetQuery_bindings = (String -> Name
Core.Name String
"bindings")

_LetQuery_environment :: Name
_LetQuery_environment = (String -> Name
Core.Name String
"environment")

data MatchQuery = 
  MatchQuery {
    MatchQuery -> Bool
matchQueryOptional :: Bool,
    MatchQuery -> [Projection]
matchQueryPattern :: [Projection],
    MatchQuery -> Maybe Expression
matchQueryWhere :: (Maybe Expression)}
  deriving (MatchQuery -> MatchQuery -> Bool
(MatchQuery -> MatchQuery -> Bool)
-> (MatchQuery -> MatchQuery -> Bool) -> Eq MatchQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MatchQuery -> MatchQuery -> Bool
== :: MatchQuery -> MatchQuery -> Bool
$c/= :: MatchQuery -> MatchQuery -> Bool
/= :: MatchQuery -> MatchQuery -> Bool
Eq, Eq MatchQuery
Eq MatchQuery =>
(MatchQuery -> MatchQuery -> Ordering)
-> (MatchQuery -> MatchQuery -> Bool)
-> (MatchQuery -> MatchQuery -> Bool)
-> (MatchQuery -> MatchQuery -> Bool)
-> (MatchQuery -> MatchQuery -> Bool)
-> (MatchQuery -> MatchQuery -> MatchQuery)
-> (MatchQuery -> MatchQuery -> MatchQuery)
-> Ord MatchQuery
MatchQuery -> MatchQuery -> Bool
MatchQuery -> MatchQuery -> Ordering
MatchQuery -> MatchQuery -> MatchQuery
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MatchQuery -> MatchQuery -> Ordering
compare :: MatchQuery -> MatchQuery -> Ordering
$c< :: MatchQuery -> MatchQuery -> Bool
< :: MatchQuery -> MatchQuery -> Bool
$c<= :: MatchQuery -> MatchQuery -> Bool
<= :: MatchQuery -> MatchQuery -> Bool
$c> :: MatchQuery -> MatchQuery -> Bool
> :: MatchQuery -> MatchQuery -> Bool
$c>= :: MatchQuery -> MatchQuery -> Bool
>= :: MatchQuery -> MatchQuery -> Bool
$cmax :: MatchQuery -> MatchQuery -> MatchQuery
max :: MatchQuery -> MatchQuery -> MatchQuery
$cmin :: MatchQuery -> MatchQuery -> MatchQuery
min :: MatchQuery -> MatchQuery -> MatchQuery
Ord, ReadPrec [MatchQuery]
ReadPrec MatchQuery
Int -> ReadS MatchQuery
ReadS [MatchQuery]
(Int -> ReadS MatchQuery)
-> ReadS [MatchQuery]
-> ReadPrec MatchQuery
-> ReadPrec [MatchQuery]
-> Read MatchQuery
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MatchQuery
readsPrec :: Int -> ReadS MatchQuery
$creadList :: ReadS [MatchQuery]
readList :: ReadS [MatchQuery]
$creadPrec :: ReadPrec MatchQuery
readPrec :: ReadPrec MatchQuery
$creadListPrec :: ReadPrec [MatchQuery]
readListPrec :: ReadPrec [MatchQuery]
Read, Int -> MatchQuery -> ShowS
[MatchQuery] -> ShowS
MatchQuery -> String
(Int -> MatchQuery -> ShowS)
-> (MatchQuery -> String)
-> ([MatchQuery] -> ShowS)
-> Show MatchQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MatchQuery -> ShowS
showsPrec :: Int -> MatchQuery -> ShowS
$cshow :: MatchQuery -> String
show :: MatchQuery -> String
$cshowList :: [MatchQuery] -> ShowS
showList :: [MatchQuery] -> ShowS
Show)

_MatchQuery :: Name
_MatchQuery = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.MatchQuery")

_MatchQuery_optional :: Name
_MatchQuery_optional = (String -> Name
Core.Name String
"optional")

_MatchQuery_pattern :: Name
_MatchQuery_pattern = (String -> Name
Core.Name String
"pattern")

_MatchQuery_where :: Name
_MatchQuery_where = (String -> Name
Core.Name String
"where")

data Projection = 
  Projection {
    Projection -> Expression
projectionValue :: Expression,
    Projection -> Maybe Variable
projectionAs :: (Maybe Variable)}
  deriving (Projection -> Projection -> Bool
(Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool) -> Eq Projection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Projection -> Projection -> Bool
== :: Projection -> Projection -> Bool
$c/= :: Projection -> Projection -> Bool
/= :: Projection -> Projection -> Bool
Eq, Eq Projection
Eq Projection =>
(Projection -> Projection -> Ordering)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Projection)
-> (Projection -> Projection -> Projection)
-> Ord Projection
Projection -> Projection -> Bool
Projection -> Projection -> Ordering
Projection -> Projection -> Projection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Projection -> Projection -> Ordering
compare :: Projection -> Projection -> Ordering
$c< :: Projection -> Projection -> Bool
< :: Projection -> Projection -> Bool
$c<= :: Projection -> Projection -> Bool
<= :: Projection -> Projection -> Bool
$c> :: Projection -> Projection -> Bool
> :: Projection -> Projection -> Bool
$c>= :: Projection -> Projection -> Bool
>= :: Projection -> Projection -> Bool
$cmax :: Projection -> Projection -> Projection
max :: Projection -> Projection -> Projection
$cmin :: Projection -> Projection -> Projection
min :: Projection -> Projection -> Projection
Ord, ReadPrec [Projection]
ReadPrec Projection
Int -> ReadS Projection
ReadS [Projection]
(Int -> ReadS Projection)
-> ReadS [Projection]
-> ReadPrec Projection
-> ReadPrec [Projection]
-> Read Projection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Projection
readsPrec :: Int -> ReadS Projection
$creadList :: ReadS [Projection]
readList :: ReadS [Projection]
$creadPrec :: ReadPrec Projection
readPrec :: ReadPrec Projection
$creadListPrec :: ReadPrec [Projection]
readListPrec :: ReadPrec [Projection]
Read, Int -> Projection -> ShowS
[Projection] -> ShowS
Projection -> String
(Int -> Projection -> ShowS)
-> (Projection -> String)
-> ([Projection] -> ShowS)
-> Show Projection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Projection -> ShowS
showsPrec :: Int -> Projection -> ShowS
$cshow :: Projection -> String
show :: Projection -> String
$cshowList :: [Projection] -> ShowS
showList :: [Projection] -> ShowS
Show)

_Projection :: Name
_Projection = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Projection")

_Projection_value :: Name
_Projection_value = (String -> Name
Core.Name String
"value")

_Projection_as :: Name
_Projection_as = (String -> Name
Core.Name String
"as")

data Projections = 
  Projections {
    Projections -> Bool
projectionsAll :: Bool,
    Projections -> [Projection]
projectionsExplicit :: [Projection]}
  deriving (Projections -> Projections -> Bool
(Projections -> Projections -> Bool)
-> (Projections -> Projections -> Bool) -> Eq Projections
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Projections -> Projections -> Bool
== :: Projections -> Projections -> Bool
$c/= :: Projections -> Projections -> Bool
/= :: Projections -> Projections -> Bool
Eq, Eq Projections
Eq Projections =>
(Projections -> Projections -> Ordering)
-> (Projections -> Projections -> Bool)
-> (Projections -> Projections -> Bool)
-> (Projections -> Projections -> Bool)
-> (Projections -> Projections -> Bool)
-> (Projections -> Projections -> Projections)
-> (Projections -> Projections -> Projections)
-> Ord Projections
Projections -> Projections -> Bool
Projections -> Projections -> Ordering
Projections -> Projections -> Projections
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Projections -> Projections -> Ordering
compare :: Projections -> Projections -> Ordering
$c< :: Projections -> Projections -> Bool
< :: Projections -> Projections -> Bool
$c<= :: Projections -> Projections -> Bool
<= :: Projections -> Projections -> Bool
$c> :: Projections -> Projections -> Bool
> :: Projections -> Projections -> Bool
$c>= :: Projections -> Projections -> Bool
>= :: Projections -> Projections -> Bool
$cmax :: Projections -> Projections -> Projections
max :: Projections -> Projections -> Projections
$cmin :: Projections -> Projections -> Projections
min :: Projections -> Projections -> Projections
Ord, ReadPrec [Projections]
ReadPrec Projections
Int -> ReadS Projections
ReadS [Projections]
(Int -> ReadS Projections)
-> ReadS [Projections]
-> ReadPrec Projections
-> ReadPrec [Projections]
-> Read Projections
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Projections
readsPrec :: Int -> ReadS Projections
$creadList :: ReadS [Projections]
readList :: ReadS [Projections]
$creadPrec :: ReadPrec Projections
readPrec :: ReadPrec Projections
$creadListPrec :: ReadPrec [Projections]
readListPrec :: ReadPrec [Projections]
Read, Int -> Projections -> ShowS
[Projections] -> ShowS
Projections -> String
(Int -> Projections -> ShowS)
-> (Projections -> String)
-> ([Projections] -> ShowS)
-> Show Projections
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Projections -> ShowS
showsPrec :: Int -> Projections -> ShowS
$cshow :: Projections -> String
show :: Projections -> String
$cshowList :: [Projections] -> ShowS
showList :: [Projections] -> ShowS
Show)

_Projections :: Name
_Projections = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Projections")

_Projections_all :: Name
_Projections_all = (String -> Name
Core.Name String
"all")

_Projections_explicit :: Name
_Projections_explicit = (String -> Name
Core.Name String
"explicit")

data PropertyPattern = 
  PropertyPattern {
    PropertyPattern -> PropertyKey
propertyPatternKey :: PropertyGraph.PropertyKey,
    PropertyPattern -> PropertyValuePattern
propertyPatternValue :: PropertyValuePattern}
  deriving (PropertyPattern -> PropertyPattern -> Bool
(PropertyPattern -> PropertyPattern -> Bool)
-> (PropertyPattern -> PropertyPattern -> Bool)
-> Eq PropertyPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyPattern -> PropertyPattern -> Bool
== :: PropertyPattern -> PropertyPattern -> Bool
$c/= :: PropertyPattern -> PropertyPattern -> Bool
/= :: PropertyPattern -> PropertyPattern -> Bool
Eq, Eq PropertyPattern
Eq PropertyPattern =>
(PropertyPattern -> PropertyPattern -> Ordering)
-> (PropertyPattern -> PropertyPattern -> Bool)
-> (PropertyPattern -> PropertyPattern -> Bool)
-> (PropertyPattern -> PropertyPattern -> Bool)
-> (PropertyPattern -> PropertyPattern -> Bool)
-> (PropertyPattern -> PropertyPattern -> PropertyPattern)
-> (PropertyPattern -> PropertyPattern -> PropertyPattern)
-> Ord PropertyPattern
PropertyPattern -> PropertyPattern -> Bool
PropertyPattern -> PropertyPattern -> Ordering
PropertyPattern -> PropertyPattern -> PropertyPattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyPattern -> PropertyPattern -> Ordering
compare :: PropertyPattern -> PropertyPattern -> Ordering
$c< :: PropertyPattern -> PropertyPattern -> Bool
< :: PropertyPattern -> PropertyPattern -> Bool
$c<= :: PropertyPattern -> PropertyPattern -> Bool
<= :: PropertyPattern -> PropertyPattern -> Bool
$c> :: PropertyPattern -> PropertyPattern -> Bool
> :: PropertyPattern -> PropertyPattern -> Bool
$c>= :: PropertyPattern -> PropertyPattern -> Bool
>= :: PropertyPattern -> PropertyPattern -> Bool
$cmax :: PropertyPattern -> PropertyPattern -> PropertyPattern
max :: PropertyPattern -> PropertyPattern -> PropertyPattern
$cmin :: PropertyPattern -> PropertyPattern -> PropertyPattern
min :: PropertyPattern -> PropertyPattern -> PropertyPattern
Ord, ReadPrec [PropertyPattern]
ReadPrec PropertyPattern
Int -> ReadS PropertyPattern
ReadS [PropertyPattern]
(Int -> ReadS PropertyPattern)
-> ReadS [PropertyPattern]
-> ReadPrec PropertyPattern
-> ReadPrec [PropertyPattern]
-> Read PropertyPattern
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyPattern
readsPrec :: Int -> ReadS PropertyPattern
$creadList :: ReadS [PropertyPattern]
readList :: ReadS [PropertyPattern]
$creadPrec :: ReadPrec PropertyPattern
readPrec :: ReadPrec PropertyPattern
$creadListPrec :: ReadPrec [PropertyPattern]
readListPrec :: ReadPrec [PropertyPattern]
Read, Int -> PropertyPattern -> ShowS
[PropertyPattern] -> ShowS
PropertyPattern -> String
(Int -> PropertyPattern -> ShowS)
-> (PropertyPattern -> String)
-> ([PropertyPattern] -> ShowS)
-> Show PropertyPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyPattern -> ShowS
showsPrec :: Int -> PropertyPattern -> ShowS
$cshow :: PropertyPattern -> String
show :: PropertyPattern -> String
$cshowList :: [PropertyPattern] -> ShowS
showList :: [PropertyPattern] -> ShowS
Show)

_PropertyPattern :: Name
_PropertyPattern = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.PropertyPattern")

_PropertyPattern_key :: Name
_PropertyPattern_key = (String -> Name
Core.Name String
"key")

_PropertyPattern_value :: Name
_PropertyPattern_value = (String -> Name
Core.Name String
"value")

data PropertyProjection = 
  PropertyProjection {
    PropertyProjection -> Expression
propertyProjectionBase :: Expression,
    PropertyProjection -> PropertyKey
propertyProjectionKey :: PropertyGraph.PropertyKey}
  deriving (PropertyProjection -> PropertyProjection -> Bool
(PropertyProjection -> PropertyProjection -> Bool)
-> (PropertyProjection -> PropertyProjection -> Bool)
-> Eq PropertyProjection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyProjection -> PropertyProjection -> Bool
== :: PropertyProjection -> PropertyProjection -> Bool
$c/= :: PropertyProjection -> PropertyProjection -> Bool
/= :: PropertyProjection -> PropertyProjection -> Bool
Eq, Eq PropertyProjection
Eq PropertyProjection =>
(PropertyProjection -> PropertyProjection -> Ordering)
-> (PropertyProjection -> PropertyProjection -> Bool)
-> (PropertyProjection -> PropertyProjection -> Bool)
-> (PropertyProjection -> PropertyProjection -> Bool)
-> (PropertyProjection -> PropertyProjection -> Bool)
-> (PropertyProjection -> PropertyProjection -> PropertyProjection)
-> (PropertyProjection -> PropertyProjection -> PropertyProjection)
-> Ord PropertyProjection
PropertyProjection -> PropertyProjection -> Bool
PropertyProjection -> PropertyProjection -> Ordering
PropertyProjection -> PropertyProjection -> PropertyProjection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyProjection -> PropertyProjection -> Ordering
compare :: PropertyProjection -> PropertyProjection -> Ordering
$c< :: PropertyProjection -> PropertyProjection -> Bool
< :: PropertyProjection -> PropertyProjection -> Bool
$c<= :: PropertyProjection -> PropertyProjection -> Bool
<= :: PropertyProjection -> PropertyProjection -> Bool
$c> :: PropertyProjection -> PropertyProjection -> Bool
> :: PropertyProjection -> PropertyProjection -> Bool
$c>= :: PropertyProjection -> PropertyProjection -> Bool
>= :: PropertyProjection -> PropertyProjection -> Bool
$cmax :: PropertyProjection -> PropertyProjection -> PropertyProjection
max :: PropertyProjection -> PropertyProjection -> PropertyProjection
$cmin :: PropertyProjection -> PropertyProjection -> PropertyProjection
min :: PropertyProjection -> PropertyProjection -> PropertyProjection
Ord, ReadPrec [PropertyProjection]
ReadPrec PropertyProjection
Int -> ReadS PropertyProjection
ReadS [PropertyProjection]
(Int -> ReadS PropertyProjection)
-> ReadS [PropertyProjection]
-> ReadPrec PropertyProjection
-> ReadPrec [PropertyProjection]
-> Read PropertyProjection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyProjection
readsPrec :: Int -> ReadS PropertyProjection
$creadList :: ReadS [PropertyProjection]
readList :: ReadS [PropertyProjection]
$creadPrec :: ReadPrec PropertyProjection
readPrec :: ReadPrec PropertyProjection
$creadListPrec :: ReadPrec [PropertyProjection]
readListPrec :: ReadPrec [PropertyProjection]
Read, Int -> PropertyProjection -> ShowS
[PropertyProjection] -> ShowS
PropertyProjection -> String
(Int -> PropertyProjection -> ShowS)
-> (PropertyProjection -> String)
-> ([PropertyProjection] -> ShowS)
-> Show PropertyProjection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyProjection -> ShowS
showsPrec :: Int -> PropertyProjection -> ShowS
$cshow :: PropertyProjection -> String
show :: PropertyProjection -> String
$cshowList :: [PropertyProjection] -> ShowS
showList :: [PropertyProjection] -> ShowS
Show)

_PropertyProjection :: Name
_PropertyProjection = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.PropertyProjection")

_PropertyProjection_base :: Name
_PropertyProjection_base = (String -> Name
Core.Name String
"base")

_PropertyProjection_key :: Name
_PropertyProjection_key = (String -> Name
Core.Name String
"key")

newtype PropertyValue = 
  PropertyValue {
    PropertyValue -> String
unPropertyValue :: String}
  deriving (PropertyValue -> PropertyValue -> Bool
(PropertyValue -> PropertyValue -> Bool)
-> (PropertyValue -> PropertyValue -> Bool) -> Eq PropertyValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyValue -> PropertyValue -> Bool
== :: PropertyValue -> PropertyValue -> Bool
$c/= :: PropertyValue -> PropertyValue -> Bool
/= :: PropertyValue -> PropertyValue -> Bool
Eq, Eq PropertyValue
Eq PropertyValue =>
(PropertyValue -> PropertyValue -> Ordering)
-> (PropertyValue -> PropertyValue -> Bool)
-> (PropertyValue -> PropertyValue -> Bool)
-> (PropertyValue -> PropertyValue -> Bool)
-> (PropertyValue -> PropertyValue -> Bool)
-> (PropertyValue -> PropertyValue -> PropertyValue)
-> (PropertyValue -> PropertyValue -> PropertyValue)
-> Ord PropertyValue
PropertyValue -> PropertyValue -> Bool
PropertyValue -> PropertyValue -> Ordering
PropertyValue -> PropertyValue -> PropertyValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyValue -> PropertyValue -> Ordering
compare :: PropertyValue -> PropertyValue -> Ordering
$c< :: PropertyValue -> PropertyValue -> Bool
< :: PropertyValue -> PropertyValue -> Bool
$c<= :: PropertyValue -> PropertyValue -> Bool
<= :: PropertyValue -> PropertyValue -> Bool
$c> :: PropertyValue -> PropertyValue -> Bool
> :: PropertyValue -> PropertyValue -> Bool
$c>= :: PropertyValue -> PropertyValue -> Bool
>= :: PropertyValue -> PropertyValue -> Bool
$cmax :: PropertyValue -> PropertyValue -> PropertyValue
max :: PropertyValue -> PropertyValue -> PropertyValue
$cmin :: PropertyValue -> PropertyValue -> PropertyValue
min :: PropertyValue -> PropertyValue -> PropertyValue
Ord, ReadPrec [PropertyValue]
ReadPrec PropertyValue
Int -> ReadS PropertyValue
ReadS [PropertyValue]
(Int -> ReadS PropertyValue)
-> ReadS [PropertyValue]
-> ReadPrec PropertyValue
-> ReadPrec [PropertyValue]
-> Read PropertyValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyValue
readsPrec :: Int -> ReadS PropertyValue
$creadList :: ReadS [PropertyValue]
readList :: ReadS [PropertyValue]
$creadPrec :: ReadPrec PropertyValue
readPrec :: ReadPrec PropertyValue
$creadListPrec :: ReadPrec [PropertyValue]
readListPrec :: ReadPrec [PropertyValue]
Read, Int -> PropertyValue -> ShowS
[PropertyValue] -> ShowS
PropertyValue -> String
(Int -> PropertyValue -> ShowS)
-> (PropertyValue -> String)
-> ([PropertyValue] -> ShowS)
-> Show PropertyValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyValue -> ShowS
showsPrec :: Int -> PropertyValue -> ShowS
$cshow :: PropertyValue -> String
show :: PropertyValue -> String
$cshowList :: [PropertyValue] -> ShowS
showList :: [PropertyValue] -> ShowS
Show)

_PropertyValue :: Name
_PropertyValue = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.PropertyValue")

data PropertyValuePattern = 
  PropertyValuePatternVariable PropertyGraph.PropertyKey |
  PropertyValuePatternValue String
  deriving (PropertyValuePattern -> PropertyValuePattern -> Bool
(PropertyValuePattern -> PropertyValuePattern -> Bool)
-> (PropertyValuePattern -> PropertyValuePattern -> Bool)
-> Eq PropertyValuePattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyValuePattern -> PropertyValuePattern -> Bool
== :: PropertyValuePattern -> PropertyValuePattern -> Bool
$c/= :: PropertyValuePattern -> PropertyValuePattern -> Bool
/= :: PropertyValuePattern -> PropertyValuePattern -> Bool
Eq, Eq PropertyValuePattern
Eq PropertyValuePattern =>
(PropertyValuePattern -> PropertyValuePattern -> Ordering)
-> (PropertyValuePattern -> PropertyValuePattern -> Bool)
-> (PropertyValuePattern -> PropertyValuePattern -> Bool)
-> (PropertyValuePattern -> PropertyValuePattern -> Bool)
-> (PropertyValuePattern -> PropertyValuePattern -> Bool)
-> (PropertyValuePattern
    -> PropertyValuePattern -> PropertyValuePattern)
-> (PropertyValuePattern
    -> PropertyValuePattern -> PropertyValuePattern)
-> Ord PropertyValuePattern
PropertyValuePattern -> PropertyValuePattern -> Bool
PropertyValuePattern -> PropertyValuePattern -> Ordering
PropertyValuePattern
-> PropertyValuePattern -> PropertyValuePattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyValuePattern -> PropertyValuePattern -> Ordering
compare :: PropertyValuePattern -> PropertyValuePattern -> Ordering
$c< :: PropertyValuePattern -> PropertyValuePattern -> Bool
< :: PropertyValuePattern -> PropertyValuePattern -> Bool
$c<= :: PropertyValuePattern -> PropertyValuePattern -> Bool
<= :: PropertyValuePattern -> PropertyValuePattern -> Bool
$c> :: PropertyValuePattern -> PropertyValuePattern -> Bool
> :: PropertyValuePattern -> PropertyValuePattern -> Bool
$c>= :: PropertyValuePattern -> PropertyValuePattern -> Bool
>= :: PropertyValuePattern -> PropertyValuePattern -> Bool
$cmax :: PropertyValuePattern
-> PropertyValuePattern -> PropertyValuePattern
max :: PropertyValuePattern
-> PropertyValuePattern -> PropertyValuePattern
$cmin :: PropertyValuePattern
-> PropertyValuePattern -> PropertyValuePattern
min :: PropertyValuePattern
-> PropertyValuePattern -> PropertyValuePattern
Ord, ReadPrec [PropertyValuePattern]
ReadPrec PropertyValuePattern
Int -> ReadS PropertyValuePattern
ReadS [PropertyValuePattern]
(Int -> ReadS PropertyValuePattern)
-> ReadS [PropertyValuePattern]
-> ReadPrec PropertyValuePattern
-> ReadPrec [PropertyValuePattern]
-> Read PropertyValuePattern
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyValuePattern
readsPrec :: Int -> ReadS PropertyValuePattern
$creadList :: ReadS [PropertyValuePattern]
readList :: ReadS [PropertyValuePattern]
$creadPrec :: ReadPrec PropertyValuePattern
readPrec :: ReadPrec PropertyValuePattern
$creadListPrec :: ReadPrec [PropertyValuePattern]
readListPrec :: ReadPrec [PropertyValuePattern]
Read, Int -> PropertyValuePattern -> ShowS
[PropertyValuePattern] -> ShowS
PropertyValuePattern -> String
(Int -> PropertyValuePattern -> ShowS)
-> (PropertyValuePattern -> String)
-> ([PropertyValuePattern] -> ShowS)
-> Show PropertyValuePattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyValuePattern -> ShowS
showsPrec :: Int -> PropertyValuePattern -> ShowS
$cshow :: PropertyValuePattern -> String
show :: PropertyValuePattern -> String
$cshowList :: [PropertyValuePattern] -> ShowS
showList :: [PropertyValuePattern] -> ShowS
Show)

_PropertyValuePattern :: Name
_PropertyValuePattern = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.PropertyValuePattern")

_PropertyValuePattern_variable :: Name
_PropertyValuePattern_variable = (String -> Name
Core.Name String
"variable")

_PropertyValuePattern_value :: Name
_PropertyValuePattern_value = (String -> Name
Core.Name String
"value")

data Query = 
  QueryApplication ApplicationQuery |
  QueryAggregate AggregationQuery |
  QueryLetQuery LetQuery |
  QueryMatch MatchQuery |
  QuerySelect SelectQuery |
  QueryValue String
  deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
/= :: Query -> Query -> Bool
Eq, Eq Query
Eq Query =>
(Query -> Query -> Ordering)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Query)
-> (Query -> Query -> Query)
-> Ord Query
Query -> Query -> Bool
Query -> Query -> Ordering
Query -> Query -> Query
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Query -> Query -> Ordering
compare :: Query -> Query -> Ordering
$c< :: Query -> Query -> Bool
< :: Query -> Query -> Bool
$c<= :: Query -> Query -> Bool
<= :: Query -> Query -> Bool
$c> :: Query -> Query -> Bool
> :: Query -> Query -> Bool
$c>= :: Query -> Query -> Bool
>= :: Query -> Query -> Bool
$cmax :: Query -> Query -> Query
max :: Query -> Query -> Query
$cmin :: Query -> Query -> Query
min :: Query -> Query -> Query
Ord, ReadPrec [Query]
ReadPrec Query
Int -> ReadS Query
ReadS [Query]
(Int -> ReadS Query)
-> ReadS [Query]
-> ReadPrec Query
-> ReadPrec [Query]
-> Read Query
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Query
readsPrec :: Int -> ReadS Query
$creadList :: ReadS [Query]
readList :: ReadS [Query]
$creadPrec :: ReadPrec Query
readPrec :: ReadPrec Query
$creadListPrec :: ReadPrec [Query]
readListPrec :: ReadPrec [Query]
Read, Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Query -> ShowS
showsPrec :: Int -> Query -> ShowS
$cshow :: Query -> String
show :: Query -> String
$cshowList :: [Query] -> ShowS
showList :: [Query] -> ShowS
Show)

_Query :: Name
_Query = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Query")

_Query_application :: Name
_Query_application = (String -> Name
Core.Name String
"application")

_Query_aggregate :: Name
_Query_aggregate = (String -> Name
Core.Name String
"aggregate")

_Query_LetQuery :: Name
_Query_LetQuery = (String -> Name
Core.Name String
"LetQuery")

_Query_match :: Name
_Query_match = (String -> Name
Core.Name String
"match")

_Query_select :: Name
_Query_select = (String -> Name
Core.Name String
"select")

_Query_value :: Name
_Query_value = (String -> Name
Core.Name String
"value")

data SelectQuery = 
  SelectQuery {
    SelectQuery -> Bool
selectQueryDistinct :: Bool,
    SelectQuery -> Projections
selectQueryProjection :: Projections}
  deriving (SelectQuery -> SelectQuery -> Bool
(SelectQuery -> SelectQuery -> Bool)
-> (SelectQuery -> SelectQuery -> Bool) -> Eq SelectQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SelectQuery -> SelectQuery -> Bool
== :: SelectQuery -> SelectQuery -> Bool
$c/= :: SelectQuery -> SelectQuery -> Bool
/= :: SelectQuery -> SelectQuery -> Bool
Eq, Eq SelectQuery
Eq SelectQuery =>
(SelectQuery -> SelectQuery -> Ordering)
-> (SelectQuery -> SelectQuery -> Bool)
-> (SelectQuery -> SelectQuery -> Bool)
-> (SelectQuery -> SelectQuery -> Bool)
-> (SelectQuery -> SelectQuery -> Bool)
-> (SelectQuery -> SelectQuery -> SelectQuery)
-> (SelectQuery -> SelectQuery -> SelectQuery)
-> Ord SelectQuery
SelectQuery -> SelectQuery -> Bool
SelectQuery -> SelectQuery -> Ordering
SelectQuery -> SelectQuery -> SelectQuery
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SelectQuery -> SelectQuery -> Ordering
compare :: SelectQuery -> SelectQuery -> Ordering
$c< :: SelectQuery -> SelectQuery -> Bool
< :: SelectQuery -> SelectQuery -> Bool
$c<= :: SelectQuery -> SelectQuery -> Bool
<= :: SelectQuery -> SelectQuery -> Bool
$c> :: SelectQuery -> SelectQuery -> Bool
> :: SelectQuery -> SelectQuery -> Bool
$c>= :: SelectQuery -> SelectQuery -> Bool
>= :: SelectQuery -> SelectQuery -> Bool
$cmax :: SelectQuery -> SelectQuery -> SelectQuery
max :: SelectQuery -> SelectQuery -> SelectQuery
$cmin :: SelectQuery -> SelectQuery -> SelectQuery
min :: SelectQuery -> SelectQuery -> SelectQuery
Ord, ReadPrec [SelectQuery]
ReadPrec SelectQuery
Int -> ReadS SelectQuery
ReadS [SelectQuery]
(Int -> ReadS SelectQuery)
-> ReadS [SelectQuery]
-> ReadPrec SelectQuery
-> ReadPrec [SelectQuery]
-> Read SelectQuery
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SelectQuery
readsPrec :: Int -> ReadS SelectQuery
$creadList :: ReadS [SelectQuery]
readList :: ReadS [SelectQuery]
$creadPrec :: ReadPrec SelectQuery
readPrec :: ReadPrec SelectQuery
$creadListPrec :: ReadPrec [SelectQuery]
readListPrec :: ReadPrec [SelectQuery]
Read, Int -> SelectQuery -> ShowS
[SelectQuery] -> ShowS
SelectQuery -> String
(Int -> SelectQuery -> ShowS)
-> (SelectQuery -> String)
-> ([SelectQuery] -> ShowS)
-> Show SelectQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SelectQuery -> ShowS
showsPrec :: Int -> SelectQuery -> ShowS
$cshow :: SelectQuery -> String
show :: SelectQuery -> String
$cshowList :: [SelectQuery] -> ShowS
showList :: [SelectQuery] -> ShowS
Show)

_SelectQuery :: Name
_SelectQuery = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.SelectQuery")

_SelectQuery_distinct :: Name
_SelectQuery_distinct = (String -> Name
Core.Name String
"distinct")

_SelectQuery_projection :: Name
_SelectQuery_projection = (String -> Name
Core.Name String
"projection")

data UnaryExpression = 
  UnaryExpression {
    UnaryExpression -> UnaryOperator
unaryExpressionOperator :: UnaryOperator,
    UnaryExpression -> Expression
unaryExpressionOperand :: Expression}
  deriving (UnaryExpression -> UnaryExpression -> Bool
(UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> Eq UnaryExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryExpression -> UnaryExpression -> Bool
== :: UnaryExpression -> UnaryExpression -> Bool
$c/= :: UnaryExpression -> UnaryExpression -> Bool
/= :: UnaryExpression -> UnaryExpression -> Bool
Eq, Eq UnaryExpression
Eq UnaryExpression =>
(UnaryExpression -> UnaryExpression -> Ordering)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> Ord UnaryExpression
UnaryExpression -> UnaryExpression -> Bool
UnaryExpression -> UnaryExpression -> Ordering
UnaryExpression -> UnaryExpression -> UnaryExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnaryExpression -> UnaryExpression -> Ordering
compare :: UnaryExpression -> UnaryExpression -> Ordering
$c< :: UnaryExpression -> UnaryExpression -> Bool
< :: UnaryExpression -> UnaryExpression -> Bool
$c<= :: UnaryExpression -> UnaryExpression -> Bool
<= :: UnaryExpression -> UnaryExpression -> Bool
$c> :: UnaryExpression -> UnaryExpression -> Bool
> :: UnaryExpression -> UnaryExpression -> Bool
$c>= :: UnaryExpression -> UnaryExpression -> Bool
>= :: UnaryExpression -> UnaryExpression -> Bool
$cmax :: UnaryExpression -> UnaryExpression -> UnaryExpression
max :: UnaryExpression -> UnaryExpression -> UnaryExpression
$cmin :: UnaryExpression -> UnaryExpression -> UnaryExpression
min :: UnaryExpression -> UnaryExpression -> UnaryExpression
Ord, ReadPrec [UnaryExpression]
ReadPrec UnaryExpression
Int -> ReadS UnaryExpression
ReadS [UnaryExpression]
(Int -> ReadS UnaryExpression)
-> ReadS [UnaryExpression]
-> ReadPrec UnaryExpression
-> ReadPrec [UnaryExpression]
-> Read UnaryExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryExpression
readsPrec :: Int -> ReadS UnaryExpression
$creadList :: ReadS [UnaryExpression]
readList :: ReadS [UnaryExpression]
$creadPrec :: ReadPrec UnaryExpression
readPrec :: ReadPrec UnaryExpression
$creadListPrec :: ReadPrec [UnaryExpression]
readListPrec :: ReadPrec [UnaryExpression]
Read, Int -> UnaryExpression -> ShowS
[UnaryExpression] -> ShowS
UnaryExpression -> String
(Int -> UnaryExpression -> ShowS)
-> (UnaryExpression -> String)
-> ([UnaryExpression] -> ShowS)
-> Show UnaryExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnaryExpression -> ShowS
showsPrec :: Int -> UnaryExpression -> ShowS
$cshow :: UnaryExpression -> String
show :: UnaryExpression -> String
$cshowList :: [UnaryExpression] -> ShowS
showList :: [UnaryExpression] -> ShowS
Show)

_UnaryExpression :: Name
_UnaryExpression = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.UnaryExpression")

_UnaryExpression_operator :: Name
_UnaryExpression_operator = (String -> Name
Core.Name String
"operator")

_UnaryExpression_operand :: Name
_UnaryExpression_operand = (String -> Name
Core.Name String
"operand")

data UnaryOperator = 
  UnaryOperatorNegate 
  deriving (UnaryOperator -> UnaryOperator -> Bool
(UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool) -> Eq UnaryOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryOperator -> UnaryOperator -> Bool
== :: UnaryOperator -> UnaryOperator -> Bool
$c/= :: UnaryOperator -> UnaryOperator -> Bool
/= :: UnaryOperator -> UnaryOperator -> Bool
Eq, Eq UnaryOperator
Eq UnaryOperator =>
(UnaryOperator -> UnaryOperator -> Ordering)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> UnaryOperator)
-> (UnaryOperator -> UnaryOperator -> UnaryOperator)
-> Ord UnaryOperator
UnaryOperator -> UnaryOperator -> Bool
UnaryOperator -> UnaryOperator -> Ordering
UnaryOperator -> UnaryOperator -> UnaryOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnaryOperator -> UnaryOperator -> Ordering
compare :: UnaryOperator -> UnaryOperator -> Ordering
$c< :: UnaryOperator -> UnaryOperator -> Bool
< :: UnaryOperator -> UnaryOperator -> Bool
$c<= :: UnaryOperator -> UnaryOperator -> Bool
<= :: UnaryOperator -> UnaryOperator -> Bool
$c> :: UnaryOperator -> UnaryOperator -> Bool
> :: UnaryOperator -> UnaryOperator -> Bool
$c>= :: UnaryOperator -> UnaryOperator -> Bool
>= :: UnaryOperator -> UnaryOperator -> Bool
$cmax :: UnaryOperator -> UnaryOperator -> UnaryOperator
max :: UnaryOperator -> UnaryOperator -> UnaryOperator
$cmin :: UnaryOperator -> UnaryOperator -> UnaryOperator
min :: UnaryOperator -> UnaryOperator -> UnaryOperator
Ord, ReadPrec [UnaryOperator]
ReadPrec UnaryOperator
Int -> ReadS UnaryOperator
ReadS [UnaryOperator]
(Int -> ReadS UnaryOperator)
-> ReadS [UnaryOperator]
-> ReadPrec UnaryOperator
-> ReadPrec [UnaryOperator]
-> Read UnaryOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryOperator
readsPrec :: Int -> ReadS UnaryOperator
$creadList :: ReadS [UnaryOperator]
readList :: ReadS [UnaryOperator]
$creadPrec :: ReadPrec UnaryOperator
readPrec :: ReadPrec UnaryOperator
$creadListPrec :: ReadPrec [UnaryOperator]
readListPrec :: ReadPrec [UnaryOperator]
Read, Int -> UnaryOperator -> ShowS
[UnaryOperator] -> ShowS
UnaryOperator -> String
(Int -> UnaryOperator -> ShowS)
-> (UnaryOperator -> String)
-> ([UnaryOperator] -> ShowS)
-> Show UnaryOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnaryOperator -> ShowS
showsPrec :: Int -> UnaryOperator -> ShowS
$cshow :: UnaryOperator -> String
show :: UnaryOperator -> String
$cshowList :: [UnaryOperator] -> ShowS
showList :: [UnaryOperator] -> ShowS
Show)

_UnaryOperator :: Name
_UnaryOperator = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.UnaryOperator")

_UnaryOperator_negate :: Name
_UnaryOperator_negate = (String -> Name
Core.Name String
"negate")

newtype Variable = 
  Variable {
    Variable -> String
unVariable :: String}
  deriving (Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, Eq Variable
Eq Variable =>
(Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Variable -> Variable -> Ordering
compare :: Variable -> Variable -> Ordering
$c< :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
>= :: Variable -> Variable -> Bool
$cmax :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
min :: Variable -> Variable -> Variable
Ord, ReadPrec [Variable]
ReadPrec Variable
Int -> ReadS Variable
ReadS [Variable]
(Int -> ReadS Variable)
-> ReadS [Variable]
-> ReadPrec Variable
-> ReadPrec [Variable]
-> Read Variable
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Variable
readsPrec :: Int -> ReadS Variable
$creadList :: ReadS [Variable]
readList :: ReadS [Variable]
$creadPrec :: ReadPrec Variable
readPrec :: ReadPrec Variable
$creadListPrec :: ReadPrec [Variable]
readListPrec :: ReadPrec [Variable]
Read, Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Variable -> ShowS
showsPrec :: Int -> Variable -> ShowS
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> ShowS
showList :: [Variable] -> ShowS
Show)

_Variable :: Name
_Variable = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.Variable")

data VertexPattern = 
  VertexPattern {
    VertexPattern -> Maybe Variable
vertexPatternVariable :: (Maybe Variable),
    VertexPattern -> Maybe VertexLabel
vertexPatternLabel :: (Maybe PropertyGraph.VertexLabel),
    VertexPattern -> [PropertyPattern]
vertexPatternProperties :: [PropertyPattern],
    VertexPattern -> [EdgeProjectionPattern]
vertexPatternEdges :: [EdgeProjectionPattern]}
  deriving (VertexPattern -> VertexPattern -> Bool
(VertexPattern -> VertexPattern -> Bool)
-> (VertexPattern -> VertexPattern -> Bool) -> Eq VertexPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VertexPattern -> VertexPattern -> Bool
== :: VertexPattern -> VertexPattern -> Bool
$c/= :: VertexPattern -> VertexPattern -> Bool
/= :: VertexPattern -> VertexPattern -> Bool
Eq, Eq VertexPattern
Eq VertexPattern =>
(VertexPattern -> VertexPattern -> Ordering)
-> (VertexPattern -> VertexPattern -> Bool)
-> (VertexPattern -> VertexPattern -> Bool)
-> (VertexPattern -> VertexPattern -> Bool)
-> (VertexPattern -> VertexPattern -> Bool)
-> (VertexPattern -> VertexPattern -> VertexPattern)
-> (VertexPattern -> VertexPattern -> VertexPattern)
-> Ord VertexPattern
VertexPattern -> VertexPattern -> Bool
VertexPattern -> VertexPattern -> Ordering
VertexPattern -> VertexPattern -> VertexPattern
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: VertexPattern -> VertexPattern -> Ordering
compare :: VertexPattern -> VertexPattern -> Ordering
$c< :: VertexPattern -> VertexPattern -> Bool
< :: VertexPattern -> VertexPattern -> Bool
$c<= :: VertexPattern -> VertexPattern -> Bool
<= :: VertexPattern -> VertexPattern -> Bool
$c> :: VertexPattern -> VertexPattern -> Bool
> :: VertexPattern -> VertexPattern -> Bool
$c>= :: VertexPattern -> VertexPattern -> Bool
>= :: VertexPattern -> VertexPattern -> Bool
$cmax :: VertexPattern -> VertexPattern -> VertexPattern
max :: VertexPattern -> VertexPattern -> VertexPattern
$cmin :: VertexPattern -> VertexPattern -> VertexPattern
min :: VertexPattern -> VertexPattern -> VertexPattern
Ord, ReadPrec [VertexPattern]
ReadPrec VertexPattern
Int -> ReadS VertexPattern
ReadS [VertexPattern]
(Int -> ReadS VertexPattern)
-> ReadS [VertexPattern]
-> ReadPrec VertexPattern
-> ReadPrec [VertexPattern]
-> Read VertexPattern
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VertexPattern
readsPrec :: Int -> ReadS VertexPattern
$creadList :: ReadS [VertexPattern]
readList :: ReadS [VertexPattern]
$creadPrec :: ReadPrec VertexPattern
readPrec :: ReadPrec VertexPattern
$creadListPrec :: ReadPrec [VertexPattern]
readListPrec :: ReadPrec [VertexPattern]
Read, Int -> VertexPattern -> ShowS
[VertexPattern] -> ShowS
VertexPattern -> String
(Int -> VertexPattern -> ShowS)
-> (VertexPattern -> String)
-> ([VertexPattern] -> ShowS)
-> Show VertexPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VertexPattern -> ShowS
showsPrec :: Int -> VertexPattern -> ShowS
$cshow :: VertexPattern -> String
show :: VertexPattern -> String
$cshowList :: [VertexPattern] -> ShowS
showList :: [VertexPattern] -> ShowS
Show)

_VertexPattern :: Name
_VertexPattern = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/queries.VertexPattern")

_VertexPattern_variable :: Name
_VertexPattern_variable = (String -> Name
Core.Name String
"variable")

_VertexPattern_label :: Name
_VertexPattern_label = (String -> Name
Core.Name String
"label")

_VertexPattern_properties :: Name
_VertexPattern_properties = (String -> Name
Core.Name String
"properties")

_VertexPattern_edges :: Name
_VertexPattern_edges = (String -> Name
Core.Name String
"edges")