greskell-0.2.0.3: Haskell binding for Gremlin graph query language

MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Greskell.GTraversal

Contents

Description

This module defines GTraversal, greskell counterpart of GraphTraversal class object, and a DSL of composing graph traversal steps.

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

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 #

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

ProjectionLike (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type GreskellReturn (GTraversal c 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 (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 ProjectionLikeEnd (GTraversal Filter 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
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 Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Filter 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 ProjectionLikeStart (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 ProjectionLikeEnd (Greskell (GraphTraversal Transform 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 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.

Minimal complete definition

toGTraversal, liftWalk

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.

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

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 #

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

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 #

WalkType c => Category (Walk c :: * -> * -> *) Source #

id is gIdentity.

Instance details

Defined in Data.Greskell.GTraversal

Methods

id :: Walk c a a #

(.) :: Walk c 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 #

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 #

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 #

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

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Transform s e) :: * Source #

type ProjectionLikeEnd (Walk Transform s e) :: * Source #

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Filter s e) :: * Source #

type ProjectionLikeEnd (Walk Filter s e) :: * Source #

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

Defined in Data.Greskell.GTraversal

type GreskellReturn (Walk c s e) = GraphTraversal c s e
type ProjectionLikeStart (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 ProjectionLikeEnd (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

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

Defined in Data.Greskell.GTraversal

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.

Instances
WalkType SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType Filter 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
WalkType Filter Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType p => Split Filter p Source # 
Instance details

Defined in Data.Greskell.GTraversal

WalkType c => Lift Filter c Source # 
Instance details

Defined in Data.Greskell.GTraversal

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

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Filter s e) :: * Source #

type ProjectionLikeEnd (Walk Filter s e) :: * Source #

ProjectionLike (GTraversal 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 (Greskell (GraphTraversal 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

type ProjectionLikeStart (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 ProjectionLikeEnd (GTraversal 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
WalkType 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

Lift Transform SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform Transform Source # 
Instance details

Defined in Data.Greskell.GTraversal

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

Defined in Data.Greskell.GTraversal

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Transform s e) :: * Source #

type ProjectionLikeEnd (Walk Transform s e) :: * Source #

ProjectionLike (GTraversal 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 (Greskell (GraphTraversal 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

type ProjectionLikeStart (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 ProjectionLikeEnd (GTraversal 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
WalkType 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

Lift SideEffect SideEffect Source # 
Instance details

Defined in Data.Greskell.GTraversal

Lift Transform SideEffect Source # 
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.

Instances
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

WalkType c => Lift Filter c 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.

Instances
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

WalkType p => Split Filter p Source # 
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

>>> toGremlin $ source "g"
"g"

sV Source #

Arguments

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

vertex IDs

-> Greskell GraphTraversalSource 
-> GTraversal Transform () v 

.V() method on GraphTraversalSource.

sV' :: [Greskell GValue] -> Greskell GraphTraversalSource -> GTraversal Transform () AVertex Source #

Monomorphic version of sV.

>>> toGremlin (source "g" & sV' (map gvalueInt ([1,2,3] :: [Int])))
"g.V(1,2,3)"

sE Source #

Arguments

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

edge IDs

-> Greskell GraphTraversalSource 
-> GTraversal Transform () e 

.E() method on GraphTraversalSource.

sE' :: [Greskell GValue] -> Greskell GraphTraversalSource -> GTraversal Transform () AEdge Source #

Monomorphic version of sE.

>>> toGremlin (source "g" & sE' (map gvalueInt ([1] :: [Int])))
"g.E(1)"

sAddV Source #

Arguments

:: Vertex v 
=> Greskell Text

vertex label

-> Greskell GraphTraversalSource 
-> GTraversal SideEffect () v 

.addV() method on GraphTraversalSource.

Since: greskell-0.2.0.0

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

Monomorphic version of sAddV.

>>> toGremlin (source "g" & sAddV' "person")
"g.addV(\"person\")"

Since: greskell-0.2.0.0

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.

>>> toGremlin (source "g" & sV' [] &. gValues ["age"])
"g.V().values(\"age\")"

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

Same as &. with arguments flipped.

>>> toGremlin (gValues ["age"] $. sV' [] $ source "g")
"g.V().values(\"age\")"

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

Unsafely create GTraversal from the given raw Gremlin script.

>>> toGremlin $ unsafeGTraversal "g.V().count()"
"g.V().count()"

Walk/Steps

Functions for TinkerPop graph traversal steps. For now greskell does not cover all graph traversal steps. If you want some steps added, just open an issue.

There may be multiple versions of Haskell functions for a single step. This is because Gremlin steps are too polymorphic for Haskell. greskell should be type-safe so that incorrect combination of steps is detected in compile time.

Low-level functions

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.

>>> toGremlin (source "g" & sV' [] &. unsafeWalk "valueMap" ["'foo'", "'bar'"])
"g.V().valueMap('foo','bar')"

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.

>>> toGremlin (source "g" & sV' [] &. modulateWith (unsafeWalk "path" []) [unsafeWalk "by" ["'name'"], unsafeWalk "by" ["'age'"]])
"g.V().path().by('name').by('age')"

Filter steps

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.

>>> toGremlin (source "g" & sV' [] &. gFilter (gOut' ["knows"]))
"g.V().filter(__.out(\"knows\"))"

Has steps

gHas1 Source #

Arguments

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

property key

-> Walk c s s 

.has step with one argument.

>>> toGremlin (source "g" & sV' [] &. gHas1 "age")
"g.V().has(\"age\")"

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.

>>> toGremlin (source "g" & sV' [] &. gHas2 "age" (31 :: Greskell Int))
"g.V().has(\"age\",31)"

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.

>>> toGremlin (source "g" & sV' [] &. gHas2P "age" (pBetween (30 :: Greskell Int) 40))
"g.V().has(\"age\",P.between(30,40))"

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.

>>> toGremlin (source "g" & sV' [] &. gHasLabel "person")
"g.V().hasLabel(\"person\")"

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.

>>> toGremlin (source "g" & sV' [] &. gHasLabelP (pEq "person"))
"g.V().hasLabel(P.eq(\"person\"))"

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.

>>> toGremlin (source "g" & sV' [] &. gHasId (gvalueInt $ (7 :: Int)))
"g.V().hasId(7)"

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.

>>> toGremlin (source "g" & sV' [] &. gHasIdP (pLte $ gvalueInt (100 :: Int)))
"g.V().hasId(P.lte(100))"

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.

>>> toGremlin (source "g" & sV' [] &. gProperties [] &. gHasKey "age")
"g.V().properties().hasKey(\"age\")"

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.

>>> toGremlin (source "g" & sV' [] &. gProperties ["age"] &. gHasValue (32 :: Greskell Int))
"g.V().properties(\"age\").hasValue(32)"

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.

>>> toGremlin (source "g" & sV' [] &. gProperties ["age"] &. gHasValueP (pBetween (30 :: Greskell Int) 40))
"g.V().properties(\"age\").hasValue(P.between(30,40))"

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

Monomorphic version of gHasValueP.

Logic steps

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

.and step.

>>> toGremlin (source "g" & sV' [] &. gAnd [gOut' ["knows"], gHas1 "age"])
"g.V().and(__.out(\"knows\"),__.has(\"age\"))"

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

.or step.

>>> toGremlin (source "g" & sV' [] &. gOr [gOut' ["knows"], gHas1 "age"])
"g.V().or(__.out(\"knows\"),__.has(\"age\"))"

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

.not step.

>>> toGremlin (source "g" & sV' [] &. gNot (gOut' ["knows"]))
"g.V().not(__.out(\"knows\"))"

Sorting steps

gOrder Source #

Arguments

:: [ByComparator s]

following .by steps.

-> Walk Transform s s 

.order step.

>>> let key_age = ("age" :: Key AVertex Int)
>>> toGremlin (source "g" & sV' [] &. gOrder [gBy1 key_age])
"g.V().order().by(\"age\")"
>>> toGremlin (source "g" & sV' [] &. gOrder [gBy2 key_age oDecr, gBy1 tId])
"g.V().order().by(\"age\",Order.decr).by(T.id)"
>>> toGremlin (source "g" & sV' [] &. gOrder [gBy2 (gOut' ["knows"] >>> gCount) oIncr, gBy2 tId oIncr])
"g.V().order().by(__.out(\"knows\").count(),Order.incr).by(T.id,Order.incr)"

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

>>> toGremlin (source "g" & sV' [] &. gOrder ["age"])
"g.V().order().by(\"age\")"

Paging steps

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.

>>> toGremlin (source "g" & sV' [] &. gRange 0 100)
"g.V().range(0,100)"

Transformation steps

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

.flatMap step.

.flatMap step is a Transform step even if the child walk is Filter type. This is because .flatMap step always modifies the path of the Traverser.

>>> toGremlin (source "g" & sV' [] &. gFlatMap (gOut' ["knows"] >>> gOut' ["created"]))
"g.V().flatMap(__.out(\"knows\").out(\"created\"))"

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: greskell-0.2.0.0

gV' :: [Greskell GValue] -> Walk Transform s AVertex Source #

Monomorphic version of gV.

Since: greskell-0.2.0.0

Accessor steps

gValues Source #

Arguments

:: Element s 
=> [Key s e]

property keys

-> Walk Transform s e 

.values step.

>>> toGremlin (source "g" & sV' [] &. gValues ["name", "age"])
"g.V().values(\"name\",\"age\")"

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

.properties step.

>>> toGremlin (source "g" & sV' [] &. gProperties ["age"])
"g.V().properties(\"age\")"

Summarizing steps

gFold :: Walk Transform a [a] Source #

.fold step.

gCount :: Walk Transform a Int Source #

.count step.

Graph traversal steps

gOut Source #

Arguments

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

edge labels

-> Walk Transform v1 v2 

.out step

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

Monomorphic version of gOut.

>>> toGremlin (source "g" & sV' [gvalueInt (8 :: Int)] &. gOut' ["knows"])
"g.V(8).out(\"knows\")"

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

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.

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.

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.

>>> toGremlin (source "g" & sV' [] & liftWalk &. gHas2 "name" "marko" &. gSideEffect' (gAddV' "toshio"))
"g.V().has(\"name\",\"marko\").sideEffect(__.addV(\"toshio\"))"

Graph manipulation steps

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.

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.

>>> let key_name = "name" :: Key AVertex Text
>>> toGremlin (source "g" & sV' [] & liftWalk &. gAddE' "knows" (gFrom $ gV' [] >>> gHas2 key_name "marko"))
"g.V().addE(\"knows\").from(__.V().has(\"name\",\"marko\"))"
>>> toGremlin (source "g" & sV' [] &. gHas2 key_name "marko" & liftWalk &. gAddE' "knows" (gTo $ gV' []))
"g.V().has(\"name\",\"marko\").addE(\"knows\").to(__.V())"

Since: greskell-0.2.0.0

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

Monomorphic version of gAddE

Since: greskell-0.2.0.0

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: greskell-0.2.0.0

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

.from step with a traversal.

Since: greskell-0.2.0.0

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

.to step with a traversal.

Since: greskell-0.2.0.0

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

.drop step on Element.

>>> toGremlin (source "g" & sV' [] &. gHas2 "name" "marko" & liftWalk &. gDrop)
"g.V().has(\"name\",\"marko\").drop()"

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

.drop step on Property.

>>> toGremlin (source "g" & sE' [] &. gProperties ["weight"] & liftWalk &. gDropP)
"g.E().properties(\"weight\").drop()"

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.

>>> toGremlin (source "g" & sV' [] & liftWalk &. gProperty "age" (20 :: Greskell Int))
"g.V().property(\"age\",20)"

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

>>> let key_location = "location" :: Key AVertex Text
>>> let key_since = "since" :: Key (AVertexProperty Text) Text
>>> let key_score = "score" :: Key (AVertexProperty Text) Int
>>> toGremlin (source "g" & sV' [] & liftWalk &. gPropertyV (Just cList) key_location "New York" [key_since =: "2012-09-23", key_score =: 8])
"g.V().property(list,\"location\",\"New York\",\"since\",\"2012-09-23\",\"score\",8)"

Since: greskell-0.2.0.0

.by steps

.by steps are not Walk on their own because they are always used in conjunction with other steps like gOrder.

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

Associated Types

type ProjectionLikeStart (ByProjection s e) :: * Source #

type ProjectionLikeEnd (ByProjection s e) :: * Source #

type ProjectionLikeStart (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

type ProjectionLikeEnd (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
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 (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 (GraphTraversal Transform s e)) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (Greskell (GraphTraversal Filter 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 (ByProjection s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (ByProjection s e) :: * Source #

type ProjectionLikeEnd (ByProjection s e) :: * Source #

ProjectionLike (Walk Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Transform s e) :: * Source #

type ProjectionLikeEnd (Walk Transform s e) :: * Source #

ProjectionLike (Walk Filter s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

Associated Types

type ProjectionLikeStart (Walk Filter s e) :: * Source #

type ProjectionLikeEnd (Walk Filter s e) :: * Source #

ProjectionLike (GTraversal Transform s e) Source # 
Instance details

Defined in Data.Greskell.GTraversal

ProjectionLike (GTraversal Filter 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
IsString (ByComparator s) Source #

ByComparatorProj by literal property key.

Instance details

Defined in Data.Greskell.GTraversal

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.