module Hydra.Langs.Tinkerpop.Mappings where
import qualified Hydra.Compute as Compute
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 AnnotationSchema =
AnnotationSchema {
AnnotationSchema -> String
annotationSchemaVertexLabel :: String,
AnnotationSchema -> String
annotationSchemaEdgeLabel :: String,
AnnotationSchema -> String
annotationSchemaVertexId :: String,
AnnotationSchema -> String
annotationSchemaEdgeId :: String,
AnnotationSchema -> String
annotationSchemaPropertyKey :: String,
AnnotationSchema -> String
annotationSchemaPropertyValue :: String,
AnnotationSchema -> String
annotationSchemaOutVertex :: String,
AnnotationSchema -> String
annotationSchemaOutVertexLabel :: String,
AnnotationSchema -> String
annotationSchemaInVertex :: String,
AnnotationSchema -> String
annotationSchemaInVertexLabel :: String,
AnnotationSchema -> String
annotationSchemaOutEdge :: String,
AnnotationSchema -> String
annotationSchemaOutEdgeLabel :: String,
AnnotationSchema -> String
annotationSchemaInEdge :: String,
AnnotationSchema -> String
annotationSchemaInEdgeLabel :: String,
AnnotationSchema -> String
annotationSchemaIgnore :: String}
deriving (AnnotationSchema -> AnnotationSchema -> Bool
(AnnotationSchema -> AnnotationSchema -> Bool)
-> (AnnotationSchema -> AnnotationSchema -> Bool)
-> Eq AnnotationSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationSchema -> AnnotationSchema -> Bool
== :: AnnotationSchema -> AnnotationSchema -> Bool
$c/= :: AnnotationSchema -> AnnotationSchema -> Bool
/= :: AnnotationSchema -> AnnotationSchema -> Bool
Eq, Eq AnnotationSchema
Eq AnnotationSchema =>
(AnnotationSchema -> AnnotationSchema -> Ordering)
-> (AnnotationSchema -> AnnotationSchema -> Bool)
-> (AnnotationSchema -> AnnotationSchema -> Bool)
-> (AnnotationSchema -> AnnotationSchema -> Bool)
-> (AnnotationSchema -> AnnotationSchema -> Bool)
-> (AnnotationSchema -> AnnotationSchema -> AnnotationSchema)
-> (AnnotationSchema -> AnnotationSchema -> AnnotationSchema)
-> Ord AnnotationSchema
AnnotationSchema -> AnnotationSchema -> Bool
AnnotationSchema -> AnnotationSchema -> Ordering
AnnotationSchema -> AnnotationSchema -> AnnotationSchema
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 :: AnnotationSchema -> AnnotationSchema -> Ordering
compare :: AnnotationSchema -> AnnotationSchema -> Ordering
$c< :: AnnotationSchema -> AnnotationSchema -> Bool
< :: AnnotationSchema -> AnnotationSchema -> Bool
$c<= :: AnnotationSchema -> AnnotationSchema -> Bool
<= :: AnnotationSchema -> AnnotationSchema -> Bool
$c> :: AnnotationSchema -> AnnotationSchema -> Bool
> :: AnnotationSchema -> AnnotationSchema -> Bool
$c>= :: AnnotationSchema -> AnnotationSchema -> Bool
>= :: AnnotationSchema -> AnnotationSchema -> Bool
$cmax :: AnnotationSchema -> AnnotationSchema -> AnnotationSchema
max :: AnnotationSchema -> AnnotationSchema -> AnnotationSchema
$cmin :: AnnotationSchema -> AnnotationSchema -> AnnotationSchema
min :: AnnotationSchema -> AnnotationSchema -> AnnotationSchema
Ord, ReadPrec [AnnotationSchema]
ReadPrec AnnotationSchema
Int -> ReadS AnnotationSchema
ReadS [AnnotationSchema]
(Int -> ReadS AnnotationSchema)
-> ReadS [AnnotationSchema]
-> ReadPrec AnnotationSchema
-> ReadPrec [AnnotationSchema]
-> Read AnnotationSchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationSchema
readsPrec :: Int -> ReadS AnnotationSchema
$creadList :: ReadS [AnnotationSchema]
readList :: ReadS [AnnotationSchema]
$creadPrec :: ReadPrec AnnotationSchema
readPrec :: ReadPrec AnnotationSchema
$creadListPrec :: ReadPrec [AnnotationSchema]
readListPrec :: ReadPrec [AnnotationSchema]
Read, Int -> AnnotationSchema -> ShowS
[AnnotationSchema] -> ShowS
AnnotationSchema -> String
(Int -> AnnotationSchema -> ShowS)
-> (AnnotationSchema -> String)
-> ([AnnotationSchema] -> ShowS)
-> Show AnnotationSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationSchema -> ShowS
showsPrec :: Int -> AnnotationSchema -> ShowS
$cshow :: AnnotationSchema -> String
show :: AnnotationSchema -> String
$cshowList :: [AnnotationSchema] -> ShowS
showList :: [AnnotationSchema] -> ShowS
Show)
_AnnotationSchema :: Name
_AnnotationSchema = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.AnnotationSchema")
_AnnotationSchema_vertexLabel :: Name
_AnnotationSchema_vertexLabel = (String -> Name
Core.Name String
"vertexLabel")
_AnnotationSchema_edgeLabel :: Name
_AnnotationSchema_edgeLabel = (String -> Name
Core.Name String
"edgeLabel")
_AnnotationSchema_vertexId :: Name
_AnnotationSchema_vertexId = (String -> Name
Core.Name String
"vertexId")
_AnnotationSchema_edgeId :: Name
_AnnotationSchema_edgeId = (String -> Name
Core.Name String
"edgeId")
_AnnotationSchema_propertyKey :: Name
_AnnotationSchema_propertyKey = (String -> Name
Core.Name String
"propertyKey")
_AnnotationSchema_propertyValue :: Name
_AnnotationSchema_propertyValue = (String -> Name
Core.Name String
"propertyValue")
_AnnotationSchema_outVertex :: Name
_AnnotationSchema_outVertex = (String -> Name
Core.Name String
"outVertex")
_AnnotationSchema_outVertexLabel :: Name
_AnnotationSchema_outVertexLabel = (String -> Name
Core.Name String
"outVertexLabel")
_AnnotationSchema_inVertex :: Name
_AnnotationSchema_inVertex = (String -> Name
Core.Name String
"inVertex")
_AnnotationSchema_inVertexLabel :: Name
_AnnotationSchema_inVertexLabel = (String -> Name
Core.Name String
"inVertexLabel")
_AnnotationSchema_outEdge :: Name
_AnnotationSchema_outEdge = (String -> Name
Core.Name String
"outEdge")
_AnnotationSchema_outEdgeLabel :: Name
_AnnotationSchema_outEdgeLabel = (String -> Name
Core.Name String
"outEdgeLabel")
_AnnotationSchema_inEdge :: Name
_AnnotationSchema_inEdge = (String -> Name
Core.Name String
"inEdge")
_AnnotationSchema_inEdgeLabel :: Name
_AnnotationSchema_inEdgeLabel = (String -> Name
Core.Name String
"inEdgeLabel")
_AnnotationSchema_ignore :: Name
_AnnotationSchema_ignore = (String -> Name
Core.Name String
"ignore")
data EdgeSpec =
EdgeSpec {
EdgeSpec -> EdgeLabel
edgeSpecLabel :: PropertyGraph.EdgeLabel,
EdgeSpec -> ValueSpec
edgeSpecId :: ValueSpec,
EdgeSpec -> ValueSpec
edgeSpecOut :: ValueSpec,
EdgeSpec -> ValueSpec
edgeSpecIn :: ValueSpec,
EdgeSpec -> [PropertySpec]
edgeSpecProperties :: [PropertySpec]}
deriving (EdgeSpec -> EdgeSpec -> Bool
(EdgeSpec -> EdgeSpec -> Bool)
-> (EdgeSpec -> EdgeSpec -> Bool) -> Eq EdgeSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeSpec -> EdgeSpec -> Bool
== :: EdgeSpec -> EdgeSpec -> Bool
$c/= :: EdgeSpec -> EdgeSpec -> Bool
/= :: EdgeSpec -> EdgeSpec -> Bool
Eq, Eq EdgeSpec
Eq EdgeSpec =>
(EdgeSpec -> EdgeSpec -> Ordering)
-> (EdgeSpec -> EdgeSpec -> Bool)
-> (EdgeSpec -> EdgeSpec -> Bool)
-> (EdgeSpec -> EdgeSpec -> Bool)
-> (EdgeSpec -> EdgeSpec -> Bool)
-> (EdgeSpec -> EdgeSpec -> EdgeSpec)
-> (EdgeSpec -> EdgeSpec -> EdgeSpec)
-> Ord EdgeSpec
EdgeSpec -> EdgeSpec -> Bool
EdgeSpec -> EdgeSpec -> Ordering
EdgeSpec -> EdgeSpec -> EdgeSpec
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 :: EdgeSpec -> EdgeSpec -> Ordering
compare :: EdgeSpec -> EdgeSpec -> Ordering
$c< :: EdgeSpec -> EdgeSpec -> Bool
< :: EdgeSpec -> EdgeSpec -> Bool
$c<= :: EdgeSpec -> EdgeSpec -> Bool
<= :: EdgeSpec -> EdgeSpec -> Bool
$c> :: EdgeSpec -> EdgeSpec -> Bool
> :: EdgeSpec -> EdgeSpec -> Bool
$c>= :: EdgeSpec -> EdgeSpec -> Bool
>= :: EdgeSpec -> EdgeSpec -> Bool
$cmax :: EdgeSpec -> EdgeSpec -> EdgeSpec
max :: EdgeSpec -> EdgeSpec -> EdgeSpec
$cmin :: EdgeSpec -> EdgeSpec -> EdgeSpec
min :: EdgeSpec -> EdgeSpec -> EdgeSpec
Ord, ReadPrec [EdgeSpec]
ReadPrec EdgeSpec
Int -> ReadS EdgeSpec
ReadS [EdgeSpec]
(Int -> ReadS EdgeSpec)
-> ReadS [EdgeSpec]
-> ReadPrec EdgeSpec
-> ReadPrec [EdgeSpec]
-> Read EdgeSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgeSpec
readsPrec :: Int -> ReadS EdgeSpec
$creadList :: ReadS [EdgeSpec]
readList :: ReadS [EdgeSpec]
$creadPrec :: ReadPrec EdgeSpec
readPrec :: ReadPrec EdgeSpec
$creadListPrec :: ReadPrec [EdgeSpec]
readListPrec :: ReadPrec [EdgeSpec]
Read, Int -> EdgeSpec -> ShowS
[EdgeSpec] -> ShowS
EdgeSpec -> String
(Int -> EdgeSpec -> ShowS)
-> (EdgeSpec -> String) -> ([EdgeSpec] -> ShowS) -> Show EdgeSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeSpec -> ShowS
showsPrec :: Int -> EdgeSpec -> ShowS
$cshow :: EdgeSpec -> String
show :: EdgeSpec -> String
$cshowList :: [EdgeSpec] -> ShowS
showList :: [EdgeSpec] -> ShowS
Show)
_EdgeSpec :: Name
_EdgeSpec = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.EdgeSpec")
_EdgeSpec_label :: Name
_EdgeSpec_label = (String -> Name
Core.Name String
"label")
_EdgeSpec_id :: Name
_EdgeSpec_id = (String -> Name
Core.Name String
"id")
_EdgeSpec_out :: Name
_EdgeSpec_out = (String -> Name
Core.Name String
"out")
_EdgeSpec_in :: Name
_EdgeSpec_in = (String -> Name
Core.Name String
"in")
_EdgeSpec_properties :: Name
_EdgeSpec_properties = (String -> Name
Core.Name String
"properties")
data ElementSpec =
ElementSpecVertex VertexSpec |
ElementSpecEdge EdgeSpec
deriving (ElementSpec -> ElementSpec -> Bool
(ElementSpec -> ElementSpec -> Bool)
-> (ElementSpec -> ElementSpec -> Bool) -> Eq ElementSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElementSpec -> ElementSpec -> Bool
== :: ElementSpec -> ElementSpec -> Bool
$c/= :: ElementSpec -> ElementSpec -> Bool
/= :: ElementSpec -> ElementSpec -> Bool
Eq, Eq ElementSpec
Eq ElementSpec =>
(ElementSpec -> ElementSpec -> Ordering)
-> (ElementSpec -> ElementSpec -> Bool)
-> (ElementSpec -> ElementSpec -> Bool)
-> (ElementSpec -> ElementSpec -> Bool)
-> (ElementSpec -> ElementSpec -> Bool)
-> (ElementSpec -> ElementSpec -> ElementSpec)
-> (ElementSpec -> ElementSpec -> ElementSpec)
-> Ord ElementSpec
ElementSpec -> ElementSpec -> Bool
ElementSpec -> ElementSpec -> Ordering
ElementSpec -> ElementSpec -> ElementSpec
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 :: ElementSpec -> ElementSpec -> Ordering
compare :: ElementSpec -> ElementSpec -> Ordering
$c< :: ElementSpec -> ElementSpec -> Bool
< :: ElementSpec -> ElementSpec -> Bool
$c<= :: ElementSpec -> ElementSpec -> Bool
<= :: ElementSpec -> ElementSpec -> Bool
$c> :: ElementSpec -> ElementSpec -> Bool
> :: ElementSpec -> ElementSpec -> Bool
$c>= :: ElementSpec -> ElementSpec -> Bool
>= :: ElementSpec -> ElementSpec -> Bool
$cmax :: ElementSpec -> ElementSpec -> ElementSpec
max :: ElementSpec -> ElementSpec -> ElementSpec
$cmin :: ElementSpec -> ElementSpec -> ElementSpec
min :: ElementSpec -> ElementSpec -> ElementSpec
Ord, ReadPrec [ElementSpec]
ReadPrec ElementSpec
Int -> ReadS ElementSpec
ReadS [ElementSpec]
(Int -> ReadS ElementSpec)
-> ReadS [ElementSpec]
-> ReadPrec ElementSpec
-> ReadPrec [ElementSpec]
-> Read ElementSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ElementSpec
readsPrec :: Int -> ReadS ElementSpec
$creadList :: ReadS [ElementSpec]
readList :: ReadS [ElementSpec]
$creadPrec :: ReadPrec ElementSpec
readPrec :: ReadPrec ElementSpec
$creadListPrec :: ReadPrec [ElementSpec]
readListPrec :: ReadPrec [ElementSpec]
Read, Int -> ElementSpec -> ShowS
[ElementSpec] -> ShowS
ElementSpec -> String
(Int -> ElementSpec -> ShowS)
-> (ElementSpec -> String)
-> ([ElementSpec] -> ShowS)
-> Show ElementSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElementSpec -> ShowS
showsPrec :: Int -> ElementSpec -> ShowS
$cshow :: ElementSpec -> String
show :: ElementSpec -> String
$cshowList :: [ElementSpec] -> ShowS
showList :: [ElementSpec] -> ShowS
Show)
_ElementSpec :: Name
_ElementSpec = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.ElementSpec")
_ElementSpec_vertex :: Name
_ElementSpec_vertex = (String -> Name
Core.Name String
"vertex")
_ElementSpec_edge :: Name
_ElementSpec_edge = (String -> Name
Core.Name String
"edge")
data PropertySpec =
PropertySpec {
PropertySpec -> PropertyKey
propertySpecKey :: PropertyGraph.PropertyKey,
PropertySpec -> ValueSpec
propertySpecValue :: ValueSpec}
deriving (PropertySpec -> PropertySpec -> Bool
(PropertySpec -> PropertySpec -> Bool)
-> (PropertySpec -> PropertySpec -> Bool) -> Eq PropertySpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertySpec -> PropertySpec -> Bool
== :: PropertySpec -> PropertySpec -> Bool
$c/= :: PropertySpec -> PropertySpec -> Bool
/= :: PropertySpec -> PropertySpec -> Bool
Eq, Eq PropertySpec
Eq PropertySpec =>
(PropertySpec -> PropertySpec -> Ordering)
-> (PropertySpec -> PropertySpec -> Bool)
-> (PropertySpec -> PropertySpec -> Bool)
-> (PropertySpec -> PropertySpec -> Bool)
-> (PropertySpec -> PropertySpec -> Bool)
-> (PropertySpec -> PropertySpec -> PropertySpec)
-> (PropertySpec -> PropertySpec -> PropertySpec)
-> Ord PropertySpec
PropertySpec -> PropertySpec -> Bool
PropertySpec -> PropertySpec -> Ordering
PropertySpec -> PropertySpec -> PropertySpec
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 :: PropertySpec -> PropertySpec -> Ordering
compare :: PropertySpec -> PropertySpec -> Ordering
$c< :: PropertySpec -> PropertySpec -> Bool
< :: PropertySpec -> PropertySpec -> Bool
$c<= :: PropertySpec -> PropertySpec -> Bool
<= :: PropertySpec -> PropertySpec -> Bool
$c> :: PropertySpec -> PropertySpec -> Bool
> :: PropertySpec -> PropertySpec -> Bool
$c>= :: PropertySpec -> PropertySpec -> Bool
>= :: PropertySpec -> PropertySpec -> Bool
$cmax :: PropertySpec -> PropertySpec -> PropertySpec
max :: PropertySpec -> PropertySpec -> PropertySpec
$cmin :: PropertySpec -> PropertySpec -> PropertySpec
min :: PropertySpec -> PropertySpec -> PropertySpec
Ord, ReadPrec [PropertySpec]
ReadPrec PropertySpec
Int -> ReadS PropertySpec
ReadS [PropertySpec]
(Int -> ReadS PropertySpec)
-> ReadS [PropertySpec]
-> ReadPrec PropertySpec
-> ReadPrec [PropertySpec]
-> Read PropertySpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertySpec
readsPrec :: Int -> ReadS PropertySpec
$creadList :: ReadS [PropertySpec]
readList :: ReadS [PropertySpec]
$creadPrec :: ReadPrec PropertySpec
readPrec :: ReadPrec PropertySpec
$creadListPrec :: ReadPrec [PropertySpec]
readListPrec :: ReadPrec [PropertySpec]
Read, Int -> PropertySpec -> ShowS
[PropertySpec] -> ShowS
PropertySpec -> String
(Int -> PropertySpec -> ShowS)
-> (PropertySpec -> String)
-> ([PropertySpec] -> ShowS)
-> Show PropertySpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertySpec -> ShowS
showsPrec :: Int -> PropertySpec -> ShowS
$cshow :: PropertySpec -> String
show :: PropertySpec -> String
$cshowList :: [PropertySpec] -> ShowS
showList :: [PropertySpec] -> ShowS
Show)
_PropertySpec :: Name
_PropertySpec = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.PropertySpec")
_PropertySpec_key :: Name
_PropertySpec_key = (String -> Name
Core.Name String
"key")
_PropertySpec_value :: Name
_PropertySpec_value = (String -> Name
Core.Name String
"value")
data Schema s t v =
Schema {
forall s t v. Schema s t v -> Coder s s Type t
schemaVertexIdTypes :: (Compute.Coder s s Core.Type t),
forall s t v. Schema s t v -> Coder s s Term v
schemaVertexIds :: (Compute.Coder s s Core.Term v),
forall s t v. Schema s t v -> Coder s s Type t
schemaEdgeIdTypes :: (Compute.Coder s s Core.Type t),
forall s t v. Schema s t v -> Coder s s Term v
schemaEdgeIds :: (Compute.Coder s s Core.Term v),
forall s t v. Schema s t v -> Coder s s Type t
schemaPropertyTypes :: (Compute.Coder s s Core.Type t),
forall s t v. Schema s t v -> Coder s s Term v
schemaPropertyValues :: (Compute.Coder s s Core.Term v),
forall s t v. Schema s t v -> AnnotationSchema
schemaAnnotations :: AnnotationSchema,
forall s t v. Schema s t v -> v
schemaDefaultVertexId :: v,
forall s t v. Schema s t v -> v
schemaDefaultEdgeId :: v}
_Schema :: Name
_Schema = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.Schema")
_Schema_vertexIdTypes :: Name
_Schema_vertexIdTypes = (String -> Name
Core.Name String
"vertexIdTypes")
_Schema_vertexIds :: Name
_Schema_vertexIds = (String -> Name
Core.Name String
"vertexIds")
_Schema_edgeIdTypes :: Name
_Schema_edgeIdTypes = (String -> Name
Core.Name String
"edgeIdTypes")
_Schema_edgeIds :: Name
_Schema_edgeIds = (String -> Name
Core.Name String
"edgeIds")
_Schema_propertyTypes :: Name
_Schema_propertyTypes = (String -> Name
Core.Name String
"propertyTypes")
_Schema_propertyValues :: Name
_Schema_propertyValues = (String -> Name
Core.Name String
"propertyValues")
_Schema_annotations :: Name
_Schema_annotations = (String -> Name
Core.Name String
"annotations")
_Schema_defaultVertexId :: Name
_Schema_defaultVertexId = (String -> Name
Core.Name String
"defaultVertexId")
_Schema_defaultEdgeId :: Name
_Schema_defaultEdgeId = (String -> Name
Core.Name String
"defaultEdgeId")
data ValueSpec =
ValueSpecValue |
ValueSpecPattern String
deriving (ValueSpec -> ValueSpec -> Bool
(ValueSpec -> ValueSpec -> Bool)
-> (ValueSpec -> ValueSpec -> Bool) -> Eq ValueSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueSpec -> ValueSpec -> Bool
== :: ValueSpec -> ValueSpec -> Bool
$c/= :: ValueSpec -> ValueSpec -> Bool
/= :: ValueSpec -> ValueSpec -> Bool
Eq, Eq ValueSpec
Eq ValueSpec =>
(ValueSpec -> ValueSpec -> Ordering)
-> (ValueSpec -> ValueSpec -> Bool)
-> (ValueSpec -> ValueSpec -> Bool)
-> (ValueSpec -> ValueSpec -> Bool)
-> (ValueSpec -> ValueSpec -> Bool)
-> (ValueSpec -> ValueSpec -> ValueSpec)
-> (ValueSpec -> ValueSpec -> ValueSpec)
-> Ord ValueSpec
ValueSpec -> ValueSpec -> Bool
ValueSpec -> ValueSpec -> Ordering
ValueSpec -> ValueSpec -> ValueSpec
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 :: ValueSpec -> ValueSpec -> Ordering
compare :: ValueSpec -> ValueSpec -> Ordering
$c< :: ValueSpec -> ValueSpec -> Bool
< :: ValueSpec -> ValueSpec -> Bool
$c<= :: ValueSpec -> ValueSpec -> Bool
<= :: ValueSpec -> ValueSpec -> Bool
$c> :: ValueSpec -> ValueSpec -> Bool
> :: ValueSpec -> ValueSpec -> Bool
$c>= :: ValueSpec -> ValueSpec -> Bool
>= :: ValueSpec -> ValueSpec -> Bool
$cmax :: ValueSpec -> ValueSpec -> ValueSpec
max :: ValueSpec -> ValueSpec -> ValueSpec
$cmin :: ValueSpec -> ValueSpec -> ValueSpec
min :: ValueSpec -> ValueSpec -> ValueSpec
Ord, ReadPrec [ValueSpec]
ReadPrec ValueSpec
Int -> ReadS ValueSpec
ReadS [ValueSpec]
(Int -> ReadS ValueSpec)
-> ReadS [ValueSpec]
-> ReadPrec ValueSpec
-> ReadPrec [ValueSpec]
-> Read ValueSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ValueSpec
readsPrec :: Int -> ReadS ValueSpec
$creadList :: ReadS [ValueSpec]
readList :: ReadS [ValueSpec]
$creadPrec :: ReadPrec ValueSpec
readPrec :: ReadPrec ValueSpec
$creadListPrec :: ReadPrec [ValueSpec]
readListPrec :: ReadPrec [ValueSpec]
Read, Int -> ValueSpec -> ShowS
[ValueSpec] -> ShowS
ValueSpec -> String
(Int -> ValueSpec -> ShowS)
-> (ValueSpec -> String)
-> ([ValueSpec] -> ShowS)
-> Show ValueSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueSpec -> ShowS
showsPrec :: Int -> ValueSpec -> ShowS
$cshow :: ValueSpec -> String
show :: ValueSpec -> String
$cshowList :: [ValueSpec] -> ShowS
showList :: [ValueSpec] -> ShowS
Show)
_ValueSpec :: Name
_ValueSpec = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.ValueSpec")
_ValueSpec_value :: Name
_ValueSpec_value = (String -> Name
Core.Name String
"value")
_ValueSpec_pattern :: Name
_ValueSpec_pattern = (String -> Name
Core.Name String
"pattern")
data VertexSpec =
VertexSpec {
VertexSpec -> VertexLabel
vertexSpecLabel :: PropertyGraph.VertexLabel,
VertexSpec -> ValueSpec
vertexSpecId :: ValueSpec,
VertexSpec -> [PropertySpec]
vertexSpecProperties :: [PropertySpec]}
deriving (VertexSpec -> VertexSpec -> Bool
(VertexSpec -> VertexSpec -> Bool)
-> (VertexSpec -> VertexSpec -> Bool) -> Eq VertexSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VertexSpec -> VertexSpec -> Bool
== :: VertexSpec -> VertexSpec -> Bool
$c/= :: VertexSpec -> VertexSpec -> Bool
/= :: VertexSpec -> VertexSpec -> Bool
Eq, Eq VertexSpec
Eq VertexSpec =>
(VertexSpec -> VertexSpec -> Ordering)
-> (VertexSpec -> VertexSpec -> Bool)
-> (VertexSpec -> VertexSpec -> Bool)
-> (VertexSpec -> VertexSpec -> Bool)
-> (VertexSpec -> VertexSpec -> Bool)
-> (VertexSpec -> VertexSpec -> VertexSpec)
-> (VertexSpec -> VertexSpec -> VertexSpec)
-> Ord VertexSpec
VertexSpec -> VertexSpec -> Bool
VertexSpec -> VertexSpec -> Ordering
VertexSpec -> VertexSpec -> VertexSpec
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 :: VertexSpec -> VertexSpec -> Ordering
compare :: VertexSpec -> VertexSpec -> Ordering
$c< :: VertexSpec -> VertexSpec -> Bool
< :: VertexSpec -> VertexSpec -> Bool
$c<= :: VertexSpec -> VertexSpec -> Bool
<= :: VertexSpec -> VertexSpec -> Bool
$c> :: VertexSpec -> VertexSpec -> Bool
> :: VertexSpec -> VertexSpec -> Bool
$c>= :: VertexSpec -> VertexSpec -> Bool
>= :: VertexSpec -> VertexSpec -> Bool
$cmax :: VertexSpec -> VertexSpec -> VertexSpec
max :: VertexSpec -> VertexSpec -> VertexSpec
$cmin :: VertexSpec -> VertexSpec -> VertexSpec
min :: VertexSpec -> VertexSpec -> VertexSpec
Ord, ReadPrec [VertexSpec]
ReadPrec VertexSpec
Int -> ReadS VertexSpec
ReadS [VertexSpec]
(Int -> ReadS VertexSpec)
-> ReadS [VertexSpec]
-> ReadPrec VertexSpec
-> ReadPrec [VertexSpec]
-> Read VertexSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VertexSpec
readsPrec :: Int -> ReadS VertexSpec
$creadList :: ReadS [VertexSpec]
readList :: ReadS [VertexSpec]
$creadPrec :: ReadPrec VertexSpec
readPrec :: ReadPrec VertexSpec
$creadListPrec :: ReadPrec [VertexSpec]
readListPrec :: ReadPrec [VertexSpec]
Read, Int -> VertexSpec -> ShowS
[VertexSpec] -> ShowS
VertexSpec -> String
(Int -> VertexSpec -> ShowS)
-> (VertexSpec -> String)
-> ([VertexSpec] -> ShowS)
-> Show VertexSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VertexSpec -> ShowS
showsPrec :: Int -> VertexSpec -> ShowS
$cshow :: VertexSpec -> String
show :: VertexSpec -> String
$cshowList :: [VertexSpec] -> ShowS
showList :: [VertexSpec] -> ShowS
Show)
_VertexSpec :: Name
_VertexSpec = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/mappings.VertexSpec")
_VertexSpec_label :: Name
_VertexSpec_label = (String -> Name
Core.Name String
"label")
_VertexSpec_id :: Name
_VertexSpec_id = (String -> Name
Core.Name String
"id")
_VertexSpec_properties :: Name
_VertexSpec_properties = (String -> Name
Core.Name String
"properties")