module Hydra.Impl.Haskell.Sources.Ext.Owl.Syntax where

import Hydra.Impl.Haskell.Sources.Core

import Hydra.Kernel
import Hydra.Impl.Haskell.Dsl.Types as Types
import qualified Hydra.Impl.Haskell.Dsl.Terms as Terms
import Hydra.Impl.Haskell.Dsl.Standard
import Hydra.Impl.Haskell.Sources.Ext.Rdf.Syntax
import Hydra.Impl.Haskell.Sources.Ext.Xml.Schema


key_iri :: String
key_iri :: String
key_iri = String
"iri"

withIri :: String -> Type Meta -> Type Meta
withIri :: String -> Type Meta -> Type Meta
withIri String
iriStr = String -> Maybe (Term Meta) -> Type Meta -> Type Meta
annotateType String
key_iri (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall m. String -> Term m
Terms.string String
iriStr)

nonNegativeInteger :: Type m
nonNegativeInteger :: forall m. Type m
nonNegativeInteger = forall m. Type m
Types.bigint

owlIri :: [Char] -> Type Meta -> Type Meta
owlIri :: String -> Type Meta -> Type Meta
owlIri String
local = String -> Type Meta -> Type Meta
withIri forall a b. (a -> b) -> a -> b
$ String
"http://www.w3.org/2002/07/owl#" forall a. [a] -> [a] -> [a]
++ String
local

owlSyntaxModule :: Module Meta
owlSyntaxModule :: Module Meta
owlSyntaxModule = forall m.
Namespace -> [Element m] -> [Module m] -> Maybe String -> Module m
Module Namespace
ns [Element Meta]
elements [Module Meta
rdfSyntaxModule, Module Meta
xmlSchemaModule] forall a b. (a -> b) -> a -> b
$
    forall a. a -> Maybe a
Just String
"An OWL 2 syntax model. See https://www.w3.org/TR/owl2-syntax"
  where
    ns :: Namespace
ns = String -> Namespace
Namespace String
"hydra/ext/owl/syntax"
    def :: String -> Type m -> Element m
def = forall m. Namespace -> String -> Type m -> Element m
datatype Namespace
ns
    inst :: String -> Type Meta -> Term Meta -> Element Meta
inst = Namespace -> String -> Type Meta -> Term Meta -> Element Meta
dataterm Namespace
ns

    owl :: String -> Type m
owl = forall m. Namespace -> String -> Type m
nsref Namespace
ns
    rdf :: String -> Type m
rdf = forall m. Namespace -> String -> Type m
nsref forall a b. (a -> b) -> a -> b
$ forall m. Module m -> Namespace
moduleNamespace Module Meta
rdfSyntaxModule
    xsd :: String -> Type m
xsd = forall m. Namespace -> String -> Type m
nsref forall a b. (a -> b) -> a -> b
$ forall m. Module m -> Namespace
moduleNamespace Module Meta
xmlSchemaModule

    objectPropertyConstraint :: String -> Element m
objectPropertyConstraint String
lname = forall {m}. String -> Type m -> Element m
def String
lname forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
      String
"annotations"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Annotation",
      String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression"]

    simpleUnion :: [String] -> Type m
simpleUnion [String]
names = forall m. [FieldType m] -> Type m
union forall a b. (a -> b) -> a -> b
$ (\String
n -> forall m. FieldName -> Type m -> FieldType m
FieldType (String -> FieldName
FieldName forall a b. (a -> b) -> a -> b
$ String -> String
decapitalize String
n) forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
n) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String]
names

    withAnns :: [FieldType m] -> Type m
withAnns [FieldType m]
fields = forall m. [FieldType m] -> Type m
record forall a b. (a -> b) -> a -> b
$
      (String
"annotations"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list (forall {m}. String -> Type m
owl String
"Annotation"))forall a. a -> [a] -> [a]
:[FieldType m]
fields

    elements :: [Element Meta]
elements = forall {m}. [Element m]
generalDefinitions forall a. [a] -> [a] -> [a]
++ [Element Meta]
owl2Definitions -- ++ instances

    instances :: [Element Meta]
instances = [
      String -> Type Meta -> Term Meta -> Element Meta
inst String
"Nothing" (forall {m}. String -> Type m
owl String
"Class") forall m. Term m
Terms.unit,
      String -> Type Meta -> Term Meta -> Element Meta
inst String
"Thing" (forall {m}. String -> Type m
owl String
"Class") forall m. Term m
Terms.unit]

    generalDefinitions :: [Element m]
generalDefinitions = [
-- nonNegativeInteger := a nonempty finite sequence of digits between 0 and 9
-- quotedString := a finite sequence of characters in which " (U+22) and \ (U+5C) occur only in pairs of the form \" (U+5C, U+22) and \\ (U+5C, U+5C), enclosed in a pair of " (U+22) characters
-- languageTag := @ (U+40) followed a nonempty sequence of characters matching the langtag production from [BCP 47]
-- nodeID := a finite sequence of characters matching the BLANK_NODE_LABEL production of [SPARQL]
-- fullIRI := an IRI as defined in [RFC3987], enclosed in a pair of < (U+3C) and > (U+3E) characters
-- prefixName := a finite sequence of characters matching the as PNAME_NS production of [SPARQL]
-- abbreviatedIRI := a finite sequence of characters matching the PNAME_LN production of [SPARQL]
-- IRI := fullIRI | abbreviatedIRI
-- ontologyDocument := { prefixDeclaration } Ontology
-- prefixDeclaration := 'Prefix' '(' prefixName '=' fullIRI ')'

-- Ontology :=
--     'Ontology' '(' [ ontologyIRI [ versionIRI ] ]
--        directlyImportsDocuments
--        ontologyAnnotations
--        axioms
--     ')'
      forall {m}. String -> Type m -> Element m
def String
"Ontology" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [ -- note: omitting IRI and version
        String
"directImports"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall m. Type m -> Type m
element forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Ontology",
        String
"annotations"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Annotation",
        String
"axioms"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Axiom"],

-- ontologyIRI := IRI
-- versionIRI := IRI
-- directlyImportsDocuments := { 'Import' '(' IRI ')' }
-- ontologyAnnotations := { Annotation }
-- axioms := { Axiom }

-- Declaration := 'Declaration' '(' axiomAnnotations Entity ')'
      forall {m}. String -> Type m -> Element m
def String
"Declaration" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"entity"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Entity"],

-- Entity :=
--     'Class' '(' Class ')' |
--     'Datatype' '(' Datatype ')' |
--     'ObjectProperty' '(' ObjectProperty ')' |
--     'DataProperty' '(' DataProperty ')' |
--     'AnnotationProperty' '(' AnnotationProperty ')' |
--     'NamedIndividual' '(' NamedIndividual ')'
      forall {m}. String -> Type m -> Element m
def String
"Entity" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"AnnotationProperty",
        String
"Class",
        String
"DataProperty",
        String
"Datatype",
        String
"NamedIndividual",
        String
"ObjectProperty"],

-- AnnotationSubject := IRI | AnonymousIndividual
      forall {m}. String -> Type m -> Element m
def String
"AnnotationSubject" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
union [
        String
"iri"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri",
        String
"anonymousIndividual"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnonymousIndividual"],

-- AnnotationValue := AnonymousIndividual | IRI | Literal
      forall {m}. String -> Type m -> Element m
def String
"AnnotationValue" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
union [
        String
"anonymousIndividual"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnonymousIndividual",
        String
"iri"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri",
        String
"literal"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Literal"],

-- axiomAnnotations := { Annotation }

-- Annotation := 'Annotation' '(' annotationAnnotations AnnotationProperty AnnotationValue ')'
      forall {m}. String -> Type m -> Element m
def String
"Annotation" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty",
        String
"value"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationValue"],

-- annotationAnnotations  := { Annotation }

-- AnnotationAxiom := AnnotationAssertion | SubAnnotationPropertyOf | AnnotationPropertyDomain | AnnotationPropertyRange
      forall {m}. String -> Type m -> Element m
def String
"AnnotationAxiom" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"AnnotationAssertion",
        String
"AnnotationPropertyDomain",
        String
"AnnotationPropertyRange",
        String
"SubAnnotationPropertyOf"],

-- AnnotationAssertion := 'AnnotationAssertion' '(' axiomAnnotations AnnotationProperty AnnotationSubject AnnotationValue ')'
      forall {m}. String -> Type m -> Element m
def String
"AnnotationAssertion" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty",
        String
"subject"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationSubject",
        String
"value"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationValue"],

-- SubAnnotationPropertyOf := 'SubAnnotationPropertyOf' '(' axiomAnnotations subAnnotationProperty superAnnotationProperty ')'
      forall {m}. String -> Type m -> Element m
def String
"SubAnnotationPropertyOf" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"subProperty"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty",
        String
"superProperty"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty"],

-- subAnnotationProperty := AnnotationProperty
-- superAnnotationProperty := AnnotationProperty

-- AnnotationPropertyDomain := 'AnnotationPropertyDomain' '(' axiomAnnotations AnnotationProperty IRI ')'
      forall {m}. String -> Type m -> Element m
def String
"AnnotationPropertyDomain" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty",
        String
"iri"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri"],

-- AnnotationPropertyRange := 'AnnotationPropertyRange' '(' axiomAnnotations AnnotationProperty IRI ')'
      forall {m}. String -> Type m -> Element m
def String
"AnnotationPropertyRange" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnnotationProperty",
        String
"iri"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri"]]

    owl2Definitions :: [Element Meta]
owl2Definitions = [
-- Class := IRI
      forall {m}. String -> Type m -> Element m
def String
"Class" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Classes" forall m. Type m
unit,

-- Datatype := IRI
      forall {m}. String -> Type m -> Element m
def String
"Datatype" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Datatypes" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
union [
          String
"xmlSchema"forall m. String -> Type m -> FieldType m
>:
            String -> Type Meta -> Type Meta
note (String
"XML Schema datatypes are treated as a special case in this model " forall a. [a] -> [a] -> [a]
++
                  String
"(not in the OWL 2 specification itself) because they are particularly common") forall a b. (a -> b) -> a -> b
$
            forall {m}. String -> Type m
xsd String
"Datatype",
          String
"other"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri"],

-- ObjectProperty := IRI
      forall {m}. String -> Type m -> Element m
def String
"ObjectProperty" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Object_Properties" forall m. Type m
unit,

-- DataProperty := IRI
      forall {m}. String -> Type m -> Element m
def String
"DataProperty" forall m. Type m
unit,

-- AnnotationProperty := IRI
      forall {m}. String -> Type m -> Element m
def String
"AnnotationProperty" forall m. Type m
unit,

-- Individual := NamedIndividual | AnonymousIndividual
      forall {m}. String -> Type m -> Element m
def String
"Individual" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
union [
        String
"named"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"NamedIndividual",
        String
"anonymous"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"AnonymousIndividual"],

-- NamedIndividual := IRI
      forall {m}. String -> Type m -> Element m
def String
"NamedIndividual" forall m. Type m
unit,

-- AnonymousIndividual := nodeID
      forall {m}. String -> Type m -> Element m
def String
"AnonymousIndividual" forall m. Type m
unit,

-- Literal := typedLiteral | stringLiteralNoLanguage | stringLiteralWithLanguage
-- typedLiteral := lexicalForm '^^' Datatype
-- lexicalForm := quotedString
-- stringLiteralNoLanguage := quotedString
-- stringLiteralWithLanguage := quotedString languageTag

-- ObjectPropertyExpression := ObjectProperty | InverseObjectProperty
      forall {m}. String -> Type m -> Element m
def String
"ObjectPropertyExpression" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
union [
        String
"object"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectProperty",
        String
"inverseObject"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"InverseObjectProperty"],

-- InverseObjectProperty := 'ObjectInverseOf' '(' ObjectProperty ')'
      forall {m}. String -> Type m -> Element m
def String
"InverseObjectProperty" forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectProperty",

-- DataPropertyExpression := DataProperty
      forall {m}. String -> Type m -> Element m
def String
"DataPropertyExpression" forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataProperty",

-- DataRange :=
--     Datatype |
--     DataIntersectionOf |
--     DataUnionOf |
--     DataComplementOf |
--     DataOneOf |
--     DatatypeRestriction
      forall {m}. String -> Type m -> Element m
def String
"DataRange" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Data_Ranges" forall a b. (a -> b) -> a -> b
$
        forall {m}. [String] -> Type m
simpleUnion [
          String
"DataComplementOf",
          String
"DataIntersectionOf",
          String
"DataOneOf",
          String
"DataUnionOf",
          String
"Datatype",
          String
"DatatypeRestriction"],

-- DataIntersectionOf := 'DataIntersectionOf' '(' DataRange DataRange { DataRange } ')'
      forall {m}. String -> Type m -> Element m
def String
"DataIntersectionOf" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Intersection_of_Data_Ranges" forall a b. (a -> b) -> a -> b
$
        Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataRange",

-- DataUnionOf := 'DataUnionOf' '(' DataRange DataRange { DataRange } ')'
      forall {m}. String -> Type m -> Element m
def String
"DataUnionOf" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Union_of_Data_Ranges" forall a b. (a -> b) -> a -> b
$
        Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataRange",

-- DataComplementOf := 'DataComplementOf' '(' DataRange ')'
      forall {m}. String -> Type m -> Element m
def String
"DataComplementOf" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Complement_of_Data_Ranges" forall a b. (a -> b) -> a -> b
$
        forall {m}. String -> Type m
owl String
"DataRange",

-- DataOneOf := 'DataOneOf' '(' Literal { Literal } ')'
      forall {m}. String -> Type m -> Element m
def String
"DataOneOf" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Enumeration_of_Literals" forall a b. (a -> b) -> a -> b
$
        Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
rdf String
"Literal",

-- DatatypeRestriction := 'DatatypeRestriction' '(' Datatype constrainingFacet restrictionValue { constrainingFacet restrictionValue } ')'
-- constrainingFacet := IRI
-- restrictionValue := Literal
      forall {m}. String -> Type m -> Element m
def String
"DatatypeRestriction" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Datatype_Restrictions" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
record [
          String
"datatype"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Datatype",
          String
"constraints"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DatatypeRestriction.Constraint"],

      forall {m}. String -> Type m -> Element m
def String
"DatatypeRestriction.Constraint" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"constrainingFacet"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DatatypeRestriction.ConstrainingFacet",
        String
"restrictionValue"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Literal"],

      forall {m}. String -> Type m -> Element m
def String
"DatatypeRestriction.ConstrainingFacet" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
union [
          String
"xmlSchema"forall m. String -> Type m -> FieldType m
>:
            String -> Type Meta -> Type Meta
note (String
"XML Schema constraining facets are treated as a special case in this model " forall a. [a] -> [a] -> [a]
++
                  String
"(not in the OWL 2 specification itself) because they are particularly common") forall a b. (a -> b) -> a -> b
$
            forall {m}. String -> Type m
xsd String
"ConstrainingFacet",
          String
"other"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Iri"],

-- ClassExpression :=
--     Class |
--     ObjectIntersectionOf | ObjectUnionOf | ObjectComplementOf | ObjectOneOf |
--     ObjectSomeValuesFrom | ObjectAllValuesFrom | ObjectHasValue | ObjectHasSelf |
--     ObjectMinCardinality | ObjectMaxCardinality | ObjectExactCardinality |
--     DataSomeValuesFrom | DataAllValuesFrom | DataHasValue |
--     DataMinCardinality | DataMaxCardinality | DataExactCardinality
      forall {m}. String -> Type m -> Element m
def String
"ClassExpression" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"Class",
        String
"DataSomeValuesFrom",
        String
"DataAllValuesFrom",
        String
"DataHasValue",
        String
"DataMinCardinality",
        String
"DataMaxCardinality",
        String
"DataExactCardinality",
        String
"ObjectAllValuesFrom",
        String
"ObjectExactCardinality",
        String
"ObjectHasSelf",
        String
"ObjectHasValue",
        String
"ObjectIntersectionOf",
        String
"ObjectMaxCardinality",
        String
"ObjectMinCardinality",
        String
"ObjectOneOf",
        String
"ObjectSomeValuesFrom",
        String
"ObjectUnionOf"],

-- ObjectIntersectionOf := 'ObjectIntersectionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectIntersectionOf" forall a b. (a -> b) -> a -> b
$ Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression",

-- ObjectUnionOf := 'ObjectUnionOf' '(' ClassExpression ClassExpression { ClassExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectUnionOf" forall a b. (a -> b) -> a -> b
$ Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression",

-- ObjectComplementOf := 'ObjectComplementOf' '(' ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectComplementOf" forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression",

-- ObjectOneOf := 'ObjectOneOf' '(' Individual { Individual }')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectOneOf" forall a b. (a -> b) -> a -> b
$ Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Individual",

-- ObjectSomeValuesFrom := 'ObjectSomeValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectSomeValuesFrom" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"class"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectAllValuesFrom := 'ObjectAllValuesFrom' '(' ObjectPropertyExpression ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectAllValuesFrom" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"class"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectHasValue := 'ObjectHasValue' '(' ObjectPropertyExpression Individual ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectHasValue" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"individual"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"],

-- ObjectHasSelf := 'ObjectHasSelf' '(' ObjectPropertyExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectHasSelf" forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",

-- ObjectMinCardinality := 'ObjectMinCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectMinCardinality" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Minimum_Cardinality" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
record [
          String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
          String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"class"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectMaxCardinality := 'ObjectMaxCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectMaxCardinality" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Maximum_Cardinality" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
record [
          String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
          String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"class"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectExactCardinality := 'ObjectExactCardinality' '(' nonNegativeInteger ObjectPropertyExpression [ ClassExpression ] ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectExactCardinality" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Exact_Cardinality" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
record [
          String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
          String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"class"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- DataSomeValuesFrom := 'DataSomeValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
      forall {m}. String -> Type m -> Element m
def String
"DataSomeValuesFrom" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataRange"],

-- DataAllValuesFrom := 'DataAllValuesFrom' '(' DataPropertyExpression { DataPropertyExpression } DataRange ')'
      forall {m}. String -> Type m -> Element m
def String
"DataAllValuesFrom" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataRange"],

-- DataHasValue := 'DataHasValue' '(' DataPropertyExpression Literal ')'
      forall {m}. String -> Type m -> Element m
def String
"DataHasValue" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"value"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
rdf String
"Literal"],

-- DataMinCardinality := 'DataMinCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
      forall {m}. String -> Type m -> Element m
def String
"DataMinCardinality" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataRange"],

-- DataMaxCardinality := 'DataMaxCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
      forall {m}. String -> Type m -> Element m
def String
"DataMaxCardinality" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataRange"],

-- DataExactCardinality := 'DataExactCardinality' '(' nonNegativeInteger DataPropertyExpression [ DataRange ] ')'
      forall {m}. String -> Type m -> Element m
def String
"DataExactCardinality" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
record [
        String
"bound"forall m. String -> Type m -> FieldType m
>: forall m. Type m
nonNegativeInteger,
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataRange"],

-- Axiom := Declaration | ClassAxiom | ObjectPropertyAxiom | DataPropertyAxiom | DatatypeDefinition | HasKey | Assertion | AnnotationAxiom
      forall {m}. String -> Type m -> Element m
def String
"Axiom" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Axioms" forall a b. (a -> b) -> a -> b
$
        forall {m}. [String] -> Type m
simpleUnion [
          String
"AnnotationAxiom",
          String
"Assertion",
          String
"ClassAxiom",
          String
"DataPropertyAxiom",
          String
"DatatypeDefinition",
          String
"Declaration",
          String
"HasKey",
          String
"ObjectPropertyAxiom"],

-- ClassAxiom := SubClassOf | EquivalentClasses | DisjointClasses | DisjointUnion
      forall {m}. String -> Type m -> Element m
def String
"ClassAxiom" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"DisjointClasses",
        String
"DisjointUnion",
        String
"EquivalentClasses",
        String
"SubClassOf"],

-- SubClassOf := 'SubClassOf' '(' axiomAnnotations subClassExpression superClassExpression ')'
-- subClassExpression := ClassExpression
-- superClassExpression := ClassExpression
      forall {m}. String -> Type m -> Element m
def String
"SubClassOf" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"subClass"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression",
        String
"superClass"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- EquivalentClasses := 'EquivalentClasses' '(' axiomAnnotations ClassExpression ClassExpression { ClassExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"EquivalentClasses" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"classes"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- DisjointClasses := 'DisjointClasses' '(' axiomAnnotations ClassExpression ClassExpression { ClassExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"DisjointClasses" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"classes"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- DisjointUnion := 'DisjointUnion' '(' axiomAnnotations Class disjointClassExpressions ')'
-- disjointClassExpressions := ClassExpression ClassExpression { ClassExpression }
      forall {m}. String -> Type m -> Element m
def String
"DisjointUnion" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Disjoint_Union_of_Class_Expressions" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
withAnns [
          String
"class"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Class",
          String
"classes"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectPropertyAxiom :=
--     SubObjectPropertyOf | EquivalentObjectProperties |
--     DisjointObjectProperties | InverseObjectProperties |
--     ObjectPropertyDomain | ObjectPropertyRange |
--     FunctionalObjectProperty | InverseFunctionalObjectProperty |
--     ReflexiveObjectProperty | IrreflexiveObjectProperty |
--     SymmetricObjectProperty | AsymmetricObjectProperty |
--     TransitiveObjectProperty
      forall {m}. String -> Type m -> Element m
def String
"ObjectPropertyAxiom" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"AsymmetricObjectProperty",
        String
"DisjointObjectProperties",
        String
"EquivalentObjectProperties",
        String
"FunctionalObjectProperty",
        String
"InverseFunctionalObjectProperty",
        String
"InverseObjectProperties",
        String
"IrreflexiveObjectProperty",
        String
"ObjectPropertyDomain",
        String
"ObjectPropertyRange",
        String
"ReflexiveObjectProperty",
        String
"SubObjectPropertyOf",
        String
"SymmetricObjectProperty",
        String
"TransitiveObjectProperty"],

-- SubObjectPropertyOf := 'SubObjectPropertyOf' '(' axiomAnnotations subObjectPropertyExpression superObjectPropertyExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"SubObjectPropertyOf" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"subProperty"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
nonemptyList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"superProperty"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression"],
-- subObjectPropertyExpression := ObjectPropertyExpression | propertyExpressionChain
-- propertyExpressionChain := 'ObjectPropertyChain' '(' ObjectPropertyExpression ObjectPropertyExpression { ObjectPropertyExpression } ')'
-- superObjectPropertyExpression := ObjectPropertyExpression

-- EquivalentObjectProperties := 'EquivalentObjectProperties' '(' axiomAnnotations ObjectPropertyExpression ObjectPropertyExpression { ObjectPropertyExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"EquivalentObjectProperties" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"properties"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectPropertyExpression"],

-- DisjointObjectProperties := 'DisjointObjectProperties' '(' axiomAnnotations ObjectPropertyExpression ObjectPropertyExpression { ObjectPropertyExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"DisjointObjectProperties" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"properties"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectPropertyExpression"],

-- ObjectPropertyDomain := 'ObjectPropertyDomain' '(' axiomAnnotations ObjectPropertyExpression ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectPropertyDomain" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Object_Property_Domain" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
withAnns [
          String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"domain"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- ObjectPropertyRange := 'ObjectPropertyRange' '(' axiomAnnotations ObjectPropertyExpression ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectPropertyRange" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Object_Property_Range" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
withAnns [
          String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"range"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- InverseObjectProperties := 'InverseObjectProperties' '(' axiomAnnotations ObjectPropertyExpression ObjectPropertyExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"InverseObjectProperties" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property1"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"property2"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression"],

-- FunctionalObjectProperty := 'FunctionalObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"FunctionalObjectProperty",

-- InverseFunctionalObjectProperty := 'InverseFunctionalObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"InverseFunctionalObjectProperty",

-- ReflexiveObjectProperty := 'ReflexiveObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"ReflexiveObjectProperty",

-- IrreflexiveObjectProperty := 'IrreflexiveObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"IrreflexiveObjectProperty",

-- SymmetricObjectProperty := 'SymmetricObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"SymmetricObjectProperty",

-- AsymmetricObjectProperty := 'AsymmetricObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"AsymmetricObjectProperty",

-- TransitiveObjectProperty := 'TransitiveObjectProperty' '(' axiomAnnotations ObjectPropertyExpression ')'
      forall {m}. String -> Element m
objectPropertyConstraint String
"TransitiveObjectProperty",

-- DataPropertyAxiom :=
--     SubDataPropertyOf | EquivalentDataProperties | DisjointDataProperties |
--     DataPropertyDomain | DataPropertyRange | FunctionalDataProperty
      forall {m}. String -> Type m -> Element m
def String
"DataPropertyAxiom" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
        String
"DataPropertyAxiom",
        String
"DataPropertyRange",
        String
"DisjointDataProperties",
        String
"EquivalentDataProperties",
        String
"FunctionalDataProperty",
        String
"SubDataPropertyOf"],

-- SubDataPropertyOf := 'SubDataPropertyOf' '(' axiomAnnotations subDataPropertyExpression superDataPropertyExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"SubDataPropertyOf" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"subProperty"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"superProperty"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression"],
-- subDataPropertyExpression := DataPropertyExpression
-- superDataPropertyExpression := DataPropertyExpression

-- EquivalentDataProperties := 'EquivalentDataProperties' '(' axiomAnnotations DataPropertyExpression DataPropertyExpression { DataPropertyExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"EquivalentDataProperties" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"properties"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataPropertyExpression"],

-- DisjointDataProperties := 'DisjointDataProperties' '(' axiomAnnotations DataPropertyExpression DataPropertyExpression { DataPropertyExpression } ')'
      forall {m}. String -> Type m -> Element m
def String
"DisjointDataProperties" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"properties"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataPropertyExpression"],

-- DataPropertyDomain := 'DataPropertyDomain' '(' axiomAnnotations DataPropertyExpression ClassExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"DataPropertyDomain" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"domain"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- DataPropertyRange := 'DataPropertyRange' '(' axiomAnnotations DataPropertyExpression DataRange ')'
      forall {m}. String -> Type m -> Element m
def String
"DataPropertyRange" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression"],

-- FunctionalDataProperty := 'FunctionalDataProperty' '(' axiomAnnotations DataPropertyExpression ')'
      forall {m}. String -> Type m -> Element m
def String
"FunctionalDataProperty" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression"],

-- DatatypeDefinition := 'DatatypeDefinition' '(' axiomAnnotations Datatype DataRange ')'
      forall {m}. String -> Type m -> Element m
def String
"DatatypeDefinition" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"datatype"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Datatype",
        String
"range"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataRange"],

-- HasKey := 'HasKey' '(' axiomAnnotations ClassExpression '(' { ObjectPropertyExpression } ')' '(' { DataPropertyExpression } ')' ')'
      forall {m}. String -> Type m -> Element m
def String
"HasKey" forall a b. (a -> b) -> a -> b
$
        String -> Type Meta -> Type Meta
see String
"https://www.w3.org/TR/owl2-syntax/#Keys" forall a b. (a -> b) -> a -> b
$
        forall m. [FieldType m] -> Type m
withAnns [
          String
"class"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression",
          String
"objectProperties"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
          String
"dataProperties"forall m. String -> Type m -> FieldType m
>: forall m. Type m -> Type m
list forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"DataPropertyExpression"],

-- Assertion :=
--     SameIndividual | DifferentIndividuals | ClassAssertion |
--     ObjectPropertyAssertion | NegativeObjectPropertyAssertion |
--     DataPropertyAssertion | NegativeDataPropertyAssertion
      forall {m}. String -> Type m -> Element m
def String
"Assertion" forall a b. (a -> b) -> a -> b
$ forall {m}. [String] -> Type m
simpleUnion [
       String
"ClassAssertion",
       String
"DataPropertyAssertion",
       String
"DifferentIndividuals",
       String
"ObjectPropertyAssertion",
       String
"NegativeDataPropertyAssertion",
       String
"NegativeObjectPropertyAssertion",
       String
"SameIndividual"],

-- sourceIndividual := Individual
-- targetIndividual := Individual
-- targetValue := Literal
-- SameIndividual := 'SameIndividual' '(' axiomAnnotations Individual Individual { Individual } ')'
      forall {m}. String -> Type m -> Element m
def String
"SameIndividual" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"individuals"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Individual"],

-- DifferentIndividuals := 'DifferentIndividuals' '(' axiomAnnotations Individual Individual { Individual } ')'
      forall {m}. String -> Type m -> Element m
def String
"DifferentIndividuals" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"individuals"forall m. String -> Type m -> FieldType m
>: Type Meta -> Type Meta
twoOrMoreList forall a b. (a -> b) -> a -> b
$ forall {m}. String -> Type m
owl String
"Individual"],

-- ClassAssertion := 'ClassAssertion' '(' axiomAnnotations ClassExpression Individual ')'
      forall {m}. String -> Type m -> Element m
def String
"ClassAssertion"forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"class"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ClassExpression",
        String
"individual"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"],

-- ObjectPropertyAssertion := 'ObjectPropertyAssertion' '(' axiomAnnotations ObjectPropertyExpression sourceIndividual targetIndividual ')'
      forall {m}. String -> Type m -> Element m
def String
"ObjectPropertyAssertion" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"source"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual",
        String
"target"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"],

-- NegativeObjectPropertyAssertion := 'NegativeObjectPropertyAssertion' '(' axiomAnnotations ObjectPropertyExpression sourceIndividual targetIndividual ')'
      forall {m}. String -> Type m -> Element m
def String
"NegativeObjectPropertyAssertion" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"ObjectPropertyExpression",
        String
"source"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual",
        String
"target"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"],

-- DataPropertyAssertion := 'DataPropertyAssertion' '(' axiomAnnotations DataPropertyExpression sourceIndividual targetValue ')'
      forall {m}. String -> Type m -> Element m
def String
"DataPropertyAssertion" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"source"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual",
        String
"target"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"],

-- NegativeDataPropertyAssertion := 'NegativeDataPropertyAssertion' '(' axiomAnnotations DataPropertyExpression sourceIndividual targetValue ')'
      forall {m}. String -> Type m -> Element m
def String
"NegativeDataPropertyAssertion" forall a b. (a -> b) -> a -> b
$ forall m. [FieldType m] -> Type m
withAnns [
        String
"property"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"DataPropertyExpression",
        String
"source"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual",
        String
"target"forall m. String -> Type m -> FieldType m
>: forall {m}. String -> Type m
owl String
"Individual"]]