Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Langs.Tinkerpop.Mappings
Description
A model for property graph mapping specifications. See https://github.com/CategoricalData/hydra/wiki/Property-graphs
Synopsis
- data AnnotationSchema = AnnotationSchema {
- annotationSchemaVertexLabel :: String
- annotationSchemaEdgeLabel :: String
- annotationSchemaVertexId :: String
- annotationSchemaEdgeId :: String
- annotationSchemaPropertyKey :: String
- annotationSchemaPropertyValue :: String
- annotationSchemaOutVertex :: String
- annotationSchemaOutVertexLabel :: String
- annotationSchemaInVertex :: String
- annotationSchemaInVertexLabel :: String
- annotationSchemaOutEdge :: String
- annotationSchemaOutEdgeLabel :: String
- annotationSchemaInEdge :: String
- annotationSchemaInEdgeLabel :: String
- annotationSchemaIgnore :: String
- _AnnotationSchema :: Name
- _AnnotationSchema_vertexLabel :: Name
- _AnnotationSchema_edgeLabel :: Name
- _AnnotationSchema_vertexId :: Name
- _AnnotationSchema_edgeId :: Name
- _AnnotationSchema_propertyKey :: Name
- _AnnotationSchema_propertyValue :: Name
- _AnnotationSchema_outVertex :: Name
- _AnnotationSchema_outVertexLabel :: Name
- _AnnotationSchema_inVertex :: Name
- _AnnotationSchema_inVertexLabel :: Name
- _AnnotationSchema_outEdge :: Name
- _AnnotationSchema_outEdgeLabel :: Name
- _AnnotationSchema_inEdge :: Name
- _AnnotationSchema_inEdgeLabel :: Name
- _AnnotationSchema_ignore :: Name
- data EdgeSpec = EdgeSpec {}
- _EdgeSpec :: Name
- _EdgeSpec_label :: Name
- _EdgeSpec_id :: Name
- _EdgeSpec_out :: Name
- _EdgeSpec_in :: Name
- _EdgeSpec_properties :: Name
- data ElementSpec
- _ElementSpec :: Name
- _ElementSpec_vertex :: Name
- _ElementSpec_edge :: Name
- data PropertySpec = PropertySpec {}
- _PropertySpec :: Name
- _PropertySpec_key :: Name
- _PropertySpec_value :: Name
- data Schema s t v = Schema {
- schemaVertexIdTypes :: Coder s s Type t
- schemaVertexIds :: Coder s s Term v
- schemaEdgeIdTypes :: Coder s s Type t
- schemaEdgeIds :: Coder s s Term v
- schemaPropertyTypes :: Coder s s Type t
- schemaPropertyValues :: Coder s s Term v
- schemaAnnotations :: AnnotationSchema
- schemaDefaultVertexId :: v
- schemaDefaultEdgeId :: v
- _Schema :: Name
- _Schema_vertexIdTypes :: Name
- _Schema_vertexIds :: Name
- _Schema_edgeIdTypes :: Name
- _Schema_edgeIds :: Name
- _Schema_propertyTypes :: Name
- _Schema_propertyValues :: Name
- _Schema_annotations :: Name
- _Schema_defaultVertexId :: Name
- _Schema_defaultEdgeId :: Name
- data ValueSpec
- _ValueSpec :: Name
- _ValueSpec_value :: Name
- _ValueSpec_pattern :: Name
- data VertexSpec = VertexSpec {}
- _VertexSpec :: Name
- _VertexSpec_label :: Name
- _VertexSpec_id :: Name
- _VertexSpec_properties :: Name
Documentation
data AnnotationSchema Source #
Configurable annotation keys for property graph mapping specifications
Constructors
Instances
A mapping specification producing edges of a specified label.
Constructors
EdgeSpec | |
Fields
|
_EdgeSpec_id :: Name Source #
_EdgeSpec_out :: Name Source #
_EdgeSpec_in :: Name Source #
data ElementSpec Source #
Either a vertex specification or an edge specification
Constructors
ElementSpecVertex VertexSpec | |
ElementSpecEdge EdgeSpec |
Instances
Read ElementSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods readsPrec :: Int -> ReadS ElementSpec # readList :: ReadS [ElementSpec] # readPrec :: ReadPrec ElementSpec # readListPrec :: ReadPrec [ElementSpec] # | |
Show ElementSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods showsPrec :: Int -> ElementSpec -> ShowS # show :: ElementSpec -> String # showList :: [ElementSpec] -> ShowS # | |
Eq ElementSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings | |
Ord ElementSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods compare :: ElementSpec -> ElementSpec -> Ordering # (<) :: ElementSpec -> ElementSpec -> Bool # (<=) :: ElementSpec -> ElementSpec -> Bool # (>) :: ElementSpec -> ElementSpec -> Bool # (>=) :: ElementSpec -> ElementSpec -> Bool # max :: ElementSpec -> ElementSpec -> ElementSpec # min :: ElementSpec -> ElementSpec -> ElementSpec # |
_ElementSpec :: Name Source #
data PropertySpec Source #
A mapping specification producing properties of a specified key, and values of the appropriate type.
Constructors
PropertySpec | |
Fields
|
Instances
Read PropertySpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods readsPrec :: Int -> ReadS PropertySpec # readList :: ReadS [PropertySpec] # | |
Show PropertySpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods showsPrec :: Int -> PropertySpec -> ShowS # show :: PropertySpec -> String # showList :: [PropertySpec] -> ShowS # | |
Eq PropertySpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings | |
Ord PropertySpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods compare :: PropertySpec -> PropertySpec -> Ordering # (<) :: PropertySpec -> PropertySpec -> Bool # (<=) :: PropertySpec -> PropertySpec -> Bool # (>) :: PropertySpec -> PropertySpec -> Bool # (>=) :: PropertySpec -> PropertySpec -> Bool # max :: PropertySpec -> PropertySpec -> PropertySpec # min :: PropertySpec -> PropertySpec -> PropertySpec # |
_PropertySpec :: Name Source #
A set of mappings which translates between Hydra terms and annotations, and application-specific property graph types
Constructors
Schema | |
Fields
|
A mapping specification producing values (usually literal values) whose type is understood in context
Constructors
ValueSpecValue | A trivial no-op specification which passes the entire value |
ValueSpecPattern String | A compact path representing the function, e.g. engine-${engineInfomodelname} |
Instances
Read ValueSpec Source # | |
Show ValueSpec Source # | |
Eq ValueSpec Source # | |
Ord ValueSpec Source # | |
_ValueSpec :: Name Source #
data VertexSpec Source #
A mapping specification producing vertices of a specified label
Constructors
VertexSpec | |
Fields
|
Instances
Read VertexSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods readsPrec :: Int -> ReadS VertexSpec # readList :: ReadS [VertexSpec] # readPrec :: ReadPrec VertexSpec # readListPrec :: ReadPrec [VertexSpec] # | |
Show VertexSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods showsPrec :: Int -> VertexSpec -> ShowS # show :: VertexSpec -> String # showList :: [VertexSpec] -> ShowS # | |
Eq VertexSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings | |
Ord VertexSpec Source # | |
Defined in Hydra.Langs.Tinkerpop.Mappings Methods compare :: VertexSpec -> VertexSpec -> Ordering # (<) :: VertexSpec -> VertexSpec -> Bool # (<=) :: VertexSpec -> VertexSpec -> Bool # (>) :: VertexSpec -> VertexSpec -> Bool # (>=) :: VertexSpec -> VertexSpec -> Bool # max :: VertexSpec -> VertexSpec -> VertexSpec # min :: VertexSpec -> VertexSpec -> VertexSpec # |
_VertexSpec :: Name Source #