Skip to content

Commit ee3ee3f

Browse files
Jan WielemakerJan Wielemaker
Jan Wielemaker
authored and
Jan Wielemaker
committedDec 19, 2016
Fixed trailing whitespace errors
1 parent 2254ca5 commit ee3ee3f

35 files changed

+123
-123
lines changed
 

‎html_head.pl

+1-1
Original file line numberDiff line numberDiff line change
@@ -578,7 +578,7 @@
578578
html_include(Mime, Path).
579579

580580
html_include(Mime, Path) -->
581-
mime_include(Mime, Path),
581+
mime_include(Mime, Path),
582582
!. % user hook
583583
html_include(text/css, Path) -->
584584
!,

‎html_quasiquotations.pl

+2-2
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@
9191

9292
xml_content(Dict, [Name], [Var]) :-
9393
atom(Name),
94-
memberchk(Name=Var, Dict),
94+
memberchk(Name=Var, Dict),
9595
!.
9696
xml_content(Dict, Content0, Content) :-
9797
maplist(xml_content_element(Dict), Content0, Content).
@@ -105,6 +105,6 @@
105105
xml_content_element(_, Element, Element).
106106

107107
xml_attribute(Dict, Attr=Name, Attr=Var) :-
108-
memberchk(Name=Var, Dict),
108+
memberchk(Name=Var, Dict),
109109
!.
110110
xml_attribute(_, Attr, Attr).

‎html_write.pl

+17-17
Original file line numberDiff line numberDiff line change
@@ -323,13 +323,13 @@
323323
{ strip_module(Head, M, _),
324324
hook_module(M, HM, head//2)
325325
},
326-
HM:head(Style, Head),
326+
HM:head(Style, Head),
327327
!.
328328
pagehead(_, Head) -->
329329
{ strip_module(Head, M, _),
330330
hook_module(M, HM, head//1)
331331
},
332-
HM:head(Head),
332+
HM:head(Head),
333333
!.
334334
pagehead(_, Head) -->
335335
html(head(Head)).
@@ -344,20 +344,20 @@
344344
{ strip_module(Body, M, _),
345345
hook_module(M, HM, body//2)
346346
},
347-
HM:body(Style, Body),
347+
HM:body(Style, Body),
348348
!.
349349
pagebody(_, Body) -->
350350
{ strip_module(Body, M, _),
351351
hook_module(M, HM, body//1)
352352
},
353-
HM:body(Body),
353+
HM:body(Body),
354354
!.
355355
pagebody(_, Body) -->
356356
html(body(Body)).
357357

358358

359359
hook_module(M, M, PI) :-
360-
current_predicate(M:PI),
360+
current_predicate(M:PI),
361361
!.
362362
hook_module(_, user, PI) :-
363363
current_predicate(user:PI).
@@ -392,14 +392,14 @@
392392
instantiation_error(Var)
393393
}.
394394
html_expand(Term, Module) -->
395-
do_expand(Term, Module),
395+
do_expand(Term, Module),
396396
!.
397397
html_expand(Term, _Module) -->
398398
{ print_message(error, html(expand_failed(Term))) }.
399399

400400

401401
do_expand(Token, _) --> % call user hooks
402-
expand(Token),
402+
expand(Token),
403403
!.
404404
do_expand(Fmt-Args, _) -->
405405
!,
@@ -744,7 +744,7 @@
744744
{ uri_encoded(query_value, Value, Encoded) },
745745
[ Encoded ].
746746
attribute_value_s(Value) -->
747-
expand_attribute_value(Value),
747+
expand_attribute_value(Value),
748748
!.
749749
attribute_value_s(Fmt-Args) -->
750750
!,
@@ -1469,7 +1469,7 @@
14691469

14701470
% TBD: Check with do_expand!
14711471
html_colours(Var, classify) :-
1472-
var(Var),
1472+
var(Var),
14731473
!.
14741474
html_colours(\List, built_in-[built_in-Colours]) :-
14751475
is_list(List),
@@ -1505,7 +1505,7 @@
15051505
html_colours(_, classify).
15061506

15071507
list_colours(Var, classify) :-
1508-
var(Var),
1508+
var(Var),
15091509
!.
15101510
list_colours([], []).
15111511
list_colours([H0|T0], [H|T]) :-
@@ -1516,7 +1516,7 @@
15161516
html_colours(Last, Colours).
15171517

15181518
attr_colours(Var, classify) :-
1519-
var(Var),
1519+
var(Var),
15201520
!.
15211521
attr_colours([], classify) :- !.
15221522
attr_colours(Term, list-Elements) :-
@@ -1538,16 +1538,16 @@
15381538
Term =.. [Name,Value],
15391539
attr_value_colour(Value, VColour).
15401540
attr_colours(Name, html_attribute(Name)) :-
1541-
atom(Name),
1541+
atom(Name),
15421542
!.
15431543
attr_colours(Term, classify) :-
15441544
compound(Term),
1545-
compound_name_arity(Term, '.', 2),
1545+
compound_name_arity(Term, '.', 2),
15461546
!.
15471547
attr_colours(_, error).
15481548

15491549
attr_list_colours(Var, classify) :-
1550-
var(Var),
1550+
var(Var),
15511551
!.
15521552
attr_list_colours([], []).
15531553
attr_list_colours([H0|T0], [H|T]) :-
@@ -1565,18 +1565,18 @@
15651565
attr_value_colour(B, CB).
15661566
attr_value_colour(encode(_), sgml_attr_function-[classify]) :- !.
15671567
attr_value_colour(Atom, classify) :-
1568-
atomic(Atom),
1568+
atomic(Atom),
15691569
!.
15701570
attr_value_colour([_|_], classify) :- !.
15711571
attr_value_colour(_Fmt-_Args, classify) :- !.
15721572
attr_value_colour(Term, classify) :-
15731573
compound(Term),
1574-
compound_name_arity(Term, '.', 2),
1574+
compound_name_arity(Term, '.', 2),
15751575
!.
15761576
attr_value_colour(_, error).
15771577

15781578
location_id(ID, classify) :-
1579-
var(ID),
1579+
var(ID),
15801580
!.
15811581
location_id(ID, Class) :-
15821582
( catch(http_dispatch:http_location_by_id(ID, Location), _, fail)

‎http_authenticate.pl

+2-2
Original file line numberDiff line numberDiff line change
@@ -157,7 +157,7 @@
157157
cached_authenticated(Authorization, File, User, Fields) :-
158158
authenticated(Authorization, File, User, Time, Fields),
159159
get_time(Now),
160-
Now-Time =< 60,
160+
Now-Time =< 60,
161161
!. % 60-second timeout
162162
cached_authenticated(_, _, _, _) :-
163163
get_time(Now),
@@ -216,7 +216,7 @@
216216
).
217217

218218
reload_passwd_file(Path, Stamp) :-
219-
last_modified(Path, Stamp),
219+
last_modified(Path, Stamp),
220220
!. % another thread did the work
221221
reload_passwd_file(Path, Stamp) :-
222222
http_read_passwd_file(Path, Data),

‎http_client.pl

+2-2
Original file line numberDiff line numberDiff line change
@@ -282,7 +282,7 @@
282282
-> delete(Fields, content_type(_), Fields1),
283283
http_convert_data(In, [content_type(Type)|Fields1], Data, Options1)
284284
; http_convert_data(In, Fields, Data, Options)
285-
),
285+
),
286286
!.
287287
http_read_data(In, Fields, Data, Options) :-
288288
http_read_data(In, Fields, Data, [to(atom)|Options]).
@@ -300,7 +300,7 @@
300300
( sub_atom(Type, _, _, _, 'UTF-8')
301301
-> true
302302
; sub_atom(Type, _, _, _, 'utf-8')
303-
),
303+
),
304304
!.
305305
encoding(_, octet).
306306

‎http_cors.pl

+1-1
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@
9595
% request that typically serve JSON or XML).
9696

9797
cors_enable :-
98-
cors_enable_domain,
98+
cors_enable_domain,
9999
!.
100100
cors_enable. % CORS not enabled
101101

‎http_digest.pl

+7-7
Original file line numberDiff line numberDiff line change
@@ -183,7 +183,7 @@
183183
nonce_gc_time(Last),
184184
get_time(Now),
185185
setting(nonce_timeout, TimeOut),
186-
Now-Last < TimeOut/4,
186+
Now-Last < TimeOut/4,
187187
!.
188188
gc_nonce :-
189189
with_mutex(http_digest_gc_nonce,
@@ -231,14 +231,14 @@
231231
% Return our private key.
232232

233233
private_key(PrivateKey) :-
234-
nonce_key(PrivateKey),
234+
nonce_key(PrivateKey),
235235
!.
236236
private_key(PrivateKey) :-
237237
with_mutex(http_digest,
238238
private_key_sync(PrivateKey)).
239239

240240
private_key_sync(PrivateKey) :-
241-
nonce_key(PrivateKey),
241+
nonce_key(PrivateKey),
242242
!.
243243
private_key_sync(PrivateKey) :-
244244
PrivateKey is random(1<<63-1),
@@ -659,7 +659,7 @@
659659
).
660660

661661
add_option(Option, Options0, _) :-
662-
option(Option, Options0),
662+
option(Option, Options0),
663663
!.
664664
add_option(Option, Options0, [Option|Options0]).
665665

@@ -746,12 +746,12 @@
746746
digest_credentials(Authority, Path, Nonce, Fields) :-
747747
client_nonce(Authority, Domains, Fields, _Created),
748748
in_domain(Path, Domains),
749-
memberchk(nonce(Nonce), Fields),
749+
memberchk(nonce(Nonce), Fields),
750750
!.
751751

752752
in_domain(Path, Domains) :-
753753
member(Domain, Domains),
754-
sub_atom(Path, 0, _, _, Domain),
754+
sub_atom(Path, 0, _, _, Domain),
755755
!.
756756

757757
next_nonce_count(Nonce, NC) :-
@@ -793,7 +793,7 @@
793793
client_nonce_gc_time(Last),
794794
get_time(Now),
795795
setting(client_nonce_timeout, TimeOut),
796-
Now-Last < TimeOut/4,
796+
Now-Last < TimeOut/4,
797797
!.
798798
gc_client_nonce :-
799799
get_time(Now),

‎http_dirindex.pl

+1-1
Original file line numberDiff line numberDiff line change
@@ -237,7 +237,7 @@
237237
% file_mime_type/2.
238238

239239
mime_type_icon(Ext, Icon) :-
240-
http:mime_type_icon(Ext, Icon),
240+
http:mime_type_icon(Ext, Icon),
241241
!.
242242
mime_type_icon(_, 'generic.png').
243243

‎http_dispatch.pl

+8-8
Original file line numberDiff line numberDiff line change
@@ -254,7 +254,7 @@
254254
assert(generation(1)).
255255

256256
current_generation(G) :-
257-
with_mutex(http_dispatch, generation(G)),
257+
with_mutex(http_dispatch, generation(G)),
258258
!.
259259
current_generation(0).
260260

@@ -366,7 +366,7 @@
366366
type_error(path_or_alias, PathSpec).
367367

368368
to_atom(Atom, Atom) :-
369-
atom(Atom),
369+
atom(Atom),
370370
!.
371371
to_atom(Path, Atom) :-
372372
phrase(path_to_list(Path), Components),
@@ -516,7 +516,7 @@
516516
functor(C, PN, _),
517517
( ID = M:PN
518518
; ID = PN
519-
),
519+
),
520520
!.
521521

522522

@@ -693,7 +693,7 @@
693693
memberchk(Method, Methods)
694694
)
695695
; true
696-
),
696+
),
697697
!.
698698
supports_method(Request, _Options) :-
699699
memberchk(path(Location), Request),
@@ -767,7 +767,7 @@
767767
).
768768

769769
extend(Var, _, Var) :-
770-
var(Var),
770+
var(Var),
771771
!.
772772
extend(M:G0, Extra, M:G) :-
773773
extend(G0, Extra, G).
@@ -868,7 +868,7 @@
868868
!,
869869
instantiation_error(File).
870870
http_safe_file(_, Options) :-
871-
option(unsafe(true), Options, false),
871+
option(unsafe(true), Options, false),
872872
!.
873873
http_safe_file(File, _) :-
874874
http_safe_file(File).
@@ -889,7 +889,7 @@
889889
safe_name(Name, _) :-
890890
must_be(atom, Name),
891891
prolog_to_os_filename(FileName, Name),
892-
\+ unsafe_name(FileName),
892+
\+ unsafe_name(FileName),
893893
!.
894894
safe_name(_, Spec) :-
895895
permission_error(read, file, Spec).
@@ -1012,7 +1012,7 @@
10121012

10131013
path_tree(Tree) :-
10141014
current_generation(G),
1015-
nb_current(http_dispatch_tree, G-Tree),
1015+
nb_current(http_dispatch_tree, G-Tree),
10161016
!. % Avoid existence error
10171017
path_tree(Tree) :-
10181018
path_tree_nocache(Tree),

‎http_error.pl

+2-2
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@
7575
saved_request/2.
7676

7777
http_listen(_) :-
78-
\+ debugging(http(error)),
78+
\+ debugging(http(error)),
7979
!.
8080
http_listen(request_start(Id, Request)) :-
8181
!,
@@ -92,7 +92,7 @@
9292
'~w ~w: [~w] ~w', [UMethod, Path, Code, Reply]).
9393

9494
reply_status(Status, Reply) :-
95-
map_exception(Status, Reply),
95+
map_exception(Status, Reply),
9696
!.
9797
reply_status(Status, Message) :-
9898
message_to_string(Status, Message).

‎http_exception.pl

+4-4
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@
111111
resource_error(E),
112112
[connection(close)],
113113
[]) :-
114-
resource_error(E),
114+
resource_error(E),
115115
!.
116116
map_exception_to_http_status(E,
117117
bad_request(E2),
@@ -134,7 +134,7 @@
134134
-> true
135135
; Context = context(_Stack, ContextInstance)
136136
-> subsumes_term(ContextGeneral, ContextInstance)
137-
),
137+
),
138138
!.
139139

140140
bad_request_error(Error, Context) :-
@@ -159,10 +159,10 @@
159159

160160
in_or_exclude_backtrace(Error, Error) :-
161161
current_setting(http:client_backtrace),
162-
setting(http:client_backtrace, true),
162+
setting(http:client_backtrace, true),
163163
!.
164164
in_or_exclude_backtrace(Error0, Error) :-
165-
discard_stack_trace(Error0, Error),
165+
discard_stack_trace(Error0, Error),
166166
!.
167167
in_or_exclude_backtrace(Exception, Exception).
168168

0 commit comments

Comments
 (0)
Please sign in to comment.