| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Langs.Tinkerpop.Gremlin
Description
A Gremlin model, based on the Gremlin ANTLR grammar (master branch, as of 2024-06-30).
Documentation
Constructors
| QueryList | |
Fields
| |
Instances
| Read QueryList Source # | |
| Show QueryList Source # | |
| Eq QueryList Source # | |
| Ord QueryList Source # | |
_QueryList :: Name Source #
Constructors
| QueryTraversalSource TraversalSourceQuery | |
| QueryRootTraversal RootTraversalQuery | |
| QueryToString | |
| QueryEmpty |
_Query_empty :: Name Source #
data TraversalSourceQuery Source #
Constructors
| TraversalSourceQuery | |
Instances
data RootTraversalQuery Source #
Constructors
| RootTraversalQuery | |
Instances
newtype TraversalSource Source #
Constructors
| TraversalSource | |
Fields | |
Instances
data TransactionPart Source #
Instances
data RootTraversal Source #
Constructors
| RootTraversal | |
Instances
| Read RootTraversal Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS RootTraversal # readList :: ReadS [RootTraversal] # | |
| Show RootTraversal Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> RootTraversal -> ShowS # show :: RootTraversal -> String # showList :: [RootTraversal] -> ShowS # | |
| Eq RootTraversal Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: RootTraversal -> RootTraversal -> Bool # (/=) :: RootTraversal -> RootTraversal -> Bool # | |
| Ord RootTraversal Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: RootTraversal -> RootTraversal -> Ordering # (<) :: RootTraversal -> RootTraversal -> Bool # (<=) :: RootTraversal -> RootTraversal -> Bool # (>) :: RootTraversal -> RootTraversal -> Bool # (>=) :: RootTraversal -> RootTraversal -> Bool # max :: RootTraversal -> RootTraversal -> RootTraversal # min :: RootTraversal -> RootTraversal -> RootTraversal # | |
data TraversalSourceSelfMethod Source #
Constructors
Instances
data GenericLiteralArgumentAndOptionalTraversalBiFunctionArgument Source #
Instances
data StringArgumentAndGenericLiteralArgument Source #
Constructors
| StringArgumentAndGenericLiteralArgument | |
Instances
data StringArgumentAndOptionalGenericLiteralArgument Source #
Constructors
| StringArgumentAndOptionalGenericLiteralArgument | |
Instances
data TraversalSourceSpawnMethod Source #
Constructors
Instances
data GenericLiteralMapNullableArgumentOrNestedTraversal Source #
Constructors
| GenericLiteralMapNullableArgumentOrNestedTraversalMap GenericLiteralMapNullableArgument | |
| GenericLiteralMapNullableArgumentOrNestedTraversalTraversal NestedTraversal |
Instances
data ServiceCall Source #
Constructors
| ServiceCall | |
Instances
| Read ServiceCall Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ServiceCall # readList :: ReadS [ServiceCall] # readPrec :: ReadPrec ServiceCall # readListPrec :: ReadPrec [ServiceCall] # | |
| Show ServiceCall Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ServiceCall -> ShowS # show :: ServiceCall -> String # showList :: [ServiceCall] -> ShowS # | |
| Eq ServiceCall Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ServiceCall Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ServiceCall -> ServiceCall -> Ordering # (<) :: ServiceCall -> ServiceCall -> Bool # (<=) :: ServiceCall -> ServiceCall -> Bool # (>) :: ServiceCall -> ServiceCall -> Bool # (>=) :: ServiceCall -> ServiceCall -> Bool # max :: ServiceCall -> ServiceCall -> ServiceCall # min :: ServiceCall -> ServiceCall -> ServiceCall # | |
_ServiceCall :: Name Source #
data ServiceArguments Source #
Constructors
| ServiceArgumentsMap (Maybe GenericLiteralMapArgument) | |
| ServiceArgumentsTraversal (Maybe NestedTraversal) |
Instances
data ChainedTraversal Source #
Constructors
| ChainedTraversal | |
Instances
data ChainedTraversalElement Source #
Constructors
| ChainedTraversalElementMethod TraversalMethod | |
| ChainedTraversalElementSelf TraversalSelfMethod |
Instances
data NestedTraversal Source #
Constructors
| NestedTraversalRoot RootTraversal | |
| NestedTraversalChained ChainedTraversal | |
| NestedTraversalAnonymous ChainedTraversal |
Instances
data TerminatedTraversal Source #
Constructors
| TerminatedTraversal | |
Instances
data TraversalMethod Source #
Constructors
Instances
data StringArgumentOrNestedTraversal Source #
Constructors
| StringArgumentOrNestedTraversalString StringArgument | |
| StringArgumentOrNestedTraversalTraversal NestedTraversal |
Instances
data OptionalTraversalScopeArgumentAndStringArgument Source #
Constructors
| OptionalTraversalScopeArgumentAndStringArgument | |
Instances
data StringArgumentAndOptionalStringLiteralVarargs Source #
Constructors
| StringArgumentAndOptionalStringLiteralVarargs | |
Instances
data TraversalSackMethodArgumentOrIntegerArgument Source #
Constructors
| TraversalSackMethodArgumentOrIntegerArgumentConsumer TraversalSackMethodArgument | |
| TraversalSackMethodArgumentOrIntegerArgumentInt IntegerArgument |
Instances
Constructors
| ByArgsOrder TraversalOrderArgument | |
| ByArgsToken TraversalTokenArgument | |
| ByArgsOther ByOtherArgs |
_ByArgs_order :: Name Source #
_ByArgs_token :: Name Source #
_ByArgs_other :: Name Source #
data ByOtherArgs Source #
Constructors
| ByOtherArgsComparator (Maybe TraversalComparatorArgument) | |
| ByOtherArgsOther (Maybe TraversalFunctionArgumentOrStringArgumentOrNestedTraversal) |
Instances
| Read ByOtherArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ByOtherArgs # readList :: ReadS [ByOtherArgs] # readPrec :: ReadPrec ByOtherArgs # readListPrec :: ReadPrec [ByOtherArgs] # | |
| Show ByOtherArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ByOtherArgs -> ShowS # show :: ByOtherArgs -> String # showList :: [ByOtherArgs] -> ShowS # | |
| Eq ByOtherArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ByOtherArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ByOtherArgs -> ByOtherArgs -> Ordering # (<) :: ByOtherArgs -> ByOtherArgs -> Bool # (<=) :: ByOtherArgs -> ByOtherArgs -> Bool # (>) :: ByOtherArgs -> ByOtherArgs -> Bool # (>=) :: ByOtherArgs -> ByOtherArgs -> Bool # max :: ByOtherArgs -> ByOtherArgs -> ByOtherArgs # min :: ByOtherArgs -> ByOtherArgs -> ByOtherArgs # | |
_ByOtherArgs :: Name Source #
data TraversalFunctionArgumentOrStringArgumentOrNestedTraversal Source #
Constructors
Instances
data ChooseArgs Source #
Constructors
| ChooseArgsFunction TraversalFunctionArgument | |
| ChooseArgsPredicateTraversal PredicateTraversalArgument | |
| ChooseArgsTraversal NestedTraversalArgument |
Instances
| Read ChooseArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ChooseArgs # readList :: ReadS [ChooseArgs] # readPrec :: ReadPrec ChooseArgs # readListPrec :: ReadPrec [ChooseArgs] # | |
| Show ChooseArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ChooseArgs -> ShowS # show :: ChooseArgs -> String # showList :: [ChooseArgs] -> ShowS # | |
| Eq ChooseArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ChooseArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ChooseArgs -> ChooseArgs -> Ordering # (<) :: ChooseArgs -> ChooseArgs -> Bool # (<=) :: ChooseArgs -> ChooseArgs -> Bool # (>) :: ChooseArgs -> ChooseArgs -> Bool # (>=) :: ChooseArgs -> ChooseArgs -> Bool # max :: ChooseArgs -> ChooseArgs -> ChooseArgs # min :: ChooseArgs -> ChooseArgs -> ChooseArgs # | |
_ChooseArgs :: Name Source #
data PredicateTraversalArgument Source #
Constructors
| PredicateTraversalArgument | |
Instances
data NestedTraversalArgument Source #
Constructors
| NestedTraversalArgument | |
Instances
Instances
| Read DedupArgs Source # | |
| Show DedupArgs Source # | |
| Eq DedupArgs Source # | |
| Ord DedupArgs Source # | |
_DedupArgs :: Name Source #
data ScopeStringArgument Source #
Constructors
| ScopeStringArgument | |
Instances
data PredicateOrTraversal Source #
Constructors
| PredicateOrTraversalPredicate TraversalPredicate | |
| PredicateOrTraversalTraversal NestedTraversal |
Instances
data GenericLiteralArgumentAndTraversalBiFunctionArgument Source #
Instances
Constructors
| FromArgsString StringArgument | |
| FromArgsVertex StructureVertexArgument | |
| FromArgsTraversal NestedTraversal |
Constructors
| HasArgsString HasStringArgumentAndOptionalStringLiteralVarargs | |
| HasArgsTraversalToken HasTraversalTokenArgs |
data HasStringArgumentAndOptionalStringLiteralVarargs Source #
Constructors
| HasStringArgumentAndOptionalStringLiteralVarargs | |
Instances
data HasStringArgumentAndOptionalStringLiteralVarargsRest Source #
Constructors
Instances
data StringNullableArgumentAndGenericLiteralArgument Source #
Constructors
| StringNullableArgumentAndGenericLiteralArgument | |
Instances
data StringNullableArgumentAndTraversalPredicate Source #
Constructors
| StringNullableArgumentAndTraversalPredicate | |
Instances
data HasTraversalTokenArgs Source #
Constructors
| HasTraversalTokenArgs | |
Instances
data HasTraversalTokenArgsRest Source #
Constructors
| HasTraversalTokenArgsRestLiteral GenericLiteralArgument | |
| HasTraversalTokenArgsRestPredicate TraversalPredicate | |
| HasTraversalTokenArgsRestTraversal NestedTraversal |
Instances
data GenericLiteralArgumentAndTraversalPredicate Source #
Constructors
| GenericLiteralArgumentAndTraversalPredicateLiteral GenericLiteralArgument | |
| GenericLiteralArgumentAndTraversalPredicatePredicate TraversalPredicate |
Instances
data TraversalPredicateOrStringLiteralVarargs Source #
Constructors
| TraversalPredicateOrStringLiteralVarargsPredicate TraversalPredicate | |
| TraversalPredicateOrStringLiteralVarargsString [StringNullableArgument] |
Instances
data TraversalPredicateOrGenericLiteralArgument Source #
Constructors
| TraversalPredicateOrGenericLiteralArgumentPredicate TraversalPredicate | |
| TraversalPredicateOrGenericLiteralArgumentLiteral [GenericLiteralArgument] |
Instances
data OptionArgs Source #
Constructors
Instances
| Read OptionArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS OptionArgs # readList :: ReadS [OptionArgs] # readPrec :: ReadPrec OptionArgs # readListPrec :: ReadPrec [OptionArgs] # | |
| Show OptionArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> OptionArgs -> ShowS # show :: OptionArgs -> String # showList :: [OptionArgs] -> ShowS # | |
| Eq OptionArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord OptionArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: OptionArgs -> OptionArgs -> Ordering # (<) :: OptionArgs -> OptionArgs -> Bool # (<=) :: OptionArgs -> OptionArgs -> Bool # (>) :: OptionArgs -> OptionArgs -> Bool # (>=) :: OptionArgs -> OptionArgs -> Bool # max :: OptionArgs -> OptionArgs -> OptionArgs # min :: OptionArgs -> OptionArgs -> OptionArgs # | |
_OptionArgs :: Name Source #
data TraversalPredicateAndNestedTraversal Source #
Constructors
| TraversalPredicateAndNestedTraversal | |
Instances
data TraversalMergeArgumentAndGenericLiteralMapNullableArgument Source #
Instances
data TraversalMergeArgumentAndNestedTraversal Source #
Constructors
| TraversalMergeArgumentAndNestedTraversal | |
Instances
data GenericLiteralArgumentAndNestedTraversal Source #
Constructors
| GenericLiteralArgumentAndNestedTraversal | |
Instances
data PropertyArgs Source #
Constructors
Instances
| Read PropertyArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS PropertyArgs # readList :: ReadS [PropertyArgs] # | |
| Show PropertyArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> PropertyArgs -> ShowS # show :: PropertyArgs -> String # showList :: [PropertyArgs] -> ShowS # | |
| Eq PropertyArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord PropertyArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: PropertyArgs -> PropertyArgs -> Ordering # (<) :: PropertyArgs -> PropertyArgs -> Bool # (<=) :: PropertyArgs -> PropertyArgs -> Bool # (>) :: PropertyArgs -> PropertyArgs -> Bool # (>=) :: PropertyArgs -> PropertyArgs -> Bool # max :: PropertyArgs -> PropertyArgs -> PropertyArgs # min :: PropertyArgs -> PropertyArgs -> PropertyArgs # | |
_PropertyArgs :: Name Source #
data TraversalCardinalityArgumentAndObjects Source #
Constructors
| TraversalCardinalityArgumentAndObjects | |
Instances
data GenericLiteralMapNullableArgumentAndTraversalCardinalityArgument Source #
Instances
Constructors
| RangeArgs | |
Instances
| Read RangeArgs Source # | |
| Show RangeArgs Source # | |
| Eq RangeArgs Source # | |
| Ord RangeArgs Source # | |
_RangeArgs :: Name Source #
data OptionalStringArgumentAndNestedTraversal Source #
Constructors
| OptionalStringArgumentAndNestedTraversal | |
Instances
data SelectArgs Source #
Constructors
Instances
| Read SelectArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS SelectArgs # readList :: ReadS [SelectArgs] # readPrec :: ReadPrec SelectArgs # readListPrec :: ReadPrec [SelectArgs] # | |
| Show SelectArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> SelectArgs -> ShowS # show :: SelectArgs -> String # showList :: [SelectArgs] -> ShowS # | |
| Eq SelectArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord SelectArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: SelectArgs -> SelectArgs -> Ordering # (<) :: SelectArgs -> SelectArgs -> Bool # (<=) :: SelectArgs -> SelectArgs -> Bool # (>) :: SelectArgs -> SelectArgs -> Bool # (>=) :: SelectArgs -> SelectArgs -> Bool # max :: SelectArgs -> SelectArgs -> SelectArgs # min :: SelectArgs -> SelectArgs -> SelectArgs # | |
_SelectArgs :: Name Source #
data PopStringsArgument Source #
Constructors
| PopStringsArgument | |
Instances
data TraversalPopArgumentAndNestedTraversal Source #
Constructors
| TraversalPopArgumentAndNestedTraversal | |
Instances
data OptionalTraversalScopeArgumentAndIntegerArgument Source #
Constructors
| OptionalTraversalScopeArgumentAndIntegerArgument | |
Instances
Constructors
| TailArgs | |
Constructors
| ToArgsDirection DirectionAndVarargs | |
| ToArgsString StringArgument | |
| ToArgsVertex StructureVertexArgument | |
| ToArgsTraversal NestedTraversal |
data DirectionAndVarargs Source #
Constructors
| DirectionAndVarargs | |
Instances
data ValueMapArgs Source #
Instances
| Read ValueMapArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ValueMapArgs # readList :: ReadS [ValueMapArgs] # | |
| Show ValueMapArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ValueMapArgs -> ShowS # show :: ValueMapArgs -> String # showList :: [ValueMapArgs] -> ShowS # | |
| Eq ValueMapArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ValueMapArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ValueMapArgs -> ValueMapArgs -> Ordering # (<) :: ValueMapArgs -> ValueMapArgs -> Bool # (<=) :: ValueMapArgs -> ValueMapArgs -> Bool # (>) :: ValueMapArgs -> ValueMapArgs -> Bool # (>=) :: ValueMapArgs -> ValueMapArgs -> Bool # max :: ValueMapArgs -> ValueMapArgs -> ValueMapArgs # min :: ValueMapArgs -> ValueMapArgs -> ValueMapArgs # | |
_ValueMapArgs :: Name Source #
data ValueMapBooleanArgs Source #
Constructors
| ValueMapBooleanArgs | |
Instances
Constructors
| WhereArgsPredicate WhereWithPredicateArgs | |
| WhereArgsString StringArgument | |
| WhereArgsTraversal NestedTraversal |
Instances
| Read WhereArgs Source # | |
| Show WhereArgs Source # | |
| Eq WhereArgs Source # | |
| Ord WhereArgs Source # | |
_WhereArgs :: Name Source #
data WhereWithPredicateArgs Source #
Constructors
| WhereWithPredicateArgs | |
Instances
Constructors
| WithArgs | |
Fields | |
data WithArgsKeys Source #
Instances
| Read WithArgsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS WithArgsKeys # readList :: ReadS [WithArgsKeys] # | |
| Show WithArgsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> WithArgsKeys -> ShowS # show :: WithArgsKeys -> String # showList :: [WithArgsKeys] -> ShowS # | |
| Eq WithArgsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord WithArgsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: WithArgsKeys -> WithArgsKeys -> Ordering # (<) :: WithArgsKeys -> WithArgsKeys -> Bool # (<=) :: WithArgsKeys -> WithArgsKeys -> Bool # (>) :: WithArgsKeys -> WithArgsKeys -> Bool # (>=) :: WithArgsKeys -> WithArgsKeys -> Bool # max :: WithArgsKeys -> WithArgsKeys -> WithArgsKeys # min :: WithArgsKeys -> WithArgsKeys -> WithArgsKeys # | |
_WithArgsKeys :: Name Source #
data WithArgsValues Source #
Constructors
| WithArgsValuesWithOptions WithOptionsValues | |
| WithArgsValuesIo IoOptionsValues | |
| WithArgsValuesObject GenericLiteralArgument |
Instances
| Read WithArgsValues Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS WithArgsValues # readList :: ReadS [WithArgsValues] # | |
| Show WithArgsValues Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> WithArgsValues -> ShowS # show :: WithArgsValues -> String # showList :: [WithArgsValues] -> ShowS # | |
| Eq WithArgsValues Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: WithArgsValues -> WithArgsValues -> Bool # (/=) :: WithArgsValues -> WithArgsValues -> Bool # | |
| Ord WithArgsValues Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: WithArgsValues -> WithArgsValues -> Ordering # (<) :: WithArgsValues -> WithArgsValues -> Bool # (<=) :: WithArgsValues -> WithArgsValues -> Bool # (>) :: WithArgsValues -> WithArgsValues -> Bool # (>=) :: WithArgsValues -> WithArgsValues -> Bool # max :: WithArgsValues -> WithArgsValues -> WithArgsValues # min :: WithArgsValues -> WithArgsValues -> WithArgsValues # | |
data ConcatArgs Source #
Constructors
| ConcatArgsTraversal [NestedTraversal] | |
| ConcatArgsString [StringNullableArgument] |
Instances
| Read ConcatArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ConcatArgs # readList :: ReadS [ConcatArgs] # readPrec :: ReadPrec ConcatArgs # readListPrec :: ReadPrec [ConcatArgs] # | |
| Show ConcatArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ConcatArgs -> ShowS # show :: ConcatArgs -> String # showList :: [ConcatArgs] -> ShowS # | |
| Eq ConcatArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ConcatArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ConcatArgs -> ConcatArgs -> Ordering # (<) :: ConcatArgs -> ConcatArgs -> Bool # (<=) :: ConcatArgs -> ConcatArgs -> Bool # (>) :: ConcatArgs -> ConcatArgs -> Bool # (>=) :: ConcatArgs -> ConcatArgs -> Bool # max :: ConcatArgs -> ConcatArgs -> ConcatArgs # min :: ConcatArgs -> ConcatArgs -> ConcatArgs # | |
_ConcatArgs :: Name Source #
data ReplaceArgs Source #
Constructors
| ReplaceArgs | |
Instances
| Read ReplaceArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS ReplaceArgs # readList :: ReadS [ReplaceArgs] # readPrec :: ReadPrec ReplaceArgs # readListPrec :: ReadPrec [ReplaceArgs] # | |
| Show ReplaceArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> ReplaceArgs -> ShowS # show :: ReplaceArgs -> String # showList :: [ReplaceArgs] -> ShowS # | |
| Eq ReplaceArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord ReplaceArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: ReplaceArgs -> ReplaceArgs -> Ordering # (<) :: ReplaceArgs -> ReplaceArgs -> Bool # (<=) :: ReplaceArgs -> ReplaceArgs -> Bool # (>) :: ReplaceArgs -> ReplaceArgs -> Bool # (>=) :: ReplaceArgs -> ReplaceArgs -> Bool # max :: ReplaceArgs -> ReplaceArgs -> ReplaceArgs # min :: ReplaceArgs -> ReplaceArgs -> ReplaceArgs # | |
_ReplaceArgs :: Name Source #
Constructors
| SplitArgs | |
Instances
| Read SplitArgs Source # | |
| Show SplitArgs Source # | |
| Eq SplitArgs Source # | |
| Ord SplitArgs Source # | |
_SplitArgs :: Name Source #
data SubstringArgs Source #
Constructors
| SubstringArgs | |
Instances
| Read SubstringArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS SubstringArgs # readList :: ReadS [SubstringArgs] # | |
| Show SubstringArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> SubstringArgs -> ShowS # show :: SubstringArgs -> String # showList :: [SubstringArgs] -> ShowS # | |
| Eq SubstringArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: SubstringArgs -> SubstringArgs -> Bool # (/=) :: SubstringArgs -> SubstringArgs -> Bool # | |
| Ord SubstringArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: SubstringArgs -> SubstringArgs -> Ordering # (<) :: SubstringArgs -> SubstringArgs -> Bool # (<=) :: SubstringArgs -> SubstringArgs -> Bool # (>) :: SubstringArgs -> SubstringArgs -> Bool # (>=) :: SubstringArgs -> SubstringArgs -> Bool # max :: SubstringArgs -> SubstringArgs -> SubstringArgs # min :: SubstringArgs -> SubstringArgs -> SubstringArgs # | |
data DateAddArgs Source #
Constructors
| DateAddArgs | |
Instances
| Read DateAddArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS DateAddArgs # readList :: ReadS [DateAddArgs] # readPrec :: ReadPrec DateAddArgs # readListPrec :: ReadPrec [DateAddArgs] # | |
| Show DateAddArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> DateAddArgs -> ShowS # show :: DateAddArgs -> String # showList :: [DateAddArgs] -> ShowS # | |
| Eq DateAddArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord DateAddArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: DateAddArgs -> DateAddArgs -> Ordering # (<) :: DateAddArgs -> DateAddArgs -> Bool # (<=) :: DateAddArgs -> DateAddArgs -> Bool # (>) :: DateAddArgs -> DateAddArgs -> Bool # (>=) :: DateAddArgs -> DateAddArgs -> Bool # max :: DateAddArgs -> DateAddArgs -> DateAddArgs # min :: DateAddArgs -> DateAddArgs -> DateAddArgs # | |
_DateAddArgs :: Name Source #
data DateDiffArgs Source #
Instances
| Read DateDiffArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS DateDiffArgs # readList :: ReadS [DateDiffArgs] # | |
| Show DateDiffArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> DateDiffArgs -> ShowS # show :: DateDiffArgs -> String # showList :: [DateDiffArgs] -> ShowS # | |
| Eq DateDiffArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord DateDiffArgs Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: DateDiffArgs -> DateDiffArgs -> Ordering # (<) :: DateDiffArgs -> DateDiffArgs -> Bool # (<=) :: DateDiffArgs -> DateDiffArgs -> Bool # (>) :: DateDiffArgs -> DateDiffArgs -> Bool # (>=) :: DateDiffArgs -> DateDiffArgs -> Bool # max :: DateDiffArgs -> DateDiffArgs -> DateDiffArgs # min :: DateDiffArgs -> DateDiffArgs -> DateDiffArgs # | |
_DateDiffArgs :: Name Source #
data StructureVertex Source #
Constructors
| StructureVertex | |
Instances
data TraversalStrategy Source #
Constructors
| TraversalStrategy | |
Instances
data Configuration Source #
Constructors
| Configuration | |
Instances
| Read Configuration Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS Configuration # readList :: ReadS [Configuration] # | |
| Show Configuration Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> Configuration -> ShowS # show :: Configuration -> String # showList :: [Configuration] -> ShowS # | |
| Eq Configuration Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: Configuration -> Configuration -> Bool # (/=) :: Configuration -> Configuration -> Bool # | |
| Ord Configuration Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: Configuration -> Configuration -> Ordering # (<) :: Configuration -> Configuration -> Bool # (<=) :: Configuration -> Configuration -> Bool # (>) :: Configuration -> Configuration -> Bool # (>=) :: Configuration -> Configuration -> Bool # max :: Configuration -> Configuration -> Configuration # min :: Configuration -> Configuration -> Configuration # | |
data KeywordOrIdentifier Source #
Instances
data TraversalScope Source #
Constructors
| TraversalScopeLocal | |
| TraversalScopeGlobal |
Instances
| Read TraversalScope Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalScope # readList :: ReadS [TraversalScope] # | |
| Show TraversalScope Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalScope -> ShowS # show :: TraversalScope -> String # showList :: [TraversalScope] -> ShowS # | |
| Eq TraversalScope Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: TraversalScope -> TraversalScope -> Bool # (/=) :: TraversalScope -> TraversalScope -> Bool # | |
| Ord TraversalScope Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalScope -> TraversalScope -> Ordering # (<) :: TraversalScope -> TraversalScope -> Bool # (<=) :: TraversalScope -> TraversalScope -> Bool # (>) :: TraversalScope -> TraversalScope -> Bool # (>=) :: TraversalScope -> TraversalScope -> Bool # max :: TraversalScope -> TraversalScope -> TraversalScope # min :: TraversalScope -> TraversalScope -> TraversalScope # | |
data TraversalToken Source #
Instances
| Read TraversalToken Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalToken # readList :: ReadS [TraversalToken] # | |
| Show TraversalToken Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalToken -> ShowS # show :: TraversalToken -> String # showList :: [TraversalToken] -> ShowS # | |
| Eq TraversalToken Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: TraversalToken -> TraversalToken -> Bool # (/=) :: TraversalToken -> TraversalToken -> Bool # | |
| Ord TraversalToken Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalToken -> TraversalToken -> Ordering # (<) :: TraversalToken -> TraversalToken -> Bool # (<=) :: TraversalToken -> TraversalToken -> Bool # (>) :: TraversalToken -> TraversalToken -> Bool # (>=) :: TraversalToken -> TraversalToken -> Bool # max :: TraversalToken -> TraversalToken -> TraversalToken # min :: TraversalToken -> TraversalToken -> TraversalToken # | |
data TraversalMerge Source #
Instances
| Read TraversalMerge Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalMerge # readList :: ReadS [TraversalMerge] # | |
| Show TraversalMerge Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalMerge -> ShowS # show :: TraversalMerge -> String # showList :: [TraversalMerge] -> ShowS # | |
| Eq TraversalMerge Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: TraversalMerge -> TraversalMerge -> Bool # (/=) :: TraversalMerge -> TraversalMerge -> Bool # | |
| Ord TraversalMerge Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalMerge -> TraversalMerge -> Ordering # (<) :: TraversalMerge -> TraversalMerge -> Bool # (<=) :: TraversalMerge -> TraversalMerge -> Bool # (>) :: TraversalMerge -> TraversalMerge -> Bool # (>=) :: TraversalMerge -> TraversalMerge -> Bool # max :: TraversalMerge -> TraversalMerge -> TraversalMerge # min :: TraversalMerge -> TraversalMerge -> TraversalMerge # | |
data TraversalOrder Source #
Constructors
| TraversalOrderIncr | |
| TraversalOrderDecr | |
| TraversalOrderAsc | |
| TraversalOrderDesc | |
| TraversalOrderShuffle |
Instances
| Read TraversalOrder Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalOrder # readList :: ReadS [TraversalOrder] # | |
| Show TraversalOrder Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalOrder -> ShowS # show :: TraversalOrder -> String # showList :: [TraversalOrder] -> ShowS # | |
| Eq TraversalOrder Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: TraversalOrder -> TraversalOrder -> Bool # (/=) :: TraversalOrder -> TraversalOrder -> Bool # | |
| Ord TraversalOrder Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalOrder -> TraversalOrder -> Ordering # (<) :: TraversalOrder -> TraversalOrder -> Bool # (<=) :: TraversalOrder -> TraversalOrder -> Bool # (>) :: TraversalOrder -> TraversalOrder -> Bool # (>=) :: TraversalOrder -> TraversalOrder -> Bool # max :: TraversalOrder -> TraversalOrder -> TraversalOrder # min :: TraversalOrder -> TraversalOrder -> TraversalOrder # | |
data TraversalDirection Source #
Instances
data TraversalCardinality Source #
Constructors
| TraversalCardinalitySingle GenericLiteral | |
| TraversalCardinalitySet GenericLiteral | |
| TraversalCardinalityList GenericLiteral |
Instances
data TraversalColumn Source #
Constructors
| TraversalColumnKeys | |
| TraversalColumnValues |
Instances
data TraversalPop Source #
Instances
| Read TraversalPop Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalPop # readList :: ReadS [TraversalPop] # | |
| Show TraversalPop Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalPop -> ShowS # show :: TraversalPop -> String # showList :: [TraversalPop] -> ShowS # | |
| Eq TraversalPop Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord TraversalPop Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalPop -> TraversalPop -> Ordering # (<) :: TraversalPop -> TraversalPop -> Bool # (<=) :: TraversalPop -> TraversalPop -> Bool # (>) :: TraversalPop -> TraversalPop -> Bool # (>=) :: TraversalPop -> TraversalPop -> Bool # max :: TraversalPop -> TraversalPop -> TraversalPop # min :: TraversalPop -> TraversalPop -> TraversalPop # | |
_TraversalPop :: Name Source #
data TraversalOperator Source #
Constructors
Instances
data TraversalPick Source #
Constructors
| TraversalPickAny | |
| TraversalPickNone |
Instances
| Read TraversalPick Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalPick # readList :: ReadS [TraversalPick] # | |
| Show TraversalPick Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalPick -> ShowS # show :: TraversalPick -> String # showList :: [TraversalPick] -> ShowS # | |
| Eq TraversalPick Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: TraversalPick -> TraversalPick -> Bool # (/=) :: TraversalPick -> TraversalPick -> Bool # | |
| Ord TraversalPick Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalPick -> TraversalPick -> Ordering # (<) :: TraversalPick -> TraversalPick -> Bool # (<=) :: TraversalPick -> TraversalPick -> Bool # (>) :: TraversalPick -> TraversalPick -> Bool # (>=) :: TraversalPick -> TraversalPick -> Bool # max :: TraversalPick -> TraversalPick -> TraversalPick # min :: TraversalPick -> TraversalPick -> TraversalPick # | |
data TraversalDT Source #
Instances
| Read TraversalDT Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS TraversalDT # readList :: ReadS [TraversalDT] # readPrec :: ReadPrec TraversalDT # readListPrec :: ReadPrec [TraversalDT] # | |
| Show TraversalDT Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> TraversalDT -> ShowS # show :: TraversalDT -> String # showList :: [TraversalDT] -> ShowS # | |
| Eq TraversalDT Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord TraversalDT Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: TraversalDT -> TraversalDT -> Ordering # (<) :: TraversalDT -> TraversalDT -> Bool # (<=) :: TraversalDT -> TraversalDT -> Bool # (>) :: TraversalDT -> TraversalDT -> Bool # (>=) :: TraversalDT -> TraversalDT -> Bool # max :: TraversalDT -> TraversalDT -> TraversalDT # min :: TraversalDT -> TraversalDT -> TraversalDT # | |
_TraversalDT :: Name Source #
data TraversalPredicate Source #
Constructors
Instances
data TwoTraversalPredicates Source #
Constructors
| TwoTraversalPredicates | |
Instances
data TraversalTerminalMethod Source #
Constructors
Instances
data TraversalSelfMethod Source #
Constructors
| TraversalSelfMethodDiscard |
Instances
data TraversalFunction Source #
Instances
data RangeArgument Source #
Constructors
| RangeArgument | |
Instances
| Read RangeArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS RangeArgument # readList :: ReadS [RangeArgument] # | |
| Show RangeArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> RangeArgument -> ShowS # show :: RangeArgument -> String # showList :: [RangeArgument] -> ShowS # | |
| Eq RangeArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: RangeArgument -> RangeArgument -> Bool # (/=) :: RangeArgument -> RangeArgument -> Bool # | |
| Ord RangeArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: RangeArgument -> RangeArgument -> Ordering # (<) :: RangeArgument -> RangeArgument -> Bool # (<=) :: RangeArgument -> RangeArgument -> Bool # (>) :: RangeArgument -> RangeArgument -> Bool # (>=) :: RangeArgument -> RangeArgument -> Bool # max :: RangeArgument -> RangeArgument -> RangeArgument # min :: RangeArgument -> RangeArgument -> RangeArgument # | |
data WithOptionKeys Source #
Constructors
Instances
| Read WithOptionKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS WithOptionKeys # readList :: ReadS [WithOptionKeys] # | |
| Show WithOptionKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> WithOptionKeys -> ShowS # show :: WithOptionKeys -> String # showList :: [WithOptionKeys] -> ShowS # | |
| Eq WithOptionKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: WithOptionKeys -> WithOptionKeys -> Bool # (/=) :: WithOptionKeys -> WithOptionKeys -> Bool # | |
| Ord WithOptionKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: WithOptionKeys -> WithOptionKeys -> Ordering # (<) :: WithOptionKeys -> WithOptionKeys -> Bool # (<=) :: WithOptionKeys -> WithOptionKeys -> Bool # (>) :: WithOptionKeys -> WithOptionKeys -> Bool # (>=) :: WithOptionKeys -> WithOptionKeys -> Bool # max :: WithOptionKeys -> WithOptionKeys -> WithOptionKeys # min :: WithOptionKeys -> WithOptionKeys -> WithOptionKeys # | |
data ConnectedComponentConstants Source #
Constructors
| ConnectedComponentConstantsComponent | |
| ConnectedComponentConstantsEdges | |
| ConnectedComponentConstantsPropertyName |
Instances
data PageRankConstants Source #
Instances
data PeerPressureConstants Source #
Instances
data ShortestPathConstants Source #
Constructors
| ShortestPathConstantsTarget | |
| ShortestPathConstantsEdges | |
| ShortestPathConstantsDistance | |
| ShortestPathConstantsMaxDistance | |
| ShortestPathConstantsIncludeEdges |
Instances
data WithOptionsValues Source #
Constructors
Instances
data IoOptionsKeys Source #
Constructors
| IoOptionsKeysReader | |
| IoOptionsKeysWriter |
Instances
| Read IoOptionsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS IoOptionsKeys # readList :: ReadS [IoOptionsKeys] # | |
| Show IoOptionsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> IoOptionsKeys -> ShowS # show :: IoOptionsKeys -> String # showList :: [IoOptionsKeys] -> ShowS # | |
| Eq IoOptionsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: IoOptionsKeys -> IoOptionsKeys -> Bool # (/=) :: IoOptionsKeys -> IoOptionsKeys -> Bool # | |
| Ord IoOptionsKeys Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: IoOptionsKeys -> IoOptionsKeys -> Ordering # (<) :: IoOptionsKeys -> IoOptionsKeys -> Bool # (<=) :: IoOptionsKeys -> IoOptionsKeys -> Bool # (>) :: IoOptionsKeys -> IoOptionsKeys -> Bool # (>=) :: IoOptionsKeys -> IoOptionsKeys -> Bool # max :: IoOptionsKeys -> IoOptionsKeys -> IoOptionsKeys # min :: IoOptionsKeys -> IoOptionsKeys -> IoOptionsKeys # | |
data IoOptionsValues Source #
Instances
data BooleanArgument Source #
Constructors
| BooleanArgumentValue Bool | |
| BooleanArgumentVariable Identifier |
Instances
data IntegerArgument Source #
Instances
data FloatArgument Source #
Instances
| Read FloatArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS FloatArgument # readList :: ReadS [FloatArgument] # | |
| Show FloatArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> FloatArgument -> ShowS # show :: FloatArgument -> String # showList :: [FloatArgument] -> ShowS # | |
| Eq FloatArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: FloatArgument -> FloatArgument -> Bool # (/=) :: FloatArgument -> FloatArgument -> Bool # | |
| Ord FloatArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: FloatArgument -> FloatArgument -> Ordering # (<) :: FloatArgument -> FloatArgument -> Bool # (<=) :: FloatArgument -> FloatArgument -> Bool # (>) :: FloatArgument -> FloatArgument -> Bool # (>=) :: FloatArgument -> FloatArgument -> Bool # max :: FloatArgument -> FloatArgument -> FloatArgument # min :: FloatArgument -> FloatArgument -> FloatArgument # | |
data StringArgument Source #
Constructors
| StringArgumentValue String | |
| StringArgumentVariable Identifier |
Instances
| Read StringArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS StringArgument # readList :: ReadS [StringArgument] # | |
| Show StringArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> StringArgument -> ShowS # show :: StringArgument -> String # showList :: [StringArgument] -> ShowS # | |
| Eq StringArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: StringArgument -> StringArgument -> Bool # (/=) :: StringArgument -> StringArgument -> Bool # | |
| Ord StringArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: StringArgument -> StringArgument -> Ordering # (<) :: StringArgument -> StringArgument -> Bool # (<=) :: StringArgument -> StringArgument -> Bool # (>) :: StringArgument -> StringArgument -> Bool # (>=) :: StringArgument -> StringArgument -> Bool # max :: StringArgument -> StringArgument -> StringArgument # min :: StringArgument -> StringArgument -> StringArgument # | |
data StringNullableArgument Source #
Instances
data DateArgument Source #
Constructors
| DateArgumentValue DateLiteral | |
| DateArgumentVariable Identifier |
Instances
| Read DateArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS DateArgument # readList :: ReadS [DateArgument] # | |
| Show DateArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> DateArgument -> ShowS # show :: DateArgument -> String # showList :: [DateArgument] -> ShowS # | |
| Eq DateArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord DateArgument Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: DateArgument -> DateArgument -> Ordering # (<) :: DateArgument -> DateArgument -> Bool # (<=) :: DateArgument -> DateArgument -> Bool # (>) :: DateArgument -> DateArgument -> Bool # (>=) :: DateArgument -> DateArgument -> Bool # max :: DateArgument -> DateArgument -> DateArgument # min :: DateArgument -> DateArgument -> DateArgument # | |
_DateArgument :: Name Source #
data GenericLiteralArgument Source #
Instances
data GenericLiteralListArgument Source #
Constructors
| GenericLiteralListArgumentValue GenericLiteralList | |
| GenericLiteralListArgumentVariable Identifier |
Instances
data GenericLiteralMapArgument Source #
Constructors
| GenericLiteralMapArgumentValue GenericLiteralMap | |
| GenericLiteralMapArgumentVariable Identifier |
Instances
data GenericLiteralMapNullableArgument Source #
Constructors
| GenericLiteralMapNullableArgumentValue (Maybe GenericLiteralMap) | |
| GenericLiteralMapNullableArgumentVariable Identifier |
Instances
data StructureVertexArgument Source #
Instances
data TraversalCardinalityArgument Source #
Constructors
| TraversalCardinalityArgumentValue TraversalCardinality | |
| TraversalCardinalityArgumentVariable Identifier |
Instances
data TraversalColumnArgument Source #
Instances
data TraversalDirectionArgument Source #
Constructors
| TraversalDirectionArgumentValue TraversalDirection | |
| TraversalDirectionArgumentVariable Identifier |
Instances
data TraversalMergeArgument Source #
Instances
data TraversalOrderArgument Source #
Instances
data TraversalPopArgument Source #
Instances
data TraversalSackMethodArgument Source #
Instances
data TraversalScopeArgument Source #
Instances
data TraversalTokenArgument Source #
Instances
data TraversalComparatorArgument Source #
Constructors
| TraversalComparatorArgumentValue TraversalOrder | |
| TraversalComparatorArgumentVariable Identifier |
Instances
data TraversalFunctionArgument Source #
Constructors
| TraversalFunctionArgumentValue TraversalFunction | |
| TraversalFunctionArgumentVariable Identifier |
Instances
data TraversalBiFunctionArgument Source #
Constructors
| TraversalBiFunctionArgumentValue TraversalOperator | |
| TraversalBiFunctionArgumentVariable Identifier |
Instances
data TraversalDTArgument Source #
Instances
newtype GenericLiteralList Source #
Constructors
| GenericLiteralList | |
Fields | |
Instances
data GenericLiteralRange Source #
Instances
data IntegerRange Source #
Constructors
| IntegerRange | |
Instances
| Read IntegerRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS IntegerRange # readList :: ReadS [IntegerRange] # | |
| Show IntegerRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> IntegerRange -> ShowS # show :: IntegerRange -> String # showList :: [IntegerRange] -> ShowS # | |
| Eq IntegerRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord IntegerRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: IntegerRange -> IntegerRange -> Ordering # (<) :: IntegerRange -> IntegerRange -> Bool # (<=) :: IntegerRange -> IntegerRange -> Bool # (>) :: IntegerRange -> IntegerRange -> Bool # (>=) :: IntegerRange -> IntegerRange -> Bool # max :: IntegerRange -> IntegerRange -> IntegerRange # min :: IntegerRange -> IntegerRange -> IntegerRange # | |
_IntegerRange :: Name Source #
data StringRange Source #
Constructors
| StringRange | |
Fields | |
Instances
| Read StringRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS StringRange # readList :: ReadS [StringRange] # readPrec :: ReadPrec StringRange # readListPrec :: ReadPrec [StringRange] # | |
| Show StringRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> StringRange -> ShowS # show :: StringRange -> String # showList :: [StringRange] -> ShowS # | |
| Eq StringRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord StringRange Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: StringRange -> StringRange -> Ordering # (<) :: StringRange -> StringRange -> Bool # (<=) :: StringRange -> StringRange -> Bool # (>) :: StringRange -> StringRange -> Bool # (>=) :: StringRange -> StringRange -> Bool # max :: StringRange -> StringRange -> StringRange # min :: StringRange -> StringRange -> StringRange # | |
_StringRange :: Name Source #
newtype GenericLiteralSet Source #
Constructors
| GenericLiteralSet | |
Fields | |
Instances
newtype GenericLiteralCollection Source #
Constructors
| GenericLiteralCollection | |
Fields | |
Instances
data GenericLiteral Source #
Constructors
Instances
| Read GenericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS GenericLiteral # readList :: ReadS [GenericLiteral] # | |
| Show GenericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> GenericLiteral -> ShowS # show :: GenericLiteral -> String # showList :: [GenericLiteral] -> ShowS # | |
| Eq GenericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: GenericLiteral -> GenericLiteral -> Bool # (/=) :: GenericLiteral -> GenericLiteral -> Bool # | |
| Ord GenericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: GenericLiteral -> GenericLiteral -> Ordering # (<) :: GenericLiteral -> GenericLiteral -> Bool # (<=) :: GenericLiteral -> GenericLiteral -> Bool # (>) :: GenericLiteral -> GenericLiteral -> Bool # (>=) :: GenericLiteral -> GenericLiteral -> Bool # max :: GenericLiteral -> GenericLiteral -> GenericLiteral # min :: GenericLiteral -> GenericLiteral -> GenericLiteral # | |
newtype GenericLiteralMap Source #
Constructors
| GenericLiteralMap | |
Fields | |
Instances
Constructors
| MapEntryKey MapKey | |
| MapEntryValue GenericLiteral |
_MapEntry_key :: Name Source #
Constructors
_MapKey_set :: Name Source #
_MapKey_map :: Name Source #
newtype IntegerLiteral Source #
Constructors
| IntegerLiteral | |
Fields | |
Instances
| Read IntegerLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS IntegerLiteral # readList :: ReadS [IntegerLiteral] # | |
| Show IntegerLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> IntegerLiteral -> ShowS # show :: IntegerLiteral -> String # showList :: [IntegerLiteral] -> ShowS # | |
| Eq IntegerLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: IntegerLiteral -> IntegerLiteral -> Bool # (/=) :: IntegerLiteral -> IntegerLiteral -> Bool # | |
| Ord IntegerLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: IntegerLiteral -> IntegerLiteral -> Ordering # (<) :: IntegerLiteral -> IntegerLiteral -> Bool # (<=) :: IntegerLiteral -> IntegerLiteral -> Bool # (>) :: IntegerLiteral -> IntegerLiteral -> Bool # (>=) :: IntegerLiteral -> IntegerLiteral -> Bool # max :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral # min :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral # | |
newtype FloatLiteral Source #
Constructors
| FloatLiteral | |
Fields | |
Instances
| Read FloatLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS FloatLiteral # readList :: ReadS [FloatLiteral] # | |
| Show FloatLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> FloatLiteral -> ShowS # show :: FloatLiteral -> String # showList :: [FloatLiteral] -> ShowS # | |
| Eq FloatLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord FloatLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: FloatLiteral -> FloatLiteral -> Ordering # (<) :: FloatLiteral -> FloatLiteral -> Bool # (<=) :: FloatLiteral -> FloatLiteral -> Bool # (>) :: FloatLiteral -> FloatLiteral -> Bool # (>=) :: FloatLiteral -> FloatLiteral -> Bool # max :: FloatLiteral -> FloatLiteral -> FloatLiteral # min :: FloatLiteral -> FloatLiteral -> FloatLiteral # | |
_FloatLiteral :: Name Source #
data NumericLiteral Source #
Instances
| Read NumericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS NumericLiteral # readList :: ReadS [NumericLiteral] # | |
| Show NumericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> NumericLiteral -> ShowS # show :: NumericLiteral -> String # showList :: [NumericLiteral] -> ShowS # | |
| Eq NumericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods (==) :: NumericLiteral -> NumericLiteral -> Bool # (/=) :: NumericLiteral -> NumericLiteral -> Bool # | |
| Ord NumericLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: NumericLiteral -> NumericLiteral -> Ordering # (<) :: NumericLiteral -> NumericLiteral -> Bool # (<=) :: NumericLiteral -> NumericLiteral -> Bool # (>) :: NumericLiteral -> NumericLiteral -> Bool # (>=) :: NumericLiteral -> NumericLiteral -> Bool # max :: NumericLiteral -> NumericLiteral -> NumericLiteral # min :: NumericLiteral -> NumericLiteral -> NumericLiteral # | |
newtype DateLiteral Source #
Constructors
| DateLiteral | |
Fields | |
Instances
| Read DateLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS DateLiteral # readList :: ReadS [DateLiteral] # readPrec :: ReadPrec DateLiteral # readListPrec :: ReadPrec [DateLiteral] # | |
| Show DateLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> DateLiteral -> ShowS # show :: DateLiteral -> String # showList :: [DateLiteral] -> ShowS # | |
| Eq DateLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord DateLiteral Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: DateLiteral -> DateLiteral -> Ordering # (<) :: DateLiteral -> DateLiteral -> Bool # (<=) :: DateLiteral -> DateLiteral -> Bool # (>) :: DateLiteral -> DateLiteral -> Bool # (>=) :: DateLiteral -> DateLiteral -> Bool # max :: DateLiteral -> DateLiteral -> DateLiteral # min :: DateLiteral -> DateLiteral -> DateLiteral # | |
_DateLiteral :: Name Source #
Constructors
| KeywordEdges | |
| KeywordKeys | |
| KeywordNew | |
| KeywordValues |
_Keyword_keys :: Name Source #
_Keyword_new :: Name Source #
newtype Identifier Source #
Constructors
| Identifier | |
Fields | |
Instances
| Read Identifier Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods readsPrec :: Int -> ReadS Identifier # readList :: ReadS [Identifier] # readPrec :: ReadPrec Identifier # readListPrec :: ReadPrec [Identifier] # | |
| Show Identifier Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |
| Eq Identifier Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin | |
| Ord Identifier Source # | |
Defined in Hydra.Langs.Tinkerpop.Gremlin Methods compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # | |
_Identifier :: Name Source #