Copyright | (c) C. Maeder Felix Gabriel Mance |
---|---|
License | GPLv2 or higher, see LICENSE.txt |
Maintainer | Alexander.Koslowski@st.ovgu.de |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
OWL 2 Functional Syntax constructs
References: http://www.w3.org/TR/2009/REC-owl2-syntax-20091027/#Functional-Style_Syntax http://www.w3.org/TR/owl2-manchester-syntax/
Synopsis
- isAnonymous :: IRI -> Bool
- type PrefixMap = Map String String
- changePrefixMapTypeToString :: PrefixMap -> PrefixMap
- changePrefixMapTypeToGA :: PrefixMap -> PrefixMap
- predefPrefixesGA :: PrefixMap
- predefPrefixes :: PrefixMap
- plainDatatypeIRI :: IRI
- topDataProperty :: IRI
- topObjectProperty :: IRI
- owlThing :: IRI
- bottomObjectProperty :: IRI
- type LexicalForm = String
- type LanguageTag = String
- type ImportIRI = IRI
- type OntologyIRI = IRI
- type VersionIRI = IRI
- type Class = IRI
- type Datatype = IRI
- type ObjectProperty = IRI
- type DataProperty = IRI
- type DirectlyImportsDocuments = [IRI]
- type AnnotationProperty = IRI
- type Individual = IRI
- type AnonymousIndividual = IRI
- type NamedIndividual = IRI
- data EquivOrDisjoint
- showEquivOrDisjoint :: EquivOrDisjoint -> String
- data DomainOrRange
- showDomainOrRange :: DomainOrRange -> String
- data SameOrDifferent
- showSameOrDifferent :: SameOrDifferent -> String
- data Relation
- showRelation :: Relation -> String
- getED :: Relation -> EquivOrDisjoint
- getDR :: Relation -> DomainOrRange
- getSD :: Relation -> SameOrDifferent
- data Character
- data PositiveOrNegative
- data QuantifierType
- showQuantifierType :: QuantifierType -> String
- thingMap :: PreDefMaps
- isThing :: IRI -> Bool
- makePredefObjProp :: PreDefMaps
- isPredefObjProp :: IRI -> Bool
- makePredefDataProp :: PreDefMaps
- isPredefDataProp :: IRI -> Bool
- makePredefRDFSAnnoProp :: PreDefMaps
- isPredefRDFSAnnoProp :: IRI -> Bool
- makePredefOWLAnnoProp :: PreDefMaps
- isPredefOWLAnnoProp :: IRI -> Bool
- isPredefAnnoProp :: IRI -> Bool
- isPredefPropOrClass :: IRI -> Bool
- predefIRIs :: Set IRI
- isDatatypeKey :: IRI -> Bool
- isSWRLBuiltIn :: IRI -> Bool
- xsdMap :: PreDefMaps
- owlNumbersMap :: PreDefMaps
- rdfMap :: PreDefMaps
- rdfsMap :: PreDefMaps
- isDatatypeKeyAux :: IRI -> [(String, String)]
- type PreDefMaps = ([String], String, String)
- preDefMaps :: [String] -> String -> PreDefMaps
- checkPredefAux :: PreDefMaps -> IRI -> Maybe (String, String)
- checkPredef :: PreDefMaps -> IRI -> Bool
- makeOWLPredefMaps :: [String] -> PreDefMaps
- setDatatypePrefix :: IRI -> IRI
- setReservedPrefix :: IRI -> IRI
- stripReservedPrefix :: IRI -> IRI
- uriToId :: IRI -> Id
- getPredefName :: IRI -> String
- uriToTok :: IRI -> Token
- entityToId :: Entity -> Id
- printDatatype :: IRI -> String
- data DatatypeCat
- getDatatypeCat :: IRI -> DatatypeCat
- makeXsdMap :: [String] -> PreDefMaps
- xsdBooleanMap :: PreDefMaps
- xsdNumbersMap :: PreDefMaps
- xsdStringsMap :: PreDefMaps
- facetToIRI :: DatatypeFacet -> ConstrainingFacet
- facetToIRINoSign :: DatatypeFacet -> ConstrainingFacet
- symsOfAxiom :: Axiom -> Set Entity
- symsOfDGAtoms :: [DGAtom] -> Set Entity
- symsOfDLSafeAtoms :: [Atom] -> Set Entity
- symsOfIArg :: IndividualArg -> Set Entity
- symsOfDGEdges :: DGEdges -> Set Entity
- symsOfObjectPropertyExpression :: ObjectPropertyExpression -> Set Entity
- symsOfClassExpression :: ClassExpression -> Set Entity
- symsOfDataRange :: DataRange -> Set Entity
- symsOfAnnotation :: Annotation -> Set Entity
- symsOfAnnotations :: [Annotation] -> Set Entity
- data CardinalityType
- showCardinalityType :: CardinalityType -> String
- data Cardinality a b = Cardinality CardinalityType Int a (Maybe b)
- data JunctionType
- type ConstrainingFacet = IRI
- type RestrictionValue = Literal
- data Entity = Entity {
- label :: Maybe String
- entityKind :: EntityType
- cutIRI :: IRI
- mkEntity :: EntityType -> IRI -> Entity
- mkEntityLbl :: String -> EntityType -> IRI -> Entity
- data EntityType
- showEntityType :: EntityType -> String
- entityTypes :: [EntityType]
- pairSymbols :: Entity -> Entity -> Result Entity
- data TypedOrUntyped
- = Typed Datatype
- | Untyped (Maybe LanguageTag)
- data Literal
- data NNInt = NNInt [Int]
- zeroNNInt :: NNInt
- isZeroNNInt :: NNInt -> Bool
- data IntLit = IntLit {}
- zeroInt :: IntLit
- isZeroInt :: IntLit -> Bool
- negNNInt :: Bool -> NNInt -> IntLit
- negInt :: IntLit -> IntLit
- data DecLit = DecLit {}
- isDecInt :: DecLit -> Bool
- negDec :: Bool -> DecLit -> DecLit
- data FloatLit = FloatLit {}
- isFloatDec :: FloatLit -> Bool
- isFloatInt :: FloatLit -> Bool
- floatToInt :: FloatLit -> IntLit
- intToDec :: IntLit -> DecLit
- decToFloat :: DecLit -> FloatLit
- intToFloat :: IntLit -> FloatLit
- abInt :: IntLit -> IntLit
- abDec :: DecLit -> DecLit
- abFloat :: FloatLit -> FloatLit
- isNegDec :: DecLit -> Bool
- numberName :: FloatLit -> String
- litType :: Literal -> Maybe IRI
- cTypeS :: String
- type InverseObjectProperty = ObjectPropertyExpression
- data ObjectPropertyExpression
- isObjectProperty :: ObjectPropertyExpression -> Bool
- objPropToIRI :: ObjectPropertyExpression -> IRI
- inverseOf :: ObjectPropertyExpression -> ObjectPropertyExpression
- type DataPropertyExpression = DataProperty
- data DataRange
- basedOn :: DataRange -> [Datatype]
- data ClassExpression
- = Expression Class
- | ObjectJunction JunctionType [ClassExpression]
- | ObjectComplementOf ClassExpression
- | ObjectOneOf [Individual]
- | ObjectValuesFrom QuantifierType ObjectPropertyExpression ClassExpression
- | ObjectHasValue ObjectPropertyExpression Individual
- | ObjectHasSelf ObjectPropertyExpression
- | ObjectCardinality (Cardinality ObjectPropertyExpression ClassExpression)
- | DataValuesFrom QuantifierType [DataPropertyExpression] DataRange
- | DataHasValue DataPropertyExpression Literal
- | DataCardinality (Cardinality DataPropertyExpression DataRange)
- data Annotation = Annotation {}
- type OntologyAnnotations = [Annotation]
- data AnnotationValue
- data AnnotationAxiom
- = AnnotationAssertion AxiomAnnotations AnnotationProperty AnnotationSubject AnnotationValue
- | SubAnnotationPropertyOf AxiomAnnotations SubAnnotationProperty SuperAnnotationProperty
- | AnnotationPropertyDomain AxiomAnnotations AnnotationProperty IRI
- | AnnotationPropertyRange AxiomAnnotations AnnotationProperty IRI
- data AnnotationSubject
- type SubAnnotationProperty = AnnotationProperty
- type SuperAnnotationProperty = AnnotationProperty
- data Axiom
- = Declaration AxiomAnnotations Entity
- | ClassAxiom ClassAxiom
- | ObjectPropertyAxiom ObjectPropertyAxiom
- | DataPropertyAxiom DataPropertyAxiom
- | DatatypeDefinition AxiomAnnotations Datatype DataRange
- | HasKey AxiomAnnotations ClassExpression [ObjectPropertyExpression] [DataPropertyExpression]
- | Assertion Assertion
- | AnnotationAxiom AnnotationAxiom
- | Rule Rule
- | DGAxiom AxiomAnnotations DGName DGNodes DGEdges MainClasses
- type AxiomAnnotations = [Annotation]
- type SubClassExpression = ClassExpression
- type SuperClassExpression = ClassExpression
- type DisjointClassExpression = [ClassExpression]
- data ClassAxiom
- data ObjectPropertyAxiom
- = SubObjectPropertyOf AxiomAnnotations SubObjectPropertyExpression SuperObjectPropertyExpression
- | EquivalentObjectProperties AxiomAnnotations [ObjectPropertyExpression]
- | DisjointObjectProperties AxiomAnnotations [ObjectPropertyExpression]
- | InverseObjectProperties AxiomAnnotations ObjectPropertyExpression ObjectPropertyExpression
- | ObjectPropertyDomain AxiomAnnotations ObjectPropertyExpression ClassExpression
- | ObjectPropertyRange AxiomAnnotations ObjectPropertyExpression ClassExpression
- | FunctionalObjectProperty AxiomAnnotations ObjectPropertyExpression
- | InverseFunctionalObjectProperty AxiomAnnotations ObjectPropertyExpression
- | ReflexiveObjectProperty AxiomAnnotations ObjectPropertyExpression
- | IrreflexiveObjectProperty AxiomAnnotations ObjectPropertyExpression
- | SymmetricObjectProperty AxiomAnnotations ObjectPropertyExpression
- | AsymmetricObjectProperty AxiomAnnotations ObjectPropertyExpression
- | TransitiveObjectProperty AxiomAnnotations ObjectPropertyExpression
- type PropertyExpressionChain = [ObjectPropertyExpression]
- type SuperObjectPropertyExpression = ObjectPropertyExpression
- data SubObjectPropertyExpression
- data DataPropertyAxiom
- = SubDataPropertyOf AxiomAnnotations SubDataPropertyExpression SuperDataPropertyExpression
- | EquivalentDataProperties AxiomAnnotations [DataPropertyExpression]
- | DisjointDataProperties AxiomAnnotations [DataPropertyExpression]
- | DataPropertyDomain AxiomAnnotations DataPropertyExpression ClassExpression
- | DataPropertyRange AxiomAnnotations DataPropertyExpression DataRange
- | FunctionalDataProperty AxiomAnnotations DataPropertyExpression
- type SubDataPropertyExpression = DataPropertyExpression
- type SuperDataPropertyExpression = DataPropertyExpression
- data Assertion
- = SameIndividual AxiomAnnotations [Individual]
- | DifferentIndividuals AxiomAnnotations [Individual]
- | ClassAssertion AxiomAnnotations ClassExpression Individual
- | ObjectPropertyAssertion AxiomAnnotations ObjectPropertyExpression SourceIndividual TargetIndividual
- | NegativeObjectPropertyAssertion AxiomAnnotations ObjectPropertyExpression SourceIndividual TargetIndividual
- | DataPropertyAssertion AxiomAnnotations DataPropertyExpression SourceIndividual TargetValue
- | NegativeDataPropertyAssertion AxiomAnnotations DataPropertyExpression SourceIndividual TargetValue
- type SourceIndividual = Individual
- type TargetIndividual = Individual
- type TargetValue = Literal
- data Rule
- type Body = [Atom]
- type Head = [Atom]
- type DGBody = [DGAtom]
- type DGHead = [DGAtom]
- data IndividualArg
- data DataArg
- type IndividualVar = Variable
- type DataVar = Variable
- type Variable = IRI
- data UnknownArg
- data Atom
- = ClassAtom ClassExpression IndividualArg
- | DataRangeAtom DataRange DataArg
- | ObjectPropertyAtom ObjectPropertyExpression IndividualArg IndividualArg
- | DataPropertyAtom DataProperty IndividualArg DataArg
- | BuiltInAtom IRI [DataArg]
- | SameIndividualAtom IndividualArg IndividualArg
- | DifferentIndividualsAtom IndividualArg IndividualArg
- | UnknownUnaryAtom IRI UnknownArg
- | UnknownBinaryAtom IRI UnknownArg UnknownArg
- getVariablesFromIArg :: IndividualArg -> Set Variable
- getVariablesFromDArg :: DataArg -> Set Variable
- getVariablesFromAtom :: Atom -> Set Variable
- data DGAtom
- type DGName = IRI
- type DGNodes = [DGNodeAssertion]
- type DGEdges = [DGEdgeAssertion]
- type MainClasses = [Class]
- data DGNodeAssertion = DGNodeAssertion Class DGNode
- type DGNode = IRI
- data DGEdgeAssertion = DGEdgeAssertion ObjectProperty DGNode DGNode
- emptyOntology :: Ontology
- emptyOntologyDoc :: OntologyDocument
- data OntologySyntaxType
- data OntologyMetadata = OntologyMetadata {}
- changeSyntax :: OntologySyntaxType -> OntologyDocument -> OntologyDocument
- data OntologyDocument = OntologyDocument {}
- data PrefixDeclaration = PrefixDeclaration PrefixName IRI
- type PrefixName = String
- data Ontology = Ontology {}
Documentation
isAnonymous :: IRI -> Bool Source #
checks if an IRI is an anonymous individual
type LexicalForm = String Source #
type LanguageTag = String Source #
type OntologyIRI = IRI Source #
type VersionIRI = IRI Source #
type ObjectProperty = IRI Source #
type DataProperty = IRI Source #
type DirectlyImportsDocuments = [IRI] Source #
type AnnotationProperty = IRI Source #
type Individual = IRI Source #
type AnonymousIndividual = IRI Source #
type NamedIndividual = IRI Source #
data EquivOrDisjoint Source #
Instances
Eq EquivOrDisjoint Source # | |
Defined in OWL2.AS (==) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool (/=) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool | |
Data EquivOrDisjoint Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: EquivOrDisjoint -> EquivOrDisjoint -> Ordering (<) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool (<=) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool (>) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool (>=) :: EquivOrDisjoint -> EquivOrDisjoint -> Bool max :: EquivOrDisjoint -> EquivOrDisjoint -> EquivOrDisjoint min :: EquivOrDisjoint -> EquivOrDisjoint -> EquivOrDisjoint | |
Show EquivOrDisjoint Source # | |
Defined in OWL2.AS showsPrec :: Int -> EquivOrDisjoint -> ShowS show :: EquivOrDisjoint -> String showList :: [EquivOrDisjoint] -> ShowS | |
Generic EquivOrDisjoint | |
Defined in OWL2.ATC_OWL2 type Rep EquivOrDisjoint :: Type -> Type from :: EquivOrDisjoint -> Rep EquivOrDisjoint x to :: Rep EquivOrDisjoint x -> EquivOrDisjoint | |
FromJSON EquivOrDisjoint | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser EquivOrDisjoint parseJSONList :: Value -> Parser [EquivOrDisjoint] | |
ToJSON EquivOrDisjoint | |
Defined in OWL2.ATC_OWL2 toJSON :: EquivOrDisjoint -> Value toEncoding :: EquivOrDisjoint -> Encoding toJSONList :: [EquivOrDisjoint] -> Value toEncodingList :: [EquivOrDisjoint] -> Encoding | |
ShATermConvertible EquivOrDisjoint | |
Defined in OWL2.ATC_OWL2 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 | |
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)) |
showEquivOrDisjoint :: EquivOrDisjoint -> String Source #
data DomainOrRange Source #
Instances
Eq DomainOrRange Source # | |
Defined in OWL2.AS (==) :: DomainOrRange -> DomainOrRange -> Bool (/=) :: DomainOrRange -> DomainOrRange -> Bool | |
Data DomainOrRange Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: DomainOrRange -> DomainOrRange -> Ordering (<) :: DomainOrRange -> DomainOrRange -> Bool (<=) :: DomainOrRange -> DomainOrRange -> Bool (>) :: DomainOrRange -> DomainOrRange -> Bool (>=) :: DomainOrRange -> DomainOrRange -> Bool max :: DomainOrRange -> DomainOrRange -> DomainOrRange min :: DomainOrRange -> DomainOrRange -> DomainOrRange | |
Show DomainOrRange Source # | |
Defined in OWL2.AS showsPrec :: Int -> DomainOrRange -> ShowS show :: DomainOrRange -> String showList :: [DomainOrRange] -> ShowS | |
Generic DomainOrRange | |
Defined in OWL2.ATC_OWL2 type Rep DomainOrRange :: Type -> Type from :: DomainOrRange -> Rep DomainOrRange x to :: Rep DomainOrRange x -> DomainOrRange | |
FromJSON DomainOrRange | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DomainOrRange parseJSONList :: Value -> Parser [DomainOrRange] | |
ToJSON DomainOrRange | |
Defined in OWL2.ATC_OWL2 toJSON :: DomainOrRange -> Value toEncoding :: DomainOrRange -> Encoding toJSONList :: [DomainOrRange] -> Value toEncodingList :: [DomainOrRange] -> Encoding | |
ShATermConvertible DomainOrRange | |
Defined in OWL2.ATC_OWL2 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 | |
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)) |
showDomainOrRange :: DomainOrRange -> String Source #
data SameOrDifferent Source #
Instances
Eq SameOrDifferent Source # | |
Defined in OWL2.AS (==) :: SameOrDifferent -> SameOrDifferent -> Bool (/=) :: SameOrDifferent -> SameOrDifferent -> Bool | |
Data SameOrDifferent Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: SameOrDifferent -> SameOrDifferent -> Ordering (<) :: SameOrDifferent -> SameOrDifferent -> Bool (<=) :: SameOrDifferent -> SameOrDifferent -> Bool (>) :: SameOrDifferent -> SameOrDifferent -> Bool (>=) :: SameOrDifferent -> SameOrDifferent -> Bool max :: SameOrDifferent -> SameOrDifferent -> SameOrDifferent min :: SameOrDifferent -> SameOrDifferent -> SameOrDifferent | |
Show SameOrDifferent Source # | |
Defined in OWL2.AS showsPrec :: Int -> SameOrDifferent -> ShowS show :: SameOrDifferent -> String showList :: [SameOrDifferent] -> ShowS | |
Generic SameOrDifferent | |
Defined in OWL2.ATC_OWL2 type Rep SameOrDifferent :: Type -> Type from :: SameOrDifferent -> Rep SameOrDifferent x to :: Rep SameOrDifferent x -> SameOrDifferent | |
FromJSON SameOrDifferent | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser SameOrDifferent parseJSONList :: Value -> Parser [SameOrDifferent] | |
ToJSON SameOrDifferent | |
Defined in OWL2.ATC_OWL2 toJSON :: SameOrDifferent -> Value toEncoding :: SameOrDifferent -> Encoding toJSONList :: [SameOrDifferent] -> Value toEncodingList :: [SameOrDifferent] -> Encoding | |
ShATermConvertible SameOrDifferent | |
Defined in OWL2.ATC_OWL2 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 | |
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)) |
showSameOrDifferent :: SameOrDifferent -> String Source #
EDRelation EquivOrDisjoint | |
SubPropertyOf | |
InverseOf | |
SubClass | |
Types | |
DRRelation DomainOrRange | |
SDRelation SameOrDifferent |
Instances
Eq Relation Source # | |
Data Relation Source # | |
Defined in OWL2.AS 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 # | |
Show Relation Source # | |
Generic Relation | |
FromJSON Relation | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Relation parseJSONList :: Value -> Parser [Relation] | |
ToJSON Relation | |
Defined in OWL2.ATC_OWL2 toEncoding :: Relation -> Encoding toJSONList :: [Relation] -> Value toEncodingList :: [Relation] -> Encoding | |
ShATermConvertible Relation | |
Defined in OWL2.ATC_OWL2 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 | |
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))))) |
showRelation :: Relation -> String Source #
getED :: Relation -> EquivOrDisjoint Source #
getDR :: Relation -> DomainOrRange Source #
getSD :: Relation -> SameOrDifferent Source #
Instances
Bounded Character Source # | |
Enum Character Source # | |
Eq Character Source # | |
Data Character Source # | |
Defined in OWL2.AS 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 # | |
Show Character Source # | |
Generic Character | |
FromJSON Character | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Character parseJSONList :: Value -> Parser [Character] | |
ToJSON Character | |
Defined in OWL2.ATC_OWL2 toEncoding :: Character -> Encoding toJSONList :: [Character] -> Value toEncodingList :: [Character] -> Encoding | |
ShATermConvertible Character | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep Character | |
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 #
Instances
Eq PositiveOrNegative Source # | |
Defined in OWL2.AS (==) :: PositiveOrNegative -> PositiveOrNegative -> Bool (/=) :: PositiveOrNegative -> PositiveOrNegative -> Bool | |
Data PositiveOrNegative Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: PositiveOrNegative -> PositiveOrNegative -> Ordering (<) :: PositiveOrNegative -> PositiveOrNegative -> Bool (<=) :: PositiveOrNegative -> PositiveOrNegative -> Bool (>) :: PositiveOrNegative -> PositiveOrNegative -> Bool (>=) :: PositiveOrNegative -> PositiveOrNegative -> Bool max :: PositiveOrNegative -> PositiveOrNegative -> PositiveOrNegative min :: PositiveOrNegative -> PositiveOrNegative -> PositiveOrNegative | |
Show PositiveOrNegative Source # | |
Defined in OWL2.AS showsPrec :: Int -> PositiveOrNegative -> ShowS show :: PositiveOrNegative -> String showList :: [PositiveOrNegative] -> ShowS | |
Generic PositiveOrNegative | |
Defined in OWL2.ATC_OWL2 type Rep PositiveOrNegative :: Type -> Type from :: PositiveOrNegative -> Rep PositiveOrNegative x to :: Rep PositiveOrNegative x -> PositiveOrNegative | |
FromJSON PositiveOrNegative | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser PositiveOrNegative parseJSONList :: Value -> Parser [PositiveOrNegative] | |
ToJSON PositiveOrNegative | |
Defined in OWL2.ATC_OWL2 toJSON :: PositiveOrNegative -> Value toEncoding :: PositiveOrNegative -> Encoding toJSONList :: [PositiveOrNegative] -> Value toEncodingList :: [PositiveOrNegative] -> Encoding | |
ShATermConvertible PositiveOrNegative | |
Defined in OWL2.ATC_OWL2 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 | |
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
Eq QuantifierType Source # | |
Defined in OWL2.AS (==) :: QuantifierType -> QuantifierType -> Bool (/=) :: QuantifierType -> QuantifierType -> Bool | |
Data QuantifierType Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: QuantifierType -> QuantifierType -> Ordering (<) :: QuantifierType -> QuantifierType -> Bool (<=) :: QuantifierType -> QuantifierType -> Bool (>) :: QuantifierType -> QuantifierType -> Bool (>=) :: QuantifierType -> QuantifierType -> Bool max :: QuantifierType -> QuantifierType -> QuantifierType min :: QuantifierType -> QuantifierType -> QuantifierType | |
Show QuantifierType Source # | |
Defined in OWL2.AS showsPrec :: Int -> QuantifierType -> ShowS show :: QuantifierType -> String showList :: [QuantifierType] -> ShowS | |
Generic QuantifierType | |
Defined in OWL2.ATC_OWL2 type Rep QuantifierType :: Type -> Type from :: QuantifierType -> Rep QuantifierType x to :: Rep QuantifierType x -> QuantifierType | |
FromJSON QuantifierType | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser QuantifierType parseJSONList :: Value -> Parser [QuantifierType] | |
ToJSON QuantifierType | |
Defined in OWL2.ATC_OWL2 toJSON :: QuantifierType -> Value toEncoding :: QuantifierType -> Encoding toJSONList :: [QuantifierType] -> Value toEncodingList :: [QuantifierType] -> Encoding | |
ShATermConvertible QuantifierType | |
Defined in OWL2.ATC_OWL2 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 | |
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)) |
showQuantifierType :: QuantifierType -> String Source #
Predefined IRI checkings
isPredefObjProp :: IRI -> Bool Source #
isPredefDataProp :: IRI -> Bool Source #
isPredefRDFSAnnoProp :: IRI -> Bool Source #
isPredefOWLAnnoProp :: IRI -> Bool Source #
isPredefAnnoProp :: IRI -> Bool Source #
isPredefPropOrClass :: IRI -> Bool Source #
predefIRIs :: Set IRI Source #
isDatatypeKey :: IRI -> Bool Source #
isSWRLBuiltIn :: IRI -> Bool Source #
xsdMap :: PreDefMaps Source #
rdfMap :: PreDefMaps Source #
rdfsMap :: PreDefMaps Source #
isDatatypeKeyAux :: IRI -> [(String, String)] Source #
type PreDefMaps = ([String], String, String) Source #
preDefMaps :: [String] -> String -> PreDefMaps Source #
checkPredefAux :: PreDefMaps -> IRI -> Maybe (String, String) Source #
checkPredef :: PreDefMaps -> IRI -> Bool Source #
makeOWLPredefMaps :: [String] -> PreDefMaps 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
stripReservedPrefix :: IRI -> IRI 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 #
entityToId :: Entity -> Id Source #
Extracts Id from Entities
printDatatype :: IRI -> String Source #
data DatatypeCat Source #
Instances
Eq DatatypeCat Source # | |
Defined in OWL2.AS (==) :: DatatypeCat -> DatatypeCat -> Bool (/=) :: DatatypeCat -> DatatypeCat -> Bool | |
Data DatatypeCat Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: DatatypeCat -> DatatypeCat -> Ordering (<) :: DatatypeCat -> DatatypeCat -> Bool (<=) :: DatatypeCat -> DatatypeCat -> Bool (>) :: DatatypeCat -> DatatypeCat -> Bool (>=) :: DatatypeCat -> DatatypeCat -> Bool max :: DatatypeCat -> DatatypeCat -> DatatypeCat min :: DatatypeCat -> DatatypeCat -> DatatypeCat | |
Show DatatypeCat Source # | |
Defined in OWL2.AS showsPrec :: Int -> DatatypeCat -> ShowS show :: DatatypeCat -> String showList :: [DatatypeCat] -> ShowS | |
Generic DatatypeCat | |
Defined in OWL2.ATC_OWL2 type Rep DatatypeCat :: Type -> Type from :: DatatypeCat -> Rep DatatypeCat x to :: Rep DatatypeCat x -> DatatypeCat | |
FromJSON DatatypeCat | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DatatypeCat parseJSONList :: Value -> Parser [DatatypeCat] | |
ToJSON DatatypeCat | |
Defined in OWL2.ATC_OWL2 toJSON :: DatatypeCat -> Value toEncoding :: DatatypeCat -> Encoding toJSONList :: [DatatypeCat] -> Value toEncodingList :: [DatatypeCat] -> Encoding | |
ShATermConvertible DatatypeCat | |
Defined in OWL2.ATC_OWL2 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 | |
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))) |
getDatatypeCat :: IRI -> DatatypeCat Source #
makeXsdMap :: [String] -> PreDefMaps Source #
Extracting Symbols
symsOfAxiom :: Axiom -> Set Entity Source #
symsOfDGAtoms :: [DGAtom] -> Set Entity Source #
symsOfDLSafeAtoms :: [Atom] -> Set Entity Source #
symsOfIArg :: IndividualArg -> Set Entity Source #
symsOfDGEdges :: DGEdges -> Set Entity Source #
symsOfClassExpression :: ClassExpression -> Set Entity Source #
symsOfDataRange :: DataRange -> Set Entity Source #
symsOfAnnotation :: Annotation -> Set Entity Source #
symsOfAnnotations :: [Annotation] -> Set Entity Source #
Cardinalities
data CardinalityType Source #
Instances
Eq CardinalityType Source # | |
Defined in OWL2.AS (==) :: CardinalityType -> CardinalityType -> Bool (/=) :: CardinalityType -> CardinalityType -> Bool | |
Data CardinalityType Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: CardinalityType -> CardinalityType -> Ordering (<) :: CardinalityType -> CardinalityType -> Bool (<=) :: CardinalityType -> CardinalityType -> Bool (>) :: CardinalityType -> CardinalityType -> Bool (>=) :: CardinalityType -> CardinalityType -> Bool max :: CardinalityType -> CardinalityType -> CardinalityType min :: CardinalityType -> CardinalityType -> CardinalityType | |
Show CardinalityType Source # | |
Defined in OWL2.AS showsPrec :: Int -> CardinalityType -> ShowS show :: CardinalityType -> String showList :: [CardinalityType] -> ShowS | |
Generic CardinalityType | |
Defined in OWL2.ATC_OWL2 type Rep CardinalityType :: Type -> Type from :: CardinalityType -> Rep CardinalityType x to :: Rep CardinalityType x -> CardinalityType | |
FromJSON CardinalityType | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser CardinalityType parseJSONList :: Value -> Parser [CardinalityType] | |
ToJSON CardinalityType | |
Defined in OWL2.ATC_OWL2 toJSON :: CardinalityType -> Value toEncoding :: CardinalityType -> Encoding toJSONList :: [CardinalityType] -> Value toEncodingList :: [CardinalityType] -> Encoding | |
ShATermConvertible CardinalityType | |
Defined in OWL2.ATC_OWL2 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 | |
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))) |
showCardinalityType :: CardinalityType -> String Source #
data Cardinality a b Source #
Cardinality CardinalityType Int a (Maybe b) |
Instances
(Eq a, Eq b) => Eq (Cardinality a b) Source # | |
Defined in OWL2.AS (==) :: Cardinality a b -> Cardinality a b -> Bool (/=) :: Cardinality a b -> Cardinality a b -> Bool | |
(Data a, Data b) => Data (Cardinality a b) Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS showsPrec :: Int -> Cardinality a b -> ShowS show :: Cardinality a b -> String showList :: [Cardinality a b] -> ShowS | |
Generic (Cardinality a b) | |
Defined in OWL2.ATC_OWL2 type Rep (Cardinality a b) :: Type -> Type 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) | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser (Cardinality a b) parseJSONList :: Value -> Parser [Cardinality a b] | |
(ToJSON a, ToJSON b) => ToJSON (Cardinality a b) | |
Defined in OWL2.ATC_OWL2 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) | |
Defined in OWL2.ATC_OWL2 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) | |
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 #
Instances
Eq JunctionType Source # | |
Defined in OWL2.AS (==) :: JunctionType -> JunctionType -> Bool (/=) :: JunctionType -> JunctionType -> Bool | |
Data JunctionType Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: JunctionType -> JunctionType -> Ordering (<) :: JunctionType -> JunctionType -> Bool (<=) :: JunctionType -> JunctionType -> Bool (>) :: JunctionType -> JunctionType -> Bool (>=) :: JunctionType -> JunctionType -> Bool max :: JunctionType -> JunctionType -> JunctionType min :: JunctionType -> JunctionType -> JunctionType | |
Show JunctionType Source # | |
Defined in OWL2.AS showsPrec :: Int -> JunctionType -> ShowS show :: JunctionType -> String showList :: [JunctionType] -> ShowS | |
Generic JunctionType | |
Defined in OWL2.ATC_OWL2 type Rep JunctionType :: Type -> Type from :: JunctionType -> Rep JunctionType x to :: Rep JunctionType x -> JunctionType | |
FromJSON JunctionType | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser JunctionType parseJSONList :: Value -> Parser [JunctionType] | |
ToJSON JunctionType | |
Defined in OWL2.ATC_OWL2 toJSON :: JunctionType -> Value toEncoding :: JunctionType -> Encoding toJSONList :: [JunctionType] -> Value toEncodingList :: [JunctionType] -> Encoding | |
ShATermConvertible JunctionType | |
Defined in OWL2.ATC_OWL2 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 | |
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)) |
type ConstrainingFacet = IRI Source #
type RestrictionValue = Literal Source #
ENTITIES
Entity | |
|
Instances
mkEntityLbl :: String -> EntityType -> IRI -> Entity Source #
data EntityType Source #
Instances
Bounded EntityType Source # | |
Defined in OWL2.AS | |
Enum EntityType Source # | |
Defined in OWL2.AS succ :: EntityType -> EntityType pred :: EntityType -> EntityType toEnum :: Int -> EntityType fromEnum :: EntityType -> Int enumFrom :: EntityType -> [EntityType] enumFromThen :: EntityType -> EntityType -> [EntityType] enumFromTo :: EntityType -> EntityType -> [EntityType] enumFromThenTo :: EntityType -> EntityType -> EntityType -> [EntityType] | |
Eq EntityType Source # | |
Defined in OWL2.AS (==) :: EntityType -> EntityType -> Bool (/=) :: EntityType -> EntityType -> Bool | |
Data EntityType Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: EntityType -> EntityType -> Ordering (<) :: EntityType -> EntityType -> Bool (<=) :: EntityType -> EntityType -> Bool (>) :: EntityType -> EntityType -> Bool (>=) :: EntityType -> EntityType -> Bool max :: EntityType -> EntityType -> EntityType min :: EntityType -> EntityType -> EntityType | |
Read EntityType Source # | |
Defined in OWL2.AS readsPrec :: Int -> ReadS EntityType readList :: ReadS [EntityType] readPrec :: ReadPrec EntityType readListPrec :: ReadPrec [EntityType] | |
Show EntityType Source # | |
Defined in OWL2.AS showsPrec :: Int -> EntityType -> ShowS show :: EntityType -> String showList :: [EntityType] -> ShowS | |
Generic EntityType | |
Defined in OWL2.ATC_OWL2 type Rep EntityType :: Type -> Type from :: EntityType -> Rep EntityType x to :: Rep EntityType x -> EntityType | |
FromJSON EntityType | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser EntityType parseJSONList :: Value -> Parser [EntityType] | |
ToJSON EntityType | |
Defined in OWL2.ATC_OWL2 toJSON :: EntityType -> Value toEncoding :: EntityType -> Encoding toJSONList :: [EntityType] -> Value toEncodingList :: [EntityType] -> Encoding | |
ShATermConvertible EntityType | |
Defined in OWL2.ATC_OWL2 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 | |
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)))) |
showEntityType :: EntityType -> String Source #
entityTypes :: [EntityType] Source #
LITERALS
data TypedOrUntyped Source #
Typed Datatype | |
Untyped (Maybe LanguageTag) |
Instances
Eq TypedOrUntyped Source # | |
Defined in OWL2.AS (==) :: TypedOrUntyped -> TypedOrUntyped -> Bool (/=) :: TypedOrUntyped -> TypedOrUntyped -> Bool | |
Data TypedOrUntyped Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: TypedOrUntyped -> TypedOrUntyped -> Ordering (<) :: TypedOrUntyped -> TypedOrUntyped -> Bool (<=) :: TypedOrUntyped -> TypedOrUntyped -> Bool (>) :: TypedOrUntyped -> TypedOrUntyped -> Bool (>=) :: TypedOrUntyped -> TypedOrUntyped -> Bool max :: TypedOrUntyped -> TypedOrUntyped -> TypedOrUntyped min :: TypedOrUntyped -> TypedOrUntyped -> TypedOrUntyped | |
Show TypedOrUntyped Source # | |
Defined in OWL2.AS showsPrec :: Int -> TypedOrUntyped -> ShowS show :: TypedOrUntyped -> String showList :: [TypedOrUntyped] -> ShowS | |
Generic TypedOrUntyped | |
Defined in OWL2.ATC_OWL2 type Rep TypedOrUntyped :: Type -> Type from :: TypedOrUntyped -> Rep TypedOrUntyped x to :: Rep TypedOrUntyped x -> TypedOrUntyped | |
FromJSON TypedOrUntyped | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser TypedOrUntyped parseJSONList :: Value -> Parser [TypedOrUntyped] | |
ToJSON TypedOrUntyped | |
Defined in OWL2.ATC_OWL2 toJSON :: TypedOrUntyped -> Value toEncoding :: TypedOrUntyped -> Encoding toJSONList :: [TypedOrUntyped] -> Value toEncodingList :: [TypedOrUntyped] -> Encoding | |
ShATermConvertible TypedOrUntyped | |
Defined in OWL2.ATC_OWL2 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 | |
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)))) |
Instances
Eq Literal Source # | |
Data Literal Source # | |
Defined in OWL2.AS 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 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 # | |
Show Literal Source # | |
Generic Literal | |
FromJSON Literal | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Literal parseJSONList :: Value -> Parser [Literal] | |
ToJSON Literal | |
Defined in OWL2.ATC_OWL2 toEncoding :: Literal -> Encoding toJSONList :: [Literal] -> Value toEncodingList :: [Literal] -> Encoding | |
ShATermConvertible Literal | |
Defined in OWL2.ATC_OWL2 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 # | |
Function Literal Source # | |
type Rep Literal | |
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))) |
non-negative integers given by the sequence of digits
NNInt [Int] |
Instances
Eq NNInt Source # | |
Data NNInt Source # | |
Defined in OWL2.AS 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 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 # | |
Show NNInt Source # | |
Generic NNInt | |
FromJSON NNInt | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser NNInt parseJSONList :: Value -> Parser [NNInt] | |
ToJSON NNInt | |
Defined in OWL2.ATC_OWL2 | |
ShATermConvertible NNInt | |
Defined in OWL2.ATC_OWL2 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 | |
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]))) |
isZeroNNInt :: NNInt -> Bool Source #
Instances
Eq IntLit Source # | |
Data IntLit Source # | |
Defined in OWL2.AS 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 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 # | |
Show IntLit Source # | |
Generic IntLit | |
FromJSON IntLit | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser IntLit parseJSONList :: Value -> Parser [IntLit] | |
ToJSON IntLit | |
Defined in OWL2.ATC_OWL2 toEncoding :: IntLit -> Encoding toJSONList :: [IntLit] -> Value toEncodingList :: [IntLit] -> Encoding | |
ShATermConvertible IntLit | |
Defined in OWL2.ATC_OWL2 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 | |
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))) |
Instances
Eq DecLit Source # | |
Data DecLit Source # | |
Defined in OWL2.AS 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 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 # | |
Show DecLit Source # | |
Generic DecLit | |
FromJSON DecLit | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DecLit parseJSONList :: Value -> Parser [DecLit] | |
ToJSON DecLit | |
Defined in OWL2.ATC_OWL2 toEncoding :: DecLit -> Encoding toJSONList :: [DecLit] -> Value toEncodingList :: [DecLit] -> Encoding | |
ShATermConvertible DecLit | |
Defined in OWL2.ATC_OWL2 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 | |
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))) |
Instances
Eq FloatLit Source # | |
Data FloatLit Source # | |
Defined in OWL2.AS 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 # | |
Show FloatLit Source # | |
Generic FloatLit | |
FromJSON FloatLit | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser FloatLit parseJSONList :: Value -> Parser [FloatLit] | |
ToJSON FloatLit | |
Defined in OWL2.ATC_OWL2 toEncoding :: FloatLit -> Encoding toJSONList :: [FloatLit] -> Value toEncodingList :: [FloatLit] -> Encoding | |
ShATermConvertible FloatLit | |
Defined in OWL2.ATC_OWL2 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 | |
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))) |
isFloatDec :: FloatLit -> Bool Source #
isFloatInt :: FloatLit -> Bool Source #
floatToInt :: FloatLit -> IntLit Source #
decToFloat :: DecLit -> FloatLit Source #
intToFloat :: IntLit -> FloatLit Source #
numberName :: FloatLit -> String Source #
PROPERTY EXPRESSIONS
data ObjectPropertyExpression Source #
Instances
isObjectProperty :: ObjectPropertyExpression -> Bool Source #
DATA RANGES
DataType Datatype [(ConstrainingFacet, RestrictionValue)] | |
DataJunction JunctionType [DataRange] | |
DataComplementOf DataRange | |
DataOneOf [Literal] |
Instances
Eq DataRange Source # | |
Data DataRange Source # | |
Defined in OWL2.AS 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 # | |
Show DataRange Source # | |
Generic DataRange | |
FromJSON DataRange | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DataRange parseJSONList :: Value -> Parser [DataRange] | |
ToJSON DataRange | |
Defined in OWL2.ATC_OWL2 toEncoding :: DataRange -> Encoding toJSONList :: [DataRange] -> Value toEncodingList :: [DataRange] -> Encoding | |
ShATermConvertible DataRange | |
Defined in OWL2.ATC_OWL2 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 |
Function DataRange Source # | |
type Rep DataRange | |
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])))) |
CLASS EXPERSSIONS
data ClassExpression Source #
Instances
Eq ClassExpression Source # | |
Defined in OWL2.AS (==) :: ClassExpression -> ClassExpression -> Bool (/=) :: ClassExpression -> ClassExpression -> Bool | |
Data ClassExpression Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: ClassExpression -> ClassExpression -> Ordering (<) :: ClassExpression -> ClassExpression -> Bool (<=) :: ClassExpression -> ClassExpression -> Bool (>) :: ClassExpression -> ClassExpression -> Bool (>=) :: ClassExpression -> ClassExpression -> Bool max :: ClassExpression -> ClassExpression -> ClassExpression min :: ClassExpression -> ClassExpression -> ClassExpression | |
Show ClassExpression Source # | |
Defined in OWL2.AS showsPrec :: Int -> ClassExpression -> ShowS show :: ClassExpression -> String showList :: [ClassExpression] -> ShowS | |
Generic ClassExpression | |
Defined in OWL2.ATC_OWL2 type Rep ClassExpression :: Type -> Type from :: ClassExpression -> Rep ClassExpression x to :: Rep ClassExpression x -> ClassExpression | |
FromJSON ClassExpression | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser ClassExpression parseJSONList :: Value -> Parser [ClassExpression] | |
ToJSON ClassExpression | |
Defined in OWL2.ATC_OWL2 toJSON :: ClassExpression -> Value toEncoding :: ClassExpression -> Encoding toJSONList :: [ClassExpression] -> Value toEncodingList :: [ClassExpression] -> Encoding | |
ShATermConvertible ClassExpression | |
Defined in OWL2.ATC_OWL2 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 |
Defined in OWL2.Print pretty :: ClassExpression -> Doc Source # pretties :: [ClassExpression] -> Doc Source # | |
Function ClassExpression Source # | |
Defined in OWL2.Function function :: Action -> AMap -> ClassExpression -> ClassExpression Source # | |
type Rep ClassExpression | |
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
Eq Annotation Source # | |
Defined in OWL2.AS (==) :: Annotation -> Annotation -> Bool (/=) :: Annotation -> Annotation -> Bool | |
Data Annotation Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: Annotation -> Annotation -> Ordering (<) :: Annotation -> Annotation -> Bool (<=) :: Annotation -> Annotation -> Bool (>) :: Annotation -> Annotation -> Bool (>=) :: Annotation -> Annotation -> Bool max :: Annotation -> Annotation -> Annotation min :: Annotation -> Annotation -> Annotation | |
Show Annotation Source # | |
Defined in OWL2.AS showsPrec :: Int -> Annotation -> ShowS show :: Annotation -> String showList :: [Annotation] -> ShowS | |
Generic Annotation | |
Defined in OWL2.ATC_OWL2 type Rep Annotation :: Type -> Type from :: Annotation -> Rep Annotation x to :: Rep Annotation x -> Annotation | |
FromJSON Annotation | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Annotation parseJSONList :: Value -> Parser [Annotation] | |
ToJSON Annotation | |
Defined in OWL2.ATC_OWL2 toJSON :: Annotation -> Value toEncoding :: Annotation -> Encoding toJSONList :: [Annotation] -> Value toEncodingList :: [Annotation] -> Encoding | |
ShATermConvertible Annotation | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Print pretty :: Annotation -> Doc Source # pretties :: [Annotation] -> Doc Source # | |
Function Annotation Source # | |
Defined in OWL2.Function function :: Action -> AMap -> Annotation -> Annotation Source # | |
type Rep Annotation | |
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)))) |
type OntologyAnnotations = [Annotation] Source #
data AnnotationValue Source #
Instances
Eq AnnotationValue Source # | |
Defined in OWL2.AS (==) :: AnnotationValue -> AnnotationValue -> Bool (/=) :: AnnotationValue -> AnnotationValue -> Bool | |
Data AnnotationValue Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: AnnotationValue -> AnnotationValue -> Ordering (<) :: AnnotationValue -> AnnotationValue -> Bool (<=) :: AnnotationValue -> AnnotationValue -> Bool (>) :: AnnotationValue -> AnnotationValue -> Bool (>=) :: AnnotationValue -> AnnotationValue -> Bool max :: AnnotationValue -> AnnotationValue -> AnnotationValue min :: AnnotationValue -> AnnotationValue -> AnnotationValue | |
Show AnnotationValue Source # | |
Defined in OWL2.AS showsPrec :: Int -> AnnotationValue -> ShowS show :: AnnotationValue -> String showList :: [AnnotationValue] -> ShowS | |
Generic AnnotationValue | |
Defined in OWL2.ATC_OWL2 type Rep AnnotationValue :: Type -> Type from :: AnnotationValue -> Rep AnnotationValue x to :: Rep AnnotationValue x -> AnnotationValue | |
FromJSON AnnotationValue | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser AnnotationValue parseJSONList :: Value -> Parser [AnnotationValue] | |
ToJSON AnnotationValue | |
Defined in OWL2.ATC_OWL2 toJSON :: AnnotationValue -> Value toEncoding :: AnnotationValue -> Encoding toJSONList :: [AnnotationValue] -> Value toEncodingList :: [AnnotationValue] -> Encoding | |
ShATermConvertible AnnotationValue | |
Defined in OWL2.ATC_OWL2 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 |
Defined in OWL2.Print pretty :: AnnotationValue -> Doc Source # pretties :: [AnnotationValue] -> Doc Source # | |
Function AnnotationValue Source # | |
Defined in OWL2.Function function :: Action -> AMap -> AnnotationValue -> AnnotationValue Source # | |
type Rep AnnotationValue | |
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
Eq AnnotationAxiom Source # | |
Defined in OWL2.AS (==) :: AnnotationAxiom -> AnnotationAxiom -> Bool (/=) :: AnnotationAxiom -> AnnotationAxiom -> Bool | |
Data AnnotationAxiom Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: AnnotationAxiom -> AnnotationAxiom -> Ordering (<) :: AnnotationAxiom -> AnnotationAxiom -> Bool (<=) :: AnnotationAxiom -> AnnotationAxiom -> Bool (>) :: AnnotationAxiom -> AnnotationAxiom -> Bool (>=) :: AnnotationAxiom -> AnnotationAxiom -> Bool max :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom min :: AnnotationAxiom -> AnnotationAxiom -> AnnotationAxiom | |
Show AnnotationAxiom Source # | |
Defined in OWL2.AS showsPrec :: Int -> AnnotationAxiom -> ShowS show :: AnnotationAxiom -> String showList :: [AnnotationAxiom] -> ShowS | |
Generic AnnotationAxiom | |
Defined in OWL2.ATC_OWL2 type Rep AnnotationAxiom :: Type -> Type from :: AnnotationAxiom -> Rep AnnotationAxiom x to :: Rep AnnotationAxiom x -> AnnotationAxiom | |
FromJSON AnnotationAxiom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser AnnotationAxiom parseJSONList :: Value -> Parser [AnnotationAxiom] | |
ToJSON AnnotationAxiom | |
Defined in OWL2.ATC_OWL2 toJSON :: AnnotationAxiom -> Value toEncoding :: AnnotationAxiom -> Encoding toJSONList :: [AnnotationAxiom] -> Value toEncodingList :: [AnnotationAxiom] -> Encoding | |
ShATermConvertible AnnotationAxiom | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> AnnotationAxiom -> AnnotationAxiom Source # | |
type Rep AnnotationAxiom | |
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
Eq AnnotationSubject Source # | |
Defined in OWL2.AS (==) :: AnnotationSubject -> AnnotationSubject -> Bool (/=) :: AnnotationSubject -> AnnotationSubject -> Bool | |
Data AnnotationSubject Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: AnnotationSubject -> AnnotationSubject -> Ordering (<) :: AnnotationSubject -> AnnotationSubject -> Bool (<=) :: AnnotationSubject -> AnnotationSubject -> Bool (>) :: AnnotationSubject -> AnnotationSubject -> Bool (>=) :: AnnotationSubject -> AnnotationSubject -> Bool max :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject min :: AnnotationSubject -> AnnotationSubject -> AnnotationSubject | |
Show AnnotationSubject Source # | |
Defined in OWL2.AS showsPrec :: Int -> AnnotationSubject -> ShowS show :: AnnotationSubject -> String showList :: [AnnotationSubject] -> ShowS | |
Generic AnnotationSubject | |
Defined in OWL2.ATC_OWL2 type Rep AnnotationSubject :: Type -> Type from :: AnnotationSubject -> Rep AnnotationSubject x to :: Rep AnnotationSubject x -> AnnotationSubject | |
FromJSON AnnotationSubject | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser AnnotationSubject parseJSONList :: Value -> Parser [AnnotationSubject] | |
ToJSON AnnotationSubject | |
Defined in OWL2.ATC_OWL2 toJSON :: AnnotationSubject -> Value toEncoding :: AnnotationSubject -> Encoding toJSONList :: [AnnotationSubject] -> Value toEncodingList :: [AnnotationSubject] -> Encoding | |
ShATermConvertible AnnotationSubject | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> AnnotationSubject -> AnnotationSubject Source # | |
type Rep AnnotationSubject | |
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
Instances
type AxiomAnnotations = [Annotation] Source #
type SubClassExpression = ClassExpression Source #
type DisjointClassExpression = [ClassExpression] Source #
data ClassAxiom Source #
Instances
Eq ClassAxiom Source # | |
Defined in OWL2.AS (==) :: ClassAxiom -> ClassAxiom -> Bool (/=) :: ClassAxiom -> ClassAxiom -> Bool | |
Data ClassAxiom Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: ClassAxiom -> ClassAxiom -> Ordering (<) :: ClassAxiom -> ClassAxiom -> Bool (<=) :: ClassAxiom -> ClassAxiom -> Bool (>) :: ClassAxiom -> ClassAxiom -> Bool (>=) :: ClassAxiom -> ClassAxiom -> Bool max :: ClassAxiom -> ClassAxiom -> ClassAxiom min :: ClassAxiom -> ClassAxiom -> ClassAxiom | |
Show ClassAxiom Source # | |
Defined in OWL2.AS showsPrec :: Int -> ClassAxiom -> ShowS show :: ClassAxiom -> String showList :: [ClassAxiom] -> ShowS | |
Generic ClassAxiom | |
Defined in OWL2.ATC_OWL2 type Rep ClassAxiom :: Type -> Type from :: ClassAxiom -> Rep ClassAxiom x to :: Rep ClassAxiom x -> ClassAxiom | |
FromJSON ClassAxiom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser ClassAxiom parseJSONList :: Value -> Parser [ClassAxiom] | |
ToJSON ClassAxiom | |
Defined in OWL2.ATC_OWL2 toJSON :: ClassAxiom -> Value toEncoding :: ClassAxiom -> Encoding toJSONList :: [ClassAxiom] -> Value toEncodingList :: [ClassAxiom] -> Encoding | |
ShATermConvertible ClassAxiom | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> ClassAxiom -> ClassAxiom Source # | |
type Rep ClassAxiom | |
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
Eq ObjectPropertyAxiom Source # | |
Defined in OWL2.AS (==) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool (/=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool | |
Data ObjectPropertyAxiom Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Ordering (<) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool (<=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool (>) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool (>=) :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> Bool max :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom min :: ObjectPropertyAxiom -> ObjectPropertyAxiom -> ObjectPropertyAxiom | |
Show ObjectPropertyAxiom Source # | |
Defined in OWL2.AS showsPrec :: Int -> ObjectPropertyAxiom -> ShowS show :: ObjectPropertyAxiom -> String showList :: [ObjectPropertyAxiom] -> ShowS | |
Generic ObjectPropertyAxiom | |
Defined in OWL2.ATC_OWL2 type Rep ObjectPropertyAxiom :: Type -> Type from :: ObjectPropertyAxiom -> Rep ObjectPropertyAxiom x to :: Rep ObjectPropertyAxiom x -> ObjectPropertyAxiom | |
FromJSON ObjectPropertyAxiom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser ObjectPropertyAxiom parseJSONList :: Value -> Parser [ObjectPropertyAxiom] | |
ToJSON ObjectPropertyAxiom | |
Defined in OWL2.ATC_OWL2 toJSON :: ObjectPropertyAxiom -> Value toEncoding :: ObjectPropertyAxiom -> Encoding toJSONList :: [ObjectPropertyAxiom] -> Value toEncodingList :: [ObjectPropertyAxiom] -> Encoding | |
ShATermConvertible ObjectPropertyAxiom | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> ObjectPropertyAxiom -> ObjectPropertyAxiom Source # | |
type Rep ObjectPropertyAxiom | |
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
data DataPropertyAxiom Source #
Instances
Eq DataPropertyAxiom Source # | |
Defined in OWL2.AS (==) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool (/=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool | |
Data DataPropertyAxiom Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: DataPropertyAxiom -> DataPropertyAxiom -> Ordering (<) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool (<=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool (>) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool (>=) :: DataPropertyAxiom -> DataPropertyAxiom -> Bool max :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom min :: DataPropertyAxiom -> DataPropertyAxiom -> DataPropertyAxiom | |
Show DataPropertyAxiom Source # | |
Defined in OWL2.AS showsPrec :: Int -> DataPropertyAxiom -> ShowS show :: DataPropertyAxiom -> String showList :: [DataPropertyAxiom] -> ShowS | |
Generic DataPropertyAxiom | |
Defined in OWL2.ATC_OWL2 type Rep DataPropertyAxiom :: Type -> Type from :: DataPropertyAxiom -> Rep DataPropertyAxiom x to :: Rep DataPropertyAxiom x -> DataPropertyAxiom | |
FromJSON DataPropertyAxiom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DataPropertyAxiom parseJSONList :: Value -> Parser [DataPropertyAxiom] | |
ToJSON DataPropertyAxiom | |
Defined in OWL2.ATC_OWL2 toJSON :: DataPropertyAxiom -> Value toEncoding :: DataPropertyAxiom -> Encoding toJSONList :: [DataPropertyAxiom] -> Value toEncodingList :: [DataPropertyAxiom] -> Encoding | |
ShATermConvertible DataPropertyAxiom | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> DataPropertyAxiom -> DataPropertyAxiom Source # | |
type Rep DataPropertyAxiom | |
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))))) |
Instances
Eq Assertion Source # | |
Data Assertion Source # | |
Defined in OWL2.AS 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 # | |
Show Assertion Source # | |
Generic Assertion | |
FromJSON Assertion | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Assertion parseJSONList :: Value -> Parser [Assertion] | |
ToJSON Assertion | |
Defined in OWL2.ATC_OWL2 toEncoding :: Assertion -> Encoding toJSONList :: [Assertion] -> Value toEncodingList :: [Assertion] -> Encoding | |
ShATermConvertible Assertion | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep Assertion | |
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)))))) |
type SourceIndividual = Individual Source #
type TargetIndividual = Individual Source #
type TargetValue = Literal Source #
Instances
Eq Rule Source # | |
Data Rule Source # | |
Defined in OWL2.AS 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 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 # | |
Show Rule Source # | |
Generic Rule | |
FromJSON Rule | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Rule parseJSONList :: Value -> Parser [Rule] | |
ToJSON Rule | |
Defined in OWL2.ATC_OWL2 | |
ShATermConvertible Rule | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep Rule | |
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)))) |
data IndividualArg Source #
Instances
Eq IndividualArg Source # | |
Defined in OWL2.AS (==) :: IndividualArg -> IndividualArg -> Bool (/=) :: IndividualArg -> IndividualArg -> Bool | |
Data IndividualArg Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: IndividualArg -> IndividualArg -> Ordering (<) :: IndividualArg -> IndividualArg -> Bool (<=) :: IndividualArg -> IndividualArg -> Bool (>) :: IndividualArg -> IndividualArg -> Bool (>=) :: IndividualArg -> IndividualArg -> Bool max :: IndividualArg -> IndividualArg -> IndividualArg min :: IndividualArg -> IndividualArg -> IndividualArg | |
Show IndividualArg Source # | |
Defined in OWL2.AS showsPrec :: Int -> IndividualArg -> ShowS show :: IndividualArg -> String showList :: [IndividualArg] -> ShowS | |
Generic IndividualArg | |
Defined in OWL2.ATC_OWL2 type Rep IndividualArg :: Type -> Type from :: IndividualArg -> Rep IndividualArg x to :: Rep IndividualArg x -> IndividualArg | |
FromJSON IndividualArg | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser IndividualArg parseJSONList :: Value -> Parser [IndividualArg] | |
ToJSON IndividualArg | |
Defined in OWL2.ATC_OWL2 toJSON :: IndividualArg -> Value toEncoding :: IndividualArg -> Encoding toJSONList :: [IndividualArg] -> Value toEncodingList :: [IndividualArg] -> Encoding | |
ShATermConvertible IndividualArg | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> IndividualArg -> IndividualArg Source # | |
type Rep IndividualArg | |
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))) |
Instances
Eq DataArg Source # | |
Data DataArg Source # | |
Defined in OWL2.AS 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 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 # | |
Show DataArg Source # | |
Generic DataArg | |
FromJSON DataArg | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DataArg parseJSONList :: Value -> Parser [DataArg] | |
ToJSON DataArg | |
Defined in OWL2.ATC_OWL2 toEncoding :: DataArg -> Encoding toJSONList :: [DataArg] -> Value toEncodingList :: [DataArg] -> Encoding | |
ShATermConvertible DataArg | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep DataArg | |
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))) |
type IndividualVar = Variable Source #
data UnknownArg Source #
See UnknownUnaryAtom
Instances
Eq UnknownArg Source # | |
Defined in OWL2.AS (==) :: UnknownArg -> UnknownArg -> Bool (/=) :: UnknownArg -> UnknownArg -> Bool | |
Data UnknownArg Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: UnknownArg -> UnknownArg -> Ordering (<) :: UnknownArg -> UnknownArg -> Bool (<=) :: UnknownArg -> UnknownArg -> Bool (>) :: UnknownArg -> UnknownArg -> Bool (>=) :: UnknownArg -> UnknownArg -> Bool max :: UnknownArg -> UnknownArg -> UnknownArg min :: UnknownArg -> UnknownArg -> UnknownArg | |
Show UnknownArg Source # | |
Defined in OWL2.AS showsPrec :: Int -> UnknownArg -> ShowS show :: UnknownArg -> String showList :: [UnknownArg] -> ShowS | |
Generic UnknownArg | |
Defined in OWL2.ATC_OWL2 type Rep UnknownArg :: Type -> Type from :: UnknownArg -> Rep UnknownArg x to :: Rep UnknownArg x -> UnknownArg | |
FromJSON UnknownArg | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser UnknownArg parseJSONList :: Value -> Parser [UnknownArg] | |
ToJSON UnknownArg | |
Defined in OWL2.ATC_OWL2 toJSON :: UnknownArg -> Value toEncoding :: UnknownArg -> Encoding toJSONList :: [UnknownArg] -> Value toEncodingList :: [UnknownArg] -> Encoding | |
ShATermConvertible UnknownArg | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> UnknownArg -> UnknownArg Source # | |
type Rep UnknownArg | |
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)))) |
ClassAtom ClassExpression IndividualArg | |
DataRangeAtom DataRange DataArg | |
ObjectPropertyAtom ObjectPropertyExpression IndividualArg IndividualArg | |
DataPropertyAtom DataProperty IndividualArg DataArg | |
BuiltInAtom IRI [DataArg] | |
SameIndividualAtom IndividualArg IndividualArg | |
DifferentIndividualsAtom IndividualArg IndividualArg | |
UnknownUnaryAtom IRI UnknownArg | Ambiguous predicates used in SWRL Rules which type cannot be inferred during parsing. This predicates get resolved and replaced with a specific one in static analysis. |
UnknownBinaryAtom IRI UnknownArg UnknownArg |
Instances
Eq Atom Source # | |
Data Atom Source # | |
Defined in OWL2.AS 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 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 # | |
Show Atom Source # | |
Generic Atom | |
FromJSON Atom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Atom parseJSONList :: Value -> Parser [Atom] | |
ToJSON Atom | |
Defined in OWL2.ATC_OWL2 | |
ShATermConvertible Atom | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep Atom | |
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))))))) |
getVariablesFromIArg :: IndividualArg -> Set Variable Source #
getVariablesFromDArg :: DataArg -> Set Variable Source #
getVariablesFromAtom :: Atom -> Set Variable Source #
DGClassAtom ClassExpression IndividualArg | |
DGObjectPropertyAtom ObjectPropertyExpression IndividualArg IndividualArg |
Instances
Eq DGAtom Source # | |
Data DGAtom Source # | |
Defined in OWL2.AS 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 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 # | |
Show DGAtom Source # | |
Generic DGAtom | |
FromJSON DGAtom | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DGAtom parseJSONList :: Value -> Parser [DGAtom] | |
ToJSON DGAtom | |
Defined in OWL2.ATC_OWL2 toEncoding :: DGAtom -> Encoding toJSONList :: [DGAtom] -> Value toEncodingList :: [DGAtom] -> Encoding | |
ShATermConvertible DGAtom | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep DGAtom | |
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)))) |
type DGNodes = [DGNodeAssertion] Source #
type DGEdges = [DGEdgeAssertion] Source #
type MainClasses = [Class] Source #
data DGNodeAssertion Source #
Instances
Eq DGNodeAssertion Source # | |
Defined in OWL2.AS (==) :: DGNodeAssertion -> DGNodeAssertion -> Bool (/=) :: DGNodeAssertion -> DGNodeAssertion -> Bool | |
Data DGNodeAssertion Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: DGNodeAssertion -> DGNodeAssertion -> Ordering (<) :: DGNodeAssertion -> DGNodeAssertion -> Bool (<=) :: DGNodeAssertion -> DGNodeAssertion -> Bool (>) :: DGNodeAssertion -> DGNodeAssertion -> Bool (>=) :: DGNodeAssertion -> DGNodeAssertion -> Bool max :: DGNodeAssertion -> DGNodeAssertion -> DGNodeAssertion min :: DGNodeAssertion -> DGNodeAssertion -> DGNodeAssertion | |
Show DGNodeAssertion Source # | |
Defined in OWL2.AS showsPrec :: Int -> DGNodeAssertion -> ShowS show :: DGNodeAssertion -> String showList :: [DGNodeAssertion] -> ShowS | |
Generic DGNodeAssertion | |
Defined in OWL2.ATC_OWL2 type Rep DGNodeAssertion :: Type -> Type from :: DGNodeAssertion -> Rep DGNodeAssertion x to :: Rep DGNodeAssertion x -> DGNodeAssertion | |
FromJSON DGNodeAssertion | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DGNodeAssertion parseJSONList :: Value -> Parser [DGNodeAssertion] | |
ToJSON DGNodeAssertion | |
Defined in OWL2.ATC_OWL2 toJSON :: DGNodeAssertion -> Value toEncoding :: DGNodeAssertion -> Encoding toJSONList :: [DGNodeAssertion] -> Value toEncodingList :: [DGNodeAssertion] -> Encoding | |
ShATermConvertible DGNodeAssertion | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> DGNodeAssertion -> DGNodeAssertion Source # | |
type Rep DGNodeAssertion | |
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
Eq DGEdgeAssertion Source # | |
Defined in OWL2.AS (==) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool (/=) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool | |
Data DGEdgeAssertion Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: DGEdgeAssertion -> DGEdgeAssertion -> Ordering (<) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool (<=) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool (>) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool (>=) :: DGEdgeAssertion -> DGEdgeAssertion -> Bool max :: DGEdgeAssertion -> DGEdgeAssertion -> DGEdgeAssertion min :: DGEdgeAssertion -> DGEdgeAssertion -> DGEdgeAssertion | |
Show DGEdgeAssertion Source # | |
Defined in OWL2.AS showsPrec :: Int -> DGEdgeAssertion -> ShowS show :: DGEdgeAssertion -> String showList :: [DGEdgeAssertion] -> ShowS | |
Generic DGEdgeAssertion | |
Defined in OWL2.ATC_OWL2 type Rep DGEdgeAssertion :: Type -> Type from :: DGEdgeAssertion -> Rep DGEdgeAssertion x to :: Rep DGEdgeAssertion x -> DGEdgeAssertion | |
FromJSON DGEdgeAssertion | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser DGEdgeAssertion parseJSONList :: Value -> Parser [DGEdgeAssertion] | |
ToJSON DGEdgeAssertion | |
Defined in OWL2.ATC_OWL2 toJSON :: DGEdgeAssertion -> Value toEncoding :: DGEdgeAssertion -> Encoding toJSONList :: [DGEdgeAssertion] -> Value toEncodingList :: [DGEdgeAssertion] -> Encoding | |
ShATermConvertible DGEdgeAssertion | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> DGEdgeAssertion -> DGEdgeAssertion Source # | |
type Rep DGEdgeAssertion | |
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 #
Instances
Eq OntologySyntaxType Source # | |
Defined in OWL2.AS (==) :: OntologySyntaxType -> OntologySyntaxType -> Bool (/=) :: OntologySyntaxType -> OntologySyntaxType -> Bool | |
Data OntologySyntaxType Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: OntologySyntaxType -> OntologySyntaxType -> Ordering (<) :: OntologySyntaxType -> OntologySyntaxType -> Bool (<=) :: OntologySyntaxType -> OntologySyntaxType -> Bool (>) :: OntologySyntaxType -> OntologySyntaxType -> Bool (>=) :: OntologySyntaxType -> OntologySyntaxType -> Bool max :: OntologySyntaxType -> OntologySyntaxType -> OntologySyntaxType min :: OntologySyntaxType -> OntologySyntaxType -> OntologySyntaxType | |
Show OntologySyntaxType Source # | |
Defined in OWL2.AS showsPrec :: Int -> OntologySyntaxType -> ShowS show :: OntologySyntaxType -> String showList :: [OntologySyntaxType] -> ShowS | |
Generic OntologySyntaxType | |
Defined in OWL2.ATC_OWL2 type Rep OntologySyntaxType :: Type -> Type from :: OntologySyntaxType -> Rep OntologySyntaxType x to :: Rep OntologySyntaxType x -> OntologySyntaxType | |
FromJSON OntologySyntaxType | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser OntologySyntaxType parseJSONList :: Value -> Parser [OntologySyntaxType] | |
ToJSON OntologySyntaxType | |
Defined in OWL2.ATC_OWL2 toJSON :: OntologySyntaxType -> Value toEncoding :: OntologySyntaxType -> Encoding toJSONList :: [OntologySyntaxType] -> Value toEncodingList :: [OntologySyntaxType] -> Encoding | |
ShATermConvertible OntologySyntaxType | |
Defined in OWL2.ATC_OWL2 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 | |
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
Eq OntologyMetadata Source # | |
Defined in OWL2.AS (==) :: OntologyMetadata -> OntologyMetadata -> Bool (/=) :: OntologyMetadata -> OntologyMetadata -> Bool | |
Data OntologyMetadata Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: OntologyMetadata -> OntologyMetadata -> Ordering (<) :: OntologyMetadata -> OntologyMetadata -> Bool (<=) :: OntologyMetadata -> OntologyMetadata -> Bool (>) :: OntologyMetadata -> OntologyMetadata -> Bool (>=) :: OntologyMetadata -> OntologyMetadata -> Bool max :: OntologyMetadata -> OntologyMetadata -> OntologyMetadata min :: OntologyMetadata -> OntologyMetadata -> OntologyMetadata | |
Show OntologyMetadata Source # | |
Defined in OWL2.AS showsPrec :: Int -> OntologyMetadata -> ShowS show :: OntologyMetadata -> String showList :: [OntologyMetadata] -> ShowS | |
Generic OntologyMetadata | |
Defined in OWL2.ATC_OWL2 type Rep OntologyMetadata :: Type -> Type from :: OntologyMetadata -> Rep OntologyMetadata x to :: Rep OntologyMetadata x -> OntologyMetadata | |
FromJSON OntologyMetadata | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser OntologyMetadata parseJSONList :: Value -> Parser [OntologyMetadata] | |
ToJSON OntologyMetadata | |
Defined in OWL2.ATC_OWL2 toJSON :: OntologyMetadata -> Value toEncoding :: OntologyMetadata -> Encoding toJSONList :: [OntologyMetadata] -> Value toEncodingList :: [OntologyMetadata] -> Encoding | |
ShATermConvertible OntologyMetadata | |
Defined in OWL2.ATC_OWL2 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 | |
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
data PrefixDeclaration Source #
Instances
Eq PrefixDeclaration Source # | |
Defined in OWL2.AS (==) :: PrefixDeclaration -> PrefixDeclaration -> Bool (/=) :: PrefixDeclaration -> PrefixDeclaration -> Bool | |
Data PrefixDeclaration Source # | |
Defined in OWL2.AS 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 # | |
Defined in OWL2.AS compare :: PrefixDeclaration -> PrefixDeclaration -> Ordering (<) :: PrefixDeclaration -> PrefixDeclaration -> Bool (<=) :: PrefixDeclaration -> PrefixDeclaration -> Bool (>) :: PrefixDeclaration -> PrefixDeclaration -> Bool (>=) :: PrefixDeclaration -> PrefixDeclaration -> Bool max :: PrefixDeclaration -> PrefixDeclaration -> PrefixDeclaration min :: PrefixDeclaration -> PrefixDeclaration -> PrefixDeclaration | |
Show PrefixDeclaration Source # | |
Defined in OWL2.AS showsPrec :: Int -> PrefixDeclaration -> ShowS show :: PrefixDeclaration -> String showList :: [PrefixDeclaration] -> ShowS | |
Generic PrefixDeclaration | |
Defined in OWL2.ATC_OWL2 type Rep PrefixDeclaration :: Type -> Type from :: PrefixDeclaration -> Rep PrefixDeclaration x to :: Rep PrefixDeclaration x -> PrefixDeclaration | |
FromJSON PrefixDeclaration | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser PrefixDeclaration parseJSONList :: Value -> Parser [PrefixDeclaration] | |
ToJSON PrefixDeclaration | |
Defined in OWL2.ATC_OWL2 toJSON :: PrefixDeclaration -> Value toEncoding :: PrefixDeclaration -> Encoding toJSONList :: [PrefixDeclaration] -> Value toEncodingList :: [PrefixDeclaration] -> Encoding | |
ShATermConvertible PrefixDeclaration | |
Defined in OWL2.ATC_OWL2 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 # | |
Defined in OWL2.Function function :: Action -> AMap -> PrefixDeclaration -> PrefixDeclaration Source # | |
type Rep PrefixDeclaration | |
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 #
Ontology | |
|
Instances
Eq Ontology Source # | |
Data Ontology Source # | |
Defined in OWL2.AS 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 # | |
Show Ontology Source # | |
Generic Ontology | |
Semigroup Ontology | |
Monoid Ontology | |
FromJSON Ontology | |
Defined in OWL2.ATC_OWL2 parseJSON :: Value -> Parser Ontology parseJSONList :: Value -> Parser [Ontology] | |
ToJSON Ontology | |
Defined in OWL2.ATC_OWL2 toEncoding :: Ontology -> Encoding toJSONList :: [Ontology] -> Value toEncodingList :: [Ontology] -> Encoding | |
ShATermConvertible Ontology | |
Defined in OWL2.ATC_OWL2 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 # | |
type Rep Ontology | |
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]))))) |