amalgame/commit

remove now redundant filter mode

authorJacco van Ossenbruggen
Sat Sep 6 15:23:41 2014 +0200
committerJacco van Ossenbruggen
Sat Sep 6 15:23:41 2014 +0200
commitce2c5cbfa2f3d9111f9eb872ea6fdc174f4ece4d
treee26bf3b6378b2447e72d09c493d629ed0f428970
parentbb4ea6e7402798151f6a3f49e787bc618612e51d
Diff style: patch stat
diff --git a/lib/ag_modules/ancestor_match.pl b/lib/ag_modules/ancestor_match.pl
index 3377727..09fcc49 100644
--- a/lib/ag_modules/ancestor_match.pl
+++ b/lib/ag_modules/ancestor_match.pl
@@ -1,4 +1,4 @@
-:- module(ancestor_match,
+:- module(ancestor_generator,
 	  []).
 
 :- use_module(library(assoc)).
@@ -8,27 +8,14 @@
 :- use_module(ancestor).
 
 :- public amalgame_module/1.
-:- public filter/3.
 :- public matcher/4.
 :- public parameter/4.
 
 amalgame_module(amalgame:'AncestorMatcher').
-amalgame_module(amalgame:'AncestorFilter').
 
 parameter(steps, integer, 1,
 	  'depth of search, defaults to 1, e.g. direct parents only').
 
-%%	filter(+MappingsIn, -MappingsOut, +Options)
-%
-%	Filter mappings based on ancestor matches in snd_input.
-
-filter(In, Out, Options) :-
-	option(snd_input(SecList), Options),
-	findall(S-T-P, member(align(S,T,P), SecList), KeyValueList),
-	keysort(KeyValueList, Deduped),
-	ord_list_to_assoc(Deduped, BackgroundMatches),
-	filter_(In, BackgroundMatches, Out, Options).
-
 %%	matcher(+Source, +Target, -Mappings, +Options)
 %
 %	Mappings is a list of matches between instances of Source and
@@ -42,20 +29,6 @@ matcher(Source, Target, Mappings, Options) :-
 	findall(M, align(Source, Target, BackgroundMatches, M, Options), Mappings0),
 	sort(Mappings0, Mappings).
 
-filter_([], _, [], _).
-filter_([align(S,T,P)|Cs], BackgroundMatches, [C|Mappings], Options) :-
-	(   T = scheme(_)
-	->  ancestor_match(align(S,_,P), BackgroundMatches, C, Options),
-	    C=align(_,T2,_),
-	    vocab_member(T2, T)
-	;   ancestor_match(align(S,T,P), BackgroundMatches, C, Options)
-	),
-	!,
-	filter_(Cs, BackgroundMatches, Mappings, Options).
-filter_([_|Cs], BackgroundMatches, Mappings, Options) :-
-	filter_(Cs, BackgroundMatches, Mappings, Options).
-
-
 align(Source, Target, BackgroundMatches, Match, Options) :-
 	vocab_member(S, Source),
 	vocab_member(T, Target),
diff --git a/lib/ag_modules/exact_label_generator.pl b/lib/ag_modules/exact_label_generator.pl
index caa4bb3..8ab58b9 100644
--- a/lib/ag_modules/exact_label_generator.pl
+++ b/lib/ag_modules/exact_label_generator.pl
@@ -6,12 +6,10 @@
 :- use_module(string_match_util).
 
 :- public amalgame_module/1.
-:- public filter/3.
 :- public matcher/4.
 :- public parameter/4.
 
 amalgame_module(amalgame:'ExactLabelMatcher').
-amalgame_module(amalgame:'ExactLabelFilter').
 
 parameter(sourcelabel, oneof(LabelProps), Default,
 	  '(Super)Property to get label of the source by') :-
@@ -33,22 +31,6 @@ parameter(case_sensitive, boolean, false,
 parameter(match_qualified_only, boolean, false,
 	  'Match only on the fully qualified label').
 
-%%	filter(+MappingsIn, -MappingsOut, +Options)
-%
-%	Filter mappings based on exact matching of labels.
-
-filter([], [], _).
-filter([align(S,T,P)|Cs], [C|Mappings], Options) :-
-	(   T = scheme(TargetScheme)
-	->  exact_label_match(align(S,_,P), C, [target_scheme(TargetScheme)|Options])
-	;   exact_label_match(align(S,T,P), C, Options)
-	),
-	!,
-	filter(Cs, Mappings, Options).
-filter([_|Cs], Mappings, Options) :-
-	filter(Cs, Mappings, Options).
-
-
 %%	matcher(+Source, +Target, -Mappings, +Options)
 %
 %	Mappings is a sorted list of matches between instances of Source