Copyright | (c) 2003 Graham Klyne 2009 Vasili I Galchin 2011 2012 2016 2018 2020 2022 2024 Douglas Burke |
---|---|
License | GPL V2 |
Maintainer | Douglas Burke |
Stability | experimental |
Portability | FlexibleInstances, MultiParamTypeClasses |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module contains graph-matching logic.
The algorithm used is derived from a paper on RDF graph matching by Jeremy Carroll http://www.hpl.hp.com/techreports/2001/HPL-2001-293.html.
Synopsis
- graphMatch :: Label lb => (lb -> lb -> Bool) -> ArcSet lb -> ArcSet lb -> (Bool, LabelMap (ScopedLabel lb))
- type LabelMap lb = GenLabelMap lb LabelIndex
- data (Label lb, Eq lv, Show lv) => GenLabelMap lb lv = LabelMap Word32 (Map lb lv)
- type LabelEntry lb = GenLabelEntry lb LabelIndex
- data Label lb => GenLabelEntry lb lv = LabelEntry lb lv
- data Label lb => ScopedLabel lb = ScopedLabel Int lb
- makeScopedLabel :: Label lb => Int -> lb -> ScopedLabel lb
- makeScopedArc :: Label lb => Int -> Arc lb -> Arc (ScopedLabel lb)
- type LabelIndex = (Word32, Word32)
- type EquivalenceClass lb = (LabelIndex, [lb])
- nullLabelVal :: LabelIndex
- emptyMap :: Label lb => LabelMap lb
- labelIsVar :: Label lb => lb -> Bool
- labelHash :: Label lb => Int -> lb -> Int
- mapLabelIndex :: Label lb => LabelMap lb -> lb -> LabelIndex
- setLabelHash :: Label lb => LabelMap lb -> (lb, Word32) -> LabelMap lb
- newLabelMap :: Label lb => LabelMap lb -> [(lb, Word32)] -> LabelMap lb
- graphLabels :: Label lb => ArcSet lb -> Set lb
- assignLabelMap :: Label lb => Set lb -> LabelMap lb -> LabelMap lb
- newGenerationMap :: Label lb => LabelMap lb -> LabelMap lb
- graphMatch1 :: Label lb => Bool -> (lb -> lb -> Bool) -> ArcSet lb -> ArcSet lb -> LabelMap lb -> [(EquivalenceClass lb, EquivalenceClass lb)] -> (Bool, LabelMap lb)
- graphMatch2 :: Label lb => (lb -> lb -> Bool) -> ArcSet lb -> ArcSet lb -> LabelMap lb -> [(EquivalenceClass lb, EquivalenceClass lb)] -> (Bool, LabelMap lb)
- equivalenceClasses :: Label lb => LabelMap lb -> Set lb -> [EquivalenceClass lb]
- reclassify :: Label lb => ArcSet lb -> ArcSet lb -> LabelMap lb -> [(EquivalenceClass lb, EquivalenceClass lb)] -> (LabelMap lb, [(EquivalenceClass lb, EquivalenceClass lb)], Bool, Bool)
Documentation
:: Label lb | |
=> (lb -> lb -> Bool) | a function that tests for additional constraints
that may prevent the matching of a supplied pair
of nodes. Returns |
-> ArcSet lb | the first graph to be compared |
-> ArcSet lb | the second graph to be compared |
-> (Bool, LabelMap (ScopedLabel lb)) | If the first element is |
Graph matching function accepting two lists of arcs and returning a node map if successful
Exported for testing
type LabelMap lb = GenLabelMap lb LabelIndex Source #
A label lookup table specialized to LabelIndex
indices.
data (Label lb, Eq lv, Show lv) => GenLabelMap lb lv Source #
Type for label->index lookup table
type LabelEntry lb = GenLabelEntry lb LabelIndex Source #
A label associated with a LabelIndex
data Label lb => GenLabelEntry lb lv Source #
A Mapping between a label and a value (e.g. an index value).
LabelEntry lb lv |
Instances
(Label lb, Show lv) => Show (GenLabelEntry lb lv) Source # | |
Defined in Swish.GraphMatch showsPrec :: Int -> GenLabelEntry lb lv -> ShowS # show :: GenLabelEntry lb lv -> String # showList :: [GenLabelEntry lb lv] -> ShowS # | |
(Label lb, Eq lv) => Eq (GenLabelEntry lb lv) Source # | |
Defined in Swish.GraphMatch (==) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # (/=) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # | |
(Label lb, Ord lv) => Ord (GenLabelEntry lb lv) Source # | |
Defined in Swish.GraphMatch compare :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Ordering # (<) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # (<=) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # (>) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # (>=) :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> Bool # max :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> GenLabelEntry lb lv # min :: GenLabelEntry lb lv -> GenLabelEntry lb lv -> GenLabelEntry 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).
ScopedLabel Int lb |
Instances
makeScopedLabel :: Label lb => Int -> lb -> ScopedLabel lb Source #
Create a scoped label given an identifier and label.
makeScopedArc :: Label lb => Int -> Arc lb -> Arc (ScopedLabel lb) Source #
Create an arc containining a scoped label with the given identifier.
type LabelIndex = (Word32, Word32) 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.)
nullLabelVal :: LabelIndex Source #
The null, or empty, index value.
labelIsVar :: Label lb => lb -> Bool Source #
Does this node have a variable binding?
labelHash :: Label lb => Int -> lb -> Int Source #
Calculate the hash of the label using the supplied seed.
mapLabelIndex :: Label lb => LabelMap lb -> lb -> LabelIndex Source #
Map a label to its corresponding label index value in the supplied LabelMap.
setLabelHash :: Label lb => LabelMap lb -> (lb, Word32) -> LabelMap lb Source #
Replace a label and its associated value in a label map
with a new value using the supplied hash value and the current
GenLabelMap
generation number. If the key is not found, then no change
is made to the label map.
newLabelMap :: Label lb => LabelMap lb -> [(lb, Word32)] -> LabelMap lb Source #
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 => ArcSet lb -> Set lb Source #
Return the set of distinct labels used in the graph.
assignLabelMap :: Label lb => Set lb -> LabelMap lb -> LabelMap lb Source #
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 lb Source #
Increment the generation of the label map.
Returns a new label map identical to the supplied value but with an incremented generation number.
:: Label lb | |
=> Bool |
|
-> (lb -> lb -> Bool) | Test for additional constraints that may prevent the matching
of a supplied pair of nodes. Returns |
-> ArcSet lb | ( |
-> ArcSet lb | ( |
-> LabelMap lb | the map so far used to map label values to equivalence class values |
-> [(EquivalenceClass lb, EquivalenceClass lb)] | (the |
-> (Bool, LabelMap lb) | the pair |
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.)
graphMatch2 :: Label lb => (lb -> lb -> Bool) -> ArcSet lb -> ArcSet 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.
:: Label lb | |
=> LabelMap lb | label map |
-> Set lb | nodes to be reclassified |
-> [EquivalenceClass lb] |
Return the equivalence classes of the supplied nodes using the label map.
:: Label lb | |
=> ArcSet lb | (the |
-> ArcSet lb | (the |
-> LabelMap lb | the label map used for classification of the labels in the supplied equivalence classes |
-> [(EquivalenceClass lb, EquivalenceClass lb)] | (the |
-> (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 4) if reclassification results in each equivalence class
being split same-sized equivalence classes in the two graphs,
then |
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.