swish-0.10.0.4: A semantic web toolkit.

Copyright(c) 2003 Graham Klyne 2009 Vasili I Galchin
2011 2012 2013 2014 2015 2016 2018 Douglas Burke
LicenseGPL V2
MaintainerDouglas Burke
Stabilityexperimental
PortabilityCPP, FlexibleInstances, MultiParamTypeClasses, OverloadedStrings
Safe HaskellNone
LanguageHaskell2010

Swish.RDF.Graph

Contents

Description

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

Labels

data RDFLabel Source #

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.

Constructors

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

Instance details

Defined in Swish.RDF.Graph

Ord RDFLabel Source # 
Instance details

Defined in Swish.RDF.Graph

Show RDFLabel Source # 
Instance details

Defined in Swish.RDF.Graph

IsString RDFLabel Source # 
Instance details

Defined in Swish.RDF.Graph

ShowLines RDFGraph Source # 
Instance details

Defined in Swish.RDF.GraphShowLines

Label RDFLabel Source # 
Instance details

Defined in Swish.RDF.Graph

FromRDFLabel RDFLabel Source #

This is just Just.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel RDFLabel Source #

This is just id.

Instance details

Defined in Swish.RDF.Graph

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.

Methods

toRDFLabel :: a -> RDFLabel Source #

Instances
ToRDFLabel Bool Source #

Converts to a literal with a xsd:boolean datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Char Source #

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

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Double Source #

Converts to a literal with a xsd:double datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Float Source #

Converts to a literal with a xsd:float datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Int Source #

Converts to a literal with a xsd:integer datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Integer Source #

Converts to a literal with a xsd:integer datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel String Source #

Strings are converted to untyped literals.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel URI Source #

Converts to a Resource.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel UTCTime Source #

Converts to a literal with a xsd:datetime datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel Day Source #

Converts to a literal with a xsd:date datatype.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel QName Source #

Converts to a Resource.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel ScopedName Source #

Converts to a Resource.

Instance details

Defined in Swish.RDF.Graph

ToRDFLabel RDFLabel Source #

This is just id.

Instance details

Defined in Swish.RDF.Graph

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 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 similar to fromRDFLabel; the code should probably be combined at some point.

Instances
FromRDFLabel Bool Source #

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

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Char Source #

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

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Double Source #

Converts from a literal with a xsd:double datatype.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Float Source #

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.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Int Source #

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.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Integer Source #

Converts from a literal with a xsd:integer datatype.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel String Source #

Only untyped literals are converted to strings.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel URI Source #

Converts from a Resource.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel UTCTime Source #

Converts from a literal with a xsd:datetime datatype.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel Day Source #

Converts from a literal with a xsd:date datatype.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel QName Source #

Converts from a Resource.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel ScopedName Source #

Converts from a Resource.

Instance details

Defined in Swish.RDF.Graph

FromRDFLabel RDFLabel Source #

This is just Just.

Instance details

Defined in Swish.RDF.Graph

isLiteral :: RDFLabel -> Bool Source #

Test if supplied labal is a literal node (Lit, LangLit, or TypedLit).

isUntypedLiteral :: RDFLabel -> Bool Source #

Test if supplied labal is an untyped literal node (either Lit or LangLit).

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

isUri :: RDFLabel -> Bool Source #

Test if supplied labal is a URI resource node

isBlank :: RDFLabel -> Bool Source #

Test if supplied labal is a blank node

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

quote Source #

Arguments

:: Bool

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

-> 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 RDFArcSet = ArcSet RDFLabel Source #

A set of RDF triples.

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.

toRDFTriple Source #

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.

fromRDFTriple Source #

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

Instances
ShowLines RDFGraph Source # 
Instance details

Defined in Swish.RDF.GraphShowLines

LDGraph NSGraph lb Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

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 => Eq (NSGraph lb) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

(==) :: NSGraph lb -> NSGraph lb -> Bool #

(/=) :: NSGraph lb -> NSGraph lb -> Bool #

Label lb => Ord (NSGraph lb) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

compare :: NSGraph lb -> NSGraph lb -> Ordering #

(<) :: NSGraph lb -> NSGraph lb -> Bool #

(<=) :: NSGraph lb -> NSGraph lb -> Bool #

(>) :: NSGraph lb -> NSGraph lb -> Bool #

(>=) :: NSGraph lb -> NSGraph lb -> Bool #

max :: NSGraph lb -> NSGraph lb -> NSGraph lb #

min :: NSGraph lb -> NSGraph lb -> NSGraph lb #

Label lb => Show (NSGraph lb) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

showsPrec :: Int -> NSGraph lb -> ShowS #

show :: NSGraph lb -> String #

showList :: [NSGraph lb] -> ShowS #

Label lb => Show (Formula lb) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

showsPrec :: Int -> Formula lb -> ShowS #

show :: Formula lb -> String #

showList :: [Formula lb] -> ShowS #

Label lb => Semigroup (NSGraph lb) Source #

The <> operation uses merge rather than addGraphs.

Instance details

Defined in Swish.RDF.Graph

Methods

(<>) :: NSGraph lb -> NSGraph lb -> NSGraph lb #

sconcat :: NonEmpty (NSGraph lb) -> NSGraph lb #

stimes :: Integral b => b -> NSGraph lb -> NSGraph lb #

Label lb => Monoid (NSGraph lb) Source #

The mappend operation uses the Semigroup instance (so merge rather than addGraphs).

Instance details

Defined in Swish.RDF.Graph

Methods

mempty :: NSGraph lb #

mappend :: NSGraph lb -> NSGraph lb -> NSGraph lb #

mconcat :: [NSGraph lb] -> NSGraph lb #

type RDFGraph = NSGraph RDFLabel Source #

Memory-based RDF graph type

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

Constructors

Formula 

Fields

Instances
Label lb => Show (Formula lb) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

showsPrec :: Int -> Formula lb -> ShowS #

show :: Formula lb -> String #

showList :: [Formula lb] -> ShowS #

(Eq lb, Eq gr) => Eq (LookupFormula lb gr) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

(==) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool #

(/=) :: LookupFormula lb gr -> LookupFormula lb gr -> Bool #

(Ord lb, Ord gr) => Ord (LookupFormula lb gr) Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

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.

remapLabels Source #

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.

remapLabelList Source #

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

fmapNSGraph :: Ord lb => (lb -> lb) -> NSGraph lb -> NSGraph lb Source #

fmap for NSGraph instances.

traverseNSGraph :: (Applicative f, Ord a) => (a -> f a) -> NSGraph a -> f (NSGraph a) Source #

traverse for NSGraph instances.

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.

Minimal complete definition

emptyGraph, setArcs, getArcs

Methods

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

delete Source #

Arguments

:: 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
LDGraph GraphMem lb Source # 
Instance details

Defined in Swish.GraphMem

LDGraph NSGraph lb Source # 
Instance details

Defined in Swish.RDF.Graph

Methods

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 #

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.

Methods

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.

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

Constructors

Arc 

Fields

  • arcSubj :: lb

    The subject of the arc.

  • arcPred :: lb

    The predicate (property) of the arc.

  • arcObj :: lb

    The object of the arc.

Instances
Functor Arc Source # 
Instance details

Defined in Swish.GraphClass

Methods

fmap :: (a -> b) -> Arc a -> Arc b #

(<$) :: a -> Arc b -> Arc a #

Foldable Arc Source # 
Instance details

Defined in Swish.GraphClass

Methods

fold :: Monoid m => Arc m -> 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 #

toList :: Arc a -> [a] #

null :: Arc a -> Bool #

length :: Arc a -> Int #

elem :: Eq a => a -> Arc a -> Bool #

maximum :: Ord a => Arc a -> a #

minimum :: Ord a => Arc a -> a #

sum :: Num a => Arc a -> a #

product :: Num a => Arc a -> a #

Traversable Arc Source # 
Instance details

Defined in Swish.GraphClass

Methods

traverse :: Applicative f => (a -> f b) -> Arc a -> f (Arc b) #

sequenceA :: Applicative f => Arc (f a) -> f (Arc a) #

mapM :: Monad m => (a -> m b) -> Arc a -> m (Arc b) #

sequence :: Monad m => Arc (m a) -> m (Arc a) #

Eq lb => Eq (Arc lb) Source # 
Instance details

Defined in Swish.GraphClass

Methods

(==) :: Arc lb -> Arc lb -> Bool #

(/=) :: Arc lb -> Arc lb -> Bool #

Ord lb => Ord (Arc lb) Source # 
Instance details

Defined in Swish.GraphClass

Methods

compare :: Arc lb -> Arc lb -> Ordering #

(<) :: Arc lb -> Arc lb -> Bool #

(<=) :: Arc lb -> Arc lb -> Bool #

(>) :: Arc lb -> Arc lb -> Bool #

(>=) :: Arc lb -> Arc lb -> Bool #

max :: Arc lb -> Arc lb -> Arc lb #

min :: Arc lb -> Arc lb -> Arc lb #

Show lb => Show (Arc lb) Source # 
Instance details

Defined in Swish.GraphClass

Methods

showsPrec :: Int -> Arc lb -> ShowS #

show :: Arc lb -> String #

showList :: [Arc lb] -> ShowS #

Hashable lb => Hashable (Arc lb) Source # 
Instance details

Defined in Swish.GraphClass

Methods

hashWithSalt :: Int -> Arc lb -> Int #

hash :: Arc lb -> Int #

arc Source #

Arguments

:: lb

The subject of the arc.

-> lb

The predicate of the arc.

-> lb

The object of the arc.

-> Arc lb 

Create an arc.

type Selector lb = Arc lb -> Bool Source #

Identify arcs.

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.

resRdfParseType :: RDFLabel Source #

rdf:parseType.

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.

Properties

See the "Properties" section at http://www.w3.org/TR/rdf-schema/#ch_classes for more information.

Containers

See the "Container Classes and Properties" section at http://www.w3.org/TR/rdf-schema/#ch_containervocab.

Collections

See the "Collections" section at http://www.w3.org/TR/rdf-schema/#ch_collectionvocab.

Reification Vocabulary

See the "Reification Vocabulary" section at http://www.w3.org/TR/rdf-schema/#ch_reificationvocab.

Utility Properties

See the "Utility Properties" section at http://www.w3.org/TR/rdf-schema/#ch_utilvocab.

OWL

Miscellaneous

resRdfdGeneralRestriction :: RDFLabel Source #

rdfd:GeneralRestriction.

resRdfdOnProperties :: RDFLabel Source #

rdfd:onProperties.

resRdfdConstraint :: RDFLabel Source #

rdfd:constraint.

resRdfdMaxCardinality :: RDFLabel Source #

rdfd:maxCardinality.

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

grEq :: Label lb => NSGraph lb -> NSGraph lb -> Bool Source #

Graph equality.

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.

maplist Source #

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.