:- module(download_video_stream, [ download_waisda_videos/0, download_waisda_video/1, download_video_stream/2 ]). :- use_module(library(semweb/rdf_db)). :- 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).