amalgame/commit

ADDED: best source/target selecter mode for label-type selecters

authorJacco van Ossenbruggen
Mon Sep 8 14:22:59 2014 +0200
committerJacco van Ossenbruggen
Mon Sep 8 14:22:59 2014 +0200
commit07e760bdbb3de93e5360c9a98ce5b02faee7dcec
treed92ec4d825a3551d99c30edf08ec1ba96e80f49a
parent0fb9cd37ca2d46e1fcd6a8d98fcd68fd863195b4
Diff style: patch stat
diff --git a/lib/ag_modules/label_selecter.pl b/lib/ag_modules/label_selecter.pl
index 422a35c..252188e 100644
--- a/lib/ag_modules/label_selecter.pl
+++ b/lib/ag_modules/label_selecter.pl
@@ -6,6 +6,13 @@
  * label matching partitioners.
  */
 
+:- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(pairs)).
+:- use_module(library(sort)).
+:- use_module(library(amalgame/map)).
+
 :- meta_predicate label_selecter(3, +, -, -, -, +).
 
 label_selecter(Matcher, In, Sel, Dis, Und, Options) :-
@@ -21,6 +28,7 @@ label_selecter(Matcher, In, Sel, Dis, Und, Options) :-
 
 label_selecter(  _, _, [],  [],  [],  [], _).
 label_selecter(all, Matcher, [Head|Tail], Sel, Dis, [], Options) :-
+	!,
 	(   call(Matcher, Head, Match, Options)
 	->  Sel = [Match|TSel],
 	    Dis = TDis
@@ -31,3 +39,41 @@ label_selecter(all, Matcher, [Head|Tail], Sel, Dis, [], Options) :-
 	    Dis = [MisMatch|TDis]
 	),
 	label_selecter(all, Matcher, Tail, TSel, TDis, [], Options).
+
+label_selecter(Type, Matcher, [Head|Tail], 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
+	label_selecter(Type, Matcher, Rest, TailSel, TailDis, TailUnd, Options),
+
+	Candidates = [Head|Same],
+	(   pick_best(Candidates, Matcher, 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, [Selected], Disgarded, Options) :-
+	length(Candidates, N), N > 1, % do not pick a best if we have only one alternative
+	maplist(label_count(Matcher, Options), Candidates, Counts0),
+	keysort(Counts0, Sorted),
+	append([DiscardedPairs, [SecondBest-Value2], [Best-Selected]], Sorted),
+	Best > SecondBest,
+	Best > 0,
+	pairs_values([SecondBest-Value2|DiscardedPairs], Disgarded).
+
+label_count(Matcher, Options, Corr, Count-Merged) :-
+	findall(Match,
+		call(Matcher, Corr, Match, Options),
+		Matches),
+	length(Matches, Count),
+	(   Count > 0
+	->  merge_provenance(Matches, [Merged])
+	;   Merged = Corr
+	).