swish-0.6.1.0: A semantic web toolkit.

PortabilityFlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances, OverloadedStrings
Stabilityexperimental
MaintainerDouglas Burke

Swish.RDF.RDFGraph

Contents

Description

This module defines a memory-based RDF graph instance.

Synopsis

Labels

data RDFLabel Source

RDF graph node values

cf. http://www.w3.org/TR/rdf-concepts/#section-Graph-syntax

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).

Constructors

Res ScopedName

resource

Lit Text (Maybe ScopedName)

literal [type/language]

Blank String

blank node

Var String

variable (not used in ordinary graphs)

NoNode

no node (not used in ordinary graphs)

Instances

Eq RDFLabel

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 
Show RDFLabel 
IsString RDFLabel 
ShowM RDFGraph 
Label RDFLabel 
FromRDFLabel RDFLabel

This is just `Just . id`.

ToRDFLabel RDFLabel

This is just id.

LookupEntryClass NamedGraph ScopedName [RDFGraph] 

class ToRDFLabel a whereSource

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 very similar to Swish.RDF.RDFDatatype.toRDFLabel and should be moved into a Swish.RDF.Datatype module.

Methods

toRDFLabel :: a -> RDFLabelSource

Instances

ToRDFLabel Bool

Converts to a literal with a xsd:boolean datatype.

ToRDFLabel Char

The character is converted to an untyped literal of length one.

ToRDFLabel Double

Converts to a literal with a xsd:double datatype.

ToRDFLabel Float

Converts to a literal with a xsd:float datatype.

ToRDFLabel Int

Converts to a literal with a xsd:integer datatype.

ToRDFLabel Integer

Converts to a literal with a xsd:integer datatype.

ToRDFLabel String

Strings are converted to untyped literals.

ToRDFLabel URI

Converts to a Resource.

ToRDFLabel UTCTime

Converts to a literal with a xsd:datetime datatype.

ToRDFLabel Day

Converts to a literal with a xsd:date datatype.

ToRDFLabel QName

Converts to a Resource.

ToRDFLabel ScopedName

Converts to a Resource.

ToRDFLabel RDFLabel

This is just id.

class FromRDFLabel a whereSource

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 to Bool
  • xsd:integer to Int and Integer
  • xsd:float to Float
  • xsd:double to Double
  • xsd:dateTime to UTCTime
  • xsd:date to Day

Note that this is very similar to Swish.RDF.RDFDatatype.fromRDFLabel and should be moved into a Swish.RDF.Datatype module.

Instances

FromRDFLabel Bool

Converts from a literal with a xsd:boolean datatype. The literal can be any of the supported XSD forms - e.g. "0" or "true".

FromRDFLabel Char

The label must be an untyped literal containing a single character.

FromRDFLabel Double

Converts from a literal with a xsd:double datatype.

FromRDFLabel Float

Converts from a literal with a xsd:float datatype. The conversion will fail if the value is outside the valid range of a Haskell Float.

FromRDFLabel Int

Converts from a literal with a xsd:integer datatype. The conversion will fail if the value is outside the valid range of a Haskell Int.

FromRDFLabel Integer

Converts from a literal with a xsd:integer datatype.

FromRDFLabel String

Only untyped literals are converted to strings.

FromRDFLabel URI

Converts from a Resource.

FromRDFLabel UTCTime

Converts from a literal with a xsd:datetime datatype.

FromRDFLabel Day

Converts from a literal with a xsd:date datatype.

FromRDFLabel QName

Converts from a Resource.

FromRDFLabel ScopedName

Converts from a Resource.

FromRDFLabel RDFLabel

This is just `Just . id`.

isLiteral :: RDFLabel -> BoolSource

Test if supplied labal is a literal node

isUntypedLiteral :: RDFLabel -> BoolSource

Test if supplied labal is an untyped literal node

isTypedLiteral :: RDFLabel -> BoolSource

Test if supplied labal is an untyped literal node

isXMLLiteral :: RDFLabel -> BoolSource

Test if supplied labal is an XML literal node

isDatatyped :: ScopedName -> RDFLabel -> BoolSource

Test if supplied label is an typed literal node of a given datatype

isMemberProp :: RDFLabel -> BoolSource

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

isUri :: RDFLabel -> BoolSource

Test if supplied labal is a URI resource node

isBlank :: RDFLabel -> BoolSource

Test if supplied labal is a blank node

isQueryVar :: RDFLabel -> BoolSource

Test if supplied labal is a query variable

getLiteralText :: RDFLabel -> TextSource

Extract text value from a literal node

getScopedName :: RDFLabel -> ScopedNameSource

Extract ScopedName value from a resource node

makeBlank :: RDFLabel -> RDFLabelSource

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.)

quoteSource

Arguments

:: Bool

True if the string is to be displayed using one rather than three quotes.

-> String

String to quote.

-> String 

N3-style quoting rules for a string.

TODO: when flag is False need to worry about multiple quotes (> 2) in a row.

RDF Graphs

type RDFTriple = Arc RDFLabelSource

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.

toRDFTripleSource

Arguments

:: (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.

fromRDFTripleSource

Arguments

:: (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.

data NSGraph lb Source

Memory-based graph with namespaces and subgraphs.

The primary means for adding arcs to an existing graph are:

  • setArcs from the LDGraph instance, which replaces the existing set of arcs and does not change the namespace map.
  • addArc which checks that the arc is unknown before adding it but does not change the namespace map or re-label any blank nodes in the arc.

Constructors

NSGraph 

Fields

namespaces :: NamespaceMap

the namespaces to use

formulae :: FormulaMap lb

any associated formulae (a.k.a. sub- or named- graps)

statements :: [Arc lb]

the statements in the graph

type RDFGraph = NSGraph RDFLabelSource

Memory-based RDF graph type

toRDFGraph :: [RDFTriple] -> RDFGraphSource

Create a new RDF graph from a supplied list 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 :: RDFGraphSource

Create a new, empty RDF graph.

This uses mempty from the Monoid instance of NSGraph.

type NamespaceMap = LookupMap NamespaceSource

Namespace prefix list entry

emptyNamespaceMap :: NamespaceMapSource

Create an emoty namespace map.

data LookupFormula lb gr Source

Graph formula entry

Constructors

Formula 

Fields

formLabel :: lb

The label for the formula

formGraph :: gr

The contents of the formula

Instances

(Eq lb, Eq gr) => Eq (LookupFormula lb gr) 
Label lb => Show (LookupFormula lb (NSGraph lb)) 
Label lb => LookupEntryClass (LookupFormula lb (NSGraph lb)) lb (NSGraph lb) 

emptyFormulaMap :: FormulaMap RDFLabelSource

Create an empty formula map.

addArc :: Label lb => Arc lb -> NSGraph lb -> NSGraph lbSource

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 lbSource

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 -> [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 -> [lb]Source

Return list of all subjects and objects in the graph satisfying a supplied filter predicate.

remapLabelsSource

Arguments

:: Label lb 
=> [lb]

variable nodes to be renamed (dupbn)

-> [lb]

variable nodes used that must be avoided (allbn)

-> (lb -> lb)

node conversion function that is applied to nodes from dupbn in the graph that are to be replaced by new blank nodes. If no such conversion is required, supply id. The function makeBlank can be used to convert RDF query nodes into RDF blank nodes.

-> 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.

remapLabelListSource

Arguments

:: 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] -> lbSource

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.)

TODO: optimize this for common case nnn and _nnn: always generate _nnn and keep track of last allocated

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 lbSource

Replace the namespace information in the graph.

getNamespaces :: NSGraph lb -> NamespaceMapSource

Retrieve the namespace map in the graph.

setFormulae :: FormulaMap lb -> NSGraph lb -> NSGraph lbSource

Replace the formulae in the graph.

getFormulae :: NSGraph lb -> FormulaMap lbSource

Retrieve the formulae in the graph.

setFormula :: Label lb => Formula lb -> NSGraph lb -> NSGraph lbSource

Add (or replace) a formula.

getFormula :: Label lb => NSGraph lb -> lb -> Maybe (NSGraph lb)Source

Find a formula in the graph, if it exists.

Re-export from GraphClass

class (Eq (lg lb), Eq lb) => LDGraph lg lb whereSource

Labelled Directed Graph class

Minimum required implementation: setArcs, getArcs and containedIn (although containedIn may be removed as it is currently unused).

Methods

setArcs :: [Arc lb] -> lg lb -> lg lbSource

Replace the existing arcs in the graph.

getArcs :: lg lb -> [Arc lb]Source

Extract all the arcs from a graph

extract :: Selector lb -> lg lb -> lg lbSource

Extract those arcs that match the given Selector.

add :: lg lb -> lg lb -> lg lbSource

Add the two graphs

deleteSource

Arguments

:: lg lb

g1

-> lg lb

g2

-> lg lb

g2 - g1 -> g3

Remove those arcs in the first graph from the second graph

labels :: lg lb -> [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 :: lg lb -> [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.

containedIn :: lg lb -> lg lb -> BoolSource

Test for graph containment in another.

At present this is unused and may be removed in a future release.

update :: ([Arc lb] -> [Arc lb]) -> lg lb -> lg lbSource

Update the arcs in a graph using a supplied function.

Instances

Label lb => LDGraph GraphMem lb 
Label lb => LDGraph NSGraph lb 

class (Eq lb, Show lb, Ord lb) => Label lb whereSource

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.

Methods

labelIsVar :: lb -> BoolSource

Does this node have a variable binding?

labelHash :: Int -> lb -> IntSource

Calculate the hash of the label using the supplied seed.

getLocal :: lb -> StringSource

Extract the local id from a variable node.

makeLabel :: String -> lbSource

Make a label value from a local id.

data Arc lb Source

Arc type

Constructors

Arc 

Fields

asubj :: lb

The subject of the arc.

apred :: lb

The predicate (property) of the arc.

aobj :: lb

The object of the arc.

Instances

Functor Arc 
Foldable Arc 
Traversable Arc 
Eq lb => Eq (Arc lb) 
Ord lb => Ord (Arc lb) 
Show lb => Show (Arc lb) 
Hashable lb => Hashable (Arc lb) 

arcSource

Arguments

:: lb

The subject of the arc.

-> lb

The predicate of the arc.

-> lb

The object of the arc.

-> Arc lb 

Create an arc.

arcSubj :: Arc lb -> lbSource

Return the subject of the arc.

arcPred :: Arc lb -> lbSource

Return the predicate (property) of the arc.

arcObj :: Arc lb -> lbSource

Return the object of the arc.

type Selector lb = Arc lb -> BoolSource

Identify arcs.

Export selected RDFLabel values

Exported for testing

grEq :: Label lb => NSGraph lb -> NSGraph lb -> BoolSource

mapnode :: Label lb => [lb] -> [lb] -> (lb -> lb) -> lb -> lbSource

Remap a single graph node.

If the node is not one of those to be remapped, the supplied value is returned unchanged.

maplistSource

Arguments

:: 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.