-- | A model derived from TinkerPop's Graph.Features. See
-- |   https://tinkerpop.apache.org/javadocs/current/core/org/apache/tinkerpop/gremlin/structure/Graph.Features.html
-- | 
-- | An interface that represents the capabilities of a Graph implementation.
-- | By default all methods of features return true and it is up to implementers to disable feature they don't support.
-- | Users should check features prior to using various functions of TinkerPop to help ensure code portability across implementations.
-- | For example, a common usage would be to check if a graph supports transactions prior to calling the commit method on Graph.tx().

module Hydra.Ext.Tinkerpop.Features where

import qualified Hydra.Core as Core
import Data.List
import Data.Map
import Data.Set

-- | Base interface for features that relate to supporting different data types.
data DataTypeFeatures = 
  DataTypeFeatures {
    -- | Supports setting of an array of boolean values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsBooleanArrayValues :: Bool,
    -- | Supports setting of a boolean value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsBooleanValues :: Bool,
    -- | Supports setting of an array of byte values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsByteArrayValues :: Bool,
    -- | Supports setting of a byte value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsByteValues :: Bool,
    -- | Supports setting of an array of double values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsDoubleArrayValues :: Bool,
    -- | Supports setting of a double value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsDoubleValues :: Bool,
    -- | Supports setting of an array of float values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsFloatArrayValues :: Bool,
    -- | Supports setting of a float value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsFloatValues :: Bool,
    -- | Supports setting of an array of integer values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsIntegerArrayValues :: Bool,
    -- | Supports setting of a integer value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsIntegerValues :: Bool,
    -- | Supports setting of an array of long values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsLongArrayValues :: Bool,
    -- | Supports setting of a long value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsLongValues :: Bool,
    -- | Supports setting of a Map value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsMapValues :: Bool,
    -- | Supports setting of a List value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsMixedListValues :: Bool,
    -- | Supports setting of a Java serializable value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsSerializableValues :: Bool,
    -- | Supports setting of an array of string values.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsStringArrayValues :: Bool,
    -- | Supports setting of a string value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsStringValues :: Bool,
    -- | Supports setting of a List value.
    DataTypeFeatures -> Bool
dataTypeFeaturesSupportsUniformListValues :: Bool}
  deriving (DataTypeFeatures -> DataTypeFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c/= :: DataTypeFeatures -> DataTypeFeatures -> Bool
== :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c== :: DataTypeFeatures -> DataTypeFeatures -> Bool
Eq, Eq DataTypeFeatures
DataTypeFeatures -> DataTypeFeatures -> Bool
DataTypeFeatures -> DataTypeFeatures -> Ordering
DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
$cmin :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
max :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
$cmax :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
>= :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c>= :: DataTypeFeatures -> DataTypeFeatures -> Bool
> :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c> :: DataTypeFeatures -> DataTypeFeatures -> Bool
<= :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c<= :: DataTypeFeatures -> DataTypeFeatures -> Bool
< :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c< :: DataTypeFeatures -> DataTypeFeatures -> Bool
compare :: DataTypeFeatures -> DataTypeFeatures -> Ordering
$ccompare :: DataTypeFeatures -> DataTypeFeatures -> Ordering
Ord, ReadPrec [DataTypeFeatures]
ReadPrec DataTypeFeatures
Int -> ReadS DataTypeFeatures
ReadS [DataTypeFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataTypeFeatures]
$creadListPrec :: ReadPrec [DataTypeFeatures]
readPrec :: ReadPrec DataTypeFeatures
$creadPrec :: ReadPrec DataTypeFeatures
readList :: ReadS [DataTypeFeatures]
$creadList :: ReadS [DataTypeFeatures]
readsPrec :: Int -> ReadS DataTypeFeatures
$creadsPrec :: Int -> ReadS DataTypeFeatures
Read, Int -> DataTypeFeatures -> ShowS
[DataTypeFeatures] -> ShowS
DataTypeFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataTypeFeatures] -> ShowS
$cshowList :: [DataTypeFeatures] -> ShowS
show :: DataTypeFeatures -> String
$cshow :: DataTypeFeatures -> String
showsPrec :: Int -> DataTypeFeatures -> ShowS
$cshowsPrec :: Int -> DataTypeFeatures -> ShowS
Show)

_DataTypeFeatures :: Name
_DataTypeFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.DataTypeFeatures")

_DataTypeFeatures_supportsBooleanArrayValues :: FieldName
_DataTypeFeatures_supportsBooleanArrayValues = (String -> FieldName
Core.FieldName String
"supportsBooleanArrayValues")

_DataTypeFeatures_supportsBooleanValues :: FieldName
_DataTypeFeatures_supportsBooleanValues = (String -> FieldName
Core.FieldName String
"supportsBooleanValues")

_DataTypeFeatures_supportsByteArrayValues :: FieldName
_DataTypeFeatures_supportsByteArrayValues = (String -> FieldName
Core.FieldName String
"supportsByteArrayValues")

_DataTypeFeatures_supportsByteValues :: FieldName
_DataTypeFeatures_supportsByteValues = (String -> FieldName
Core.FieldName String
"supportsByteValues")

_DataTypeFeatures_supportsDoubleArrayValues :: FieldName
_DataTypeFeatures_supportsDoubleArrayValues = (String -> FieldName
Core.FieldName String
"supportsDoubleArrayValues")

_DataTypeFeatures_supportsDoubleValues :: FieldName
_DataTypeFeatures_supportsDoubleValues = (String -> FieldName
Core.FieldName String
"supportsDoubleValues")

_DataTypeFeatures_supportsFloatArrayValues :: FieldName
_DataTypeFeatures_supportsFloatArrayValues = (String -> FieldName
Core.FieldName String
"supportsFloatArrayValues")

_DataTypeFeatures_supportsFloatValues :: FieldName
_DataTypeFeatures_supportsFloatValues = (String -> FieldName
Core.FieldName String
"supportsFloatValues")

_DataTypeFeatures_supportsIntegerArrayValues :: FieldName
_DataTypeFeatures_supportsIntegerArrayValues = (String -> FieldName
Core.FieldName String
"supportsIntegerArrayValues")

_DataTypeFeatures_supportsIntegerValues :: FieldName
_DataTypeFeatures_supportsIntegerValues = (String -> FieldName
Core.FieldName String
"supportsIntegerValues")

_DataTypeFeatures_supportsLongArrayValues :: FieldName
_DataTypeFeatures_supportsLongArrayValues = (String -> FieldName
Core.FieldName String
"supportsLongArrayValues")

_DataTypeFeatures_supportsLongValues :: FieldName
_DataTypeFeatures_supportsLongValues = (String -> FieldName
Core.FieldName String
"supportsLongValues")

_DataTypeFeatures_supportsMapValues :: FieldName
_DataTypeFeatures_supportsMapValues = (String -> FieldName
Core.FieldName String
"supportsMapValues")

_DataTypeFeatures_supportsMixedListValues :: FieldName
_DataTypeFeatures_supportsMixedListValues = (String -> FieldName
Core.FieldName String
"supportsMixedListValues")

_DataTypeFeatures_supportsSerializableValues :: FieldName
_DataTypeFeatures_supportsSerializableValues = (String -> FieldName
Core.FieldName String
"supportsSerializableValues")

_DataTypeFeatures_supportsStringArrayValues :: FieldName
_DataTypeFeatures_supportsStringArrayValues = (String -> FieldName
Core.FieldName String
"supportsStringArrayValues")

_DataTypeFeatures_supportsStringValues :: FieldName
_DataTypeFeatures_supportsStringValues = (String -> FieldName
Core.FieldName String
"supportsStringValues")

_DataTypeFeatures_supportsUniformListValues :: FieldName
_DataTypeFeatures_supportsUniformListValues = (String -> FieldName
Core.FieldName String
"supportsUniformListValues")

-- | Features that are related to Edge operations.
data EdgeFeatures = 
  EdgeFeatures {
    EdgeFeatures -> ElementFeatures
edgeFeaturesElementFeatures :: ElementFeatures,
    EdgeFeatures -> EdgePropertyFeatures
edgeFeaturesProperties :: EdgePropertyFeatures,
    -- | Determines if an Edge can be added to a Vertex.
    EdgeFeatures -> Bool
edgeFeaturesSupportsAddEdges :: Bool,
    -- | Determines if an Edge can be removed from a Vertex.
    EdgeFeatures -> Bool
edgeFeaturesSupportsRemoveEdges :: Bool,
    -- | Determines if the Graph implementation uses upsert functionality as opposed to insert functionality for Vertex.addEdge(String, Vertex, Object...).
    EdgeFeatures -> Bool
edgeFeaturesSupportsUpsert :: Bool}
  deriving (EdgeFeatures -> EdgeFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EdgeFeatures -> EdgeFeatures -> Bool
$c/= :: EdgeFeatures -> EdgeFeatures -> Bool
== :: EdgeFeatures -> EdgeFeatures -> Bool
$c== :: EdgeFeatures -> EdgeFeatures -> Bool
Eq, Eq EdgeFeatures
EdgeFeatures -> EdgeFeatures -> Bool
EdgeFeatures -> EdgeFeatures -> Ordering
EdgeFeatures -> EdgeFeatures -> EdgeFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
$cmin :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
max :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
$cmax :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
>= :: EdgeFeatures -> EdgeFeatures -> Bool
$c>= :: EdgeFeatures -> EdgeFeatures -> Bool
> :: EdgeFeatures -> EdgeFeatures -> Bool
$c> :: EdgeFeatures -> EdgeFeatures -> Bool
<= :: EdgeFeatures -> EdgeFeatures -> Bool
$c<= :: EdgeFeatures -> EdgeFeatures -> Bool
< :: EdgeFeatures -> EdgeFeatures -> Bool
$c< :: EdgeFeatures -> EdgeFeatures -> Bool
compare :: EdgeFeatures -> EdgeFeatures -> Ordering
$ccompare :: EdgeFeatures -> EdgeFeatures -> Ordering
Ord, ReadPrec [EdgeFeatures]
ReadPrec EdgeFeatures
Int -> ReadS EdgeFeatures
ReadS [EdgeFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EdgeFeatures]
$creadListPrec :: ReadPrec [EdgeFeatures]
readPrec :: ReadPrec EdgeFeatures
$creadPrec :: ReadPrec EdgeFeatures
readList :: ReadS [EdgeFeatures]
$creadList :: ReadS [EdgeFeatures]
readsPrec :: Int -> ReadS EdgeFeatures
$creadsPrec :: Int -> ReadS EdgeFeatures
Read, Int -> EdgeFeatures -> ShowS
[EdgeFeatures] -> ShowS
EdgeFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EdgeFeatures] -> ShowS
$cshowList :: [EdgeFeatures] -> ShowS
show :: EdgeFeatures -> String
$cshow :: EdgeFeatures -> String
showsPrec :: Int -> EdgeFeatures -> ShowS
$cshowsPrec :: Int -> EdgeFeatures -> ShowS
Show)

_EdgeFeatures :: Name
_EdgeFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.EdgeFeatures")

_EdgeFeatures_elementFeatures :: FieldName
_EdgeFeatures_elementFeatures = (String -> FieldName
Core.FieldName String
"elementFeatures")

_EdgeFeatures_properties :: FieldName
_EdgeFeatures_properties = (String -> FieldName
Core.FieldName String
"properties")

_EdgeFeatures_supportsAddEdges :: FieldName
_EdgeFeatures_supportsAddEdges = (String -> FieldName
Core.FieldName String
"supportsAddEdges")

_EdgeFeatures_supportsRemoveEdges :: FieldName
_EdgeFeatures_supportsRemoveEdges = (String -> FieldName
Core.FieldName String
"supportsRemoveEdges")

_EdgeFeatures_supportsUpsert :: FieldName
_EdgeFeatures_supportsUpsert = (String -> FieldName
Core.FieldName String
"supportsUpsert")

-- | Features that are related to Edge Property objects.
data EdgePropertyFeatures = 
  EdgePropertyFeatures {
    EdgePropertyFeatures -> PropertyFeatures
edgePropertyFeaturesPropertyFeatures :: PropertyFeatures}
  deriving (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c/= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
== :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c== :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
Eq, Eq EdgePropertyFeatures
EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering
EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
$cmin :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
max :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
$cmax :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
>= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c>= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
> :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c> :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
<= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c<= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
< :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c< :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
compare :: EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering
$ccompare :: EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering
Ord, ReadPrec [EdgePropertyFeatures]
ReadPrec EdgePropertyFeatures
Int -> ReadS EdgePropertyFeatures
ReadS [EdgePropertyFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EdgePropertyFeatures]
$creadListPrec :: ReadPrec [EdgePropertyFeatures]
readPrec :: ReadPrec EdgePropertyFeatures
$creadPrec :: ReadPrec EdgePropertyFeatures
readList :: ReadS [EdgePropertyFeatures]
$creadList :: ReadS [EdgePropertyFeatures]
readsPrec :: Int -> ReadS EdgePropertyFeatures
$creadsPrec :: Int -> ReadS EdgePropertyFeatures
Read, Int -> EdgePropertyFeatures -> ShowS
[EdgePropertyFeatures] -> ShowS
EdgePropertyFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EdgePropertyFeatures] -> ShowS
$cshowList :: [EdgePropertyFeatures] -> ShowS
show :: EdgePropertyFeatures -> String
$cshow :: EdgePropertyFeatures -> String
showsPrec :: Int -> EdgePropertyFeatures -> ShowS
$cshowsPrec :: Int -> EdgePropertyFeatures -> ShowS
Show)

_EdgePropertyFeatures :: Name
_EdgePropertyFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.EdgePropertyFeatures")

_EdgePropertyFeatures_propertyFeatures :: FieldName
_EdgePropertyFeatures_propertyFeatures = (String -> FieldName
Core.FieldName String
"propertyFeatures")

-- | Features that are related to Element objects.
data ElementFeatures = 
  ElementFeatures {
    -- | Determines if an Element allows properties to be added.
    ElementFeatures -> Bool
elementFeaturesSupportsAddProperty :: Bool,
    -- | Determines if an Element any Java object is a suitable identifier.
    ElementFeatures -> Bool
elementFeaturesSupportsAnyIds :: Bool,
    -- | Determines if an Element has a specific custom object as their internal representation.
    ElementFeatures -> Bool
elementFeaturesSupportsCustomIds :: Bool,
    -- | Determines if an Element has numeric identifiers as their internal representation.
    ElementFeatures -> Bool
elementFeaturesSupportsNumericIds :: Bool,
    -- | Determines if an Element allows properties to be removed.
    ElementFeatures -> Bool
elementFeaturesSupportsRemoveProperty :: Bool,
    -- | Determines if an Element has string identifiers as their internal representation.
    ElementFeatures -> Bool
elementFeaturesSupportsStringIds :: Bool,
    -- | Determines if an Element can have a user defined identifier.
    ElementFeatures -> Bool
elementFeaturesSupportsUserSuppliedIds :: Bool,
    -- | Determines if an Element has UUID identifiers as their internal representation.
    ElementFeatures -> Bool
elementFeaturesSupportsUuidIds :: Bool}
  deriving (ElementFeatures -> ElementFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementFeatures -> ElementFeatures -> Bool
$c/= :: ElementFeatures -> ElementFeatures -> Bool
== :: ElementFeatures -> ElementFeatures -> Bool
$c== :: ElementFeatures -> ElementFeatures -> Bool
Eq, Eq ElementFeatures
ElementFeatures -> ElementFeatures -> Bool
ElementFeatures -> ElementFeatures -> Ordering
ElementFeatures -> ElementFeatures -> ElementFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ElementFeatures -> ElementFeatures -> ElementFeatures
$cmin :: ElementFeatures -> ElementFeatures -> ElementFeatures
max :: ElementFeatures -> ElementFeatures -> ElementFeatures
$cmax :: ElementFeatures -> ElementFeatures -> ElementFeatures
>= :: ElementFeatures -> ElementFeatures -> Bool
$c>= :: ElementFeatures -> ElementFeatures -> Bool
> :: ElementFeatures -> ElementFeatures -> Bool
$c> :: ElementFeatures -> ElementFeatures -> Bool
<= :: ElementFeatures -> ElementFeatures -> Bool
$c<= :: ElementFeatures -> ElementFeatures -> Bool
< :: ElementFeatures -> ElementFeatures -> Bool
$c< :: ElementFeatures -> ElementFeatures -> Bool
compare :: ElementFeatures -> ElementFeatures -> Ordering
$ccompare :: ElementFeatures -> ElementFeatures -> Ordering
Ord, ReadPrec [ElementFeatures]
ReadPrec ElementFeatures
Int -> ReadS ElementFeatures
ReadS [ElementFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ElementFeatures]
$creadListPrec :: ReadPrec [ElementFeatures]
readPrec :: ReadPrec ElementFeatures
$creadPrec :: ReadPrec ElementFeatures
readList :: ReadS [ElementFeatures]
$creadList :: ReadS [ElementFeatures]
readsPrec :: Int -> ReadS ElementFeatures
$creadsPrec :: Int -> ReadS ElementFeatures
Read, Int -> ElementFeatures -> ShowS
[ElementFeatures] -> ShowS
ElementFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElementFeatures] -> ShowS
$cshowList :: [ElementFeatures] -> ShowS
show :: ElementFeatures -> String
$cshow :: ElementFeatures -> String
showsPrec :: Int -> ElementFeatures -> ShowS
$cshowsPrec :: Int -> ElementFeatures -> ShowS
Show)

_ElementFeatures :: Name
_ElementFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.ElementFeatures")

_ElementFeatures_supportsAddProperty :: FieldName
_ElementFeatures_supportsAddProperty = (String -> FieldName
Core.FieldName String
"supportsAddProperty")

_ElementFeatures_supportsAnyIds :: FieldName
_ElementFeatures_supportsAnyIds = (String -> FieldName
Core.FieldName String
"supportsAnyIds")

_ElementFeatures_supportsCustomIds :: FieldName
_ElementFeatures_supportsCustomIds = (String -> FieldName
Core.FieldName String
"supportsCustomIds")

_ElementFeatures_supportsNumericIds :: FieldName
_ElementFeatures_supportsNumericIds = (String -> FieldName
Core.FieldName String
"supportsNumericIds")

_ElementFeatures_supportsRemoveProperty :: FieldName
_ElementFeatures_supportsRemoveProperty = (String -> FieldName
Core.FieldName String
"supportsRemoveProperty")

_ElementFeatures_supportsStringIds :: FieldName
_ElementFeatures_supportsStringIds = (String -> FieldName
Core.FieldName String
"supportsStringIds")

_ElementFeatures_supportsUserSuppliedIds :: FieldName
_ElementFeatures_supportsUserSuppliedIds = (String -> FieldName
Core.FieldName String
"supportsUserSuppliedIds")

_ElementFeatures_supportsUuidIds :: FieldName
_ElementFeatures_supportsUuidIds = (String -> FieldName
Core.FieldName String
"supportsUuidIds")

-- | Additional features which are needed for the complete specification of language constraints in Hydra, above and beyond TinkerPop Graph.Features
data ExtraFeatures m = 
  ExtraFeatures {
    forall m. ExtraFeatures m -> Type m -> Bool
extraFeaturesSupportsMapKey :: (Core.Type m -> Bool)}

_ExtraFeatures :: Name
_ExtraFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.ExtraFeatures")

_ExtraFeatures_supportsMapKey :: FieldName
_ExtraFeatures_supportsMapKey = (String -> FieldName
Core.FieldName String
"supportsMapKey")

-- | An interface that represents the capabilities of a Graph implementation. By default all methods of features return true and it is up to implementers to disable feature they don't support. Users should check features prior to using various functions of TinkerPop to help ensure code portability across implementations. For example, a common usage would be to check if a graph supports transactions prior to calling the commit method on Graph.tx().
-- | 
-- | As an additional notice to Graph Providers, feature methods will be used by the test suite to determine which tests will be ignored and which will be executed, therefore proper setting of these features is essential to maximizing the amount of testing performed by the suite. Further note, that these methods may be called by the TinkerPop core code to determine what operations may be appropriately executed which will have impact on features utilized by users.
data Features = 
  Features {
    -- | Gets the features related to edge operation.
    Features -> EdgeFeatures
featuresEdge :: EdgeFeatures,
    -- | Gets the features related to graph operation.
    Features -> GraphFeatures
featuresGraph :: GraphFeatures,
    -- | Gets the features related to vertex operation.
    Features -> VertexFeatures
featuresVertex :: VertexFeatures}
  deriving (Features -> Features -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Features -> Features -> Bool
$c/= :: Features -> Features -> Bool
== :: Features -> Features -> Bool
$c== :: Features -> Features -> Bool
Eq, Eq Features
Features -> Features -> Bool
Features -> Features -> Ordering
Features -> Features -> Features
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Features -> Features -> Features
$cmin :: Features -> Features -> Features
max :: Features -> Features -> Features
$cmax :: Features -> Features -> Features
>= :: Features -> Features -> Bool
$c>= :: Features -> Features -> Bool
> :: Features -> Features -> Bool
$c> :: Features -> Features -> Bool
<= :: Features -> Features -> Bool
$c<= :: Features -> Features -> Bool
< :: Features -> Features -> Bool
$c< :: Features -> Features -> Bool
compare :: Features -> Features -> Ordering
$ccompare :: Features -> Features -> Ordering
Ord, ReadPrec [Features]
ReadPrec Features
Int -> ReadS Features
ReadS [Features]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Features]
$creadListPrec :: ReadPrec [Features]
readPrec :: ReadPrec Features
$creadPrec :: ReadPrec Features
readList :: ReadS [Features]
$creadList :: ReadS [Features]
readsPrec :: Int -> ReadS Features
$creadsPrec :: Int -> ReadS Features
Read, Int -> Features -> ShowS
[Features] -> ShowS
Features -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Features] -> ShowS
$cshowList :: [Features] -> ShowS
show :: Features -> String
$cshow :: Features -> String
showsPrec :: Int -> Features -> ShowS
$cshowsPrec :: Int -> Features -> ShowS
Show)

_Features :: Name
_Features = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.Features")

_Features_edge :: FieldName
_Features_edge = (String -> FieldName
Core.FieldName String
"edge")

_Features_graph :: FieldName
_Features_graph = (String -> FieldName
Core.FieldName String
"graph")

_Features_vertex :: FieldName
_Features_vertex = (String -> FieldName
Core.FieldName String
"vertex")

-- | Features specific to a operations of a graph.
data GraphFeatures = 
  GraphFeatures {
    -- | Determines if the Graph implementation supports GraphComputer based processing.
    GraphFeatures -> Bool
graphFeaturesSupportsComputer :: Bool,
    -- | Determines if the Graph implementation supports more than one connection to the same instance at the same time.
    GraphFeatures -> Bool
graphFeaturesSupportsConcurrentAccess :: Bool,
    -- | Determines if the Graph implementations supports read operations as executed with the GraphTraversalSource.io(String) step.
    GraphFeatures -> Bool
graphFeaturesSupportsIoRead :: Bool,
    -- | Determines if the Graph implementations supports write operations as executed with the GraphTraversalSource.io(String) step.
    GraphFeatures -> Bool
graphFeaturesSupportsIoWrite :: Bool,
    -- | Determines if the Graph implementation supports persisting it's contents natively to disk.
    GraphFeatures -> Bool
graphFeaturesSupportsPersistence :: Bool,
    -- | Determines if the Graph implementation supports threaded transactions which allow a transaction to be executed across multiple threads via Transaction.createThreadedTx().
    GraphFeatures -> Bool
graphFeaturesSupportsThreadedTransactions :: Bool,
    -- | Determines if the Graph implementations supports transactions.
    GraphFeatures -> Bool
graphFeaturesSupportsTransactions :: Bool,
    -- | Gets the features related to graph sideEffects operation.
    GraphFeatures -> VariableFeatures
graphFeaturesVariables :: VariableFeatures}
  deriving (GraphFeatures -> GraphFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GraphFeatures -> GraphFeatures -> Bool
$c/= :: GraphFeatures -> GraphFeatures -> Bool
== :: GraphFeatures -> GraphFeatures -> Bool
$c== :: GraphFeatures -> GraphFeatures -> Bool
Eq, Eq GraphFeatures
GraphFeatures -> GraphFeatures -> Bool
GraphFeatures -> GraphFeatures -> Ordering
GraphFeatures -> GraphFeatures -> GraphFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GraphFeatures -> GraphFeatures -> GraphFeatures
$cmin :: GraphFeatures -> GraphFeatures -> GraphFeatures
max :: GraphFeatures -> GraphFeatures -> GraphFeatures
$cmax :: GraphFeatures -> GraphFeatures -> GraphFeatures
>= :: GraphFeatures -> GraphFeatures -> Bool
$c>= :: GraphFeatures -> GraphFeatures -> Bool
> :: GraphFeatures -> GraphFeatures -> Bool
$c> :: GraphFeatures -> GraphFeatures -> Bool
<= :: GraphFeatures -> GraphFeatures -> Bool
$c<= :: GraphFeatures -> GraphFeatures -> Bool
< :: GraphFeatures -> GraphFeatures -> Bool
$c< :: GraphFeatures -> GraphFeatures -> Bool
compare :: GraphFeatures -> GraphFeatures -> Ordering
$ccompare :: GraphFeatures -> GraphFeatures -> Ordering
Ord, ReadPrec [GraphFeatures]
ReadPrec GraphFeatures
Int -> ReadS GraphFeatures
ReadS [GraphFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GraphFeatures]
$creadListPrec :: ReadPrec [GraphFeatures]
readPrec :: ReadPrec GraphFeatures
$creadPrec :: ReadPrec GraphFeatures
readList :: ReadS [GraphFeatures]
$creadList :: ReadS [GraphFeatures]
readsPrec :: Int -> ReadS GraphFeatures
$creadsPrec :: Int -> ReadS GraphFeatures
Read, Int -> GraphFeatures -> ShowS
[GraphFeatures] -> ShowS
GraphFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GraphFeatures] -> ShowS
$cshowList :: [GraphFeatures] -> ShowS
show :: GraphFeatures -> String
$cshow :: GraphFeatures -> String
showsPrec :: Int -> GraphFeatures -> ShowS
$cshowsPrec :: Int -> GraphFeatures -> ShowS
Show)

_GraphFeatures :: Name
_GraphFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.GraphFeatures")

_GraphFeatures_supportsComputer :: FieldName
_GraphFeatures_supportsComputer = (String -> FieldName
Core.FieldName String
"supportsComputer")

_GraphFeatures_supportsConcurrentAccess :: FieldName
_GraphFeatures_supportsConcurrentAccess = (String -> FieldName
Core.FieldName String
"supportsConcurrentAccess")

_GraphFeatures_supportsIoRead :: FieldName
_GraphFeatures_supportsIoRead = (String -> FieldName
Core.FieldName String
"supportsIoRead")

_GraphFeatures_supportsIoWrite :: FieldName
_GraphFeatures_supportsIoWrite = (String -> FieldName
Core.FieldName String
"supportsIoWrite")

_GraphFeatures_supportsPersistence :: FieldName
_GraphFeatures_supportsPersistence = (String -> FieldName
Core.FieldName String
"supportsPersistence")

_GraphFeatures_supportsThreadedTransactions :: FieldName
_GraphFeatures_supportsThreadedTransactions = (String -> FieldName
Core.FieldName String
"supportsThreadedTransactions")

_GraphFeatures_supportsTransactions :: FieldName
_GraphFeatures_supportsTransactions = (String -> FieldName
Core.FieldName String
"supportsTransactions")

_GraphFeatures_variables :: FieldName
_GraphFeatures_variables = (String -> FieldName
Core.FieldName String
"variables")

-- | A base interface for Edge or Vertex Property features.
data PropertyFeatures = 
  PropertyFeatures {
    PropertyFeatures -> DataTypeFeatures
propertyFeaturesDataTypeFeatures :: DataTypeFeatures,
    -- | Determines if an Element allows for the processing of at least one data type defined by the features.
    PropertyFeatures -> Bool
propertyFeaturesSupportsProperties :: Bool}
  deriving (PropertyFeatures -> PropertyFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyFeatures -> PropertyFeatures -> Bool
$c/= :: PropertyFeatures -> PropertyFeatures -> Bool
== :: PropertyFeatures -> PropertyFeatures -> Bool
$c== :: PropertyFeatures -> PropertyFeatures -> Bool
Eq, Eq PropertyFeatures
PropertyFeatures -> PropertyFeatures -> Bool
PropertyFeatures -> PropertyFeatures -> Ordering
PropertyFeatures -> PropertyFeatures -> PropertyFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
$cmin :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
max :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
$cmax :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
>= :: PropertyFeatures -> PropertyFeatures -> Bool
$c>= :: PropertyFeatures -> PropertyFeatures -> Bool
> :: PropertyFeatures -> PropertyFeatures -> Bool
$c> :: PropertyFeatures -> PropertyFeatures -> Bool
<= :: PropertyFeatures -> PropertyFeatures -> Bool
$c<= :: PropertyFeatures -> PropertyFeatures -> Bool
< :: PropertyFeatures -> PropertyFeatures -> Bool
$c< :: PropertyFeatures -> PropertyFeatures -> Bool
compare :: PropertyFeatures -> PropertyFeatures -> Ordering
$ccompare :: PropertyFeatures -> PropertyFeatures -> Ordering
Ord, ReadPrec [PropertyFeatures]
ReadPrec PropertyFeatures
Int -> ReadS PropertyFeatures
ReadS [PropertyFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PropertyFeatures]
$creadListPrec :: ReadPrec [PropertyFeatures]
readPrec :: ReadPrec PropertyFeatures
$creadPrec :: ReadPrec PropertyFeatures
readList :: ReadS [PropertyFeatures]
$creadList :: ReadS [PropertyFeatures]
readsPrec :: Int -> ReadS PropertyFeatures
$creadsPrec :: Int -> ReadS PropertyFeatures
Read, Int -> PropertyFeatures -> ShowS
[PropertyFeatures] -> ShowS
PropertyFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PropertyFeatures] -> ShowS
$cshowList :: [PropertyFeatures] -> ShowS
show :: PropertyFeatures -> String
$cshow :: PropertyFeatures -> String
showsPrec :: Int -> PropertyFeatures -> ShowS
$cshowsPrec :: Int -> PropertyFeatures -> ShowS
Show)

_PropertyFeatures :: Name
_PropertyFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.PropertyFeatures")

_PropertyFeatures_dataTypeFeatures :: FieldName
_PropertyFeatures_dataTypeFeatures = (String -> FieldName
Core.FieldName String
"dataTypeFeatures")

_PropertyFeatures_supportsProperties :: FieldName
_PropertyFeatures_supportsProperties = (String -> FieldName
Core.FieldName String
"supportsProperties")

-- | Features for Graph.Variables.
data VariableFeatures = 
  VariableFeatures {
    VariableFeatures -> DataTypeFeatures
variableFeaturesDataTypeFeatures :: DataTypeFeatures,
    -- | If any of the features on Graph.Features.VariableFeatures is true then this value must be true.
    VariableFeatures -> Bool
variableFeaturesSupportsVariables :: Bool}
  deriving (VariableFeatures -> VariableFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableFeatures -> VariableFeatures -> Bool
$c/= :: VariableFeatures -> VariableFeatures -> Bool
== :: VariableFeatures -> VariableFeatures -> Bool
$c== :: VariableFeatures -> VariableFeatures -> Bool
Eq, Eq VariableFeatures
VariableFeatures -> VariableFeatures -> Bool
VariableFeatures -> VariableFeatures -> Ordering
VariableFeatures -> VariableFeatures -> VariableFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableFeatures -> VariableFeatures -> VariableFeatures
$cmin :: VariableFeatures -> VariableFeatures -> VariableFeatures
max :: VariableFeatures -> VariableFeatures -> VariableFeatures
$cmax :: VariableFeatures -> VariableFeatures -> VariableFeatures
>= :: VariableFeatures -> VariableFeatures -> Bool
$c>= :: VariableFeatures -> VariableFeatures -> Bool
> :: VariableFeatures -> VariableFeatures -> Bool
$c> :: VariableFeatures -> VariableFeatures -> Bool
<= :: VariableFeatures -> VariableFeatures -> Bool
$c<= :: VariableFeatures -> VariableFeatures -> Bool
< :: VariableFeatures -> VariableFeatures -> Bool
$c< :: VariableFeatures -> VariableFeatures -> Bool
compare :: VariableFeatures -> VariableFeatures -> Ordering
$ccompare :: VariableFeatures -> VariableFeatures -> Ordering
Ord, ReadPrec [VariableFeatures]
ReadPrec VariableFeatures
Int -> ReadS VariableFeatures
ReadS [VariableFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableFeatures]
$creadListPrec :: ReadPrec [VariableFeatures]
readPrec :: ReadPrec VariableFeatures
$creadPrec :: ReadPrec VariableFeatures
readList :: ReadS [VariableFeatures]
$creadList :: ReadS [VariableFeatures]
readsPrec :: Int -> ReadS VariableFeatures
$creadsPrec :: Int -> ReadS VariableFeatures
Read, Int -> VariableFeatures -> ShowS
[VariableFeatures] -> ShowS
VariableFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariableFeatures] -> ShowS
$cshowList :: [VariableFeatures] -> ShowS
show :: VariableFeatures -> String
$cshow :: VariableFeatures -> String
showsPrec :: Int -> VariableFeatures -> ShowS
$cshowsPrec :: Int -> VariableFeatures -> ShowS
Show)

_VariableFeatures :: Name
_VariableFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.VariableFeatures")

_VariableFeatures_dataTypeFeatures :: FieldName
_VariableFeatures_dataTypeFeatures = (String -> FieldName
Core.FieldName String
"dataTypeFeatures")

_VariableFeatures_supportsVariables :: FieldName
_VariableFeatures_supportsVariables = (String -> FieldName
Core.FieldName String
"supportsVariables")

-- | Features that are related to Vertex operations.
data VertexFeatures = 
  VertexFeatures {
    VertexFeatures -> ElementFeatures
vertexFeaturesElementFeatures :: ElementFeatures,
    VertexFeatures -> VertexPropertyFeatures
vertexFeaturesProperties :: VertexPropertyFeatures,
    -- | Determines if a Vertex can be added to the Graph.
    VertexFeatures -> Bool
vertexFeaturesSupportsAddVertices :: Bool,
    -- | Determines if a Vertex can support non-unique values on the same key.
    VertexFeatures -> Bool
vertexFeaturesSupportsDuplicateMultiProperties :: Bool,
    -- | Determines if a Vertex can support properties on vertex properties.
    VertexFeatures -> Bool
vertexFeaturesSupportsMetaProperties :: Bool,
    -- | Determines if a Vertex can support multiple properties with the same key.
    VertexFeatures -> Bool
vertexFeaturesSupportsMultiProperties :: Bool,
    -- | Determines if a Vertex can be removed from the Graph.
    VertexFeatures -> Bool
vertexFeaturesSupportsRemoveVertices :: Bool,
    -- | Determines if the Graph implementation uses upsert functionality as opposed to insert functionality for Graph.addVertex(String).
    VertexFeatures -> Bool
vertexFeaturesSupportsUpsert :: Bool}
  deriving (VertexFeatures -> VertexFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VertexFeatures -> VertexFeatures -> Bool
$c/= :: VertexFeatures -> VertexFeatures -> Bool
== :: VertexFeatures -> VertexFeatures -> Bool
$c== :: VertexFeatures -> VertexFeatures -> Bool
Eq, Eq VertexFeatures
VertexFeatures -> VertexFeatures -> Bool
VertexFeatures -> VertexFeatures -> Ordering
VertexFeatures -> VertexFeatures -> VertexFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VertexFeatures -> VertexFeatures -> VertexFeatures
$cmin :: VertexFeatures -> VertexFeatures -> VertexFeatures
max :: VertexFeatures -> VertexFeatures -> VertexFeatures
$cmax :: VertexFeatures -> VertexFeatures -> VertexFeatures
>= :: VertexFeatures -> VertexFeatures -> Bool
$c>= :: VertexFeatures -> VertexFeatures -> Bool
> :: VertexFeatures -> VertexFeatures -> Bool
$c> :: VertexFeatures -> VertexFeatures -> Bool
<= :: VertexFeatures -> VertexFeatures -> Bool
$c<= :: VertexFeatures -> VertexFeatures -> Bool
< :: VertexFeatures -> VertexFeatures -> Bool
$c< :: VertexFeatures -> VertexFeatures -> Bool
compare :: VertexFeatures -> VertexFeatures -> Ordering
$ccompare :: VertexFeatures -> VertexFeatures -> Ordering
Ord, ReadPrec [VertexFeatures]
ReadPrec VertexFeatures
Int -> ReadS VertexFeatures
ReadS [VertexFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VertexFeatures]
$creadListPrec :: ReadPrec [VertexFeatures]
readPrec :: ReadPrec VertexFeatures
$creadPrec :: ReadPrec VertexFeatures
readList :: ReadS [VertexFeatures]
$creadList :: ReadS [VertexFeatures]
readsPrec :: Int -> ReadS VertexFeatures
$creadsPrec :: Int -> ReadS VertexFeatures
Read, Int -> VertexFeatures -> ShowS
[VertexFeatures] -> ShowS
VertexFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VertexFeatures] -> ShowS
$cshowList :: [VertexFeatures] -> ShowS
show :: VertexFeatures -> String
$cshow :: VertexFeatures -> String
showsPrec :: Int -> VertexFeatures -> ShowS
$cshowsPrec :: Int -> VertexFeatures -> ShowS
Show)

_VertexFeatures :: Name
_VertexFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.VertexFeatures")

_VertexFeatures_elementFeatures :: FieldName
_VertexFeatures_elementFeatures = (String -> FieldName
Core.FieldName String
"elementFeatures")

_VertexFeatures_properties :: FieldName
_VertexFeatures_properties = (String -> FieldName
Core.FieldName String
"properties")

_VertexFeatures_supportsAddVertices :: FieldName
_VertexFeatures_supportsAddVertices = (String -> FieldName
Core.FieldName String
"supportsAddVertices")

_VertexFeatures_supportsDuplicateMultiProperties :: FieldName
_VertexFeatures_supportsDuplicateMultiProperties = (String -> FieldName
Core.FieldName String
"supportsDuplicateMultiProperties")

_VertexFeatures_supportsMetaProperties :: FieldName
_VertexFeatures_supportsMetaProperties = (String -> FieldName
Core.FieldName String
"supportsMetaProperties")

_VertexFeatures_supportsMultiProperties :: FieldName
_VertexFeatures_supportsMultiProperties = (String -> FieldName
Core.FieldName String
"supportsMultiProperties")

_VertexFeatures_supportsRemoveVertices :: FieldName
_VertexFeatures_supportsRemoveVertices = (String -> FieldName
Core.FieldName String
"supportsRemoveVertices")

_VertexFeatures_supportsUpsert :: FieldName
_VertexFeatures_supportsUpsert = (String -> FieldName
Core.FieldName String
"supportsUpsert")

-- | Features that are related to Vertex Property objects.
data VertexPropertyFeatures = 
  VertexPropertyFeatures {
    VertexPropertyFeatures -> DataTypeFeatures
vertexPropertyFeaturesDataTypeFeatures :: DataTypeFeatures,
    VertexPropertyFeatures -> PropertyFeatures
vertexPropertyFeaturesPropertyFeatures :: PropertyFeatures,
    VertexPropertyFeatures -> ElementFeatures
vertexPropertyFeaturesElementFeatures :: ElementFeatures,
    -- | Determines if a VertexProperty allows properties to be removed.
    VertexPropertyFeatures -> Bool
vertexPropertyFeaturesSupportsRemove :: Bool}
  deriving (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c/= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
== :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c== :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
Eq, Eq VertexPropertyFeatures
VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering
VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
$cmin :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
max :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
$cmax :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
>= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c>= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
> :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c> :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
<= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c<= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
< :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c< :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
compare :: VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering
$ccompare :: VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering
Ord, ReadPrec [VertexPropertyFeatures]
ReadPrec VertexPropertyFeatures
Int -> ReadS VertexPropertyFeatures
ReadS [VertexPropertyFeatures]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VertexPropertyFeatures]
$creadListPrec :: ReadPrec [VertexPropertyFeatures]
readPrec :: ReadPrec VertexPropertyFeatures
$creadPrec :: ReadPrec VertexPropertyFeatures
readList :: ReadS [VertexPropertyFeatures]
$creadList :: ReadS [VertexPropertyFeatures]
readsPrec :: Int -> ReadS VertexPropertyFeatures
$creadsPrec :: Int -> ReadS VertexPropertyFeatures
Read, Int -> VertexPropertyFeatures -> ShowS
[VertexPropertyFeatures] -> ShowS
VertexPropertyFeatures -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VertexPropertyFeatures] -> ShowS
$cshowList :: [VertexPropertyFeatures] -> ShowS
show :: VertexPropertyFeatures -> String
$cshow :: VertexPropertyFeatures -> String
showsPrec :: Int -> VertexPropertyFeatures -> ShowS
$cshowsPrec :: Int -> VertexPropertyFeatures -> ShowS
Show)

_VertexPropertyFeatures :: Name
_VertexPropertyFeatures = (String -> Name
Core.Name String
"hydra/ext/tinkerpop/features.VertexPropertyFeatures")

_VertexPropertyFeatures_dataTypeFeatures :: FieldName
_VertexPropertyFeatures_dataTypeFeatures = (String -> FieldName
Core.FieldName String
"dataTypeFeatures")

_VertexPropertyFeatures_propertyFeatures :: FieldName
_VertexPropertyFeatures_propertyFeatures = (String -> FieldName
Core.FieldName String
"propertyFeatures")

_VertexPropertyFeatures_elementFeatures :: FieldName
_VertexPropertyFeatures_elementFeatures = (String -> FieldName
Core.FieldName String
"elementFeatures")

_VertexPropertyFeatures_supportsRemove :: FieldName
_VertexPropertyFeatures_supportsRemove = (String -> FieldName
Core.FieldName String
"supportsRemove")