Maintainer | Toshio Ito <debug.ito@gmail.com> |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data GraphSON v = GraphSON {}
- class GraphSONTyped a where
- gsonTypeFor :: a -> Text
- nonTypedGraphSON :: v -> GraphSON v
- typedGraphSON :: GraphSONTyped v => v -> GraphSON v
- typedGraphSON' :: Text -> v -> GraphSON v
- parseTypedGraphSON :: (GraphSONTyped v, FromJSON v) => Value -> Parser (GraphSON v)
- data GValue
- data GValueBody
- nonTypedGValue :: GValueBody -> GValue
- typedGValue' :: Text -> GValueBody -> GValue
- class FromGraphSON a where
- parseGraphSON :: GValue -> Parser a
- data Parser a
- parseEither :: FromGraphSON a => GValue -> Either String a
- parseUnwrapAll :: FromJSON a => GValue -> Parser a
- parseUnwrapList :: (IsList a, i ~ Item a, FromGraphSON i) => GValue -> Parser a
- (.:) :: FromGraphSON a => HashMap Text GValue -> Text -> Parser a
- parseJSONViaGValue :: FromGraphSON a => Value -> Parser a
GraphSON
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.
Instances
Functor GraphSON Source # | |
Foldable GraphSON Source # | |
Defined in Data.Greskell.GraphSON.Core 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 # elem :: Eq a => a -> GraphSON a -> Bool # maximum :: Ord a => GraphSON a -> a # minimum :: Ord a => GraphSON a -> a # | |
Traversable GraphSON Source # | |
Eq v => Eq (GraphSON v) Source # | |
Ord v => Ord (GraphSON v) Source # | |
Defined in Data.Greskell.GraphSON.Core | |
Show v => Show (GraphSON v) Source # | |
Generic (GraphSON v) Source # | |
Hashable v => Hashable (GraphSON v) Source # | Since: 0.1.2.0 |
Defined in Data.Greskell.GraphSON.Core | |
ToJSON v => ToJSON (GraphSON v) Source # | If |
Defined in Data.Greskell.GraphSON.Core | |
FromJSON v => FromJSON (GraphSON v) Source # | If the given |
type Rep (GraphSON v) Source # | |
Defined in Data.Greskell.GraphSON.Core type Rep (GraphSON v) = D1 (MetaData "GraphSON" "Data.Greskell.GraphSON.Core" "greskell-core-0.1.2.7-GElgchiRe82I0theVrO8jf" 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.
gsonTypeFor :: a -> Text Source #
Type ID for gsonType
.
Instances
constructors
nonTypedGraphSON :: v -> GraphSON v Source #
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
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 # | |
Show GValue Source # | |
Generic GValue Source # | |
Hashable GValue Source # | |
Defined in Data.Greskell.GraphSON.GValue | |
ToJSON GValue Source # | Reconstruct |
Defined in Data.Greskell.GraphSON.GValue | |
FromJSON GValue Source # | Parse |
FromGraphSON GValue Source # | |
Defined in Data.Greskell.GraphSON | |
type Rep GValue Source # | |
Defined in Data.Greskell.GraphSON.GValue type Rep GValue = D1 (MetaData "GValue" "Data.Greskell.GraphSON.GValue" "greskell-core-0.1.2.7-GElgchiRe82I0theVrO8jf" True) (C1 (MetaCons "GValue" PrefixI True) (S1 (MetaSel (Just "unGValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (GraphSON GValueBody)))) |
data GValueBody Source #
GObject !(HashMap Text GValue) | |
GArray !(Vector GValue) | |
GString !Text | |
GNumber !Scientific | |
GBool !Bool | |
GNull |
Instances
constructors
nonTypedGValue :: GValueBody -> GValue Source #
Create a GValue
without "@type" field.
Since: 0.1.2.0
:: 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
andText
): useparseUnwrapAll
. - List-like types (e.g.
[]
,Vector
andSet
): useparseUnwrapList
. - Map-like types (e.g.
HashMap
andMap
): parse intoGMap
first, then unwrap theGMap
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
parseGraphSON :: GValue -> Parser a Source #
Instances
parser support
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.
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