module Hydra.Langs.Tinkerpop.Features where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data DataTypeFeatures =
DataTypeFeatures {
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsBooleanArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsBooleanValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsByteArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsByteValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsDoubleArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsDoubleValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsFloatArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsFloatValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsIntegerArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsIntegerValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsLongArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsLongValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsMapValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsMixedListValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsSerializableValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsStringArrayValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsStringValues :: Bool,
DataTypeFeatures -> Bool
dataTypeFeaturesSupportsUniformListValues :: Bool}
deriving (DataTypeFeatures -> DataTypeFeatures -> Bool
(DataTypeFeatures -> DataTypeFeatures -> Bool)
-> (DataTypeFeatures -> DataTypeFeatures -> Bool)
-> Eq DataTypeFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataTypeFeatures -> DataTypeFeatures -> Bool
== :: DataTypeFeatures -> DataTypeFeatures -> Bool
$c/= :: DataTypeFeatures -> DataTypeFeatures -> Bool
/= :: DataTypeFeatures -> DataTypeFeatures -> Bool
Eq, Eq DataTypeFeatures
Eq DataTypeFeatures =>
(DataTypeFeatures -> DataTypeFeatures -> Ordering)
-> (DataTypeFeatures -> DataTypeFeatures -> Bool)
-> (DataTypeFeatures -> DataTypeFeatures -> Bool)
-> (DataTypeFeatures -> DataTypeFeatures -> Bool)
-> (DataTypeFeatures -> DataTypeFeatures -> Bool)
-> (DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures)
-> (DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures)
-> Ord 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
$ccompare :: DataTypeFeatures -> DataTypeFeatures -> Ordering
compare :: DataTypeFeatures -> DataTypeFeatures -> Ordering
$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
>= :: DataTypeFeatures -> DataTypeFeatures -> Bool
$cmax :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
max :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
$cmin :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
min :: DataTypeFeatures -> DataTypeFeatures -> DataTypeFeatures
Ord, ReadPrec [DataTypeFeatures]
ReadPrec DataTypeFeatures
Int -> ReadS DataTypeFeatures
ReadS [DataTypeFeatures]
(Int -> ReadS DataTypeFeatures)
-> ReadS [DataTypeFeatures]
-> ReadPrec DataTypeFeatures
-> ReadPrec [DataTypeFeatures]
-> Read DataTypeFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataTypeFeatures
readsPrec :: Int -> ReadS DataTypeFeatures
$creadList :: ReadS [DataTypeFeatures]
readList :: ReadS [DataTypeFeatures]
$creadPrec :: ReadPrec DataTypeFeatures
readPrec :: ReadPrec DataTypeFeatures
$creadListPrec :: ReadPrec [DataTypeFeatures]
readListPrec :: ReadPrec [DataTypeFeatures]
Read, Int -> DataTypeFeatures -> ShowS
[DataTypeFeatures] -> ShowS
DataTypeFeatures -> String
(Int -> DataTypeFeatures -> ShowS)
-> (DataTypeFeatures -> String)
-> ([DataTypeFeatures] -> ShowS)
-> Show DataTypeFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataTypeFeatures -> ShowS
showsPrec :: Int -> DataTypeFeatures -> ShowS
$cshow :: DataTypeFeatures -> String
show :: DataTypeFeatures -> String
$cshowList :: [DataTypeFeatures] -> ShowS
showList :: [DataTypeFeatures] -> ShowS
Show)
_DataTypeFeatures :: Name
_DataTypeFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.DataTypeFeatures")
_DataTypeFeatures_supportsBooleanArrayValues :: Name
_DataTypeFeatures_supportsBooleanArrayValues = (String -> Name
Core.Name String
"supportsBooleanArrayValues")
_DataTypeFeatures_supportsBooleanValues :: Name
_DataTypeFeatures_supportsBooleanValues = (String -> Name
Core.Name String
"supportsBooleanValues")
_DataTypeFeatures_supportsByteArrayValues :: Name
_DataTypeFeatures_supportsByteArrayValues = (String -> Name
Core.Name String
"supportsByteArrayValues")
_DataTypeFeatures_supportsByteValues :: Name
_DataTypeFeatures_supportsByteValues = (String -> Name
Core.Name String
"supportsByteValues")
_DataTypeFeatures_supportsDoubleArrayValues :: Name
_DataTypeFeatures_supportsDoubleArrayValues = (String -> Name
Core.Name String
"supportsDoubleArrayValues")
_DataTypeFeatures_supportsDoubleValues :: Name
_DataTypeFeatures_supportsDoubleValues = (String -> Name
Core.Name String
"supportsDoubleValues")
_DataTypeFeatures_supportsFloatArrayValues :: Name
_DataTypeFeatures_supportsFloatArrayValues = (String -> Name
Core.Name String
"supportsFloatArrayValues")
_DataTypeFeatures_supportsFloatValues :: Name
_DataTypeFeatures_supportsFloatValues = (String -> Name
Core.Name String
"supportsFloatValues")
_DataTypeFeatures_supportsIntegerArrayValues :: Name
_DataTypeFeatures_supportsIntegerArrayValues = (String -> Name
Core.Name String
"supportsIntegerArrayValues")
_DataTypeFeatures_supportsIntegerValues :: Name
_DataTypeFeatures_supportsIntegerValues = (String -> Name
Core.Name String
"supportsIntegerValues")
_DataTypeFeatures_supportsLongArrayValues :: Name
_DataTypeFeatures_supportsLongArrayValues = (String -> Name
Core.Name String
"supportsLongArrayValues")
_DataTypeFeatures_supportsLongValues :: Name
_DataTypeFeatures_supportsLongValues = (String -> Name
Core.Name String
"supportsLongValues")
_DataTypeFeatures_supportsMapValues :: Name
_DataTypeFeatures_supportsMapValues = (String -> Name
Core.Name String
"supportsMapValues")
_DataTypeFeatures_supportsMixedListValues :: Name
_DataTypeFeatures_supportsMixedListValues = (String -> Name
Core.Name String
"supportsMixedListValues")
_DataTypeFeatures_supportsSerializableValues :: Name
_DataTypeFeatures_supportsSerializableValues = (String -> Name
Core.Name String
"supportsSerializableValues")
_DataTypeFeatures_supportsStringArrayValues :: Name
_DataTypeFeatures_supportsStringArrayValues = (String -> Name
Core.Name String
"supportsStringArrayValues")
_DataTypeFeatures_supportsStringValues :: Name
_DataTypeFeatures_supportsStringValues = (String -> Name
Core.Name String
"supportsStringValues")
_DataTypeFeatures_supportsUniformListValues :: Name
_DataTypeFeatures_supportsUniformListValues = (String -> Name
Core.Name String
"supportsUniformListValues")
data EdgeFeatures =
EdgeFeatures {
EdgeFeatures -> ElementFeatures
edgeFeaturesElementFeatures :: ElementFeatures,
EdgeFeatures -> EdgePropertyFeatures
edgeFeaturesProperties :: EdgePropertyFeatures,
EdgeFeatures -> Bool
edgeFeaturesSupportsAddEdges :: Bool,
EdgeFeatures -> Bool
edgeFeaturesSupportsRemoveEdges :: Bool,
EdgeFeatures -> Bool
edgeFeaturesSupportsUpsert :: Bool}
deriving (EdgeFeatures -> EdgeFeatures -> Bool
(EdgeFeatures -> EdgeFeatures -> Bool)
-> (EdgeFeatures -> EdgeFeatures -> Bool) -> Eq EdgeFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeFeatures -> EdgeFeatures -> Bool
== :: EdgeFeatures -> EdgeFeatures -> Bool
$c/= :: EdgeFeatures -> EdgeFeatures -> Bool
/= :: EdgeFeatures -> EdgeFeatures -> Bool
Eq, Eq EdgeFeatures
Eq EdgeFeatures =>
(EdgeFeatures -> EdgeFeatures -> Ordering)
-> (EdgeFeatures -> EdgeFeatures -> Bool)
-> (EdgeFeatures -> EdgeFeatures -> Bool)
-> (EdgeFeatures -> EdgeFeatures -> Bool)
-> (EdgeFeatures -> EdgeFeatures -> Bool)
-> (EdgeFeatures -> EdgeFeatures -> EdgeFeatures)
-> (EdgeFeatures -> EdgeFeatures -> EdgeFeatures)
-> Ord 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
$ccompare :: EdgeFeatures -> EdgeFeatures -> Ordering
compare :: EdgeFeatures -> EdgeFeatures -> Ordering
$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
>= :: EdgeFeatures -> EdgeFeatures -> Bool
$cmax :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
max :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
$cmin :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
min :: EdgeFeatures -> EdgeFeatures -> EdgeFeatures
Ord, ReadPrec [EdgeFeatures]
ReadPrec EdgeFeatures
Int -> ReadS EdgeFeatures
ReadS [EdgeFeatures]
(Int -> ReadS EdgeFeatures)
-> ReadS [EdgeFeatures]
-> ReadPrec EdgeFeatures
-> ReadPrec [EdgeFeatures]
-> Read EdgeFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgeFeatures
readsPrec :: Int -> ReadS EdgeFeatures
$creadList :: ReadS [EdgeFeatures]
readList :: ReadS [EdgeFeatures]
$creadPrec :: ReadPrec EdgeFeatures
readPrec :: ReadPrec EdgeFeatures
$creadListPrec :: ReadPrec [EdgeFeatures]
readListPrec :: ReadPrec [EdgeFeatures]
Read, Int -> EdgeFeatures -> ShowS
[EdgeFeatures] -> ShowS
EdgeFeatures -> String
(Int -> EdgeFeatures -> ShowS)
-> (EdgeFeatures -> String)
-> ([EdgeFeatures] -> ShowS)
-> Show EdgeFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeFeatures -> ShowS
showsPrec :: Int -> EdgeFeatures -> ShowS
$cshow :: EdgeFeatures -> String
show :: EdgeFeatures -> String
$cshowList :: [EdgeFeatures] -> ShowS
showList :: [EdgeFeatures] -> ShowS
Show)
_EdgeFeatures :: Name
_EdgeFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.EdgeFeatures")
_EdgeFeatures_elementFeatures :: Name
_EdgeFeatures_elementFeatures = (String -> Name
Core.Name String
"elementFeatures")
_EdgeFeatures_properties :: Name
_EdgeFeatures_properties = (String -> Name
Core.Name String
"properties")
_EdgeFeatures_supportsAddEdges :: Name
_EdgeFeatures_supportsAddEdges = (String -> Name
Core.Name String
"supportsAddEdges")
_EdgeFeatures_supportsRemoveEdges :: Name
_EdgeFeatures_supportsRemoveEdges = (String -> Name
Core.Name String
"supportsRemoveEdges")
_EdgeFeatures_supportsUpsert :: Name
_EdgeFeatures_supportsUpsert = (String -> Name
Core.Name String
"supportsUpsert")
data EdgePropertyFeatures =
EdgePropertyFeatures {
EdgePropertyFeatures -> PropertyFeatures
edgePropertyFeaturesPropertyFeatures :: PropertyFeatures}
deriving (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
(EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> Eq EdgePropertyFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
== :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$c/= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
/= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
Eq, Eq EdgePropertyFeatures
Eq EdgePropertyFeatures =>
(EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering)
-> (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> (EdgePropertyFeatures -> EdgePropertyFeatures -> Bool)
-> (EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures)
-> (EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures)
-> Ord 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
$ccompare :: EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering
compare :: EdgePropertyFeatures -> EdgePropertyFeatures -> Ordering
$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
>= :: EdgePropertyFeatures -> EdgePropertyFeatures -> Bool
$cmax :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
max :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
$cmin :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
min :: EdgePropertyFeatures
-> EdgePropertyFeatures -> EdgePropertyFeatures
Ord, ReadPrec [EdgePropertyFeatures]
ReadPrec EdgePropertyFeatures
Int -> ReadS EdgePropertyFeatures
ReadS [EdgePropertyFeatures]
(Int -> ReadS EdgePropertyFeatures)
-> ReadS [EdgePropertyFeatures]
-> ReadPrec EdgePropertyFeatures
-> ReadPrec [EdgePropertyFeatures]
-> Read EdgePropertyFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgePropertyFeatures
readsPrec :: Int -> ReadS EdgePropertyFeatures
$creadList :: ReadS [EdgePropertyFeatures]
readList :: ReadS [EdgePropertyFeatures]
$creadPrec :: ReadPrec EdgePropertyFeatures
readPrec :: ReadPrec EdgePropertyFeatures
$creadListPrec :: ReadPrec [EdgePropertyFeatures]
readListPrec :: ReadPrec [EdgePropertyFeatures]
Read, Int -> EdgePropertyFeatures -> ShowS
[EdgePropertyFeatures] -> ShowS
EdgePropertyFeatures -> String
(Int -> EdgePropertyFeatures -> ShowS)
-> (EdgePropertyFeatures -> String)
-> ([EdgePropertyFeatures] -> ShowS)
-> Show EdgePropertyFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgePropertyFeatures -> ShowS
showsPrec :: Int -> EdgePropertyFeatures -> ShowS
$cshow :: EdgePropertyFeatures -> String
show :: EdgePropertyFeatures -> String
$cshowList :: [EdgePropertyFeatures] -> ShowS
showList :: [EdgePropertyFeatures] -> ShowS
Show)
_EdgePropertyFeatures :: Name
_EdgePropertyFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.EdgePropertyFeatures")
_EdgePropertyFeatures_propertyFeatures :: Name
_EdgePropertyFeatures_propertyFeatures = (String -> Name
Core.Name String
"propertyFeatures")
data ElementFeatures =
ElementFeatures {
ElementFeatures -> Bool
elementFeaturesSupportsAddProperty :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsAnyIds :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsCustomIds :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsNumericIds :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsRemoveProperty :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsStringIds :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsUserSuppliedIds :: Bool,
ElementFeatures -> Bool
elementFeaturesSupportsUuidIds :: Bool}
deriving (ElementFeatures -> ElementFeatures -> Bool
(ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> Eq ElementFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElementFeatures -> ElementFeatures -> Bool
== :: ElementFeatures -> ElementFeatures -> Bool
$c/= :: ElementFeatures -> ElementFeatures -> Bool
/= :: ElementFeatures -> ElementFeatures -> Bool
Eq, Eq ElementFeatures
Eq ElementFeatures =>
(ElementFeatures -> ElementFeatures -> Ordering)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> Bool)
-> (ElementFeatures -> ElementFeatures -> ElementFeatures)
-> (ElementFeatures -> ElementFeatures -> ElementFeatures)
-> Ord 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
$ccompare :: ElementFeatures -> ElementFeatures -> Ordering
compare :: ElementFeatures -> ElementFeatures -> Ordering
$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
>= :: ElementFeatures -> ElementFeatures -> Bool
$cmax :: ElementFeatures -> ElementFeatures -> ElementFeatures
max :: ElementFeatures -> ElementFeatures -> ElementFeatures
$cmin :: ElementFeatures -> ElementFeatures -> ElementFeatures
min :: ElementFeatures -> ElementFeatures -> ElementFeatures
Ord, ReadPrec [ElementFeatures]
ReadPrec ElementFeatures
Int -> ReadS ElementFeatures
ReadS [ElementFeatures]
(Int -> ReadS ElementFeatures)
-> ReadS [ElementFeatures]
-> ReadPrec ElementFeatures
-> ReadPrec [ElementFeatures]
-> Read ElementFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ElementFeatures
readsPrec :: Int -> ReadS ElementFeatures
$creadList :: ReadS [ElementFeatures]
readList :: ReadS [ElementFeatures]
$creadPrec :: ReadPrec ElementFeatures
readPrec :: ReadPrec ElementFeatures
$creadListPrec :: ReadPrec [ElementFeatures]
readListPrec :: ReadPrec [ElementFeatures]
Read, Int -> ElementFeatures -> ShowS
[ElementFeatures] -> ShowS
ElementFeatures -> String
(Int -> ElementFeatures -> ShowS)
-> (ElementFeatures -> String)
-> ([ElementFeatures] -> ShowS)
-> Show ElementFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElementFeatures -> ShowS
showsPrec :: Int -> ElementFeatures -> ShowS
$cshow :: ElementFeatures -> String
show :: ElementFeatures -> String
$cshowList :: [ElementFeatures] -> ShowS
showList :: [ElementFeatures] -> ShowS
Show)
_ElementFeatures :: Name
_ElementFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.ElementFeatures")
_ElementFeatures_supportsAddProperty :: Name
_ElementFeatures_supportsAddProperty = (String -> Name
Core.Name String
"supportsAddProperty")
_ElementFeatures_supportsAnyIds :: Name
_ElementFeatures_supportsAnyIds = (String -> Name
Core.Name String
"supportsAnyIds")
_ElementFeatures_supportsCustomIds :: Name
_ElementFeatures_supportsCustomIds = (String -> Name
Core.Name String
"supportsCustomIds")
_ElementFeatures_supportsNumericIds :: Name
_ElementFeatures_supportsNumericIds = (String -> Name
Core.Name String
"supportsNumericIds")
_ElementFeatures_supportsRemoveProperty :: Name
_ElementFeatures_supportsRemoveProperty = (String -> Name
Core.Name String
"supportsRemoveProperty")
_ElementFeatures_supportsStringIds :: Name
_ElementFeatures_supportsStringIds = (String -> Name
Core.Name String
"supportsStringIds")
_ElementFeatures_supportsUserSuppliedIds :: Name
_ElementFeatures_supportsUserSuppliedIds = (String -> Name
Core.Name String
"supportsUserSuppliedIds")
_ElementFeatures_supportsUuidIds :: Name
_ElementFeatures_supportsUuidIds = (String -> Name
Core.Name String
"supportsUuidIds")
data a =
{
:: (Core.Type -> Bool)}
= (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.ExtraFeatures")
= (String -> Name
Core.Name String
"supportsMapKey")
data Features =
Features {
Features -> EdgeFeatures
featuresEdge :: EdgeFeatures,
Features -> GraphFeatures
featuresGraph :: GraphFeatures,
Features -> VertexFeatures
featuresVertex :: VertexFeatures}
deriving (Features -> Features -> Bool
(Features -> Features -> Bool)
-> (Features -> Features -> Bool) -> Eq Features
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Features -> Features -> Bool
== :: Features -> Features -> Bool
$c/= :: Features -> Features -> Bool
/= :: Features -> Features -> Bool
Eq, Eq Features
Eq Features =>
(Features -> Features -> Ordering)
-> (Features -> Features -> Bool)
-> (Features -> Features -> Bool)
-> (Features -> Features -> Bool)
-> (Features -> Features -> Bool)
-> (Features -> Features -> Features)
-> (Features -> Features -> Features)
-> Ord 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
$ccompare :: Features -> Features -> Ordering
compare :: Features -> Features -> Ordering
$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
>= :: Features -> Features -> Bool
$cmax :: Features -> Features -> Features
max :: Features -> Features -> Features
$cmin :: Features -> Features -> Features
min :: Features -> Features -> Features
Ord, ReadPrec [Features]
ReadPrec Features
Int -> ReadS Features
ReadS [Features]
(Int -> ReadS Features)
-> ReadS [Features]
-> ReadPrec Features
-> ReadPrec [Features]
-> Read Features
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Features
readsPrec :: Int -> ReadS Features
$creadList :: ReadS [Features]
readList :: ReadS [Features]
$creadPrec :: ReadPrec Features
readPrec :: ReadPrec Features
$creadListPrec :: ReadPrec [Features]
readListPrec :: ReadPrec [Features]
Read, Int -> Features -> ShowS
[Features] -> ShowS
Features -> String
(Int -> Features -> ShowS)
-> (Features -> String) -> ([Features] -> ShowS) -> Show Features
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Features -> ShowS
showsPrec :: Int -> Features -> ShowS
$cshow :: Features -> String
show :: Features -> String
$cshowList :: [Features] -> ShowS
showList :: [Features] -> ShowS
Show)
_Features :: Name
_Features = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.Features")
_Features_edge :: Name
_Features_edge = (String -> Name
Core.Name String
"edge")
_Features_graph :: Name
_Features_graph = (String -> Name
Core.Name String
"graph")
_Features_vertex :: Name
_Features_vertex = (String -> Name
Core.Name String
"vertex")
data GraphFeatures =
GraphFeatures {
GraphFeatures -> Bool
graphFeaturesSupportsComputer :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsConcurrentAccess :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsIoRead :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsIoWrite :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsPersistence :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsThreadedTransactions :: Bool,
GraphFeatures -> Bool
graphFeaturesSupportsTransactions :: Bool,
GraphFeatures -> VariableFeatures
graphFeaturesVariables :: VariableFeatures}
deriving (GraphFeatures -> GraphFeatures -> Bool
(GraphFeatures -> GraphFeatures -> Bool)
-> (GraphFeatures -> GraphFeatures -> Bool) -> Eq GraphFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GraphFeatures -> GraphFeatures -> Bool
== :: GraphFeatures -> GraphFeatures -> Bool
$c/= :: GraphFeatures -> GraphFeatures -> Bool
/= :: GraphFeatures -> GraphFeatures -> Bool
Eq, Eq GraphFeatures
Eq GraphFeatures =>
(GraphFeatures -> GraphFeatures -> Ordering)
-> (GraphFeatures -> GraphFeatures -> Bool)
-> (GraphFeatures -> GraphFeatures -> Bool)
-> (GraphFeatures -> GraphFeatures -> Bool)
-> (GraphFeatures -> GraphFeatures -> Bool)
-> (GraphFeatures -> GraphFeatures -> GraphFeatures)
-> (GraphFeatures -> GraphFeatures -> GraphFeatures)
-> Ord 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
$ccompare :: GraphFeatures -> GraphFeatures -> Ordering
compare :: GraphFeatures -> GraphFeatures -> Ordering
$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
>= :: GraphFeatures -> GraphFeatures -> Bool
$cmax :: GraphFeatures -> GraphFeatures -> GraphFeatures
max :: GraphFeatures -> GraphFeatures -> GraphFeatures
$cmin :: GraphFeatures -> GraphFeatures -> GraphFeatures
min :: GraphFeatures -> GraphFeatures -> GraphFeatures
Ord, ReadPrec [GraphFeatures]
ReadPrec GraphFeatures
Int -> ReadS GraphFeatures
ReadS [GraphFeatures]
(Int -> ReadS GraphFeatures)
-> ReadS [GraphFeatures]
-> ReadPrec GraphFeatures
-> ReadPrec [GraphFeatures]
-> Read GraphFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GraphFeatures
readsPrec :: Int -> ReadS GraphFeatures
$creadList :: ReadS [GraphFeatures]
readList :: ReadS [GraphFeatures]
$creadPrec :: ReadPrec GraphFeatures
readPrec :: ReadPrec GraphFeatures
$creadListPrec :: ReadPrec [GraphFeatures]
readListPrec :: ReadPrec [GraphFeatures]
Read, Int -> GraphFeatures -> ShowS
[GraphFeatures] -> ShowS
GraphFeatures -> String
(Int -> GraphFeatures -> ShowS)
-> (GraphFeatures -> String)
-> ([GraphFeatures] -> ShowS)
-> Show GraphFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GraphFeatures -> ShowS
showsPrec :: Int -> GraphFeatures -> ShowS
$cshow :: GraphFeatures -> String
show :: GraphFeatures -> String
$cshowList :: [GraphFeatures] -> ShowS
showList :: [GraphFeatures] -> ShowS
Show)
_GraphFeatures :: Name
_GraphFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.GraphFeatures")
_GraphFeatures_supportsComputer :: Name
_GraphFeatures_supportsComputer = (String -> Name
Core.Name String
"supportsComputer")
_GraphFeatures_supportsConcurrentAccess :: Name
_GraphFeatures_supportsConcurrentAccess = (String -> Name
Core.Name String
"supportsConcurrentAccess")
_GraphFeatures_supportsIoRead :: Name
_GraphFeatures_supportsIoRead = (String -> Name
Core.Name String
"supportsIoRead")
_GraphFeatures_supportsIoWrite :: Name
_GraphFeatures_supportsIoWrite = (String -> Name
Core.Name String
"supportsIoWrite")
_GraphFeatures_supportsPersistence :: Name
_GraphFeatures_supportsPersistence = (String -> Name
Core.Name String
"supportsPersistence")
_GraphFeatures_supportsThreadedTransactions :: Name
_GraphFeatures_supportsThreadedTransactions = (String -> Name
Core.Name String
"supportsThreadedTransactions")
_GraphFeatures_supportsTransactions :: Name
_GraphFeatures_supportsTransactions = (String -> Name
Core.Name String
"supportsTransactions")
_GraphFeatures_variables :: Name
_GraphFeatures_variables = (String -> Name
Core.Name String
"variables")
data PropertyFeatures =
PropertyFeatures {
PropertyFeatures -> DataTypeFeatures
propertyFeaturesDataTypeFeatures :: DataTypeFeatures,
PropertyFeatures -> Bool
propertyFeaturesSupportsProperties :: Bool}
deriving (PropertyFeatures -> PropertyFeatures -> Bool
(PropertyFeatures -> PropertyFeatures -> Bool)
-> (PropertyFeatures -> PropertyFeatures -> Bool)
-> Eq PropertyFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyFeatures -> PropertyFeatures -> Bool
== :: PropertyFeatures -> PropertyFeatures -> Bool
$c/= :: PropertyFeatures -> PropertyFeatures -> Bool
/= :: PropertyFeatures -> PropertyFeatures -> Bool
Eq, Eq PropertyFeatures
Eq PropertyFeatures =>
(PropertyFeatures -> PropertyFeatures -> Ordering)
-> (PropertyFeatures -> PropertyFeatures -> Bool)
-> (PropertyFeatures -> PropertyFeatures -> Bool)
-> (PropertyFeatures -> PropertyFeatures -> Bool)
-> (PropertyFeatures -> PropertyFeatures -> Bool)
-> (PropertyFeatures -> PropertyFeatures -> PropertyFeatures)
-> (PropertyFeatures -> PropertyFeatures -> PropertyFeatures)
-> Ord 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
$ccompare :: PropertyFeatures -> PropertyFeatures -> Ordering
compare :: PropertyFeatures -> PropertyFeatures -> Ordering
$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
>= :: PropertyFeatures -> PropertyFeatures -> Bool
$cmax :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
max :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
$cmin :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
min :: PropertyFeatures -> PropertyFeatures -> PropertyFeatures
Ord, ReadPrec [PropertyFeatures]
ReadPrec PropertyFeatures
Int -> ReadS PropertyFeatures
ReadS [PropertyFeatures]
(Int -> ReadS PropertyFeatures)
-> ReadS [PropertyFeatures]
-> ReadPrec PropertyFeatures
-> ReadPrec [PropertyFeatures]
-> Read PropertyFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyFeatures
readsPrec :: Int -> ReadS PropertyFeatures
$creadList :: ReadS [PropertyFeatures]
readList :: ReadS [PropertyFeatures]
$creadPrec :: ReadPrec PropertyFeatures
readPrec :: ReadPrec PropertyFeatures
$creadListPrec :: ReadPrec [PropertyFeatures]
readListPrec :: ReadPrec [PropertyFeatures]
Read, Int -> PropertyFeatures -> ShowS
[PropertyFeatures] -> ShowS
PropertyFeatures -> String
(Int -> PropertyFeatures -> ShowS)
-> (PropertyFeatures -> String)
-> ([PropertyFeatures] -> ShowS)
-> Show PropertyFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyFeatures -> ShowS
showsPrec :: Int -> PropertyFeatures -> ShowS
$cshow :: PropertyFeatures -> String
show :: PropertyFeatures -> String
$cshowList :: [PropertyFeatures] -> ShowS
showList :: [PropertyFeatures] -> ShowS
Show)
_PropertyFeatures :: Name
_PropertyFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.PropertyFeatures")
_PropertyFeatures_dataTypeFeatures :: Name
_PropertyFeatures_dataTypeFeatures = (String -> Name
Core.Name String
"dataTypeFeatures")
_PropertyFeatures_supportsProperties :: Name
_PropertyFeatures_supportsProperties = (String -> Name
Core.Name String
"supportsProperties")
data VariableFeatures =
VariableFeatures {
VariableFeatures -> DataTypeFeatures
variableFeaturesDataTypeFeatures :: DataTypeFeatures,
VariableFeatures -> Bool
variableFeaturesSupportsVariables :: Bool}
deriving (VariableFeatures -> VariableFeatures -> Bool
(VariableFeatures -> VariableFeatures -> Bool)
-> (VariableFeatures -> VariableFeatures -> Bool)
-> Eq VariableFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariableFeatures -> VariableFeatures -> Bool
== :: VariableFeatures -> VariableFeatures -> Bool
$c/= :: VariableFeatures -> VariableFeatures -> Bool
/= :: VariableFeatures -> VariableFeatures -> Bool
Eq, Eq VariableFeatures
Eq VariableFeatures =>
(VariableFeatures -> VariableFeatures -> Ordering)
-> (VariableFeatures -> VariableFeatures -> Bool)
-> (VariableFeatures -> VariableFeatures -> Bool)
-> (VariableFeatures -> VariableFeatures -> Bool)
-> (VariableFeatures -> VariableFeatures -> Bool)
-> (VariableFeatures -> VariableFeatures -> VariableFeatures)
-> (VariableFeatures -> VariableFeatures -> VariableFeatures)
-> Ord 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
$ccompare :: VariableFeatures -> VariableFeatures -> Ordering
compare :: VariableFeatures -> VariableFeatures -> Ordering
$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
>= :: VariableFeatures -> VariableFeatures -> Bool
$cmax :: VariableFeatures -> VariableFeatures -> VariableFeatures
max :: VariableFeatures -> VariableFeatures -> VariableFeatures
$cmin :: VariableFeatures -> VariableFeatures -> VariableFeatures
min :: VariableFeatures -> VariableFeatures -> VariableFeatures
Ord, ReadPrec [VariableFeatures]
ReadPrec VariableFeatures
Int -> ReadS VariableFeatures
ReadS [VariableFeatures]
(Int -> ReadS VariableFeatures)
-> ReadS [VariableFeatures]
-> ReadPrec VariableFeatures
-> ReadPrec [VariableFeatures]
-> Read VariableFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VariableFeatures
readsPrec :: Int -> ReadS VariableFeatures
$creadList :: ReadS [VariableFeatures]
readList :: ReadS [VariableFeatures]
$creadPrec :: ReadPrec VariableFeatures
readPrec :: ReadPrec VariableFeatures
$creadListPrec :: ReadPrec [VariableFeatures]
readListPrec :: ReadPrec [VariableFeatures]
Read, Int -> VariableFeatures -> ShowS
[VariableFeatures] -> ShowS
VariableFeatures -> String
(Int -> VariableFeatures -> ShowS)
-> (VariableFeatures -> String)
-> ([VariableFeatures] -> ShowS)
-> Show VariableFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VariableFeatures -> ShowS
showsPrec :: Int -> VariableFeatures -> ShowS
$cshow :: VariableFeatures -> String
show :: VariableFeatures -> String
$cshowList :: [VariableFeatures] -> ShowS
showList :: [VariableFeatures] -> ShowS
Show)
_VariableFeatures :: Name
_VariableFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.VariableFeatures")
_VariableFeatures_dataTypeFeatures :: Name
_VariableFeatures_dataTypeFeatures = (String -> Name
Core.Name String
"dataTypeFeatures")
_VariableFeatures_supportsVariables :: Name
_VariableFeatures_supportsVariables = (String -> Name
Core.Name String
"supportsVariables")
data VertexFeatures =
VertexFeatures {
VertexFeatures -> ElementFeatures
vertexFeaturesElementFeatures :: ElementFeatures,
VertexFeatures -> VertexPropertyFeatures
vertexFeaturesProperties :: VertexPropertyFeatures,
VertexFeatures -> Bool
vertexFeaturesSupportsAddVertices :: Bool,
VertexFeatures -> Bool
vertexFeaturesSupportsDuplicateMultiProperties :: Bool,
VertexFeatures -> Bool
vertexFeaturesSupportsMetaProperties :: Bool,
VertexFeatures -> Bool
vertexFeaturesSupportsMultiProperties :: Bool,
VertexFeatures -> Bool
vertexFeaturesSupportsRemoveVertices :: Bool,
VertexFeatures -> Bool
vertexFeaturesSupportsUpsert :: Bool}
deriving (VertexFeatures -> VertexFeatures -> Bool
(VertexFeatures -> VertexFeatures -> Bool)
-> (VertexFeatures -> VertexFeatures -> Bool) -> Eq VertexFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VertexFeatures -> VertexFeatures -> Bool
== :: VertexFeatures -> VertexFeatures -> Bool
$c/= :: VertexFeatures -> VertexFeatures -> Bool
/= :: VertexFeatures -> VertexFeatures -> Bool
Eq, Eq VertexFeatures
Eq VertexFeatures =>
(VertexFeatures -> VertexFeatures -> Ordering)
-> (VertexFeatures -> VertexFeatures -> Bool)
-> (VertexFeatures -> VertexFeatures -> Bool)
-> (VertexFeatures -> VertexFeatures -> Bool)
-> (VertexFeatures -> VertexFeatures -> Bool)
-> (VertexFeatures -> VertexFeatures -> VertexFeatures)
-> (VertexFeatures -> VertexFeatures -> VertexFeatures)
-> Ord 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
$ccompare :: VertexFeatures -> VertexFeatures -> Ordering
compare :: VertexFeatures -> VertexFeatures -> Ordering
$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
>= :: VertexFeatures -> VertexFeatures -> Bool
$cmax :: VertexFeatures -> VertexFeatures -> VertexFeatures
max :: VertexFeatures -> VertexFeatures -> VertexFeatures
$cmin :: VertexFeatures -> VertexFeatures -> VertexFeatures
min :: VertexFeatures -> VertexFeatures -> VertexFeatures
Ord, ReadPrec [VertexFeatures]
ReadPrec VertexFeatures
Int -> ReadS VertexFeatures
ReadS [VertexFeatures]
(Int -> ReadS VertexFeatures)
-> ReadS [VertexFeatures]
-> ReadPrec VertexFeatures
-> ReadPrec [VertexFeatures]
-> Read VertexFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VertexFeatures
readsPrec :: Int -> ReadS VertexFeatures
$creadList :: ReadS [VertexFeatures]
readList :: ReadS [VertexFeatures]
$creadPrec :: ReadPrec VertexFeatures
readPrec :: ReadPrec VertexFeatures
$creadListPrec :: ReadPrec [VertexFeatures]
readListPrec :: ReadPrec [VertexFeatures]
Read, Int -> VertexFeatures -> ShowS
[VertexFeatures] -> ShowS
VertexFeatures -> String
(Int -> VertexFeatures -> ShowS)
-> (VertexFeatures -> String)
-> ([VertexFeatures] -> ShowS)
-> Show VertexFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VertexFeatures -> ShowS
showsPrec :: Int -> VertexFeatures -> ShowS
$cshow :: VertexFeatures -> String
show :: VertexFeatures -> String
$cshowList :: [VertexFeatures] -> ShowS
showList :: [VertexFeatures] -> ShowS
Show)
_VertexFeatures :: Name
_VertexFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.VertexFeatures")
_VertexFeatures_elementFeatures :: Name
_VertexFeatures_elementFeatures = (String -> Name
Core.Name String
"elementFeatures")
_VertexFeatures_properties :: Name
_VertexFeatures_properties = (String -> Name
Core.Name String
"properties")
_VertexFeatures_supportsAddVertices :: Name
_VertexFeatures_supportsAddVertices = (String -> Name
Core.Name String
"supportsAddVertices")
_VertexFeatures_supportsDuplicateMultiProperties :: Name
_VertexFeatures_supportsDuplicateMultiProperties = (String -> Name
Core.Name String
"supportsDuplicateMultiProperties")
_VertexFeatures_supportsMetaProperties :: Name
_VertexFeatures_supportsMetaProperties = (String -> Name
Core.Name String
"supportsMetaProperties")
_VertexFeatures_supportsMultiProperties :: Name
_VertexFeatures_supportsMultiProperties = (String -> Name
Core.Name String
"supportsMultiProperties")
_VertexFeatures_supportsRemoveVertices :: Name
_VertexFeatures_supportsRemoveVertices = (String -> Name
Core.Name String
"supportsRemoveVertices")
_VertexFeatures_supportsUpsert :: Name
_VertexFeatures_supportsUpsert = (String -> Name
Core.Name String
"supportsUpsert")
data VertexPropertyFeatures =
VertexPropertyFeatures {
VertexPropertyFeatures -> DataTypeFeatures
vertexPropertyFeaturesDataTypeFeatures :: DataTypeFeatures,
VertexPropertyFeatures -> PropertyFeatures
vertexPropertyFeaturesPropertyFeatures :: PropertyFeatures,
VertexPropertyFeatures -> ElementFeatures
vertexPropertyFeaturesElementFeatures :: ElementFeatures,
VertexPropertyFeatures -> Bool
vertexPropertyFeaturesSupportsRemove :: Bool}
deriving (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
(VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> Eq VertexPropertyFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
== :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$c/= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
/= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
Eq, Eq VertexPropertyFeatures
Eq VertexPropertyFeatures =>
(VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering)
-> (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> (VertexPropertyFeatures -> VertexPropertyFeatures -> Bool)
-> (VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures)
-> (VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures)
-> Ord 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
$ccompare :: VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering
compare :: VertexPropertyFeatures -> VertexPropertyFeatures -> Ordering
$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
>= :: VertexPropertyFeatures -> VertexPropertyFeatures -> Bool
$cmax :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
max :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
$cmin :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
min :: VertexPropertyFeatures
-> VertexPropertyFeatures -> VertexPropertyFeatures
Ord, ReadPrec [VertexPropertyFeatures]
ReadPrec VertexPropertyFeatures
Int -> ReadS VertexPropertyFeatures
ReadS [VertexPropertyFeatures]
(Int -> ReadS VertexPropertyFeatures)
-> ReadS [VertexPropertyFeatures]
-> ReadPrec VertexPropertyFeatures
-> ReadPrec [VertexPropertyFeatures]
-> Read VertexPropertyFeatures
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VertexPropertyFeatures
readsPrec :: Int -> ReadS VertexPropertyFeatures
$creadList :: ReadS [VertexPropertyFeatures]
readList :: ReadS [VertexPropertyFeatures]
$creadPrec :: ReadPrec VertexPropertyFeatures
readPrec :: ReadPrec VertexPropertyFeatures
$creadListPrec :: ReadPrec [VertexPropertyFeatures]
readListPrec :: ReadPrec [VertexPropertyFeatures]
Read, Int -> VertexPropertyFeatures -> ShowS
[VertexPropertyFeatures] -> ShowS
VertexPropertyFeatures -> String
(Int -> VertexPropertyFeatures -> ShowS)
-> (VertexPropertyFeatures -> String)
-> ([VertexPropertyFeatures] -> ShowS)
-> Show VertexPropertyFeatures
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VertexPropertyFeatures -> ShowS
showsPrec :: Int -> VertexPropertyFeatures -> ShowS
$cshow :: VertexPropertyFeatures -> String
show :: VertexPropertyFeatures -> String
$cshowList :: [VertexPropertyFeatures] -> ShowS
showList :: [VertexPropertyFeatures] -> ShowS
Show)
_VertexPropertyFeatures :: Name
_VertexPropertyFeatures = (String -> Name
Core.Name String
"hydra/langs/tinkerpop/features.VertexPropertyFeatures")
_VertexPropertyFeatures_dataTypeFeatures :: Name
_VertexPropertyFeatures_dataTypeFeatures = (String -> Name
Core.Name String
"dataTypeFeatures")
_VertexPropertyFeatures_propertyFeatures :: Name
_VertexPropertyFeatures_propertyFeatures = (String -> Name
Core.Name String
"propertyFeatures")
_VertexPropertyFeatures_elementFeatures :: Name
_VertexPropertyFeatures_elementFeatures = (String -> Name
Core.Name String
"elementFeatures")
_VertexPropertyFeatures_supportsRemove :: Name
_VertexPropertyFeatures_supportsRemove = (String -> Name
Core.Name String
"supportsRemove")