greskell-0.2.2.0: Haskell binding for Gremlin graph query language

MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Greskell.Graph

Contents

Description

This module defines types and functions about TinkerPop graph structure API.

Synopsis

TinkerPop graph structure types

class Element e Source #

org.apache.tinkerpop.gremlin.structure.Element interface in a TinkerPop graph.

Associated Types

type ElementID e Source #

ID type of the Element. This depends on graph database implementation and its settings.

type ElementProperty e :: * -> * Source #

Property type of the Element. It should be of Property class. If you don't care, use AVertexProperty if type e is an Vertex and use AProperty if type e is an Edge or VertexProperty.

Instances
Element AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type ElementID AEdge :: Type Source #

type ElementProperty AEdge :: Type -> Type Source #

Element AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type ElementID AVertex :: Type Source #

type ElementProperty AVertex :: Type -> Type Source #

Element (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

class Element v => Vertex v Source #

org.apache.tinkerpop.gremlin.structure.Vertex interface in a TinkerPop graph.

Instances
Vertex AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

class Element e => Edge e Source #

org.apache.tinkerpop.gremlin.structure.Edge interface in a TinkerPop graph.

Associated Types

type EdgeVertexID e Source #

ID type of the Vertex this edge connects.

Instances
Edge AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type EdgeVertexID AEdge :: Type Source #

class Property p where Source #

org.apache.tinkerpop.gremlin.structure.Property interface in a TinkerPop graph.

Methods

propertyKey :: p v -> Text Source #

Get key of this property.

propertyValue :: p v -> v Source #

Get value of this property.

T Enum

data T a b Source #

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 # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (T s e)) :: Type Source #

type ProjectionLikeEnd (Greskell (T s e)) :: Type Source #

GraphSONTyped (T a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: T a b -> Text #

type ProjectionLikeStart (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (T s e)) = s
type ProjectionLikeEnd (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (T s e)) = e

tId :: Element a => Greskell (T a (ElementID a)) Source #

T.id token.

tKey :: (Element (p v), Property p) => Greskell (T (p v) Text) Source #

T.key token.

tLabel :: Element a => Greskell (T a Text) Source #

T.label token.

tValue :: (Element (p v), Property p) => Greskell (T (p v) v) Source #

T.value token.

Cardinality Enum

data Cardinality Source #

org.apache.tinkerpop.gremlin.structure.VertexProperty.Cardinality enum.

Since: 0.2.0.0

cList :: Greskell Cardinality Source #

list Cardinality.

>>> toGremlin cList
"list"

Since: 0.2.0.0

cSet :: Greskell Cardinality Source #

set Cardinality.

Since: 0.2.0.0

cSingle :: Greskell Cardinality Source #

single Cardinality.

Since: 0.2.0.0

Typed Key (accessor of a Property)

newtype Key a b Source #

A property key accessing value b in an Element a. In Gremlin, it's just a String type.

Constructors

Key 

Fields

Instances
Functor (Key a) Source #

Unsafely convert the value type b.

Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a0 -> b) -> Key a a0 -> Key a b #

(<$) :: a0 -> Key a b -> Key a a0 #

Eq (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: Key a b -> Key a b -> Bool #

(/=) :: Key a b -> Key a b -> Bool #

Show (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

showsPrec :: Int -> Key a b -> ShowS #

show :: Key a b -> String #

showList :: [Key a b] -> ShowS #

IsString (Key a b) Source #

Gremlin String literal as a Key.

Instance details

Defined in Data.Greskell.Graph

Methods

fromString :: String -> Key a b #

ToGreskell (Key a b) Source #

Unwrap Key constructor.

Instance details

Defined in Data.Greskell.Graph

Associated Types

type GreskellReturn (Key a b) :: Type #

Methods

toGreskell :: Key a b -> Greskell (GreskellReturn (Key a b)) #

ProjectionLike (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Key s e) :: Type Source #

type ProjectionLikeEnd (Key s e) :: Type Source #

type GreskellReturn (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

type GreskellReturn (Key a b) = Text
type ProjectionLikeStart (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Key s e) = s
type ProjectionLikeEnd (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Key s e) = e

key :: Text -> Key a b Source #

Create a Key from a literal string.

key-value pair

data KeyValue a where Source #

Pair of Key and its value.

Type a is the type of Element that keeps the KeyValue pair. It drops the type of the value, so that you can construct a heterogeneous list of key-value pairs for a given Element.

Since: 0.2.0.0

Constructors

KeyValue :: Key a b -> Greskell b -> KeyValue a 

(=:) :: Key a b -> Greskell b -> KeyValue a Source #

Constructor operator of KeyValue.

Since: 0.2.0.0

Concrete data types

Concrete data types based on Aeson data types.

Element IDs and property values are all GValue, because they are highly polymorphic. ElementID and EdgeVertexID are GValue, too.

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. Basically you can use FromGraphSON instances of these concrete data types to implement parsers for your own types.

NOTE: In version 0.1.1.0 and before, these conrete data types were based on GraphSON Value. In version 0.2.0.0, this was changed to GValue, so that it can parse nested data structures encoded in GraphSON.

Vertex

data AVertex Source #

General vertex type you can use for Vertex class, based on Aeson data types.

Constructors

AVertex 

Fields

Instances
Eq AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: AVertex -> AVertex -> Bool #

(/=) :: AVertex -> AVertex -> Bool #

Show AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

FromJSON AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AVertex -> Text #

Vertex AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Element AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type ElementID AVertex :: Type Source #

type ElementProperty AVertex :: Type -> Type Source #

type ElementID AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementProperty AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Edge

data AEdge Source #

General edge type you can use for Edge class, based on Aeson data types.

Constructors

AEdge 

Fields

Instances
Eq AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: AEdge -> AEdge -> Bool #

(/=) :: AEdge -> AEdge -> Bool #

Show AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

showsPrec :: Int -> AEdge -> ShowS #

show :: AEdge -> String #

showList :: [AEdge] -> ShowS #

FromJSON AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AEdge -> Text #

Edge AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type EdgeVertexID AEdge :: Type Source #

Element AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type ElementID AEdge :: Type Source #

type ElementProperty AEdge :: Type -> Type Source #

type EdgeVertexID AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementID AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementProperty AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

VertexProperty

data AVertexProperty v Source #

General vertex property type you can use for VertexProperty, based on Aeson data types.

If you are not sure about the type v, just use GValue.

Constructors

AVertexProperty 

Fields

Instances
Functor AVertexProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a -> b) -> AVertexProperty a -> AVertexProperty b #

(<$) :: a -> AVertexProperty b -> AVertexProperty a #

Foldable AVertexProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fold :: Monoid m => AVertexProperty m -> m #

foldMap :: Monoid m => (a -> m) -> AVertexProperty a -> m #

foldr :: (a -> b -> b) -> b -> AVertexProperty a -> b #

foldr' :: (a -> b -> b) -> b -> AVertexProperty a -> b #

foldl :: (b -> a -> b) -> b -> AVertexProperty a -> b #

foldl' :: (b -> a -> b) -> b -> AVertexProperty a -> b #

foldr1 :: (a -> a -> a) -> AVertexProperty a -> a #

foldl1 :: (a -> a -> a) -> AVertexProperty a -> a #

toList :: AVertexProperty a -> [a] #

null :: AVertexProperty a -> Bool #

length :: AVertexProperty a -> Int #

elem :: Eq a => a -> AVertexProperty a -> Bool #

maximum :: Ord a => AVertexProperty a -> a #

minimum :: Ord a => AVertexProperty a -> a #

sum :: Num a => AVertexProperty a -> a #

product :: Num a => AVertexProperty a -> a #

Traversable AVertexProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

traverse :: Applicative f => (a -> f b) -> AVertexProperty a -> f (AVertexProperty b) #

sequenceA :: Applicative f => AVertexProperty (f a) -> f (AVertexProperty a) #

mapM :: Monad m => (a -> m b) -> AVertexProperty a -> m (AVertexProperty b) #

sequence :: Monad m => AVertexProperty (m a) -> m (AVertexProperty a) #

Property AVertexProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Eq v => Eq (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Show v => Show (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON v => FromJSON (AVertexProperty v) Source #

In version 0.1.1.0 and before, the constraint was FromJSON v. This has changed.

Instance details

Defined in Data.Greskell.Graph

FromGraphSON v => FromGraphSON (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON v => FromGraphSONWithKey (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Element (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementID (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementProperty (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Property

data AProperty v Source #

General simple property type you can use for Property class.

If you are not sure about the type v, just use GValue.

Constructors

AProperty 

Fields

Instances
Functor AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a -> b) -> AProperty a -> AProperty b #

(<$) :: a -> AProperty b -> AProperty a #

Foldable AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fold :: Monoid m => AProperty m -> m #

foldMap :: Monoid m => (a -> m) -> AProperty a -> m #

foldr :: (a -> b -> b) -> b -> AProperty a -> b #

foldr' :: (a -> b -> b) -> b -> AProperty a -> b #

foldl :: (b -> a -> b) -> b -> AProperty a -> b #

foldl' :: (b -> a -> b) -> b -> AProperty a -> b #

foldr1 :: (a -> a -> a) -> AProperty a -> a #

foldl1 :: (a -> a -> a) -> AProperty a -> a #

toList :: AProperty a -> [a] #

null :: AProperty a -> Bool #

length :: AProperty a -> Int #

elem :: Eq a => a -> AProperty a -> Bool #

maximum :: Ord a => AProperty a -> a #

minimum :: Ord a => AProperty a -> a #

sum :: Num a => AProperty a -> a #

product :: Num a => AProperty a -> a #

Traversable AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

traverse :: Applicative f => (a -> f b) -> AProperty a -> f (AProperty b) #

sequenceA :: Applicative f => AProperty (f a) -> f (AProperty a) #

mapM :: Monad m => (a -> m b) -> AProperty a -> m (AProperty b) #

sequence :: Monad m => AProperty (m a) -> m (AProperty a) #

Property AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Eq v => Eq (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: AProperty v -> AProperty v -> Bool #

(/=) :: AProperty v -> AProperty v -> Bool #

Ord v => Ord (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Show v => Show (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON v => FromJSON (AProperty v) Source #

Parse Property of GraphSON 1.0.

In version 0.1.1.0 and before, the constraint was FromJSON v. This has changed.

Instance details

Defined in Data.Greskell.Graph

FromGraphSON v => FromGraphSON (AProperty v) Source #

Parse Property of GraphSON 1.0.

Instance details

Defined in Data.Greskell.Graph

GraphSONTyped (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AProperty v -> Text #

FromGraphSON v => FromGraphSONWithKey (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

PropertyMap

class PropertyMap m where Source #

Common basic operations supported by maps of properties.

Minimal complete definition

lookupList, putProperty, removeProperty, allProperties

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.

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 # 
Instance details

Defined in Data.Greskell.Graph

Functor p => Functor (PropertyMapSingle p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a -> b) -> PropertyMapSingle p a -> PropertyMapSingle p b #

(<$) :: a -> PropertyMapSingle p b -> PropertyMapSingle p a #

Foldable p => Foldable (PropertyMapSingle p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fold :: Monoid m => PropertyMapSingle p m -> m #

foldMap :: Monoid m => (a -> m) -> PropertyMapSingle p a -> m #

foldr :: (a -> b -> b) -> b -> PropertyMapSingle p a -> b #

foldr' :: (a -> b -> b) -> b -> PropertyMapSingle p a -> b #

foldl :: (b -> a -> b) -> b -> PropertyMapSingle p a -> b #

foldl' :: (b -> a -> b) -> b -> PropertyMapSingle p a -> b #

foldr1 :: (a -> a -> a) -> PropertyMapSingle p a -> a #

foldl1 :: (a -> a -> a) -> PropertyMapSingle p a -> a #

toList :: PropertyMapSingle p a -> [a] #

null :: PropertyMapSingle p a -> Bool #

length :: PropertyMapSingle p a -> Int #

elem :: Eq a => a -> PropertyMapSingle p a -> Bool #

maximum :: Ord a => PropertyMapSingle p a -> a #

minimum :: Ord a => PropertyMapSingle p a -> a #

sum :: Num a => PropertyMapSingle p a -> a #

product :: Num a => PropertyMapSingle p a -> a #

Traversable p => Traversable (PropertyMapSingle p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

traverse :: Applicative f => (a -> f b) -> PropertyMapSingle p a -> f (PropertyMapSingle p b) #

sequenceA :: Applicative f => PropertyMapSingle p (f a) -> f (PropertyMapSingle p a) #

mapM :: Monad m => (a -> m b) -> PropertyMapSingle p a -> m (PropertyMapSingle p b) #

sequence :: Monad m => PropertyMapSingle p (m a) -> m (PropertyMapSingle p a) #

Eq (p v) => Eq (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Show (p v) => Show (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Semigroup (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Monoid (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph

(Property p, GraphSONTyped (p v), FromGraphSON (p v), FromGraphSONWithKey (p v)) => FromJSON (PropertyMapSingle p v) Source #

In version 0.1.1.0 and before, the constraint was FromJSON v. This has changed.

Instance details

Defined in Data.Greskell.Graph

(Property p, GraphSONTyped (p v), FromGraphSON (p v), FromGraphSONWithKey (p v)) => FromGraphSON (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph

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 # 
Instance details

Defined in Data.Greskell.Graph

Functor p => Functor (PropertyMapList p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a -> b) -> PropertyMapList p a -> PropertyMapList p b #

(<$) :: a -> PropertyMapList p b -> PropertyMapList p a #

Foldable p => Foldable (PropertyMapList p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fold :: Monoid m => PropertyMapList p m -> m #

foldMap :: Monoid m => (a -> m) -> PropertyMapList p a -> m #

foldr :: (a -> b -> b) -> b -> PropertyMapList p a -> b #

foldr' :: (a -> b -> b) -> b -> PropertyMapList p a -> b #

foldl :: (b -> a -> b) -> b -> PropertyMapList p a -> b #

foldl' :: (b -> a -> b) -> b -> PropertyMapList p a -> b #

foldr1 :: (a -> a -> a) -> PropertyMapList p a -> a #

foldl1 :: (a -> a -> a) -> PropertyMapList p a -> a #

toList :: PropertyMapList p a -> [a] #

null :: PropertyMapList p a -> Bool #

length :: PropertyMapList p a -> Int #

elem :: Eq a => a -> PropertyMapList p a -> Bool #

maximum :: Ord a => PropertyMapList p a -> a #

minimum :: Ord a => PropertyMapList p a -> a #

sum :: Num a => PropertyMapList p a -> a #

product :: Num a => PropertyMapList p a -> a #

Traversable p => Traversable (PropertyMapList p) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

traverse :: Applicative f => (a -> f b) -> PropertyMapList p a -> f (PropertyMapList p b) #

sequenceA :: Applicative f => PropertyMapList p (f a) -> f (PropertyMapList p a) #

mapM :: Monad m => (a -> m b) -> PropertyMapList p a -> m (PropertyMapList p b) #

sequence :: Monad m => PropertyMapList p (m a) -> m (PropertyMapList p a) #

Eq (p v) => Eq (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Show (p v) => Show (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Semigroup (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph

Monoid (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph

(Property p, GraphSONTyped (p v), FromGraphSON (p v), FromGraphSONWithKey (p v)) => FromJSON (PropertyMapList p v) Source #

In version 0.1.1.0 and before, the constraint was FromJSON v. This has changed.

Instance details

Defined in Data.Greskell.Graph

(Property p, GraphSONTyped (p v), FromGraphSON (p v), FromGraphSONWithKey (p v)) => FromGraphSON (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph

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, FromGraphSON v) => Text -> m p GValue -> Parser v Source #

Lookup a property GValue by the given key, and parse it.

In version 0.1.1.0 and before, this function took an argument m p (GraphSON Value). This has changed, because property types for AVertex etc have changed.

parseListValues :: (PropertyMap m, Property p, FromGraphSON v) => Text -> m p GValue -> Parser [v] Source #

Lookup a list of property values from a PropertyMap by the given key, and parse them.

In version 0.1.1.0 and before, this function took an argument m p (GraphSON Value). This has changed, because property types for AVertex etc have changed.

parseNonEmptyValues :: (PropertyMap m, Property p, FromGraphSON v) => Text -> m p GValue -> Parser (NonEmpty v) Source #

Like parseListValues, but this function fails when there is no property with the given key.

In version 0.1.1.0 and before, this function took an argument m p (GraphSON Value). This has changed, because property types for AVertex etc have changed.

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 FromGraphSONWithKey a Source #

This typeclass is for internal use.

GraphSON parser with a property key given from outside.

Since: 0.2.0.0

Minimal complete definition

parseGraphSONWithKey