vumix/commit

start with prototype1

authorMichiel Hildebrand
Wed Apr 4 18:08:08 2012 +0200
committerMichiel Hildebrand
Wed Apr 4 18:08:08 2012 +0200
commit01157554506401cf176682c3fd2acad1687b565d
tree6cbb45959cfd0c6126aca97b99498c2154d5a6ec
parent01cbb0025408821affea5bf62f481ddc07da35c4
Diff style: patch stat
diff --git a/applications/p1.pl b/applications/p1.pl
new file mode 100644
index 0000000..8606ab4
--- /dev/null
+++ b/applications/p1.pl
@@ -0,0 +1,270 @@
+:- module(vumix_p1,
+	[]).
+
+
+% semweb
+:- use_module(library('semweb/rdf_db')).
+:- use_module(library('semweb/rdfs')).
+:- use_module(library('semweb/rdf_label')).
+:- use_module(library(yui3_beta)).
+
+% http libraries
+:- use_module(library('http/http_dispatch')).
+:- use_module(library('http/http_parameters')).
+:- use_module(library('http/html_write')).
+:- use_module(library('http/html_head')).
+:- use_module(library('http/http_path')).
+:- use_module(library('http/http_json')).
+:- use_module(components(label)).
+:- use_module(library(settings)).
+:- use_module(user(user_db)).
+:- use_module(library(instance_search)).
+:- use_module(library(graph_version)).
+
+:- use_module(applications(annotation)).
+:- use_module(library(user_process)).
+
+
+/***************************************************
+* http handlers
+***************************************************/
+
+:- http_handler(cliopatria(vumix/p1), http_vumix_p1, []).
+
+
+/***************************************************
+* settings
+***************************************************/
+
+
+/***************************************************
+* http replies
+***************************************************/
+
+%%	http_vumix_p1(+Request)
+%
+%	Generate page to annotate a vumix.
+
+http_vumix_p1(Request) :-
+	http_parameters(Request,
+		[ target(Target,
+		     [uri,
+		      description('URI of the object to be annotated')
+		     ]),
+		  field(Fields0,
+			[zero_or_more,
+			 description('URI of annotation field')
+			])
+		]),
+	(   Fields0 = []
+	->  Fields = ['http://semanticweb.cs.vu.nl/prestoprime/personAnnotation',
+		      'http://semanticweb.cs.vu.nl/prestoprime/placeAnnotation',
+		      'http://semanticweb.cs.vu.nl/prestoprime/nameAnnotation',
+		      'http://semanticweb.cs.vu.nl/prestoprime/subjectAnnotation']
+	;   Fields = Fields0
+	),
+	(   setting(vumix:login, true)
+        ->  authorized(write(_,_)),
+	    logged_on(User)
+	;   logged_on(User, anonymous)
+        ),
+	user_process(User, Target, _),
+	html_page(Target, Fields).
+
+user_process(User, Target, Process) :-
+	(   current_user_process(Process),
+	    rdf(Process, rdf:type, pprime:'Annotation'),
+	    rdf(Process, opmv:used, Target)
+	->  true
+	;   create_user_process(User, [rdf:type=pprime:'Annotation',
+				       opmv:used=Target
+				      ], Process)
+	),
+	start_user_process(Process).
+
+
+/***************************************************
+* annotation page
+***************************************************/
+
+%%	html_page(+Target, +Fields)
+%
+%	HTML page
+
+html_page(Target, Fields) :-
+	rdf_global_id(_:Id, Target),
+	reply_html_page(
+	    [ title(['Annotate -- ', Id])
+	    ],
+	    [ \html_requires(yui3('cssgrids/grids-min.css')),
+	      \html_requires(css('annotation.css')),
+	      \html_requires(css('vumix.css')),
+	      div(class('yui3-skin-sam yui-skin-sam'),
+		  [ div(id(hd), []),
+		    div(id(bd),
+			div([id(layout), class('yui3-g')],
+			    [ div(id(title), []),
+			      div(id(frames),
+				  \html_frames(Target))
+			    ])
+		       ),
+		    div(id(ft), [])
+		  ]),
+	      script(type('text/javascript'),
+		    [])% \yui_script(Target, Fields))
+	    ]).
+
+html_frames(Target) -->
+	{ video_source(Target, Source),
+	  rdf(Target, pprime:duration, literal(DA)),
+	  atom_number(DA, Duration)
+	},
+	!,
+	html_frame_list(1000, Duration, 10000, Source).
+html_frames(_) --> !.
+
+html_frame_list(Time, Duration, _, _) -->
+	{ Time > Duration },
+	!.
+html_frame_list(Time, Duration, Interval, Source) -->
+	{ Next is Time+Interval,
+	  http_link_to_id(serve_video_frame, [url(Source),time(Time)], Link)
+	},
+	html(div(class(frame),
+	     [ div(class(thumb),
+		   img([src(Link)])),
+	       div(class(tags), [])
+	     ])),
+	html_frame_list(Next, Duration, Interval, Source).
+
+% hack for mbh demo
+video_source(R, Video) :-
+	rdf_has(R, dc:id, literal(FragmentId)),
+	!,
+	concat_atom(['http://eculture2.cs.vu.nl/pprime/videos/',FragmentId,'.mp4'], Video).
+video_source(_R, @null).
+
+
+
+
+		 /*******************************
+		 *	     JavaScript		*
+		 *******************************/
+
+%%	yui_script(+Graph)
+%
+%	Emit YUI object.
+
+yui_script(Target, Fields) -->
+	{ findall(M-C, js_module(M,C), Modules),
+	  pairs_keys(Modules, Includes)
+	},
+	yui3([json([modules(json(Modules))])],
+	     ['recordset-base'|Includes],
+	     [\js_video(Target),
+	      \js_video_frames(Target),
+	      \js_title_edit(Target),
+	      \js_annotation_fields(Fields, Target),
+	      'videoFrames.on("frameSelect", function(e) {videoPlayer.setTime(e.time, true)});']).
+
+js_module('videoplayer', json([fullpath(Path),
+			       requires([node,event,widget])
+			      ])) :-
+	http_absolute_location(js('vuplayer/videoplayer.js'), Path, []).
+js_module('videoframes', json([fullpath(Path),
+			       requires([node,event,widget])
+			      ])) :-
+	http_absolute_location(js('videoframes.js'), Path, []).
+js_module('textedit', json([fullpath(Path),
+			    requires([node,event,io,plugin,'querystring-stringify-simple'])
+			      ])) :-
+	http_absolute_location(js('textedit.js'), Path, []).
+js_module('annotation', json([fullpath(Path),
+			      requires(['recordset-base',
+					autocomplete,
+					'autocomplete-highlighters',
+					overlay,
+					'io','json',
+					'querystring-stringify-simple'
+				       ])
+			     ])) :-
+	http_absolute_location(js('annotation.js'), Path, []).
+
+js_video_frames(Target) -->
+	{ http_location_by_id(serve_video_frame, FrameServer),
+	  video_source(Target, Src)
+	},
+	yui3_new(videoFrames,
+		 'Y.VideoFrames',
+		 {frameServer:FrameServer,
+		  video:Src,
+		  duration:343000,
+		  interval:5000,
+		  width:730
+		 }),
+	yui3_render(videoFrames, one(id(videoFrames))).
+
+js_title_edit(Target) -->
+	{ http_location_by_id(http_update_annotation, Update),
+	  rdf_equal(dcterms:title, Field),
+	  (   annotation_in_field(Target, Field, Annotation, _Body, Text)
+	  ->  true
+	  ;   Annotation = @null,
+	      Text = @null
+	  )
+	},
+	yui3_plug(one(id(title)),
+		  'Y.Plugin.TextEdit',
+		  {target:Target,
+		   field:Field,
+		   annotation:Annotation,
+		   text:Text,
+		   store:{update:Update}
+		  }).
+
+js_video(Target) -->
+	{ http_absolute_location(js('vuplayer/'), FilePath, []),
+	  video_source(Target, Src)
+	},
+	yui3_new(videoPlayer,
+		 'Y.VideoPlayer',
+		 {filepath:FilePath,
+		  src:Src,
+		  width:730,
+		  height:460,
+		  autoplay:symbol(false),
+		  controls:symbol(true)
+		 }),
+	yui3_render(videoPlayer, one(id(video))).
+
+%%	js_annotation_fields(+FieldURIs, +AnnotationTarget)
+%
+%	Write JavaScript to init annotation fields
+
+js_annotation_fields([], _) --> !.
+js_annotation_fields([URI|T], Target) -->
+	js_annotation_field(URI, Target),
+	js_annotation_fields(T, Target).
+
+js_annotation_field(FieldURI, Target) -->
+	{ http_location_by_id(http_add_annotation, Add),
+	  http_location_by_id(http_remove_annotation, Remove),
+	  rdf_global_id(_:Id, FieldURI),
+	  setting(min_query_length, MinQueryLength),
+	  rdf(FieldURI, an:source, literal(Source)),
+	  json_annotation_list(Target, FieldURI, Tags)
+	},
+	yui3_plug(one(id(Id)),
+		  'Y.Plugin.Annotation',
+		  {target:Target,
+		   field:FieldURI,
+		   source:Source,
+		   store:{add:Add,
+			  remove:Remove
+			 },
+		   tags:Tags,
+		   minQueryLength:MinQueryLength,
+		   resultListLocator: results,
+		   resultTextLocator: label,
+		   resultHighlighter: phraseMatch}).
+
diff --git a/lib/tfidf.pl b/lib/tfidf.pl
new file mode 100644
index 0000000..b558e0a
--- /dev/null
+++ b/lib/tfidf.pl
@@ -0,0 +1,52 @@
+:- module(tfidf,
+	  [tag_rank/2,
+	   documents/1,
+	   tf/3,
+	   idf/3
+	  ]).
+
+tag_rank(Video, RankedTagList) :-
+	documents(Videos),
+	findall(T, document_term(Video, T), Ts0),
+	sort(Ts0, Ts),
+	maplist(tag_score(Video, Videos), Ts, Scored),
+	keysort(Scored, Sorted),
+	reverse(Sorted, RankedTagList).
+
+tag_score(D, Collection, Tag, Score-Tag) :-
+	tf(Tag, D, TF),
+	idf(Tag, Collection, IDF),
+	Score is TF*IDF.
+
+documents(Videos) :-
+	findall(V, rdf(V,rdf:type,pprime:'Video'), Videos).
+
+
+document_term(D, T) :-
+	rdf(D, pprime:hasAnnotation, E),
+	rdf(E, rdf:value, literal(T)),
+	rdf(E, pprime:score, literal(SA)),
+	atom_number(SA, S),
+	S > 5.
+
+tf(T, D, TF) :-
+	findall(T,
+		document_term(D, T),
+		Ts),
+	length(Ts, TF).
+
+idf(T, Collection, IDF) :-
+	length(Collection, CollectionSize),
+	findall(D,
+		(   member(D, Collection),
+		    document_term(T, D)
+		),
+		DT),
+	length(DT, DTCount),
+	IDF is log(CollectionSize/(1+DTCount)).
+
+
+
+
+
+