AS.hs revision 9cb6af1a7632f12b60f592ce5eb2ac51e6bd33bb
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance{-# LANGUAGE DeriveDataTypeable #-}
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance{- |
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceModule : $Header$
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceCopyright : (c) Heng Jiang, Uni Bremen 2004-2007
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceLicense : GPLv2 or higher, see LICENSE.txt
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceMaintainer : Christian.Maeder@dfki.de
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceStability : provisional
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancePortability : non-portable(deriving Typeable)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceThis module defines all the data types for the functional style Syntax
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Manceof OWL 2
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceIt is modeled after the W3C document:
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance<http://www.w3.org/TR/2009/REC-owl2-syntax-20091027/#Functional-Style_Syntax>
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-}
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancemodule OWL2.AS where
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport Common.Keywords
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport Common.Id (GetRange)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport OWL.Keywords
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport OWL.ColonKeywords
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport qualified Data.Map as Map
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport Data.Typeable
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance{- | full or abbreviated IRIs with a possible uri for the prefix
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance or a local part following a hash sign -}
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata QName = QN
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance { namePrefix :: String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance -- ^ the name prefix part of a qualified name \"namePrefix:localPart\"
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , localPart :: String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance -- ^ the local part of a qualified name \"namePrefix:localPart\"
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , isFullIri :: Bool
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , namespaceUri :: String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance -- ^ the associated namespace uri (not printed)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance } deriving (Typeable, Show)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQN :: QName -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQN q = (if isFullIri q then showQI else showQU) q
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | show QName as abbreviated iri
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQU :: QName -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQU (QN pre local _ _) =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance if null pre then local else pre ++ ":" ++ local
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | show QName in ankle brackets as full iris
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQI :: QName -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQI = ('<' :) . (++ ">") . showQU
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancenullQName :: QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancenullQName = QN "" "" False ""
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedummyQName :: QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedummyQName = QN "http" "//www.dfki.de/sks/hets/ontology/unamed" True ""
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName :: String -> QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName s = nullQName { localPart = s }
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance Eq QName where
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance p == q = compare p q == EQ
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance Ord QName where
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance compare (QN p1 l1 b1 n1) (QN p2 l2 b2 n2) =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance if null n1 then
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance if null n2 then compare (b1, p1, l1) (b2, p2, l2) else LT
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance else if null n2 then GT else compare (b1, l1, n1) (b2, l2, n2)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype IRIreference = QName
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype IRI = QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | prefix -> localname
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype PrefixMap = Map.Map String String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mancetype NodeID = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype LexicalForm = String
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype LanguageTag = String
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype PrefixName = String
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype ImportIRI = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype OntologyIRI = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype Class = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype Datatype = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype ObjectProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype DataProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype AnnotationProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype NamedIndividual = IRI
9cb6af1a7632f12b60f592ce5eb2ac51e6bd33bbFelix Gabriel Mancetype Individual = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- ONTOLOGIES SYNTAX
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance------------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata OntologyFile = OntologyFile
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance { prefixName :: PrefixMap
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , ontology :: Ontology
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance } deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance GetRange OntologyFile
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata Ontology = Ontology
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance { uri :: OntologyIRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance , importsList :: [ImportIRI]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , annotationsList :: [Annotation]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , axiomsList :: [Axiom]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance } deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancetype OntologyMap = Map.Map String OntologyFile
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- SYMBOL ITEMS FOR HETS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance------------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata SymbItems = SymbItems (Maybe EntityType) [IRI]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata SymbMapItems = SymbMapItems (Maybe EntityType) [(IRI, Maybe IRI)]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | raw symbols
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata RawSymb = ASymbol Entity | AnUri IRI deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- LITERALS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-------------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancedata TypedOrUntyped = Typed Datatype | Untyped (Maybe LanguageTag)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
a921ae1da1302f673204e7b63cdce01439a9bd5eFelix Gabriel Mancedata Literal = Literal LexicalForm TypedOrUntyped
a921ae1da1302f673204e7b63cdce01439a9bd5eFelix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
a921ae1da1302f673204e7b63cdce01439a9bd5eFelix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancecTypeS :: String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancecTypeS = "^^"
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | a lexical representation either with an "^^" URI (typed) or
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- an optional language tag starting with "\@" (untyped)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance--------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- PROPERTY EXPRESSIONS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance--------------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancetype InverseObjectProperty = ObjectPropertyExpression
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancedata ObjectPropertyExpression = ObjectProp ObjectProperty | ObjectInverseOf InverseObjectProperty
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype DataPropertyExpression = DataProperty
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | data type strings (some are not listed in the grammar)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedatatypeKeys :: [String]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedatatypeKeys =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance [ booleanS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , dATAS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , decimalS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , floatS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , integerS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , negativeIntegerS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , nonNegativeIntegerS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , nonPositiveIntegerS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , positiveIntegerS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , stringS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , universalS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance ]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance--------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- DATA RANGES
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance--------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata DatatypeFacet =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance LENGTH
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MINLENGTH
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MAXLENGTH
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | PATTERN
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MININCLUSIVE
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MINEXCLUSIVE
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MAXINCLUSIVE
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | MAXEXCLUSIVE
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | TOTALDIGITS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | FRACTIONDIGITS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowFacet :: DatatypeFacet -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowFacet df = case df of
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance LENGTH -> lengthS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MINLENGTH -> minLengthS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MAXLENGTH -> maxLengthS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance PATTERN -> patternS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MININCLUSIVE -> lessEq
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MINEXCLUSIVE -> lessS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MAXINCLUSIVE -> greaterEq
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MAXEXCLUSIVE -> greaterS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance TOTALDIGITS -> digitsS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance FRACTIONDIGITS -> fractionS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata DataRange
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance = DataType Datatype
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mance | DataJunction JunctionType [DataRange] -- at least two elements in the list
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataComplementOf DataRange
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataOneOf [Literal] -- at least one element in the list
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DatatypeRestriction Datatype [(ConstrainingFacet, RestrictionValue)] -- at least one element in the list
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata JunctionType = UnionOf | IntersectionOf deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype ConstrainingFacet = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype RestrictionValue = Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- CLASS EXPERSSIONS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata QuantifierType = AllValuesFrom | SomeValuesFrom deriving (Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel ManceshowQuantifierType :: QuantifierType -> String
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel ManceshowQuantifierType ty = case ty of
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance AllValuesFrom -> onlyS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance SomeValuesFrom -> someS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata CardinalityType = MinCardinality | MaxCardinality | ExactCardinality
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowCardinalityType :: CardinalityType -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowCardinalityType ty = case ty of
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MinCardinality -> minS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance MaxCardinality -> maxS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance ExactCardinality -> exactlyS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata Cardinality a b = Cardinality CardinalityType Int a (Maybe b)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata ClassExpression =
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance Expression Class
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectJunction JunctionType [ClassExpression] -- min. 2 ClassExpressions
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectComplementOf ClassExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectOneOf [Individual] -- min. 1 Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectValuesFrom QuantifierType ObjectPropertyExpression ClassExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectHasValue ObjectPropertyExpression Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectHasSelf ObjectPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectCardinality (Cardinality ObjectPropertyExpression ClassExpression)
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mance | DataValuesFrom
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mance QuantifierType DataPropertyExpression [DataPropertyExpression] DataRange
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataHasValue DataPropertyExpression Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | DataCardinality (Cardinality DataPropertyExpression DataRange)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- ANNOTATIONS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata Annotation = Annotation [Annotation] AnnotationProperty AnnotationValue
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata AnnotationAxiom
9cb6af1a7632f12b60f592ce5eb2ac51e6bd33bbFelix Gabriel Mance = AnnotationAssertion [Annotation] IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | SubAnnotationPropertyOf [Annotation] AnnotationProperty AnnotationProperty
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | AnnotationPropertyDomainOrRange AnnotationDomainOrRange [Annotation] AnnotationProperty IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata AnnotationDomainOrRange = AnnDomain | AnnRange deriving (Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel ManceshowAnnDomainOrRange :: AnnotationDomainOrRange -> String
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel ManceshowAnnDomainOrRange dr = case dr of
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mance AnnDomain -> domainC
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mance AnnRange -> rangeC
6a058c55573e9bbb71cee8a7361ef12bfaedd9efFelix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata AnnotationValue
9cb6af1a7632f12b60f592ce5eb2ac51e6bd33bbFelix Gabriel Mance = AnnValue IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | AnnValLit Literal
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- AXIOMS
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance--Entities
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata EntityType =
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance Datatype
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | Class
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectProperty
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataProperty
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | AnnotationProperty
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | NamedIndividual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Enum, Bounded, Show, Read, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- | Syntax of Entities
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata Entity = Entity EntityType IRI deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Manceinstance GetRange Entity
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel ManceentityTypes :: [EntityType]
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel ManceentityTypes = [minBound .. maxBound]
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype SourceIndividual = Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype TargetIndividual = Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype TargetValue = Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata Axiom = -- Annotations can be ignored
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance PlainAxiom [Annotation] PlainAxiom
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | EntityAnno AnnotationAxiom
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance GetRange Axiom
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata EquivOrDisjoint = Equivalent | Disjoint deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowEquivOrDisjoint :: EquivOrDisjoint -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowEquivOrDisjoint ed = case ed of
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Equivalent -> equivalentToC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Disjoint -> disjointWithC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata ObjDomainOrRange = ObjDomain | ObjRange deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowObjDomainOrRange :: ObjDomainOrRange -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowObjDomainOrRange dr = case dr of
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance ObjDomain -> domainC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance ObjRange -> rangeC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata DataDomainOrRange = DataDomain ClassExpression | DataRange DataRange
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata Character =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Functional
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | InverseFunctional
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Reflexive
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Irreflexive
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Symmetric
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Asymmetric
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Antisymmetric
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Transitive
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Enum, Bounded, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata SameOrDifferent = Same | Different deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowSameOrDifferent :: SameOrDifferent -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowSameOrDifferent sd = case sd of
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Same -> sameAsC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Different -> differentFromC
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata PositiveOrNegative = Positive | Negative deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata Assertion a b = Assertion a PositiveOrNegative SourceIndividual b
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata PlainAxiom =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance SubClassOf SubClass SuperClass
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | EquivOrDisjointClasses EquivOrDisjoint [ClassExpression] -- min. 2 desc.
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DisjointUnion Class [ClassExpression] -- min. 2 desc.
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | SubObjectPropertyOf SubObjectPropertyExpression ObjectPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | EquivOrDisjointObjectProperties EquivOrDisjoint [ObjectPropertyExpression] -- min. 2 ObjectPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectPropertyDomainOrRange ObjDomainOrRange ObjectPropertyExpression ClassExpression
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | InverseObjectProperties ObjectPropertyExpression ObjectPropertyExpression
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | ObjectPropertyCharacter Character ObjectPropertyExpression
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | SubDataPropertyOf DataPropertyExpression DataPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | EquivOrDisjointDataProperties EquivOrDisjoint [DataPropertyExpression] -- min. 2 DataPropertyExpressions
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | DataPropertyDomainOrRange DataDomainOrRange DataPropertyExpression
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | FunctionalDataProperty DataPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | SameOrDifferentIndividual SameOrDifferent [Individual] -- min. 2 ind.
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ClassAssertion ClassExpression Individual -- arguments are reversed from OWL-1
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectPropertyAssertion (Assertion ObjectPropertyExpression TargetIndividual)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataPropertyAssertion (Assertion DataPropertyExpression TargetValue)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | Declaration Entity
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DatatypeDefinition Datatype DataRange
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | HasKey ClassExpression [ObjectPropertyExpression] [DataPropertyExpression]
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype SubClass = ClassExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype SuperClass = ClassExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata SubObjectPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance = OPExpression ObjectPropertyExpression
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | SubObjectPropertyChain [ObjectPropertyExpression] -- min. 2 ObjectPropertyExpression
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Typeable, Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance-- ONTOLOGY FILES
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance---------------------
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceemptyOntologyFile :: OntologyFile
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceemptyOntologyFile = OntologyFile Map.empty emptyOntology
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceemptyOntology :: Ontology
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceemptyOntology = Ontology nullQName [] [] []
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisEmptyOntologyFile :: OntologyFile -> Bool
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisEmptyOntologyFile (OntologyFile ns onto) =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance Map.null ns && isEmptyOntology onto
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisEmptyOntology :: Ontology -> Bool
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisEmptyOntology (Ontology (QN _ l _ n) annoList impList axioms) =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance null l && null n && null annoList && null impList && null axioms