amalgame/commit

FIXED: broken structure partitioning logic - not backward compatible fix

authorJacco van Ossenbruggen
Fri Sep 5 19:17:57 2014 +0200
committerJacco van Ossenbruggen
Fri Sep 5 19:17:57 2014 +0200
commite9787e590056f70413e59e737d24e76a82106558
tree5cd0d4065678b586daf36e5674ac14f65bddd9b6
parentd06d1b788a885f72fd3fae3ff5f124802f6c75f3
Diff style: patch stat
diff --git a/lib/ag_modules/ancestor_selecter.pl b/lib/ag_modules/ancestor_selecter.pl
index 196d19f..3f1e688 100644
--- a/lib/ag_modules/ancestor_selecter.pl
+++ b/lib/ag_modules/ancestor_selecter.pl
@@ -1,15 +1,8 @@
 :- module(ancestor_selecter,
 	  []).
 
-:- use_module(library(apply)).
-:- use_module(library(assoc)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(pairs)).
-:- use_module(library(sort)).
-
-:- use_module(library(amalgame/map)).
 :- use_module(ancestor).
+:- use_module(structure_selecter).
 
 :- public amalgame_module/1.
 :- public selecter/5.
@@ -20,55 +13,10 @@ amalgame_module(amalgame:'AncestorSelecter').
 parameter(steps, integer, 1,
 	  'depth of search, defaults to 1, e.g. direct parents only').
 parameter(type,
-          oneof([source, target]), source,
-          'Discard other matches with the same source/target').
+          oneof([source, target, all]), all,
+          'Select all ancestor matches or pick the best source/target.').
 
 selecter(In, Sel, Dis, Und, Options) :-
-	option(snd_input(SecList), Options),
-	option(type(SourceOrTarget), Options, source),
-	findall(S-T-P, member(align(S,T,P), SecList), KeyValueList),
-	keysort(KeyValueList, Deduped),
-	ord_list_to_assoc(Deduped, BackgroundMatches),
-	(   SourceOrTarget = source
-	->  selecter_(SourceOrTarget, In, BackgroundMatches, Sel, Dis, Und, Options)
-	;   predsort(ag_map:compare_align(target), In, InT),
-	    selecter_(SourceOrTarget, InT, BackgroundMatches, Sel0, Dis0, Und0, Options),
-	    predsort(ag_map:compare_align(source), Sel0,  Sel),
-	    predsort(ag_map:compare_align(source), Dis0,  Dis),
-	    predsort(ag_map:compare_align(source), Und0,  Und)
-	).
-
-selecter_(_, [], _, [], [], [], _).
-selecter_(Type, [Head|Tail], BackgroundMatches, Sel, Dis, Und, Options) :-
-	Head = align(S,T,_),
-	(   Type == source
-	->  same_source(Tail, S, Same, Rest)
-	;   same_target(Tail, T, Same, Rest)
-	),
-	selecter_(Type, Rest, BackgroundMatches, TailSel, TailDis, TailUnd, Options),
-	Candidates = [Head|Same],
-	maplist(ancestor_count(BackgroundMatches, Options), Candidates, Counts0),
-	keysort(Counts0, Counts),
-	partition(zero_key, Counts, Zero, NonZero),
-	(   NonZero \= []
-	->  pairs_values(Zero,   DisgardedSame),
-	    pairs_values(NonZero, SelectedSame),
-	    append([SelectedSame,  TailSel], Sel),
-	    append([DisgardedSame, TailDis], Dis),
-	    Und = TailUnd
-	;   Sel = TailSel,
-	    Dis = TailDis,
-	    append([Candidates, TailUnd], Und)
-	).
+	selecter(ancestor_match, In, Sel, Dis, Und, Options).
 
-zero_key(0-_Value).
 
-ancestor_count(BackgroundMatches, Options, Corr, Count-Merged) :-
-	findall(Match,
-		ancestor_match(Corr, BackgroundMatches, Match, Options),
-		Matches),
-	length(Matches, Count),
-	(   Count > 0
-	->  merge_provenance(Matches, [Merged])
-	;   Merged = Corr
-	).
diff --git a/lib/ag_modules/descendent_selecter.pl b/lib/ag_modules/descendent_selecter.pl
index bd1ce21..dca5988 100644
--- a/lib/ag_modules/descendent_selecter.pl
+++ b/lib/ag_modules/descendent_selecter.pl
@@ -1,14 +1,7 @@
-:- module(descedent_selecter,
+:- module(descendent_selecter,
 	  []).
 
-:- use_module(library(apply)).
-:- use_module(library(assoc)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(pairs)).
-:- use_module(library(sort)).
-
-:- use_module(library(amalgame/map)).
+:- use_module(structure_selecter).
 :- use_module(descendent).
 
 :- public amalgame_module/1.
@@ -18,57 +11,11 @@
 amalgame_module(amalgame:'DescendentSelecter').
 
 parameter(steps, integer, 1,
-	  'depth of search, defaults to 1, e.g. direct parents only').
+	  'depth of search, defaults to 1, e.g. direct children only').
 parameter(type,
-          oneof([source, target]), source,
-          'Discard other matches with the same source/target').
+          oneof([source, target, all]), all,
+          'Select all descendent matches or pick the best source/target.').
 
 selecter(In, Sel, Dis, Und, Options) :-
-	option(snd_input(SecList), Options),
-	option(type(SourceOrTarget), Options, source),
-	findall(S-T-P, member(align(S,T,P), SecList), KeyValueList),
-	keysort(KeyValueList, Deduped),
-	ord_list_to_assoc(Deduped, BackgroundMatches),
-	(   SourceOrTarget = source
-	->  selecter_(SourceOrTarget, In, BackgroundMatches, Sel, Dis, Und, Options)
-	;   predsort(ag_map:compare_align(target), In, InT),
-	    selecter_(SourceOrTarget, InT, BackgroundMatches, Sel0, Dis0, Und0, Options),
-	    predsort(ag_map:compare_align(source), Sel0,  Sel),
-	    predsort(ag_map:compare_align(source), Dis0,  Dis),
-	    predsort(ag_map:compare_align(source), Und0,  Und)
-	).
-
-selecter_(_, [], _, [], [], [], _).
-selecter_(Type, [Head|Tail], BackgroundMatches, Sel, Dis, Und, Options) :-
-	Head = align(S,T,_),
-	(   Type == source
-	->  same_source(Tail, S, Same, Rest)
-	;   same_target(Tail, T, Same, Rest)
-	),
-	selecter_(Type, Rest, BackgroundMatches, TailSel, TailDis, TailUnd, Options),
-	Candidates = [Head|Same],
-	maplist(descedent_count(BackgroundMatches, Options), Candidates, Counts0),
-	keysort(Counts0, Counts),
-	partition(zero_key, Counts, Zero, NonZero),
-	(   NonZero \= []
-	->  pairs_values(Zero,   DisgardedSame),
-	    pairs_values(NonZero, SelectedSame),
-	    append([SelectedSame,  TailSel], Sel),
-	    append([DisgardedSame, TailDis], Dis),
-	    Und = TailUnd
-	;   Sel = TailSel,
-	    Dis = TailDis,
-	    append([Candidates, TailUnd], Und)
-	).
-
-zero_key(0-_Value).
+	selecter(descendent_match, In, Sel, Dis, Und, Options).
 
-descedent_count(BackgroundMatches, Options, Corr, Count-Merged) :-
-	findall(Match,
-		descendent_match(Corr, BackgroundMatches, Match, Options),
-		Matches),
-	length(Matches, Count),
-	(   Count > 0
-	->  merge_provenance(Matches, [Merged])
-	;   Merged = Corr
-	).
diff --git a/lib/ag_modules/related_selecter.pl b/lib/ag_modules/related_selecter.pl
index 884c962..6d32f9a 100644
--- a/lib/ag_modules/related_selecter.pl
+++ b/lib/ag_modules/related_selecter.pl
@@ -1,13 +1,7 @@
 :- module(related_selecter,
 	  []).
 
-:- use_module(library(apply)).
-:- use_module(library(assoc)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(pairs)).
-:- use_module(library(sort)).
-:- use_module(library(amalgame/map)).
+:- use_module(structure_selecter).
 :- use_module(related).
 
 :- public amalgame_module/1.
@@ -19,55 +13,8 @@ amalgame_module(amalgame:'RelatedSelecter').
 parameter(steps, integer, 1,
 	  'depth of search, defaults to 1, e.g. direct related concepts only').
 parameter(type,
-          oneof([source, target]), source,
-          'Discard other matches with the same source/target').
+          oneof([source, target, all]), all,
+          'Select all related concepts or pick the best source/target.').
 
 selecter(In, Sel, Dis, Und, Options) :-
-	option(snd_input(SecList), Options),
-	option(type(SourceOrTarget), Options, source),
-	findall(S-T-P, member(align(S,T,P), SecList), KeyValueList),
-	keysort(KeyValueList, Deduped),
-	ord_list_to_assoc(Deduped, BackgroundMatches),
-	(   SourceOrTarget = source
-	->  selecter_(SourceOrTarget, In, BackgroundMatches, Sel, Dis, Und, Options)
-	;   predsort(ag_map:compare_align(target), In, InT),
-	    selecter_(SourceOrTarget, InT, BackgroundMatches, Sel0, Dis0, Und0, Options),
-	    predsort(ag_map:compare_align(source), Sel0,  Sel),
-	    predsort(ag_map:compare_align(source), Dis0,  Dis),
-	    predsort(ag_map:compare_align(source), Und0,  Und)
-	).
-
-selecter_(_, [], _, [], [], [], _).
-selecter_(Type, [Head|Tail], BackgroundMatches, Sel, Dis, Und, Options) :-
-	Head = align(S,T,_),
-	(   Type == source
-	->  same_source(Tail, S, Same, Rest)
-	;   same_target(Tail, T, Same, Rest)
-	),
-	selecter_(Type, Rest, BackgroundMatches, TailSel, TailDis, TailUnd, Options),
-	Candidates = [Head|Same],
-	maplist(related_count(BackgroundMatches, Options), Candidates, Counts0),
-	keysort(Counts0, Counts),
-	partition(zero_key, Counts, Zero, NonZero),
-	(   NonZero \= []
-	->  pairs_values(Zero,   DisgardedSame),
-	    pairs_values(NonZero, SelectedSame),
-	    append([SelectedSame,  TailSel], Sel),
-	    append([DisgardedSame, TailDis], Dis),
-	    Und = TailUnd
-	;   Sel = TailSel,
-	    Dis = TailDis,
-	    append([Candidates, TailUnd], Und)
-	).
-
-zero_key(0-_Value).
-
-related_count(BackgroundMatches, Options, Corr, Count-Merged) :-
-	findall(Match,
-		related_match(Corr, BackgroundMatches, Match, Options),
-		Matches),
-	length(Matches, Count),
-	(   Count > 0
-	->  merge_provenance(Matches, [Merged])
-	;   Merged = Corr
-	).
+	selecter(related_match, In, Sel, Dis, Und, Options).
diff --git a/lib/ag_modules/structure_selecter.pl b/lib/ag_modules/structure_selecter.pl
new file mode 100644
index 0000000..959bb2e
--- /dev/null
+++ b/lib/ag_modules/structure_selecter.pl
@@ -0,0 +1,81 @@
+:- module(structure_selecter,
+	  [ selecter/6
+	  ]).
+
+/* This module provides a meta predicate selecter/6, which implements the selecter/5 predicate of the
+ *  skos ancestor, descendent and related partitioners.
+ */
+
+:- use_module(library(apply)).
+:- use_module(library(assoc)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(pairs)).
+:- use_module(library(sort)).
+
+:- use_module(library(amalgame/map)).
+
+:- meta_predicate selecter(4, +, -, -, -, +).
+
+selecter(Matcher, In, Sel, Dis, Und, Options) :-
+	option(snd_input(SecList), Options),
+	option(type(SourceOrTarget), Options, all),
+	findall(S-T-P, member(align(S,T,P), SecList), KeyValueList),
+	keysort(KeyValueList, Deduped),
+	ord_list_to_assoc(Deduped, BackgroundMatches),
+	(   SourceOrTarget \= source
+	->  selecter_(SourceOrTarget, Matcher, In, BackgroundMatches, Sel, Dis, Und, Options)
+	;   predsort(ag_map:compare_align(target), In, InT),
+	    selecter_(SourceOrTarget, Matcher, InT, BackgroundMatches, Sel0, Dis0, Und0, Options),
+	    predsort(ag_map:compare_align(source), Sel0,  Sel),
+	    predsort(ag_map:compare_align(source), Dis0,  Dis),
+	    predsort(ag_map:compare_align(source), Und0,  Und)
+	).
+
+selecter_(_, _, [], _, [], [], [], _).
+selecter_(all, Matcher, [Head|Tail], BackgroundMatches, Sel, Dis, [], Options) :-
+	structure_count(Matcher, BackgroundMatches, Options, Head, Count-Match),
+	(   Count > 0
+	->  Sel = [Match|TSel],
+	    Dis = TDis
+	;   Sel = TSel,
+	    Dis = [Head|TDis]
+	),
+	selecter_(all, Matcher, Tail, BackgroundMatches, TSel, TDis, [], Options).
+selecter_(Type, Matcher, [Head|Tail], BackgroundMatches, Sel, Dis, Und, Options) :-
+	Head = align(S,T,_),
+	(   Type == target
+	->  same_source(Tail, S, Same, Rest)
+	;   same_target(Tail, T, Same, Rest)
+	),
+	% Fix me: make this tail recursive
+	selecter_(Type, Matcher, Rest, BackgroundMatches, TailSel, TailDis, TailUnd, Options),
+
+	Candidates = [Head|Same],
+	(   pick_best(Candidates, Matcher, BackgroundMatches, SelectedSame, DisgardedSame, Options)
+	->  append([SelectedSame,  TailSel], Sel),
+	    append([DisgardedSame, TailDis], Dis),
+	    Und = TailUnd
+	;   Sel = TailSel,
+	    Dis = TailDis,
+	    append([Candidates, TailUnd], Und)
+	).
+
+pick_best(Candidates, Matcher, BackgroundMatches, [Selected], Disgarded, Options) :-
+	length(Candidates, N), N > 1, % do not pick a best if we have only one alternative
+	maplist(structure_count(Matcher, BackgroundMatches, Options), Candidates, Counts0),
+	keysort(Counts0, Sorted),
+	append([DiscardedPairs, [SecondBest-Value2], [Best-Selected]], Sorted),
+	Best > SecondBest,
+	Best > 0,
+	pairs_values([SecondBest-Value2|DiscardedPairs], Disgarded).
+
+structure_count(Matcher, BackgroundMatches, Options, Corr, Count-Merged) :-
+	findall(Match,
+		call(Matcher, Corr, BackgroundMatches, Match, Options),
+		Matches),
+	length(Matches, Count),
+	(   Count > 0
+	->  merge_provenance(Matches, [Merged])
+	;   Merged = Corr
+	).