greskell-0.1.0.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

class Element v => Vertex v Source #

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

Instances

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 # 

Associated Types

type EdgeVertexID AEdge :: * Source #

class Property p where Source #

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

Minimal complete definition

propertyKey, propertyValue

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 # 

Associated Types

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

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

GraphSONTyped (T a b) Source # 

Methods

gsonTypeFor :: T a b -> Text #

type ProjectionLikeStart (Greskell (T s e)) Source # 
type ProjectionLikeStart (Greskell (T s e)) = s
type ProjectionLikeEnd (Greskell (T s e)) Source # 
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.

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.

Methods

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

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

Eq (Key a b) Source # 

Methods

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

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

Show (Key a b) Source # 

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.

Methods

fromString :: String -> Key a b #

ToGreskell (Key a b) Source #

Unwrap Key constructor.

Associated Types

type GreskellReturn (Key a b) :: * #

Methods

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

ProjectionLike (Key s e) Source # 

Associated Types

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

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

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

key :: Text -> Key a b Source #

Create a Key from a literal string.

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.

data AVertex Source #

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

Constructors

AVertex 

Fields

Edge

data AEdge Source #

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 

Fields

Instances

Functor AVertexProperty Source # 

Methods

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

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

Foldable AVertexProperty Source # 

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 # 

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

Associated Types

type ElementID (AVertexProperty v) :: * Source #

type ElementProperty (AVertexProperty v) :: * -> * Source #

type ElementID (AVertexProperty v) Source # 
type ElementProperty (AVertexProperty v) Source # 

Property

data AProperty v Source #

General simple property type you can use for Property class.

Constructors

AProperty 

Fields

Instances

Functor AProperty Source # 

Methods

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

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

Foldable AProperty Source # 

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 # 

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 # 
Eq v => Eq (AProperty v) Source # 

Methods

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

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

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 # 

Methods

gsonTypeFor :: AProperty v -> Text #

FromJSON v => FromJSONWithKey (AProperty v) Source # 

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 # 
Functor p => Functor (PropertyMapSingle p) Source # 

Methods

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

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

Foldable p => Foldable (PropertyMapSingle p) Source # 

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 # 

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 # 
Show (p v) => Show (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 # 

Methods

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

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

Foldable p => Foldable (PropertyMapList p) Source # 

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 # 

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 # 
Show (p v) => Show (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