{-# LANGUAGE DeriveDataTypeable #-}
module OWL2.Profiles
( Profiles(..)
, bottomProfile
, topProfile
, allProfiles
, profileMax
, printProfile
, axiom
, ontologyProfiles
) where
import OWL2.AS
import Data.Data
import qualified Data.Set as Set
import Common.IRI(setPrefix, mkIRI)
data Profiles = Profiles
{ Profiles -> Bool
outsideEL :: Bool
, Profiles -> Bool
outsideQL :: Bool
, Profiles -> Bool
outsideRL :: Bool
} deriving (Int -> Profiles -> ShowS
[Profiles] -> ShowS
Profiles -> String
(Int -> Profiles -> ShowS)
-> (Profiles -> String) -> ([Profiles] -> ShowS) -> Show Profiles
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Profiles] -> ShowS
$cshowList :: [Profiles] -> ShowS
show :: Profiles -> String
$cshow :: Profiles -> String
showsPrec :: Int -> Profiles -> ShowS
$cshowsPrec :: Int -> Profiles -> ShowS
Show, Profiles -> Profiles -> Bool
(Profiles -> Profiles -> Bool)
-> (Profiles -> Profiles -> Bool) -> Eq Profiles
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Profiles -> Profiles -> Bool
$c/= :: Profiles -> Profiles -> Bool
== :: Profiles -> Profiles -> Bool
$c== :: Profiles -> Profiles -> Bool
Eq, Eq Profiles
Eq Profiles =>
(Profiles -> Profiles -> Ordering)
-> (Profiles -> Profiles -> Bool)
-> (Profiles -> Profiles -> Bool)
-> (Profiles -> Profiles -> Bool)
-> (Profiles -> Profiles -> Bool)
-> (Profiles -> Profiles -> Profiles)
-> (Profiles -> Profiles -> Profiles)
-> Ord Profiles
Profiles -> Profiles -> Bool
Profiles -> Profiles -> Ordering
Profiles -> Profiles -> Profiles
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Profiles -> Profiles -> Profiles
$cmin :: Profiles -> Profiles -> Profiles
max :: Profiles -> Profiles -> Profiles
$cmax :: Profiles -> Profiles -> Profiles
>= :: Profiles -> Profiles -> Bool
$c>= :: Profiles -> Profiles -> Bool
> :: Profiles -> Profiles -> Bool
$c> :: Profiles -> Profiles -> Bool
<= :: Profiles -> Profiles -> Bool
$c<= :: Profiles -> Profiles -> Bool
< :: Profiles -> Profiles -> Bool
$c< :: Profiles -> Profiles -> Bool
compare :: Profiles -> Profiles -> Ordering
$ccompare :: Profiles -> Profiles -> Ordering
$cp1Ord :: Eq Profiles
Ord, Typeable, Typeable Profiles
Constr
DataType
Typeable Profiles =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Profiles -> c Profiles)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Profiles)
-> (Profiles -> Constr)
-> (Profiles -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Profiles))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Profiles))
-> ((forall b. Data b => b -> b) -> Profiles -> Profiles)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r)
-> (forall u. (forall d. Data d => d -> u) -> Profiles -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Profiles -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles)
-> Data Profiles
Profiles -> Constr
Profiles -> DataType
(forall b. Data b => b -> b) -> Profiles -> Profiles
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Profiles -> c Profiles
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Profiles
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Profiles -> u
forall u. (forall d. Data d => d -> u) -> Profiles -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Profiles
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Profiles -> c Profiles
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Profiles)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Profiles)
$cProfiles :: Constr
$tProfiles :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Profiles -> m Profiles
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles
gmapMp :: (forall d. Data d => d -> m d) -> Profiles -> m Profiles
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles
gmapM :: (forall d. Data d => d -> m d) -> Profiles -> m Profiles
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Profiles -> m Profiles
gmapQi :: Int -> (forall d. Data d => d -> u) -> Profiles -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Profiles -> u
gmapQ :: (forall d. Data d => d -> u) -> Profiles -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Profiles -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Profiles -> r
gmapT :: (forall b. Data b => b -> b) -> Profiles -> Profiles
$cgmapT :: (forall b. Data b => b -> b) -> Profiles -> Profiles
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Profiles)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Profiles)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Profiles)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Profiles)
dataTypeOf :: Profiles -> DataType
$cdataTypeOf :: Profiles -> DataType
toConstr :: Profiles -> Constr
$ctoConstr :: Profiles -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Profiles
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Profiles
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Profiles -> c Profiles
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Profiles -> c Profiles
$cp1Data :: Typeable Profiles
Data)
allProfiles :: [[Profiles]]
allProfiles :: [[Profiles]]
allProfiles = [[Profiles
bottomProfile]
, [Profiles
elProfile, Profiles
qlProfile, Profiles
rlProfile]
, [Profiles
elqlProfile, Profiles
elrlProfile, Profiles
qlrlProfile]
, [Profiles
topProfile]]
bottomProfile :: Profiles
bottomProfile :: Profiles
bottomProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
False Bool
False Bool
False
topProfile :: Profiles
topProfile :: Profiles
topProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
True Bool
True Bool
True
elProfile :: Profiles
elProfile :: Profiles
elProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
False Bool
True Bool
True
qlProfile :: Profiles
qlProfile :: Profiles
qlProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
True Bool
False Bool
True
rlProfile :: Profiles
rlProfile :: Profiles
rlProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
True Bool
True Bool
False
elqlProfile :: Profiles
elqlProfile :: Profiles
elqlProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
False Bool
False Bool
True
elrlProfile :: Profiles
elrlProfile :: Profiles
elrlProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
False Bool
True Bool
False
qlrlProfile :: Profiles
qlrlProfile :: Profiles
qlrlProfile = Bool -> Bool -> Bool -> Profiles
Profiles Bool
True Bool
False Bool
False
printProfile :: Profiles -> String
printProfile :: Profiles -> String
printProfile p :: Profiles
p@(Profiles e :: Bool
e q :: Bool
q r :: Bool
r) = case Profiles
p of
(Profiles True True True) -> "NP"
_ -> (if Bool -> Bool
not Bool
e then "EL" else "")
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (if Bool -> Bool
not Bool
q then "QL" else "")
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (if Bool -> Bool
not Bool
r then "RL" else "")
profileMax :: [Profiles] -> Profiles
profileMax :: [Profiles] -> Profiles
profileMax pl :: [Profiles]
pl = Profiles :: Bool -> Bool -> Bool -> Profiles
Profiles
{ outsideEL :: Bool
outsideEL = (Profiles -> Bool) -> [Profiles] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Profiles -> Bool
outsideEL [Profiles]
pl
, outsideQL :: Bool
outsideQL = (Profiles -> Bool) -> [Profiles] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Profiles -> Bool
outsideQL [Profiles]
pl
, outsideRL :: Bool
outsideRL = (Profiles -> Bool) -> [Profiles] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Profiles -> Bool
outsideRL [Profiles]
pl }
profileMaxWith :: (a -> Profiles) -> [a] -> Profiles
profileMaxWith :: (a -> Profiles) -> [a] -> Profiles
profileMaxWith f :: a -> Profiles
f cel :: [a]
cel = [Profiles] -> Profiles
profileMax ((a -> Profiles) -> [a] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map a -> Profiles
f [a]
cel)
maximalCovering :: Profiles -> [Profiles] -> Profiles
maximalCovering :: Profiles -> [Profiles] -> Profiles
maximalCovering c :: Profiles
c pl :: [Profiles]
pl = [Profiles] -> Profiles
profileMax [Profiles
c, [Profiles] -> Profiles
profileMax [Profiles]
pl]
owlELQLForbiddenDatatypes :: Set.Set Datatype
owlELQLForbiddenDatatypes :: Set Datatype
owlELQLForbiddenDatatypes = [Datatype] -> Set Datatype
forall a. Ord a => [a] -> Set a
Set.fromList ([Datatype] -> Set Datatype)
-> ([String] -> [Datatype]) -> [String] -> Set Datatype
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Datatype) -> [String] -> [Datatype]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Datatype -> Datatype
setPrefix "xsd" (Datatype -> Datatype)
-> (String -> Datatype) -> String -> Datatype
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Datatype
mkIRI) ([String] -> Set Datatype) -> [String] -> Set Datatype
forall a b. (a -> b) -> a -> b
$
[ "double", "float", "nonPositiveInteger", "positiveInteger"
, "negativeInteger", "long", "int", "short", "byte", "unsignedLong"
, "unsignedInt", "unsignedShort", "unsignedByte", "language", "boolean"]
datatype :: Datatype -> Profiles
datatype :: Datatype -> Profiles
datatype dt :: Datatype
dt = if Datatype
dt Datatype -> Set Datatype -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Datatype
owlELQLForbiddenDatatypes then Profiles
rlProfile else Profiles
bottomProfile
literal :: Literal -> Profiles
literal :: Literal -> Profiles
literal l :: Literal
l = case Literal
l of
Literal _ (Typed dt :: Datatype
dt) -> Datatype -> Profiles
datatype Datatype
dt
NumberLit f :: FloatLit
f -> Datatype -> Profiles
datatype (Datatype -> Profiles)
-> (FloatLit -> Datatype) -> FloatLit -> Profiles
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Datatype -> Datatype
setPrefix "xsd" (Datatype -> Datatype)
-> (FloatLit -> Datatype) -> FloatLit -> Datatype
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Datatype
mkIRI (String -> Datatype)
-> (FloatLit -> String) -> FloatLit -> Datatype
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FloatLit -> String
numberName (FloatLit -> Profiles) -> FloatLit -> Profiles
forall a b. (a -> b) -> a -> b
$ FloatLit
f
_ -> Profiles
bottomProfile
individual :: Individual -> Profiles
individual :: Datatype -> Profiles
individual i :: Datatype
i = if Datatype -> Bool
isAnonymous Datatype
i then Profiles
rlProfile else Profiles
bottomProfile
objProp :: ObjectPropertyExpression -> Profiles
objProp :: ObjectPropertyExpression -> Profiles
objProp ope :: ObjectPropertyExpression
ope = case ObjectPropertyExpression
ope of
ObjectInverseOf _ -> Profiles
qlrlProfile
_ -> Profiles
bottomProfile
dataRange :: DataRange -> Profiles
dataRange :: DataRange -> Profiles
dataRange dr :: DataRange
dr = case DataRange
dr of
DataType dt :: Datatype
dt cfl :: [(Datatype, Literal)]
cfl ->
if [(Datatype, Literal)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Datatype, Literal)]
cfl then Datatype -> Profiles
datatype Datatype
dt
else Profiles
topProfile
DataJunction IntersectionOf drl :: [DataRange]
drl -> [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (DataRange -> Profiles) -> [DataRange] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map DataRange -> Profiles
dataRange [DataRange]
drl
DataOneOf ll :: [Literal]
ll -> Profiles
topProfile {
outsideEL :: Bool
outsideEL = [Literal] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Literal]
ll Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 1 Bool -> Bool -> Bool
|| Profiles -> Bool
outsideEL ((Literal -> Profiles) -> [Literal] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Literal -> Profiles
literal [Literal]
ll)
}
_ -> Profiles
topProfile
subClass :: ClassExpression -> Profiles
subClass :: ClassExpression -> Profiles
subClass cex :: ClassExpression
cex = case ClassExpression
cex of
Expression c :: Datatype
c -> if Datatype -> Bool
isThing Datatype
c then Profiles
elqlProfile else Profiles
bottomProfile
ObjectJunction jt :: JunctionType
jt cel :: [ClassExpression]
cel -> Profiles -> [Profiles] -> Profiles
maximalCovering (case JunctionType
jt of
IntersectionOf -> Profiles
elrlProfile
UnionOf -> Profiles
rlProfile) ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (ClassExpression -> Profiles) -> [ClassExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ClassExpression -> Profiles
subClass [ClassExpression]
cel
ObjectOneOf il :: [Datatype]
il -> Profiles
bottomProfile {
outsideEL :: Bool
outsideEL = [Datatype] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Datatype]
il Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 1 Bool -> Bool -> Bool
|| Profiles -> Bool
outsideEL ((Datatype -> Profiles) -> [Datatype] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Datatype -> Profiles
individual [Datatype]
il),
outsideRL :: Bool
outsideRL = Profiles -> Bool
outsideRL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ (Datatype -> Profiles) -> [Datatype] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Datatype -> Profiles
individual [Datatype]
il
}
ObjectValuesFrom SomeValuesFrom ope :: ObjectPropertyExpression
ope ce :: ClassExpression
ce -> [Profiles] -> Profiles
profileMax [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope,
case ClassExpression
ce of
Expression c :: Datatype
c -> if Datatype -> Bool
isThing Datatype
c then Profiles
bottomProfile
else Profiles
elrlProfile
_ -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile [ClassExpression -> Profiles
subClass ClassExpression
ce]]
ObjectHasValue ope :: ObjectPropertyExpression
ope i :: Datatype
i -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile
[ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope, Datatype -> Profiles
individual Datatype
i]
ObjectHasSelf ope :: ObjectPropertyExpression
ope -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope]
DataValuesFrom SomeValuesFrom _ dr :: DataRange
dr -> DataRange -> Profiles
dataRange DataRange
dr
DataHasValue _ l :: Literal
l -> Literal -> Profiles
literal Literal
l
_ -> Profiles
bottomProfile
superClass :: ClassExpression -> Profiles
superClass :: ClassExpression -> Profiles
superClass cex :: ClassExpression
cex = case ClassExpression
cex of
Expression c :: Datatype
c -> if Datatype -> Bool
isThing Datatype
c then Profiles
elqlProfile else Profiles
bottomProfile
ObjectJunction IntersectionOf cel :: [ClassExpression]
cel -> (ClassExpression -> Profiles) -> [ClassExpression] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith ClassExpression -> Profiles
superClass [ClassExpression]
cel
ObjectComplementOf ce :: ClassExpression
ce -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile [ClassExpression -> Profiles
subClass ClassExpression
ce]
ObjectOneOf il :: [Datatype]
il -> Profiles
bottomProfile {
outsideEL :: Bool
outsideEL = [Datatype] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Datatype]
il Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 1 Bool -> Bool -> Bool
|| Profiles -> Bool
outsideEL ((Datatype -> Profiles) -> [Datatype] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Datatype -> Profiles
individual [Datatype]
il),
outsideRL :: Bool
outsideRL = Profiles -> Bool
outsideRL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ (Datatype -> Profiles) -> [Datatype] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Datatype -> Profiles
individual [Datatype]
il
}
ObjectValuesFrom qt :: QuantifierType
qt ope :: ObjectPropertyExpression
ope ce :: ClassExpression
ce -> case QuantifierType
qt of
SomeValuesFrom -> [Profiles] -> Profiles
profileMax [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope, case ClassExpression
ce of
Expression _ -> Profiles
elqlProfile
_ -> Profiles
elProfile]
AllValuesFrom -> [Profiles] -> Profiles
profileMax [ClassExpression -> Profiles
superClass ClassExpression
ce, Profiles
rlProfile]
ObjectHasValue ope :: ObjectPropertyExpression
ope i :: Datatype
i -> [Profiles] -> Profiles
profileMax [Profiles
elrlProfile, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope,
Datatype -> Profiles
individual Datatype
i]
ObjectHasSelf ope :: ObjectPropertyExpression
ope -> [Profiles] -> Profiles
profileMax [Profiles
elProfile, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
ope]
ObjectCardinality (Cardinality MaxCardinality i :: Int
i _ mce :: Maybe ClassExpression
mce) ->
if Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Int
i [0, 1] then [Profiles] -> Profiles
profileMax [Profiles
rlProfile, case Maybe ClassExpression
mce of
Nothing -> Profiles
bottomProfile
Just ce :: ClassExpression
ce -> case ClassExpression
ce of
Expression _ -> Profiles
bottomProfile
_ -> ClassExpression -> Profiles
subClass ClassExpression
ce]
else Profiles
bottomProfile
DataValuesFrom qt :: QuantifierType
qt _ dr :: DataRange
dr -> [Profiles] -> Profiles
profileMax [DataRange -> Profiles
dataRange DataRange
dr, case QuantifierType
qt of
SomeValuesFrom -> Profiles
elqlProfile
AllValuesFrom -> Profiles
rlProfile]
DataHasValue _ l :: Literal
l -> [Profiles] -> Profiles
profileMax [Profiles
elrlProfile, Literal -> Profiles
literal Literal
l]
DataCardinality (Cardinality MaxCardinality i :: Int
i _ mdr :: Maybe DataRange
mdr) ->
if Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Int
i [0, 1] then [Profiles] -> Profiles
profileMax [Profiles
rlProfile, case Maybe DataRange
mdr of
Nothing -> Profiles
topProfile
Just dr :: DataRange
dr -> DataRange -> Profiles
dataRange DataRange
dr]
else Profiles
bottomProfile
_ -> Profiles
bottomProfile
equivClassRL :: ClassExpression -> Bool
equivClassRL :: ClassExpression -> Bool
equivClassRL cex :: ClassExpression
cex = case ClassExpression
cex of
Expression c :: Datatype
c -> (Bool -> Bool
not (Bool -> Bool) -> (Datatype -> Bool) -> Datatype -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Datatype -> Bool
isThing) Datatype
c
ObjectJunction IntersectionOf cel :: [ClassExpression]
cel -> (ClassExpression -> Bool) -> [ClassExpression] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ClassExpression -> Bool
equivClassRL [ClassExpression]
cel
ObjectHasValue _ i :: Datatype
i -> Profiles -> Bool
outsideRL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ Datatype -> Profiles
individual Datatype
i
DataHasValue _ l :: Literal
l -> Profiles -> Bool
outsideRL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ Literal -> Profiles
literal Literal
l
_ -> Bool
False
annotation :: Annotation -> Profiles
annotation :: Annotation -> Profiles
annotation (Annotation as :: [Annotation]
as _ av :: AnnotationValue
av) = [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
as, case AnnotationValue
av of
AnnValLit l :: Literal
l -> Literal -> Profiles
literal Literal
l
_ -> Profiles
topProfile]
annotations :: [Annotation] -> Profiles
annotations :: [Annotation] -> Profiles
annotations = [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles)
-> ([Annotation] -> [Profiles]) -> [Annotation] -> Profiles
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Annotation -> Profiles) -> [Annotation] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map Annotation -> Profiles
annotation
classAxiomClassExpressions :: [Annotation] -> [ClassExpression] -> Profiles
classAxiomClassExpressions :: [Annotation] -> [ClassExpression] -> Profiles
classAxiomClassExpressions anns :: [Annotation]
anns clExprs :: [ClassExpression]
clExprs = [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, Profiles
bottomProfile {
outsideEL :: Bool
outsideEL = Profiles -> Bool
outsideEL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ (ClassExpression -> Profiles) -> [ClassExpression] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith ClassExpression -> Profiles
subClass ([ClassExpression] -> Profiles) -> [ClassExpression] -> Profiles
forall a b. (a -> b) -> a -> b
$ [ClassExpression]
clExprs,
outsideQL :: Bool
outsideQL = Profiles -> Bool
outsideQL (Profiles -> Bool) -> Profiles -> Bool
forall a b. (a -> b) -> a -> b
$ (ClassExpression -> Profiles) -> [ClassExpression] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith ClassExpression -> Profiles
subClass ([ClassExpression] -> Profiles) -> [ClassExpression] -> Profiles
forall a b. (a -> b) -> a -> b
$ [ClassExpression]
clExprs,
outsideRL :: Bool
outsideRL = (ClassExpression -> Bool) -> [ClassExpression] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ClassExpression -> Bool
equivClassRL ([ClassExpression] -> Bool) -> [ClassExpression] -> Bool
forall a b. (a -> b) -> a -> b
$ [ClassExpression]
clExprs
}]
axiom :: Axiom -> Profiles
axiom :: Axiom -> Profiles
axiom ax :: Axiom
ax = case Axiom
ax of
Declaration _ _ -> Profiles
bottomProfile
ClassAxiom cax :: ClassAxiom
cax -> case ClassAxiom
cax of
SubClassOf anns :: [Annotation]
anns sub :: ClassExpression
sub sup :: ClassExpression
sup -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, ClassExpression -> Profiles
subClass ClassExpression
sub, ClassExpression -> Profiles
superClass ClassExpression
sup]
EquivalentClasses anns :: [Annotation]
anns cExprs :: [ClassExpression]
cExprs -> [Annotation] -> [ClassExpression] -> Profiles
classAxiomClassExpressions [Annotation]
anns [ClassExpression]
cExprs
DisjointClasses anns :: [Annotation]
anns cExprs :: [ClassExpression]
cExprs -> [Annotation] -> [ClassExpression] -> Profiles
classAxiomClassExpressions [Annotation]
anns [ClassExpression]
cExprs
DisjointUnion anns :: [Annotation]
anns c :: Datatype
c cExprs :: [ClassExpression]
cExprs -> [Annotation] -> [ClassExpression] -> Profiles
classAxiomClassExpressions [Annotation]
anns (Datatype -> ClassExpression
Expression Datatype
c ClassExpression -> [ClassExpression] -> [ClassExpression]
forall a. a -> [a] -> [a]
: [ClassExpression]
cExprs)
ObjectPropertyAxiom opax :: ObjectPropertyAxiom
opax -> case ObjectPropertyAxiom
opax of
SubObjectPropertyOf anns :: [Annotation]
anns subOpExpr :: SubObjectPropertyExpression
subOpExpr supOpExpr :: ObjectPropertyExpression
supOpExpr -> case SubObjectPropertyExpression
subOpExpr of
SubObjPropExpr_obj oExpr :: ObjectPropertyExpression
oExpr ->
[Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp [ObjectPropertyExpression
oExpr, ObjectPropertyExpression
supOpExpr]]
SubObjPropExpr_exprchain oExprs :: [ObjectPropertyExpression]
oExprs ->
Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile [[Annotation] -> Profiles
annotations [Annotation]
anns, [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp (ObjectPropertyExpression
supOpExpr ObjectPropertyExpression
-> [ObjectPropertyExpression] -> [ObjectPropertyExpression]
forall a. a -> [a] -> [a]
: [ObjectPropertyExpression]
oExprs)]
EquivalentObjectProperties anns :: [Annotation]
anns oExprs :: [ObjectPropertyExpression]
oExprs -> Profiles -> [Profiles] -> Profiles
maximalCovering ([Annotation] -> Profiles
annotations [Annotation]
anns) ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp [ObjectPropertyExpression]
oExprs
DisjointObjectProperties anns :: [Annotation]
anns oExprs :: [ObjectPropertyExpression]
oExprs -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ ([Annotation] -> Profiles
annotations [Annotation]
anns) Profiles -> [Profiles] -> [Profiles]
forall a. a -> [a] -> [a]
: (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp [ObjectPropertyExpression]
oExprs
InverseObjectProperties anns :: [Annotation]
anns o1 :: ObjectPropertyExpression
o1 o2 :: ObjectPropertyExpression
o2 -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ ([Annotation] -> Profiles
annotations [Annotation]
anns) Profiles -> [Profiles] -> [Profiles]
forall a. a -> [a] -> [a]
: (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp [ObjectPropertyExpression
o1, ObjectPropertyExpression
o2]
ObjectPropertyDomain anns :: [Annotation]
anns oe :: ObjectPropertyExpression
oe ce :: ClassExpression
ce -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe, ClassExpression -> Profiles
superClass ClassExpression
ce]
ObjectPropertyRange anns :: [Annotation]
anns oe :: ObjectPropertyExpression
oe ce :: ClassExpression
ce -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe, ClassExpression -> Profiles
superClass ClassExpression
ce]
FunctionalObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
rlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
InverseFunctionalObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
rlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
ReflexiveObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elqlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
IrreflexiveObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
SymmetricObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
AsymmetricObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
TransitiveObjectProperty _ oe :: ObjectPropertyExpression
oe -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile [ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oe]
DataPropertyAxiom a :: DataPropertyAxiom
a -> case DataPropertyAxiom
a of
SubDataPropertyOf anns :: [Annotation]
anns _ _ -> [Annotation] -> Profiles
annotations [Annotation]
anns
EquivalentDataProperties anns :: [Annotation]
anns _ -> [Annotation] -> Profiles
annotations [Annotation]
anns
DisjointDataProperties anns :: [Annotation]
anns _ -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
qlrlProfile [[Annotation] -> Profiles
annotations [Annotation]
anns]
DataPropertyDomain anns :: [Annotation]
anns _ classExpr :: ClassExpression
classExpr -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, ClassExpression -> Profiles
superClass ClassExpression
classExpr]
DataPropertyRange anns :: [Annotation]
anns _ dr :: DataRange
dr -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, DataRange -> Profiles
dataRange DataRange
dr]
FunctionalDataProperty anns :: [Annotation]
anns _ -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile [[Annotation] -> Profiles
annotations [Annotation]
anns]
DatatypeDefinition anns :: [Annotation]
anns dt :: Datatype
dt dr :: DataRange
dr -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, Datatype -> Profiles
datatype Datatype
dt, DataRange -> Profiles
dataRange DataRange
dr]
HasKey anns :: [Annotation]
anns classExpr :: ClassExpression
classExpr oExprs :: [ObjectPropertyExpression]
oExprs _ -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile
[[Annotation] -> Profiles
annotations [Annotation]
anns, ClassExpression -> Profiles
subClass ClassExpression
classExpr, [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (ObjectPropertyExpression -> Profiles)
-> [ObjectPropertyExpression] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map ObjectPropertyExpression -> Profiles
objProp [ObjectPropertyExpression]
oExprs]
Assertion a :: Assertion
a -> case Assertion
a of
SameIndividual anns :: [Annotation]
anns inds :: [Datatype]
inds -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile
[[Annotation] -> Profiles
annotations [Annotation]
anns, [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (Datatype -> Profiles) -> [Datatype] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map Datatype -> Profiles
individual [Datatype]
inds]
DifferentIndividuals anns :: [Annotation]
anns inds :: [Datatype]
inds -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile
[[Annotation] -> Profiles
annotations [Annotation]
anns, [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$ (Datatype -> Profiles) -> [Datatype] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map Datatype -> Profiles
individual [Datatype]
inds]
ClassAssertion anns :: [Annotation]
anns ce :: ClassExpression
ce ind :: Datatype
ind -> [Profiles] -> Profiles
profileMax [[Annotation] -> Profiles
annotations [Annotation]
anns, ClassExpression -> Profiles
subClass ClassExpression
ce, Datatype -> Profiles
individual Datatype
ind]
ObjectPropertyAssertion anns :: [Annotation]
anns oExpr :: ObjectPropertyExpression
oExpr i1 :: Datatype
i1 i2 :: Datatype
i2 -> [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$
[[Annotation] -> Profiles
annotations [Annotation]
anns, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oExpr] [Profiles] -> [Profiles] -> [Profiles]
forall a. [a] -> [a] -> [a]
++ (Datatype -> Profiles) -> [Datatype] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map Datatype -> Profiles
individual [Datatype
i1, Datatype
i2]
NegativeObjectPropertyAssertion anns :: [Annotation]
anns oExpr :: ObjectPropertyExpression
oExpr i1 :: Datatype
i1 i2 :: Datatype
i2 -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$
[[Annotation] -> Profiles
annotations [Annotation]
anns, ObjectPropertyExpression -> Profiles
objProp ObjectPropertyExpression
oExpr] [Profiles] -> [Profiles] -> [Profiles]
forall a. [a] -> [a] -> [a]
++ (Datatype -> Profiles) -> [Datatype] -> [Profiles]
forall a b. (a -> b) -> [a] -> [b]
map Datatype -> Profiles
individual [Datatype
i1, Datatype
i2]
DataPropertyAssertion anns :: [Annotation]
anns _ ind :: Datatype
ind lit :: Literal
lit -> [Profiles] -> Profiles
profileMax ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$
[[Annotation] -> Profiles
annotations [Annotation]
anns, Datatype -> Profiles
individual Datatype
ind, Literal -> Profiles
literal Literal
lit]
NegativeDataPropertyAssertion anns :: [Annotation]
anns _ ind :: Datatype
ind lit :: Literal
lit -> Profiles -> [Profiles] -> Profiles
maximalCovering Profiles
elrlProfile ([Profiles] -> Profiles) -> [Profiles] -> Profiles
forall a b. (a -> b) -> a -> b
$
[[Annotation] -> Profiles
annotations [Annotation]
anns, Datatype -> Profiles
individual Datatype
ind, Literal -> Profiles
literal Literal
lit]
AnnotationAxiom a :: AnnotationAxiom
a -> case AnnotationAxiom
a of
AnnotationAssertion anns :: [Annotation]
anns prop :: Datatype
prop _ val :: AnnotationValue
val -> Annotation -> Profiles
annotation (Annotation -> Profiles) -> Annotation -> Profiles
forall a b. (a -> b) -> a -> b
$ [Annotation] -> Datatype -> AnnotationValue -> Annotation
Annotation [Annotation]
anns Datatype
prop AnnotationValue
val
SubAnnotationPropertyOf anns :: [Annotation]
anns _ _ -> [Annotation] -> Profiles
annotations [Annotation]
anns
AnnotationPropertyDomain anns :: [Annotation]
anns _ _ -> [Annotation] -> Profiles
annotations [Annotation]
anns
AnnotationPropertyRange anns :: [Annotation]
anns _ _ -> [Annotation] -> Profiles
annotations [Annotation]
anns
Rule _ -> Profiles
topProfile
DGAxiom _ _ _ _ _ -> Profiles
topProfile
ontologyP :: Ontology -> Profiles
ontologyP :: Ontology -> Profiles
ontologyP ont :: Ontology
ont =
let anns :: [Annotation]
anns = Ontology -> [Annotation]
ontologyAnnotation Ontology
ont
ax :: [Axiom]
ax = Ontology -> [Axiom]
axioms Ontology
ont
in [Profiles] -> Profiles
profileMax [(Axiom -> Profiles) -> [Axiom] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Axiom -> Profiles
axiom [Axiom]
ax, (Annotation -> Profiles) -> [Annotation] -> Profiles
forall a. (a -> Profiles) -> [a] -> Profiles
profileMaxWith Annotation -> Profiles
annotation [Annotation]
anns]
ontologyProfiles :: OntologyDocument -> Profiles
ontologyProfiles :: OntologyDocument -> Profiles
ontologyProfiles odoc :: OntologyDocument
odoc = Ontology -> Profiles
ontologyP (Ontology -> Profiles) -> Ontology -> Profiles
forall a b. (a -> b) -> a -> b
$ OntologyDocument -> Ontology
ontology OntologyDocument
odoc