AS.hs revision 668c9c725a11c0f77057152148570af853a1bc0d
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance{- |
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceModule : $Header$
5d801400993c9671010d244646936d8fd435638cChristian MaederCopyright : (c) C. Maeder
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceLicense : GPLv2 or higher, see LICENSE.txt
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceMaintainer : Christian.Maeder@dfki.de
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceStability : provisional
5d801400993c9671010d244646936d8fd435638cChristian MaederPortability : portable
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceCommon datatypes for the Functional and Manchester Syntaxes of OWL 2
aa0ca44e856c87db27e61687cbb630f270976da1Felix Gabriel Mance
5d801400993c9671010d244646936d8fd435638cChristian MaederReferences:
5d801400993c9671010d244646936d8fd435638cChristian Maeder <http://www.w3.org/TR/2009/REC-owl2-syntax-20091027/#Functional-Style_Syntax>
5d801400993c9671010d244646936d8fd435638cChristian Maeder <http://www.w3.org/TR/owl2-manchester-syntax/>
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-}
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancemodule OWL2.AS where
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maederimport Common.Keywords
dc8c83e9922e4746c192916565f3522418534f3aFelix Gabriel Manceimport Common.Id
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
feab1106bbee4f2ea2fd48bca7106dd041e4211dFelix Gabriel Manceimport OWL2.Keywords
18ff56829e5e99383ee6106584d55bcbd8ed45e7Felix Gabriel Manceimport OWL2.ColonKeywords
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mance
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maederimport Data.List
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Manceimport qualified Data.Map as Map
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata IRIType = Full | Abbreviated | NodeID
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mance deriving (Show, Eq, Ord)
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mance
668c9c725a11c0f77057152148570af853a1bc0dFelix 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 , iriType :: IRIType
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mance , expandedIRI :: String
0ec1551231bc5dfdcb3f2bd68fec7457fade7bfdFelix Gabriel Mance -- ^ the associated namespace uri (not printed)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance , iriPos :: Range
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder } deriving Show
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance GetRange QName where
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance getRange = iriPos
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQN :: QName -> String
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQN q = (if (iriType q /= Abbreviated) then showQI else showQU) q
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance-- | show QName as abbreviated iri
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQU :: QName -> String
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQU (QN pre local _ _ _) =
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maeder if null pre then local else pre ++ ":" ++ local
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maeder
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maeder-- | show QName in ankle brackets as full iris
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowQI :: QName -> String
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel ManceshowQI = ('<' :) . (++ ">") . showQU
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancenullQName :: QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancenullQName = QN "" "" Abbreviated "" nullRange
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedummyQName :: QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedummyQName =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance QN "http" "//www.dfki.de/sks/hets/ontology/unamed" Full "" nullRange
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName :: String -> QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName s = nullQName { localPart = s }
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel MancesetQRange :: Range -> QName -> QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancesetQRange r q = q { iriPos = r }
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaedersetPrefix :: String -> QName -> QName
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel MancesetPrefix s q = q { namePrefix = s }
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancesetFull :: QName -> QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancesetFull q = q {iriType = Full}
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaederisAnonymous :: IRI -> Bool
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaederisAnonymous iri =
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder let np = namePrefix iri
ea3f858eb531d981df3ed00beeadd99cf025adecChristian Maeder in (not . null) np && head np == '_'
ea3f858eb531d981df3ed00beeadd99cf025adecChristian Maeder
ea3f858eb531d981df3ed00beeadd99cf025adecChristian Maederinstance Eq QName where
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance p == q = compare p q == EQ
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Manceinstance Ord QName where
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance compare (QN p1 l1 b1 n1 _) (QN p2 l2 b2 n2 _) =
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance if null n1 || null n2 then compare (b1, p1, l1) (b2, p2, l2) else
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance compare n1 n2 -- compare fully expanded names only
75aaf82c430ad2a5cf159962b1c5c09255010fb4Felix Gabriel Mance
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel ManceisThing :: IRI -> Bool
75aaf82c430ad2a5cf159962b1c5c09255010fb4Felix Gabriel ManceisThing u = localPart u `elem` ["Thing", "Nothing"]
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance-- ^ checks if a string (bound to be localPart of an IRI) contains "://"
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel MancecssIRI :: String -> IRIType
1b1144abf7f95a4b23405b8d5604813cfe7b036aFelix Gabriel MancecssIRI iri = if isInfixOf "://" iri then Full else Abbreviated
4c684d7a2343be7350eba088f8be42888f86a495Felix Gabriel Mance
1b1144abf7f95a4b23405b8d5604813cfe7b036aFelix Gabriel Mancetype IRIreference = QName
e93f944968a75becbfb496994b85263b9cc1669fFrancisc Nicolae Bungiutype IRI = QName
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance
3c6b4f79cea11dd2acc2060bf1502b6ba9e905f2Felix Gabriel Mance-- | prefix -> localname
e93f944968a75becbfb496994b85263b9cc1669fFrancisc Nicolae Bungiutype PrefixMap = Map.Map String String
5a3ae0a9224276de25e709ef8788c1b9716cd206Christian Maeder
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mancetype LexicalForm = String
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mancetype LanguageTag = String
668c9c725a11c0f77057152148570af853a1bc0dFelix Gabriel Mancetype ImportIRI = IRI
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancetype OntologyIRI = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype Class = IRI
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancetype Datatype = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype ObjectProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype DataProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype AnnotationProperty = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype NamedIndividual = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype Individual = IRI
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype SourceIndividual = Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype TargetIndividual = Individual
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype TargetValue = Literal
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
9cb6af1a7632f12b60f592ce5eb2ac51e6bd33bbFelix Gabriel Mancedata EquivOrDisjoint = Equivalent | Disjoint
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
968930c7674ae3b63d308bf4fa651400aa263054Christian MaedershowEquivOrDisjoint :: EquivOrDisjoint -> String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceshowEquivOrDisjoint ed = case ed of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Equivalent -> equivalentToC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Disjoint -> disjointWithC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata DomainOrRange = ADomain | ARange deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowDomainOrRange :: DomainOrRange -> String
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowDomainOrRange dr = case dr of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance ADomain -> domainC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance ARange -> rangeC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata Relation =
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance EDRelation EquivOrDisjoint
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | SubPropertyOf
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | InverseOf
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | SubClass
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | Types
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | DRRelation DomainOrRange
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | SDRelation SameOrDifferent
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance deriving (Show, Eq, Ord)
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowRelation :: Relation -> String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowRelation r = case r of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance EDRelation ed -> showEquivOrDisjoint ed
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SubPropertyOf -> subPropertyOfC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance InverseOf -> inverseOfC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SubClass -> subClassOfC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Types -> typesC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance DRRelation dr -> showDomainOrRange dr
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SDRelation sd -> showSameOrDifferent sd
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder
a921ae1da1302f673204e7b63cdce01439a9bd5eFelix Gabriel MancegetDR :: Relation -> DomainOrRange
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancegetDR r = case r of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance DRRelation dr -> dr
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance _ -> error "not domain or range"
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancegetED :: Relation -> EquivOrDisjoint
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancegetED r = case r of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance EDRelation ed -> ed
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance _ -> error "not domain or range"
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancegetSD :: Relation -> SameOrDifferent
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancegetSD s = case s of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SDRelation sd -> sd
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance _ -> error "not same or different"
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mancedata DataDomainOrRange = DataDomain ClassExpression | DataRange DataRange
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance deriving (Show, Eq, Ord)
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mancedata Character =
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance Functional
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | InverseFunctional
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Reflexive
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Irreflexive
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Symmetric
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Asymmetric
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | Antisymmetric
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Transitive
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance deriving (Enum, Bounded, Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata SameOrDifferent = Same | Different deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowSameOrDifferent :: SameOrDifferent -> String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowSameOrDifferent sd = case sd of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Same -> sameAsC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Different -> differentFromC
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata PositiveOrNegative = Positive | Negative deriving (Show, Eq, Ord)
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mancedata QuantifierType = AllValuesFrom | SomeValuesFrom deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQuantifierType :: QuantifierType -> String
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel ManceshowQuantifierType ty = case ty of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance AllValuesFrom -> onlyS
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SomeValuesFrom -> someS
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance-- | data type strings (some are not listed in the grammar)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisDatatypeKey :: IRI -> Bool
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel ManceisDatatypeKey u =
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance elem (localPart u) datatypeKeys && elem (namePrefix u) ["", "xsd"]
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maeder
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maederdata DatatypeFacet =
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maeder LENGTH
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maeder | MINLENGTH
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | MAXLENGTH
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | PATTERN
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | MININCLUSIVE
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | MINEXCLUSIVE
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | MAXINCLUSIVE
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | MAXEXCLUSIVE
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | TOTALDIGITS
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance | FRACTIONDIGITS
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance deriving (Show, Eq, Ord)
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel ManceshowFacet :: DatatypeFacet -> String
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel ManceshowFacet df = case df of
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance LENGTH -> lengthS
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix Gabriel Mance MINLENGTH -> minLengthS
83f5f3291f9b40fa688776b4da10b5fa102a5ff8Felix 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
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata CardinalityType = MinCardinality | MaxCardinality | ExactCardinality
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
968930c7674ae3b63d308bf4fa651400aa263054Christian MaedershowCardinalityType :: 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 (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancedata JunctionType = UnionOf | IntersectionOf deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancetype ConstrainingFacet = IRI
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mancetype RestrictionValue = Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- * ENTITIES
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata Entity = Entity EntityType IRI deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Manceinstance GetRange Entity where
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance getRange (Entity _ iri) = iriPos iri
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata EntityType =
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance Datatype
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | Class
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | ObjectProperty
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | DataProperty
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | AnnotationProperty
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance | NamedIndividual
ffa6044b04fa0e31242141ff56a5d80c4233b676Felix Gabriel Mance deriving (Enum, Bounded, Show, Read, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceshowEntityType :: EntityType -> String
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceshowEntityType e = case e of
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance Datatype -> datatypeC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance Class -> classC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance ObjectProperty -> objectPropertyC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance DataProperty -> dataPropertyC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance AnnotationProperty -> annotationPropertyC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance NamedIndividual -> individualC
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceentityTypes :: [EntityType]
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceentityTypes = [minBound .. maxBound]
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance-- * LITERALS
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata TypedOrUntyped = Typed Datatype | Untyped (Maybe LanguageTag)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata Literal = Literal LexicalForm TypedOrUntyped
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel MancecTypeS :: String
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel MancecTypeS = "^^"
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance-- * PROPERTY EXPRESSIONS
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancetype InverseObjectProperty = ObjectPropertyExpression
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata ObjectPropertyExpression = ObjectProp ObjectProperty
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | ObjectInverseOf InverseObjectProperty
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype DataPropertyExpression = DataProperty
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance-- * DATA RANGES
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata DataRange
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder = DataType Datatype [(ConstrainingFacet, RestrictionValue)]
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | DataJunction JunctionType [DataRange]
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | DataComplementOf DataRange
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | DataOneOf [Literal]
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder deriving (Show, Eq, Ord)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder-- * CLASS EXPERSSIONS
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maederdata ClassExpression =
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder Expression Class
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectJunction JunctionType [ClassExpression]
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectComplementOf ClassExpression
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectOneOf [Individual]
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectValuesFrom QuantifierType ObjectPropertyExpression ClassExpression
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectHasValue ObjectPropertyExpression Individual
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectHasSelf ObjectPropertyExpression
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | ObjectCardinality (Cardinality ObjectPropertyExpression ClassExpression)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | DataValuesFrom QuantifierType
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder DataPropertyExpression DataRange
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | DataHasValue DataPropertyExpression Literal
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | DataCardinality (Cardinality DataPropertyExpression DataRange)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder deriving (Show, Eq, Ord)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder-- * ANNOTATIONS
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maederdata Annotation = Annotation [Annotation] AnnotationProperty AnnotationValue
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder deriving (Show, Eq, Ord)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maederdata AnnotationValue
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder = AnnValue IRI
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder | AnnValLit Literal
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder deriving (Show, Eq, Ord)
b1162cc13e8371724e3382ae6d1cfdeb43891fbbChristian Maeder