module Hydra.Langs.Tinkerpop.PropertyGraph where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data Direction =
DirectionOut |
DirectionIn |
DirectionBoth |
DirectionUndirected
deriving (Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
/= :: Direction -> Direction -> Bool
Eq, Eq Direction
Eq Direction =>
(Direction -> Direction -> Ordering)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Direction)
-> (Direction -> Direction -> Direction)
-> Ord Direction
Direction -> Direction -> Bool
Direction -> Direction -> Ordering
Direction -> Direction -> Direction
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 :: Direction -> Direction -> Ordering
compare :: Direction -> Direction -> Ordering
$c< :: Direction -> Direction -> Bool
< :: Direction -> Direction -> Bool
$c<= :: Direction -> Direction -> Bool
<= :: Direction -> Direction -> Bool
$c> :: Direction -> Direction -> Bool
> :: Direction -> Direction -> Bool
$c>= :: Direction -> Direction -> Bool
>= :: Direction -> Direction -> Bool
$cmax :: Direction -> Direction -> Direction
max :: Direction -> Direction -> Direction
$cmin :: Direction -> Direction -> Direction
min :: Direction -> Direction -> Direction
Ord, ReadPrec [Direction]
ReadPrec Direction
Int -> ReadS Direction
ReadS [Direction]
(Int -> ReadS Direction)
-> ReadS [Direction]
-> ReadPrec Direction
-> ReadPrec [Direction]
-> Read Direction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Direction
readsPrec :: Int -> ReadS Direction
$creadList :: ReadS [Direction]
readList :: ReadS [Direction]
$creadPrec :: ReadPrec Direction
readPrec :: ReadPrec Direction
$creadListPrec :: ReadPrec [Direction]
readListPrec :: ReadPrec [Direction]
Read, Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Direction -> ShowS
showsPrec :: Int -> Direction -> ShowS
$cshow :: Direction -> String
show :: Direction -> String
$cshowList :: [Direction] -> ShowS
showList :: [Direction] -> ShowS
Show)
_Direction :: Name
_Direction = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Direction")
_Direction_out :: Name
_Direction_out = (String -> Name
Core.Name String
"out")
_Direction_in :: Name
_Direction_in = (String -> Name
Core.Name String
"in")
_Direction_both :: Name
_Direction_both = (String -> Name
Core.Name String
"both")
_Direction_undirected :: Name
_Direction_undirected = (String -> Name
Core.Name String
"undirected")
data Edge v =
Edge {
forall v. Edge v -> EdgeLabel
edgeLabel :: EdgeLabel,
forall v. Edge v -> v
edgeId :: v,
forall v. Edge v -> v
edgeOut :: v,
forall v. Edge v -> v
edgeIn :: v,
forall v. Edge v -> Map PropertyKey v
edgeProperties :: (Map PropertyKey v)}
deriving (Edge v -> Edge v -> Bool
(Edge v -> Edge v -> Bool)
-> (Edge v -> Edge v -> Bool) -> Eq (Edge v)
forall v. Eq v => Edge v -> Edge v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Edge v -> Edge v -> Bool
== :: Edge v -> Edge v -> Bool
$c/= :: forall v. Eq v => Edge v -> Edge v -> Bool
/= :: Edge v -> Edge v -> Bool
Eq, Eq (Edge v)
Eq (Edge v) =>
(Edge v -> Edge v -> Ordering)
-> (Edge v -> Edge v -> Bool)
-> (Edge v -> Edge v -> Bool)
-> (Edge v -> Edge v -> Bool)
-> (Edge v -> Edge v -> Bool)
-> (Edge v -> Edge v -> Edge v)
-> (Edge v -> Edge v -> Edge v)
-> Ord (Edge v)
Edge v -> Edge v -> Bool
Edge v -> Edge v -> Ordering
Edge v -> Edge v -> Edge v
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
forall v. Ord v => Eq (Edge v)
forall v. Ord v => Edge v -> Edge v -> Bool
forall v. Ord v => Edge v -> Edge v -> Ordering
forall v. Ord v => Edge v -> Edge v -> Edge v
$ccompare :: forall v. Ord v => Edge v -> Edge v -> Ordering
compare :: Edge v -> Edge v -> Ordering
$c< :: forall v. Ord v => Edge v -> Edge v -> Bool
< :: Edge v -> Edge v -> Bool
$c<= :: forall v. Ord v => Edge v -> Edge v -> Bool
<= :: Edge v -> Edge v -> Bool
$c> :: forall v. Ord v => Edge v -> Edge v -> Bool
> :: Edge v -> Edge v -> Bool
$c>= :: forall v. Ord v => Edge v -> Edge v -> Bool
>= :: Edge v -> Edge v -> Bool
$cmax :: forall v. Ord v => Edge v -> Edge v -> Edge v
max :: Edge v -> Edge v -> Edge v
$cmin :: forall v. Ord v => Edge v -> Edge v -> Edge v
min :: Edge v -> Edge v -> Edge v
Ord, ReadPrec [Edge v]
ReadPrec (Edge v)
Int -> ReadS (Edge v)
ReadS [Edge v]
(Int -> ReadS (Edge v))
-> ReadS [Edge v]
-> ReadPrec (Edge v)
-> ReadPrec [Edge v]
-> Read (Edge v)
forall v. Read v => ReadPrec [Edge v]
forall v. Read v => ReadPrec (Edge v)
forall v. Read v => Int -> ReadS (Edge v)
forall v. Read v => ReadS [Edge v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. Read v => Int -> ReadS (Edge v)
readsPrec :: Int -> ReadS (Edge v)
$creadList :: forall v. Read v => ReadS [Edge v]
readList :: ReadS [Edge v]
$creadPrec :: forall v. Read v => ReadPrec (Edge v)
readPrec :: ReadPrec (Edge v)
$creadListPrec :: forall v. Read v => ReadPrec [Edge v]
readListPrec :: ReadPrec [Edge v]
Read, Int -> Edge v -> ShowS
[Edge v] -> ShowS
Edge v -> String
(Int -> Edge v -> ShowS)
-> (Edge v -> String) -> ([Edge v] -> ShowS) -> Show (Edge v)
forall v. Show v => Int -> Edge v -> ShowS
forall v. Show v => [Edge v] -> ShowS
forall v. Show v => Edge v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Edge v -> ShowS
showsPrec :: Int -> Edge v -> ShowS
$cshow :: forall v. Show v => Edge v -> String
show :: Edge v -> String
$cshowList :: forall v. Show v => [Edge v] -> ShowS
showList :: [Edge v] -> ShowS
Show)
_Edge :: Name
_Edge = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Edge")
_Edge_label :: Name
_Edge_label = (String -> Name
Core.Name String
"label")
_Edge_id :: Name
_Edge_id = (String -> Name
Core.Name String
"id")
_Edge_out :: Name
_Edge_out = (String -> Name
Core.Name String
"out")
_Edge_in :: Name
_Edge_in = (String -> Name
Core.Name String
"in")
_Edge_properties :: Name
_Edge_properties = (String -> Name
Core.Name String
"properties")
newtype EdgeLabel =
EdgeLabel {
EdgeLabel -> String
unEdgeLabel :: String}
deriving (EdgeLabel -> EdgeLabel -> Bool
(EdgeLabel -> EdgeLabel -> Bool)
-> (EdgeLabel -> EdgeLabel -> Bool) -> Eq EdgeLabel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeLabel -> EdgeLabel -> Bool
== :: EdgeLabel -> EdgeLabel -> Bool
$c/= :: EdgeLabel -> EdgeLabel -> Bool
/= :: EdgeLabel -> EdgeLabel -> Bool
Eq, Eq EdgeLabel
Eq EdgeLabel =>
(EdgeLabel -> EdgeLabel -> Ordering)
-> (EdgeLabel -> EdgeLabel -> Bool)
-> (EdgeLabel -> EdgeLabel -> Bool)
-> (EdgeLabel -> EdgeLabel -> Bool)
-> (EdgeLabel -> EdgeLabel -> Bool)
-> (EdgeLabel -> EdgeLabel -> EdgeLabel)
-> (EdgeLabel -> EdgeLabel -> EdgeLabel)
-> Ord EdgeLabel
EdgeLabel -> EdgeLabel -> Bool
EdgeLabel -> EdgeLabel -> Ordering
EdgeLabel -> EdgeLabel -> EdgeLabel
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 :: EdgeLabel -> EdgeLabel -> Ordering
compare :: EdgeLabel -> EdgeLabel -> Ordering
$c< :: EdgeLabel -> EdgeLabel -> Bool
< :: EdgeLabel -> EdgeLabel -> Bool
$c<= :: EdgeLabel -> EdgeLabel -> Bool
<= :: EdgeLabel -> EdgeLabel -> Bool
$c> :: EdgeLabel -> EdgeLabel -> Bool
> :: EdgeLabel -> EdgeLabel -> Bool
$c>= :: EdgeLabel -> EdgeLabel -> Bool
>= :: EdgeLabel -> EdgeLabel -> Bool
$cmax :: EdgeLabel -> EdgeLabel -> EdgeLabel
max :: EdgeLabel -> EdgeLabel -> EdgeLabel
$cmin :: EdgeLabel -> EdgeLabel -> EdgeLabel
min :: EdgeLabel -> EdgeLabel -> EdgeLabel
Ord, ReadPrec [EdgeLabel]
ReadPrec EdgeLabel
Int -> ReadS EdgeLabel
ReadS [EdgeLabel]
(Int -> ReadS EdgeLabel)
-> ReadS [EdgeLabel]
-> ReadPrec EdgeLabel
-> ReadPrec [EdgeLabel]
-> Read EdgeLabel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgeLabel
readsPrec :: Int -> ReadS EdgeLabel
$creadList :: ReadS [EdgeLabel]
readList :: ReadS [EdgeLabel]
$creadPrec :: ReadPrec EdgeLabel
readPrec :: ReadPrec EdgeLabel
$creadListPrec :: ReadPrec [EdgeLabel]
readListPrec :: ReadPrec [EdgeLabel]
Read, Int -> EdgeLabel -> ShowS
[EdgeLabel] -> ShowS
EdgeLabel -> String
(Int -> EdgeLabel -> ShowS)
-> (EdgeLabel -> String)
-> ([EdgeLabel] -> ShowS)
-> Show EdgeLabel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeLabel -> ShowS
showsPrec :: Int -> EdgeLabel -> ShowS
$cshow :: EdgeLabel -> String
show :: EdgeLabel -> String
$cshowList :: [EdgeLabel] -> ShowS
showList :: [EdgeLabel] -> ShowS
Show)
_EdgeLabel :: Name
_EdgeLabel = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.EdgeLabel")
data EdgeType t =
EdgeType {
forall t. EdgeType t -> EdgeLabel
edgeTypeLabel :: EdgeLabel,
forall t. EdgeType t -> t
edgeTypeId :: t,
forall t. EdgeType t -> VertexLabel
edgeTypeOut :: VertexLabel,
forall t. EdgeType t -> VertexLabel
edgeTypeIn :: VertexLabel,
forall t. EdgeType t -> [PropertyType t]
edgeTypeProperties :: [PropertyType t]}
deriving (EdgeType t -> EdgeType t -> Bool
(EdgeType t -> EdgeType t -> Bool)
-> (EdgeType t -> EdgeType t -> Bool) -> Eq (EdgeType t)
forall t. Eq t => EdgeType t -> EdgeType t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => EdgeType t -> EdgeType t -> Bool
== :: EdgeType t -> EdgeType t -> Bool
$c/= :: forall t. Eq t => EdgeType t -> EdgeType t -> Bool
/= :: EdgeType t -> EdgeType t -> Bool
Eq, Eq (EdgeType t)
Eq (EdgeType t) =>
(EdgeType t -> EdgeType t -> Ordering)
-> (EdgeType t -> EdgeType t -> Bool)
-> (EdgeType t -> EdgeType t -> Bool)
-> (EdgeType t -> EdgeType t -> Bool)
-> (EdgeType t -> EdgeType t -> Bool)
-> (EdgeType t -> EdgeType t -> EdgeType t)
-> (EdgeType t -> EdgeType t -> EdgeType t)
-> Ord (EdgeType t)
EdgeType t -> EdgeType t -> Bool
EdgeType t -> EdgeType t -> Ordering
EdgeType t -> EdgeType t -> EdgeType t
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
forall t. Ord t => Eq (EdgeType t)
forall t. Ord t => EdgeType t -> EdgeType t -> Bool
forall t. Ord t => EdgeType t -> EdgeType t -> Ordering
forall t. Ord t => EdgeType t -> EdgeType t -> EdgeType t
$ccompare :: forall t. Ord t => EdgeType t -> EdgeType t -> Ordering
compare :: EdgeType t -> EdgeType t -> Ordering
$c< :: forall t. Ord t => EdgeType t -> EdgeType t -> Bool
< :: EdgeType t -> EdgeType t -> Bool
$c<= :: forall t. Ord t => EdgeType t -> EdgeType t -> Bool
<= :: EdgeType t -> EdgeType t -> Bool
$c> :: forall t. Ord t => EdgeType t -> EdgeType t -> Bool
> :: EdgeType t -> EdgeType t -> Bool
$c>= :: forall t. Ord t => EdgeType t -> EdgeType t -> Bool
>= :: EdgeType t -> EdgeType t -> Bool
$cmax :: forall t. Ord t => EdgeType t -> EdgeType t -> EdgeType t
max :: EdgeType t -> EdgeType t -> EdgeType t
$cmin :: forall t. Ord t => EdgeType t -> EdgeType t -> EdgeType t
min :: EdgeType t -> EdgeType t -> EdgeType t
Ord, ReadPrec [EdgeType t]
ReadPrec (EdgeType t)
Int -> ReadS (EdgeType t)
ReadS [EdgeType t]
(Int -> ReadS (EdgeType t))
-> ReadS [EdgeType t]
-> ReadPrec (EdgeType t)
-> ReadPrec [EdgeType t]
-> Read (EdgeType t)
forall t. Read t => ReadPrec [EdgeType t]
forall t. Read t => ReadPrec (EdgeType t)
forall t. Read t => Int -> ReadS (EdgeType t)
forall t. Read t => ReadS [EdgeType t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (EdgeType t)
readsPrec :: Int -> ReadS (EdgeType t)
$creadList :: forall t. Read t => ReadS [EdgeType t]
readList :: ReadS [EdgeType t]
$creadPrec :: forall t. Read t => ReadPrec (EdgeType t)
readPrec :: ReadPrec (EdgeType t)
$creadListPrec :: forall t. Read t => ReadPrec [EdgeType t]
readListPrec :: ReadPrec [EdgeType t]
Read, Int -> EdgeType t -> ShowS
[EdgeType t] -> ShowS
EdgeType t -> String
(Int -> EdgeType t -> ShowS)
-> (EdgeType t -> String)
-> ([EdgeType t] -> ShowS)
-> Show (EdgeType t)
forall t. Show t => Int -> EdgeType t -> ShowS
forall t. Show t => [EdgeType t] -> ShowS
forall t. Show t => EdgeType t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> EdgeType t -> ShowS
showsPrec :: Int -> EdgeType t -> ShowS
$cshow :: forall t. Show t => EdgeType t -> String
show :: EdgeType t -> String
$cshowList :: forall t. Show t => [EdgeType t] -> ShowS
showList :: [EdgeType t] -> ShowS
Show)
_EdgeType :: Name
_EdgeType = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.EdgeType")
_EdgeType_label :: Name
_EdgeType_label = (String -> Name
Core.Name String
"label")
_EdgeType_id :: Name
_EdgeType_id = (String -> Name
Core.Name String
"id")
_EdgeType_out :: Name
_EdgeType_out = (String -> Name
Core.Name String
"out")
_EdgeType_in :: Name
_EdgeType_in = (String -> Name
Core.Name String
"in")
_EdgeType_properties :: Name
_EdgeType_properties = (String -> Name
Core.Name String
"properties")
data Element v =
ElementVertex (Vertex v) |
ElementEdge (Edge v)
deriving (Element v -> Element v -> Bool
(Element v -> Element v -> Bool)
-> (Element v -> Element v -> Bool) -> Eq (Element v)
forall v. Eq v => Element v -> Element v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Element v -> Element v -> Bool
== :: Element v -> Element v -> Bool
$c/= :: forall v. Eq v => Element v -> Element v -> Bool
/= :: Element v -> Element v -> Bool
Eq, Eq (Element v)
Eq (Element v) =>
(Element v -> Element v -> Ordering)
-> (Element v -> Element v -> Bool)
-> (Element v -> Element v -> Bool)
-> (Element v -> Element v -> Bool)
-> (Element v -> Element v -> Bool)
-> (Element v -> Element v -> Element v)
-> (Element v -> Element v -> Element v)
-> Ord (Element v)
Element v -> Element v -> Bool
Element v -> Element v -> Ordering
Element v -> Element v -> Element v
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
forall v. Ord v => Eq (Element v)
forall v. Ord v => Element v -> Element v -> Bool
forall v. Ord v => Element v -> Element v -> Ordering
forall v. Ord v => Element v -> Element v -> Element v
$ccompare :: forall v. Ord v => Element v -> Element v -> Ordering
compare :: Element v -> Element v -> Ordering
$c< :: forall v. Ord v => Element v -> Element v -> Bool
< :: Element v -> Element v -> Bool
$c<= :: forall v. Ord v => Element v -> Element v -> Bool
<= :: Element v -> Element v -> Bool
$c> :: forall v. Ord v => Element v -> Element v -> Bool
> :: Element v -> Element v -> Bool
$c>= :: forall v. Ord v => Element v -> Element v -> Bool
>= :: Element v -> Element v -> Bool
$cmax :: forall v. Ord v => Element v -> Element v -> Element v
max :: Element v -> Element v -> Element v
$cmin :: forall v. Ord v => Element v -> Element v -> Element v
min :: Element v -> Element v -> Element v
Ord, ReadPrec [Element v]
ReadPrec (Element v)
Int -> ReadS (Element v)
ReadS [Element v]
(Int -> ReadS (Element v))
-> ReadS [Element v]
-> ReadPrec (Element v)
-> ReadPrec [Element v]
-> Read (Element v)
forall v. Read v => ReadPrec [Element v]
forall v. Read v => ReadPrec (Element v)
forall v. Read v => Int -> ReadS (Element v)
forall v. Read v => ReadS [Element v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. Read v => Int -> ReadS (Element v)
readsPrec :: Int -> ReadS (Element v)
$creadList :: forall v. Read v => ReadS [Element v]
readList :: ReadS [Element v]
$creadPrec :: forall v. Read v => ReadPrec (Element v)
readPrec :: ReadPrec (Element v)
$creadListPrec :: forall v. Read v => ReadPrec [Element v]
readListPrec :: ReadPrec [Element v]
Read, Int -> Element v -> ShowS
[Element v] -> ShowS
Element v -> String
(Int -> Element v -> ShowS)
-> (Element v -> String)
-> ([Element v] -> ShowS)
-> Show (Element v)
forall v. Show v => Int -> Element v -> ShowS
forall v. Show v => [Element v] -> ShowS
forall v. Show v => Element v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Element v -> ShowS
showsPrec :: Int -> Element v -> ShowS
$cshow :: forall v. Show v => Element v -> String
show :: Element v -> String
$cshowList :: forall v. Show v => [Element v] -> ShowS
showList :: [Element v] -> ShowS
Show)
_Element :: Name
_Element = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Element")
_Element_vertex :: Name
_Element_vertex = (String -> Name
Core.Name String
"vertex")
_Element_edge :: Name
_Element_edge = (String -> Name
Core.Name String
"edge")
data ElementKind =
ElementKindVertex |
ElementKindEdge
deriving (ElementKind -> ElementKind -> Bool
(ElementKind -> ElementKind -> Bool)
-> (ElementKind -> ElementKind -> Bool) -> Eq ElementKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElementKind -> ElementKind -> Bool
== :: ElementKind -> ElementKind -> Bool
$c/= :: ElementKind -> ElementKind -> Bool
/= :: ElementKind -> ElementKind -> Bool
Eq, Eq ElementKind
Eq ElementKind =>
(ElementKind -> ElementKind -> Ordering)
-> (ElementKind -> ElementKind -> Bool)
-> (ElementKind -> ElementKind -> Bool)
-> (ElementKind -> ElementKind -> Bool)
-> (ElementKind -> ElementKind -> Bool)
-> (ElementKind -> ElementKind -> ElementKind)
-> (ElementKind -> ElementKind -> ElementKind)
-> Ord ElementKind
ElementKind -> ElementKind -> Bool
ElementKind -> ElementKind -> Ordering
ElementKind -> ElementKind -> ElementKind
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 :: ElementKind -> ElementKind -> Ordering
compare :: ElementKind -> ElementKind -> Ordering
$c< :: ElementKind -> ElementKind -> Bool
< :: ElementKind -> ElementKind -> Bool
$c<= :: ElementKind -> ElementKind -> Bool
<= :: ElementKind -> ElementKind -> Bool
$c> :: ElementKind -> ElementKind -> Bool
> :: ElementKind -> ElementKind -> Bool
$c>= :: ElementKind -> ElementKind -> Bool
>= :: ElementKind -> ElementKind -> Bool
$cmax :: ElementKind -> ElementKind -> ElementKind
max :: ElementKind -> ElementKind -> ElementKind
$cmin :: ElementKind -> ElementKind -> ElementKind
min :: ElementKind -> ElementKind -> ElementKind
Ord, ReadPrec [ElementKind]
ReadPrec ElementKind
Int -> ReadS ElementKind
ReadS [ElementKind]
(Int -> ReadS ElementKind)
-> ReadS [ElementKind]
-> ReadPrec ElementKind
-> ReadPrec [ElementKind]
-> Read ElementKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ElementKind
readsPrec :: Int -> ReadS ElementKind
$creadList :: ReadS [ElementKind]
readList :: ReadS [ElementKind]
$creadPrec :: ReadPrec ElementKind
readPrec :: ReadPrec ElementKind
$creadListPrec :: ReadPrec [ElementKind]
readListPrec :: ReadPrec [ElementKind]
Read, Int -> ElementKind -> ShowS
[ElementKind] -> ShowS
ElementKind -> String
(Int -> ElementKind -> ShowS)
-> (ElementKind -> String)
-> ([ElementKind] -> ShowS)
-> Show ElementKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElementKind -> ShowS
showsPrec :: Int -> ElementKind -> ShowS
$cshow :: ElementKind -> String
show :: ElementKind -> String
$cshowList :: [ElementKind] -> ShowS
showList :: [ElementKind] -> ShowS
Show)
_ElementKind :: Name
_ElementKind = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.ElementKind")
_ElementKind_vertex :: Name
_ElementKind_vertex = (String -> Name
Core.Name String
"vertex")
_ElementKind_edge :: Name
_ElementKind_edge = (String -> Name
Core.Name String
"edge")
data ElementTree v =
ElementTree {
forall v. ElementTree v -> Element v
elementTreeSelf :: (Element v),
forall v. ElementTree v -> [ElementTree v]
elementTreeDependencies :: [ElementTree v]}
deriving (ElementTree v -> ElementTree v -> Bool
(ElementTree v -> ElementTree v -> Bool)
-> (ElementTree v -> ElementTree v -> Bool) -> Eq (ElementTree v)
forall v. Eq v => ElementTree v -> ElementTree v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => ElementTree v -> ElementTree v -> Bool
== :: ElementTree v -> ElementTree v -> Bool
$c/= :: forall v. Eq v => ElementTree v -> ElementTree v -> Bool
/= :: ElementTree v -> ElementTree v -> Bool
Eq, Eq (ElementTree v)
Eq (ElementTree v) =>
(ElementTree v -> ElementTree v -> Ordering)
-> (ElementTree v -> ElementTree v -> Bool)
-> (ElementTree v -> ElementTree v -> Bool)
-> (ElementTree v -> ElementTree v -> Bool)
-> (ElementTree v -> ElementTree v -> Bool)
-> (ElementTree v -> ElementTree v -> ElementTree v)
-> (ElementTree v -> ElementTree v -> ElementTree v)
-> Ord (ElementTree v)
ElementTree v -> ElementTree v -> Bool
ElementTree v -> ElementTree v -> Ordering
ElementTree v -> ElementTree v -> ElementTree v
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
forall v. Ord v => Eq (ElementTree v)
forall v. Ord v => ElementTree v -> ElementTree v -> Bool
forall v. Ord v => ElementTree v -> ElementTree v -> Ordering
forall v. Ord v => ElementTree v -> ElementTree v -> ElementTree v
$ccompare :: forall v. Ord v => ElementTree v -> ElementTree v -> Ordering
compare :: ElementTree v -> ElementTree v -> Ordering
$c< :: forall v. Ord v => ElementTree v -> ElementTree v -> Bool
< :: ElementTree v -> ElementTree v -> Bool
$c<= :: forall v. Ord v => ElementTree v -> ElementTree v -> Bool
<= :: ElementTree v -> ElementTree v -> Bool
$c> :: forall v. Ord v => ElementTree v -> ElementTree v -> Bool
> :: ElementTree v -> ElementTree v -> Bool
$c>= :: forall v. Ord v => ElementTree v -> ElementTree v -> Bool
>= :: ElementTree v -> ElementTree v -> Bool
$cmax :: forall v. Ord v => ElementTree v -> ElementTree v -> ElementTree v
max :: ElementTree v -> ElementTree v -> ElementTree v
$cmin :: forall v. Ord v => ElementTree v -> ElementTree v -> ElementTree v
min :: ElementTree v -> ElementTree v -> ElementTree v
Ord, ReadPrec [ElementTree v]
ReadPrec (ElementTree v)
Int -> ReadS (ElementTree v)
ReadS [ElementTree v]
(Int -> ReadS (ElementTree v))
-> ReadS [ElementTree v]
-> ReadPrec (ElementTree v)
-> ReadPrec [ElementTree v]
-> Read (ElementTree v)
forall v. Read v => ReadPrec [ElementTree v]
forall v. Read v => ReadPrec (ElementTree v)
forall v. Read v => Int -> ReadS (ElementTree v)
forall v. Read v => ReadS [ElementTree v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. Read v => Int -> ReadS (ElementTree v)
readsPrec :: Int -> ReadS (ElementTree v)
$creadList :: forall v. Read v => ReadS [ElementTree v]
readList :: ReadS [ElementTree v]
$creadPrec :: forall v. Read v => ReadPrec (ElementTree v)
readPrec :: ReadPrec (ElementTree v)
$creadListPrec :: forall v. Read v => ReadPrec [ElementTree v]
readListPrec :: ReadPrec [ElementTree v]
Read, Int -> ElementTree v -> ShowS
[ElementTree v] -> ShowS
ElementTree v -> String
(Int -> ElementTree v -> ShowS)
-> (ElementTree v -> String)
-> ([ElementTree v] -> ShowS)
-> Show (ElementTree v)
forall v. Show v => Int -> ElementTree v -> ShowS
forall v. Show v => [ElementTree v] -> ShowS
forall v. Show v => ElementTree v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> ElementTree v -> ShowS
showsPrec :: Int -> ElementTree v -> ShowS
$cshow :: forall v. Show v => ElementTree v -> String
show :: ElementTree v -> String
$cshowList :: forall v. Show v => [ElementTree v] -> ShowS
showList :: [ElementTree v] -> ShowS
Show)
_ElementTree :: Name
_ElementTree = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.ElementTree")
_ElementTree_self :: Name
_ElementTree_self = (String -> Name
Core.Name String
"self")
_ElementTree_dependencies :: Name
_ElementTree_dependencies = (String -> Name
Core.Name String
"dependencies")
data ElementType t =
ElementTypeVertex (VertexType t) |
ElementTypeEdge (EdgeType t)
deriving (ElementType t -> ElementType t -> Bool
(ElementType t -> ElementType t -> Bool)
-> (ElementType t -> ElementType t -> Bool) -> Eq (ElementType t)
forall t. Eq t => ElementType t -> ElementType t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => ElementType t -> ElementType t -> Bool
== :: ElementType t -> ElementType t -> Bool
$c/= :: forall t. Eq t => ElementType t -> ElementType t -> Bool
/= :: ElementType t -> ElementType t -> Bool
Eq, Eq (ElementType t)
Eq (ElementType t) =>
(ElementType t -> ElementType t -> Ordering)
-> (ElementType t -> ElementType t -> Bool)
-> (ElementType t -> ElementType t -> Bool)
-> (ElementType t -> ElementType t -> Bool)
-> (ElementType t -> ElementType t -> Bool)
-> (ElementType t -> ElementType t -> ElementType t)
-> (ElementType t -> ElementType t -> ElementType t)
-> Ord (ElementType t)
ElementType t -> ElementType t -> Bool
ElementType t -> ElementType t -> Ordering
ElementType t -> ElementType t -> ElementType t
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
forall t. Ord t => Eq (ElementType t)
forall t. Ord t => ElementType t -> ElementType t -> Bool
forall t. Ord t => ElementType t -> ElementType t -> Ordering
forall t. Ord t => ElementType t -> ElementType t -> ElementType t
$ccompare :: forall t. Ord t => ElementType t -> ElementType t -> Ordering
compare :: ElementType t -> ElementType t -> Ordering
$c< :: forall t. Ord t => ElementType t -> ElementType t -> Bool
< :: ElementType t -> ElementType t -> Bool
$c<= :: forall t. Ord t => ElementType t -> ElementType t -> Bool
<= :: ElementType t -> ElementType t -> Bool
$c> :: forall t. Ord t => ElementType t -> ElementType t -> Bool
> :: ElementType t -> ElementType t -> Bool
$c>= :: forall t. Ord t => ElementType t -> ElementType t -> Bool
>= :: ElementType t -> ElementType t -> Bool
$cmax :: forall t. Ord t => ElementType t -> ElementType t -> ElementType t
max :: ElementType t -> ElementType t -> ElementType t
$cmin :: forall t. Ord t => ElementType t -> ElementType t -> ElementType t
min :: ElementType t -> ElementType t -> ElementType t
Ord, ReadPrec [ElementType t]
ReadPrec (ElementType t)
Int -> ReadS (ElementType t)
ReadS [ElementType t]
(Int -> ReadS (ElementType t))
-> ReadS [ElementType t]
-> ReadPrec (ElementType t)
-> ReadPrec [ElementType t]
-> Read (ElementType t)
forall t. Read t => ReadPrec [ElementType t]
forall t. Read t => ReadPrec (ElementType t)
forall t. Read t => Int -> ReadS (ElementType t)
forall t. Read t => ReadS [ElementType t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (ElementType t)
readsPrec :: Int -> ReadS (ElementType t)
$creadList :: forall t. Read t => ReadS [ElementType t]
readList :: ReadS [ElementType t]
$creadPrec :: forall t. Read t => ReadPrec (ElementType t)
readPrec :: ReadPrec (ElementType t)
$creadListPrec :: forall t. Read t => ReadPrec [ElementType t]
readListPrec :: ReadPrec [ElementType t]
Read, Int -> ElementType t -> ShowS
[ElementType t] -> ShowS
ElementType t -> String
(Int -> ElementType t -> ShowS)
-> (ElementType t -> String)
-> ([ElementType t] -> ShowS)
-> Show (ElementType t)
forall t. Show t => Int -> ElementType t -> ShowS
forall t. Show t => [ElementType t] -> ShowS
forall t. Show t => ElementType t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> ElementType t -> ShowS
showsPrec :: Int -> ElementType t -> ShowS
$cshow :: forall t. Show t => ElementType t -> String
show :: ElementType t -> String
$cshowList :: forall t. Show t => [ElementType t] -> ShowS
showList :: [ElementType t] -> ShowS
Show)
_ElementType :: Name
_ElementType = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.ElementType")
_ElementType_vertex :: Name
_ElementType_vertex = (String -> Name
Core.Name String
"vertex")
_ElementType_edge :: Name
_ElementType_edge = (String -> Name
Core.Name String
"edge")
data ElementTypeTree t =
ElementTypeTree {
forall t. ElementTypeTree t -> ElementType t
elementTypeTreeSelf :: (ElementType t),
forall t. ElementTypeTree t -> [ElementTypeTree t]
elementTypeTreeDependencies :: [ElementTypeTree t]}
deriving (ElementTypeTree t -> ElementTypeTree t -> Bool
(ElementTypeTree t -> ElementTypeTree t -> Bool)
-> (ElementTypeTree t -> ElementTypeTree t -> Bool)
-> Eq (ElementTypeTree t)
forall t. Eq t => ElementTypeTree t -> ElementTypeTree t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => ElementTypeTree t -> ElementTypeTree t -> Bool
== :: ElementTypeTree t -> ElementTypeTree t -> Bool
$c/= :: forall t. Eq t => ElementTypeTree t -> ElementTypeTree t -> Bool
/= :: ElementTypeTree t -> ElementTypeTree t -> Bool
Eq, Eq (ElementTypeTree t)
Eq (ElementTypeTree t) =>
(ElementTypeTree t -> ElementTypeTree t -> Ordering)
-> (ElementTypeTree t -> ElementTypeTree t -> Bool)
-> (ElementTypeTree t -> ElementTypeTree t -> Bool)
-> (ElementTypeTree t -> ElementTypeTree t -> Bool)
-> (ElementTypeTree t -> ElementTypeTree t -> Bool)
-> (ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t)
-> (ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t)
-> Ord (ElementTypeTree t)
ElementTypeTree t -> ElementTypeTree t -> Bool
ElementTypeTree t -> ElementTypeTree t -> Ordering
ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
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
forall t. Ord t => Eq (ElementTypeTree t)
forall t. Ord t => ElementTypeTree t -> ElementTypeTree t -> Bool
forall t.
Ord t =>
ElementTypeTree t -> ElementTypeTree t -> Ordering
forall t.
Ord t =>
ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
$ccompare :: forall t.
Ord t =>
ElementTypeTree t -> ElementTypeTree t -> Ordering
compare :: ElementTypeTree t -> ElementTypeTree t -> Ordering
$c< :: forall t. Ord t => ElementTypeTree t -> ElementTypeTree t -> Bool
< :: ElementTypeTree t -> ElementTypeTree t -> Bool
$c<= :: forall t. Ord t => ElementTypeTree t -> ElementTypeTree t -> Bool
<= :: ElementTypeTree t -> ElementTypeTree t -> Bool
$c> :: forall t. Ord t => ElementTypeTree t -> ElementTypeTree t -> Bool
> :: ElementTypeTree t -> ElementTypeTree t -> Bool
$c>= :: forall t. Ord t => ElementTypeTree t -> ElementTypeTree t -> Bool
>= :: ElementTypeTree t -> ElementTypeTree t -> Bool
$cmax :: forall t.
Ord t =>
ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
max :: ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
$cmin :: forall t.
Ord t =>
ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
min :: ElementTypeTree t -> ElementTypeTree t -> ElementTypeTree t
Ord, ReadPrec [ElementTypeTree t]
ReadPrec (ElementTypeTree t)
Int -> ReadS (ElementTypeTree t)
ReadS [ElementTypeTree t]
(Int -> ReadS (ElementTypeTree t))
-> ReadS [ElementTypeTree t]
-> ReadPrec (ElementTypeTree t)
-> ReadPrec [ElementTypeTree t]
-> Read (ElementTypeTree t)
forall t. Read t => ReadPrec [ElementTypeTree t]
forall t. Read t => ReadPrec (ElementTypeTree t)
forall t. Read t => Int -> ReadS (ElementTypeTree t)
forall t. Read t => ReadS [ElementTypeTree t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (ElementTypeTree t)
readsPrec :: Int -> ReadS (ElementTypeTree t)
$creadList :: forall t. Read t => ReadS [ElementTypeTree t]
readList :: ReadS [ElementTypeTree t]
$creadPrec :: forall t. Read t => ReadPrec (ElementTypeTree t)
readPrec :: ReadPrec (ElementTypeTree t)
$creadListPrec :: forall t. Read t => ReadPrec [ElementTypeTree t]
readListPrec :: ReadPrec [ElementTypeTree t]
Read, Int -> ElementTypeTree t -> ShowS
[ElementTypeTree t] -> ShowS
ElementTypeTree t -> String
(Int -> ElementTypeTree t -> ShowS)
-> (ElementTypeTree t -> String)
-> ([ElementTypeTree t] -> ShowS)
-> Show (ElementTypeTree t)
forall t. Show t => Int -> ElementTypeTree t -> ShowS
forall t. Show t => [ElementTypeTree t] -> ShowS
forall t. Show t => ElementTypeTree t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> ElementTypeTree t -> ShowS
showsPrec :: Int -> ElementTypeTree t -> ShowS
$cshow :: forall t. Show t => ElementTypeTree t -> String
show :: ElementTypeTree t -> String
$cshowList :: forall t. Show t => [ElementTypeTree t] -> ShowS
showList :: [ElementTypeTree t] -> ShowS
Show)
_ElementTypeTree :: Name
_ElementTypeTree = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.ElementTypeTree")
_ElementTypeTree_self :: Name
_ElementTypeTree_self = (String -> Name
Core.Name String
"self")
_ElementTypeTree_dependencies :: Name
_ElementTypeTree_dependencies = (String -> Name
Core.Name String
"dependencies")
data Graph v =
Graph {
forall v. Graph v -> Map v (Vertex v)
graphVertices :: (Map v (Vertex v)),
forall v. Graph v -> Map v (Edge v)
graphEdges :: (Map v (Edge v))}
deriving (Graph v -> Graph v -> Bool
(Graph v -> Graph v -> Bool)
-> (Graph v -> Graph v -> Bool) -> Eq (Graph v)
forall v. Eq v => Graph v -> Graph v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Graph v -> Graph v -> Bool
== :: Graph v -> Graph v -> Bool
$c/= :: forall v. Eq v => Graph v -> Graph v -> Bool
/= :: Graph v -> Graph v -> Bool
Eq, Eq (Graph v)
Eq (Graph v) =>
(Graph v -> Graph v -> Ordering)
-> (Graph v -> Graph v -> Bool)
-> (Graph v -> Graph v -> Bool)
-> (Graph v -> Graph v -> Bool)
-> (Graph v -> Graph v -> Bool)
-> (Graph v -> Graph v -> Graph v)
-> (Graph v -> Graph v -> Graph v)
-> Ord (Graph v)
Graph v -> Graph v -> Bool
Graph v -> Graph v -> Ordering
Graph v -> Graph v -> Graph v
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
forall v. Ord v => Eq (Graph v)
forall v. Ord v => Graph v -> Graph v -> Bool
forall v. Ord v => Graph v -> Graph v -> Ordering
forall v. Ord v => Graph v -> Graph v -> Graph v
$ccompare :: forall v. Ord v => Graph v -> Graph v -> Ordering
compare :: Graph v -> Graph v -> Ordering
$c< :: forall v. Ord v => Graph v -> Graph v -> Bool
< :: Graph v -> Graph v -> Bool
$c<= :: forall v. Ord v => Graph v -> Graph v -> Bool
<= :: Graph v -> Graph v -> Bool
$c> :: forall v. Ord v => Graph v -> Graph v -> Bool
> :: Graph v -> Graph v -> Bool
$c>= :: forall v. Ord v => Graph v -> Graph v -> Bool
>= :: Graph v -> Graph v -> Bool
$cmax :: forall v. Ord v => Graph v -> Graph v -> Graph v
max :: Graph v -> Graph v -> Graph v
$cmin :: forall v. Ord v => Graph v -> Graph v -> Graph v
min :: Graph v -> Graph v -> Graph v
Ord, ReadPrec [Graph v]
ReadPrec (Graph v)
Int -> ReadS (Graph v)
ReadS [Graph v]
(Int -> ReadS (Graph v))
-> ReadS [Graph v]
-> ReadPrec (Graph v)
-> ReadPrec [Graph v]
-> Read (Graph v)
forall v. (Ord v, Read v) => ReadPrec [Graph v]
forall v. (Ord v, Read v) => ReadPrec (Graph v)
forall v. (Ord v, Read v) => Int -> ReadS (Graph v)
forall v. (Ord v, Read v) => ReadS [Graph v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. (Ord v, Read v) => Int -> ReadS (Graph v)
readsPrec :: Int -> ReadS (Graph v)
$creadList :: forall v. (Ord v, Read v) => ReadS [Graph v]
readList :: ReadS [Graph v]
$creadPrec :: forall v. (Ord v, Read v) => ReadPrec (Graph v)
readPrec :: ReadPrec (Graph v)
$creadListPrec :: forall v. (Ord v, Read v) => ReadPrec [Graph v]
readListPrec :: ReadPrec [Graph v]
Read, Int -> Graph v -> ShowS
[Graph v] -> ShowS
Graph v -> String
(Int -> Graph v -> ShowS)
-> (Graph v -> String) -> ([Graph v] -> ShowS) -> Show (Graph v)
forall v. Show v => Int -> Graph v -> ShowS
forall v. Show v => [Graph v] -> ShowS
forall v. Show v => Graph v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Graph v -> ShowS
showsPrec :: Int -> Graph v -> ShowS
$cshow :: forall v. Show v => Graph v -> String
show :: Graph v -> String
$cshowList :: forall v. Show v => [Graph v] -> ShowS
showList :: [Graph v] -> ShowS
Show)
_Graph :: Name
_Graph = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Graph")
_Graph_vertices :: Name
_Graph_vertices = (String -> Name
Core.Name String
"vertices")
_Graph_edges :: Name
_Graph_edges = (String -> Name
Core.Name String
"edges")
data GraphSchema t =
GraphSchema {
forall t. GraphSchema t -> Map VertexLabel (VertexType t)
graphSchemaVertices :: (Map VertexLabel (VertexType t)),
forall t. GraphSchema t -> Map EdgeLabel (EdgeType t)
graphSchemaEdges :: (Map EdgeLabel (EdgeType t))}
deriving (GraphSchema t -> GraphSchema t -> Bool
(GraphSchema t -> GraphSchema t -> Bool)
-> (GraphSchema t -> GraphSchema t -> Bool) -> Eq (GraphSchema t)
forall t. Eq t => GraphSchema t -> GraphSchema t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => GraphSchema t -> GraphSchema t -> Bool
== :: GraphSchema t -> GraphSchema t -> Bool
$c/= :: forall t. Eq t => GraphSchema t -> GraphSchema t -> Bool
/= :: GraphSchema t -> GraphSchema t -> Bool
Eq, Eq (GraphSchema t)
Eq (GraphSchema t) =>
(GraphSchema t -> GraphSchema t -> Ordering)
-> (GraphSchema t -> GraphSchema t -> Bool)
-> (GraphSchema t -> GraphSchema t -> Bool)
-> (GraphSchema t -> GraphSchema t -> Bool)
-> (GraphSchema t -> GraphSchema t -> Bool)
-> (GraphSchema t -> GraphSchema t -> GraphSchema t)
-> (GraphSchema t -> GraphSchema t -> GraphSchema t)
-> Ord (GraphSchema t)
GraphSchema t -> GraphSchema t -> Bool
GraphSchema t -> GraphSchema t -> Ordering
GraphSchema t -> GraphSchema t -> GraphSchema t
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
forall t. Ord t => Eq (GraphSchema t)
forall t. Ord t => GraphSchema t -> GraphSchema t -> Bool
forall t. Ord t => GraphSchema t -> GraphSchema t -> Ordering
forall t. Ord t => GraphSchema t -> GraphSchema t -> GraphSchema t
$ccompare :: forall t. Ord t => GraphSchema t -> GraphSchema t -> Ordering
compare :: GraphSchema t -> GraphSchema t -> Ordering
$c< :: forall t. Ord t => GraphSchema t -> GraphSchema t -> Bool
< :: GraphSchema t -> GraphSchema t -> Bool
$c<= :: forall t. Ord t => GraphSchema t -> GraphSchema t -> Bool
<= :: GraphSchema t -> GraphSchema t -> Bool
$c> :: forall t. Ord t => GraphSchema t -> GraphSchema t -> Bool
> :: GraphSchema t -> GraphSchema t -> Bool
$c>= :: forall t. Ord t => GraphSchema t -> GraphSchema t -> Bool
>= :: GraphSchema t -> GraphSchema t -> Bool
$cmax :: forall t. Ord t => GraphSchema t -> GraphSchema t -> GraphSchema t
max :: GraphSchema t -> GraphSchema t -> GraphSchema t
$cmin :: forall t. Ord t => GraphSchema t -> GraphSchema t -> GraphSchema t
min :: GraphSchema t -> GraphSchema t -> GraphSchema t
Ord, ReadPrec [GraphSchema t]
ReadPrec (GraphSchema t)
Int -> ReadS (GraphSchema t)
ReadS [GraphSchema t]
(Int -> ReadS (GraphSchema t))
-> ReadS [GraphSchema t]
-> ReadPrec (GraphSchema t)
-> ReadPrec [GraphSchema t]
-> Read (GraphSchema t)
forall t. Read t => ReadPrec [GraphSchema t]
forall t. Read t => ReadPrec (GraphSchema t)
forall t. Read t => Int -> ReadS (GraphSchema t)
forall t. Read t => ReadS [GraphSchema t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (GraphSchema t)
readsPrec :: Int -> ReadS (GraphSchema t)
$creadList :: forall t. Read t => ReadS [GraphSchema t]
readList :: ReadS [GraphSchema t]
$creadPrec :: forall t. Read t => ReadPrec (GraphSchema t)
readPrec :: ReadPrec (GraphSchema t)
$creadListPrec :: forall t. Read t => ReadPrec [GraphSchema t]
readListPrec :: ReadPrec [GraphSchema t]
Read, Int -> GraphSchema t -> ShowS
[GraphSchema t] -> ShowS
GraphSchema t -> String
(Int -> GraphSchema t -> ShowS)
-> (GraphSchema t -> String)
-> ([GraphSchema t] -> ShowS)
-> Show (GraphSchema t)
forall t. Show t => Int -> GraphSchema t -> ShowS
forall t. Show t => [GraphSchema t] -> ShowS
forall t. Show t => GraphSchema t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> GraphSchema t -> ShowS
showsPrec :: Int -> GraphSchema t -> ShowS
$cshow :: forall t. Show t => GraphSchema t -> String
show :: GraphSchema t -> String
$cshowList :: forall t. Show t => [GraphSchema t] -> ShowS
showList :: [GraphSchema t] -> ShowS
Show)
_GraphSchema :: Name
_GraphSchema = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.GraphSchema")
_GraphSchema_vertices :: Name
_GraphSchema_vertices = (String -> Name
Core.Name String
"vertices")
_GraphSchema_edges :: Name
_GraphSchema_edges = (String -> Name
Core.Name String
"edges")
data Label =
LabelVertex VertexLabel |
LabelEdge EdgeLabel
deriving (Label -> Label -> Bool
(Label -> Label -> Bool) -> (Label -> Label -> Bool) -> Eq Label
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Label -> Label -> Bool
== :: Label -> Label -> Bool
$c/= :: Label -> Label -> Bool
/= :: Label -> Label -> Bool
Eq, Eq Label
Eq Label =>
(Label -> Label -> Ordering)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Label)
-> (Label -> Label -> Label)
-> Ord Label
Label -> Label -> Bool
Label -> Label -> Ordering
Label -> Label -> Label
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 :: Label -> Label -> Ordering
compare :: Label -> Label -> Ordering
$c< :: Label -> Label -> Bool
< :: Label -> Label -> Bool
$c<= :: Label -> Label -> Bool
<= :: Label -> Label -> Bool
$c> :: Label -> Label -> Bool
> :: Label -> Label -> Bool
$c>= :: Label -> Label -> Bool
>= :: Label -> Label -> Bool
$cmax :: Label -> Label -> Label
max :: Label -> Label -> Label
$cmin :: Label -> Label -> Label
min :: Label -> Label -> Label
Ord, ReadPrec [Label]
ReadPrec Label
Int -> ReadS Label
ReadS [Label]
(Int -> ReadS Label)
-> ReadS [Label]
-> ReadPrec Label
-> ReadPrec [Label]
-> Read Label
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Label
readsPrec :: Int -> ReadS Label
$creadList :: ReadS [Label]
readList :: ReadS [Label]
$creadPrec :: ReadPrec Label
readPrec :: ReadPrec Label
$creadListPrec :: ReadPrec [Label]
readListPrec :: ReadPrec [Label]
Read, Int -> Label -> ShowS
[Label] -> ShowS
Label -> String
(Int -> Label -> ShowS)
-> (Label -> String) -> ([Label] -> ShowS) -> Show Label
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Label -> ShowS
showsPrec :: Int -> Label -> ShowS
$cshow :: Label -> String
show :: Label -> String
$cshowList :: [Label] -> ShowS
showList :: [Label] -> ShowS
Show)
_Label :: Name
_Label = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Label")
_Label_vertex :: Name
_Label_vertex = (String -> Name
Core.Name String
"vertex")
_Label_edge :: Name
_Label_edge = (String -> Name
Core.Name String
"edge")
data Property v =
Property {
forall v. Property v -> PropertyKey
propertyKey :: PropertyKey,
forall v. Property v -> v
propertyValue :: v}
deriving (Property v -> Property v -> Bool
(Property v -> Property v -> Bool)
-> (Property v -> Property v -> Bool) -> Eq (Property v)
forall v. Eq v => Property v -> Property v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Property v -> Property v -> Bool
== :: Property v -> Property v -> Bool
$c/= :: forall v. Eq v => Property v -> Property v -> Bool
/= :: Property v -> Property v -> Bool
Eq, Eq (Property v)
Eq (Property v) =>
(Property v -> Property v -> Ordering)
-> (Property v -> Property v -> Bool)
-> (Property v -> Property v -> Bool)
-> (Property v -> Property v -> Bool)
-> (Property v -> Property v -> Bool)
-> (Property v -> Property v -> Property v)
-> (Property v -> Property v -> Property v)
-> Ord (Property v)
Property v -> Property v -> Bool
Property v -> Property v -> Ordering
Property v -> Property v -> Property v
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
forall v. Ord v => Eq (Property v)
forall v. Ord v => Property v -> Property v -> Bool
forall v. Ord v => Property v -> Property v -> Ordering
forall v. Ord v => Property v -> Property v -> Property v
$ccompare :: forall v. Ord v => Property v -> Property v -> Ordering
compare :: Property v -> Property v -> Ordering
$c< :: forall v. Ord v => Property v -> Property v -> Bool
< :: Property v -> Property v -> Bool
$c<= :: forall v. Ord v => Property v -> Property v -> Bool
<= :: Property v -> Property v -> Bool
$c> :: forall v. Ord v => Property v -> Property v -> Bool
> :: Property v -> Property v -> Bool
$c>= :: forall v. Ord v => Property v -> Property v -> Bool
>= :: Property v -> Property v -> Bool
$cmax :: forall v. Ord v => Property v -> Property v -> Property v
max :: Property v -> Property v -> Property v
$cmin :: forall v. Ord v => Property v -> Property v -> Property v
min :: Property v -> Property v -> Property v
Ord, ReadPrec [Property v]
ReadPrec (Property v)
Int -> ReadS (Property v)
ReadS [Property v]
(Int -> ReadS (Property v))
-> ReadS [Property v]
-> ReadPrec (Property v)
-> ReadPrec [Property v]
-> Read (Property v)
forall v. Read v => ReadPrec [Property v]
forall v. Read v => ReadPrec (Property v)
forall v. Read v => Int -> ReadS (Property v)
forall v. Read v => ReadS [Property v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. Read v => Int -> ReadS (Property v)
readsPrec :: Int -> ReadS (Property v)
$creadList :: forall v. Read v => ReadS [Property v]
readList :: ReadS [Property v]
$creadPrec :: forall v. Read v => ReadPrec (Property v)
readPrec :: ReadPrec (Property v)
$creadListPrec :: forall v. Read v => ReadPrec [Property v]
readListPrec :: ReadPrec [Property v]
Read, Int -> Property v -> ShowS
[Property v] -> ShowS
Property v -> String
(Int -> Property v -> ShowS)
-> (Property v -> String)
-> ([Property v] -> ShowS)
-> Show (Property v)
forall v. Show v => Int -> Property v -> ShowS
forall v. Show v => [Property v] -> ShowS
forall v. Show v => Property v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Property v -> ShowS
showsPrec :: Int -> Property v -> ShowS
$cshow :: forall v. Show v => Property v -> String
show :: Property v -> String
$cshowList :: forall v. Show v => [Property v] -> ShowS
showList :: [Property v] -> ShowS
Show)
_Property :: Name
_Property = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Property")
_Property_key :: Name
_Property_key = (String -> Name
Core.Name String
"key")
_Property_value :: Name
_Property_value = (String -> Name
Core.Name String
"value")
newtype PropertyKey =
PropertyKey {
PropertyKey -> String
unPropertyKey :: String}
deriving (PropertyKey -> PropertyKey -> Bool
(PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool) -> Eq PropertyKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyKey -> PropertyKey -> Bool
== :: PropertyKey -> PropertyKey -> Bool
$c/= :: PropertyKey -> PropertyKey -> Bool
/= :: PropertyKey -> PropertyKey -> Bool
Eq, Eq PropertyKey
Eq PropertyKey =>
(PropertyKey -> PropertyKey -> Ordering)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> Ord PropertyKey
PropertyKey -> PropertyKey -> Bool
PropertyKey -> PropertyKey -> Ordering
PropertyKey -> PropertyKey -> PropertyKey
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 :: PropertyKey -> PropertyKey -> Ordering
compare :: PropertyKey -> PropertyKey -> Ordering
$c< :: PropertyKey -> PropertyKey -> Bool
< :: PropertyKey -> PropertyKey -> Bool
$c<= :: PropertyKey -> PropertyKey -> Bool
<= :: PropertyKey -> PropertyKey -> Bool
$c> :: PropertyKey -> PropertyKey -> Bool
> :: PropertyKey -> PropertyKey -> Bool
$c>= :: PropertyKey -> PropertyKey -> Bool
>= :: PropertyKey -> PropertyKey -> Bool
$cmax :: PropertyKey -> PropertyKey -> PropertyKey
max :: PropertyKey -> PropertyKey -> PropertyKey
$cmin :: PropertyKey -> PropertyKey -> PropertyKey
min :: PropertyKey -> PropertyKey -> PropertyKey
Ord, ReadPrec [PropertyKey]
ReadPrec PropertyKey
Int -> ReadS PropertyKey
ReadS [PropertyKey]
(Int -> ReadS PropertyKey)
-> ReadS [PropertyKey]
-> ReadPrec PropertyKey
-> ReadPrec [PropertyKey]
-> Read PropertyKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyKey
readsPrec :: Int -> ReadS PropertyKey
$creadList :: ReadS [PropertyKey]
readList :: ReadS [PropertyKey]
$creadPrec :: ReadPrec PropertyKey
readPrec :: ReadPrec PropertyKey
$creadListPrec :: ReadPrec [PropertyKey]
readListPrec :: ReadPrec [PropertyKey]
Read, Int -> PropertyKey -> ShowS
[PropertyKey] -> ShowS
PropertyKey -> String
(Int -> PropertyKey -> ShowS)
-> (PropertyKey -> String)
-> ([PropertyKey] -> ShowS)
-> Show PropertyKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyKey -> ShowS
showsPrec :: Int -> PropertyKey -> ShowS
$cshow :: PropertyKey -> String
show :: PropertyKey -> String
$cshowList :: [PropertyKey] -> ShowS
showList :: [PropertyKey] -> ShowS
Show)
_PropertyKey :: Name
_PropertyKey = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.PropertyKey")
data PropertyType t =
PropertyType {
forall t. PropertyType t -> PropertyKey
propertyTypeKey :: PropertyKey,
forall t. PropertyType t -> t
propertyTypeValue :: t,
forall t. PropertyType t -> Bool
propertyTypeRequired :: Bool}
deriving (PropertyType t -> PropertyType t -> Bool
(PropertyType t -> PropertyType t -> Bool)
-> (PropertyType t -> PropertyType t -> Bool)
-> Eq (PropertyType t)
forall t. Eq t => PropertyType t -> PropertyType t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => PropertyType t -> PropertyType t -> Bool
== :: PropertyType t -> PropertyType t -> Bool
$c/= :: forall t. Eq t => PropertyType t -> PropertyType t -> Bool
/= :: PropertyType t -> PropertyType t -> Bool
Eq, Eq (PropertyType t)
Eq (PropertyType t) =>
(PropertyType t -> PropertyType t -> Ordering)
-> (PropertyType t -> PropertyType t -> Bool)
-> (PropertyType t -> PropertyType t -> Bool)
-> (PropertyType t -> PropertyType t -> Bool)
-> (PropertyType t -> PropertyType t -> Bool)
-> (PropertyType t -> PropertyType t -> PropertyType t)
-> (PropertyType t -> PropertyType t -> PropertyType t)
-> Ord (PropertyType t)
PropertyType t -> PropertyType t -> Bool
PropertyType t -> PropertyType t -> Ordering
PropertyType t -> PropertyType t -> PropertyType t
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
forall t. Ord t => Eq (PropertyType t)
forall t. Ord t => PropertyType t -> PropertyType t -> Bool
forall t. Ord t => PropertyType t -> PropertyType t -> Ordering
forall t.
Ord t =>
PropertyType t -> PropertyType t -> PropertyType t
$ccompare :: forall t. Ord t => PropertyType t -> PropertyType t -> Ordering
compare :: PropertyType t -> PropertyType t -> Ordering
$c< :: forall t. Ord t => PropertyType t -> PropertyType t -> Bool
< :: PropertyType t -> PropertyType t -> Bool
$c<= :: forall t. Ord t => PropertyType t -> PropertyType t -> Bool
<= :: PropertyType t -> PropertyType t -> Bool
$c> :: forall t. Ord t => PropertyType t -> PropertyType t -> Bool
> :: PropertyType t -> PropertyType t -> Bool
$c>= :: forall t. Ord t => PropertyType t -> PropertyType t -> Bool
>= :: PropertyType t -> PropertyType t -> Bool
$cmax :: forall t.
Ord t =>
PropertyType t -> PropertyType t -> PropertyType t
max :: PropertyType t -> PropertyType t -> PropertyType t
$cmin :: forall t.
Ord t =>
PropertyType t -> PropertyType t -> PropertyType t
min :: PropertyType t -> PropertyType t -> PropertyType t
Ord, ReadPrec [PropertyType t]
ReadPrec (PropertyType t)
Int -> ReadS (PropertyType t)
ReadS [PropertyType t]
(Int -> ReadS (PropertyType t))
-> ReadS [PropertyType t]
-> ReadPrec (PropertyType t)
-> ReadPrec [PropertyType t]
-> Read (PropertyType t)
forall t. Read t => ReadPrec [PropertyType t]
forall t. Read t => ReadPrec (PropertyType t)
forall t. Read t => Int -> ReadS (PropertyType t)
forall t. Read t => ReadS [PropertyType t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (PropertyType t)
readsPrec :: Int -> ReadS (PropertyType t)
$creadList :: forall t. Read t => ReadS [PropertyType t]
readList :: ReadS [PropertyType t]
$creadPrec :: forall t. Read t => ReadPrec (PropertyType t)
readPrec :: ReadPrec (PropertyType t)
$creadListPrec :: forall t. Read t => ReadPrec [PropertyType t]
readListPrec :: ReadPrec [PropertyType t]
Read, Int -> PropertyType t -> ShowS
[PropertyType t] -> ShowS
PropertyType t -> String
(Int -> PropertyType t -> ShowS)
-> (PropertyType t -> String)
-> ([PropertyType t] -> ShowS)
-> Show (PropertyType t)
forall t. Show t => Int -> PropertyType t -> ShowS
forall t. Show t => [PropertyType t] -> ShowS
forall t. Show t => PropertyType t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> PropertyType t -> ShowS
showsPrec :: Int -> PropertyType t -> ShowS
$cshow :: forall t. Show t => PropertyType t -> String
show :: PropertyType t -> String
$cshowList :: forall t. Show t => [PropertyType t] -> ShowS
showList :: [PropertyType t] -> ShowS
Show)
_PropertyType :: Name
_PropertyType = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.PropertyType")
_PropertyType_key :: Name
_PropertyType_key = (String -> Name
Core.Name String
"key")
_PropertyType_value :: Name
_PropertyType_value = (String -> Name
Core.Name String
"value")
_PropertyType_required :: Name
_PropertyType_required = (String -> Name
Core.Name String
"required")
data Vertex v =
Vertex {
forall v. Vertex v -> VertexLabel
vertexLabel :: VertexLabel,
forall v. Vertex v -> v
vertexId :: v,
forall v. Vertex v -> Map PropertyKey v
vertexProperties :: (Map PropertyKey v)}
deriving (Vertex v -> Vertex v -> Bool
(Vertex v -> Vertex v -> Bool)
-> (Vertex v -> Vertex v -> Bool) -> Eq (Vertex v)
forall v. Eq v => Vertex v -> Vertex v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall v. Eq v => Vertex v -> Vertex v -> Bool
== :: Vertex v -> Vertex v -> Bool
$c/= :: forall v. Eq v => Vertex v -> Vertex v -> Bool
/= :: Vertex v -> Vertex v -> Bool
Eq, Eq (Vertex v)
Eq (Vertex v) =>
(Vertex v -> Vertex v -> Ordering)
-> (Vertex v -> Vertex v -> Bool)
-> (Vertex v -> Vertex v -> Bool)
-> (Vertex v -> Vertex v -> Bool)
-> (Vertex v -> Vertex v -> Bool)
-> (Vertex v -> Vertex v -> Vertex v)
-> (Vertex v -> Vertex v -> Vertex v)
-> Ord (Vertex v)
Vertex v -> Vertex v -> Bool
Vertex v -> Vertex v -> Ordering
Vertex v -> Vertex v -> Vertex v
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
forall v. Ord v => Eq (Vertex v)
forall v. Ord v => Vertex v -> Vertex v -> Bool
forall v. Ord v => Vertex v -> Vertex v -> Ordering
forall v. Ord v => Vertex v -> Vertex v -> Vertex v
$ccompare :: forall v. Ord v => Vertex v -> Vertex v -> Ordering
compare :: Vertex v -> Vertex v -> Ordering
$c< :: forall v. Ord v => Vertex v -> Vertex v -> Bool
< :: Vertex v -> Vertex v -> Bool
$c<= :: forall v. Ord v => Vertex v -> Vertex v -> Bool
<= :: Vertex v -> Vertex v -> Bool
$c> :: forall v. Ord v => Vertex v -> Vertex v -> Bool
> :: Vertex v -> Vertex v -> Bool
$c>= :: forall v. Ord v => Vertex v -> Vertex v -> Bool
>= :: Vertex v -> Vertex v -> Bool
$cmax :: forall v. Ord v => Vertex v -> Vertex v -> Vertex v
max :: Vertex v -> Vertex v -> Vertex v
$cmin :: forall v. Ord v => Vertex v -> Vertex v -> Vertex v
min :: Vertex v -> Vertex v -> Vertex v
Ord, ReadPrec [Vertex v]
ReadPrec (Vertex v)
Int -> ReadS (Vertex v)
ReadS [Vertex v]
(Int -> ReadS (Vertex v))
-> ReadS [Vertex v]
-> ReadPrec (Vertex v)
-> ReadPrec [Vertex v]
-> Read (Vertex v)
forall v. Read v => ReadPrec [Vertex v]
forall v. Read v => ReadPrec (Vertex v)
forall v. Read v => Int -> ReadS (Vertex v)
forall v. Read v => ReadS [Vertex v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall v. Read v => Int -> ReadS (Vertex v)
readsPrec :: Int -> ReadS (Vertex v)
$creadList :: forall v. Read v => ReadS [Vertex v]
readList :: ReadS [Vertex v]
$creadPrec :: forall v. Read v => ReadPrec (Vertex v)
readPrec :: ReadPrec (Vertex v)
$creadListPrec :: forall v. Read v => ReadPrec [Vertex v]
readListPrec :: ReadPrec [Vertex v]
Read, Int -> Vertex v -> ShowS
[Vertex v] -> ShowS
Vertex v -> String
(Int -> Vertex v -> ShowS)
-> (Vertex v -> String) -> ([Vertex v] -> ShowS) -> Show (Vertex v)
forall v. Show v => Int -> Vertex v -> ShowS
forall v. Show v => [Vertex v] -> ShowS
forall v. Show v => Vertex v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall v. Show v => Int -> Vertex v -> ShowS
showsPrec :: Int -> Vertex v -> ShowS
$cshow :: forall v. Show v => Vertex v -> String
show :: Vertex v -> String
$cshowList :: forall v. Show v => [Vertex v] -> ShowS
showList :: [Vertex v] -> ShowS
Show)
_Vertex :: Name
_Vertex = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.Vertex")
_Vertex_label :: Name
_Vertex_label = (String -> Name
Core.Name String
"label")
_Vertex_id :: Name
_Vertex_id = (String -> Name
Core.Name String
"id")
_Vertex_properties :: Name
_Vertex_properties = (String -> Name
Core.Name String
"properties")
newtype VertexLabel =
VertexLabel {
VertexLabel -> String
unVertexLabel :: String}
deriving (VertexLabel -> VertexLabel -> Bool
(VertexLabel -> VertexLabel -> Bool)
-> (VertexLabel -> VertexLabel -> Bool) -> Eq VertexLabel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VertexLabel -> VertexLabel -> Bool
== :: VertexLabel -> VertexLabel -> Bool
$c/= :: VertexLabel -> VertexLabel -> Bool
/= :: VertexLabel -> VertexLabel -> Bool
Eq, Eq VertexLabel
Eq VertexLabel =>
(VertexLabel -> VertexLabel -> Ordering)
-> (VertexLabel -> VertexLabel -> Bool)
-> (VertexLabel -> VertexLabel -> Bool)
-> (VertexLabel -> VertexLabel -> Bool)
-> (VertexLabel -> VertexLabel -> Bool)
-> (VertexLabel -> VertexLabel -> VertexLabel)
-> (VertexLabel -> VertexLabel -> VertexLabel)
-> Ord VertexLabel
VertexLabel -> VertexLabel -> Bool
VertexLabel -> VertexLabel -> Ordering
VertexLabel -> VertexLabel -> VertexLabel
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 :: VertexLabel -> VertexLabel -> Ordering
compare :: VertexLabel -> VertexLabel -> Ordering
$c< :: VertexLabel -> VertexLabel -> Bool
< :: VertexLabel -> VertexLabel -> Bool
$c<= :: VertexLabel -> VertexLabel -> Bool
<= :: VertexLabel -> VertexLabel -> Bool
$c> :: VertexLabel -> VertexLabel -> Bool
> :: VertexLabel -> VertexLabel -> Bool
$c>= :: VertexLabel -> VertexLabel -> Bool
>= :: VertexLabel -> VertexLabel -> Bool
$cmax :: VertexLabel -> VertexLabel -> VertexLabel
max :: VertexLabel -> VertexLabel -> VertexLabel
$cmin :: VertexLabel -> VertexLabel -> VertexLabel
min :: VertexLabel -> VertexLabel -> VertexLabel
Ord, ReadPrec [VertexLabel]
ReadPrec VertexLabel
Int -> ReadS VertexLabel
ReadS [VertexLabel]
(Int -> ReadS VertexLabel)
-> ReadS [VertexLabel]
-> ReadPrec VertexLabel
-> ReadPrec [VertexLabel]
-> Read VertexLabel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VertexLabel
readsPrec :: Int -> ReadS VertexLabel
$creadList :: ReadS [VertexLabel]
readList :: ReadS [VertexLabel]
$creadPrec :: ReadPrec VertexLabel
readPrec :: ReadPrec VertexLabel
$creadListPrec :: ReadPrec [VertexLabel]
readListPrec :: ReadPrec [VertexLabel]
Read, Int -> VertexLabel -> ShowS
[VertexLabel] -> ShowS
VertexLabel -> String
(Int -> VertexLabel -> ShowS)
-> (VertexLabel -> String)
-> ([VertexLabel] -> ShowS)
-> Show VertexLabel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VertexLabel -> ShowS
showsPrec :: Int -> VertexLabel -> ShowS
$cshow :: VertexLabel -> String
show :: VertexLabel -> String
$cshowList :: [VertexLabel] -> ShowS
showList :: [VertexLabel] -> ShowS
Show)
_VertexLabel :: Name
_VertexLabel = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.VertexLabel")
data VertexType t =
VertexType {
forall t. VertexType t -> VertexLabel
vertexTypeLabel :: VertexLabel,
forall t. VertexType t -> t
vertexTypeId :: t,
forall t. VertexType t -> [PropertyType t]
vertexTypeProperties :: [PropertyType t]}
deriving (VertexType t -> VertexType t -> Bool
(VertexType t -> VertexType t -> Bool)
-> (VertexType t -> VertexType t -> Bool) -> Eq (VertexType t)
forall t. Eq t => VertexType t -> VertexType t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => VertexType t -> VertexType t -> Bool
== :: VertexType t -> VertexType t -> Bool
$c/= :: forall t. Eq t => VertexType t -> VertexType t -> Bool
/= :: VertexType t -> VertexType t -> Bool
Eq, Eq (VertexType t)
Eq (VertexType t) =>
(VertexType t -> VertexType t -> Ordering)
-> (VertexType t -> VertexType t -> Bool)
-> (VertexType t -> VertexType t -> Bool)
-> (VertexType t -> VertexType t -> Bool)
-> (VertexType t -> VertexType t -> Bool)
-> (VertexType t -> VertexType t -> VertexType t)
-> (VertexType t -> VertexType t -> VertexType t)
-> Ord (VertexType t)
VertexType t -> VertexType t -> Bool
VertexType t -> VertexType t -> Ordering
VertexType t -> VertexType t -> VertexType t
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
forall t. Ord t => Eq (VertexType t)
forall t. Ord t => VertexType t -> VertexType t -> Bool
forall t. Ord t => VertexType t -> VertexType t -> Ordering
forall t. Ord t => VertexType t -> VertexType t -> VertexType t
$ccompare :: forall t. Ord t => VertexType t -> VertexType t -> Ordering
compare :: VertexType t -> VertexType t -> Ordering
$c< :: forall t. Ord t => VertexType t -> VertexType t -> Bool
< :: VertexType t -> VertexType t -> Bool
$c<= :: forall t. Ord t => VertexType t -> VertexType t -> Bool
<= :: VertexType t -> VertexType t -> Bool
$c> :: forall t. Ord t => VertexType t -> VertexType t -> Bool
> :: VertexType t -> VertexType t -> Bool
$c>= :: forall t. Ord t => VertexType t -> VertexType t -> Bool
>= :: VertexType t -> VertexType t -> Bool
$cmax :: forall t. Ord t => VertexType t -> VertexType t -> VertexType t
max :: VertexType t -> VertexType t -> VertexType t
$cmin :: forall t. Ord t => VertexType t -> VertexType t -> VertexType t
min :: VertexType t -> VertexType t -> VertexType t
Ord, ReadPrec [VertexType t]
ReadPrec (VertexType t)
Int -> ReadS (VertexType t)
ReadS [VertexType t]
(Int -> ReadS (VertexType t))
-> ReadS [VertexType t]
-> ReadPrec (VertexType t)
-> ReadPrec [VertexType t]
-> Read (VertexType t)
forall t. Read t => ReadPrec [VertexType t]
forall t. Read t => ReadPrec (VertexType t)
forall t. Read t => Int -> ReadS (VertexType t)
forall t. Read t => ReadS [VertexType t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (VertexType t)
readsPrec :: Int -> ReadS (VertexType t)
$creadList :: forall t. Read t => ReadS [VertexType t]
readList :: ReadS [VertexType t]
$creadPrec :: forall t. Read t => ReadPrec (VertexType t)
readPrec :: ReadPrec (VertexType t)
$creadListPrec :: forall t. Read t => ReadPrec [VertexType t]
readListPrec :: ReadPrec [VertexType t]
Read, Int -> VertexType t -> ShowS
[VertexType t] -> ShowS
VertexType t -> String
(Int -> VertexType t -> ShowS)
-> (VertexType t -> String)
-> ([VertexType t] -> ShowS)
-> Show (VertexType t)
forall t. Show t => Int -> VertexType t -> ShowS
forall t. Show t => [VertexType t] -> ShowS
forall t. Show t => VertexType t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> VertexType t -> ShowS
showsPrec :: Int -> VertexType t -> ShowS
$cshow :: forall t. Show t => VertexType t -> String
show :: VertexType t -> String
$cshowList :: forall t. Show t => [VertexType t] -> ShowS
showList :: [VertexType t] -> ShowS
Show)
_VertexType :: Name
_VertexType = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/propertyGraph.VertexType")
_VertexType_label :: Name
_VertexType_label = (String -> Name
Core.Name String
"label")
_VertexType_id :: Name
_VertexType_id = (String -> Name
Core.Name String
"id")
_VertexType_properties :: Name
_VertexType_properties = (String -> Name
Core.Name String
"properties")