amalgame/commit

added merge module

authorJacco van Ossenbruggen
Tue May 3 14:10:52 2011 +0200
committerJacco van Ossenbruggen
Tue May 3 14:10:52 2011 +0200
commit1c48fd2fed2ef83b99dbb98520349bccbd58ec7c
tree7c798ea538e2428373b704142860ab19c4d44dc1
parent4d23491f43ff8b193f2e9af53999ab1ad3ad4832
Diff style: patch stat
diff --git a/config-available/ag_modules.pl b/config-available/ag_modules.pl
index b0d990e..4e50973 100644
--- a/config-available/ag_modules.pl
+++ b/config-available/ag_modules.pl
@@ -6,3 +6,4 @@ user:file_search_path(ag_modules, library(ag_modules)).
 :- use_module(ag_modules(snowball_match)).
 :- use_module(ag_modules(select1_1)).  % I think we should deprecate this, is really select N-1
 :- use_module(ag_modules(arity_select)).
+:- use_module(ag_modules(map_merger)).
diff --git a/lib/ag_modules/map_merger.pl b/lib/ag_modules/map_merger.pl
new file mode 100644
index 0000000..1f7489a
--- /dev/null
+++ b/lib/ag_modules/map_merger.pl
@@ -0,0 +1,50 @@
+:- module(map_merger, []).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(amalgame/map)).
+
+:- public amalgame_module/1.
+:- public merger/3.
+
+amalgame_module(amalgame:'MapMerger').
+
+%%      merge_mappings(+ListOfGraphs, -Merged)
+%
+%       Merge alignment terms. ListOfGraphs is ordered.
+
+merger([], [], _) :- !.
+merger([L], L, _) :- !.
+merger([[]|Tail], Merged, Options) :- merger(Tail, Merged, Options).
+merger([L|Ls], [Merged|Ms], Options) :-
+        smallest_heads(Ls, [L], Heads, Rest),
+        merge_provenance(Heads, [Merged]),
+        merger(Rest, Ms, Options).
+
+
+smallest_heads([], Smallest, Heads, Tails) :-
+        heads_tails(Smallest, Heads, Tails).
+smallest_heads([[]|Ls1], Ls0, Smallest, Rest) :-
+        !,
+        smallest_heads(Ls1, Ls0, Smallest, Rest).
+smallest_heads([L1|Ls1], [L0|Ls0], Smallest, Rest) :-
+        L1 = [align(S1,T1,_)|_],
+        L0 = [align(S0,T0,_)|_],
+        (   S1 == S0,
+            T1 == T0
+        ->  smallest_heads(Ls1, [L0,L1|Ls0], Smallest, Rest)
+        ;   (   (S1 == S0, compare(<, T1, T0))
+            ;   compare(<, S1, S0)
+            )
+        ->  smallest_heads(Ls1, [L1], Smallest, Rest0),
+            append([L0|Ls0], Rest0, Rest)
+        ;   Rest = [L1|Rest0],
+            smallest_heads(Ls1, [L0|Ls0], Smallest, Rest0)
+        ).
+
+
+heads_tails([], [], []).
+heads_tails([[H]|Ls], [H|Hs], Ts) :-
+        !,
+        heads_tails(Ls, Hs, Ts).
+heads_tails([[H1|T1]|Ls], [H1|Hs], [T1|Ts]) :-
+        heads_tails(Ls, Hs, Ts).
diff --git a/lib/amalgame/expand_graph.pl b/lib/amalgame/expand_graph.pl
index 72d294f..feaeafd 100644
--- a/lib/amalgame/expand_graph.pl
+++ b/lib/amalgame/expand_graph.pl
@@ -9,6 +9,7 @@
 :- use_module(library(semweb/rdfs)).
 :- use_module(library(http/http_parameters)).
 :- use_module(library(amalgame/amalgame_modules)).
+:- use_module(library(amalgame/map)).
 
 :- dynamic
 	mapping_cache/2,
@@ -107,6 +108,15 @@ exec_mapping_process(Class, Process, Module, Result, Options) :-
  	rdf(Process, amalgame:input, InputId),
 	expand_mapping(InputId, MappingIn),
   	call(Module:selecter, MappingIn, Selected, Discarded, Undecided, Options).
+
+exec_mapping_process(Class, Process, Module, Result, Options) :-
+	rdfs_subclass_of(Class, amalgame:'Merger'),
+	!,
+	findall(Input, rdf(Process, amalgame:input, Input), Inputs),
+	maplist(expand_mapping, Inputs, Expanded),
+  	call(Module:merger, Expanded, Result, Options).
+
+
 exec_mapping_process(Class, Process, _, _, _) :-
 	throw(error(existence_error(mapping_process, [Class, Process]), _)).
 
@@ -169,21 +179,3 @@ module_options(Module, Options, Parameters) :-
 		),
 		Pairs),
 	pairs_keys_values(Pairs, Options, Parameters).
-
-
-%%	merge_provenance(+AlignIn, -AlignOut)
-%
-%	Collects all provenance for similar source target pairs.
-%	AlignIn is a sorted list of align/3 terms.
-
-merge_provenance([], []).
-merge_provenance([align(S, T, P)|As], Gs) :-
-	group_provenance(As, S, T, P, Gs).
-
-group_provenance([align(S,T,P)|As], S, T, P0, Gs) :-
-	!,
-	append(P, P0, P1),
-	group_provenance(As, S, T, P1, Gs).
-group_provenance(As, S, T, P, [align(S, T, Psorted)|Gs]) :-
-	sort(P, Psorted),
-	merge_provenance(As, Gs).
diff --git a/lib/amalgame/map.pl b/lib/amalgame/map.pl
index bd3ede1..9c92269 100644
--- a/lib/amalgame/map.pl
+++ b/lib/amalgame/map.pl
@@ -1,5 +1,6 @@
 :- module(ag_map,
 	  [
+	   merge_provenance/2,     % +List, -Merged
 	   compare_align/4,        % +Type, ?Order, A1, A2
 	   map_iterator/1,	   % -Map
 	   map_iterator/2,	   % -Map, +GraphList
@@ -223,5 +224,21 @@ compare_align(targetplus, Order, align(S1,T1,P1), align(S2,T2,P2)) :-
         ).
 
 
+%%      merge_provenance(+AlignIn, -AlignOut)
+%
+%       Collects all provenance for similar source target pairs.
+%       AlignIn is a sorted list of align/3 terms.
+
+merge_provenance([], []).
+merge_provenance([align(S, T, P)|As], Gs) :-
+        group_provenance(As, S, T, P, Gs).
+
+group_provenance([align(S,T,P)|As], S, T, P0, Gs) :-
+        !,
+        append(P, P0, P1),
+        group_provenance(As, S, T, P1, Gs).
+group_provenance(As, S, T, P, [align(S, T, Psorted)|Gs]) :-
+        sort(P, Psorted),
+        merge_provenance(As, Gs).
 
 
diff --git a/rdf/tool/amalgame.ttl b/rdf/tool/amalgame.ttl
index d513888..c7b122e 100644
--- a/rdf/tool/amalgame.ttl
+++ b/rdf/tool/amalgame.ttl
@@ -7,10 +7,10 @@
 @prefix skos:	  <http://www.w3.org/2004/02/skos/core#> .
 @prefix xsd:      <http://www.w3.org/2001/XMLSchema#> .
 
-amalgame:Process rdfs:subClassOf opmv:Process.
-amalgame:Matcher  rdfs:subClassOf amalgame:Process.
-amalgame:Merger  rdfs:subClassOf amalgame:Process.
-amalgame:Selecter rdfs:subClassOf amalgame:Process.
+amalgame:Process     rdfs:subClassOf opmv:Process.
+amalgame:Matcher     rdfs:subClassOf amalgame:Process.
+amalgame:Selecter    rdfs:subClassOf amalgame:Process.
+amalgame:Merger      rdfs:subClassOf amalgame:Process.
 amalgame:Voc_Exclude rdfs:subClassOf opmv:Process.
 
 amalgame:Snowball_Matcher    rdfs:subClassOf amalgame:Matcher .
@@ -24,6 +24,8 @@ amalgame:Isub_Matcher
 amalgame:Select1_1    rdfs:subClassOf amalgame:Selecter .
 amalgame:Arity_select rdfs:subClassOf amalgame:Selecter .
 
+amalgame:MapMerger   rdfs:subClassOf amalgame:Merger.
+
 amalgame:includes
         rdfs:domain skos:ConceptScheme ;
         rdfs:range amalgame:Alignment .