greskell-1.1.0.0: Haskell binding for Gremlin graph query language

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

Data.Greskell.Graph.PropertyMap

Contents

Description

Deprecated: Use PMap instead

PropertyMap was used in greskell prior than 1.0.0.0, but is now deprecated. Use Data.Greskell.PMap instead.

Synopsis

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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

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.PropertyMap

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.PropertyMap

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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

Semigroup (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph.PropertyMap

Monoid (PropertyMapSingle p v) Source # 
Instance details

Defined in Data.Greskell.Graph.PropertyMap

(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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

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.PropertyMap

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.PropertyMap

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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

Semigroup (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph.PropertyMap

Monoid (PropertyMapList p v) Source # 
Instance details

Defined in Data.Greskell.Graph.PropertyMap

(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.PropertyMap

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

Defined in Data.Greskell.Graph.PropertyMap

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

Re-exports

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

data AVertexProperty v Source #

General vertex property type you can use for VertexProperty.

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

Constructors

AVertexProperty 

Fields

Instances
Functor AVertexProperty Source #

Map the property value.

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 #

Traverse the property value.

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

Element (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

ElementData (AVertexProperty v) Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

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

Defined in Data.Greskell.Graph.PropertyMap

type ElementProperty (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementPropertyContainer (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph