swish-0.3.1.2: A semantic web toolkit.

PortabilityFlexibleInstances, TypeSynonymInstances, MultiParamTypeClasses
Stabilityexperimental
MaintainerDouglas Burke

Swish.RDF.GraphMatch

Contents

Description

This module contains graph-matching logic.

The algorithm used is derived from a paper on RDF graph matching by Jeremy Carroll [1].

1
http://www.hpl.hp.com/techreports/2001/HPL-2001-293.html

Synopsis

Documentation

graphMatchSource

Arguments

:: Label lb 
=> (lb -> lb -> Bool)

a function that tests for additional constraints that may prevent the matching of a supplied pair of nodes. Returns True if the supplied nodes may be matched. (Used in RDF graph matching for checking that formula assignments are compatible.)

-> [Arc lb]

the first graph to be compared, as a list of arcs

-> [Arc lb]

the second graph to be compared, as a list of arcs

-> (Bool, LabelMap (ScopedLabel lb))

If the first element is True then the second element maps each label to an equivalence class identifier, otherwise it is just emptyMap.

Graph matching function accepting two lists of arcs and returning a node map if successful

Exported for testing

data (Label lb, Eq lv, Show lv) => GenLabelMap lb lv Source

Type for label->index lookup table

Constructors

LabelMap Int (LookupMap (GenLabelEntry lb lv)) 

Instances

Label lb => Eq (LabelMap lb) 
Label lb => Show (LabelMap lb) 

data Label lb => GenLabelEntry lb lv Source

Constructors

LabelEntry lb lv 

Instances

(Label lb, Eq lb, Show lb, Eq lv, Show lv) => Eq (GenLabelEntry lb lv) 
(Label lb, Eq lb, Show lb, Eq lv, Show lv) => Show (GenLabelEntry lb lv) 
(Label lb, Eq lb, Show lb, Eq lv, Show lv) => LookupEntryClass (GenLabelEntry lb lv) lb lv 

data Label lb => ScopedLabel lb Source

This instance of class label adds a graph identifier to each variable label, so that variable labels from different graphs are always seen as distinct values.

The essential logic added by this class instance is embodied in the eq and hash functions. Note that variable label hashes depend only on the graph in which they appear, and non-variable label hashes depend only on the variable. Label hash values are used when initializing a label equivalence-class map (and, for non-variable labels, also for resolving hash collisions).

Constructors

ScopedLabel Int lb 

Instances

Label lb => Eq (ScopedLabel lb) 
Label lb => Ord (ScopedLabel lb) 
Label lb => Show (ScopedLabel lb) 
Label lb => Label (ScopedLabel lb) 

type LabelIndex = (Int, Int)Source

LabelIndex is a unique value assigned to each label, such that labels with different values are definitely different values in the graph; e.g. do not map to each other in the graph bijection. The first member is a generation counter that ensures new values are distinct from earlier passes.

type EquivalenceClass lb = (LabelIndex, [lb])Source

Type for equivalence class description (An equivalence class is a collection of labels with the same LabelIndex value.)

labelIsVar :: Label lb => lb -> BoolSource

Does this node have a variable binding?

labelHash :: Label lb => Int -> lb -> IntSource

Calculate the hash of the label using the supplied seed.

mapLabelIndex :: Label lb => LabelMap lb -> lb -> LabelIndexSource

Map a label to its corresponding label index value in the supplied LabelMap

setLabelHash :: Label lb => LabelMap lb -> (lb, Int) -> LabelMap lbSource

Replace a label and its associated value in a label map with a new value using the supplied hash value and the current LabelMap generation number. If the key is not found, then no change is made to the label map.

newLabelMap :: Label lb => LabelMap lb -> [(lb, Int)] -> LabelMap lbSource

Replace selected values in a label map with new values from the supplied list of labels and new label index values. The generation number is supplied from the current label map. The generation number in the resulting label map is incremented.

graphLabels :: Label lb => [Arc lb] -> [lb]Source

Return list of distinct labels used in a graph

assignLabelMap :: Label lb => [lb] -> LabelMap lb -> LabelMap lbSource

Scan label list, assigning initial label map values, adding new values to the label map supplied.

Label map values are assigned on the basis of the label alone, without regard for it's connectivity in the graph. (cf. reclassify).

All variable node labels are assigned the same initial value, as they may be matched with each other.

newGenerationMap :: Label lb => LabelMap lb -> LabelMap lbSource

Increment the generation of the label map.

Returns a new label map identical to the supplied value but with an incremented generation number.

graphMatch1Source

Arguments

:: Label lb 
=> Bool

True if a guess has been used before trying this comparison, False if nodes are being matched without any guesswork

-> (lb -> lb -> Bool)

Test for additional constraints that may prevent the matching of a supplied pair of nodes. Returns True if the supplied nodes may be matched.

-> [Arc lb]

(gs1 argument) first of two lists of arcs (triples) to be compared

-> [Arc lb]

(gs2 argument) secind of two lists of arcs (triples) to be compared

-> LabelMap lb

the map so far used to map label values to equivalence class values

-> [(EquivalenceClass lb, EquivalenceClass lb)]

(the ecpairs argument) list of pairs of corresponding equivalence classes of nodes from gs1 and gs2 that have not been confirmed in 1:1 correspondence with each other. Each pair of equivalence classes contains nodes that must be placed in 1:1 correspondence with each other.

-> (Bool, LabelMap lb)

the pair (match, map) where match is True if the supplied sets of arcs can be matched, in which case map is a corresponding map from labels to equivalence class identifiers. When match is False, map is the most detailed equivalence class map obtained before a mismatch was detected or a guess was required -- this is intended to help identify where the graph mismatch may be.

Recursive graph matching function

This function assumes that no variable label appears in both graphs. (Function graphMatch, which calls this, ensures that all variable labels are distinct.)

TODO:

  • replace Equivalence class pair by (index,[lb],[lb]) ?
  • possible optimization: the graphMapEq test should be needed only if graphMatch2 has been used to guess a mapping; either: a) supply flag saying guess has been used, or b) move test to graphMatch2 and use different test to prevent rechecking for each guess used.

graphMatch2 :: Label lb => (lb -> lb -> Bool) -> [Arc lb] -> [Arc lb] -> LabelMap lb -> [(EquivalenceClass lb, EquivalenceClass lb)] -> (Bool, LabelMap lb)Source

Auxiliary graph matching function

This function is called when deterministic decomposition of node mapping equivalence classes has run its course.

It picks a pair of equivalence classes in ecpairs, and arbitrarily matches pairs of nodes in those equivalence classes, recursively calling the graph matching function until a suitable node mapping is discovered (success), or until all such pairs have been tried (failure).

This function represents a point to which arbitrary choices are backtracked. The list comprehension glp represents the alternative choices at the point of backtracking

The selected pair of nodes are placed in a new equivalence class based on their original equivalence class value, but with a new NodeVal generation number.

equivalenceClassesSource

Arguments

:: Label lb 
=> LabelMap lb

label map

-> [lb]

list of nodes to be reclassified

-> [EquivalenceClass lb]

the equivalence classes of the supplied labels under the supplied label map

reclassifySource

Arguments

:: Label lb 
=> [Arc lb]

(the gs1 argument) the first of two lists of arcs (triples) to perform a basis for reclassifying the labels in the first equivalence class in each pair of ecpairs.

-> [Arc lb]

(the gs2 argument) the second of two lists of arcs (triples) to perform a basis for reclassifying the labels in the second equivalence class in each pair of the ecpairs argument

-> LabelMap lb

the label map used for classification of the labels in the supplied equivalence classes

-> [(EquivalenceClass lb, EquivalenceClass lb)]

(the ecpairs argument) a list of pairs of corresponding equivalence classes of nodes from gs1 and gs2 that have not been confirmed in 1:1 correspondence with each other.

-> (LabelMap lb, [(EquivalenceClass lb, EquivalenceClass lb)], Bool, Bool)

The output tuple consists of:

1) a revised label map reflecting the reclassification

2) a new list of equivalence class pairs based on the new node map

3) if the reclassification partitions any of the supplied equivalence classes then True, else False

4) if reclassification results in each equivalence class being split same-sized equivalence classes in the two graphs, then True, otherwise False.

Reclassify labels

Examines the supplied label equivalence classes (based on the supplied label map), and evaluates new equivalence subclasses based on node values and adjacency (for variable nodes) and rehashing (for non-variable nodes).

Note, assumes that all all equivalence classes supplied are non-singletons; i.e. contain more than one label.