Copyright | (c) 2003 Graham Klyne 2009 Vasili I Galchin 2011 - 2016 2018 2020. 2022 2024 Douglas Burke |
---|---|
License | GPL V2 |
Maintainer | Douglas Burke |
Stability | experimental |
Portability | CPP, FlexibleInstances, MultiParamTypeClasses, OverloadedStrings |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines a memory-based RDF graph instance. At present only
RDF 1.0 is explicitly supported; I have not gone through the RDF 1.1
changes to see how the code needs to be updated. This means that you
can have untyped strings in your graph that do not match the same content
but with an explicit xsd:string
datatype.
Note that the identifiers for blank nodes may not be propogated when
a graph is written out using one of the formatters, such as
Turtle
. There is limited support for
generating new blank nodes from an existing set of triples; e.g.
newNode
and newNodes
.
Synopsis
- data RDFLabel
- class ToRDFLabel a where
- toRDFLabel :: a -> RDFLabel
- class FromRDFLabel a where
- fromRDFLabel :: RDFLabel -> Maybe a
- isLiteral :: RDFLabel -> Bool
- isUntypedLiteral :: RDFLabel -> Bool
- isTypedLiteral :: RDFLabel -> Bool
- isXMLLiteral :: RDFLabel -> Bool
- isDatatyped :: ScopedName -> RDFLabel -> Bool
- isMemberProp :: RDFLabel -> Bool
- isUri :: RDFLabel -> Bool
- isBlank :: RDFLabel -> Bool
- isQueryVar :: RDFLabel -> Bool
- getLiteralText :: RDFLabel -> Text
- getScopedName :: RDFLabel -> ScopedName
- makeBlank :: RDFLabel -> RDFLabel
- quote :: Bool -> String -> String
- quoteT :: Bool -> Text -> Text
- type RDFArcSet = ArcSet RDFLabel
- type RDFTriple = Arc RDFLabel
- toRDFTriple :: (ToRDFLabel s, ToRDFLabel p, ToRDFLabel o) => s -> p -> o -> RDFTriple
- fromRDFTriple :: (FromRDFLabel s, FromRDFLabel p, FromRDFLabel o) => RDFTriple -> Maybe (s, p, o)
- data NSGraph lb = NSGraph {
- namespaces :: NamespaceMap
- formulae :: FormulaMap lb
- statements :: ArcSet lb
- type RDFGraph = NSGraph RDFLabel
- toRDFGraph :: RDFArcSet -> RDFGraph
- emptyRDFGraph :: RDFGraph
- type NamespaceMap = Map (Maybe Text) URI
- emptyNamespaceMap :: NamespaceMap
- data LookupFormula lb gr = Formula {}
- type Formula lb = LookupFormula lb (NSGraph lb)
- type FormulaMap lb = Map lb (NSGraph lb)
- emptyFormulaMap :: FormulaMap RDFLabel
- addArc :: Label lb => Arc lb -> NSGraph lb -> NSGraph lb
- merge :: Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb
- allLabels :: Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
- allNodes :: Label lb => (lb -> Bool) -> NSGraph lb -> Set lb
- remapLabels :: Label lb => [lb] -> [lb] -> (lb -> lb) -> NSGraph lb -> NSGraph lb
- remapLabelList :: Label lb => [lb] -> [lb] -> [(lb, lb)]
- newNode :: Label lb => lb -> [lb] -> lb
- newNodes :: Label lb => lb -> [lb] -> [lb]
- setNamespaces :: NamespaceMap -> NSGraph lb -> NSGraph lb
- getNamespaces :: NSGraph lb -> NamespaceMap
- setFormulae :: FormulaMap lb -> NSGraph lb -> NSGraph lb
- getFormulae :: NSGraph lb -> FormulaMap lb
- setFormula :: Label lb => Formula lb -> NSGraph lb -> NSGraph lb
- getFormula :: Label lb => NSGraph lb -> lb -> Maybe (NSGraph lb)
- fmapNSGraph :: Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb
- traverseNSGraph :: (Applicative f, Ord a) => (a -> f a) -> NSGraph a -> f (NSGraph a)
- class LDGraph lg lb where
- emptyGraph :: lg lb
- setArcs :: lg lb -> ArcSet lb -> lg lb
- getArcs :: lg lb -> ArcSet lb
- extract :: Ord lb => Selector lb -> lg lb -> lg lb
- addGraphs :: Ord lb => lg lb -> lg lb -> lg lb
- delete :: Ord lb => lg lb -> lg lb -> lg lb
- labels :: Ord lb => lg lb -> Set lb
- nodes :: Ord lb => lg lb -> Set lb
- update :: (ArcSet lb -> ArcSet lb) -> lg lb -> lg lb
- class (Ord lb, Show lb) => Label lb where
- data Arc lb = Arc {}
- arc :: lb -> lb -> lb -> Arc lb
- type Selector lb = Arc lb -> Bool
- resRdfRDF :: RDFLabel
- resRdfDescription :: RDFLabel
- resRdfID :: RDFLabel
- resRdfAbout :: RDFLabel
- resRdfParseType :: RDFLabel
- resRdfResource :: RDFLabel
- resRdfLi :: RDFLabel
- resRdfNodeID :: RDFLabel
- resRdfDatatype :: RDFLabel
- resRdf1 :: RDFLabel
- resRdf2 :: RDFLabel
- resRdfn :: Word32 -> RDFLabel
- resRdfsResource :: RDFLabel
- resRdfsClass :: RDFLabel
- resRdfsLiteral :: RDFLabel
- resRdfsDatatype :: RDFLabel
- resRdfXMLLiteral :: RDFLabel
- resRdfProperty :: RDFLabel
- resRdfsRange :: RDFLabel
- resRdfsDomain :: RDFLabel
- resRdfType :: RDFLabel
- resRdfsSubClassOf :: RDFLabel
- resRdfsSubPropertyOf :: RDFLabel
- resRdfsLabel :: RDFLabel
- resRdfsComment :: RDFLabel
- resRdfsContainer :: RDFLabel
- resRdfBag :: RDFLabel
- resRdfSeq :: RDFLabel
- resRdfAlt :: RDFLabel
- resRdfsContainerMembershipProperty :: RDFLabel
- resRdfsMember :: RDFLabel
- resRdfList :: RDFLabel
- resRdfFirst :: RDFLabel
- resRdfRest :: RDFLabel
- resRdfNil :: RDFLabel
- resRdfStatement :: RDFLabel
- resRdfSubject :: RDFLabel
- resRdfPredicate :: RDFLabel
- resRdfObject :: RDFLabel
- resRdfsSeeAlso :: RDFLabel
- resRdfsIsDefinedBy :: RDFLabel
- resRdfValue :: RDFLabel
- resOwlSameAs :: RDFLabel
- resRdfdGeneralRestriction :: RDFLabel
- resRdfdOnProperties :: RDFLabel
- resRdfdConstraint :: RDFLabel
- resRdfdMaxCardinality :: RDFLabel
- resLogImplies :: RDFLabel
- grMatchMap :: Label lb => NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb))
- grEq :: Label lb => NSGraph lb -> NSGraph lb -> Bool
- mapnode :: Label lb => [lb] -> [lb] -> (lb -> lb) -> lb -> lb
- maplist :: Label lb => [lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]
Labels
RDF graph node values
cf. http://www.w3.org/TR/rdf-concepts/#section-Graph-syntax version 1.0
This is extended from the RDF abstract graph syntax in the following ways:
(a) a graph can be part of a resource node or blank node (cf. Notation3 formulae)
(b) a "variable" node option is distinguished from a blank node. I have found this useful for encoding and handling queries, even though query variables can be expressed as blank nodes.
(c) a "NoNode" option is defined.
This might otherwise be handled by Maybe (RDFLabel g)
.
Prior to version 0.7.0.0
, literals were represented by a
single constructor, Lit
, with an optional argument. Language
codes for literals was also stored as a ScopedName
rather than
as a LanguageTag
.
Res ScopedName | resource |
Lit Text | plain literal (http://www.w3.org/TR/rdf-concepts/#dfn-plain-literal) |
LangLit Text LanguageTag | plain literal |
TypedLit Text ScopedName | typed literal (http://www.w3.org/TR/rdf-concepts/#dfn-typed-literal) |
Blank String | blank node |
Var String | variable (not used in ordinary graphs) |
NoNode | no node (not used in ordinary graphs) |
Instances
IsString RDFLabel Source # | |
Defined in Swish.RDF.Graph fromString :: String -> RDFLabel # | |
Show RDFLabel Source # | |
Eq RDFLabel Source # | Define equality of nodes possibly based on different graph types. The equality of literals is taken from section 6.5.1 ("Literal Equality") of the RDF Concepts and Abstract Document, http://www.w3.org/TR/2004/REC-rdf-concepts-20040210/#section-Literal-Equality. |
Ord RDFLabel Source # | |
Defined in Swish.RDF.Graph | |
ShowLines RDFGraph Source # | |
Label RDFLabel Source # | |
FromRDFLabel RDFLabel Source # | This is just |
Defined in Swish.RDF.Graph | |
ToRDFLabel RDFLabel Source # | This is just |
Defined in Swish.RDF.Graph toRDFLabel :: RDFLabel -> RDFLabel Source # |
class ToRDFLabel a where Source #
A type that can be converted to a RDF Label.
The String instance converts to an untyped literal (so no language tag is assumed).
The UTCTime
and Day
instances assume values are in UTC.
The conversion for XSD types attempts to use the canonical form described in section 2.3.1 of http://www.w3.org/TR/2004/REC-xmlschema-2-20041028/#lexical-space.
Note that this is similar to
toRDFLabel
;
the code should probably be combined at some point.
toRDFLabel :: a -> RDFLabel Source #
Instances
class FromRDFLabel a where Source #
A type that can be converted from a RDF Label, with the possibility of failure.
The String instance converts from an untyped literal (so it can not be used with a string with a language tag).
The following conversions are supported for common XSD
types (out-of-band values result in Nothing
):
xsd:boolean
toBool
xsd:integer
toInt
andInteger
xsd:float
toFloat
xsd:double
toDouble
xsd:dateTime
toUTCTime
xsd:date
toDay
Note that this is similar to
fromRDFLabel
;
the code should probably be combined at some point.
fromRDFLabel :: RDFLabel -> Maybe a Source #
Instances
FromRDFLabel URI Source # | Converts from a Resource. |
Defined in Swish.RDF.Graph | |
FromRDFLabel ScopedName Source # | Converts from a Resource. |
Defined in Swish.RDF.Graph fromRDFLabel :: RDFLabel -> Maybe ScopedName Source # | |
FromRDFLabel QName Source # | Converts from a Resource. |
Defined in Swish.RDF.Graph | |
FromRDFLabel RDFLabel Source # | This is just |
Defined in Swish.RDF.Graph | |
FromRDFLabel Day Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel UTCTime Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel String Source # | Only untyped literals are converted to strings. |
Defined in Swish.RDF.Graph | |
FromRDFLabel Integer Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel Bool Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel Char Source # | The label must be an untyped literal containing a single character. |
Defined in Swish.RDF.Graph | |
FromRDFLabel Double Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel Float Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph | |
FromRDFLabel Int Source # | Converts from a literal with a |
Defined in Swish.RDF.Graph |
isUntypedLiteral :: RDFLabel -> Bool Source #
isTypedLiteral :: RDFLabel -> Bool Source #
Test if supplied labal is a typed literal node (TypedLit
).
isXMLLiteral :: RDFLabel -> Bool Source #
Test if supplied labal is a XML literal node
isDatatyped :: ScopedName -> RDFLabel -> Bool Source #
Test if supplied label is a typed literal node of a given datatype
isMemberProp :: RDFLabel -> Bool Source #
Test if supplied label is a container membership property
Check for namespace is RDF namespace and first character of local name is '_' and remaining characters of local name are all digits
isQueryVar :: RDFLabel -> Bool Source #
Test if supplied labal is a query variable
getLiteralText :: RDFLabel -> Text Source #
Extract text value from a literal node (including the Language and Typed variants). The empty string is returned for other nodes.
getScopedName :: RDFLabel -> ScopedName Source #
Extract the ScopedName value from a resource node (nullScopedName
is returned for non-resource nodes).
makeBlank :: RDFLabel -> RDFLabel Source #
Make a blank node from a supplied query variable, or return the supplied label unchanged. (Use this in when substituting an existential for an unsubstituted query variable.)
:: Bool |
|
-> String | String to quote. |
-> String | The string does not contain the surrounding quote marks. |
Turtle-style quoting rules for a string.
At present the choice is between using one or three
double quote ("
) characters to surround the string; i.e. using
single quote ('
) characters is not supported.
As of Swish 0.9.0.6, the \f
character is converted to
\u000C
rather than left as is to aid interoperability
with some other tools.
RDF Graphs
type RDFTriple = Arc RDFLabel Source #
RDF Triple (statement)
At present there is no check or type-level constraint that stops the subject or predicate of the triple from being a literal.
:: (ToRDFLabel s, ToRDFLabel p, ToRDFLabel o) | |
=> s | Subject |
-> p | Predicate |
-> o | Object |
-> RDFTriple |
Convert 3 RDF labels to a RDF triple.
See also Swish.RDF.GraphClass.arcFromTriple
.
:: (FromRDFLabel s, FromRDFLabel p, FromRDFLabel o) | |
=> RDFTriple | |
-> Maybe (s, p, o) | The conversion only succeeds if all three components can be converted to the correct Haskell types. |
Extract the contents of a RDF triple.
See also Swish.RDF.GraphClass.arcToTriple
.
Memory-based graph with namespaces and subgraphs.
The primary means for adding arcs to an existing graph are:
NSGraph | |
|
Instances
ShowLines RDFGraph Source # | |
LDGraph NSGraph lb Source # | |
Defined in Swish.RDF.Graph emptyGraph :: NSGraph lb Source # setArcs :: NSGraph lb -> ArcSet lb -> NSGraph lb Source # getArcs :: NSGraph lb -> ArcSet lb Source # extract :: Selector lb -> NSGraph lb -> NSGraph lb Source # addGraphs :: NSGraph lb -> NSGraph lb -> NSGraph lb Source # delete :: NSGraph lb -> NSGraph lb -> NSGraph lb Source # labels :: NSGraph lb -> Set lb Source # nodes :: NSGraph lb -> Set lb Source # update :: (ArcSet lb -> ArcSet lb) -> NSGraph lb -> NSGraph lb Source # | |
Label lb => Monoid (NSGraph lb) Source # | The |
Label lb => Semigroup (NSGraph lb) Source # | |
Label lb => Show (Formula lb) Source # | |
Label lb => Show (NSGraph lb) Source # | |
Label lb => Eq (NSGraph lb) Source # | |
Label lb => Ord (NSGraph lb) Source # | |
toRDFGraph :: RDFArcSet -> RDFGraph Source #
Create a new RDF graph from a supplied set of arcs.
This version will attempt to fill up the namespace map of the graph based on the input labels (including datatypes on literals). For faster creation of a graph you can use:
emptyRDFGraph { statements = arcs }
which is how this routine was defined in version 0.3.1.1
and earlier.
emptyRDFGraph :: RDFGraph Source #
Create a new, empty RDF graph (it is just mempty
).
type NamespaceMap = Map (Maybe Text) URI Source #
Namespace prefix list entry
A map for name spaces (key is the prefix).
emptyNamespaceMap :: NamespaceMap Source #
Create an empty namespace map.
data LookupFormula lb gr Source #
Graph formula entry
Instances
Label lb => Show (Formula lb) Source # | |
(Eq lb, Eq gr) => Eq (LookupFormula lb gr) Source # | |
Defined in Swish.RDF.Graph (==) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # (/=) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # | |
(Ord lb, Ord gr) => Ord (LookupFormula lb gr) Source # | |
Defined in Swish.RDF.Graph compare :: LookupFormula lb gr -> LookupFormula lb gr -> Ordering # (<) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # (<=) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # (>) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # (>=) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool # max :: LookupFormula lb gr -> LookupFormula lb gr -> LookupFormula lb gr # min :: LookupFormula lb gr -> LookupFormula lb gr -> LookupFormula lb gr # |
type Formula lb = LookupFormula lb (NSGraph lb) Source #
A named formula.
type FormulaMap lb = Map lb (NSGraph lb) Source #
A map for named formulae.
emptyFormulaMap :: FormulaMap RDFLabel Source #
Create an empty formula map.
addArc :: Label lb => Arc lb -> NSGraph lb -> NSGraph lb Source #
Add an arc to the graph. It does not relabel any blank nodes in the input arc, nor does it change the namespace map, but it does ensure that the arc is unknown before adding it.
merge :: Label lb => NSGraph lb -> NSGraph lb -> NSGraph lb Source #
Merge RDF graphs, renaming blank and query variable nodes as needed to neep variable nodes from the two graphs distinct in the resulting graph.
Currently formulae are not guaranteed to be preserved across a merge.
allLabels :: Label lb => (lb -> Bool) -> NSGraph lb -> Set lb Source #
Return list of all labels (including properties) in the graph satisfying a supplied filter predicate. This routine includes the labels in any formulae.
allNodes :: Label lb => (lb -> Bool) -> NSGraph lb -> Set lb Source #
Return list of all subjects and objects in the graph satisfying a supplied filter predicate.
:: Label lb | |
=> [lb] | variable nodes to be renamed ( |
-> [lb] | variable nodes used that must be avoided ( |
-> (lb -> lb) | node conversion function that is applied to nodes
from |
-> NSGraph lb | graph in which nodes are to be renamed |
-> NSGraph lb |
Remap selected nodes in graph.
This is the node renaming operation that prevents graph-scoped variable nodes from being merged when two graphs are merged.
:: Label lb | |
=> [lb] | labels to be remaped |
-> [lb] | labels to be avoided by the remapping |
-> [(lb, lb)] |
Externally callable function to construct a list of (old,new) values to be used for graph label remapping.
newNode :: Label lb => lb -> [lb] -> lb Source #
Given a node and a list of existing nodes, find a new node for the supplied node that does not clash with any existing node. (Generates an non-terminating list of possible replacements, and picks the first one that isn't already in use.)
newNodes :: Label lb => lb -> [lb] -> [lb] Source #
Given a node and a list of existing nodes, generate a list of new nodes for the supplied node that do not clash with any existing node.
setNamespaces :: NamespaceMap -> NSGraph lb -> NSGraph lb Source #
Replace the namespace information in the graph.
getNamespaces :: NSGraph lb -> NamespaceMap Source #
Retrieve the namespace map in the graph.
setFormulae :: FormulaMap lb -> NSGraph lb -> NSGraph lb Source #
Replace the formulae in the graph.
getFormulae :: NSGraph lb -> FormulaMap lb Source #
Retrieve the formulae in the graph.
setFormula :: Label lb => Formula lb -> NSGraph lb -> NSGraph lb Source #
Add (or replace) a formula.
getFormula :: Label lb => NSGraph lb -> lb -> Maybe (NSGraph lb) Source #
Find a formula in the graph, if it exists.
traverseNSGraph :: (Applicative f, Ord a) => (a -> f a) -> NSGraph a -> f (NSGraph a) Source #
Re-export from GraphClass
Note that asubj
, apred
and aobj
have been
removed in version 0.7.0.0
; use arcSubj
, arcPred
or arcObj
instead.
class LDGraph lg lb where Source #
Labelled Directed Graph class.
Minimum required implementation:
emptyGraph
, setArcs
, and getArcs
.
emptyGraph :: lg lb Source #
Create the empty graph.
setArcs :: lg lb -> ArcSet lb -> lg lb Source #
Replace the existing arcs in the graph.
getArcs :: lg lb -> ArcSet lb Source #
Extract all the arcs from a graph
extract :: Ord lb => Selector lb -> lg lb -> lg lb Source #
Extract those arcs that match the given Selector
.
addGraphs :: Ord lb => lg lb -> lg lb -> lg lb Source #
Add the two graphs
:: Ord lb | |
=> lg lb | g1 |
-> lg lb | g2 |
-> lg lb | g2 - g1 -> g3 |
Remove those arcs in the first graph from the second graph
labels :: Ord lb => lg lb -> Set lb Source #
Enumerate the distinct labels contained in a graph;
that is, any label that appears in the subject,
predicate or object position of an Arc
.
nodes :: Ord lb => lg lb -> Set lb Source #
Enumerate the distinct nodes contained in a graph;
that is, any label that appears in the subject
or object position of an Arc
.
update :: (ArcSet lb -> ArcSet lb) -> lg lb -> lg lb Source #
Update the arcs in a graph using a supplied function.
Instances
class (Ord lb, Show lb) => Label lb where Source #
Label class.
A label may have a fixed binding, which means that the label identifies (is) a particular graph node, and different such labels are always distinct nodes. Alternatively, a label may be unbound (variable), which means that it is a placeholder for an unknown node label. Unbound node labels are used as graph-local identifiers for indicating when the same node appears in several arcs.
For the purposes of graph-isomorphism testing, fixed labels are matched when they are the same. Variable labels may be matched with any other variable label. Our definition of isomorphism (for RDF graphs) does not match variable labels with fixed labels.
labelIsVar :: lb -> Bool Source #
Does this node have a variable binding?
labelHash :: Int -> lb -> Int Source #
Calculate the hash of the label using the supplied seed.
getLocal :: lb -> String Source #
Extract the local id from a variable node.
makeLabel :: String -> lb Source #
Make a label value from a local id.
Instances
Label LabelMem Source # | |
Label RDFLabel Source # | |
Label lb => Label (ScopedLabel lb) Source # | |
Defined in Swish.GraphMatch labelIsVar :: ScopedLabel lb -> Bool Source # labelHash :: Int -> ScopedLabel lb -> Int Source # getLocal :: ScopedLabel lb -> String Source # makeLabel :: String -> ScopedLabel lb Source # |
Arc type.
Prior to 0.7.0.0
you could also use asubj
, apred
and aobj
to access the elements of the arc.
Instances
Foldable Arc Source # | |
Defined in Swish.GraphClass fold :: Monoid m => Arc m -> m # foldMap :: Monoid m => (a -> m) -> Arc a -> m # foldMap' :: Monoid m => (a -> m) -> Arc a -> m # foldr :: (a -> b -> b) -> b -> Arc a -> b # foldr' :: (a -> b -> b) -> b -> Arc a -> b # foldl :: (b -> a -> b) -> b -> Arc a -> b # foldl' :: (b -> a -> b) -> b -> Arc a -> b # foldr1 :: (a -> a -> a) -> Arc a -> a # foldl1 :: (a -> a -> a) -> Arc a -> a # elem :: Eq a => a -> Arc a -> Bool # maximum :: Ord a => Arc a -> a # | |
Traversable Arc Source # | |
Functor Arc Source # | |
Show lb => Show (Arc lb) Source # | |
Eq lb => Eq (Arc lb) Source # | |
Ord lb => Ord (Arc lb) Source # | |
Hashable lb => Hashable (Arc lb) Source # | |
Defined in Swish.GraphClass |
:: lb | The subject of the arc. |
-> lb | The predicate of the arc. |
-> lb | The object of the arc. |
-> Arc lb |
Create an arc.
Selected RDFLabel values
The ToRDFLabel
instance of ScopedName
can also be used
to easily construct RDFLabel
versions of the terms defined
in Swish.RDF.Vocabulary.
RDF terms
These terms are described in http://www.w3.org/TR/rdf-syntax-grammar/; the version used is "W3C Recommendation 10 February 2004", http://www.w3.org/TR/2004/REC-rdf-syntax-grammar-20040210/.
Some terms are listed within the RDF Schema terms below since their definition is given within the RDF Schema document.
resRdfDescription :: RDFLabel Source #
rdf:Description
.
resRdfAbout :: RDFLabel Source #
rdf:about
.
resRdfParseType :: RDFLabel Source #
rdf:parseType
.
resRdfResource :: RDFLabel Source #
rdf:resource
.
resRdfNodeID :: RDFLabel Source #
rdf:nodeID
.
resRdfDatatype :: RDFLabel Source #
rdf:datatype
.
resRdfn :: Word32 -> RDFLabel Source #
Create a rdf:_n
entity.
There is no check that the argument is not 0
.
RDF Schema terms
These are defined by http://www.w3.org/TR/rdf-schema/; the version used is "W3C Recommendation 10 February 2004", http://www.w3.org/TR/2004/REC-rdf-schema-20040210/.
Classes
See the "Classes" section at http://www.w3.org/TR/rdf-schema/#ch_classes for more information.
resRdfsResource :: RDFLabel Source #
rdfs:Resource
from http://www.w3.org/TR/rdf-schema/#ch_resource.
resRdfsClass :: RDFLabel Source #
rdfs:Class
from http://www.w3.org/TR/rdf-schema/#ch_class.
resRdfsLiteral :: RDFLabel Source #
rdfs:Literal
from http://www.w3.org/TR/rdf-schema/#ch_literal.
resRdfsDatatype :: RDFLabel Source #
rdfs:Datatype
from http://www.w3.org/TR/rdf-schema/#ch_datatype.
resRdfXMLLiteral :: RDFLabel Source #
rdf:XMLLiteral
from http://www.w3.org/TR/rdf-schema/#ch_xmlliteral.
resRdfProperty :: RDFLabel Source #
rdf:Property
from http://www.w3.org/TR/rdf-schema/#ch_property.
Properties
See the "Properties" section at http://www.w3.org/TR/rdf-schema/#ch_classes for more information.
resRdfsRange :: RDFLabel Source #
rdfs:range
from http://www.w3.org/TR/rdf-schema/#ch_range.
resRdfsDomain :: RDFLabel Source #
rdfs:domain
from http://www.w3.org/TR/rdf-schema/#ch_domain.
resRdfType :: RDFLabel Source #
rdf:type
from http://www.w3.org/TR/rdf-schema/#ch_type.
resRdfsSubClassOf :: RDFLabel Source #
rdfs:subClassOf
from http://www.w3.org/TR/rdf-schema/#ch_subclassof.
resRdfsSubPropertyOf :: RDFLabel Source #
rdfs:subPropertyOf
from http://www.w3.org/TR/rdf-schema/#ch_subpropertyof.
resRdfsLabel :: RDFLabel Source #
rdfs:label
from http://www.w3.org/TR/rdf-schema/#ch_label.
resRdfsComment :: RDFLabel Source #
rdfs:comment
from http://www.w3.org/TR/rdf-schema/#ch_comment.
Containers
See the "Container Classes and Properties" section at http://www.w3.org/TR/rdf-schema/#ch_containervocab.
resRdfsContainer :: RDFLabel Source #
rdfs:Container
from http://www.w3.org/TR/rdf-schema/#ch_container.
resRdfBag :: RDFLabel Source #
rdf:Bag
from http://www.w3.org/TR/rdf-schema/#ch_bag.
resRdfSeq :: RDFLabel Source #
rdf:Seq
from http://www.w3.org/TR/rdf-schema/#ch_seq.
resRdfAlt :: RDFLabel Source #
rdf:Alt
from http://www.w3.org/TR/rdf-schema/#ch_alt.
resRdfsContainerMembershipProperty :: RDFLabel Source #
rdfs:ContainerMembershipProperty
from http://www.w3.org/TR/rdf-schema/#ch_containermembershipproperty.
resRdfsMember :: RDFLabel Source #
rdfs:member
from http://www.w3.org/TR/rdf-schema/#ch_member.
Collections
See the "Collections" section at http://www.w3.org/TR/rdf-schema/#ch_collectionvocab.
resRdfList :: RDFLabel Source #
rdf:List
from http://www.w3.org/TR/rdf-schema/#ch_list.
resRdfFirst :: RDFLabel Source #
rdf:first
from http://www.w3.org/TR/rdf-schema/#ch_first.
resRdfRest :: RDFLabel Source #
rdf:rest
from http://www.w3.org/TR/rdf-schema/#ch_rest.
resRdfNil :: RDFLabel Source #
rdf:nil
from http://www.w3.org/TR/rdf-schema/#ch_nil.
Reification Vocabulary
See the "Reification Vocabulary" section at http://www.w3.org/TR/rdf-schema/#ch_reificationvocab.
resRdfStatement :: RDFLabel Source #
rdf:Statement
from http://www.w3.org/TR/rdf-schema/#ch_statement.
resRdfSubject :: RDFLabel Source #
rdf:subject
from http://www.w3.org/TR/rdf-schema/#ch_subject.
resRdfPredicate :: RDFLabel Source #
rdf:predicate
from http://www.w3.org/TR/rdf-schema/#ch_predicate.
resRdfObject :: RDFLabel Source #
rdf:object
from http://www.w3.org/TR/rdf-schema/#ch_object.
Utility Properties
See the "Utility Properties" section at http://www.w3.org/TR/rdf-schema/#ch_utilvocab.
resRdfsSeeAlso :: RDFLabel Source #
rdfs:seeAlso
from http://www.w3.org/TR/rdf-schema/#ch_seealso.
resRdfsIsDefinedBy :: RDFLabel Source #
rdfs:isDefinedBy
from http://www.w3.org/TR/rdf-schema/#ch_isdefinedby.
resRdfValue :: RDFLabel Source #
rdf:value
from http://www.w3.org/TR/rdf-schema/#ch_value.
OWL
resOwlSameAs :: RDFLabel Source #
owl:sameAs
.
Miscellaneous
resRdfdGeneralRestriction :: RDFLabel Source #
rdfd:GeneralRestriction
.
resRdfdOnProperties :: RDFLabel Source #
rdfd:onProperties
.
resRdfdConstraint :: RDFLabel Source #
rdfd:constraint
.
resRdfdMaxCardinality :: RDFLabel Source #
rdfd:maxCardinality
.
resLogImplies :: RDFLabel Source #
log:implies
.
Exported for testing
grMatchMap :: Label lb => NSGraph lb -> NSGraph lb -> (Bool, LabelMap (ScopedLabel lb)) Source #
Match graphs, returning True
if they are equivalent,
with a map of labels to equivalence class identifiers
(see graphMatch
for further details).
mapnode :: Label lb => [lb] -> [lb] -> (lb -> lb) -> lb -> lb Source #
Remap a single graph node.
If the node is not one of those to be remapped, the supplied value is returned unchanged.
:: Label lb | |
=> [lb] | oldnode values |
-> [lb] | nodes to be avoided |
-> (lb -> lb) | |
-> [(lb, lb)] | accumulator |
-> [(lb, lb)] |
Construct a list of (oldnode,newnode) values to be used for graph label remapping. The function operates recursively, adding new nodes generated to the accumulator and also to the list of nodes to be avoided.