| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Greskell.Graph
Contents
Description
This module defines types and functions about TinkerPop graph structure API.
- class Element e where
- type ElementID e
- type ElementProperty e :: * -> *
- class Element v => Vertex v
- class Element e => Edge e where
- type EdgeVertexID e
- class Property p where
- data T a b
- tId :: Element a => Greskell (T a (ElementID a))
- tKey :: (Element (p v), Property p) => Greskell (T (p v) Text)
- tLabel :: Element a => Greskell (T a Text)
- tValue :: (Element (p v), Property p) => Greskell (T (p v) v)
- newtype Key a b = Key {}
- key :: Text -> Key a b
- data AVertex = AVertex {}
- data AEdge = AEdge {}
- data AVertexProperty v = AVertexProperty {}
- data AProperty v = AProperty {}
- class PropertyMap m where
- data PropertyMapSingle p v
- data PropertyMapList p v
- lookupOneValue :: (PropertyMap m, Property p) => Text -> m p v -> Maybe v
- lookupListValues :: (PropertyMap m, Property p) => Text -> m p v -> [v]
- parseOneValue :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser v
- parseListValues :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser [v]
- parseNonEmptyValues :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser (NonEmpty v)
- fromProperties :: (PropertyMap m, Property p, Monoid (m p v)) => [p v] -> m p v
- class FromJSONWithKey a
TinkerPop graph structure types
org.apache.tinkerpop.gremlin.structure.Element interface in a
TinkerPop graph.
class Element v => Vertex v Source #
org.apache.tinkerpop.gremlin.structure.Vertex interface in a
TinkerPop graph.
class Element e => Edge e Source #
org.apache.tinkerpop.gremlin.structure.Edge interface in a
TinkerPop graph.
class Property p where Source #
org.apache.tinkerpop.gremlin.structure.Property interface in a
TinkerPop graph.
Minimal complete definition
Methods
propertyKey :: p v -> Text Source #
Get key of this property.
propertyValue :: p v -> v Source #
Get value of this property.
T Enum
org.apache.tinkerpop.gremlin.structure.T enum.
T is a token to get data b from an Element a.
Instances
| ProjectionLike (Greskell (T s e)) Source # | |
| GraphSONTyped (T a b) Source # | |
| type ProjectionLikeStart (Greskell (T s e)) Source # | |
| type ProjectionLikeEnd (Greskell (T s e)) Source # | |
Typed Key (accessor of a Property)
A property key accessing value b in an Element a. In Gremlin,
it's just a String type.
Instances
| Functor (Key a) Source # | Unsafely convert the value type |
| Eq (Key a b) Source # | |
| Show (Key a b) Source # | |
| IsString (Key a b) Source # | Gremlin String literal as a |
| ToGreskell (Key a b) Source # | Unwrap |
| ProjectionLike (Key s e) Source # | |
| type GreskellReturn (Key a b) Source # | |
| type ProjectionLikeStart (Key s e) Source # | |
| type ProjectionLikeEnd (Key s e) Source # | |
Concrete data types
Concrete data types based on aeson Values.
Element IDs and property values are all Value, because they are
highly polymorphic. They are wrapped with GraphSON, so that you
can inspect gsonType field if present. ElementID and
EdgeVertexID are bare Value type for convenience.
As for properties, you can use PropertyMap and other type-classes
to manipulate them.
If you want to define your own graph structure types, see README.md for detail.
General vertex type you can use for Vertex class, based on
aeson data types.
Constructors
| AVertex | |
Fields
| |
Edge
General edge type you can use for Edge class, based on aeson
data types.
Constructors
| AEdge | |
Fields
| |
VertexProperty
data AVertexProperty v Source #
General vertex property type you can use for VertexProperty, based on aeson data types.
Constructors
| AVertexProperty | |
Instances
| Functor AVertexProperty Source # | |
| Foldable AVertexProperty Source # | |
| Traversable AVertexProperty Source # | |
| Property AVertexProperty Source # | |
| Eq v => Eq (AVertexProperty v) Source # | |
| Show v => Show (AVertexProperty v) Source # | |
| FromJSON v => FromJSON (AVertexProperty v) Source # | |
| GraphSONTyped (AVertexProperty v) Source # | |
| FromJSON v => FromJSONWithKey (AVertexProperty v) Source # | |
| Element (AVertexProperty v) Source # | |
| type ElementID (AVertexProperty v) Source # | |
| type ElementProperty (AVertexProperty v) Source # | |
Property
General simple property type you can use for Property class.
Instances
| Functor AProperty Source # | |
| Foldable AProperty Source # | |
| Traversable AProperty Source # | |
| Property AProperty Source # | |
| Eq v => Eq (AProperty v) Source # | |
| Ord v => Ord (AProperty v) Source # | |
| Show v => Show (AProperty v) Source # | |
| FromJSON v => FromJSON (AProperty v) Source # | Parse Property of GraphSON 1.0. |
| GraphSONTyped (AProperty v) Source # | |
| FromJSON v => FromJSONWithKey (AProperty v) Source # | |
PropertyMap
class PropertyMap m where Source #
Common basic operations supported by maps of properties.
Minimal complete definition
Methods
lookupOne :: Text -> m p v -> Maybe (p v) Source #
Look up a property associated with the given key.
lookupList :: Text -> m p v -> [p v] Source #
Look up all properties associated with the given key.
putProperty :: Property p => p v -> m p v -> m p v Source #
Put a property into the map.
removeProperty :: Text -> m p v -> m p v Source #
Remove all properties associated with the given key.
allProperties :: m p v -> [p v] Source #
Return all properties in the map.
Instances
data PropertyMapSingle p v Source #
A PropertyMap that has a single value per key.
putProperty replaces the old property by the given property.
<> returns the union of the two given property maps. If the two
property maps share some same keys, the value from the left map
wins.
Instances
| PropertyMap PropertyMapSingle Source # | |
| Functor p => Functor (PropertyMapSingle p) Source # | |
| Foldable p => Foldable (PropertyMapSingle p) Source # | |
| Traversable p => Traversable (PropertyMapSingle p) Source # | |
| Eq (p v) => Eq (PropertyMapSingle p v) Source # | |
| Show (p v) => Show (PropertyMapSingle p v) Source # | |
| Semigroup (PropertyMapSingle p v) Source # | |
| Monoid (PropertyMapSingle p v) Source # | |
| (Property p, GraphSONTyped (p v), FromJSON (p v), FromJSONWithKey (p v)) => FromJSON (PropertyMapSingle p v) Source # | |
data PropertyMapList p v Source #
A PropertyMap that can keep more than one values per key.
lookupOne returns the first property associated with the given
key.
putProperty prepends the given property to the property list.
<> returns the union of the two given property maps. If the two
property maps share some same keys, those property lists are
concatenated.
Instances
| PropertyMap PropertyMapList Source # | |
| Functor p => Functor (PropertyMapList p) Source # | |
| Foldable p => Foldable (PropertyMapList p) Source # | |
| Traversable p => Traversable (PropertyMapList p) Source # | |
| Eq (p v) => Eq (PropertyMapList p v) Source # | |
| Show (p v) => Show (PropertyMapList p v) Source # | |
| Semigroup (PropertyMapList p v) Source # | |
| Monoid (PropertyMapList p v) Source # | |
| (Property p, GraphSONTyped (p v), FromJSON (p v), FromJSONWithKey (p v)) => FromJSON (PropertyMapList p v) Source # | |
lookupOneValue :: (PropertyMap m, Property p) => Text -> m p v -> Maybe v Source #
Lookup a property value from a PropertyMap by key.
lookupListValues :: (PropertyMap m, Property p) => Text -> m p v -> [v] Source #
Lookup a list of property values from a PropertyMap by key.
parseOneValue :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser v Source #
Lookup a property Value by the given key, and parse it.
parseListValues :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser [v] Source #
Lookup a list of property values from a PropertyMap by the
given key, and parse them.
parseNonEmptyValues :: (PropertyMap m, Property p, FromJSON v) => Text -> m p (GraphSON Value) -> Parser (NonEmpty v) Source #
Like parseListValues, but this function fails when there is
no property with the given key.
fromProperties :: (PropertyMap m, Property p, Monoid (m p v)) => [p v] -> m p v Source #
Create a PropertyMap from list of Propertys.
Internal use
class FromJSONWithKey a Source #
This typeclass is for internal use.
JSON parser with a property key given from outside.
Minimal complete definition
parseJSONWithKey
Instances
| FromJSON v => FromJSONWithKey (AVertexProperty v) Source # | |
| FromJSON v => FromJSONWithKey (AProperty v) Source # | |