AS.hs revision e99c3c1f572d0442872bba58f187ca520ef5d040
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
5d801400993c9671010d244646936d8fd435638cChristian MaederCommon 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
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport Common.Keywords
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maederimport Common.Id
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
feab1106bbee4f2ea2fd48bca7106dd041e4211dFelix Gabriel Manceimport OWL2.Keywords
feab1106bbee4f2ea2fd48bca7106dd041e4211dFelix Gabriel Manceimport OWL2.ColonKeywords
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceimport qualified Data.Map as Map
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
0ec1551231bc5dfdcb3f2bd68fec7457fade7bfdFelix Gabriel Mance , expandedIRI :: String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance -- ^ the associated namespace uri (not printed)
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder , iriPos :: Range
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder } deriving Show
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maederinstance GetRange QName where
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maeder getRange = iriPos
fc7bd98aabe1bc26058660085e8c77d60a97bcecChristian Maeder
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
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaedershowQU (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
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaedernullQName = QN "" "" False "" nullRange
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancedummyQName :: QName
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaederdummyQName =
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder QN "http" "//www.dfki.de/sks/hets/ontology/unamed" True "" nullRange
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName :: String -> QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel MancemkQName s = nullQName { localPart = s }
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaedersetQRange :: Range -> QName -> QName
852bd6145634dc2832b61c44678fe539bc1682d5Christian MaedersetQRange r q = q { iriPos = r }
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder
ea3f858eb531d981df3ed00beeadd99cf025adecChristian MaedersetPrefix :: String -> QName -> QName
ea3f858eb531d981df3ed00beeadd99cf025adecChristian MaedersetPrefix s q = q { namePrefix = s }
ea3f858eb531d981df3ed00beeadd99cf025adecChristian Maeder
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance Eq QName where
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance p == q = compare p q == EQ
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Manceinstance Ord QName where
852bd6145634dc2832b61c44678fe539bc1682d5Christian Maeder compare (QN p1 l1 b1 n1 _) (QN p2 l2 b2 n2 _) = case (n1, n2) of
806e8e0fe1a46ce1523c0d7804f1c193321f7981Christian Maeder ("", "") -> compare (b1, p1, l1) (b2, p2, l2)
806e8e0fe1a46ce1523c0d7804f1c193321f7981Christian Maeder ("", _) -> LT
806e8e0fe1a46ce1523c0d7804f1c193321f7981Christian Maeder (_, "") -> GT
806e8e0fe1a46ce1523c0d7804f1c193321f7981Christian Maeder _ -> compare n1 n2 -- compare fully expanded names only
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype IRIreference = QName
dd3c105fcc30b5d6b750d8fbe32250207b996109Felix Gabriel Mancetype IRI = QName
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance-- | prefix -> localname
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype PrefixMap = Map.Map String String
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype LexicalForm = String
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancetype LanguageTag = 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
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype SourceIndividual = Individual
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype TargetIndividual = Individual
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype TargetValue = Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata EquivOrDisjoint = Equivalent | Disjoint
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowEquivOrDisjoint :: EquivOrDisjoint -> String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowDomainOrRange :: DomainOrRange -> String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | InverseOf
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | SubClass
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Types
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | DRRelation DomainOrRange
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | SDRelation SameOrDifferent
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder deriving (Show, Eq, Ord)
a921ae1da1302f673204e7b63cdce01439a9bd5eFelix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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"
c298a419605037f5352b5ad0f67b3e06db094051Felix 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"
097bc9f18b722812d480df0f5c634d09cbca8e21Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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"
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata DataDomainOrRange = DataDomain ClassExpression | DataRange DataRange
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata Character =
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance Functional
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | InverseFunctional
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Reflexive
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Irreflexive
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Symmetric
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | Asymmetric
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix 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)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata QuantifierType = AllValuesFrom | SomeValuesFrom deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowQuantifierType :: QuantifierType -> String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel ManceshowQuantifierType ty = case ty of
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance AllValuesFrom -> onlyS
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance SomeValuesFrom -> someS
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
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian MaederisDatatypeKey :: IRI -> Bool
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian MaederisDatatypeKey u =
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maeder elem (localPart u) datatypeKeys && elem (namePrefix u) ["", "xsd"]
44985cbd4eb61dbc348617ebdd44a774e51dac07Christian Maeder
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
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder deriving (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
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata CardinalityType = MinCardinality | MaxCardinality | ExactCardinality
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceshowCardinalityType :: CardinalityType -> String
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel ManceshowCardinalityType ty = case ty of
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance MinCardinality -> minS
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance MaxCardinality -> maxS
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance ExactCardinality -> exactlyS
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata Cardinality a b = Cardinality CardinalityType Int a (Maybe b)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancedata JunctionType = UnionOf | IntersectionOf deriving (Show, Eq, Ord)
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancetype ConstrainingFacet = IRI
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mancetype RestrictionValue = Literal
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix 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
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | NamedIndividual
e99c3c1f572d0442872bba58f187ca520ef5d040Felix 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
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance-- * LITERALS
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata TypedOrUntyped = Typed Datatype | Untyped (Maybe LanguageTag)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata Literal = Literal LexicalForm TypedOrUntyped
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancecTypeS :: String
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel MancecTypeS = "^^"
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance-- * PROPERTY EXPRESSIONS
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype InverseObjectProperty = ObjectPropertyExpression
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancedata ObjectPropertyExpression = ObjectProp ObjectProperty
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | ObjectInverseOf InverseObjectProperty
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance deriving (Show, Eq, Ord)
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mancetype DataPropertyExpression = DataProperty
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance-- * DATA RANGES
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance
962c83276bc80dd04f4a83e47eb81524d5294a4fChristian Maederdata DataRange
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance = DataType Datatype [(ConstrainingFacet, RestrictionValue)]
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | DataJunction JunctionType [DataRange]
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | DataComplementOf DataRange
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | DataOneOf [Literal]
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance-- * CLASS EXPERSSIONS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata ClassExpression =
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance Expression Class
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | ObjectJunction JunctionType [ClassExpression]
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | ObjectComplementOf ClassExpression
e99c3c1f572d0442872bba58f187ca520ef5d040Felix Gabriel Mance | ObjectOneOf [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)
ba2c0d8be230f0b274cf3e0013e3844a80d9afd4Christian Maeder | DataValuesFrom QuantifierType
a6526952d69bccd048c954eb920493a6a83e78faFelix Gabriel Mance DataPropertyExpression DataRange
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance | DataHasValue DataPropertyExpression Literal
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance | DataCardinality (Cardinality DataPropertyExpression DataRange)
968930c7674ae3b63d308bf4fa651400aa263054Christian Maeder deriving (Show, Eq, Ord)
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
1435782fda52a2898ea74e99088351d4f5b450dcChristian Maeder-- * ANNOTATIONS
c298a419605037f5352b5ad0f67b3e06db094051Felix Gabriel Mance
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mancedata Annotation = Annotation [Annotation] AnnotationProperty AnnotationValue
1435782fda52a2898ea74e99088351d4f5b450dcChristian Maeder deriving (Show, Eq, Ord)
8af00c8930672188ae80c8829428859160d329d0Felix Gabriel Mance
962c83276bc80dd04f4a83e47eb81524d5294a4fChristian Maederdata AnnotationValue
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance = AnnValue IRI
c77c0efe19dc6556ac872828bfb4cfc5fbca5ac5Felix Gabriel Mance | AnnValLit Literal
5d801400993c9671010d244646936d8fd435638cChristian Maeder deriving (Show, Eq, Ord)