swish-0.3.0.0: A semantic web toolkit.

PortabilityFlexibleInstances, MultiParamTypeClasses, TypeSynonymInstances
Stabilityexperimental
MaintainerDouglas Burke

Swish.RDF.RDFGraph

Description

This module defines a memory-based RDF graph instance.

Synopsis

Documentation

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 String (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)

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

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

type RDFTriple = Arc RDFLabelSource

RDF Triple (statement)

data NSGraph lb Source

Memory-based graph with namespaces and subgraphs

Constructors

NSGraph 

type RDFGraph = NSGraph RDFLabelSource

Memory-based RDF graph type

type NamespaceMap = LookupMap NamespaceSource

Namespace prefix list entry

data LookupFormula lb gr Source

Graph formula entry

Constructors

Formula 

Fields

formLabel :: lb
 
formGraph :: gr
 

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) 

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

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.

allLabels :: Label lb => (lb -> Bool) -> NSGraph lb -> [lb]Source

Return list of all labels (including properties) in the graph satisfying a supplied filter predicate.

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.

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

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

toRDFGraph :: [Arc RDFLabel] -> RDFGraphSource

Create a new RDF graph from a supplied list of arcs

emptyRDFGraph :: RDFGraphSource

Create a new, empty RDF graph.

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

Methods

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

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

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

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

delete :: lg lb -> lg lb -> lg lbSource

labels :: lg lb -> [lb]Source

nodes :: lg lb -> [lb]Source

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

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

Instances

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

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

data Arc lb Source

Constructors

Arc 

Fields

asubj :: lb
 
apred :: lb
 
aobj :: lb
 

Instances

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

arc :: lb -> lb -> lb -> Arc lbSource

arcSubj :: Arc lb -> lbSource

arcPred :: Arc lb -> lbSource

arcObj :: Arc lb -> lbSource

type Selector lb = Arc lb -> BoolSource

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.

maplist :: Label lb => [lb] -> [lb] -> (lb -> lb) -> [(lb, lb)] -> [(lb, lb)]Source

Construct a list of (oldnode,newnode) values to be used for graph label remapping. The function operates recursiovely, adding new nodes generated to the mapping list (mapbn') and also to the list of nodes to be avoided (allbn').