-- | An OWL 2 syntax model. See https://www.w3.org/TR/owl2-syntax

module Hydra.Langs.Owl.Syntax where

import qualified Hydra.Core as Core
import qualified Hydra.Langs.Rdf.Syntax as Syntax
import qualified Hydra.Langs.Xml.Schema as Schema
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S

data Ontology = 
  Ontology {
    Ontology -> [Ontology]
ontologyDirectImports :: [Ontology],
    Ontology -> [Annotation]
ontologyAnnotations :: [Annotation],
    Ontology -> [Axiom]
ontologyAxioms :: [Axiom]}
  deriving (Ontology -> Ontology -> Bool
(Ontology -> Ontology -> Bool)
-> (Ontology -> Ontology -> Bool) -> Eq Ontology
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ontology -> Ontology -> Bool
== :: Ontology -> Ontology -> Bool
$c/= :: Ontology -> Ontology -> Bool
/= :: Ontology -> Ontology -> Bool
Eq, Eq Ontology
Eq Ontology =>
(Ontology -> Ontology -> Ordering)
-> (Ontology -> Ontology -> Bool)
-> (Ontology -> Ontology -> Bool)
-> (Ontology -> Ontology -> Bool)
-> (Ontology -> Ontology -> Bool)
-> (Ontology -> Ontology -> Ontology)
-> (Ontology -> Ontology -> Ontology)
-> Ord Ontology
Ontology -> Ontology -> Bool
Ontology -> Ontology -> Ordering
Ontology -> Ontology -> Ontology
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Ontology -> Ontology -> Ordering
compare :: Ontology -> Ontology -> Ordering
$c< :: Ontology -> Ontology -> Bool
< :: Ontology -> Ontology -> Bool
$c<= :: Ontology -> Ontology -> Bool
<= :: Ontology -> Ontology -> Bool
$c> :: Ontology -> Ontology -> Bool
> :: Ontology -> Ontology -> Bool
$c>= :: Ontology -> Ontology -> Bool
>= :: Ontology -> Ontology -> Bool
$cmax :: Ontology -> Ontology -> Ontology
max :: Ontology -> Ontology -> Ontology
$cmin :: Ontology -> Ontology -> Ontology
min :: Ontology -> Ontology -> Ontology
Ord, ReadPrec [Ontology]
ReadPrec Ontology
Int -> ReadS Ontology
ReadS [Ontology]
(Int -> ReadS Ontology)
-> ReadS [Ontology]
-> ReadPrec Ontology
-> ReadPrec [Ontology]
-> Read Ontology
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Ontology
readsPrec :: Int -> ReadS Ontology
$creadList :: ReadS [Ontology]
readList :: ReadS [Ontology]
$creadPrec :: ReadPrec Ontology
readPrec :: ReadPrec Ontology
$creadListPrec :: ReadPrec [Ontology]
readListPrec :: ReadPrec [Ontology]
Read, Int -> Ontology -> ShowS
[Ontology] -> ShowS
Ontology -> String
(Int -> Ontology -> ShowS)
-> (Ontology -> String) -> ([Ontology] -> ShowS) -> Show Ontology
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ontology -> ShowS
showsPrec :: Int -> Ontology -> ShowS
$cshow :: Ontology -> String
show :: Ontology -> String
$cshowList :: [Ontology] -> ShowS
showList :: [Ontology] -> ShowS
Show)

_Ontology :: Name
_Ontology = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Ontology")

_Ontology_directImports :: Name
_Ontology_directImports = (String -> Name
Core.Name String
"directImports")

_Ontology_annotations :: Name
_Ontology_annotations = (String -> Name
Core.Name String
"annotations")

_Ontology_axioms :: Name
_Ontology_axioms = (String -> Name
Core.Name String
"axioms")

data Declaration = 
  Declaration {
    Declaration -> [Annotation]
declarationAnnotations :: [Annotation],
    Declaration -> Entity
declarationEntity :: Entity}
  deriving (Declaration -> Declaration -> Bool
(Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool) -> Eq Declaration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Declaration -> Declaration -> Bool
== :: Declaration -> Declaration -> Bool
$c/= :: Declaration -> Declaration -> Bool
/= :: Declaration -> Declaration -> Bool
Eq, Eq Declaration
Eq Declaration =>
(Declaration -> Declaration -> Ordering)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Bool)
-> (Declaration -> Declaration -> Declaration)
-> (Declaration -> Declaration -> Declaration)
-> Ord Declaration
Declaration -> Declaration -> Bool
Declaration -> Declaration -> Ordering
Declaration -> Declaration -> Declaration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Declaration -> Declaration -> Ordering
compare :: Declaration -> Declaration -> Ordering
$c< :: Declaration -> Declaration -> Bool
< :: Declaration -> Declaration -> Bool
$c<= :: Declaration -> Declaration -> Bool
<= :: Declaration -> Declaration -> Bool
$c> :: Declaration -> Declaration -> Bool
> :: Declaration -> Declaration -> Bool
$c>= :: Declaration -> Declaration -> Bool
>= :: Declaration -> Declaration -> Bool
$cmax :: Declaration -> Declaration -> Declaration
max :: Declaration -> Declaration -> Declaration
$cmin :: Declaration -> Declaration -> Declaration
min :: Declaration -> Declaration -> Declaration
Ord, ReadPrec [Declaration]
ReadPrec Declaration
Int -> ReadS Declaration
ReadS [Declaration]
(Int -> ReadS Declaration)
-> ReadS [Declaration]
-> ReadPrec Declaration
-> ReadPrec [Declaration]
-> Read Declaration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Declaration
readsPrec :: Int -> ReadS Declaration
$creadList :: ReadS [Declaration]
readList :: ReadS [Declaration]
$creadPrec :: ReadPrec Declaration
readPrec :: ReadPrec Declaration
$creadListPrec :: ReadPrec [Declaration]
readListPrec :: ReadPrec [Declaration]
Read, Int -> Declaration -> ShowS
[Declaration] -> ShowS
Declaration -> String
(Int -> Declaration -> ShowS)
-> (Declaration -> String)
-> ([Declaration] -> ShowS)
-> Show Declaration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Declaration -> ShowS
showsPrec :: Int -> Declaration -> ShowS
$cshow :: Declaration -> String
show :: Declaration -> String
$cshowList :: [Declaration] -> ShowS
showList :: [Declaration] -> ShowS
Show)

_Declaration :: Name
_Declaration = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Declaration")

_Declaration_annotations :: Name
_Declaration_annotations = (String -> Name
Core.Name String
"annotations")

_Declaration_entity :: Name
_Declaration_entity = (String -> Name
Core.Name String
"entity")

data Entity = 
  EntityAnnotationProperty AnnotationProperty |
  EntityClass Class |
  EntityDataProperty DataProperty |
  EntityDatatype Datatype |
  EntityNamedIndividual NamedIndividual |
  EntityObjectProperty ObjectProperty
  deriving (Entity -> Entity -> Bool
(Entity -> Entity -> Bool)
-> (Entity -> Entity -> Bool) -> Eq Entity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Entity -> Entity -> Bool
== :: Entity -> Entity -> Bool
$c/= :: Entity -> Entity -> Bool
/= :: Entity -> Entity -> Bool
Eq, Eq Entity
Eq Entity =>
(Entity -> Entity -> Ordering)
-> (Entity -> Entity -> Bool)
-> (Entity -> Entity -> Bool)
-> (Entity -> Entity -> Bool)
-> (Entity -> Entity -> Bool)
-> (Entity -> Entity -> Entity)
-> (Entity -> Entity -> Entity)
-> Ord Entity
Entity -> Entity -> Bool
Entity -> Entity -> Ordering
Entity -> Entity -> Entity
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Entity -> Entity -> Ordering
compare :: Entity -> Entity -> Ordering
$c< :: Entity -> Entity -> Bool
< :: Entity -> Entity -> Bool
$c<= :: Entity -> Entity -> Bool
<= :: Entity -> Entity -> Bool
$c> :: Entity -> Entity -> Bool
> :: Entity -> Entity -> Bool
$c>= :: Entity -> Entity -> Bool
>= :: Entity -> Entity -> Bool
$cmax :: Entity -> Entity -> Entity
max :: Entity -> Entity -> Entity
$cmin :: Entity -> Entity -> Entity
min :: Entity -> Entity -> Entity
Ord, ReadPrec [Entity]
ReadPrec Entity
Int -> ReadS Entity
ReadS [Entity]
(Int -> ReadS Entity)
-> ReadS [Entity]
-> ReadPrec Entity
-> ReadPrec [Entity]
-> Read Entity
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Entity
readsPrec :: Int -> ReadS Entity
$creadList :: ReadS [Entity]
readList :: ReadS [Entity]
$creadPrec :: ReadPrec Entity
readPrec :: ReadPrec Entity
$creadListPrec :: ReadPrec [Entity]
readListPrec :: ReadPrec [Entity]
Read, Int -> Entity -> ShowS
[Entity] -> ShowS
Entity -> String
(Int -> Entity -> ShowS)
-> (Entity -> String) -> ([Entity] -> ShowS) -> Show Entity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Entity -> ShowS
showsPrec :: Int -> Entity -> ShowS
$cshow :: Entity -> String
show :: Entity -> String
$cshowList :: [Entity] -> ShowS
showList :: [Entity] -> ShowS
Show)

_Entity :: Name
_Entity = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Entity")

_Entity_annotationProperty :: Name
_Entity_annotationProperty = (String -> Name
Core.Name String
"annotationProperty")

_Entity_class :: Name
_Entity_class = (String -> Name
Core.Name String
"class")

_Entity_dataProperty :: Name
_Entity_dataProperty = (String -> Name
Core.Name String
"dataProperty")

_Entity_datatype :: Name
_Entity_datatype = (String -> Name
Core.Name String
"datatype")

_Entity_namedIndividual :: Name
_Entity_namedIndividual = (String -> Name
Core.Name String
"namedIndividual")

_Entity_objectProperty :: Name
_Entity_objectProperty = (String -> Name
Core.Name String
"objectProperty")

data AnnotationSubject = 
  AnnotationSubjectIri Syntax.Iri |
  AnnotationSubjectAnonymousIndividual AnonymousIndividual
  deriving (AnnotationSubject -> AnnotationSubject -> Bool
(AnnotationSubject -> AnnotationSubject -> Bool)
-> (AnnotationSubject -> AnnotationSubject -> Bool)
-> Eq AnnotationSubject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationSubject -> AnnotationSubject -> Bool
== :: AnnotationSubject -> AnnotationSubject -> Bool
$c/= :: AnnotationSubject -> AnnotationSubject -> Bool
/= :: AnnotationSubject -> AnnotationSubject -> Bool
Eq, Eq AnnotationSubject
Eq AnnotationSubject =>
(AnnotationSubject -> AnnotationSubject -> Ordering)
-> (AnnotationSubject -> AnnotationSubject -> Bool)
-> (AnnotationSubject -> AnnotationSubject -> Bool)
-> (AnnotationSubject -> AnnotationSubject -> Bool)
-> (AnnotationSubject -> AnnotationSubject -> Bool)
-> (AnnotationSubject -> AnnotationSubject -> AnnotationSubject)
-> (AnnotationSubject -> AnnotationSubject -> AnnotationSubject)
-> Ord AnnotationSubject
AnnotationSubject -> AnnotationSubject -> Bool
AnnotationSubject -> AnnotationSubject -> Ordering
AnnotationSubject -> AnnotationSubject -> AnnotationSubject
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationSubject -> AnnotationSubject -> Ordering
compare :: AnnotationSubject -> AnnotationSubject -> Ordering
$c< :: AnnotationSubject -> AnnotationSubject -> Bool
< :: AnnotationSubject -> AnnotationSubject -> Bool
$c<= :: AnnotationSubject -> AnnotationSubject -> Bool
<= :: AnnotationSubject -> AnnotationSubject -> Bool
$c> :: AnnotationSubject -> AnnotationSubject -> Bool
> :: AnnotationSubject -> AnnotationSubject -> Bool
$c>= :: AnnotationSubject -> AnnotationSubject -> Bool
>= :: AnnotationSubject -> AnnotationSubject -> Bool
$cmax :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject
max :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject
$cmin :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject
min :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject
Ord, ReadPrec [AnnotationSubject]
ReadPrec AnnotationSubject
Int -> ReadS AnnotationSubject
ReadS [AnnotationSubject]
(Int -> ReadS AnnotationSubject)
-> ReadS [AnnotationSubject]
-> ReadPrec AnnotationSubject
-> ReadPrec [AnnotationSubject]
-> Read AnnotationSubject
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationSubject
readsPrec :: Int -> ReadS AnnotationSubject
$creadList :: ReadS [AnnotationSubject]
readList :: ReadS [AnnotationSubject]
$creadPrec :: ReadPrec AnnotationSubject
readPrec :: ReadPrec AnnotationSubject
$creadListPrec :: ReadPrec [AnnotationSubject]
readListPrec :: ReadPrec [AnnotationSubject]
Read, Int -> AnnotationSubject -> ShowS
[AnnotationSubject] -> ShowS
AnnotationSubject -> String
(Int -> AnnotationSubject -> ShowS)
-> (AnnotationSubject -> String)
-> ([AnnotationSubject] -> ShowS)
-> Show AnnotationSubject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationSubject -> ShowS
showsPrec :: Int -> AnnotationSubject -> ShowS
$cshow :: AnnotationSubject -> String
show :: AnnotationSubject -> String
$cshowList :: [AnnotationSubject] -> ShowS
showList :: [AnnotationSubject] -> ShowS
Show)

_AnnotationSubject :: Name
_AnnotationSubject = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationSubject")

_AnnotationSubject_iri :: Name
_AnnotationSubject_iri = (String -> Name
Core.Name String
"iri")

_AnnotationSubject_anonymousIndividual :: Name
_AnnotationSubject_anonymousIndividual = (String -> Name
Core.Name String
"anonymousIndividual")

data AnnotationValue = 
  AnnotationValueAnonymousIndividual AnonymousIndividual |
  AnnotationValueIri Syntax.Iri |
  AnnotationValueLiteral Syntax.Literal
  deriving (AnnotationValue -> AnnotationValue -> Bool
(AnnotationValue -> AnnotationValue -> Bool)
-> (AnnotationValue -> AnnotationValue -> Bool)
-> Eq AnnotationValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationValue -> AnnotationValue -> Bool
== :: AnnotationValue -> AnnotationValue -> Bool
$c/= :: AnnotationValue -> AnnotationValue -> Bool
/= :: AnnotationValue -> AnnotationValue -> Bool
Eq, Eq AnnotationValue
Eq AnnotationValue =>
(AnnotationValue -> AnnotationValue -> Ordering)
-> (AnnotationValue -> AnnotationValue -> Bool)
-> (AnnotationValue -> AnnotationValue -> Bool)
-> (AnnotationValue -> AnnotationValue -> Bool)
-> (AnnotationValue -> AnnotationValue -> Bool)
-> (AnnotationValue -> AnnotationValue -> AnnotationValue)
-> (AnnotationValue -> AnnotationValue -> AnnotationValue)
-> Ord AnnotationValue
AnnotationValue -> AnnotationValue -> Bool
AnnotationValue -> AnnotationValue -> Ordering
AnnotationValue -> AnnotationValue -> AnnotationValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationValue -> AnnotationValue -> Ordering
compare :: AnnotationValue -> AnnotationValue -> Ordering
$c< :: AnnotationValue -> AnnotationValue -> Bool
< :: AnnotationValue -> AnnotationValue -> Bool
$c<= :: AnnotationValue -> AnnotationValue -> Bool
<= :: AnnotationValue -> AnnotationValue -> Bool
$c> :: AnnotationValue -> AnnotationValue -> Bool
> :: AnnotationValue -> AnnotationValue -> Bool
$c>= :: AnnotationValue -> AnnotationValue -> Bool
>= :: AnnotationValue -> AnnotationValue -> Bool
$cmax :: AnnotationValue -> AnnotationValue -> AnnotationValue
max :: AnnotationValue -> AnnotationValue -> AnnotationValue
$cmin :: AnnotationValue -> AnnotationValue -> AnnotationValue
min :: AnnotationValue -> AnnotationValue -> AnnotationValue
Ord, ReadPrec [AnnotationValue]
ReadPrec AnnotationValue
Int -> ReadS AnnotationValue
ReadS [AnnotationValue]
(Int -> ReadS AnnotationValue)
-> ReadS [AnnotationValue]
-> ReadPrec AnnotationValue
-> ReadPrec [AnnotationValue]
-> Read AnnotationValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationValue
readsPrec :: Int -> ReadS AnnotationValue
$creadList :: ReadS [AnnotationValue]
readList :: ReadS [AnnotationValue]
$creadPrec :: ReadPrec AnnotationValue
readPrec :: ReadPrec AnnotationValue
$creadListPrec :: ReadPrec [AnnotationValue]
readListPrec :: ReadPrec [AnnotationValue]
Read, Int -> AnnotationValue -> ShowS
[AnnotationValue] -> ShowS
AnnotationValue -> String
(Int -> AnnotationValue -> ShowS)
-> (AnnotationValue -> String)
-> ([AnnotationValue] -> ShowS)
-> Show AnnotationValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationValue -> ShowS
showsPrec :: Int -> AnnotationValue -> ShowS
$cshow :: AnnotationValue -> String
show :: AnnotationValue -> String
$cshowList :: [AnnotationValue] -> ShowS
showList :: [AnnotationValue] -> ShowS
Show)

_AnnotationValue :: Name
_AnnotationValue = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationValue")

_AnnotationValue_anonymousIndividual :: Name
_AnnotationValue_anonymousIndividual = (String -> Name
Core.Name String
"anonymousIndividual")

_AnnotationValue_iri :: Name
_AnnotationValue_iri = (String -> Name
Core.Name String
"iri")

_AnnotationValue_literal :: Name
_AnnotationValue_literal = (String -> Name
Core.Name String
"literal")

data Annotation = 
  Annotation {
    Annotation -> [Annotation]
annotationAnnotations :: [Annotation],
    Annotation -> AnnotationProperty
annotationProperty :: AnnotationProperty,
    Annotation -> AnnotationValue
annotationValue :: AnnotationValue}
  deriving (Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
/= :: Annotation -> Annotation -> Bool
Eq, Eq Annotation
Eq Annotation =>
(Annotation -> Annotation -> Ordering)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Annotation)
-> (Annotation -> Annotation -> Annotation)
-> Ord Annotation
Annotation -> Annotation -> Bool
Annotation -> Annotation -> Ordering
Annotation -> Annotation -> Annotation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Annotation -> Annotation -> Ordering
compare :: Annotation -> Annotation -> Ordering
$c< :: Annotation -> Annotation -> Bool
< :: Annotation -> Annotation -> Bool
$c<= :: Annotation -> Annotation -> Bool
<= :: Annotation -> Annotation -> Bool
$c> :: Annotation -> Annotation -> Bool
> :: Annotation -> Annotation -> Bool
$c>= :: Annotation -> Annotation -> Bool
>= :: Annotation -> Annotation -> Bool
$cmax :: Annotation -> Annotation -> Annotation
max :: Annotation -> Annotation -> Annotation
$cmin :: Annotation -> Annotation -> Annotation
min :: Annotation -> Annotation -> Annotation
Ord, ReadPrec [Annotation]
ReadPrec Annotation
Int -> ReadS Annotation
ReadS [Annotation]
(Int -> ReadS Annotation)
-> ReadS [Annotation]
-> ReadPrec Annotation
-> ReadPrec [Annotation]
-> Read Annotation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Annotation
readsPrec :: Int -> ReadS Annotation
$creadList :: ReadS [Annotation]
readList :: ReadS [Annotation]
$creadPrec :: ReadPrec Annotation
readPrec :: ReadPrec Annotation
$creadListPrec :: ReadPrec [Annotation]
readListPrec :: ReadPrec [Annotation]
Read, Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Annotation -> ShowS
showsPrec :: Int -> Annotation -> ShowS
$cshow :: Annotation -> String
show :: Annotation -> String
$cshowList :: [Annotation] -> ShowS
showList :: [Annotation] -> ShowS
Show)

_Annotation :: Name
_Annotation = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Annotation")

_Annotation_annotations :: Name
_Annotation_annotations = (String -> Name
Core.Name String
"annotations")

_Annotation_property :: Name
_Annotation_property = (String -> Name
Core.Name String
"property")

_Annotation_value :: Name
_Annotation_value = (String -> Name
Core.Name String
"value")

data AnnotationAxiom = 
  AnnotationAxiomAnnotationAssertion AnnotationAssertion |
  AnnotationAxiomAnnotationPropertyDomain AnnotationPropertyDomain |
  AnnotationAxiomAnnotationPropertyRange AnnotationPropertyRange |
  AnnotationAxiomSubAnnotationPropertyOf SubAnnotationPropertyOf
  deriving (AnnotationAxiom -> AnnotationAxiom -> Bool
(AnnotationAxiom -> AnnotationAxiom -> Bool)
-> (AnnotationAxiom -> AnnotationAxiom -> Bool)
-> Eq AnnotationAxiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationAxiom -> AnnotationAxiom -> Bool
== :: AnnotationAxiom -> AnnotationAxiom -> Bool
$c/= :: AnnotationAxiom -> AnnotationAxiom -> Bool
/= :: AnnotationAxiom -> AnnotationAxiom -> Bool
Eq, Eq AnnotationAxiom
Eq AnnotationAxiom =>
(AnnotationAxiom -> AnnotationAxiom -> Ordering)
-> (AnnotationAxiom -> AnnotationAxiom -> Bool)
-> (AnnotationAxiom -> AnnotationAxiom -> Bool)
-> (AnnotationAxiom -> AnnotationAxiom -> Bool)
-> (AnnotationAxiom -> AnnotationAxiom -> Bool)
-> (AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom)
-> (AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom)
-> Ord AnnotationAxiom
AnnotationAxiom -> AnnotationAxiom -> Bool
AnnotationAxiom -> AnnotationAxiom -> Ordering
AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationAxiom -> AnnotationAxiom -> Ordering
compare :: AnnotationAxiom -> AnnotationAxiom -> Ordering
$c< :: AnnotationAxiom -> AnnotationAxiom -> Bool
< :: AnnotationAxiom -> AnnotationAxiom -> Bool
$c<= :: AnnotationAxiom -> AnnotationAxiom -> Bool
<= :: AnnotationAxiom -> AnnotationAxiom -> Bool
$c> :: AnnotationAxiom -> AnnotationAxiom -> Bool
> :: AnnotationAxiom -> AnnotationAxiom -> Bool
$c>= :: AnnotationAxiom -> AnnotationAxiom -> Bool
>= :: AnnotationAxiom -> AnnotationAxiom -> Bool
$cmax :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom
max :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom
$cmin :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom
min :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom
Ord, ReadPrec [AnnotationAxiom]
ReadPrec AnnotationAxiom
Int -> ReadS AnnotationAxiom
ReadS [AnnotationAxiom]
(Int -> ReadS AnnotationAxiom)
-> ReadS [AnnotationAxiom]
-> ReadPrec AnnotationAxiom
-> ReadPrec [AnnotationAxiom]
-> Read AnnotationAxiom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationAxiom
readsPrec :: Int -> ReadS AnnotationAxiom
$creadList :: ReadS [AnnotationAxiom]
readList :: ReadS [AnnotationAxiom]
$creadPrec :: ReadPrec AnnotationAxiom
readPrec :: ReadPrec AnnotationAxiom
$creadListPrec :: ReadPrec [AnnotationAxiom]
readListPrec :: ReadPrec [AnnotationAxiom]
Read, Int -> AnnotationAxiom -> ShowS
[AnnotationAxiom] -> ShowS
AnnotationAxiom -> String
(Int -> AnnotationAxiom -> ShowS)
-> (AnnotationAxiom -> String)
-> ([AnnotationAxiom] -> ShowS)
-> Show AnnotationAxiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationAxiom -> ShowS
showsPrec :: Int -> AnnotationAxiom -> ShowS
$cshow :: AnnotationAxiom -> String
show :: AnnotationAxiom -> String
$cshowList :: [AnnotationAxiom] -> ShowS
showList :: [AnnotationAxiom] -> ShowS
Show)

_AnnotationAxiom :: Name
_AnnotationAxiom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationAxiom")

_AnnotationAxiom_annotationAssertion :: Name
_AnnotationAxiom_annotationAssertion = (String -> Name
Core.Name String
"annotationAssertion")

_AnnotationAxiom_annotationPropertyDomain :: Name
_AnnotationAxiom_annotationPropertyDomain = (String -> Name
Core.Name String
"annotationPropertyDomain")

_AnnotationAxiom_annotationPropertyRange :: Name
_AnnotationAxiom_annotationPropertyRange = (String -> Name
Core.Name String
"annotationPropertyRange")

_AnnotationAxiom_subAnnotationPropertyOf :: Name
_AnnotationAxiom_subAnnotationPropertyOf = (String -> Name
Core.Name String
"subAnnotationPropertyOf")

data AnnotationAssertion = 
  AnnotationAssertion {
    AnnotationAssertion -> [Annotation]
annotationAssertionAnnotations :: [Annotation],
    AnnotationAssertion -> AnnotationProperty
annotationAssertionProperty :: AnnotationProperty,
    AnnotationAssertion -> AnnotationSubject
annotationAssertionSubject :: AnnotationSubject,
    AnnotationAssertion -> AnnotationValue
annotationAssertionValue :: AnnotationValue}
  deriving (AnnotationAssertion -> AnnotationAssertion -> Bool
(AnnotationAssertion -> AnnotationAssertion -> Bool)
-> (AnnotationAssertion -> AnnotationAssertion -> Bool)
-> Eq AnnotationAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationAssertion -> AnnotationAssertion -> Bool
== :: AnnotationAssertion -> AnnotationAssertion -> Bool
$c/= :: AnnotationAssertion -> AnnotationAssertion -> Bool
/= :: AnnotationAssertion -> AnnotationAssertion -> Bool
Eq, Eq AnnotationAssertion
Eq AnnotationAssertion =>
(AnnotationAssertion -> AnnotationAssertion -> Ordering)
-> (AnnotationAssertion -> AnnotationAssertion -> Bool)
-> (AnnotationAssertion -> AnnotationAssertion -> Bool)
-> (AnnotationAssertion -> AnnotationAssertion -> Bool)
-> (AnnotationAssertion -> AnnotationAssertion -> Bool)
-> (AnnotationAssertion
    -> AnnotationAssertion -> AnnotationAssertion)
-> (AnnotationAssertion
    -> AnnotationAssertion -> AnnotationAssertion)
-> Ord AnnotationAssertion
AnnotationAssertion -> AnnotationAssertion -> Bool
AnnotationAssertion -> AnnotationAssertion -> Ordering
AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationAssertion -> AnnotationAssertion -> Ordering
compare :: AnnotationAssertion -> AnnotationAssertion -> Ordering
$c< :: AnnotationAssertion -> AnnotationAssertion -> Bool
< :: AnnotationAssertion -> AnnotationAssertion -> Bool
$c<= :: AnnotationAssertion -> AnnotationAssertion -> Bool
<= :: AnnotationAssertion -> AnnotationAssertion -> Bool
$c> :: AnnotationAssertion -> AnnotationAssertion -> Bool
> :: AnnotationAssertion -> AnnotationAssertion -> Bool
$c>= :: AnnotationAssertion -> AnnotationAssertion -> Bool
>= :: AnnotationAssertion -> AnnotationAssertion -> Bool
$cmax :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion
max :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion
$cmin :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion
min :: AnnotationAssertion -> AnnotationAssertion -> AnnotationAssertion
Ord, ReadPrec [AnnotationAssertion]
ReadPrec AnnotationAssertion
Int -> ReadS AnnotationAssertion
ReadS [AnnotationAssertion]
(Int -> ReadS AnnotationAssertion)
-> ReadS [AnnotationAssertion]
-> ReadPrec AnnotationAssertion
-> ReadPrec [AnnotationAssertion]
-> Read AnnotationAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationAssertion
readsPrec :: Int -> ReadS AnnotationAssertion
$creadList :: ReadS [AnnotationAssertion]
readList :: ReadS [AnnotationAssertion]
$creadPrec :: ReadPrec AnnotationAssertion
readPrec :: ReadPrec AnnotationAssertion
$creadListPrec :: ReadPrec [AnnotationAssertion]
readListPrec :: ReadPrec [AnnotationAssertion]
Read, Int -> AnnotationAssertion -> ShowS
[AnnotationAssertion] -> ShowS
AnnotationAssertion -> String
(Int -> AnnotationAssertion -> ShowS)
-> (AnnotationAssertion -> String)
-> ([AnnotationAssertion] -> ShowS)
-> Show AnnotationAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationAssertion -> ShowS
showsPrec :: Int -> AnnotationAssertion -> ShowS
$cshow :: AnnotationAssertion -> String
show :: AnnotationAssertion -> String
$cshowList :: [AnnotationAssertion] -> ShowS
showList :: [AnnotationAssertion] -> ShowS
Show)

_AnnotationAssertion :: Name
_AnnotationAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationAssertion")

_AnnotationAssertion_annotations :: Name
_AnnotationAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_AnnotationAssertion_property :: Name
_AnnotationAssertion_property = (String -> Name
Core.Name String
"property")

_AnnotationAssertion_subject :: Name
_AnnotationAssertion_subject = (String -> Name
Core.Name String
"subject")

_AnnotationAssertion_value :: Name
_AnnotationAssertion_value = (String -> Name
Core.Name String
"value")

data SubAnnotationPropertyOf = 
  SubAnnotationPropertyOf {
    SubAnnotationPropertyOf -> [Annotation]
subAnnotationPropertyOfAnnotations :: [Annotation],
    SubAnnotationPropertyOf -> AnnotationProperty
subAnnotationPropertyOfSubProperty :: AnnotationProperty,
    SubAnnotationPropertyOf -> AnnotationProperty
subAnnotationPropertyOfSuperProperty :: AnnotationProperty}
  deriving (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
(SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> Eq SubAnnotationPropertyOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
== :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
$c/= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
/= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
Eq, Eq SubAnnotationPropertyOf
Eq SubAnnotationPropertyOf =>
(SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Ordering)
-> (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> (SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool)
-> (SubAnnotationPropertyOf
    -> SubAnnotationPropertyOf -> SubAnnotationPropertyOf)
-> (SubAnnotationPropertyOf
    -> SubAnnotationPropertyOf -> SubAnnotationPropertyOf)
-> Ord SubAnnotationPropertyOf
SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Ordering
SubAnnotationPropertyOf
-> SubAnnotationPropertyOf -> SubAnnotationPropertyOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Ordering
compare :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Ordering
$c< :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
< :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
$c<= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
<= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
$c> :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
> :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
$c>= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
>= :: SubAnnotationPropertyOf -> SubAnnotationPropertyOf -> Bool
$cmax :: SubAnnotationPropertyOf
-> SubAnnotationPropertyOf -> SubAnnotationPropertyOf
max :: SubAnnotationPropertyOf
-> SubAnnotationPropertyOf -> SubAnnotationPropertyOf
$cmin :: SubAnnotationPropertyOf
-> SubAnnotationPropertyOf -> SubAnnotationPropertyOf
min :: SubAnnotationPropertyOf
-> SubAnnotationPropertyOf -> SubAnnotationPropertyOf
Ord, ReadPrec [SubAnnotationPropertyOf]
ReadPrec SubAnnotationPropertyOf
Int -> ReadS SubAnnotationPropertyOf
ReadS [SubAnnotationPropertyOf]
(Int -> ReadS SubAnnotationPropertyOf)
-> ReadS [SubAnnotationPropertyOf]
-> ReadPrec SubAnnotationPropertyOf
-> ReadPrec [SubAnnotationPropertyOf]
-> Read SubAnnotationPropertyOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SubAnnotationPropertyOf
readsPrec :: Int -> ReadS SubAnnotationPropertyOf
$creadList :: ReadS [SubAnnotationPropertyOf]
readList :: ReadS [SubAnnotationPropertyOf]
$creadPrec :: ReadPrec SubAnnotationPropertyOf
readPrec :: ReadPrec SubAnnotationPropertyOf
$creadListPrec :: ReadPrec [SubAnnotationPropertyOf]
readListPrec :: ReadPrec [SubAnnotationPropertyOf]
Read, Int -> SubAnnotationPropertyOf -> ShowS
[SubAnnotationPropertyOf] -> ShowS
SubAnnotationPropertyOf -> String
(Int -> SubAnnotationPropertyOf -> ShowS)
-> (SubAnnotationPropertyOf -> String)
-> ([SubAnnotationPropertyOf] -> ShowS)
-> Show SubAnnotationPropertyOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubAnnotationPropertyOf -> ShowS
showsPrec :: Int -> SubAnnotationPropertyOf -> ShowS
$cshow :: SubAnnotationPropertyOf -> String
show :: SubAnnotationPropertyOf -> String
$cshowList :: [SubAnnotationPropertyOf] -> ShowS
showList :: [SubAnnotationPropertyOf] -> ShowS
Show)

_SubAnnotationPropertyOf :: Name
_SubAnnotationPropertyOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SubAnnotationPropertyOf")

_SubAnnotationPropertyOf_annotations :: Name
_SubAnnotationPropertyOf_annotations = (String -> Name
Core.Name String
"annotations")

_SubAnnotationPropertyOf_subProperty :: Name
_SubAnnotationPropertyOf_subProperty = (String -> Name
Core.Name String
"subProperty")

_SubAnnotationPropertyOf_superProperty :: Name
_SubAnnotationPropertyOf_superProperty = (String -> Name
Core.Name String
"superProperty")

data AnnotationPropertyDomain = 
  AnnotationPropertyDomain {
    AnnotationPropertyDomain -> [Annotation]
annotationPropertyDomainAnnotations :: [Annotation],
    AnnotationPropertyDomain -> AnnotationProperty
annotationPropertyDomainProperty :: AnnotationProperty,
    AnnotationPropertyDomain -> Iri
annotationPropertyDomainIri :: Syntax.Iri}
  deriving (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
(AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> Eq AnnotationPropertyDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
== :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
$c/= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
/= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
Eq, Eq AnnotationPropertyDomain
Eq AnnotationPropertyDomain =>
(AnnotationPropertyDomain -> AnnotationPropertyDomain -> Ordering)
-> (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> (AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool)
-> (AnnotationPropertyDomain
    -> AnnotationPropertyDomain -> AnnotationPropertyDomain)
-> (AnnotationPropertyDomain
    -> AnnotationPropertyDomain -> AnnotationPropertyDomain)
-> Ord AnnotationPropertyDomain
AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
AnnotationPropertyDomain -> AnnotationPropertyDomain -> Ordering
AnnotationPropertyDomain
-> AnnotationPropertyDomain -> AnnotationPropertyDomain
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Ordering
compare :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Ordering
$c< :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
< :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
$c<= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
<= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
$c> :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
> :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
$c>= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
>= :: AnnotationPropertyDomain -> AnnotationPropertyDomain -> Bool
$cmax :: AnnotationPropertyDomain
-> AnnotationPropertyDomain -> AnnotationPropertyDomain
max :: AnnotationPropertyDomain
-> AnnotationPropertyDomain -> AnnotationPropertyDomain
$cmin :: AnnotationPropertyDomain
-> AnnotationPropertyDomain -> AnnotationPropertyDomain
min :: AnnotationPropertyDomain
-> AnnotationPropertyDomain -> AnnotationPropertyDomain
Ord, ReadPrec [AnnotationPropertyDomain]
ReadPrec AnnotationPropertyDomain
Int -> ReadS AnnotationPropertyDomain
ReadS [AnnotationPropertyDomain]
(Int -> ReadS AnnotationPropertyDomain)
-> ReadS [AnnotationPropertyDomain]
-> ReadPrec AnnotationPropertyDomain
-> ReadPrec [AnnotationPropertyDomain]
-> Read AnnotationPropertyDomain
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationPropertyDomain
readsPrec :: Int -> ReadS AnnotationPropertyDomain
$creadList :: ReadS [AnnotationPropertyDomain]
readList :: ReadS [AnnotationPropertyDomain]
$creadPrec :: ReadPrec AnnotationPropertyDomain
readPrec :: ReadPrec AnnotationPropertyDomain
$creadListPrec :: ReadPrec [AnnotationPropertyDomain]
readListPrec :: ReadPrec [AnnotationPropertyDomain]
Read, Int -> AnnotationPropertyDomain -> ShowS
[AnnotationPropertyDomain] -> ShowS
AnnotationPropertyDomain -> String
(Int -> AnnotationPropertyDomain -> ShowS)
-> (AnnotationPropertyDomain -> String)
-> ([AnnotationPropertyDomain] -> ShowS)
-> Show AnnotationPropertyDomain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationPropertyDomain -> ShowS
showsPrec :: Int -> AnnotationPropertyDomain -> ShowS
$cshow :: AnnotationPropertyDomain -> String
show :: AnnotationPropertyDomain -> String
$cshowList :: [AnnotationPropertyDomain] -> ShowS
showList :: [AnnotationPropertyDomain] -> ShowS
Show)

_AnnotationPropertyDomain :: Name
_AnnotationPropertyDomain = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationPropertyDomain")

_AnnotationPropertyDomain_annotations :: Name
_AnnotationPropertyDomain_annotations = (String -> Name
Core.Name String
"annotations")

_AnnotationPropertyDomain_property :: Name
_AnnotationPropertyDomain_property = (String -> Name
Core.Name String
"property")

_AnnotationPropertyDomain_iri :: Name
_AnnotationPropertyDomain_iri = (String -> Name
Core.Name String
"iri")

data AnnotationPropertyRange = 
  AnnotationPropertyRange {
    AnnotationPropertyRange -> [Annotation]
annotationPropertyRangeAnnotations :: [Annotation],
    AnnotationPropertyRange -> AnnotationProperty
annotationPropertyRangeProperty :: AnnotationProperty,
    AnnotationPropertyRange -> Iri
annotationPropertyRangeIri :: Syntax.Iri}
  deriving (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
(AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> Eq AnnotationPropertyRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
== :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
$c/= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
/= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
Eq, Eq AnnotationPropertyRange
Eq AnnotationPropertyRange =>
(AnnotationPropertyRange -> AnnotationPropertyRange -> Ordering)
-> (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> (AnnotationPropertyRange -> AnnotationPropertyRange -> Bool)
-> (AnnotationPropertyRange
    -> AnnotationPropertyRange -> AnnotationPropertyRange)
-> (AnnotationPropertyRange
    -> AnnotationPropertyRange -> AnnotationPropertyRange)
-> Ord AnnotationPropertyRange
AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
AnnotationPropertyRange -> AnnotationPropertyRange -> Ordering
AnnotationPropertyRange
-> AnnotationPropertyRange -> AnnotationPropertyRange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationPropertyRange -> AnnotationPropertyRange -> Ordering
compare :: AnnotationPropertyRange -> AnnotationPropertyRange -> Ordering
$c< :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
< :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
$c<= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
<= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
$c> :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
> :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
$c>= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
>= :: AnnotationPropertyRange -> AnnotationPropertyRange -> Bool
$cmax :: AnnotationPropertyRange
-> AnnotationPropertyRange -> AnnotationPropertyRange
max :: AnnotationPropertyRange
-> AnnotationPropertyRange -> AnnotationPropertyRange
$cmin :: AnnotationPropertyRange
-> AnnotationPropertyRange -> AnnotationPropertyRange
min :: AnnotationPropertyRange
-> AnnotationPropertyRange -> AnnotationPropertyRange
Ord, ReadPrec [AnnotationPropertyRange]
ReadPrec AnnotationPropertyRange
Int -> ReadS AnnotationPropertyRange
ReadS [AnnotationPropertyRange]
(Int -> ReadS AnnotationPropertyRange)
-> ReadS [AnnotationPropertyRange]
-> ReadPrec AnnotationPropertyRange
-> ReadPrec [AnnotationPropertyRange]
-> Read AnnotationPropertyRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationPropertyRange
readsPrec :: Int -> ReadS AnnotationPropertyRange
$creadList :: ReadS [AnnotationPropertyRange]
readList :: ReadS [AnnotationPropertyRange]
$creadPrec :: ReadPrec AnnotationPropertyRange
readPrec :: ReadPrec AnnotationPropertyRange
$creadListPrec :: ReadPrec [AnnotationPropertyRange]
readListPrec :: ReadPrec [AnnotationPropertyRange]
Read, Int -> AnnotationPropertyRange -> ShowS
[AnnotationPropertyRange] -> ShowS
AnnotationPropertyRange -> String
(Int -> AnnotationPropertyRange -> ShowS)
-> (AnnotationPropertyRange -> String)
-> ([AnnotationPropertyRange] -> ShowS)
-> Show AnnotationPropertyRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationPropertyRange -> ShowS
showsPrec :: Int -> AnnotationPropertyRange -> ShowS
$cshow :: AnnotationPropertyRange -> String
show :: AnnotationPropertyRange -> String
$cshowList :: [AnnotationPropertyRange] -> ShowS
showList :: [AnnotationPropertyRange] -> ShowS
Show)

_AnnotationPropertyRange :: Name
_AnnotationPropertyRange = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationPropertyRange")

_AnnotationPropertyRange_annotations :: Name
_AnnotationPropertyRange_annotations = (String -> Name
Core.Name String
"annotations")

_AnnotationPropertyRange_property :: Name
_AnnotationPropertyRange_property = (String -> Name
Core.Name String
"property")

_AnnotationPropertyRange_iri :: Name
_AnnotationPropertyRange_iri = (String -> Name
Core.Name String
"iri")

-- | See https://www.w3.org/TR/owl2-syntax/#Classes
data Class = 
  Class {}
  deriving (Class -> Class -> Bool
(Class -> Class -> Bool) -> (Class -> Class -> Bool) -> Eq Class
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Class -> Class -> Bool
== :: Class -> Class -> Bool
$c/= :: Class -> Class -> Bool
/= :: Class -> Class -> Bool
Eq, Eq Class
Eq Class =>
(Class -> Class -> Ordering)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Class)
-> (Class -> Class -> Class)
-> Ord Class
Class -> Class -> Bool
Class -> Class -> Ordering
Class -> Class -> Class
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Class -> Class -> Ordering
compare :: Class -> Class -> Ordering
$c< :: Class -> Class -> Bool
< :: Class -> Class -> Bool
$c<= :: Class -> Class -> Bool
<= :: Class -> Class -> Bool
$c> :: Class -> Class -> Bool
> :: Class -> Class -> Bool
$c>= :: Class -> Class -> Bool
>= :: Class -> Class -> Bool
$cmax :: Class -> Class -> Class
max :: Class -> Class -> Class
$cmin :: Class -> Class -> Class
min :: Class -> Class -> Class
Ord, ReadPrec [Class]
ReadPrec Class
Int -> ReadS Class
ReadS [Class]
(Int -> ReadS Class)
-> ReadS [Class]
-> ReadPrec Class
-> ReadPrec [Class]
-> Read Class
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Class
readsPrec :: Int -> ReadS Class
$creadList :: ReadS [Class]
readList :: ReadS [Class]
$creadPrec :: ReadPrec Class
readPrec :: ReadPrec Class
$creadListPrec :: ReadPrec [Class]
readListPrec :: ReadPrec [Class]
Read, Int -> Class -> ShowS
[Class] -> ShowS
Class -> String
(Int -> Class -> ShowS)
-> (Class -> String) -> ([Class] -> ShowS) -> Show Class
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Class -> ShowS
showsPrec :: Int -> Class -> ShowS
$cshow :: Class -> String
show :: Class -> String
$cshowList :: [Class] -> ShowS
showList :: [Class] -> ShowS
Show)

_Class :: Name
_Class = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Class")

-- | See https://www.w3.org/TR/owl2-syntax/#Datatypes
data 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
  DatatypeXmlSchema Schema.Datatype |
  DatatypeOther Syntax.Iri
  deriving (Datatype -> Datatype -> Bool
(Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool) -> Eq Datatype
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Datatype -> Datatype -> Bool
== :: Datatype -> Datatype -> Bool
$c/= :: Datatype -> Datatype -> Bool
/= :: Datatype -> Datatype -> Bool
Eq, Eq Datatype
Eq Datatype =>
(Datatype -> Datatype -> Ordering)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Datatype)
-> (Datatype -> Datatype -> Datatype)
-> Ord Datatype
Datatype -> Datatype -> Bool
Datatype -> Datatype -> Ordering
Datatype -> Datatype -> Datatype
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Datatype -> Datatype -> Ordering
compare :: Datatype -> Datatype -> Ordering
$c< :: Datatype -> Datatype -> Bool
< :: Datatype -> Datatype -> Bool
$c<= :: Datatype -> Datatype -> Bool
<= :: Datatype -> Datatype -> Bool
$c> :: Datatype -> Datatype -> Bool
> :: Datatype -> Datatype -> Bool
$c>= :: Datatype -> Datatype -> Bool
>= :: Datatype -> Datatype -> Bool
$cmax :: Datatype -> Datatype -> Datatype
max :: Datatype -> Datatype -> Datatype
$cmin :: Datatype -> Datatype -> Datatype
min :: Datatype -> Datatype -> Datatype
Ord, ReadPrec [Datatype]
ReadPrec Datatype
Int -> ReadS Datatype
ReadS [Datatype]
(Int -> ReadS Datatype)
-> ReadS [Datatype]
-> ReadPrec Datatype
-> ReadPrec [Datatype]
-> Read Datatype
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Datatype
readsPrec :: Int -> ReadS Datatype
$creadList :: ReadS [Datatype]
readList :: ReadS [Datatype]
$creadPrec :: ReadPrec Datatype
readPrec :: ReadPrec Datatype
$creadListPrec :: ReadPrec [Datatype]
readListPrec :: ReadPrec [Datatype]
Read, Int -> Datatype -> ShowS
[Datatype] -> ShowS
Datatype -> String
(Int -> Datatype -> ShowS)
-> (Datatype -> String) -> ([Datatype] -> ShowS) -> Show Datatype
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Datatype -> ShowS
showsPrec :: Int -> Datatype -> ShowS
$cshow :: Datatype -> String
show :: Datatype -> String
$cshowList :: [Datatype] -> ShowS
showList :: [Datatype] -> ShowS
Show)

_Datatype :: Name
_Datatype = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Datatype")

_Datatype_xmlSchema :: Name
_Datatype_xmlSchema = (String -> Name
Core.Name String
"xmlSchema")

_Datatype_other :: Name
_Datatype_other = (String -> Name
Core.Name String
"other")

-- | See https://www.w3.org/TR/owl2-syntax/#Object_Properties
data ObjectProperty = 
  ObjectProperty {}
  deriving (ObjectProperty -> ObjectProperty -> Bool
(ObjectProperty -> ObjectProperty -> Bool)
-> (ObjectProperty -> ObjectProperty -> Bool) -> Eq ObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectProperty -> ObjectProperty -> Bool
== :: ObjectProperty -> ObjectProperty -> Bool
$c/= :: ObjectProperty -> ObjectProperty -> Bool
/= :: ObjectProperty -> ObjectProperty -> Bool
Eq, Eq ObjectProperty
Eq ObjectProperty =>
(ObjectProperty -> ObjectProperty -> Ordering)
-> (ObjectProperty -> ObjectProperty -> Bool)
-> (ObjectProperty -> ObjectProperty -> Bool)
-> (ObjectProperty -> ObjectProperty -> Bool)
-> (ObjectProperty -> ObjectProperty -> Bool)
-> (ObjectProperty -> ObjectProperty -> ObjectProperty)
-> (ObjectProperty -> ObjectProperty -> ObjectProperty)
-> Ord ObjectProperty
ObjectProperty -> ObjectProperty -> Bool
ObjectProperty -> ObjectProperty -> Ordering
ObjectProperty -> ObjectProperty -> ObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectProperty -> ObjectProperty -> Ordering
compare :: ObjectProperty -> ObjectProperty -> Ordering
$c< :: ObjectProperty -> ObjectProperty -> Bool
< :: ObjectProperty -> ObjectProperty -> Bool
$c<= :: ObjectProperty -> ObjectProperty -> Bool
<= :: ObjectProperty -> ObjectProperty -> Bool
$c> :: ObjectProperty -> ObjectProperty -> Bool
> :: ObjectProperty -> ObjectProperty -> Bool
$c>= :: ObjectProperty -> ObjectProperty -> Bool
>= :: ObjectProperty -> ObjectProperty -> Bool
$cmax :: ObjectProperty -> ObjectProperty -> ObjectProperty
max :: ObjectProperty -> ObjectProperty -> ObjectProperty
$cmin :: ObjectProperty -> ObjectProperty -> ObjectProperty
min :: ObjectProperty -> ObjectProperty -> ObjectProperty
Ord, ReadPrec [ObjectProperty]
ReadPrec ObjectProperty
Int -> ReadS ObjectProperty
ReadS [ObjectProperty]
(Int -> ReadS ObjectProperty)
-> ReadS [ObjectProperty]
-> ReadPrec ObjectProperty
-> ReadPrec [ObjectProperty]
-> Read ObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectProperty
readsPrec :: Int -> ReadS ObjectProperty
$creadList :: ReadS [ObjectProperty]
readList :: ReadS [ObjectProperty]
$creadPrec :: ReadPrec ObjectProperty
readPrec :: ReadPrec ObjectProperty
$creadListPrec :: ReadPrec [ObjectProperty]
readListPrec :: ReadPrec [ObjectProperty]
Read, Int -> ObjectProperty -> ShowS
[ObjectProperty] -> ShowS
ObjectProperty -> String
(Int -> ObjectProperty -> ShowS)
-> (ObjectProperty -> String)
-> ([ObjectProperty] -> ShowS)
-> Show ObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectProperty -> ShowS
showsPrec :: Int -> ObjectProperty -> ShowS
$cshow :: ObjectProperty -> String
show :: ObjectProperty -> String
$cshowList :: [ObjectProperty] -> ShowS
showList :: [ObjectProperty] -> ShowS
Show)

_ObjectProperty :: Name
_ObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectProperty")

data DataProperty = 
  DataProperty {}
  deriving (DataProperty -> DataProperty -> Bool
(DataProperty -> DataProperty -> Bool)
-> (DataProperty -> DataProperty -> Bool) -> Eq DataProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataProperty -> DataProperty -> Bool
== :: DataProperty -> DataProperty -> Bool
$c/= :: DataProperty -> DataProperty -> Bool
/= :: DataProperty -> DataProperty -> Bool
Eq, Eq DataProperty
Eq DataProperty =>
(DataProperty -> DataProperty -> Ordering)
-> (DataProperty -> DataProperty -> Bool)
-> (DataProperty -> DataProperty -> Bool)
-> (DataProperty -> DataProperty -> Bool)
-> (DataProperty -> DataProperty -> Bool)
-> (DataProperty -> DataProperty -> DataProperty)
-> (DataProperty -> DataProperty -> DataProperty)
-> Ord DataProperty
DataProperty -> DataProperty -> Bool
DataProperty -> DataProperty -> Ordering
DataProperty -> DataProperty -> DataProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataProperty -> DataProperty -> Ordering
compare :: DataProperty -> DataProperty -> Ordering
$c< :: DataProperty -> DataProperty -> Bool
< :: DataProperty -> DataProperty -> Bool
$c<= :: DataProperty -> DataProperty -> Bool
<= :: DataProperty -> DataProperty -> Bool
$c> :: DataProperty -> DataProperty -> Bool
> :: DataProperty -> DataProperty -> Bool
$c>= :: DataProperty -> DataProperty -> Bool
>= :: DataProperty -> DataProperty -> Bool
$cmax :: DataProperty -> DataProperty -> DataProperty
max :: DataProperty -> DataProperty -> DataProperty
$cmin :: DataProperty -> DataProperty -> DataProperty
min :: DataProperty -> DataProperty -> DataProperty
Ord, ReadPrec [DataProperty]
ReadPrec DataProperty
Int -> ReadS DataProperty
ReadS [DataProperty]
(Int -> ReadS DataProperty)
-> ReadS [DataProperty]
-> ReadPrec DataProperty
-> ReadPrec [DataProperty]
-> Read DataProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataProperty
readsPrec :: Int -> ReadS DataProperty
$creadList :: ReadS [DataProperty]
readList :: ReadS [DataProperty]
$creadPrec :: ReadPrec DataProperty
readPrec :: ReadPrec DataProperty
$creadListPrec :: ReadPrec [DataProperty]
readListPrec :: ReadPrec [DataProperty]
Read, Int -> DataProperty -> ShowS
[DataProperty] -> ShowS
DataProperty -> String
(Int -> DataProperty -> ShowS)
-> (DataProperty -> String)
-> ([DataProperty] -> ShowS)
-> Show DataProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataProperty -> ShowS
showsPrec :: Int -> DataProperty -> ShowS
$cshow :: DataProperty -> String
show :: DataProperty -> String
$cshowList :: [DataProperty] -> ShowS
showList :: [DataProperty] -> ShowS
Show)

_DataProperty :: Name
_DataProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataProperty")

data AnnotationProperty = 
  AnnotationProperty {}
  deriving (AnnotationProperty -> AnnotationProperty -> Bool
(AnnotationProperty -> AnnotationProperty -> Bool)
-> (AnnotationProperty -> AnnotationProperty -> Bool)
-> Eq AnnotationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotationProperty -> AnnotationProperty -> Bool
== :: AnnotationProperty -> AnnotationProperty -> Bool
$c/= :: AnnotationProperty -> AnnotationProperty -> Bool
/= :: AnnotationProperty -> AnnotationProperty -> Bool
Eq, Eq AnnotationProperty
Eq AnnotationProperty =>
(AnnotationProperty -> AnnotationProperty -> Ordering)
-> (AnnotationProperty -> AnnotationProperty -> Bool)
-> (AnnotationProperty -> AnnotationProperty -> Bool)
-> (AnnotationProperty -> AnnotationProperty -> Bool)
-> (AnnotationProperty -> AnnotationProperty -> Bool)
-> (AnnotationProperty -> AnnotationProperty -> AnnotationProperty)
-> (AnnotationProperty -> AnnotationProperty -> AnnotationProperty)
-> Ord AnnotationProperty
AnnotationProperty -> AnnotationProperty -> Bool
AnnotationProperty -> AnnotationProperty -> Ordering
AnnotationProperty -> AnnotationProperty -> AnnotationProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotationProperty -> AnnotationProperty -> Ordering
compare :: AnnotationProperty -> AnnotationProperty -> Ordering
$c< :: AnnotationProperty -> AnnotationProperty -> Bool
< :: AnnotationProperty -> AnnotationProperty -> Bool
$c<= :: AnnotationProperty -> AnnotationProperty -> Bool
<= :: AnnotationProperty -> AnnotationProperty -> Bool
$c> :: AnnotationProperty -> AnnotationProperty -> Bool
> :: AnnotationProperty -> AnnotationProperty -> Bool
$c>= :: AnnotationProperty -> AnnotationProperty -> Bool
>= :: AnnotationProperty -> AnnotationProperty -> Bool
$cmax :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty
max :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty
$cmin :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty
min :: AnnotationProperty -> AnnotationProperty -> AnnotationProperty
Ord, ReadPrec [AnnotationProperty]
ReadPrec AnnotationProperty
Int -> ReadS AnnotationProperty
ReadS [AnnotationProperty]
(Int -> ReadS AnnotationProperty)
-> ReadS [AnnotationProperty]
-> ReadPrec AnnotationProperty
-> ReadPrec [AnnotationProperty]
-> Read AnnotationProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotationProperty
readsPrec :: Int -> ReadS AnnotationProperty
$creadList :: ReadS [AnnotationProperty]
readList :: ReadS [AnnotationProperty]
$creadPrec :: ReadPrec AnnotationProperty
readPrec :: ReadPrec AnnotationProperty
$creadListPrec :: ReadPrec [AnnotationProperty]
readListPrec :: ReadPrec [AnnotationProperty]
Read, Int -> AnnotationProperty -> ShowS
[AnnotationProperty] -> ShowS
AnnotationProperty -> String
(Int -> AnnotationProperty -> ShowS)
-> (AnnotationProperty -> String)
-> ([AnnotationProperty] -> ShowS)
-> Show AnnotationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotationProperty -> ShowS
showsPrec :: Int -> AnnotationProperty -> ShowS
$cshow :: AnnotationProperty -> String
show :: AnnotationProperty -> String
$cshowList :: [AnnotationProperty] -> ShowS
showList :: [AnnotationProperty] -> ShowS
Show)

_AnnotationProperty :: Name
_AnnotationProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnnotationProperty")

data Individual = 
  IndividualNamed NamedIndividual |
  IndividualAnonymous AnonymousIndividual
  deriving (Individual -> Individual -> Bool
(Individual -> Individual -> Bool)
-> (Individual -> Individual -> Bool) -> Eq Individual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Individual -> Individual -> Bool
== :: Individual -> Individual -> Bool
$c/= :: Individual -> Individual -> Bool
/= :: Individual -> Individual -> Bool
Eq, Eq Individual
Eq Individual =>
(Individual -> Individual -> Ordering)
-> (Individual -> Individual -> Bool)
-> (Individual -> Individual -> Bool)
-> (Individual -> Individual -> Bool)
-> (Individual -> Individual -> Bool)
-> (Individual -> Individual -> Individual)
-> (Individual -> Individual -> Individual)
-> Ord Individual
Individual -> Individual -> Bool
Individual -> Individual -> Ordering
Individual -> Individual -> Individual
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Individual -> Individual -> Ordering
compare :: Individual -> Individual -> Ordering
$c< :: Individual -> Individual -> Bool
< :: Individual -> Individual -> Bool
$c<= :: Individual -> Individual -> Bool
<= :: Individual -> Individual -> Bool
$c> :: Individual -> Individual -> Bool
> :: Individual -> Individual -> Bool
$c>= :: Individual -> Individual -> Bool
>= :: Individual -> Individual -> Bool
$cmax :: Individual -> Individual -> Individual
max :: Individual -> Individual -> Individual
$cmin :: Individual -> Individual -> Individual
min :: Individual -> Individual -> Individual
Ord, ReadPrec [Individual]
ReadPrec Individual
Int -> ReadS Individual
ReadS [Individual]
(Int -> ReadS Individual)
-> ReadS [Individual]
-> ReadPrec Individual
-> ReadPrec [Individual]
-> Read Individual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Individual
readsPrec :: Int -> ReadS Individual
$creadList :: ReadS [Individual]
readList :: ReadS [Individual]
$creadPrec :: ReadPrec Individual
readPrec :: ReadPrec Individual
$creadListPrec :: ReadPrec [Individual]
readListPrec :: ReadPrec [Individual]
Read, Int -> Individual -> ShowS
[Individual] -> ShowS
Individual -> String
(Int -> Individual -> ShowS)
-> (Individual -> String)
-> ([Individual] -> ShowS)
-> Show Individual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Individual -> ShowS
showsPrec :: Int -> Individual -> ShowS
$cshow :: Individual -> String
show :: Individual -> String
$cshowList :: [Individual] -> ShowS
showList :: [Individual] -> ShowS
Show)

_Individual :: Name
_Individual = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Individual")

_Individual_named :: Name
_Individual_named = (String -> Name
Core.Name String
"named")

_Individual_anonymous :: Name
_Individual_anonymous = (String -> Name
Core.Name String
"anonymous")

data NamedIndividual = 
  NamedIndividual {}
  deriving (NamedIndividual -> NamedIndividual -> Bool
(NamedIndividual -> NamedIndividual -> Bool)
-> (NamedIndividual -> NamedIndividual -> Bool)
-> Eq NamedIndividual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamedIndividual -> NamedIndividual -> Bool
== :: NamedIndividual -> NamedIndividual -> Bool
$c/= :: NamedIndividual -> NamedIndividual -> Bool
/= :: NamedIndividual -> NamedIndividual -> Bool
Eq, Eq NamedIndividual
Eq NamedIndividual =>
(NamedIndividual -> NamedIndividual -> Ordering)
-> (NamedIndividual -> NamedIndividual -> Bool)
-> (NamedIndividual -> NamedIndividual -> Bool)
-> (NamedIndividual -> NamedIndividual -> Bool)
-> (NamedIndividual -> NamedIndividual -> Bool)
-> (NamedIndividual -> NamedIndividual -> NamedIndividual)
-> (NamedIndividual -> NamedIndividual -> NamedIndividual)
-> Ord NamedIndividual
NamedIndividual -> NamedIndividual -> Bool
NamedIndividual -> NamedIndividual -> Ordering
NamedIndividual -> NamedIndividual -> NamedIndividual
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NamedIndividual -> NamedIndividual -> Ordering
compare :: NamedIndividual -> NamedIndividual -> Ordering
$c< :: NamedIndividual -> NamedIndividual -> Bool
< :: NamedIndividual -> NamedIndividual -> Bool
$c<= :: NamedIndividual -> NamedIndividual -> Bool
<= :: NamedIndividual -> NamedIndividual -> Bool
$c> :: NamedIndividual -> NamedIndividual -> Bool
> :: NamedIndividual -> NamedIndividual -> Bool
$c>= :: NamedIndividual -> NamedIndividual -> Bool
>= :: NamedIndividual -> NamedIndividual -> Bool
$cmax :: NamedIndividual -> NamedIndividual -> NamedIndividual
max :: NamedIndividual -> NamedIndividual -> NamedIndividual
$cmin :: NamedIndividual -> NamedIndividual -> NamedIndividual
min :: NamedIndividual -> NamedIndividual -> NamedIndividual
Ord, ReadPrec [NamedIndividual]
ReadPrec NamedIndividual
Int -> ReadS NamedIndividual
ReadS [NamedIndividual]
(Int -> ReadS NamedIndividual)
-> ReadS [NamedIndividual]
-> ReadPrec NamedIndividual
-> ReadPrec [NamedIndividual]
-> Read NamedIndividual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NamedIndividual
readsPrec :: Int -> ReadS NamedIndividual
$creadList :: ReadS [NamedIndividual]
readList :: ReadS [NamedIndividual]
$creadPrec :: ReadPrec NamedIndividual
readPrec :: ReadPrec NamedIndividual
$creadListPrec :: ReadPrec [NamedIndividual]
readListPrec :: ReadPrec [NamedIndividual]
Read, Int -> NamedIndividual -> ShowS
[NamedIndividual] -> ShowS
NamedIndividual -> String
(Int -> NamedIndividual -> ShowS)
-> (NamedIndividual -> String)
-> ([NamedIndividual] -> ShowS)
-> Show NamedIndividual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NamedIndividual -> ShowS
showsPrec :: Int -> NamedIndividual -> ShowS
$cshow :: NamedIndividual -> String
show :: NamedIndividual -> String
$cshowList :: [NamedIndividual] -> ShowS
showList :: [NamedIndividual] -> ShowS
Show)

_NamedIndividual :: Name
_NamedIndividual = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.NamedIndividual")

data AnonymousIndividual = 
  AnonymousIndividual {}
  deriving (AnonymousIndividual -> AnonymousIndividual -> Bool
(AnonymousIndividual -> AnonymousIndividual -> Bool)
-> (AnonymousIndividual -> AnonymousIndividual -> Bool)
-> Eq AnonymousIndividual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnonymousIndividual -> AnonymousIndividual -> Bool
== :: AnonymousIndividual -> AnonymousIndividual -> Bool
$c/= :: AnonymousIndividual -> AnonymousIndividual -> Bool
/= :: AnonymousIndividual -> AnonymousIndividual -> Bool
Eq, Eq AnonymousIndividual
Eq AnonymousIndividual =>
(AnonymousIndividual -> AnonymousIndividual -> Ordering)
-> (AnonymousIndividual -> AnonymousIndividual -> Bool)
-> (AnonymousIndividual -> AnonymousIndividual -> Bool)
-> (AnonymousIndividual -> AnonymousIndividual -> Bool)
-> (AnonymousIndividual -> AnonymousIndividual -> Bool)
-> (AnonymousIndividual
    -> AnonymousIndividual -> AnonymousIndividual)
-> (AnonymousIndividual
    -> AnonymousIndividual -> AnonymousIndividual)
-> Ord AnonymousIndividual
AnonymousIndividual -> AnonymousIndividual -> Bool
AnonymousIndividual -> AnonymousIndividual -> Ordering
AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnonymousIndividual -> AnonymousIndividual -> Ordering
compare :: AnonymousIndividual -> AnonymousIndividual -> Ordering
$c< :: AnonymousIndividual -> AnonymousIndividual -> Bool
< :: AnonymousIndividual -> AnonymousIndividual -> Bool
$c<= :: AnonymousIndividual -> AnonymousIndividual -> Bool
<= :: AnonymousIndividual -> AnonymousIndividual -> Bool
$c> :: AnonymousIndividual -> AnonymousIndividual -> Bool
> :: AnonymousIndividual -> AnonymousIndividual -> Bool
$c>= :: AnonymousIndividual -> AnonymousIndividual -> Bool
>= :: AnonymousIndividual -> AnonymousIndividual -> Bool
$cmax :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual
max :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual
$cmin :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual
min :: AnonymousIndividual -> AnonymousIndividual -> AnonymousIndividual
Ord, ReadPrec [AnonymousIndividual]
ReadPrec AnonymousIndividual
Int -> ReadS AnonymousIndividual
ReadS [AnonymousIndividual]
(Int -> ReadS AnonymousIndividual)
-> ReadS [AnonymousIndividual]
-> ReadPrec AnonymousIndividual
-> ReadPrec [AnonymousIndividual]
-> Read AnonymousIndividual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnonymousIndividual
readsPrec :: Int -> ReadS AnonymousIndividual
$creadList :: ReadS [AnonymousIndividual]
readList :: ReadS [AnonymousIndividual]
$creadPrec :: ReadPrec AnonymousIndividual
readPrec :: ReadPrec AnonymousIndividual
$creadListPrec :: ReadPrec [AnonymousIndividual]
readListPrec :: ReadPrec [AnonymousIndividual]
Read, Int -> AnonymousIndividual -> ShowS
[AnonymousIndividual] -> ShowS
AnonymousIndividual -> String
(Int -> AnonymousIndividual -> ShowS)
-> (AnonymousIndividual -> String)
-> ([AnonymousIndividual] -> ShowS)
-> Show AnonymousIndividual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnonymousIndividual -> ShowS
showsPrec :: Int -> AnonymousIndividual -> ShowS
$cshow :: AnonymousIndividual -> String
show :: AnonymousIndividual -> String
$cshowList :: [AnonymousIndividual] -> ShowS
showList :: [AnonymousIndividual] -> ShowS
Show)

_AnonymousIndividual :: Name
_AnonymousIndividual = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AnonymousIndividual")

data ObjectPropertyExpression = 
  ObjectPropertyExpressionObject ObjectProperty |
  ObjectPropertyExpressionInverseObject InverseObjectProperty
  deriving (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
(ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> Eq ObjectPropertyExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
== :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
$c/= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
/= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
Eq, Eq ObjectPropertyExpression
Eq ObjectPropertyExpression =>
(ObjectPropertyExpression -> ObjectPropertyExpression -> Ordering)
-> (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> (ObjectPropertyExpression -> ObjectPropertyExpression -> Bool)
-> (ObjectPropertyExpression
    -> ObjectPropertyExpression -> ObjectPropertyExpression)
-> (ObjectPropertyExpression
    -> ObjectPropertyExpression -> ObjectPropertyExpression)
-> Ord ObjectPropertyExpression
ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
ObjectPropertyExpression -> ObjectPropertyExpression -> Ordering
ObjectPropertyExpression
-> ObjectPropertyExpression -> ObjectPropertyExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectPropertyExpression -> ObjectPropertyExpression -> Ordering
compare :: ObjectPropertyExpression -> ObjectPropertyExpression -> Ordering
$c< :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
< :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
$c<= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
<= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
$c> :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
> :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
$c>= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
>= :: ObjectPropertyExpression -> ObjectPropertyExpression -> Bool
$cmax :: ObjectPropertyExpression
-> ObjectPropertyExpression -> ObjectPropertyExpression
max :: ObjectPropertyExpression
-> ObjectPropertyExpression -> ObjectPropertyExpression
$cmin :: ObjectPropertyExpression
-> ObjectPropertyExpression -> ObjectPropertyExpression
min :: ObjectPropertyExpression
-> ObjectPropertyExpression -> ObjectPropertyExpression
Ord, ReadPrec [ObjectPropertyExpression]
ReadPrec ObjectPropertyExpression
Int -> ReadS ObjectPropertyExpression
ReadS [ObjectPropertyExpression]
(Int -> ReadS ObjectPropertyExpression)
-> ReadS [ObjectPropertyExpression]
-> ReadPrec ObjectPropertyExpression
-> ReadPrec [ObjectPropertyExpression]
-> Read ObjectPropertyExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectPropertyExpression
readsPrec :: Int -> ReadS ObjectPropertyExpression
$creadList :: ReadS [ObjectPropertyExpression]
readList :: ReadS [ObjectPropertyExpression]
$creadPrec :: ReadPrec ObjectPropertyExpression
readPrec :: ReadPrec ObjectPropertyExpression
$creadListPrec :: ReadPrec [ObjectPropertyExpression]
readListPrec :: ReadPrec [ObjectPropertyExpression]
Read, Int -> ObjectPropertyExpression -> ShowS
[ObjectPropertyExpression] -> ShowS
ObjectPropertyExpression -> String
(Int -> ObjectPropertyExpression -> ShowS)
-> (ObjectPropertyExpression -> String)
-> ([ObjectPropertyExpression] -> ShowS)
-> Show ObjectPropertyExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectPropertyExpression -> ShowS
showsPrec :: Int -> ObjectPropertyExpression -> ShowS
$cshow :: ObjectPropertyExpression -> String
show :: ObjectPropertyExpression -> String
$cshowList :: [ObjectPropertyExpression] -> ShowS
showList :: [ObjectPropertyExpression] -> ShowS
Show)

_ObjectPropertyExpression :: Name
_ObjectPropertyExpression = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectPropertyExpression")

_ObjectPropertyExpression_object :: Name
_ObjectPropertyExpression_object = (String -> Name
Core.Name String
"object")

_ObjectPropertyExpression_inverseObject :: Name
_ObjectPropertyExpression_inverseObject = (String -> Name
Core.Name String
"inverseObject")

newtype InverseObjectProperty = 
  InverseObjectProperty {
    InverseObjectProperty -> ObjectProperty
unInverseObjectProperty :: ObjectProperty}
  deriving (InverseObjectProperty -> InverseObjectProperty -> Bool
(InverseObjectProperty -> InverseObjectProperty -> Bool)
-> (InverseObjectProperty -> InverseObjectProperty -> Bool)
-> Eq InverseObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InverseObjectProperty -> InverseObjectProperty -> Bool
== :: InverseObjectProperty -> InverseObjectProperty -> Bool
$c/= :: InverseObjectProperty -> InverseObjectProperty -> Bool
/= :: InverseObjectProperty -> InverseObjectProperty -> Bool
Eq, Eq InverseObjectProperty
Eq InverseObjectProperty =>
(InverseObjectProperty -> InverseObjectProperty -> Ordering)
-> (InverseObjectProperty -> InverseObjectProperty -> Bool)
-> (InverseObjectProperty -> InverseObjectProperty -> Bool)
-> (InverseObjectProperty -> InverseObjectProperty -> Bool)
-> (InverseObjectProperty -> InverseObjectProperty -> Bool)
-> (InverseObjectProperty
    -> InverseObjectProperty -> InverseObjectProperty)
-> (InverseObjectProperty
    -> InverseObjectProperty -> InverseObjectProperty)
-> Ord InverseObjectProperty
InverseObjectProperty -> InverseObjectProperty -> Bool
InverseObjectProperty -> InverseObjectProperty -> Ordering
InverseObjectProperty
-> InverseObjectProperty -> InverseObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InverseObjectProperty -> InverseObjectProperty -> Ordering
compare :: InverseObjectProperty -> InverseObjectProperty -> Ordering
$c< :: InverseObjectProperty -> InverseObjectProperty -> Bool
< :: InverseObjectProperty -> InverseObjectProperty -> Bool
$c<= :: InverseObjectProperty -> InverseObjectProperty -> Bool
<= :: InverseObjectProperty -> InverseObjectProperty -> Bool
$c> :: InverseObjectProperty -> InverseObjectProperty -> Bool
> :: InverseObjectProperty -> InverseObjectProperty -> Bool
$c>= :: InverseObjectProperty -> InverseObjectProperty -> Bool
>= :: InverseObjectProperty -> InverseObjectProperty -> Bool
$cmax :: InverseObjectProperty
-> InverseObjectProperty -> InverseObjectProperty
max :: InverseObjectProperty
-> InverseObjectProperty -> InverseObjectProperty
$cmin :: InverseObjectProperty
-> InverseObjectProperty -> InverseObjectProperty
min :: InverseObjectProperty
-> InverseObjectProperty -> InverseObjectProperty
Ord, ReadPrec [InverseObjectProperty]
ReadPrec InverseObjectProperty
Int -> ReadS InverseObjectProperty
ReadS [InverseObjectProperty]
(Int -> ReadS InverseObjectProperty)
-> ReadS [InverseObjectProperty]
-> ReadPrec InverseObjectProperty
-> ReadPrec [InverseObjectProperty]
-> Read InverseObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InverseObjectProperty
readsPrec :: Int -> ReadS InverseObjectProperty
$creadList :: ReadS [InverseObjectProperty]
readList :: ReadS [InverseObjectProperty]
$creadPrec :: ReadPrec InverseObjectProperty
readPrec :: ReadPrec InverseObjectProperty
$creadListPrec :: ReadPrec [InverseObjectProperty]
readListPrec :: ReadPrec [InverseObjectProperty]
Read, Int -> InverseObjectProperty -> ShowS
[InverseObjectProperty] -> ShowS
InverseObjectProperty -> String
(Int -> InverseObjectProperty -> ShowS)
-> (InverseObjectProperty -> String)
-> ([InverseObjectProperty] -> ShowS)
-> Show InverseObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InverseObjectProperty -> ShowS
showsPrec :: Int -> InverseObjectProperty -> ShowS
$cshow :: InverseObjectProperty -> String
show :: InverseObjectProperty -> String
$cshowList :: [InverseObjectProperty] -> ShowS
showList :: [InverseObjectProperty] -> ShowS
Show)

_InverseObjectProperty :: Name
_InverseObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.InverseObjectProperty")

newtype DataPropertyExpression = 
  DataPropertyExpression {
    DataPropertyExpression -> DataProperty
unDataPropertyExpression :: DataProperty}
  deriving (DataPropertyExpression -> DataPropertyExpression -> Bool
(DataPropertyExpression -> DataPropertyExpression -> Bool)
-> (DataPropertyExpression -> DataPropertyExpression -> Bool)
-> Eq DataPropertyExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPropertyExpression -> DataPropertyExpression -> Bool
== :: DataPropertyExpression -> DataPropertyExpression -> Bool
$c/= :: DataPropertyExpression -> DataPropertyExpression -> Bool
/= :: DataPropertyExpression -> DataPropertyExpression -> Bool
Eq, Eq DataPropertyExpression
Eq DataPropertyExpression =>
(DataPropertyExpression -> DataPropertyExpression -> Ordering)
-> (DataPropertyExpression -> DataPropertyExpression -> Bool)
-> (DataPropertyExpression -> DataPropertyExpression -> Bool)
-> (DataPropertyExpression -> DataPropertyExpression -> Bool)
-> (DataPropertyExpression -> DataPropertyExpression -> Bool)
-> (DataPropertyExpression
    -> DataPropertyExpression -> DataPropertyExpression)
-> (DataPropertyExpression
    -> DataPropertyExpression -> DataPropertyExpression)
-> Ord DataPropertyExpression
DataPropertyExpression -> DataPropertyExpression -> Bool
DataPropertyExpression -> DataPropertyExpression -> Ordering
DataPropertyExpression
-> DataPropertyExpression -> DataPropertyExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPropertyExpression -> DataPropertyExpression -> Ordering
compare :: DataPropertyExpression -> DataPropertyExpression -> Ordering
$c< :: DataPropertyExpression -> DataPropertyExpression -> Bool
< :: DataPropertyExpression -> DataPropertyExpression -> Bool
$c<= :: DataPropertyExpression -> DataPropertyExpression -> Bool
<= :: DataPropertyExpression -> DataPropertyExpression -> Bool
$c> :: DataPropertyExpression -> DataPropertyExpression -> Bool
> :: DataPropertyExpression -> DataPropertyExpression -> Bool
$c>= :: DataPropertyExpression -> DataPropertyExpression -> Bool
>= :: DataPropertyExpression -> DataPropertyExpression -> Bool
$cmax :: DataPropertyExpression
-> DataPropertyExpression -> DataPropertyExpression
max :: DataPropertyExpression
-> DataPropertyExpression -> DataPropertyExpression
$cmin :: DataPropertyExpression
-> DataPropertyExpression -> DataPropertyExpression
min :: DataPropertyExpression
-> DataPropertyExpression -> DataPropertyExpression
Ord, ReadPrec [DataPropertyExpression]
ReadPrec DataPropertyExpression
Int -> ReadS DataPropertyExpression
ReadS [DataPropertyExpression]
(Int -> ReadS DataPropertyExpression)
-> ReadS [DataPropertyExpression]
-> ReadPrec DataPropertyExpression
-> ReadPrec [DataPropertyExpression]
-> Read DataPropertyExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPropertyExpression
readsPrec :: Int -> ReadS DataPropertyExpression
$creadList :: ReadS [DataPropertyExpression]
readList :: ReadS [DataPropertyExpression]
$creadPrec :: ReadPrec DataPropertyExpression
readPrec :: ReadPrec DataPropertyExpression
$creadListPrec :: ReadPrec [DataPropertyExpression]
readListPrec :: ReadPrec [DataPropertyExpression]
Read, Int -> DataPropertyExpression -> ShowS
[DataPropertyExpression] -> ShowS
DataPropertyExpression -> String
(Int -> DataPropertyExpression -> ShowS)
-> (DataPropertyExpression -> String)
-> ([DataPropertyExpression] -> ShowS)
-> Show DataPropertyExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPropertyExpression -> ShowS
showsPrec :: Int -> DataPropertyExpression -> ShowS
$cshow :: DataPropertyExpression -> String
show :: DataPropertyExpression -> String
$cshowList :: [DataPropertyExpression] -> ShowS
showList :: [DataPropertyExpression] -> ShowS
Show)

_DataPropertyExpression :: Name
_DataPropertyExpression = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataPropertyExpression")

-- | See https://www.w3.org/TR/owl2-syntax/#Data_Ranges
data DataRange = 
  DataRangeDataComplementOf DataComplementOf |
  DataRangeDataIntersectionOf DataIntersectionOf |
  DataRangeDataOneOf DataOneOf |
  DataRangeDataUnionOf DataUnionOf |
  DataRangeDatatype Datatype |
  DataRangeDatatypeRestriction DatatypeRestriction
  deriving (DataRange -> DataRange -> Bool
(DataRange -> DataRange -> Bool)
-> (DataRange -> DataRange -> Bool) -> Eq DataRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataRange -> DataRange -> Bool
== :: DataRange -> DataRange -> Bool
$c/= :: DataRange -> DataRange -> Bool
/= :: DataRange -> DataRange -> Bool
Eq, Eq DataRange
Eq DataRange =>
(DataRange -> DataRange -> Ordering)
-> (DataRange -> DataRange -> Bool)
-> (DataRange -> DataRange -> Bool)
-> (DataRange -> DataRange -> Bool)
-> (DataRange -> DataRange -> Bool)
-> (DataRange -> DataRange -> DataRange)
-> (DataRange -> DataRange -> DataRange)
-> Ord DataRange
DataRange -> DataRange -> Bool
DataRange -> DataRange -> Ordering
DataRange -> DataRange -> DataRange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataRange -> DataRange -> Ordering
compare :: DataRange -> DataRange -> Ordering
$c< :: DataRange -> DataRange -> Bool
< :: DataRange -> DataRange -> Bool
$c<= :: DataRange -> DataRange -> Bool
<= :: DataRange -> DataRange -> Bool
$c> :: DataRange -> DataRange -> Bool
> :: DataRange -> DataRange -> Bool
$c>= :: DataRange -> DataRange -> Bool
>= :: DataRange -> DataRange -> Bool
$cmax :: DataRange -> DataRange -> DataRange
max :: DataRange -> DataRange -> DataRange
$cmin :: DataRange -> DataRange -> DataRange
min :: DataRange -> DataRange -> DataRange
Ord, ReadPrec [DataRange]
ReadPrec DataRange
Int -> ReadS DataRange
ReadS [DataRange]
(Int -> ReadS DataRange)
-> ReadS [DataRange]
-> ReadPrec DataRange
-> ReadPrec [DataRange]
-> Read DataRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataRange
readsPrec :: Int -> ReadS DataRange
$creadList :: ReadS [DataRange]
readList :: ReadS [DataRange]
$creadPrec :: ReadPrec DataRange
readPrec :: ReadPrec DataRange
$creadListPrec :: ReadPrec [DataRange]
readListPrec :: ReadPrec [DataRange]
Read, Int -> DataRange -> ShowS
[DataRange] -> ShowS
DataRange -> String
(Int -> DataRange -> ShowS)
-> (DataRange -> String)
-> ([DataRange] -> ShowS)
-> Show DataRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataRange -> ShowS
showsPrec :: Int -> DataRange -> ShowS
$cshow :: DataRange -> String
show :: DataRange -> String
$cshowList :: [DataRange] -> ShowS
showList :: [DataRange] -> ShowS
Show)

_DataRange :: Name
_DataRange = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataRange")

_DataRange_dataComplementOf :: Name
_DataRange_dataComplementOf = (String -> Name
Core.Name String
"dataComplementOf")

_DataRange_dataIntersectionOf :: Name
_DataRange_dataIntersectionOf = (String -> Name
Core.Name String
"dataIntersectionOf")

_DataRange_dataOneOf :: Name
_DataRange_dataOneOf = (String -> Name
Core.Name String
"dataOneOf")

_DataRange_dataUnionOf :: Name
_DataRange_dataUnionOf = (String -> Name
Core.Name String
"dataUnionOf")

_DataRange_datatype :: Name
_DataRange_datatype = (String -> Name
Core.Name String
"datatype")

_DataRange_datatypeRestriction :: Name
_DataRange_datatypeRestriction = (String -> Name
Core.Name String
"datatypeRestriction")

-- | See https://www.w3.org/TR/owl2-syntax/#Intersection_of_Data_Ranges
newtype DataIntersectionOf = 
  DataIntersectionOf {
    DataIntersectionOf -> [DataRange]
unDataIntersectionOf :: [DataRange]}
  deriving (DataIntersectionOf -> DataIntersectionOf -> Bool
(DataIntersectionOf -> DataIntersectionOf -> Bool)
-> (DataIntersectionOf -> DataIntersectionOf -> Bool)
-> Eq DataIntersectionOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataIntersectionOf -> DataIntersectionOf -> Bool
== :: DataIntersectionOf -> DataIntersectionOf -> Bool
$c/= :: DataIntersectionOf -> DataIntersectionOf -> Bool
/= :: DataIntersectionOf -> DataIntersectionOf -> Bool
Eq, Eq DataIntersectionOf
Eq DataIntersectionOf =>
(DataIntersectionOf -> DataIntersectionOf -> Ordering)
-> (DataIntersectionOf -> DataIntersectionOf -> Bool)
-> (DataIntersectionOf -> DataIntersectionOf -> Bool)
-> (DataIntersectionOf -> DataIntersectionOf -> Bool)
-> (DataIntersectionOf -> DataIntersectionOf -> Bool)
-> (DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf)
-> (DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf)
-> Ord DataIntersectionOf
DataIntersectionOf -> DataIntersectionOf -> Bool
DataIntersectionOf -> DataIntersectionOf -> Ordering
DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataIntersectionOf -> DataIntersectionOf -> Ordering
compare :: DataIntersectionOf -> DataIntersectionOf -> Ordering
$c< :: DataIntersectionOf -> DataIntersectionOf -> Bool
< :: DataIntersectionOf -> DataIntersectionOf -> Bool
$c<= :: DataIntersectionOf -> DataIntersectionOf -> Bool
<= :: DataIntersectionOf -> DataIntersectionOf -> Bool
$c> :: DataIntersectionOf -> DataIntersectionOf -> Bool
> :: DataIntersectionOf -> DataIntersectionOf -> Bool
$c>= :: DataIntersectionOf -> DataIntersectionOf -> Bool
>= :: DataIntersectionOf -> DataIntersectionOf -> Bool
$cmax :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf
max :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf
$cmin :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf
min :: DataIntersectionOf -> DataIntersectionOf -> DataIntersectionOf
Ord, ReadPrec [DataIntersectionOf]
ReadPrec DataIntersectionOf
Int -> ReadS DataIntersectionOf
ReadS [DataIntersectionOf]
(Int -> ReadS DataIntersectionOf)
-> ReadS [DataIntersectionOf]
-> ReadPrec DataIntersectionOf
-> ReadPrec [DataIntersectionOf]
-> Read DataIntersectionOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataIntersectionOf
readsPrec :: Int -> ReadS DataIntersectionOf
$creadList :: ReadS [DataIntersectionOf]
readList :: ReadS [DataIntersectionOf]
$creadPrec :: ReadPrec DataIntersectionOf
readPrec :: ReadPrec DataIntersectionOf
$creadListPrec :: ReadPrec [DataIntersectionOf]
readListPrec :: ReadPrec [DataIntersectionOf]
Read, Int -> DataIntersectionOf -> ShowS
[DataIntersectionOf] -> ShowS
DataIntersectionOf -> String
(Int -> DataIntersectionOf -> ShowS)
-> (DataIntersectionOf -> String)
-> ([DataIntersectionOf] -> ShowS)
-> Show DataIntersectionOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataIntersectionOf -> ShowS
showsPrec :: Int -> DataIntersectionOf -> ShowS
$cshow :: DataIntersectionOf -> String
show :: DataIntersectionOf -> String
$cshowList :: [DataIntersectionOf] -> ShowS
showList :: [DataIntersectionOf] -> ShowS
Show)

_DataIntersectionOf :: Name
_DataIntersectionOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataIntersectionOf")

-- | See https://www.w3.org/TR/owl2-syntax/#Union_of_Data_Ranges
newtype DataUnionOf = 
  DataUnionOf {
    DataUnionOf -> [DataRange]
unDataUnionOf :: [DataRange]}
  deriving (DataUnionOf -> DataUnionOf -> Bool
(DataUnionOf -> DataUnionOf -> Bool)
-> (DataUnionOf -> DataUnionOf -> Bool) -> Eq DataUnionOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataUnionOf -> DataUnionOf -> Bool
== :: DataUnionOf -> DataUnionOf -> Bool
$c/= :: DataUnionOf -> DataUnionOf -> Bool
/= :: DataUnionOf -> DataUnionOf -> Bool
Eq, Eq DataUnionOf
Eq DataUnionOf =>
(DataUnionOf -> DataUnionOf -> Ordering)
-> (DataUnionOf -> DataUnionOf -> Bool)
-> (DataUnionOf -> DataUnionOf -> Bool)
-> (DataUnionOf -> DataUnionOf -> Bool)
-> (DataUnionOf -> DataUnionOf -> Bool)
-> (DataUnionOf -> DataUnionOf -> DataUnionOf)
-> (DataUnionOf -> DataUnionOf -> DataUnionOf)
-> Ord DataUnionOf
DataUnionOf -> DataUnionOf -> Bool
DataUnionOf -> DataUnionOf -> Ordering
DataUnionOf -> DataUnionOf -> DataUnionOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataUnionOf -> DataUnionOf -> Ordering
compare :: DataUnionOf -> DataUnionOf -> Ordering
$c< :: DataUnionOf -> DataUnionOf -> Bool
< :: DataUnionOf -> DataUnionOf -> Bool
$c<= :: DataUnionOf -> DataUnionOf -> Bool
<= :: DataUnionOf -> DataUnionOf -> Bool
$c> :: DataUnionOf -> DataUnionOf -> Bool
> :: DataUnionOf -> DataUnionOf -> Bool
$c>= :: DataUnionOf -> DataUnionOf -> Bool
>= :: DataUnionOf -> DataUnionOf -> Bool
$cmax :: DataUnionOf -> DataUnionOf -> DataUnionOf
max :: DataUnionOf -> DataUnionOf -> DataUnionOf
$cmin :: DataUnionOf -> DataUnionOf -> DataUnionOf
min :: DataUnionOf -> DataUnionOf -> DataUnionOf
Ord, ReadPrec [DataUnionOf]
ReadPrec DataUnionOf
Int -> ReadS DataUnionOf
ReadS [DataUnionOf]
(Int -> ReadS DataUnionOf)
-> ReadS [DataUnionOf]
-> ReadPrec DataUnionOf
-> ReadPrec [DataUnionOf]
-> Read DataUnionOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataUnionOf
readsPrec :: Int -> ReadS DataUnionOf
$creadList :: ReadS [DataUnionOf]
readList :: ReadS [DataUnionOf]
$creadPrec :: ReadPrec DataUnionOf
readPrec :: ReadPrec DataUnionOf
$creadListPrec :: ReadPrec [DataUnionOf]
readListPrec :: ReadPrec [DataUnionOf]
Read, Int -> DataUnionOf -> ShowS
[DataUnionOf] -> ShowS
DataUnionOf -> String
(Int -> DataUnionOf -> ShowS)
-> (DataUnionOf -> String)
-> ([DataUnionOf] -> ShowS)
-> Show DataUnionOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataUnionOf -> ShowS
showsPrec :: Int -> DataUnionOf -> ShowS
$cshow :: DataUnionOf -> String
show :: DataUnionOf -> String
$cshowList :: [DataUnionOf] -> ShowS
showList :: [DataUnionOf] -> ShowS
Show)

_DataUnionOf :: Name
_DataUnionOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataUnionOf")

-- | See https://www.w3.org/TR/owl2-syntax/#Complement_of_Data_Ranges
newtype DataComplementOf = 
  DataComplementOf {
    DataComplementOf -> DataRange
unDataComplementOf :: DataRange}
  deriving (DataComplementOf -> DataComplementOf -> Bool
(DataComplementOf -> DataComplementOf -> Bool)
-> (DataComplementOf -> DataComplementOf -> Bool)
-> Eq DataComplementOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataComplementOf -> DataComplementOf -> Bool
== :: DataComplementOf -> DataComplementOf -> Bool
$c/= :: DataComplementOf -> DataComplementOf -> Bool
/= :: DataComplementOf -> DataComplementOf -> Bool
Eq, Eq DataComplementOf
Eq DataComplementOf =>
(DataComplementOf -> DataComplementOf -> Ordering)
-> (DataComplementOf -> DataComplementOf -> Bool)
-> (DataComplementOf -> DataComplementOf -> Bool)
-> (DataComplementOf -> DataComplementOf -> Bool)
-> (DataComplementOf -> DataComplementOf -> Bool)
-> (DataComplementOf -> DataComplementOf -> DataComplementOf)
-> (DataComplementOf -> DataComplementOf -> DataComplementOf)
-> Ord DataComplementOf
DataComplementOf -> DataComplementOf -> Bool
DataComplementOf -> DataComplementOf -> Ordering
DataComplementOf -> DataComplementOf -> DataComplementOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataComplementOf -> DataComplementOf -> Ordering
compare :: DataComplementOf -> DataComplementOf -> Ordering
$c< :: DataComplementOf -> DataComplementOf -> Bool
< :: DataComplementOf -> DataComplementOf -> Bool
$c<= :: DataComplementOf -> DataComplementOf -> Bool
<= :: DataComplementOf -> DataComplementOf -> Bool
$c> :: DataComplementOf -> DataComplementOf -> Bool
> :: DataComplementOf -> DataComplementOf -> Bool
$c>= :: DataComplementOf -> DataComplementOf -> Bool
>= :: DataComplementOf -> DataComplementOf -> Bool
$cmax :: DataComplementOf -> DataComplementOf -> DataComplementOf
max :: DataComplementOf -> DataComplementOf -> DataComplementOf
$cmin :: DataComplementOf -> DataComplementOf -> DataComplementOf
min :: DataComplementOf -> DataComplementOf -> DataComplementOf
Ord, ReadPrec [DataComplementOf]
ReadPrec DataComplementOf
Int -> ReadS DataComplementOf
ReadS [DataComplementOf]
(Int -> ReadS DataComplementOf)
-> ReadS [DataComplementOf]
-> ReadPrec DataComplementOf
-> ReadPrec [DataComplementOf]
-> Read DataComplementOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataComplementOf
readsPrec :: Int -> ReadS DataComplementOf
$creadList :: ReadS [DataComplementOf]
readList :: ReadS [DataComplementOf]
$creadPrec :: ReadPrec DataComplementOf
readPrec :: ReadPrec DataComplementOf
$creadListPrec :: ReadPrec [DataComplementOf]
readListPrec :: ReadPrec [DataComplementOf]
Read, Int -> DataComplementOf -> ShowS
[DataComplementOf] -> ShowS
DataComplementOf -> String
(Int -> DataComplementOf -> ShowS)
-> (DataComplementOf -> String)
-> ([DataComplementOf] -> ShowS)
-> Show DataComplementOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataComplementOf -> ShowS
showsPrec :: Int -> DataComplementOf -> ShowS
$cshow :: DataComplementOf -> String
show :: DataComplementOf -> String
$cshowList :: [DataComplementOf] -> ShowS
showList :: [DataComplementOf] -> ShowS
Show)

_DataComplementOf :: Name
_DataComplementOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataComplementOf")

-- | See https://www.w3.org/TR/owl2-syntax/#Enumeration_of_Literals
newtype DataOneOf = 
  DataOneOf {
    DataOneOf -> [Literal]
unDataOneOf :: [Syntax.Literal]}
  deriving (DataOneOf -> DataOneOf -> Bool
(DataOneOf -> DataOneOf -> Bool)
-> (DataOneOf -> DataOneOf -> Bool) -> Eq DataOneOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataOneOf -> DataOneOf -> Bool
== :: DataOneOf -> DataOneOf -> Bool
$c/= :: DataOneOf -> DataOneOf -> Bool
/= :: DataOneOf -> DataOneOf -> Bool
Eq, Eq DataOneOf
Eq DataOneOf =>
(DataOneOf -> DataOneOf -> Ordering)
-> (DataOneOf -> DataOneOf -> Bool)
-> (DataOneOf -> DataOneOf -> Bool)
-> (DataOneOf -> DataOneOf -> Bool)
-> (DataOneOf -> DataOneOf -> Bool)
-> (DataOneOf -> DataOneOf -> DataOneOf)
-> (DataOneOf -> DataOneOf -> DataOneOf)
-> Ord DataOneOf
DataOneOf -> DataOneOf -> Bool
DataOneOf -> DataOneOf -> Ordering
DataOneOf -> DataOneOf -> DataOneOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataOneOf -> DataOneOf -> Ordering
compare :: DataOneOf -> DataOneOf -> Ordering
$c< :: DataOneOf -> DataOneOf -> Bool
< :: DataOneOf -> DataOneOf -> Bool
$c<= :: DataOneOf -> DataOneOf -> Bool
<= :: DataOneOf -> DataOneOf -> Bool
$c> :: DataOneOf -> DataOneOf -> Bool
> :: DataOneOf -> DataOneOf -> Bool
$c>= :: DataOneOf -> DataOneOf -> Bool
>= :: DataOneOf -> DataOneOf -> Bool
$cmax :: DataOneOf -> DataOneOf -> DataOneOf
max :: DataOneOf -> DataOneOf -> DataOneOf
$cmin :: DataOneOf -> DataOneOf -> DataOneOf
min :: DataOneOf -> DataOneOf -> DataOneOf
Ord, ReadPrec [DataOneOf]
ReadPrec DataOneOf
Int -> ReadS DataOneOf
ReadS [DataOneOf]
(Int -> ReadS DataOneOf)
-> ReadS [DataOneOf]
-> ReadPrec DataOneOf
-> ReadPrec [DataOneOf]
-> Read DataOneOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataOneOf
readsPrec :: Int -> ReadS DataOneOf
$creadList :: ReadS [DataOneOf]
readList :: ReadS [DataOneOf]
$creadPrec :: ReadPrec DataOneOf
readPrec :: ReadPrec DataOneOf
$creadListPrec :: ReadPrec [DataOneOf]
readListPrec :: ReadPrec [DataOneOf]
Read, Int -> DataOneOf -> ShowS
[DataOneOf] -> ShowS
DataOneOf -> String
(Int -> DataOneOf -> ShowS)
-> (DataOneOf -> String)
-> ([DataOneOf] -> ShowS)
-> Show DataOneOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataOneOf -> ShowS
showsPrec :: Int -> DataOneOf -> ShowS
$cshow :: DataOneOf -> String
show :: DataOneOf -> String
$cshowList :: [DataOneOf] -> ShowS
showList :: [DataOneOf] -> ShowS
Show)

_DataOneOf :: Name
_DataOneOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataOneOf")

-- | See https://www.w3.org/TR/owl2-syntax/#Datatype_Restrictions
data DatatypeRestriction = 
  DatatypeRestriction {
    DatatypeRestriction -> Datatype
datatypeRestrictionDatatype :: Datatype,
    DatatypeRestriction -> [DatatypeRestriction_Constraint]
datatypeRestrictionConstraints :: [DatatypeRestriction_Constraint]}
  deriving (DatatypeRestriction -> DatatypeRestriction -> Bool
(DatatypeRestriction -> DatatypeRestriction -> Bool)
-> (DatatypeRestriction -> DatatypeRestriction -> Bool)
-> Eq DatatypeRestriction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatatypeRestriction -> DatatypeRestriction -> Bool
== :: DatatypeRestriction -> DatatypeRestriction -> Bool
$c/= :: DatatypeRestriction -> DatatypeRestriction -> Bool
/= :: DatatypeRestriction -> DatatypeRestriction -> Bool
Eq, Eq DatatypeRestriction
Eq DatatypeRestriction =>
(DatatypeRestriction -> DatatypeRestriction -> Ordering)
-> (DatatypeRestriction -> DatatypeRestriction -> Bool)
-> (DatatypeRestriction -> DatatypeRestriction -> Bool)
-> (DatatypeRestriction -> DatatypeRestriction -> Bool)
-> (DatatypeRestriction -> DatatypeRestriction -> Bool)
-> (DatatypeRestriction
    -> DatatypeRestriction -> DatatypeRestriction)
-> (DatatypeRestriction
    -> DatatypeRestriction -> DatatypeRestriction)
-> Ord DatatypeRestriction
DatatypeRestriction -> DatatypeRestriction -> Bool
DatatypeRestriction -> DatatypeRestriction -> Ordering
DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DatatypeRestriction -> DatatypeRestriction -> Ordering
compare :: DatatypeRestriction -> DatatypeRestriction -> Ordering
$c< :: DatatypeRestriction -> DatatypeRestriction -> Bool
< :: DatatypeRestriction -> DatatypeRestriction -> Bool
$c<= :: DatatypeRestriction -> DatatypeRestriction -> Bool
<= :: DatatypeRestriction -> DatatypeRestriction -> Bool
$c> :: DatatypeRestriction -> DatatypeRestriction -> Bool
> :: DatatypeRestriction -> DatatypeRestriction -> Bool
$c>= :: DatatypeRestriction -> DatatypeRestriction -> Bool
>= :: DatatypeRestriction -> DatatypeRestriction -> Bool
$cmax :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction
max :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction
$cmin :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction
min :: DatatypeRestriction -> DatatypeRestriction -> DatatypeRestriction
Ord, ReadPrec [DatatypeRestriction]
ReadPrec DatatypeRestriction
Int -> ReadS DatatypeRestriction
ReadS [DatatypeRestriction]
(Int -> ReadS DatatypeRestriction)
-> ReadS [DatatypeRestriction]
-> ReadPrec DatatypeRestriction
-> ReadPrec [DatatypeRestriction]
-> Read DatatypeRestriction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DatatypeRestriction
readsPrec :: Int -> ReadS DatatypeRestriction
$creadList :: ReadS [DatatypeRestriction]
readList :: ReadS [DatatypeRestriction]
$creadPrec :: ReadPrec DatatypeRestriction
readPrec :: ReadPrec DatatypeRestriction
$creadListPrec :: ReadPrec [DatatypeRestriction]
readListPrec :: ReadPrec [DatatypeRestriction]
Read, Int -> DatatypeRestriction -> ShowS
[DatatypeRestriction] -> ShowS
DatatypeRestriction -> String
(Int -> DatatypeRestriction -> ShowS)
-> (DatatypeRestriction -> String)
-> ([DatatypeRestriction] -> ShowS)
-> Show DatatypeRestriction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatatypeRestriction -> ShowS
showsPrec :: Int -> DatatypeRestriction -> ShowS
$cshow :: DatatypeRestriction -> String
show :: DatatypeRestriction -> String
$cshowList :: [DatatypeRestriction] -> ShowS
showList :: [DatatypeRestriction] -> ShowS
Show)

_DatatypeRestriction :: Name
_DatatypeRestriction = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DatatypeRestriction")

_DatatypeRestriction_datatype :: Name
_DatatypeRestriction_datatype = (String -> Name
Core.Name String
"datatype")

_DatatypeRestriction_constraints :: Name
_DatatypeRestriction_constraints = (String -> Name
Core.Name String
"constraints")

data DatatypeRestriction_Constraint = 
  DatatypeRestriction_Constraint {
    DatatypeRestriction_Constraint
-> DatatypeRestriction_ConstrainingFacet
datatypeRestriction_ConstraintConstrainingFacet :: DatatypeRestriction_ConstrainingFacet,
    DatatypeRestriction_Constraint -> Literal
datatypeRestriction_ConstraintRestrictionValue :: Syntax.Literal}
  deriving (DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
(DatatypeRestriction_Constraint
 -> DatatypeRestriction_Constraint -> Bool)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint -> Bool)
-> Eq DatatypeRestriction_Constraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
== :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
$c/= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
/= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
Eq, Eq DatatypeRestriction_Constraint
Eq DatatypeRestriction_Constraint =>
(DatatypeRestriction_Constraint
 -> DatatypeRestriction_Constraint -> Ordering)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint -> Bool)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint -> Bool)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint -> Bool)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint -> Bool)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint)
-> (DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint
    -> DatatypeRestriction_Constraint)
-> Ord DatatypeRestriction_Constraint
DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Ordering
DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> DatatypeRestriction_Constraint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Ordering
compare :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Ordering
$c< :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
< :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
$c<= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
<= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
$c> :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
> :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
$c>= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
>= :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> Bool
$cmax :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> DatatypeRestriction_Constraint
max :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> DatatypeRestriction_Constraint
$cmin :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> DatatypeRestriction_Constraint
min :: DatatypeRestriction_Constraint
-> DatatypeRestriction_Constraint -> DatatypeRestriction_Constraint
Ord, ReadPrec [DatatypeRestriction_Constraint]
ReadPrec DatatypeRestriction_Constraint
Int -> ReadS DatatypeRestriction_Constraint
ReadS [DatatypeRestriction_Constraint]
(Int -> ReadS DatatypeRestriction_Constraint)
-> ReadS [DatatypeRestriction_Constraint]
-> ReadPrec DatatypeRestriction_Constraint
-> ReadPrec [DatatypeRestriction_Constraint]
-> Read DatatypeRestriction_Constraint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DatatypeRestriction_Constraint
readsPrec :: Int -> ReadS DatatypeRestriction_Constraint
$creadList :: ReadS [DatatypeRestriction_Constraint]
readList :: ReadS [DatatypeRestriction_Constraint]
$creadPrec :: ReadPrec DatatypeRestriction_Constraint
readPrec :: ReadPrec DatatypeRestriction_Constraint
$creadListPrec :: ReadPrec [DatatypeRestriction_Constraint]
readListPrec :: ReadPrec [DatatypeRestriction_Constraint]
Read, Int -> DatatypeRestriction_Constraint -> ShowS
[DatatypeRestriction_Constraint] -> ShowS
DatatypeRestriction_Constraint -> String
(Int -> DatatypeRestriction_Constraint -> ShowS)
-> (DatatypeRestriction_Constraint -> String)
-> ([DatatypeRestriction_Constraint] -> ShowS)
-> Show DatatypeRestriction_Constraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatatypeRestriction_Constraint -> ShowS
showsPrec :: Int -> DatatypeRestriction_Constraint -> ShowS
$cshow :: DatatypeRestriction_Constraint -> String
show :: DatatypeRestriction_Constraint -> String
$cshowList :: [DatatypeRestriction_Constraint] -> ShowS
showList :: [DatatypeRestriction_Constraint] -> ShowS
Show)

_DatatypeRestriction_Constraint :: Name
_DatatypeRestriction_Constraint = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DatatypeRestriction.Constraint")

_DatatypeRestriction_Constraint_constrainingFacet :: Name
_DatatypeRestriction_Constraint_constrainingFacet = (String -> Name
Core.Name String
"constrainingFacet")

_DatatypeRestriction_Constraint_restrictionValue :: Name
_DatatypeRestriction_Constraint_restrictionValue = (String -> Name
Core.Name String
"restrictionValue")

data DatatypeRestriction_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_ConstrainingFacetXmlSchema Schema.ConstrainingFacet |
  DatatypeRestriction_ConstrainingFacetOther Syntax.Iri
  deriving (DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
(DatatypeRestriction_ConstrainingFacet
 -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> Eq DatatypeRestriction_ConstrainingFacet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
== :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
$c/= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
/= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
Eq, Eq DatatypeRestriction_ConstrainingFacet
Eq DatatypeRestriction_ConstrainingFacet =>
(DatatypeRestriction_ConstrainingFacet
 -> DatatypeRestriction_ConstrainingFacet -> Ordering)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet -> Bool)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet)
-> (DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet
    -> DatatypeRestriction_ConstrainingFacet)
-> Ord DatatypeRestriction_ConstrainingFacet
DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Ordering
DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Ordering
compare :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Ordering
$c< :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
< :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
$c<= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
<= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
$c> :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
> :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
$c>= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
>= :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet -> Bool
$cmax :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
max :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
$cmin :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
min :: DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
-> DatatypeRestriction_ConstrainingFacet
Ord, ReadPrec [DatatypeRestriction_ConstrainingFacet]
ReadPrec DatatypeRestriction_ConstrainingFacet
Int -> ReadS DatatypeRestriction_ConstrainingFacet
ReadS [DatatypeRestriction_ConstrainingFacet]
(Int -> ReadS DatatypeRestriction_ConstrainingFacet)
-> ReadS [DatatypeRestriction_ConstrainingFacet]
-> ReadPrec DatatypeRestriction_ConstrainingFacet
-> ReadPrec [DatatypeRestriction_ConstrainingFacet]
-> Read DatatypeRestriction_ConstrainingFacet
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DatatypeRestriction_ConstrainingFacet
readsPrec :: Int -> ReadS DatatypeRestriction_ConstrainingFacet
$creadList :: ReadS [DatatypeRestriction_ConstrainingFacet]
readList :: ReadS [DatatypeRestriction_ConstrainingFacet]
$creadPrec :: ReadPrec DatatypeRestriction_ConstrainingFacet
readPrec :: ReadPrec DatatypeRestriction_ConstrainingFacet
$creadListPrec :: ReadPrec [DatatypeRestriction_ConstrainingFacet]
readListPrec :: ReadPrec [DatatypeRestriction_ConstrainingFacet]
Read, Int -> DatatypeRestriction_ConstrainingFacet -> ShowS
[DatatypeRestriction_ConstrainingFacet] -> ShowS
DatatypeRestriction_ConstrainingFacet -> String
(Int -> DatatypeRestriction_ConstrainingFacet -> ShowS)
-> (DatatypeRestriction_ConstrainingFacet -> String)
-> ([DatatypeRestriction_ConstrainingFacet] -> ShowS)
-> Show DatatypeRestriction_ConstrainingFacet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatatypeRestriction_ConstrainingFacet -> ShowS
showsPrec :: Int -> DatatypeRestriction_ConstrainingFacet -> ShowS
$cshow :: DatatypeRestriction_ConstrainingFacet -> String
show :: DatatypeRestriction_ConstrainingFacet -> String
$cshowList :: [DatatypeRestriction_ConstrainingFacet] -> ShowS
showList :: [DatatypeRestriction_ConstrainingFacet] -> ShowS
Show)

_DatatypeRestriction_ConstrainingFacet :: Name
_DatatypeRestriction_ConstrainingFacet = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DatatypeRestriction.ConstrainingFacet")

_DatatypeRestriction_ConstrainingFacet_xmlSchema :: Name
_DatatypeRestriction_ConstrainingFacet_xmlSchema = (String -> Name
Core.Name String
"xmlSchema")

_DatatypeRestriction_ConstrainingFacet_other :: Name
_DatatypeRestriction_ConstrainingFacet_other = (String -> Name
Core.Name String
"other")

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
  deriving (ClassExpression -> ClassExpression -> Bool
(ClassExpression -> ClassExpression -> Bool)
-> (ClassExpression -> ClassExpression -> Bool)
-> Eq ClassExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClassExpression -> ClassExpression -> Bool
== :: ClassExpression -> ClassExpression -> Bool
$c/= :: ClassExpression -> ClassExpression -> Bool
/= :: ClassExpression -> ClassExpression -> Bool
Eq, Eq ClassExpression
Eq ClassExpression =>
(ClassExpression -> ClassExpression -> Ordering)
-> (ClassExpression -> ClassExpression -> Bool)
-> (ClassExpression -> ClassExpression -> Bool)
-> (ClassExpression -> ClassExpression -> Bool)
-> (ClassExpression -> ClassExpression -> Bool)
-> (ClassExpression -> ClassExpression -> ClassExpression)
-> (ClassExpression -> ClassExpression -> ClassExpression)
-> Ord ClassExpression
ClassExpression -> ClassExpression -> Bool
ClassExpression -> ClassExpression -> Ordering
ClassExpression -> ClassExpression -> ClassExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ClassExpression -> ClassExpression -> Ordering
compare :: ClassExpression -> ClassExpression -> Ordering
$c< :: ClassExpression -> ClassExpression -> Bool
< :: ClassExpression -> ClassExpression -> Bool
$c<= :: ClassExpression -> ClassExpression -> Bool
<= :: ClassExpression -> ClassExpression -> Bool
$c> :: ClassExpression -> ClassExpression -> Bool
> :: ClassExpression -> ClassExpression -> Bool
$c>= :: ClassExpression -> ClassExpression -> Bool
>= :: ClassExpression -> ClassExpression -> Bool
$cmax :: ClassExpression -> ClassExpression -> ClassExpression
max :: ClassExpression -> ClassExpression -> ClassExpression
$cmin :: ClassExpression -> ClassExpression -> ClassExpression
min :: ClassExpression -> ClassExpression -> ClassExpression
Ord, ReadPrec [ClassExpression]
ReadPrec ClassExpression
Int -> ReadS ClassExpression
ReadS [ClassExpression]
(Int -> ReadS ClassExpression)
-> ReadS [ClassExpression]
-> ReadPrec ClassExpression
-> ReadPrec [ClassExpression]
-> Read ClassExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ClassExpression
readsPrec :: Int -> ReadS ClassExpression
$creadList :: ReadS [ClassExpression]
readList :: ReadS [ClassExpression]
$creadPrec :: ReadPrec ClassExpression
readPrec :: ReadPrec ClassExpression
$creadListPrec :: ReadPrec [ClassExpression]
readListPrec :: ReadPrec [ClassExpression]
Read, Int -> ClassExpression -> ShowS
[ClassExpression] -> ShowS
ClassExpression -> String
(Int -> ClassExpression -> ShowS)
-> (ClassExpression -> String)
-> ([ClassExpression] -> ShowS)
-> Show ClassExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClassExpression -> ShowS
showsPrec :: Int -> ClassExpression -> ShowS
$cshow :: ClassExpression -> String
show :: ClassExpression -> String
$cshowList :: [ClassExpression] -> ShowS
showList :: [ClassExpression] -> ShowS
Show)

_ClassExpression :: Name
_ClassExpression = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ClassExpression")

_ClassExpression_class :: Name
_ClassExpression_class = (String -> Name
Core.Name String
"class")

_ClassExpression_dataSomeValuesFrom :: Name
_ClassExpression_dataSomeValuesFrom = (String -> Name
Core.Name String
"dataSomeValuesFrom")

_ClassExpression_dataAllValuesFrom :: Name
_ClassExpression_dataAllValuesFrom = (String -> Name
Core.Name String
"dataAllValuesFrom")

_ClassExpression_dataHasValue :: Name
_ClassExpression_dataHasValue = (String -> Name
Core.Name String
"dataHasValue")

_ClassExpression_dataMinCardinality :: Name
_ClassExpression_dataMinCardinality = (String -> Name
Core.Name String
"dataMinCardinality")

_ClassExpression_dataMaxCardinality :: Name
_ClassExpression_dataMaxCardinality = (String -> Name
Core.Name String
"dataMaxCardinality")

_ClassExpression_dataExactCardinality :: Name
_ClassExpression_dataExactCardinality = (String -> Name
Core.Name String
"dataExactCardinality")

_ClassExpression_objectAllValuesFrom :: Name
_ClassExpression_objectAllValuesFrom = (String -> Name
Core.Name String
"objectAllValuesFrom")

_ClassExpression_objectExactCardinality :: Name
_ClassExpression_objectExactCardinality = (String -> Name
Core.Name String
"objectExactCardinality")

_ClassExpression_objectHasSelf :: Name
_ClassExpression_objectHasSelf = (String -> Name
Core.Name String
"objectHasSelf")

_ClassExpression_objectHasValue :: Name
_ClassExpression_objectHasValue = (String -> Name
Core.Name String
"objectHasValue")

_ClassExpression_objectIntersectionOf :: Name
_ClassExpression_objectIntersectionOf = (String -> Name
Core.Name String
"objectIntersectionOf")

_ClassExpression_objectMaxCardinality :: Name
_ClassExpression_objectMaxCardinality = (String -> Name
Core.Name String
"objectMaxCardinality")

_ClassExpression_objectMinCardinality :: Name
_ClassExpression_objectMinCardinality = (String -> Name
Core.Name String
"objectMinCardinality")

_ClassExpression_objectOneOf :: Name
_ClassExpression_objectOneOf = (String -> Name
Core.Name String
"objectOneOf")

_ClassExpression_objectSomeValuesFrom :: Name
_ClassExpression_objectSomeValuesFrom = (String -> Name
Core.Name String
"objectSomeValuesFrom")

_ClassExpression_objectUnionOf :: Name
_ClassExpression_objectUnionOf = (String -> Name
Core.Name String
"objectUnionOf")

newtype ObjectIntersectionOf = 
  ObjectIntersectionOf {
    ObjectIntersectionOf -> [ClassExpression]
unObjectIntersectionOf :: [ClassExpression]}
  deriving (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
(ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> Eq ObjectIntersectionOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
== :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
$c/= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
/= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
Eq, Eq ObjectIntersectionOf
Eq ObjectIntersectionOf =>
(ObjectIntersectionOf -> ObjectIntersectionOf -> Ordering)
-> (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> (ObjectIntersectionOf -> ObjectIntersectionOf -> Bool)
-> (ObjectIntersectionOf
    -> ObjectIntersectionOf -> ObjectIntersectionOf)
-> (ObjectIntersectionOf
    -> ObjectIntersectionOf -> ObjectIntersectionOf)
-> Ord ObjectIntersectionOf
ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
ObjectIntersectionOf -> ObjectIntersectionOf -> Ordering
ObjectIntersectionOf
-> ObjectIntersectionOf -> ObjectIntersectionOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectIntersectionOf -> ObjectIntersectionOf -> Ordering
compare :: ObjectIntersectionOf -> ObjectIntersectionOf -> Ordering
$c< :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
< :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
$c<= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
<= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
$c> :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
> :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
$c>= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
>= :: ObjectIntersectionOf -> ObjectIntersectionOf -> Bool
$cmax :: ObjectIntersectionOf
-> ObjectIntersectionOf -> ObjectIntersectionOf
max :: ObjectIntersectionOf
-> ObjectIntersectionOf -> ObjectIntersectionOf
$cmin :: ObjectIntersectionOf
-> ObjectIntersectionOf -> ObjectIntersectionOf
min :: ObjectIntersectionOf
-> ObjectIntersectionOf -> ObjectIntersectionOf
Ord, ReadPrec [ObjectIntersectionOf]
ReadPrec ObjectIntersectionOf
Int -> ReadS ObjectIntersectionOf
ReadS [ObjectIntersectionOf]
(Int -> ReadS ObjectIntersectionOf)
-> ReadS [ObjectIntersectionOf]
-> ReadPrec ObjectIntersectionOf
-> ReadPrec [ObjectIntersectionOf]
-> Read ObjectIntersectionOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectIntersectionOf
readsPrec :: Int -> ReadS ObjectIntersectionOf
$creadList :: ReadS [ObjectIntersectionOf]
readList :: ReadS [ObjectIntersectionOf]
$creadPrec :: ReadPrec ObjectIntersectionOf
readPrec :: ReadPrec ObjectIntersectionOf
$creadListPrec :: ReadPrec [ObjectIntersectionOf]
readListPrec :: ReadPrec [ObjectIntersectionOf]
Read, Int -> ObjectIntersectionOf -> ShowS
[ObjectIntersectionOf] -> ShowS
ObjectIntersectionOf -> String
(Int -> ObjectIntersectionOf -> ShowS)
-> (ObjectIntersectionOf -> String)
-> ([ObjectIntersectionOf] -> ShowS)
-> Show ObjectIntersectionOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectIntersectionOf -> ShowS
showsPrec :: Int -> ObjectIntersectionOf -> ShowS
$cshow :: ObjectIntersectionOf -> String
show :: ObjectIntersectionOf -> String
$cshowList :: [ObjectIntersectionOf] -> ShowS
showList :: [ObjectIntersectionOf] -> ShowS
Show)

_ObjectIntersectionOf :: Name
_ObjectIntersectionOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectIntersectionOf")

newtype ObjectUnionOf = 
  ObjectUnionOf {
    ObjectUnionOf -> [ClassExpression]
unObjectUnionOf :: [ClassExpression]}
  deriving (ObjectUnionOf -> ObjectUnionOf -> Bool
(ObjectUnionOf -> ObjectUnionOf -> Bool)
-> (ObjectUnionOf -> ObjectUnionOf -> Bool) -> Eq ObjectUnionOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectUnionOf -> ObjectUnionOf -> Bool
== :: ObjectUnionOf -> ObjectUnionOf -> Bool
$c/= :: ObjectUnionOf -> ObjectUnionOf -> Bool
/= :: ObjectUnionOf -> ObjectUnionOf -> Bool
Eq, Eq ObjectUnionOf
Eq ObjectUnionOf =>
(ObjectUnionOf -> ObjectUnionOf -> Ordering)
-> (ObjectUnionOf -> ObjectUnionOf -> Bool)
-> (ObjectUnionOf -> ObjectUnionOf -> Bool)
-> (ObjectUnionOf -> ObjectUnionOf -> Bool)
-> (ObjectUnionOf -> ObjectUnionOf -> Bool)
-> (ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf)
-> (ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf)
-> Ord ObjectUnionOf
ObjectUnionOf -> ObjectUnionOf -> Bool
ObjectUnionOf -> ObjectUnionOf -> Ordering
ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectUnionOf -> ObjectUnionOf -> Ordering
compare :: ObjectUnionOf -> ObjectUnionOf -> Ordering
$c< :: ObjectUnionOf -> ObjectUnionOf -> Bool
< :: ObjectUnionOf -> ObjectUnionOf -> Bool
$c<= :: ObjectUnionOf -> ObjectUnionOf -> Bool
<= :: ObjectUnionOf -> ObjectUnionOf -> Bool
$c> :: ObjectUnionOf -> ObjectUnionOf -> Bool
> :: ObjectUnionOf -> ObjectUnionOf -> Bool
$c>= :: ObjectUnionOf -> ObjectUnionOf -> Bool
>= :: ObjectUnionOf -> ObjectUnionOf -> Bool
$cmax :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf
max :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf
$cmin :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf
min :: ObjectUnionOf -> ObjectUnionOf -> ObjectUnionOf
Ord, ReadPrec [ObjectUnionOf]
ReadPrec ObjectUnionOf
Int -> ReadS ObjectUnionOf
ReadS [ObjectUnionOf]
(Int -> ReadS ObjectUnionOf)
-> ReadS [ObjectUnionOf]
-> ReadPrec ObjectUnionOf
-> ReadPrec [ObjectUnionOf]
-> Read ObjectUnionOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectUnionOf
readsPrec :: Int -> ReadS ObjectUnionOf
$creadList :: ReadS [ObjectUnionOf]
readList :: ReadS [ObjectUnionOf]
$creadPrec :: ReadPrec ObjectUnionOf
readPrec :: ReadPrec ObjectUnionOf
$creadListPrec :: ReadPrec [ObjectUnionOf]
readListPrec :: ReadPrec [ObjectUnionOf]
Read, Int -> ObjectUnionOf -> ShowS
[ObjectUnionOf] -> ShowS
ObjectUnionOf -> String
(Int -> ObjectUnionOf -> ShowS)
-> (ObjectUnionOf -> String)
-> ([ObjectUnionOf] -> ShowS)
-> Show ObjectUnionOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectUnionOf -> ShowS
showsPrec :: Int -> ObjectUnionOf -> ShowS
$cshow :: ObjectUnionOf -> String
show :: ObjectUnionOf -> String
$cshowList :: [ObjectUnionOf] -> ShowS
showList :: [ObjectUnionOf] -> ShowS
Show)

_ObjectUnionOf :: Name
_ObjectUnionOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectUnionOf")

newtype ObjectComplementOf = 
  ObjectComplementOf {
    ObjectComplementOf -> ClassExpression
unObjectComplementOf :: ClassExpression}
  deriving (ObjectComplementOf -> ObjectComplementOf -> Bool
(ObjectComplementOf -> ObjectComplementOf -> Bool)
-> (ObjectComplementOf -> ObjectComplementOf -> Bool)
-> Eq ObjectComplementOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectComplementOf -> ObjectComplementOf -> Bool
== :: ObjectComplementOf -> ObjectComplementOf -> Bool
$c/= :: ObjectComplementOf -> ObjectComplementOf -> Bool
/= :: ObjectComplementOf -> ObjectComplementOf -> Bool
Eq, Eq ObjectComplementOf
Eq ObjectComplementOf =>
(ObjectComplementOf -> ObjectComplementOf -> Ordering)
-> (ObjectComplementOf -> ObjectComplementOf -> Bool)
-> (ObjectComplementOf -> ObjectComplementOf -> Bool)
-> (ObjectComplementOf -> ObjectComplementOf -> Bool)
-> (ObjectComplementOf -> ObjectComplementOf -> Bool)
-> (ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf)
-> (ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf)
-> Ord ObjectComplementOf
ObjectComplementOf -> ObjectComplementOf -> Bool
ObjectComplementOf -> ObjectComplementOf -> Ordering
ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectComplementOf -> ObjectComplementOf -> Ordering
compare :: ObjectComplementOf -> ObjectComplementOf -> Ordering
$c< :: ObjectComplementOf -> ObjectComplementOf -> Bool
< :: ObjectComplementOf -> ObjectComplementOf -> Bool
$c<= :: ObjectComplementOf -> ObjectComplementOf -> Bool
<= :: ObjectComplementOf -> ObjectComplementOf -> Bool
$c> :: ObjectComplementOf -> ObjectComplementOf -> Bool
> :: ObjectComplementOf -> ObjectComplementOf -> Bool
$c>= :: ObjectComplementOf -> ObjectComplementOf -> Bool
>= :: ObjectComplementOf -> ObjectComplementOf -> Bool
$cmax :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf
max :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf
$cmin :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf
min :: ObjectComplementOf -> ObjectComplementOf -> ObjectComplementOf
Ord, ReadPrec [ObjectComplementOf]
ReadPrec ObjectComplementOf
Int -> ReadS ObjectComplementOf
ReadS [ObjectComplementOf]
(Int -> ReadS ObjectComplementOf)
-> ReadS [ObjectComplementOf]
-> ReadPrec ObjectComplementOf
-> ReadPrec [ObjectComplementOf]
-> Read ObjectComplementOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectComplementOf
readsPrec :: Int -> ReadS ObjectComplementOf
$creadList :: ReadS [ObjectComplementOf]
readList :: ReadS [ObjectComplementOf]
$creadPrec :: ReadPrec ObjectComplementOf
readPrec :: ReadPrec ObjectComplementOf
$creadListPrec :: ReadPrec [ObjectComplementOf]
readListPrec :: ReadPrec [ObjectComplementOf]
Read, Int -> ObjectComplementOf -> ShowS
[ObjectComplementOf] -> ShowS
ObjectComplementOf -> String
(Int -> ObjectComplementOf -> ShowS)
-> (ObjectComplementOf -> String)
-> ([ObjectComplementOf] -> ShowS)
-> Show ObjectComplementOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectComplementOf -> ShowS
showsPrec :: Int -> ObjectComplementOf -> ShowS
$cshow :: ObjectComplementOf -> String
show :: ObjectComplementOf -> String
$cshowList :: [ObjectComplementOf] -> ShowS
showList :: [ObjectComplementOf] -> ShowS
Show)

_ObjectComplementOf :: Name
_ObjectComplementOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectComplementOf")

newtype ObjectOneOf = 
  ObjectOneOf {
    ObjectOneOf -> [Individual]
unObjectOneOf :: [Individual]}
  deriving (ObjectOneOf -> ObjectOneOf -> Bool
(ObjectOneOf -> ObjectOneOf -> Bool)
-> (ObjectOneOf -> ObjectOneOf -> Bool) -> Eq ObjectOneOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectOneOf -> ObjectOneOf -> Bool
== :: ObjectOneOf -> ObjectOneOf -> Bool
$c/= :: ObjectOneOf -> ObjectOneOf -> Bool
/= :: ObjectOneOf -> ObjectOneOf -> Bool
Eq, Eq ObjectOneOf
Eq ObjectOneOf =>
(ObjectOneOf -> ObjectOneOf -> Ordering)
-> (ObjectOneOf -> ObjectOneOf -> Bool)
-> (ObjectOneOf -> ObjectOneOf -> Bool)
-> (ObjectOneOf -> ObjectOneOf -> Bool)
-> (ObjectOneOf -> ObjectOneOf -> Bool)
-> (ObjectOneOf -> ObjectOneOf -> ObjectOneOf)
-> (ObjectOneOf -> ObjectOneOf -> ObjectOneOf)
-> Ord ObjectOneOf
ObjectOneOf -> ObjectOneOf -> Bool
ObjectOneOf -> ObjectOneOf -> Ordering
ObjectOneOf -> ObjectOneOf -> ObjectOneOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectOneOf -> ObjectOneOf -> Ordering
compare :: ObjectOneOf -> ObjectOneOf -> Ordering
$c< :: ObjectOneOf -> ObjectOneOf -> Bool
< :: ObjectOneOf -> ObjectOneOf -> Bool
$c<= :: ObjectOneOf -> ObjectOneOf -> Bool
<= :: ObjectOneOf -> ObjectOneOf -> Bool
$c> :: ObjectOneOf -> ObjectOneOf -> Bool
> :: ObjectOneOf -> ObjectOneOf -> Bool
$c>= :: ObjectOneOf -> ObjectOneOf -> Bool
>= :: ObjectOneOf -> ObjectOneOf -> Bool
$cmax :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf
max :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf
$cmin :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf
min :: ObjectOneOf -> ObjectOneOf -> ObjectOneOf
Ord, ReadPrec [ObjectOneOf]
ReadPrec ObjectOneOf
Int -> ReadS ObjectOneOf
ReadS [ObjectOneOf]
(Int -> ReadS ObjectOneOf)
-> ReadS [ObjectOneOf]
-> ReadPrec ObjectOneOf
-> ReadPrec [ObjectOneOf]
-> Read ObjectOneOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectOneOf
readsPrec :: Int -> ReadS ObjectOneOf
$creadList :: ReadS [ObjectOneOf]
readList :: ReadS [ObjectOneOf]
$creadPrec :: ReadPrec ObjectOneOf
readPrec :: ReadPrec ObjectOneOf
$creadListPrec :: ReadPrec [ObjectOneOf]
readListPrec :: ReadPrec [ObjectOneOf]
Read, Int -> ObjectOneOf -> ShowS
[ObjectOneOf] -> ShowS
ObjectOneOf -> String
(Int -> ObjectOneOf -> ShowS)
-> (ObjectOneOf -> String)
-> ([ObjectOneOf] -> ShowS)
-> Show ObjectOneOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectOneOf -> ShowS
showsPrec :: Int -> ObjectOneOf -> ShowS
$cshow :: ObjectOneOf -> String
show :: ObjectOneOf -> String
$cshowList :: [ObjectOneOf] -> ShowS
showList :: [ObjectOneOf] -> ShowS
Show)

_ObjectOneOf :: Name
_ObjectOneOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectOneOf")

data ObjectSomeValuesFrom = 
  ObjectSomeValuesFrom {
    ObjectSomeValuesFrom -> ObjectPropertyExpression
objectSomeValuesFromProperty :: ObjectPropertyExpression,
    ObjectSomeValuesFrom -> ClassExpression
objectSomeValuesFromClass :: ClassExpression}
  deriving (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
(ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> Eq ObjectSomeValuesFrom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
== :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
$c/= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
/= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
Eq, Eq ObjectSomeValuesFrom
Eq ObjectSomeValuesFrom =>
(ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Ordering)
-> (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> (ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool)
-> (ObjectSomeValuesFrom
    -> ObjectSomeValuesFrom -> ObjectSomeValuesFrom)
-> (ObjectSomeValuesFrom
    -> ObjectSomeValuesFrom -> ObjectSomeValuesFrom)
-> Ord ObjectSomeValuesFrom
ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Ordering
ObjectSomeValuesFrom
-> ObjectSomeValuesFrom -> ObjectSomeValuesFrom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Ordering
compare :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Ordering
$c< :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
< :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
$c<= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
<= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
$c> :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
> :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
$c>= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
>= :: ObjectSomeValuesFrom -> ObjectSomeValuesFrom -> Bool
$cmax :: ObjectSomeValuesFrom
-> ObjectSomeValuesFrom -> ObjectSomeValuesFrom
max :: ObjectSomeValuesFrom
-> ObjectSomeValuesFrom -> ObjectSomeValuesFrom
$cmin :: ObjectSomeValuesFrom
-> ObjectSomeValuesFrom -> ObjectSomeValuesFrom
min :: ObjectSomeValuesFrom
-> ObjectSomeValuesFrom -> ObjectSomeValuesFrom
Ord, ReadPrec [ObjectSomeValuesFrom]
ReadPrec ObjectSomeValuesFrom
Int -> ReadS ObjectSomeValuesFrom
ReadS [ObjectSomeValuesFrom]
(Int -> ReadS ObjectSomeValuesFrom)
-> ReadS [ObjectSomeValuesFrom]
-> ReadPrec ObjectSomeValuesFrom
-> ReadPrec [ObjectSomeValuesFrom]
-> Read ObjectSomeValuesFrom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectSomeValuesFrom
readsPrec :: Int -> ReadS ObjectSomeValuesFrom
$creadList :: ReadS [ObjectSomeValuesFrom]
readList :: ReadS [ObjectSomeValuesFrom]
$creadPrec :: ReadPrec ObjectSomeValuesFrom
readPrec :: ReadPrec ObjectSomeValuesFrom
$creadListPrec :: ReadPrec [ObjectSomeValuesFrom]
readListPrec :: ReadPrec [ObjectSomeValuesFrom]
Read, Int -> ObjectSomeValuesFrom -> ShowS
[ObjectSomeValuesFrom] -> ShowS
ObjectSomeValuesFrom -> String
(Int -> ObjectSomeValuesFrom -> ShowS)
-> (ObjectSomeValuesFrom -> String)
-> ([ObjectSomeValuesFrom] -> ShowS)
-> Show ObjectSomeValuesFrom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectSomeValuesFrom -> ShowS
showsPrec :: Int -> ObjectSomeValuesFrom -> ShowS
$cshow :: ObjectSomeValuesFrom -> String
show :: ObjectSomeValuesFrom -> String
$cshowList :: [ObjectSomeValuesFrom] -> ShowS
showList :: [ObjectSomeValuesFrom] -> ShowS
Show)

_ObjectSomeValuesFrom :: Name
_ObjectSomeValuesFrom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectSomeValuesFrom")

_ObjectSomeValuesFrom_property :: Name
_ObjectSomeValuesFrom_property = (String -> Name
Core.Name String
"property")

_ObjectSomeValuesFrom_class :: Name
_ObjectSomeValuesFrom_class = (String -> Name
Core.Name String
"class")

data ObjectAllValuesFrom = 
  ObjectAllValuesFrom {
    ObjectAllValuesFrom -> ObjectPropertyExpression
objectAllValuesFromProperty :: ObjectPropertyExpression,
    ObjectAllValuesFrom -> ClassExpression
objectAllValuesFromClass :: ClassExpression}
  deriving (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
(ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> Eq ObjectAllValuesFrom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
== :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
$c/= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
/= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
Eq, Eq ObjectAllValuesFrom
Eq ObjectAllValuesFrom =>
(ObjectAllValuesFrom -> ObjectAllValuesFrom -> Ordering)
-> (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> (ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool)
-> (ObjectAllValuesFrom
    -> ObjectAllValuesFrom -> ObjectAllValuesFrom)
-> (ObjectAllValuesFrom
    -> ObjectAllValuesFrom -> ObjectAllValuesFrom)
-> Ord ObjectAllValuesFrom
ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
ObjectAllValuesFrom -> ObjectAllValuesFrom -> Ordering
ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Ordering
compare :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Ordering
$c< :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
< :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
$c<= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
<= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
$c> :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
> :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
$c>= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
>= :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> Bool
$cmax :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom
max :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom
$cmin :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom
min :: ObjectAllValuesFrom -> ObjectAllValuesFrom -> ObjectAllValuesFrom
Ord, ReadPrec [ObjectAllValuesFrom]
ReadPrec ObjectAllValuesFrom
Int -> ReadS ObjectAllValuesFrom
ReadS [ObjectAllValuesFrom]
(Int -> ReadS ObjectAllValuesFrom)
-> ReadS [ObjectAllValuesFrom]
-> ReadPrec ObjectAllValuesFrom
-> ReadPrec [ObjectAllValuesFrom]
-> Read ObjectAllValuesFrom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectAllValuesFrom
readsPrec :: Int -> ReadS ObjectAllValuesFrom
$creadList :: ReadS [ObjectAllValuesFrom]
readList :: ReadS [ObjectAllValuesFrom]
$creadPrec :: ReadPrec ObjectAllValuesFrom
readPrec :: ReadPrec ObjectAllValuesFrom
$creadListPrec :: ReadPrec [ObjectAllValuesFrom]
readListPrec :: ReadPrec [ObjectAllValuesFrom]
Read, Int -> ObjectAllValuesFrom -> ShowS
[ObjectAllValuesFrom] -> ShowS
ObjectAllValuesFrom -> String
(Int -> ObjectAllValuesFrom -> ShowS)
-> (ObjectAllValuesFrom -> String)
-> ([ObjectAllValuesFrom] -> ShowS)
-> Show ObjectAllValuesFrom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectAllValuesFrom -> ShowS
showsPrec :: Int -> ObjectAllValuesFrom -> ShowS
$cshow :: ObjectAllValuesFrom -> String
show :: ObjectAllValuesFrom -> String
$cshowList :: [ObjectAllValuesFrom] -> ShowS
showList :: [ObjectAllValuesFrom] -> ShowS
Show)

_ObjectAllValuesFrom :: Name
_ObjectAllValuesFrom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectAllValuesFrom")

_ObjectAllValuesFrom_property :: Name
_ObjectAllValuesFrom_property = (String -> Name
Core.Name String
"property")

_ObjectAllValuesFrom_class :: Name
_ObjectAllValuesFrom_class = (String -> Name
Core.Name String
"class")

data ObjectHasValue = 
  ObjectHasValue {
    ObjectHasValue -> ObjectPropertyExpression
objectHasValueProperty :: ObjectPropertyExpression,
    ObjectHasValue -> Individual
objectHasValueIndividual :: Individual}
  deriving (ObjectHasValue -> ObjectHasValue -> Bool
(ObjectHasValue -> ObjectHasValue -> Bool)
-> (ObjectHasValue -> ObjectHasValue -> Bool) -> Eq ObjectHasValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectHasValue -> ObjectHasValue -> Bool
== :: ObjectHasValue -> ObjectHasValue -> Bool
$c/= :: ObjectHasValue -> ObjectHasValue -> Bool
/= :: ObjectHasValue -> ObjectHasValue -> Bool
Eq, Eq ObjectHasValue
Eq ObjectHasValue =>
(ObjectHasValue -> ObjectHasValue -> Ordering)
-> (ObjectHasValue -> ObjectHasValue -> Bool)
-> (ObjectHasValue -> ObjectHasValue -> Bool)
-> (ObjectHasValue -> ObjectHasValue -> Bool)
-> (ObjectHasValue -> ObjectHasValue -> Bool)
-> (ObjectHasValue -> ObjectHasValue -> ObjectHasValue)
-> (ObjectHasValue -> ObjectHasValue -> ObjectHasValue)
-> Ord ObjectHasValue
ObjectHasValue -> ObjectHasValue -> Bool
ObjectHasValue -> ObjectHasValue -> Ordering
ObjectHasValue -> ObjectHasValue -> ObjectHasValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectHasValue -> ObjectHasValue -> Ordering
compare :: ObjectHasValue -> ObjectHasValue -> Ordering
$c< :: ObjectHasValue -> ObjectHasValue -> Bool
< :: ObjectHasValue -> ObjectHasValue -> Bool
$c<= :: ObjectHasValue -> ObjectHasValue -> Bool
<= :: ObjectHasValue -> ObjectHasValue -> Bool
$c> :: ObjectHasValue -> ObjectHasValue -> Bool
> :: ObjectHasValue -> ObjectHasValue -> Bool
$c>= :: ObjectHasValue -> ObjectHasValue -> Bool
>= :: ObjectHasValue -> ObjectHasValue -> Bool
$cmax :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue
max :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue
$cmin :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue
min :: ObjectHasValue -> ObjectHasValue -> ObjectHasValue
Ord, ReadPrec [ObjectHasValue]
ReadPrec ObjectHasValue
Int -> ReadS ObjectHasValue
ReadS [ObjectHasValue]
(Int -> ReadS ObjectHasValue)
-> ReadS [ObjectHasValue]
-> ReadPrec ObjectHasValue
-> ReadPrec [ObjectHasValue]
-> Read ObjectHasValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectHasValue
readsPrec :: Int -> ReadS ObjectHasValue
$creadList :: ReadS [ObjectHasValue]
readList :: ReadS [ObjectHasValue]
$creadPrec :: ReadPrec ObjectHasValue
readPrec :: ReadPrec ObjectHasValue
$creadListPrec :: ReadPrec [ObjectHasValue]
readListPrec :: ReadPrec [ObjectHasValue]
Read, Int -> ObjectHasValue -> ShowS
[ObjectHasValue] -> ShowS
ObjectHasValue -> String
(Int -> ObjectHasValue -> ShowS)
-> (ObjectHasValue -> String)
-> ([ObjectHasValue] -> ShowS)
-> Show ObjectHasValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectHasValue -> ShowS
showsPrec :: Int -> ObjectHasValue -> ShowS
$cshow :: ObjectHasValue -> String
show :: ObjectHasValue -> String
$cshowList :: [ObjectHasValue] -> ShowS
showList :: [ObjectHasValue] -> ShowS
Show)

_ObjectHasValue :: Name
_ObjectHasValue = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectHasValue")

_ObjectHasValue_property :: Name
_ObjectHasValue_property = (String -> Name
Core.Name String
"property")

_ObjectHasValue_individual :: Name
_ObjectHasValue_individual = (String -> Name
Core.Name String
"individual")

newtype ObjectHasSelf = 
  ObjectHasSelf {
    ObjectHasSelf -> ObjectPropertyExpression
unObjectHasSelf :: ObjectPropertyExpression}
  deriving (ObjectHasSelf -> ObjectHasSelf -> Bool
(ObjectHasSelf -> ObjectHasSelf -> Bool)
-> (ObjectHasSelf -> ObjectHasSelf -> Bool) -> Eq ObjectHasSelf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectHasSelf -> ObjectHasSelf -> Bool
== :: ObjectHasSelf -> ObjectHasSelf -> Bool
$c/= :: ObjectHasSelf -> ObjectHasSelf -> Bool
/= :: ObjectHasSelf -> ObjectHasSelf -> Bool
Eq, Eq ObjectHasSelf
Eq ObjectHasSelf =>
(ObjectHasSelf -> ObjectHasSelf -> Ordering)
-> (ObjectHasSelf -> ObjectHasSelf -> Bool)
-> (ObjectHasSelf -> ObjectHasSelf -> Bool)
-> (ObjectHasSelf -> ObjectHasSelf -> Bool)
-> (ObjectHasSelf -> ObjectHasSelf -> Bool)
-> (ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf)
-> (ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf)
-> Ord ObjectHasSelf
ObjectHasSelf -> ObjectHasSelf -> Bool
ObjectHasSelf -> ObjectHasSelf -> Ordering
ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectHasSelf -> ObjectHasSelf -> Ordering
compare :: ObjectHasSelf -> ObjectHasSelf -> Ordering
$c< :: ObjectHasSelf -> ObjectHasSelf -> Bool
< :: ObjectHasSelf -> ObjectHasSelf -> Bool
$c<= :: ObjectHasSelf -> ObjectHasSelf -> Bool
<= :: ObjectHasSelf -> ObjectHasSelf -> Bool
$c> :: ObjectHasSelf -> ObjectHasSelf -> Bool
> :: ObjectHasSelf -> ObjectHasSelf -> Bool
$c>= :: ObjectHasSelf -> ObjectHasSelf -> Bool
>= :: ObjectHasSelf -> ObjectHasSelf -> Bool
$cmax :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf
max :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf
$cmin :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf
min :: ObjectHasSelf -> ObjectHasSelf -> ObjectHasSelf
Ord, ReadPrec [ObjectHasSelf]
ReadPrec ObjectHasSelf
Int -> ReadS ObjectHasSelf
ReadS [ObjectHasSelf]
(Int -> ReadS ObjectHasSelf)
-> ReadS [ObjectHasSelf]
-> ReadPrec ObjectHasSelf
-> ReadPrec [ObjectHasSelf]
-> Read ObjectHasSelf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectHasSelf
readsPrec :: Int -> ReadS ObjectHasSelf
$creadList :: ReadS [ObjectHasSelf]
readList :: ReadS [ObjectHasSelf]
$creadPrec :: ReadPrec ObjectHasSelf
readPrec :: ReadPrec ObjectHasSelf
$creadListPrec :: ReadPrec [ObjectHasSelf]
readListPrec :: ReadPrec [ObjectHasSelf]
Read, Int -> ObjectHasSelf -> ShowS
[ObjectHasSelf] -> ShowS
ObjectHasSelf -> String
(Int -> ObjectHasSelf -> ShowS)
-> (ObjectHasSelf -> String)
-> ([ObjectHasSelf] -> ShowS)
-> Show ObjectHasSelf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectHasSelf -> ShowS
showsPrec :: Int -> ObjectHasSelf -> ShowS
$cshow :: ObjectHasSelf -> String
show :: ObjectHasSelf -> String
$cshowList :: [ObjectHasSelf] -> ShowS
showList :: [ObjectHasSelf] -> ShowS
Show)

_ObjectHasSelf :: Name
_ObjectHasSelf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectHasSelf")

-- | See https://www.w3.org/TR/owl2-syntax/#Minimum_Cardinality
data ObjectMinCardinality = 
  ObjectMinCardinality {
    ObjectMinCardinality -> Integer
objectMinCardinalityBound :: Integer,
    ObjectMinCardinality -> ObjectPropertyExpression
objectMinCardinalityProperty :: ObjectPropertyExpression,
    ObjectMinCardinality -> [ClassExpression]
objectMinCardinalityClass :: [ClassExpression]}
  deriving (ObjectMinCardinality -> ObjectMinCardinality -> Bool
(ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> (ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> Eq ObjectMinCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
== :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
$c/= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
/= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
Eq, Eq ObjectMinCardinality
Eq ObjectMinCardinality =>
(ObjectMinCardinality -> ObjectMinCardinality -> Ordering)
-> (ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> (ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> (ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> (ObjectMinCardinality -> ObjectMinCardinality -> Bool)
-> (ObjectMinCardinality
    -> ObjectMinCardinality -> ObjectMinCardinality)
-> (ObjectMinCardinality
    -> ObjectMinCardinality -> ObjectMinCardinality)
-> Ord ObjectMinCardinality
ObjectMinCardinality -> ObjectMinCardinality -> Bool
ObjectMinCardinality -> ObjectMinCardinality -> Ordering
ObjectMinCardinality
-> ObjectMinCardinality -> ObjectMinCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectMinCardinality -> ObjectMinCardinality -> Ordering
compare :: ObjectMinCardinality -> ObjectMinCardinality -> Ordering
$c< :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
< :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
$c<= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
<= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
$c> :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
> :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
$c>= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
>= :: ObjectMinCardinality -> ObjectMinCardinality -> Bool
$cmax :: ObjectMinCardinality
-> ObjectMinCardinality -> ObjectMinCardinality
max :: ObjectMinCardinality
-> ObjectMinCardinality -> ObjectMinCardinality
$cmin :: ObjectMinCardinality
-> ObjectMinCardinality -> ObjectMinCardinality
min :: ObjectMinCardinality
-> ObjectMinCardinality -> ObjectMinCardinality
Ord, ReadPrec [ObjectMinCardinality]
ReadPrec ObjectMinCardinality
Int -> ReadS ObjectMinCardinality
ReadS [ObjectMinCardinality]
(Int -> ReadS ObjectMinCardinality)
-> ReadS [ObjectMinCardinality]
-> ReadPrec ObjectMinCardinality
-> ReadPrec [ObjectMinCardinality]
-> Read ObjectMinCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectMinCardinality
readsPrec :: Int -> ReadS ObjectMinCardinality
$creadList :: ReadS [ObjectMinCardinality]
readList :: ReadS [ObjectMinCardinality]
$creadPrec :: ReadPrec ObjectMinCardinality
readPrec :: ReadPrec ObjectMinCardinality
$creadListPrec :: ReadPrec [ObjectMinCardinality]
readListPrec :: ReadPrec [ObjectMinCardinality]
Read, Int -> ObjectMinCardinality -> ShowS
[ObjectMinCardinality] -> ShowS
ObjectMinCardinality -> String
(Int -> ObjectMinCardinality -> ShowS)
-> (ObjectMinCardinality -> String)
-> ([ObjectMinCardinality] -> ShowS)
-> Show ObjectMinCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectMinCardinality -> ShowS
showsPrec :: Int -> ObjectMinCardinality -> ShowS
$cshow :: ObjectMinCardinality -> String
show :: ObjectMinCardinality -> String
$cshowList :: [ObjectMinCardinality] -> ShowS
showList :: [ObjectMinCardinality] -> ShowS
Show)

_ObjectMinCardinality :: Name
_ObjectMinCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectMinCardinality")

_ObjectMinCardinality_bound :: Name
_ObjectMinCardinality_bound = (String -> Name
Core.Name String
"bound")

_ObjectMinCardinality_property :: Name
_ObjectMinCardinality_property = (String -> Name
Core.Name String
"property")

_ObjectMinCardinality_class :: Name
_ObjectMinCardinality_class = (String -> Name
Core.Name String
"class")

-- | See https://www.w3.org/TR/owl2-syntax/#Maximum_Cardinality
data ObjectMaxCardinality = 
  ObjectMaxCardinality {
    ObjectMaxCardinality -> Integer
objectMaxCardinalityBound :: Integer,
    ObjectMaxCardinality -> ObjectPropertyExpression
objectMaxCardinalityProperty :: ObjectPropertyExpression,
    ObjectMaxCardinality -> [ClassExpression]
objectMaxCardinalityClass :: [ClassExpression]}
  deriving (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
(ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> Eq ObjectMaxCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
== :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
$c/= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
/= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
Eq, Eq ObjectMaxCardinality
Eq ObjectMaxCardinality =>
(ObjectMaxCardinality -> ObjectMaxCardinality -> Ordering)
-> (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> (ObjectMaxCardinality -> ObjectMaxCardinality -> Bool)
-> (ObjectMaxCardinality
    -> ObjectMaxCardinality -> ObjectMaxCardinality)
-> (ObjectMaxCardinality
    -> ObjectMaxCardinality -> ObjectMaxCardinality)
-> Ord ObjectMaxCardinality
ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
ObjectMaxCardinality -> ObjectMaxCardinality -> Ordering
ObjectMaxCardinality
-> ObjectMaxCardinality -> ObjectMaxCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectMaxCardinality -> ObjectMaxCardinality -> Ordering
compare :: ObjectMaxCardinality -> ObjectMaxCardinality -> Ordering
$c< :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
< :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
$c<= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
<= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
$c> :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
> :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
$c>= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
>= :: ObjectMaxCardinality -> ObjectMaxCardinality -> Bool
$cmax :: ObjectMaxCardinality
-> ObjectMaxCardinality -> ObjectMaxCardinality
max :: ObjectMaxCardinality
-> ObjectMaxCardinality -> ObjectMaxCardinality
$cmin :: ObjectMaxCardinality
-> ObjectMaxCardinality -> ObjectMaxCardinality
min :: ObjectMaxCardinality
-> ObjectMaxCardinality -> ObjectMaxCardinality
Ord, ReadPrec [ObjectMaxCardinality]
ReadPrec ObjectMaxCardinality
Int -> ReadS ObjectMaxCardinality
ReadS [ObjectMaxCardinality]
(Int -> ReadS ObjectMaxCardinality)
-> ReadS [ObjectMaxCardinality]
-> ReadPrec ObjectMaxCardinality
-> ReadPrec [ObjectMaxCardinality]
-> Read ObjectMaxCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectMaxCardinality
readsPrec :: Int -> ReadS ObjectMaxCardinality
$creadList :: ReadS [ObjectMaxCardinality]
readList :: ReadS [ObjectMaxCardinality]
$creadPrec :: ReadPrec ObjectMaxCardinality
readPrec :: ReadPrec ObjectMaxCardinality
$creadListPrec :: ReadPrec [ObjectMaxCardinality]
readListPrec :: ReadPrec [ObjectMaxCardinality]
Read, Int -> ObjectMaxCardinality -> ShowS
[ObjectMaxCardinality] -> ShowS
ObjectMaxCardinality -> String
(Int -> ObjectMaxCardinality -> ShowS)
-> (ObjectMaxCardinality -> String)
-> ([ObjectMaxCardinality] -> ShowS)
-> Show ObjectMaxCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectMaxCardinality -> ShowS
showsPrec :: Int -> ObjectMaxCardinality -> ShowS
$cshow :: ObjectMaxCardinality -> String
show :: ObjectMaxCardinality -> String
$cshowList :: [ObjectMaxCardinality] -> ShowS
showList :: [ObjectMaxCardinality] -> ShowS
Show)

_ObjectMaxCardinality :: Name
_ObjectMaxCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectMaxCardinality")

_ObjectMaxCardinality_bound :: Name
_ObjectMaxCardinality_bound = (String -> Name
Core.Name String
"bound")

_ObjectMaxCardinality_property :: Name
_ObjectMaxCardinality_property = (String -> Name
Core.Name String
"property")

_ObjectMaxCardinality_class :: Name
_ObjectMaxCardinality_class = (String -> Name
Core.Name String
"class")

-- | See https://www.w3.org/TR/owl2-syntax/#Exact_Cardinality
data ObjectExactCardinality = 
  ObjectExactCardinality {
    ObjectExactCardinality -> Integer
objectExactCardinalityBound :: Integer,
    ObjectExactCardinality -> ObjectPropertyExpression
objectExactCardinalityProperty :: ObjectPropertyExpression,
    ObjectExactCardinality -> [ClassExpression]
objectExactCardinalityClass :: [ClassExpression]}
  deriving (ObjectExactCardinality -> ObjectExactCardinality -> Bool
(ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> (ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> Eq ObjectExactCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
== :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
$c/= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
/= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
Eq, Eq ObjectExactCardinality
Eq ObjectExactCardinality =>
(ObjectExactCardinality -> ObjectExactCardinality -> Ordering)
-> (ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> (ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> (ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> (ObjectExactCardinality -> ObjectExactCardinality -> Bool)
-> (ObjectExactCardinality
    -> ObjectExactCardinality -> ObjectExactCardinality)
-> (ObjectExactCardinality
    -> ObjectExactCardinality -> ObjectExactCardinality)
-> Ord ObjectExactCardinality
ObjectExactCardinality -> ObjectExactCardinality -> Bool
ObjectExactCardinality -> ObjectExactCardinality -> Ordering
ObjectExactCardinality
-> ObjectExactCardinality -> ObjectExactCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectExactCardinality -> ObjectExactCardinality -> Ordering
compare :: ObjectExactCardinality -> ObjectExactCardinality -> Ordering
$c< :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
< :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
$c<= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
<= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
$c> :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
> :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
$c>= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
>= :: ObjectExactCardinality -> ObjectExactCardinality -> Bool
$cmax :: ObjectExactCardinality
-> ObjectExactCardinality -> ObjectExactCardinality
max :: ObjectExactCardinality
-> ObjectExactCardinality -> ObjectExactCardinality
$cmin :: ObjectExactCardinality
-> ObjectExactCardinality -> ObjectExactCardinality
min :: ObjectExactCardinality
-> ObjectExactCardinality -> ObjectExactCardinality
Ord, ReadPrec [ObjectExactCardinality]
ReadPrec ObjectExactCardinality
Int -> ReadS ObjectExactCardinality
ReadS [ObjectExactCardinality]
(Int -> ReadS ObjectExactCardinality)
-> ReadS [ObjectExactCardinality]
-> ReadPrec ObjectExactCardinality
-> ReadPrec [ObjectExactCardinality]
-> Read ObjectExactCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectExactCardinality
readsPrec :: Int -> ReadS ObjectExactCardinality
$creadList :: ReadS [ObjectExactCardinality]
readList :: ReadS [ObjectExactCardinality]
$creadPrec :: ReadPrec ObjectExactCardinality
readPrec :: ReadPrec ObjectExactCardinality
$creadListPrec :: ReadPrec [ObjectExactCardinality]
readListPrec :: ReadPrec [ObjectExactCardinality]
Read, Int -> ObjectExactCardinality -> ShowS
[ObjectExactCardinality] -> ShowS
ObjectExactCardinality -> String
(Int -> ObjectExactCardinality -> ShowS)
-> (ObjectExactCardinality -> String)
-> ([ObjectExactCardinality] -> ShowS)
-> Show ObjectExactCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectExactCardinality -> ShowS
showsPrec :: Int -> ObjectExactCardinality -> ShowS
$cshow :: ObjectExactCardinality -> String
show :: ObjectExactCardinality -> String
$cshowList :: [ObjectExactCardinality] -> ShowS
showList :: [ObjectExactCardinality] -> ShowS
Show)

_ObjectExactCardinality :: Name
_ObjectExactCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectExactCardinality")

_ObjectExactCardinality_bound :: Name
_ObjectExactCardinality_bound = (String -> Name
Core.Name String
"bound")

_ObjectExactCardinality_property :: Name
_ObjectExactCardinality_property = (String -> Name
Core.Name String
"property")

_ObjectExactCardinality_class :: Name
_ObjectExactCardinality_class = (String -> Name
Core.Name String
"class")

data DataSomeValuesFrom = 
  DataSomeValuesFrom {
    DataSomeValuesFrom -> [DataPropertyExpression]
dataSomeValuesFromProperty :: [DataPropertyExpression],
    DataSomeValuesFrom -> DataRange
dataSomeValuesFromRange :: DataRange}
  deriving (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
(DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> Eq DataSomeValuesFrom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
== :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
$c/= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
/= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
Eq, Eq DataSomeValuesFrom
Eq DataSomeValuesFrom =>
(DataSomeValuesFrom -> DataSomeValuesFrom -> Ordering)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> Bool)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom)
-> (DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom)
-> Ord DataSomeValuesFrom
DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
DataSomeValuesFrom -> DataSomeValuesFrom -> Ordering
DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataSomeValuesFrom -> DataSomeValuesFrom -> Ordering
compare :: DataSomeValuesFrom -> DataSomeValuesFrom -> Ordering
$c< :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
< :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
$c<= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
<= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
$c> :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
> :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
$c>= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
>= :: DataSomeValuesFrom -> DataSomeValuesFrom -> Bool
$cmax :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom
max :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom
$cmin :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom
min :: DataSomeValuesFrom -> DataSomeValuesFrom -> DataSomeValuesFrom
Ord, ReadPrec [DataSomeValuesFrom]
ReadPrec DataSomeValuesFrom
Int -> ReadS DataSomeValuesFrom
ReadS [DataSomeValuesFrom]
(Int -> ReadS DataSomeValuesFrom)
-> ReadS [DataSomeValuesFrom]
-> ReadPrec DataSomeValuesFrom
-> ReadPrec [DataSomeValuesFrom]
-> Read DataSomeValuesFrom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataSomeValuesFrom
readsPrec :: Int -> ReadS DataSomeValuesFrom
$creadList :: ReadS [DataSomeValuesFrom]
readList :: ReadS [DataSomeValuesFrom]
$creadPrec :: ReadPrec DataSomeValuesFrom
readPrec :: ReadPrec DataSomeValuesFrom
$creadListPrec :: ReadPrec [DataSomeValuesFrom]
readListPrec :: ReadPrec [DataSomeValuesFrom]
Read, Int -> DataSomeValuesFrom -> ShowS
[DataSomeValuesFrom] -> ShowS
DataSomeValuesFrom -> String
(Int -> DataSomeValuesFrom -> ShowS)
-> (DataSomeValuesFrom -> String)
-> ([DataSomeValuesFrom] -> ShowS)
-> Show DataSomeValuesFrom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataSomeValuesFrom -> ShowS
showsPrec :: Int -> DataSomeValuesFrom -> ShowS
$cshow :: DataSomeValuesFrom -> String
show :: DataSomeValuesFrom -> String
$cshowList :: [DataSomeValuesFrom] -> ShowS
showList :: [DataSomeValuesFrom] -> ShowS
Show)

_DataSomeValuesFrom :: Name
_DataSomeValuesFrom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataSomeValuesFrom")

_DataSomeValuesFrom_property :: Name
_DataSomeValuesFrom_property = (String -> Name
Core.Name String
"property")

_DataSomeValuesFrom_range :: Name
_DataSomeValuesFrom_range = (String -> Name
Core.Name String
"range")

data DataAllValuesFrom = 
  DataAllValuesFrom {
    DataAllValuesFrom -> [DataPropertyExpression]
dataAllValuesFromProperty :: [DataPropertyExpression],
    DataAllValuesFrom -> DataRange
dataAllValuesFromRange :: DataRange}
  deriving (DataAllValuesFrom -> DataAllValuesFrom -> Bool
(DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> (DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> Eq DataAllValuesFrom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
== :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
$c/= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
/= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
Eq, Eq DataAllValuesFrom
Eq DataAllValuesFrom =>
(DataAllValuesFrom -> DataAllValuesFrom -> Ordering)
-> (DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> (DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> (DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> (DataAllValuesFrom -> DataAllValuesFrom -> Bool)
-> (DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom)
-> (DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom)
-> Ord DataAllValuesFrom
DataAllValuesFrom -> DataAllValuesFrom -> Bool
DataAllValuesFrom -> DataAllValuesFrom -> Ordering
DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataAllValuesFrom -> DataAllValuesFrom -> Ordering
compare :: DataAllValuesFrom -> DataAllValuesFrom -> Ordering
$c< :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
< :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
$c<= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
<= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
$c> :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
> :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
$c>= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
>= :: DataAllValuesFrom -> DataAllValuesFrom -> Bool
$cmax :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom
max :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom
$cmin :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom
min :: DataAllValuesFrom -> DataAllValuesFrom -> DataAllValuesFrom
Ord, ReadPrec [DataAllValuesFrom]
ReadPrec DataAllValuesFrom
Int -> ReadS DataAllValuesFrom
ReadS [DataAllValuesFrom]
(Int -> ReadS DataAllValuesFrom)
-> ReadS [DataAllValuesFrom]
-> ReadPrec DataAllValuesFrom
-> ReadPrec [DataAllValuesFrom]
-> Read DataAllValuesFrom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataAllValuesFrom
readsPrec :: Int -> ReadS DataAllValuesFrom
$creadList :: ReadS [DataAllValuesFrom]
readList :: ReadS [DataAllValuesFrom]
$creadPrec :: ReadPrec DataAllValuesFrom
readPrec :: ReadPrec DataAllValuesFrom
$creadListPrec :: ReadPrec [DataAllValuesFrom]
readListPrec :: ReadPrec [DataAllValuesFrom]
Read, Int -> DataAllValuesFrom -> ShowS
[DataAllValuesFrom] -> ShowS
DataAllValuesFrom -> String
(Int -> DataAllValuesFrom -> ShowS)
-> (DataAllValuesFrom -> String)
-> ([DataAllValuesFrom] -> ShowS)
-> Show DataAllValuesFrom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataAllValuesFrom -> ShowS
showsPrec :: Int -> DataAllValuesFrom -> ShowS
$cshow :: DataAllValuesFrom -> String
show :: DataAllValuesFrom -> String
$cshowList :: [DataAllValuesFrom] -> ShowS
showList :: [DataAllValuesFrom] -> ShowS
Show)

_DataAllValuesFrom :: Name
_DataAllValuesFrom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataAllValuesFrom")

_DataAllValuesFrom_property :: Name
_DataAllValuesFrom_property = (String -> Name
Core.Name String
"property")

_DataAllValuesFrom_range :: Name
_DataAllValuesFrom_range = (String -> Name
Core.Name String
"range")

data DataHasValue = 
  DataHasValue {
    DataHasValue -> DataPropertyExpression
dataHasValueProperty :: DataPropertyExpression,
    DataHasValue -> Literal
dataHasValueValue :: Syntax.Literal}
  deriving (DataHasValue -> DataHasValue -> Bool
(DataHasValue -> DataHasValue -> Bool)
-> (DataHasValue -> DataHasValue -> Bool) -> Eq DataHasValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataHasValue -> DataHasValue -> Bool
== :: DataHasValue -> DataHasValue -> Bool
$c/= :: DataHasValue -> DataHasValue -> Bool
/= :: DataHasValue -> DataHasValue -> Bool
Eq, Eq DataHasValue
Eq DataHasValue =>
(DataHasValue -> DataHasValue -> Ordering)
-> (DataHasValue -> DataHasValue -> Bool)
-> (DataHasValue -> DataHasValue -> Bool)
-> (DataHasValue -> DataHasValue -> Bool)
-> (DataHasValue -> DataHasValue -> Bool)
-> (DataHasValue -> DataHasValue -> DataHasValue)
-> (DataHasValue -> DataHasValue -> DataHasValue)
-> Ord DataHasValue
DataHasValue -> DataHasValue -> Bool
DataHasValue -> DataHasValue -> Ordering
DataHasValue -> DataHasValue -> DataHasValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataHasValue -> DataHasValue -> Ordering
compare :: DataHasValue -> DataHasValue -> Ordering
$c< :: DataHasValue -> DataHasValue -> Bool
< :: DataHasValue -> DataHasValue -> Bool
$c<= :: DataHasValue -> DataHasValue -> Bool
<= :: DataHasValue -> DataHasValue -> Bool
$c> :: DataHasValue -> DataHasValue -> Bool
> :: DataHasValue -> DataHasValue -> Bool
$c>= :: DataHasValue -> DataHasValue -> Bool
>= :: DataHasValue -> DataHasValue -> Bool
$cmax :: DataHasValue -> DataHasValue -> DataHasValue
max :: DataHasValue -> DataHasValue -> DataHasValue
$cmin :: DataHasValue -> DataHasValue -> DataHasValue
min :: DataHasValue -> DataHasValue -> DataHasValue
Ord, ReadPrec [DataHasValue]
ReadPrec DataHasValue
Int -> ReadS DataHasValue
ReadS [DataHasValue]
(Int -> ReadS DataHasValue)
-> ReadS [DataHasValue]
-> ReadPrec DataHasValue
-> ReadPrec [DataHasValue]
-> Read DataHasValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataHasValue
readsPrec :: Int -> ReadS DataHasValue
$creadList :: ReadS [DataHasValue]
readList :: ReadS [DataHasValue]
$creadPrec :: ReadPrec DataHasValue
readPrec :: ReadPrec DataHasValue
$creadListPrec :: ReadPrec [DataHasValue]
readListPrec :: ReadPrec [DataHasValue]
Read, Int -> DataHasValue -> ShowS
[DataHasValue] -> ShowS
DataHasValue -> String
(Int -> DataHasValue -> ShowS)
-> (DataHasValue -> String)
-> ([DataHasValue] -> ShowS)
-> Show DataHasValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataHasValue -> ShowS
showsPrec :: Int -> DataHasValue -> ShowS
$cshow :: DataHasValue -> String
show :: DataHasValue -> String
$cshowList :: [DataHasValue] -> ShowS
showList :: [DataHasValue] -> ShowS
Show)

_DataHasValue :: Name
_DataHasValue = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataHasValue")

_DataHasValue_property :: Name
_DataHasValue_property = (String -> Name
Core.Name String
"property")

_DataHasValue_value :: Name
_DataHasValue_value = (String -> Name
Core.Name String
"value")

data DataMinCardinality = 
  DataMinCardinality {
    DataMinCardinality -> Integer
dataMinCardinalityBound :: Integer,
    DataMinCardinality -> DataPropertyExpression
dataMinCardinalityProperty :: DataPropertyExpression,
    DataMinCardinality -> [DataRange]
dataMinCardinalityRange :: [DataRange]}
  deriving (DataMinCardinality -> DataMinCardinality -> Bool
(DataMinCardinality -> DataMinCardinality -> Bool)
-> (DataMinCardinality -> DataMinCardinality -> Bool)
-> Eq DataMinCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataMinCardinality -> DataMinCardinality -> Bool
== :: DataMinCardinality -> DataMinCardinality -> Bool
$c/= :: DataMinCardinality -> DataMinCardinality -> Bool
/= :: DataMinCardinality -> DataMinCardinality -> Bool
Eq, Eq DataMinCardinality
Eq DataMinCardinality =>
(DataMinCardinality -> DataMinCardinality -> Ordering)
-> (DataMinCardinality -> DataMinCardinality -> Bool)
-> (DataMinCardinality -> DataMinCardinality -> Bool)
-> (DataMinCardinality -> DataMinCardinality -> Bool)
-> (DataMinCardinality -> DataMinCardinality -> Bool)
-> (DataMinCardinality -> DataMinCardinality -> DataMinCardinality)
-> (DataMinCardinality -> DataMinCardinality -> DataMinCardinality)
-> Ord DataMinCardinality
DataMinCardinality -> DataMinCardinality -> Bool
DataMinCardinality -> DataMinCardinality -> Ordering
DataMinCardinality -> DataMinCardinality -> DataMinCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataMinCardinality -> DataMinCardinality -> Ordering
compare :: DataMinCardinality -> DataMinCardinality -> Ordering
$c< :: DataMinCardinality -> DataMinCardinality -> Bool
< :: DataMinCardinality -> DataMinCardinality -> Bool
$c<= :: DataMinCardinality -> DataMinCardinality -> Bool
<= :: DataMinCardinality -> DataMinCardinality -> Bool
$c> :: DataMinCardinality -> DataMinCardinality -> Bool
> :: DataMinCardinality -> DataMinCardinality -> Bool
$c>= :: DataMinCardinality -> DataMinCardinality -> Bool
>= :: DataMinCardinality -> DataMinCardinality -> Bool
$cmax :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality
max :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality
$cmin :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality
min :: DataMinCardinality -> DataMinCardinality -> DataMinCardinality
Ord, ReadPrec [DataMinCardinality]
ReadPrec DataMinCardinality
Int -> ReadS DataMinCardinality
ReadS [DataMinCardinality]
(Int -> ReadS DataMinCardinality)
-> ReadS [DataMinCardinality]
-> ReadPrec DataMinCardinality
-> ReadPrec [DataMinCardinality]
-> Read DataMinCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataMinCardinality
readsPrec :: Int -> ReadS DataMinCardinality
$creadList :: ReadS [DataMinCardinality]
readList :: ReadS [DataMinCardinality]
$creadPrec :: ReadPrec DataMinCardinality
readPrec :: ReadPrec DataMinCardinality
$creadListPrec :: ReadPrec [DataMinCardinality]
readListPrec :: ReadPrec [DataMinCardinality]
Read, Int -> DataMinCardinality -> ShowS
[DataMinCardinality] -> ShowS
DataMinCardinality -> String
(Int -> DataMinCardinality -> ShowS)
-> (DataMinCardinality -> String)
-> ([DataMinCardinality] -> ShowS)
-> Show DataMinCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataMinCardinality -> ShowS
showsPrec :: Int -> DataMinCardinality -> ShowS
$cshow :: DataMinCardinality -> String
show :: DataMinCardinality -> String
$cshowList :: [DataMinCardinality] -> ShowS
showList :: [DataMinCardinality] -> ShowS
Show)

_DataMinCardinality :: Name
_DataMinCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataMinCardinality")

_DataMinCardinality_bound :: Name
_DataMinCardinality_bound = (String -> Name
Core.Name String
"bound")

_DataMinCardinality_property :: Name
_DataMinCardinality_property = (String -> Name
Core.Name String
"property")

_DataMinCardinality_range :: Name
_DataMinCardinality_range = (String -> Name
Core.Name String
"range")

data DataMaxCardinality = 
  DataMaxCardinality {
    DataMaxCardinality -> Integer
dataMaxCardinalityBound :: Integer,
    DataMaxCardinality -> DataPropertyExpression
dataMaxCardinalityProperty :: DataPropertyExpression,
    DataMaxCardinality -> [DataRange]
dataMaxCardinalityRange :: [DataRange]}
  deriving (DataMaxCardinality -> DataMaxCardinality -> Bool
(DataMaxCardinality -> DataMaxCardinality -> Bool)
-> (DataMaxCardinality -> DataMaxCardinality -> Bool)
-> Eq DataMaxCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataMaxCardinality -> DataMaxCardinality -> Bool
== :: DataMaxCardinality -> DataMaxCardinality -> Bool
$c/= :: DataMaxCardinality -> DataMaxCardinality -> Bool
/= :: DataMaxCardinality -> DataMaxCardinality -> Bool
Eq, Eq DataMaxCardinality
Eq DataMaxCardinality =>
(DataMaxCardinality -> DataMaxCardinality -> Ordering)
-> (DataMaxCardinality -> DataMaxCardinality -> Bool)
-> (DataMaxCardinality -> DataMaxCardinality -> Bool)
-> (DataMaxCardinality -> DataMaxCardinality -> Bool)
-> (DataMaxCardinality -> DataMaxCardinality -> Bool)
-> (DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality)
-> (DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality)
-> Ord DataMaxCardinality
DataMaxCardinality -> DataMaxCardinality -> Bool
DataMaxCardinality -> DataMaxCardinality -> Ordering
DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataMaxCardinality -> DataMaxCardinality -> Ordering
compare :: DataMaxCardinality -> DataMaxCardinality -> Ordering
$c< :: DataMaxCardinality -> DataMaxCardinality -> Bool
< :: DataMaxCardinality -> DataMaxCardinality -> Bool
$c<= :: DataMaxCardinality -> DataMaxCardinality -> Bool
<= :: DataMaxCardinality -> DataMaxCardinality -> Bool
$c> :: DataMaxCardinality -> DataMaxCardinality -> Bool
> :: DataMaxCardinality -> DataMaxCardinality -> Bool
$c>= :: DataMaxCardinality -> DataMaxCardinality -> Bool
>= :: DataMaxCardinality -> DataMaxCardinality -> Bool
$cmax :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality
max :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality
$cmin :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality
min :: DataMaxCardinality -> DataMaxCardinality -> DataMaxCardinality
Ord, ReadPrec [DataMaxCardinality]
ReadPrec DataMaxCardinality
Int -> ReadS DataMaxCardinality
ReadS [DataMaxCardinality]
(Int -> ReadS DataMaxCardinality)
-> ReadS [DataMaxCardinality]
-> ReadPrec DataMaxCardinality
-> ReadPrec [DataMaxCardinality]
-> Read DataMaxCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataMaxCardinality
readsPrec :: Int -> ReadS DataMaxCardinality
$creadList :: ReadS [DataMaxCardinality]
readList :: ReadS [DataMaxCardinality]
$creadPrec :: ReadPrec DataMaxCardinality
readPrec :: ReadPrec DataMaxCardinality
$creadListPrec :: ReadPrec [DataMaxCardinality]
readListPrec :: ReadPrec [DataMaxCardinality]
Read, Int -> DataMaxCardinality -> ShowS
[DataMaxCardinality] -> ShowS
DataMaxCardinality -> String
(Int -> DataMaxCardinality -> ShowS)
-> (DataMaxCardinality -> String)
-> ([DataMaxCardinality] -> ShowS)
-> Show DataMaxCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataMaxCardinality -> ShowS
showsPrec :: Int -> DataMaxCardinality -> ShowS
$cshow :: DataMaxCardinality -> String
show :: DataMaxCardinality -> String
$cshowList :: [DataMaxCardinality] -> ShowS
showList :: [DataMaxCardinality] -> ShowS
Show)

_DataMaxCardinality :: Name
_DataMaxCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataMaxCardinality")

_DataMaxCardinality_bound :: Name
_DataMaxCardinality_bound = (String -> Name
Core.Name String
"bound")

_DataMaxCardinality_property :: Name
_DataMaxCardinality_property = (String -> Name
Core.Name String
"property")

_DataMaxCardinality_range :: Name
_DataMaxCardinality_range = (String -> Name
Core.Name String
"range")

data DataExactCardinality = 
  DataExactCardinality {
    DataExactCardinality -> Integer
dataExactCardinalityBound :: Integer,
    DataExactCardinality -> DataPropertyExpression
dataExactCardinalityProperty :: DataPropertyExpression,
    DataExactCardinality -> [DataRange]
dataExactCardinalityRange :: [DataRange]}
  deriving (DataExactCardinality -> DataExactCardinality -> Bool
(DataExactCardinality -> DataExactCardinality -> Bool)
-> (DataExactCardinality -> DataExactCardinality -> Bool)
-> Eq DataExactCardinality
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataExactCardinality -> DataExactCardinality -> Bool
== :: DataExactCardinality -> DataExactCardinality -> Bool
$c/= :: DataExactCardinality -> DataExactCardinality -> Bool
/= :: DataExactCardinality -> DataExactCardinality -> Bool
Eq, Eq DataExactCardinality
Eq DataExactCardinality =>
(DataExactCardinality -> DataExactCardinality -> Ordering)
-> (DataExactCardinality -> DataExactCardinality -> Bool)
-> (DataExactCardinality -> DataExactCardinality -> Bool)
-> (DataExactCardinality -> DataExactCardinality -> Bool)
-> (DataExactCardinality -> DataExactCardinality -> Bool)
-> (DataExactCardinality
    -> DataExactCardinality -> DataExactCardinality)
-> (DataExactCardinality
    -> DataExactCardinality -> DataExactCardinality)
-> Ord DataExactCardinality
DataExactCardinality -> DataExactCardinality -> Bool
DataExactCardinality -> DataExactCardinality -> Ordering
DataExactCardinality
-> DataExactCardinality -> DataExactCardinality
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataExactCardinality -> DataExactCardinality -> Ordering
compare :: DataExactCardinality -> DataExactCardinality -> Ordering
$c< :: DataExactCardinality -> DataExactCardinality -> Bool
< :: DataExactCardinality -> DataExactCardinality -> Bool
$c<= :: DataExactCardinality -> DataExactCardinality -> Bool
<= :: DataExactCardinality -> DataExactCardinality -> Bool
$c> :: DataExactCardinality -> DataExactCardinality -> Bool
> :: DataExactCardinality -> DataExactCardinality -> Bool
$c>= :: DataExactCardinality -> DataExactCardinality -> Bool
>= :: DataExactCardinality -> DataExactCardinality -> Bool
$cmax :: DataExactCardinality
-> DataExactCardinality -> DataExactCardinality
max :: DataExactCardinality
-> DataExactCardinality -> DataExactCardinality
$cmin :: DataExactCardinality
-> DataExactCardinality -> DataExactCardinality
min :: DataExactCardinality
-> DataExactCardinality -> DataExactCardinality
Ord, ReadPrec [DataExactCardinality]
ReadPrec DataExactCardinality
Int -> ReadS DataExactCardinality
ReadS [DataExactCardinality]
(Int -> ReadS DataExactCardinality)
-> ReadS [DataExactCardinality]
-> ReadPrec DataExactCardinality
-> ReadPrec [DataExactCardinality]
-> Read DataExactCardinality
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataExactCardinality
readsPrec :: Int -> ReadS DataExactCardinality
$creadList :: ReadS [DataExactCardinality]
readList :: ReadS [DataExactCardinality]
$creadPrec :: ReadPrec DataExactCardinality
readPrec :: ReadPrec DataExactCardinality
$creadListPrec :: ReadPrec [DataExactCardinality]
readListPrec :: ReadPrec [DataExactCardinality]
Read, Int -> DataExactCardinality -> ShowS
[DataExactCardinality] -> ShowS
DataExactCardinality -> String
(Int -> DataExactCardinality -> ShowS)
-> (DataExactCardinality -> String)
-> ([DataExactCardinality] -> ShowS)
-> Show DataExactCardinality
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataExactCardinality -> ShowS
showsPrec :: Int -> DataExactCardinality -> ShowS
$cshow :: DataExactCardinality -> String
show :: DataExactCardinality -> String
$cshowList :: [DataExactCardinality] -> ShowS
showList :: [DataExactCardinality] -> ShowS
Show)

_DataExactCardinality :: Name
_DataExactCardinality = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataExactCardinality")

_DataExactCardinality_bound :: Name
_DataExactCardinality_bound = (String -> Name
Core.Name String
"bound")

_DataExactCardinality_property :: Name
_DataExactCardinality_property = (String -> Name
Core.Name String
"property")

_DataExactCardinality_range :: Name
_DataExactCardinality_range = (String -> Name
Core.Name String
"range")

-- | See https://www.w3.org/TR/owl2-syntax/#Axioms
data Axiom = 
  AxiomAnnotationAxiom AnnotationAxiom |
  AxiomAssertion Assertion |
  AxiomClassAxiom ClassAxiom |
  AxiomDataPropertyAxiom DataPropertyAxiom |
  AxiomDatatypeDefinition DatatypeDefinition |
  AxiomDeclaration Declaration |
  AxiomHasKey HasKey |
  AxiomObjectPropertyAxiom ObjectPropertyAxiom
  deriving (Axiom -> Axiom -> Bool
(Axiom -> Axiom -> Bool) -> (Axiom -> Axiom -> Bool) -> Eq Axiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Axiom -> Axiom -> Bool
== :: Axiom -> Axiom -> Bool
$c/= :: Axiom -> Axiom -> Bool
/= :: Axiom -> Axiom -> Bool
Eq, Eq Axiom
Eq Axiom =>
(Axiom -> Axiom -> Ordering)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Bool)
-> (Axiom -> Axiom -> Axiom)
-> (Axiom -> Axiom -> Axiom)
-> Ord Axiom
Axiom -> Axiom -> Bool
Axiom -> Axiom -> Ordering
Axiom -> Axiom -> Axiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Axiom -> Axiom -> Ordering
compare :: Axiom -> Axiom -> Ordering
$c< :: Axiom -> Axiom -> Bool
< :: Axiom -> Axiom -> Bool
$c<= :: Axiom -> Axiom -> Bool
<= :: Axiom -> Axiom -> Bool
$c> :: Axiom -> Axiom -> Bool
> :: Axiom -> Axiom -> Bool
$c>= :: Axiom -> Axiom -> Bool
>= :: Axiom -> Axiom -> Bool
$cmax :: Axiom -> Axiom -> Axiom
max :: Axiom -> Axiom -> Axiom
$cmin :: Axiom -> Axiom -> Axiom
min :: Axiom -> Axiom -> Axiom
Ord, ReadPrec [Axiom]
ReadPrec Axiom
Int -> ReadS Axiom
ReadS [Axiom]
(Int -> ReadS Axiom)
-> ReadS [Axiom]
-> ReadPrec Axiom
-> ReadPrec [Axiom]
-> Read Axiom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Axiom
readsPrec :: Int -> ReadS Axiom
$creadList :: ReadS [Axiom]
readList :: ReadS [Axiom]
$creadPrec :: ReadPrec Axiom
readPrec :: ReadPrec Axiom
$creadListPrec :: ReadPrec [Axiom]
readListPrec :: ReadPrec [Axiom]
Read, Int -> Axiom -> ShowS
[Axiom] -> ShowS
Axiom -> String
(Int -> Axiom -> ShowS)
-> (Axiom -> String) -> ([Axiom] -> ShowS) -> Show Axiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Axiom -> ShowS
showsPrec :: Int -> Axiom -> ShowS
$cshow :: Axiom -> String
show :: Axiom -> String
$cshowList :: [Axiom] -> ShowS
showList :: [Axiom] -> ShowS
Show)

_Axiom :: Name
_Axiom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Axiom")

_Axiom_annotationAxiom :: Name
_Axiom_annotationAxiom = (String -> Name
Core.Name String
"annotationAxiom")

_Axiom_assertion :: Name
_Axiom_assertion = (String -> Name
Core.Name String
"assertion")

_Axiom_classAxiom :: Name
_Axiom_classAxiom = (String -> Name
Core.Name String
"classAxiom")

_Axiom_dataPropertyAxiom :: Name
_Axiom_dataPropertyAxiom = (String -> Name
Core.Name String
"dataPropertyAxiom")

_Axiom_datatypeDefinition :: Name
_Axiom_datatypeDefinition = (String -> Name
Core.Name String
"datatypeDefinition")

_Axiom_declaration :: Name
_Axiom_declaration = (String -> Name
Core.Name String
"declaration")

_Axiom_hasKey :: Name
_Axiom_hasKey = (String -> Name
Core.Name String
"hasKey")

_Axiom_objectPropertyAxiom :: Name
_Axiom_objectPropertyAxiom = (String -> Name
Core.Name String
"objectPropertyAxiom")

data ClassAxiom = 
  ClassAxiomDisjointClasses DisjointClasses |
  ClassAxiomDisjointUnion DisjointUnion |
  ClassAxiomEquivalentClasses EquivalentClasses |
  ClassAxiomSubClassOf SubClassOf
  deriving (ClassAxiom -> ClassAxiom -> Bool
(ClassAxiom -> ClassAxiom -> Bool)
-> (ClassAxiom -> ClassAxiom -> Bool) -> Eq ClassAxiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClassAxiom -> ClassAxiom -> Bool
== :: ClassAxiom -> ClassAxiom -> Bool
$c/= :: ClassAxiom -> ClassAxiom -> Bool
/= :: ClassAxiom -> ClassAxiom -> Bool
Eq, Eq ClassAxiom
Eq ClassAxiom =>
(ClassAxiom -> ClassAxiom -> Ordering)
-> (ClassAxiom -> ClassAxiom -> Bool)
-> (ClassAxiom -> ClassAxiom -> Bool)
-> (ClassAxiom -> ClassAxiom -> Bool)
-> (ClassAxiom -> ClassAxiom -> Bool)
-> (ClassAxiom -> ClassAxiom -> ClassAxiom)
-> (ClassAxiom -> ClassAxiom -> ClassAxiom)
-> Ord ClassAxiom
ClassAxiom -> ClassAxiom -> Bool
ClassAxiom -> ClassAxiom -> Ordering
ClassAxiom -> ClassAxiom -> ClassAxiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ClassAxiom -> ClassAxiom -> Ordering
compare :: ClassAxiom -> ClassAxiom -> Ordering
$c< :: ClassAxiom -> ClassAxiom -> Bool
< :: ClassAxiom -> ClassAxiom -> Bool
$c<= :: ClassAxiom -> ClassAxiom -> Bool
<= :: ClassAxiom -> ClassAxiom -> Bool
$c> :: ClassAxiom -> ClassAxiom -> Bool
> :: ClassAxiom -> ClassAxiom -> Bool
$c>= :: ClassAxiom -> ClassAxiom -> Bool
>= :: ClassAxiom -> ClassAxiom -> Bool
$cmax :: ClassAxiom -> ClassAxiom -> ClassAxiom
max :: ClassAxiom -> ClassAxiom -> ClassAxiom
$cmin :: ClassAxiom -> ClassAxiom -> ClassAxiom
min :: ClassAxiom -> ClassAxiom -> ClassAxiom
Ord, ReadPrec [ClassAxiom]
ReadPrec ClassAxiom
Int -> ReadS ClassAxiom
ReadS [ClassAxiom]
(Int -> ReadS ClassAxiom)
-> ReadS [ClassAxiom]
-> ReadPrec ClassAxiom
-> ReadPrec [ClassAxiom]
-> Read ClassAxiom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ClassAxiom
readsPrec :: Int -> ReadS ClassAxiom
$creadList :: ReadS [ClassAxiom]
readList :: ReadS [ClassAxiom]
$creadPrec :: ReadPrec ClassAxiom
readPrec :: ReadPrec ClassAxiom
$creadListPrec :: ReadPrec [ClassAxiom]
readListPrec :: ReadPrec [ClassAxiom]
Read, Int -> ClassAxiom -> ShowS
[ClassAxiom] -> ShowS
ClassAxiom -> String
(Int -> ClassAxiom -> ShowS)
-> (ClassAxiom -> String)
-> ([ClassAxiom] -> ShowS)
-> Show ClassAxiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClassAxiom -> ShowS
showsPrec :: Int -> ClassAxiom -> ShowS
$cshow :: ClassAxiom -> String
show :: ClassAxiom -> String
$cshowList :: [ClassAxiom] -> ShowS
showList :: [ClassAxiom] -> ShowS
Show)

_ClassAxiom :: Name
_ClassAxiom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ClassAxiom")

_ClassAxiom_disjointClasses :: Name
_ClassAxiom_disjointClasses = (String -> Name
Core.Name String
"disjointClasses")

_ClassAxiom_disjointUnion :: Name
_ClassAxiom_disjointUnion = (String -> Name
Core.Name String
"disjointUnion")

_ClassAxiom_equivalentClasses :: Name
_ClassAxiom_equivalentClasses = (String -> Name
Core.Name String
"equivalentClasses")

_ClassAxiom_subClassOf :: Name
_ClassAxiom_subClassOf = (String -> Name
Core.Name String
"subClassOf")

data SubClassOf = 
  SubClassOf {
    SubClassOf -> [Annotation]
subClassOfAnnotations :: [Annotation],
    SubClassOf -> ClassExpression
subClassOfSubClass :: ClassExpression,
    SubClassOf -> ClassExpression
subClassOfSuperClass :: ClassExpression}
  deriving (SubClassOf -> SubClassOf -> Bool
(SubClassOf -> SubClassOf -> Bool)
-> (SubClassOf -> SubClassOf -> Bool) -> Eq SubClassOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubClassOf -> SubClassOf -> Bool
== :: SubClassOf -> SubClassOf -> Bool
$c/= :: SubClassOf -> SubClassOf -> Bool
/= :: SubClassOf -> SubClassOf -> Bool
Eq, Eq SubClassOf
Eq SubClassOf =>
(SubClassOf -> SubClassOf -> Ordering)
-> (SubClassOf -> SubClassOf -> Bool)
-> (SubClassOf -> SubClassOf -> Bool)
-> (SubClassOf -> SubClassOf -> Bool)
-> (SubClassOf -> SubClassOf -> Bool)
-> (SubClassOf -> SubClassOf -> SubClassOf)
-> (SubClassOf -> SubClassOf -> SubClassOf)
-> Ord SubClassOf
SubClassOf -> SubClassOf -> Bool
SubClassOf -> SubClassOf -> Ordering
SubClassOf -> SubClassOf -> SubClassOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SubClassOf -> SubClassOf -> Ordering
compare :: SubClassOf -> SubClassOf -> Ordering
$c< :: SubClassOf -> SubClassOf -> Bool
< :: SubClassOf -> SubClassOf -> Bool
$c<= :: SubClassOf -> SubClassOf -> Bool
<= :: SubClassOf -> SubClassOf -> Bool
$c> :: SubClassOf -> SubClassOf -> Bool
> :: SubClassOf -> SubClassOf -> Bool
$c>= :: SubClassOf -> SubClassOf -> Bool
>= :: SubClassOf -> SubClassOf -> Bool
$cmax :: SubClassOf -> SubClassOf -> SubClassOf
max :: SubClassOf -> SubClassOf -> SubClassOf
$cmin :: SubClassOf -> SubClassOf -> SubClassOf
min :: SubClassOf -> SubClassOf -> SubClassOf
Ord, ReadPrec [SubClassOf]
ReadPrec SubClassOf
Int -> ReadS SubClassOf
ReadS [SubClassOf]
(Int -> ReadS SubClassOf)
-> ReadS [SubClassOf]
-> ReadPrec SubClassOf
-> ReadPrec [SubClassOf]
-> Read SubClassOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SubClassOf
readsPrec :: Int -> ReadS SubClassOf
$creadList :: ReadS [SubClassOf]
readList :: ReadS [SubClassOf]
$creadPrec :: ReadPrec SubClassOf
readPrec :: ReadPrec SubClassOf
$creadListPrec :: ReadPrec [SubClassOf]
readListPrec :: ReadPrec [SubClassOf]
Read, Int -> SubClassOf -> ShowS
[SubClassOf] -> ShowS
SubClassOf -> String
(Int -> SubClassOf -> ShowS)
-> (SubClassOf -> String)
-> ([SubClassOf] -> ShowS)
-> Show SubClassOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubClassOf -> ShowS
showsPrec :: Int -> SubClassOf -> ShowS
$cshow :: SubClassOf -> String
show :: SubClassOf -> String
$cshowList :: [SubClassOf] -> ShowS
showList :: [SubClassOf] -> ShowS
Show)

_SubClassOf :: Name
_SubClassOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SubClassOf")

_SubClassOf_annotations :: Name
_SubClassOf_annotations = (String -> Name
Core.Name String
"annotations")

_SubClassOf_subClass :: Name
_SubClassOf_subClass = (String -> Name
Core.Name String
"subClass")

_SubClassOf_superClass :: Name
_SubClassOf_superClass = (String -> Name
Core.Name String
"superClass")

data EquivalentClasses = 
  EquivalentClasses {
    EquivalentClasses -> [Annotation]
equivalentClassesAnnotations :: [Annotation],
    EquivalentClasses -> [ClassExpression]
equivalentClassesClasses :: [ClassExpression]}
  deriving (EquivalentClasses -> EquivalentClasses -> Bool
(EquivalentClasses -> EquivalentClasses -> Bool)
-> (EquivalentClasses -> EquivalentClasses -> Bool)
-> Eq EquivalentClasses
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EquivalentClasses -> EquivalentClasses -> Bool
== :: EquivalentClasses -> EquivalentClasses -> Bool
$c/= :: EquivalentClasses -> EquivalentClasses -> Bool
/= :: EquivalentClasses -> EquivalentClasses -> Bool
Eq, Eq EquivalentClasses
Eq EquivalentClasses =>
(EquivalentClasses -> EquivalentClasses -> Ordering)
-> (EquivalentClasses -> EquivalentClasses -> Bool)
-> (EquivalentClasses -> EquivalentClasses -> Bool)
-> (EquivalentClasses -> EquivalentClasses -> Bool)
-> (EquivalentClasses -> EquivalentClasses -> Bool)
-> (EquivalentClasses -> EquivalentClasses -> EquivalentClasses)
-> (EquivalentClasses -> EquivalentClasses -> EquivalentClasses)
-> Ord EquivalentClasses
EquivalentClasses -> EquivalentClasses -> Bool
EquivalentClasses -> EquivalentClasses -> Ordering
EquivalentClasses -> EquivalentClasses -> EquivalentClasses
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EquivalentClasses -> EquivalentClasses -> Ordering
compare :: EquivalentClasses -> EquivalentClasses -> Ordering
$c< :: EquivalentClasses -> EquivalentClasses -> Bool
< :: EquivalentClasses -> EquivalentClasses -> Bool
$c<= :: EquivalentClasses -> EquivalentClasses -> Bool
<= :: EquivalentClasses -> EquivalentClasses -> Bool
$c> :: EquivalentClasses -> EquivalentClasses -> Bool
> :: EquivalentClasses -> EquivalentClasses -> Bool
$c>= :: EquivalentClasses -> EquivalentClasses -> Bool
>= :: EquivalentClasses -> EquivalentClasses -> Bool
$cmax :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses
max :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses
$cmin :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses
min :: EquivalentClasses -> EquivalentClasses -> EquivalentClasses
Ord, ReadPrec [EquivalentClasses]
ReadPrec EquivalentClasses
Int -> ReadS EquivalentClasses
ReadS [EquivalentClasses]
(Int -> ReadS EquivalentClasses)
-> ReadS [EquivalentClasses]
-> ReadPrec EquivalentClasses
-> ReadPrec [EquivalentClasses]
-> Read EquivalentClasses
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EquivalentClasses
readsPrec :: Int -> ReadS EquivalentClasses
$creadList :: ReadS [EquivalentClasses]
readList :: ReadS [EquivalentClasses]
$creadPrec :: ReadPrec EquivalentClasses
readPrec :: ReadPrec EquivalentClasses
$creadListPrec :: ReadPrec [EquivalentClasses]
readListPrec :: ReadPrec [EquivalentClasses]
Read, Int -> EquivalentClasses -> ShowS
[EquivalentClasses] -> ShowS
EquivalentClasses -> String
(Int -> EquivalentClasses -> ShowS)
-> (EquivalentClasses -> String)
-> ([EquivalentClasses] -> ShowS)
-> Show EquivalentClasses
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EquivalentClasses -> ShowS
showsPrec :: Int -> EquivalentClasses -> ShowS
$cshow :: EquivalentClasses -> String
show :: EquivalentClasses -> String
$cshowList :: [EquivalentClasses] -> ShowS
showList :: [EquivalentClasses] -> ShowS
Show)

_EquivalentClasses :: Name
_EquivalentClasses = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.EquivalentClasses")

_EquivalentClasses_annotations :: Name
_EquivalentClasses_annotations = (String -> Name
Core.Name String
"annotations")

_EquivalentClasses_classes :: Name
_EquivalentClasses_classes = (String -> Name
Core.Name String
"classes")

data DisjointClasses = 
  DisjointClasses {
    DisjointClasses -> [Annotation]
disjointClassesAnnotations :: [Annotation],
    DisjointClasses -> [ClassExpression]
disjointClassesClasses :: [ClassExpression]}
  deriving (DisjointClasses -> DisjointClasses -> Bool
(DisjointClasses -> DisjointClasses -> Bool)
-> (DisjointClasses -> DisjointClasses -> Bool)
-> Eq DisjointClasses
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisjointClasses -> DisjointClasses -> Bool
== :: DisjointClasses -> DisjointClasses -> Bool
$c/= :: DisjointClasses -> DisjointClasses -> Bool
/= :: DisjointClasses -> DisjointClasses -> Bool
Eq, Eq DisjointClasses
Eq DisjointClasses =>
(DisjointClasses -> DisjointClasses -> Ordering)
-> (DisjointClasses -> DisjointClasses -> Bool)
-> (DisjointClasses -> DisjointClasses -> Bool)
-> (DisjointClasses -> DisjointClasses -> Bool)
-> (DisjointClasses -> DisjointClasses -> Bool)
-> (DisjointClasses -> DisjointClasses -> DisjointClasses)
-> (DisjointClasses -> DisjointClasses -> DisjointClasses)
-> Ord DisjointClasses
DisjointClasses -> DisjointClasses -> Bool
DisjointClasses -> DisjointClasses -> Ordering
DisjointClasses -> DisjointClasses -> DisjointClasses
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DisjointClasses -> DisjointClasses -> Ordering
compare :: DisjointClasses -> DisjointClasses -> Ordering
$c< :: DisjointClasses -> DisjointClasses -> Bool
< :: DisjointClasses -> DisjointClasses -> Bool
$c<= :: DisjointClasses -> DisjointClasses -> Bool
<= :: DisjointClasses -> DisjointClasses -> Bool
$c> :: DisjointClasses -> DisjointClasses -> Bool
> :: DisjointClasses -> DisjointClasses -> Bool
$c>= :: DisjointClasses -> DisjointClasses -> Bool
>= :: DisjointClasses -> DisjointClasses -> Bool
$cmax :: DisjointClasses -> DisjointClasses -> DisjointClasses
max :: DisjointClasses -> DisjointClasses -> DisjointClasses
$cmin :: DisjointClasses -> DisjointClasses -> DisjointClasses
min :: DisjointClasses -> DisjointClasses -> DisjointClasses
Ord, ReadPrec [DisjointClasses]
ReadPrec DisjointClasses
Int -> ReadS DisjointClasses
ReadS [DisjointClasses]
(Int -> ReadS DisjointClasses)
-> ReadS [DisjointClasses]
-> ReadPrec DisjointClasses
-> ReadPrec [DisjointClasses]
-> Read DisjointClasses
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DisjointClasses
readsPrec :: Int -> ReadS DisjointClasses
$creadList :: ReadS [DisjointClasses]
readList :: ReadS [DisjointClasses]
$creadPrec :: ReadPrec DisjointClasses
readPrec :: ReadPrec DisjointClasses
$creadListPrec :: ReadPrec [DisjointClasses]
readListPrec :: ReadPrec [DisjointClasses]
Read, Int -> DisjointClasses -> ShowS
[DisjointClasses] -> ShowS
DisjointClasses -> String
(Int -> DisjointClasses -> ShowS)
-> (DisjointClasses -> String)
-> ([DisjointClasses] -> ShowS)
-> Show DisjointClasses
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisjointClasses -> ShowS
showsPrec :: Int -> DisjointClasses -> ShowS
$cshow :: DisjointClasses -> String
show :: DisjointClasses -> String
$cshowList :: [DisjointClasses] -> ShowS
showList :: [DisjointClasses] -> ShowS
Show)

_DisjointClasses :: Name
_DisjointClasses = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DisjointClasses")

_DisjointClasses_annotations :: Name
_DisjointClasses_annotations = (String -> Name
Core.Name String
"annotations")

_DisjointClasses_classes :: Name
_DisjointClasses_classes = (String -> Name
Core.Name String
"classes")

-- | See https://www.w3.org/TR/owl2-syntax/#Disjoint_Union_of_Class_Expressions
data DisjointUnion = 
  DisjointUnion {
    DisjointUnion -> [Annotation]
disjointUnionAnnotations :: [Annotation],
    DisjointUnion -> Class
disjointUnionClass :: Class,
    DisjointUnion -> [ClassExpression]
disjointUnionClasses :: [ClassExpression]}
  deriving (DisjointUnion -> DisjointUnion -> Bool
(DisjointUnion -> DisjointUnion -> Bool)
-> (DisjointUnion -> DisjointUnion -> Bool) -> Eq DisjointUnion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisjointUnion -> DisjointUnion -> Bool
== :: DisjointUnion -> DisjointUnion -> Bool
$c/= :: DisjointUnion -> DisjointUnion -> Bool
/= :: DisjointUnion -> DisjointUnion -> Bool
Eq, Eq DisjointUnion
Eq DisjointUnion =>
(DisjointUnion -> DisjointUnion -> Ordering)
-> (DisjointUnion -> DisjointUnion -> Bool)
-> (DisjointUnion -> DisjointUnion -> Bool)
-> (DisjointUnion -> DisjointUnion -> Bool)
-> (DisjointUnion -> DisjointUnion -> Bool)
-> (DisjointUnion -> DisjointUnion -> DisjointUnion)
-> (DisjointUnion -> DisjointUnion -> DisjointUnion)
-> Ord DisjointUnion
DisjointUnion -> DisjointUnion -> Bool
DisjointUnion -> DisjointUnion -> Ordering
DisjointUnion -> DisjointUnion -> DisjointUnion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DisjointUnion -> DisjointUnion -> Ordering
compare :: DisjointUnion -> DisjointUnion -> Ordering
$c< :: DisjointUnion -> DisjointUnion -> Bool
< :: DisjointUnion -> DisjointUnion -> Bool
$c<= :: DisjointUnion -> DisjointUnion -> Bool
<= :: DisjointUnion -> DisjointUnion -> Bool
$c> :: DisjointUnion -> DisjointUnion -> Bool
> :: DisjointUnion -> DisjointUnion -> Bool
$c>= :: DisjointUnion -> DisjointUnion -> Bool
>= :: DisjointUnion -> DisjointUnion -> Bool
$cmax :: DisjointUnion -> DisjointUnion -> DisjointUnion
max :: DisjointUnion -> DisjointUnion -> DisjointUnion
$cmin :: DisjointUnion -> DisjointUnion -> DisjointUnion
min :: DisjointUnion -> DisjointUnion -> DisjointUnion
Ord, ReadPrec [DisjointUnion]
ReadPrec DisjointUnion
Int -> ReadS DisjointUnion
ReadS [DisjointUnion]
(Int -> ReadS DisjointUnion)
-> ReadS [DisjointUnion]
-> ReadPrec DisjointUnion
-> ReadPrec [DisjointUnion]
-> Read DisjointUnion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DisjointUnion
readsPrec :: Int -> ReadS DisjointUnion
$creadList :: ReadS [DisjointUnion]
readList :: ReadS [DisjointUnion]
$creadPrec :: ReadPrec DisjointUnion
readPrec :: ReadPrec DisjointUnion
$creadListPrec :: ReadPrec [DisjointUnion]
readListPrec :: ReadPrec [DisjointUnion]
Read, Int -> DisjointUnion -> ShowS
[DisjointUnion] -> ShowS
DisjointUnion -> String
(Int -> DisjointUnion -> ShowS)
-> (DisjointUnion -> String)
-> ([DisjointUnion] -> ShowS)
-> Show DisjointUnion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisjointUnion -> ShowS
showsPrec :: Int -> DisjointUnion -> ShowS
$cshow :: DisjointUnion -> String
show :: DisjointUnion -> String
$cshowList :: [DisjointUnion] -> ShowS
showList :: [DisjointUnion] -> ShowS
Show)

_DisjointUnion :: Name
_DisjointUnion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DisjointUnion")

_DisjointUnion_annotations :: Name
_DisjointUnion_annotations = (String -> Name
Core.Name String
"annotations")

_DisjointUnion_class :: Name
_DisjointUnion_class = (String -> Name
Core.Name String
"class")

_DisjointUnion_classes :: Name
_DisjointUnion_classes = (String -> Name
Core.Name String
"classes")

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
  deriving (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
(ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> Eq ObjectPropertyAxiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
== :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
$c/= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
/= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
Eq, Eq ObjectPropertyAxiom
Eq ObjectPropertyAxiom =>
(ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering)
-> (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> (ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool)
-> (ObjectPropertyAxiom
    -> ObjectPropertyAxiom -> ObjectPropertyAxiom)
-> (ObjectPropertyAxiom
    -> ObjectPropertyAxiom -> ObjectPropertyAxiom)
-> Ord ObjectPropertyAxiom
ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering
ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering
compare :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering
$c< :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
< :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
$c<= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
<= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
$c> :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
> :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
$c>= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
>= :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool
$cmax :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom
max :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom
$cmin :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom
min :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom
Ord, ReadPrec [ObjectPropertyAxiom]
ReadPrec ObjectPropertyAxiom
Int -> ReadS ObjectPropertyAxiom
ReadS [ObjectPropertyAxiom]
(Int -> ReadS ObjectPropertyAxiom)
-> ReadS [ObjectPropertyAxiom]
-> ReadPrec ObjectPropertyAxiom
-> ReadPrec [ObjectPropertyAxiom]
-> Read ObjectPropertyAxiom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectPropertyAxiom
readsPrec :: Int -> ReadS ObjectPropertyAxiom
$creadList :: ReadS [ObjectPropertyAxiom]
readList :: ReadS [ObjectPropertyAxiom]
$creadPrec :: ReadPrec ObjectPropertyAxiom
readPrec :: ReadPrec ObjectPropertyAxiom
$creadListPrec :: ReadPrec [ObjectPropertyAxiom]
readListPrec :: ReadPrec [ObjectPropertyAxiom]
Read, Int -> ObjectPropertyAxiom -> ShowS
[ObjectPropertyAxiom] -> ShowS
ObjectPropertyAxiom -> String
(Int -> ObjectPropertyAxiom -> ShowS)
-> (ObjectPropertyAxiom -> String)
-> ([ObjectPropertyAxiom] -> ShowS)
-> Show ObjectPropertyAxiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectPropertyAxiom -> ShowS
showsPrec :: Int -> ObjectPropertyAxiom -> ShowS
$cshow :: ObjectPropertyAxiom -> String
show :: ObjectPropertyAxiom -> String
$cshowList :: [ObjectPropertyAxiom] -> ShowS
showList :: [ObjectPropertyAxiom] -> ShowS
Show)

_ObjectPropertyAxiom :: Name
_ObjectPropertyAxiom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectPropertyAxiom")

_ObjectPropertyAxiom_asymmetricObjectProperty :: Name
_ObjectPropertyAxiom_asymmetricObjectProperty = (String -> Name
Core.Name String
"asymmetricObjectProperty")

_ObjectPropertyAxiom_disjointObjectProperties :: Name
_ObjectPropertyAxiom_disjointObjectProperties = (String -> Name
Core.Name String
"disjointObjectProperties")

_ObjectPropertyAxiom_equivalentObjectProperties :: Name
_ObjectPropertyAxiom_equivalentObjectProperties = (String -> Name
Core.Name String
"equivalentObjectProperties")

_ObjectPropertyAxiom_functionalObjectProperty :: Name
_ObjectPropertyAxiom_functionalObjectProperty = (String -> Name
Core.Name String
"functionalObjectProperty")

_ObjectPropertyAxiom_inverseFunctionalObjectProperty :: Name
_ObjectPropertyAxiom_inverseFunctionalObjectProperty = (String -> Name
Core.Name String
"inverseFunctionalObjectProperty")

_ObjectPropertyAxiom_inverseObjectProperties :: Name
_ObjectPropertyAxiom_inverseObjectProperties = (String -> Name
Core.Name String
"inverseObjectProperties")

_ObjectPropertyAxiom_irreflexiveObjectProperty :: Name
_ObjectPropertyAxiom_irreflexiveObjectProperty = (String -> Name
Core.Name String
"irreflexiveObjectProperty")

_ObjectPropertyAxiom_objectPropertyDomain :: Name
_ObjectPropertyAxiom_objectPropertyDomain = (String -> Name
Core.Name String
"objectPropertyDomain")

_ObjectPropertyAxiom_objectPropertyRange :: Name
_ObjectPropertyAxiom_objectPropertyRange = (String -> Name
Core.Name String
"objectPropertyRange")

_ObjectPropertyAxiom_reflexiveObjectProperty :: Name
_ObjectPropertyAxiom_reflexiveObjectProperty = (String -> Name
Core.Name String
"reflexiveObjectProperty")

_ObjectPropertyAxiom_subObjectPropertyOf :: Name
_ObjectPropertyAxiom_subObjectPropertyOf = (String -> Name
Core.Name String
"subObjectPropertyOf")

_ObjectPropertyAxiom_symmetricObjectProperty :: Name
_ObjectPropertyAxiom_symmetricObjectProperty = (String -> Name
Core.Name String
"symmetricObjectProperty")

_ObjectPropertyAxiom_transitiveObjectProperty :: Name
_ObjectPropertyAxiom_transitiveObjectProperty = (String -> Name
Core.Name String
"transitiveObjectProperty")

data SubObjectPropertyOf = 
  SubObjectPropertyOf {
    SubObjectPropertyOf -> [Annotation]
subObjectPropertyOfAnnotations :: [Annotation],
    SubObjectPropertyOf -> [ObjectPropertyExpression]
subObjectPropertyOfSubProperty :: [ObjectPropertyExpression],
    SubObjectPropertyOf -> ObjectPropertyExpression
subObjectPropertyOfSuperProperty :: ObjectPropertyExpression}
  deriving (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
(SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> Eq SubObjectPropertyOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
== :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
$c/= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
/= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
Eq, Eq SubObjectPropertyOf
Eq SubObjectPropertyOf =>
(SubObjectPropertyOf -> SubObjectPropertyOf -> Ordering)
-> (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> (SubObjectPropertyOf -> SubObjectPropertyOf -> Bool)
-> (SubObjectPropertyOf
    -> SubObjectPropertyOf -> SubObjectPropertyOf)
-> (SubObjectPropertyOf
    -> SubObjectPropertyOf -> SubObjectPropertyOf)
-> Ord SubObjectPropertyOf
SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
SubObjectPropertyOf -> SubObjectPropertyOf -> Ordering
SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SubObjectPropertyOf -> SubObjectPropertyOf -> Ordering
compare :: SubObjectPropertyOf -> SubObjectPropertyOf -> Ordering
$c< :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
< :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
$c<= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
<= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
$c> :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
> :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
$c>= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
>= :: SubObjectPropertyOf -> SubObjectPropertyOf -> Bool
$cmax :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf
max :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf
$cmin :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf
min :: SubObjectPropertyOf -> SubObjectPropertyOf -> SubObjectPropertyOf
Ord, ReadPrec [SubObjectPropertyOf]
ReadPrec SubObjectPropertyOf
Int -> ReadS SubObjectPropertyOf
ReadS [SubObjectPropertyOf]
(Int -> ReadS SubObjectPropertyOf)
-> ReadS [SubObjectPropertyOf]
-> ReadPrec SubObjectPropertyOf
-> ReadPrec [SubObjectPropertyOf]
-> Read SubObjectPropertyOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SubObjectPropertyOf
readsPrec :: Int -> ReadS SubObjectPropertyOf
$creadList :: ReadS [SubObjectPropertyOf]
readList :: ReadS [SubObjectPropertyOf]
$creadPrec :: ReadPrec SubObjectPropertyOf
readPrec :: ReadPrec SubObjectPropertyOf
$creadListPrec :: ReadPrec [SubObjectPropertyOf]
readListPrec :: ReadPrec [SubObjectPropertyOf]
Read, Int -> SubObjectPropertyOf -> ShowS
[SubObjectPropertyOf] -> ShowS
SubObjectPropertyOf -> String
(Int -> SubObjectPropertyOf -> ShowS)
-> (SubObjectPropertyOf -> String)
-> ([SubObjectPropertyOf] -> ShowS)
-> Show SubObjectPropertyOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubObjectPropertyOf -> ShowS
showsPrec :: Int -> SubObjectPropertyOf -> ShowS
$cshow :: SubObjectPropertyOf -> String
show :: SubObjectPropertyOf -> String
$cshowList :: [SubObjectPropertyOf] -> ShowS
showList :: [SubObjectPropertyOf] -> ShowS
Show)

_SubObjectPropertyOf :: Name
_SubObjectPropertyOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SubObjectPropertyOf")

_SubObjectPropertyOf_annotations :: Name
_SubObjectPropertyOf_annotations = (String -> Name
Core.Name String
"annotations")

_SubObjectPropertyOf_subProperty :: Name
_SubObjectPropertyOf_subProperty = (String -> Name
Core.Name String
"subProperty")

_SubObjectPropertyOf_superProperty :: Name
_SubObjectPropertyOf_superProperty = (String -> Name
Core.Name String
"superProperty")

data EquivalentObjectProperties = 
  EquivalentObjectProperties {
    EquivalentObjectProperties -> [Annotation]
equivalentObjectPropertiesAnnotations :: [Annotation],
    EquivalentObjectProperties -> [ObjectPropertyExpression]
equivalentObjectPropertiesProperties :: [ObjectPropertyExpression]}
  deriving (EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
(EquivalentObjectProperties -> EquivalentObjectProperties -> Bool)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> Bool)
-> Eq EquivalentObjectProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
== :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
$c/= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
/= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
Eq, Eq EquivalentObjectProperties
Eq EquivalentObjectProperties =>
(EquivalentObjectProperties
 -> EquivalentObjectProperties -> Ordering)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> Bool)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> Bool)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> Bool)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> Bool)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> EquivalentObjectProperties)
-> (EquivalentObjectProperties
    -> EquivalentObjectProperties -> EquivalentObjectProperties)
-> Ord EquivalentObjectProperties
EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
EquivalentObjectProperties
-> EquivalentObjectProperties -> Ordering
EquivalentObjectProperties
-> EquivalentObjectProperties -> EquivalentObjectProperties
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EquivalentObjectProperties
-> EquivalentObjectProperties -> Ordering
compare :: EquivalentObjectProperties
-> EquivalentObjectProperties -> Ordering
$c< :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
< :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
$c<= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
<= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
$c> :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
> :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
$c>= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
>= :: EquivalentObjectProperties -> EquivalentObjectProperties -> Bool
$cmax :: EquivalentObjectProperties
-> EquivalentObjectProperties -> EquivalentObjectProperties
max :: EquivalentObjectProperties
-> EquivalentObjectProperties -> EquivalentObjectProperties
$cmin :: EquivalentObjectProperties
-> EquivalentObjectProperties -> EquivalentObjectProperties
min :: EquivalentObjectProperties
-> EquivalentObjectProperties -> EquivalentObjectProperties
Ord, ReadPrec [EquivalentObjectProperties]
ReadPrec EquivalentObjectProperties
Int -> ReadS EquivalentObjectProperties
ReadS [EquivalentObjectProperties]
(Int -> ReadS EquivalentObjectProperties)
-> ReadS [EquivalentObjectProperties]
-> ReadPrec EquivalentObjectProperties
-> ReadPrec [EquivalentObjectProperties]
-> Read EquivalentObjectProperties
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EquivalentObjectProperties
readsPrec :: Int -> ReadS EquivalentObjectProperties
$creadList :: ReadS [EquivalentObjectProperties]
readList :: ReadS [EquivalentObjectProperties]
$creadPrec :: ReadPrec EquivalentObjectProperties
readPrec :: ReadPrec EquivalentObjectProperties
$creadListPrec :: ReadPrec [EquivalentObjectProperties]
readListPrec :: ReadPrec [EquivalentObjectProperties]
Read, Int -> EquivalentObjectProperties -> ShowS
[EquivalentObjectProperties] -> ShowS
EquivalentObjectProperties -> String
(Int -> EquivalentObjectProperties -> ShowS)
-> (EquivalentObjectProperties -> String)
-> ([EquivalentObjectProperties] -> ShowS)
-> Show EquivalentObjectProperties
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EquivalentObjectProperties -> ShowS
showsPrec :: Int -> EquivalentObjectProperties -> ShowS
$cshow :: EquivalentObjectProperties -> String
show :: EquivalentObjectProperties -> String
$cshowList :: [EquivalentObjectProperties] -> ShowS
showList :: [EquivalentObjectProperties] -> ShowS
Show)

_EquivalentObjectProperties :: Name
_EquivalentObjectProperties = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.EquivalentObjectProperties")

_EquivalentObjectProperties_annotations :: Name
_EquivalentObjectProperties_annotations = (String -> Name
Core.Name String
"annotations")

_EquivalentObjectProperties_properties :: Name
_EquivalentObjectProperties_properties = (String -> Name
Core.Name String
"properties")

data DisjointObjectProperties = 
  DisjointObjectProperties {
    DisjointObjectProperties -> [Annotation]
disjointObjectPropertiesAnnotations :: [Annotation],
    DisjointObjectProperties -> [ObjectPropertyExpression]
disjointObjectPropertiesProperties :: [ObjectPropertyExpression]}
  deriving (DisjointObjectProperties -> DisjointObjectProperties -> Bool
(DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> (DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> Eq DisjointObjectProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
== :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
$c/= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
/= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
Eq, Eq DisjointObjectProperties
Eq DisjointObjectProperties =>
(DisjointObjectProperties -> DisjointObjectProperties -> Ordering)
-> (DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> (DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> (DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> (DisjointObjectProperties -> DisjointObjectProperties -> Bool)
-> (DisjointObjectProperties
    -> DisjointObjectProperties -> DisjointObjectProperties)
-> (DisjointObjectProperties
    -> DisjointObjectProperties -> DisjointObjectProperties)
-> Ord DisjointObjectProperties
DisjointObjectProperties -> DisjointObjectProperties -> Bool
DisjointObjectProperties -> DisjointObjectProperties -> Ordering
DisjointObjectProperties
-> DisjointObjectProperties -> DisjointObjectProperties
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DisjointObjectProperties -> DisjointObjectProperties -> Ordering
compare :: DisjointObjectProperties -> DisjointObjectProperties -> Ordering
$c< :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
< :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
$c<= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
<= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
$c> :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
> :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
$c>= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
>= :: DisjointObjectProperties -> DisjointObjectProperties -> Bool
$cmax :: DisjointObjectProperties
-> DisjointObjectProperties -> DisjointObjectProperties
max :: DisjointObjectProperties
-> DisjointObjectProperties -> DisjointObjectProperties
$cmin :: DisjointObjectProperties
-> DisjointObjectProperties -> DisjointObjectProperties
min :: DisjointObjectProperties
-> DisjointObjectProperties -> DisjointObjectProperties
Ord, ReadPrec [DisjointObjectProperties]
ReadPrec DisjointObjectProperties
Int -> ReadS DisjointObjectProperties
ReadS [DisjointObjectProperties]
(Int -> ReadS DisjointObjectProperties)
-> ReadS [DisjointObjectProperties]
-> ReadPrec DisjointObjectProperties
-> ReadPrec [DisjointObjectProperties]
-> Read DisjointObjectProperties
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DisjointObjectProperties
readsPrec :: Int -> ReadS DisjointObjectProperties
$creadList :: ReadS [DisjointObjectProperties]
readList :: ReadS [DisjointObjectProperties]
$creadPrec :: ReadPrec DisjointObjectProperties
readPrec :: ReadPrec DisjointObjectProperties
$creadListPrec :: ReadPrec [DisjointObjectProperties]
readListPrec :: ReadPrec [DisjointObjectProperties]
Read, Int -> DisjointObjectProperties -> ShowS
[DisjointObjectProperties] -> ShowS
DisjointObjectProperties -> String
(Int -> DisjointObjectProperties -> ShowS)
-> (DisjointObjectProperties -> String)
-> ([DisjointObjectProperties] -> ShowS)
-> Show DisjointObjectProperties
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisjointObjectProperties -> ShowS
showsPrec :: Int -> DisjointObjectProperties -> ShowS
$cshow :: DisjointObjectProperties -> String
show :: DisjointObjectProperties -> String
$cshowList :: [DisjointObjectProperties] -> ShowS
showList :: [DisjointObjectProperties] -> ShowS
Show)

_DisjointObjectProperties :: Name
_DisjointObjectProperties = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DisjointObjectProperties")

_DisjointObjectProperties_annotations :: Name
_DisjointObjectProperties_annotations = (String -> Name
Core.Name String
"annotations")

_DisjointObjectProperties_properties :: Name
_DisjointObjectProperties_properties = (String -> Name
Core.Name String
"properties")

-- | See https://www.w3.org/TR/owl2-syntax/#Object_Property_Domain
data ObjectPropertyDomain = 
  ObjectPropertyDomain {
    ObjectPropertyDomain -> [Annotation]
objectPropertyDomainAnnotations :: [Annotation],
    ObjectPropertyDomain -> ObjectPropertyExpression
objectPropertyDomainProperty :: ObjectPropertyExpression,
    ObjectPropertyDomain -> ClassExpression
objectPropertyDomainDomain :: ClassExpression}
  deriving (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
(ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> Eq ObjectPropertyDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
== :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
$c/= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
/= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
Eq, Eq ObjectPropertyDomain
Eq ObjectPropertyDomain =>
(ObjectPropertyDomain -> ObjectPropertyDomain -> Ordering)
-> (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> (ObjectPropertyDomain -> ObjectPropertyDomain -> Bool)
-> (ObjectPropertyDomain
    -> ObjectPropertyDomain -> ObjectPropertyDomain)
-> (ObjectPropertyDomain
    -> ObjectPropertyDomain -> ObjectPropertyDomain)
-> Ord ObjectPropertyDomain
ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
ObjectPropertyDomain -> ObjectPropertyDomain -> Ordering
ObjectPropertyDomain
-> ObjectPropertyDomain -> ObjectPropertyDomain
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectPropertyDomain -> ObjectPropertyDomain -> Ordering
compare :: ObjectPropertyDomain -> ObjectPropertyDomain -> Ordering
$c< :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
< :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
$c<= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
<= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
$c> :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
> :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
$c>= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
>= :: ObjectPropertyDomain -> ObjectPropertyDomain -> Bool
$cmax :: ObjectPropertyDomain
-> ObjectPropertyDomain -> ObjectPropertyDomain
max :: ObjectPropertyDomain
-> ObjectPropertyDomain -> ObjectPropertyDomain
$cmin :: ObjectPropertyDomain
-> ObjectPropertyDomain -> ObjectPropertyDomain
min :: ObjectPropertyDomain
-> ObjectPropertyDomain -> ObjectPropertyDomain
Ord, ReadPrec [ObjectPropertyDomain]
ReadPrec ObjectPropertyDomain
Int -> ReadS ObjectPropertyDomain
ReadS [ObjectPropertyDomain]
(Int -> ReadS ObjectPropertyDomain)
-> ReadS [ObjectPropertyDomain]
-> ReadPrec ObjectPropertyDomain
-> ReadPrec [ObjectPropertyDomain]
-> Read ObjectPropertyDomain
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectPropertyDomain
readsPrec :: Int -> ReadS ObjectPropertyDomain
$creadList :: ReadS [ObjectPropertyDomain]
readList :: ReadS [ObjectPropertyDomain]
$creadPrec :: ReadPrec ObjectPropertyDomain
readPrec :: ReadPrec ObjectPropertyDomain
$creadListPrec :: ReadPrec [ObjectPropertyDomain]
readListPrec :: ReadPrec [ObjectPropertyDomain]
Read, Int -> ObjectPropertyDomain -> ShowS
[ObjectPropertyDomain] -> ShowS
ObjectPropertyDomain -> String
(Int -> ObjectPropertyDomain -> ShowS)
-> (ObjectPropertyDomain -> String)
-> ([ObjectPropertyDomain] -> ShowS)
-> Show ObjectPropertyDomain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectPropertyDomain -> ShowS
showsPrec :: Int -> ObjectPropertyDomain -> ShowS
$cshow :: ObjectPropertyDomain -> String
show :: ObjectPropertyDomain -> String
$cshowList :: [ObjectPropertyDomain] -> ShowS
showList :: [ObjectPropertyDomain] -> ShowS
Show)

_ObjectPropertyDomain :: Name
_ObjectPropertyDomain = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectPropertyDomain")

_ObjectPropertyDomain_annotations :: Name
_ObjectPropertyDomain_annotations = (String -> Name
Core.Name String
"annotations")

_ObjectPropertyDomain_property :: Name
_ObjectPropertyDomain_property = (String -> Name
Core.Name String
"property")

_ObjectPropertyDomain_domain :: Name
_ObjectPropertyDomain_domain = (String -> Name
Core.Name String
"domain")

-- | See https://www.w3.org/TR/owl2-syntax/#Object_Property_Range
data ObjectPropertyRange = 
  ObjectPropertyRange {
    ObjectPropertyRange -> [Annotation]
objectPropertyRangeAnnotations :: [Annotation],
    ObjectPropertyRange -> ObjectPropertyExpression
objectPropertyRangeProperty :: ObjectPropertyExpression,
    ObjectPropertyRange -> ClassExpression
objectPropertyRangeRange :: ClassExpression}
  deriving (ObjectPropertyRange -> ObjectPropertyRange -> Bool
(ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> (ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> Eq ObjectPropertyRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
== :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
$c/= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
/= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
Eq, Eq ObjectPropertyRange
Eq ObjectPropertyRange =>
(ObjectPropertyRange -> ObjectPropertyRange -> Ordering)
-> (ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> (ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> (ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> (ObjectPropertyRange -> ObjectPropertyRange -> Bool)
-> (ObjectPropertyRange
    -> ObjectPropertyRange -> ObjectPropertyRange)
-> (ObjectPropertyRange
    -> ObjectPropertyRange -> ObjectPropertyRange)
-> Ord ObjectPropertyRange
ObjectPropertyRange -> ObjectPropertyRange -> Bool
ObjectPropertyRange -> ObjectPropertyRange -> Ordering
ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectPropertyRange -> ObjectPropertyRange -> Ordering
compare :: ObjectPropertyRange -> ObjectPropertyRange -> Ordering
$c< :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
< :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
$c<= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
<= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
$c> :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
> :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
$c>= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
>= :: ObjectPropertyRange -> ObjectPropertyRange -> Bool
$cmax :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange
max :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange
$cmin :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange
min :: ObjectPropertyRange -> ObjectPropertyRange -> ObjectPropertyRange
Ord, ReadPrec [ObjectPropertyRange]
ReadPrec ObjectPropertyRange
Int -> ReadS ObjectPropertyRange
ReadS [ObjectPropertyRange]
(Int -> ReadS ObjectPropertyRange)
-> ReadS [ObjectPropertyRange]
-> ReadPrec ObjectPropertyRange
-> ReadPrec [ObjectPropertyRange]
-> Read ObjectPropertyRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectPropertyRange
readsPrec :: Int -> ReadS ObjectPropertyRange
$creadList :: ReadS [ObjectPropertyRange]
readList :: ReadS [ObjectPropertyRange]
$creadPrec :: ReadPrec ObjectPropertyRange
readPrec :: ReadPrec ObjectPropertyRange
$creadListPrec :: ReadPrec [ObjectPropertyRange]
readListPrec :: ReadPrec [ObjectPropertyRange]
Read, Int -> ObjectPropertyRange -> ShowS
[ObjectPropertyRange] -> ShowS
ObjectPropertyRange -> String
(Int -> ObjectPropertyRange -> ShowS)
-> (ObjectPropertyRange -> String)
-> ([ObjectPropertyRange] -> ShowS)
-> Show ObjectPropertyRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectPropertyRange -> ShowS
showsPrec :: Int -> ObjectPropertyRange -> ShowS
$cshow :: ObjectPropertyRange -> String
show :: ObjectPropertyRange -> String
$cshowList :: [ObjectPropertyRange] -> ShowS
showList :: [ObjectPropertyRange] -> ShowS
Show)

_ObjectPropertyRange :: Name
_ObjectPropertyRange = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectPropertyRange")

_ObjectPropertyRange_annotations :: Name
_ObjectPropertyRange_annotations = (String -> Name
Core.Name String
"annotations")

_ObjectPropertyRange_property :: Name
_ObjectPropertyRange_property = (String -> Name
Core.Name String
"property")

_ObjectPropertyRange_range :: Name
_ObjectPropertyRange_range = (String -> Name
Core.Name String
"range")

data InverseObjectProperties = 
  InverseObjectProperties {
    InverseObjectProperties -> [Annotation]
inverseObjectPropertiesAnnotations :: [Annotation],
    InverseObjectProperties -> ObjectPropertyExpression
inverseObjectPropertiesProperty1 :: ObjectPropertyExpression,
    InverseObjectProperties -> ObjectPropertyExpression
inverseObjectPropertiesProperty2 :: ObjectPropertyExpression}
  deriving (InverseObjectProperties -> InverseObjectProperties -> Bool
(InverseObjectProperties -> InverseObjectProperties -> Bool)
-> (InverseObjectProperties -> InverseObjectProperties -> Bool)
-> Eq InverseObjectProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InverseObjectProperties -> InverseObjectProperties -> Bool
== :: InverseObjectProperties -> InverseObjectProperties -> Bool
$c/= :: InverseObjectProperties -> InverseObjectProperties -> Bool
/= :: InverseObjectProperties -> InverseObjectProperties -> Bool
Eq, Eq InverseObjectProperties
Eq InverseObjectProperties =>
(InverseObjectProperties -> InverseObjectProperties -> Ordering)
-> (InverseObjectProperties -> InverseObjectProperties -> Bool)
-> (InverseObjectProperties -> InverseObjectProperties -> Bool)
-> (InverseObjectProperties -> InverseObjectProperties -> Bool)
-> (InverseObjectProperties -> InverseObjectProperties -> Bool)
-> (InverseObjectProperties
    -> InverseObjectProperties -> InverseObjectProperties)
-> (InverseObjectProperties
    -> InverseObjectProperties -> InverseObjectProperties)
-> Ord InverseObjectProperties
InverseObjectProperties -> InverseObjectProperties -> Bool
InverseObjectProperties -> InverseObjectProperties -> Ordering
InverseObjectProperties
-> InverseObjectProperties -> InverseObjectProperties
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InverseObjectProperties -> InverseObjectProperties -> Ordering
compare :: InverseObjectProperties -> InverseObjectProperties -> Ordering
$c< :: InverseObjectProperties -> InverseObjectProperties -> Bool
< :: InverseObjectProperties -> InverseObjectProperties -> Bool
$c<= :: InverseObjectProperties -> InverseObjectProperties -> Bool
<= :: InverseObjectProperties -> InverseObjectProperties -> Bool
$c> :: InverseObjectProperties -> InverseObjectProperties -> Bool
> :: InverseObjectProperties -> InverseObjectProperties -> Bool
$c>= :: InverseObjectProperties -> InverseObjectProperties -> Bool
>= :: InverseObjectProperties -> InverseObjectProperties -> Bool
$cmax :: InverseObjectProperties
-> InverseObjectProperties -> InverseObjectProperties
max :: InverseObjectProperties
-> InverseObjectProperties -> InverseObjectProperties
$cmin :: InverseObjectProperties
-> InverseObjectProperties -> InverseObjectProperties
min :: InverseObjectProperties
-> InverseObjectProperties -> InverseObjectProperties
Ord, ReadPrec [InverseObjectProperties]
ReadPrec InverseObjectProperties
Int -> ReadS InverseObjectProperties
ReadS [InverseObjectProperties]
(Int -> ReadS InverseObjectProperties)
-> ReadS [InverseObjectProperties]
-> ReadPrec InverseObjectProperties
-> ReadPrec [InverseObjectProperties]
-> Read InverseObjectProperties
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InverseObjectProperties
readsPrec :: Int -> ReadS InverseObjectProperties
$creadList :: ReadS [InverseObjectProperties]
readList :: ReadS [InverseObjectProperties]
$creadPrec :: ReadPrec InverseObjectProperties
readPrec :: ReadPrec InverseObjectProperties
$creadListPrec :: ReadPrec [InverseObjectProperties]
readListPrec :: ReadPrec [InverseObjectProperties]
Read, Int -> InverseObjectProperties -> ShowS
[InverseObjectProperties] -> ShowS
InverseObjectProperties -> String
(Int -> InverseObjectProperties -> ShowS)
-> (InverseObjectProperties -> String)
-> ([InverseObjectProperties] -> ShowS)
-> Show InverseObjectProperties
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InverseObjectProperties -> ShowS
showsPrec :: Int -> InverseObjectProperties -> ShowS
$cshow :: InverseObjectProperties -> String
show :: InverseObjectProperties -> String
$cshowList :: [InverseObjectProperties] -> ShowS
showList :: [InverseObjectProperties] -> ShowS
Show)

_InverseObjectProperties :: Name
_InverseObjectProperties = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.InverseObjectProperties")

_InverseObjectProperties_annotations :: Name
_InverseObjectProperties_annotations = (String -> Name
Core.Name String
"annotations")

_InverseObjectProperties_property1 :: Name
_InverseObjectProperties_property1 = (String -> Name
Core.Name String
"property1")

_InverseObjectProperties_property2 :: Name
_InverseObjectProperties_property2 = (String -> Name
Core.Name String
"property2")

data FunctionalObjectProperty = 
  FunctionalObjectProperty {
    FunctionalObjectProperty -> [Annotation]
functionalObjectPropertyAnnotations :: [Annotation],
    FunctionalObjectProperty -> ObjectPropertyExpression
functionalObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
(FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> Eq FunctionalObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
== :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
$c/= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
/= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
Eq, Eq FunctionalObjectProperty
Eq FunctionalObjectProperty =>
(FunctionalObjectProperty -> FunctionalObjectProperty -> Ordering)
-> (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> (FunctionalObjectProperty -> FunctionalObjectProperty -> Bool)
-> (FunctionalObjectProperty
    -> FunctionalObjectProperty -> FunctionalObjectProperty)
-> (FunctionalObjectProperty
    -> FunctionalObjectProperty -> FunctionalObjectProperty)
-> Ord FunctionalObjectProperty
FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
FunctionalObjectProperty -> FunctionalObjectProperty -> Ordering
FunctionalObjectProperty
-> FunctionalObjectProperty -> FunctionalObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FunctionalObjectProperty -> FunctionalObjectProperty -> Ordering
compare :: FunctionalObjectProperty -> FunctionalObjectProperty -> Ordering
$c< :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
< :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
$c<= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
<= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
$c> :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
> :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
$c>= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
>= :: FunctionalObjectProperty -> FunctionalObjectProperty -> Bool
$cmax :: FunctionalObjectProperty
-> FunctionalObjectProperty -> FunctionalObjectProperty
max :: FunctionalObjectProperty
-> FunctionalObjectProperty -> FunctionalObjectProperty
$cmin :: FunctionalObjectProperty
-> FunctionalObjectProperty -> FunctionalObjectProperty
min :: FunctionalObjectProperty
-> FunctionalObjectProperty -> FunctionalObjectProperty
Ord, ReadPrec [FunctionalObjectProperty]
ReadPrec FunctionalObjectProperty
Int -> ReadS FunctionalObjectProperty
ReadS [FunctionalObjectProperty]
(Int -> ReadS FunctionalObjectProperty)
-> ReadS [FunctionalObjectProperty]
-> ReadPrec FunctionalObjectProperty
-> ReadPrec [FunctionalObjectProperty]
-> Read FunctionalObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionalObjectProperty
readsPrec :: Int -> ReadS FunctionalObjectProperty
$creadList :: ReadS [FunctionalObjectProperty]
readList :: ReadS [FunctionalObjectProperty]
$creadPrec :: ReadPrec FunctionalObjectProperty
readPrec :: ReadPrec FunctionalObjectProperty
$creadListPrec :: ReadPrec [FunctionalObjectProperty]
readListPrec :: ReadPrec [FunctionalObjectProperty]
Read, Int -> FunctionalObjectProperty -> ShowS
[FunctionalObjectProperty] -> ShowS
FunctionalObjectProperty -> String
(Int -> FunctionalObjectProperty -> ShowS)
-> (FunctionalObjectProperty -> String)
-> ([FunctionalObjectProperty] -> ShowS)
-> Show FunctionalObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionalObjectProperty -> ShowS
showsPrec :: Int -> FunctionalObjectProperty -> ShowS
$cshow :: FunctionalObjectProperty -> String
show :: FunctionalObjectProperty -> String
$cshowList :: [FunctionalObjectProperty] -> ShowS
showList :: [FunctionalObjectProperty] -> ShowS
Show)

_FunctionalObjectProperty :: Name
_FunctionalObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.FunctionalObjectProperty")

_FunctionalObjectProperty_annotations :: Name
_FunctionalObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_FunctionalObjectProperty_property :: Name
_FunctionalObjectProperty_property = (String -> Name
Core.Name String
"property")

data InverseFunctionalObjectProperty = 
  InverseFunctionalObjectProperty {
    InverseFunctionalObjectProperty -> [Annotation]
inverseFunctionalObjectPropertyAnnotations :: [Annotation],
    InverseFunctionalObjectProperty -> ObjectPropertyExpression
inverseFunctionalObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
(InverseFunctionalObjectProperty
 -> InverseFunctionalObjectProperty -> Bool)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty -> Bool)
-> Eq InverseFunctionalObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
== :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
$c/= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
/= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
Eq, Eq InverseFunctionalObjectProperty
Eq InverseFunctionalObjectProperty =>
(InverseFunctionalObjectProperty
 -> InverseFunctionalObjectProperty -> Ordering)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty -> Bool)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty -> Bool)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty -> Bool)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty -> Bool)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty)
-> (InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty
    -> InverseFunctionalObjectProperty)
-> Ord InverseFunctionalObjectProperty
InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Ordering
InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Ordering
compare :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Ordering
$c< :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
< :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
$c<= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
<= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
$c> :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
> :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
$c>= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
>= :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty -> Bool
$cmax :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
max :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
$cmin :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
min :: InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
-> InverseFunctionalObjectProperty
Ord, ReadPrec [InverseFunctionalObjectProperty]
ReadPrec InverseFunctionalObjectProperty
Int -> ReadS InverseFunctionalObjectProperty
ReadS [InverseFunctionalObjectProperty]
(Int -> ReadS InverseFunctionalObjectProperty)
-> ReadS [InverseFunctionalObjectProperty]
-> ReadPrec InverseFunctionalObjectProperty
-> ReadPrec [InverseFunctionalObjectProperty]
-> Read InverseFunctionalObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InverseFunctionalObjectProperty
readsPrec :: Int -> ReadS InverseFunctionalObjectProperty
$creadList :: ReadS [InverseFunctionalObjectProperty]
readList :: ReadS [InverseFunctionalObjectProperty]
$creadPrec :: ReadPrec InverseFunctionalObjectProperty
readPrec :: ReadPrec InverseFunctionalObjectProperty
$creadListPrec :: ReadPrec [InverseFunctionalObjectProperty]
readListPrec :: ReadPrec [InverseFunctionalObjectProperty]
Read, Int -> InverseFunctionalObjectProperty -> ShowS
[InverseFunctionalObjectProperty] -> ShowS
InverseFunctionalObjectProperty -> String
(Int -> InverseFunctionalObjectProperty -> ShowS)
-> (InverseFunctionalObjectProperty -> String)
-> ([InverseFunctionalObjectProperty] -> ShowS)
-> Show InverseFunctionalObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InverseFunctionalObjectProperty -> ShowS
showsPrec :: Int -> InverseFunctionalObjectProperty -> ShowS
$cshow :: InverseFunctionalObjectProperty -> String
show :: InverseFunctionalObjectProperty -> String
$cshowList :: [InverseFunctionalObjectProperty] -> ShowS
showList :: [InverseFunctionalObjectProperty] -> ShowS
Show)

_InverseFunctionalObjectProperty :: Name
_InverseFunctionalObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.InverseFunctionalObjectProperty")

_InverseFunctionalObjectProperty_annotations :: Name
_InverseFunctionalObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_InverseFunctionalObjectProperty_property :: Name
_InverseFunctionalObjectProperty_property = (String -> Name
Core.Name String
"property")

data ReflexiveObjectProperty = 
  ReflexiveObjectProperty {
    ReflexiveObjectProperty -> [Annotation]
reflexiveObjectPropertyAnnotations :: [Annotation],
    ReflexiveObjectProperty -> ObjectPropertyExpression
reflexiveObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
(ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> Eq ReflexiveObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
== :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
$c/= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
/= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
Eq, Eq ReflexiveObjectProperty
Eq ReflexiveObjectProperty =>
(ReflexiveObjectProperty -> ReflexiveObjectProperty -> Ordering)
-> (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> (ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool)
-> (ReflexiveObjectProperty
    -> ReflexiveObjectProperty -> ReflexiveObjectProperty)
-> (ReflexiveObjectProperty
    -> ReflexiveObjectProperty -> ReflexiveObjectProperty)
-> Ord ReflexiveObjectProperty
ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
ReflexiveObjectProperty -> ReflexiveObjectProperty -> Ordering
ReflexiveObjectProperty
-> ReflexiveObjectProperty -> ReflexiveObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Ordering
compare :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Ordering
$c< :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
< :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
$c<= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
<= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
$c> :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
> :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
$c>= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
>= :: ReflexiveObjectProperty -> ReflexiveObjectProperty -> Bool
$cmax :: ReflexiveObjectProperty
-> ReflexiveObjectProperty -> ReflexiveObjectProperty
max :: ReflexiveObjectProperty
-> ReflexiveObjectProperty -> ReflexiveObjectProperty
$cmin :: ReflexiveObjectProperty
-> ReflexiveObjectProperty -> ReflexiveObjectProperty
min :: ReflexiveObjectProperty
-> ReflexiveObjectProperty -> ReflexiveObjectProperty
Ord, ReadPrec [ReflexiveObjectProperty]
ReadPrec ReflexiveObjectProperty
Int -> ReadS ReflexiveObjectProperty
ReadS [ReflexiveObjectProperty]
(Int -> ReadS ReflexiveObjectProperty)
-> ReadS [ReflexiveObjectProperty]
-> ReadPrec ReflexiveObjectProperty
-> ReadPrec [ReflexiveObjectProperty]
-> Read ReflexiveObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ReflexiveObjectProperty
readsPrec :: Int -> ReadS ReflexiveObjectProperty
$creadList :: ReadS [ReflexiveObjectProperty]
readList :: ReadS [ReflexiveObjectProperty]
$creadPrec :: ReadPrec ReflexiveObjectProperty
readPrec :: ReadPrec ReflexiveObjectProperty
$creadListPrec :: ReadPrec [ReflexiveObjectProperty]
readListPrec :: ReadPrec [ReflexiveObjectProperty]
Read, Int -> ReflexiveObjectProperty -> ShowS
[ReflexiveObjectProperty] -> ShowS
ReflexiveObjectProperty -> String
(Int -> ReflexiveObjectProperty -> ShowS)
-> (ReflexiveObjectProperty -> String)
-> ([ReflexiveObjectProperty] -> ShowS)
-> Show ReflexiveObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReflexiveObjectProperty -> ShowS
showsPrec :: Int -> ReflexiveObjectProperty -> ShowS
$cshow :: ReflexiveObjectProperty -> String
show :: ReflexiveObjectProperty -> String
$cshowList :: [ReflexiveObjectProperty] -> ShowS
showList :: [ReflexiveObjectProperty] -> ShowS
Show)

_ReflexiveObjectProperty :: Name
_ReflexiveObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ReflexiveObjectProperty")

_ReflexiveObjectProperty_annotations :: Name
_ReflexiveObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_ReflexiveObjectProperty_property :: Name
_ReflexiveObjectProperty_property = (String -> Name
Core.Name String
"property")

data IrreflexiveObjectProperty = 
  IrreflexiveObjectProperty {
    IrreflexiveObjectProperty -> [Annotation]
irreflexiveObjectPropertyAnnotations :: [Annotation],
    IrreflexiveObjectProperty -> ObjectPropertyExpression
irreflexiveObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
(IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> Eq IrreflexiveObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
== :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
$c/= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
/= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
Eq, Eq IrreflexiveObjectProperty
Eq IrreflexiveObjectProperty =>
(IrreflexiveObjectProperty
 -> IrreflexiveObjectProperty -> Ordering)
-> (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> (IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool)
-> (IrreflexiveObjectProperty
    -> IrreflexiveObjectProperty -> IrreflexiveObjectProperty)
-> (IrreflexiveObjectProperty
    -> IrreflexiveObjectProperty -> IrreflexiveObjectProperty)
-> Ord IrreflexiveObjectProperty
IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Ordering
IrreflexiveObjectProperty
-> IrreflexiveObjectProperty -> IrreflexiveObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Ordering
compare :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Ordering
$c< :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
< :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
$c<= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
<= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
$c> :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
> :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
$c>= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
>= :: IrreflexiveObjectProperty -> IrreflexiveObjectProperty -> Bool
$cmax :: IrreflexiveObjectProperty
-> IrreflexiveObjectProperty -> IrreflexiveObjectProperty
max :: IrreflexiveObjectProperty
-> IrreflexiveObjectProperty -> IrreflexiveObjectProperty
$cmin :: IrreflexiveObjectProperty
-> IrreflexiveObjectProperty -> IrreflexiveObjectProperty
min :: IrreflexiveObjectProperty
-> IrreflexiveObjectProperty -> IrreflexiveObjectProperty
Ord, ReadPrec [IrreflexiveObjectProperty]
ReadPrec IrreflexiveObjectProperty
Int -> ReadS IrreflexiveObjectProperty
ReadS [IrreflexiveObjectProperty]
(Int -> ReadS IrreflexiveObjectProperty)
-> ReadS [IrreflexiveObjectProperty]
-> ReadPrec IrreflexiveObjectProperty
-> ReadPrec [IrreflexiveObjectProperty]
-> Read IrreflexiveObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IrreflexiveObjectProperty
readsPrec :: Int -> ReadS IrreflexiveObjectProperty
$creadList :: ReadS [IrreflexiveObjectProperty]
readList :: ReadS [IrreflexiveObjectProperty]
$creadPrec :: ReadPrec IrreflexiveObjectProperty
readPrec :: ReadPrec IrreflexiveObjectProperty
$creadListPrec :: ReadPrec [IrreflexiveObjectProperty]
readListPrec :: ReadPrec [IrreflexiveObjectProperty]
Read, Int -> IrreflexiveObjectProperty -> ShowS
[IrreflexiveObjectProperty] -> ShowS
IrreflexiveObjectProperty -> String
(Int -> IrreflexiveObjectProperty -> ShowS)
-> (IrreflexiveObjectProperty -> String)
-> ([IrreflexiveObjectProperty] -> ShowS)
-> Show IrreflexiveObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IrreflexiveObjectProperty -> ShowS
showsPrec :: Int -> IrreflexiveObjectProperty -> ShowS
$cshow :: IrreflexiveObjectProperty -> String
show :: IrreflexiveObjectProperty -> String
$cshowList :: [IrreflexiveObjectProperty] -> ShowS
showList :: [IrreflexiveObjectProperty] -> ShowS
Show)

_IrreflexiveObjectProperty :: Name
_IrreflexiveObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.IrreflexiveObjectProperty")

_IrreflexiveObjectProperty_annotations :: Name
_IrreflexiveObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_IrreflexiveObjectProperty_property :: Name
_IrreflexiveObjectProperty_property = (String -> Name
Core.Name String
"property")

data SymmetricObjectProperty = 
  SymmetricObjectProperty {
    SymmetricObjectProperty -> [Annotation]
symmetricObjectPropertyAnnotations :: [Annotation],
    SymmetricObjectProperty -> ObjectPropertyExpression
symmetricObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
(SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> Eq SymmetricObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
== :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
$c/= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
/= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
Eq, Eq SymmetricObjectProperty
Eq SymmetricObjectProperty =>
(SymmetricObjectProperty -> SymmetricObjectProperty -> Ordering)
-> (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> (SymmetricObjectProperty -> SymmetricObjectProperty -> Bool)
-> (SymmetricObjectProperty
    -> SymmetricObjectProperty -> SymmetricObjectProperty)
-> (SymmetricObjectProperty
    -> SymmetricObjectProperty -> SymmetricObjectProperty)
-> Ord SymmetricObjectProperty
SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
SymmetricObjectProperty -> SymmetricObjectProperty -> Ordering
SymmetricObjectProperty
-> SymmetricObjectProperty -> SymmetricObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SymmetricObjectProperty -> SymmetricObjectProperty -> Ordering
compare :: SymmetricObjectProperty -> SymmetricObjectProperty -> Ordering
$c< :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
< :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
$c<= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
<= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
$c> :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
> :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
$c>= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
>= :: SymmetricObjectProperty -> SymmetricObjectProperty -> Bool
$cmax :: SymmetricObjectProperty
-> SymmetricObjectProperty -> SymmetricObjectProperty
max :: SymmetricObjectProperty
-> SymmetricObjectProperty -> SymmetricObjectProperty
$cmin :: SymmetricObjectProperty
-> SymmetricObjectProperty -> SymmetricObjectProperty
min :: SymmetricObjectProperty
-> SymmetricObjectProperty -> SymmetricObjectProperty
Ord, ReadPrec [SymmetricObjectProperty]
ReadPrec SymmetricObjectProperty
Int -> ReadS SymmetricObjectProperty
ReadS [SymmetricObjectProperty]
(Int -> ReadS SymmetricObjectProperty)
-> ReadS [SymmetricObjectProperty]
-> ReadPrec SymmetricObjectProperty
-> ReadPrec [SymmetricObjectProperty]
-> Read SymmetricObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SymmetricObjectProperty
readsPrec :: Int -> ReadS SymmetricObjectProperty
$creadList :: ReadS [SymmetricObjectProperty]
readList :: ReadS [SymmetricObjectProperty]
$creadPrec :: ReadPrec SymmetricObjectProperty
readPrec :: ReadPrec SymmetricObjectProperty
$creadListPrec :: ReadPrec [SymmetricObjectProperty]
readListPrec :: ReadPrec [SymmetricObjectProperty]
Read, Int -> SymmetricObjectProperty -> ShowS
[SymmetricObjectProperty] -> ShowS
SymmetricObjectProperty -> String
(Int -> SymmetricObjectProperty -> ShowS)
-> (SymmetricObjectProperty -> String)
-> ([SymmetricObjectProperty] -> ShowS)
-> Show SymmetricObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SymmetricObjectProperty -> ShowS
showsPrec :: Int -> SymmetricObjectProperty -> ShowS
$cshow :: SymmetricObjectProperty -> String
show :: SymmetricObjectProperty -> String
$cshowList :: [SymmetricObjectProperty] -> ShowS
showList :: [SymmetricObjectProperty] -> ShowS
Show)

_SymmetricObjectProperty :: Name
_SymmetricObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SymmetricObjectProperty")

_SymmetricObjectProperty_annotations :: Name
_SymmetricObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_SymmetricObjectProperty_property :: Name
_SymmetricObjectProperty_property = (String -> Name
Core.Name String
"property")

data AsymmetricObjectProperty = 
  AsymmetricObjectProperty {
    AsymmetricObjectProperty -> [Annotation]
asymmetricObjectPropertyAnnotations :: [Annotation],
    AsymmetricObjectProperty -> ObjectPropertyExpression
asymmetricObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
(AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> Eq AsymmetricObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
== :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
$c/= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
/= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
Eq, Eq AsymmetricObjectProperty
Eq AsymmetricObjectProperty =>
(AsymmetricObjectProperty -> AsymmetricObjectProperty -> Ordering)
-> (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> (AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool)
-> (AsymmetricObjectProperty
    -> AsymmetricObjectProperty -> AsymmetricObjectProperty)
-> (AsymmetricObjectProperty
    -> AsymmetricObjectProperty -> AsymmetricObjectProperty)
-> Ord AsymmetricObjectProperty
AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
AsymmetricObjectProperty -> AsymmetricObjectProperty -> Ordering
AsymmetricObjectProperty
-> AsymmetricObjectProperty -> AsymmetricObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Ordering
compare :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Ordering
$c< :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
< :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
$c<= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
<= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
$c> :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
> :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
$c>= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
>= :: AsymmetricObjectProperty -> AsymmetricObjectProperty -> Bool
$cmax :: AsymmetricObjectProperty
-> AsymmetricObjectProperty -> AsymmetricObjectProperty
max :: AsymmetricObjectProperty
-> AsymmetricObjectProperty -> AsymmetricObjectProperty
$cmin :: AsymmetricObjectProperty
-> AsymmetricObjectProperty -> AsymmetricObjectProperty
min :: AsymmetricObjectProperty
-> AsymmetricObjectProperty -> AsymmetricObjectProperty
Ord, ReadPrec [AsymmetricObjectProperty]
ReadPrec AsymmetricObjectProperty
Int -> ReadS AsymmetricObjectProperty
ReadS [AsymmetricObjectProperty]
(Int -> ReadS AsymmetricObjectProperty)
-> ReadS [AsymmetricObjectProperty]
-> ReadPrec AsymmetricObjectProperty
-> ReadPrec [AsymmetricObjectProperty]
-> Read AsymmetricObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AsymmetricObjectProperty
readsPrec :: Int -> ReadS AsymmetricObjectProperty
$creadList :: ReadS [AsymmetricObjectProperty]
readList :: ReadS [AsymmetricObjectProperty]
$creadPrec :: ReadPrec AsymmetricObjectProperty
readPrec :: ReadPrec AsymmetricObjectProperty
$creadListPrec :: ReadPrec [AsymmetricObjectProperty]
readListPrec :: ReadPrec [AsymmetricObjectProperty]
Read, Int -> AsymmetricObjectProperty -> ShowS
[AsymmetricObjectProperty] -> ShowS
AsymmetricObjectProperty -> String
(Int -> AsymmetricObjectProperty -> ShowS)
-> (AsymmetricObjectProperty -> String)
-> ([AsymmetricObjectProperty] -> ShowS)
-> Show AsymmetricObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AsymmetricObjectProperty -> ShowS
showsPrec :: Int -> AsymmetricObjectProperty -> ShowS
$cshow :: AsymmetricObjectProperty -> String
show :: AsymmetricObjectProperty -> String
$cshowList :: [AsymmetricObjectProperty] -> ShowS
showList :: [AsymmetricObjectProperty] -> ShowS
Show)

_AsymmetricObjectProperty :: Name
_AsymmetricObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.AsymmetricObjectProperty")

_AsymmetricObjectProperty_annotations :: Name
_AsymmetricObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_AsymmetricObjectProperty_property :: Name
_AsymmetricObjectProperty_property = (String -> Name
Core.Name String
"property")

data TransitiveObjectProperty = 
  TransitiveObjectProperty {
    TransitiveObjectProperty -> [Annotation]
transitiveObjectPropertyAnnotations :: [Annotation],
    TransitiveObjectProperty -> ObjectPropertyExpression
transitiveObjectPropertyProperty :: ObjectPropertyExpression}
  deriving (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
(TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> Eq TransitiveObjectProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
== :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
$c/= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
/= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
Eq, Eq TransitiveObjectProperty
Eq TransitiveObjectProperty =>
(TransitiveObjectProperty -> TransitiveObjectProperty -> Ordering)
-> (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> (TransitiveObjectProperty -> TransitiveObjectProperty -> Bool)
-> (TransitiveObjectProperty
    -> TransitiveObjectProperty -> TransitiveObjectProperty)
-> (TransitiveObjectProperty
    -> TransitiveObjectProperty -> TransitiveObjectProperty)
-> Ord TransitiveObjectProperty
TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
TransitiveObjectProperty -> TransitiveObjectProperty -> Ordering
TransitiveObjectProperty
-> TransitiveObjectProperty -> TransitiveObjectProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TransitiveObjectProperty -> TransitiveObjectProperty -> Ordering
compare :: TransitiveObjectProperty -> TransitiveObjectProperty -> Ordering
$c< :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
< :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
$c<= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
<= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
$c> :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
> :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
$c>= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
>= :: TransitiveObjectProperty -> TransitiveObjectProperty -> Bool
$cmax :: TransitiveObjectProperty
-> TransitiveObjectProperty -> TransitiveObjectProperty
max :: TransitiveObjectProperty
-> TransitiveObjectProperty -> TransitiveObjectProperty
$cmin :: TransitiveObjectProperty
-> TransitiveObjectProperty -> TransitiveObjectProperty
min :: TransitiveObjectProperty
-> TransitiveObjectProperty -> TransitiveObjectProperty
Ord, ReadPrec [TransitiveObjectProperty]
ReadPrec TransitiveObjectProperty
Int -> ReadS TransitiveObjectProperty
ReadS [TransitiveObjectProperty]
(Int -> ReadS TransitiveObjectProperty)
-> ReadS [TransitiveObjectProperty]
-> ReadPrec TransitiveObjectProperty
-> ReadPrec [TransitiveObjectProperty]
-> Read TransitiveObjectProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TransitiveObjectProperty
readsPrec :: Int -> ReadS TransitiveObjectProperty
$creadList :: ReadS [TransitiveObjectProperty]
readList :: ReadS [TransitiveObjectProperty]
$creadPrec :: ReadPrec TransitiveObjectProperty
readPrec :: ReadPrec TransitiveObjectProperty
$creadListPrec :: ReadPrec [TransitiveObjectProperty]
readListPrec :: ReadPrec [TransitiveObjectProperty]
Read, Int -> TransitiveObjectProperty -> ShowS
[TransitiveObjectProperty] -> ShowS
TransitiveObjectProperty -> String
(Int -> TransitiveObjectProperty -> ShowS)
-> (TransitiveObjectProperty -> String)
-> ([TransitiveObjectProperty] -> ShowS)
-> Show TransitiveObjectProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransitiveObjectProperty -> ShowS
showsPrec :: Int -> TransitiveObjectProperty -> ShowS
$cshow :: TransitiveObjectProperty -> String
show :: TransitiveObjectProperty -> String
$cshowList :: [TransitiveObjectProperty] -> ShowS
showList :: [TransitiveObjectProperty] -> ShowS
Show)

_TransitiveObjectProperty :: Name
_TransitiveObjectProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.TransitiveObjectProperty")

_TransitiveObjectProperty_annotations :: Name
_TransitiveObjectProperty_annotations = (String -> Name
Core.Name String
"annotations")

_TransitiveObjectProperty_property :: Name
_TransitiveObjectProperty_property = (String -> Name
Core.Name String
"property")

data DataPropertyAxiom = 
  DataPropertyAxiomDataPropertyAxiom DataPropertyAxiom |
  DataPropertyAxiomDataPropertyRange DataPropertyRange |
  DataPropertyAxiomDisjointDataProperties DisjointDataProperties |
  DataPropertyAxiomEquivalentDataProperties EquivalentDataProperties |
  DataPropertyAxiomFunctionalDataProperty FunctionalDataProperty |
  DataPropertyAxiomSubDataPropertyOf SubDataPropertyOf
  deriving (DataPropertyAxiom -> DataPropertyAxiom -> Bool
(DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> (DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> Eq DataPropertyAxiom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
== :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
$c/= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
/= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
Eq, Eq DataPropertyAxiom
Eq DataPropertyAxiom =>
(DataPropertyAxiom -> DataPropertyAxiom -> Ordering)
-> (DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> (DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> (DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> (DataPropertyAxiom -> DataPropertyAxiom -> Bool)
-> (DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom)
-> (DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom)
-> Ord DataPropertyAxiom
DataPropertyAxiom -> DataPropertyAxiom -> Bool
DataPropertyAxiom -> DataPropertyAxiom -> Ordering
DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPropertyAxiom -> DataPropertyAxiom -> Ordering
compare :: DataPropertyAxiom -> DataPropertyAxiom -> Ordering
$c< :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
< :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
$c<= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
<= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
$c> :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
> :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
$c>= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
>= :: DataPropertyAxiom -> DataPropertyAxiom -> Bool
$cmax :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom
max :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom
$cmin :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom
min :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom
Ord, ReadPrec [DataPropertyAxiom]
ReadPrec DataPropertyAxiom
Int -> ReadS DataPropertyAxiom
ReadS [DataPropertyAxiom]
(Int -> ReadS DataPropertyAxiom)
-> ReadS [DataPropertyAxiom]
-> ReadPrec DataPropertyAxiom
-> ReadPrec [DataPropertyAxiom]
-> Read DataPropertyAxiom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPropertyAxiom
readsPrec :: Int -> ReadS DataPropertyAxiom
$creadList :: ReadS [DataPropertyAxiom]
readList :: ReadS [DataPropertyAxiom]
$creadPrec :: ReadPrec DataPropertyAxiom
readPrec :: ReadPrec DataPropertyAxiom
$creadListPrec :: ReadPrec [DataPropertyAxiom]
readListPrec :: ReadPrec [DataPropertyAxiom]
Read, Int -> DataPropertyAxiom -> ShowS
[DataPropertyAxiom] -> ShowS
DataPropertyAxiom -> String
(Int -> DataPropertyAxiom -> ShowS)
-> (DataPropertyAxiom -> String)
-> ([DataPropertyAxiom] -> ShowS)
-> Show DataPropertyAxiom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPropertyAxiom -> ShowS
showsPrec :: Int -> DataPropertyAxiom -> ShowS
$cshow :: DataPropertyAxiom -> String
show :: DataPropertyAxiom -> String
$cshowList :: [DataPropertyAxiom] -> ShowS
showList :: [DataPropertyAxiom] -> ShowS
Show)

_DataPropertyAxiom :: Name
_DataPropertyAxiom = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataPropertyAxiom")

_DataPropertyAxiom_dataPropertyAxiom :: Name
_DataPropertyAxiom_dataPropertyAxiom = (String -> Name
Core.Name String
"dataPropertyAxiom")

_DataPropertyAxiom_dataPropertyRange :: Name
_DataPropertyAxiom_dataPropertyRange = (String -> Name
Core.Name String
"dataPropertyRange")

_DataPropertyAxiom_disjointDataProperties :: Name
_DataPropertyAxiom_disjointDataProperties = (String -> Name
Core.Name String
"disjointDataProperties")

_DataPropertyAxiom_equivalentDataProperties :: Name
_DataPropertyAxiom_equivalentDataProperties = (String -> Name
Core.Name String
"equivalentDataProperties")

_DataPropertyAxiom_functionalDataProperty :: Name
_DataPropertyAxiom_functionalDataProperty = (String -> Name
Core.Name String
"functionalDataProperty")

_DataPropertyAxiom_subDataPropertyOf :: Name
_DataPropertyAxiom_subDataPropertyOf = (String -> Name
Core.Name String
"subDataPropertyOf")

data SubDataPropertyOf = 
  SubDataPropertyOf {
    SubDataPropertyOf -> [Annotation]
subDataPropertyOfAnnotations :: [Annotation],
    SubDataPropertyOf -> DataPropertyExpression
subDataPropertyOfSubProperty :: DataPropertyExpression,
    SubDataPropertyOf -> DataPropertyExpression
subDataPropertyOfSuperProperty :: DataPropertyExpression}
  deriving (SubDataPropertyOf -> SubDataPropertyOf -> Bool
(SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> (SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> Eq SubDataPropertyOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
== :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
$c/= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
/= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
Eq, Eq SubDataPropertyOf
Eq SubDataPropertyOf =>
(SubDataPropertyOf -> SubDataPropertyOf -> Ordering)
-> (SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> (SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> (SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> (SubDataPropertyOf -> SubDataPropertyOf -> Bool)
-> (SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf)
-> (SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf)
-> Ord SubDataPropertyOf
SubDataPropertyOf -> SubDataPropertyOf -> Bool
SubDataPropertyOf -> SubDataPropertyOf -> Ordering
SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SubDataPropertyOf -> SubDataPropertyOf -> Ordering
compare :: SubDataPropertyOf -> SubDataPropertyOf -> Ordering
$c< :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
< :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
$c<= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
<= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
$c> :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
> :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
$c>= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
>= :: SubDataPropertyOf -> SubDataPropertyOf -> Bool
$cmax :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf
max :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf
$cmin :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf
min :: SubDataPropertyOf -> SubDataPropertyOf -> SubDataPropertyOf
Ord, ReadPrec [SubDataPropertyOf]
ReadPrec SubDataPropertyOf
Int -> ReadS SubDataPropertyOf
ReadS [SubDataPropertyOf]
(Int -> ReadS SubDataPropertyOf)
-> ReadS [SubDataPropertyOf]
-> ReadPrec SubDataPropertyOf
-> ReadPrec [SubDataPropertyOf]
-> Read SubDataPropertyOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SubDataPropertyOf
readsPrec :: Int -> ReadS SubDataPropertyOf
$creadList :: ReadS [SubDataPropertyOf]
readList :: ReadS [SubDataPropertyOf]
$creadPrec :: ReadPrec SubDataPropertyOf
readPrec :: ReadPrec SubDataPropertyOf
$creadListPrec :: ReadPrec [SubDataPropertyOf]
readListPrec :: ReadPrec [SubDataPropertyOf]
Read, Int -> SubDataPropertyOf -> ShowS
[SubDataPropertyOf] -> ShowS
SubDataPropertyOf -> String
(Int -> SubDataPropertyOf -> ShowS)
-> (SubDataPropertyOf -> String)
-> ([SubDataPropertyOf] -> ShowS)
-> Show SubDataPropertyOf
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubDataPropertyOf -> ShowS
showsPrec :: Int -> SubDataPropertyOf -> ShowS
$cshow :: SubDataPropertyOf -> String
show :: SubDataPropertyOf -> String
$cshowList :: [SubDataPropertyOf] -> ShowS
showList :: [SubDataPropertyOf] -> ShowS
Show)

_SubDataPropertyOf :: Name
_SubDataPropertyOf = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SubDataPropertyOf")

_SubDataPropertyOf_annotations :: Name
_SubDataPropertyOf_annotations = (String -> Name
Core.Name String
"annotations")

_SubDataPropertyOf_subProperty :: Name
_SubDataPropertyOf_subProperty = (String -> Name
Core.Name String
"subProperty")

_SubDataPropertyOf_superProperty :: Name
_SubDataPropertyOf_superProperty = (String -> Name
Core.Name String
"superProperty")

data EquivalentDataProperties = 
  EquivalentDataProperties {
    EquivalentDataProperties -> [Annotation]
equivalentDataPropertiesAnnotations :: [Annotation],
    EquivalentDataProperties -> [DataPropertyExpression]
equivalentDataPropertiesProperties :: [DataPropertyExpression]}
  deriving (EquivalentDataProperties -> EquivalentDataProperties -> Bool
(EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> (EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> Eq EquivalentDataProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
== :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
$c/= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
/= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
Eq, Eq EquivalentDataProperties
Eq EquivalentDataProperties =>
(EquivalentDataProperties -> EquivalentDataProperties -> Ordering)
-> (EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> (EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> (EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> (EquivalentDataProperties -> EquivalentDataProperties -> Bool)
-> (EquivalentDataProperties
    -> EquivalentDataProperties -> EquivalentDataProperties)
-> (EquivalentDataProperties
    -> EquivalentDataProperties -> EquivalentDataProperties)
-> Ord EquivalentDataProperties
EquivalentDataProperties -> EquivalentDataProperties -> Bool
EquivalentDataProperties -> EquivalentDataProperties -> Ordering
EquivalentDataProperties
-> EquivalentDataProperties -> EquivalentDataProperties
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EquivalentDataProperties -> EquivalentDataProperties -> Ordering
compare :: EquivalentDataProperties -> EquivalentDataProperties -> Ordering
$c< :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
< :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
$c<= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
<= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
$c> :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
> :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
$c>= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
>= :: EquivalentDataProperties -> EquivalentDataProperties -> Bool
$cmax :: EquivalentDataProperties
-> EquivalentDataProperties -> EquivalentDataProperties
max :: EquivalentDataProperties
-> EquivalentDataProperties -> EquivalentDataProperties
$cmin :: EquivalentDataProperties
-> EquivalentDataProperties -> EquivalentDataProperties
min :: EquivalentDataProperties
-> EquivalentDataProperties -> EquivalentDataProperties
Ord, ReadPrec [EquivalentDataProperties]
ReadPrec EquivalentDataProperties
Int -> ReadS EquivalentDataProperties
ReadS [EquivalentDataProperties]
(Int -> ReadS EquivalentDataProperties)
-> ReadS [EquivalentDataProperties]
-> ReadPrec EquivalentDataProperties
-> ReadPrec [EquivalentDataProperties]
-> Read EquivalentDataProperties
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EquivalentDataProperties
readsPrec :: Int -> ReadS EquivalentDataProperties
$creadList :: ReadS [EquivalentDataProperties]
readList :: ReadS [EquivalentDataProperties]
$creadPrec :: ReadPrec EquivalentDataProperties
readPrec :: ReadPrec EquivalentDataProperties
$creadListPrec :: ReadPrec [EquivalentDataProperties]
readListPrec :: ReadPrec [EquivalentDataProperties]
Read, Int -> EquivalentDataProperties -> ShowS
[EquivalentDataProperties] -> ShowS
EquivalentDataProperties -> String
(Int -> EquivalentDataProperties -> ShowS)
-> (EquivalentDataProperties -> String)
-> ([EquivalentDataProperties] -> ShowS)
-> Show EquivalentDataProperties
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EquivalentDataProperties -> ShowS
showsPrec :: Int -> EquivalentDataProperties -> ShowS
$cshow :: EquivalentDataProperties -> String
show :: EquivalentDataProperties -> String
$cshowList :: [EquivalentDataProperties] -> ShowS
showList :: [EquivalentDataProperties] -> ShowS
Show)

_EquivalentDataProperties :: Name
_EquivalentDataProperties = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.EquivalentDataProperties")

_EquivalentDataProperties_annotations :: Name
_EquivalentDataProperties_annotations = (String -> Name
Core.Name String
"annotations")

_EquivalentDataProperties_properties :: Name
_EquivalentDataProperties_properties = (String -> Name
Core.Name String
"properties")

data DisjointDataProperties = 
  DisjointDataProperties {
    DisjointDataProperties -> [Annotation]
disjointDataPropertiesAnnotations :: [Annotation],
    DisjointDataProperties -> [DataPropertyExpression]
disjointDataPropertiesProperties :: [DataPropertyExpression]}
  deriving (DisjointDataProperties -> DisjointDataProperties -> Bool
(DisjointDataProperties -> DisjointDataProperties -> Bool)
-> (DisjointDataProperties -> DisjointDataProperties -> Bool)
-> Eq DisjointDataProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisjointDataProperties -> DisjointDataProperties -> Bool
== :: DisjointDataProperties -> DisjointDataProperties -> Bool
$c/= :: DisjointDataProperties -> DisjointDataProperties -> Bool
/= :: DisjointDataProperties -> DisjointDataProperties -> Bool
Eq, Eq DisjointDataProperties
Eq DisjointDataProperties =>
(DisjointDataProperties -> DisjointDataProperties -> Ordering)
-> (DisjointDataProperties -> DisjointDataProperties -> Bool)
-> (DisjointDataProperties -> DisjointDataProperties -> Bool)
-> (DisjointDataProperties -> DisjointDataProperties -> Bool)
-> (DisjointDataProperties -> DisjointDataProperties -> Bool)
-> (DisjointDataProperties
    -> DisjointDataProperties -> DisjointDataProperties)
-> (DisjointDataProperties
    -> DisjointDataProperties -> DisjointDataProperties)
-> Ord DisjointDataProperties
DisjointDataProperties -> DisjointDataProperties -> Bool
DisjointDataProperties -> DisjointDataProperties -> Ordering
DisjointDataProperties
-> DisjointDataProperties -> DisjointDataProperties
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DisjointDataProperties -> DisjointDataProperties -> Ordering
compare :: DisjointDataProperties -> DisjointDataProperties -> Ordering
$c< :: DisjointDataProperties -> DisjointDataProperties -> Bool
< :: DisjointDataProperties -> DisjointDataProperties -> Bool
$c<= :: DisjointDataProperties -> DisjointDataProperties -> Bool
<= :: DisjointDataProperties -> DisjointDataProperties -> Bool
$c> :: DisjointDataProperties -> DisjointDataProperties -> Bool
> :: DisjointDataProperties -> DisjointDataProperties -> Bool
$c>= :: DisjointDataProperties -> DisjointDataProperties -> Bool
>= :: DisjointDataProperties -> DisjointDataProperties -> Bool
$cmax :: DisjointDataProperties
-> DisjointDataProperties -> DisjointDataProperties
max :: DisjointDataProperties
-> DisjointDataProperties -> DisjointDataProperties
$cmin :: DisjointDataProperties
-> DisjointDataProperties -> DisjointDataProperties
min :: DisjointDataProperties
-> DisjointDataProperties -> DisjointDataProperties
Ord, ReadPrec [DisjointDataProperties]
ReadPrec DisjointDataProperties
Int -> ReadS DisjointDataProperties
ReadS [DisjointDataProperties]
(Int -> ReadS DisjointDataProperties)
-> ReadS [DisjointDataProperties]
-> ReadPrec DisjointDataProperties
-> ReadPrec [DisjointDataProperties]
-> Read DisjointDataProperties
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DisjointDataProperties
readsPrec :: Int -> ReadS DisjointDataProperties
$creadList :: ReadS [DisjointDataProperties]
readList :: ReadS [DisjointDataProperties]
$creadPrec :: ReadPrec DisjointDataProperties
readPrec :: ReadPrec DisjointDataProperties
$creadListPrec :: ReadPrec [DisjointDataProperties]
readListPrec :: ReadPrec [DisjointDataProperties]
Read, Int -> DisjointDataProperties -> ShowS
[DisjointDataProperties] -> ShowS
DisjointDataProperties -> String
(Int -> DisjointDataProperties -> ShowS)
-> (DisjointDataProperties -> String)
-> ([DisjointDataProperties] -> ShowS)
-> Show DisjointDataProperties
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DisjointDataProperties -> ShowS
showsPrec :: Int -> DisjointDataProperties -> ShowS
$cshow :: DisjointDataProperties -> String
show :: DisjointDataProperties -> String
$cshowList :: [DisjointDataProperties] -> ShowS
showList :: [DisjointDataProperties] -> ShowS
Show)

_DisjointDataProperties :: Name
_DisjointDataProperties = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DisjointDataProperties")

_DisjointDataProperties_annotations :: Name
_DisjointDataProperties_annotations = (String -> Name
Core.Name String
"annotations")

_DisjointDataProperties_properties :: Name
_DisjointDataProperties_properties = (String -> Name
Core.Name String
"properties")

data DataPropertyDomain = 
  DataPropertyDomain {
    DataPropertyDomain -> [Annotation]
dataPropertyDomainAnnotations :: [Annotation],
    DataPropertyDomain -> DataPropertyExpression
dataPropertyDomainProperty :: DataPropertyExpression,
    DataPropertyDomain -> ClassExpression
dataPropertyDomainDomain :: ClassExpression}
  deriving (DataPropertyDomain -> DataPropertyDomain -> Bool
(DataPropertyDomain -> DataPropertyDomain -> Bool)
-> (DataPropertyDomain -> DataPropertyDomain -> Bool)
-> Eq DataPropertyDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPropertyDomain -> DataPropertyDomain -> Bool
== :: DataPropertyDomain -> DataPropertyDomain -> Bool
$c/= :: DataPropertyDomain -> DataPropertyDomain -> Bool
/= :: DataPropertyDomain -> DataPropertyDomain -> Bool
Eq, Eq DataPropertyDomain
Eq DataPropertyDomain =>
(DataPropertyDomain -> DataPropertyDomain -> Ordering)
-> (DataPropertyDomain -> DataPropertyDomain -> Bool)
-> (DataPropertyDomain -> DataPropertyDomain -> Bool)
-> (DataPropertyDomain -> DataPropertyDomain -> Bool)
-> (DataPropertyDomain -> DataPropertyDomain -> Bool)
-> (DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain)
-> (DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain)
-> Ord DataPropertyDomain
DataPropertyDomain -> DataPropertyDomain -> Bool
DataPropertyDomain -> DataPropertyDomain -> Ordering
DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPropertyDomain -> DataPropertyDomain -> Ordering
compare :: DataPropertyDomain -> DataPropertyDomain -> Ordering
$c< :: DataPropertyDomain -> DataPropertyDomain -> Bool
< :: DataPropertyDomain -> DataPropertyDomain -> Bool
$c<= :: DataPropertyDomain -> DataPropertyDomain -> Bool
<= :: DataPropertyDomain -> DataPropertyDomain -> Bool
$c> :: DataPropertyDomain -> DataPropertyDomain -> Bool
> :: DataPropertyDomain -> DataPropertyDomain -> Bool
$c>= :: DataPropertyDomain -> DataPropertyDomain -> Bool
>= :: DataPropertyDomain -> DataPropertyDomain -> Bool
$cmax :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain
max :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain
$cmin :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain
min :: DataPropertyDomain -> DataPropertyDomain -> DataPropertyDomain
Ord, ReadPrec [DataPropertyDomain]
ReadPrec DataPropertyDomain
Int -> ReadS DataPropertyDomain
ReadS [DataPropertyDomain]
(Int -> ReadS DataPropertyDomain)
-> ReadS [DataPropertyDomain]
-> ReadPrec DataPropertyDomain
-> ReadPrec [DataPropertyDomain]
-> Read DataPropertyDomain
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPropertyDomain
readsPrec :: Int -> ReadS DataPropertyDomain
$creadList :: ReadS [DataPropertyDomain]
readList :: ReadS [DataPropertyDomain]
$creadPrec :: ReadPrec DataPropertyDomain
readPrec :: ReadPrec DataPropertyDomain
$creadListPrec :: ReadPrec [DataPropertyDomain]
readListPrec :: ReadPrec [DataPropertyDomain]
Read, Int -> DataPropertyDomain -> ShowS
[DataPropertyDomain] -> ShowS
DataPropertyDomain -> String
(Int -> DataPropertyDomain -> ShowS)
-> (DataPropertyDomain -> String)
-> ([DataPropertyDomain] -> ShowS)
-> Show DataPropertyDomain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPropertyDomain -> ShowS
showsPrec :: Int -> DataPropertyDomain -> ShowS
$cshow :: DataPropertyDomain -> String
show :: DataPropertyDomain -> String
$cshowList :: [DataPropertyDomain] -> ShowS
showList :: [DataPropertyDomain] -> ShowS
Show)

_DataPropertyDomain :: Name
_DataPropertyDomain = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataPropertyDomain")

_DataPropertyDomain_annotations :: Name
_DataPropertyDomain_annotations = (String -> Name
Core.Name String
"annotations")

_DataPropertyDomain_property :: Name
_DataPropertyDomain_property = (String -> Name
Core.Name String
"property")

_DataPropertyDomain_domain :: Name
_DataPropertyDomain_domain = (String -> Name
Core.Name String
"domain")

data DataPropertyRange = 
  DataPropertyRange {
    DataPropertyRange -> [Annotation]
dataPropertyRangeAnnotations :: [Annotation],
    DataPropertyRange -> DataPropertyExpression
dataPropertyRangeProperty :: DataPropertyExpression,
    DataPropertyRange -> ClassExpression
dataPropertyRangeRange :: ClassExpression}
  deriving (DataPropertyRange -> DataPropertyRange -> Bool
(DataPropertyRange -> DataPropertyRange -> Bool)
-> (DataPropertyRange -> DataPropertyRange -> Bool)
-> Eq DataPropertyRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPropertyRange -> DataPropertyRange -> Bool
== :: DataPropertyRange -> DataPropertyRange -> Bool
$c/= :: DataPropertyRange -> DataPropertyRange -> Bool
/= :: DataPropertyRange -> DataPropertyRange -> Bool
Eq, Eq DataPropertyRange
Eq DataPropertyRange =>
(DataPropertyRange -> DataPropertyRange -> Ordering)
-> (DataPropertyRange -> DataPropertyRange -> Bool)
-> (DataPropertyRange -> DataPropertyRange -> Bool)
-> (DataPropertyRange -> DataPropertyRange -> Bool)
-> (DataPropertyRange -> DataPropertyRange -> Bool)
-> (DataPropertyRange -> DataPropertyRange -> DataPropertyRange)
-> (DataPropertyRange -> DataPropertyRange -> DataPropertyRange)
-> Ord DataPropertyRange
DataPropertyRange -> DataPropertyRange -> Bool
DataPropertyRange -> DataPropertyRange -> Ordering
DataPropertyRange -> DataPropertyRange -> DataPropertyRange
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPropertyRange -> DataPropertyRange -> Ordering
compare :: DataPropertyRange -> DataPropertyRange -> Ordering
$c< :: DataPropertyRange -> DataPropertyRange -> Bool
< :: DataPropertyRange -> DataPropertyRange -> Bool
$c<= :: DataPropertyRange -> DataPropertyRange -> Bool
<= :: DataPropertyRange -> DataPropertyRange -> Bool
$c> :: DataPropertyRange -> DataPropertyRange -> Bool
> :: DataPropertyRange -> DataPropertyRange -> Bool
$c>= :: DataPropertyRange -> DataPropertyRange -> Bool
>= :: DataPropertyRange -> DataPropertyRange -> Bool
$cmax :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange
max :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange
$cmin :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange
min :: DataPropertyRange -> DataPropertyRange -> DataPropertyRange
Ord, ReadPrec [DataPropertyRange]
ReadPrec DataPropertyRange
Int -> ReadS DataPropertyRange
ReadS [DataPropertyRange]
(Int -> ReadS DataPropertyRange)
-> ReadS [DataPropertyRange]
-> ReadPrec DataPropertyRange
-> ReadPrec [DataPropertyRange]
-> Read DataPropertyRange
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPropertyRange
readsPrec :: Int -> ReadS DataPropertyRange
$creadList :: ReadS [DataPropertyRange]
readList :: ReadS [DataPropertyRange]
$creadPrec :: ReadPrec DataPropertyRange
readPrec :: ReadPrec DataPropertyRange
$creadListPrec :: ReadPrec [DataPropertyRange]
readListPrec :: ReadPrec [DataPropertyRange]
Read, Int -> DataPropertyRange -> ShowS
[DataPropertyRange] -> ShowS
DataPropertyRange -> String
(Int -> DataPropertyRange -> ShowS)
-> (DataPropertyRange -> String)
-> ([DataPropertyRange] -> ShowS)
-> Show DataPropertyRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPropertyRange -> ShowS
showsPrec :: Int -> DataPropertyRange -> ShowS
$cshow :: DataPropertyRange -> String
show :: DataPropertyRange -> String
$cshowList :: [DataPropertyRange] -> ShowS
showList :: [DataPropertyRange] -> ShowS
Show)

_DataPropertyRange :: Name
_DataPropertyRange = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataPropertyRange")

_DataPropertyRange_annotations :: Name
_DataPropertyRange_annotations = (String -> Name
Core.Name String
"annotations")

_DataPropertyRange_property :: Name
_DataPropertyRange_property = (String -> Name
Core.Name String
"property")

_DataPropertyRange_range :: Name
_DataPropertyRange_range = (String -> Name
Core.Name String
"range")

data FunctionalDataProperty = 
  FunctionalDataProperty {
    FunctionalDataProperty -> [Annotation]
functionalDataPropertyAnnotations :: [Annotation],
    FunctionalDataProperty -> DataPropertyExpression
functionalDataPropertyProperty :: DataPropertyExpression}
  deriving (FunctionalDataProperty -> FunctionalDataProperty -> Bool
(FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> (FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> Eq FunctionalDataProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
== :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
$c/= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
/= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
Eq, Eq FunctionalDataProperty
Eq FunctionalDataProperty =>
(FunctionalDataProperty -> FunctionalDataProperty -> Ordering)
-> (FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> (FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> (FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> (FunctionalDataProperty -> FunctionalDataProperty -> Bool)
-> (FunctionalDataProperty
    -> FunctionalDataProperty -> FunctionalDataProperty)
-> (FunctionalDataProperty
    -> FunctionalDataProperty -> FunctionalDataProperty)
-> Ord FunctionalDataProperty
FunctionalDataProperty -> FunctionalDataProperty -> Bool
FunctionalDataProperty -> FunctionalDataProperty -> Ordering
FunctionalDataProperty
-> FunctionalDataProperty -> FunctionalDataProperty
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FunctionalDataProperty -> FunctionalDataProperty -> Ordering
compare :: FunctionalDataProperty -> FunctionalDataProperty -> Ordering
$c< :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
< :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
$c<= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
<= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
$c> :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
> :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
$c>= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
>= :: FunctionalDataProperty -> FunctionalDataProperty -> Bool
$cmax :: FunctionalDataProperty
-> FunctionalDataProperty -> FunctionalDataProperty
max :: FunctionalDataProperty
-> FunctionalDataProperty -> FunctionalDataProperty
$cmin :: FunctionalDataProperty
-> FunctionalDataProperty -> FunctionalDataProperty
min :: FunctionalDataProperty
-> FunctionalDataProperty -> FunctionalDataProperty
Ord, ReadPrec [FunctionalDataProperty]
ReadPrec FunctionalDataProperty
Int -> ReadS FunctionalDataProperty
ReadS [FunctionalDataProperty]
(Int -> ReadS FunctionalDataProperty)
-> ReadS [FunctionalDataProperty]
-> ReadPrec FunctionalDataProperty
-> ReadPrec [FunctionalDataProperty]
-> Read FunctionalDataProperty
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionalDataProperty
readsPrec :: Int -> ReadS FunctionalDataProperty
$creadList :: ReadS [FunctionalDataProperty]
readList :: ReadS [FunctionalDataProperty]
$creadPrec :: ReadPrec FunctionalDataProperty
readPrec :: ReadPrec FunctionalDataProperty
$creadListPrec :: ReadPrec [FunctionalDataProperty]
readListPrec :: ReadPrec [FunctionalDataProperty]
Read, Int -> FunctionalDataProperty -> ShowS
[FunctionalDataProperty] -> ShowS
FunctionalDataProperty -> String
(Int -> FunctionalDataProperty -> ShowS)
-> (FunctionalDataProperty -> String)
-> ([FunctionalDataProperty] -> ShowS)
-> Show FunctionalDataProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionalDataProperty -> ShowS
showsPrec :: Int -> FunctionalDataProperty -> ShowS
$cshow :: FunctionalDataProperty -> String
show :: FunctionalDataProperty -> String
$cshowList :: [FunctionalDataProperty] -> ShowS
showList :: [FunctionalDataProperty] -> ShowS
Show)

_FunctionalDataProperty :: Name
_FunctionalDataProperty = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.FunctionalDataProperty")

_FunctionalDataProperty_annotations :: Name
_FunctionalDataProperty_annotations = (String -> Name
Core.Name String
"annotations")

_FunctionalDataProperty_property :: Name
_FunctionalDataProperty_property = (String -> Name
Core.Name String
"property")

data DatatypeDefinition = 
  DatatypeDefinition {
    DatatypeDefinition -> [Annotation]
datatypeDefinitionAnnotations :: [Annotation],
    DatatypeDefinition -> Datatype
datatypeDefinitionDatatype :: Datatype,
    DatatypeDefinition -> DataRange
datatypeDefinitionRange :: DataRange}
  deriving (DatatypeDefinition -> DatatypeDefinition -> Bool
(DatatypeDefinition -> DatatypeDefinition -> Bool)
-> (DatatypeDefinition -> DatatypeDefinition -> Bool)
-> Eq DatatypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DatatypeDefinition -> DatatypeDefinition -> Bool
== :: DatatypeDefinition -> DatatypeDefinition -> Bool
$c/= :: DatatypeDefinition -> DatatypeDefinition -> Bool
/= :: DatatypeDefinition -> DatatypeDefinition -> Bool
Eq, Eq DatatypeDefinition
Eq DatatypeDefinition =>
(DatatypeDefinition -> DatatypeDefinition -> Ordering)
-> (DatatypeDefinition -> DatatypeDefinition -> Bool)
-> (DatatypeDefinition -> DatatypeDefinition -> Bool)
-> (DatatypeDefinition -> DatatypeDefinition -> Bool)
-> (DatatypeDefinition -> DatatypeDefinition -> Bool)
-> (DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition)
-> (DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition)
-> Ord DatatypeDefinition
DatatypeDefinition -> DatatypeDefinition -> Bool
DatatypeDefinition -> DatatypeDefinition -> Ordering
DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DatatypeDefinition -> DatatypeDefinition -> Ordering
compare :: DatatypeDefinition -> DatatypeDefinition -> Ordering
$c< :: DatatypeDefinition -> DatatypeDefinition -> Bool
< :: DatatypeDefinition -> DatatypeDefinition -> Bool
$c<= :: DatatypeDefinition -> DatatypeDefinition -> Bool
<= :: DatatypeDefinition -> DatatypeDefinition -> Bool
$c> :: DatatypeDefinition -> DatatypeDefinition -> Bool
> :: DatatypeDefinition -> DatatypeDefinition -> Bool
$c>= :: DatatypeDefinition -> DatatypeDefinition -> Bool
>= :: DatatypeDefinition -> DatatypeDefinition -> Bool
$cmax :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition
max :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition
$cmin :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition
min :: DatatypeDefinition -> DatatypeDefinition -> DatatypeDefinition
Ord, ReadPrec [DatatypeDefinition]
ReadPrec DatatypeDefinition
Int -> ReadS DatatypeDefinition
ReadS [DatatypeDefinition]
(Int -> ReadS DatatypeDefinition)
-> ReadS [DatatypeDefinition]
-> ReadPrec DatatypeDefinition
-> ReadPrec [DatatypeDefinition]
-> Read DatatypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DatatypeDefinition
readsPrec :: Int -> ReadS DatatypeDefinition
$creadList :: ReadS [DatatypeDefinition]
readList :: ReadS [DatatypeDefinition]
$creadPrec :: ReadPrec DatatypeDefinition
readPrec :: ReadPrec DatatypeDefinition
$creadListPrec :: ReadPrec [DatatypeDefinition]
readListPrec :: ReadPrec [DatatypeDefinition]
Read, Int -> DatatypeDefinition -> ShowS
[DatatypeDefinition] -> ShowS
DatatypeDefinition -> String
(Int -> DatatypeDefinition -> ShowS)
-> (DatatypeDefinition -> String)
-> ([DatatypeDefinition] -> ShowS)
-> Show DatatypeDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DatatypeDefinition -> ShowS
showsPrec :: Int -> DatatypeDefinition -> ShowS
$cshow :: DatatypeDefinition -> String
show :: DatatypeDefinition -> String
$cshowList :: [DatatypeDefinition] -> ShowS
showList :: [DatatypeDefinition] -> ShowS
Show)

_DatatypeDefinition :: Name
_DatatypeDefinition = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DatatypeDefinition")

_DatatypeDefinition_annotations :: Name
_DatatypeDefinition_annotations = (String -> Name
Core.Name String
"annotations")

_DatatypeDefinition_datatype :: Name
_DatatypeDefinition_datatype = (String -> Name
Core.Name String
"datatype")

_DatatypeDefinition_range :: Name
_DatatypeDefinition_range = (String -> Name
Core.Name String
"range")

-- | See https://www.w3.org/TR/owl2-syntax/#Keys
data HasKey = 
  HasKey {
    HasKey -> [Annotation]
hasKeyAnnotations :: [Annotation],
    HasKey -> ClassExpression
hasKeyClass :: ClassExpression,
    HasKey -> [ObjectPropertyExpression]
hasKeyObjectProperties :: [ObjectPropertyExpression],
    HasKey -> [DataPropertyExpression]
hasKeyDataProperties :: [DataPropertyExpression]}
  deriving (HasKey -> HasKey -> Bool
(HasKey -> HasKey -> Bool)
-> (HasKey -> HasKey -> Bool) -> Eq HasKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HasKey -> HasKey -> Bool
== :: HasKey -> HasKey -> Bool
$c/= :: HasKey -> HasKey -> Bool
/= :: HasKey -> HasKey -> Bool
Eq, Eq HasKey
Eq HasKey =>
(HasKey -> HasKey -> Ordering)
-> (HasKey -> HasKey -> Bool)
-> (HasKey -> HasKey -> Bool)
-> (HasKey -> HasKey -> Bool)
-> (HasKey -> HasKey -> Bool)
-> (HasKey -> HasKey -> HasKey)
-> (HasKey -> HasKey -> HasKey)
-> Ord HasKey
HasKey -> HasKey -> Bool
HasKey -> HasKey -> Ordering
HasKey -> HasKey -> HasKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: HasKey -> HasKey -> Ordering
compare :: HasKey -> HasKey -> Ordering
$c< :: HasKey -> HasKey -> Bool
< :: HasKey -> HasKey -> Bool
$c<= :: HasKey -> HasKey -> Bool
<= :: HasKey -> HasKey -> Bool
$c> :: HasKey -> HasKey -> Bool
> :: HasKey -> HasKey -> Bool
$c>= :: HasKey -> HasKey -> Bool
>= :: HasKey -> HasKey -> Bool
$cmax :: HasKey -> HasKey -> HasKey
max :: HasKey -> HasKey -> HasKey
$cmin :: HasKey -> HasKey -> HasKey
min :: HasKey -> HasKey -> HasKey
Ord, ReadPrec [HasKey]
ReadPrec HasKey
Int -> ReadS HasKey
ReadS [HasKey]
(Int -> ReadS HasKey)
-> ReadS [HasKey]
-> ReadPrec HasKey
-> ReadPrec [HasKey]
-> Read HasKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS HasKey
readsPrec :: Int -> ReadS HasKey
$creadList :: ReadS [HasKey]
readList :: ReadS [HasKey]
$creadPrec :: ReadPrec HasKey
readPrec :: ReadPrec HasKey
$creadListPrec :: ReadPrec [HasKey]
readListPrec :: ReadPrec [HasKey]
Read, Int -> HasKey -> ShowS
[HasKey] -> ShowS
HasKey -> String
(Int -> HasKey -> ShowS)
-> (HasKey -> String) -> ([HasKey] -> ShowS) -> Show HasKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HasKey -> ShowS
showsPrec :: Int -> HasKey -> ShowS
$cshow :: HasKey -> String
show :: HasKey -> String
$cshowList :: [HasKey] -> ShowS
showList :: [HasKey] -> ShowS
Show)

_HasKey :: Name
_HasKey = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.HasKey")

_HasKey_annotations :: Name
_HasKey_annotations = (String -> Name
Core.Name String
"annotations")

_HasKey_class :: Name
_HasKey_class = (String -> Name
Core.Name String
"class")

_HasKey_objectProperties :: Name
_HasKey_objectProperties = (String -> Name
Core.Name String
"objectProperties")

_HasKey_dataProperties :: Name
_HasKey_dataProperties = (String -> Name
Core.Name String
"dataProperties")

data Assertion = 
  AssertionClassAssertion ClassAssertion |
  AssertionDataPropertyAssertion DataPropertyAssertion |
  AssertionDifferentIndividuals DifferentIndividuals |
  AssertionObjectPropertyAssertion ObjectPropertyAssertion |
  AssertionNegativeDataPropertyAssertion NegativeDataPropertyAssertion |
  AssertionNegativeObjectPropertyAssertion NegativeObjectPropertyAssertion |
  AssertionSameIndividual SameIndividual
  deriving (Assertion -> Assertion -> Bool
(Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool) -> Eq Assertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Assertion -> Assertion -> Bool
== :: Assertion -> Assertion -> Bool
$c/= :: Assertion -> Assertion -> Bool
/= :: Assertion -> Assertion -> Bool
Eq, Eq Assertion
Eq Assertion =>
(Assertion -> Assertion -> Ordering)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Bool)
-> (Assertion -> Assertion -> Assertion)
-> (Assertion -> Assertion -> Assertion)
-> Ord Assertion
Assertion -> Assertion -> Bool
Assertion -> Assertion -> Ordering
Assertion -> Assertion -> Assertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Assertion -> Assertion -> Ordering
compare :: Assertion -> Assertion -> Ordering
$c< :: Assertion -> Assertion -> Bool
< :: Assertion -> Assertion -> Bool
$c<= :: Assertion -> Assertion -> Bool
<= :: Assertion -> Assertion -> Bool
$c> :: Assertion -> Assertion -> Bool
> :: Assertion -> Assertion -> Bool
$c>= :: Assertion -> Assertion -> Bool
>= :: Assertion -> Assertion -> Bool
$cmax :: Assertion -> Assertion -> Assertion
max :: Assertion -> Assertion -> Assertion
$cmin :: Assertion -> Assertion -> Assertion
min :: Assertion -> Assertion -> Assertion
Ord, ReadPrec [Assertion]
ReadPrec Assertion
Int -> ReadS Assertion
ReadS [Assertion]
(Int -> ReadS Assertion)
-> ReadS [Assertion]
-> ReadPrec Assertion
-> ReadPrec [Assertion]
-> Read Assertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Assertion
readsPrec :: Int -> ReadS Assertion
$creadList :: ReadS [Assertion]
readList :: ReadS [Assertion]
$creadPrec :: ReadPrec Assertion
readPrec :: ReadPrec Assertion
$creadListPrec :: ReadPrec [Assertion]
readListPrec :: ReadPrec [Assertion]
Read, Int -> Assertion -> ShowS
[Assertion] -> ShowS
Assertion -> String
(Int -> Assertion -> ShowS)
-> (Assertion -> String)
-> ([Assertion] -> ShowS)
-> Show Assertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Assertion -> ShowS
showsPrec :: Int -> Assertion -> ShowS
$cshow :: Assertion -> String
show :: Assertion -> String
$cshowList :: [Assertion] -> ShowS
showList :: [Assertion] -> ShowS
Show)

_Assertion :: Name
_Assertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.Assertion")

_Assertion_classAssertion :: Name
_Assertion_classAssertion = (String -> Name
Core.Name String
"classAssertion")

_Assertion_dataPropertyAssertion :: Name
_Assertion_dataPropertyAssertion = (String -> Name
Core.Name String
"dataPropertyAssertion")

_Assertion_differentIndividuals :: Name
_Assertion_differentIndividuals = (String -> Name
Core.Name String
"differentIndividuals")

_Assertion_objectPropertyAssertion :: Name
_Assertion_objectPropertyAssertion = (String -> Name
Core.Name String
"objectPropertyAssertion")

_Assertion_negativeDataPropertyAssertion :: Name
_Assertion_negativeDataPropertyAssertion = (String -> Name
Core.Name String
"negativeDataPropertyAssertion")

_Assertion_negativeObjectPropertyAssertion :: Name
_Assertion_negativeObjectPropertyAssertion = (String -> Name
Core.Name String
"negativeObjectPropertyAssertion")

_Assertion_sameIndividual :: Name
_Assertion_sameIndividual = (String -> Name
Core.Name String
"sameIndividual")

data SameIndividual = 
  SameIndividual {
    SameIndividual -> [Annotation]
sameIndividualAnnotations :: [Annotation],
    SameIndividual -> [Individual]
sameIndividualIndividuals :: [Individual]}
  deriving (SameIndividual -> SameIndividual -> Bool
(SameIndividual -> SameIndividual -> Bool)
-> (SameIndividual -> SameIndividual -> Bool) -> Eq SameIndividual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SameIndividual -> SameIndividual -> Bool
== :: SameIndividual -> SameIndividual -> Bool
$c/= :: SameIndividual -> SameIndividual -> Bool
/= :: SameIndividual -> SameIndividual -> Bool
Eq, Eq SameIndividual
Eq SameIndividual =>
(SameIndividual -> SameIndividual -> Ordering)
-> (SameIndividual -> SameIndividual -> Bool)
-> (SameIndividual -> SameIndividual -> Bool)
-> (SameIndividual -> SameIndividual -> Bool)
-> (SameIndividual -> SameIndividual -> Bool)
-> (SameIndividual -> SameIndividual -> SameIndividual)
-> (SameIndividual -> SameIndividual -> SameIndividual)
-> Ord SameIndividual
SameIndividual -> SameIndividual -> Bool
SameIndividual -> SameIndividual -> Ordering
SameIndividual -> SameIndividual -> SameIndividual
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SameIndividual -> SameIndividual -> Ordering
compare :: SameIndividual -> SameIndividual -> Ordering
$c< :: SameIndividual -> SameIndividual -> Bool
< :: SameIndividual -> SameIndividual -> Bool
$c<= :: SameIndividual -> SameIndividual -> Bool
<= :: SameIndividual -> SameIndividual -> Bool
$c> :: SameIndividual -> SameIndividual -> Bool
> :: SameIndividual -> SameIndividual -> Bool
$c>= :: SameIndividual -> SameIndividual -> Bool
>= :: SameIndividual -> SameIndividual -> Bool
$cmax :: SameIndividual -> SameIndividual -> SameIndividual
max :: SameIndividual -> SameIndividual -> SameIndividual
$cmin :: SameIndividual -> SameIndividual -> SameIndividual
min :: SameIndividual -> SameIndividual -> SameIndividual
Ord, ReadPrec [SameIndividual]
ReadPrec SameIndividual
Int -> ReadS SameIndividual
ReadS [SameIndividual]
(Int -> ReadS SameIndividual)
-> ReadS [SameIndividual]
-> ReadPrec SameIndividual
-> ReadPrec [SameIndividual]
-> Read SameIndividual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SameIndividual
readsPrec :: Int -> ReadS SameIndividual
$creadList :: ReadS [SameIndividual]
readList :: ReadS [SameIndividual]
$creadPrec :: ReadPrec SameIndividual
readPrec :: ReadPrec SameIndividual
$creadListPrec :: ReadPrec [SameIndividual]
readListPrec :: ReadPrec [SameIndividual]
Read, Int -> SameIndividual -> ShowS
[SameIndividual] -> ShowS
SameIndividual -> String
(Int -> SameIndividual -> ShowS)
-> (SameIndividual -> String)
-> ([SameIndividual] -> ShowS)
-> Show SameIndividual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SameIndividual -> ShowS
showsPrec :: Int -> SameIndividual -> ShowS
$cshow :: SameIndividual -> String
show :: SameIndividual -> String
$cshowList :: [SameIndividual] -> ShowS
showList :: [SameIndividual] -> ShowS
Show)

_SameIndividual :: Name
_SameIndividual = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.SameIndividual")

_SameIndividual_annotations :: Name
_SameIndividual_annotations = (String -> Name
Core.Name String
"annotations")

_SameIndividual_individuals :: Name
_SameIndividual_individuals = (String -> Name
Core.Name String
"individuals")

data DifferentIndividuals = 
  DifferentIndividuals {
    DifferentIndividuals -> [Annotation]
differentIndividualsAnnotations :: [Annotation],
    DifferentIndividuals -> [Individual]
differentIndividualsIndividuals :: [Individual]}
  deriving (DifferentIndividuals -> DifferentIndividuals -> Bool
(DifferentIndividuals -> DifferentIndividuals -> Bool)
-> (DifferentIndividuals -> DifferentIndividuals -> Bool)
-> Eq DifferentIndividuals
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DifferentIndividuals -> DifferentIndividuals -> Bool
== :: DifferentIndividuals -> DifferentIndividuals -> Bool
$c/= :: DifferentIndividuals -> DifferentIndividuals -> Bool
/= :: DifferentIndividuals -> DifferentIndividuals -> Bool
Eq, Eq DifferentIndividuals
Eq DifferentIndividuals =>
(DifferentIndividuals -> DifferentIndividuals -> Ordering)
-> (DifferentIndividuals -> DifferentIndividuals -> Bool)
-> (DifferentIndividuals -> DifferentIndividuals -> Bool)
-> (DifferentIndividuals -> DifferentIndividuals -> Bool)
-> (DifferentIndividuals -> DifferentIndividuals -> Bool)
-> (DifferentIndividuals
    -> DifferentIndividuals -> DifferentIndividuals)
-> (DifferentIndividuals
    -> DifferentIndividuals -> DifferentIndividuals)
-> Ord DifferentIndividuals
DifferentIndividuals -> DifferentIndividuals -> Bool
DifferentIndividuals -> DifferentIndividuals -> Ordering
DifferentIndividuals
-> DifferentIndividuals -> DifferentIndividuals
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DifferentIndividuals -> DifferentIndividuals -> Ordering
compare :: DifferentIndividuals -> DifferentIndividuals -> Ordering
$c< :: DifferentIndividuals -> DifferentIndividuals -> Bool
< :: DifferentIndividuals -> DifferentIndividuals -> Bool
$c<= :: DifferentIndividuals -> DifferentIndividuals -> Bool
<= :: DifferentIndividuals -> DifferentIndividuals -> Bool
$c> :: DifferentIndividuals -> DifferentIndividuals -> Bool
> :: DifferentIndividuals -> DifferentIndividuals -> Bool
$c>= :: DifferentIndividuals -> DifferentIndividuals -> Bool
>= :: DifferentIndividuals -> DifferentIndividuals -> Bool
$cmax :: DifferentIndividuals
-> DifferentIndividuals -> DifferentIndividuals
max :: DifferentIndividuals
-> DifferentIndividuals -> DifferentIndividuals
$cmin :: DifferentIndividuals
-> DifferentIndividuals -> DifferentIndividuals
min :: DifferentIndividuals
-> DifferentIndividuals -> DifferentIndividuals
Ord, ReadPrec [DifferentIndividuals]
ReadPrec DifferentIndividuals
Int -> ReadS DifferentIndividuals
ReadS [DifferentIndividuals]
(Int -> ReadS DifferentIndividuals)
-> ReadS [DifferentIndividuals]
-> ReadPrec DifferentIndividuals
-> ReadPrec [DifferentIndividuals]
-> Read DifferentIndividuals
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DifferentIndividuals
readsPrec :: Int -> ReadS DifferentIndividuals
$creadList :: ReadS [DifferentIndividuals]
readList :: ReadS [DifferentIndividuals]
$creadPrec :: ReadPrec DifferentIndividuals
readPrec :: ReadPrec DifferentIndividuals
$creadListPrec :: ReadPrec [DifferentIndividuals]
readListPrec :: ReadPrec [DifferentIndividuals]
Read, Int -> DifferentIndividuals -> ShowS
[DifferentIndividuals] -> ShowS
DifferentIndividuals -> String
(Int -> DifferentIndividuals -> ShowS)
-> (DifferentIndividuals -> String)
-> ([DifferentIndividuals] -> ShowS)
-> Show DifferentIndividuals
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DifferentIndividuals -> ShowS
showsPrec :: Int -> DifferentIndividuals -> ShowS
$cshow :: DifferentIndividuals -> String
show :: DifferentIndividuals -> String
$cshowList :: [DifferentIndividuals] -> ShowS
showList :: [DifferentIndividuals] -> ShowS
Show)

_DifferentIndividuals :: Name
_DifferentIndividuals = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DifferentIndividuals")

_DifferentIndividuals_annotations :: Name
_DifferentIndividuals_annotations = (String -> Name
Core.Name String
"annotations")

_DifferentIndividuals_individuals :: Name
_DifferentIndividuals_individuals = (String -> Name
Core.Name String
"individuals")

data ClassAssertion = 
  ClassAssertion {
    ClassAssertion -> [Annotation]
classAssertionAnnotations :: [Annotation],
    ClassAssertion -> ClassExpression
classAssertionClass :: ClassExpression,
    ClassAssertion -> Individual
classAssertionIndividual :: Individual}
  deriving (ClassAssertion -> ClassAssertion -> Bool
(ClassAssertion -> ClassAssertion -> Bool)
-> (ClassAssertion -> ClassAssertion -> Bool) -> Eq ClassAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClassAssertion -> ClassAssertion -> Bool
== :: ClassAssertion -> ClassAssertion -> Bool
$c/= :: ClassAssertion -> ClassAssertion -> Bool
/= :: ClassAssertion -> ClassAssertion -> Bool
Eq, Eq ClassAssertion
Eq ClassAssertion =>
(ClassAssertion -> ClassAssertion -> Ordering)
-> (ClassAssertion -> ClassAssertion -> Bool)
-> (ClassAssertion -> ClassAssertion -> Bool)
-> (ClassAssertion -> ClassAssertion -> Bool)
-> (ClassAssertion -> ClassAssertion -> Bool)
-> (ClassAssertion -> ClassAssertion -> ClassAssertion)
-> (ClassAssertion -> ClassAssertion -> ClassAssertion)
-> Ord ClassAssertion
ClassAssertion -> ClassAssertion -> Bool
ClassAssertion -> ClassAssertion -> Ordering
ClassAssertion -> ClassAssertion -> ClassAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ClassAssertion -> ClassAssertion -> Ordering
compare :: ClassAssertion -> ClassAssertion -> Ordering
$c< :: ClassAssertion -> ClassAssertion -> Bool
< :: ClassAssertion -> ClassAssertion -> Bool
$c<= :: ClassAssertion -> ClassAssertion -> Bool
<= :: ClassAssertion -> ClassAssertion -> Bool
$c> :: ClassAssertion -> ClassAssertion -> Bool
> :: ClassAssertion -> ClassAssertion -> Bool
$c>= :: ClassAssertion -> ClassAssertion -> Bool
>= :: ClassAssertion -> ClassAssertion -> Bool
$cmax :: ClassAssertion -> ClassAssertion -> ClassAssertion
max :: ClassAssertion -> ClassAssertion -> ClassAssertion
$cmin :: ClassAssertion -> ClassAssertion -> ClassAssertion
min :: ClassAssertion -> ClassAssertion -> ClassAssertion
Ord, ReadPrec [ClassAssertion]
ReadPrec ClassAssertion
Int -> ReadS ClassAssertion
ReadS [ClassAssertion]
(Int -> ReadS ClassAssertion)
-> ReadS [ClassAssertion]
-> ReadPrec ClassAssertion
-> ReadPrec [ClassAssertion]
-> Read ClassAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ClassAssertion
readsPrec :: Int -> ReadS ClassAssertion
$creadList :: ReadS [ClassAssertion]
readList :: ReadS [ClassAssertion]
$creadPrec :: ReadPrec ClassAssertion
readPrec :: ReadPrec ClassAssertion
$creadListPrec :: ReadPrec [ClassAssertion]
readListPrec :: ReadPrec [ClassAssertion]
Read, Int -> ClassAssertion -> ShowS
[ClassAssertion] -> ShowS
ClassAssertion -> String
(Int -> ClassAssertion -> ShowS)
-> (ClassAssertion -> String)
-> ([ClassAssertion] -> ShowS)
-> Show ClassAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClassAssertion -> ShowS
showsPrec :: Int -> ClassAssertion -> ShowS
$cshow :: ClassAssertion -> String
show :: ClassAssertion -> String
$cshowList :: [ClassAssertion] -> ShowS
showList :: [ClassAssertion] -> ShowS
Show)

_ClassAssertion :: Name
_ClassAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ClassAssertion")

_ClassAssertion_annotations :: Name
_ClassAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_ClassAssertion_class :: Name
_ClassAssertion_class = (String -> Name
Core.Name String
"class")

_ClassAssertion_individual :: Name
_ClassAssertion_individual = (String -> Name
Core.Name String
"individual")

data ObjectPropertyAssertion = 
  ObjectPropertyAssertion {
    ObjectPropertyAssertion -> [Annotation]
objectPropertyAssertionAnnotations :: [Annotation],
    ObjectPropertyAssertion -> ObjectPropertyExpression
objectPropertyAssertionProperty :: ObjectPropertyExpression,
    ObjectPropertyAssertion -> Individual
objectPropertyAssertionSource :: Individual,
    ObjectPropertyAssertion -> Individual
objectPropertyAssertionTarget :: Individual}
  deriving (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
(ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> Eq ObjectPropertyAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
== :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
$c/= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
/= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
Eq, Eq ObjectPropertyAssertion
Eq ObjectPropertyAssertion =>
(ObjectPropertyAssertion -> ObjectPropertyAssertion -> Ordering)
-> (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> (ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool)
-> (ObjectPropertyAssertion
    -> ObjectPropertyAssertion -> ObjectPropertyAssertion)
-> (ObjectPropertyAssertion
    -> ObjectPropertyAssertion -> ObjectPropertyAssertion)
-> Ord ObjectPropertyAssertion
ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
ObjectPropertyAssertion -> ObjectPropertyAssertion -> Ordering
ObjectPropertyAssertion
-> ObjectPropertyAssertion -> ObjectPropertyAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Ordering
compare :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Ordering
$c< :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
< :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
$c<= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
<= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
$c> :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
> :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
$c>= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
>= :: ObjectPropertyAssertion -> ObjectPropertyAssertion -> Bool
$cmax :: ObjectPropertyAssertion
-> ObjectPropertyAssertion -> ObjectPropertyAssertion
max :: ObjectPropertyAssertion
-> ObjectPropertyAssertion -> ObjectPropertyAssertion
$cmin :: ObjectPropertyAssertion
-> ObjectPropertyAssertion -> ObjectPropertyAssertion
min :: ObjectPropertyAssertion
-> ObjectPropertyAssertion -> ObjectPropertyAssertion
Ord, ReadPrec [ObjectPropertyAssertion]
ReadPrec ObjectPropertyAssertion
Int -> ReadS ObjectPropertyAssertion
ReadS [ObjectPropertyAssertion]
(Int -> ReadS ObjectPropertyAssertion)
-> ReadS [ObjectPropertyAssertion]
-> ReadPrec ObjectPropertyAssertion
-> ReadPrec [ObjectPropertyAssertion]
-> Read ObjectPropertyAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectPropertyAssertion
readsPrec :: Int -> ReadS ObjectPropertyAssertion
$creadList :: ReadS [ObjectPropertyAssertion]
readList :: ReadS [ObjectPropertyAssertion]
$creadPrec :: ReadPrec ObjectPropertyAssertion
readPrec :: ReadPrec ObjectPropertyAssertion
$creadListPrec :: ReadPrec [ObjectPropertyAssertion]
readListPrec :: ReadPrec [ObjectPropertyAssertion]
Read, Int -> ObjectPropertyAssertion -> ShowS
[ObjectPropertyAssertion] -> ShowS
ObjectPropertyAssertion -> String
(Int -> ObjectPropertyAssertion -> ShowS)
-> (ObjectPropertyAssertion -> String)
-> ([ObjectPropertyAssertion] -> ShowS)
-> Show ObjectPropertyAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectPropertyAssertion -> ShowS
showsPrec :: Int -> ObjectPropertyAssertion -> ShowS
$cshow :: ObjectPropertyAssertion -> String
show :: ObjectPropertyAssertion -> String
$cshowList :: [ObjectPropertyAssertion] -> ShowS
showList :: [ObjectPropertyAssertion] -> ShowS
Show)

_ObjectPropertyAssertion :: Name
_ObjectPropertyAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.ObjectPropertyAssertion")

_ObjectPropertyAssertion_annotations :: Name
_ObjectPropertyAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_ObjectPropertyAssertion_property :: Name
_ObjectPropertyAssertion_property = (String -> Name
Core.Name String
"property")

_ObjectPropertyAssertion_source :: Name
_ObjectPropertyAssertion_source = (String -> Name
Core.Name String
"source")

_ObjectPropertyAssertion_target :: Name
_ObjectPropertyAssertion_target = (String -> Name
Core.Name String
"target")

data NegativeObjectPropertyAssertion = 
  NegativeObjectPropertyAssertion {
    NegativeObjectPropertyAssertion -> [Annotation]
negativeObjectPropertyAssertionAnnotations :: [Annotation],
    NegativeObjectPropertyAssertion -> ObjectPropertyExpression
negativeObjectPropertyAssertionProperty :: ObjectPropertyExpression,
    NegativeObjectPropertyAssertion -> Individual
negativeObjectPropertyAssertionSource :: Individual,
    NegativeObjectPropertyAssertion -> Individual
negativeObjectPropertyAssertionTarget :: Individual}
  deriving (NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
(NegativeObjectPropertyAssertion
 -> NegativeObjectPropertyAssertion -> Bool)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion -> Bool)
-> Eq NegativeObjectPropertyAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
== :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
$c/= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
/= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
Eq, Eq NegativeObjectPropertyAssertion
Eq NegativeObjectPropertyAssertion =>
(NegativeObjectPropertyAssertion
 -> NegativeObjectPropertyAssertion -> Ordering)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion -> Bool)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion -> Bool)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion -> Bool)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion -> Bool)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion)
-> (NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion
    -> NegativeObjectPropertyAssertion)
-> Ord NegativeObjectPropertyAssertion
NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Ordering
NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Ordering
compare :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Ordering
$c< :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
< :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
$c<= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
<= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
$c> :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
> :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
$c>= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
>= :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion -> Bool
$cmax :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
max :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
$cmin :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
min :: NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
-> NegativeObjectPropertyAssertion
Ord, ReadPrec [NegativeObjectPropertyAssertion]
ReadPrec NegativeObjectPropertyAssertion
Int -> ReadS NegativeObjectPropertyAssertion
ReadS [NegativeObjectPropertyAssertion]
(Int -> ReadS NegativeObjectPropertyAssertion)
-> ReadS [NegativeObjectPropertyAssertion]
-> ReadPrec NegativeObjectPropertyAssertion
-> ReadPrec [NegativeObjectPropertyAssertion]
-> Read NegativeObjectPropertyAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NegativeObjectPropertyAssertion
readsPrec :: Int -> ReadS NegativeObjectPropertyAssertion
$creadList :: ReadS [NegativeObjectPropertyAssertion]
readList :: ReadS [NegativeObjectPropertyAssertion]
$creadPrec :: ReadPrec NegativeObjectPropertyAssertion
readPrec :: ReadPrec NegativeObjectPropertyAssertion
$creadListPrec :: ReadPrec [NegativeObjectPropertyAssertion]
readListPrec :: ReadPrec [NegativeObjectPropertyAssertion]
Read, Int -> NegativeObjectPropertyAssertion -> ShowS
[NegativeObjectPropertyAssertion] -> ShowS
NegativeObjectPropertyAssertion -> String
(Int -> NegativeObjectPropertyAssertion -> ShowS)
-> (NegativeObjectPropertyAssertion -> String)
-> ([NegativeObjectPropertyAssertion] -> ShowS)
-> Show NegativeObjectPropertyAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NegativeObjectPropertyAssertion -> ShowS
showsPrec :: Int -> NegativeObjectPropertyAssertion -> ShowS
$cshow :: NegativeObjectPropertyAssertion -> String
show :: NegativeObjectPropertyAssertion -> String
$cshowList :: [NegativeObjectPropertyAssertion] -> ShowS
showList :: [NegativeObjectPropertyAssertion] -> ShowS
Show)

_NegativeObjectPropertyAssertion :: Name
_NegativeObjectPropertyAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.NegativeObjectPropertyAssertion")

_NegativeObjectPropertyAssertion_annotations :: Name
_NegativeObjectPropertyAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_NegativeObjectPropertyAssertion_property :: Name
_NegativeObjectPropertyAssertion_property = (String -> Name
Core.Name String
"property")

_NegativeObjectPropertyAssertion_source :: Name
_NegativeObjectPropertyAssertion_source = (String -> Name
Core.Name String
"source")

_NegativeObjectPropertyAssertion_target :: Name
_NegativeObjectPropertyAssertion_target = (String -> Name
Core.Name String
"target")

data DataPropertyAssertion = 
  DataPropertyAssertion {
    DataPropertyAssertion -> [Annotation]
dataPropertyAssertionAnnotations :: [Annotation],
    DataPropertyAssertion -> DataPropertyExpression
dataPropertyAssertionProperty :: DataPropertyExpression,
    DataPropertyAssertion -> Individual
dataPropertyAssertionSource :: Individual,
    DataPropertyAssertion -> Individual
dataPropertyAssertionTarget :: Individual}
  deriving (DataPropertyAssertion -> DataPropertyAssertion -> Bool
(DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> (DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> Eq DataPropertyAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
== :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
$c/= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
/= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
Eq, Eq DataPropertyAssertion
Eq DataPropertyAssertion =>
(DataPropertyAssertion -> DataPropertyAssertion -> Ordering)
-> (DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> (DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> (DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> (DataPropertyAssertion -> DataPropertyAssertion -> Bool)
-> (DataPropertyAssertion
    -> DataPropertyAssertion -> DataPropertyAssertion)
-> (DataPropertyAssertion
    -> DataPropertyAssertion -> DataPropertyAssertion)
-> Ord DataPropertyAssertion
DataPropertyAssertion -> DataPropertyAssertion -> Bool
DataPropertyAssertion -> DataPropertyAssertion -> Ordering
DataPropertyAssertion
-> DataPropertyAssertion -> DataPropertyAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DataPropertyAssertion -> DataPropertyAssertion -> Ordering
compare :: DataPropertyAssertion -> DataPropertyAssertion -> Ordering
$c< :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
< :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
$c<= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
<= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
$c> :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
> :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
$c>= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
>= :: DataPropertyAssertion -> DataPropertyAssertion -> Bool
$cmax :: DataPropertyAssertion
-> DataPropertyAssertion -> DataPropertyAssertion
max :: DataPropertyAssertion
-> DataPropertyAssertion -> DataPropertyAssertion
$cmin :: DataPropertyAssertion
-> DataPropertyAssertion -> DataPropertyAssertion
min :: DataPropertyAssertion
-> DataPropertyAssertion -> DataPropertyAssertion
Ord, ReadPrec [DataPropertyAssertion]
ReadPrec DataPropertyAssertion
Int -> ReadS DataPropertyAssertion
ReadS [DataPropertyAssertion]
(Int -> ReadS DataPropertyAssertion)
-> ReadS [DataPropertyAssertion]
-> ReadPrec DataPropertyAssertion
-> ReadPrec [DataPropertyAssertion]
-> Read DataPropertyAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DataPropertyAssertion
readsPrec :: Int -> ReadS DataPropertyAssertion
$creadList :: ReadS [DataPropertyAssertion]
readList :: ReadS [DataPropertyAssertion]
$creadPrec :: ReadPrec DataPropertyAssertion
readPrec :: ReadPrec DataPropertyAssertion
$creadListPrec :: ReadPrec [DataPropertyAssertion]
readListPrec :: ReadPrec [DataPropertyAssertion]
Read, Int -> DataPropertyAssertion -> ShowS
[DataPropertyAssertion] -> ShowS
DataPropertyAssertion -> String
(Int -> DataPropertyAssertion -> ShowS)
-> (DataPropertyAssertion -> String)
-> ([DataPropertyAssertion] -> ShowS)
-> Show DataPropertyAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DataPropertyAssertion -> ShowS
showsPrec :: Int -> DataPropertyAssertion -> ShowS
$cshow :: DataPropertyAssertion -> String
show :: DataPropertyAssertion -> String
$cshowList :: [DataPropertyAssertion] -> ShowS
showList :: [DataPropertyAssertion] -> ShowS
Show)

_DataPropertyAssertion :: Name
_DataPropertyAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.DataPropertyAssertion")

_DataPropertyAssertion_annotations :: Name
_DataPropertyAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_DataPropertyAssertion_property :: Name
_DataPropertyAssertion_property = (String -> Name
Core.Name String
"property")

_DataPropertyAssertion_source :: Name
_DataPropertyAssertion_source = (String -> Name
Core.Name String
"source")

_DataPropertyAssertion_target :: Name
_DataPropertyAssertion_target = (String -> Name
Core.Name String
"target")

data NegativeDataPropertyAssertion = 
  NegativeDataPropertyAssertion {
    NegativeDataPropertyAssertion -> [Annotation]
negativeDataPropertyAssertionAnnotations :: [Annotation],
    NegativeDataPropertyAssertion -> DataPropertyExpression
negativeDataPropertyAssertionProperty :: DataPropertyExpression,
    NegativeDataPropertyAssertion -> Individual
negativeDataPropertyAssertionSource :: Individual,
    NegativeDataPropertyAssertion -> Individual
negativeDataPropertyAssertionTarget :: Individual}
  deriving (NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
(NegativeDataPropertyAssertion
 -> NegativeDataPropertyAssertion -> Bool)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> Bool)
-> Eq NegativeDataPropertyAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
== :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
$c/= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
/= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
Eq, Eq NegativeDataPropertyAssertion
Eq NegativeDataPropertyAssertion =>
(NegativeDataPropertyAssertion
 -> NegativeDataPropertyAssertion -> Ordering)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> Bool)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> Bool)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> Bool)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> Bool)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion)
-> (NegativeDataPropertyAssertion
    -> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion)
-> Ord NegativeDataPropertyAssertion
NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Ordering
NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Ordering
compare :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Ordering
$c< :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
< :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
$c<= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
<= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
$c> :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
> :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
$c>= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
>= :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> Bool
$cmax :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion
max :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion
$cmin :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion
min :: NegativeDataPropertyAssertion
-> NegativeDataPropertyAssertion -> NegativeDataPropertyAssertion
Ord, ReadPrec [NegativeDataPropertyAssertion]
ReadPrec NegativeDataPropertyAssertion
Int -> ReadS NegativeDataPropertyAssertion
ReadS [NegativeDataPropertyAssertion]
(Int -> ReadS NegativeDataPropertyAssertion)
-> ReadS [NegativeDataPropertyAssertion]
-> ReadPrec NegativeDataPropertyAssertion
-> ReadPrec [NegativeDataPropertyAssertion]
-> Read NegativeDataPropertyAssertion
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NegativeDataPropertyAssertion
readsPrec :: Int -> ReadS NegativeDataPropertyAssertion
$creadList :: ReadS [NegativeDataPropertyAssertion]
readList :: ReadS [NegativeDataPropertyAssertion]
$creadPrec :: ReadPrec NegativeDataPropertyAssertion
readPrec :: ReadPrec NegativeDataPropertyAssertion
$creadListPrec :: ReadPrec [NegativeDataPropertyAssertion]
readListPrec :: ReadPrec [NegativeDataPropertyAssertion]
Read, Int -> NegativeDataPropertyAssertion -> ShowS
[NegativeDataPropertyAssertion] -> ShowS
NegativeDataPropertyAssertion -> String
(Int -> NegativeDataPropertyAssertion -> ShowS)
-> (NegativeDataPropertyAssertion -> String)
-> ([NegativeDataPropertyAssertion] -> ShowS)
-> Show NegativeDataPropertyAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NegativeDataPropertyAssertion -> ShowS
showsPrec :: Int -> NegativeDataPropertyAssertion -> ShowS
$cshow :: NegativeDataPropertyAssertion -> String
show :: NegativeDataPropertyAssertion -> String
$cshowList :: [NegativeDataPropertyAssertion] -> ShowS
showList :: [NegativeDataPropertyAssertion] -> ShowS
Show)

_NegativeDataPropertyAssertion :: Name
_NegativeDataPropertyAssertion = (String -> Name
Core.Name String
"hydra/langs/owl/syntax.NegativeDataPropertyAssertion")

_NegativeDataPropertyAssertion_annotations :: Name
_NegativeDataPropertyAssertion_annotations = (String -> Name
Core.Name String
"annotations")

_NegativeDataPropertyAssertion_property :: Name
_NegativeDataPropertyAssertion_property = (String -> Name
Core.Name String
"property")

_NegativeDataPropertyAssertion_source :: Name
_NegativeDataPropertyAssertion_source = (String -> Name
Core.Name String
"source")

_NegativeDataPropertyAssertion_target :: Name
_NegativeDataPropertyAssertion_target = (String -> Name
Core.Name String
"target")