-
Notifications
You must be signed in to change notification settings - Fork 0
/
static_handlers.pl
35 lines (28 loc) · 983 Bytes
/
static_handlers.pl
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
:- module(static_handlers, []).
/** <module> handle static files
*/
:- use_module(library(http/http_dispatch)).
:- use_module(library(http/html_write)).
% we'll need to fiddle with abstract locations
:- use_module(library(http/http_path)).
% and we need file support
:- use_module(library(http/http_files)).
:- use_module(library(http/http_server_files)).
%
% In a real application, we'd do this in strangeloop.pl
%
% Add an abstract URI path root to serve files from
%
% this is NOT a file location, it's an URI path
http:location(files, '/f', []).
%
% Now we want an abstract *file path* - not a URI, but
% an abstract name for a location, as when we say
% use_module(library(blah)).
%
user:file_search_path(static_files, assets).
% and now we're ready to serve files in a directory
:- http_handler(files(.), % abstract name of URI path
serve_files_in_directory(static_files),
[prefix]). % prefix option on handler so we handle every
% URI which starts /f/