:- module(yaz_game, [ http_yaz_game/1, match_score/5, update_tag_score/4, active_players/2, active_player/4, game_player_score/3, set_game_player_score/3, update_player_score/3 ]). :- use_module(library(http/http_dispatch)). :- use_module(library(http/http_parameters)). :- use_module(library(http/http_path)). :- use_module(library(http/html_write)). :- use_module(library(http/html_head)). :- use_module(library(http/http_json)). :- use_module(library(http/js_write)). :- use_module(library(http/json)). :- use_module(library(http/json_convert)). :- use_module(library(http/http_session)). :- use_module(user(user_db)). :- use_module(library(semweb/rdf_db)). :- use_module(library(semweb/rdfs)). :- use_module(library(semweb/rdf_label)). :- use_module(library(yaz_util)). :- use_module(library(yui3)). :- use_module(library(user_process)). :- use_module(library(video_annotation)). :- use_module(components(label)). :- use_module(components(yaz_page)). :- use_module(api(video_frames)). :- setting(match_interval, integer, 10000, 'Interval in which tags can be matched (in miliseconds)'). :- setting(max_player_count, integer, 4, 'Maximum number of players before auto starting a game'). :- setting(request_interval, integer, 2000, 'Interval between requests to the server (in miliseconds)'). :- setting(video_buffer_time, integer, 1, 'Expect delay in load of page and start of Video (in seconds)'). :- setting(gamestart, oneof([all,creator,none,false]), creator, 'Determines who can start the game'). :- setting(garden, oneof([player,sgarden,mgarden,cgarden,false]), mgarden, 'Redirect to gardening when video is finished'). :- dynamic player_score/3. :- rdf_meta cond_object_assert(r,r,o,r). channel(pprime1, 'https://ecrit10:pPRIME4ever@fileportal.rai.it/da%20RAI%20PRIME/LL/PrestoPRIME_ORF_197668_P0142620.webm', 'PPrime test 1', 600). channel(pprime2, 'https://ecrit10:pPRIME4ever@fileportal.rai.it/da%20RAI%20PRIME/LL/PrestoPRIME_UIBK_003383.ogv', 'PPrime test 2', 1000). channel('http://nos.nl/uitzending/32556-nos-journaal-1000-uur.html', video('nos_journaal_10022011.flv'), 'NOS journaal 10 Feb 2011', 435). channel('http://www.openbeelden.nl/media/17674/Nederlandse_ontwikkelingshulp_voor_Indonesiƫ__sanering_waterhuishouding', video('openbeelden1.flv'), 'Nederlandse ontwikkelingshulp voor Indonesia', 120). channel('http://www.openbeelden.nl/media/17260/Indische_tentoonstelling_voor_de_Nederlandse_jeugd', video('openbeelden2.flv'), 'Inische tentoonstelling', 120). channel('http://nos.nl/video/217191-het-nieuws-in-60-seconden-1430-uur.html', video('nos_journaal_07022011.flv'), 'NOS journaal 7 Feb 2011', 60). /*channel('http://g.bbcredux.com/programme/bbcone/2011-02-05/12-00-00', video('bbc_news_05022011.flv'), 'BBC News 5 Feb 2011 12:00', 1101). channel('http://g.bbcredux.com/programme/bbcone/2010-11-21/22-00-00', 'http://g.bbcredux.com/programme/5542126155790075626/download/12340-1295719806-48faefbd0b0f9057050098ef47daf3a5/flash.flv', 'BBC News 21 Nov 2010 22:00', 1101). */ :- http_handler(yaz(game), http_yaz_game, []). :- http_handler(root(game), http_yaz_game, []). % shortcut %% http_yaz_game(+Request) % % Emit a web page with a video tagging game. http_yaz_game(Request) :- ensure_logged_on(User0), user_property(User0, url(User)), http_parameters(Request, [ url(URL, [optional(true), descritpion('URL of a video to start a game with')]), video(Video, [optional(true), description('Video source of the URL')]), title(Title, [optional(true), description('Title of URL')]), game(Game, [optional(true), description('URL of current Game')]) ]), ( var(Game), var(URL) -> findall(channel(U, V, T), channel(U, V, T, _), Channels), html_home_page(Channels) ; var(Game), nonvar(URL) -> create_game(URL, User, Game, [video(Video),title(Title)]), active_players(Game, Players), html_waiting_page(Game, URL, User, Players) ; join_game(Game, User), game_video_start(Game, URL, PlayHead), active_players(Game, Players), user_tags(Game, User, Tags), html_game_page(Game, URL, User, PlayHead, Players, Tags) ). %% active_player(+Game, -Players) % % Players are all users that joined Game. active_players(Game, Players) :- PlayerObj = {player:P, name:Name, score:Score}, findall(PlayerObj, active_player(Game, P, Name, Score), Players). active_player(Game, Player, Name, Score) :- user_process_joined(Game, Player), player_score(Game, Player, Score), % this would be retracted if the user has left the game display_label(Player, Name). %% user_tags(+Game, +User, -Tags) % % Tags are all tag entries by User in Game. user_tags(Game, User, Tags) :- TagObj = json([id=A, label=Tag, time=Time, match=Match]), findall(Time-TagObj, user_tag(Game, User, A, Tag, Time, Match), Tags0), keysort(Tags0, Tags1), reverse(Tags1, Tags2), pairs_values(Tags2, Tags). user_tag(Game, User, Annotation, Tag, Time, Match) :- rdf(Annotation, pprime:creator, User, Game), rdf(Annotation, rdf:value, literal(Tag)), rdf(Annotation, pprime:videoPlayhead, literal(Time), _), ( matched_json_term(Annotation, Match) -> true ; Match = @false ). matched_json_term(Annotation, json([score=Score, multiplier=Multiplier])) :- rdf(Annotation, pprime:score, literal(Score)), rdf(Annotation, pprime:multiplier, literal(Multiplier)). /******************************* * HTML * *******************************/ %% html_home_page(+Channels) % % Emit html page with a list of video channels. html_home_page(Channels) :- reply_html_page(yaz, [ title(['YAZ tagging game']) ], [ \html_requires(css('game.css')), div([class(topic), id(channels)], [ div(class(header), h2('Select a video')), div(class(body), \html_channels(Channels)) ]), div([class(topic), id(new)], [ div(class(header), h2('Start game with a new video')), div(class(body), \html_new_game) ]), script(type('text/javascript'), []) ]). html_channels([]) --> !. html_channels([channel(URL, Video0, Title)|Vs]) --> { http_absolute_location(Video0, Video, []), http_link_to_id(serve_video_frame, [url(Video),time(5)], Frame), ( waiting_game(URL, _Game, Players) -> length(Players, Count) ; Count = 0, Players = [] ), http_link_to_id(http_yaz_game, [url(URL)], Link) }, html(div(class(channel), [ h4(Title), div(class('thumb-container video'), [ a(href(Link), img([title(Title), src(Frame), alt(Title)])), div(class(players), \html_waiting_count(Count)) ]) ])), html_channels(Vs). html_waiting_count(0) --> !. html_waiting_count(1) --> !, html([ 1, ' player waiting']). html_waiting_count(N) --> !, html([ N, ' players waiting']). waiting_game(URL, Game, Players) :- rdf(Game, opmv:used, URL), rdf(Game, rdf:type, pprime:'Game'), \+ rdf(Game, opmv:wasStartedAt, _), !, findall(P, active_player(Game, P, _, _), Players). html_new_game --> html(form([div(class(inputline), [div(class(label), title), input([type(text), size(30), name(title)])]), div(class(inputline), [div(class(label), 'page URL'), input([type(text), size(30), name(url)])]), div(class(inputline), [div(class(label), 'video source'), input([type(text), size(30), name(video)])]), div(class(inputline), input([type(submit), value(play)])) ])). %% html_waiting_page(+Game, +URL, +User, +Players) % % Emit html page with a list of video channels. html_waiting_page(Game, URL, User, Players) :- display_label(URL, Title), video_source(URL, Video), http_link_to_id(serve_video_frame, [url(Video),time(5)], Frame), reply_html_page(yaz, [ title(['YAZ tagging game - ', Title]) ], [ \html_requires(css('game.css')), h2(Title), div(id(waiting), [ div([class('thumb-container'), id('video')], img([title(Title), alt(Title), src(Frame)])), div(id(players), [ h4(class(message), ['Current players']) ]) ]), div(id(options), [ \html_creator_options(Game, User) ]), script(type('text/javascript'), \html_waiting_yui(Game, Players, User)) ]). html_creator_options(Game, _User) --> { setting(gamestart, all), http_link_to_id(http_yaz_game, [game(Game)], Link) }, html(a(href(Link), 'start the game')). html_creator_options(Game, User) --> { setting(gamestart, creator), user_process_creator(Game, User), http_link_to_id(http_yaz_game, [game(Game)], Link) }, html(a(href(Link), 'start the game')). html_creator_options(_, _) --> !. html_waiting_yui(Game, Players, User) --> { http_location_by_id(http_waiting_data, DataServer), http_link_to_id(http_yaz_game, [game(Game)], GameLink), http_absolute_location(js('game/players.js'), GamePlayers, []), setting(max_player_count, Max) }, js_yui3([{modules:{'game-players':{fullpath:GamePlayers}}}], [node,'base','io-base','json-parse','querystring-stringify-simple', 'game-players' ], [ \js_function_decl(fetchData, [], \[ ' Y.io("',DataServer,'", {data:{game:"',Game,'",user:"',User,'"}, on:{success:function(id,o) { var result = Y.JSON.parse(o.responseText); if(result.start) { window.location.href="',GameLink,'" } else { gamePlayers.set("players", result.players)} }}})\n' ]), \js_new(gamePlayers, 'Y.mazzle.GamePlayers'({container:'#players', user:User, players:Players, maxNumberOfPlayers:Max, emptyShow:symbol(true) })), %\js_call(fetchData) \js_call('Y.later'(500, symbol('Y'), symbol(fetchData), {}, symbol(true))) ]). %% html_game_page(+Game, +URL, +User, +PlayHead, +Player, +Tags) % % Emit an html page with an active tagging game. html_game_page(Game, URL, User, PlayHead, Players, Tags) :- display_label(URL, Title), reply_html_page(yaz, [ title(['YAZ tagging game - ', Title]) ], [ \html_requires(css('game.css')), \html_page_containers(Title), script(type('text/javascript'), \html_page_yui(Game, URL, User, PlayHead, Players, Tags)) ]). html_page_containers(Title) --> html([ h2(Title), div(id(main), [ div(id(videoplayer), []), div(class(input), [ input([type(text), id(taginput)]), div(id(suggest), []), div([id(tags)], []) ]) ]), div(id(players), []) ]). html_page_yui(Game, URL, User, PlayHead, Players, Tags) --> { http_absolute_location(js('videoplayer/'), FilePath, []), http_absolute_location(js('videoplayer/videoplayer.js'), VideoPlayer, []), http_absolute_location(js('game/input.js'), GameInput, []), http_absolute_location(js('game/players.js'), GamePlayers, []), setting(request_interval, RequestInterval), setting(garden, Garden), video_source(URL, Video) }, html_requires(js('videoplayer/swfobject.js')), js_yui3([{modules:{'game-players':{fullpath:GamePlayers}, 'video-player':{fullpath:VideoPlayer}, 'game-input':{fullpath:GameInput} }} ], [node,event,widget,anim, 'io-base','json-parse','querystring-stringify-simple', 'video-player','game-input','game-players' ], [ \js_new(videoPlayer, 'Y.mazzle.VideoPlayer'({filepath:FilePath, src:Video, width:640, height:380, controls:symbol(false), autoplay:symbol(true), start:PlayHead })), \js_new(gameInput, 'Y.mazzle.GameInput'({input:'#taginput', output:'#tags', tags:Tags })), \js_new(gamePlayers, 'Y.mazzle.GamePlayers'({container:'#players', user:User, players:Players })), \js_support_functions(Game, User), \js_call('Y.later'(RequestInterval, symbol('Y'), symbol(fetchData), symbol({}), symbol(true))), \js_call('videoPlayer.render'('#videoplayer')), \js_yui3_on(gameInput, addTag, addTag), \js_yui3_on(videoPlayer, end, \js_video_end(Garden, Game)) ]). js_support_functions(Game, User) --> { http_location_by_id(http_game_add_tag, AddTag), http_location_by_id(http_game_data, GameData) }, js_function_decl(addTag, [e], \[ ' var node = e.node, data = {game:"',Game,'",user:"',User,'",playhead:videoPlayer.getTime()*1000}; data.tag = e.label; Y.io("',AddTag,'", {data: data, on: {success:function(i,o) { gameInput._tagNodes[Y.JSON.parse(o.responseText).id]=node}}, });\n' ]), js_function_decl(fetchData, [e], \[ ' var data = {game:"',Game,'",user:"',User,'",playhead:videoPlayer.getTime()*1000}; Y.io("',GameData,'", {data: data, on: {success:handleResponse} });\n' ]), js_function_decl(handleResponse, [id, o], \[ ' var r = Y.JSON.parse(o.responseText); gamePlayers.set("players", r.players); gameInput.updateTags(r.tags);\n' ]). js_video_end(false, _) --> !. js_video_end(Garden, Process) --> { http_absolute_location(yaz(Garden), URL, []) }, js_function([], \[ ' window.location.href = "',URL,'?process=',Process,'"' ]). /******************************* * game events * *******************************/ %% create_game(+URL, +Player, -Game, +Options) % % Player starts a new game for Video. create_game(URL, Player, Game, _Options) :- waiting_game(URL, Game, _), !, ( user_process_creator(Game, Player) -> new_player_score(Game, Player) % just to make sure ; join_game(Game, Player) ). create_game(URL, Player, Game, Options) :- option(video(Video), Options, _), option(title(Title), Options, _), create_user_process(Player, [rdf:type=pprime:'Game', opmv:used=URL ], Game), new_player_score(Game, Player), add_video(URL, Video, Title, _), debug(game, 'Game ~w created for ~w by ~w', [Game,Video,Player]). new_player_score(Game, Player) :- ( player_score(Game, Player, _) -> retractall(player_score(Game, Player, _)) ; true ), assert(player_score(Game, Player, 0)). %% game_video_start(+Game, -URL, -PlayHead) is det % % True if PlayHead is the current time of the Video. The PlayHead % is determined by the startTime of the game. If no startTime is % defined the Game process is started. game_video_start(Game, URL, PlayHead) :- rdf(Game, opmv:used, URL), !, setting(video_buffer_time, BufferTime), ( rdf(Game, opmv:wasStartedAt, literal(type(_, XMLDateTime))) -> parse_time(XMLDateTime, StartTime), get_time(Time), PlayHead is (Time - StartTime)+BufferTime ; start_user_process(Game), PlayHead = BufferTime ). game_video_start(_Game, '', 0). % for testing %% join_game(+Game, +Player) is det % % Asserts that Player has joined game. join_game(Game, Player) :- ( user_process_joined(Game, Player) -> set_active_process(Game) ; join_user_process(Game, Player), debug(game, 'Game ~w joined by ~w', [Game, Player]), new_player_score(Game, Player) ). %% add_tag(+Game, +Player, +Tag, +PlayHeadTime, -AnnotationId) % % Asserts that User has entered a Tag. add_tag(Game, Player, Tag, PlayHead, AnnotationId) :- rdf(Game, opmv:used, URL), create_video_annotation(URL, literal(Tag), PlayHead, Player, AnnotationId), debug(game, 'Added tag ~w at time ~w by ~w (~w)', [Tag, PlayHead, Player, AnnotationId]). /******************************* * data services * *******************************/ :- http_handler(yaz('waitingdata'), http_waiting_data, []). :- http_handler(yaz('gamedata'), http_game_data, []). :- http_handler(yaz('gameaddtag'), http_game_add_tag, []). %% http_waiting_data(+Request) % % Return JSON object with waiting players in game. http_waiting_data(Request) :- http_parameters(Request, [ game(Game, [uri, description('URL of current Game')]) ]), ( rdf(Game, opmv:wasStartedAt, _) -> reply_json(json([start= @true])) ; PlayerObj = json([player=P, name=N]), findall(PlayerObj, active_player(Game, P, N, _), Players), length(Players, Count), setting(max_player_count, Max), ( Count >= Max -> reply_json(json([start= @true])) ; reply_json(json([players=Players])) ) ). %% http_game_add_tag(+Request) % % Return JSON object with players in a game. http_game_add_tag(Request) :- http_parameters(Request, [ game(Game, [uri, description('URL of current Game')]), user(User, [uri, description('URL of current User')]), playhead(Playhead, [number, description('Current time of the video play head (in miliseconds)')]), tag(Tag, [description('Optionally a new tag can be added')]) ]), setting(match_interval, Interval), add_tag(Game, User, Tag, Playhead, Id), matching_tags(Game, User, Id, Tag, Playhead, Interval, Matches), length(Matches, C), rdf_transaction(update_scores(Matches, 0, C, Game)), reply_json(json([id=Id])). %% match_existing_tags(+Game, +User, +Tag, +Playhead, +Interval, %% -Matches) % % Returns all matches with tag within Interval of Playhead. % Matches are sorted by time. matching_tags(Game, User, Id, Tag, Playhead, Interval, Matches) :- findall(Time-match(Entry, Player, Type), matching_tag(Game, User, Tag, Playhead, Interval, Entry, Player, Type, Time), Matches0), ( Matches0 = [] -> Matches = [] ; keysort([Playhead-match(Id,User,exact)|Matches0], Matches1), pairs_values(Matches1, Matches) ). matching_tag(Game, User, Tag, Playhead, Interval, Id, Player, Match, Time) :- Start is Playhead-Interval, tag_match(Tag, Game, Id, Match), rdf(Id, pprime:videoPlayhead, literal(between(Start,Playhead), Time)), rdf(Id, pprime:creator, Player), User \== Player. tag_match(Tag, Game, Annotation, exact) :- rdf(Annotation, rdf:value, literal(Tag), Game). %% update_scores(+Matches, +Current, +Total, +Game) % % Update player scores. update_scores([], _, _, _). update_scores([match(Id,Player,Match)|Ms], N, Count, Game) :- N1 is N + 1, match_score(Match, N1, Count, Points, Multiplier), update_tag_score(Id, Game, Points, Multiplier), update_player_score(Game, Player, Points), update_scores(Ms, N1, Count, Game). update_player_score(Game, Player, Points) :- player_score(Game, Player, OldScore), retractall(player_score(Game, Player, OldScore)), NewScore is OldScore+Points, assert(player_score(Game, Player, NewScore)). match_score(Match, N1, Count, Points, Multiplier) :- match_type_points(Match, MPoints), order_count_multiplier(N1, Count, Multiplier), Points is MPoints*Multiplier. match_type_points(exact, 50). order_count_multiplier(Order, Count, X) :- X is 4/(Order*2) + ((Count-2)/2). update_tag_score(Annotation, Game, Score, Multiplier) :- rdf_retractall(Annotation, pprime:score, _), rdf_retractall(Annotation, pprime:multiplier, _), rdf_assert(Annotation, pprime:score, literal(Score), Game), rdf_assert(Annotation, pprime:multiplier, literal(Multiplier), Game). %% http_game_data(+Request) % % Return JSON object with players in a game. http_game_data(Request) :- http_parameters(Request, [ game(Game, [uri, description('URL of current Game')]), user(User, [uri, description('URL of current User')]), playhead(Playhead, [number, description('Current time of the video play head (in miliseconds)')]) ]), setting(match_interval, Interval), PlayerObj = json([player=P, name=Name, score=Score]), findall(PlayerObj, active_player(Game, P, Name, Score), Players), TagObj = json([id=A, label=Label, time=Time, match=Match]), findall(TagObj, user_matched_tag(Game, User, Playhead, Interval, A, Label, Time, Match), Tags), reply_json(json([user=User, players=Players, tags=Tags])). %% user_matched_tag(+Game, +User, +PlayHead, +Interval, %% -Annotation, -Match, -Score) % % Tag is entered by User during Game. user_matched_tag(Game, User, Playhead, Interval, Id, Tag, Time, Match) :- Start is Playhead-Interval, rdf(Id, pprime:videoPlayhead, literal(between(Start,Playhead), Time), Game), rdf(Id, pprime:creator, User), matched_json_term(Id, Match), rdf(Id, rdf:value, literal(Tag)). /******************************* * store channnels * *******************************/ %% assert_channel_info % % Store info of channel videos in RDF. assert_channel_info :- rdf_transaction(( channel(URL, Video0, Title, Duration), http_absolute_location(Video0, Video, []), add_video(URL, Video, Title, Duration), fail ; true )). %% add_video(+URL, ?Video, ?Title, ?Duration) % % Store video properties in RDF. add_video(URL, Video, Title, Duration) :- %rdf_retractall(URL, _, _), cond_object_assert(URL, rdf:type, pprime:'Video', video), cond_object_assert(URL, pprime:source, Video, video), cond_object_assert(URL, dc:title, literal(Title), video), cond_object_assert(URL, pprime:duration, literal(Duration), video). cond_object_assert(S,P,O,G) :- ground(O), !, ( rdf(S,P,O) -> true ; rdf_assert(S,P,O,G) ). cond_object_assert(_,_,_,_). %:- assert_channel_info. game_player_score(Game, User, Score) :- player_score(Game, User, Score). set_game_player_score(Game, User, Score) :- assert(player_score(Game, User, Score)).