| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Pg.Query
Description
A common model for pattern-matching queries over property graphs
Documentation
data AggregationQuery Source #
Constructors
| AggregationQueryCount |
Instances
| Read AggregationQuery Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS AggregationQuery # readList :: ReadS [AggregationQuery] # | |
| Show AggregationQuery Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> AggregationQuery -> ShowS # show :: AggregationQuery -> String # showList :: [AggregationQuery] -> ShowS # | |
| Eq AggregationQuery Source # | |
Defined in Hydra.Pg.Query Methods (==) :: AggregationQuery -> AggregationQuery -> Bool # (/=) :: AggregationQuery -> AggregationQuery -> Bool # | |
| Ord AggregationQuery Source # | |
Defined in Hydra.Pg.Query Methods compare :: AggregationQuery -> AggregationQuery -> Ordering # (<) :: AggregationQuery -> AggregationQuery -> Bool # (<=) :: AggregationQuery -> AggregationQuery -> Bool # (>) :: AggregationQuery -> AggregationQuery -> Bool # (>=) :: AggregationQuery -> AggregationQuery -> Bool # max :: AggregationQuery -> AggregationQuery -> AggregationQuery # min :: AggregationQuery -> AggregationQuery -> AggregationQuery # | |
newtype ApplicationQuery Source #
Constructors
| ApplicationQuery | |
Fields
| |
Instances
| Read ApplicationQuery Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS ApplicationQuery # readList :: ReadS [ApplicationQuery] # | |
| Show ApplicationQuery Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> ApplicationQuery -> ShowS # show :: ApplicationQuery -> String # showList :: [ApplicationQuery] -> ShowS # | |
| Eq ApplicationQuery Source # | |
Defined in Hydra.Pg.Query Methods (==) :: ApplicationQuery -> ApplicationQuery -> Bool # (/=) :: ApplicationQuery -> ApplicationQuery -> Bool # | |
| Ord ApplicationQuery Source # | |
Defined in Hydra.Pg.Query Methods compare :: ApplicationQuery -> ApplicationQuery -> Ordering # (<) :: ApplicationQuery -> ApplicationQuery -> Bool # (<=) :: ApplicationQuery -> ApplicationQuery -> Bool # (>) :: ApplicationQuery -> ApplicationQuery -> Bool # (>=) :: ApplicationQuery -> ApplicationQuery -> Bool # max :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery # min :: ApplicationQuery -> ApplicationQuery -> ApplicationQuery # | |
data AssociativeExpression Source #
Constructors
| AssociativeExpression | |
Instances
data BinaryExpression Source #
Constructors
| BinaryExpression | |
Instances
| Read BinaryExpression Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS BinaryExpression # readList :: ReadS [BinaryExpression] # | |
| Show BinaryExpression Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> BinaryExpression -> ShowS # show :: BinaryExpression -> String # showList :: [BinaryExpression] -> ShowS # | |
| Eq BinaryExpression Source # | |
Defined in Hydra.Pg.Query Methods (==) :: BinaryExpression -> BinaryExpression -> Bool # (/=) :: BinaryExpression -> BinaryExpression -> Bool # | |
| Ord BinaryExpression Source # | |
Defined in Hydra.Pg.Query Methods compare :: BinaryExpression -> BinaryExpression -> Ordering # (<) :: BinaryExpression -> BinaryExpression -> Bool # (<=) :: BinaryExpression -> BinaryExpression -> Bool # (>) :: BinaryExpression -> BinaryExpression -> Bool # (>=) :: BinaryExpression -> BinaryExpression -> Bool # max :: BinaryExpression -> BinaryExpression -> BinaryExpression # min :: BinaryExpression -> BinaryExpression -> BinaryExpression # | |
data BinaryBooleanOperator Source #
Instances
data BinaryOperator Source #
Constructors
| BinaryOperatorBoolean BinaryBooleanOperator | |
| BinaryOperatorComparison ComparisonOperator | |
| BinaryOperatorPower |
Instances
| Read BinaryOperator Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS BinaryOperator # readList :: ReadS [BinaryOperator] # | |
| Show BinaryOperator Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> BinaryOperator -> ShowS # show :: BinaryOperator -> String # showList :: [BinaryOperator] -> ShowS # | |
| Eq BinaryOperator Source # | |
Defined in Hydra.Pg.Query Methods (==) :: BinaryOperator -> BinaryOperator -> Bool # (/=) :: BinaryOperator -> BinaryOperator -> Bool # | |
| Ord BinaryOperator Source # | |
Defined in Hydra.Pg.Query Methods compare :: BinaryOperator -> BinaryOperator -> Ordering # (<) :: BinaryOperator -> BinaryOperator -> Bool # (<=) :: BinaryOperator -> BinaryOperator -> Bool # (>) :: BinaryOperator -> BinaryOperator -> Bool # (>=) :: BinaryOperator -> BinaryOperator -> Bool # max :: BinaryOperator -> BinaryOperator -> BinaryOperator # min :: BinaryOperator -> BinaryOperator -> BinaryOperator # | |
Constructors
| Binding | |
Fields
| |
_Binding_key :: Name Source #
data ComparisonOperator Source #
Constructors
| ComparisonOperatorEq | |
| ComparisonOperatorNeq | |
| ComparisonOperatorLt | |
| ComparisonOperatorLte | |
| ComparisonOperatorGt | |
| ComparisonOperatorGte |
Instances
data EdgeProjectionPattern Source #
Constructors
| EdgeProjectionPattern | |
Instances
data Expression Source #
Constructors
Instances
| Read Expression Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS Expression # readList :: ReadS [Expression] # readPrec :: ReadPrec Expression # readListPrec :: ReadPrec [Expression] # | |
| Show Expression Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
| Eq Expression Source # | |
Defined in Hydra.Pg.Query | |
| Ord Expression Source # | |
Defined in Hydra.Pg.Query Methods compare :: Expression -> Expression -> Ordering # (<) :: Expression -> Expression -> Bool # (<=) :: Expression -> Expression -> Bool # (>) :: Expression -> Expression -> Bool # (>=) :: Expression -> Expression -> Bool # max :: Expression -> Expression -> Expression # min :: Expression -> Expression -> Expression # | |
_Expression :: Name Source #
Constructors
| LetQuery | |
Fields | |
data MatchQuery Source #
Constructors
| MatchQuery | |
Fields | |
Instances
| Read MatchQuery Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS MatchQuery # readList :: ReadS [MatchQuery] # readPrec :: ReadPrec MatchQuery # readListPrec :: ReadPrec [MatchQuery] # | |
| Show MatchQuery Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> MatchQuery -> ShowS # show :: MatchQuery -> String # showList :: [MatchQuery] -> ShowS # | |
| Eq MatchQuery Source # | |
Defined in Hydra.Pg.Query | |
| Ord MatchQuery Source # | |
Defined in Hydra.Pg.Query Methods compare :: MatchQuery -> MatchQuery -> Ordering # (<) :: MatchQuery -> MatchQuery -> Bool # (<=) :: MatchQuery -> MatchQuery -> Bool # (>) :: MatchQuery -> MatchQuery -> Bool # (>=) :: MatchQuery -> MatchQuery -> Bool # max :: MatchQuery -> MatchQuery -> MatchQuery # min :: MatchQuery -> MatchQuery -> MatchQuery # | |
_MatchQuery :: Name Source #
data Projection Source #
Constructors
| Projection | |
Fields | |
Instances
| Read Projection Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS Projection # readList :: ReadS [Projection] # readPrec :: ReadPrec Projection # readListPrec :: ReadPrec [Projection] # | |
| Show Projection Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
| Eq Projection Source # | |
Defined in Hydra.Pg.Query | |
| Ord Projection Source # | |
Defined in Hydra.Pg.Query Methods compare :: Projection -> Projection -> Ordering # (<) :: Projection -> Projection -> Bool # (<=) :: Projection -> Projection -> Bool # (>) :: Projection -> Projection -> Bool # (>=) :: Projection -> Projection -> Bool # max :: Projection -> Projection -> Projection # min :: Projection -> Projection -> Projection # | |
_Projection :: Name Source #
data Projections Source #
Constructors
| Projections | |
Fields | |
Instances
| Read Projections Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS Projections # readList :: ReadS [Projections] # readPrec :: ReadPrec Projections # readListPrec :: ReadPrec [Projections] # | |
| Show Projections Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> Projections -> ShowS # show :: Projections -> String # showList :: [Projections] -> ShowS # | |
| Eq Projections Source # | |
Defined in Hydra.Pg.Query | |
| Ord Projections Source # | |
Defined in Hydra.Pg.Query Methods compare :: Projections -> Projections -> Ordering # (<) :: Projections -> Projections -> Bool # (<=) :: Projections -> Projections -> Bool # (>) :: Projections -> Projections -> Bool # (>=) :: Projections -> Projections -> Bool # max :: Projections -> Projections -> Projections # min :: Projections -> Projections -> Projections # | |
_Projections :: Name Source #
data PropertyPattern Source #
Constructors
| PropertyPattern | |
Instances
| Read PropertyPattern Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS PropertyPattern # readList :: ReadS [PropertyPattern] # | |
| Show PropertyPattern Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> PropertyPattern -> ShowS # show :: PropertyPattern -> String # showList :: [PropertyPattern] -> ShowS # | |
| Eq PropertyPattern Source # | |
Defined in Hydra.Pg.Query Methods (==) :: PropertyPattern -> PropertyPattern -> Bool # (/=) :: PropertyPattern -> PropertyPattern -> Bool # | |
| Ord PropertyPattern Source # | |
Defined in Hydra.Pg.Query Methods compare :: PropertyPattern -> PropertyPattern -> Ordering # (<) :: PropertyPattern -> PropertyPattern -> Bool # (<=) :: PropertyPattern -> PropertyPattern -> Bool # (>) :: PropertyPattern -> PropertyPattern -> Bool # (>=) :: PropertyPattern -> PropertyPattern -> Bool # max :: PropertyPattern -> PropertyPattern -> PropertyPattern # min :: PropertyPattern -> PropertyPattern -> PropertyPattern # | |
data PropertyProjection Source #
Constructors
| PropertyProjection | |
Instances
newtype PropertyValue Source #
Constructors
| PropertyValue | |
Fields | |
Instances
| Read PropertyValue Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS PropertyValue # readList :: ReadS [PropertyValue] # | |
| Show PropertyValue Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> PropertyValue -> ShowS # show :: PropertyValue -> String # showList :: [PropertyValue] -> ShowS # | |
| Eq PropertyValue Source # | |
Defined in Hydra.Pg.Query Methods (==) :: PropertyValue -> PropertyValue -> Bool # (/=) :: PropertyValue -> PropertyValue -> Bool # | |
| Ord PropertyValue Source # | |
Defined in Hydra.Pg.Query Methods compare :: PropertyValue -> PropertyValue -> Ordering # (<) :: PropertyValue -> PropertyValue -> Bool # (<=) :: PropertyValue -> PropertyValue -> Bool # (>) :: PropertyValue -> PropertyValue -> Bool # (>=) :: PropertyValue -> PropertyValue -> Bool # max :: PropertyValue -> PropertyValue -> PropertyValue # min :: PropertyValue -> PropertyValue -> PropertyValue # | |
data PropertyValuePattern Source #
Instances
Constructors
| QueryApplication ApplicationQuery | |
| QueryAggregate AggregationQuery | |
| QueryLetQuery LetQuery | |
| QueryMatch MatchQuery | |
| QuerySelect SelectQuery | |
| QueryValue String |
_Query_match :: Name Source #
_Query_select :: Name Source #
_Query_value :: Name Source #
data SelectQuery Source #
Constructors
| SelectQuery | |
Fields | |
Instances
| Read SelectQuery Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS SelectQuery # readList :: ReadS [SelectQuery] # readPrec :: ReadPrec SelectQuery # readListPrec :: ReadPrec [SelectQuery] # | |
| Show SelectQuery Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> SelectQuery -> ShowS # show :: SelectQuery -> String # showList :: [SelectQuery] -> ShowS # | |
| Eq SelectQuery Source # | |
Defined in Hydra.Pg.Query | |
| Ord SelectQuery Source # | |
Defined in Hydra.Pg.Query Methods compare :: SelectQuery -> SelectQuery -> Ordering # (<) :: SelectQuery -> SelectQuery -> Bool # (<=) :: SelectQuery -> SelectQuery -> Bool # (>) :: SelectQuery -> SelectQuery -> Bool # (>=) :: SelectQuery -> SelectQuery -> Bool # max :: SelectQuery -> SelectQuery -> SelectQuery # min :: SelectQuery -> SelectQuery -> SelectQuery # | |
_SelectQuery :: Name Source #
data UnaryExpression Source #
Constructors
| UnaryExpression | |
Instances
| Read UnaryExpression Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS UnaryExpression # readList :: ReadS [UnaryExpression] # | |
| Show UnaryExpression Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> UnaryExpression -> ShowS # show :: UnaryExpression -> String # showList :: [UnaryExpression] -> ShowS # | |
| Eq UnaryExpression Source # | |
Defined in Hydra.Pg.Query Methods (==) :: UnaryExpression -> UnaryExpression -> Bool # (/=) :: UnaryExpression -> UnaryExpression -> Bool # | |
| Ord UnaryExpression Source # | |
Defined in Hydra.Pg.Query Methods compare :: UnaryExpression -> UnaryExpression -> Ordering # (<) :: UnaryExpression -> UnaryExpression -> Bool # (<=) :: UnaryExpression -> UnaryExpression -> Bool # (>) :: UnaryExpression -> UnaryExpression -> Bool # (>=) :: UnaryExpression -> UnaryExpression -> Bool # max :: UnaryExpression -> UnaryExpression -> UnaryExpression # min :: UnaryExpression -> UnaryExpression -> UnaryExpression # | |
data UnaryOperator Source #
Constructors
| UnaryOperatorNegate |
Instances
| Read UnaryOperator Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS UnaryOperator # readList :: ReadS [UnaryOperator] # | |
| Show UnaryOperator Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> UnaryOperator -> ShowS # show :: UnaryOperator -> String # showList :: [UnaryOperator] -> ShowS # | |
| Eq UnaryOperator Source # | |
Defined in Hydra.Pg.Query Methods (==) :: UnaryOperator -> UnaryOperator -> Bool # (/=) :: UnaryOperator -> UnaryOperator -> Bool # | |
| Ord UnaryOperator Source # | |
Defined in Hydra.Pg.Query Methods compare :: UnaryOperator -> UnaryOperator -> Ordering # (<) :: UnaryOperator -> UnaryOperator -> Bool # (<=) :: UnaryOperator -> UnaryOperator -> Bool # (>) :: UnaryOperator -> UnaryOperator -> Bool # (>=) :: UnaryOperator -> UnaryOperator -> Bool # max :: UnaryOperator -> UnaryOperator -> UnaryOperator # min :: UnaryOperator -> UnaryOperator -> UnaryOperator # | |
Constructors
| Variable | |
Fields
| |
data VertexPattern Source #
Constructors
| VertexPattern | |
Instances
| Read VertexPattern Source # | |
Defined in Hydra.Pg.Query Methods readsPrec :: Int -> ReadS VertexPattern # readList :: ReadS [VertexPattern] # | |
| Show VertexPattern Source # | |
Defined in Hydra.Pg.Query Methods showsPrec :: Int -> VertexPattern -> ShowS # show :: VertexPattern -> String # showList :: [VertexPattern] -> ShowS # | |
| Eq VertexPattern Source # | |
Defined in Hydra.Pg.Query Methods (==) :: VertexPattern -> VertexPattern -> Bool # (/=) :: VertexPattern -> VertexPattern -> Bool # | |
| Ord VertexPattern Source # | |
Defined in Hydra.Pg.Query Methods compare :: VertexPattern -> VertexPattern -> Ordering # (<) :: VertexPattern -> VertexPattern -> Bool # (<=) :: VertexPattern -> VertexPattern -> Bool # (>) :: VertexPattern -> VertexPattern -> Bool # (>=) :: VertexPattern -> VertexPattern -> Bool # max :: VertexPattern -> VertexPattern -> VertexPattern # min :: VertexPattern -> VertexPattern -> VertexPattern # | |