Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
Ontology | |
|
data Declaration Source #
Instances
Read Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS Declaration # readList :: ReadS [Declaration] # readPrec :: ReadPrec Declaration # readListPrec :: ReadPrec [Declaration] # | |
Show Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
Eq Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: Declaration -> Declaration -> Bool # (/=) :: Declaration -> Declaration -> Bool # | |
Ord Declaration Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
EntityAnnotationProperty AnnotationProperty | |
EntityClass Class | |
EntityDataProperty DataProperty | |
EntityDatatype Datatype | |
EntityNamedIndividual NamedIndividual | |
EntityObjectProperty ObjectProperty |
data AnnotationSubject Source #
Instances
Read AnnotationSubject Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnnotationSubject Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnnotationSubject -> ShowS # show :: AnnotationSubject -> String # showList :: [AnnotationSubject] -> ShowS # | |
Eq AnnotationSubject Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnnotationSubject -> AnnotationSubject -> Bool # (/=) :: AnnotationSubject -> AnnotationSubject -> Bool # | |
Ord AnnotationSubject Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: AnnotationSubject -> AnnotationSubject -> Ordering # (<) :: AnnotationSubject -> AnnotationSubject -> Bool # (<=) :: AnnotationSubject -> AnnotationSubject -> Bool # (>) :: AnnotationSubject -> AnnotationSubject -> Bool # (>=) :: AnnotationSubject -> AnnotationSubject -> Bool # max :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject # min :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject # |
data AnnotationValue Source #
AnnotationValueAnonymousIndividual AnonymousIndividual | |
AnnotationValueIri Iri | |
AnnotationValueLiteral Literal |
Instances
Read AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnnotationValue -> ShowS # show :: AnnotationValue -> String # showList :: [AnnotationValue] -> ShowS # | |
Eq AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnnotationValue -> AnnotationValue -> Bool # (/=) :: AnnotationValue -> AnnotationValue -> Bool # | |
Ord AnnotationValue Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS Annotation # readList :: ReadS [Annotation] # readPrec :: ReadPrec Annotation # readListPrec :: ReadPrec [Annotation] # | |
Show Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Eq Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: Annotation -> Annotation -> Bool # (/=) :: Annotation -> Annotation -> Bool # | |
Ord Annotation Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnnotationAxiom -> ShowS # show :: AnnotationAxiom -> String # showList :: [AnnotationAxiom] -> ShowS # | |
Eq AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnnotationAxiom -> AnnotationAxiom -> Bool # (/=) :: AnnotationAxiom -> AnnotationAxiom -> Bool # | |
Ord AnnotationAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read AnnotationAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnnotationAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnnotationAssertion -> ShowS # show :: AnnotationAssertion -> String # showList :: [AnnotationAssertion] -> ShowS # | |
Eq AnnotationAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnnotationAssertion -> AnnotationAssertion -> Bool # (/=) :: AnnotationAssertion -> AnnotationAssertion -> Bool # | |
Ord AnnotationAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: AnnotationAssertion -> AnnotationAssertion -> Ordering # (<) :: AnnotationAssertion -> AnnotationAssertion -> Bool # (<=) :: AnnotationAssertion -> AnnotationAssertion -> Bool # (>) :: AnnotationAssertion -> AnnotationAssertion -> Bool # (>=) :: AnnotationAssertion -> AnnotationAssertion -> Bool # max :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion # min :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion # |
data SubAnnotationPropertyOf Source #
Instances
data AnnotationPropertyDomain Source #
Instances
data AnnotationPropertyRange Source #
Instances
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 #
Instances
Read ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ObjectProperty # readList :: ReadS [ObjectProperty] # | |
Show ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectProperty -> ShowS # show :: ObjectProperty -> String # showList :: [ObjectProperty] -> ShowS # | |
Eq ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectProperty -> ObjectProperty -> Bool # (/=) :: ObjectProperty -> ObjectProperty -> Bool # | |
Ord ObjectProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS DataProperty # readList :: ReadS [DataProperty] # | |
Show DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataProperty -> ShowS # show :: DataProperty -> String # showList :: [DataProperty] -> ShowS # | |
Eq DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataProperty -> DataProperty -> Bool # (/=) :: DataProperty -> DataProperty -> Bool # | |
Ord DataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read AnnotationProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnnotationProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnnotationProperty -> ShowS # show :: AnnotationProperty -> String # showList :: [AnnotationProperty] -> ShowS # | |
Eq AnnotationProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnnotationProperty -> AnnotationProperty -> Bool # (/=) :: AnnotationProperty -> AnnotationProperty -> Bool # | |
Ord AnnotationProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: AnnotationProperty -> AnnotationProperty -> Ordering # (<) :: AnnotationProperty -> AnnotationProperty -> Bool # (<=) :: AnnotationProperty -> AnnotationProperty -> Bool # (>) :: AnnotationProperty -> AnnotationProperty -> Bool # (>=) :: AnnotationProperty -> AnnotationProperty -> Bool # max :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty # min :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty # |
data Individual Source #
Instances
Read Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS Individual # readList :: ReadS [Individual] # readPrec :: ReadPrec Individual # readListPrec :: ReadPrec [Individual] # | |
Show Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> Individual -> ShowS # show :: Individual -> String # showList :: [Individual] -> ShowS # | |
Eq Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: Individual -> Individual -> Bool # (/=) :: Individual -> Individual -> Bool # | |
Ord Individual Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> NamedIndividual -> ShowS # show :: NamedIndividual -> String # showList :: [NamedIndividual] -> ShowS # | |
Eq NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: NamedIndividual -> NamedIndividual -> Bool # (/=) :: NamedIndividual -> NamedIndividual -> Bool # | |
Ord NamedIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read AnonymousIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show AnonymousIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> AnonymousIndividual -> ShowS # show :: AnonymousIndividual -> String # showList :: [AnonymousIndividual] -> ShowS # | |
Eq AnonymousIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: AnonymousIndividual -> AnonymousIndividual -> Bool # (/=) :: AnonymousIndividual -> AnonymousIndividual -> Bool # | |
Ord AnonymousIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: AnonymousIndividual -> AnonymousIndividual -> Ordering # (<) :: AnonymousIndividual -> AnonymousIndividual -> Bool # (<=) :: AnonymousIndividual -> AnonymousIndividual -> Bool # (>) :: AnonymousIndividual -> AnonymousIndividual -> Bool # (>=) :: AnonymousIndividual -> AnonymousIndividual -> Bool # max :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual # min :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual # |
data ObjectPropertyExpression Source #
ObjectPropertyExpressionObject ObjectProperty | |
ObjectPropertyExpressionInverseObject InverseObjectProperty |
Instances
newtype InverseObjectProperty Source #
Instances
newtype DataPropertyExpression Source #
Instances
Read DataPropertyExpression Source # | |
Show DataPropertyExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataPropertyExpression -> ShowS # show :: DataPropertyExpression -> String # showList :: [DataPropertyExpression] -> ShowS # | |
Eq DataPropertyExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord DataPropertyExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataPropertyExpression -> DataPropertyExpression -> Ordering # (<) :: DataPropertyExpression -> DataPropertyExpression -> Bool # (<=) :: DataPropertyExpression -> DataPropertyExpression -> Bool # (>) :: DataPropertyExpression -> DataPropertyExpression -> Bool # (>=) :: DataPropertyExpression -> DataPropertyExpression -> Bool # max :: DataPropertyExpression -> DataPropertyExpression -> DataPropertyExpression # min :: DataPropertyExpression -> DataPropertyExpression -> DataPropertyExpression # |
_DataRange :: Name Source #
newtype DataIntersectionOf Source #
Instances
Read DataIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataIntersectionOf -> ShowS # show :: DataIntersectionOf -> String # showList :: [DataIntersectionOf] -> ShowS # | |
Eq DataIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataIntersectionOf -> DataIntersectionOf -> Bool # (/=) :: DataIntersectionOf -> DataIntersectionOf -> Bool # | |
Ord DataIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataIntersectionOf -> DataIntersectionOf -> Ordering # (<) :: DataIntersectionOf -> DataIntersectionOf -> Bool # (<=) :: DataIntersectionOf -> DataIntersectionOf -> Bool # (>) :: DataIntersectionOf -> DataIntersectionOf -> Bool # (>=) :: DataIntersectionOf -> DataIntersectionOf -> Bool # max :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf # min :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf # |
newtype DataUnionOf Source #
Instances
Read DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS DataUnionOf # readList :: ReadS [DataUnionOf] # readPrec :: ReadPrec DataUnionOf # readListPrec :: ReadPrec [DataUnionOf] # | |
Show DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataUnionOf -> ShowS # show :: DataUnionOf -> String # showList :: [DataUnionOf] -> ShowS # | |
Eq DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataUnionOf -> DataUnionOf -> Bool # (/=) :: DataUnionOf -> DataUnionOf -> Bool # | |
Ord DataUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataComplementOf -> ShowS # show :: DataComplementOf -> String # showList :: [DataComplementOf] -> ShowS # | |
Eq DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataComplementOf -> DataComplementOf -> Bool # (/=) :: DataComplementOf -> DataComplementOf -> Bool # | |
Ord DataComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataComplementOf -> DataComplementOf -> Ordering # (<) :: DataComplementOf -> DataComplementOf -> Bool # (<=) :: DataComplementOf -> DataComplementOf -> Bool # (>) :: DataComplementOf -> DataComplementOf -> Bool # (>=) :: DataComplementOf -> DataComplementOf -> Bool # max :: DataComplementOf -> DataComplementOf -> DataComplementOf # min :: DataComplementOf -> DataComplementOf -> DataComplementOf # |
_DataOneOf :: Name Source #
data DatatypeRestriction Source #
Instances
Read DatatypeRestriction Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DatatypeRestriction Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DatatypeRestriction -> ShowS # show :: DatatypeRestriction -> String # showList :: [DatatypeRestriction] -> ShowS # | |
Eq DatatypeRestriction Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DatatypeRestriction -> DatatypeRestriction -> Bool # (/=) :: DatatypeRestriction -> DatatypeRestriction -> Bool # | |
Ord DatatypeRestriction Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DatatypeRestriction -> DatatypeRestriction -> Ordering # (<) :: DatatypeRestriction -> DatatypeRestriction -> Bool # (<=) :: DatatypeRestriction -> DatatypeRestriction -> Bool # (>) :: DatatypeRestriction -> DatatypeRestriction -> Bool # (>=) :: DatatypeRestriction -> DatatypeRestriction -> Bool # max :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction # min :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction # |
data DatatypeRestriction_Constraint Source #
Instances
data DatatypeRestriction_ConstrainingFacet Source #
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 #
Instances
Read ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ClassExpression -> ShowS # show :: ClassExpression -> String # showList :: [ClassExpression] -> ShowS # | |
Eq ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ClassExpression -> ClassExpression -> Bool # (/=) :: ClassExpression -> ClassExpression -> Bool # | |
Ord ClassExpression Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectIntersectionOf -> ShowS # show :: ObjectIntersectionOf -> String # showList :: [ObjectIntersectionOf] -> ShowS # | |
Eq ObjectIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # (/=) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # | |
Ord ObjectIntersectionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectIntersectionOf -> ObjectIntersectionOf -> Ordering # (<) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # (<=) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # (>) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # (>=) :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool # max :: ObjectIntersectionOf -> ObjectIntersectionOf -> ObjectIntersectionOf # min :: ObjectIntersectionOf -> ObjectIntersectionOf -> ObjectIntersectionOf # |
newtype ObjectUnionOf Source #
Instances
Read ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ObjectUnionOf # readList :: ReadS [ObjectUnionOf] # | |
Show ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectUnionOf -> ShowS # show :: ObjectUnionOf -> String # showList :: [ObjectUnionOf] -> ShowS # | |
Eq ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectUnionOf -> ObjectUnionOf -> Bool # (/=) :: ObjectUnionOf -> ObjectUnionOf -> Bool # | |
Ord ObjectUnionOf Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectComplementOf -> ShowS # show :: ObjectComplementOf -> String # showList :: [ObjectComplementOf] -> ShowS # | |
Eq ObjectComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectComplementOf -> ObjectComplementOf -> Bool # (/=) :: ObjectComplementOf -> ObjectComplementOf -> Bool # | |
Ord ObjectComplementOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectComplementOf -> ObjectComplementOf -> Ordering # (<) :: ObjectComplementOf -> ObjectComplementOf -> Bool # (<=) :: ObjectComplementOf -> ObjectComplementOf -> Bool # (>) :: ObjectComplementOf -> ObjectComplementOf -> Bool # (>=) :: ObjectComplementOf -> ObjectComplementOf -> Bool # max :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf # min :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf # |
newtype ObjectOneOf Source #
Instances
Read ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ObjectOneOf # readList :: ReadS [ObjectOneOf] # readPrec :: ReadPrec ObjectOneOf # readListPrec :: ReadPrec [ObjectOneOf] # | |
Show ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectOneOf -> ShowS # show :: ObjectOneOf -> String # showList :: [ObjectOneOf] -> ShowS # | |
Eq ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectOneOf -> ObjectOneOf -> Bool # (/=) :: ObjectOneOf -> ObjectOneOf -> Bool # | |
Ord ObjectOneOf Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectSomeValuesFrom -> ShowS # show :: ObjectSomeValuesFrom -> String # showList :: [ObjectSomeValuesFrom] -> ShowS # | |
Eq ObjectSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # (/=) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # | |
Ord ObjectSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Ordering # (<) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # (<=) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # (>) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # (>=) :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool # max :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> ObjectSomeValuesFrom # min :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> ObjectSomeValuesFrom # |
data ObjectAllValuesFrom Source #
Instances
Read ObjectAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectAllValuesFrom -> ShowS # show :: ObjectAllValuesFrom -> String # showList :: [ObjectAllValuesFrom] -> ShowS # | |
Eq ObjectAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # (/=) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # | |
Ord ObjectAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Ordering # (<) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # (<=) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # (>) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # (>=) :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool # max :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom # min :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom # |
data ObjectHasValue Source #
Instances
Read ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ObjectHasValue # readList :: ReadS [ObjectHasValue] # | |
Show ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectHasValue -> ShowS # show :: ObjectHasValue -> String # showList :: [ObjectHasValue] -> ShowS # | |
Eq ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectHasValue -> ObjectHasValue -> Bool # (/=) :: ObjectHasValue -> ObjectHasValue -> Bool # | |
Ord ObjectHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ObjectHasSelf # readList :: ReadS [ObjectHasSelf] # | |
Show ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectHasSelf -> ShowS # show :: ObjectHasSelf -> String # showList :: [ObjectHasSelf] -> ShowS # | |
Eq ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectHasSelf -> ObjectHasSelf -> Bool # (/=) :: ObjectHasSelf -> ObjectHasSelf -> Bool # | |
Ord ObjectHasSelf Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectMinCardinality -> ShowS # show :: ObjectMinCardinality -> String # showList :: [ObjectMinCardinality] -> ShowS # | |
Eq ObjectMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # (/=) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # | |
Ord ObjectMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectMinCardinality -> ObjectMinCardinality -> Ordering # (<) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # (<=) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # (>) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # (>=) :: ObjectMinCardinality -> ObjectMinCardinality -> Bool # max :: ObjectMinCardinality -> ObjectMinCardinality -> ObjectMinCardinality # min :: ObjectMinCardinality -> ObjectMinCardinality -> ObjectMinCardinality # |
data ObjectMaxCardinality Source #
Instances
Read ObjectMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectMaxCardinality -> ShowS # show :: ObjectMaxCardinality -> String # showList :: [ObjectMaxCardinality] -> ShowS # | |
Eq ObjectMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # (/=) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # | |
Ord ObjectMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectMaxCardinality -> ObjectMaxCardinality -> Ordering # (<) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # (<=) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # (>) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # (>=) :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool # max :: ObjectMaxCardinality -> ObjectMaxCardinality -> ObjectMaxCardinality # min :: ObjectMaxCardinality -> ObjectMaxCardinality -> ObjectMaxCardinality # |
data ObjectExactCardinality Source #
Instances
Read ObjectExactCardinality Source # | |
Show ObjectExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectExactCardinality -> ShowS # show :: ObjectExactCardinality -> String # showList :: [ObjectExactCardinality] -> ShowS # | |
Eq ObjectExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord ObjectExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectExactCardinality -> ObjectExactCardinality -> Ordering # (<) :: ObjectExactCardinality -> ObjectExactCardinality -> Bool # (<=) :: ObjectExactCardinality -> ObjectExactCardinality -> Bool # (>) :: ObjectExactCardinality -> ObjectExactCardinality -> Bool # (>=) :: ObjectExactCardinality -> ObjectExactCardinality -> Bool # max :: ObjectExactCardinality -> ObjectExactCardinality -> ObjectExactCardinality # min :: ObjectExactCardinality -> ObjectExactCardinality -> ObjectExactCardinality # |
data DataSomeValuesFrom Source #
Instances
Read DataSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataSomeValuesFrom -> ShowS # show :: DataSomeValuesFrom -> String # showList :: [DataSomeValuesFrom] -> ShowS # | |
Eq DataSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # (/=) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # | |
Ord DataSomeValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataSomeValuesFrom -> DataSomeValuesFrom -> Ordering # (<) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # (<=) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # (>) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # (>=) :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool # max :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom # min :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom # |
data DataAllValuesFrom Source #
Instances
Read DataAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataAllValuesFrom -> ShowS # show :: DataAllValuesFrom -> String # showList :: [DataAllValuesFrom] -> ShowS # | |
Eq DataAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # (/=) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # | |
Ord DataAllValuesFrom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataAllValuesFrom -> DataAllValuesFrom -> Ordering # (<) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # (<=) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # (>) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # (>=) :: DataAllValuesFrom -> DataAllValuesFrom -> Bool # max :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom # min :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom # |
data DataHasValue Source #
Instances
Read DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS DataHasValue # readList :: ReadS [DataHasValue] # | |
Show DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataHasValue -> ShowS # show :: DataHasValue -> String # showList :: [DataHasValue] -> ShowS # | |
Eq DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataHasValue -> DataHasValue -> Bool # (/=) :: DataHasValue -> DataHasValue -> Bool # | |
Ord DataHasValue Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read DataMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataMinCardinality -> ShowS # show :: DataMinCardinality -> String # showList :: [DataMinCardinality] -> ShowS # | |
Eq DataMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataMinCardinality -> DataMinCardinality -> Bool # (/=) :: DataMinCardinality -> DataMinCardinality -> Bool # | |
Ord DataMinCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataMinCardinality -> DataMinCardinality -> Ordering # (<) :: DataMinCardinality -> DataMinCardinality -> Bool # (<=) :: DataMinCardinality -> DataMinCardinality -> Bool # (>) :: DataMinCardinality -> DataMinCardinality -> Bool # (>=) :: DataMinCardinality -> DataMinCardinality -> Bool # max :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality # min :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality # |
data DataMaxCardinality Source #
Instances
Read DataMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataMaxCardinality -> ShowS # show :: DataMaxCardinality -> String # showList :: [DataMaxCardinality] -> ShowS # | |
Eq DataMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataMaxCardinality -> DataMaxCardinality -> Bool # (/=) :: DataMaxCardinality -> DataMaxCardinality -> Bool # | |
Ord DataMaxCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataMaxCardinality -> DataMaxCardinality -> Ordering # (<) :: DataMaxCardinality -> DataMaxCardinality -> Bool # (<=) :: DataMaxCardinality -> DataMaxCardinality -> Bool # (>) :: DataMaxCardinality -> DataMaxCardinality -> Bool # (>=) :: DataMaxCardinality -> DataMaxCardinality -> Bool # max :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality # min :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality # |
data DataExactCardinality Source #
Instances
Read DataExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataExactCardinality -> ShowS # show :: DataExactCardinality -> String # showList :: [DataExactCardinality] -> ShowS # | |
Eq DataExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataExactCardinality -> DataExactCardinality -> Bool # (/=) :: DataExactCardinality -> DataExactCardinality -> Bool # | |
Ord DataExactCardinality Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataExactCardinality -> DataExactCardinality -> Ordering # (<) :: DataExactCardinality -> DataExactCardinality -> Bool # (<=) :: DataExactCardinality -> DataExactCardinality -> Bool # (>) :: DataExactCardinality -> DataExactCardinality -> Bool # (>=) :: DataExactCardinality -> DataExactCardinality -> Bool # max :: DataExactCardinality -> DataExactCardinality -> DataExactCardinality # min :: DataExactCardinality -> DataExactCardinality -> DataExactCardinality # |
data ClassAxiom Source #
ClassAxiomDisjointClasses DisjointClasses | |
ClassAxiomDisjointUnion DisjointUnion | |
ClassAxiomEquivalentClasses EquivalentClasses | |
ClassAxiomSubClassOf SubClassOf |
Instances
Read ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ClassAxiom # readList :: ReadS [ClassAxiom] # readPrec :: ReadPrec ClassAxiom # readListPrec :: ReadPrec [ClassAxiom] # | |
Show ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ClassAxiom -> ShowS # show :: ClassAxiom -> String # showList :: [ClassAxiom] -> ShowS # | |
Eq ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ClassAxiom -> ClassAxiom -> Bool # (/=) :: ClassAxiom -> ClassAxiom -> Bool # | |
Ord ClassAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS SubClassOf # readList :: ReadS [SubClassOf] # readPrec :: ReadPrec SubClassOf # readListPrec :: ReadPrec [SubClassOf] # | |
Show SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> SubClassOf -> ShowS # show :: SubClassOf -> String # showList :: [SubClassOf] -> ShowS # | |
Eq SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: SubClassOf -> SubClassOf -> Bool # (/=) :: SubClassOf -> SubClassOf -> Bool # | |
Ord SubClassOf Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read EquivalentClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show EquivalentClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> EquivalentClasses -> ShowS # show :: EquivalentClasses -> String # showList :: [EquivalentClasses] -> ShowS # | |
Eq EquivalentClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: EquivalentClasses -> EquivalentClasses -> Bool # (/=) :: EquivalentClasses -> EquivalentClasses -> Bool # | |
Ord EquivalentClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: EquivalentClasses -> EquivalentClasses -> Ordering # (<) :: EquivalentClasses -> EquivalentClasses -> Bool # (<=) :: EquivalentClasses -> EquivalentClasses -> Bool # (>) :: EquivalentClasses -> EquivalentClasses -> Bool # (>=) :: EquivalentClasses -> EquivalentClasses -> Bool # max :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses # min :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses # |
data DisjointClasses Source #
Instances
Read DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DisjointClasses -> ShowS # show :: DisjointClasses -> String # showList :: [DisjointClasses] -> ShowS # | |
Eq DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DisjointClasses -> DisjointClasses -> Bool # (/=) :: DisjointClasses -> DisjointClasses -> Bool # | |
Ord DisjointClasses Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS DisjointUnion # readList :: ReadS [DisjointUnion] # | |
Show DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DisjointUnion -> ShowS # show :: DisjointUnion -> String # showList :: [DisjointUnion] -> ShowS # | |
Eq DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DisjointUnion -> DisjointUnion -> Bool # (/=) :: DisjointUnion -> DisjointUnion -> Bool # | |
Ord DisjointUnion Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read ObjectPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectPropertyAxiom -> ShowS # show :: ObjectPropertyAxiom -> String # showList :: [ObjectPropertyAxiom] -> ShowS # | |
Eq ObjectPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # (/=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # | |
Ord ObjectPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering # (<) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # (<=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # (>) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # (>=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool # max :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom # min :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom # |
data SubObjectPropertyOf Source #
Instances
Read SubObjectPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show SubObjectPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> SubObjectPropertyOf -> ShowS # show :: SubObjectPropertyOf -> String # showList :: [SubObjectPropertyOf] -> ShowS # | |
Eq SubObjectPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # (/=) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # | |
Ord SubObjectPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: SubObjectPropertyOf -> SubObjectPropertyOf -> Ordering # (<) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # (<=) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # (>) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # (>=) :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool # max :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf # min :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf # |
data EquivalentObjectProperties Source #
Instances
data DisjointObjectProperties Source #
Instances
data ObjectPropertyDomain Source #
Instances
Read ObjectPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectPropertyDomain -> ShowS # show :: ObjectPropertyDomain -> String # showList :: [ObjectPropertyDomain] -> ShowS # | |
Eq ObjectPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # (/=) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # | |
Ord ObjectPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectPropertyDomain -> ObjectPropertyDomain -> Ordering # (<) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # (<=) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # (>) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # (>=) :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool # max :: ObjectPropertyDomain -> ObjectPropertyDomain -> ObjectPropertyDomain # min :: ObjectPropertyDomain -> ObjectPropertyDomain -> ObjectPropertyDomain # |
data ObjectPropertyRange Source #
Instances
Read ObjectPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show ObjectPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ObjectPropertyRange -> ShowS # show :: ObjectPropertyRange -> String # showList :: [ObjectPropertyRange] -> ShowS # | |
Eq ObjectPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # (/=) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # | |
Ord ObjectPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: ObjectPropertyRange -> ObjectPropertyRange -> Ordering # (<) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # (<=) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # (>) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # (>=) :: ObjectPropertyRange -> ObjectPropertyRange -> Bool # max :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange # min :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange # |
data InverseObjectProperties Source #
Instances
data FunctionalObjectProperty Source #
Instances
data InverseFunctionalObjectProperty Source #
Instances
data ReflexiveObjectProperty Source #
Instances
data IrreflexiveObjectProperty Source #
Instances
data SymmetricObjectProperty Source #
Instances
data AsymmetricObjectProperty Source #
Instances
data TransitiveObjectProperty Source #
Instances
data DataPropertyAxiom Source #
Instances
Read DataPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataPropertyAxiom -> ShowS # show :: DataPropertyAxiom -> String # showList :: [DataPropertyAxiom] -> ShowS # | |
Eq DataPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # (/=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # | |
Ord DataPropertyAxiom Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataPropertyAxiom -> DataPropertyAxiom -> Ordering # (<) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # (<=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # (>) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # (>=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool # max :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom # min :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom # |
data SubDataPropertyOf Source #
Instances
Read SubDataPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show SubDataPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> SubDataPropertyOf -> ShowS # show :: SubDataPropertyOf -> String # showList :: [SubDataPropertyOf] -> ShowS # | |
Eq SubDataPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # (/=) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # | |
Ord SubDataPropertyOf Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: SubDataPropertyOf -> SubDataPropertyOf -> Ordering # (<) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # (<=) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # (>) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # (>=) :: SubDataPropertyOf -> SubDataPropertyOf -> Bool # max :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf # min :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf # |
data EquivalentDataProperties Source #
Instances
data DisjointDataProperties Source #
Instances
Read DisjointDataProperties Source # | |
Show DisjointDataProperties Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DisjointDataProperties -> ShowS # show :: DisjointDataProperties -> String # showList :: [DisjointDataProperties] -> ShowS # | |
Eq DisjointDataProperties Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord DisjointDataProperties Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DisjointDataProperties -> DisjointDataProperties -> Ordering # (<) :: DisjointDataProperties -> DisjointDataProperties -> Bool # (<=) :: DisjointDataProperties -> DisjointDataProperties -> Bool # (>) :: DisjointDataProperties -> DisjointDataProperties -> Bool # (>=) :: DisjointDataProperties -> DisjointDataProperties -> Bool # max :: DisjointDataProperties -> DisjointDataProperties -> DisjointDataProperties # min :: DisjointDataProperties -> DisjointDataProperties -> DisjointDataProperties # |
data DataPropertyDomain Source #
Instances
Read DataPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataPropertyDomain -> ShowS # show :: DataPropertyDomain -> String # showList :: [DataPropertyDomain] -> ShowS # | |
Eq DataPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataPropertyDomain -> DataPropertyDomain -> Bool # (/=) :: DataPropertyDomain -> DataPropertyDomain -> Bool # | |
Ord DataPropertyDomain Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataPropertyDomain -> DataPropertyDomain -> Ordering # (<) :: DataPropertyDomain -> DataPropertyDomain -> Bool # (<=) :: DataPropertyDomain -> DataPropertyDomain -> Bool # (>) :: DataPropertyDomain -> DataPropertyDomain -> Bool # (>=) :: DataPropertyDomain -> DataPropertyDomain -> Bool # max :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain # min :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain # |
data DataPropertyRange Source #
Instances
Read DataPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DataPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DataPropertyRange -> ShowS # show :: DataPropertyRange -> String # showList :: [DataPropertyRange] -> ShowS # | |
Eq DataPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DataPropertyRange -> DataPropertyRange -> Bool # (/=) :: DataPropertyRange -> DataPropertyRange -> Bool # | |
Ord DataPropertyRange Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DataPropertyRange -> DataPropertyRange -> Ordering # (<) :: DataPropertyRange -> DataPropertyRange -> Bool # (<=) :: DataPropertyRange -> DataPropertyRange -> Bool # (>) :: DataPropertyRange -> DataPropertyRange -> Bool # (>=) :: DataPropertyRange -> DataPropertyRange -> Bool # max :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange # min :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange # |
data FunctionalDataProperty Source #
Instances
Read FunctionalDataProperty Source # | |
Show FunctionalDataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> FunctionalDataProperty -> ShowS # show :: FunctionalDataProperty -> String # showList :: [FunctionalDataProperty] -> ShowS # | |
Eq FunctionalDataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Ord FunctionalDataProperty Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: FunctionalDataProperty -> FunctionalDataProperty -> Ordering # (<) :: FunctionalDataProperty -> FunctionalDataProperty -> Bool # (<=) :: FunctionalDataProperty -> FunctionalDataProperty -> Bool # (>) :: FunctionalDataProperty -> FunctionalDataProperty -> Bool # (>=) :: FunctionalDataProperty -> FunctionalDataProperty -> Bool # max :: FunctionalDataProperty -> FunctionalDataProperty -> FunctionalDataProperty # min :: FunctionalDataProperty -> FunctionalDataProperty -> FunctionalDataProperty # |
data DatatypeDefinition Source #
Instances
Read DatatypeDefinition Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DatatypeDefinition Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DatatypeDefinition -> ShowS # show :: DatatypeDefinition -> String # showList :: [DatatypeDefinition] -> ShowS # | |
Eq DatatypeDefinition Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DatatypeDefinition -> DatatypeDefinition -> Bool # (/=) :: DatatypeDefinition -> DatatypeDefinition -> Bool # | |
Ord DatatypeDefinition Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DatatypeDefinition -> DatatypeDefinition -> Ordering # (<) :: DatatypeDefinition -> DatatypeDefinition -> Bool # (<=) :: DatatypeDefinition -> DatatypeDefinition -> Bool # (>) :: DatatypeDefinition -> DatatypeDefinition -> Bool # (>=) :: DatatypeDefinition -> DatatypeDefinition -> Bool # max :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition # min :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition # |
_Assertion :: Name Source #
data SameIndividual Source #
Instances
Read SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS SameIndividual # readList :: ReadS [SameIndividual] # | |
Show SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> SameIndividual -> ShowS # show :: SameIndividual -> String # showList :: [SameIndividual] -> ShowS # | |
Eq SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: SameIndividual -> SameIndividual -> Bool # (/=) :: SameIndividual -> SameIndividual -> Bool # | |
Ord SameIndividual Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
Read DifferentIndividuals Source # | |
Defined in Hydra.Ext.Owl.Syntax | |
Show DifferentIndividuals Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> DifferentIndividuals -> ShowS # show :: DifferentIndividuals -> String # showList :: [DifferentIndividuals] -> ShowS # | |
Eq DifferentIndividuals Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: DifferentIndividuals -> DifferentIndividuals -> Bool # (/=) :: DifferentIndividuals -> DifferentIndividuals -> Bool # | |
Ord DifferentIndividuals Source # | |
Defined in Hydra.Ext.Owl.Syntax compare :: DifferentIndividuals -> DifferentIndividuals -> Ordering # (<) :: DifferentIndividuals -> DifferentIndividuals -> Bool # (<=) :: DifferentIndividuals -> DifferentIndividuals -> Bool # (>) :: DifferentIndividuals -> DifferentIndividuals -> Bool # (>=) :: DifferentIndividuals -> DifferentIndividuals -> Bool # max :: DifferentIndividuals -> DifferentIndividuals -> DifferentIndividuals # min :: DifferentIndividuals -> DifferentIndividuals -> DifferentIndividuals # |
data ClassAssertion Source #
Instances
Read ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax readsPrec :: Int -> ReadS ClassAssertion # readList :: ReadS [ClassAssertion] # | |
Show ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax showsPrec :: Int -> ClassAssertion -> ShowS # show :: ClassAssertion -> String # showList :: [ClassAssertion] -> ShowS # | |
Eq ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax (==) :: ClassAssertion -> ClassAssertion -> Bool # (/=) :: ClassAssertion -> ClassAssertion -> Bool # | |
Ord ClassAssertion Source # | |
Defined in Hydra.Ext.Owl.Syntax 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 #
Instances
data NegativeObjectPropertyAssertion Source #
Instances
data DataPropertyAssertion Source #
Instances
data NegativeDataPropertyAssertion Source #