greskell-core-0.1.2.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

GraphSON

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})

Note that encoding of the "g:Map" type is inconsistent between GraphSON v1 and v2, v3. To handle the encoding, use Data.Greskell.GMap.

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 #

Generic (GraphSON v) Source # 

Associated Types

type Rep (GraphSON v) :: * -> * #

Methods

from :: GraphSON v -> Rep (GraphSON v) x #

to :: Rep (GraphSON v) x -> GraphSON v #

Hashable v => Hashable (GraphSON v) Source #

Since: 0.1.2.0

Methods

hashWithSalt :: Int -> GraphSON v -> Int #

hash :: GraphSON v -> Int #

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.

type Rep (GraphSON v) Source # 
type Rep (GraphSON v) = D1 * (MetaData "GraphSON" "Data.Greskell.GraphSON.Core" "greskell-core-0.1.2.0-HrobBCKEhQy2PrcN852fWr" False) (C1 * (MetaCons "GraphSON" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "gsonType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "gsonValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * v))))

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

Since: 0.1.2.0

GraphSONTyped [a] Source # 

Methods

gsonTypeFor :: [a] -> Text Source #

GraphSONTyped (IntMap v) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: IntMap v -> Text Source #

GraphSONTyped (Seq a) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: Seq a -> Text Source #

GraphSONTyped (Set a) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: Set a -> Text Source #

GraphSONTyped (HashSet a) Source # 
GraphSONTyped (Vector a) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: Vector a -> Text Source #

(GraphSONTyped a, GraphSONTyped b) => GraphSONTyped (Either a b) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: Either a b -> Text Source #

GraphSONTyped (HashMap k v) Source # 

Methods

gsonTypeFor :: HashMap k v -> Text Source #

GraphSONTyped (Map k v) Source #

Since: 0.1.2.0

Methods

gsonTypeFor :: Map k v -> Text Source #

GraphSONTyped (GMapEntry k v) Source #

Map to "g:Map".

Methods

gsonTypeFor :: GMapEntry k v -> Text Source #

GraphSONTyped (GMap c k v) Source #

Map to "g:Map".

Methods

gsonTypeFor :: GMap c k v -> Text Source #

GraphSONTyped (FlattenedMap c k v) Source #

Map to "g:Map".

Methods

gsonTypeFor :: FlattenedMap c 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.

GValue

data GValue Source #

An Aeson Value wrapped in GraphSON wrapper type. Basically this type is the Haskell representaiton of a GraphSON-encoded document.

This type is used to parse GraphSON documents. See also FromGraphSON class.

Since: 0.1.2.0

Instances

Eq GValue Source # 

Methods

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

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

Show GValue Source # 
Generic GValue Source # 

Associated Types

type Rep GValue :: * -> * #

Methods

from :: GValue -> Rep GValue x #

to :: Rep GValue x -> GValue #

Hashable GValue Source # 

Methods

hashWithSalt :: Int -> GValue -> Int #

hash :: GValue -> Int #

ToJSON GValue Source #

Reconstruct Value from GValue. It preserves all GraphSON wrappers.

FromJSON GValue Source #

Parse GraphSON wrappers recursively in Value, making it into GValue.

FromGraphSON GValue Source # 
type Rep GValue Source # 
type Rep GValue = D1 * (MetaData "GValue" "Data.Greskell.GraphSON.GValue" "greskell-core-0.1.2.0-HrobBCKEhQy2PrcN852fWr" True) (C1 * (MetaCons "GValue" PrefixI True) (S1 * (MetaSel (Just Symbol "unGValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (GraphSON GValueBody))))

data GValueBody Source #

GValue without the top-level GraphSON wrapper.

Since: 0.1.2.0

Instances

Eq GValueBody Source # 
Show GValueBody Source # 
Generic GValueBody Source # 

Associated Types

type Rep GValueBody :: * -> * #

Hashable GValueBody Source # 
ToJSON GValueBody Source # 
type Rep GValueBody Source # 

constructors

nonTypedGValue :: GValueBody -> GValue Source #

Create a GValue without "@type" field.

Since: 0.1.2.0

typedGValue' Source #

Arguments

:: Text

"@type" field.

-> GValueBody 
-> GValue 

Create a GValue with the given "@type" field.

Since: 0.1.2.0

FromGraphSON

class FromGraphSON a where Source #

Types that can be constructed from GValue. This is analogous to FromJSON class.

Instances of basic types are implemented based on the following rule.

  • Simple scalar types (e.g. Int and Text): use parseUnwrapAll.
  • List-like types (e.g. [], Vector and Set): use parseUnwrapList.
  • Map-like types (e.g. HashMap and Map): parse into GMap first, then unwrap the GMap wrapper. That way, all versions of GraphSON formats are handled properly.
  • Other types: see the individual instance documentation.

Note that Char does not have FromGraphSON instance. This is intentional. As stated in the document of AsIterator, using String in greskell is an error in most cases. To prevent you from using String, Char (and thus String) don't have FromGraphSON instances.

Since: 0.1.2.0

Minimal complete definition

parseGraphSON

Instances

FromGraphSON Bool Source # 
FromGraphSON Double Source # 
FromGraphSON Float Source # 
FromGraphSON Int Source # 
FromGraphSON Int8 Source # 
FromGraphSON Int16 Source # 
FromGraphSON Int32 Source # 
FromGraphSON Int64 Source # 
FromGraphSON Integer Source # 
FromGraphSON Natural Source # 
FromGraphSON Word Source # 
FromGraphSON Word8 Source # 
FromGraphSON Word16 Source # 
FromGraphSON Word32 Source # 
FromGraphSON Word64 Source # 
FromGraphSON () Source #

For any input GValue, parseGraphSON returns (). For example, you can use it to ignore data you get from the Gremlin server.

FromGraphSON Scientific Source # 
FromGraphSON Text Source # 
FromGraphSON Value Source #

Call unwrapAll to remove all GraphSON wrappers.

FromGraphSON Text Source # 
FromGraphSON IntSet Source # 
FromGraphSON UUID Source # 
FromGraphSON GValue Source # 
FromGraphSON a => FromGraphSON [a] Source # 
FromGraphSON a => FromGraphSON (Maybe a) Source #

Parse GNull into Nothing.

(FromJSON a, Integral a) => FromGraphSON (Ratio a) Source # 
FromGraphSON v => FromGraphSON (IntMap v) Source # 
FromGraphSON a => FromGraphSON (Seq a) Source # 
(FromGraphSON a, Ord a) => FromGraphSON (Set a) Source # 
(FromGraphSON a, Eq a, Hashable a) => FromGraphSON (HashSet a) Source # 
FromGraphSON a => FromGraphSON (Vector a) Source # 
(FromGraphSON a, FromGraphSON b) => FromGraphSON (Either a b) Source #

Try Left, then Right.

(FromGraphSON v, Eq k, Hashable k, FromJSONKey k, FromGraphSON k) => FromGraphSON (HashMap k v) Source # 
(FromGraphSON v, Ord k, FromJSONKey k, FromGraphSON k) => FromGraphSON (Map k v) Source # 

Methods

parseGraphSON :: GValue -> Parser (Map k v) Source #

(FromGraphSON k, FromGraphSON v, FromJSONKey k) => FromGraphSON (GMapEntry k v) Source #

Use parseToGMapEntry.

(FromGraphSON k, FromGraphSON v, IsList (c k v), (~) * (Item (c k v)) (k, v), Traversable (c k), FromJSON (c k GValue)) => FromGraphSON (GMap c k v) Source #

Use parseToGMap.

Methods

parseGraphSON :: GValue -> Parser (GMap c k v) Source #

(FromGraphSON k, FromGraphSON v, IsList (c k v), (~) * (Item (c k v)) (k, v)) => FromGraphSON (FlattenedMap c k v) Source #

Use parseToFlattenedMap.

parser support

data Parser a :: * -> * #

A JSON parser.

Instances

Monad Parser 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser 

Methods

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

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

MonadFail Parser 

Methods

fail :: String -> Parser a #

Applicative Parser 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Semigroup (Parser a) 

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

Monoid (Parser a) 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

parseEither :: FromGraphSON a => GValue -> Either String a Source #

Parse GValue into FromGraphSON.

Since: 0.1.2.0

parseUnwrapAll :: FromJSON a => GValue -> Parser a Source #

Unwrap the given GValue with unwrapAll, and just parse the result with parseJSON.

Useful to implement FromGraphSON instances for scalar types.

Since: 0.1.2.0

parseUnwrapList :: (IsList a, i ~ Item a, FromGraphSON i) => GValue -> Parser a Source #

Extract GArray from the given GValue, parse the items in the array, and gather them by fromList.

Useful to implement FromGraphSON instances for IsList types.

Since: 0.1.2.0

(.:) :: FromGraphSON a => HashMap Text GValue -> Text -> Parser a Source #

Like Aeson's .:, but for FromGraphSON.

Since: 0.1.2.0

parseJSONViaGValue :: FromGraphSON a => Value -> Parser a Source #

Implementation of parseJSON based on parseGraphSON. The input Value is first converted to GValue, and it's parsed to the output type.

Since: 0.1.2.0