{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Greskell.GTraversal.Gen
(
GTraversal (..)
, GraphTraversal
, ToGTraversal (..)
, Walk
, GraphTraversalSource
, WalkType
, Filter
, Transform
, SideEffect
, Lift
, Split
, source
, sV
, sV'
, sE
, sE'
, sAddV
, sAddV'
, (&.)
, ($.)
, (<$.>)
, (<*.>)
, gIterate
, unsafeGTraversal
, unsafeWalk
, modulateWith
, gIdentity
, gFilter
, gCyclicPath
, gSimplePath
, gIs
, gIsP
, gHas1
, gHas2
, gHas2P
, gHasLabel
, gHasLabelP
, gHasId
, gHasIdP
, gHasKey
, gHasKeyP
, gHasValue
, gHasValueP
, gAnd
, gOr
, gNot
, gWhereP1
, gWhereP2
, gOrder
, gRange
, gLimit
, gTail
, gSkip
, gRepeat
, gTimes
, gUntilHead
, gUntilTail
, gEmitHead
, gEmitTail
, gEmitHeadT
, gEmitTailT
, gLoops
, RepeatUntil (..)
, RepeatEmit (..)
, RepeatPos (..)
, RepeatLabel (..)
, gLocal
, gUnion
, gCoalesce
, gChoose3
, gBarrier
, gDedup
, gDedupN
, gFlatMap
, gV
, gV'
, gConstant
, gProject
, gAs
, gValues
, gProperties
, gId
, gLabel
, gValueMap
, gElementMap
, gSelect1
, gSelectN
, gSelectBy1
, gSelectByN
, gUnfold
, gPath
, gPathBy
, gFold
, gCount
, gOut
, gOut'
, gOutE
, gOutE'
, gOutV
, gOutV'
, gIn
, gIn'
, gInE
, gInE'
, gInV
, gInV'
, gMatch
, MatchPattern (..)
, mPattern
, MatchResult
, gSideEffect
, gAddV
, gAddV'
, gAddE
, gAddE'
, AddAnchor
, gFrom
, gTo
, gDrop
, gDropP
, gProperty
, gPropertyV
, ByProjection (..)
, ProjectionLike (..)
, ByComparator (..)
, LabeledByProjection (..)
, gBy
, gBy1
, gBy2
, gByL
) where
import Data.Text (Text)
import Data.Greskell.AsIterator (AsIterator (IteratorItem))
import Data.Greskell.AsLabel (AsLabel, LabeledP, SelectedMap)
import Data.Greskell.Graph (AEdge, AVertex, Cardinality, Edge, Element (..),
ElementID, Key, KeyValue, Keys, Path, Property, Vertex)
import Data.Greskell.GraphSON (GValue)
import Data.Greskell.Greskell (Greskell)
import Data.Greskell.GTraversal (AddAnchor, ByComparator (..), ByProjection (..), Filter,
GTraversal (..), GraphTraversal, GraphTraversalSource,
LabeledByProjection (..), Lift, MatchPattern (..),
MatchResult, ProjectionLike (..), RepeatEmit (..),
RepeatLabel (..), RepeatPos (..), RepeatUntil (..),
SideEffect, Split, ToGTraversal (..), Transform, Walk,
WalkType, gAnd, gBarrier, gBy, gBy1, gBy2, gByL,
gChoose3, gCoalesce, gCyclicPath, gEmitHead, gEmitHeadT,
gEmitTail, gEmitTailT, gFilter, gFlatMap, gHas1, gHas2,
gHas2P, gHasId, gHasIdP, gHasKey, gHasKeyP, gHasLabel,
gHasLabelP, gHasValue, gHasValueP, gIdentity, gIs, gIsP,
gIterate, gLocal, gNot, gOr, gRepeat, gSideEffect,
gSimplePath, gTimes, gUnion, gUntilHead, gUntilTail,
gWhereP1, gWhereP2, mPattern, modulateWith, source,
unsafeGTraversal, unsafeWalk, ($.), (&.), (<$.>), (<*.>))
import qualified Data.Greskell.GTraversal as G
import Data.Greskell.Logic (Logic)
import Data.Greskell.PMap (PMap, Single)
sV :: (Vertex v, WalkType c, Lift Transform c) => [Greskell (ElementID v)] -> Greskell GraphTraversalSource -> GTraversal c () v
sV :: forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell (ElementID v)]
-> Greskell GraphTraversalSource -> GTraversal c () v
sV [Greskell (ElementID v)]
a Greskell GraphTraversalSource
b = GTraversal Transform () v -> GTraversal c () v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
GTraversal from s e -> GTraversal to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (GTraversal Transform () v -> GTraversal c () v)
-> GTraversal Transform () v -> GTraversal c () v
forall a b. (a -> b) -> a -> b
$ [Greskell (ElementID v)]
-> Greskell GraphTraversalSource -> GTraversal Transform () v
forall v.
Vertex v =>
[Greskell (ElementID v)]
-> Greskell GraphTraversalSource -> GTraversal Transform () v
G.sV [Greskell (ElementID v)]
a Greskell GraphTraversalSource
b
sV' :: (WalkType c, Lift Transform c) => [Greskell (ElementID AVertex)] -> Greskell GraphTraversalSource -> GTraversal c () AVertex
sV' :: forall c.
(WalkType c, Lift Transform c) =>
[Greskell (ElementID AVertex)]
-> Greskell GraphTraversalSource -> GTraversal c () AVertex
sV' = [Greskell (ElementID AVertex)]
-> Greskell GraphTraversalSource -> GTraversal c () AVertex
forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell (ElementID v)]
-> Greskell GraphTraversalSource -> GTraversal c () v
sV
sE :: (Edge e, WalkType c, Lift Transform c) => [Greskell (ElementID e)] -> Greskell GraphTraversalSource -> GTraversal c () e
sE :: forall e c.
(Edge e, WalkType c, Lift Transform c) =>
[Greskell (ElementID e)]
-> Greskell GraphTraversalSource -> GTraversal c () e
sE [Greskell (ElementID e)]
a Greskell GraphTraversalSource
b = GTraversal Transform () e -> GTraversal c () e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
GTraversal from s e -> GTraversal to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (GTraversal Transform () e -> GTraversal c () e)
-> GTraversal Transform () e -> GTraversal c () e
forall a b. (a -> b) -> a -> b
$ [Greskell (ElementID e)]
-> Greskell GraphTraversalSource -> GTraversal Transform () e
forall e.
Edge e =>
[Greskell (ElementID e)]
-> Greskell GraphTraversalSource -> GTraversal Transform () e
G.sE [Greskell (ElementID e)]
a Greskell GraphTraversalSource
b
sE' :: (WalkType c, Lift Transform c) => [Greskell (ElementID AEdge)] -> Greskell GraphTraversalSource -> GTraversal c () AEdge
sE' :: forall c.
(WalkType c, Lift Transform c) =>
[Greskell (ElementID AEdge)]
-> Greskell GraphTraversalSource -> GTraversal c () AEdge
sE' = [Greskell (ElementID AEdge)]
-> Greskell GraphTraversalSource -> GTraversal c () AEdge
forall e c.
(Edge e, WalkType c, Lift Transform c) =>
[Greskell (ElementID e)]
-> Greskell GraphTraversalSource -> GTraversal c () e
sE
sAddV :: (Vertex v, WalkType c, Lift SideEffect c) => Greskell Text -> Greskell GraphTraversalSource -> GTraversal c () v
sAddV :: forall v c.
(Vertex v, WalkType c, Lift SideEffect c) =>
Greskell Text -> Greskell GraphTraversalSource -> GTraversal c () v
sAddV Greskell Text
a Greskell GraphTraversalSource
b = GTraversal SideEffect () v -> GTraversal c () v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
GTraversal from s e -> GTraversal to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (GTraversal SideEffect () v -> GTraversal c () v)
-> GTraversal SideEffect () v -> GTraversal c () v
forall a b. (a -> b) -> a -> b
$ Greskell Text
-> Greskell GraphTraversalSource -> GTraversal SideEffect () v
forall v.
Vertex v =>
Greskell Text
-> Greskell GraphTraversalSource -> GTraversal SideEffect () v
G.sAddV Greskell Text
a Greskell GraphTraversalSource
b
sAddV' :: (WalkType c, Lift SideEffect c) => Greskell Text -> Greskell GraphTraversalSource -> GTraversal c () AVertex
sAddV' :: forall c.
(WalkType c, Lift SideEffect c) =>
Greskell Text
-> Greskell GraphTraversalSource -> GTraversal c () AVertex
sAddV' = Greskell Text
-> Greskell GraphTraversalSource -> GTraversal c () AVertex
forall v c.
(Vertex v, WalkType c, Lift SideEffect c) =>
Greskell Text -> Greskell GraphTraversalSource -> GTraversal c () v
sAddV
gOrder :: (WalkType c, Lift Transform c) => [ByComparator s] -> Walk c s s
gOrder :: forall c s.
(WalkType c, Lift Transform c) =>
[ByComparator s] -> Walk c s s
gOrder [ByComparator s]
b = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ [ByComparator s] -> Walk Transform s s
forall s. [ByComparator s] -> Walk Transform s s
G.gOrder [ByComparator s]
b
gRange :: (WalkType c, Lift Transform c) => Greskell Int -> Greskell Int -> Walk c s s
gRange :: forall c s.
(WalkType c, Lift Transform c) =>
Greskell Int -> Greskell Int -> Walk c s s
gRange Greskell Int
a Greskell Int
b = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ Greskell Int -> Greskell Int -> Walk Transform s s
forall s. Greskell Int -> Greskell Int -> Walk Transform s s
G.gRange Greskell Int
a Greskell Int
b
gLimit :: (WalkType c, Lift Transform c) => Greskell Int -> Walk c s s
gLimit :: forall c s.
(WalkType c, Lift Transform c) =>
Greskell Int -> Walk c s s
gLimit Greskell Int
a = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ Greskell Int -> Walk Transform s s
forall s. Greskell Int -> Walk Transform s s
G.gLimit Greskell Int
a
gTail :: (WalkType c, Lift Transform c) => Greskell Int -> Walk c s s
gTail :: forall c s.
(WalkType c, Lift Transform c) =>
Greskell Int -> Walk c s s
gTail Greskell Int
a = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ Greskell Int -> Walk Transform s s
forall s. Greskell Int -> Walk Transform s s
G.gTail Greskell Int
a
gSkip :: (WalkType c, Lift Transform c) => Greskell Int -> Walk c s s
gSkip :: forall c s.
(WalkType c, Lift Transform c) =>
Greskell Int -> Walk c s s
gSkip Greskell Int
a = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ Greskell Int -> Walk Transform s s
forall s. Greskell Int -> Walk Transform s s
G.gSkip Greskell Int
a
gLoops :: (WalkType c, Lift Transform c) => Maybe RepeatLabel -> Walk c s Int
gLoops :: forall c s.
(WalkType c, Lift Transform c) =>
Maybe RepeatLabel -> Walk c s Int
gLoops Maybe RepeatLabel
a = Walk Transform s Int -> Walk c s Int
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s Int -> Walk c s Int)
-> Walk Transform s Int -> Walk c s Int
forall a b. (a -> b) -> a -> b
$ Maybe RepeatLabel -> Walk Transform s Int
forall s. Maybe RepeatLabel -> Walk Transform s Int
G.gLoops Maybe RepeatLabel
a
gDedup :: (WalkType c, Lift Transform c) => Maybe (ByProjection s e) -> Walk c s s
gDedup :: forall c s e.
(WalkType c, Lift Transform c) =>
Maybe (ByProjection s e) -> Walk c s s
gDedup Maybe (ByProjection s e)
a = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ Maybe (ByProjection s e) -> Walk Transform s s
forall s e. Maybe (ByProjection s e) -> Walk Transform s s
G.gDedup Maybe (ByProjection s e)
a
gDedupN :: (WalkType c, Lift Transform c) => AsLabel a -> [AsLabel a] -> Maybe (ByProjection a e) -> Walk c s s
gDedupN :: forall c a e s.
(WalkType c, Lift Transform c) =>
AsLabel a -> [AsLabel a] -> Maybe (ByProjection a e) -> Walk c s s
gDedupN AsLabel a
a [AsLabel a]
b Maybe (ByProjection a e)
c = Walk Transform s s -> Walk c s s
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s s -> Walk c s s)
-> Walk Transform s s -> Walk c s s
forall a b. (a -> b) -> a -> b
$ AsLabel a
-> [AsLabel a] -> Maybe (ByProjection a e) -> Walk Transform s s
forall a e s.
AsLabel a
-> [AsLabel a] -> Maybe (ByProjection a e) -> Walk Transform s s
G.gDedupN AsLabel a
a [AsLabel a]
b Maybe (ByProjection a e)
c
gV :: (Vertex v, WalkType c, Lift Transform c) => [Greskell (ElementID v)] -> Walk c s v
gV :: forall v c s.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell (ElementID v)] -> Walk c s v
gV [Greskell (ElementID v)]
a = Walk Transform s v -> Walk c s v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s v -> Walk c s v)
-> Walk Transform s v -> Walk c s v
forall a b. (a -> b) -> a -> b
$ [Greskell (ElementID v)] -> Walk Transform s v
forall v s.
Vertex v =>
[Greskell (ElementID v)] -> Walk Transform s v
G.gV [Greskell (ElementID v)]
a
gV' :: (WalkType c, Lift Transform c) => [Greskell (ElementID AVertex)] -> Walk c s AVertex
gV' :: forall c s.
(WalkType c, Lift Transform c) =>
[Greskell (ElementID AVertex)] -> Walk c s AVertex
gV' = [Greskell (ElementID AVertex)] -> Walk c s AVertex
forall v c s.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell (ElementID v)] -> Walk c s v
gV
gConstant :: (WalkType c, Lift Transform c) => Greskell a -> Walk c s a
gConstant :: forall c a s.
(WalkType c, Lift Transform c) =>
Greskell a -> Walk c s a
gConstant Greskell a
a = Walk Transform s a -> Walk c s a
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s a -> Walk c s a)
-> Walk Transform s a -> Walk c s a
forall a b. (a -> b) -> a -> b
$ Greskell a -> Walk Transform s a
forall a s. Greskell a -> Walk Transform s a
G.gConstant Greskell a
a
gProject :: (WalkType c, Lift Transform c) => LabeledByProjection s -> [LabeledByProjection s] -> Walk c s (PMap Single GValue)
gProject :: forall c s.
(WalkType c, Lift Transform c) =>
LabeledByProjection s
-> [LabeledByProjection s] -> Walk c s (PMap Single GValue)
gProject LabeledByProjection s
a [LabeledByProjection s]
b = Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue))
-> Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall a b. (a -> b) -> a -> b
$ LabeledByProjection s
-> [LabeledByProjection s] -> Walk Transform s (PMap Single GValue)
forall s.
LabeledByProjection s
-> [LabeledByProjection s] -> Walk Transform s (PMap Single GValue)
G.gProject LabeledByProjection s
a [LabeledByProjection s]
b
gAs :: (WalkType c, Lift Transform c) => AsLabel a -> Walk c a a
gAs :: forall c a.
(WalkType c, Lift Transform c) =>
AsLabel a -> Walk c a a
gAs AsLabel a
a = Walk Transform a a -> Walk c a a
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform a a -> Walk c a a)
-> Walk Transform a a -> Walk c a a
forall a b. (a -> b) -> a -> b
$ AsLabel a -> Walk Transform a a
forall a. AsLabel a -> Walk Transform a a
G.gAs AsLabel a
a
gValues :: (Element s, WalkType c, Lift Transform c) => [Key s e] -> Walk c s e
gValues :: forall s c e.
(Element s, WalkType c, Lift Transform c) =>
[Key s e] -> Walk c s e
gValues [Key s e]
a = Walk Transform s e -> Walk c s e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s e -> Walk c s e)
-> Walk Transform s e -> Walk c s e
forall a b. (a -> b) -> a -> b
$ [Key s e] -> Walk Transform s e
forall s e. Element s => [Key s e] -> Walk Transform s e
G.gValues [Key s e]
a
gProperties :: (Element s, Property p, ElementProperty s ~ p, WalkType c, Lift Transform c) => [Key s v] -> Walk c s (p v)
gProperties :: forall s (p :: * -> *) c v.
(Element s, Property p, ElementProperty s ~ p, WalkType c,
Lift Transform c) =>
[Key s v] -> Walk c s (p v)
gProperties [Key s v]
a = Walk Transform s (p v) -> Walk c s (p v)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (p v) -> Walk c s (p v))
-> Walk Transform s (p v) -> Walk c s (p v)
forall a b. (a -> b) -> a -> b
$ [Key s v] -> Walk Transform s (p v)
forall s (p :: * -> *) v.
(Element s, Property p, ElementProperty s ~ p) =>
[Key s v] -> Walk Transform s (p v)
G.gProperties [Key s v]
a
gId :: (Element s, WalkType c, Lift Transform c) => Walk c s (ElementID s)
gId :: forall s c.
(Element s, WalkType c, Lift Transform c) =>
Walk c s (ElementID s)
gId = Walk Transform s (ElementID s) -> Walk c s (ElementID s)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk Walk Transform s (ElementID s)
forall s. Element s => Walk Transform s (ElementID s)
G.gId
gLabel :: (Element s, WalkType c, Lift Transform c) => Walk c s Text
gLabel :: forall s c.
(Element s, WalkType c, Lift Transform c) =>
Walk c s Text
gLabel = Walk Transform s Text -> Walk c s Text
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk Walk Transform s Text
forall s. Element s => Walk Transform s Text
G.gLabel
gValueMap :: (Element s, WalkType c, Lift Transform c) => Keys s -> Walk c s (PMap (ElementPropertyContainer s) GValue)
gValueMap :: forall s c.
(Element s, WalkType c, Lift Transform c) =>
Keys s -> Walk c s (PMap (ElementPropertyContainer s) GValue)
gValueMap Keys s
a = Walk Transform s (PMap (ElementPropertyContainer s) GValue)
-> Walk c s (PMap (ElementPropertyContainer s) GValue)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (PMap (ElementPropertyContainer s) GValue)
-> Walk c s (PMap (ElementPropertyContainer s) GValue))
-> Walk Transform s (PMap (ElementPropertyContainer s) GValue)
-> Walk c s (PMap (ElementPropertyContainer s) GValue)
forall a b. (a -> b) -> a -> b
$ Keys s
-> Walk Transform s (PMap (ElementPropertyContainer s) GValue)
forall s.
Element s =>
Keys s
-> Walk Transform s (PMap (ElementPropertyContainer s) GValue)
G.gValueMap Keys s
a
gElementMap :: (Element s, WalkType c, Lift Transform c) => Keys s -> Walk c s (PMap Single GValue)
gElementMap :: forall s c.
(Element s, WalkType c, Lift Transform c) =>
Keys s -> Walk c s (PMap Single GValue)
gElementMap Keys s
a = Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue))
-> Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall a b. (a -> b) -> a -> b
$ Keys s -> Walk Transform s (PMap Single GValue)
forall s.
Element s =>
Keys s -> Walk Transform s (PMap Single GValue)
G.gElementMap Keys s
a
gSelect1 :: (WalkType c, Lift Transform c) => AsLabel a -> Walk c s a
gSelect1 :: forall c a s.
(WalkType c, Lift Transform c) =>
AsLabel a -> Walk c s a
gSelect1 AsLabel a
a = Walk Transform s a -> Walk c s a
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s a -> Walk c s a)
-> Walk Transform s a -> Walk c s a
forall a b. (a -> b) -> a -> b
$ AsLabel a -> Walk Transform s a
forall a s. AsLabel a -> Walk Transform s a
G.gSelect1 AsLabel a
a
gSelectN :: (WalkType c, Lift Transform c) => AsLabel a -> AsLabel b -> [AsLabel c] -> Walk c s (SelectedMap GValue)
gSelectN :: forall c a b s.
(WalkType c, Lift Transform c) =>
AsLabel a
-> AsLabel b -> [AsLabel c] -> Walk c s (PMap Single GValue)
gSelectN AsLabel a
a AsLabel b
b [AsLabel c]
c = Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue))
-> Walk Transform s (PMap Single GValue)
-> Walk c s (PMap Single GValue)
forall a b. (a -> b) -> a -> b
$ AsLabel a
-> AsLabel b
-> [AsLabel c]
-> Walk Transform s (PMap Single GValue)
forall a b c s.
AsLabel a
-> AsLabel b
-> [AsLabel c]
-> Walk Transform s (PMap Single GValue)
G.gSelectN AsLabel a
a AsLabel b
b [AsLabel c]
c
gSelectBy1 :: (WalkType c, Lift Transform c) => AsLabel a -> ByProjection a b -> Walk c s b
gSelectBy1 :: forall c a b s.
(WalkType c, Lift Transform c) =>
AsLabel a -> ByProjection a b -> Walk c s b
gSelectBy1 AsLabel a
a ByProjection a b
b = Walk Transform s b -> Walk c s b
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s b -> Walk c s b)
-> Walk Transform s b -> Walk c s b
forall a b. (a -> b) -> a -> b
$ AsLabel a -> ByProjection a b -> Walk Transform s b
forall a b s. AsLabel a -> ByProjection a b -> Walk Transform s b
G.gSelectBy1 AsLabel a
a ByProjection a b
b
gSelectByN :: (WalkType c, Lift Transform c) => AsLabel a -> AsLabel a -> [AsLabel a] -> ByProjection a b -> Walk c s (SelectedMap b)
gSelectByN :: forall c a b s.
(WalkType c, Lift Transform c) =>
AsLabel a
-> AsLabel a
-> [AsLabel a]
-> ByProjection a b
-> Walk c s (SelectedMap b)
gSelectByN AsLabel a
a AsLabel a
b [AsLabel a]
c ByProjection a b
d = Walk Transform s (SelectedMap b) -> Walk c s (SelectedMap b)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (SelectedMap b) -> Walk c s (SelectedMap b))
-> Walk Transform s (SelectedMap b) -> Walk c s (SelectedMap b)
forall a b. (a -> b) -> a -> b
$ AsLabel a
-> AsLabel a
-> [AsLabel a]
-> ByProjection a b
-> Walk Transform s (SelectedMap b)
forall a b s.
AsLabel a
-> AsLabel a
-> [AsLabel a]
-> ByProjection a b
-> Walk Transform s (SelectedMap b)
G.gSelectByN AsLabel a
a AsLabel a
b [AsLabel a]
c ByProjection a b
d
gUnfold :: (AsIterator a, WalkType c, Lift Transform c) => Walk c a (IteratorItem a)
gUnfold :: forall a c.
(AsIterator a, WalkType c, Lift Transform c) =>
Walk c a (IteratorItem a)
gUnfold = Walk Transform a (IteratorItem a) -> Walk c a (IteratorItem a)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform a (IteratorItem a) -> Walk c a (IteratorItem a))
-> Walk Transform a (IteratorItem a) -> Walk c a (IteratorItem a)
forall a b. (a -> b) -> a -> b
$ Walk Transform a (IteratorItem a)
forall a. AsIterator a => Walk Transform a (IteratorItem a)
G.gUnfold
gPath :: (WalkType c, Lift Transform c) => Walk c s (Path GValue)
gPath :: forall c s.
(WalkType c, Lift Transform c) =>
Walk c s (Path GValue)
gPath = Walk Transform s (Path GValue) -> Walk c s (Path GValue)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (Path GValue) -> Walk c s (Path GValue))
-> Walk Transform s (Path GValue) -> Walk c s (Path GValue)
forall a b. (a -> b) -> a -> b
$ Walk Transform s (Path GValue)
forall s. Walk Transform s (Path GValue)
G.gPath
gPathBy :: (WalkType c, Lift Transform c) => ByProjection a b -> [ByProjection a b] -> Walk c s (Path b)
gPathBy :: forall c a b s.
(WalkType c, Lift Transform c) =>
ByProjection a b -> [ByProjection a b] -> Walk c s (Path b)
gPathBy ByProjection a b
a [ByProjection a b]
b = Walk Transform s (Path b) -> Walk c s (Path b)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform s (Path b) -> Walk c s (Path b))
-> Walk Transform s (Path b) -> Walk c s (Path b)
forall a b. (a -> b) -> a -> b
$ ByProjection a b -> [ByProjection a b] -> Walk Transform s (Path b)
forall a b s.
ByProjection a b -> [ByProjection a b] -> Walk Transform s (Path b)
G.gPathBy ByProjection a b
a [ByProjection a b]
b
gFold :: (WalkType c, Lift Transform c) => Walk c a [a]
gFold :: forall c a. (WalkType c, Lift Transform c) => Walk c a [a]
gFold = Walk Transform a [a] -> Walk c a [a]
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform a [a] -> Walk c a [a])
-> Walk Transform a [a] -> Walk c a [a]
forall a b. (a -> b) -> a -> b
$ Walk Transform a [a]
forall a. Walk Transform a [a]
G.gFold
gCount :: (WalkType c, Lift Transform c) => Walk c a Int
gCount :: forall c a. (WalkType c, Lift Transform c) => Walk c a Int
gCount = Walk Transform a Int -> Walk c a Int
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform a Int -> Walk c a Int)
-> Walk Transform a Int -> Walk c a Int
forall a b. (a -> b) -> a -> b
$ Walk Transform a Int
forall a. Walk Transform a Int
G.gCount
gOut :: (Vertex v1, Vertex v2, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v1 v2
gOut :: forall v1 v2 c.
(Vertex v1, Vertex v2, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v1 v2
gOut [Greskell Text]
a = Walk Transform v1 v2 -> Walk c v1 v2
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform v1 v2 -> Walk c v1 v2)
-> Walk Transform v1 v2 -> Walk c v1 v2
forall a b. (a -> b) -> a -> b
$ [Greskell Text] -> Walk Transform v1 v2
forall v1 v2.
(Vertex v1, Vertex v2) =>
[Greskell Text] -> Walk Transform v1 v2
G.gOut [Greskell Text]
a
gOut' :: (Vertex v, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v AVertex
gOut' :: forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v AVertex
gOut' = [Greskell Text] -> Walk c v AVertex
forall v1 v2 c.
(Vertex v1, Vertex v2, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v1 v2
gOut
gOutE :: (Vertex v, Edge e, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v e
gOutE :: forall v e c.
(Vertex v, Edge e, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v e
gOutE [Greskell Text]
a = Walk Transform v e -> Walk c v e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform v e -> Walk c v e)
-> Walk Transform v e -> Walk c v e
forall a b. (a -> b) -> a -> b
$ [Greskell Text] -> Walk Transform v e
forall v e.
(Vertex v, Edge e) =>
[Greskell Text] -> Walk Transform v e
G.gOutE [Greskell Text]
a
gOutE' :: (Vertex v, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v AEdge
gOutE' :: forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v AEdge
gOutE' = [Greskell Text] -> Walk c v AEdge
forall v e c.
(Vertex v, Edge e, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v e
gOutE
gOutV :: (Edge e, Vertex v, WalkType c, Lift Transform c) => Walk c e v
gOutV :: forall e v c.
(Edge e, Vertex v, WalkType c, Lift Transform c) =>
Walk c e v
gOutV = Walk Transform e v -> Walk c e v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform e v -> Walk c e v)
-> Walk Transform e v -> Walk c e v
forall a b. (a -> b) -> a -> b
$ Walk Transform e v
forall e v. (Edge e, Vertex v) => Walk Transform e v
G.gOutV
gOutV' :: (Edge e, WalkType c, Lift Transform c) => Walk c e AVertex
gOutV' :: forall e c.
(Edge e, WalkType c, Lift Transform c) =>
Walk c e AVertex
gOutV' = Walk c e AVertex
forall e v c.
(Edge e, Vertex v, WalkType c, Lift Transform c) =>
Walk c e v
gOutV
gIn :: (Vertex v1, Vertex v2, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v1 v2
gIn :: forall v1 v2 c.
(Vertex v1, Vertex v2, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v1 v2
gIn [Greskell Text]
a = Walk Transform v1 v2 -> Walk c v1 v2
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform v1 v2 -> Walk c v1 v2)
-> Walk Transform v1 v2 -> Walk c v1 v2
forall a b. (a -> b) -> a -> b
$ [Greskell Text] -> Walk Transform v1 v2
forall v1 v2.
(Vertex v1, Vertex v2) =>
[Greskell Text] -> Walk Transform v1 v2
G.gIn [Greskell Text]
a
gIn' :: (Vertex v, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v AVertex
gIn' :: forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v AVertex
gIn' = [Greskell Text] -> Walk c v AVertex
forall v1 v2 c.
(Vertex v1, Vertex v2, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v1 v2
gIn
gInE :: (Vertex v, Edge e, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v e
gInE :: forall v e c.
(Vertex v, Edge e, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v e
gInE [Greskell Text]
a = Walk Transform v e -> Walk c v e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform v e -> Walk c v e)
-> Walk Transform v e -> Walk c v e
forall a b. (a -> b) -> a -> b
$ [Greskell Text] -> Walk Transform v e
forall v e.
(Vertex v, Edge e) =>
[Greskell Text] -> Walk Transform v e
G.gInE [Greskell Text]
a
gInE' :: (Vertex v, WalkType c, Lift Transform c) => [Greskell Text] -> Walk c v AEdge
gInE' :: forall v c.
(Vertex v, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v AEdge
gInE' = [Greskell Text] -> Walk c v AEdge
forall v e c.
(Vertex v, Edge e, WalkType c, Lift Transform c) =>
[Greskell Text] -> Walk c v e
gInE
gInV :: (Edge e, Vertex v, WalkType c, Lift Transform c) => Walk c e v
gInV :: forall e v c.
(Edge e, Vertex v, WalkType c, Lift Transform c) =>
Walk c e v
gInV = Walk Transform e v -> Walk c e v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform e v -> Walk c e v)
-> Walk Transform e v -> Walk c e v
forall a b. (a -> b) -> a -> b
$ Walk Transform e v
forall e v. (Edge e, Vertex v) => Walk Transform e v
G.gInV
gInV' :: (Edge e, WalkType c, Lift Transform c) => Walk c e AVertex
gInV' :: forall e c.
(Edge e, WalkType c, Lift Transform c) =>
Walk c e AVertex
gInV' = Walk c e AVertex
forall e v c.
(Edge e, Vertex v, WalkType c, Lift Transform c) =>
Walk c e v
gInV
gMatch :: (WalkType c, Lift Transform c) => Logic MatchPattern -> Walk c a MatchResult
gMatch :: forall c a.
(WalkType c, Lift Transform c) =>
Logic MatchPattern -> Walk c a MatchResult
gMatch Logic MatchPattern
a = Walk Transform a MatchResult -> Walk c a MatchResult
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk Transform a MatchResult -> Walk c a MatchResult)
-> Walk Transform a MatchResult -> Walk c a MatchResult
forall a b. (a -> b) -> a -> b
$ Logic MatchPattern -> Walk Transform a MatchResult
forall a. Logic MatchPattern -> Walk Transform a MatchResult
G.gMatch Logic MatchPattern
a
gAddV :: (Vertex v, WalkType c, Lift SideEffect c) => Greskell Text -> Walk c a v
gAddV :: forall v c a.
(Vertex v, WalkType c, Lift SideEffect c) =>
Greskell Text -> Walk c a v
gAddV Greskell Text
a = Walk SideEffect a v -> Walk c a v
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk SideEffect a v -> Walk c a v)
-> Walk SideEffect a v -> Walk c a v
forall a b. (a -> b) -> a -> b
$ Greskell Text -> Walk SideEffect a v
forall v a. Vertex v => Greskell Text -> Walk SideEffect a v
G.gAddV Greskell Text
a
gAddV' :: (WalkType c, Lift SideEffect c) => Greskell Text -> Walk c a AVertex
gAddV' :: forall c a.
(WalkType c, Lift SideEffect c) =>
Greskell Text -> Walk c a AVertex
gAddV' = Greskell Text -> Walk c a AVertex
forall v c a.
(Vertex v, WalkType c, Lift SideEffect c) =>
Greskell Text -> Walk c a v
gAddV
gAddE :: (Vertex vs, Vertex ve, Edge e, WalkType c, Lift SideEffect c) => Greskell Text -> AddAnchor vs ve -> Walk c vs e
gAddE :: forall vs ve e c.
(Vertex vs, Vertex ve, Edge e, WalkType c, Lift SideEffect c) =>
Greskell Text -> AddAnchor vs ve -> Walk c vs e
gAddE Greskell Text
a AddAnchor vs ve
b = Walk SideEffect vs e -> Walk c vs e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk SideEffect vs e -> Walk c vs e)
-> Walk SideEffect vs e -> Walk c vs e
forall a b. (a -> b) -> a -> b
$ Greskell Text -> AddAnchor vs ve -> Walk SideEffect vs e
forall vs ve e.
(Vertex vs, Vertex ve, Edge e) =>
Greskell Text -> AddAnchor vs ve -> Walk SideEffect vs e
G.gAddE Greskell Text
a AddAnchor vs ve
b
gAddE' :: (WalkType c, Lift SideEffect c) => Greskell Text -> AddAnchor AVertex AVertex -> Walk c AVertex AEdge
gAddE' :: forall c.
(WalkType c, Lift SideEffect c) =>
Greskell Text -> AddAnchor AVertex AVertex -> Walk c AVertex AEdge
gAddE' = Greskell Text -> AddAnchor AVertex AVertex -> Walk c AVertex AEdge
forall vs ve e c.
(Vertex vs, Vertex ve, Edge e, WalkType c, Lift SideEffect c) =>
Greskell Text -> AddAnchor vs ve -> Walk c vs e
gAddE
gFrom :: (ToGTraversal g, WalkType c, Lift c Transform) => g c s e -> AddAnchor s e
gFrom :: forall (g :: * -> * -> * -> *) c s e.
(ToGTraversal g, WalkType c, Lift c Transform) =>
g c s e -> AddAnchor s e
gFrom g c s e
a = g Transform s e -> AddAnchor s e
forall (g :: * -> * -> * -> *) s e.
ToGTraversal g =>
g Transform s e -> AddAnchor s e
G.gFrom (g Transform s e -> AddAnchor s e)
-> g Transform s e -> AddAnchor s e
forall a b. (a -> b) -> a -> b
$ g c s e -> g Transform s e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk g c s e
a
gTo :: (ToGTraversal g, WalkType c, Lift c Transform) => g c s e -> AddAnchor s e
gTo :: forall (g :: * -> * -> * -> *) c s e.
(ToGTraversal g, WalkType c, Lift c Transform) =>
g c s e -> AddAnchor s e
gTo g c s e
a = g Transform s e -> AddAnchor s e
forall (g :: * -> * -> * -> *) s e.
ToGTraversal g =>
g Transform s e -> AddAnchor s e
G.gTo (g Transform s e -> AddAnchor s e)
-> g Transform s e -> AddAnchor s e
forall a b. (a -> b) -> a -> b
$ g c s e -> g Transform s e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk g c s e
a
gDrop :: (Element e, WalkType c, Lift SideEffect c) => Walk c e e
gDrop :: forall e c.
(Element e, WalkType c, Lift SideEffect c) =>
Walk c e e
gDrop = Walk SideEffect e e -> Walk c e e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk Walk SideEffect e e
forall e. Element e => Walk SideEffect e e
G.gDrop
gDropP :: (Property p, WalkType c, Lift SideEffect c) => Walk c (p a) (p a)
gDropP :: forall (p :: * -> *) c a.
(Property p, WalkType c, Lift SideEffect c) =>
Walk c (p a) (p a)
gDropP = Walk SideEffect (p a) (p a) -> Walk c (p a) (p a)
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk Walk SideEffect (p a) (p a)
forall (p :: * -> *) a. Property p => Walk SideEffect (p a) (p a)
G.gDropP
gProperty :: (Element e, WalkType c, Lift SideEffect c) => Key e v -> Greskell v -> Walk c e e
gProperty :: forall e c v.
(Element e, WalkType c, Lift SideEffect c) =>
Key e v -> Greskell v -> Walk c e e
gProperty Key e v
a Greskell v
b = Walk SideEffect e e -> Walk c e e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk SideEffect e e -> Walk c e e)
-> Walk SideEffect e e -> Walk c e e
forall a b. (a -> b) -> a -> b
$ Key e v -> Greskell v -> Walk SideEffect e e
forall e v.
Element e =>
Key e v -> Greskell v -> Walk SideEffect e e
G.gProperty Key e v
a Greskell v
b
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
gPropertyV :: forall e (vp :: * -> *) v c.
(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
gPropertyV Maybe (Greskell Cardinality)
a Key e v
b Greskell v
c [KeyValue (vp v)]
d = Walk SideEffect e e -> Walk c e e
forall from to s e.
(WalkType from, WalkType to, Lift from to) =>
Walk from s e -> Walk to s e
forall (g :: * -> * -> * -> *) from to s e.
(ToGTraversal g, WalkType from, WalkType to, Lift from to) =>
g from s e -> g to s e
liftWalk (Walk SideEffect e e -> Walk c e e)
-> Walk SideEffect e e -> Walk c e e
forall a b. (a -> b) -> a -> b
$ Maybe (Greskell Cardinality)
-> Key e v
-> Greskell v
-> [KeyValue (vp v)]
-> Walk SideEffect e e
forall e (vp :: * -> *) v.
(Vertex e, vp ~ ElementProperty e, Property vp, Element (vp v)) =>
Maybe (Greskell Cardinality)
-> Key e v
-> Greskell v
-> [KeyValue (vp v)]
-> Walk SideEffect e e
G.gPropertyV Maybe (Greskell Cardinality)
a Key e v
b Greskell v
c [KeyValue (vp v)]
d