Maintainer | Toshio Ito <debug.ito@gmail.com> |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
This modules defines types and functions for utility classes in Gremlin.
Synopsis
- class Predicate p where
- newtype PredicateA a = PredicateA {
- unPredicateA :: a -> Bool
- data P a
- pNot :: Greskell (P a) -> Greskell (P a)
- pEq :: Greskell a -> Greskell (P a)
- pNeq :: Greskell a -> Greskell (P a)
- pLt :: Greskell a -> Greskell (P a)
- pLte :: Greskell a -> Greskell (P a)
- pGt :: Greskell a -> Greskell (P a)
- pGte :: Greskell a -> Greskell (P a)
- pInside :: Greskell a -> Greskell a -> Greskell (P a)
- pOutside :: Greskell a -> Greskell a -> Greskell (P a)
- pBetween :: Greskell a -> Greskell a -> Greskell (P a)
- pWithin :: [Greskell a] -> Greskell (P a)
- pWithout :: [Greskell a] -> Greskell (P a)
- class Comparator c where
- type CompareArg c
- cCompare :: Greskell c -> Greskell (CompareArg c) -> Greskell (CompareArg c) -> Greskell Int
- cReversed :: Greskell c -> Greskell c
- cThenComparing :: Greskell c -> Greskell c -> Greskell c
- newtype ComparatorA a = ComparatorA {
- unComparatorA :: a -> a -> Int
- data Order a
- oDecr :: Greskell (Order a)
- oIncr :: Greskell (Order a)
- oShuffle :: Greskell (Order a)
Predicate
class Predicate p where Source #
java.util.function.Predicate
interface.
A Predicate
p
is a function that takes PredicateArg
p
and
returns Bool
.
Nothing
type PredicateArg p Source #
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 # | |
Defined in Data.Greskell.Gremlin type PredicateArg (P a) :: Type Source # | |
Predicate (PredicateA a) Source # | |
Defined in Data.Greskell.Gremlin type PredicateArg (PredicateA a) :: Type Source # pAnd :: Greskell (PredicateA a) -> Greskell (PredicateA a) -> Greskell (PredicateA a) Source # pOr :: Greskell (PredicateA a) -> Greskell (PredicateA a) -> Greskell (PredicateA a) Source # pTest :: Greskell (PredicateA a) -> Greskell (PredicateArg (PredicateA a)) -> Greskell Bool Source # pNegate :: Greskell (PredicateA a) -> Greskell (PredicateA a) Source # |
newtype PredicateA a Source #
Type for anonymous class of Predicate
interface.
PredicateA | |
|
Instances
Predicate (PredicateA a) Source # | |
Defined in Data.Greskell.Gremlin type PredicateArg (PredicateA a) :: Type Source # pAnd :: Greskell (PredicateA a) -> Greskell (PredicateA a) -> Greskell (PredicateA a) Source # pOr :: Greskell (PredicateA a) -> Greskell (PredicateA a) -> Greskell (PredicateA a) Source # pTest :: Greskell (PredicateA a) -> Greskell (PredicateArg (PredicateA a)) -> Greskell Bool Source # pNegate :: Greskell (PredicateA a) -> Greskell (PredicateA a) Source # | |
type PredicateArg (PredicateA a) Source # | |
Defined in Data.Greskell.Gremlin |
P class
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 # | |
Defined in Data.Greskell.Gremlin gsonTypeFor :: P a -> Text # | |
Predicate (P a) Source # | |
Defined in Data.Greskell.Gremlin type PredicateArg (P a) :: Type Source # | |
type PredicateArg (P a) Source # | |
Defined in Data.Greskell.Gremlin |
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\")"
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)"
pWithin :: [Greskell a] -> Greskell (P a) Source #
P.within
static method.
>>>
toGremlin $ pWithin (["foo", "bar", "hoge"] :: [Greskell String])
"P.within(\"foo\",\"bar\",\"hoge\")"
Comparator
class Comparator c where Source #
java.util.Comparator
interface.
Comparator
compares two data of type CompareArg
c
.
Nothing
type CompareArg c Source #
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.
Instances
Comparator (Order a) Source # |
|
Defined in Data.Greskell.Gremlin type CompareArg (Order a) :: Type Source # | |
Comparator (ComparatorA a) Source # | |
Defined in Data.Greskell.Gremlin type CompareArg (ComparatorA a) :: Type Source # cCompare :: Greskell (ComparatorA a) -> Greskell (CompareArg (ComparatorA a)) -> Greskell (CompareArg (ComparatorA a)) -> Greskell Int Source # cReversed :: Greskell (ComparatorA a) -> Greskell (ComparatorA a) Source # cThenComparing :: Greskell (ComparatorA a) -> Greskell (ComparatorA a) -> Greskell (ComparatorA a) Source # |
newtype ComparatorA a Source #
Type for anonymous class of Comparator
interface.
ComparatorA | |
|
Instances
Comparator (ComparatorA a) Source # | |
Defined in Data.Greskell.Gremlin type CompareArg (ComparatorA a) :: Type Source # cCompare :: Greskell (ComparatorA a) -> Greskell (CompareArg (ComparatorA a)) -> Greskell (CompareArg (ComparatorA a)) -> Greskell Int Source # cReversed :: Greskell (ComparatorA a) -> Greskell (ComparatorA a) Source # cThenComparing :: Greskell (ComparatorA a) -> Greskell (ComparatorA a) -> Greskell (ComparatorA a) Source # | |
type CompareArg (ComparatorA a) Source # | |
Defined in Data.Greskell.Gremlin |
Order enum
org.apache.tinkerpop.gremlin.process.traversal.Order
enum.
Instances
GraphSONTyped (Order a) Source # | |
Defined in Data.Greskell.Gremlin gsonTypeFor :: Order a -> Text # | |
Comparator (Order a) Source # |
|
Defined in Data.Greskell.Gremlin type CompareArg (Order a) :: Type Source # | |
type CompareArg (Order a) Source # | |
Defined in Data.Greskell.Gremlin |