greskell-core-0.1.1.0: Haskell binding for Gremlin graph query language - core data types and tools

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

Data.Greskell.GraphSON

Contents

Description

 

Synopsis

Type

data GraphSON v Source #

Wrapper for "typed JSON object" introduced in GraphSON version 2. See http://tinkerpop.apache.org/docs/current/dev/io/#graphson

This data type is useful for encoding/decoding GraphSON text.

>>> Aeson.decode "1000" :: Maybe (GraphSON Int32)
Just (GraphSON {gsonType = Nothing, gsonValue = 1000})
>>> Aeson.decode "{\"@type\": \"g:Int32\", \"@value\": 1000}" :: Maybe (GraphSON Int32)
Just (GraphSON {gsonType = Just "g:Int32", gsonValue = 1000})

Constructors

GraphSON 

Fields

Instances

Functor GraphSON Source # 

Methods

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

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

Foldable GraphSON Source # 

Methods

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

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

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

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

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

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

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

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

toList :: GraphSON a -> [a] #

null :: GraphSON a -> Bool #

length :: GraphSON a -> Int #

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

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

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

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

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

Traversable GraphSON Source # 

Methods

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

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

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

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

Eq v => Eq (GraphSON v) Source # 

Methods

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

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

Ord v => Ord (GraphSON v) Source # 

Methods

compare :: GraphSON v -> GraphSON v -> Ordering #

(<) :: GraphSON v -> GraphSON v -> Bool #

(<=) :: GraphSON v -> GraphSON v -> Bool #

(>) :: GraphSON v -> GraphSON v -> Bool #

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

max :: GraphSON v -> GraphSON v -> GraphSON v #

min :: GraphSON v -> GraphSON v -> GraphSON v #

Show v => Show (GraphSON v) Source # 

Methods

showsPrec :: Int -> GraphSON v -> ShowS #

show :: GraphSON v -> String #

showList :: [GraphSON v] -> ShowS #

ToJSON v => ToJSON (GraphSON v) Source #

If gsonType is Just, the GraphSON is encoded as a typed JSON object. If gsonType is Nothing, the gsonValue is directly encoded.

FromJSON v => FromJSON (GraphSON v) Source #

If the given Value is a typed JSON object, gsonType field of the result is Just. Otherwise, the given Value is directly parsed into gsonValue, and gsonType is Nothing.

class GraphSONTyped a where Source #

Types that have an intrinsic type ID for gsonType field.

Minimal complete definition

gsonTypeFor

Methods

gsonTypeFor :: a -> Text Source #

Type ID for gsonType.

Instances

GraphSONTyped Char Source # 
GraphSONTyped Double Source # 
GraphSONTyped Float Source # 
GraphSONTyped Int8 Source #

Map to "gx:Byte". Note that Java's Byte is signed.

GraphSONTyped Int16 Source # 
GraphSONTyped Int32 Source # 
GraphSONTyped Int64 Source # 
GraphSONTyped Scientific Source #

Map to "g:Double".

GraphSONTyped [a] Source # 

Methods

gsonTypeFor :: [a] -> Text Source #

GraphSONTyped (HashSet a) Source # 
GraphSONTyped (HashMap k v) Source #

Note that Lazy HashMap and Strict HashMap are the same data type.

Methods

gsonTypeFor :: HashMap k v -> Text Source #

Constructors

nonTypedGraphSON :: v -> GraphSON v Source #

Create a GraphSON without gsonType.

>>> nonTypedGraphSON (10 :: Int)
GraphSON {gsonType = Nothing, gsonValue = 10}

typedGraphSON :: GraphSONTyped v => v -> GraphSON v Source #

Create a GraphSON with its type ID.

>>> typedGraphSON (10 :: Int32)
GraphSON {gsonType = Just "g:Int32", gsonValue = 10}

typedGraphSON' :: Text -> v -> GraphSON v Source #

Create a GraphSON with the given type ID.

>>> typedGraphSON' "g:Int32" (10 :: Int)
GraphSON {gsonType = Just "g:Int32", gsonValue = 10}

Parser support

parseTypedGraphSON :: (GraphSONTyped v, FromJSON v) => Value -> Parser (GraphSON v) Source #

Parse GraphSON v, but it checks gsonType. If gsonType is Nothing or it's not equal to gsonTypeFor, the Parser fails.