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

Data.Greskell.Gremlin

Description

This modules defines types and functions for utility classes in Gremlin.

Synopsis

Predicate

class Predicate p where Source #

java.util.function.Predicate interface.

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

Minimal complete definition

Nothing

Associated Types

type PredicateArg p Source #

Methods

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

.and method.

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

.or method.

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

.test method.

pNegate :: Greskell p -> Greskell p Source #

.nagate method.

Instances

Instances details
Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) Source #

Methods

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

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

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

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

Predicate (PredicateA a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (PredicateA a) Source #

newtype PredicateA a Source #

Type for anonymous class of Predicate interface.

Constructors

PredicateA 

Fields

P class

data P a Source #

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

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

Instances

Instances details
GraphSONTyped (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: P a -> Text #

PLike (P a) Source #

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

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PParameter (P a) Source #

Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) Source #

Methods

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

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

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

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

type PParameter (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

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

Defined in Data.Greskell.Gremlin

type PredicateArg (P a) = a

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

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

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

Since: 1.2.0.0

Associated Types

type PParameter p Source #

Instances

Instances details
PLike (P a) Source #

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

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PParameter (P a) Source #

PLike (LabeledP a) Source #

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

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type PParameter (LabeledP a) Source #

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

P.not static method.

>>> toGremlin (pNot $ pEq $ 10 :: Greskell (P Int))
"P.not(P.eq(10))"

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

P.eq static method.

>>> toGremlin (pEq $ string "hoge" :: Greskell (P Text))
"P.eq(\"hoge\")"

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

P.neq static method.

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

P.lt static method.

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

P.lte static method.

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

P.gt static method.

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

P.gte static method.

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

P.inside static method.

>>> toGremlin (pInside 10 20 :: Greskell (P Int))
"P.inside(10,20)"

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

P.outside static method.

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

P.between static method.

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

P.within static method.

>>> toGremlin (pWithin ["foo", "bar", "hoge"] :: Greskell (P Text))
"P.within(\"foo\",\"bar\",\"hoge\")"

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

P.without static method.

Comparator

class Comparator c where Source #

java.util.Comparator interface.

Comparator compares two data of type CompareArg c.

Minimal complete definition

Nothing

Associated Types

type CompareArg c Source #

Methods

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

.compare method.

cReversed :: Greskell c -> Greskell c Source #

.reversed method.

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

.thenComparing method.

Instances

Instances details
Comparator (Order a) Source #

Order a compares the type a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (Order a) Source #

Comparator (ComparatorA a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (ComparatorA a) Source #

newtype ComparatorA a Source #

Type for anonymous class of Comparator interface.

Constructors

ComparatorA 

Fields

Order enum

data Order a Source #

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

Instances

Instances details
GraphSONTyped (Order a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: Order a -> Text #

Comparator (Order a) Source #

Order a compares the type a.

Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type CompareArg (Order a) Source #

type CompareArg (Order a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

type CompareArg (Order a) = a

oDecr :: Greskell (Order a) Source #

decr order.

>>> toGremlin oDecr
"Order.decr"

oIncr :: Greskell (Order a) Source #

incr order.

oShuffle :: Greskell (Order a) Source #

shuffle order.