greskell-core-0.1.3.2: 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 # 
Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

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

Foldable GraphSON Source # 
Instance details

Defined in Data.Greskell.GraphSON.Core

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

Defined in Data.Greskell.GraphSON.Core

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

Defined in Data.Greskell.GraphSON.Core

Methods

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

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

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

Defined in Data.Greskell.GraphSON.Core

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

Defined in Data.Greskell.GraphSON.Core

Methods

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

show :: GraphSON v -> String #

showList :: [GraphSON v] -> ShowS #

Generic (GraphSON v) Source # 
Instance details

Defined in Data.Greskell.GraphSON.Core

Associated Types

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

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

Instance details

Defined in Data.Greskell.GraphSON.Core

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.

Instance details

Defined in Data.Greskell.GraphSON.Core

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.

Instance details

Defined in Data.Greskell.GraphSON.Core

type Rep (GraphSON v) Source # 
Instance details

Defined in Data.Greskell.GraphSON.Core

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

class GraphSONTyped a where Source #

Types that have an intrinsic type ID for gsonType field.

Methods

gsonTypeFor :: a -> Text Source #

Type ID for gsonType.

Instances
GraphSONTyped Char Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Double Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Float Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Int8 Source #

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

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Int16 Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Int32 Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Int64 Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Scientific Source #

Map to "g:Double".

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped IntSet Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped [a] Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: [a] -> Text Source #

GraphSONTyped (IntMap v) Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: IntMap v -> Text Source #

GraphSONTyped (Seq a) Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Seq a -> Text Source #

GraphSONTyped (Set a) Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Set a -> Text Source #

GraphSONTyped (HashSet a) Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped (Vector a) Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Vector a -> Text Source #

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

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Either a b -> Text Source #

GraphSONTyped (HashMap k v) Source # 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: HashMap k v -> Text Source #

GraphSONTyped (Map k v) Source #

Since: 0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Map k v -> Text Source #

GraphSONTyped (GMapEntry k v) Source #

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: GMapEntry k v -> Text Source #

GraphSONTyped (GMap c k v) Source #

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

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

GraphSONTyped (FlattenedMap c k v) Source #

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

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

Defined in Data.Greskell.GraphSON.GValue

Methods

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

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

Show GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Generic GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Associated Types

type Rep GValue :: Type -> Type #

Methods

from :: GValue -> Rep GValue x #

to :: Rep GValue x -> GValue #

Hashable GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Methods

hashWithSalt :: Int -> GValue -> Int #

hash :: GValue -> Int #

ToJSON GValue Source #

Reconstruct Value from GValue. It preserves all GraphSON wrappers.

Instance details

Defined in Data.Greskell.GraphSON.GValue

FromJSON GValue Source #

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

Instance details

Defined in Data.Greskell.GraphSON.GValue

FromGraphSON GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON

type Rep GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

type Rep GValue = D1 (MetaData "GValue" "Data.Greskell.GraphSON.GValue" "greskell-core-0.1.3.2-GBkgJ5r6sEBK6lsdDT2qda" True) (C1 (MetaCons "GValue" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Show GValueBody Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Generic GValueBody Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Associated Types

type Rep GValueBody :: Type -> Type #

Hashable GValueBody Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

ToJSON GValueBody Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

type Rep GValueBody Source # 
Instance details

Defined in Data.Greskell.GraphSON.GValue

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.
  • Trivial wrapper types (e.g. Identity): just parse the item inside.
  • 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

Instances
FromGraphSON Bool Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Double Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Float Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int8 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int16 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int32 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int64 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Integer Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Natural Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word8 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word16 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word32 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word64 Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON () Source #

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

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Scientific Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Text Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Value Source #

Call unwrapAll to remove all GraphSON wrappers.

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Text Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON All Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Any Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON IntSet Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON UUID Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON GValue Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON [a] Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Maybe a) Source #

Parse GNull into Nothing.

Instance details

Defined in Data.Greskell.GraphSON

(FromJSON a, Integral a) => FromGraphSON (Ratio a) Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Min a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Max a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (First a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Last a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (WrappedMonoid a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Option a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Identity a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (First a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Last a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Dual a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Sum a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Product a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (NonEmpty a) Source #

Since: 0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

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

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Seq a) Source # 
Instance details

Defined in Data.Greskell.GraphSON

(FromGraphSON a, Ord a) => FromGraphSON (Set a) Source # 
Instance details

Defined in Data.Greskell.GraphSON

(FromGraphSON a, Eq a, Hashable a) => FromGraphSON (HashSet a) Source # 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Vector a) Source # 
Instance details

Defined in Data.Greskell.GraphSON

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

Try Left, then Right.

Instance details

Defined in Data.Greskell.GraphSON

(FromGraphSON v, Eq k, Hashable k, FromJSONKey k, FromGraphSON k) => FromGraphSON (HashMap k v) Source # 
Instance details

Defined in Data.Greskell.GraphSON

(FromGraphSON v, Ord k, FromJSONKey k, FromGraphSON k) => FromGraphSON (Map k v) Source # 
Instance details

Defined in Data.Greskell.GraphSON

Methods

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

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

Use parseToGMapEntry.

Instance details

Defined in Data.Greskell.GraphSON

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

Instance details

Defined in Data.Greskell.GraphSON

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.

Instance details

Defined in Data.Greskell.GraphSON

parser support

data Parser a #

A JSON parser. N.B. This might not fit your usual understanding of "parser". Instead you might like to think of Parser as a "parse result", i.e. a parser to which the input has already been applied.

Instances
Monad Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

MonadFail Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fail :: String -> Parser a #

Applicative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

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

Defined in Data.Aeson.Types.Internal

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mzero :: Parser a #

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

Semigroup (Parser a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

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

Monoid (Parser a) 
Instance details

Defined in Data.Aeson.Types.Internal

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