greskell-2.0.3.0: Haskell binding for Gremlin graph query language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Greskell.GTraversal.Gen

Description

This module is experimental. It may have breaking changes in future.

This module has Gremlin traversals defined in GTraversal generalized on the walk type. It may save you from calling liftWalk manually.

Since: 2.0.3.0

Synopsis

Types

GraphTraversal and others

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

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

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

data GraphTraversalSource Source #

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

Walk types

class WalkType t Source #

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

Minimal complete definition

showWalkType

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

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

class Lift from to Source #

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

Minimal complete definition

showLift

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

class Split c p 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.

Minimal complete definition

showSplit

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

GraphTraversalSource

source Source #

Arguments

:: Text

variable name of GraphTraversalSource

-> Greskell GraphTraversalSource 

Create GraphTraversalSource from a varible name in Gremlin

GTraversal

(&.) :: 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

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

Unsafely create GTraversal from the given raw Gremlin script.

Walk/Steps

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.

Filter steps

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

.identity step.

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

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

.simplePath step.

Since: 1.0.1.0

Is step

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

.is step of simple equality.

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

Has steps

gHas1 Source #

Arguments

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

property key

-> Walk c s s 

.has step with one argument.

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

.has step with two arguments.

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.

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

.hasLabel step.

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.

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

.hasId step.

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.

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.

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.

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.

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.

Logic steps

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.

Where step

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

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

Sorting steps

Paging steps

Repeat step

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

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

Branching steps

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

Barrier steps

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

gDedupN :: (WalkType c, Lift Transform c) => AsLabel a -> [AsLabel a] -> Maybe (ByProjection a e) -> Walk c s s Source #

Transformation steps

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

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

As step

gAs :: (WalkType c, Lift Transform c) => AsLabel a -> Walk c a a Source #

Accessor steps

gValues :: (Element s, WalkType c, Lift Transform c) => [Key s e] -> Walk c s e Source #

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

gPathBy :: (WalkType c, Lift Transform c) => ByProjection a b -> [ByProjection a b] -> Walk c s (Path b) Source #

Summarizing steps

gFold :: (WalkType c, Lift Transform c) => Walk c a [a] Source #

Graph traversal steps

gOut :: (Vertex v1, Vertex v2, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v1 v2 Source #

gOutE :: (Vertex v, Edge e, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v e Source #

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

gIn :: (Vertex v1, Vertex v2, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v1 v2 Source #

gInE :: (Vertex v, Edge e, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v e Source #

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

Match step

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.

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

data MatchResult Source #

Result of .match step.

Since: 1.2.0.0

Side-effect steps

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.

Graph manipulation steps

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

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

gFrom :: (ToGTraversal g, WalkType c, Lift c Transform) => g c s e -> AddAnchor s e Source #

gTo :: (ToGTraversal g, WalkType c, Lift c Transform) => g c s e -> AddAnchor s e Source #

gDropP :: (Property p, WalkType c, Lift SideEffect c) => Walk c (p a) (p a) Source #

gProperty :: (Element e, WalkType c, Lift SideEffect c) => Key e v -> Greskell v -> Walk c e e Source #

gPropertyV :: (Vertex e, vp ~ ElementProperty e, Property vp, Element (vp v), WalkType c, Lift SideEffect c) => Maybe (Greskell Cardinality) -> Key e v -> Greskell v -> [KeyValue (vp v)] -> Walk c e e Source #

.by steps

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 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 LabeledByProjection s where Source #

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

Since: 1.0.0.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.

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

.by step associated with an AsLabel.

Since: 1.0.0.0