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