| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Greskell.GTraversal
Contents
Description
This module defines GTraversal, greskell counterpart of
GraphTraversal class object, and a DSL of composing graph
traversal steps.
- newtype GTraversal c s e = GTraversal {
- unGTraversal :: Greskell (GraphTraversal c s e)
- data GraphTraversal c s e
- class ToGTraversal g where
- data Walk c s e
- data GraphTraversalSource
- class WalkType t
- data Filter
- data Transform
- data SideEffect
- class Lift from to
- class Split c p
- source :: Text -> Greskell GraphTraversalSource
- sV :: Vertex v => [Greskell (ElementID v)] -> Greskell GraphTraversalSource -> GTraversal Transform () v
- sV' :: [Greskell Value] -> Greskell GraphTraversalSource -> GTraversal Transform () AVertex
- sE :: Edge e => [Greskell (ElementID e)] -> Greskell GraphTraversalSource -> GTraversal Transform () e
- sE' :: [Greskell Value] -> Greskell GraphTraversalSource -> GTraversal Transform () AEdge
- (&.) :: GTraversal c a b -> Walk c b d -> GTraversal c a d
- ($.) :: Walk c b d -> GTraversal c a b -> GTraversal c a d
- unsafeGTraversal :: Text -> GTraversal c s e
- unsafeWalk :: WalkType c => Text -> [Text] -> Walk c s e
- modulateWith :: WalkType c => Walk c s e -> [Walk c e e] -> Walk c s e
- gIdentity :: WalkType c => Walk c s s
- gIdentity' :: Walk Filter s s
- gFilter :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s
- gHas1 :: (WalkType c, Element s) => Key s v -> Walk c s s
- gHas1' :: Element s => Key s v -> Walk Filter s s
- gHas2 :: (WalkType c, Element s) => Key s v -> Greskell v -> Walk c s s
- gHas2' :: Element s => Key s v -> Greskell v -> Walk Filter s s
- gHas2P :: (WalkType c, Element s) => Key s v -> Greskell (P v) -> Walk c s s
- gHas2P' :: Element s => Key s v -> Greskell (P v) -> Walk Filter s s
- gHasLabel :: (Element s, WalkType c) => Greskell Text -> Walk c s s
- gHasLabel' :: Element s => Greskell Text -> Walk Filter s s
- gHasLabelP :: (Element s, WalkType c) => Greskell (P Text) -> Walk c s s
- gHasLabelP' :: Element s => Greskell (P Text) -> Walk Filter s s
- gHasId :: (Element s, WalkType c) => Greskell (ElementID s) -> Walk c s s
- gHasId' :: Element s => Greskell (ElementID s) -> Walk Filter s s
- gHasIdP :: (Element s, WalkType c) => Greskell (P (ElementID s)) -> Walk c s s
- gHasIdP' :: Element s => Greskell (P (ElementID s)) -> Walk Filter s s
- gHasKey :: (Element (p v), Property p, WalkType c) => Greskell Text -> Walk c (p v) (p v)
- gHasKey' :: (Element (p v), Property p) => Greskell Text -> Walk Filter (p v) (p v)
- gHasKeyP :: (Element (p v), Property p, WalkType c) => Greskell (P Text) -> Walk c (p v) (p v)
- gHasKeyP' :: (Element (p v), Property p) => Greskell (P Text) -> Walk Filter (p v) (p v)
- gHasValue :: (Element (p v), Property p, WalkType c) => Greskell v -> Walk c (p v) (p v)
- gHasValue' :: (Element (p v), Property p) => Greskell v -> Walk Filter (p v) (p v)
- gHasValueP :: (Element (p v), Property p, WalkType c) => Greskell (P v) -> Walk c (p v) (p v)
- gHasValueP' :: (Element (p v), Property p) => Greskell (P v) -> Walk Filter (p v) (p v)
- gAnd :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => [g c s e] -> Walk p s s
- gOr :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => [g c s e] -> Walk p s s
- gNot :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s
- gOrder :: [ByComparator s] -> Walk Transform s s
- gRange :: Greskell Int -> Greskell Int -> Walk Transform s s
- gFlatMap :: ToGTraversal g => g Transform s e -> Walk Transform s e
- gValues :: Element s => [Key s e] -> Walk Transform s e
- gProperties :: (Element s, Property p, ElementProperty s ~ p) => [Key s v] -> Walk Transform s (p v)
- gFold :: Walk Transform a [a]
- gCount :: Walk Transform a Int
- gOut :: (Vertex v1, Vertex v2) => [Greskell Text] -> Walk Transform v1 v2
- gOut' :: Vertex v => [Greskell Text] -> Walk Transform v AVertex
- gOutE :: (Vertex v, Edge e) => [Greskell Text] -> Walk Transform v e
- gOutE' :: Vertex v => [Greskell Text] -> Walk Transform v AEdge
- gIn :: (Vertex v1, Vertex v2) => [Greskell Text] -> Walk Transform v1 v2
- gIn' :: Vertex v => [Greskell Text] -> Walk Transform v AVertex
- gInE :: (Vertex v, Edge e) => [Greskell Text] -> Walk Transform v e
- gInE' :: Vertex v => [Greskell Text] -> Walk Transform v AEdge
- gSideEffect :: (ToGTraversal g, WalkType c, WalkType p, Split c p) => g c s e -> Walk p s s
- gSideEffect' :: (ToGTraversal g, WalkType c, Split c SideEffect) => g c s e -> Walk SideEffect s s
- gAddV :: Vertex v => Greskell Text -> Walk SideEffect a v
- gAddV' :: Greskell Text -> Walk SideEffect a AVertex
- gDrop :: Element e => Walk SideEffect e e
- gDropP :: Property p => Walk SideEffect (p a) (p a)
- data ByProjection s e where
- ByProjection :: (ProjectionLike p, ToGreskell p) => p -> ByProjection (ProjectionLikeStart p) (ProjectionLikeEnd p)
- class ProjectionLike p where
- type ProjectionLikeStart p
- type ProjectionLikeEnd p
- data ByComparator s where
- ByComparatorProj :: ByProjection s e -> ByComparator s
- ByComparatorComp :: Comparator comp => Greskell comp -> ByComparator (CompareArg comp)
- ByComparatorProjComp :: Comparator comp => ByProjection s (CompareArg comp) -> Greskell comp -> ByComparator s
- gBy :: (ProjectionLike p, ToGreskell p) => p -> ByProjection (ProjectionLikeStart p) (ProjectionLikeEnd p)
- gBy1 :: (ProjectionLike p, ToGreskell p) => p -> ByComparator (ProjectionLikeStart p)
- gBy2 :: (ProjectionLike p, ToGreskell p, Comparator comp, ProjectionLikeEnd p ~ CompareArg comp) => p -> Greskell comp -> ByComparator (ProjectionLikeStart p)
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 | |
Fields
| |
Instances
| ToGTraversal GTraversal Source # | |
| Bifunctor (GTraversal c) Source # | Unsafely convert input and output types. |
| Functor (GTraversal c s) Source # | Unsafely convert output type. |
| Show (GTraversal c s e) Source # | |
| ToGreskell (GTraversal c s e) Source # | Unwrap |
| ProjectionLike (GTraversal Transform s e) Source # | |
| ProjectionLike (GTraversal Filter s e) Source # | |
| type GreskellReturn (GTraversal c s e) Source # | |
| type ProjectionLikeStart (GTraversal Transform s e) Source # | |
| type ProjectionLikeStart (GTraversal Filter s e) Source # | |
| type ProjectionLikeEnd (GTraversal Transform s e) Source # | |
| type ProjectionLikeEnd (GTraversal Filter s e) Source # | |
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. |
| ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # | |
| ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # | |
| Functor (GraphTraversal c s) Source # | Unsafely convert output type. |
| Show (GraphTraversal c s e) Source # | |
| type ProjectionLikeStart (Greskell (GraphTraversal Transform s e)) Source # | |
| type ProjectionLikeStart (Greskell (GraphTraversal Filter s e)) Source # | |
| type ProjectionLikeEnd (Greskell (GraphTraversal Transform s e)) Source # | |
| type ProjectionLikeEnd (Greskell (GraphTraversal Filter s e)) Source # | |
class ToGTraversal g where Source #
Types that can convert to GTraversal.
Minimal complete definition
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 |
| ToGTraversal GTraversal 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 |
| Bifunctor (Walk c) Source # | Unsafely convert input and output types. |
| WalkType c => Category * (Walk c) Source # | |
| Functor (Walk c s) Source # | Unsafely convert output type |
| Show (Walk c s e) Source # | |
| WalkType c => Semigroup (Walk c s s) Source # | |
| WalkType c => Monoid (Walk c s s) Source # | |
| WalkType c => ToGreskell (Walk c s e) Source # | The |
| ProjectionLike (Walk Transform s e) Source # | |
| ProjectionLike (Walk Filter s e) Source # | |
| type GreskellReturn (Walk c s e) Source # | |
| type ProjectionLikeStart (Walk Transform s e) Source # | |
| type ProjectionLikeStart (Walk Filter s e) Source # | |
| type ProjectionLikeEnd (Walk Transform s e) Source # | |
| type ProjectionLikeEnd (Walk Filter s e) Source # | |
data GraphTraversalSource Source #
GraphTraversalSource class object of TinkerPop. It is a factory
object of GraphTraversals.
Instances
Walk types
Class of phantom type markers to describe the effect of the walk/traversals.
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.
(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 # | |
| WalkType p => Split Filter p Source # | |
| WalkType c => Lift Filter c Source # | |
| ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # | |
| ProjectionLike (Walk Filter s e) Source # | |
| ProjectionLike (GTraversal Filter s e) Source # | |
| type ProjectionLikeStart (Greskell (GraphTraversal Filter s e)) Source # | |
| type ProjectionLikeEnd (Greskell (GraphTraversal Filter s e)) Source # | |
| type ProjectionLikeStart (Walk Filter s e) Source # | |
| type ProjectionLikeStart (GTraversal Filter s e) Source # | |
| type ProjectionLikeEnd (Walk Filter s e) Source # | |
| type ProjectionLikeEnd (GTraversal Filter s e) 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
Instances
| WalkType Transform Source # | |
| WalkType p => Split Transform p Source # |
|
| Lift Transform SideEffect Source # | |
| Lift Transform Transform Source # | |
| ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # | |
| ProjectionLike (Walk Transform s e) Source # | |
| ProjectionLike (GTraversal Transform s e) Source # | |
| type ProjectionLikeStart (Greskell (GraphTraversal Transform s e)) Source # | |
| type ProjectionLikeEnd (Greskell (GraphTraversal Transform s e)) Source # | |
| type ProjectionLikeStart (Walk Transform s e) Source # | |
| type ProjectionLikeStart (GTraversal Transform s e) Source # | |
| type ProjectionLikeEnd (Walk Transform s e) Source # | |
| type ProjectionLikeEnd (GTraversal Transform s e) Source # | |
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 # | |
| Split SideEffect SideEffect Source # |
|
| Lift SideEffect SideEffect Source # | |
| Lift Transform SideEffect Source # | |
Relation of WalkTypes where one includes the other. from can
be lifted to to, because to is more powerful than from.
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.
GraphTraversalSource
Arguments
| :: Text | variable name of |
| -> Greskell GraphTraversalSource |
Create GraphTraversalSource from a varible name in Gremlin
>>>toGremlin $ source "g""g"
Arguments
| :: Vertex v | |
| => [Greskell (ElementID v)] | vertex IDs |
| -> Greskell GraphTraversalSource | |
| -> GTraversal Transform () v |
.V() method on GraphTraversalSource.
sV' :: [Greskell Value] -> Greskell GraphTraversalSource -> GTraversal Transform () AVertex Source #
Monomorphic version of sV.
>>>toGremlin (source "g" & sV' (map (value . Aeson.Number) [1,2,3]))"g.V(1.0,2.0,3.0)"
Arguments
| :: Edge e | |
| => [Greskell (ElementID e)] | edge IDs |
| -> Greskell GraphTraversalSource | |
| -> GTraversal Transform () e |
.E() method on GraphTraversalSource.
sE' :: [Greskell Value] -> Greskell GraphTraversalSource -> GTraversal Transform () AEdge Source #
Monomorphic version of sE.
>>>toGremlin (source "g" & sE' (map (value . Aeson.Number) [1]))"g.E(1.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
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')"
Filter steps
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
.has step with one argument.
>>>toGremlin (source "g" & sV' [] &. gHas1 "age")"g.V().has(\"age\")"
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.
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.
.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 (value $ Aeson.Number 7))"g.V().hasId(7.0)"
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 $ value $ Aeson.Number 100))"g.V().hasId(P.lte(100.0))"
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.
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.
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
Arguments
| :: [ByComparator s] | following |
| -> 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)"
Paging steps
Transformation steps
Accessor steps
.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
Graph traversal steps
.out step
gOut' :: Vertex v => [Greskell Text] -> Walk Transform v AVertex Source #
Monomorphic version of gOut.
>>>toGremlin (source "g" & sV' ["person"] &. gOut' ["knows"])"g.V(\"person\").out(\"knows\")"
.outE step
gOutE' :: Vertex v => [Greskell Text] -> Walk Transform v AEdge Source #
Monomorphic version of gOutE
.in step
.inE step.
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
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()"
.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.
Constructors
| ByProjection :: (ProjectionLike p, ToGreskell p) => p -> ByProjection (ProjectionLikeStart p) (ProjectionLikeEnd p) |
Instances
| IsString (ByProjection s e) Source # | Projection by literal property key. |
| ProjectionLike (ByProjection s e) Source # | |
| type ProjectionLikeStart (ByProjection s e) Source # | |
| type ProjectionLikeEnd (ByProjection s e) Source # | |
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 # | |
| ProjectionLike (Greskell (T s e)) Source # | |
| ProjectionLike (Greskell (GraphTraversal Transform s e)) Source # | |
| ProjectionLike (Greskell (GraphTraversal Filter s e)) Source # | |
| ProjectionLike (Key s e) Source # | |
| ProjectionLike (ByProjection s e) Source # | |
| ProjectionLike (Walk Transform s e) Source # | |
| ProjectionLike (Walk Filter s e) Source # | |
| ProjectionLike (GTraversal Transform s e) Source # | |
| ProjectionLike (GTraversal Filter s e) Source # | |
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 |
| ByComparatorComp :: Comparator comp => Greskell comp -> ByComparator (CompareArg comp) | Type |
| ByComparatorProjComp :: Comparator comp => ByProjection s (CompareArg comp) -> Greskell comp -> ByComparator s | Type |
Instances
| IsString (ByComparator s) Source # |
|
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 argumernt, 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.