Chris@0
|
1 /* This file is part of ClioPatria.
|
Chris@0
|
2
|
Chris@0
|
3 Author: Jan Wielemaker <wielemak@science.uva.nl>
|
Chris@0
|
4 HTTP: http://e-culture.multimedian.nl/
|
Chris@0
|
5 GITWEB: http://gollem.science.uva.nl/git/ClioPatria.git
|
Chris@0
|
6 GIT: git://gollem.science.uva.nl/home/git/ClioPatria.git
|
Chris@0
|
7 GIT: http://gollem.science.uva.nl/home/git/ClioPatria.git
|
Chris@0
|
8 Copyright: 2007, E-Culture/MultimediaN
|
Chris@0
|
9
|
Chris@0
|
10 ClioPatria is free software: you can redistribute it and/or modify
|
Chris@0
|
11 it under the terms of the GNU General Public License as published by
|
Chris@0
|
12 the Free Software Foundation, either version 2 of the License, or
|
Chris@0
|
13 (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 ClioPatria is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU General Public License
|
Chris@0
|
21 along with ClioPatria. If not, see <http://www.gnu.org/licenses/>.
|
Chris@0
|
22 */
|
Chris@0
|
23
|
Chris@0
|
24 :- module(html_head,
|
Chris@0
|
25 [ html_resource/2, % +Resource, +Attributes
|
Chris@0
|
26 html_requires//1, % +Resource
|
Chris@0
|
27 absolute_http_location/2 % +Spec, -Path
|
Chris@0
|
28 ]).
|
Chris@0
|
29 :- use_module(library(http/html_write)).
|
Chris@0
|
30 :- use_module(library(http/mimetype)).
|
Chris@0
|
31 :- use_module(library(error)).
|
Chris@0
|
32 :- use_module(library(settings)).
|
Chris@0
|
33 :- use_module(library(lists)).
|
Chris@0
|
34 :- use_module(library(option)).
|
Chris@0
|
35 :- use_module(library(ordsets)).
|
Chris@0
|
36 :- use_module(library(assoc)).
|
Chris@0
|
37 :- use_module(library(ugraphs)).
|
Chris@0
|
38 :- use_module(library(broadcast)).
|
Chris@0
|
39 :- use_module(library(apply)).
|
Chris@0
|
40 :- use_module(library(debug)).
|
Chris@0
|
41
|
Chris@0
|
42
|
Chris@0
|
43 /** <module> Deal with CSS and scripts
|
Chris@0
|
44
|
Chris@0
|
45 This module is to clean up the mess related to managing Javascript and
|
Chris@0
|
46 CSS files. It defines relations between scripts and style files.
|
Chris@0
|
47
|
Chris@0
|
48 Declarations come in two forms. First of all, clauses for
|
Chris@0
|
49 http:location_path/2 define HTTP locations globally, similar to
|
Chris@0
|
50 file_search_path/2. Second, html_resource/2 specifies HTML resources to
|
Chris@0
|
51 be used in the =head= and their dependencies. Resources are currently
|
Chris@0
|
52 limited to Javascript files (.js) and style sheets (.css). It is trivial
|
Chris@0
|
53 to add support for other material in the head. See html_include//1.
|
Chris@0
|
54
|
Chris@0
|
55 For usage in HTML generation, there is the DCG rule html_requires/1 that
|
Chris@0
|
56 demands named resources in the HTML head. For general purpose reasoning,
|
Chris@0
|
57 absolute_http_location/2 translates a path specification into an
|
Chris@0
|
58 absolute HTTP location on the server.
|
Chris@0
|
59
|
Chris@0
|
60 ---++ About resource ordering
|
Chris@0
|
61
|
Chris@0
|
62 All calls to html_requires//1 for the page are collected and duplicates
|
Chris@0
|
63 are removed. Next, the following steps are taken:
|
Chris@0
|
64
|
Chris@0
|
65 1. Add all dependencies to the set
|
Chris@0
|
66 2. Replace multiple members by `aggregate' scripts or css files.
|
Chris@0
|
67 see use_agregates/4.
|
Chris@0
|
68 3. Order all resources by demanding that their dependencies
|
Chris@0
|
69 preceede the resource itself. Note that the ordering of
|
Chris@0
|
70 resources in the dependency list is *ignored*. This implies
|
Chris@0
|
71 that if the order matters the dependency list must be split
|
Chris@0
|
72 and only the primary dependency must be added.
|
Chris@0
|
73
|
Chris@0
|
74 ---++ Debugging dependencies
|
Chris@0
|
75
|
Chris@0
|
76 Use ?- debug(html(script)). to see the requested and final set of
|
Chris@0
|
77 resources. All declared resources are in html_resource/3. The edit/1
|
Chris@0
|
78 command recognises the names of HTML resources.
|
Chris@0
|
79
|
Chris@0
|
80 @see For ClioPatria, the resources are defined in server/html_resource.pl
|
Chris@0
|
81 @tbd Possibly we should add img//2 to include images from symbolic
|
Chris@0
|
82 path notation.
|
Chris@0
|
83 @tbd It would be nice if the HTTP file server could use our location
|
Chris@0
|
84 declarations.
|
Chris@0
|
85 */
|
Chris@0
|
86
|
Chris@0
|
87 :- dynamic
|
Chris@0
|
88 html_resource/3. % Resource, Source, Properties
|
Chris@0
|
89
|
Chris@0
|
90 %% html_resource(+About, +Properties) is det.
|
Chris@0
|
91 %
|
Chris@0
|
92 % Register an HTML head resource. About is either an atom that
|
Chris@0
|
93 % specifies an HTTP location or a term Alias(Sub). This works
|
Chris@0
|
94 % similar to absolute_file_name/2. See http:location_path/2 for
|
Chris@0
|
95 % details. Recognised properties are:
|
Chris@0
|
96 %
|
Chris@0
|
97 % * requires(+Requirements)
|
Chris@0
|
98 % Other required script and css files. If this is a plain
|
Chris@0
|
99 % file name, it is interpreted relative to the declared
|
Chris@0
|
100 % resource. Requirements can be a list, which is equivalent
|
Chris@0
|
101 % to multiple requires properties.
|
Chris@0
|
102 %
|
Chris@0
|
103 % * virtual(+Bool)
|
Chris@0
|
104 % If =true= (default =false=), do not include About itself,
|
Chris@0
|
105 % but only its dependencies. This allows for defining an
|
Chris@0
|
106 % alias for one or more resources.
|
Chris@0
|
107 %
|
Chris@0
|
108 % * aggregate(+List)
|
Chris@0
|
109 % States that About is an aggregate of the resources in
|
Chris@0
|
110 % List.
|
Chris@0
|
111
|
Chris@0
|
112 html_resource(About, Properties) :-
|
Chris@0
|
113 source_location(File, Line), !,
|
Chris@0
|
114 retractall(html_resource(About, File:Line, _)),
|
Chris@0
|
115 assert_resource(About, File:Line, Properties).
|
Chris@0
|
116 html_resource(About, Properties) :-
|
Chris@0
|
117 assert_resource(About, -, Properties).
|
Chris@0
|
118
|
Chris@0
|
119 assert_resource(About, Location, Properties) :-
|
Chris@0
|
120 assert(html_resource(About, Location, Properties)),
|
Chris@0
|
121 clean_same_about_cache,
|
Chris@0
|
122 ( memberchk(aggregate(_), Properties)
|
Chris@0
|
123 -> clean_aggregate_cache
|
Chris@0
|
124 ; true
|
Chris@0
|
125 ).
|
Chris@0
|
126
|
Chris@0
|
127
|
Chris@0
|
128 %% html_requires(+ResourceOrList)// is det.
|
Chris@0
|
129 %
|
Chris@0
|
130 % Include ResourceOrList and all dependencies derived from it and
|
Chris@0
|
131 % add them to the HTML =head= using html_post/2. The actual
|
Chris@0
|
132 % dependencies are computed during the HTML output phase by
|
Chris@0
|
133 % html_insert_resource//1.
|
Chris@0
|
134
|
Chris@0
|
135 html_requires(Required) -->
|
Chris@0
|
136 html_post(head, 'html required'(Required)).
|
Chris@0
|
137
|
Chris@0
|
138 :- multifile
|
Chris@0
|
139 html_write:html_head_expansion/2.
|
Chris@0
|
140
|
Chris@0
|
141 html_write:html_head_expansion(In, Out) :-
|
Chris@0
|
142 require_commands(In, Required, Rest),
|
Chris@0
|
143 Required \== [], !,
|
Chris@0
|
144 flatten(Required, Plain),
|
Chris@0
|
145 Out = [ html_head:(\html_insert_resource(Plain))
|
Chris@0
|
146 | Rest
|
Chris@0
|
147 ].
|
Chris@0
|
148
|
Chris@0
|
149 require_commands([], [], []).
|
Chris@0
|
150 require_commands([_:('html required'(Required))|T0], [Required|TR], R) :- !,
|
Chris@0
|
151 require_commands(T0, TR, R).
|
Chris@0
|
152 require_commands([R|T0], TR, [R|T]) :- !,
|
Chris@0
|
153 require_commands(T0, TR, T).
|
Chris@0
|
154
|
Chris@0
|
155
|
Chris@0
|
156 %% html_insert_resource(+ResourceOrList)// is det.
|
Chris@0
|
157 %
|
Chris@0
|
158 % Actually include HTML head resources. Called through
|
Chris@0
|
159 % html_post//2 from html_requires//1 after rewrite by
|
Chris@0
|
160 % html_head_expansion/2. We are guaranteed we will only get one
|
Chris@0
|
161 % call that is passed a flat list of requested requirements. We
|
Chris@0
|
162 % have three jobs:
|
Chris@0
|
163 %
|
Chris@0
|
164 % 1. Figure out all indirect requirements
|
Chris@0
|
165 % 2. See whether we can use any `aggregate' resources
|
Chris@0
|
166 % 3. Put required resources before their requiree.
|
Chris@0
|
167
|
Chris@0
|
168 html_insert_resource(Required) -->
|
Chris@0
|
169 { requirements(Required, Paths),
|
Chris@0
|
170 debug(html(script), 'Requirements: ~q~nFinal: ~q', [Required, Paths])
|
Chris@0
|
171 },
|
Chris@0
|
172 html_include(Paths).
|
Chris@0
|
173
|
Chris@0
|
174 requirements(Required, Paths) :-
|
Chris@0
|
175 phrase(requires(Required), List),
|
Chris@0
|
176 sort(List, Paths0), % remove duplicates
|
Chris@0
|
177 use_agregates(Paths0, Paths1, AggregatedBy),
|
Chris@0
|
178 order_html_resources(Paths1, AggregatedBy, Paths).
|
Chris@0
|
179
|
Chris@0
|
180 %% use_agregates(+Paths, -Aggregated, -AggregatedBy) is det.
|
Chris@0
|
181 %
|
Chris@0
|
182 % Try to replace sets of resources by an `aggregate', a large
|
Chris@0
|
183 % javascript or css file that combines the content of multiple
|
Chris@0
|
184 % small ones to reduce the number of files that must be
|
Chris@0
|
185 % transferred to the server. The current rule says that aggregates
|
Chris@0
|
186 % are used if at least half of the members are used.
|
Chris@0
|
187
|
Chris@0
|
188 use_agregates(Paths, Aggregated, AggregatedBy) :-
|
Chris@0
|
189 empty_assoc(AggregatedBy0),
|
Chris@0
|
190 use_agregates(Paths, Aggregated, AggregatedBy0, AggregatedBy).
|
Chris@0
|
191
|
Chris@0
|
192 use_agregates(Paths, Aggregated, AggregatedBy0, AggregatedBy) :-
|
Chris@0
|
193 aggregate(Aggregate, Parts, Size),
|
Chris@0
|
194 ord_subtract(Paths, Parts, NotCovered),
|
Chris@0
|
195 length(Paths, Len0),
|
Chris@0
|
196 length(NotCovered, Len1),
|
Chris@0
|
197 Covered is Len0-Len1,
|
Chris@0
|
198 Covered >= Size/2, !,
|
Chris@0
|
199 ord_add_element(NotCovered, Aggregate, NewPaths),
|
Chris@0
|
200 add_aggregated_by(Parts, AggregatedBy0, Aggregate, AggregatedBy1),
|
Chris@0
|
201 use_agregates(NewPaths, Aggregated, AggregatedBy1, AggregatedBy).
|
Chris@0
|
202 use_agregates(Paths, Paths, AggregatedBy, AggregatedBy).
|
Chris@0
|
203
|
Chris@0
|
204 add_aggregated_by([], Assoc, _, Assoc).
|
Chris@0
|
205 add_aggregated_by([H|T], Assoc0, V, Assoc) :-
|
Chris@0
|
206 put_assoc(H, Assoc0, V, Assoc1),
|
Chris@0
|
207 add_aggregated_by(T, Assoc1, V, Assoc).
|
Chris@0
|
208
|
Chris@0
|
209
|
Chris@0
|
210 :- dynamic
|
Chris@0
|
211 aggregate_cache_filled/0,
|
Chris@0
|
212 aggregate_cache/3.
|
Chris@0
|
213 :- volatile
|
Chris@0
|
214 aggregate_cache_filled/0,
|
Chris@0
|
215 aggregate_cache/3.
|
Chris@0
|
216
|
Chris@0
|
217 clean_aggregate_cache :-
|
Chris@0
|
218 retractall(aggregate_cache_filled).
|
Chris@0
|
219
|
Chris@0
|
220 %% aggregate(-Aggregate, -Parts, -Size) is nondet.
|
Chris@0
|
221 %
|
Chris@0
|
222 % True if Aggregate is a defined aggregate with Size Parts. All
|
Chris@0
|
223 % parts are canonical absolute HTTP locations and Parts is sorted
|
Chris@0
|
224 % to allow for processing using ordered set predicates.
|
Chris@0
|
225
|
Chris@0
|
226 aggregate(Path, Parts, Size) :-
|
Chris@0
|
227 aggregate_cache_filled, !,
|
Chris@0
|
228 aggregate_cache(Path, Parts, Size).
|
Chris@0
|
229 aggregate(Path, Parts, Size) :-
|
Chris@0
|
230 retractall(aggregate_cache(_,_, _)),
|
Chris@0
|
231 forall(uncached_aggregate(Path, Parts, Size),
|
Chris@0
|
232 assert(aggregate_cache(Path, Parts, Size))),
|
Chris@0
|
233 assert(aggregate_cache_filled),
|
Chris@0
|
234 aggregate_cache(Path, Parts, Size).
|
Chris@0
|
235
|
Chris@0
|
236 uncached_aggregate(Path, APartsS, Size) :-
|
Chris@0
|
237 html_resource(Aggregate, _, Properties),
|
Chris@0
|
238 memberchk(aggregate(Parts), Properties),
|
Chris@0
|
239 absolute_http_location(Aggregate, Path),
|
Chris@0
|
240 absolute_paths(Parts, Path, AParts),
|
Chris@0
|
241 sort(AParts, APartsS),
|
Chris@0
|
242 length(APartsS, Size).
|
Chris@0
|
243
|
Chris@0
|
244 absolute_paths([], _, []).
|
Chris@0
|
245 absolute_paths([H0|T0], Base, [H|T]) :-
|
Chris@0
|
246 absolute_http_location(H0, Base, H),
|
Chris@0
|
247 absolute_paths(T0, Base, T).
|
Chris@0
|
248
|
Chris@0
|
249
|
Chris@0
|
250 %% requires(+Spec)// is det.
|
Chris@0
|
251 %% requires(+Spec, +Base)// is det.
|
Chris@0
|
252 %
|
Chris@0
|
253 % True if Files is the set of files that need to be loaded for
|
Chris@0
|
254 % Spec. Note that Spec normally appears in Files, but this is not
|
Chris@0
|
255 % necessary (i.e. virtual resources or the usage of aggregate
|
Chris@0
|
256 % resources).
|
Chris@0
|
257
|
Chris@0
|
258 requires(Spec) -->
|
Chris@0
|
259 requires(Spec, /).
|
Chris@0
|
260
|
Chris@0
|
261 requires([], _) --> !,
|
Chris@0
|
262 [].
|
Chris@0
|
263 requires([H|T], Base) --> !,
|
Chris@0
|
264 requires(H, Base),
|
Chris@0
|
265 requires(T, Base).
|
Chris@0
|
266 requires(Spec, Base) -->
|
Chris@0
|
267 requires(Spec, Base, true).
|
Chris@0
|
268
|
Chris@0
|
269 requires(Spec, Base, Virtual) -->
|
Chris@0
|
270 { res_properties(Spec, Properties),
|
Chris@0
|
271 absolute_http_location(Spec, Base, File)
|
Chris@0
|
272 },
|
Chris@0
|
273 ( { option(virtual(true), Properties)
|
Chris@0
|
274 ; Virtual == false
|
Chris@0
|
275 }
|
Chris@0
|
276 -> []
|
Chris@0
|
277 ; [File]
|
Chris@0
|
278 ),
|
Chris@0
|
279 requires_from_properties(Properties, File).
|
Chris@0
|
280
|
Chris@0
|
281
|
Chris@0
|
282 requires_from_properties([], _) -->
|
Chris@0
|
283 [].
|
Chris@0
|
284 requires_from_properties([H|T], Base) -->
|
Chris@0
|
285 requires_from_property(H, Base),
|
Chris@0
|
286 requires_from_properties(T, Base).
|
Chris@0
|
287
|
Chris@0
|
288 requires_from_property(requires(What), Base) --> !,
|
Chris@0
|
289 requires(What, Base).
|
Chris@0
|
290 requires_from_property(_, _) -->
|
Chris@0
|
291 [].
|
Chris@0
|
292
|
Chris@0
|
293
|
Chris@0
|
294 % % order_html_resources(+Requirements, +AggregatedBy, -Ordered) is det.
|
Chris@0
|
295 %
|
Chris@0
|
296 % Establish a proper order for the collected (sorted and unique)
|
Chris@0
|
297 % list of Requirements.
|
Chris@0
|
298
|
Chris@0
|
299 order_html_resources(Requirements, AggregatedBy, Ordered) :-
|
Chris@0
|
300 requirements_graph(Requirements, AggregatedBy, Graph),
|
Chris@0
|
301 ( top_sort(Graph, Ordered)
|
Chris@0
|
302 -> true
|
Chris@0
|
303 ; connect_graph(Graph, Start, Connected),
|
Chris@0
|
304 top_sort(Connected, Ordered0),
|
Chris@0
|
305 Ordered0 = [Start|Ordered]
|
Chris@0
|
306 ).
|
Chris@0
|
307
|
Chris@0
|
308 %% requirements_graph(+Requirements, +AggregatedBy, -Graph) is det.
|
Chris@0
|
309 %
|
Chris@0
|
310 % Produce an S-graph (see library(ugraphs)) that represents the
|
Chris@0
|
311 % dependencies in the list of Requirements. Edges run from
|
Chris@0
|
312 % required to requirer.
|
Chris@0
|
313
|
Chris@0
|
314 requirements_graph(Requirements, AggregatedBy, Graph) :-
|
Chris@0
|
315 phrase(prerequisites(Requirements, AggregatedBy, Vertices, []), Edges),
|
Chris@0
|
316 vertices_edges_to_ugraph(Vertices, Edges, Graph).
|
Chris@0
|
317
|
Chris@0
|
318 prerequisites([], _, Vs, Vs) -->
|
Chris@0
|
319 [].
|
Chris@0
|
320 prerequisites([R|T], AggregatedBy, Vs, Vt) -->
|
Chris@0
|
321 prerequisites_for(R, AggregatedBy, Vs, Vt0),
|
Chris@0
|
322 prerequisites(T, AggregatedBy, Vt0, Vt).
|
Chris@0
|
323
|
Chris@0
|
324 prerequisites_for(R, AggregatedBy, Vs, Vt) -->
|
Chris@0
|
325 { phrase(requires(R, /, false), Req) },
|
Chris@0
|
326 ( {Req == []}
|
Chris@0
|
327 -> {Vs = [R|Vt]}
|
Chris@0
|
328 ; req_edges(Req, AggregatedBy, R),
|
Chris@0
|
329 {Vs = Vt}
|
Chris@0
|
330 ).
|
Chris@0
|
331
|
Chris@0
|
332 req_edges([], _, _) -->
|
Chris@0
|
333 [].
|
Chris@0
|
334 req_edges([H|T], AggregatedBy, R) -->
|
Chris@0
|
335 ( { get_assoc(H, AggregatedBy, Aggregate) }
|
Chris@0
|
336 -> [Aggregate-R]
|
Chris@0
|
337 ; [H-R]
|
Chris@0
|
338 ),
|
Chris@0
|
339 req_edges(T, AggregatedBy, R).
|
Chris@0
|
340
|
Chris@0
|
341
|
Chris@0
|
342 %% connect_graph(+Graph, -Connected) is det.
|
Chris@0
|
343 %
|
Chris@0
|
344 % Turn Graph into a connected graph by putting a shared starting
|
Chris@0
|
345 % point before all vertices.
|
Chris@0
|
346
|
Chris@0
|
347 connect_graph([], 0, []) :- !.
|
Chris@0
|
348 connect_graph(Graph, Start, [Start-Vertices|Graph]) :-
|
Chris@0
|
349 vertices(Graph, Vertices),
|
Chris@0
|
350 Vertices = [First|_],
|
Chris@0
|
351 before(First, Start).
|
Chris@0
|
352
|
Chris@0
|
353 %% before(+Term, -Before) is det.
|
Chris@0
|
354 %
|
Chris@0
|
355 % Unify Before to a term that comes before Term in the standard
|
Chris@0
|
356 % order of terms.
|
Chris@0
|
357 %
|
Chris@0
|
358 % @error instantiation_error if Term is unbound.
|
Chris@0
|
359
|
Chris@0
|
360 before(X, _) :-
|
Chris@0
|
361 var(X), !,
|
Chris@0
|
362 instantiation_error(X).
|
Chris@0
|
363 before(Number, Start) :-
|
Chris@0
|
364 number(Number), !,
|
Chris@0
|
365 Start is Number - 1.
|
Chris@0
|
366 before(_, 0).
|
Chris@0
|
367
|
Chris@0
|
368
|
Chris@0
|
369 %% res_properties(+Spec, -Properties) is det.
|
Chris@0
|
370 %
|
Chris@0
|
371 % True if Properties is the set of defined properties on Spec.
|
Chris@0
|
372
|
Chris@0
|
373 res_properties(Spec, Properties) :-
|
Chris@0
|
374 findall(P, res_property(Spec, P), Properties0),
|
Chris@0
|
375 list_to_set(Properties0, Properties).
|
Chris@0
|
376
|
Chris@0
|
377 res_property(Spec, Property) :-
|
Chris@0
|
378 same_about(Spec, About),
|
Chris@0
|
379 html_resource(About, _, Properties),
|
Chris@0
|
380 member(Property, Properties).
|
Chris@0
|
381
|
Chris@0
|
382 :- dynamic
|
Chris@0
|
383 same_about_cache/2.
|
Chris@0
|
384 :- volatile
|
Chris@0
|
385 same_about_cache/2.
|
Chris@0
|
386
|
Chris@0
|
387 clean_same_about_cache :-
|
Chris@0
|
388 retractall(same_about_cache(_,_)).
|
Chris@0
|
389
|
Chris@0
|
390 same_about(Spec, About) :-
|
Chris@0
|
391 same_about_cache(Spec, Same), !,
|
Chris@0
|
392 member(About, Same).
|
Chris@0
|
393 same_about(Spec, About) :-
|
Chris@0
|
394 findall(A, uncached_same_about(Spec, A), List),
|
Chris@0
|
395 assert(same_about_cache(Spec, List)),
|
Chris@0
|
396 member(About, List).
|
Chris@0
|
397
|
Chris@0
|
398 uncached_same_about(Spec, About) :-
|
Chris@0
|
399 html_resource(About, _, _),
|
Chris@0
|
400 same_resource(Spec, About).
|
Chris@0
|
401
|
Chris@0
|
402
|
Chris@0
|
403 %% same_resource(+R1, +R2) is semidet.
|
Chris@0
|
404 %
|
Chris@0
|
405 % True if R1 an R2 represent the same resource. R1 and R2 are
|
Chris@0
|
406 % resource specifications are defined by absolute_http_location/2.
|
Chris@0
|
407
|
Chris@0
|
408 same_resource(R, R) :- !.
|
Chris@0
|
409 same_resource(R1, R2) :-
|
Chris@0
|
410 resource_base_name(R1, B),
|
Chris@0
|
411 resource_base_name(R2, B),
|
Chris@0
|
412 absolute_http_location(R1, Path),
|
Chris@0
|
413 absolute_http_location(R2, Path).
|
Chris@0
|
414
|
Chris@0
|
415 :- dynamic
|
Chris@0
|
416 base_cache/2.
|
Chris@0
|
417 :- volatile
|
Chris@0
|
418 base_cache/2.
|
Chris@0
|
419
|
Chris@0
|
420 resource_base_name(Spec, Base) :-
|
Chris@0
|
421 ( base_cache(Spec, Base0)
|
Chris@0
|
422 -> Base = Base0
|
Chris@0
|
423 ; uncached_resource_base_name(Spec, Base0),
|
Chris@0
|
424 assert(base_cache(Spec, Base0)),
|
Chris@0
|
425 Base = Base0
|
Chris@0
|
426 ).
|
Chris@0
|
427
|
Chris@0
|
428 uncached_resource_base_name(Atom, Base) :-
|
Chris@0
|
429 atomic(Atom), !,
|
Chris@0
|
430 file_base_name(Atom, Base).
|
Chris@0
|
431 uncached_resource_base_name(Compound, Base) :-
|
Chris@0
|
432 arg(1, Compound, Base0),
|
Chris@0
|
433 file_base_name(Base0, Base).
|
Chris@0
|
434
|
Chris@0
|
435 %% html_include(+PathOrList)// is det.
|
Chris@0
|
436 %
|
Chris@0
|
437 % Include to HTML resources that must be in the HTML <head>
|
Chris@0
|
438 % element. Currently onlu supports =|.js|= and =|.css|= files.
|
Chris@0
|
439 % Extend this to support more header material. Do not use this
|
Chris@0
|
440 % predicate directly. html_requires//1 is the public interface to
|
Chris@0
|
441 % include HTML resources.
|
Chris@0
|
442 %
|
Chris@0
|
443 % @param HTTP location or list of these.
|
Chris@0
|
444
|
Chris@0
|
445 html_include([]) --> !.
|
Chris@0
|
446 html_include([H|T]) --> !,
|
Chris@0
|
447 html_include(H),
|
Chris@0
|
448 html_include(T).
|
Chris@0
|
449 html_include(Path) -->
|
Chris@0
|
450 { file_mime_type(Path, Mime) }, !,
|
Chris@0
|
451 html_include(Mime, Path).
|
Chris@0
|
452
|
Chris@0
|
453 html_include(text/css, Path) --> !,
|
Chris@0
|
454 html(link([ rel(stylesheet),
|
Chris@0
|
455 type('text/css'),
|
Chris@0
|
456 href(Path)
|
Chris@0
|
457 ], [])).
|
Chris@0
|
458 html_include(text/javascript, Path) --> !,
|
Chris@0
|
459 html(script([ type('text/javascript'),
|
Chris@0
|
460 src(Path)
|
Chris@0
|
461 ], [])).
|
Chris@0
|
462 html_include(Mime, Path) -->
|
Chris@0
|
463 { print_message(warning, html_include(dont_know, Mime, Path))
|
Chris@0
|
464 }.
|
Chris@0
|
465
|
Chris@0
|
466
|
Chris@0
|
467
|
Chris@0
|
468 /*******************************
|
Chris@0
|
469 * PATHS *
|
Chris@0
|
470 *******************************/
|
Chris@0
|
471
|
Chris@0
|
472 :- multifile
|
Chris@0
|
473 http:location_path/2.
|
Chris@0
|
474 :- dynamic
|
Chris@0
|
475 http:location_path/2.
|
Chris@0
|
476
|
Chris@0
|
477 %% http_location_path(+Alias, -Expansion) is det.
|
Chris@0
|
478 %
|
Chris@0
|
479 % Expansion is the expanded HTTP location for Alias. As we have no
|
Chris@0
|
480 % condition search, we demand a single expansion for an alias. An
|
Chris@0
|
481 % ambiguous alias results in a printed warning. A lacking alias
|
Chris@0
|
482 % results in an exception.
|
Chris@0
|
483 %
|
Chris@0
|
484 % @error existence_error(http_alias, Alias)
|
Chris@0
|
485
|
Chris@0
|
486 http_location_path(Alias, Path) :-
|
Chris@0
|
487 findall(Path, http:location_path(Alias, Path), Paths0),
|
Chris@0
|
488 sort(Paths0, Paths),
|
Chris@0
|
489 ( Paths = [One]
|
Chris@0
|
490 -> Path = One
|
Chris@0
|
491 ; Paths = [Path|_]
|
Chris@0
|
492 -> print_message(warning, ambiguous_http_location(Alias, Paths))
|
Chris@0
|
493 ; Alias \== prefix
|
Chris@0
|
494 -> existence_error(http_alias, Alias)
|
Chris@0
|
495 ).
|
Chris@0
|
496 http_location_path(prefix, Path) :-
|
Chris@0
|
497 ( setting(http:prefix, Prefix),
|
Chris@0
|
498 Prefix \== ''
|
Chris@0
|
499 -> ( sub_atom(Prefix, 0, _, _, /)
|
Chris@0
|
500 -> Path = Prefix
|
Chris@0
|
501 ; atom_concat(/, Prefix, Path)
|
Chris@0
|
502 )
|
Chris@0
|
503 ; Path = /
|
Chris@0
|
504 ).
|
Chris@0
|
505
|
Chris@0
|
506 %% absolute_http_location(+Spec, -Path) is det.
|
Chris@0
|
507 %% absolute_http_location(+Spec, +Base, -Path) is det.
|
Chris@0
|
508 %
|
Chris@0
|
509 % True if Path is the full HTTP location for Spec. This behaves
|
Chris@0
|
510 % very much like absolute_file_name/2. Path-alias are defined by
|
Chris@0
|
511 % the dynamic multifile predicate http:location_path/2, using the
|
Chris@0
|
512 % same syntax as user:file_search_path/2.
|
Chris@0
|
513
|
Chris@0
|
514 :- dynamic
|
Chris@0
|
515 location_cache/3.
|
Chris@0
|
516 :- volatile
|
Chris@0
|
517 location_cache/3.
|
Chris@0
|
518
|
Chris@0
|
519 absolute_http_location(Spec, Path) :-
|
Chris@0
|
520 absolute_http_location(Spec, /, Path).
|
Chris@0
|
521
|
Chris@0
|
522 absolute_http_location(Spec, Base, Path) :-
|
Chris@0
|
523 location_cache(Spec, Base, Path), !.
|
Chris@0
|
524 absolute_http_location(Spec, Base, Path) :-
|
Chris@0
|
525 uncached_absolute_http_location(Spec, Base, Path),
|
Chris@0
|
526 assert(location_cache(Spec, Base, Path)).
|
Chris@0
|
527
|
Chris@0
|
528 uncached_absolute_http_location(Spec, Base, Path) :-
|
Chris@0
|
529 ( atomic(Spec)
|
Chris@0
|
530 -> relative_to(Base, Spec, Path)
|
Chris@0
|
531 ; Spec =.. [Alias, Sub],
|
Chris@0
|
532 http_location_path(Alias, Parent),
|
Chris@0
|
533 absolute_http_location(Parent, /, ParentLocation),
|
Chris@0
|
534 phrase(sub_list(Sub), List),
|
Chris@0
|
535 concat_atom(List, /, SubAtom),
|
Chris@0
|
536 ( ParentLocation == ''
|
Chris@0
|
537 -> Path = SubAtom
|
Chris@0
|
538 ; sub_atom(ParentLocation, _, _, 0, /)
|
Chris@0
|
539 -> atom_concat(ParentLocation, SubAtom, Path)
|
Chris@0
|
540 ; concat_atom([ParentLocation, SubAtom], /, Path)
|
Chris@0
|
541 )
|
Chris@0
|
542 ).
|
Chris@0
|
543
|
Chris@0
|
544 %% relative_to(+Base, +Path, -AbsPath) is det.
|
Chris@0
|
545 %
|
Chris@0
|
546 % AbsPath is an absolute URL location created from Base and Path.
|
Chris@0
|
547 % The result is cleaned
|
Chris@0
|
548
|
Chris@0
|
549 relative_to(/, Path, Path) :- !.
|
Chris@0
|
550 relative_to(_Base, Path, Path) :-
|
Chris@0
|
551 sub_atom(Path, 0, _, _, /), !.
|
Chris@0
|
552 relative_to(Base, Local, Path) :-
|
Chris@0
|
553 path_segments(Base, BaseSegments),
|
Chris@0
|
554 append(BaseDir, [_], BaseSegments) ->
|
Chris@0
|
555 path_segments(Local, LocalSegments),
|
Chris@0
|
556 append(BaseDir, LocalSegments, Segments0),
|
Chris@0
|
557 clean_segments(Segments0, Segments),
|
Chris@0
|
558 path_segments(Path, Segments).
|
Chris@0
|
559
|
Chris@0
|
560 path_segments(Path, Segments) :-
|
Chris@0
|
561 concat_atom(Segments, /, Path).
|
Chris@0
|
562
|
Chris@0
|
563 %% clean_segments(+SegmentsIn, -SegmentsOut) is det.
|
Chris@0
|
564 %
|
Chris@0
|
565 % Clean a path represented as a segment list, removing empty
|
Chris@0
|
566 % segments and resolving .. based on syntax.
|
Chris@0
|
567
|
Chris@0
|
568 clean_segments([''|T0], [''|T]) :- !,
|
Chris@0
|
569 exclude(empty_segment, T0, T1),
|
Chris@0
|
570 clean_parent_segments(T1, T).
|
Chris@0
|
571 clean_segments(T0, T) :-
|
Chris@0
|
572 exclude(empty_segment, T0, T1),
|
Chris@0
|
573 clean_parent_segments(T1, T).
|
Chris@0
|
574
|
Chris@0
|
575 clean_parent_segments([], []).
|
Chris@0
|
576 clean_parent_segments([..|T0], T) :- !,
|
Chris@0
|
577 clean_parent_segments(T0, T).
|
Chris@0
|
578 clean_parent_segments([_,..|T0], T) :- !,
|
Chris@0
|
579 clean_parent_segments(T0, T).
|
Chris@0
|
580 clean_parent_segments([H|T0], [H|T]) :-
|
Chris@0
|
581 clean_parent_segments(T0, T).
|
Chris@0
|
582
|
Chris@0
|
583 empty_segment('').
|
Chris@0
|
584 empty_segment('.').
|
Chris@0
|
585
|
Chris@0
|
586
|
Chris@0
|
587 %% sub_list(+Spec, -List) is det.
|
Chris@0
|
588
|
Chris@0
|
589 sub_list(Var) -->
|
Chris@0
|
590 { var(Var), !,
|
Chris@0
|
591 instantiation_error(Var)
|
Chris@0
|
592 }.
|
Chris@0
|
593 sub_list(A/B) --> !,
|
Chris@0
|
594 sub_list(A),
|
Chris@0
|
595 sub_list(B).
|
Chris@0
|
596 sub_list(A) -->
|
Chris@0
|
597 [A].
|
Chris@0
|
598
|
Chris@0
|
599
|
Chris@0
|
600 /*******************************
|
Chris@0
|
601 * CACHE CLEANUP *
|
Chris@0
|
602 *******************************/
|
Chris@0
|
603
|
Chris@0
|
604 clean_location_cache :-
|
Chris@0
|
605 retractall(location_cache(_,_,_)).
|
Chris@0
|
606
|
Chris@0
|
607 :- listen(settings(changed(http:prefix, _, _)),
|
Chris@0
|
608 clean_location_cache).
|
Chris@0
|
609
|
Chris@0
|
610 :- multifile
|
Chris@0
|
611 user:message_hook/3.
|
Chris@0
|
612 :- dynamic
|
Chris@0
|
613 user:message_hook/3.
|
Chris@0
|
614
|
Chris@0
|
615 user:message_hook(make(done(Reload)), _Level, _Lines) :-
|
Chris@0
|
616 Reload \== [],
|
Chris@0
|
617 clean_location_cache,
|
Chris@0
|
618 clean_same_about_cache,
|
Chris@0
|
619 clean_aggregate_cache,
|
Chris@0
|
620 fail.
|
Chris@0
|
621
|
Chris@0
|
622
|
Chris@0
|
623 /*******************************
|
Chris@0
|
624 * EDIT *
|
Chris@0
|
625 *******************************/
|
Chris@0
|
626
|
Chris@0
|
627 % Allow edit(Location) to edit the :- html_resource declaration.
|
Chris@0
|
628 :- multifile
|
Chris@0
|
629 prolog_edit:locate/3.
|
Chris@0
|
630
|
Chris@0
|
631 prolog_edit:locate(Path, html_resource(Spec), [file(File), line(Line)]) :-
|
Chris@0
|
632 atom(Path),
|
Chris@0
|
633 html_resource(Spec, File:Line, _Properties),
|
Chris@0
|
634 sub_term(Path, Spec).
|