AS.hs revision 431571057e88a650a974adec93ea4bb5173b6213
98fa6135beb09a6612ea256eb34ac5b2805d3ea5Ewaryst Schulz{- |
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzModule : $Header$
e9458b1a7a19a63aa4c179f9ab20f4d50681c168Jens ElknerCopyright : (c) C. Maeder
25449dd4a796d3244e754bde21a5e9c401dc135eEwaryst SchulzLicense : GPLv2 or higher, see LICENSE.txt
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz
98890889ffb2e8f6f722b00e265a211f13b5a861Corneliu-Claudiu ProdescuMaintainer : Christian.Maeder@dfki.de
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzStability : provisional
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzPortability : portable
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzOWL 2 Functional Syntax constructs
1b353d403dbdb365ae93a568f32b3ebf5698cab5Ewaryst Schulz
1b353d403dbdb365ae93a568f32b3ebf5698cab5Ewaryst SchulzReferences:
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz <http://www.w3.org/TR/2009/REC-owl2-syntax-20091027/#Functional-Style_Syntax>
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz <http://www.w3.org/TR/owl2-manchester-syntax/>
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz-}
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzmodule OWL2.AS where
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport Common.Id
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport Common.Keywords
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport OWL2.ColonKeywords
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport OWL2.Keywords
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport Data.Char (intToDigit)
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulzimport Data.List
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulzimport qualified Data.Map as Map
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulzdata IRIType = Full | Abbreviated | NodeID
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz deriving (Show, Eq, Ord)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
c73c3d0df595b7feab36cf441a1a31cd1a2c7c1dEwaryst Schulz{- | full or abbreviated IRIs with a possible uri for the prefix
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz or a local part following a hash sign -}
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst Schulzdata QName = QN
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz { namePrefix :: String
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz -- ^ the name prefix part of a qualified name \"namePrefix:localPart\"
62ff5e56ab685e81ebde4712eb1bf677322bfba9Ewaryst Schulz , localPart :: String
62ff5e56ab685e81ebde4712eb1bf677322bfba9Ewaryst Schulz -- ^ the local part of a qualified name \"namePrefix:localPart\"
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz , iriType :: IRIType
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz , expandedIRI :: String
c208973c890b8f993297720fd0247bc7481d4304Christian Maeder -- ^ the associated namespace uri (not printed)
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz , iriPos :: Range
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz } deriving Show
5f2c34b8971f9ca7e63364b69e167851d001168eEwaryst Schulz
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulzinstance Eq QName where
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz p == q = compare p q == EQ
df0d1a7e7dfff3be40c24b25318a6a07c748be20Ewaryst Schulz
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulzinstance Ord QName where
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz compare (QN p1 l1 b1 n1 _) (QN p2 l2 b2 n2 _) =
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst Schulz if null n1 || null n2 then compare (b1, p1, l1) (b2, p2, l2) else
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz compare n1 n2 -- compare fully expanded names only
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulzinstance GetRange QName where
df0d1a7e7dfff3be40c24b25318a6a07c748be20Ewaryst Schulz getRange = iriPos
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzshowQN :: QName -> String
348346590dc302381df4daf372d6dc601b860eaeEwaryst SchulzshowQN q = (if iriType q /= Abbreviated then showQI else showQU) q
49c8d0af1a96cab75795d49b078b9163b666473fEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz-- | show QName as abbreviated iri
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzshowQU :: QName -> String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzshowQU (QN pre local _ _ _) =
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder if null pre then local else pre ++ ":" ++ local
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz-- | show QName in ankle brackets as full iris
938677803842b384a91fef21f58f86b8e3188b43Ewaryst SchulzshowQI :: QName -> String
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst SchulzshowQI = ('<' :) . (++ ">") . showQU
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulznullQName :: QName
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulznullQName = QN "" "" Abbreviated "" nullRange
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzdummyQName :: QName
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzdummyQName =
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz QN "http" "//www.dfki.de/sks/hets/ontology/unamed" Full "" nullRange
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzmkQName :: String -> QName
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzmkQName s = nullQName { localPart = s }
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzsetQRange :: Range -> QName -> QName
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzsetQRange r q = q { iriPos = r }
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzsetPrefix :: String -> QName -> QName
8b6641f92fd899798421ef2b3d3e335da7425030Ewaryst SchulzsetPrefix s q = q { namePrefix = s }
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzsetReservedPrefix :: QName -> QName
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzsetReservedPrefix iri
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz | isDatatypeKey iri && null (namePrefix iri) = setPrefix "xsd" iri
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz | isThing iri && null (namePrefix iri) = setPrefix "owl" iri
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz | otherwise = iri
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzsetFull :: QName -> QName
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst SchulzsetFull q = q {iriType = Full}
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulztype IRI = QName
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz-- | checks if an IRI is an anonymous individual
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst SchulzisAnonymous :: IRI -> Bool
938677803842b384a91fef21f58f86b8e3188b43Ewaryst SchulzisAnonymous iri = iriType iri == NodeID
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz-- | checks if a string (bound to be localPart of an IRI) contains \":\/\/\"
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzcssIRI :: String -> IRIType
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzcssIRI iri = if isInfixOf "://" iri then Full else Abbreviated
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder-- | prefix -> localname
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulztype PrefixMap = Map.Map String String
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype LexicalForm = String
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulztype LanguageTag = String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype ImportIRI = IRI
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype OntologyIRI = IRI
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype Class = IRI
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype Datatype = IRI
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype ObjectProperty = IRI
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulztype DataProperty = IRI
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype AnnotationProperty = IRI
bdf2e01977470bedcb4425e2dadabc9e9f6ba149Ewaryst Schulztype NamedIndividual = IRI
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulztype Individual = IRI
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulzdata EquivOrDisjoint = Equivalent | Disjoint
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz deriving (Show, Eq, Ord)
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzshowEquivOrDisjoint :: EquivOrDisjoint -> String
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzshowEquivOrDisjoint ed = case ed of
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz Equivalent -> equivalentToC
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz Disjoint -> disjointWithC
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulzdata DomainOrRange = ADomain | ARange
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz deriving (Show, Eq, Ord)
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzshowDomainOrRange :: DomainOrRange -> String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzshowDomainOrRange dr = case dr of
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz ADomain -> domainC
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz ARange -> rangeC
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata SameOrDifferent = Same | Different
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz deriving (Show, Eq, Ord)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzshowSameOrDifferent :: SameOrDifferent -> String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzshowSameOrDifferent sd = case sd of
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz Same -> sameAsC
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz Different -> differentFromC
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata Relation =
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz EDRelation EquivOrDisjoint
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz | SubPropertyOf
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz | InverseOf
a413fff68823617afb1fa4fced0d7a8ec3880664Ewaryst Schulz | SubClass
a413fff68823617afb1fa4fced0d7a8ec3880664Ewaryst Schulz | Types
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | DRRelation DomainOrRange
a86a4bf157e15434838f217d44ecd8645555c58bEwaryst Schulz | SDRelation SameOrDifferent
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz deriving (Show, Eq, Ord)
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst SchulzshowRelation :: Relation -> String
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzshowRelation r = case r of
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz EDRelation ed -> showEquivOrDisjoint ed
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst Schulz SubPropertyOf -> subPropertyOfC
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz InverseOf -> inverseOfC
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz SubClass -> subClassOfC
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz Types -> typesC
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulz DRRelation dr -> showDomainOrRange dr
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulz SDRelation sd -> showSameOrDifferent sd
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulz
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst SchulzgetED :: Relation -> EquivOrDisjoint
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst SchulzgetED r = case r of
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz EDRelation ed -> ed
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz _ -> error "not domain or range"
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzgetDR :: Relation -> DomainOrRange
938677803842b384a91fef21f58f86b8e3188b43Ewaryst SchulzgetDR r = case r of
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder DRRelation dr -> dr
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz _ -> error "not domain or range"
1596a4d2cc01bff500afdd3789a43ec93210e81fChristian Maeder
938677803842b384a91fef21f58f86b8e3188b43Ewaryst SchulzgetSD :: Relation -> SameOrDifferent
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von SchroedergetSD s = case s of
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz SDRelation sd -> sd
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz _ -> error "not same or different"
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulzdata Character =
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder Functional
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | InverseFunctional
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | Reflexive
5ca1fe655d7d4e35e59a082b5955b306643329d0Ewaryst Schulz | Irreflexive
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz | Symmetric
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz | Asymmetric
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz | Antisymmetric
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz | Transitive
df0d1a7e7dfff3be40c24b25318a6a07c748be20Ewaryst Schulz deriving (Enum, Bounded, Show, Eq, Ord)
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
1a5414972199f27756b513d5cf515e4c0d688c08Ewaryst Schulzdata PositiveOrNegative = Positive | Negative
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder deriving (Show, Eq, Ord)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulzdata QuantifierType = AllValuesFrom | SomeValuesFrom
348346590dc302381df4daf372d6dc601b860eaeEwaryst Schulz deriving (Show, Eq, Ord)
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst SchulzshowQuantifierType :: QuantifierType -> String
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzshowQuantifierType ty = case ty of
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz AllValuesFrom -> onlyS
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz SomeValuesFrom -> someS
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
c1d06b3018b34ede2b3fb6c7fe2ad28cd5ce5b68Christian MaedercheckPredef :: [String] -> String -> String -> IRI -> Bool
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzcheckPredef sl pref sc u =
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz localPart u `elem` sl && elem (namePrefix u) ["", pref]
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz || showQU u `elem` map (sc ++) sl
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzowlSomething :: [String]
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst SchulzowlSomething = ["Thing", "Nothing"]
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisThing :: IRI -> Bool
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisThing = checkPredef owlSomething "owl" "http://www.w3.org/2002/07/owl#"
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz-- | data type strings (some are not listed in the grammar)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzdatatypeKeys :: [String]
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzdatatypeKeys = [booleanS, dATAS, stringS, universalS] ++ owlNumbers
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulzowlNumbers :: [String]
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulzowlNumbers = [integerS, negativeIntegerS, nonNegativeIntegerS,
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz nonPositiveIntegerS, positiveIntegerS, decimalS, doubleS, floatS]
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisDatatypeKey :: IRI -> Bool
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisDatatypeKey = checkPredef datatypeKeys "xsd"
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz "http://www.w3.org/2001/XMLSchema#"
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst SchulzisOWLSmth :: [String] -> IRI -> Bool
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzisOWLSmth sl = checkPredef sl "xsd" "http://www.w3.org/2001/XMLSchema#"
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulzdata DatatypeType = OWL2Number | OWL2String | OWL2Bool | Other
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz deriving (Show, Eq, Ord)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzdatatypeType :: IRI -> DatatypeType
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulzdatatypeType iri = case isDatatypeKey iri of
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz True
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | isOWLSmth [booleanS] iri -> OWL2Bool
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | isOWLSmth owlNumbers iri -> OWL2Number
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst Schulz | isOWLSmth [stringS] iri -> OWL2String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | otherwise -> Other
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz False -> Other
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulzdata DatatypeFacet =
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz LENGTH
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MINLENGTH
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MAXLENGTH
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | PATTERN
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MININCLUSIVE
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MINEXCLUSIVE
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MAXINCLUSIVE
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | MAXEXCLUSIVE
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz | TOTALDIGITS
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz | FRACTIONDIGITS
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz deriving (Show, Eq, Ord)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzshowFacet :: DatatypeFacet -> String
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst SchulzshowFacet df = case df of
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz LENGTH -> lengthS
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz MINLENGTH -> minLengthS
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz MAXLENGTH -> maxLengthS
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz PATTERN -> patternS
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz MININCLUSIVE -> lessEq
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz MINEXCLUSIVE -> lessS
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz MAXINCLUSIVE -> greaterEq
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz MAXEXCLUSIVE -> greaterS
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz TOTALDIGITS -> digitsS
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz FRACTIONDIGITS -> fractionS
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulzdata CardinalityType = MinCardinality | MaxCardinality | ExactCardinality
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz deriving (Show, Eq, Ord)
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzshowCardinalityType :: CardinalityType -> String
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzshowCardinalityType ty = case ty of
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz MinCardinality -> minS
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz MaxCardinality -> maxS
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz ExactCardinality -> exactlyS
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulzdata Cardinality a b = Cardinality CardinalityType Int a (Maybe b)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz deriving (Show, Eq, Ord)
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulzdata JunctionType = UnionOf | IntersectionOf
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz deriving (Show, Eq, Ord)
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulz
6b4cee497ea04900311e7d6cde162f8ec8fbb3f4Ewaryst Schulztype ConstrainingFacet = IRI
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulztype RestrictionValue = Literal
f5ae473759d00ab503cf52f323376dd2b1f87065Ewaryst Schulz
70e364e1d09840d15ae9298656b602b636fac811cmaeder-- * ENTITIES
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulzdata Entity = Entity EntityType IRI deriving (Show, Eq, Ord)
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
70e364e1d09840d15ae9298656b602b636fac811cmaederinstance GetRange Entity where
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz getRange (Entity _ iri) = iriPos iri
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
f5ae473759d00ab503cf52f323376dd2b1f87065Ewaryst Schulzdata EntityType =
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz Datatype
f5257648a040fda02fc27a28b1d17f6ba53307c5Christian Maeder | Class
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz | ObjectProperty
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz | DataProperty
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz | AnnotationProperty
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz | NamedIndividual
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz deriving (Enum, Bounded, Show, Read, Eq, Ord)
c1d06b3018b34ede2b3fb6c7fe2ad28cd5ce5b68Christian Maeder
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzshowEntityType :: EntityType -> String
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzshowEntityType e = case e of
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz Datatype -> datatypeC
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz Class -> classC
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz ObjectProperty -> objectPropertyC
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst Schulz DataProperty -> dataPropertyC
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz AnnotationProperty -> annotationPropertyC
e15d180842b94668f77df50ed61b261568b804aaEwaryst Schulz NamedIndividual -> individualC
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulzentityTypes :: [EntityType]
49c8d0af1a96cab75795d49b078b9163b666473fEwaryst SchulzentityTypes = [minBound .. maxBound]
b524978df6a89e40139f2862ad9eb6f9f5c8a1b5Ewaryst Schulz
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst SchulzcutIRI :: Entity -> IRI
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst SchulzcutIRI (Entity _ iri) = iri
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz-- * LITERALS
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
f5257648a040fda02fc27a28b1d17f6ba53307c5Christian Maederdata TypedOrUntyped = Typed Datatype | Untyped (Maybe LanguageTag)
6620aac969e8c5e41ef774956c58c083d37f3f56Ewaryst Schulz deriving (Show, Eq, Ord)
eca2369b114ede9e8590d38d353d88a924190f7dEwaryst Schulz
6620aac969e8c5e41ef774956c58c083d37f3f56Ewaryst Schulzdata Literal = Literal LexicalForm TypedOrUntyped | NumberLit FloatLit
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz deriving (Show, Eq, Ord)
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz-- | non-negative integers given by the sequence of digits
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulzdata NNInt = NNInt [Int] deriving (Eq, Ord)
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulzinstance Show NNInt where
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz show (NNInt l) = map intToDigit l
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzzeroNNInt :: NNInt
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzzeroNNInt = NNInt []
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst SchulzisZeroNNInt :: NNInt -> Bool
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzisZeroNNInt (NNInt l) = null l
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroederdata IntLit = IntLit
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz { absInt :: NNInt
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz , isNegInt :: Bool }
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz deriving (Eq, Ord)
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulzinstance Show IntLit where
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz show (IntLit n b) = (if b then ('-' :) else id) $ show n
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzzeroInt :: IntLit
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulzzeroInt = IntLit zeroNNInt False
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst Schulz
f58e5059e02c7e903059f3ec37bcb3b482afd63fEwaryst SchulzisZeroInt :: IntLit -> Bool
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulzisZeroInt (IntLit n _) = isZeroNNInt n
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulznegNNInt :: Bool -> NNInt -> IntLit
e15d180842b94668f77df50ed61b261568b804aaEwaryst SchulznegNNInt b n = IntLit n b
e15d180842b94668f77df50ed61b261568b804aaEwaryst Schulz
e15d180842b94668f77df50ed61b261568b804aaEwaryst SchulznegInt :: IntLit -> IntLit
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst SchulznegInt (IntLit n b) = IntLit n $ not b
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulzdata DecLit = DecLit
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz { truncDec :: IntLit
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz , fracDec :: NNInt }
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz deriving (Eq, Ord)
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulzinstance Show DecLit where
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz show (DecLit t f) = show t
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz ++ if isZeroNNInt f then "" else
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz '.' : show f
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisDecInt :: DecLit -> Bool
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisDecInt = isZeroNNInt . fracDec
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulznegDec :: Bool -> DecLit -> DecLit
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulznegDec b (DecLit t f) = DecLit (if b then negInt t else t) f
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata FloatLit = FloatLit
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz { floatBase :: DecLit
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz , floatExp :: IntLit }
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulz deriving (Eq, Ord)
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulzinstance Show FloatLit where
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz show (FloatLit b e) = show b
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulz ++ if isZeroInt e then "" else
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz 'E' : show e ++ "F"
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisFloatDec :: FloatLit -> Bool
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzisFloatDec = isZeroInt . floatExp
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisFloatInt :: FloatLit -> Bool
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisFloatInt f = isFloatDec f && isDecInt (floatBase f)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzfloatToInt :: FloatLit -> IntLit
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzfloatToInt = truncDec . floatBase
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzintToDec :: IntLit -> DecLit
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzintToDec i = DecLit i zeroNNInt
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzdecToFloat :: DecLit -> FloatLit
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzdecToFloat d = FloatLit d zeroInt
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzintToFloat :: IntLit -> FloatLit
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzintToFloat = decToFloat . intToDec
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzabInt :: IntLit -> IntLit
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst SchulzabInt int = int {isNegInt = False}
699f8456142e7c89bd15acf3aa8790fd02f4420dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzabDec :: DecLit -> DecLit
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzabDec dec = dec {truncDec = abInt $ truncDec dec}
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzabFloat :: FloatLit -> FloatLit
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzabFloat f = f {floatBase = abDec $ floatBase f}
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisNegDec :: DecLit -> Bool
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzisNegDec d = isNegInt $ truncDec d
cae4916b0844b837a4dd7e29730c56a3e26ef94dEwaryst Schulz
aae33d0d1a0f8174a7a704e2fdbb29482e0bf587Ewaryst SchulznumberName :: FloatLit -> String
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst SchulznumberName f
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulz | isFloatInt f = integerS
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | isFloatDec f = decimalS
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | otherwise = floatS
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzcTypeS :: String
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst SchulzcTypeS = "^^"
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz-- * PROPERTY EXPRESSIONS
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulztype InverseObjectProperty = ObjectPropertyExpression
32e0cbe45839af0ec675bcff62a34ca3709f5588Ewaryst Schulz
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulzdata ObjectPropertyExpression = ObjectProp ObjectProperty
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz | ObjectInverseOf InverseObjectProperty
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz deriving (Show, Eq, Ord)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulztype DataPropertyExpression = DataProperty
1a426f3cc3eedb6ed9736e9bde60c34273049137Ewaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz-- * DATA RANGES
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata DataRange =
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz DataType Datatype [(ConstrainingFacet, RestrictionValue)]
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | DataJunction JunctionType [DataRange]
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | DataComplementOf DataRange
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz | DataOneOf [Literal]
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz deriving (Show, Eq, Ord)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz-- * CLASS EXPERSSIONS
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata ClassExpression =
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst Schulz Expression Class
e15d180842b94668f77df50ed61b261568b804aaEwaryst Schulz | ObjectJunction JunctionType [ClassExpression]
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectComplementOf ClassExpression
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectOneOf [Individual]
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectValuesFrom QuantifierType ObjectPropertyExpression ClassExpression
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectHasValue ObjectPropertyExpression Individual
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectHasSelf ObjectPropertyExpression
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | ObjectCardinality (Cardinality ObjectPropertyExpression ClassExpression)
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | DataValuesFrom QuantifierType DataPropertyExpression DataRange
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | DataHasValue DataPropertyExpression Literal
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz | DataCardinality (Cardinality DataPropertyExpression DataRange)
938677803842b384a91fef21f58f86b8e3188b43Ewaryst Schulz deriving (Show, Eq, Ord)
3d3889e0cefcdce9b3f43c53aaa201943ac2e895Jonathan von Schroeder
df0d1a7e7dfff3be40c24b25318a6a07c748be20Ewaryst Schulz-- * ANNOTATIONS
f887ef77051188d95ceb8c37f39af91fc1195137Ewaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata Annotation = Annotation [Annotation] AnnotationProperty AnnotationValue
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz deriving (Show, Eq, Ord)
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulzdata AnnotationValue =
0850c3e5fb6285405ebaeb5aa433985203ac892dEwaryst Schulz AnnValue IRI
d1fddc394ac2af87a6210e7a3504bb565d088e7aEwaryst Schulz | AnnValLit Literal
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst Schulz deriving (Show, Eq, Ord)
e77f7260babdf86b287a632f9676c601bd0db077Ewaryst Schulz