greskell-2.0.2.0: Haskell binding for Gremlin graph query language
MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Greskell

Description

Data.Greskell is a Haskell support to use the Gremlin graph query language. For more information, see project README.

This module re-exports most modules from greskell and greskell-core packages. The following modules are excluded from re-export:

Synopsis

Documentation

unsafeMethodCall #

Arguments

:: Greskell a

target object

-> Text

method name

-> [Text]

arguments

-> Greskell b

return value of the method call

Unsafely create a Greskell that calls the given object method call with the given target and arguments.

unsafeFunCall #

Arguments

:: Text

function name

-> [Text]

arguments

-> Greskell a

return value of the function call

Unsafely create a Greskell that calls the given function with the given arguments.

toGremlinLazy :: ToGreskell a => a -> Text #

Same as toGremlin except that this returns lazy Text.

toGremlin :: ToGreskell a => a -> Text #

Create a readable Gremlin script from Greskell.

gvalueInt :: Integral a => a -> Greskell GValue #

Integer literal as GValue type.

Since: greskell-core-0.1.2.0

gvalue :: Value -> Greskell GValue #

Value literal as GValue type.

Since: greskell-core-0.1.2.0

valueInt :: Integral a => a -> Greskell Value #

Integer literal as Value type.

Since: greskell-core-0.1.2.0

value :: Value -> Greskell Value #

Aeson Value literal.

Note that Number does not distinguish integers from floating-point numbers, so value function may format an integer as a floating-point number. To ensure formatting as integers, use valueInt.

number :: Scientific -> Greskell Scientific #

Arbitrary precision number literal, like "123e8".

single :: Greskell a -> Greskell [a] #

Make a list with a single object. Useful to prevent the Gremlin Server from automatically iterating the result object.

list :: [Greskell a] -> Greskell [a] #

List literal.

false :: Greskell Bool #

Boolean false literal.

true :: Greskell Bool #

Boolean true literal.

string :: Text -> Greskell Text #

Create a String literal in Gremlin script. The content is automatically escaped.

unsafeGreskellLazy #

Arguments

:: Text

Gremlin script

-> Greskell a 

Same as unsafeGreskell, but it takes lazy Text.

unsafeGreskell #

Arguments

:: Text

Gremlin script

-> Greskell a 

Unsafely create a Greskell of arbitrary type. The given Gremlin script is printed as-is.

data Greskell a #

Gremlin expression of type a.

Greskell is essentially just a piece of Gremlin script with a phantom type. The type a represents the type of data that the script is supposed to evaluate to.

Eq and Ord instances compare Gremlin scripts, NOT the values they evaluate to.

Instances

Instances details
Functor Greskell

Unsafely convert the phantom type.

Instance details

Defined in Data.Greskell.Greskell

Methods

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

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

IsString a => IsString (Greskell a)

Same as string except for the input and output type.

Instance details

Defined in Data.Greskell.Greskell

Methods

fromString :: String -> Greskell a #

IsString a => Monoid (Greskell a)

Monoidal operations on Greskell assumes String operations in Gremlin. mempty is the empty String, and mappend is String concatenation.

Instance details

Defined in Data.Greskell.Greskell

Methods

mempty :: Greskell a #

mappend :: Greskell a -> Greskell a -> Greskell a #

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

IsString a => Semigroup (Greskell a)

Semigroup operator <> on Greskell assumes String concatenation on Gremlin.

Instance details

Defined in Data.Greskell.Greskell

Methods

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

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

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

Num a => Num (Greskell a)

Integer literals and numeric operation in Gremlin

Instance details

Defined in Data.Greskell.Greskell

Fractional a => Fractional (Greskell a)

Floating-point number literals and numeric operation in Gremlin

Instance details

Defined in Data.Greskell.Greskell

Show (Greskell a) 
Instance details

Defined in Data.Greskell.Greskell

Methods

showsPrec :: Int -> Greskell a -> ShowS #

show :: Greskell a -> String #

showList :: [Greskell a] -> ShowS #

Eq (Greskell a) 
Instance details

Defined in Data.Greskell.Greskell

Methods

(==) :: Greskell a -> Greskell a -> Bool #

(/=) :: Greskell a -> Greskell a -> Bool #

Ord (Greskell a) 
Instance details

Defined in Data.Greskell.Greskell

Methods

compare :: Greskell a -> Greskell a -> Ordering #

(<) :: Greskell a -> Greskell a -> Bool #

(<=) :: Greskell a -> Greskell a -> Bool #

(>) :: Greskell a -> Greskell a -> Bool #

(>=) :: Greskell a -> Greskell a -> Bool #

max :: Greskell a -> Greskell a -> Greskell a #

min :: Greskell a -> Greskell a -> Greskell a #

ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (T s e)) Source #

type ProjectionLikeEnd (Greskell (T s e)) Source #

ProjectionLike (Greskell (s -> e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (s -> e)) Source #

type ProjectionLikeEnd (Greskell (s -> e)) Source #

ToGreskell (Greskell a)

It's just id.

Instance details

Defined in Data.Greskell.Greskell

Associated Types

type GreskellReturn (Greskell a) #

type ProjectionLikeEnd (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (T s e)) = e
type ProjectionLikeEnd (Greskell (s -> e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (s -> e)) = e
type ProjectionLikeStart (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (T s e)) = s
type ProjectionLikeStart (Greskell (s -> e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (s -> e)) = s
type GreskellReturn (Greskell a) 
Instance details

Defined in Data.Greskell.Greskell

type family GreskellReturn a #

type of return value by Greskell.

Instances

Instances details
type GreskellReturn RepeatLabel Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

type GreskellReturn (Greskell a) 
Instance details

Defined in Data.Greskell.Greskell

type GreskellReturn (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

type GreskellReturn (Key a b) = Text
type GreskellReturn (GTraversal c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (Walk c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (Walk c s e) = GraphTraversal c s e

class ToGreskell a where #

Something that can convert to Greskell.

Associated Types

type GreskellReturn a #

type of return value by Greskell.

Methods

toGreskell :: a -> Greskell (GreskellReturn a) #

Instances

Instances details
ToGreskell RepeatLabel Source #

Return Gremlin String literal.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type GreskellReturn RepeatLabel #

ToGreskell (AsLabel a) Source #

Returns the Text as a Gremlin string.

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type GreskellReturn (AsLabel a) #

ToGreskell (Greskell a)

It's just id.

Instance details

Defined in Data.Greskell.Greskell

Associated Types

type GreskellReturn (Greskell a) #

ToGreskell (Key a b) Source #

Return Gremlin String literal.

Instance details

Defined in Data.Greskell.Graph

Associated Types

type GreskellReturn (Key a b) #

Methods

toGreskell :: Key a b -> Greskell (GreskellReturn (Key a b)) #

ToGreskell (GTraversal c s e) Source #

Unwrap GTraversal data constructor.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type GreskellReturn (GTraversal c s e) #

WalkType c => ToGreskell (Walk c s e) Source #

The Walk is first converted to GTraversal, and it's converted to Greskell.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type GreskellReturn (Walk c s e) #

Methods

toGreskell :: Walk c s e -> Greskell (GreskellReturn (Walk c s e)) #

data AddAnchor s e Source #

Vertex anchor for gAddE. It corresponds to .from or .to step following an .addE step.

Type s is the input Vertex for the .addE step. Type e is the type of the anchor Vertex that the AddAnchor yields. So, .addE step creates an edge between s and e.

Since: 0.2.0.0

data LabeledByProjection s where Source #

A ByProjection associated with an AsLabel. You can construct it by gByL.

Since: 1.0.0.0

data ByComparator s where Source #

Comparison of type s used in .by step. You can also use gBy1 and gBy2 to construct ByComparator.

Constructors

ByComparatorProj :: ByProjection s e -> ByComparator s

Type s is projected to type e, and compared by the natural comparator of type e.

ByComparatorComp :: Comparator comp => Greskell comp -> ByComparator (CompareArg comp)

Type s is compared by the Comparator comp.

ByComparatorProjComp :: Comparator comp => ByProjection s (CompareArg comp) -> Greskell comp -> ByComparator s

Type s is projected to type CompareArg comp, and compared by the Comparator comp.

Instances

Instances details
IsString (ByComparator s) Source #

ByComparatorProj by literal property key.

Instance details

Defined in Data.Greskell.GTraversal

data ByProjection s e where Source #

Projection from type s to type e used in .by step. You can also use gBy to construct ByProjection.

Instances

Instances details
IsString (ByProjection s e) Source #

Projection by literal property key.

Instance details

Defined in Data.Greskell.GTraversal

Methods

fromString :: String -> ByProjection s e #

ProjectionLike (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

class ProjectionLike p Source #

Data types that mean a projection from one type to another.

Associated Types

type ProjectionLikeStart p Source #

The start type of the projection.

type ProjectionLikeEnd p Source #

The end type of the projection.

Instances

Instances details
ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (T s e)) Source #

type ProjectionLikeEnd (Greskell (T s e)) Source #

ProjectionLike (Greskell (s -> e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (s -> e)) Source #

type ProjectionLikeEnd (Greskell (s -> e)) Source #

ProjectionLike (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Key s e) Source #

type ProjectionLikeEnd (Key s e) Source #

ProjectionLike (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

data RepeatEmit c s where Source #

.emit modulator step.

Type c is the WalkType of the parent .repeat step. Type s is the start (and end) type of the .repeat step.

Since: 1.0.1.0

Constructors

RepeatEmit :: RepeatEmit c s

.emit modulator without argument. It always emits the input traverser of type s.

RepeatEmitT :: (WalkType cc, WalkType c, Split cc c) => GTraversal cc s e -> RepeatEmit c s

.emit modulator with a sub-traversal as the predicate to decide if it emits the traverser.

Instances

Instances details
Show (RepeatEmit c s) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

showsPrec :: Int -> RepeatEmit c s -> ShowS #

show :: RepeatEmit c s -> String #

showList :: [RepeatEmit c s] -> ShowS #

data RepeatUntil c s where Source #

.until or .times modulator step.

Type c is the WalkType of the parent .repeat step. Type s is the start (and end) type of the .repeat step.

Since: 1.0.1.0

Constructors

RepeatTimes :: Greskell Int -> RepeatUntil c s

.times modulator.

RepeatUntilT :: (WalkType cc, WalkType c, Split cc c) => GTraversal cc s e -> RepeatUntil c s

.until modulator with a sub-traversal as the predicate to decide if the repetition should stop.

Instances

Instances details
Show (RepeatUntil c s) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

showsPrec :: Int -> RepeatUntil c s -> ShowS #

show :: RepeatUntil c s -> String #

showList :: [RepeatUntil c s] -> ShowS #

data RepeatPos Source #

Position of a step modulator relative to .repeat step.

Since: 1.0.1.0

Constructors

RepeatHead

Modulator before the .repeat step.

RepeatTail

Modulator after the .repeat step.

newtype RepeatLabel Source #

A label that points to a loop created by .repeat step. It can be used by .loops step to specify the loop.

Since: 1.0.1.0

Constructors

RepeatLabel 

Fields

data MatchPattern where Source #

A pattern for .match step.

Since: 1.2.0.0

Constructors

MatchPattern :: AsLabel a -> Walk Transform a b -> MatchPattern

A pattern with the starting .as label followed by traversal steps.

data MatchResult Source #

Result of .match step.

Since: 1.2.0.0

data GraphTraversalSource Source #

GraphTraversalSource class object of TinkerPop. It is a factory object of GraphTraversals.

class Split c p where Source #

Relation of WalkTypes where the child walk c is split from the parent walk p.

When splitting, transformation effect done in the child walk is rolled back (canceled) in the parent walk.

Methods

showSplit :: Proxy c -> Proxy p -> String Source #

Only for tests.

Instances

Instances details
WalkType p => Split Filter p Source # 
Instance details

Defined in Data.Greskell.GTraversal

Split SideEffect SideEffect Source #

SideEffect in the child walk remains in the parent walk.

Instance details

Defined in Data.Greskell.GTraversal

WalkType p => Split Transform p Source #

Transform effect in the child walk is rolled back in the parent walk.

Instance details

Defined in Data.Greskell.GTraversal

class Lift from to where Source #

Relation of WalkTypes where one includes the other. from can be lifted to to, because to is more powerful than from.

Methods

showLift :: Proxy from -> Proxy to -> String Source #

Only for tests.

Instances

Instances details
WalkType c => Lift Filter c Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift SideEffect SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

data SideEffect Source #

WalkType for steps that may have side-effects.

A side-effect here means manipulation of the "sideEffect" in Gremlin context (i.e. the stash of data kept in a Traversal object), as well as interaction with the world outside the Traversal object.

For example, the following steps (in Gremlin) all have side-effects.

.addE('label')
.aggregate('x')
.sideEffect(System.out.&println)
.map { some_variable += 1 }

Instances

Instances details
WalkType SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift SideEffect SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Split SideEffect SideEffect Source #

SideEffect in the child walk remains in the parent walk.

Instance details

Defined in Data.Greskell.GTraversal

data Transform Source #

WalkType for steps without any side-effects. This includes transformations, reordring, injections and graph traversal actions.

A Walk w is Transform type iff:

gSideEffect w == gIdentity

Obviously, every Filter type Walks are also Transform type.

Instances

Instances details
WalkType Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType p => Split Transform p Source #

Transform effect in the child walk is rolled back in the parent walk.

Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

data Filter Source #

WalkType for filtering steps.

A filtering step is a step that does filtering only. It takes input and emits some of them without any modification, reordering, traversal actions, or side-effects. Filtering decision must be solely based on each element.

A Walk w is Filter type iff:

(gSideEffect w == gIdentity) AND (gFilter w == w)

If Walks w1 and w2 are Filter type, then

gAnd [w1, w2] == w1 >>> w2 == w2 >>> w1

Instances

Instances details
WalkType Filter Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType c => Lift Filter c Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType p => Split Filter p Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

class WalkType t where Source #

Class of phantom type markers to describe the effect of the walk/traversals.

Methods

showWalkType :: Proxy t -> String Source #

Only for tests.

Instances

Instances details
WalkType Filter Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

data Walk c s e Source #

A chain of one or more Gremlin steps. Like GTraversal, type s is the input, type e is the output, and type c is a marker to describe the step.

Walk represents a chain of method calls such as .has(x).outE(). Because this is not a Gremlin (Groovy) expression, we use bare Walk, not Greskell Walk.

Walk is a Category. You can use functions from Control.Category to compose Walks. This is equivalent to making a chain of method calls in Gremlin.

Walk is not an Eq, because it's difficult to define true equality between Gremlin method calls. If we define it naively, it might have conflict with Category law.

Instances

Instances details
ToGTraversal Walk Source #

To convert a Walk to GTraversal, it calls its static method version on __ class.

Instance details

Defined in Data.Greskell.GTraversal

Methods

toGTraversal :: WalkType c => Walk c s e -> GTraversal c s e Source #

liftWalk :: (WalkType from, WalkType to, Lift from to) => Walk from s e -> Walk to s e Source #

unsafeCastStart :: WalkType c => Walk c s1 e -> Walk c s2 e Source #

unsafeCastEnd :: WalkType c => Walk c s e1 -> Walk c s e2 Source #

WalkType c => Category (Walk c :: Type -> Type -> TYPE LiftedRep) Source #

id is gIdentity.

Instance details

Defined in Data.Greskell.GTraversal

Methods

id :: forall (a :: k). Walk c a a #

(.) :: forall (b :: k) (c0 :: k) (a :: k). Walk c b c0 -> Walk c a b -> Walk c a c0 #

Bifunctor (Walk c) Source #

Unsafely convert input and output types.

Instance details

Defined in Data.Greskell.GTraversal

Methods

bimap :: (a -> b) -> (c0 -> d) -> Walk c a c0 -> Walk c b d #

first :: (a -> b) -> Walk c a c0 -> Walk c b c0 #

second :: (b -> c0) -> Walk c a b -> Walk c a c0 #

Functor (Walk c s) Source #

Unsafely convert output type

Instance details

Defined in Data.Greskell.GTraversal

Methods

fmap :: (a -> b) -> Walk c s a -> Walk c s b #

(<$) :: a -> Walk c s b -> Walk c s a #

WalkType c => Monoid (Walk c s s) Source #

Based on Category and Semigroup. mempty is id.

Instance details

Defined in Data.Greskell.GTraversal

Methods

mempty :: Walk c s s #

mappend :: Walk c s s -> Walk c s s -> Walk c s s #

mconcat :: [Walk c s s] -> Walk c s s #

WalkType c => Semigroup (Walk c s s) Source #

Based on Category. <> is >>>.

Instance details

Defined in Data.Greskell.GTraversal

Methods

(<>) :: Walk c s s -> Walk c s s -> Walk c s s #

sconcat :: NonEmpty (Walk c s s) -> Walk c s s #

stimes :: Integral b => b -> Walk c s s -> Walk c s s #

Show (Walk c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

showsPrec :: Int -> Walk c s e -> ShowS #

show :: Walk c s e -> String #

showList :: [Walk c s e] -> ShowS #

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType c => ToGreskell (Walk c s e) Source #

The Walk is first converted to GTraversal, and it's converted to Greskell.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type GreskellReturn (Walk c s e) #

Methods

toGreskell :: Walk c s e -> Greskell (GreskellReturn (Walk c s e)) #

type ProjectionLikeEnd (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (Walk c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (Walk c s e) = GraphTraversal c s e

class ToGTraversal g where Source #

Types that can convert to GTraversal.

Methods

toGTraversal :: WalkType c => g c s e -> GTraversal c s e Source #

liftWalk :: (WalkType from, WalkType to, Lift from to) => g from s e -> g to s e Source #

Lift WalkType from to to. Use this for type matching.

unsafeCastStart :: WalkType c => g c s1 e -> g c s2 e Source #

Unsafely cast the start type s1 into s2.

It is recommended that s2 is coercible to s1 in terms of FromGraphSON. That is, if s2 can parse a GValue, s1 should also be able to parse that GValue.

Since: 1.0.0.0

unsafeCastEnd :: WalkType c => g c s e1 -> g c s e2 Source #

Unsafely cast the end type e1 into e2. See unsafeCastStart.

Since: 1.0.0.0

Instances

Instances details
ToGTraversal GTraversal Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

toGTraversal :: WalkType c => GTraversal c s e -> GTraversal c s e Source #

liftWalk :: (WalkType from, WalkType to, Lift from to) => GTraversal from s e -> GTraversal to s e Source #

unsafeCastStart :: WalkType c => GTraversal c s1 e -> GTraversal c s2 e Source #

unsafeCastEnd :: WalkType c => GTraversal c s e1 -> GTraversal c s e2 Source #

ToGTraversal Walk Source #

To convert a Walk to GTraversal, it calls its static method version on __ class.

Instance details

Defined in Data.Greskell.GTraversal

Methods

toGTraversal :: WalkType c => Walk c s e -> GTraversal c s e Source #

liftWalk :: (WalkType from, WalkType to, Lift from to) => Walk from s e -> Walk to s e Source #

unsafeCastStart :: WalkType c => Walk c s1 e -> Walk c s2 e Source #

unsafeCastEnd :: WalkType c => Walk c s e1 -> Walk c s e2 Source #

data GraphTraversal c s e Source #

Phantom type for GraphTraversal class. In greskell, we usually use GTraversal instead of Greskell GraphTraversal.

Instances

Instances details
Bifunctor (GraphTraversal c) Source #

Unsafely convert input and output types.

Instance details

Defined in Data.Greskell.GTraversal

Methods

bimap :: (a -> b) -> (c0 -> d) -> GraphTraversal c a c0 -> GraphTraversal c b d #

first :: (a -> b) -> GraphTraversal c a c0 -> GraphTraversal c b c0 #

second :: (b -> c0) -> GraphTraversal c a b -> GraphTraversal c a c0 #

ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Functor (GraphTraversal c s) Source #

Unsafely convert output type.

Instance details

Defined in Data.Greskell.GTraversal

Methods

fmap :: (a -> b) -> GraphTraversal c s a -> GraphTraversal c s b #

(<$) :: a -> GraphTraversal c s b -> GraphTraversal c s a #

Show (GraphTraversal c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

showsPrec :: Int -> GraphTraversal c s e -> ShowS #

show :: GraphTraversal c s e -> String #

showList :: [GraphTraversal c s e] -> ShowS #

AsIterator (GraphTraversal c s e) Source #

GraphTraversal is an Iterator.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type IteratorItem (GraphTraversal c s e) #

type ProjectionLikeEnd (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (GraphTraversal Filter s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type IteratorItem (GraphTraversal c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type IteratorItem (GraphTraversal c s e) = e

newtype GTraversal c s e Source #

GraphTraversal class object of TinkerPop. It takes data s from upstream and emits data e to downstream. Type c is called "walk type", a marker to describe the effect of the traversal.

GTraversal is NOT a Category. Because a GraphTraversal object keeps some context data, the starting (left-most) GraphTraversal object controls most of the behavior of entire composition of traversals and steps. This violates Category law.

Constructors

GTraversal 

Instances

Instances details
ToGTraversal GTraversal Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

toGTraversal :: WalkType c => GTraversal c s e -> GTraversal c s e Source #

liftWalk :: (WalkType from, WalkType to, Lift from to) => GTraversal from s e -> GTraversal to s e Source #

unsafeCastStart :: WalkType c => GTraversal c s1 e -> GTraversal c s2 e Source #

unsafeCastEnd :: WalkType c => GTraversal c s e1 -> GTraversal c s e2 Source #

Bifunctor (GTraversal c) Source #

Unsafely convert input and output types.

Instance details

Defined in Data.Greskell.GTraversal

Methods

bimap :: (a -> b) -> (c0 -> d) -> GTraversal c a c0 -> GTraversal c b d #

first :: (a -> b) -> GTraversal c a c0 -> GTraversal c b c0 #

second :: (b -> c0) -> GTraversal c a b -> GTraversal c a c0 #

Functor (GTraversal c s) Source #

Unsafely convert output type.

Instance details

Defined in Data.Greskell.GTraversal

Methods

fmap :: (a -> b) -> GTraversal c s a -> GTraversal c s b #

(<$) :: a -> GTraversal c s b -> GTraversal c s a #

Show (GTraversal c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Methods

showsPrec :: Int -> GTraversal c s e -> ShowS #

show :: GTraversal c s e -> String #

showList :: [GTraversal c s e] -> ShowS #

ProjectionLike (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ToGreskell (GTraversal c s e) Source #

Unwrap GTraversal data constructor.

Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type GreskellReturn (GTraversal c s e) #

type ProjectionLikeEnd (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (GTraversal c s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

source Source #

Arguments

:: Text

variable name of GraphTraversalSource

-> Greskell GraphTraversalSource 

Create GraphTraversalSource from a varible name in Gremlin

sV Source #

Arguments

:: Vertex v 
=> [Greskell (ElementID v)]

vertex IDs

-> Greskell GraphTraversalSource 
-> GTraversal Transform () v 

.V() method on GraphTraversalSource.

sV' Source #

Monomorphic version of sV.

sE Source #

Arguments

:: Edge e 
=> [Greskell (ElementID e)]

edge IDs

-> Greskell GraphTraversalSource 
-> GTraversal Transform () e 

.E() method on GraphTraversalSource.

sE' Source #

Monomorphic version of sE.

sAddV Source #

Arguments

:: Vertex v 
=> Greskell Text

vertex label

-> Greskell GraphTraversalSource 
-> GTraversal SideEffect () v 

.addV() method on GraphTraversalSource.

Since: 0.2.0.0

sAddV' :: Greskell Text -> Greskell GraphTraversalSource -> GTraversal SideEffect () AVertex Source #

Monomorphic version of sAddV.

Since: 0.2.0.0

unsafeGTraversal :: Text -> GTraversal c s e Source #

Unsafely create GTraversal from the given raw Gremlin script.

(&.) :: GTraversal c a b -> Walk c b d -> GTraversal c a d infixl 1 Source #

Apply the Walk to the GTraversal. In Gremlin, this means calling a chain of methods on the Traversal object.

($.) :: Walk c b d -> GTraversal c a b -> GTraversal c a d infixr 0 Source #

Same as &. with arguments flipped.

(<$.>) :: Functor f => Walk c b d -> f (GTraversal c a b) -> f (GTraversal c a d) infixr 0 Source #

Similar to <$>, but for $..

Since: 0.2.1.0

(<*.>) :: Applicative f => f (Walk c b d) -> f (GTraversal c a b) -> f (GTraversal c a d) infixr 0 Source #

Similar to <*>, but for $..

Since: 0.2.1.0

gIterate :: WalkType c => GTraversal c s e -> GTraversal c s () Source #

.iterate method on GraphTraversal.

gIterate is not a Walk because it's usually used to terminate the method chain of Gremlin steps. The returned GTraversal outputs nothing, thus its end type is ().

Since: 1.1.0.0

unsafeWalk Source #

Arguments

:: WalkType c 
=> Text

step method name (e.g. "outE")

-> [Text]

step method arguments

-> Walk c s e 

Unsafely create a Walk that represents a single method call on a GraphTraversal.

modulateWith Source #

Arguments

:: WalkType c 
=> Walk c s e

the main Walk

-> [Walk c e e]

the modulating Walks

-> Walk c s e 

Optionally modulate the main Walk with some modulating Walks.

gIdentity :: WalkType c => Walk c s s Source #

.identity step.

gIdentity' :: Walk Filter s s Source #

Monomorphic version of gIdentity.

gFilter :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s Source #

.filter step that takes a traversal.

gCyclicPath :: WalkType c => Walk c a a Source #

.cyclicPath step.

Since: 1.0.1.0

gCyclicPath' :: Walk Filter a a Source #

Monomorphic version of gCyclicPath.

Since: 1.0.1.0

gSimplePath :: WalkType c => Walk c a a Source #

.simplePath step.

Since: 1.0.1.0

gSimplePath' :: Walk Filter a a Source #

Monomorphic version of gSimplePath.

Since: 1.0.1.0

gWhereP1 Source #

Arguments

:: WalkType c 
=> Greskell (LabeledP a)

the P argument for .where step.

-> Maybe (ByProjection a b)

optional .by modulation following the .where step.

-> Walk c a a 

.where step with P argument only.

If the ByProjection argument is Nothing, comparison is performed on the type a. You have to ensure that the comparator included in the LabeledP argument can handle the type a. Usually this means the type a should implement Java's Comparable interface (this is true for most Java classes).

If the ByProjection argument is given, comparison is performed on the projected values of type b. So, the type b should implement Java's Comparable interface.

Since: 1.2.0.0

gWhereP1' :: Greskell (LabeledP a) -> Maybe (ByProjection a b) -> Walk Filter a a Source #

Monomorphic version of gWhereP1.

Since: 1.2.0.0

gWhereP2 Source #

Arguments

:: WalkType c 
=> AsLabel a

the starting label of .where.

-> Greskell (LabeledP a)

the P argument for .where step.

-> Maybe (ByProjection a b)

optional .by modulation following the .where step.

-> Walk c x x 

.where step with the starting label and P arguments. See also gWhereP1.

Since: 1.2.0.0

gWhereP2' :: AsLabel a -> Greskell (LabeledP a) -> Maybe (ByProjection a b) -> Walk Filter x x Source #

Monomorphic version of gWhereP2.

Since: 1.2.0.0

mPattern :: (WalkType c, Lift c Transform) => AsLabel a -> Walk c a b -> Logic MatchPattern Source #

A convenient function to make a MatchPattern wrapped by Leaf.

Since: 1.2.0.0

gMatch :: Logic MatchPattern -> Walk Transform a MatchResult Source #

.match step.

If the top-level Logic of the argument is And, the patterns are directly passed to the .match step arguments.

The result of .match step, MatchResult, is an opaque type. Basically you should not use it. Instead, you should use gSelectN etc to access the path history labels inside the MatchPattern.

See also: https://groups.google.com/g/gremlin-users/c/HVtldzV0Xk8

Since: 1.2.0.0

gIs :: WalkType c => Greskell v -> Walk c v v Source #

.is step of simple equality.

Since: 1.0.1.0

gIs' :: Greskell v -> Walk Filter v v Source #

Monomorphic version of gIs.

Since: 1.0.1.0

gIsP :: WalkType c => Greskell (P v) -> Walk c v v Source #

.is step with predicate P.

Since: 1.0.1.0

gIsP' :: Greskell (P v) -> Walk Filter v v Source #

Monomorphic version of gIsP.

Since: 1.0.1.0

gHas1 Source #

Arguments

:: (WalkType c, Element s) 
=> Key s v

property key

-> Walk c s s 

.has step with one argument.

gHas1' :: Element s => Key s v -> Walk Filter s s Source #

Monomorphic version of gHas1.

gHas2 :: (WalkType c, Element s) => Key s v -> Greskell v -> Walk c s s Source #

.has step with two arguments.

gHas2' :: Element s => Key s v -> Greskell v -> Walk Filter s s Source #

Monomorphic verson of gHas2.

gHas2P Source #

Arguments

:: (WalkType c, Element s) 
=> Key s v

property key

-> Greskell (P v)

predicate on the property value

-> Walk c s s 

.has step with two arguments and P type.

gHas2P' :: Element s => Key s v -> Greskell (P v) -> Walk Filter s s Source #

Monomorphic version of gHas2P.

gHasLabel :: (Element s, WalkType c) => Greskell Text -> Walk c s s Source #

.hasLabel step.

gHasLabel' :: Element s => Greskell Text -> Walk Filter s s Source #

Monomorphic version of gHasLabel.

gHasLabelP Source #

Arguments

:: (Element s, WalkType c) 
=> Greskell (P Text)

predicate on Element label.

-> Walk c s s 

.hasLabel step with P type. Supported since TinkerPop 3.2.7.

gHasLabelP' :: Element s => Greskell (P Text) -> Walk Filter s s Source #

Monomorphic version of gHasLabelP.

gHasId :: (Element s, WalkType c) => Greskell (ElementID s) -> Walk c s s Source #

.hasId step.

gHasId' :: Element s => Greskell (ElementID s) -> Walk Filter s s Source #

Monomorphic version of gHasId.

gHasIdP :: (Element s, WalkType c) => Greskell (P (ElementID s)) -> Walk c s s Source #

.hasId step with P type. Supported since TinkerPop 3.2.7.

gHasIdP' :: Element s => Greskell (P (ElementID s)) -> Walk Filter s s Source #

Monomorphic version of gHasIdP.

gHasKey :: (Element (p v), Property p, WalkType c) => Greskell Text -> Walk c (p v) (p v) Source #

.hasKey step. The input type should be a VertexProperty.

gHasKey' :: (Element (p v), Property p) => Greskell Text -> Walk Filter (p v) (p v) Source #

Monomorphic version of gHasKey.

gHasKeyP Source #

Arguments

:: (Element (p v), Property p, WalkType c) 
=> Greskell (P Text)

predicate on the VertexProperty's key.

-> Walk c (p v) (p v) 

.hasKey step with P type. Supported since TinkerPop 3.2.7.

gHasKeyP' :: (Element (p v), Property p) => Greskell (P Text) -> Walk Filter (p v) (p v) Source #

Monomorphic version of gHasKeyP.

gHasValue :: (Element (p v), Property p, WalkType c) => Greskell v -> Walk c (p v) (p v) Source #

.hasValue step. The input type should be a VertexProperty.

gHasValue' :: (Element (p v), Property p) => Greskell v -> Walk Filter (p v) (p v) Source #

Monomorphic version of gHasValue.

gHasValueP Source #

Arguments

:: (Element (p v), Property p, WalkType c) 
=> Greskell (P v)

predicate on the VertexProperty's value

-> Walk c (p v) (p v) 

.hasValue step with P type. Supported since TinkerPop 3.2.7.

gHasValueP' :: (Element (p v), Property p) => Greskell (P v) -> Walk Filter (p v) (p v) Source #

Monomorphic version of gHasValueP.

gAnd :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => [g c s e] -> Walk p s s Source #

.and step.

gOr :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => [g c s e] -> Walk p s s Source #

.or step.

gNot :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s Source #

.not step.

gRange Source #

Arguments

:: Greskell Int

min

-> Greskell Int

max

-> Walk Transform s s 

.range step. This step is not a Filter, because the filtering decision by this step is based on position of each element, not the element itself. This violates Filter law.

gLimit :: Greskell Int -> Walk Transform s s Source #

.limit step.

Since: 0.2.1.0

gTail :: Greskell Int -> Walk Transform s s Source #

.tail step.

Since: 0.2.1.0

gSkip :: Greskell Int -> Walk Transform s s Source #

.skip step.

Since: 0.2.1.0

gRepeat Source #

Arguments

:: (ToGTraversal g, WalkType c) 
=> Maybe RepeatLabel

Label for the loop.

-> Maybe (RepeatPos, RepeatUntil c s)

.until or .times modulator. You can use gTimes, gUntilHead, gUntilTail to make this argument.

-> Maybe (RepeatPos, RepeatEmit c s)

.emit modulator. You can use gEmitHead, gEmitTail, gEmitHeadT, gEmitTailT to make this argument.

-> g c s s

Repeated traversal

-> Walk c s s 

.repeat step.

Since: 1.0.1.0

gTimes Source #

Arguments

:: Greskell Int

Repeat count. If it's less than or equal to 0, the repeated traversal is never executed.

-> Maybe (RepeatPos, RepeatUntil c s) 

.times modulator before the .repeat step. It always returns Just.

Since: 1.0.1.0

gUntilHead :: (ToGTraversal g, WalkType c, WalkType cc, Split cc c) => g cc s e -> Maybe (RepeatPos, RepeatUntil c s) Source #

.until modulator before the .repeat step. It always returns Just.

Since: 1.0.1.0

gUntilTail :: (ToGTraversal g, WalkType c, WalkType cc, Split cc c) => g cc s e -> Maybe (RepeatPos, RepeatUntil c s) Source #

.until modulator after the .repeat step. It always returns Just.

Since: 1.0.1.0

gEmitHead :: Maybe (RepeatPos, RepeatEmit c s) Source #

.emit modulator without argument before the .repeat step. It always returns Just.

Since: 1.0.1.0

gEmitTail :: Maybe (RepeatPos, RepeatEmit c s) Source #

.emit modulator without argument after the .repeat step. It always returns Just.

Since: 1.0.1.0

gEmitHeadT :: (ToGTraversal g, WalkType c, WalkType cc, Split cc c) => g cc s e -> Maybe (RepeatPos, RepeatEmit c s) Source #

.emit modulator with a sub-traversal argument before the .repeat step. It always returns Just.

Since: 1.0.1.0

gEmitTailT :: (ToGTraversal g, WalkType c, WalkType cc, Split cc c) => g cc s e -> Maybe (RepeatPos, RepeatEmit c s) Source #

.emit modulator with a sub-traversal argument after the .repeat step. It always returns Just.

Since: 1.0.1.0

gLoops :: Maybe RepeatLabel -> Walk Transform s Int Source #

.loops step.

Since: 1.0.1.0

gLocal :: (ToGTraversal g, WalkType c) => g c s e -> Walk c s e Source #

.local step.

Since: 1.0.1.0

gUnion :: (ToGTraversal g, WalkType c) => [g c s e] -> Walk c s e Source #

.union step.

Since: 1.0.1.0

gCoalesce :: (ToGTraversal g, Split cc c, Lift Transform c, WalkType c, WalkType cc) => [g cc s e] -> Walk c s e Source #

.coalesce step.

Like gFlatMap, gCoalesce always modifies path history.

Since: 1.1.0.0

gChoose3 Source #

Arguments

:: (ToGTraversal g, Split cc c, WalkType cc, WalkType c) 
=> g cc s ep

the predicate traversal.

-> g c s e

The traversal executed if the predicate traversal outputs something.

-> g c s e

The traversal executed if the predicate traversal outputs nothing.

-> Walk c s e 

.choose step with if-then-else style.

Since: 1.0.1.0

gBarrier Source #

Arguments

:: WalkType c 
=> Maybe (Greskell Int)

Max number of traversers kept at this barrier.

-> Walk c s s 

.barrier step.

Since: 1.0.1.0

gDedup Source #

Arguments

:: Maybe (ByProjection s e)

.by modulator. If specified, the result of type e is used as the criterion of deduplication.

-> Walk Transform s s 

.dedup step without argument.

.dedup step is Transform because the filtering decision depends on the sequence (order) of input elements.

Since: 1.0.1.0

gDedupN :: AsLabel a -> [AsLabel a] -> Maybe (ByProjection a e) -> Walk Transform s s Source #

.dedup step with at least one argument. The tuple specified by the AsLabels is used as the criterion of deduplication.

Since: 1.0.1.0

gBy :: (ProjectionLike p, ToGreskell p) => p -> ByProjection (ProjectionLikeStart p) (ProjectionLikeEnd p) Source #

.by step with 1 argument, used for projection.

gBy1 :: (ProjectionLike p, ToGreskell p) => p -> ByComparator (ProjectionLikeStart p) Source #

.by step with 1 argument, used for comparison.

gBy2 :: (ProjectionLike p, ToGreskell p, Comparator comp, ProjectionLikeEnd p ~ CompareArg comp) => p -> Greskell comp -> ByComparator (ProjectionLikeStart p) Source #

.by step with 2 arguments, used for comparison.

gOrder Source #

Arguments

:: [ByComparator s]

following .by steps.

-> Walk Transform s s 

.order step.

ByComparator is an IsString, meaning projection by the given key.

gByL :: (ProjectionLike p, ToGreskell p) => AsLabel (ProjectionLikeEnd p) -> p -> LabeledByProjection (ProjectionLikeStart p) Source #

.by step associated with an AsLabel.

Since: 1.0.0.0

gFlatMap :: (Lift Transform c, Split cc c, ToGTraversal g, WalkType c, WalkType cc) => g cc s e -> Walk c s e Source #

.flatMap step.

.flatMap step is at least as powerful as Transform, even if the child walk is Filter type. This is because .flatMap step always modifies the path of the Traverser.

Since: 1.1.0.0

gFlatMap' :: ToGTraversal g => g Transform s e -> Walk Transform s e Source #

Monomorphic version of gFlatMap.

Since: 1.1.0.0

gV :: Vertex v => [Greskell (ElementID v)] -> Walk Transform s v Source #

.V step.

For each input item, .V step emits vertices selected by the argument (or all vertices if the empty list is passed.)

Since: 0.2.0.0

gV' :: [Greskell (ElementID AVertex)] -> Walk Transform s AVertex Source #

Monomorphic version of gV.

Since: 0.2.0.0

gConstant :: Greskell a -> Walk Transform s a Source #

.constant step.

Since: 1.0.1.0

gUnfold :: AsIterator a => Walk Transform a (IteratorItem a) Source #

.unfold step.

Note that we use AsIterator here because basically the .unfold step does the same thing as IteratorUtils.asIterator function in Tinkerpop. However, Tinkerpop's implementation of .unfold step doesn't necessarily use asIterator, so there may be some corner cases where asIterator and .unfold step behave differently.

Since: 1.0.1.0

gAs :: AsLabel a -> Walk Transform a a Source #

.as step.

.as step is Transform because it adds the label to the traverser.

Since: 0.2.2.0

gValues Source #

Arguments

:: Element s 
=> [Key s e]

property keys

-> Walk Transform s e 

.values step.

gProperties :: (Element s, Property p, ElementProperty s ~ p) => [Key s v] -> Walk Transform s (p v) Source #

.properties step.

gId :: Element s => Walk Transform s (ElementID s) Source #

.id step.

Since: 0.2.1.0

gLabel :: Element s => Walk Transform s Text Source #

.label step.

Since: 0.2.1.0

gValueMap :: Element s => Keys s -> Walk Transform s (PMap (ElementPropertyContainer s) GValue) Source #

.valueMap step.

Since: 1.0.0.0

gElementMap :: Element s => Keys s -> Walk Transform s (PMap Single GValue) Source #

.elementMap step.

Since: 2.0.1.0

gSelect1 :: AsLabel a -> Walk Transform s a Source #

.select step with one argument.

Since: 0.2.2.0

gSelectN :: AsLabel a -> AsLabel b -> [AsLabel c] -> Walk Transform s (SelectedMap GValue) Source #

.select step with more than one arguments.

Since: 0.2.2.0

gSelectBy1 :: AsLabel a -> ByProjection a b -> Walk Transform s b Source #

.select step with one argument followed by .by step.

Since: 0.2.2.0

gSelectByN :: AsLabel a -> AsLabel a -> [AsLabel a] -> ByProjection a b -> Walk Transform s (SelectedMap b) Source #

.select step with more than one arguments followed by .by step.

Since: 0.2.2.0

gProject :: LabeledByProjection s -> [LabeledByProjection s] -> Walk Transform s (PMap Single GValue) Source #

.project step.

Since: 1.0.0.0

gPath :: Walk Transform s (Path GValue) Source #

.path step without modulation.

Since: 1.1.0.0

gPathBy :: ByProjection a b -> [ByProjection a b] -> Walk Transform s (Path b) Source #

.path step with one or more .by modulations.

Since: 1.1.0.0

gFold :: Walk Transform a [a] Source #

.fold step.

gCount :: Walk Transform a Int Source #

.count step.

gOut Source #

Arguments

:: (Vertex v1, Vertex v2) 
=> [Greskell Text]

edge labels

-> Walk Transform v1 v2 

.out step

gOut' Source #

Arguments

:: Vertex v 
=> [Greskell Text]

edge labels

-> Walk Transform v AVertex 

Monomorphic version of gOut.

gOutE Source #

Arguments

:: (Vertex v, Edge e) 
=> [Greskell Text]

edge labels

-> Walk Transform v e 

.outE step

gOutE' :: Vertex v => [Greskell Text] -> Walk Transform v AEdge Source #

Monomorphic version of gOutE.

gOutV :: (Edge e, Vertex v) => Walk Transform e v Source #

.outV step.

Since: 0.2.2.0

gOutV' :: Edge e => Walk Transform e AVertex Source #

Monomorphic version of gOutV.

Since: 0.2.2.0

gIn Source #

Arguments

:: (Vertex v1, Vertex v2) 
=> [Greskell Text]

edge labels

-> Walk Transform v1 v2 

.in step

gIn' :: Vertex v => [Greskell Text] -> Walk Transform v AVertex Source #

Monomorphic version of gIn.

gInE Source #

Arguments

:: (Vertex v, Edge e) 
=> [Greskell Text]

edge labels

-> Walk Transform v e 

.inE step.

gInE' Source #

Arguments

:: Vertex v 
=> [Greskell Text]

edge labels

-> Walk Transform v AEdge 

Monomorphic version of gInE.

gInV :: (Edge e, Vertex v) => Walk Transform e v Source #

.inV step.

Since: 0.2.2.0

gInV' :: Edge e => Walk Transform e AVertex Source #

Monomorphic version of gInV.

Since: 0.2.2.0

gSideEffect :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s Source #

.sideEffect step that takes a traversal.

gSideEffect' :: (ToGTraversal g, WalkType c, Split c SideEffect) => g c s e -> Walk SideEffect s s Source #

Monomorphic version of gSideEffect. The result walk is always SideEffect type.

gAddV :: Vertex v => Greskell Text -> Walk SideEffect a v Source #

.addV step with a label.

gAddV' :: Greskell Text -> Walk SideEffect a AVertex Source #

Monomorphic version of gAddV.

gDrop :: Element e => Walk SideEffect e e Source #

.drop step on Element.

gDropP :: Property p => Walk SideEffect (p a) (p a) Source #

.drop step on Property.

gProperty Source #

Arguments

:: Element e 
=> Key e v

key of the property

-> Greskell v

value of the property

-> Walk SideEffect e e 

Simple .property step. It adds a value to the property.

Since: 0.2.0.0

gPropertyV Source #

Arguments

:: (Vertex e, vp ~ ElementProperty e, Property vp, Element (vp v)) 
=> Maybe (Greskell Cardinality)

optional cardinality of the vertex property.

-> Key e v

key of the vertex property

-> Greskell v

value of the vertex property

-> [KeyValue (vp v)]

optional meta-properties for the vertex property.

-> Walk SideEffect e e 

.property step for Vertex.

Since: 0.2.0.0

gFrom :: ToGTraversal g => g Transform s e -> AddAnchor s e Source #

.from step with a traversal.

Since: 0.2.0.0

gTo :: ToGTraversal g => g Transform s e -> AddAnchor s e Source #

.to step with a traversal.

Since: 0.2.0.0

gAddE :: (Vertex vs, Vertex ve, Edge e) => Greskell Text -> AddAnchor vs ve -> Walk SideEffect vs e Source #

.addE step. Supported since TinkerPop 3.1.0.

Since: 0.2.0.0

gAddE' :: Greskell Text -> AddAnchor AVertex AVertex -> Walk SideEffect AVertex AEdge Source #

Monomorphic version of gAddE.

Since: 0.2.0.0

data Order a Source #

org.apache.tinkerpop.gremlin.process.traversal.Order enum.

Instances

Instances details
Comparator (Order a) Source #

Order a compares the type a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (Order a) Source #

GraphSONTyped (Order a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: Order a -> Text #

type CompareArg (Order a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

type CompareArg (Order a) = a

newtype ComparatorA a Source #

Type for anonymous class of Comparator interface.

Constructors

ComparatorA 

Fields

class Comparator c where Source #

java.util.Comparator interface.

Comparator compares two data of type CompareArg c.

Minimal complete definition

Nothing

Associated Types

type CompareArg c Source #

Methods

cCompare :: Greskell c -> Greskell (CompareArg c) -> Greskell (CompareArg c) -> Greskell Int Source #

.compare method.

cReversed :: Greskell c -> Greskell c Source #

.reversed method.

cThenComparing :: Greskell c -> Greskell c -> Greskell c Source #

.thenComparing method.

Instances

Instances details
Comparator (ComparatorA a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (ComparatorA a) Source #

Comparator (Order a) Source #

Order a compares the type a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (Order a) Source #

class ToGreskell (PParameter p) => PLike p Source #

Type that is compatible with P. You can construct a value of type Greskell p using values of PParameter p.

Note that the type of constuctor arguments (i.e. GreskellReturn (PParameter p)) should implement Java's Comparable interface. This is true for most types, so greskell doesn't have any explicit constraint about it.

Since: 1.2.0.0

Associated Types

type PParameter p Source #

Instances

Instances details
PLike (LabeledP a) Source #

You can construct Greskell (LabeledP a) from AsLabel a.

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type PParameter (LabeledP a) Source #

PLike (P a) Source #

You can construct Greskell (P a) from Greskell a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PParameter (P a) Source #

data P a Source #

org.apache.tinkerpop.gremlin.process.traversal.P class.

P a keeps data of type a and compares it with data of type a given as the Predicate argument.

Instances

Instances details
PLike (P a) Source #

You can construct Greskell (P a) from Greskell a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PParameter (P a) Source #

Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) Source #

Methods

pAnd :: Greskell (P a) -> Greskell (P a) -> Greskell (P a) Source #

pOr :: Greskell (P a) -> Greskell (P a) -> Greskell (P a) Source #

pTest :: Greskell (P a) -> Greskell (PredicateArg (P a)) -> Greskell Bool Source #

pNegate :: Greskell (P a) -> Greskell (P a) Source #

GraphSONTyped (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: P a -> Text #

type PParameter (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

type PParameter (P a) = Greskell a
type PredicateArg (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

type PredicateArg (P a) = a

newtype PredicateA a Source #

Type for anonymous class of Predicate interface.

Constructors

PredicateA 

Fields

class Predicate p where Source #

java.util.function.Predicate interface.

A Predicate p is a function that takes PredicateArg p and returns Bool.

Minimal complete definition

Nothing

Associated Types

type PredicateArg p Source #

Methods

pAnd :: Greskell p -> Greskell p -> Greskell p Source #

.and method.

pOr :: Greskell p -> Greskell p -> Greskell p Source #

.or method.

pTest :: Greskell p -> Greskell (PredicateArg p) -> Greskell Bool Source #

.test method.

pNegate :: Greskell p -> Greskell p Source #

.nagate method.

Instances

Instances details
Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) Source #

Methods

pAnd :: Greskell (P a) -> Greskell (P a) -> Greskell (P a) Source #

pOr :: Greskell (P a) -> Greskell (P a) -> Greskell (P a) Source #

pTest :: Greskell (P a) -> Greskell (PredicateArg (P a)) -> Greskell Bool Source #

pNegate :: Greskell (P a) -> Greskell (P a) Source #

Predicate (PredicateA a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (PredicateA a) Source #

pNot :: PLike p => Greskell p -> Greskell p Source #

P.not static method.

pEq :: PLike p => PParameter p -> Greskell p Source #

P.eq static method.

pNeq :: PLike p => PParameter p -> Greskell p Source #

P.neq static method.

pLt :: PLike p => PParameter p -> Greskell p Source #

P.lt static method.

pLte :: PLike p => PParameter p -> Greskell p Source #

P.lte static method.

pGt :: PLike p => PParameter p -> Greskell p Source #

P.gt static method.

pGte :: PLike p => PParameter p -> Greskell p Source #

P.gte static method.

pInside :: PLike p => PParameter p -> PParameter p -> Greskell p Source #

P.inside static method.

pOutside :: PLike p => PParameter p -> PParameter p -> Greskell p Source #

P.outside static method.

pBetween :: PLike p => PParameter p -> PParameter p -> Greskell p Source #

P.between static method.

pWithin :: PLike p => [PParameter p] -> Greskell p Source #

P.within static method.

pWithout :: PLike p => [PParameter p] -> Greskell p Source #

P.without static method.

oDesc :: Greskell (Order a) Source #

desc order.

Since: 2.0.2.0

oAsc :: Greskell (Order a) Source #

asc order.

Since: 2.0.2.0

oDecr :: Greskell (Order a) Source #

decr order.

Note that decr was removed in TinkerPop 3.5.0. Use oDesc instead.

oIncr :: Greskell (Order a) Source #

incr order.

Note that incr was removed in TinkerPop 3.5.0. Use oAsc instead.

oShuffle :: Greskell (Order a) Source #

shuffle order.

data PathEntry a Source #

An entry in a Path.

Since: 1.1.0.0

Constructors

PathEntry 

Fields

Instances

Instances details
Foldable PathEntry Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> PathEntry a -> m #

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

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

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

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

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

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

toList :: PathEntry a -> [a] #

null :: PathEntry a -> Bool #

length :: PathEntry a -> Int #

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

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

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

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

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

Traversable PathEntry Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

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

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

Functor PathEntry Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

Show a => Show (PathEntry a) Source # 
Instance details

Defined in Data.Greskell.Graph

Eq a => Eq (PathEntry a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: PathEntry a -> PathEntry a -> Bool #

(/=) :: PathEntry a -> PathEntry a -> Bool #

Ord a => Ord (PathEntry a) Source # 
Instance details

Defined in Data.Greskell.Graph

newtype Path a Source #

org.apache.tinkerpop.gremlin.process.traversal.Path interface.

Since: 1.1.0.0

Constructors

Path 

Fields

Instances

Instances details
Foldable Path Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Path a -> m #

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

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

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

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

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

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

toList :: Path a -> [a] #

null :: Path a -> Bool #

length :: Path a -> Int #

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

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

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

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

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

Traversable Path Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

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

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

Functor Path Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

FromGraphSON a => FromJSON (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Monoid (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

mempty :: Path a #

mappend :: Path a -> Path a -> Path a #

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

Semigroup (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

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

Show a => Show (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

showsPrec :: Int -> Path a -> ShowS #

show :: Path a -> String #

showList :: [Path a] -> ShowS #

Eq a => Eq (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: Path a -> Path a -> Bool #

(/=) :: Path a -> Path a -> Bool #

Ord a => Ord (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

compare :: Path a -> Path a -> Ordering #

(<) :: Path a -> Path a -> Bool #

(<=) :: Path a -> Path a -> Bool #

(>) :: Path a -> Path a -> Bool #

(>=) :: Path a -> Path a -> Bool #

max :: Path a -> Path a -> Path a #

min :: Path a -> Path a -> Path a #

AsIterator (Path a) Source #

Path is an Iterable that emits its objects of type a.

Instance details

Defined in Data.Greskell.Graph

Associated Types

type IteratorItem (Path a) #

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

Defined in Data.Greskell.Graph

Methods

parseGraphSON :: GValue -> Parser (Path a) #

GraphSONTyped (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: Path a -> Text #

type IteratorItem (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

type IteratorItem (Path a) = a

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

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

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

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 #

Property AVertexProperty 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

Show v => Show (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Eq v => Eq (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

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

Defined in Data.Greskell.Graph

GraphSONTyped (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementProperty (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementPropertyContainer (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

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

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

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

Functor AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

Property AProperty 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

Show v => Show (AProperty v) 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

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

Defined in Data.Greskell.Graph.PropertyMap

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 #

data AEdge Source #

General edge type you can use for Edge class.

Constructors

AEdge 

Fields

Instances

Instances details
FromJSON AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Show AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

showsPrec :: Int -> AEdge -> ShowS #

show :: AEdge -> String #

showList :: [AEdge] -> ShowS #

Eq AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

Edge AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Element AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

ElementData AEdge Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

FromGraphSON AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AEdge -> Text #

type ElementProperty AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementPropertyContainer AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

data AVertex Source #

General vertex type you can use for Vertex class.

Constructors

AVertex 

Fields

Instances

Instances details
FromJSON AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Show AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Eq AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

Element AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

ElementData AVertex Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

Vertex AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AVertex -> Text #

type ElementProperty AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

type ElementPropertyContainer AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

data Keys a where Source #

Heterogeneous list of Keys. It keeps the parent type a, but discards the value type b.

Since: 1.0.0.0

Constructors

KeysNil :: Keys a

Empty Keys.

KeysCons :: Key a b -> Keys a -> Keys a

Add a Key to Keys.

Instances

Instances details
Monoid (Keys a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

mempty :: Keys a #

mappend :: Keys a -> Keys a -> Keys a #

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

Semigroup (Keys a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

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

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

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

data KeyValue a where Source #

Pair of Key and its value. Mainly used for writing properties into the database.

Type a is the type of Element that keeps the KeyValue pair. It drops the type of the value, so that you can construct a heterogeneous list of key-value pairs for a given Element.

Since: 0.2.0.0

Constructors

KeyValue :: Key a b -> Greskell b -> KeyValue a

Key and value

KeyNoValue :: Key a b -> KeyValue a

Key without value

Since: 1.0.0.0

newtype Key a b Source #

A property key accessing value b in an Element a. In Gremlin, it's just a String type.

Since greskell-1.0.0.0, Key is newtype of Text. Before that, it was newtype of Greskell Text.

Constructors

Key 

Fields

Instances

Instances details
Functor (Key a) Source #

Unsafely convert the value type b.

Instance details

Defined in Data.Greskell.Graph

Methods

fmap :: (a0 -> b) -> Key a a0 -> Key a b #

(<$) :: a0 -> Key a b -> Key a a0 #

IsString (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

fromString :: String -> Key a b #

Show (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

showsPrec :: Int -> Key a b -> ShowS #

show :: Key a b -> String #

showList :: [Key a b] -> ShowS #

Eq (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: Key a b -> Key a b -> Bool #

(/=) :: Key a b -> Key a b -> Bool #

ProjectionLike (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Key s e) Source #

type ProjectionLikeEnd (Key s e) Source #

PMapKey (Key a b) Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

Associated Types

type PMapValue (Key a b) Source #

Methods

keyText :: Key a b -> Text Source #

ToGreskell (Key a b) Source #

Return Gremlin String literal.

Instance details

Defined in Data.Greskell.Graph

Associated Types

type GreskellReturn (Key a b) #

Methods

toGreskell :: Key a b -> Greskell (GreskellReturn (Key a b)) #

type ProjectionLikeEnd (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Key s e) = e
type ProjectionLikeStart (Key s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Key s e) = s
type PMapValue (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

type PMapValue (Key a b) = b
type GreskellReturn (Key a b) Source # 
Instance details

Defined in Data.Greskell.Graph

type GreskellReturn (Key a b) = Text

data Cardinality Source #

org.apache.tinkerpop.gremlin.structure.VertexProperty.Cardinality enum.

Since: 0.2.0.0

data T a b Source #

org.apache.tinkerpop.gremlin.structure.T enum.

T is a token to get data b from an Element a.

Instances

Instances details
ProjectionLike (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Greskell (T s e)) Source #

type ProjectionLikeEnd (Greskell (T s e)) Source #

GraphSONTyped (T a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: T a b -> Text #

type ProjectionLikeEnd (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (Greskell (T s e)) = e
type ProjectionLikeStart (Greskell (T s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeStart (Greskell (T s e)) = s

class Property p where Source #

org.apache.tinkerpop.gremlin.structure.Property interface in a TinkerPop graph.

Methods

propertyKey :: p v -> Text Source #

Get key of this property.

propertyValue :: p v -> v Source #

Get value of this property.

Instances

Instances details
Property AProperty Source # 
Instance details

Defined in Data.Greskell.Graph

Property AVertexProperty Source # 
Instance details

Defined in Data.Greskell.Graph

class Element e => Edge e Source #

org.apache.tinkerpop.gremlin.structure.Edge interface in a TinkerPop graph.

Instances

Instances details
Edge AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

class Element v => Vertex v Source #

org.apache.tinkerpop.gremlin.structure.Vertex interface in a TinkerPop graph.

Instances

Instances details
Vertex AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

class ElementData e => Element e Source #

org.apache.tinkerpop.gremlin.structure.Element interface in a TinkerPop graph.

Since greskell-1.0.0.0, ElementData is a super-class of Element.

Associated Types

type ElementProperty e :: Type -> Type Source #

Property type of the Element. It should be of Property class.

type ElementPropertyContainer e :: Type -> Type Source #

Container type of the properties of the Element. It should be of NonEmptyLike class.

Since: 1.0.0.0

Instances

Instances details
Element AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Element AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Element (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

class ElementData e where Source #

Types that keep reference to TinkerPop graph Elements.

Since: 1.0.0.0

Methods

elementId :: e -> ElementID e Source #

ID of this Element.

elementLabel :: e -> Text Source #

Label of this Element.

Instances

Instances details
ElementData AEdge Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

ElementData AVertex Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

ElementData (AVertexProperty v) Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.Graph

newtype ElementID e Source #

ID of a graph element e (vertex, edge and vertex property).

Although the internal of ElementID is exposed, you should treat it as an opaque value. That's because it depends on graph implementation.

Since: 1.0.0.0

Constructors

ElementID 

Fields

Instances

Instances details
Functor ElementID Source #

Unsafely convert the element type.

Instance details

Defined in Data.Greskell.Graph

Methods

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

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

FromJSON (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

ToJSON (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Generic (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Associated Types

type Rep (ElementID e) :: Type -> Type #

Methods

from :: ElementID e -> Rep (ElementID e) x #

to :: Rep (ElementID e) x -> ElementID e #

Show (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Eq (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

(==) :: ElementID e -> ElementID e -> Bool #

(/=) :: ElementID e -> ElementID e -> Bool #

FromGraphSON (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Hashable (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

hashWithSalt :: Int -> ElementID e -> Int #

hash :: ElementID e -> Int #

type Rep (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

type Rep (ElementID e) = D1 ('MetaData "ElementID" "Data.Greskell.Graph" "greskell-2.0.2.0-6A5NfXFiowBD9PV5wGc6yO" 'True) (C1 ('MetaCons "ElementID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unElementID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GValue)))

unsafeCastElementID :: ElementID a -> ElementID b Source #

Unsafely cast the phantom type of ElementID.

Since: 1.0.0.0

tId :: Element a => Greskell (T a (ElementID a)) Source #

T.id token.

tKey :: (Element (p v), Property p) => Greskell (T (p v) Text) Source #

T.key token.

tLabel :: Element a => Greskell (T a Text) Source #

T.label token.

tValue :: (Element (p v), Property p) => Greskell (T (p v) v) Source #

T.value token.

cList :: Greskell Cardinality Source #

list Cardinality.

Since: 0.2.0.0

cSet :: Greskell Cardinality Source #

set Cardinality.

Since: 0.2.0.0

cSingle :: Greskell Cardinality Source #

single Cardinality.

Since: 0.2.0.0

key :: Text -> Key a b Source #

Create a Key a text.

unsafeCastKey :: Key a1 b1 -> Key a2 b2 Source #

Unsafely cast the type signature of the Key.

Since: 1.0.0.0

(=:) :: Key a b -> Greskell b -> KeyValue a Source #

Constructor operator of KeyValue.

Since: 0.2.0.0

singletonKeys :: Key a b -> Keys a Source #

Keys with a single Key.

Since: 1.0.0.0

toGremlinKeys :: Keys a -> [Text] Source #

Convert Keys to a list of Gremlin scripts.

Since: 2.0.1.0

(-:) :: Key a b -> Keys a -> Keys a infixr 5 Source #

Prepend a Key to Keys.

Since: 1.0.0.0

pathToPMap :: Path a -> PMap Multi a Source #

Convert a Path into PMap.

In the result PMap, the keys are the labels in the Path, and the values are the objects associated with the labels. The values are stored in the same order in the Path. Objects without any label are discarded.

Since: 1.1.0.0

makePathEntry Source #

Arguments

:: [AsLabel a]

labels

-> a

object

-> PathEntry a 

Make a PathEntry.

Since: 1.1.0.0

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

Instances details
MonadFail Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fail :: String -> Parser a #

MonadFix Parser

Since: aeson-2.1.0.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

mfix :: (a -> Parser a) -> 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] #

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 #

Functor Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

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 #

MonadPlus Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mzero :: Parser a #

mplus :: Parser a -> 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 #

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 #

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

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

Since: greskell-core-0.1.2.0

(.:) :: FromGraphSON a => KeyMap GValue -> Key -> Parser a #

Like Aeson's .:, but for FromGraphSON.

Since: greskell-core-1.0.0.0

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

Parse GValue into FromGraphSON.

Since: greskell-core-0.1.2.0

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

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: greskell-core-0.1.2.0

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

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

Useful to implement FromGraphSON instances for scalar types.

Since: greskell-core-0.1.2.0

class FromGraphSON a where #

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 Value in greskell is an error in most cases. To prevent you from using Value, Char (and thus Value) don't have FromGraphSON instances.

Since: greskell-core-0.1.2.0

Methods

parseGraphSON :: GValue -> Parser a #

Instances

Instances details
FromGraphSON Key

First convert to Text, and convert to Key.

Since: greskell-core-1.0.0.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Value

Call unwrapAll to remove all GraphSON wrappers.

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON All

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Any

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int16 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int32 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int64 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int8 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word16 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word32 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word64 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word8 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON IntSet 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

FromGraphSON GValue 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Scientific 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Text 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Text 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON UUID 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Integer 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Natural 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON ()

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

Methods

parseGraphSON :: GValue -> Parser () #

FromGraphSON Bool 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Double 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Float 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Int 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON Word 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON v => FromGraphSON (KeyMap v)

First convert to Map with Text key, and convert to KeyMap.

Since: greskell-core-1.0.0.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Identity a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (First a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (First a) #

FromGraphSON a => FromGraphSON (Last a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Last a) #

FromGraphSON a => FromGraphSON (First a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (First a) #

FromGraphSON a => FromGraphSON (Last a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Last a) #

FromGraphSON a => FromGraphSON (Max a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Max a) #

FromGraphSON a => FromGraphSON (Min a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Min a) #

FromGraphSON a => FromGraphSON (WrappedMonoid a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Dual a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Dual a) #

FromGraphSON a => FromGraphSON (Product a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Sum a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Sum a) #

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

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Ratio a) #

FromGraphSON v => FromGraphSON (IntMap v) 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Seq a) 
Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Seq a) #

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

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Set a) #

FromGraphSON v => FromGraphSON (AProperty v) Source #

Parse Property of GraphSON 1.0.

Instance details

Defined in Data.Greskell.Graph

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

Defined in Data.Greskell.Graph

FromGraphSON (ElementID e) Source # 
Instance details

Defined in Data.Greskell.Graph

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

Defined in Data.Greskell.Graph

Methods

parseGraphSON :: GValue -> Parser (Path a) #

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

Defined in Data.Greskell.PMap

Methods

parseGraphSON :: GValue -> Parser (Multi a) #

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

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Vector a) 
Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (NonEmpty a)

Since: greskell-core-0.1.3.0

Instance details

Defined in Data.Greskell.GraphSON

FromGraphSON a => FromGraphSON (Maybe a)

Parse GNull into Nothing.

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Maybe a) #

FromGraphSON a => FromGraphSON [a] 
Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser [a] #

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

Try Left, then Right.

Instance details

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (Either a b) #

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

Defined in Data.Greskell.GraphSON

Methods

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

(Property p, GraphSONTyped (p v), FromGraphSON (p v), FromGraphSONWithKey (p v)) => FromGraphSON (PropertyMapList p v) Source # 
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

FromGraphSON (c v) => FromGraphSON (PMap c v) Source # 
Instance details

Defined in Data.Greskell.PMap

Methods

parseGraphSON :: GValue -> Parser (PMap c v) #

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

Use parseToGMapEntry.

Instance details

Defined in Data.Greskell.GraphSON

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

Defined in Data.Greskell.GraphSON

Methods

parseGraphSON :: GValue -> Parser (HashMap k v) #

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

Use parseToFlattenedMap.

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)

Use parseToGMap.

Instance details

Defined in Data.Greskell.GraphSON

Methods

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

typedGValue' #

Arguments

:: Text

"@type" field.

-> GValueBody 
-> GValue 

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

Since: greskell-core-0.1.2.0

nonTypedGValue :: GValueBody -> GValue #

Create a GValue without "@type" field.

Since: greskell-core-0.1.2.0

data 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: greskell-core-0.1.2.0

Instances

Instances details
FromJSON GValue

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

Instance details

Defined in Data.Greskell.GraphSON.GValue

ToJSON GValue

Reconstruct Value from GValue. It preserves all GraphSON wrappers.

Instance details

Defined in Data.Greskell.GraphSON.GValue

Generic GValue 
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 #

Show GValue 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Eq GValue 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Methods

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

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

FromGraphSON GValue 
Instance details

Defined in Data.Greskell.GraphSON

Hashable GValue 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Methods

hashWithSalt :: Int -> GValue -> Int #

hash :: GValue -> Int #

type Rep GValue 
Instance details

Defined in Data.Greskell.GraphSON.GValue

type Rep GValue = D1 ('MetaData "GValue" "Data.Greskell.GraphSON.GValue" "greskell-core-1.0.0.1-31D77Wa70NqBxuO9IRRtlt" 'True) (C1 ('MetaCons "GValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GraphSON GValueBody))))

data GValueBody #

GValue without the top-level GraphSON wrapper.

Since: greskell-core-1.0.0.0

Instances

Instances details
ToJSON GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Generic GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Associated Types

type Rep GValueBody :: Type -> Type #

Show GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Eq GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

Hashable GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

type Rep GValueBody 
Instance details

Defined in Data.Greskell.GraphSON.GValue

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

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

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

Create a GraphSON with the given type ID.

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

Create a GraphSON with its type ID.

nonTypedGraphSON :: v -> GraphSON v #

Create a GraphSON without gsonType.

data GraphSON v #

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.

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

Instances details
Foldable GraphSON 
Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

foldMap :: Monoid m => (a -> m) -> GraphSON a -> 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 
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) #

Functor GraphSON 
Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

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

FromJSON v => FromJSON (GraphSON v)

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

ToJSON v => ToJSON (GraphSON v)

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

Generic (GraphSON v) 
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 #

Show v => Show (GraphSON v) 
Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

show :: GraphSON v -> String #

showList :: [GraphSON v] -> ShowS #

Eq v => Eq (GraphSON v) 
Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

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

Ord v => Ord (GraphSON v) 
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 #

Hashable v => Hashable (GraphSON v)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.Core

Methods

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

hash :: GraphSON v -> Int #

type Rep (GraphSON v) 
Instance details

Defined in Data.Greskell.GraphSON.Core

type Rep (GraphSON v) = D1 ('MetaData "GraphSON" "Data.Greskell.GraphSON.Core" "greskell-core-1.0.0.1-31D77Wa70NqBxuO9IRRtlt" '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 #

Types that have an intrinsic type ID for gsonType field.

Methods

gsonTypeFor :: a -> Text #

Type ID for gsonType.

Instances

Instances details
GraphSONTyped Int16 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Int16 -> Text #

GraphSONTyped Int32 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Int32 -> Text #

GraphSONTyped Int64 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Int64 -> Text #

GraphSONTyped Int8

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

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Int8 -> Text #

GraphSONTyped IntSet

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: IntSet -> Text #

GraphSONTyped AEdge Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AEdge -> Text #

GraphSONTyped AVertex Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AVertex -> Text #

GraphSONTyped Scientific

Map to "g:Double".

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

GraphSONTyped Char 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Char -> Text #

GraphSONTyped Double 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Double -> Text #

GraphSONTyped Float 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Float -> Text #

GraphSONTyped (IntMap v)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: IntMap v -> Text #

GraphSONTyped (Seq a)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Seq a -> Text #

GraphSONTyped (Set a)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Set a -> Text #

GraphSONTyped (AProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: AProperty v -> Text #

GraphSONTyped (AVertexProperty v) Source # 
Instance details

Defined in Data.Greskell.Graph

GraphSONTyped (Path a) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: Path a -> Text #

GraphSONTyped (Order a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: Order a -> Text #

GraphSONTyped (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: P a -> Text #

GraphSONTyped (HashSet a) 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: HashSet a -> Text #

GraphSONTyped (Vector a)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Vector a -> Text #

GraphSONTyped [a] 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: [a] -> Text #

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

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Either a b -> Text #

GraphSONTyped (Map k v)

Since: greskell-core-0.1.2.0

Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: Map k v -> Text #

GraphSONTyped (T a b) Source # 
Instance details

Defined in Data.Greskell.Graph

Methods

gsonTypeFor :: T a b -> Text #

GraphSONTyped (PMap c v) Source # 
Instance details

Defined in Data.Greskell.PMap

Methods

gsonTypeFor :: PMap c v -> Text #

GraphSONTyped (GMapEntry k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: GMapEntry k v -> Text #

GraphSONTyped (HashMap k v) 
Instance details

Defined in Data.Greskell.GraphSON.GraphSONTyped

Methods

gsonTypeFor :: HashMap k v -> Text #

GraphSONTyped (FlattenedMap c k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: FlattenedMap c k v -> Text #

GraphSONTyped (GMap c k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: GMap c k v -> Text #

toList :: forall (c :: Type -> Type -> Type) k v. (IsList (c k v), Item (c k v) ~ (k, v)) => GMap c k v -> [GMapEntry k v] #

Deconstruct GMap into a list of GMapEntrys.

singleton :: forall (c :: Type -> Type -> Type) k v. (IsList (c k v), Item (c k v) ~ (k, v)) => GMapEntry k v -> GMap c k v #

Create GMap that has the single GMapEntry.

unGMapEntry :: GMapEntry k v -> (k, v) #

Get the key-value pair from GMapEntry.

parseToGMapEntry #

Arguments

:: FromJSONKey k 
=> (s -> Parser k)

key parser

-> (s -> Parser v)

value parser

-> Either (KeyMap s) (Vector s)

input object or flattened key-values

-> Parser (GMapEntry k v) 

General parser for GMapEntry.

unGMap :: GMap c k v -> c k v #

Get the map implementation from GMap.

parseToGMap #

Arguments

:: (IsList (c k v), Item (c k v) ~ (k, v)) 
=> (s -> Parser k)

key parser

-> (s -> Parser v)

value parser

-> (KeyMap s -> Parser (c k v))

object parser

-> Either (KeyMap s) (Vector s)

input object or flattened key-values.

-> Parser (GMap c k v) 

General parser for GMap.

parseToFlattenedMap #

Arguments

:: forall (c :: Type -> Type -> Type) k v s. (IsList (c k v), Item (c k v) ~ (k, v)) 
=> (s -> Parser k)

key parser

-> (s -> Parser v)

value parser

-> Vector s

input vector of flattened key-values.

-> Parser (FlattenedMap c k v) 

General parser for FlattenedMap.

newtype FlattenedMap (c :: Type -> Type -> Type) k v #

JSON encoding of a map as an array of flattened key-value pairs.

ToJSON instance of this type encodes the internal map as an array of keys and values. FromJSON instance of this type parses that flattened map.

  • type c: container type for a map (e.g. Map and HashMap).
  • type k: key of the map.
  • type v: value of the map.

Constructors

FlattenedMap 

Fields

Instances

Instances details
Foldable (c k) => Foldable (FlattenedMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fold :: Monoid m => FlattenedMap c k m -> m #

foldMap :: Monoid m => (a -> m) -> FlattenedMap c k a -> m #

foldMap' :: Monoid m => (a -> m) -> FlattenedMap c k a -> m #

foldr :: (a -> b -> b) -> b -> FlattenedMap c k a -> b #

foldr' :: (a -> b -> b) -> b -> FlattenedMap c k a -> b #

foldl :: (b -> a -> b) -> b -> FlattenedMap c k a -> b #

foldl' :: (b -> a -> b) -> b -> FlattenedMap c k a -> b #

foldr1 :: (a -> a -> a) -> FlattenedMap c k a -> a #

foldl1 :: (a -> a -> a) -> FlattenedMap c k a -> a #

toList :: FlattenedMap c k a -> [a] #

null :: FlattenedMap c k a -> Bool #

length :: FlattenedMap c k a -> Int #

elem :: Eq a => a -> FlattenedMap c k a -> Bool #

maximum :: Ord a => FlattenedMap c k a -> a #

minimum :: Ord a => FlattenedMap c k a -> a #

sum :: Num a => FlattenedMap c k a -> a #

product :: Num a => FlattenedMap c k a -> a #

Traversable (c k) => Traversable (FlattenedMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

traverse :: Applicative f => (a -> f b) -> FlattenedMap c k a -> f (FlattenedMap c k b) #

sequenceA :: Applicative f => FlattenedMap c k (f a) -> f (FlattenedMap c k a) #

mapM :: Monad m => (a -> m b) -> FlattenedMap c k a -> m (FlattenedMap c k b) #

sequence :: Monad m => FlattenedMap c k (m a) -> m (FlattenedMap c k a) #

Functor (c k) => Functor (FlattenedMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fmap :: (a -> b) -> FlattenedMap c k a -> FlattenedMap c k b #

(<$) :: a -> FlattenedMap c k b -> FlattenedMap c k a #

(FromJSON k, FromJSON v, IsList (c k v), Item (c k v) ~ (k, v)) => FromJSON (FlattenedMap c k v)

Use parseToFlattenedMap.

Instance details

Defined in Data.Greskell.GMap

(ToJSON k, ToJSON v, IsList (c k v), Item (c k v) ~ (k, v)) => ToJSON (FlattenedMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Show (c k v) => Show (FlattenedMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

showsPrec :: Int -> FlattenedMap c k v -> ShowS #

show :: FlattenedMap c k v -> String #

showList :: [FlattenedMap c k v] -> ShowS #

Eq (c k v) => Eq (FlattenedMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

(==) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

(/=) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

Ord (c k v) => Ord (FlattenedMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

compare :: FlattenedMap c k v -> FlattenedMap c k v -> Ordering #

(<) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

(<=) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

(>) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

(>=) :: FlattenedMap c k v -> FlattenedMap c k v -> Bool #

max :: FlattenedMap c k v -> FlattenedMap c k v -> FlattenedMap c k v #

min :: FlattenedMap c k v -> FlattenedMap c k v -> FlattenedMap c k v #

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

Use parseToFlattenedMap.

Instance details

Defined in Data.Greskell.GraphSON

GraphSONTyped (FlattenedMap c k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: FlattenedMap c k v -> Text #

data GMap (c :: Type -> Type -> Type) k v #

Haskell representation of g:Map type.

GraphSON v1 and v2 encode Java Map type as a JSON Object, while GraphSON v3 encodes it as an array of flattened keys and values (like FlattenedMap.) GMap type handles both encoding schemes.

  • type c: container type for a map (e.g. Map and HashMap).
  • type k: key of the map.
  • type v: value of the map.

Constructors

GMap 

Fields

Instances

Instances details
Foldable (c k) => Foldable (GMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fold :: Monoid m => GMap c k m -> m #

foldMap :: Monoid m => (a -> m) -> GMap c k a -> m #

foldMap' :: Monoid m => (a -> m) -> GMap c k a -> m #

foldr :: (a -> b -> b) -> b -> GMap c k a -> b #

foldr' :: (a -> b -> b) -> b -> GMap c k a -> b #

foldl :: (b -> a -> b) -> b -> GMap c k a -> b #

foldl' :: (b -> a -> b) -> b -> GMap c k a -> b #

foldr1 :: (a -> a -> a) -> GMap c k a -> a #

foldl1 :: (a -> a -> a) -> GMap c k a -> a #

toList :: GMap c k a -> [a] #

null :: GMap c k a -> Bool #

length :: GMap c k a -> Int #

elem :: Eq a => a -> GMap c k a -> Bool #

maximum :: Ord a => GMap c k a -> a #

minimum :: Ord a => GMap c k a -> a #

sum :: Num a => GMap c k a -> a #

product :: Num a => GMap c k a -> a #

Traversable (c k) => Traversable (GMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

traverse :: Applicative f => (a -> f b) -> GMap c k a -> f (GMap c k b) #

sequenceA :: Applicative f => GMap c k (f a) -> f (GMap c k a) #

mapM :: Monad m => (a -> m b) -> GMap c k a -> m (GMap c k b) #

sequence :: Monad m => GMap c k (m a) -> m (GMap c k a) #

Functor (c k) => Functor (GMap c k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fmap :: (a -> b) -> GMap c k a -> GMap c k b #

(<$) :: a -> GMap c k b -> GMap c k a #

(FromJSON k, FromJSON v, IsList (c k v), Item (c k v) ~ (k, v), FromJSON (c k v)) => FromJSON (GMap c k v)

Use parseToGMap.

Instance details

Defined in Data.Greskell.GMap

Methods

parseJSON :: Value -> Parser (GMap c k v) #

parseJSONList :: Value -> Parser [GMap c k v] #

(ToJSON k, ToJSON v, IsList (c k v), Item (c k v) ~ (k, v), ToJSON (c k v)) => ToJSON (GMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

toJSON :: GMap c k v -> Value #

toEncoding :: GMap c k v -> Encoding #

toJSONList :: [GMap c k v] -> Value #

toEncodingList :: [GMap c k v] -> Encoding #

Show (c k v) => Show (GMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

showsPrec :: Int -> GMap c k v -> ShowS #

show :: GMap c k v -> String #

showList :: [GMap c k v] -> ShowS #

Eq (c k v) => Eq (GMap c k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

(==) :: GMap c k v -> GMap c k v -> Bool #

(/=) :: GMap c k v -> GMap c k v -> Bool #

AsIterator (GMap c k v) 
Instance details

Defined in Data.Greskell.AsIterator

Associated Types

type IteratorItem (GMap c k v) #

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

Use parseToGMap.

Instance details

Defined in Data.Greskell.GraphSON

Methods

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

GraphSONTyped (GMap c k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: GMap c k v -> Text #

type IteratorItem (GMap c k v) 
Instance details

Defined in Data.Greskell.AsIterator

type IteratorItem (GMap c k v) = GMapEntry k v

data GMapEntry k v #

Haskell representation of Map.Entry type.

Basically GraphSON encodes Java's Map.Entry type as if it were a Map with a single entry. Thus its encoded form is either a JSON object or a flattened key-values, as explained in GMap.

In old versions of TinkerPop, Map.Entry is encoded as a JSON object with "key" and "value" fields. FromJSON instance of GMapEntry supports this format as well, but ToJSON instance doesn't support it.

Constructors

GMapEntry 

Fields

Instances

Instances details
Foldable (GMapEntry k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fold :: Monoid m => GMapEntry k m -> m #

foldMap :: Monoid m => (a -> m) -> GMapEntry k a -> m #

foldMap' :: Monoid m => (a -> m) -> GMapEntry k a -> m #

foldr :: (a -> b -> b) -> b -> GMapEntry k a -> b #

foldr' :: (a -> b -> b) -> b -> GMapEntry k a -> b #

foldl :: (b -> a -> b) -> b -> GMapEntry k a -> b #

foldl' :: (b -> a -> b) -> b -> GMapEntry k a -> b #

foldr1 :: (a -> a -> a) -> GMapEntry k a -> a #

foldl1 :: (a -> a -> a) -> GMapEntry k a -> a #

toList :: GMapEntry k a -> [a] #

null :: GMapEntry k a -> Bool #

length :: GMapEntry k a -> Int #

elem :: Eq a => a -> GMapEntry k a -> Bool #

maximum :: Ord a => GMapEntry k a -> a #

minimum :: Ord a => GMapEntry k a -> a #

sum :: Num a => GMapEntry k a -> a #

product :: Num a => GMapEntry k a -> a #

Traversable (GMapEntry k) 
Instance details

Defined in Data.Greskell.GMap

Methods

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

sequenceA :: Applicative f => GMapEntry k (f a) -> f (GMapEntry k a) #

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

sequence :: Monad m => GMapEntry k (m a) -> m (GMapEntry k a) #

Functor (GMapEntry k) 
Instance details

Defined in Data.Greskell.GMap

Methods

fmap :: (a -> b) -> GMapEntry k a -> GMapEntry k b #

(<$) :: a -> GMapEntry k b -> GMapEntry k a #

(FromJSON k, FromJSONKey k, FromJSON v) => FromJSON (GMapEntry k v)

Use parseToGMapEntry.

Instance details

Defined in Data.Greskell.GMap

(ToJSON k, ToJSONKey k, Ord k, ToJSON v) => ToJSON (GMapEntry k v) 
Instance details

Defined in Data.Greskell.GMap

(Show k, Show v) => Show (GMapEntry k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

showsPrec :: Int -> GMapEntry k v -> ShowS #

show :: GMapEntry k v -> String #

showList :: [GMapEntry k v] -> ShowS #

(Eq k, Eq v) => Eq (GMapEntry k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

(==) :: GMapEntry k v -> GMapEntry k v -> Bool #

(/=) :: GMapEntry k v -> GMapEntry k v -> Bool #

(Ord k, Ord v) => Ord (GMapEntry k v) 
Instance details

Defined in Data.Greskell.GMap

Methods

compare :: GMapEntry k v -> GMapEntry k v -> Ordering #

(<) :: GMapEntry k v -> GMapEntry k v -> Bool #

(<=) :: GMapEntry k v -> GMapEntry k v -> Bool #

(>) :: GMapEntry k v -> GMapEntry k v -> Bool #

(>=) :: GMapEntry k v -> GMapEntry k v -> Bool #

max :: GMapEntry k v -> GMapEntry k v -> GMapEntry k v #

min :: GMapEntry k v -> GMapEntry k v -> GMapEntry k v #

AsIterator (GMapEntry k v) 
Instance details

Defined in Data.Greskell.AsIterator

Associated Types

type IteratorItem (GMapEntry k v) #

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

Use parseToGMapEntry.

Instance details

Defined in Data.Greskell.GraphSON

GraphSONTyped (GMapEntry k v)

Map to "g:Map".

Instance details

Defined in Data.Greskell.GMap

Methods

gsonTypeFor :: GMapEntry k v -> Text #

type IteratorItem (GMapEntry k v) 
Instance details

Defined in Data.Greskell.AsIterator