Hets - the Heterogeneous Tool Set
Copyright(c) C. Maeder Felix Gabriel Mance
LicenseGPLv2 or higher, see LICENSE.txt
MaintainerAlexander.Koslowski@st.ovgu.de
Stabilityprovisional
Portabilityportable
Safe HaskellSafe

OWL2.AS

Description

Synopsis

Documentation

isAnonymous :: IRI -> Bool Source #

checks if an IRI is an anonymous individual

type PrefixMap = Map String String Source #

prefix -> localname

type LexicalForm = String Source #

type LanguageTag = String Source #

type Class = IRI Source #

data EquivOrDisjoint Source #

Constructors

Equivalent 
Disjoint 

Instances

Instances details
Eq EquivOrDisjoint Source # 
Instance details

Defined in OWL2.AS

Data EquivOrDisjoint Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EquivOrDisjoint -> c EquivOrDisjoint

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EquivOrDisjoint

toConstr :: EquivOrDisjoint -> Constr

dataTypeOf :: EquivOrDisjoint -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EquivOrDisjoint)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EquivOrDisjoint)

gmapT :: (forall b. Data b => b -> b) -> EquivOrDisjoint -> EquivOrDisjoint

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EquivOrDisjoint -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EquivOrDisjoint -> r

gmapQ :: (forall d. Data d => d -> u) -> EquivOrDisjoint -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> EquivOrDisjoint -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EquivOrDisjoint -> m EquivOrDisjoint

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EquivOrDisjoint -> m EquivOrDisjoint

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EquivOrDisjoint -> m EquivOrDisjoint

Ord EquivOrDisjoint Source # 
Instance details

Defined in OWL2.AS

Show EquivOrDisjoint Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> EquivOrDisjoint -> ShowS

show :: EquivOrDisjoint -> String

showList :: [EquivOrDisjoint] -> ShowS

Generic EquivOrDisjoint 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep EquivOrDisjoint :: Type -> Type

FromJSON EquivOrDisjoint 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser EquivOrDisjoint

parseJSONList :: Value -> Parser [EquivOrDisjoint]

ToJSON EquivOrDisjoint 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: EquivOrDisjoint -> Value

toEncoding :: EquivOrDisjoint -> Encoding

toJSONList :: [EquivOrDisjoint] -> Value

toEncodingList :: [EquivOrDisjoint] -> Encoding

ShATermConvertible EquivOrDisjoint 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> EquivOrDisjoint -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [EquivOrDisjoint] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, EquivOrDisjoint)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [EquivOrDisjoint])

type Rep EquivOrDisjoint 
Instance details

Defined in OWL2.ATC_OWL2

type Rep EquivOrDisjoint = D1 ('MetaData "EquivOrDisjoint" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Equivalent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Disjoint" 'PrefixI 'False) (U1 :: Type -> Type))

data DomainOrRange Source #

Constructors

ADomain 
ARange 

Instances

Instances details
Eq DomainOrRange Source # 
Instance details

Defined in OWL2.AS

Data DomainOrRange Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DomainOrRange -> c DomainOrRange

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DomainOrRange

toConstr :: DomainOrRange -> Constr

dataTypeOf :: DomainOrRange -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DomainOrRange)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DomainOrRange)

gmapT :: (forall b. Data b => b -> b) -> DomainOrRange -> DomainOrRange

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DomainOrRange -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DomainOrRange -> r

gmapQ :: (forall d. Data d => d -> u) -> DomainOrRange -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DomainOrRange -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DomainOrRange -> m DomainOrRange

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainOrRange -> m DomainOrRange

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DomainOrRange -> m DomainOrRange

Ord DomainOrRange Source # 
Instance details

Defined in OWL2.AS

Show DomainOrRange Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DomainOrRange -> ShowS

show :: DomainOrRange -> String

showList :: [DomainOrRange] -> ShowS

Generic DomainOrRange 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DomainOrRange :: Type -> Type

FromJSON DomainOrRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DomainOrRange

parseJSONList :: Value -> Parser [DomainOrRange]

ToJSON DomainOrRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DomainOrRange -> Value

toEncoding :: DomainOrRange -> Encoding

toJSONList :: [DomainOrRange] -> Value

toEncodingList :: [DomainOrRange] -> Encoding

ShATermConvertible DomainOrRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DomainOrRange -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DomainOrRange] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DomainOrRange)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DomainOrRange])

type Rep DomainOrRange 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DomainOrRange = D1 ('MetaData "DomainOrRange" "OWL2.AS" "main" 'False) (C1 ('MetaCons "ADomain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARange" 'PrefixI 'False) (U1 :: Type -> Type))

data SameOrDifferent Source #

Constructors

Same 
Different 

Instances

Instances details
Eq SameOrDifferent Source # 
Instance details

Defined in OWL2.AS

Data SameOrDifferent Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SameOrDifferent -> c SameOrDifferent

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SameOrDifferent

toConstr :: SameOrDifferent -> Constr

dataTypeOf :: SameOrDifferent -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SameOrDifferent)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SameOrDifferent)

gmapT :: (forall b. Data b => b -> b) -> SameOrDifferent -> SameOrDifferent

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SameOrDifferent -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SameOrDifferent -> r

gmapQ :: (forall d. Data d => d -> u) -> SameOrDifferent -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SameOrDifferent -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SameOrDifferent -> m SameOrDifferent

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SameOrDifferent -> m SameOrDifferent

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SameOrDifferent -> m SameOrDifferent

Ord SameOrDifferent Source # 
Instance details

Defined in OWL2.AS

Show SameOrDifferent Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> SameOrDifferent -> ShowS

show :: SameOrDifferent -> String

showList :: [SameOrDifferent] -> ShowS

Generic SameOrDifferent 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep SameOrDifferent :: Type -> Type

FromJSON SameOrDifferent 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser SameOrDifferent

parseJSONList :: Value -> Parser [SameOrDifferent]

ToJSON SameOrDifferent 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: SameOrDifferent -> Value

toEncoding :: SameOrDifferent -> Encoding

toJSONList :: [SameOrDifferent] -> Value

toEncodingList :: [SameOrDifferent] -> Encoding

ShATermConvertible SameOrDifferent 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> SameOrDifferent -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [SameOrDifferent] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, SameOrDifferent)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [SameOrDifferent])

type Rep SameOrDifferent 
Instance details

Defined in OWL2.ATC_OWL2

type Rep SameOrDifferent = D1 ('MetaData "SameOrDifferent" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Same" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Different" 'PrefixI 'False) (U1 :: Type -> Type))

data Relation Source #

Instances

Instances details
Eq Relation Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Relation -> Relation -> Bool

(/=) :: Relation -> Relation -> Bool

Data Relation Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relation -> c Relation

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relation

toConstr :: Relation -> Constr

dataTypeOf :: Relation -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Relation)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relation)

gmapT :: (forall b. Data b => b -> b) -> Relation -> Relation

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relation -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relation -> r

gmapQ :: (forall d. Data d => d -> u) -> Relation -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Relation -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Relation -> m Relation

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Relation -> m Relation

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Relation -> m Relation

Ord Relation Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Relation -> Relation -> Ordering

(<) :: Relation -> Relation -> Bool

(<=) :: Relation -> Relation -> Bool

(>) :: Relation -> Relation -> Bool

(>=) :: Relation -> Relation -> Bool

max :: Relation -> Relation -> Relation

min :: Relation -> Relation -> Relation

Show Relation Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Relation -> ShowS

show :: Relation -> String

showList :: [Relation] -> ShowS

Generic Relation 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Relation :: Type -> Type

Methods

from :: Relation -> Rep Relation x

to :: Rep Relation x -> Relation

FromJSON Relation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Relation

parseJSONList :: Value -> Parser [Relation]

ToJSON Relation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Relation -> Value

toEncoding :: Relation -> Encoding

toJSONList :: [Relation] -> Value

toEncodingList :: [Relation] -> Encoding

ShATermConvertible Relation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Relation -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Relation] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Relation)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Relation])

type Rep Relation 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Relation = D1 ('MetaData "Relation" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "EDRelation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EquivOrDisjoint)) :+: (C1 ('MetaCons "SubPropertyOf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InverseOf" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SubClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Types" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DRRelation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomainOrRange)) :+: C1 ('MetaCons "SDRelation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SameOrDifferent)))))

data Character Source #

Instances

Instances details
Bounded Character Source # 
Instance details

Defined in OWL2.AS

Enum Character Source # 
Instance details

Defined in OWL2.AS

Eq Character Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Character -> Character -> Bool

(/=) :: Character -> Character -> Bool

Data Character Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Character -> c Character

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Character

toConstr :: Character -> Constr

dataTypeOf :: Character -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Character)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Character)

gmapT :: (forall b. Data b => b -> b) -> Character -> Character

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Character -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Character -> r

gmapQ :: (forall d. Data d => d -> u) -> Character -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Character -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Character -> m Character

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Character -> m Character

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Character -> m Character

Ord Character Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Character -> Character -> Ordering

(<) :: Character -> Character -> Bool

(<=) :: Character -> Character -> Bool

(>) :: Character -> Character -> Bool

(>=) :: Character -> Character -> Bool

max :: Character -> Character -> Character

min :: Character -> Character -> Character

Show Character Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Character -> ShowS

show :: Character -> String

showList :: [Character] -> ShowS

Generic Character 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Character :: Type -> Type

Methods

from :: Character -> Rep Character x

to :: Rep Character x -> Character

FromJSON Character 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Character

parseJSONList :: Value -> Parser [Character]

ToJSON Character 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Character -> Value

toEncoding :: Character -> Encoding

toJSONList :: [Character] -> Value

toEncodingList :: [Character] -> Encoding

ShATermConvertible Character 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Character -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Character] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Character)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Character])

Pretty Character Source # 
Instance details

Defined in OWL2.Print

type Rep Character 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Character = D1 ('MetaData "Character" "OWL2.AS" "main" 'False) (((C1 ('MetaCons "Functional" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InverseFunctional" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Reflexive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Irreflexive" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Symmetric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Asymmetric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Antisymmetric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Transitive" 'PrefixI 'False) (U1 :: Type -> Type))))

data PositiveOrNegative Source #

Constructors

Positive 
Negative 

Instances

Instances details
Eq PositiveOrNegative Source # 
Instance details

Defined in OWL2.AS

Data PositiveOrNegative Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PositiveOrNegative -> c PositiveOrNegative

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PositiveOrNegative

toConstr :: PositiveOrNegative -> Constr

dataTypeOf :: PositiveOrNegative -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PositiveOrNegative)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PositiveOrNegative)

gmapT :: (forall b. Data b => b -> b) -> PositiveOrNegative -> PositiveOrNegative

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PositiveOrNegative -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PositiveOrNegative -> r

gmapQ :: (forall d. Data d => d -> u) -> PositiveOrNegative -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PositiveOrNegative -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PositiveOrNegative -> m PositiveOrNegative

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PositiveOrNegative -> m PositiveOrNegative

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PositiveOrNegative -> m PositiveOrNegative

Ord PositiveOrNegative Source # 
Instance details

Defined in OWL2.AS

Show PositiveOrNegative Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> PositiveOrNegative -> ShowS

show :: PositiveOrNegative -> String

showList :: [PositiveOrNegative] -> ShowS

Generic PositiveOrNegative 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep PositiveOrNegative :: Type -> Type

FromJSON PositiveOrNegative 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser PositiveOrNegative

parseJSONList :: Value -> Parser [PositiveOrNegative]

ToJSON PositiveOrNegative 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible PositiveOrNegative 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> PositiveOrNegative -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [PositiveOrNegative] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, PositiveOrNegative)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [PositiveOrNegative])

type Rep PositiveOrNegative 
Instance details

Defined in OWL2.ATC_OWL2

type Rep PositiveOrNegative = D1 ('MetaData "PositiveOrNegative" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Positive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Negative" 'PrefixI 'False) (U1 :: Type -> Type))

data QuantifierType Source #

Instances

Instances details
Eq QuantifierType Source # 
Instance details

Defined in OWL2.AS

Data QuantifierType Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuantifierType -> c QuantifierType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuantifierType

toConstr :: QuantifierType -> Constr

dataTypeOf :: QuantifierType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuantifierType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuantifierType)

gmapT :: (forall b. Data b => b -> b) -> QuantifierType -> QuantifierType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuantifierType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuantifierType -> r

gmapQ :: (forall d. Data d => d -> u) -> QuantifierType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> QuantifierType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuantifierType -> m QuantifierType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuantifierType -> m QuantifierType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuantifierType -> m QuantifierType

Ord QuantifierType Source # 
Instance details

Defined in OWL2.AS

Show QuantifierType Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> QuantifierType -> ShowS

show :: QuantifierType -> String

showList :: [QuantifierType] -> ShowS

Generic QuantifierType 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep QuantifierType :: Type -> Type

FromJSON QuantifierType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser QuantifierType

parseJSONList :: Value -> Parser [QuantifierType]

ToJSON QuantifierType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: QuantifierType -> Value

toEncoding :: QuantifierType -> Encoding

toJSONList :: [QuantifierType] -> Value

toEncodingList :: [QuantifierType] -> Encoding

ShATermConvertible QuantifierType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> QuantifierType -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [QuantifierType] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, QuantifierType)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [QuantifierType])

type Rep QuantifierType 
Instance details

Defined in OWL2.ATC_OWL2

type Rep QuantifierType = D1 ('MetaData "QuantifierType" "OWL2.AS" "main" 'False) (C1 ('MetaCons "AllValuesFrom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SomeValuesFrom" 'PrefixI 'False) (U1 :: Type -> Type))

Predefined IRI checkings

isThing :: IRI -> Bool Source #

isDatatypeKeyAux :: IRI -> [(String, String)] Source #

type PreDefMaps = ([String], String, String) Source #

preDefMaps :: [String] -> String -> PreDefMaps Source #

checkPredefAux :: PreDefMaps -> IRI -> Maybe (String, String) Source #

setDatatypePrefix :: IRI -> IRI Source #

sets the correct prefix for the predefined datatypes

setReservedPrefix :: IRI -> IRI Source #

checks if the IRI is part of the built-in ones and puts the correct prefix

uriToId :: IRI -> Id Source #

Extracts Id from IRI returns the name of the predefined IRI (e.g xsd:string returns "string" or http://www.w3.org/2002/07/owl#real returns "real")

getPredefName :: IRI -> String Source #

uriToTok :: IRI -> Token Source #

Extracts Token from IRI

entityToId :: Entity -> Id Source #

Extracts Id from Entities

printDatatype :: IRI -> String Source #

data DatatypeCat Source #

Instances

Instances details
Eq DatatypeCat Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: DatatypeCat -> DatatypeCat -> Bool

(/=) :: DatatypeCat -> DatatypeCat -> Bool

Data DatatypeCat Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatatypeCat -> c DatatypeCat

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatatypeCat

toConstr :: DatatypeCat -> Constr

dataTypeOf :: DatatypeCat -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DatatypeCat)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatatypeCat)

gmapT :: (forall b. Data b => b -> b) -> DatatypeCat -> DatatypeCat

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeCat -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeCat -> r

gmapQ :: (forall d. Data d => d -> u) -> DatatypeCat -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeCat -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatatypeCat -> m DatatypeCat

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeCat -> m DatatypeCat

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeCat -> m DatatypeCat

Ord DatatypeCat Source # 
Instance details

Defined in OWL2.AS

Show DatatypeCat Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DatatypeCat -> ShowS

show :: DatatypeCat -> String

showList :: [DatatypeCat] -> ShowS

Generic DatatypeCat 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DatatypeCat :: Type -> Type

Methods

from :: DatatypeCat -> Rep DatatypeCat x

to :: Rep DatatypeCat x -> DatatypeCat

FromJSON DatatypeCat 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DatatypeCat

parseJSONList :: Value -> Parser [DatatypeCat]

ToJSON DatatypeCat 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DatatypeCat -> Value

toEncoding :: DatatypeCat -> Encoding

toJSONList :: [DatatypeCat] -> Value

toEncodingList :: [DatatypeCat] -> Encoding

ShATermConvertible DatatypeCat 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DatatypeCat -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DatatypeCat] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DatatypeCat)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DatatypeCat])

type Rep DatatypeCat 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DatatypeCat = D1 ('MetaData "DatatypeCat" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "OWL2Number" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OWL2String" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OWL2Bool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (U1 :: Type -> Type)))

makeXsdMap :: [String] -> PreDefMaps Source #

Extracting Symbols

Cardinalities

data CardinalityType Source #

Instances

Instances details
Eq CardinalityType Source # 
Instance details

Defined in OWL2.AS

Data CardinalityType Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CardinalityType -> c CardinalityType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CardinalityType

toConstr :: CardinalityType -> Constr

dataTypeOf :: CardinalityType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CardinalityType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CardinalityType)

gmapT :: (forall b. Data b => b -> b) -> CardinalityType -> CardinalityType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CardinalityType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CardinalityType -> r

gmapQ :: (forall d. Data d => d -> u) -> CardinalityType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CardinalityType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CardinalityType -> m CardinalityType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CardinalityType -> m CardinalityType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CardinalityType -> m CardinalityType

Ord CardinalityType Source # 
Instance details

Defined in OWL2.AS

Show CardinalityType Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> CardinalityType -> ShowS

show :: CardinalityType -> String

showList :: [CardinalityType] -> ShowS

Generic CardinalityType 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep CardinalityType :: Type -> Type

FromJSON CardinalityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser CardinalityType

parseJSONList :: Value -> Parser [CardinalityType]

ToJSON CardinalityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: CardinalityType -> Value

toEncoding :: CardinalityType -> Encoding

toJSONList :: [CardinalityType] -> Value

toEncodingList :: [CardinalityType] -> Encoding

ShATermConvertible CardinalityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> CardinalityType -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [CardinalityType] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, CardinalityType)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [CardinalityType])

type Rep CardinalityType 
Instance details

Defined in OWL2.ATC_OWL2

type Rep CardinalityType = D1 ('MetaData "CardinalityType" "OWL2.AS" "main" 'False) (C1 ('MetaCons "MinCardinality" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MaxCardinality" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExactCardinality" 'PrefixI 'False) (U1 :: Type -> Type)))

data Cardinality a b Source #

Constructors

Cardinality CardinalityType Int a (Maybe b) 

Instances

Instances details
(Eq a, Eq b) => Eq (Cardinality a b) Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Cardinality a b -> Cardinality a b -> Bool

(/=) :: Cardinality a b -> Cardinality a b -> Bool

(Data a, Data b) => Data (Cardinality a b) Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Cardinality a b -> c (Cardinality a b)

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Cardinality a b)

toConstr :: Cardinality a b -> Constr

dataTypeOf :: Cardinality a b -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Cardinality a b))

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Cardinality a b))

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Cardinality a b -> Cardinality a b

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cardinality a b -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cardinality a b -> r

gmapQ :: (forall d. Data d => d -> u) -> Cardinality a b -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cardinality a b -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cardinality a b -> m (Cardinality a b)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cardinality a b -> m (Cardinality a b)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cardinality a b -> m (Cardinality a b)

(Ord a, Ord b) => Ord (Cardinality a b) Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Cardinality a b -> Cardinality a b -> Ordering

(<) :: Cardinality a b -> Cardinality a b -> Bool

(<=) :: Cardinality a b -> Cardinality a b -> Bool

(>) :: Cardinality a b -> Cardinality a b -> Bool

(>=) :: Cardinality a b -> Cardinality a b -> Bool

max :: Cardinality a b -> Cardinality a b -> Cardinality a b

min :: Cardinality a b -> Cardinality a b -> Cardinality a b

(Show a, Show b) => Show (Cardinality a b) Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Cardinality a b -> ShowS

show :: Cardinality a b -> String

showList :: [Cardinality a b] -> ShowS

Generic (Cardinality a b) 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep (Cardinality a b) :: Type -> Type

Methods

from :: Cardinality a b -> Rep (Cardinality a b) x

to :: Rep (Cardinality a b) x -> Cardinality a b

(FromJSON a, FromJSON b) => FromJSON (Cardinality a b) 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser (Cardinality a b)

parseJSONList :: Value -> Parser [Cardinality a b]

(ToJSON a, ToJSON b) => ToJSON (Cardinality a b) 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Cardinality a b -> Value

toEncoding :: Cardinality a b -> Encoding

toJSONList :: [Cardinality a b] -> Value

toEncodingList :: [Cardinality a b] -> Encoding

(ShATermConvertible a, ShATermConvertible b) => ShATermConvertible (Cardinality a b) 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Cardinality a b -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Cardinality a b] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Cardinality a b)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Cardinality a b])

type Rep (Cardinality a b) 
Instance details

Defined in OWL2.ATC_OWL2

type Rep (Cardinality a b) = D1 ('MetaData "Cardinality" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Cardinality" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardinalityType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe b)))))

data JunctionType Source #

Constructors

UnionOf 
IntersectionOf 

Instances

Instances details
Eq JunctionType Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: JunctionType -> JunctionType -> Bool

(/=) :: JunctionType -> JunctionType -> Bool

Data JunctionType Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JunctionType -> c JunctionType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JunctionType

toConstr :: JunctionType -> Constr

dataTypeOf :: JunctionType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JunctionType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JunctionType)

gmapT :: (forall b. Data b => b -> b) -> JunctionType -> JunctionType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JunctionType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JunctionType -> r

gmapQ :: (forall d. Data d => d -> u) -> JunctionType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> JunctionType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JunctionType -> m JunctionType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JunctionType -> m JunctionType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JunctionType -> m JunctionType

Ord JunctionType Source # 
Instance details

Defined in OWL2.AS

Show JunctionType Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> JunctionType -> ShowS

show :: JunctionType -> String

showList :: [JunctionType] -> ShowS

Generic JunctionType 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep JunctionType :: Type -> Type

FromJSON JunctionType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser JunctionType

parseJSONList :: Value -> Parser [JunctionType]

ToJSON JunctionType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: JunctionType -> Value

toEncoding :: JunctionType -> Encoding

toJSONList :: [JunctionType] -> Value

toEncodingList :: [JunctionType] -> Encoding

ShATermConvertible JunctionType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> JunctionType -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [JunctionType] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, JunctionType)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [JunctionType])

type Rep JunctionType 
Instance details

Defined in OWL2.ATC_OWL2

type Rep JunctionType = D1 ('MetaData "JunctionType" "OWL2.AS" "main" 'False) (C1 ('MetaCons "UnionOf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IntersectionOf" 'PrefixI 'False) (U1 :: Type -> Type))

ENTITIES

data Entity Source #

Constructors

Entity 

Fields

Instances

Instances details
Eq Entity Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Entity -> Entity -> Bool

(/=) :: Entity -> Entity -> Bool

Data Entity Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Entity -> c Entity

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Entity

toConstr :: Entity -> Constr

dataTypeOf :: Entity -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Entity)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Entity)

gmapT :: (forall b. Data b => b -> b) -> Entity -> Entity

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Entity -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Entity -> r

gmapQ :: (forall d. Data d => d -> u) -> Entity -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Entity -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Entity -> m Entity

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Entity -> m Entity

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Entity -> m Entity

Ord Entity Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Entity -> Entity -> Ordering

(<) :: Entity -> Entity -> Bool

(<=) :: Entity -> Entity -> Bool

(>) :: Entity -> Entity -> Bool

(>=) :: Entity -> Entity -> Bool

max :: Entity -> Entity -> Entity

min :: Entity -> Entity -> Entity

Show Entity Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Entity -> ShowS

show :: Entity -> String

showList :: [Entity] -> ShowS

Generic Entity 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Entity :: Type -> Type

Methods

from :: Entity -> Rep Entity x

to :: Rep Entity x -> Entity

GetRange Entity Source # 
Instance details

Defined in OWL2.AS

FromJSON Entity 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Entity

parseJSONList :: Value -> Parser [Entity]

ToJSON Entity 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Entity -> Value

toEncoding :: Entity -> Encoding

toJSONList :: [Entity] -> Value

toEncodingList :: [Entity] -> Encoding

ShATermConvertible Entity 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Entity -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Entity] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Entity)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Entity])

Pretty Entity Source # 
Instance details

Defined in OWL2.Print

Function Entity Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> Entity -> Entity Source #

ProjectSublogicM ProfSub Entity Source # 
Instance details

Defined in OWL2.Logic_OWL2

MinSublogic ProfSub Entity Source # 
Instance details

Defined in OWL2.Logic_OWL2

Sentences OWL2 Axiom Sign OWLMorphism Entity Source # 
Instance details

Defined in OWL2.Logic_OWL2

Syntax OWL2 OntologyDocument Entity SymbItems SymbMapItems Source # 
Instance details

Defined in OWL2.Logic_OWL2

StaticAnalysis OWL2 OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

basic_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, GlobalAnnos) -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom])) Source #

sen_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, Axiom) -> Result Axiom) Source #

extBasicAnalysis :: OWL2 -> IRI -> LibName -> OntologyDocument -> Sign -> GlobalAnnos -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom]) Source #

stat_symb_map_items :: OWL2 -> Sign -> Maybe Sign -> [SymbMapItems] -> Result (EndoMap RawSymb) Source #

stat_symb_items :: OWL2 -> Sign -> [SymbItems] -> Result [RawSymb] Source #

convertTheory :: OWL2 -> Maybe ((Sign, [Named Axiom]) -> OntologyDocument) Source #

ensures_amalgamability :: OWL2 -> ([CASLAmalgOpt], Gr Sign (Int, OWLMorphism), [(Int, OWLMorphism)], Gr String String) -> Result Amalgamates Source #

quotient_term_algebra :: OWL2 -> OWLMorphism -> [Named Axiom] -> Result (Sign, [Named Axiom]) Source #

signature_colimit :: OWL2 -> Gr Sign (Int, OWLMorphism) -> Result (Sign, Map Int OWLMorphism) Source #

qualify :: OWL2 -> SIMPLE_ID -> LibName -> OWLMorphism -> Sign -> Result (OWLMorphism, [Named Axiom]) Source #

symbol_to_raw :: OWL2 -> Entity -> RawSymb Source #

id_to_raw :: OWL2 -> Id -> RawSymb Source #

matches :: OWL2 -> Entity -> RawSymb -> Bool Source #

empty_signature :: OWL2 -> Sign Source #

add_symb_to_sign :: OWL2 -> Sign -> Entity -> Result Sign Source #

signature_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

signatureDiff :: OWL2 -> Sign -> Sign -> Result Sign Source #

intersection :: OWL2 -> Sign -> Sign -> Result Sign Source #

final_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

morphism_union :: OWL2 -> OWLMorphism -> OWLMorphism -> Result OWLMorphism Source #

is_subsig :: OWL2 -> Sign -> Sign -> Bool Source #

subsig_inclusion :: OWL2 -> Sign -> Sign -> Result OWLMorphism Source #

generated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

cogenerated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

induced_from_morphism :: OWL2 -> EndoMap RawSymb -> Sign -> Result OWLMorphism Source #

induced_from_to_morphism :: OWL2 -> EndoMap RawSymb -> ExtSign Sign Entity -> ExtSign Sign Entity -> Result OWLMorphism Source #

is_transportable :: OWL2 -> OWLMorphism -> Bool Source #

is_injective :: OWL2 -> OWLMorphism -> Bool Source #

theory_to_taxonomy :: OWL2 -> TaxoGraphKind -> MMiSSOntology -> Sign -> [Named Axiom] -> Result MMiSSOntology Source #

corresp2th :: OWL2 -> String -> Bool -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> EndoMap Entity -> EndoMap Entity -> REL_REF -> Result (Sign, [Named Axiom], Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

equiv2cospan :: OWL2 -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> Result (Sign, Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

extract_module :: OWL2 -> [IRI] -> (Sign, [Named Axiom]) -> Result (Sign, [Named Axiom]) Source #

Logic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

parse_basic_sen :: OWL2 -> Maybe (OntologyDocument -> AParser st Axiom) Source #

stability :: OWL2 -> Stability Source #

data_logic :: OWL2 -> Maybe AnyLogic Source #

top_sublogic :: OWL2 -> ProfSub Source #

all_sublogics :: OWL2 -> [ProfSub] Source #

bottomSublogic :: OWL2 -> Maybe ProfSub Source #

sublogicDimensions :: OWL2 -> [[ProfSub]] Source #

parseSublogic :: OWL2 -> String -> Maybe ProfSub Source #

proj_sublogic_epsilon :: OWL2 -> ProfSub -> Sign -> OWLMorphism Source #

provers :: OWL2 -> [Prover Sign Axiom OWLMorphism ProfSub ProofTree] Source #

default_prover :: OWL2 -> String Source #

cons_checkers :: OWL2 -> [ConsChecker Sign Axiom ProfSub OWLMorphism ProofTree] Source #

conservativityCheck :: OWL2 -> [ConservativityChecker Sign Axiom OWLMorphism] Source #

empty_proof_tree :: OWL2 -> ProofTree Source #

syntaxTable :: OWL2 -> Sign -> Maybe SyntaxTable Source #

omdoc_metatheory :: OWL2 -> Maybe OMCD Source #

export_symToOmdoc :: OWL2 -> NameMap Entity -> Entity -> String -> Result TCElement Source #

export_senToOmdoc :: OWL2 -> NameMap Entity -> Axiom -> Result TCorOMElement Source #

export_theoryToOmdoc :: OWL2 -> SigMap Entity -> Sign -> [Named Axiom] -> Result [TCElement] Source #

omdocToSym :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result Entity Source #

omdocToSen :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result (Maybe (Named Axiom)) Source #

addOMadtToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [[OmdADT]] -> Result (Sign, [Named Axiom]) Source #

addOmdocToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [TCElement] -> Result (Sign, [Named Axiom]) Source #

sublogicOfTheo :: OWL2 -> (Sign, [Axiom]) -> ProfSub Source #

Comorphism Propositional2OWL2 Propositional PropSL BASIC_SPEC FORMULA SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Propositional2OWL2

Comorphism OWL22NeSyPatterns OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree NeSyPatterns () BASIC_SPEC () SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22NeSyPatterns

Comorphism OWL22CommonLogic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CommonLogic CommonLogicSL BASIC_SPEC TEXT_META SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CommonLogic

Comorphism OWL22CASL OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CASL

Comorphism CASL2OWL CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.CASL2OWL

Comorphism ExtModal2OWL ExtModal ExtModalSL EM_BASIC_SPEC ExtModalFORMULA SYMB_ITEMS SYMB_MAP_ITEMS ExtModalSign ExtModalMorph Symbol RawSymbol () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in Comorphisms.ExtModal2OWL

Comorphism DMU2OWL2 DMU () Text () () () Text (DefaultMorphism Text) () () () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.DMU2OWL2

type Rep Entity 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Entity = D1 ('MetaData "Entity" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Entity" 'PrefixI 'True) (S1 ('MetaSel ('Just "label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "entityKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntityType) :*: S1 ('MetaSel ('Just "cutIRI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI))))

data EntityType Source #

Instances

Instances details
Bounded EntityType Source # 
Instance details

Defined in OWL2.AS

Enum EntityType Source # 
Instance details

Defined in OWL2.AS

Eq EntityType Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: EntityType -> EntityType -> Bool

(/=) :: EntityType -> EntityType -> Bool

Data EntityType Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EntityType -> c EntityType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EntityType

toConstr :: EntityType -> Constr

dataTypeOf :: EntityType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EntityType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EntityType)

gmapT :: (forall b. Data b => b -> b) -> EntityType -> EntityType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EntityType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EntityType -> r

gmapQ :: (forall d. Data d => d -> u) -> EntityType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> EntityType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EntityType -> m EntityType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EntityType -> m EntityType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EntityType -> m EntityType

Ord EntityType Source # 
Instance details

Defined in OWL2.AS

Read EntityType Source # 
Instance details

Defined in OWL2.AS

Methods

readsPrec :: Int -> ReadS EntityType

readList :: ReadS [EntityType]

readPrec :: ReadPrec EntityType

readListPrec :: ReadPrec [EntityType]

Show EntityType Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> EntityType -> ShowS

show :: EntityType -> String

showList :: [EntityType] -> ShowS

Generic EntityType 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep EntityType :: Type -> Type

Methods

from :: EntityType -> Rep EntityType x

to :: Rep EntityType x -> EntityType

FromJSON EntityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser EntityType

parseJSONList :: Value -> Parser [EntityType]

ToJSON EntityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: EntityType -> Value

toEncoding :: EntityType -> Encoding

toJSONList :: [EntityType] -> Value

toEncodingList :: [EntityType] -> Encoding

ShATermConvertible EntityType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> EntityType -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [EntityType] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, EntityType)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [EntityType])

type Rep EntityType 
Instance details

Defined in OWL2.ATC_OWL2

type Rep EntityType = D1 ('MetaData "EntityType" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "Datatype" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Class" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ObjectProperty" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DataProperty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AnnotationProperty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedIndividual" 'PrefixI 'False) (U1 :: Type -> Type))))

LITERALS

data TypedOrUntyped Source #

Constructors

Typed Datatype 
Untyped (Maybe LanguageTag) 

Instances

Instances details
Eq TypedOrUntyped Source # 
Instance details

Defined in OWL2.AS

Data TypedOrUntyped Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypedOrUntyped -> c TypedOrUntyped

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypedOrUntyped

toConstr :: TypedOrUntyped -> Constr

dataTypeOf :: TypedOrUntyped -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypedOrUntyped)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypedOrUntyped)

gmapT :: (forall b. Data b => b -> b) -> TypedOrUntyped -> TypedOrUntyped

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypedOrUntyped -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypedOrUntyped -> r

gmapQ :: (forall d. Data d => d -> u) -> TypedOrUntyped -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypedOrUntyped -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypedOrUntyped -> m TypedOrUntyped

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedOrUntyped -> m TypedOrUntyped

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedOrUntyped -> m TypedOrUntyped

Ord TypedOrUntyped Source # 
Instance details

Defined in OWL2.AS

Show TypedOrUntyped Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> TypedOrUntyped -> ShowS

show :: TypedOrUntyped -> String

showList :: [TypedOrUntyped] -> ShowS

Generic TypedOrUntyped 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep TypedOrUntyped :: Type -> Type

FromJSON TypedOrUntyped 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser TypedOrUntyped

parseJSONList :: Value -> Parser [TypedOrUntyped]

ToJSON TypedOrUntyped 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: TypedOrUntyped -> Value

toEncoding :: TypedOrUntyped -> Encoding

toJSONList :: [TypedOrUntyped] -> Value

toEncodingList :: [TypedOrUntyped] -> Encoding

ShATermConvertible TypedOrUntyped 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> TypedOrUntyped -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [TypedOrUntyped] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, TypedOrUntyped)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [TypedOrUntyped])

type Rep TypedOrUntyped 
Instance details

Defined in OWL2.ATC_OWL2

type Rep TypedOrUntyped = D1 ('MetaData "TypedOrUntyped" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Typed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datatype)) :+: C1 ('MetaCons "Untyped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LanguageTag))))

data Literal Source #

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Literal -> Literal -> Bool

(/=) :: Literal -> Literal -> Bool

Data Literal Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal

toConstr :: Literal -> Constr

dataTypeOf :: Literal -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal)

gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r

gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal

Ord Literal Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Literal -> Literal -> Ordering

(<) :: Literal -> Literal -> Bool

(<=) :: Literal -> Literal -> Bool

(>) :: Literal -> Literal -> Bool

(>=) :: Literal -> Literal -> Bool

max :: Literal -> Literal -> Literal

min :: Literal -> Literal -> Literal

Show Literal Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Literal -> ShowS

show :: Literal -> String

showList :: [Literal] -> ShowS

Generic Literal 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Literal :: Type -> Type

Methods

from :: Literal -> Rep Literal x

to :: Rep Literal x -> Literal

FromJSON Literal 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Literal

parseJSONList :: Value -> Parser [Literal]

ToJSON Literal 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Literal -> Value

toEncoding :: Literal -> Encoding

toJSONList :: [Literal] -> Value

toEncodingList :: [Literal] -> Encoding

ShATermConvertible Literal 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Literal -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Literal] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Literal)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Literal])

Pretty Literal Source # 
Instance details

Defined in OWL2.Print

Function Literal Source # 
Instance details

Defined in OWL2.Function

type Rep Literal 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Literal = D1 ('MetaData "Literal" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Literal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LexicalForm) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypedOrUntyped)) :+: C1 ('MetaCons "NumberLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FloatLit)))

data NNInt Source #

non-negative integers given by the sequence of digits

Constructors

NNInt [Int] 

Instances

Instances details
Eq NNInt Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: NNInt -> NNInt -> Bool

(/=) :: NNInt -> NNInt -> Bool

Data NNInt Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NNInt -> c NNInt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NNInt

toConstr :: NNInt -> Constr

dataTypeOf :: NNInt -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NNInt)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NNInt)

gmapT :: (forall b. Data b => b -> b) -> NNInt -> NNInt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NNInt -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NNInt -> r

gmapQ :: (forall d. Data d => d -> u) -> NNInt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> NNInt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NNInt -> m NNInt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NNInt -> m NNInt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NNInt -> m NNInt

Ord NNInt Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: NNInt -> NNInt -> Ordering

(<) :: NNInt -> NNInt -> Bool

(<=) :: NNInt -> NNInt -> Bool

(>) :: NNInt -> NNInt -> Bool

(>=) :: NNInt -> NNInt -> Bool

max :: NNInt -> NNInt -> NNInt

min :: NNInt -> NNInt -> NNInt

Show NNInt Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> NNInt -> ShowS

show :: NNInt -> String

showList :: [NNInt] -> ShowS

Generic NNInt 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep NNInt :: Type -> Type

Methods

from :: NNInt -> Rep NNInt x

to :: Rep NNInt x -> NNInt

FromJSON NNInt 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser NNInt

parseJSONList :: Value -> Parser [NNInt]

ToJSON NNInt 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: NNInt -> Value

toEncoding :: NNInt -> Encoding

toJSONList :: [NNInt] -> Value

toEncodingList :: [NNInt] -> Encoding

ShATermConvertible NNInt 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> NNInt -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [NNInt] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, NNInt)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [NNInt])

type Rep NNInt 
Instance details

Defined in OWL2.ATC_OWL2

type Rep NNInt = D1 ('MetaData "NNInt" "OWL2.AS" "main" 'False) (C1 ('MetaCons "NNInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))

data IntLit Source #

Constructors

IntLit 

Fields

Instances

Instances details
Eq IntLit Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: IntLit -> IntLit -> Bool

(/=) :: IntLit -> IntLit -> Bool

Data IntLit Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntLit -> c IntLit

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntLit

toConstr :: IntLit -> Constr

dataTypeOf :: IntLit -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntLit)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntLit)

gmapT :: (forall b. Data b => b -> b) -> IntLit -> IntLit

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntLit -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntLit -> r

gmapQ :: (forall d. Data d => d -> u) -> IntLit -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntLit -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntLit -> m IntLit

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntLit -> m IntLit

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntLit -> m IntLit

Ord IntLit Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: IntLit -> IntLit -> Ordering

(<) :: IntLit -> IntLit -> Bool

(<=) :: IntLit -> IntLit -> Bool

(>) :: IntLit -> IntLit -> Bool

(>=) :: IntLit -> IntLit -> Bool

max :: IntLit -> IntLit -> IntLit

min :: IntLit -> IntLit -> IntLit

Show IntLit Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> IntLit -> ShowS

show :: IntLit -> String

showList :: [IntLit] -> ShowS

Generic IntLit 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep IntLit :: Type -> Type

Methods

from :: IntLit -> Rep IntLit x

to :: Rep IntLit x -> IntLit

FromJSON IntLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser IntLit

parseJSONList :: Value -> Parser [IntLit]

ToJSON IntLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: IntLit -> Value

toEncoding :: IntLit -> Encoding

toJSONList :: [IntLit] -> Value

toEncodingList :: [IntLit] -> Encoding

ShATermConvertible IntLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> IntLit -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [IntLit] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, IntLit)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [IntLit])

type Rep IntLit 
Instance details

Defined in OWL2.ATC_OWL2

type Rep IntLit = D1 ('MetaData "IntLit" "OWL2.AS" "main" 'False) (C1 ('MetaCons "IntLit" 'PrefixI 'True) (S1 ('MetaSel ('Just "absInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NNInt) :*: S1 ('MetaSel ('Just "isNegInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

negNNInt :: Bool -> NNInt -> IntLit Source #

data DecLit Source #

Constructors

DecLit 

Fields

Instances

Instances details
Eq DecLit Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: DecLit -> DecLit -> Bool

(/=) :: DecLit -> DecLit -> Bool

Data DecLit Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DecLit -> c DecLit

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DecLit

toConstr :: DecLit -> Constr

dataTypeOf :: DecLit -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DecLit)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DecLit)

gmapT :: (forall b. Data b => b -> b) -> DecLit -> DecLit

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DecLit -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DecLit -> r

gmapQ :: (forall d. Data d => d -> u) -> DecLit -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DecLit -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DecLit -> m DecLit

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DecLit -> m DecLit

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DecLit -> m DecLit

Ord DecLit Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: DecLit -> DecLit -> Ordering

(<) :: DecLit -> DecLit -> Bool

(<=) :: DecLit -> DecLit -> Bool

(>) :: DecLit -> DecLit -> Bool

(>=) :: DecLit -> DecLit -> Bool

max :: DecLit -> DecLit -> DecLit

min :: DecLit -> DecLit -> DecLit

Show DecLit Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DecLit -> ShowS

show :: DecLit -> String

showList :: [DecLit] -> ShowS

Generic DecLit 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DecLit :: Type -> Type

Methods

from :: DecLit -> Rep DecLit x

to :: Rep DecLit x -> DecLit

FromJSON DecLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DecLit

parseJSONList :: Value -> Parser [DecLit]

ToJSON DecLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DecLit -> Value

toEncoding :: DecLit -> Encoding

toJSONList :: [DecLit] -> Value

toEncodingList :: [DecLit] -> Encoding

ShATermConvertible DecLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DecLit -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DecLit] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DecLit)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DecLit])

type Rep DecLit 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DecLit = D1 ('MetaData "DecLit" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DecLit" 'PrefixI 'True) (S1 ('MetaSel ('Just "truncDec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntLit) :*: S1 ('MetaSel ('Just "fracDec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NNInt)))

isDecInt :: DecLit -> Bool Source #

negDec :: Bool -> DecLit -> DecLit Source #

data FloatLit Source #

Constructors

FloatLit 

Instances

Instances details
Eq FloatLit Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: FloatLit -> FloatLit -> Bool

(/=) :: FloatLit -> FloatLit -> Bool

Data FloatLit Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FloatLit -> c FloatLit

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FloatLit

toConstr :: FloatLit -> Constr

dataTypeOf :: FloatLit -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FloatLit)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FloatLit)

gmapT :: (forall b. Data b => b -> b) -> FloatLit -> FloatLit

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FloatLit -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FloatLit -> r

gmapQ :: (forall d. Data d => d -> u) -> FloatLit -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> FloatLit -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FloatLit -> m FloatLit

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatLit -> m FloatLit

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FloatLit -> m FloatLit

Ord FloatLit Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: FloatLit -> FloatLit -> Ordering

(<) :: FloatLit -> FloatLit -> Bool

(<=) :: FloatLit -> FloatLit -> Bool

(>) :: FloatLit -> FloatLit -> Bool

(>=) :: FloatLit -> FloatLit -> Bool

max :: FloatLit -> FloatLit -> FloatLit

min :: FloatLit -> FloatLit -> FloatLit

Show FloatLit Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> FloatLit -> ShowS

show :: FloatLit -> String

showList :: [FloatLit] -> ShowS

Generic FloatLit 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep FloatLit :: Type -> Type

Methods

from :: FloatLit -> Rep FloatLit x

to :: Rep FloatLit x -> FloatLit

FromJSON FloatLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser FloatLit

parseJSONList :: Value -> Parser [FloatLit]

ToJSON FloatLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: FloatLit -> Value

toEncoding :: FloatLit -> Encoding

toJSONList :: [FloatLit] -> Value

toEncodingList :: [FloatLit] -> Encoding

ShATermConvertible FloatLit 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> FloatLit -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [FloatLit] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, FloatLit)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [FloatLit])

type Rep FloatLit 
Instance details

Defined in OWL2.ATC_OWL2

type Rep FloatLit = D1 ('MetaData "FloatLit" "OWL2.AS" "main" 'False) (C1 ('MetaCons "FloatLit" 'PrefixI 'True) (S1 ('MetaSel ('Just "floatBase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DecLit) :*: S1 ('MetaSel ('Just "floatExp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntLit)))

isNegDec :: DecLit -> Bool Source #

litType :: Literal -> Maybe IRI Source #

cTypeS :: String Source #

PROPERTY EXPRESSIONS

data ObjectPropertyExpression Source #

Instances

Instances details
Eq ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Data ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectPropertyExpression -> c ObjectPropertyExpression

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectPropertyExpression

toConstr :: ObjectPropertyExpression -> Constr

dataTypeOf :: ObjectPropertyExpression -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectPropertyExpression)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectPropertyExpression)

gmapT :: (forall b. Data b => b -> b) -> ObjectPropertyExpression -> ObjectPropertyExpression

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectPropertyExpression -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectPropertyExpression -> r

gmapQ :: (forall d. Data d => d -> u) -> ObjectPropertyExpression -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectPropertyExpression -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectPropertyExpression -> m ObjectPropertyExpression

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectPropertyExpression -> m ObjectPropertyExpression

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectPropertyExpression -> m ObjectPropertyExpression

Ord ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Show ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Generic ObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep ObjectPropertyExpression :: Type -> Type

FromJSON ObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser ObjectPropertyExpression

parseJSONList :: Value -> Parser [ObjectPropertyExpression]

ToJSON ObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible ObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> ObjectPropertyExpression -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [ObjectPropertyExpression] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, ObjectPropertyExpression)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [ObjectPropertyExpression])

Pretty ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.Print

Function ObjectPropertyExpression Source # 
Instance details

Defined in OWL2.Function

type Rep ObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

type Rep ObjectPropertyExpression = D1 ('MetaData "ObjectPropertyExpression" "OWL2.AS" "main" 'False) (C1 ('MetaCons "ObjectProp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectProperty)) :+: C1 ('MetaCons "ObjectInverseOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InverseObjectProperty)))

DATA RANGES

data DataRange Source #

Instances

Instances details
Eq DataRange Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: DataRange -> DataRange -> Bool

(/=) :: DataRange -> DataRange -> Bool

Data DataRange Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataRange -> c DataRange

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataRange

toConstr :: DataRange -> Constr

dataTypeOf :: DataRange -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataRange)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataRange)

gmapT :: (forall b. Data b => b -> b) -> DataRange -> DataRange

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataRange -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataRange -> r

gmapQ :: (forall d. Data d => d -> u) -> DataRange -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataRange -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataRange -> m DataRange

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataRange -> m DataRange

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataRange -> m DataRange

Ord DataRange Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: DataRange -> DataRange -> Ordering

(<) :: DataRange -> DataRange -> Bool

(<=) :: DataRange -> DataRange -> Bool

(>) :: DataRange -> DataRange -> Bool

(>=) :: DataRange -> DataRange -> Bool

max :: DataRange -> DataRange -> DataRange

min :: DataRange -> DataRange -> DataRange

Show DataRange Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DataRange -> ShowS

show :: DataRange -> String

showList :: [DataRange] -> ShowS

Generic DataRange 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DataRange :: Type -> Type

Methods

from :: DataRange -> Rep DataRange x

to :: Rep DataRange x -> DataRange

FromJSON DataRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DataRange

parseJSONList :: Value -> Parser [DataRange]

ToJSON DataRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DataRange -> Value

toEncoding :: DataRange -> Encoding

toJSONList :: [DataRange] -> Value

toEncodingList :: [DataRange] -> Encoding

ShATermConvertible DataRange 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DataRange -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DataRange] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DataRange)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DataRange])

Pretty DataRange Source #

Printing the DataRange

Instance details

Defined in OWL2.Print

Function DataRange Source # 
Instance details

Defined in OWL2.Function

type Rep DataRange 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DataRange = D1 ('MetaData "DataRange" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "DataType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datatype) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConstrainingFacet, RestrictionValue)])) :+: C1 ('MetaCons "DataJunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JunctionType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataRange]))) :+: (C1 ('MetaCons "DataComplementOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataRange)) :+: C1 ('MetaCons "DataOneOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Literal]))))

basedOn :: DataRange -> [Datatype] Source #

Extracts all Datatypes used in a Datarange.

CLASS EXPERSSIONS

data ClassExpression Source #

Instances

Instances details
Eq ClassExpression Source # 
Instance details

Defined in OWL2.AS

Data ClassExpression Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassExpression -> c ClassExpression

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassExpression

toConstr :: ClassExpression -> Constr

dataTypeOf :: ClassExpression -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClassExpression)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassExpression)

gmapT :: (forall b. Data b => b -> b) -> ClassExpression -> ClassExpression

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassExpression -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassExpression -> r

gmapQ :: (forall d. Data d => d -> u) -> ClassExpression -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassExpression -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassExpression -> m ClassExpression

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassExpression -> m ClassExpression

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassExpression -> m ClassExpression

Ord ClassExpression Source # 
Instance details

Defined in OWL2.AS

Show ClassExpression Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> ClassExpression -> ShowS

show :: ClassExpression -> String

showList :: [ClassExpression] -> ShowS

Generic ClassExpression 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep ClassExpression :: Type -> Type

FromJSON ClassExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser ClassExpression

parseJSONList :: Value -> Parser [ClassExpression]

ToJSON ClassExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: ClassExpression -> Value

toEncoding :: ClassExpression -> Encoding

toJSONList :: [ClassExpression] -> Value

toEncodingList :: [ClassExpression] -> Encoding

ShATermConvertible ClassExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> ClassExpression -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [ClassExpression] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, ClassExpression)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [ClassExpression])

Pretty ClassExpression Source #

Printing the ClassExpression

Instance details

Defined in OWL2.Print

Function ClassExpression Source # 
Instance details

Defined in OWL2.Function

type Rep ClassExpression 
Instance details

Defined in OWL2.ATC_OWL2

type Rep ClassExpression = D1 ('MetaData "ClassExpression" "OWL2.AS" "main" 'False) (((C1 ('MetaCons "Expression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Class)) :+: C1 ('MetaCons "ObjectJunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JunctionType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ClassExpression]))) :+: (C1 ('MetaCons "ObjectComplementOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression)) :+: (C1 ('MetaCons "ObjectOneOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Individual])) :+: C1 ('MetaCons "ObjectValuesFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QuantifierType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression)))))) :+: ((C1 ('MetaCons "ObjectHasValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Individual)) :+: (C1 ('MetaCons "ObjectHasSelf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: C1 ('MetaCons "ObjectCardinality" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Cardinality ObjectPropertyExpression ClassExpression))))) :+: (C1 ('MetaCons "DataValuesFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QuantifierType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataPropertyExpression]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataRange))) :+: (C1 ('MetaCons "DataHasValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Literal)) :+: C1 ('MetaCons "DataCardinality" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Cardinality DataPropertyExpression DataRange)))))))

ANNOTATIONS

data Annotation Source #

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Annotation -> Annotation -> Bool

(/=) :: Annotation -> Annotation -> Bool

Data Annotation Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation

toConstr :: Annotation -> Constr

dataTypeOf :: Annotation -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation)

gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r

gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation

Ord Annotation Source # 
Instance details

Defined in OWL2.AS

Show Annotation Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Annotation -> ShowS

show :: Annotation -> String

showList :: [Annotation] -> ShowS

Generic Annotation 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Annotation :: Type -> Type

Methods

from :: Annotation -> Rep Annotation x

to :: Rep Annotation x -> Annotation

FromJSON Annotation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Annotation

parseJSONList :: Value -> Parser [Annotation]

ToJSON Annotation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Annotation -> Value

toEncoding :: Annotation -> Encoding

toJSONList :: [Annotation] -> Value

toEncodingList :: [Annotation] -> Encoding

ShATermConvertible Annotation 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Annotation -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Annotation] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Annotation)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Annotation])

Pretty Annotation Source # 
Instance details

Defined in OWL2.Print

Function Annotation Source # 
Instance details

Defined in OWL2.Function

type Rep Annotation 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Annotation = D1 ('MetaData "Annotation" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Annotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annAnnotations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Annotation]) :*: (S1 ('MetaSel ('Just "annProperty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationProperty) :*: S1 ('MetaSel ('Just "annValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationValue))))

data AnnotationValue Source #

Instances

Instances details
Eq AnnotationValue Source # 
Instance details

Defined in OWL2.AS

Data AnnotationValue Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnotationValue -> c AnnotationValue

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationValue

toConstr :: AnnotationValue -> Constr

dataTypeOf :: AnnotationValue -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationValue)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationValue)

gmapT :: (forall b. Data b => b -> b) -> AnnotationValue -> AnnotationValue

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationValue -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationValue -> r

gmapQ :: (forall d. Data d => d -> u) -> AnnotationValue -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationValue -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationValue -> m AnnotationValue

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationValue -> m AnnotationValue

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationValue -> m AnnotationValue

Ord AnnotationValue Source # 
Instance details

Defined in OWL2.AS

Show AnnotationValue Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> AnnotationValue -> ShowS

show :: AnnotationValue -> String

showList :: [AnnotationValue] -> ShowS

Generic AnnotationValue 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep AnnotationValue :: Type -> Type

FromJSON AnnotationValue 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser AnnotationValue

parseJSONList :: Value -> Parser [AnnotationValue]

ToJSON AnnotationValue 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: AnnotationValue -> Value

toEncoding :: AnnotationValue -> Encoding

toJSONList :: [AnnotationValue] -> Value

toEncodingList :: [AnnotationValue] -> Encoding

ShATermConvertible AnnotationValue 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> AnnotationValue -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [AnnotationValue] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, AnnotationValue)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [AnnotationValue])

Pretty AnnotationValue Source #

annotations printing

Instance details

Defined in OWL2.Print

Function AnnotationValue Source # 
Instance details

Defined in OWL2.Function

type Rep AnnotationValue 
Instance details

Defined in OWL2.ATC_OWL2

type Rep AnnotationValue = D1 ('MetaData "AnnotationValue" "OWL2.AS" "main" 'False) (C1 ('MetaCons "AnnAnInd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnonymousIndividual)) :+: (C1 ('MetaCons "AnnValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI)) :+: C1 ('MetaCons "AnnValLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Literal))))

data AnnotationAxiom Source #

Instances

Instances details
Eq AnnotationAxiom Source # 
Instance details

Defined in OWL2.AS

Data AnnotationAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnotationAxiom -> c AnnotationAxiom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationAxiom

toConstr :: AnnotationAxiom -> Constr

dataTypeOf :: AnnotationAxiom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationAxiom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationAxiom)

gmapT :: (forall b. Data b => b -> b) -> AnnotationAxiom -> AnnotationAxiom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationAxiom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationAxiom -> r

gmapQ :: (forall d. Data d => d -> u) -> AnnotationAxiom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationAxiom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationAxiom -> m AnnotationAxiom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationAxiom -> m AnnotationAxiom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationAxiom -> m AnnotationAxiom

Ord AnnotationAxiom Source # 
Instance details

Defined in OWL2.AS

Show AnnotationAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> AnnotationAxiom -> ShowS

show :: AnnotationAxiom -> String

showList :: [AnnotationAxiom] -> ShowS

Generic AnnotationAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep AnnotationAxiom :: Type -> Type

FromJSON AnnotationAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser AnnotationAxiom

parseJSONList :: Value -> Parser [AnnotationAxiom]

ToJSON AnnotationAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: AnnotationAxiom -> Value

toEncoding :: AnnotationAxiom -> Encoding

toJSONList :: [AnnotationAxiom] -> Value

toEncodingList :: [AnnotationAxiom] -> Encoding

ShATermConvertible AnnotationAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> AnnotationAxiom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [AnnotationAxiom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, AnnotationAxiom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [AnnotationAxiom])

Function AnnotationAxiom Source # 
Instance details

Defined in OWL2.Function

type Rep AnnotationAxiom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep AnnotationAxiom = D1 ('MetaData "AnnotationAxiom" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "AnnotationAssertion" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationProperty)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationSubject) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationValue))) :+: C1 ('MetaCons "SubAnnotationPropertyOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubAnnotationProperty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperAnnotationProperty)))) :+: (C1 ('MetaCons "AnnotationPropertyDomain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationProperty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI))) :+: C1 ('MetaCons "AnnotationPropertyRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationProperty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI)))))

data AnnotationSubject Source #

Instances

Instances details
Eq AnnotationSubject Source # 
Instance details

Defined in OWL2.AS

Data AnnotationSubject Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnotationSubject -> c AnnotationSubject

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnotationSubject

toConstr :: AnnotationSubject -> Constr

dataTypeOf :: AnnotationSubject -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnotationSubject)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnotationSubject)

gmapT :: (forall b. Data b => b -> b) -> AnnotationSubject -> AnnotationSubject

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationSubject -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnotationSubject -> r

gmapQ :: (forall d. Data d => d -> u) -> AnnotationSubject -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnotationSubject -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnotationSubject -> m AnnotationSubject

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationSubject -> m AnnotationSubject

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnotationSubject -> m AnnotationSubject

Ord AnnotationSubject Source # 
Instance details

Defined in OWL2.AS

Show AnnotationSubject Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> AnnotationSubject -> ShowS

show :: AnnotationSubject -> String

showList :: [AnnotationSubject] -> ShowS

Generic AnnotationSubject 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep AnnotationSubject :: Type -> Type

FromJSON AnnotationSubject 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser AnnotationSubject

parseJSONList :: Value -> Parser [AnnotationSubject]

ToJSON AnnotationSubject 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible AnnotationSubject 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> AnnotationSubject -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [AnnotationSubject] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, AnnotationSubject)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [AnnotationSubject])

Function AnnotationSubject Source # 
Instance details

Defined in OWL2.Function

type Rep AnnotationSubject 
Instance details

Defined in OWL2.ATC_OWL2

type Rep AnnotationSubject = D1 ('MetaData "AnnotationSubject" "OWL2.AS" "main" 'False) (C1 ('MetaCons "AnnSubIri" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI)) :+: C1 ('MetaCons "AnnSubAnInd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnonymousIndividual)))

AXIOMS

data Axiom Source #

Instances

Instances details
Eq Axiom Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Axiom -> Axiom -> Bool

(/=) :: Axiom -> Axiom -> Bool

Data Axiom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Axiom -> c Axiom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Axiom

toConstr :: Axiom -> Constr

dataTypeOf :: Axiom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Axiom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Axiom)

gmapT :: (forall b. Data b => b -> b) -> Axiom -> Axiom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Axiom -> r

gmapQ :: (forall d. Data d => d -> u) -> Axiom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Axiom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Axiom -> m Axiom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Axiom -> m Axiom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Axiom -> m Axiom

Ord Axiom Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Axiom -> Axiom -> Ordering

(<) :: Axiom -> Axiom -> Bool

(<=) :: Axiom -> Axiom -> Bool

(>) :: Axiom -> Axiom -> Bool

(>=) :: Axiom -> Axiom -> Bool

max :: Axiom -> Axiom -> Axiom

min :: Axiom -> Axiom -> Axiom

Show Axiom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Axiom -> ShowS

show :: Axiom -> String

showList :: [Axiom] -> ShowS

Generic Axiom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Axiom :: Type -> Type

Methods

from :: Axiom -> Rep Axiom x

to :: Rep Axiom x -> Axiom

GetRange Axiom Source # 
Instance details

Defined in OWL2.AS

FromJSON Axiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Axiom

parseJSONList :: Value -> Parser [Axiom]

ToJSON Axiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Axiom -> Value

toEncoding :: Axiom -> Encoding

toJSONList :: [Axiom] -> Value

toEncodingList :: [Axiom] -> Encoding

ShATermConvertible Axiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Axiom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Axiom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Axiom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Axiom])

Pretty Axiom Source # 
Instance details

Defined in OWL2.Pretty

Function Axiom Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> Axiom -> Axiom Source #

MinSublogic ProfSub Axiom Source # 
Instance details

Defined in OWL2.Logic_OWL2

Sentences OWL2 Axiom Sign OWLMorphism Entity Source # 
Instance details

Defined in OWL2.Logic_OWL2

StaticAnalysis OWL2 OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

basic_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, GlobalAnnos) -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom])) Source #

sen_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, Axiom) -> Result Axiom) Source #

extBasicAnalysis :: OWL2 -> IRI -> LibName -> OntologyDocument -> Sign -> GlobalAnnos -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom]) Source #

stat_symb_map_items :: OWL2 -> Sign -> Maybe Sign -> [SymbMapItems] -> Result (EndoMap RawSymb) Source #

stat_symb_items :: OWL2 -> Sign -> [SymbItems] -> Result [RawSymb] Source #

convertTheory :: OWL2 -> Maybe ((Sign, [Named Axiom]) -> OntologyDocument) Source #

ensures_amalgamability :: OWL2 -> ([CASLAmalgOpt], Gr Sign (Int, OWLMorphism), [(Int, OWLMorphism)], Gr String String) -> Result Amalgamates Source #

quotient_term_algebra :: OWL2 -> OWLMorphism -> [Named Axiom] -> Result (Sign, [Named Axiom]) Source #

signature_colimit :: OWL2 -> Gr Sign (Int, OWLMorphism) -> Result (Sign, Map Int OWLMorphism) Source #

qualify :: OWL2 -> SIMPLE_ID -> LibName -> OWLMorphism -> Sign -> Result (OWLMorphism, [Named Axiom]) Source #

symbol_to_raw :: OWL2 -> Entity -> RawSymb Source #

id_to_raw :: OWL2 -> Id -> RawSymb Source #

matches :: OWL2 -> Entity -> RawSymb -> Bool Source #

empty_signature :: OWL2 -> Sign Source #

add_symb_to_sign :: OWL2 -> Sign -> Entity -> Result Sign Source #

signature_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

signatureDiff :: OWL2 -> Sign -> Sign -> Result Sign Source #

intersection :: OWL2 -> Sign -> Sign -> Result Sign Source #

final_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

morphism_union :: OWL2 -> OWLMorphism -> OWLMorphism -> Result OWLMorphism Source #

is_subsig :: OWL2 -> Sign -> Sign -> Bool Source #

subsig_inclusion :: OWL2 -> Sign -> Sign -> Result OWLMorphism Source #

generated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

cogenerated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

induced_from_morphism :: OWL2 -> EndoMap RawSymb -> Sign -> Result OWLMorphism Source #

induced_from_to_morphism :: OWL2 -> EndoMap RawSymb -> ExtSign Sign Entity -> ExtSign Sign Entity -> Result OWLMorphism Source #

is_transportable :: OWL2 -> OWLMorphism -> Bool Source #

is_injective :: OWL2 -> OWLMorphism -> Bool Source #

theory_to_taxonomy :: OWL2 -> TaxoGraphKind -> MMiSSOntology -> Sign -> [Named Axiom] -> Result MMiSSOntology Source #

corresp2th :: OWL2 -> String -> Bool -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> EndoMap Entity -> EndoMap Entity -> REL_REF -> Result (Sign, [Named Axiom], Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

equiv2cospan :: OWL2 -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> Result (Sign, Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

extract_module :: OWL2 -> [IRI] -> (Sign, [Named Axiom]) -> Result (Sign, [Named Axiom]) Source #

Logic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

parse_basic_sen :: OWL2 -> Maybe (OntologyDocument -> AParser st Axiom) Source #

stability :: OWL2 -> Stability Source #

data_logic :: OWL2 -> Maybe AnyLogic Source #

top_sublogic :: OWL2 -> ProfSub Source #

all_sublogics :: OWL2 -> [ProfSub] Source #

bottomSublogic :: OWL2 -> Maybe ProfSub Source #

sublogicDimensions :: OWL2 -> [[ProfSub]] Source #

parseSublogic :: OWL2 -> String -> Maybe ProfSub Source #

proj_sublogic_epsilon :: OWL2 -> ProfSub -> Sign -> OWLMorphism Source #

provers :: OWL2 -> [Prover Sign Axiom OWLMorphism ProfSub ProofTree] Source #

default_prover :: OWL2 -> String Source #

cons_checkers :: OWL2 -> [ConsChecker Sign Axiom ProfSub OWLMorphism ProofTree] Source #

conservativityCheck :: OWL2 -> [ConservativityChecker Sign Axiom OWLMorphism] Source #

empty_proof_tree :: OWL2 -> ProofTree Source #

syntaxTable :: OWL2 -> Sign -> Maybe SyntaxTable Source #

omdoc_metatheory :: OWL2 -> Maybe OMCD Source #

export_symToOmdoc :: OWL2 -> NameMap Entity -> Entity -> String -> Result TCElement Source #

export_senToOmdoc :: OWL2 -> NameMap Entity -> Axiom -> Result TCorOMElement Source #

export_theoryToOmdoc :: OWL2 -> SigMap Entity -> Sign -> [Named Axiom] -> Result [TCElement] Source #

omdocToSym :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result Entity Source #

omdocToSen :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result (Maybe (Named Axiom)) Source #

addOMadtToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [[OmdADT]] -> Result (Sign, [Named Axiom]) Source #

addOmdocToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [TCElement] -> Result (Sign, [Named Axiom]) Source #

sublogicOfTheo :: OWL2 -> (Sign, [Axiom]) -> ProfSub Source #

Comorphism Propositional2OWL2 Propositional PropSL BASIC_SPEC FORMULA SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Propositional2OWL2

Comorphism OWL22NeSyPatterns OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree NeSyPatterns () BASIC_SPEC () SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22NeSyPatterns

Comorphism OWL22CommonLogic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CommonLogic CommonLogicSL BASIC_SPEC TEXT_META SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CommonLogic

Comorphism OWL22CASL OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CASL

Comorphism CASL2OWL CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.CASL2OWL

Comorphism ExtModal2OWL ExtModal ExtModalSL EM_BASIC_SPEC ExtModalFORMULA SYMB_ITEMS SYMB_MAP_ITEMS ExtModalSign ExtModalMorph Symbol RawSymbol () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in Comorphisms.ExtModal2OWL

Comorphism DMU2OWL2 DMU () Text () () () Text (DefaultMorphism Text) () () () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.DMU2OWL2

type Rep Axiom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Axiom = D1 ('MetaData "Axiom" "OWL2.AS" "main" 'False) (((C1 ('MetaCons "Declaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Entity)) :+: C1 ('MetaCons "ClassAxiom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassAxiom))) :+: (C1 ('MetaCons "ObjectPropertyAxiom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyAxiom)) :+: (C1 ('MetaCons "DataPropertyAxiom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyAxiom)) :+: C1 ('MetaCons "DatatypeDefinition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datatype) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataRange)))))) :+: ((C1 ('MetaCons "HasKey" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ObjectPropertyExpression]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataPropertyExpression]))) :+: C1 ('MetaCons "Assertion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Assertion))) :+: (C1 ('MetaCons "AnnotationAxiom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnotationAxiom)) :+: (C1 ('MetaCons "Rule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rule)) :+: C1 ('MetaCons "DGAxiom" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGName)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGNodes) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGEdges) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MainClasses))))))))

data ClassAxiom Source #

Instances

Instances details
Eq ClassAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: ClassAxiom -> ClassAxiom -> Bool

(/=) :: ClassAxiom -> ClassAxiom -> Bool

Data ClassAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassAxiom -> c ClassAxiom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassAxiom

toConstr :: ClassAxiom -> Constr

dataTypeOf :: ClassAxiom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClassAxiom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassAxiom)

gmapT :: (forall b. Data b => b -> b) -> ClassAxiom -> ClassAxiom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassAxiom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassAxiom -> r

gmapQ :: (forall d. Data d => d -> u) -> ClassAxiom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassAxiom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassAxiom -> m ClassAxiom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassAxiom -> m ClassAxiom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassAxiom -> m ClassAxiom

Ord ClassAxiom Source # 
Instance details

Defined in OWL2.AS

Show ClassAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> ClassAxiom -> ShowS

show :: ClassAxiom -> String

showList :: [ClassAxiom] -> ShowS

Generic ClassAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep ClassAxiom :: Type -> Type

Methods

from :: ClassAxiom -> Rep ClassAxiom x

to :: Rep ClassAxiom x -> ClassAxiom

FromJSON ClassAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser ClassAxiom

parseJSONList :: Value -> Parser [ClassAxiom]

ToJSON ClassAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: ClassAxiom -> Value

toEncoding :: ClassAxiom -> Encoding

toJSONList :: [ClassAxiom] -> Value

toEncodingList :: [ClassAxiom] -> Encoding

ShATermConvertible ClassAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> ClassAxiom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [ClassAxiom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, ClassAxiom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [ClassAxiom])

Function ClassAxiom Source # 
Instance details

Defined in OWL2.Function

type Rep ClassAxiom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep ClassAxiom = D1 ('MetaData "ClassAxiom" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "SubClassOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubClassExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperClassExpression))) :+: C1 ('MetaCons "EquivalentClasses" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ClassExpression]))) :+: (C1 ('MetaCons "DisjointClasses" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ClassExpression])) :+: C1 ('MetaCons "DisjointUnion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Class) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisjointClassExpression)))))

data ObjectPropertyAxiom Source #

Instances

Instances details
Eq ObjectPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Data ObjectPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectPropertyAxiom -> c ObjectPropertyAxiom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectPropertyAxiom

toConstr :: ObjectPropertyAxiom -> Constr

dataTypeOf :: ObjectPropertyAxiom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectPropertyAxiom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectPropertyAxiom)

gmapT :: (forall b. Data b => b -> b) -> ObjectPropertyAxiom -> ObjectPropertyAxiom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectPropertyAxiom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectPropertyAxiom -> r

gmapQ :: (forall d. Data d => d -> u) -> ObjectPropertyAxiom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectPropertyAxiom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectPropertyAxiom -> m ObjectPropertyAxiom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectPropertyAxiom -> m ObjectPropertyAxiom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectPropertyAxiom -> m ObjectPropertyAxiom

Ord ObjectPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Show ObjectPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> ObjectPropertyAxiom -> ShowS

show :: ObjectPropertyAxiom -> String

showList :: [ObjectPropertyAxiom] -> ShowS

Generic ObjectPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep ObjectPropertyAxiom :: Type -> Type

FromJSON ObjectPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser ObjectPropertyAxiom

parseJSONList :: Value -> Parser [ObjectPropertyAxiom]

ToJSON ObjectPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible ObjectPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> ObjectPropertyAxiom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [ObjectPropertyAxiom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, ObjectPropertyAxiom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [ObjectPropertyAxiom])

Function ObjectPropertyAxiom Source # 
Instance details

Defined in OWL2.Function

type Rep ObjectPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep ObjectPropertyAxiom = D1 ('MetaData "ObjectPropertyAxiom" "OWL2.AS" "main" 'False) (((C1 ('MetaCons "SubObjectPropertyOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperObjectPropertyExpression))) :+: (C1 ('MetaCons "EquivalentObjectProperties" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ObjectPropertyExpression])) :+: C1 ('MetaCons "DisjointObjectProperties" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ObjectPropertyExpression])))) :+: (C1 ('MetaCons "InverseObjectProperties" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression))) :+: (C1 ('MetaCons "ObjectPropertyDomain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression))) :+: C1 ('MetaCons "ObjectPropertyRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression)))))) :+: ((C1 ('MetaCons "FunctionalObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: (C1 ('MetaCons "InverseFunctionalObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: C1 ('MetaCons "ReflexiveObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)))) :+: ((C1 ('MetaCons "IrreflexiveObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: C1 ('MetaCons "SymmetricObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression))) :+: (C1 ('MetaCons "AsymmetricObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: C1 ('MetaCons "TransitiveObjectProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression))))))

data SubObjectPropertyExpression Source #

Instances

Instances details
Eq SubObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Data SubObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SubObjectPropertyExpression -> c SubObjectPropertyExpression

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SubObjectPropertyExpression

toConstr :: SubObjectPropertyExpression -> Constr

dataTypeOf :: SubObjectPropertyExpression -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SubObjectPropertyExpression)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SubObjectPropertyExpression)

gmapT :: (forall b. Data b => b -> b) -> SubObjectPropertyExpression -> SubObjectPropertyExpression

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SubObjectPropertyExpression -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SubObjectPropertyExpression -> r

gmapQ :: (forall d. Data d => d -> u) -> SubObjectPropertyExpression -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> SubObjectPropertyExpression -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SubObjectPropertyExpression -> m SubObjectPropertyExpression

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SubObjectPropertyExpression -> m SubObjectPropertyExpression

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SubObjectPropertyExpression -> m SubObjectPropertyExpression

Ord SubObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Show SubObjectPropertyExpression Source # 
Instance details

Defined in OWL2.AS

Generic SubObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep SubObjectPropertyExpression :: Type -> Type

FromJSON SubObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

ToJSON SubObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible SubObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> SubObjectPropertyExpression -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [SubObjectPropertyExpression] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, SubObjectPropertyExpression)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [SubObjectPropertyExpression])

Function SubObjectPropertyExpression Source # 
Instance details

Defined in OWL2.Function

type Rep SubObjectPropertyExpression 
Instance details

Defined in OWL2.ATC_OWL2

type Rep SubObjectPropertyExpression = D1 ('MetaData "SubObjectPropertyExpression" "OWL2.AS" "main" 'False) (C1 ('MetaCons "SubObjPropExpr_obj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :+: C1 ('MetaCons "SubObjPropExpr_exprchain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PropertyExpressionChain)))

data DataPropertyAxiom Source #

Instances

Instances details
Eq DataPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Data DataPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataPropertyAxiom -> c DataPropertyAxiom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataPropertyAxiom

toConstr :: DataPropertyAxiom -> Constr

dataTypeOf :: DataPropertyAxiom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataPropertyAxiom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataPropertyAxiom)

gmapT :: (forall b. Data b => b -> b) -> DataPropertyAxiom -> DataPropertyAxiom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataPropertyAxiom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataPropertyAxiom -> r

gmapQ :: (forall d. Data d => d -> u) -> DataPropertyAxiom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataPropertyAxiom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataPropertyAxiom -> m DataPropertyAxiom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataPropertyAxiom -> m DataPropertyAxiom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataPropertyAxiom -> m DataPropertyAxiom

Ord DataPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Show DataPropertyAxiom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DataPropertyAxiom -> ShowS

show :: DataPropertyAxiom -> String

showList :: [DataPropertyAxiom] -> ShowS

Generic DataPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DataPropertyAxiom :: Type -> Type

FromJSON DataPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DataPropertyAxiom

parseJSONList :: Value -> Parser [DataPropertyAxiom]

ToJSON DataPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible DataPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DataPropertyAxiom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DataPropertyAxiom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DataPropertyAxiom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DataPropertyAxiom])

Function DataPropertyAxiom Source # 
Instance details

Defined in OWL2.Function

type Rep DataPropertyAxiom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DataPropertyAxiom = D1 ('MetaData "DataPropertyAxiom" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "SubDataPropertyOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubDataPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperDataPropertyExpression))) :+: (C1 ('MetaCons "EquivalentDataProperties" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataPropertyExpression])) :+: C1 ('MetaCons "DisjointDataProperties" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataPropertyExpression])))) :+: (C1 ('MetaCons "DataPropertyDomain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression))) :+: (C1 ('MetaCons "DataPropertyRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataRange))) :+: C1 ('MetaCons "FunctionalDataProperty" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression)))))

data Assertion Source #

Instances

Instances details
Eq Assertion Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Assertion -> Assertion -> Bool

(/=) :: Assertion -> Assertion -> Bool

Data Assertion Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assertion -> c Assertion

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Assertion

toConstr :: Assertion -> Constr

dataTypeOf :: Assertion -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Assertion)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Assertion)

gmapT :: (forall b. Data b => b -> b) -> Assertion -> Assertion

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assertion -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assertion -> r

gmapQ :: (forall d. Data d => d -> u) -> Assertion -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Assertion -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assertion -> m Assertion

Ord Assertion Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Assertion -> Assertion -> Ordering

(<) :: Assertion -> Assertion -> Bool

(<=) :: Assertion -> Assertion -> Bool

(>) :: Assertion -> Assertion -> Bool

(>=) :: Assertion -> Assertion -> Bool

max :: Assertion -> Assertion -> Assertion

min :: Assertion -> Assertion -> Assertion

Show Assertion Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Assertion -> ShowS

show :: Assertion -> String

showList :: [Assertion] -> ShowS

Generic Assertion 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Assertion :: Type -> Type

Methods

from :: Assertion -> Rep Assertion x

to :: Rep Assertion x -> Assertion

FromJSON Assertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Assertion

parseJSONList :: Value -> Parser [Assertion]

ToJSON Assertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Assertion -> Value

toEncoding :: Assertion -> Encoding

toJSONList :: [Assertion] -> Value

toEncodingList :: [Assertion] -> Encoding

ShATermConvertible Assertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Assertion -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Assertion] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Assertion)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Assertion])

Function Assertion Source # 
Instance details

Defined in OWL2.Function

type Rep Assertion 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Assertion = D1 ('MetaData "Assertion" "OWL2.AS" "main" 'False) ((C1 ('MetaCons "SameIndividual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Individual])) :+: (C1 ('MetaCons "DifferentIndividuals" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Individual])) :+: C1 ('MetaCons "ClassAssertion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Individual))))) :+: ((C1 ('MetaCons "ObjectPropertyAssertion" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceIndividual) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetIndividual))) :+: C1 ('MetaCons "NegativeObjectPropertyAssertion" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceIndividual) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetIndividual)))) :+: (C1 ('MetaCons "DataPropertyAssertion" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceIndividual) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetValue))) :+: C1 ('MetaCons "NegativeDataPropertyAssertion" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataPropertyExpression)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceIndividual) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetValue))))))

data Rule Source #

Instances

Instances details
Eq Rule Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Rule -> Rule -> Bool

(/=) :: Rule -> Rule -> Bool

Data Rule Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rule -> c Rule

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rule

toConstr :: Rule -> Constr

dataTypeOf :: Rule -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rule)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule)

gmapT :: (forall b. Data b => b -> b) -> Rule -> Rule

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r

gmapQ :: (forall d. Data d => d -> u) -> Rule -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rule -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rule -> m Rule

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rule -> m Rule

Ord Rule Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Rule -> Rule -> Ordering

(<) :: Rule -> Rule -> Bool

(<=) :: Rule -> Rule -> Bool

(>) :: Rule -> Rule -> Bool

(>=) :: Rule -> Rule -> Bool

max :: Rule -> Rule -> Rule

min :: Rule -> Rule -> Rule

Show Rule Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Rule -> ShowS

show :: Rule -> String

showList :: [Rule] -> ShowS

Generic Rule 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Rule :: Type -> Type

Methods

from :: Rule -> Rep Rule x

to :: Rep Rule x -> Rule

FromJSON Rule 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Rule

parseJSONList :: Value -> Parser [Rule]

ToJSON Rule 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Rule -> Value

toEncoding :: Rule -> Encoding

toJSONList :: [Rule] -> Value

toEncodingList :: [Rule] -> Encoding

ShATermConvertible Rule 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Rule -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Rule] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Rule)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Rule])

Function Rule Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> Rule -> Rule Source #

type Rep Rule 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Rule = D1 ('MetaData "Rule" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DLSafeRule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Head))) :+: C1 ('MetaCons "DGRule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AxiomAnnotations) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGBody) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGHead))))

type Body = [Atom] Source #

type Head = [Atom] Source #

data IndividualArg Source #

Instances

Instances details
Eq IndividualArg Source # 
Instance details

Defined in OWL2.AS

Data IndividualArg Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IndividualArg -> c IndividualArg

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IndividualArg

toConstr :: IndividualArg -> Constr

dataTypeOf :: IndividualArg -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IndividualArg)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IndividualArg)

gmapT :: (forall b. Data b => b -> b) -> IndividualArg -> IndividualArg

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IndividualArg -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IndividualArg -> r

gmapQ :: (forall d. Data d => d -> u) -> IndividualArg -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IndividualArg -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IndividualArg -> m IndividualArg

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IndividualArg -> m IndividualArg

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IndividualArg -> m IndividualArg

Ord IndividualArg Source # 
Instance details

Defined in OWL2.AS

Show IndividualArg Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> IndividualArg -> ShowS

show :: IndividualArg -> String

showList :: [IndividualArg] -> ShowS

Generic IndividualArg 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep IndividualArg :: Type -> Type

FromJSON IndividualArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser IndividualArg

parseJSONList :: Value -> Parser [IndividualArg]

ToJSON IndividualArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: IndividualArg -> Value

toEncoding :: IndividualArg -> Encoding

toJSONList :: [IndividualArg] -> Value

toEncodingList :: [IndividualArg] -> Encoding

ShATermConvertible IndividualArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> IndividualArg -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [IndividualArg] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, IndividualArg)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [IndividualArg])

Function IndividualArg Source # 
Instance details

Defined in OWL2.Function

type Rep IndividualArg 
Instance details

Defined in OWL2.ATC_OWL2

type Rep IndividualArg = D1 ('MetaData "IndividualArg" "OWL2.AS" "main" 'False) (C1 ('MetaCons "IArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Individual)) :+: C1 ('MetaCons "IVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualVar)))

data DataArg Source #

Constructors

DArg Literal 
DVar DataVar 

Instances

Instances details
Eq DataArg Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: DataArg -> DataArg -> Bool

(/=) :: DataArg -> DataArg -> Bool

Data DataArg Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataArg -> c DataArg

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataArg

toConstr :: DataArg -> Constr

dataTypeOf :: DataArg -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataArg)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataArg)

gmapT :: (forall b. Data b => b -> b) -> DataArg -> DataArg

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataArg -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataArg -> r

gmapQ :: (forall d. Data d => d -> u) -> DataArg -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataArg -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataArg -> m DataArg

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataArg -> m DataArg

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataArg -> m DataArg

Ord DataArg Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: DataArg -> DataArg -> Ordering

(<) :: DataArg -> DataArg -> Bool

(<=) :: DataArg -> DataArg -> Bool

(>) :: DataArg -> DataArg -> Bool

(>=) :: DataArg -> DataArg -> Bool

max :: DataArg -> DataArg -> DataArg

min :: DataArg -> DataArg -> DataArg

Show DataArg Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DataArg -> ShowS

show :: DataArg -> String

showList :: [DataArg] -> ShowS

Generic DataArg 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DataArg :: Type -> Type

Methods

from :: DataArg -> Rep DataArg x

to :: Rep DataArg x -> DataArg

FromJSON DataArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DataArg

parseJSONList :: Value -> Parser [DataArg]

ToJSON DataArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DataArg -> Value

toEncoding :: DataArg -> Encoding

toJSONList :: [DataArg] -> Value

toEncodingList :: [DataArg] -> Encoding

ShATermConvertible DataArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DataArg -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DataArg] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DataArg)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DataArg])

Function DataArg Source # 
Instance details

Defined in OWL2.Function

type Rep DataArg 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DataArg = D1 ('MetaData "DataArg" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Literal)) :+: C1 ('MetaCons "DVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataVar)))

data UnknownArg Source #

Instances

Instances details
Eq UnknownArg Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: UnknownArg -> UnknownArg -> Bool

(/=) :: UnknownArg -> UnknownArg -> Bool

Data UnknownArg Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnknownArg -> c UnknownArg

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnknownArg

toConstr :: UnknownArg -> Constr

dataTypeOf :: UnknownArg -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnknownArg)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnknownArg)

gmapT :: (forall b. Data b => b -> b) -> UnknownArg -> UnknownArg

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnknownArg -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnknownArg -> r

gmapQ :: (forall d. Data d => d -> u) -> UnknownArg -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnknownArg -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnknownArg -> m UnknownArg

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnknownArg -> m UnknownArg

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnknownArg -> m UnknownArg

Ord UnknownArg Source # 
Instance details

Defined in OWL2.AS

Show UnknownArg Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> UnknownArg -> ShowS

show :: UnknownArg -> String

showList :: [UnknownArg] -> ShowS

Generic UnknownArg 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep UnknownArg :: Type -> Type

Methods

from :: UnknownArg -> Rep UnknownArg x

to :: Rep UnknownArg x -> UnknownArg

FromJSON UnknownArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser UnknownArg

parseJSONList :: Value -> Parser [UnknownArg]

ToJSON UnknownArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: UnknownArg -> Value

toEncoding :: UnknownArg -> Encoding

toJSONList :: [UnknownArg] -> Value

toEncodingList :: [UnknownArg] -> Encoding

ShATermConvertible UnknownArg 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> UnknownArg -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [UnknownArg] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, UnknownArg)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [UnknownArg])

Function UnknownArg Source # 
Instance details

Defined in OWL2.Function

type Rep UnknownArg 
Instance details

Defined in OWL2.ATC_OWL2

type Rep UnknownArg = D1 ('MetaData "UnknownArg" "OWL2.AS" "main" 'False) (C1 ('MetaCons "IndividualArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg)) :+: (C1 ('MetaCons "DataArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataArg)) :+: C1 ('MetaCons "Variable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Variable))))

data Atom Source #

Instances

Instances details
Eq Atom Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Atom -> Atom -> Bool

(/=) :: Atom -> Atom -> Bool

Data Atom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Atom -> c Atom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Atom

toConstr :: Atom -> Constr

dataTypeOf :: Atom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Atom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom)

gmapT :: (forall b. Data b => b -> b) -> Atom -> Atom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r

gmapQ :: (forall d. Data d => d -> u) -> Atom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Atom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Atom -> m Atom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom

Ord Atom Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Atom -> Atom -> Ordering

(<) :: Atom -> Atom -> Bool

(<=) :: Atom -> Atom -> Bool

(>) :: Atom -> Atom -> Bool

(>=) :: Atom -> Atom -> Bool

max :: Atom -> Atom -> Atom

min :: Atom -> Atom -> Atom

Show Atom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Atom -> ShowS

show :: Atom -> String

showList :: [Atom] -> ShowS

Generic Atom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Atom :: Type -> Type

Methods

from :: Atom -> Rep Atom x

to :: Rep Atom x -> Atom

FromJSON Atom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Atom

parseJSONList :: Value -> Parser [Atom]

ToJSON Atom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Atom -> Value

toEncoding :: Atom -> Encoding

toJSONList :: [Atom] -> Value

toEncodingList :: [Atom] -> Encoding

ShATermConvertible Atom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Atom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Atom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Atom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Atom])

Function Atom Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> Atom -> Atom Source #

type Rep Atom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Atom = D1 ('MetaData "Atom" "OWL2.AS" "main" 'False) (((C1 ('MetaCons "ClassAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg)) :+: C1 ('MetaCons "DataRangeAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataArg))) :+: (C1 ('MetaCons "ObjectPropertyAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg))) :+: C1 ('MetaCons "DataPropertyAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataProperty) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataArg))))) :+: ((C1 ('MetaCons "BuiltInAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataArg])) :+: C1 ('MetaCons "SameIndividualAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg))) :+: (C1 ('MetaCons "DifferentIndividualsAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg)) :+: (C1 ('MetaCons "UnknownUnaryAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownArg)) :+: C1 ('MetaCons "UnknownBinaryAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownArg)))))))

data DGAtom Source #

Instances

Instances details
Eq DGAtom Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: DGAtom -> DGAtom -> Bool

(/=) :: DGAtom -> DGAtom -> Bool

Data DGAtom Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DGAtom -> c DGAtom

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DGAtom

toConstr :: DGAtom -> Constr

dataTypeOf :: DGAtom -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DGAtom)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DGAtom)

gmapT :: (forall b. Data b => b -> b) -> DGAtom -> DGAtom

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DGAtom -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DGAtom -> r

gmapQ :: (forall d. Data d => d -> u) -> DGAtom -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DGAtom -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DGAtom -> m DGAtom

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DGAtom -> m DGAtom

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DGAtom -> m DGAtom

Ord DGAtom Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: DGAtom -> DGAtom -> Ordering

(<) :: DGAtom -> DGAtom -> Bool

(<=) :: DGAtom -> DGAtom -> Bool

(>) :: DGAtom -> DGAtom -> Bool

(>=) :: DGAtom -> DGAtom -> Bool

max :: DGAtom -> DGAtom -> DGAtom

min :: DGAtom -> DGAtom -> DGAtom

Show DGAtom Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DGAtom -> ShowS

show :: DGAtom -> String

showList :: [DGAtom] -> ShowS

Generic DGAtom 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DGAtom :: Type -> Type

Methods

from :: DGAtom -> Rep DGAtom x

to :: Rep DGAtom x -> DGAtom

FromJSON DGAtom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DGAtom

parseJSONList :: Value -> Parser [DGAtom]

ToJSON DGAtom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DGAtom -> Value

toEncoding :: DGAtom -> Encoding

toJSONList :: [DGAtom] -> Value

toEncodingList :: [DGAtom] -> Encoding

ShATermConvertible DGAtom 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DGAtom -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DGAtom] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DGAtom)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DGAtom])

Function DGAtom Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> DGAtom -> DGAtom Source #

type Rep DGAtom 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DGAtom = D1 ('MetaData "DGAtom" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DGClassAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassExpression) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg)) :+: C1 ('MetaCons "DGObjectPropertyAtom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectPropertyExpression) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndividualArg))))

data DGNodeAssertion Source #

Instances

Instances details
Eq DGNodeAssertion Source # 
Instance details

Defined in OWL2.AS

Data DGNodeAssertion Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DGNodeAssertion -> c DGNodeAssertion

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DGNodeAssertion

toConstr :: DGNodeAssertion -> Constr

dataTypeOf :: DGNodeAssertion -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DGNodeAssertion)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DGNodeAssertion)

gmapT :: (forall b. Data b => b -> b) -> DGNodeAssertion -> DGNodeAssertion

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DGNodeAssertion -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DGNodeAssertion -> r

gmapQ :: (forall d. Data d => d -> u) -> DGNodeAssertion -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DGNodeAssertion -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DGNodeAssertion -> m DGNodeAssertion

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DGNodeAssertion -> m DGNodeAssertion

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DGNodeAssertion -> m DGNodeAssertion

Ord DGNodeAssertion Source # 
Instance details

Defined in OWL2.AS

Show DGNodeAssertion Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DGNodeAssertion -> ShowS

show :: DGNodeAssertion -> String

showList :: [DGNodeAssertion] -> ShowS

Generic DGNodeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DGNodeAssertion :: Type -> Type

FromJSON DGNodeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DGNodeAssertion

parseJSONList :: Value -> Parser [DGNodeAssertion]

ToJSON DGNodeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DGNodeAssertion -> Value

toEncoding :: DGNodeAssertion -> Encoding

toJSONList :: [DGNodeAssertion] -> Value

toEncodingList :: [DGNodeAssertion] -> Encoding

ShATermConvertible DGNodeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DGNodeAssertion -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DGNodeAssertion] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DGNodeAssertion)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DGNodeAssertion])

Function DGNodeAssertion Source # 
Instance details

Defined in OWL2.Function

type Rep DGNodeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DGNodeAssertion = D1 ('MetaData "DGNodeAssertion" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DGNodeAssertion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Class) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGNode)))

data DGEdgeAssertion Source #

Instances

Instances details
Eq DGEdgeAssertion Source # 
Instance details

Defined in OWL2.AS

Data DGEdgeAssertion Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DGEdgeAssertion -> c DGEdgeAssertion

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DGEdgeAssertion

toConstr :: DGEdgeAssertion -> Constr

dataTypeOf :: DGEdgeAssertion -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DGEdgeAssertion)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DGEdgeAssertion)

gmapT :: (forall b. Data b => b -> b) -> DGEdgeAssertion -> DGEdgeAssertion

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DGEdgeAssertion -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DGEdgeAssertion -> r

gmapQ :: (forall d. Data d => d -> u) -> DGEdgeAssertion -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> DGEdgeAssertion -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DGEdgeAssertion -> m DGEdgeAssertion

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DGEdgeAssertion -> m DGEdgeAssertion

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DGEdgeAssertion -> m DGEdgeAssertion

Ord DGEdgeAssertion Source # 
Instance details

Defined in OWL2.AS

Show DGEdgeAssertion Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> DGEdgeAssertion -> ShowS

show :: DGEdgeAssertion -> String

showList :: [DGEdgeAssertion] -> ShowS

Generic DGEdgeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep DGEdgeAssertion :: Type -> Type

FromJSON DGEdgeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser DGEdgeAssertion

parseJSONList :: Value -> Parser [DGEdgeAssertion]

ToJSON DGEdgeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: DGEdgeAssertion -> Value

toEncoding :: DGEdgeAssertion -> Encoding

toJSONList :: [DGEdgeAssertion] -> Value

toEncodingList :: [DGEdgeAssertion] -> Encoding

ShATermConvertible DGEdgeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> DGEdgeAssertion -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [DGEdgeAssertion] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, DGEdgeAssertion)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [DGEdgeAssertion])

Function DGEdgeAssertion Source # 
Instance details

Defined in OWL2.Function

type Rep DGEdgeAssertion 
Instance details

Defined in OWL2.ATC_OWL2

type Rep DGEdgeAssertion = D1 ('MetaData "DGEdgeAssertion" "OWL2.AS" "main" 'False) (C1 ('MetaCons "DGEdgeAssertion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ObjectProperty) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGNode) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DGNode))))

data OntologySyntaxType Source #

Constructors

MS 
AS 
XML 

Instances

Instances details
Eq OntologySyntaxType Source # 
Instance details

Defined in OWL2.AS

Data OntologySyntaxType Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OntologySyntaxType -> c OntologySyntaxType

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OntologySyntaxType

toConstr :: OntologySyntaxType -> Constr

dataTypeOf :: OntologySyntaxType -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OntologySyntaxType)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OntologySyntaxType)

gmapT :: (forall b. Data b => b -> b) -> OntologySyntaxType -> OntologySyntaxType

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OntologySyntaxType -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OntologySyntaxType -> r

gmapQ :: (forall d. Data d => d -> u) -> OntologySyntaxType -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> OntologySyntaxType -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OntologySyntaxType -> m OntologySyntaxType

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologySyntaxType -> m OntologySyntaxType

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologySyntaxType -> m OntologySyntaxType

Ord OntologySyntaxType Source # 
Instance details

Defined in OWL2.AS

Show OntologySyntaxType Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> OntologySyntaxType -> ShowS

show :: OntologySyntaxType -> String

showList :: [OntologySyntaxType] -> ShowS

Generic OntologySyntaxType 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep OntologySyntaxType :: Type -> Type

FromJSON OntologySyntaxType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser OntologySyntaxType

parseJSONList :: Value -> Parser [OntologySyntaxType]

ToJSON OntologySyntaxType 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible OntologySyntaxType 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> OntologySyntaxType -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [OntologySyntaxType] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, OntologySyntaxType)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [OntologySyntaxType])

type Rep OntologySyntaxType 
Instance details

Defined in OWL2.ATC_OWL2

type Rep OntologySyntaxType = D1 ('MetaData "OntologySyntaxType" "OWL2.AS" "main" 'False) (C1 ('MetaCons "MS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XML" 'PrefixI 'False) (U1 :: Type -> Type)))

data OntologyMetadata Source #

Instances

Instances details
Eq OntologyMetadata Source # 
Instance details

Defined in OWL2.AS

Data OntologyMetadata Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OntologyMetadata -> c OntologyMetadata

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OntologyMetadata

toConstr :: OntologyMetadata -> Constr

dataTypeOf :: OntologyMetadata -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OntologyMetadata)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OntologyMetadata)

gmapT :: (forall b. Data b => b -> b) -> OntologyMetadata -> OntologyMetadata

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OntologyMetadata -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OntologyMetadata -> r

gmapQ :: (forall d. Data d => d -> u) -> OntologyMetadata -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> OntologyMetadata -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OntologyMetadata -> m OntologyMetadata

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologyMetadata -> m OntologyMetadata

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologyMetadata -> m OntologyMetadata

Ord OntologyMetadata Source # 
Instance details

Defined in OWL2.AS

Show OntologyMetadata Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> OntologyMetadata -> ShowS

show :: OntologyMetadata -> String

showList :: [OntologyMetadata] -> ShowS

Generic OntologyMetadata 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep OntologyMetadata :: Type -> Type

FromJSON OntologyMetadata 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser OntologyMetadata

parseJSONList :: Value -> Parser [OntologyMetadata]

ToJSON OntologyMetadata 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible OntologyMetadata 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> OntologyMetadata -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [OntologyMetadata] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, OntologyMetadata)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [OntologyMetadata])

type Rep OntologyMetadata 
Instance details

Defined in OWL2.ATC_OWL2

type Rep OntologyMetadata = D1 ('MetaData "OntologyMetadata" "OWL2.AS" "main" 'False) (C1 ('MetaCons "OntologyMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "syntaxType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OntologySyntaxType)))

data OntologyDocument Source #

Instances

Instances details
Eq OntologyDocument Source # 
Instance details

Defined in OWL2.AS

Data OntologyDocument Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OntologyDocument -> c OntologyDocument

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OntologyDocument

toConstr :: OntologyDocument -> Constr

dataTypeOf :: OntologyDocument -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OntologyDocument)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OntologyDocument)

gmapT :: (forall b. Data b => b -> b) -> OntologyDocument -> OntologyDocument

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OntologyDocument -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OntologyDocument -> r

gmapQ :: (forall d. Data d => d -> u) -> OntologyDocument -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> OntologyDocument -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OntologyDocument -> m OntologyDocument

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologyDocument -> m OntologyDocument

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OntologyDocument -> m OntologyDocument

Ord OntologyDocument Source # 
Instance details

Defined in OWL2.AS

Show OntologyDocument Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> OntologyDocument -> ShowS

show :: OntologyDocument -> String

showList :: [OntologyDocument] -> ShowS

Generic OntologyDocument 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep OntologyDocument :: Type -> Type

Semigroup OntologyDocument 
Instance details

Defined in OWL2.Logic_OWL2

Monoid OntologyDocument 
Instance details

Defined in OWL2.Logic_OWL2

GetRange OntologyDocument Source # 
Instance details

Defined in OWL2.AS

FromJSON OntologyDocument 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser OntologyDocument

parseJSONList :: Value -> Parser [OntologyDocument]

ToJSON OntologyDocument 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible OntologyDocument 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> OntologyDocument -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [OntologyDocument] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, OntologyDocument)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [OntologyDocument])

Pretty OntologyDocument Source # 
Instance details

Defined in OWL2.Pretty

Function OntologyDocument Source # 
Instance details

Defined in OWL2.Function

ProjectSublogic ProfSub OntologyDocument Source # 
Instance details

Defined in OWL2.Logic_OWL2

MinSublogic ProfSub OntologyDocument Source # 
Instance details

Defined in OWL2.Logic_OWL2

Syntax OWL2 OntologyDocument Entity SymbItems SymbMapItems Source # 
Instance details

Defined in OWL2.Logic_OWL2

StaticAnalysis OWL2 OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

basic_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, GlobalAnnos) -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom])) Source #

sen_analysis :: OWL2 -> Maybe ((OntologyDocument, Sign, Axiom) -> Result Axiom) Source #

extBasicAnalysis :: OWL2 -> IRI -> LibName -> OntologyDocument -> Sign -> GlobalAnnos -> Result (OntologyDocument, ExtSign Sign Entity, [Named Axiom]) Source #

stat_symb_map_items :: OWL2 -> Sign -> Maybe Sign -> [SymbMapItems] -> Result (EndoMap RawSymb) Source #

stat_symb_items :: OWL2 -> Sign -> [SymbItems] -> Result [RawSymb] Source #

convertTheory :: OWL2 -> Maybe ((Sign, [Named Axiom]) -> OntologyDocument) Source #

ensures_amalgamability :: OWL2 -> ([CASLAmalgOpt], Gr Sign (Int, OWLMorphism), [(Int, OWLMorphism)], Gr String String) -> Result Amalgamates Source #

quotient_term_algebra :: OWL2 -> OWLMorphism -> [Named Axiom] -> Result (Sign, [Named Axiom]) Source #

signature_colimit :: OWL2 -> Gr Sign (Int, OWLMorphism) -> Result (Sign, Map Int OWLMorphism) Source #

qualify :: OWL2 -> SIMPLE_ID -> LibName -> OWLMorphism -> Sign -> Result (OWLMorphism, [Named Axiom]) Source #

symbol_to_raw :: OWL2 -> Entity -> RawSymb Source #

id_to_raw :: OWL2 -> Id -> RawSymb Source #

matches :: OWL2 -> Entity -> RawSymb -> Bool Source #

empty_signature :: OWL2 -> Sign Source #

add_symb_to_sign :: OWL2 -> Sign -> Entity -> Result Sign Source #

signature_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

signatureDiff :: OWL2 -> Sign -> Sign -> Result Sign Source #

intersection :: OWL2 -> Sign -> Sign -> Result Sign Source #

final_union :: OWL2 -> Sign -> Sign -> Result Sign Source #

morphism_union :: OWL2 -> OWLMorphism -> OWLMorphism -> Result OWLMorphism Source #

is_subsig :: OWL2 -> Sign -> Sign -> Bool Source #

subsig_inclusion :: OWL2 -> Sign -> Sign -> Result OWLMorphism Source #

generated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

cogenerated_sign :: OWL2 -> Set Entity -> Sign -> Result OWLMorphism Source #

induced_from_morphism :: OWL2 -> EndoMap RawSymb -> Sign -> Result OWLMorphism Source #

induced_from_to_morphism :: OWL2 -> EndoMap RawSymb -> ExtSign Sign Entity -> ExtSign Sign Entity -> Result OWLMorphism Source #

is_transportable :: OWL2 -> OWLMorphism -> Bool Source #

is_injective :: OWL2 -> OWLMorphism -> Bool Source #

theory_to_taxonomy :: OWL2 -> TaxoGraphKind -> MMiSSOntology -> Sign -> [Named Axiom] -> Result MMiSSOntology Source #

corresp2th :: OWL2 -> String -> Bool -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> EndoMap Entity -> EndoMap Entity -> REL_REF -> Result (Sign, [Named Axiom], Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

equiv2cospan :: OWL2 -> Sign -> Sign -> [SymbItems] -> [SymbItems] -> Result (Sign, Sign, Sign, EndoMap Entity, EndoMap Entity) Source #

extract_module :: OWL2 -> [IRI] -> (Sign, [Named Axiom]) -> Result (Sign, [Named Axiom]) Source #

Logic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Logic_OWL2

Methods

parse_basic_sen :: OWL2 -> Maybe (OntologyDocument -> AParser st Axiom) Source #

stability :: OWL2 -> Stability Source #

data_logic :: OWL2 -> Maybe AnyLogic Source #

top_sublogic :: OWL2 -> ProfSub Source #

all_sublogics :: OWL2 -> [ProfSub] Source #

bottomSublogic :: OWL2 -> Maybe ProfSub Source #

sublogicDimensions :: OWL2 -> [[ProfSub]] Source #

parseSublogic :: OWL2 -> String -> Maybe ProfSub Source #

proj_sublogic_epsilon :: OWL2 -> ProfSub -> Sign -> OWLMorphism Source #

provers :: OWL2 -> [Prover Sign Axiom OWLMorphism ProfSub ProofTree] Source #

default_prover :: OWL2 -> String Source #

cons_checkers :: OWL2 -> [ConsChecker Sign Axiom ProfSub OWLMorphism ProofTree] Source #

conservativityCheck :: OWL2 -> [ConservativityChecker Sign Axiom OWLMorphism] Source #

empty_proof_tree :: OWL2 -> ProofTree Source #

syntaxTable :: OWL2 -> Sign -> Maybe SyntaxTable Source #

omdoc_metatheory :: OWL2 -> Maybe OMCD Source #

export_symToOmdoc :: OWL2 -> NameMap Entity -> Entity -> String -> Result TCElement Source #

export_senToOmdoc :: OWL2 -> NameMap Entity -> Axiom -> Result TCorOMElement Source #

export_theoryToOmdoc :: OWL2 -> SigMap Entity -> Sign -> [Named Axiom] -> Result [TCElement] Source #

omdocToSym :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result Entity Source #

omdocToSen :: OWL2 -> SigMapI Entity -> TCElement -> String -> Result (Maybe (Named Axiom)) Source #

addOMadtToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [[OmdADT]] -> Result (Sign, [Named Axiom]) Source #

addOmdocToTheory :: OWL2 -> SigMapI Entity -> (Sign, [Named Axiom]) -> [TCElement] -> Result (Sign, [Named Axiom]) Source #

sublogicOfTheo :: OWL2 -> (Sign, [Axiom]) -> ProfSub Source #

Comorphism Propositional2OWL2 Propositional PropSL BASIC_SPEC FORMULA SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.Propositional2OWL2

Comorphism OWL22NeSyPatterns OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree NeSyPatterns () BASIC_SPEC () SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22NeSyPatterns

Comorphism OWL22CommonLogic OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CommonLogic CommonLogicSL BASIC_SPEC TEXT_META SYMB_ITEMS SYMB_MAP_ITEMS Sign Morphism Symbol Symbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CommonLogic

Comorphism OWL22CASL OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree Source # 
Instance details

Defined in OWL2.OWL22CASL

Comorphism CASL2OWL CASL CASL_Sublogics CASLBasicSpec CASLFORMULA SYMB_ITEMS SYMB_MAP_ITEMS CASLSign CASLMor Symbol RawSymbol ProofTree OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.CASL2OWL

Comorphism ExtModal2OWL ExtModal ExtModalSL EM_BASIC_SPEC ExtModalFORMULA SYMB_ITEMS SYMB_MAP_ITEMS ExtModalSign ExtModalMorph Symbol RawSymbol () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in Comorphisms.ExtModal2OWL

Comorphism DMU2OWL2 DMU () Text () () () Text (DefaultMorphism Text) () () () OWL2 ProfSub OntologyDocument Axiom SymbItems SymbMapItems Sign OWLMorphism Entity RawSymb ProofTree Source # 
Instance details

Defined in OWL2.DMU2OWL2

type Rep OntologyDocument 
Instance details

Defined in OWL2.ATC_OWL2

type Rep OntologyDocument = D1 ('MetaData "OntologyDocument" "OWL2.AS" "main" 'False) (C1 ('MetaCons "OntologyDocument" 'PrefixI 'True) (S1 ('MetaSel ('Just "ontologyMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OntologyMetadata) :*: (S1 ('MetaSel ('Just "prefixDeclaration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixMap) :*: S1 ('MetaSel ('Just "ontology") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ontology))))

data PrefixDeclaration Source #

Instances

Instances details
Eq PrefixDeclaration Source # 
Instance details

Defined in OWL2.AS

Data PrefixDeclaration Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrefixDeclaration -> c PrefixDeclaration

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrefixDeclaration

toConstr :: PrefixDeclaration -> Constr

dataTypeOf :: PrefixDeclaration -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrefixDeclaration)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrefixDeclaration)

gmapT :: (forall b. Data b => b -> b) -> PrefixDeclaration -> PrefixDeclaration

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrefixDeclaration -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrefixDeclaration -> r

gmapQ :: (forall d. Data d => d -> u) -> PrefixDeclaration -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrefixDeclaration -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrefixDeclaration -> m PrefixDeclaration

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrefixDeclaration -> m PrefixDeclaration

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrefixDeclaration -> m PrefixDeclaration

Ord PrefixDeclaration Source # 
Instance details

Defined in OWL2.AS

Show PrefixDeclaration Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> PrefixDeclaration -> ShowS

show :: PrefixDeclaration -> String

showList :: [PrefixDeclaration] -> ShowS

Generic PrefixDeclaration 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep PrefixDeclaration :: Type -> Type

FromJSON PrefixDeclaration 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser PrefixDeclaration

parseJSONList :: Value -> Parser [PrefixDeclaration]

ToJSON PrefixDeclaration 
Instance details

Defined in OWL2.ATC_OWL2

ShATermConvertible PrefixDeclaration 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> PrefixDeclaration -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [PrefixDeclaration] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, PrefixDeclaration)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [PrefixDeclaration])

Function PrefixDeclaration Source # 
Instance details

Defined in OWL2.Function

type Rep PrefixDeclaration 
Instance details

Defined in OWL2.ATC_OWL2

type Rep PrefixDeclaration = D1 ('MetaData "PrefixDeclaration" "OWL2.AS" "main" 'False) (C1 ('MetaCons "PrefixDeclaration" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRI)))

type PrefixName = String Source #

data Ontology Source #

Instances

Instances details
Eq Ontology Source # 
Instance details

Defined in OWL2.AS

Methods

(==) :: Ontology -> Ontology -> Bool

(/=) :: Ontology -> Ontology -> Bool

Data Ontology Source # 
Instance details

Defined in OWL2.AS

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ontology -> c Ontology

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ontology

toConstr :: Ontology -> Constr

dataTypeOf :: Ontology -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ontology)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ontology)

gmapT :: (forall b. Data b => b -> b) -> Ontology -> Ontology

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ontology -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ontology -> r

gmapQ :: (forall d. Data d => d -> u) -> Ontology -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ontology -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ontology -> m Ontology

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ontology -> m Ontology

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ontology -> m Ontology

Ord Ontology Source # 
Instance details

Defined in OWL2.AS

Methods

compare :: Ontology -> Ontology -> Ordering

(<) :: Ontology -> Ontology -> Bool

(<=) :: Ontology -> Ontology -> Bool

(>) :: Ontology -> Ontology -> Bool

(>=) :: Ontology -> Ontology -> Bool

max :: Ontology -> Ontology -> Ontology

min :: Ontology -> Ontology -> Ontology

Show Ontology Source # 
Instance details

Defined in OWL2.AS

Methods

showsPrec :: Int -> Ontology -> ShowS

show :: Ontology -> String

showList :: [Ontology] -> ShowS

Generic Ontology 
Instance details

Defined in OWL2.ATC_OWL2

Associated Types

type Rep Ontology :: Type -> Type

Methods

from :: Ontology -> Rep Ontology x

to :: Rep Ontology x -> Ontology

Semigroup Ontology 
Instance details

Defined in OWL2.Logic_OWL2

Methods

(<>) :: Ontology -> Ontology -> Ontology #

sconcat :: NonEmpty Ontology -> Ontology

stimes :: Integral b => b -> Ontology -> Ontology

Monoid Ontology 
Instance details

Defined in OWL2.Logic_OWL2

FromJSON Ontology 
Instance details

Defined in OWL2.ATC_OWL2

Methods

parseJSON :: Value -> Parser Ontology

parseJSONList :: Value -> Parser [Ontology]

ToJSON Ontology 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toJSON :: Ontology -> Value

toEncoding :: Ontology -> Encoding

toJSONList :: [Ontology] -> Value

toEncodingList :: [Ontology] -> Encoding

ShATermConvertible Ontology 
Instance details

Defined in OWL2.ATC_OWL2

Methods

toShATermAux :: ATermTable -> Ontology -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [Ontology] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, Ontology)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [Ontology])

Function Ontology Source # 
Instance details

Defined in OWL2.Function

type Rep Ontology 
Instance details

Defined in OWL2.ATC_OWL2

type Rep Ontology = D1 ('MetaData "Ontology" "OWL2.AS" "main" 'False) (C1 ('MetaCons "Ontology" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mOntologyIRI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe OntologyIRI)) :*: S1 ('MetaSel ('Just "mOntologyVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe VersionIRI))) :*: (S1 ('MetaSel ('Just "importsDocuments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DirectlyImportsDocuments) :*: (S1 ('MetaSel ('Just "ontologyAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OntologyAnnotations) :*: S1 ('MetaSel ('Just "axioms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Axiom])))))