Skip to content

Commit d759e00

Browse files
committed
FIXED: Handle HTML error replies that contain non-ASCII.
HTML error replies are now sent using UTF-8 encoding. This patch also includes more careful computation of the length of replies, resulting in exceptions rather than claiming the wrong length on invalid input.
1 parent dd446aa commit d759e00

File tree

1 file changed

+40
-41
lines changed

1 file changed

+40
-41
lines changed

http_header.pl

+40-41
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
Author: Jan Wielemaker
44
55
WWW: http://www.swi-prolog.org
6-
Copyright (c) 2002-2024, University of Amsterdam
6+
Copyright (c) 2002-2025, University of Amsterdam
77
VU University Amsterdam
88
SWI-Prolog Solutions b.v.
99
All rights reserved.
@@ -265,7 +265,8 @@
265265
:- endif.
266266

267267
:- meta_predicate
268-
if_no_head(0, +).
268+
if_no_head(0, +),
269+
with_encoding(+, +, 0).
269270

270271
%! http_reply_data(+Data, +Out, +HdrExtra, +Method, -Code) is semidet.
271272
%
@@ -282,7 +283,7 @@
282283
!,
283284
phrase(reply_header(html(HTML), HdrExtra, Code), Header),
284285
send_reply_header(Out, Header),
285-
if_no_head(print_html(Out, HTML), Method).
286+
if_no_head(with_encoding(Out, utf8, print_html(Out, HTML)), Method).
286287
http_reply_data_(file(Type, File), Out, HdrExtra, Method, Code) :-
287288
!,
288289
phrase(reply_header(file(Type, File), HdrExtra, Code), Header),
@@ -322,6 +323,16 @@
322323
if_no_head(Goal, _) :-
323324
call(Goal).
324325

326+
with_encoding(Out, Encoding, Goal) :-
327+
stream_property(Out, encoding(Old)),
328+
( Old == Encoding
329+
-> call(Goal)
330+
; setup_call_cleanup(
331+
set_stream(Out, encoding(Encoding)),
332+
call(Goal),
333+
set_stream(Out, encoding(Old)))
334+
).
335+
325336
reply_file(Out, _File, Header, head) :-
326337
!,
327338
send_reply_header(Out, Header).
@@ -1327,8 +1338,8 @@
13271338
vstatus(ok, Code, HdrExtra),
13281339
date(now),
13291340
header_fields(HdrExtra, CLen),
1330-
content_length(html(Tokens), CLen),
1331-
content_type(text/html),
1341+
content_length(html(Tokens, utf8), CLen),
1342+
content_type(text/html, utf8),
13321343
"\r\n".
13331344
reply_header(file(Type, File), HdrExtra, Code) -->
13341345
vstatus(ok, Code, HdrExtra),
@@ -1668,50 +1679,38 @@
16681679
"Content-Length: ", integer(Len),
16691680
"\r\n".
16701681

1682+
:- meta_predicate
1683+
print_length(0, -, +, -).
16711684

1672-
length_of(_, Len) :-
1673-
nonvar(Len),
1674-
!.
1675-
length_of(string(String, Encoding), Len) :-
1685+
:- det(length_of/2).
1686+
length_of(_, Len), integer(Len) => true.
1687+
length_of(string(String, Encoding), Len) =>
16761688
length_of(codes(String, Encoding), Len).
1677-
length_of(codes(String, Encoding), Len) :-
1678-
!,
1679-
setup_call_cleanup(
1680-
open_null_stream(Out),
1681-
( set_stream(Out, encoding(Encoding)),
1682-
format(Out, '~s', [String]),
1683-
byte_count(Out, Len)
1684-
),
1685-
close(Out)).
1686-
length_of(atom(Atom, Encoding), Len) :-
1687-
!,
1689+
length_of(codes(String, Encoding), Len) =>
1690+
print_length(format(Out, '~s', [String]), Out, Encoding, Len).
1691+
length_of(atom(Atom, Encoding), Len) =>
1692+
print_length(format(Out, '~a', [Atom]), Out, Encoding, Len).
1693+
length_of(file(File), Len) =>
1694+
size_file(File, Len).
1695+
length_of(memory_file(Handle), Len) =>
1696+
size_memory_file(Handle, Len, octet).
1697+
length_of(html_tokens(Tokens), Len) =>
1698+
html_print_length(Tokens, Len).
1699+
length_of(html(Tokens, Encoding), Len) =>
1700+
print_length(print_html(Out, Tokens), Out, Encoding, Len).
1701+
length_of(bytes(Bytes), Len) =>
1702+
print_length(format(Out, '~s', [Bytes]), Out, octet, Len).
1703+
length_of(Num, Len), integer(Num) =>
1704+
Len = Num.
1705+
1706+
print_length(Goal, Out, Encoding, Len) :-
16881707
setup_call_cleanup(
16891708
open_null_stream(Out),
16901709
( set_stream(Out, encoding(Encoding)),
1691-
format(Out, '~a', [Atom]),
1710+
call(Goal),
16921711
byte_count(Out, Len)
16931712
),
16941713
close(Out)).
1695-
length_of(file(File), Len) :-
1696-
!,
1697-
size_file(File, Len).
1698-
length_of(memory_file(Handle), Len) :-
1699-
!,
1700-
size_memory_file(Handle, Len, octet).
1701-
length_of(html_tokens(Tokens), Len) :-
1702-
!,
1703-
html_print_length(Tokens, Len).
1704-
length_of(html(Tokens), Len) :- % deprecated
1705-
!,
1706-
html_print_length(Tokens, Len).
1707-
length_of(bytes(Bytes), Len) :-
1708-
!,
1709-
( string(Bytes)
1710-
-> string_length(Bytes, Len)
1711-
; length(Bytes, Len) % assuming a list of 0..255
1712-
).
1713-
length_of(Len, Len).
1714-
17151714

17161715
%! content_range(+Unit:atom, +From:int, +RangeEnd:int, +Size:int)// is det
17171716
%

0 commit comments

Comments
 (0)