| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Greskell.Gremlin
Description
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
- class ToGreskell (PParameter p) => PLike p where
- type PParameter p
- pNot :: PLike p => Greskell p -> Greskell p
- pEq :: PLike p => PParameter p -> Greskell p
- pNeq :: PLike p => PParameter p -> Greskell p
- pLt :: PLike p => PParameter p -> Greskell p
- pLte :: PLike p => PParameter p -> Greskell p
- pGt :: PLike p => PParameter p -> Greskell p
- pGte :: PLike p => PParameter p -> Greskell p
- pInside :: PLike p => PParameter p -> PParameter p -> Greskell p
- pOutside :: PLike p => PParameter p -> PParameter p -> Greskell p
- pBetween :: PLike p => PParameter p -> PParameter p -> Greskell p
- pWithin :: PLike p => [PParameter p] -> Greskell p
- pWithout :: PLike p => [PParameter p] -> Greskell p
- 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.
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 # | |
Defined in Data.Greskell.Gremlin Associated Types type PredicateArg (P a) Source # | |
| Predicate (PredicateA a) Source # | |
Defined in Data.Greskell.Gremlin Associated Types type PredicateArg (PredicateA a) Source # Methods 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.
Constructors
| PredicateA | |
Fields
| |
Instances
| Predicate (PredicateA a) Source # | |
Defined in Data.Greskell.Gremlin Associated Types type PredicateArg (PredicateA a) Source # Methods 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 Methods gsonTypeFor :: P a -> Text # | |
| PLike (P a) Source # | You can construct |
Defined in Data.Greskell.Gremlin Associated Types type PParameter (P a) Source # | |
| Predicate (P a) Source # | |
Defined in Data.Greskell.Gremlin Associated Types type PredicateArg (P a) Source # | |
| type PParameter (P a) Source # | |
Defined in Data.Greskell.Gremlin | |
| type PredicateArg (P a) Source # | |
Defined in Data.Greskell.Gremlin | |
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
| PLike (P a) Source # | You can construct |
Defined in Data.Greskell.Gremlin Associated Types type PParameter (P a) Source # | |
| PLike (LabeledP a) Source # | You can construct |
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\")"
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\")"
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
| Comparator (Order a) Source # |
|
Defined in Data.Greskell.Gremlin Associated Types type CompareArg (Order a) Source # | |
| Comparator (ComparatorA a) Source # | |
Defined in Data.Greskell.Gremlin Associated Types type CompareArg (ComparatorA a) Source # Methods 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.
Constructors
| ComparatorA | |
Fields
| |
Instances
| Comparator (ComparatorA a) Source # | |
Defined in Data.Greskell.Gremlin Associated Types type CompareArg (ComparatorA a) Source # Methods 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 Methods gsonTypeFor :: Order a -> Text # | |
| Comparator (Order a) Source # |
|
Defined in Data.Greskell.Gremlin Associated Types type CompareArg (Order a) Source # | |
| type CompareArg (Order a) Source # | |
Defined in Data.Greskell.Gremlin | |