Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Ext.Owl.Syntax
Description
An OWL 2 syntax model. See https://www.w3.org/TR/owl2-syntax
Synopsis
- data Ontology = Ontology {}
- _Ontology :: Name
- _Ontology_directImports :: FieldName
- _Ontology_annotations :: FieldName
- _Ontology_axioms :: FieldName
- data Declaration = Declaration {}
- _Declaration :: Name
- _Declaration_annotations :: FieldName
- _Declaration_entity :: FieldName
- data Entity
- _Entity :: Name
- _Entity_annotationProperty :: FieldName
- _Entity_class :: FieldName
- _Entity_dataProperty :: FieldName
- _Entity_datatype :: FieldName
- _Entity_namedIndividual :: FieldName
- _Entity_objectProperty :: FieldName
- data AnnotationSubject
- _AnnotationSubject :: Name
- _AnnotationSubject_iri :: FieldName
- _AnnotationSubject_anonymousIndividual :: FieldName
- data AnnotationValue
- _AnnotationValue :: Name
- _AnnotationValue_anonymousIndividual :: FieldName
- _AnnotationValue_iri :: FieldName
- _AnnotationValue_literal :: FieldName
- data Annotation = Annotation {}
- _Annotation :: Name
- _Annotation_annotations :: FieldName
- _Annotation_property :: FieldName
- _Annotation_value :: FieldName
- data AnnotationAxiom
- _AnnotationAxiom :: Name
- _AnnotationAxiom_annotationAssertion :: FieldName
- _AnnotationAxiom_annotationPropertyDomain :: FieldName
- _AnnotationAxiom_annotationPropertyRange :: FieldName
- _AnnotationAxiom_subAnnotationPropertyOf :: FieldName
- data AnnotationAssertion = AnnotationAssertion {}
- _AnnotationAssertion :: Name
- _AnnotationAssertion_annotations :: FieldName
- _AnnotationAssertion_property :: FieldName
- _AnnotationAssertion_subject :: FieldName
- _AnnotationAssertion_value :: FieldName
- data SubAnnotationPropertyOf = SubAnnotationPropertyOf {}
- _SubAnnotationPropertyOf :: Name
- _SubAnnotationPropertyOf_annotations :: FieldName
- _SubAnnotationPropertyOf_subProperty :: FieldName
- _SubAnnotationPropertyOf_superProperty :: FieldName
- data AnnotationPropertyDomain = AnnotationPropertyDomain {}
- _AnnotationPropertyDomain :: Name
- _AnnotationPropertyDomain_annotations :: FieldName
- _AnnotationPropertyDomain_property :: FieldName
- _AnnotationPropertyDomain_iri :: FieldName
- data AnnotationPropertyRange = AnnotationPropertyRange {}
- _AnnotationPropertyRange :: Name
- _AnnotationPropertyRange_annotations :: FieldName
- _AnnotationPropertyRange_property :: FieldName
- _AnnotationPropertyRange_iri :: FieldName
- data Class = Class {
- _Class :: Name
- data Datatype
- _Datatype :: Name
- _Datatype_xmlSchema :: FieldName
- _Datatype_other :: FieldName
- data ObjectProperty = ObjectProperty {
- _ObjectProperty :: Name
- data DataProperty = DataProperty {
- _DataProperty :: Name
- data AnnotationProperty = AnnotationProperty {
- _AnnotationProperty :: Name
- data Individual
- _Individual :: Name
- _Individual_named :: FieldName
- _Individual_anonymous :: FieldName
- data NamedIndividual = NamedIndividual {
- _NamedIndividual :: Name
- data AnonymousIndividual = AnonymousIndividual {
- _AnonymousIndividual :: Name
- data ObjectPropertyExpression
- _ObjectPropertyExpression :: Name
- _ObjectPropertyExpression_object :: FieldName
- _ObjectPropertyExpression_inverseObject :: FieldName
- newtype InverseObjectProperty = InverseObjectProperty {}
- _InverseObjectProperty :: Name
- newtype DataPropertyExpression = DataPropertyExpression {}
- _DataPropertyExpression :: Name
- data DataRange
- _DataRange :: Name
- _DataRange_dataComplementOf :: FieldName
- _DataRange_dataIntersectionOf :: FieldName
- _DataRange_dataOneOf :: FieldName
- _DataRange_dataUnionOf :: FieldName
- _DataRange_datatype :: FieldName
- _DataRange_datatypeRestriction :: FieldName
- newtype DataIntersectionOf = DataIntersectionOf {}
- _DataIntersectionOf :: Name
- newtype DataUnionOf = DataUnionOf {
- unDataUnionOf :: [DataRange]
- _DataUnionOf :: Name
- newtype DataComplementOf = DataComplementOf {}
- _DataComplementOf :: Name
- newtype DataOneOf = DataOneOf {
- unDataOneOf :: [Literal]
- _DataOneOf :: Name
- data DatatypeRestriction = DatatypeRestriction {}
- _DatatypeRestriction :: Name
- _DatatypeRestriction_datatype :: FieldName
- _DatatypeRestriction_constraints :: FieldName
- data DatatypeRestriction_Constraint = DatatypeRestriction_Constraint {}
- _DatatypeRestriction_Constraint :: Name
- _DatatypeRestriction_Constraint_constrainingFacet :: FieldName
- _DatatypeRestriction_Constraint_restrictionValue :: FieldName
- data DatatypeRestriction_ConstrainingFacet
- _DatatypeRestriction_ConstrainingFacet :: Name
- _DatatypeRestriction_ConstrainingFacet_xmlSchema :: FieldName
- _DatatypeRestriction_ConstrainingFacet_other :: FieldName
- data ClassExpression
- = ClassExpressionClass Class
- | ClassExpressionDataSomeValuesFrom DataSomeValuesFrom
- | ClassExpressionDataAllValuesFrom DataAllValuesFrom
- | ClassExpressionDataHasValue DataHasValue
- | ClassExpressionDataMinCardinality DataMinCardinality
- | ClassExpressionDataMaxCardinality DataMaxCardinality
- | ClassExpressionDataExactCardinality DataExactCardinality
- | ClassExpressionObjectAllValuesFrom ObjectAllValuesFrom
- | ClassExpressionObjectExactCardinality ObjectExactCardinality
- | ClassExpressionObjectHasSelf ObjectHasSelf
- | ClassExpressionObjectHasValue ObjectHasValue
- | ClassExpressionObjectIntersectionOf ObjectIntersectionOf
- | ClassExpressionObjectMaxCardinality ObjectMaxCardinality
- | ClassExpressionObjectMinCardinality ObjectMinCardinality
- | ClassExpressionObjectOneOf ObjectOneOf
- | ClassExpressionObjectSomeValuesFrom ObjectSomeValuesFrom
- | ClassExpressionObjectUnionOf ObjectUnionOf
- _ClassExpression :: Name
- _ClassExpression_class :: FieldName
- _ClassExpression_dataSomeValuesFrom :: FieldName
- _ClassExpression_dataAllValuesFrom :: FieldName
- _ClassExpression_dataHasValue :: FieldName
- _ClassExpression_dataMinCardinality :: FieldName
- _ClassExpression_dataMaxCardinality :: FieldName
- _ClassExpression_dataExactCardinality :: FieldName
- _ClassExpression_objectAllValuesFrom :: FieldName
- _ClassExpression_objectExactCardinality :: FieldName
- _ClassExpression_objectHasSelf :: FieldName
- _ClassExpression_objectHasValue :: FieldName
- _ClassExpression_objectIntersectionOf :: FieldName
- _ClassExpression_objectMaxCardinality :: FieldName
- _ClassExpression_objectMinCardinality :: FieldName
- _ClassExpression_objectOneOf :: FieldName
- _ClassExpression_objectSomeValuesFrom :: FieldName
- _ClassExpression_objectUnionOf :: FieldName
- newtype ObjectIntersectionOf = ObjectIntersectionOf {}
- _ObjectIntersectionOf :: Name
- newtype ObjectUnionOf = ObjectUnionOf {}
- _ObjectUnionOf :: Name
- newtype ObjectComplementOf = ObjectComplementOf {}
- _ObjectComplementOf :: Name
- newtype ObjectOneOf = ObjectOneOf {
- unObjectOneOf :: [Individual]
- _ObjectOneOf :: Name
- data ObjectSomeValuesFrom = ObjectSomeValuesFrom {}
- _ObjectSomeValuesFrom :: Name
- _ObjectSomeValuesFrom_property :: FieldName
- _ObjectSomeValuesFrom_class :: FieldName
- data ObjectAllValuesFrom = ObjectAllValuesFrom {}
- _ObjectAllValuesFrom :: Name
- _ObjectAllValuesFrom_property :: FieldName
- _ObjectAllValuesFrom_class :: FieldName
- data ObjectHasValue = ObjectHasValue {}
- _ObjectHasValue :: Name
- _ObjectHasValue_property :: FieldName
- _ObjectHasValue_individual :: FieldName
- newtype ObjectHasSelf = ObjectHasSelf {}
- _ObjectHasSelf :: Name
- data ObjectMinCardinality = ObjectMinCardinality {}
- _ObjectMinCardinality :: Name
- _ObjectMinCardinality_bound :: FieldName
- _ObjectMinCardinality_property :: FieldName
- _ObjectMinCardinality_class :: FieldName
- data ObjectMaxCardinality = ObjectMaxCardinality {}
- _ObjectMaxCardinality :: Name
- _ObjectMaxCardinality_bound :: FieldName
- _ObjectMaxCardinality_property :: FieldName
- _ObjectMaxCardinality_class :: FieldName
- data ObjectExactCardinality = ObjectExactCardinality {}
- _ObjectExactCardinality :: Name
- _ObjectExactCardinality_bound :: FieldName
- _ObjectExactCardinality_property :: FieldName
- _ObjectExactCardinality_class :: FieldName
- data DataSomeValuesFrom = DataSomeValuesFrom {}
- _DataSomeValuesFrom :: Name
- _DataSomeValuesFrom_property :: FieldName
- _DataSomeValuesFrom_range :: FieldName
- data DataAllValuesFrom = DataAllValuesFrom {}
- _DataAllValuesFrom :: Name
- _DataAllValuesFrom_property :: FieldName
- _DataAllValuesFrom_range :: FieldName
- data DataHasValue = DataHasValue {}
- _DataHasValue :: Name
- _DataHasValue_property :: FieldName
- _DataHasValue_value :: FieldName
- data DataMinCardinality = DataMinCardinality {}
- _DataMinCardinality :: Name
- _DataMinCardinality_bound :: FieldName
- _DataMinCardinality_property :: FieldName
- _DataMinCardinality_range :: FieldName
- data DataMaxCardinality = DataMaxCardinality {}
- _DataMaxCardinality :: Name
- _DataMaxCardinality_bound :: FieldName
- _DataMaxCardinality_property :: FieldName
- _DataMaxCardinality_range :: FieldName
- data DataExactCardinality = DataExactCardinality {}
- _DataExactCardinality :: Name
- _DataExactCardinality_bound :: FieldName
- _DataExactCardinality_property :: FieldName
- _DataExactCardinality_range :: FieldName
- data Axiom
- _Axiom :: Name
- _Axiom_annotationAxiom :: FieldName
- _Axiom_assertion :: FieldName
- _Axiom_classAxiom :: FieldName
- _Axiom_dataPropertyAxiom :: FieldName
- _Axiom_datatypeDefinition :: FieldName
- _Axiom_declaration :: FieldName
- _Axiom_hasKey :: FieldName
- _Axiom_objectPropertyAxiom :: FieldName
- data ClassAxiom
- _ClassAxiom :: Name
- _ClassAxiom_disjointClasses :: FieldName
- _ClassAxiom_disjointUnion :: FieldName
- _ClassAxiom_equivalentClasses :: FieldName
- _ClassAxiom_subClassOf :: FieldName
- data SubClassOf = SubClassOf {}
- _SubClassOf :: Name
- _SubClassOf_annotations :: FieldName
- _SubClassOf_subClass :: FieldName
- _SubClassOf_superClass :: FieldName
- data EquivalentClasses = EquivalentClasses {}
- _EquivalentClasses :: Name
- _EquivalentClasses_annotations :: FieldName
- _EquivalentClasses_classes :: FieldName
- data DisjointClasses = DisjointClasses {}
- _DisjointClasses :: Name
- _DisjointClasses_annotations :: FieldName
- _DisjointClasses_classes :: FieldName
- data DisjointUnion = DisjointUnion {}
- _DisjointUnion :: Name
- _DisjointUnion_annotations :: FieldName
- _DisjointUnion_class :: FieldName
- _DisjointUnion_classes :: FieldName
- data ObjectPropertyAxiom
- = ObjectPropertyAxiomAsymmetricObjectProperty AsymmetricObjectProperty
- | ObjectPropertyAxiomDisjointObjectProperties DisjointObjectProperties
- | ObjectPropertyAxiomEquivalentObjectProperties EquivalentObjectProperties
- | ObjectPropertyAxiomFunctionalObjectProperty FunctionalObjectProperty
- | ObjectPropertyAxiomInverseFunctionalObjectProperty InverseFunctionalObjectProperty
- | ObjectPropertyAxiomInverseObjectProperties InverseObjectProperties
- | ObjectPropertyAxiomIrreflexiveObjectProperty IrreflexiveObjectProperty
- | ObjectPropertyAxiomObjectPropertyDomain ObjectPropertyDomain
- | ObjectPropertyAxiomObjectPropertyRange ObjectPropertyRange
- | ObjectPropertyAxiomReflexiveObjectProperty ReflexiveObjectProperty
- | ObjectPropertyAxiomSubObjectPropertyOf SubObjectPropertyOf
- | ObjectPropertyAxiomSymmetricObjectProperty SymmetricObjectProperty
- | ObjectPropertyAxiomTransitiveObjectProperty TransitiveObjectProperty
- _ObjectPropertyAxiom :: Name
- _ObjectPropertyAxiom_asymmetricObjectProperty :: FieldName
- _ObjectPropertyAxiom_disjointObjectProperties :: FieldName
- _ObjectPropertyAxiom_equivalentObjectProperties :: FieldName
- _ObjectPropertyAxiom_functionalObjectProperty :: FieldName
- _ObjectPropertyAxiom_inverseFunctionalObjectProperty :: FieldName
- _ObjectPropertyAxiom_inverseObjectProperties :: FieldName
- _ObjectPropertyAxiom_irreflexiveObjectProperty :: FieldName
- _ObjectPropertyAxiom_objectPropertyDomain :: FieldName
- _ObjectPropertyAxiom_objectPropertyRange :: FieldName
- _ObjectPropertyAxiom_reflexiveObjectProperty :: FieldName
- _ObjectPropertyAxiom_subObjectPropertyOf :: FieldName
- _ObjectPropertyAxiom_symmetricObjectProperty :: FieldName
- _ObjectPropertyAxiom_transitiveObjectProperty :: FieldName
- data SubObjectPropertyOf = SubObjectPropertyOf {}
- _SubObjectPropertyOf :: Name
- _SubObjectPropertyOf_annotations :: FieldName
- _SubObjectPropertyOf_subProperty :: FieldName
- _SubObjectPropertyOf_superProperty :: FieldName
- data EquivalentObjectProperties = EquivalentObjectProperties {}
- _EquivalentObjectProperties :: Name
- _EquivalentObjectProperties_annotations :: FieldName
- _EquivalentObjectProperties_properties :: FieldName
- data DisjointObjectProperties = DisjointObjectProperties {}
- _DisjointObjectProperties :: Name
- _DisjointObjectProperties_annotations :: FieldName
- _DisjointObjectProperties_properties :: FieldName
- data ObjectPropertyDomain = ObjectPropertyDomain {}
- _ObjectPropertyDomain :: Name
- _ObjectPropertyDomain_annotations :: FieldName
- _ObjectPropertyDomain_property :: FieldName
- _ObjectPropertyDomain_domain :: FieldName
- data ObjectPropertyRange = ObjectPropertyRange {}
- _ObjectPropertyRange :: Name
- _ObjectPropertyRange_annotations :: FieldName
- _ObjectPropertyRange_property :: FieldName
- _ObjectPropertyRange_range :: FieldName
- data InverseObjectProperties = InverseObjectProperties {}
- _InverseObjectProperties :: Name
- _InverseObjectProperties_annotations :: FieldName
- _InverseObjectProperties_property1 :: FieldName
- _InverseObjectProperties_property2 :: FieldName
- data FunctionalObjectProperty = FunctionalObjectProperty {}
- _FunctionalObjectProperty :: Name
- _FunctionalObjectProperty_annotations :: FieldName
- _FunctionalObjectProperty_property :: FieldName
- data InverseFunctionalObjectProperty = InverseFunctionalObjectProperty {}
- _InverseFunctionalObjectProperty :: Name
- _InverseFunctionalObjectProperty_annotations :: FieldName
- _InverseFunctionalObjectProperty_property :: FieldName
- data ReflexiveObjectProperty = ReflexiveObjectProperty {}
- _ReflexiveObjectProperty :: Name
- _ReflexiveObjectProperty_annotations :: FieldName
- _ReflexiveObjectProperty_property :: FieldName
- data IrreflexiveObjectProperty = IrreflexiveObjectProperty {}
- _IrreflexiveObjectProperty :: Name
- _IrreflexiveObjectProperty_annotations :: FieldName
- _IrreflexiveObjectProperty_property :: FieldName
- data SymmetricObjectProperty = SymmetricObjectProperty {}
- _SymmetricObjectProperty :: Name
- _SymmetricObjectProperty_annotations :: FieldName
- _SymmetricObjectProperty_property :: FieldName
- data AsymmetricObjectProperty = AsymmetricObjectProperty {}
- _AsymmetricObjectProperty :: Name
- _AsymmetricObjectProperty_annotations :: FieldName
- _AsymmetricObjectProperty_property :: FieldName
- data TransitiveObjectProperty = TransitiveObjectProperty {}
- _TransitiveObjectProperty :: Name
- _TransitiveObjectProperty_annotations :: FieldName
- _TransitiveObjectProperty_property :: FieldName
- data DataPropertyAxiom
- = DataPropertyAxiomDataPropertyAxiom DataPropertyAxiom
- | DataPropertyAxiomDataPropertyRange DataPropertyRange
- | DataPropertyAxiomDisjointDataProperties DisjointDataProperties
- | DataPropertyAxiomEquivalentDataProperties EquivalentDataProperties
- | DataPropertyAxiomFunctionalDataProperty FunctionalDataProperty
- | DataPropertyAxiomSubDataPropertyOf SubDataPropertyOf
- _DataPropertyAxiom :: Name
- _DataPropertyAxiom_dataPropertyAxiom :: FieldName
- _DataPropertyAxiom_dataPropertyRange :: FieldName
- _DataPropertyAxiom_disjointDataProperties :: FieldName
- _DataPropertyAxiom_equivalentDataProperties :: FieldName
- _DataPropertyAxiom_functionalDataProperty :: FieldName
- _DataPropertyAxiom_subDataPropertyOf :: FieldName
- data SubDataPropertyOf = SubDataPropertyOf {}
- _SubDataPropertyOf :: Name
- _SubDataPropertyOf_annotations :: FieldName
- _SubDataPropertyOf_subProperty :: FieldName
- _SubDataPropertyOf_superProperty :: FieldName
- data EquivalentDataProperties = EquivalentDataProperties {}
- _EquivalentDataProperties :: Name
- _EquivalentDataProperties_annotations :: FieldName
- _EquivalentDataProperties_properties :: FieldName
- data DisjointDataProperties = DisjointDataProperties {}
- _DisjointDataProperties :: Name
- _DisjointDataProperties_annotations :: FieldName
- _DisjointDataProperties_properties :: FieldName
- data DataPropertyDomain = DataPropertyDomain {}
- _DataPropertyDomain :: Name
- _DataPropertyDomain_annotations :: FieldName
- _DataPropertyDomain_property :: FieldName
- _DataPropertyDomain_domain :: FieldName
- data DataPropertyRange = DataPropertyRange {}
- _DataPropertyRange :: Name
- _DataPropertyRange_annotations :: FieldName
- _DataPropertyRange_property :: FieldName
- _DataPropertyRange_range :: FieldName
- data FunctionalDataProperty = FunctionalDataProperty {}
- _FunctionalDataProperty :: Name
- _FunctionalDataProperty_annotations :: FieldName
- _FunctionalDataProperty_property :: FieldName
- data DatatypeDefinition = DatatypeDefinition {}
- _DatatypeDefinition :: Name
- _DatatypeDefinition_annotations :: FieldName
- _DatatypeDefinition_datatype :: FieldName
- _DatatypeDefinition_range :: FieldName
- data HasKey = HasKey {}
- _HasKey :: Name
- _HasKey_annotations :: FieldName
- _HasKey_class :: FieldName
- _HasKey_objectProperties :: FieldName
- _HasKey_dataProperties :: FieldName
- data Assertion
- = AssertionClassAssertion ClassAssertion
- | AssertionDataPropertyAssertion DataPropertyAssertion
- | AssertionDifferentIndividuals DifferentIndividuals
- | AssertionObjectPropertyAssertion ObjectPropertyAssertion
- | AssertionNegativeDataPropertyAssertion NegativeDataPropertyAssertion
- | AssertionNegativeObjectPropertyAssertion NegativeObjectPropertyAssertion
- | AssertionSameIndividual SameIndividual
- _Assertion :: Name
- _Assertion_classAssertion :: FieldName
- _Assertion_dataPropertyAssertion :: FieldName
- _Assertion_differentIndividuals :: FieldName
- _Assertion_objectPropertyAssertion :: FieldName
- _Assertion_negativeDataPropertyAssertion :: FieldName
- _Assertion_negativeObjectPropertyAssertion :: FieldName
- _Assertion_sameIndividual :: FieldName
- data SameIndividual = SameIndividual {}
- _SameIndividual :: Name
- _SameIndividual_annotations :: FieldName
- _SameIndividual_individuals :: FieldName
- data DifferentIndividuals = DifferentIndividuals {}
- _DifferentIndividuals :: Name
- _DifferentIndividuals_annotations :: FieldName
- _DifferentIndividuals_individuals :: FieldName
- data ClassAssertion = ClassAssertion {}
- _ClassAssertion :: Name
- _ClassAssertion_annotations :: FieldName
- _ClassAssertion_class :: FieldName
- _ClassAssertion_individual :: FieldName
- data ObjectPropertyAssertion = ObjectPropertyAssertion {}
- _ObjectPropertyAssertion :: Name
- _ObjectPropertyAssertion_annotations :: FieldName
- _ObjectPropertyAssertion_property :: FieldName
- _ObjectPropertyAssertion_source :: FieldName
- _ObjectPropertyAssertion_target :: FieldName
- data NegativeObjectPropertyAssertion = NegativeObjectPropertyAssertion {}
- _NegativeObjectPropertyAssertion :: Name
- _NegativeObjectPropertyAssertion_annotations :: FieldName
- _NegativeObjectPropertyAssertion_property :: FieldName
- _NegativeObjectPropertyAssertion_source :: FieldName
- _NegativeObjectPropertyAssertion_target :: FieldName
- data DataPropertyAssertion = DataPropertyAssertion {}
- _DataPropertyAssertion :: Name
- _DataPropertyAssertion_annotations :: FieldName
- _DataPropertyAssertion_property :: FieldName
- _DataPropertyAssertion_source :: FieldName
- _DataPropertyAssertion_target :: FieldName
- data NegativeDataPropertyAssertion = NegativeDataPropertyAssertion {}
- _NegativeDataPropertyAssertion :: Name
- _NegativeDataPropertyAssertion_annotations :: FieldName
- _NegativeDataPropertyAssertion_property :: FieldName
- _NegativeDataPropertyAssertion_source :: FieldName
- _NegativeDataPropertyAssertion_target :: FieldName
Documentation
Constructors
Ontology | |
Fields
|
data Declaration Source #
Constructors
Declaration | |
Fields |
Instances
Read Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS Declaration # readList :: ReadS [Declaration] # readPrec :: ReadPrec Declaration # readListPrec :: ReadPrec [Declaration] # | |
Show Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
Eq Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: Declaration -> Declaration -> Ordering # (<) :: Declaration -> Declaration -> Bool # (<=) :: Declaration -> Declaration -> Bool # (>) :: Declaration -> Declaration -> Bool # (>=) :: Declaration -> Declaration -> Bool # max :: Declaration -> Declaration -> Declaration # min :: Declaration -> Declaration -> Declaration # |
_Declaration :: Name Source #
Constructors
EntityAnnotationProperty AnnotationProperty | |
EntityClass Class | |
EntityDataProperty DataProperty | |
EntityDatatype Datatype | |
EntityNamedIndividual NamedIndividual | |
EntityObjectProperty ObjectProperty |
data AnnotationSubject Source #
Instances
data AnnotationValue Source #
Constructors
AnnotationValueAnonymousIndividual AnonymousIndividual | |
AnnotationValueIri Iri | |
AnnotationValueLiteral Literal |
Instances
Read AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS AnnotationValue # readList :: ReadS [AnnotationValue] # | |
Show AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> AnnotationValue -> ShowS # show :: AnnotationValue -> String # showList :: [AnnotationValue] -> ShowS # | |
Eq AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: AnnotationValue -> AnnotationValue -> Bool # (/=) :: AnnotationValue -> AnnotationValue -> Bool # | |
Ord AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: AnnotationValue -> AnnotationValue -> Ordering # (<) :: AnnotationValue -> AnnotationValue -> Bool # (<=) :: AnnotationValue -> AnnotationValue -> Bool # (>) :: AnnotationValue -> AnnotationValue -> Bool # (>=) :: AnnotationValue -> AnnotationValue -> Bool # max :: AnnotationValue -> AnnotationValue -> AnnotationValue # min :: AnnotationValue -> AnnotationValue -> AnnotationValue # |
data Annotation Source #
Constructors
Annotation | |
Instances
Read Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS Annotation # readList :: ReadS [Annotation] # readPrec :: ReadPrec Annotation # readListPrec :: ReadPrec [Annotation] # | |
Show Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Eq Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: Annotation -> Annotation -> Ordering # (<) :: Annotation -> Annotation -> Bool # (<=) :: Annotation -> Annotation -> Bool # (>) :: Annotation -> Annotation -> Bool # (>=) :: Annotation -> Annotation -> Bool # max :: Annotation -> Annotation -> Annotation # min :: Annotation -> Annotation -> Annotation # |
_Annotation :: Name Source #
data AnnotationAxiom Source #
Constructors
Instances
Read AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS AnnotationAxiom # readList :: ReadS [AnnotationAxiom] # | |
Show AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> AnnotationAxiom -> ShowS # show :: AnnotationAxiom -> String # showList :: [AnnotationAxiom] -> ShowS # | |
Eq AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: AnnotationAxiom -> AnnotationAxiom -> Bool # (/=) :: AnnotationAxiom -> AnnotationAxiom -> Bool # | |
Ord AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: AnnotationAxiom -> AnnotationAxiom -> Ordering # (<) :: AnnotationAxiom -> AnnotationAxiom -> Bool # (<=) :: AnnotationAxiom -> AnnotationAxiom -> Bool # (>) :: AnnotationAxiom -> AnnotationAxiom -> Bool # (>=) :: AnnotationAxiom -> AnnotationAxiom -> Bool # max :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom # min :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom # |
data AnnotationAssertion Source #
Constructors
AnnotationAssertion | |
Instances
data SubAnnotationPropertyOf Source #
Constructors
SubAnnotationPropertyOf | |
Instances
data AnnotationPropertyDomain Source #
Constructors
AnnotationPropertyDomain | |
Instances
data AnnotationPropertyRange Source #
Constructors
AnnotationPropertyRange | |
Instances
Constructors
Class | |
Constructors
DatatypeXmlSchema Datatype | Note: XML Schema datatypes are treated as a special case in this model (not in the OWL 2 specification itself) because they are particularly common |
DatatypeOther Iri |
data ObjectProperty Source #
Constructors
ObjectProperty | |
Instances
Read ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ObjectProperty # readList :: ReadS [ObjectProperty] # | |
Show ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ObjectProperty -> ShowS # show :: ObjectProperty -> String # showList :: [ObjectProperty] -> ShowS # | |
Eq ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ObjectProperty -> ObjectProperty -> Bool # (/=) :: ObjectProperty -> ObjectProperty -> Bool # | |
Ord ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ObjectProperty -> ObjectProperty -> Ordering # (<) :: ObjectProperty -> ObjectProperty -> Bool # (<=) :: ObjectProperty -> ObjectProperty -> Bool # (>) :: ObjectProperty -> ObjectProperty -> Bool # (>=) :: ObjectProperty -> ObjectProperty -> Bool # max :: ObjectProperty -> ObjectProperty -> ObjectProperty # min :: ObjectProperty -> ObjectProperty -> ObjectProperty # |
data DataProperty Source #
Constructors
DataProperty | |
Instances
Read DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DataProperty # readList :: ReadS [DataProperty] # | |
Show DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DataProperty -> ShowS # show :: DataProperty -> String # showList :: [DataProperty] -> ShowS # | |
Eq DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DataProperty -> DataProperty -> Ordering # (<) :: DataProperty -> DataProperty -> Bool # (<=) :: DataProperty -> DataProperty -> Bool # (>) :: DataProperty -> DataProperty -> Bool # (>=) :: DataProperty -> DataProperty -> Bool # max :: DataProperty -> DataProperty -> DataProperty # min :: DataProperty -> DataProperty -> DataProperty # |
_DataProperty :: Name Source #
data AnnotationProperty Source #
Constructors
AnnotationProperty | |
Instances
data Individual Source #
Instances
Read Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS Individual # readList :: ReadS [Individual] # readPrec :: ReadPrec Individual # readListPrec :: ReadPrec [Individual] # | |
Show Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> Individual -> ShowS # show :: Individual -> String # showList :: [Individual] -> ShowS # | |
Eq Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: Individual -> Individual -> Ordering # (<) :: Individual -> Individual -> Bool # (<=) :: Individual -> Individual -> Bool # (>) :: Individual -> Individual -> Bool # (>=) :: Individual -> Individual -> Bool # max :: Individual -> Individual -> Individual # min :: Individual -> Individual -> Individual # |
_Individual :: Name Source #
data NamedIndividual Source #
Constructors
NamedIndividual | |
Instances
Read NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS NamedIndividual # readList :: ReadS [NamedIndividual] # | |
Show NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> NamedIndividual -> ShowS # show :: NamedIndividual -> String # showList :: [NamedIndividual] -> ShowS # | |
Eq NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: NamedIndividual -> NamedIndividual -> Bool # (/=) :: NamedIndividual -> NamedIndividual -> Bool # | |
Ord NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: NamedIndividual -> NamedIndividual -> Ordering # (<) :: NamedIndividual -> NamedIndividual -> Bool # (<=) :: NamedIndividual -> NamedIndividual -> Bool # (>) :: NamedIndividual -> NamedIndividual -> Bool # (>=) :: NamedIndividual -> NamedIndividual -> Bool # max :: NamedIndividual -> NamedIndividual -> NamedIndividual # min :: NamedIndividual -> NamedIndividual -> NamedIndividual # |
data AnonymousIndividual Source #
Constructors
AnonymousIndividual | |
Instances
data ObjectPropertyExpression Source #
Constructors
ObjectPropertyExpressionObject ObjectProperty | |
ObjectPropertyExpressionInverseObject InverseObjectProperty |
Instances
newtype InverseObjectProperty Source #
Constructors
InverseObjectProperty | |
Fields |
Instances
newtype DataPropertyExpression Source #
Constructors
DataPropertyExpression | |
Fields |
Instances
Constructors
Instances
Read DataRange Source # | |
Show DataRange Source # | |
Eq DataRange Source # | |
Ord DataRange Source # | |
_DataRange :: Name Source #
newtype DataIntersectionOf Source #
Constructors
DataIntersectionOf | |
Instances
newtype DataUnionOf Source #
Constructors
DataUnionOf | |
Instances
Read DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DataUnionOf # readList :: ReadS [DataUnionOf] # readPrec :: ReadPrec DataUnionOf # readListPrec :: ReadPrec [DataUnionOf] # | |
Show DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DataUnionOf -> ShowS # show :: DataUnionOf -> String # showList :: [DataUnionOf] -> ShowS # | |
Eq DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DataUnionOf -> DataUnionOf -> Ordering # (<) :: DataUnionOf -> DataUnionOf -> Bool # (<=) :: DataUnionOf -> DataUnionOf -> Bool # (>) :: DataUnionOf -> DataUnionOf -> Bool # (>=) :: DataUnionOf -> DataUnionOf -> Bool # max :: DataUnionOf -> DataUnionOf -> DataUnionOf # min :: DataUnionOf -> DataUnionOf -> DataUnionOf # |
_DataUnionOf :: Name Source #
newtype DataComplementOf Source #
Constructors
DataComplementOf | |
Instances
Read DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DataComplementOf # readList :: ReadS [DataComplementOf] # | |
Show DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DataComplementOf -> ShowS # show :: DataComplementOf -> String # showList :: [DataComplementOf] -> ShowS # | |
Eq DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: DataComplementOf -> DataComplementOf -> Bool # (/=) :: DataComplementOf -> DataComplementOf -> Bool # | |
Ord DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DataComplementOf -> DataComplementOf -> Ordering # (<) :: DataComplementOf -> DataComplementOf -> Bool # (<=) :: DataComplementOf -> DataComplementOf -> Bool # (>) :: DataComplementOf -> DataComplementOf -> Bool # (>=) :: DataComplementOf -> DataComplementOf -> Bool # max :: DataComplementOf -> DataComplementOf -> DataComplementOf # min :: DataComplementOf -> DataComplementOf -> DataComplementOf # |
Constructors
DataOneOf | |
Instances
Read DataOneOf Source # | |
Show DataOneOf Source # | |
Eq DataOneOf Source # | |
Ord DataOneOf Source # | |
_DataOneOf :: Name Source #
data DatatypeRestriction Source #
Constructors
DatatypeRestriction | |
Instances
data DatatypeRestriction_Constraint Source #
Constructors
DatatypeRestriction_Constraint | |
Instances
data DatatypeRestriction_ConstrainingFacet Source #
Constructors
DatatypeRestriction_ConstrainingFacetXmlSchema ConstrainingFacet | Note: XML Schema constraining facets are treated as a special case in this model (not in the OWL 2 specification itself) because they are particularly common |
DatatypeRestriction_ConstrainingFacetOther Iri |
Instances
data ClassExpression Source #
Constructors
Instances
Read ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ClassExpression # readList :: ReadS [ClassExpression] # | |
Show ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ClassExpression -> ShowS # show :: ClassExpression -> String # showList :: [ClassExpression] -> ShowS # | |
Eq ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ClassExpression -> ClassExpression -> Bool # (/=) :: ClassExpression -> ClassExpression -> Bool # | |
Ord ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ClassExpression -> ClassExpression -> Ordering # (<) :: ClassExpression -> ClassExpression -> Bool # (<=) :: ClassExpression -> ClassExpression -> Bool # (>) :: ClassExpression -> ClassExpression -> Bool # (>=) :: ClassExpression -> ClassExpression -> Bool # max :: ClassExpression -> ClassExpression -> ClassExpression # min :: ClassExpression -> ClassExpression -> ClassExpression # |
newtype ObjectIntersectionOf Source #
Constructors
ObjectIntersectionOf | |
Fields |
Instances
newtype ObjectUnionOf Source #
Constructors
ObjectUnionOf | |
Fields |
Instances
Read ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ObjectUnionOf # readList :: ReadS [ObjectUnionOf] # | |
Show ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ObjectUnionOf -> ShowS # show :: ObjectUnionOf -> String # showList :: [ObjectUnionOf] -> ShowS # | |
Eq ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ObjectUnionOf -> ObjectUnionOf -> Bool # (/=) :: ObjectUnionOf -> ObjectUnionOf -> Bool # | |
Ord ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ObjectUnionOf -> ObjectUnionOf -> Ordering # (<) :: ObjectUnionOf -> ObjectUnionOf -> Bool # (<=) :: ObjectUnionOf -> ObjectUnionOf -> Bool # (>) :: ObjectUnionOf -> ObjectUnionOf -> Bool # (>=) :: ObjectUnionOf -> ObjectUnionOf -> Bool # max :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf # min :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf # |
newtype ObjectComplementOf Source #
Constructors
ObjectComplementOf | |
Fields |
Instances
newtype ObjectOneOf Source #
Constructors
ObjectOneOf | |
Fields
|
Instances
Read ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ObjectOneOf # readList :: ReadS [ObjectOneOf] # readPrec :: ReadPrec ObjectOneOf # readListPrec :: ReadPrec [ObjectOneOf] # | |
Show ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ObjectOneOf -> ShowS # show :: ObjectOneOf -> String # showList :: [ObjectOneOf] -> ShowS # | |
Eq ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ObjectOneOf -> ObjectOneOf -> Ordering # (<) :: ObjectOneOf -> ObjectOneOf -> Bool # (<=) :: ObjectOneOf -> ObjectOneOf -> Bool # (>) :: ObjectOneOf -> ObjectOneOf -> Bool # (>=) :: ObjectOneOf -> ObjectOneOf -> Bool # max :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf # min :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf # |
_ObjectOneOf :: Name Source #
data ObjectSomeValuesFrom Source #
Constructors
ObjectSomeValuesFrom | |
Instances
data ObjectAllValuesFrom Source #
Constructors
ObjectAllValuesFrom | |
Instances
data ObjectHasValue Source #
Constructors
ObjectHasValue | |
Instances
Read ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ObjectHasValue # readList :: ReadS [ObjectHasValue] # | |
Show ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ObjectHasValue -> ShowS # show :: ObjectHasValue -> String # showList :: [ObjectHasValue] -> ShowS # | |
Eq ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ObjectHasValue -> ObjectHasValue -> Bool # (/=) :: ObjectHasValue -> ObjectHasValue -> Bool # | |
Ord ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ObjectHasValue -> ObjectHasValue -> Ordering # (<) :: ObjectHasValue -> ObjectHasValue -> Bool # (<=) :: ObjectHasValue -> ObjectHasValue -> Bool # (>) :: ObjectHasValue -> ObjectHasValue -> Bool # (>=) :: ObjectHasValue -> ObjectHasValue -> Bool # max :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue # min :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue # |
newtype ObjectHasSelf Source #
Constructors
ObjectHasSelf | |
Fields |
Instances
Read ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ObjectHasSelf # readList :: ReadS [ObjectHasSelf] # | |
Show ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ObjectHasSelf -> ShowS # show :: ObjectHasSelf -> String # showList :: [ObjectHasSelf] -> ShowS # | |
Eq ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ObjectHasSelf -> ObjectHasSelf -> Bool # (/=) :: ObjectHasSelf -> ObjectHasSelf -> Bool # | |
Ord ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ObjectHasSelf -> ObjectHasSelf -> Ordering # (<) :: ObjectHasSelf -> ObjectHasSelf -> Bool # (<=) :: ObjectHasSelf -> ObjectHasSelf -> Bool # (>) :: ObjectHasSelf -> ObjectHasSelf -> Bool # (>=) :: ObjectHasSelf -> ObjectHasSelf -> Bool # max :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf # min :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf # |
data ObjectMinCardinality Source #
Constructors
ObjectMinCardinality | |
Instances
data ObjectMaxCardinality Source #
Constructors
ObjectMaxCardinality | |
Instances
data ObjectExactCardinality Source #
Constructors
ObjectExactCardinality | |
Instances
data DataSomeValuesFrom Source #
Constructors
DataSomeValuesFrom | |
Instances
data DataAllValuesFrom Source #
Constructors
DataAllValuesFrom | |
Instances
data DataHasValue Source #
Constructors
DataHasValue | |
Instances
Read DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DataHasValue # readList :: ReadS [DataHasValue] # | |
Show DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DataHasValue -> ShowS # show :: DataHasValue -> String # showList :: [DataHasValue] -> ShowS # | |
Eq DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DataHasValue -> DataHasValue -> Ordering # (<) :: DataHasValue -> DataHasValue -> Bool # (<=) :: DataHasValue -> DataHasValue -> Bool # (>) :: DataHasValue -> DataHasValue -> Bool # (>=) :: DataHasValue -> DataHasValue -> Bool # max :: DataHasValue -> DataHasValue -> DataHasValue # min :: DataHasValue -> DataHasValue -> DataHasValue # |
_DataHasValue :: Name Source #
data DataMinCardinality Source #
Constructors
DataMinCardinality | |
Instances
data DataMaxCardinality Source #
Constructors
DataMaxCardinality | |
Instances
data DataExactCardinality Source #
Constructors
DataExactCardinality | |
Instances
Constructors
data ClassAxiom Source #
Constructors
ClassAxiomDisjointClasses DisjointClasses | |
ClassAxiomDisjointUnion DisjointUnion | |
ClassAxiomEquivalentClasses EquivalentClasses | |
ClassAxiomSubClassOf SubClassOf |
Instances
Read ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ClassAxiom # readList :: ReadS [ClassAxiom] # readPrec :: ReadPrec ClassAxiom # readListPrec :: ReadPrec [ClassAxiom] # | |
Show ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ClassAxiom -> ShowS # show :: ClassAxiom -> String # showList :: [ClassAxiom] -> ShowS # | |
Eq ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ClassAxiom -> ClassAxiom -> Ordering # (<) :: ClassAxiom -> ClassAxiom -> Bool # (<=) :: ClassAxiom -> ClassAxiom -> Bool # (>) :: ClassAxiom -> ClassAxiom -> Bool # (>=) :: ClassAxiom -> ClassAxiom -> Bool # max :: ClassAxiom -> ClassAxiom -> ClassAxiom # min :: ClassAxiom -> ClassAxiom -> ClassAxiom # |
_ClassAxiom :: Name Source #
data SubClassOf Source #
Constructors
SubClassOf | |
Instances
Read SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS SubClassOf # readList :: ReadS [SubClassOf] # readPrec :: ReadPrec SubClassOf # readListPrec :: ReadPrec [SubClassOf] # | |
Show SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> SubClassOf -> ShowS # show :: SubClassOf -> String # showList :: [SubClassOf] -> ShowS # | |
Eq SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: SubClassOf -> SubClassOf -> Ordering # (<) :: SubClassOf -> SubClassOf -> Bool # (<=) :: SubClassOf -> SubClassOf -> Bool # (>) :: SubClassOf -> SubClassOf -> Bool # (>=) :: SubClassOf -> SubClassOf -> Bool # max :: SubClassOf -> SubClassOf -> SubClassOf # min :: SubClassOf -> SubClassOf -> SubClassOf # |
_SubClassOf :: Name Source #
data EquivalentClasses Source #
Constructors
EquivalentClasses | |
Instances
data DisjointClasses Source #
Constructors
DisjointClasses | |
Fields |
Instances
Read DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DisjointClasses # readList :: ReadS [DisjointClasses] # | |
Show DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DisjointClasses -> ShowS # show :: DisjointClasses -> String # showList :: [DisjointClasses] -> ShowS # | |
Eq DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: DisjointClasses -> DisjointClasses -> Bool # (/=) :: DisjointClasses -> DisjointClasses -> Bool # | |
Ord DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DisjointClasses -> DisjointClasses -> Ordering # (<) :: DisjointClasses -> DisjointClasses -> Bool # (<=) :: DisjointClasses -> DisjointClasses -> Bool # (>) :: DisjointClasses -> DisjointClasses -> Bool # (>=) :: DisjointClasses -> DisjointClasses -> Bool # max :: DisjointClasses -> DisjointClasses -> DisjointClasses # min :: DisjointClasses -> DisjointClasses -> DisjointClasses # |
data DisjointUnion Source #
Constructors
DisjointUnion | |
Fields |
Instances
Read DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS DisjointUnion # readList :: ReadS [DisjointUnion] # | |
Show DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> DisjointUnion -> ShowS # show :: DisjointUnion -> String # showList :: [DisjointUnion] -> ShowS # | |
Eq DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: DisjointUnion -> DisjointUnion -> Bool # (/=) :: DisjointUnion -> DisjointUnion -> Bool # | |
Ord DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: DisjointUnion -> DisjointUnion -> Ordering # (<) :: DisjointUnion -> DisjointUnion -> Bool # (<=) :: DisjointUnion -> DisjointUnion -> Bool # (>) :: DisjointUnion -> DisjointUnion -> Bool # (>=) :: DisjointUnion -> DisjointUnion -> Bool # max :: DisjointUnion -> DisjointUnion -> DisjointUnion # min :: DisjointUnion -> DisjointUnion -> DisjointUnion # |
data ObjectPropertyAxiom Source #
Constructors
Instances
data SubObjectPropertyOf Source #
Constructors
SubObjectPropertyOf | |
Instances
data EquivalentObjectProperties Source #
Constructors
EquivalentObjectProperties | |
Instances
data DisjointObjectProperties Source #
Constructors
DisjointObjectProperties | |
Instances
data ObjectPropertyDomain Source #
Constructors
ObjectPropertyDomain | |
Instances
data ObjectPropertyRange Source #
Constructors
ObjectPropertyRange | |
Instances
data InverseObjectProperties Source #
Constructors
InverseObjectProperties | |
Instances
data FunctionalObjectProperty Source #
Constructors
FunctionalObjectProperty | |
Instances
data InverseFunctionalObjectProperty Source #
Constructors
InverseFunctionalObjectProperty | |
Instances
data ReflexiveObjectProperty Source #
Constructors
ReflexiveObjectProperty | |
Instances
data IrreflexiveObjectProperty Source #
Constructors
IrreflexiveObjectProperty | |
Instances
data SymmetricObjectProperty Source #
Constructors
SymmetricObjectProperty | |
Instances
data AsymmetricObjectProperty Source #
Constructors
AsymmetricObjectProperty | |
Instances
data TransitiveObjectProperty Source #
Constructors
TransitiveObjectProperty | |
Instances
data DataPropertyAxiom Source #
Constructors
Instances
data SubDataPropertyOf Source #
Constructors
SubDataPropertyOf | |
Instances
data EquivalentDataProperties Source #
Constructors
EquivalentDataProperties | |
Instances
data DisjointDataProperties Source #
Constructors
DisjointDataProperties | |
Instances
data DataPropertyDomain Source #
Constructors
DataPropertyDomain | |
Instances
data DataPropertyRange Source #
Constructors
DataPropertyRange | |
Instances
data FunctionalDataProperty Source #
Constructors
FunctionalDataProperty | |
Instances
data DatatypeDefinition Source #
Constructors
DatatypeDefinition | |
Instances
Constructors
HasKey | |
Constructors
Instances
Read Assertion Source # | |
Show Assertion Source # | |
Eq Assertion Source # | |
Ord Assertion Source # | |
_Assertion :: Name Source #
data SameIndividual Source #
Constructors
SameIndividual | |
Fields |
Instances
Read SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS SameIndividual # readList :: ReadS [SameIndividual] # | |
Show SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> SameIndividual -> ShowS # show :: SameIndividual -> String # showList :: [SameIndividual] -> ShowS # | |
Eq SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: SameIndividual -> SameIndividual -> Bool # (/=) :: SameIndividual -> SameIndividual -> Bool # | |
Ord SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: SameIndividual -> SameIndividual -> Ordering # (<) :: SameIndividual -> SameIndividual -> Bool # (<=) :: SameIndividual -> SameIndividual -> Bool # (>) :: SameIndividual -> SameIndividual -> Bool # (>=) :: SameIndividual -> SameIndividual -> Bool # max :: SameIndividual -> SameIndividual -> SameIndividual # min :: SameIndividual -> SameIndividual -> SameIndividual # |
data DifferentIndividuals Source #
Constructors
DifferentIndividuals | |
Instances
data ClassAssertion Source #
Constructors
ClassAssertion | |
Instances
Read ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods readsPrec :: Int -> ReadS ClassAssertion # readList :: ReadS [ClassAssertion] # | |
Show ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods showsPrec :: Int -> ClassAssertion -> ShowS # show :: ClassAssertion -> String # showList :: [ClassAssertion] -> ShowS # | |
Eq ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods (==) :: ClassAssertion -> ClassAssertion -> Bool # (/=) :: ClassAssertion -> ClassAssertion -> Bool # | |
Ord ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax Methods compare :: ClassAssertion -> ClassAssertion -> Ordering # (<) :: ClassAssertion -> ClassAssertion -> Bool # (<=) :: ClassAssertion -> ClassAssertion -> Bool # (>) :: ClassAssertion -> ClassAssertion -> Bool # (>=) :: ClassAssertion -> ClassAssertion -> Bool # max :: ClassAssertion -> ClassAssertion -> ClassAssertion # min :: ClassAssertion -> ClassAssertion -> ClassAssertion # |
data ObjectPropertyAssertion Source #
Constructors
ObjectPropertyAssertion | |
Instances
data NegativeObjectPropertyAssertion Source #
Constructors
NegativeObjectPropertyAssertion | |
Instances
data DataPropertyAssertion Source #
Constructors
DataPropertyAssertion | |
Instances
data NegativeDataPropertyAssertion Source #
Constructors
NegativeDataPropertyAssertion | |