| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Hydra.Langs.Tinkerpop.PropertyGraph
Description
A typed property graph data model. Property graphs are parameterized a type for property and id values, while property graph schemas are parameterized by a type for property and id types
Synopsis
- data Direction
- _Direction :: Name
- _Direction_out :: Name
- _Direction_in :: Name
- _Direction_both :: Name
- _Direction_undirected :: Name
- data Edge v = Edge {- edgeLabel :: EdgeLabel
- edgeId :: v
- edgeOut :: v
- edgeIn :: v
- edgeProperties :: Map PropertyKey v
 
- _Edge :: Name
- _Edge_label :: Name
- _Edge_id :: Name
- _Edge_out :: Name
- _Edge_in :: Name
- _Edge_properties :: Name
- newtype EdgeLabel = EdgeLabel {}
- _EdgeLabel :: Name
- data EdgeType t = EdgeType {}
- _EdgeType :: Name
- _EdgeType_label :: Name
- _EdgeType_id :: Name
- _EdgeType_out :: Name
- _EdgeType_in :: Name
- _EdgeType_properties :: Name
- data Element v- = ElementVertex (Vertex v)
- | ElementEdge (Edge v)
 
- _Element :: Name
- _Element_vertex :: Name
- _Element_edge :: Name
- data ElementKind
- _ElementKind :: Name
- _ElementKind_vertex :: Name
- _ElementKind_edge :: Name
- data ElementTree v = ElementTree {- elementTreeSelf :: Element v
- elementTreeDependencies :: [ElementTree v]
 
- _ElementTree :: Name
- _ElementTree_self :: Name
- _ElementTree_dependencies :: Name
- data ElementType t- = ElementTypeVertex (VertexType t)
- | ElementTypeEdge (EdgeType t)
 
- _ElementType :: Name
- _ElementType_vertex :: Name
- _ElementType_edge :: Name
- data ElementTypeTree t = ElementTypeTree {}
- _ElementTypeTree :: Name
- _ElementTypeTree_self :: Name
- _ElementTypeTree_dependencies :: Name
- data Graph v = Graph {- graphVertices :: Map v (Vertex v)
- graphEdges :: Map v (Edge v)
 
- _Graph :: Name
- _Graph_vertices :: Name
- _Graph_edges :: Name
- data GraphSchema t = GraphSchema {- graphSchemaVertices :: Map VertexLabel (VertexType t)
- graphSchemaEdges :: Map EdgeLabel (EdgeType t)
 
- _GraphSchema :: Name
- _GraphSchema_vertices :: Name
- _GraphSchema_edges :: Name
- data Label
- _Label :: Name
- _Label_vertex :: Name
- _Label_edge :: Name
- data Property v = Property {- propertyKey :: PropertyKey
- propertyValue :: v
 
- _Property :: Name
- _Property_key :: Name
- _Property_value :: Name
- newtype PropertyKey = PropertyKey {}
- _PropertyKey :: Name
- data PropertyType t = PropertyType {}
- _PropertyType :: Name
- _PropertyType_key :: Name
- _PropertyType_value :: Name
- _PropertyType_required :: Name
- data Vertex v = Vertex {- vertexLabel :: VertexLabel
- vertexId :: v
- vertexProperties :: Map PropertyKey v
 
- _Vertex :: Name
- _Vertex_label :: Name
- _Vertex_id :: Name
- _Vertex_properties :: Name
- newtype VertexLabel = VertexLabel {}
- _VertexLabel :: Name
- data VertexType t = VertexType {}
- _VertexType :: Name
- _VertexType_label :: Name
- _VertexType_id :: Name
- _VertexType_properties :: Name
Documentation
The direction of an edge or edge pattern
Constructors
| DirectionOut | |
| DirectionIn | |
| DirectionBoth | |
| DirectionUndirected | 
Instances
| Read Direction Source # | |
| Show Direction Source # | |
| Eq Direction Source # | |
| Ord Direction Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
_Direction :: Name Source #
_Direction_in :: Name Source #
An edge
Constructors
| Edge | |
| Fields 
 | |
_Edge_label :: Name Source #
The label of an edge
Constructors
| EdgeLabel | |
| Fields | |
Instances
| Read EdgeLabel Source # | |
| Show EdgeLabel Source # | |
| Eq EdgeLabel Source # | |
| Ord EdgeLabel Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
_EdgeLabel :: Name Source #
The type of an edge
Constructors
| EdgeType | |
| Fields 
 | |
Instances
| Read t => Read (EdgeType t) Source # | |
| Show t => Show (EdgeType t) Source # | |
| Eq t => Eq (EdgeType t) Source # | |
| Ord t => Ord (EdgeType t) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
_EdgeType_id :: Name Source #
_EdgeType_out :: Name Source #
_EdgeType_in :: Name Source #
Either a vertex or an edge
Constructors
| ElementVertex (Vertex v) | |
| ElementEdge (Edge v) | 
Instances
| Read v => Read (Element v) Source # | |
| Show v => Show (Element v) Source # | |
| Eq v => Eq (Element v) Source # | |
| Ord v => Ord (Element v) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
_Element_edge :: Name Source #
data ElementKind Source #
The kind of an element: vertex or edge
Constructors
| ElementKindVertex | |
| ElementKindEdge | 
Instances
| Read ElementKind Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods readsPrec :: Int -> ReadS ElementKind # readList :: ReadS [ElementKind] # readPrec :: ReadPrec ElementKind # readListPrec :: ReadPrec [ElementKind] # | |
| Show ElementKind Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods showsPrec :: Int -> ElementKind -> ShowS # show :: ElementKind -> String # showList :: [ElementKind] -> ShowS # | |
| Eq ElementKind Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
| Ord ElementKind Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods compare :: ElementKind -> ElementKind -> Ordering # (<) :: ElementKind -> ElementKind -> Bool # (<=) :: ElementKind -> ElementKind -> Bool # (>) :: ElementKind -> ElementKind -> Bool # (>=) :: ElementKind -> ElementKind -> Bool # max :: ElementKind -> ElementKind -> ElementKind # min :: ElementKind -> ElementKind -> ElementKind # | |
_ElementKind :: Name Source #
data ElementTree v Source #
An element together with its dependencies in some context
Constructors
| ElementTree | |
| Fields 
 | |
Instances
_ElementTree :: Name Source #
data ElementType t Source #
The type of a vertex or edge
Constructors
| ElementTypeVertex (VertexType t) | |
| ElementTypeEdge (EdgeType t) | 
Instances
_ElementType :: Name Source #
data ElementTypeTree t Source #
An element type together with its dependencies in some context
Constructors
| ElementTypeTree | |
| Fields | |
Instances
A graph; a self-contained collection of vertices and edges
Constructors
| Graph | |
| Fields 
 | |
_Graph_edges :: Name Source #
data GraphSchema t Source #
A graph schema; a vertex and edge types for the vertices and edges of a graph conforming to the schema
Constructors
| GraphSchema | |
| Fields 
 | |
Instances
_GraphSchema :: Name Source #
Either a vertex or edge label
Constructors
| LabelVertex VertexLabel | |
| LabelEdge EdgeLabel | 
_Label_vertex :: Name Source #
_Label_edge :: Name Source #
A key/value property
Constructors
| Property | |
| Fields 
 | |
Instances
| Read v => Read (Property v) Source # | |
| Show v => Show (Property v) Source # | |
| Eq v => Eq (Property v) Source # | |
| Ord v => Ord (Property v) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
_Property_key :: Name Source #
newtype PropertyKey Source #
A property key
Constructors
| PropertyKey | |
| Fields | |
Instances
| Read PropertyKey Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods readsPrec :: Int -> ReadS PropertyKey # readList :: ReadS [PropertyKey] # readPrec :: ReadPrec PropertyKey # readListPrec :: ReadPrec [PropertyKey] # | |
| Show PropertyKey Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods showsPrec :: Int -> PropertyKey -> ShowS # show :: PropertyKey -> String # showList :: [PropertyKey] -> ShowS # | |
| Eq PropertyKey Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
| Ord PropertyKey Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods compare :: PropertyKey -> PropertyKey -> Ordering # (<) :: PropertyKey -> PropertyKey -> Bool # (<=) :: PropertyKey -> PropertyKey -> Bool # (>) :: PropertyKey -> PropertyKey -> Bool # (>=) :: PropertyKey -> PropertyKey -> Bool # max :: PropertyKey -> PropertyKey -> PropertyKey # min :: PropertyKey -> PropertyKey -> PropertyKey # | |
_PropertyKey :: Name Source #
data PropertyType t Source #
The type of a property
Constructors
| PropertyType | |
| Fields 
 | |
Instances
_PropertyType :: Name Source #
A vertex
Constructors
| Vertex | |
| Fields 
 | |
_Vertex_label :: Name Source #
_Vertex_id :: Name Source #
newtype VertexLabel Source #
The label of a vertex. The default (null) vertex is represented by the empty string
Constructors
| VertexLabel | |
| Fields | |
Instances
| Read VertexLabel Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods readsPrec :: Int -> ReadS VertexLabel # readList :: ReadS [VertexLabel] # readPrec :: ReadPrec VertexLabel # readListPrec :: ReadPrec [VertexLabel] # | |
| Show VertexLabel Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods showsPrec :: Int -> VertexLabel -> ShowS # show :: VertexLabel -> String # showList :: [VertexLabel] -> ShowS # | |
| Eq VertexLabel Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
| Ord VertexLabel Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods compare :: VertexLabel -> VertexLabel -> Ordering # (<) :: VertexLabel -> VertexLabel -> Bool # (<=) :: VertexLabel -> VertexLabel -> Bool # (>) :: VertexLabel -> VertexLabel -> Bool # (>=) :: VertexLabel -> VertexLabel -> Bool # max :: VertexLabel -> VertexLabel -> VertexLabel # min :: VertexLabel -> VertexLabel -> VertexLabel # | |
_VertexLabel :: Name Source #
data VertexType t Source #
The type of a vertex
Constructors
| VertexType | |
| Fields 
 | |
Instances
| Read t => Read (VertexType t) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods readsPrec :: Int -> ReadS (VertexType t) # readList :: ReadS [VertexType t] # readPrec :: ReadPrec (VertexType t) # readListPrec :: ReadPrec [VertexType t] # | |
| Show t => Show (VertexType t) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods showsPrec :: Int -> VertexType t -> ShowS # show :: VertexType t -> String # showList :: [VertexType t] -> ShowS # | |
| Eq t => Eq (VertexType t) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph | |
| Ord t => Ord (VertexType t) Source # | |
| Defined in Hydra.Langs.Tinkerpop.PropertyGraph Methods compare :: 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 # max :: VertexType t -> VertexType t -> VertexType t # min :: VertexType t -> VertexType t -> VertexType t # | |
_VertexType :: Name Source #