vumix/commit

start with asserting collections

authorMichiel Hildebrand
Tue May 8 18:24:45 2012 +0200
committerMichiel Hildebrand
Tue May 8 18:24:45 2012 +0200
commitf65eb7a6c664ade799534fa6b4227a5a6892fe67
tree7a4fd2d8da0521b8f1b7dde27c0ebb9b94ae42e4
parentdbc90dff787f4a020a8665626460e328c2580ec0
Diff style: patch stat
diff --git a/lib/beng_xml.pl b/lib/beng_xml.pl
index 8f930e9..1c98268 100644
--- a/lib/beng_xml.pl
+++ b/lib/beng_xml.pl
@@ -1,7 +1,8 @@
 :- module(beng_xml,
-	  [import_fragments/0,
-	   beng_selections/2,
-	   beng_date/2
+	  [overlap/1,
+	   beng_stats/0,
+	   import_fragments/0,
+	   pprime_frags_by_year/1
 	  ]).
 
 :- use_module(library(xpath)).
@@ -12,7 +13,7 @@
 :- dynamic
 	fragment/2.
 
-user:file_search_path(beng, '/Users/michiel/Desktop/werk_10629/10629').
+user:file_search_path(beng, '/Users/michiel/Projects/pprime/data/werk_10629/10629').
 user:file_search_path(mbh, '/Users/michiel/Projects/pprime/data/manbijthond').
 
 reeks('10629').
@@ -20,7 +21,26 @@ reeks('357006').
 reeks('357007').
 
 
-beng_stats(WaisdaTaggedFragments) :-
+assert_annotations([]).
+assert_annotations([FragmentId-Selection|T]) :-
+	load_xml_file(XMLFile,XMLTree),
+	xpath(XMLTree, //publicaties//begindatum, element(begindatum,_,[Date])).
+
+
+%%	overlap(-Pairs)
+%
+%	Pairs:fragment-selection maps the BandG annotated selections to
+%	Waisda tagged fragments.
+
+overlap(Pairs) :-
+	findall(R, reeks(R), Reeksen),
+	maplist(beng_selections, Reeksen, Expressies0),
+	append(Expressies0, Expressies),
+	link_beng_waisda(Expressies, WaisdaFragments0),
+	keysort(WaisdaFragments0, WaisdaFragments),
+	filter_waisda_tags(WaisdaFragments, Pairs).
+
+beng_stats :-
 	findall(R, reeks(R), Reeksen),
 	maplist(beng_selections, Reeksen, Expressies0),
 	append(Expressies0, Expressies),
@@ -38,38 +58,22 @@ beng_stats(WaisdaTaggedFragments) :-
 	format('waisda fragments, ~w~n', [WaisdaFragmentCount]),
 	format('waisda tagged fragments, ~w~n', [WaisdaTaggedFragmentCount]).
 
-beng_waisda(Pairs) :-
-	findall(R, reeks(R), Reeksen),
-	maplist(beng_selections, Reeksen, Selections),
-	%maplist(link_beng_waisda, Selections, Linked),
-	flatten(Selections, Pairs).
-	%flatten(Linked, Pairs).
-
 filter_waisda_tags([], []).
 filter_waisda_tags([F-S|T], [F-S|Rest]) :-
-	%number(F),
-	%atom_number(FA, F),
-	rdf(Video, dc:id, literal(F)),
-	findall(E,rdf(Video, pprime:hasAnnotation, E),Es),
-	length(Es,Count),
-	Count > 100,
+	number(F),
+	atom_number(FA, F),
+	rdf(Video, dc:id, literal(FA)),
+	rdf(Video, pprime:hasAnnotation, E),
+	rdf(E, pprime:score, literal(Score)),
+	atom_number(Score,ScoreN),
+	ScoreN > 5,
 	!,
 	filter_waisda_tags(T, Rest).
 filter_waisda_tags([_|T], Rest) :-
 	filter_waisda_tags(T, Rest).
-/*
-assert_beng_selections :-
-	(   reeks(Reeks),
-	    beng_selections(Reeks, Expressies),
-	    rdf_transaction(assert_expressies(Expressies)),
-	    fail
-	;   true
-	).
-
-assert_expressies([expressie(Dir,Date,Selections)|T]) :-
-*/
-
-%%	link_beng_waisda(+Expressies, -list([Fragment-Selection]))
+
+
+%%	link_beng_waisda(+Expressies, -List(fragment-selection))
 %
 %	 we assume that sorting on the ids of the fragments and the
 %	 filenames of Selections provides the right order. Thus, the
@@ -138,6 +142,9 @@ remove_non_xml([_|T], Rest) :-
 	remove_non_xml(T, Rest).
 
 
+%%	beng_date(+XMLFile, -Date)
+%
+%	Date is the broadcast date.
 
 beng_date(XMLFile, Date) :-
 	load_xml_file(XMLFile,XMLTree),
@@ -178,6 +185,10 @@ assert_fragments([Row|Rows]) :-
 	assert_fragments(Rows).
 
 
+%%	pprime_frags_by_year(-Pairs)
+%
+%
+
 pprime_frags_by_year(FragsByYear) :-
 	findall(Id, (rdf(V,rdf:type,pprime:'Video'),rdf(V,dc:id,literal(Id))), Vs),
 	maplist(fragment_year, Vs, Pairs),
@@ -186,7 +197,7 @@ pprime_frags_by_year(FragsByYear) :-
 	pairs_sort_by_value_count(Groups, FragsByYear).
 
 fragment_year(Id, Year-Id) :-
-	%atom_number(Id, N),
-	Id = N,
+	atom_number(Id, N),
+	%Id = N,
 	fragment(N, Date),
 	concat_atom([Year,_,_], '-', Date).