greskell-1.1.0.1: Haskell binding for Gremlin graph query language

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

Data.Greskell.Gremlin

Contents

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
Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) :: Type 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) :: Type 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
GraphSONTyped (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Methods

gsonTypeFor :: P a -> Text #

Predicate (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

Associated Types

type PredicateArg (P a) :: Type 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 PredicateArg (P a) Source # 
Instance details

Defined in Data.Greskell.Gremlin

type PredicateArg (P a) = a

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

P.not static method.

>>> toGremlin $ pNot $ pEq $ number 10
"P.not(P.eq(10.0))"

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

P.eq static method.

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

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

P.neq static method.

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

P.lt static method.

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

P.lte static method.

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

P.gt static method.

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

P.gte static method.

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

P.inside static method.

>>> toGremlin $ pInside (number 10) (number 20)
"P.inside(10.0,20.0)"

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

P.outside static method.

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

P.between static method.

pWithin :: [Greskell a] -> Greskell (P a) Source #

P.within static method.

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

pWithout :: [Greskell a] -> Greskell (P a) 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 #

.reverse method.

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

.thenComparing method.

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
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) :: Type 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.