1a38107941725211e7c3f051f7a8f5e12199f03acmaeder{-# LANGUAGE DeriveDataTypeable #-}
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance{- |
e9458b1a7a19a63aa4c179f9ab20f4d50681c168Jens ElknerModule : ./OWL2/Profiles.hs
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel ManceCopyright : (c) Felix Gabriel Mance
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel ManceLicense : GPLv2 or higher, see LICENSE.txt
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel ManceMaintainer : f.mance@jacobs-university.de
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel ManceStability : provisional
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel MancePortability : portable
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
51d64c2e160c971ea2ae1d4f1ddffe6a0a3b8f64Felix Gabriel ManceOWL2 Profiles (EL, QL and RL)
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel ManceReferences : <http://www.w3.org/TR/owl2-profiles/>
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance-}
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mancemodule OWL2.Profiles where
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Manceimport OWL2.AS
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Manceimport OWL2.MS
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
1a38107941725211e7c3f051f7a8f5e12199f03acmaederimport Data.Data
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Manceimport Data.Maybe
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mancedata Profiles = Profiles
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance { el :: Bool
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance , ql :: Bool
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance , rl :: Bool
1a38107941725211e7c3f051f7a8f5e12199f03acmaeder } deriving (Show, Eq, Ord, Typeable, Data)
808e2693447ecc5a311a2b9de6b81ca07f193778Felix Gabriel Mance
544bd831b3a3434899db4008bbe131beafd07c4dChristian MaederallProfiles :: [[Profiles]]
544bd831b3a3434899db4008bbe131beafd07c4dChristian MaederallProfiles =
cc57307d0ddc488f43de34aea793f05408d9e53aChristian Maeder [[qlrlProfile], [elrlProfile], [elqlProfile]]
e0c2bc4ba02902c20dae5c2e7a9bc25dbcfdfa49Christian Maeder
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancebottomProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancebottomProfile = Profiles False False False
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancetopProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancetopProfile = Profiles True True True
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelProfile = Profiles True False False
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceqlProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceqlProfile = Profiles False True False
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancerlProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancerlProfile = Profiles False False True
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelqlProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelqlProfile = Profiles True True False
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelrlProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceelrlProfile = Profiles True False True
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceqlrlProfile :: Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceqlrlProfile = Profiles False True True
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel ManceprintProfile :: Profiles -> String
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel ManceprintProfile p@(Profiles e q r) = case p of
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel Mance (Profiles False False False) -> "NP"
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel Mance _ -> (if e then "EL" else "")
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel Mance ++ (if q then "QL" else "")
551caf6791c20ff4ca928f93c520b85648693958Felix Gabriel Mance ++ (if r then "RL" else "")
45e34c7696f9dd6163686ff6798b33a126590fa2Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceandProfileList :: [Profiles] -> Profiles
cc57307d0ddc488f43de34aea793f05408d9e53aChristian MaederandProfileList pl = topProfile
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance { el = all el pl
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance , ql = all ql pl
27fdf879983dd28e211b41f3be6c0e930b7c816bFelix Gabriel Mance , rl = all rl pl }
808e2693447ecc5a311a2b9de6b81ca07f193778Felix Gabriel Mance
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel ManceandList :: (a -> Profiles) -> [a] -> Profiles
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel ManceandList f cel = andProfileList (map f cel)
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceminimalCovering :: Profiles -> [Profiles] -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceminimalCovering c pl = andProfileList [c, andProfileList pl]
808e2693447ecc5a311a2b9de6b81ca07f193778Felix Gabriel Mance
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel MancedataType :: Datatype -> Profiles
fc05327b875b5723b6c17849b83477f29ec12c90Felix Gabriel MancedataType _ = topProfile -- needs to be implemented, of course
4440f5c4ab1cb6dfd445da97f87a72d87d24c25aFelix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceliteral :: Literal -> Profiles
fc05327b875b5723b6c17849b83477f29ec12c90Felix Gabriel Manceliteral _ = topProfile -- needs to be implemented
808e2693447ecc5a311a2b9de6b81ca07f193778Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceindividual :: Individual -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceindividual i = if isAnonymous i then rlProfile else topProfile
c92573b85930868b709024284c0f13dbcaec9554Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceobjProp :: ObjectPropertyExpression -> Profiles
c92573b85930868b709024284c0f13dbcaec9554Felix Gabriel ManceobjProp ope = case ope of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectInverseOf _ -> qlrlProfile
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel Mance _ -> topProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancedataRange :: DataRange -> Profiles
ae2e84ab0a53874417f01b792cbc6907ee6d09f6Felix Gabriel MancedataRange dr = case dr of
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance DataType dt cfl ->
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance if null cfl then dataType dt
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance else bottomProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance DataJunction IntersectionOf drl -> andProfileList $ map dataRange drl
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance DataOneOf ll -> bottomProfile {
ee87c7423bf599b4f29e9b31945e00482a8b31caFelix Gabriel Mance el = el (andList literal ll) && length ll == 1
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance }
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance _ -> bottomProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancesubClass :: ClassExpression -> Profiles
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel MancesubClass cex = case cex of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression c -> if isThing c then elqlProfile else topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectJunction jt cel -> minimalCovering (case jt of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance IntersectionOf -> elrlProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance UnionOf -> rlProfile) $ map subClass cel
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance ObjectOneOf il -> bottomProfile {
ee87c7423bf599b4f29e9b31945e00482a8b31caFelix Gabriel Mance el = el (andList individual il) && length il == 1,
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance rl = ql $ andList individual il
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance }
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance ObjectValuesFrom SomeValuesFrom ope ce -> andProfileList [objProp ope,
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance case ce of
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance Expression c -> if isThing c then topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance else elrlProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance _ -> minimalCovering elrlProfile [subClass ce]]
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance ObjectHasValue ope i -> minimalCovering elrlProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance [objProp ope, individual i]
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance ObjectHasSelf ope -> minimalCovering elProfile [objProp ope]
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance DataValuesFrom SomeValuesFrom _ dr -> dataRange dr
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance DataHasValue _ l -> literal l
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance _ -> bottomProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancesuperClass :: ClassExpression -> Profiles
e615997caa046409fc68114cd72e10a528a4bb71Felix Gabriel MancesuperClass cex = case cex of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression c -> if isThing c then elqlProfile else topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectJunction IntersectionOf cel -> andList superClass cel
e615997caa046409fc68114cd72e10a528a4bb71Felix Gabriel Mance ObjectComplementOf ce -> minimalCovering qlrlProfile [subClass ce]
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance ObjectOneOf il -> bottomProfile {
ee87c7423bf599b4f29e9b31945e00482a8b31caFelix Gabriel Mance el = el (andList individual il) && length il == 1,
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance rl = ql $ andList individual il
31f536d7b9e901779ab6de28d804f53d5eb4b908Felix Gabriel Mance }
e615997caa046409fc68114cd72e10a528a4bb71Felix Gabriel Mance ObjectValuesFrom qt ope ce -> case qt of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SomeValuesFrom -> andProfileList [objProp ope, case ce of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression _ -> elqlProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> elProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance AllValuesFrom -> andProfileList [superClass ce, rlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectHasValue ope i -> andProfileList [elrlProfile, objProp ope,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance individual i]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectHasSelf ope -> andProfileList [elProfile, objProp ope]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectCardinality (Cardinality MaxCardinality i _ mce) ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance if elem i [0, 1] then andProfileList [rlProfile, case mce of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Nothing -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Just ce -> case ce of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression _ -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> subClass ce]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance else bottomProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataValuesFrom qt _ dr -> andProfileList [dataRange dr, case qt of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SomeValuesFrom -> elqlProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance AllValuesFrom -> rlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataHasValue _ l -> andProfileList [elrlProfile, literal l]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataCardinality (Cardinality MaxCardinality i _ mdr) ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance if elem i [0, 1] then andProfileList [rlProfile, case mdr of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Nothing -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Just dr -> dataRange dr]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance else bottomProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> bottomProfile
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceequivClassRL :: ClassExpression -> Bool
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceequivClassRL cex = case cex of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression c -> (not . isThing) c
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectJunction IntersectionOf cel -> all equivClassRL cel
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectHasValue _ i -> rl $ individual i
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataHasValue _ l -> rl $ literal l
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> False
ce5d83770556362fe2c8b567975c2a3758888358Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceannotation :: Annotation -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceannotation (Annotation as _ av) = andProfileList [annotations as, case av of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance AnnValLit l -> literal l
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> topProfile]
4440f5c4ab1cb6dfd445da97f87a72d87d24c25aFelix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceannotations :: Annotations -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Manceannotations ans = andProfileList $ map annotation ans
e615997caa046409fc68114cd72e10a528a4bb71Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceassertionQL :: ClassExpression -> Bool
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel ManceassertionQL ce = case ce of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Expression _ -> True
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance _ -> False
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mancechar :: [Character] -> [Character] -> Bool
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mancechar charList ls = all (`elem` ls) charList
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mancefact :: Fact -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mancefact f = case f of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectPropertyFact pn ope i -> andProfileList [objProp ope, individual i,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance case pn of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Positive -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Negative -> elrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataPropertyFact pn _ l -> andProfileList [literal l,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance case pn of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Positive -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Negative -> elrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancelFB :: Extended -> Maybe Relation -> ListFrameBit -> Profiles
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel MancelFB ext mr lfb = case lfb of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance AnnotationBit anl -> annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ExpressionBit anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance cel = map snd anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance r = fromMaybe (error "relation needed") mr
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in case ext of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Misc anno -> andProfileList [ans, annotations anno,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance bottomProfile {
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance el = el $ andList subClass cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ql = ql $ andList subClass cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance rl = all equivClassRL cel
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance }]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ClassEntity c -> case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SubClass -> andProfileList [ans, subClass c,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance andList superClass cel]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> andProfileList [ans, bottomProfile {
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance el = el $ andList subClass $ c : cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ql = ql $ andList subClass $ c : cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance rl = all equivClassRL $ c : cel
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance }]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectEntity op -> andProfileList [ans, objProp op,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance andList superClass cel]
7852de3551fc797566ee71165bafe05b6d81728cnotanartist SimpleEntity (Entity _ ty ent) -> case ty of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataProperty -> andProfileList [ans, andList superClass cel]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance NamedIndividual -> andProfileList [ans, individual ent,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance bottomProfile {
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance el = el $ andList superClass cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ql = all assertionQL cel,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance rl = rl $ andList superClass cel
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance }]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> error "invalid expression bit"
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectBit anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance opl = andList objProp $ map snd anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance r = fromMaybe (error "relation needed") mr
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in case ext of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Misc anno -> andProfileList [ans, annotations anno, opl, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance EDRelation Equivalent -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> qlrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectEntity op -> andProfileList [ans, opl, objProp op, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SubPropertyOf -> topProfile
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance EDRelation Equivalent -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> qlrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> error "invalit object bit"
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataBit anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance r = fromMaybe (error "relation needed") mr
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in case ext of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Misc anno -> andProfileList [ans, annotations anno, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance EDRelation Equivalent -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> qlrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> andProfileList [ans, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SubPropertyOf -> topProfile
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance EDRelation Equivalent -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> qlrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance IndividualSameOrDifferent anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance r = fromMaybe (error "relation needed") mr
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance i = andList individual $ map snd anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in case ext of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Misc anno -> andProfileList [ans, annotations anno, i, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SDRelation Different -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> elrlProfile]
7852de3551fc797566ee71165bafe05b6d81728cnotanartist SimpleEntity (Entity _ _ ind) -> andProfileList [ans, individual ind,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance i, case r of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance SDRelation Different -> topProfile
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> elrlProfile]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> error "bad individual bit"
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectCharacteristics anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance cl = map snd anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in case ext of
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ObjectEntity op -> andProfileList [ans, objProp op,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance bottomProfile {
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance el = char cl [Reflexive, Transitive],
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance ql = char cl [Reflexive, Symmetric, Asymmetric],
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance rl = char cl [Functional, InverseFunctional,
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance Irreflexive, Symmetric, Asymmetric, Transitive]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance }]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance _ -> error "object entity needed"
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance DataPropRange anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance dr = andList dataRange $ map snd anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance in andProfileList [ans, dr]
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance IndividualFacts anl ->
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance let ans = annotations $ concatMap fst anl
28b76e08d15cd924bb672449613c410a33361b6eFelix Gabriel Mance facts = andList fact $ map snd anl
fae04f4a69922eb1ddf0f46b34fa15a5a080b693Felix Gabriel Mance in case ext of
7852de3551fc797566ee71165bafe05b6d81728cnotanartist SimpleEntity (Entity _ _ i) ->
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance andProfileList [ans, facts, individual i]
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance _ -> error "bad fact bit"
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel ManceaFB :: Extended -> Annotations -> AnnFrameBit -> Profiles
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel ManceaFB ext anno afb =
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance let ans = annotations anno
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance in case afb of
d9afc6f8ffafb5297b4cdf5d3c97efba3d24b7faFelix Gabriel Mance AnnotationFrameBit _ -> ans
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance DataFunctional -> andProfileList [ans, elrlProfile]
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance DatatypeBit dr -> case ext of
7852de3551fc797566ee71165bafe05b6d81728cnotanartist SimpleEntity (Entity _ _ dt) -> andProfileList
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance [ans, dataType dt, dataRange dr]
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance _ -> error "bad datatype bit"
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ClassDisjointUnion _ -> bottomProfile
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ClassHasKey opl _ -> case ext of
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ClassEntity ce -> minimalCovering elrlProfile
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance [ans, andList objProp opl, subClass ce]
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance _ -> error "bad has key"
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ObjectSubPropertyChain opl -> case ext of
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ObjectEntity op -> minimalCovering elrlProfile
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance [ans, andList objProp $ op : opl]
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance _ -> error "bad sub property chain"
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel MancefB :: Extended -> FrameBit -> Profiles
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel MancefB ext fb = case fb of
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance ListFrameBit mr lfb -> lFB ext mr lfb
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance AnnFrameBit anno afb -> aFB ext anno afb
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Manceaxiom :: Axiom -> Profiles
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Manceaxiom (PlainAxiom ext fb) = fB ext fb
a57de3f6b0a0c904523910869eedc7428e5e17a3Felix Gabriel Mance
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Manceframe :: Frame -> Profiles
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Manceframe (Frame ext fbl) = andList (fB ext) fbl
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel ManceontologyP :: Ontology -> Profiles
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel ManceontologyP ont =
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance let anns = ann ont
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance fr = ontFrames ont
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance in andProfileList [andList frame fr, andList annotations anns]
61c1a9c658ddc79ef33b01c14ee8cf5039430dd8Felix Gabriel Mance
58231c02ba63cd573b7d523e938acdb0798983c4Felix Gabriel ManceontologyProfiles :: OntologyDocument -> Profiles
58231c02ba63cd573b7d523e938acdb0798983c4Felix Gabriel ManceontologyProfiles odoc = ontologyP $ ontology odoc