amalgame/commit

REFACTORING: more reuse of similar code

authorJacco van Ossenbruggen
Sat Sep 6 16:03:31 2014 +0200
committerJacco van Ossenbruggen
Sat Sep 6 16:03:31 2014 +0200
commit0a84a4b338d7b384cb7b4998bd8129960f958858
tree5acf783d034ff72755ff3510cd9dde326bf5b32f
parentc175c7bc8a3d60e88ae2ac4e4730188cdf4646f6
Diff style: patch stat
diff --git a/lib/ag_modules/ancestor_generator.pl b/lib/ag_modules/ancestor_generator.pl
index 4a663b2..46ced69 100644
--- a/lib/ag_modules/ancestor_generator.pl
+++ b/lib/ag_modules/ancestor_generator.pl
@@ -1,11 +1,8 @@
 :- module(ancestor_generator,
 	  []).
 
-:- use_module(library(assoc)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(amalgame/vocabulary)).
 :- use_module(ancestor_match).
+:- use_module(generator_snd_input).
 
 :- public amalgame_module/1.
 :- public matcher/4.
@@ -22,14 +19,5 @@ parameter(steps, integer, 1,
 %	Target.
 
 matcher(Source, Target, Mappings, 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),
-	findall(M, align(Source, Target, BackgroundMatches, M, Options), Mappings0),
-	sort(Mappings0, Mappings).
+	generator_snd_input(ancestor_match, Source, Target, Mappings, Options).
 
-align(Source, Target, BackgroundMatches, Match, Options) :-
-	vocab_member(S, Source),
-	vocab_member(T, Target),
-	ancestor_match(align(S,T,[]), BackgroundMatches, Match, Options).
diff --git a/lib/ag_modules/descendent_generator.pl b/lib/ag_modules/descendent_generator.pl
index 50cf3ea..7c828ae 100644
--- a/lib/ag_modules/descendent_generator.pl
+++ b/lib/ag_modules/descendent_generator.pl
@@ -1,10 +1,7 @@
 :- module(descendent_generator, []).
 
-:- use_module(library(assoc)).
-:- use_module(library(lists)).
-:- use_module(library(option)).
-:- use_module(library(amalgame/vocabulary)).
 :- use_module(descendent_match).
+:- use_module(generator_snd_input).
 
 :- public amalgame_module/1.
 :- public matcher/4.
@@ -21,14 +18,4 @@ parameter(steps, integer, 1,
 %	Target.
 
 matcher(Source, Target, Mappings, 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),
-	findall(M, align(Source, Target, BackgroundMatches, M, Options), Mappings0),
-	sort(Mappings0, Mappings).
-
-align(Source, Target, BackgroundMatches, Match, Options) :-
-	vocab_member(S, Source),
-	vocab_member(T, Target),
-	descendent_match(align(S,T,[]), BackgroundMatches, Match, Options).
+	generator_snd_input(descendent_match, Source, Target, Mappings, Options).
diff --git a/lib/ag_modules/generator_snd_input.pl b/lib/ag_modules/generator_snd_input.pl
new file mode 100644
index 0000000..675fd26
--- /dev/null
+++ b/lib/ag_modules/generator_snd_input.pl
@@ -0,0 +1,27 @@
+:- module(generator_snd_input,
+	  [
+	      generator_snd_input/5
+	  ]).
+
+:- use_module(library(assoc)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
+:- use_module(library(amalgame/vocabulary)).
+
+:- meta_predicate
+	generator_snd_input(4, +, +, -, +).
+
+generator_snd_input(Matcher, Source, Target, Mappings, 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),
+	findall(M, align(Matcher, Source, Target,
+			 BackgroundMatches, M, Options),
+		Mappings0),
+	sort(Mappings0, Mappings).
+
+align(Matcher, Source, Target, BackgroundMatches, Match, Options) :-
+	vocab_member(S, Source),
+	vocab_member(T, Target),
+	call(Matcher, align(S,T,[]), BackgroundMatches, Match, Options).
diff --git a/lib/ag_modules/related.pl b/lib/ag_modules/related.pl
deleted file mode 100644
index 0be5a89..0000000
--- a/lib/ag_modules/related.pl
+++ /dev/null
@@ -1,21 +0,0 @@
-:- module(related_match_util,
-	  [ related_match/4]).
-
-:- use_module(library(semweb/rdf_db)).
-:- use_module(library(skos/util)).
-
-related_match(align(S, T, Prov0), BackgroundMatches, align(S, T, [Prov|Prov0]), Options) :-
-	option(steps(MaxSteps), Options),
-	related(S, MaxSteps, AncS, R1, Steps1),
-	related(T, MaxSteps, AncT, R2, Steps2),
-	get_assoc(AncS-AncT, BackgroundMatches, _),
-	Prov = [method(related_match),
-		source(AncS),
-		target(AncT),
-		steps(Steps1/Steps2),
-		graph([R1,R2])
-	       ].
-
-related(R, MaxSteps, Related, rdf(R, Prop, Related), Steps) :-
-	skos_related_to(R, Related, MaxSteps, Steps),
-	rdf_equal(amalgame:relatedTransitive, Prop).
diff --git a/lib/ag_modules/related_generator.pl b/lib/ag_modules/related_generator.pl
new file mode 100644
index 0000000..7778eca
--- /dev/null
+++ b/lib/ag_modules/related_generator.pl
@@ -0,0 +1,23 @@
+:- module(related_generator,
+	  []).
+
+:- use_module(related_match).
+:- use_module(generator_snd_input).
+
+:- public amalgame_module/1.
+:- public matcher/4.
+:- public parameter/4.
+
+amalgame_module(amalgame:'RelatedMatcher').
+
+parameter(steps, integer, 1,
+	  'depth of search, defaults to 1, e.g. directly related only').
+
+%%	matcher(+Source, +Target, -Mappings, +Options)
+%
+%	Mappings is a list of matches between instances of Source and
+%	Target.
+
+matcher(Source, Target, Mappings, Options) :-
+	generator_snd_input(related_match, Source, Target, Mappings, Options).
+
diff --git a/lib/ag_modules/related_match.pl b/lib/ag_modules/related_match.pl
index 259fd84..7907d9d 100644
--- a/lib/ag_modules/related_match.pl
+++ b/lib/ag_modules/related_match.pl
@@ -1,61 +1,23 @@
 :- module(related_match,
-	  []).
+	  [ related_match/4]).
 
 :- use_module(library(assoc)).
 :- use_module(library(option)).
-:- use_module(library(amalgame/vocabulary)).
-:- use_module(related).
-
-:- public amalgame_module/1.
-:- public filter/3.
-:- public matcher/4.
-:- public parameter/4.
-
-amalgame_module(amalgame:'RelatedMatcher').
-amalgame_module(amalgame:'RelatedFilter').
-
-parameter(steps, integer, 1,
-	  'depth of search, defaults to 1, e.g. direct related concepts only').
-
-%%	filter(+MappingsIn, -MappingsOut, +Options)
-%
-%	Filter mappings based on exact matching of labels.
-
-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
-%	Target.
-
-matcher(Source, Target, Mappings, 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),
-	findall(M, align(Source, Target, BackgroundMatches, M, Options), Mappings0),
-	sort(Mappings0, Mappings).
-
-filter_([], _, [], _).
-filter_([align(S,T,P)|Cs], BackgroundMatches, [C|Mappings], Options) :-
-	(   S = 'http://zbw.eu/stw/descriptor/18781-5' -> gtrace; true),
-	(   T = scheme(_)
-	->  related_match(align(S,_,P), BackgroundMatches, C, Options),
-	    C=align(_,T2,_),
-	    vocab_member(T2, T)
-	;   related_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),
-	related_match(align(S,T,[]), BackgroundMatches, Match, Options).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(skos/util)).
+
+related_match(align(S, T, Prov0), BackgroundMatches, align(S, T, [Prov|Prov0]), Options) :-
+	option(steps(MaxSteps), Options),
+	related(S, MaxSteps, AncS, R1, Steps1),
+	related(T, MaxSteps, AncT, R2, Steps2),
+	get_assoc(AncS-AncT, BackgroundMatches, _),
+	Prov = [method(related_match),
+		source(AncS),
+		target(AncT),
+		steps(Steps1/Steps2),
+		graph([R1,R2])
+	       ].
+
+related(R, MaxSteps, Related, rdf(R, Prop, Related), Steps) :-
+	skos_related_to(R, Related, MaxSteps, Steps),
+	rdf_equal(amalgame:relatedTransitive, Prop).
diff --git a/lib/ag_modules/related_selecter.pl b/lib/ag_modules/related_selecter.pl
index 6d32f9a..2f87a6c 100644
--- a/lib/ag_modules/related_selecter.pl
+++ b/lib/ag_modules/related_selecter.pl
@@ -1,8 +1,8 @@
 :- module(related_selecter,
 	  []).
 
+:- use_module(related_match).
 :- use_module(structure_selecter).
-:- use_module(related).
 
 :- public amalgame_module/1.
 :- public selecter/5.
@@ -11,10 +11,12 @@
 amalgame_module(amalgame:'RelatedSelecter').
 
 parameter(steps, integer, 1,
-	  'depth of search, defaults to 1, e.g. direct related concepts only').
+	  'depth of search, defaults to 1, e.g. directly related concepts only').
 parameter(type,
           oneof([source, target, all]), all,
-          'Select all related concepts or pick the best source/target.').
+          'Select all related matches or pick the best source/target.').
 
 selecter(In, Sel, Dis, Und, Options) :-
 	selecter(related_match, In, Sel, Dis, Und, Options).
+
+