comparison cpack/dml/api/archive.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
comparison
equal deleted inserted replaced
-1:000000000000 0:718306e29690
1 /* Part of DML (Digital Music Laboratory)
2 Copyright 2014-2015 Samer Abdallah, University of London
3
4 This program is free software; you can redistribute it and/or
5 modify it under the terms of the GNU General Public License
6 as published by the Free Software Foundation; either version 2
7 of the License, or (at your option) any later version.
8
9 This program is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 GNU General Public License for more details.
13
14 You should have received a copy of the GNU General Public
15 License along with this library; if not, write to the Free Software
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17 */
18
19 :- module(api_archive, [ locator_uri/2, with_input_from_uri/2, uri_absolute_path/2, archive_file/3, archive_file/2 ]).
20
21 :- use_module(library(http/http_dispatch)).
22 :- use_module(library(http/http_parameters)).
23 :- use_module(library(xmlarchive)).
24 :- use_module(library(httpfiles)).
25 :- use_module(library(fileutils)).
26 :- use_module(library(insist)).
27
28 :- set_prolog_flag(double_quotes,string).
29 :- rdf_register_prefix(file,'file://').
30 :- http_handler(api(archive/get), archive_get, []).
31 :- setting(archive:root,string,"~/lib/dml-archive","Directory containing accessible files").
32
33 user:file_search_path(archive,Path) :- setting(archive:root,DD), expand_file_name(DD,[Path]).
34
35 archive_get(Request) :-
36 http_parameters(Request, [uri(URI, [optional(false), description("URI of archive entry")])]),
37 file_name_extension(_,Ext,URI),
38 with_input_from_uri(URI,reply_from_stream(Ext)).
39
40 uri_absolute_path(URI,Path) :- var(Path), !,
41 insist(string_concat("file://",LocString,URI)),
42 absolute_file_name(archive(LocString),Path,[access(read)]).
43 uri_absolute_path(URI,Path) :-
44 file_search_path(archive,Root),
45 atom_concat(Root,Rel,Path),
46 atom_concat('file:/',Rel,URI).
47
48 :- meta_predicate with_input_from_uri(+,1).
49 with_input_from_uri(URI,Goal) :-
50 insist(string_concat("file://",LocString,URI)),
51 ( sub_string(LocString,PathLen,1,FragLen,"#")
52 -> sub_string(LocString,0,PathLen,_,Path),
53 sub_atom(LocString,_,FragLen,0,Frag),
54 absolute_file_name(archive(Path),ArchivePath,[access(read)]),
55 with_archive_stream(ArchivePath,Frag,Goal)
56 ; absolute_file_name(archive(LocString),AbsPath,[access(read)]),
57 with_stream(S, open(AbsPath,read,S), call(Goal,S))
58 ).
59
60 reply_from_stream(Ext,Stream) :- reply_stream(Stream,Ext).
61
62 locator_uri(file(Parts), URI) :- atomic_list_concat(['file:/'|Parts],'/',URI).
63 locator_uri(archive_entry(ArchivePath,EntryName), URI) :-
64 atomic_list_concat(['file://',ArchivePath,'#',EntryName],URI).
65
66 %% archive_file(+Ext:atom, +In:path, -Out:uri) is det.
67 %% archive_file(+In:path,-Out:uri) is det.
68 %
69 % This procedure finds a permanent home for the file In, moving it into
70 % the directory tree managed by the archive, giving it a unique file name,
71 % and returning the URI of the location.
72 %
73 % !! could add extension if necessary
74 archive_file(In,Out) :- archive_file('',In,Out).
75 archive_file(Ext,In,Out) :-
76 get_time(Time),
77 format_time(atom(Dir),'auto/%Y%m%d',Time),
78 expand_file_search_path(archive(Dir),FullDir),
79 ( exists_directory(FullDir) -> true
80 ; make_directory(FullDir)
81 ),
82 once( ( repeat, random_name(Ext,8,Str),
83 directory_file_path(FullDir,Str,Path),
84 \+exists_file(Path) )),
85 rename_file(In,Path),
86 uri_absolute_path(Out,Path).
87
88 random_name(Ext,Len,String) :-
89 length(Chars,Len),
90 maplist(web_storage:random_char,Chars),
91 format(string(String),'~s~s',[Chars,Ext]).
92
93