waisda/commit

moved from yaz package

authorMichiel Hildebrand
Mon Mar 7 20:26:23 2011 +0100
committerMichiel Hildebrand
Mon Mar 7 20:26:23 2011 +0100
commitaebf667c633d8627c09d7cf2fbe3137483946ff9
tree89f9ea3c504371099a1d05d250ffe96a3d4356a0
parentcb04b35dc930a7cf28746dc6dfbe1d2ea429a405
Diff style: patch stat
diff --git a/lib/download_videos.pl b/lib/download_videos.pl
new file mode 100644
index 0000000..223fc2c
--- /dev/null
+++ b/lib/download_videos.pl
@@ -0,0 +1,154 @@
+:- module(download_video_stream,
+	  [ download_waisda_videos/0,
+	    download_waisda_video/1,
+	    download_video_stream/2
+	  ]).
+
+:- use_module(library(http/http_open)).
+:- use_module(library(xpath)).
+:- use_module(library(thread_pool)).
+
+annotated_video(V) :-
+	rdf(S,pprime:source,V0),
+	is_absolute_url(V0),
+	%sub_atom(V0, _, 3, 0, wmv), % only wmv files
+	%www_form_encode(V, V0),
+	sub_atom(V0, _, 3, 0, asf), % only asf files
+	V = V0,
+	once(rdf(S, pprime:hasAnnotation, _)).
+
+:- thread_pool_create(stream_download_pool, 5, []).
+
+%%	download_waisda_videos
+%
+%	Download video streams for all videos.
+
+download_waisda_videos :-
+	findall(V, annotated_video(V), Vs0),
+	sort(Vs0, Vs),
+	length(Vs, N),
+	download_waisda_videos(Vs, N).
+
+download_waisda_videos([Video|Vs], N) :-
+	N0 is N - 1,
+	debug(stream_download, '~w: ~w', [N, Video]),
+	download_waisda_video(Video),
+	download_waisda_videos(Vs, N0).
+
+
+%%	download_waisda_video(+Video)
+%
+%	Download a video stream
+
+download_waisda_video(URL) :-
+	www_form_encode(URL, File0),
+	absolute_file_name(video(File0), File),
+	(   exists_file(File),
+	    size_file(File, Size),
+	    Size > 500
+	->  debug(stream_download, 'file already exists', [])
+	;   catch(video_stream_location(URL, Stream), _, fail)
+	->  debug(stream_download, 'found stream ~w', [Stream]),
+	    thread_create_in_pool(stream_download_pool,
+				  download_video_stream(Stream, File),
+				  _,
+				  [])
+ 	;   thread_create_in_pool(stream_download_pool,
+				  download_video_stream(URL, File),
+				  _,
+				  [])
+ 	).
+
+%%  video_stream_location(+HTTPLocation, -StreamLocation)
+%
+%   Get location of video stream by parsing the response from the HTTP location.
+
+video_stream_location(HTTPURL, StreamLocation) :-
+	load_html(HTTPURL, Dom),
+	xpath(Dom, //ref(@href), StreamLocation).
+
+
+%%	download_video_stream(+StreamLocation, +SrcFile)
+%
+%	Download video at StreamLocation to SrcFile
+
+download_video_stream(Stream, File0) :-
+	Prog = path(mplayer),
+	win_relative_path(File, File0),
+	debug(stream_download, 'Downloading video stream ...', []),
+	process_create(Prog,
+		       [ '-dumpstream', Stream,
+			 '-dumpfile', file(File)
+		       ],
+		       [ stderr(pipe(Error)),
+			 stdout(null),
+			 process(PID)
+		       ]),
+	read_stream_to_codes(Error, Messages),
+	close(Error),
+	process_wait(PID, Status),
+	(   Status == exit(0)
+	->  debug(stream_download, 'stream: ok', [])
+	;   debug(stream_download, 'stream: status ~w: ~s', [Status, Messages]),
+	    %atom_codes(Text, Messages),
+	    catch(delete_file(File), _, true)
+	    %throw(error(download_video_stream(Status, Text), _))
+	).
+
+
+
+%%  load_html(+URL, -Dom)
+%
+%   Load HTML document.
+
+load_html(URL, DOM) :-
+	setup_call_cleanup(http_open(URL, In, []),
+			   (   dtd(html, DTD),
+			       load_structure(stream(In),
+					      DOM,
+					      [ dtd(DTD),
+						dialect(sgml),
+						shorttag(false),
+						syntax_errors(quiet)
+					      ])
+			   ),
+			   close(In)).
+
+
+
+%%	win_relative_path(+Path, -RelativePath) is det.
+%
+%	If Path is an absolute filename, translate it into a relative
+%	one to avoid too long commandlines on Windows.
+
+win_relative_path(Path, Local) :-
+	current_prolog_flag(windows, true),
+	is_absolute_file_name(Path), !,
+	relative_path(Path, Local).
+win_relative_path(Path, Path).
+
+%%	relative_path(+Path, -Relative)
+%
+%	Transform an absolute path  into  a   relative  one  to overcome
+%	limitations of the Windows commandline handling.
+
+relative_path(Path, RelPath) :-
+	working_directory(PWD, PWD),
+	relative_path(Path, PWD, RelPath), !.
+relative_path(Path, Path).
+
+relative_path(Path, RelTo, RelPath) :-
+	concat_atom(PL, /, Path),
+	concat_atom(RL, /, RelTo),
+	delete_common_prefix(PL, RL, PL1, PL2),
+	to_dot_dot(PL2, DotDot, PL1),
+	concat_atom(DotDot, /, RelPath).
+
+delete_common_prefix([H|T01], [H|T02], T1, T2) :- !,
+	delete_common_prefix(T01, T02, T1, T2).
+delete_common_prefix(T1, T2, T1, T2).
+
+to_dot_dot([], Tail, Tail).
+to_dot_dot([_], Tail, Tail) :- !.
+to_dot_dot([_|T0], ['..'|T], Tail) :-
+	to_dot_dot(T0, T, Tail).
diff --git a/lib/exp_stats.pl b/lib/exp_stats.pl
new file mode 100644
index 0000000..61c1749
--- /dev/null
+++ b/lib/exp_stats.pl
@@ -0,0 +1,497 @@
+:- module(exp_stats,
+	  [tag_stats/4,
+	   find_concepts/0,
+	   find_concepts/1,
+	   video_tags_to_concepts/3,
+	   tag_entries/0,
+	   confirm/0
+	  ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(count)).
+:- use_module(api(reconcile)).
+:- use_module(library(video_annotation)).
+:- use_module(library(yaz_util)).
+:- use_module(library(semweb/rdf_litindex)).
+:- use_module(library(semweb/rdf_label)).
+
+user:file_search_path(exp_data, exp_data).
+
+:- dynamic
+	exact_match_cache/1,
+	match_cache/2,
+	tag_concept_link/3.
+
+:- rdf_find_literals(zzz, _).
+
+
+		 /*******************************
+		 *	      tag stats		*
+		 *******************************/
+
+tag_stats(Total, Unique, Matched, MatchedUnique) :-
+	findall(E, rdf(E, rdf:type, pprime:'TagEntry'), Es),
+	length(Es, Total),
+	findall(T, rdf(T, rdf:type, pprime:'Tag'), Ts),
+	length(Ts, Unique),
+	findall(M-Tag, (rdf(M, rdf:type, pprime:'TagEntry'),
+			rdf(M, rdf:value, Tag),
+			rdf(M, pprime:score, literal(S)),
+			S > 0
+		       ), Ms),
+	length(Ms, Matched),
+	pairs_values(Ms, Tags0),
+	sort(Tags0, Tags),
+	length(Tags, MatchedUnique).
+
+
+
+
+		 /*******************************
+		 *	 tag to concepts	*
+		 *******************************/
+
+find_concepts :-
+	find_concepts(_).
+find_concepts(N) :-
+	waisda_tags(Tags),
+ 	length(Tags, Count),
+	(   var(N)
+	->  Limit = Count
+	;   Limit is min(Count, N)
+	),
+	open('tag_concept_links.pl', write, Stream, [encoding(utf8)]),
+	find_tag_concepts(Tags, Limit, Stream),
+	close(Stream).
+
+find_tag_concepts([], _, _) :- !.
+find_tag_concepts(_, 0, _) :- !.
+find_tag_concepts([Tag|Ts], N, Stream) :-
+	N0 is N-1,
+	reconcile(Tag, 100, Hits),
+	maplist(tag_hit_type, Hits, Types0),
+	sort(Types0, Types),
+	Term = tag_concept_link(Tag, Types, Hits),
+	assert(Term),
+	debug(tag_concept, '~w ~w ~w', [N, Tag, Types]),
+	format(Stream, '~q .~n', [Term]),
+	find_tag_concepts(Ts, N0, Stream).
+
+tag_hit_type(hit(_,R,_,_), Type) :-
+	c_type(R, Type).
+
+c_type(R, person(gtaa_person)) :-
+	rdf(R, skos:inScheme, gtaa:'Persoonsnamen'),
+	!.
+c_type(R, person(gtaa_naam)) :-
+	rdf(R, skos:inScheme, gtaa:'Namen'),
+	!.
+c_type(R, person(dbpedia)) :-
+	rdf(R, rdf:type, foaf:'Person'),
+	!.
+c_type(R, place(gtaa)) :-
+	rdf(R, skos:inScheme, gtaa:'GeografischeNamen'),
+	!.
+c_type(R, place(geonames)) :-
+	rdf(R, skos:inScheme, gtaa:'Geonames'),
+	!.
+c_type(R, emotion(cornetto_state)) :-
+	rdf_reachable(R, skos:broader, 'http://purl.org/vocabularies/cornetto/synset-gesteldheid-1-noun'),
+	!.
+c_type(R, subject(gtaa)) :-
+	rdf(R, skos:inScheme, gtaa:'Onderwerpen'),
+	!.
+c_type(R, subject(cornetto_noun)) :-
+	rdf(R, rdf:type, cornetto:'NounSynset'),
+	!.
+c_type(R, subject(cornetto_verb)) :-
+	rdf(R, rdf:type, cornetto:'VerbSynset'),
+	!.
+c_type(R, other(Class)) :-
+	(   rdf(R, rdf:type, Class)
+	->  true
+	;   Class = unknown
+	).
+
+
+waisda_tags(Tags) :-
+	findall(Tag, (rdf(T,rdf:type,pprime:'Tag'),
+		      rdf(T,rdfs:label,Tag0),
+		      tag_value(Tag0, Tag),
+		      atom(Tag)
+		   ),
+		Tags).
+
+tag_concepts :-
+	rdf_equal(skos:'Concept', Type),
+	tag_concepts(Type, [], Pairs),
+	tag_concept_stats(Pairs).
+tag_cornetto_nouns :-
+	rdf_equal(cornetto:'NounSynset', Type),
+	tag_concepts(Type, [], Pairs),
+	tag_concept_stats(Pairs).
+tag_gtaa_subjects :-
+	rdf_equal(skos:inScheme, P),
+	rdf_equal(gtaa:'Onderwerpen', Scheme),
+	tag_concepts([], [P-Scheme], Pairs),
+	tag_concept_stats(Pairs).
+tag_gtaa_namen :-
+	rdf_equal(skos:inScheme, P),
+	rdf_equal(gtaa:'Namen', Scheme),
+	tag_concepts([], [P-Scheme], Pairs),
+	tag_concept_stats(Pairs).
+tag_gtaa_person :-
+	rdf_equal(skos:inScheme, P),
+	rdf_equal(gtaa:'Persoonsnamen', Scheme),
+	tag_concepts([], [P-Scheme], Pairs),
+	tag_concept_stats(Pairs).
+tag_dbpedia_person :-
+	tag_concepts('http://xmlns.com/foaf/0.1/Person', [], Pairs),
+	tag_concept_stats(Pairs).
+tag_gtaa_places :-
+	rdf_equal(skos:inScheme, P),
+	rdf_equal(gtaa:'GeografischeNamen', Scheme),
+ 	tag_concepts([], [P-Scheme], Pairs),
+ 	tag_concept_stats(Pairs).
+
+tag_concepts(Type, Props, Pairs) :-
+	waisda_tags(Tags),
+	length(Tags, N),
+ 	tag_concepts_(Tags, N, Type, Props, Pairs).
+
+tag_concepts_([], _, _, _, []).
+tag_concepts_([Tag|Ts], N, Type, Props, [Tag-Concepts|Ps]) :-
+	N0 is N-1,
+ 	reconcile(Tag, -1, Type, Props, Hits),
+	maplist(hit_concept, Hits, Concepts),
+	length(Concepts, NC),
+	(   NC > 0
+	->  debug(tag_concept, '~w ~p ~w', [N, Tag, NC])
+	;   true
+	),
+	tag_concepts_(Ts, N0, Type, Props, Ps).
+
+video_tags_to_concepts(Video, Concepts, Options) :-
+	video_annotations(Video, As0, Options),
+	sort_by_arg(As0, 2, As),
+ 	rdf_equal(skos:'Concept', SKOSConcept),
+	link_tags_to_concepts(As, SKOSConcept, Concepts).
+
+
+
+tag_concept_stats(Pairs) :-
+	findall(Count-Tag,
+		(member(Tag-Cs, Pairs),
+		 length(Cs,Count)
+		),Ps),
+	keysort(Ps,Ps1),
+	group_pairs_by_key(Ps1, CountPairs),
+	format_count_pairs(CountPairs).
+
+format_count_pairs([]).
+format_count_pairs([Count-Tags|Cs]) :-
+	length(Tags, N),
+	format('~w, ~w~n', [Count, N]),
+	format_count_pairs(Cs).
+
+
+%%	link_tags_to_concepts(+Annotations, -Annotations1)
+%
+%	Add candidate concepts.
+
+link_tags_to_concepts([], _, []).
+link_tags_to_concepts([A0|As], Type, [A|Rest]) :-
+	A0 = annotation(Tag,Start,End,Entries,Score),
+	A = annotation(Tag,Start,End,Entries,Score,Concepts),
+	tag_value(Tag, Value),
+ 	(   reconcile(Value, 3, Type, [], Hits)
+	->  maplist(hit_concept, Hits, Concepts)
+	;   Concepts = []
+	),
+ 	link_tags_to_concepts(As, Type, Rest).
+
+hit_concept(hit(_,URI,_,Label), concept(URI,Label,Alt,Desc)) :-
+	(   rdf_has(URI, rdfs:label, Lit),
+	    literal_text(Lit, Alt),
+	    \+ Alt == Label
+	->  true
+	;   Alt = ''
+	),
+	(   rdf_has(URI,skos:scopeNote,Txt)
+	->  literal_text(Txt,Desc)
+	;   rdf_has(URI, skos:definition,Txt)
+	->  literal_text(Txt,Desc)
+	;   Desc = ''
+	).
+
+
+
+		 /*******************************
+		 *	       Waisda		*
+		 *******************************/
+
+games(N) :-
+	findall(G,rdf(G, rdf:type, pprime:'Game'),Gs),
+	length(Gs, N).
+
+game_stats :-
+	format('n, game, players, tags, unique, scored, unique, extra, unique~n'),
+	multi_user_games(Games),
+	length(Games, Total),
+	game_stats(Games, Total).
+
+multi_user_games(Games) :-
+	findall(Game-Us,
+		(   rdf(Game, rdf:type, pprime:'Game'),
+		    findall(U, rdf(Game,opmv:wasPerformedBy,U), Us),
+		    Us = [_,_|_]
+		),
+		Games).
+
+game_stats([], _).
+game_stats([Game-Users|Gs], N) :-
+	N0 is N-1,
+	game_matches(Game,As),
+	game_file_name(Game, File0),
+	absolute_file_name(exp_data(File0), File),
+	tell(File),
+	format('game_a(['),
+	write_annotations(As),
+	format(']).'),
+	told,
+	game_annotation_stats(Game, Users, As, N),
+	absolute_file_name(exp_data('stats.csv'), StatsFile),
+	append(StatsFile),
+	game_annotation_stats(Game, Users, As, N),
+	told,
+	game_stats(Gs, N0).
+
+game_file_name(G,File) :-
+	rdf_global_id(_:File, G),
+	!.
+game_file_name(G,G).
+
+game_annotation_stats(Game, Users, As, N) :-
+	findall(V, member(annotation(V,_,_,_,_,_), As), Vs0),
+	findall(V, (member(annotation(V,_,_,_,S,_), As),S>0), Ss0),
+	findall(V, (member(annotation(V,_,_,_,S,M),As),S==0,M=[_|_]), Ms0),
+	sort(Vs0, Vs),
+	sort(Ss0, Ss),
+	sort(Ms0, Ms),
+	length(Vs0, NTags),
+	length(Ss0, NScored),
+	length(Ms0, NMatch),
+	length(Vs, NUTags),
+	length(Ss, NUScored),
+	length(Ms, NUMatch),
+	length(Users, NUsers),
+	format('~w, ~p, ~w, ~w, ~w, ~w, ~w, ~w, ~w~n',
+	       [N, Game, NUsers, NTags, NUTags, NScored, NUScored, NMatch, NUMatch]).
+
+
+game_matches(Game, As) :-
+	Interval = 10000,
+	rdf(Game, opmv:used, Video),
+ 	video_annotations(Video, As0, [process(Game)]),
+	sort_by_arg(As0, 2, As1),
+ 	tag_matches(As1, Game, Interval, As),
+	retractall(exact_match_cache(_)).
+
+
+write_annotations([]).
+write_annotations([A]) :- !,
+	write_term(A, [quoted]).
+write_annotations([A|As]) :-
+	write_term(A, [quoted]),
+	format(', '),
+	write_annotations(As).
+
+
+
+
+
+%%	tag_entries
+%
+%	Format the tag number of tag entries per user.
+
+tag_entries :-
+	findall(C-V,(rdf(S,rdf:value,V),rdf(S,pprime:creator,C)), Ss),
+	keysort(Ss,Ss1),
+	group_pairs_by_key(Ss1,Gs),
+	forall(member(U-Tags,Gs), (length(Tags,N), format('~w ~w~n',[U,N]))).
+
+%%	confirm
+%
+%	Format the number of confirmations per user.
+
+confirm :-
+	confirmations(Cs),
+	forall(member(U-C,Cs),
+	       (length(C,N),
+		format('~w ~w ',[U,N]),
+		format_action(accept, C),
+ 		format_action(reject, C),
+		format('~n')
+	       )).
+
+%%	confirm_by_type(+Action)
+%
+%	Format the number of confirmations for each type of match.
+
+confirm_by_type :-
+	confirmations(Cs),
+	forall(member(U-C,Cs),
+	       ( length(C,N),
+		 format('~w ~w ~n', [U, N]),
+		 format_action(accept, C),
+		 format_matches([stem,synonym,sibling,related,specific,generic], accept, C),
+ 		 format_action(reject, C),
+		 format_matches([stem,synonym,sibling,related,specific,generic], reject, C)
+ 	       )).
+
+confirm_by_type(A) :-
+	confirmations(Cs),
+	Matches = [stem,synonym,sibling,related,specific,generic],
+	format_header(Matches),
+	forall(member(_U-C,Cs), format_matches(Matches, A, C)).
+
+
+format_action(A, Cs) :-
+	proof_count(member(confirm(A,_,_,_,_),Cs),_,N),
+	format('~w: ~w ', [A,N]).
+
+format_matches([], _, _) :-
+	format('~n').
+format_matches([M|Ms], A, Cs) :-
+	proof_count(member(confirm(A,M,_,_,_),Cs),_,N),
+	format('~w, ', [N]),
+	format_matches(Ms, A, Cs).
+
+format_header([]) :-
+	format('~n').
+format_header([H|Hs]) :-
+	format('~w, ', H),
+	format_header(Hs).
+
+
+confirmations(Cs) :-
+    findall(C-confirm(A,M,Id,SL,TL),
+	    ( rdf(Id, pprime:action, literal(A)),
+	      rdf(Id, pprime:match, literal(M)),
+	      rdf(Id,pprime:creator,C),
+	      rdf(Id,pprime:matchSource,S),
+	      rdf(Id,pprime:matchTarget,T),
+	      rdf(S,rdf:value,literal(SL)),
+	      rdf(T,rdf:value,literal(TL))),
+	    Cs0),
+    keysort(Cs0,Cs1),
+    group_pairs_by_key(Cs1,Cs).
+
+
+
+
+
+
+
+
+
+		 /*******************************
+		 *		matching	*
+		 *******************************/
+
+tag_matches([], _, _, []).
+tag_matches([A0|As], Process, Interval, [A|Rest]) :-
+	rdf_equal(skos:'Concept', Concept),
+	A0 = annotation(Value,Start,End,Entries,Score0),
+	A =  annotation(Value,Start,End,Entries,Score,Matches),
+	Time is Start + Interval,
+	Entries = [i(Id,_)],
+	rdf(Id,pprime:creator,User),
+	check_score_within_game(Id, As, Value, User, Time, Score0, Score),
+	tag_value(Value, Tag),
+	snowball(dutch, Tag, Stem0),
+	downcase_atom(Stem0, Stem),
+	reconcile(Tag, 10, Concept, [], Hits),
+	findall(M, backward_match(Id, M), BMatches),
+	forward_matches(As, Id, Tag, Stem, Hits, User, Time, FMatches),
+	append(BMatches, FMatches, Matches),
+  	tag_matches(As, Process, Interval, Rest).
+
+
+check_score_within_game(_,_, _, _, _, 0, 0) :-
+	!.
+check_score_within_game(Id, _, _, _, _, Score, Score) :-
+	exact_match_cache(Id),
+	!.
+check_score_within_game(_Id, As, Value, User, End, Score, Score) :-
+	match_in_game(As, Value, User, End, Score, Score),
+	!.
+check_score_within_game(_, _, _, _, _, _, 0).
+
+match_in_game([A|As], Value, User, End, Score, Score) :-
+	A =  annotation(Value1,Time1,_,[i(Id1,_)],_),
+	Time1 =< End,
+	(   Value1 = Value,
+	    \+ rdf(Id1, pprime:creator, User)
+	->  assert(exact_match_cache(Id1))
+	;   match_in_game(As, Value, User, End, Score, Score)
+	).
+
+
+
+backward_match(Id, M) :-
+	match_cache(Id, M),
+	retractall(match_cache(Id,M)).
+
+forward_matches([A|As], Id, Tag, Stem, Hits, User, End, Matches) :-
+	A =  annotation(Value1,Time1,_,[i(Id1,_)],_),
+	Time1 =< End,
+	!,
+	(   \+ rdf(Id1, pprime:creator, User),
+	    tag_value(Value1, Tag1),
+	    \+ Tag == Tag1,
+	    match(Stem, Hits, Tag1, Type)
+	->  match_reverse(Type, RType),
+	    assert(match_cache(Id1, match(RType, 0, Id, literal(Tag)))),
+	    Matches = [match(Type, 0, Id1, literal(Tag1))|Ms]
+	;   Matches = Ms
+	),
+	forward_matches(As, Id, Tag, Stem, Hits, User, End, Ms).
+forward_matches(_, _, _, _, _, _, _, []).
+
+
+match(Stem, _, Tag1, stem) :-
+	snowball(dutch, Tag1, Stem1),
+	downcase_atom(Stem1, Stem).
+match(_Stem, Hits, Tag1, Type) :-
+	Hits = [_|_],
+	reconcile(Tag1, 5, Hits1),
+	member(hit(_,C,_,_), Hits),
+	member(hit(_,C1,_,_), Hits1),
+	tag_concept_match(C, C1, Type).
+
+tag_concept_match(R, R, synonym) :- !.
+tag_concept_match(R1, R2, specific) :-
+ 	rdf_reachable(R1, skos:broader, R2),
+	!.
+tag_concept_match(R1, R2, generic) :-
+ 	rdf_reachable(R2, skos:broader, R1),
+	!.
+tag_concept_match(R1, R2, sibling) :-
+ 	rdf_reachable(R1, skos:broader, R, 2, _),
+	rdf_reachable(R2, skos:broader, R, 2, _),
+	!.
+tag_concept_match(R1, R2, related) :-
+ 	(   rdf(R2, skos:related, R1)
+	;   rdf(R1, skos:related, R2)
+	),
+	!.
+
+tag_value(literal(Tag), Tag).
+tag_value(uri(_URI,Tag), Tag).
+
+
+match_reverse(specific, generic).
+match_reverse(generic, specific).
+match_reverse(M, M).
diff --git a/lib/import_waisda.pl b/lib/import_waisda.pl
new file mode 100644
index 0000000..7ef3656
--- /dev/null
+++ b/lib/import_waisda.pl
@@ -0,0 +1,257 @@
+:- module(import_waisda,
+	  [ waisda_to_rdf/0,
+	    save_waisda_rdf/1
+	  ]).
+
+
+:- use_module(library(csv)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(user_process)).
+:- use_module(library(video_annotation)).
+:- use_module(library(count)).
+
+:- rdf_register_ns(pprime, 'http://semanticweb.cs.vu.nl/prestoprime/').
+:- rdf_register_ns(opmv, 'http://purl.org/net/opmv/ns#').
+
+:- dynamic
+	table_map/3.
+
+user:file_search_path(waisda_data, '../data/waisda').
+filename(game, 'game.csv').
+filename(video, 'video.csv').
+filename(tag, 'tag.csv').
+filename(tagentry, 'tagentry.csv').
+
+waisda_to_rdf :-
+	debug(waisda_import),
+ 	retractall(table_map(_,_,_)),
+	games_to_rdf,
+	tags_to_rdf,
+	entries_to_rdf,
+	%rdf_retractall(_,_,_,tag),
+	videos_to_rdf,
+	add_game_users.
+
+save_waisda_rdf(File) :-
+	rdf_save(File,[db(waisda)]).
+
+games_to_rdf :-
+	waisda_file(game, File),
+	debug(waisda_import, 'reading games', []),
+ 	csv_read_file(File, [Header|Content], [functor(game)]),
+	length(Content, Length),
+	debug(waisda_import, '~w', [Length]),
+ 	create_table_map(Header, game),
+	rdf_transaction(assert_games(Content)).
+
+assert_games([]).
+assert_games([T|Ts]) :-
+	table_map_value(game, id, T, Id),
+	table_map_value(game, video_id, T, VideoId),
+	table_map_value(game, starttime, T, StartTime),
+ 	pprime_url(Id, game, URL),
+	pprime_url(VideoId, video, VideoURL),
+	rdf_assert(URL, rdf:type, pprime:'Game', waisda),
+	rdf_assert(URL, opmv:used, VideoURL, waisda),
+	rdf_assert(URL, opmv:wasStartedAt, literal(StartTime), waisda),
+	assert_games(Ts).
+
+videos_to_rdf :-
+	waisda_file(video, File),
+	debug(waisda_import, 'reading videos', []),
+	csv_read_file(File, [Header|Content], [functor(video)]),
+	length(Content, Length),
+	debug(waisda_import, '~w', [Length]),
+ 	create_table_map(Header, video),
+ 	rdf_transaction(assert_videos(Content)).
+
+assert_videos([]).
+assert_videos([T|Ts]) :-
+	table_map_value(video, id, T, Id),
+	table_map_value(video, title, T, Title),
+	table_map_value(video, uri_broadband, T, Source),
+	table_map_value(video, category, T, Cat),
+	table_map_value(video, duration, T, Duration0),
+	table_map_value(video, source, T, Provider),
+	table_map_value(video, description, T, Desc),
+
+	pprime_url(Id, video, URL),
+	pprime_url(Cat, category, CatURL),
+	parse_time(Duration0, Duration),
+
+	rdf_assert(URL, rdf:type, pprime:'Video', waisda),
+	rdf_assert(URL, dc:title, literal(lang(nl, Title)), waisda),
+	rdf_assert(URL, pprime:source, Source, waisda),
+	rdf_assert(URL, pprime:duration, literal(Duration), waisda),
+	rdf_assert(URL, pprime:provider, literal(Provider), waisda),
+	rdf_assert(URL, pprime:description, literal(lang(nl, Desc)), waisda),
+	rdf_assert(URL, pprime:category, CatURL, waisda),
+	rdf_assert(CatURL, rdfs:label, literal(lang(nl, Cat)), waisda),
+
+	assert_videos(Ts).
+
+
+entries_to_rdf :-
+	waisda_file(tagentry, File),
+	debug(waisda_import, 'reading tag entries', []),
+ 	csv_read_file(File, [Header|Content], [functor(tagentry)]),
+	length(Content, Length),
+	debug(waisda_import, '~w', [Length]),
+ 	create_table_map(Header, tagentry),
+	rdf_transaction(assert_entries(Content)).
+
+assert_entries([]).
+assert_entries([T|Ts]) :-
+	table_map_value(tagentry, id, T, Id),
+	table_map_value(tagentry, game_id, T, GameId),
+	table_map_value(tagentry, player_id, T, PlayerId),
+	table_map_value(tagentry, tag_id, T, TagId),
+	table_map_value(tagentry, time, T, Playhead),
+	table_map_value(tagentry, typingDuration, T, TypingDuration),
+	table_map_value(tagentry, score, T, Score),
+	table_map_value(tagentry, multiplier, T, Multiplier),
+	table_map_value(tagentry, createdOn, T, Date),
+
+  	pprime_url(Id, tagentry, URL),
+	pprime_url(GameId, game, GameURL),
+	pprime_url(PlayerId, player, PlayerURL),
+	pprime_url(TagId, tag, TagURL),
+	%parse_time(Date, iso_8601, Time),
+
+	rdf(GameURL, opmv:used, VideoURL, waisda),
+	%rdf(TagURL, pprime:hasName, Tag, tag),
+
+	rdf_assert(VideoURL, pprime:hasAnnotation, URL, waisda),
+	rdf_assert(URL, rdf:type, pprime:'TagEntry', waisda),
+	rdf_assert(URL, opmv:used, GameURL, waisda),
+	rdf_assert(URL, opmv:wasPerformedAt, literal(Date), waisda),
+	rdf_assert(URL, rdf:value, TagURL, waisda),
+	rdf_assert(URL, pprime:videoPlayhead, literal(Playhead), waisda),
+	rdf_assert(URL, pprime:creator, PlayerURL, waisda),
+	rdf_assert(URL, pprime:score, literal(Score), waisda),
+	rdf_assert(URL, pprime:typingDuration, literal(TypingDuration), waisda),
+	rdf_assert(URL, pprime:multiplier, literal(Multiplier), waisda),
+
+	assert_entries(Ts).
+
+
+tags_to_rdf :-
+	waisda_file(tag, File),
+	debug(waisda_import, 'reading tags', []),
+ 	csv_read_file(File, [Header|Content], [functor(tag)]),
+	length(Content, Length),
+	debug(waisda_import, '~w', [Length]),
+ 	create_table_map(Header, tag),
+	rdf_transaction(assert_tags(Content)).
+
+assert_tags([]).
+assert_tags([T|Ts]) :-
+	table_map_value(tag, id, T, Id),
+	table_map_value(tag, name, T, Tag),
+	pprime_url(Id, tag, URL),
+	rdf_assert(URL, rdf:type, pprime:'Tag', waisda),
+	rdf_assert(URL, rdfs:label, literal(Tag), waisda),
+ 	assert_tags(Ts).
+
+
+%%	create_table_map(+Header, +TableMapId)
+%
+%
+
+create_table_map(Header, Table) :-
+	Header =.. [_|Cols],
+	create_table_map_(Cols, 0, Table).
+
+create_table_map_([], _, _).
+create_table_map_([C|Cs], N, Table) :-
+	N1 is N + 1,
+	assert(table_map(Table, C, N1)),
+	create_table_map_(Cs, N1, Table).
+
+
+%%	table_map_value(+TableName, +ColName, +Row, -Value)
+%
+%
+
+table_map_value(Table, Name, Row, Value) :-
+	table_map(Table, Name, N),
+	!,
+	arg(N, Row, Value).
+
+
+
+%%	pprime_url(+Id, +Specifier, -URL)
+%
+%	URL in prestoprime namespace.
+
+pprime_url(Id, Spec, URL) :-
+	atom_concat(Spec, Id, Local),
+	rdf_global_id(pprime:Local, URL).
+
+
+%%	waisda_file(+Which, -AbsoluteFileName)
+%
+%	AbsoluteFileName for one of filename/2.
+%	Request waisda_data file_search_path to be defined.
+
+waisda_file(Which, File) :-
+	filename(Which, FileName),
+	absolute_file_name(waisda_data(FileName), File).
+
+
+
+
+
+		 /*******************************
+		 *	       Additions	*
+		 *******************************/
+
+game_stats :-
+	findall(G-N,
+		(rdf(G,rdf:type,pprime:'Game'),
+		 game_users(G,Us),
+		 length(Us,N)
+		),
+		Gs),
+	length(Gs, Total),
+	proof_count(member(_-0, Gs), _, Empty),
+	proof_count(member(_-1, Gs), _, Single),
+	proof_count((member(_-N, Gs), N>1), More),
+	format('total: ~w~n empty: ~w~n single: ~w~n multiple: ~w~n',
+	       [Total,Empty,Single,More]).
+
+
+add_game_users :-
+	findall(G-Us,
+		(rdf(G,rdf:type,pprime:'Game', waisda),
+		 game_users(G,Us)
+		),
+		Gs),
+	length(Gs, N),
+	rdf_transaction(add_game_users(Gs, N)).
+
+add_game_users([], _).
+add_game_users([Game-Users|Gs], Left) :-
+	Left1 is Left-1,
+ 	length(Users, N),
+	debug(import_waisda, '~w ~p ~w', [Left,Game,N]),
+	(   N==0
+	->  rdf_retractall(Game, _, _, waisda)
+	;   assert_game_users(Users, Game)
+	),
+	add_game_users(Gs, Left1).
+
+assert_game_users([], _).
+assert_game_users([User|Us], Game) :-
+	rdf_assert(Game, opmv:wasPerformedBy, User, waisda),
+	assert_game_users(Us, Game).
+
+
+game_users(Game, Users) :-
+	 findall(U,
+		 ( rdf(Game, rdf:type, pprime:'Game',waisda),
+		   rdf(E,opmv:used,Game),
+		   rdf(E,pprime:creator,U)
+		 ),
+		 Us),
+	 sort(Us,Users).