1:- module(bc_api_file, []).
6:- use_module(library(http/http_wrapper)). 7:- use_module(library(filesex)). 8:- use_module(library(arouter)). 9
10:- use_module(bc_hex). 11:- use_module(bc_api_io). 12:- use_module(bc_api_auth). 13:- use_module(bc_api_error). 14:- use_module(bc_api_actor). 15:- use_module(bc_entry). 16:- use_module(bc_access). 17:- use_module(bc_files). 18:- use_module(bc_image). 19
21
22:- route_get(api/files/EntryId,
23 bc_auth, files_get(EntryId)). 24
25files_get(EntryId):-
26 bc_actor(Actor),
27 can_list(Actor, EntryId),
28 bc_entry_slug(EntryId, Slug),
29 atomic_list_concat([public, '/', Slug], Full),
30 check_safe_path(Full),
31 ( exists_directory(Full)
32 -> directory_only_files(Full, Files),
33 maplist(file_record, Files, List)
34 ; List = []),
35 bc_reply_success(List).
36
37can_list(Actor, EntryId):-
38 bc_entry_exists(EntryId),
39 list_access(Actor, EntryId).
40
41list_access(Actor, EntryId):-
42 bc_read_access_id(Actor, EntryId), !.
43
44list_access(_, _):-
45 throw(error(no_access)).
46
49
50file_record(File, _{ name: File }).
51
53
54:- route_post(api/upload/EntryId,
55 bc_call_handle_error, upload_file(EntryId)). 56
57upload_file(EntryId):-
58 catch(upload_file_checked(EntryId), Error, true),
59 ( var(Error)
60 -> true
61 ; drain_request,
62 throw(Error)).
63
64upload_file_checked(EntryId):-
65 ( bc_auth_user_by_key(Actor)
66 -> upload_file_checked(Actor, EntryId)
67 ; throw(error(invalid_api_key))).
68
69upload_file_checked(Actor, EntryId):-
70 can_upload(Actor, EntryId),
71 attemp_upload(EntryId).
72
73can_upload(Actor, EntryId):-
74 bc_entry_exists(EntryId),
75 upload_access(Actor, EntryId).
76
77upload_access(Actor, EntryId):-
78 bc_files_access_id(Actor, EntryId),
79 bc_update_access_id(Actor, EntryId), !.
80
81upload_access(_, _):-
82 throw(error(no_access)).
83
86
87drain_request:-
88 http_current_request(Request),
89 memberchk(input(In), Request),
90 setup_call_cleanup(
91 open_null_stream(Null),
92 ( memberchk(content_length(Len), Request)
93 -> copy_stream_data(In, Null, Len)
94 ; copy_stream_data(In, Null)),
95 close(Null)).
96
100
101attemp_upload(EntryId):-
102 http_current_request(Request),
103 memberchk(x_file_name(Target), Request),
104 bc_entry_slug(EntryId, Slug),
105 atomic_list_concat([public, '/', Slug], Directory),
106 check_safe_path(Directory),
107 ( exists_directory(Directory)
108 -> true
109 ; make_directory(Directory)),
110 atomic_list_concat([Directory, '/', Target], Full),
111 check_safe_path(Full),
112 memberchk(input(In), Request),
113 ( exists_file(Full)
114 -> throw(error(file_exists))
115 ; true),
116 ( exists_directory(Full)
117 -> throw(error(directory_exists))
118 ; true),
119 setup_call_cleanup(
120 open(Full, write, Stream, [encoding(octet)]),
121 ( memberchk(content_length(Len), Request)
122 -> copy_stream_data(In, Stream, Len)
123 ; copy_stream_data(In, Stream)),
124 close(Stream)),
125 bc_reply_success(true).
126
128
129:- route_del(api/file/EntryId/Name,
130 bc_auth, file_remove(EntryId, Name)). 131
132file_remove(EntryId, Name):-
133 bc_actor(Actor),
134 can_remove(Actor, EntryId),
135 bc_entry_slug(EntryId, Slug),
136 atomic_list_concat([public, '/', Slug, '/', Name], Full),
137 check_safe_path(Full),
138 delete_file(Full),
139 bc_reply_success(true).
140
141can_remove(Actor, EntryId):-
142 bc_entry_exists(EntryId),
143 upload_access(Actor, EntryId).
144
146
147:- route_get(api/image/size/EntryId/Name,
148 bc_auth, file_size(EntryId, Name)). 149
150file_size(EntryId, Name):-
151 bc_entry_slug(EntryId, Slug),
152 atomic_list_concat([public, '/', Slug, '/', Name], Full),
153 check_safe_path(Full),
154 ( bc_image_dimensions(Full, Width, Height)
155 -> bc_reply_success(_{ width: Width, height: Height })
156 ; bc_reply_error('Error occurred during image file reading.')).
157
159
160check_safe_path(Path):-
161 ( sub_atom(Path, _, _, _, '..')
162 -> throw(error(unsafe_path(Path)))
163 ; true)
HTTP handlers for file management
*/