Skip to content

Commit

Permalink
FIXED: Issue#157: do not try to read the reply data for HTTP return c…
Browse files Browse the repository at this point in the history
…odes

that have no reply: 1xx and 204.
  • Loading branch information
JanWielemaker committed Feb 10, 2023
1 parent 6b77a38 commit 17a093f
Showing 1 changed file with 14 additions and 12 deletions.
26 changes: 14 additions & 12 deletions http_client.pl
Original file line number Diff line number Diff line change
Expand Up @@ -248,6 +248,14 @@

is_meta(on_filename).

http_read_data(_In, Fields, Data, _Options) :-
option(status_code(Code), Fields),
no_content_status(Code),
\+ ( option(content_length(Len), Fields),
Len > 0
),
!,
Data = ''.
http_read_data(In, Fields, Data, Options) :- % Transfer-encoding: chunked
select(transfer_encoding(chunked), Fields, RestFields),
!,
Expand Down Expand Up @@ -293,11 +301,6 @@
; http_convert_data(In, Fields, Data, Options)
),
!.
http_read_data(_In, _Fields, Data, Options) :-
option(method(Method), Options),
no_content_method(Method),
!,
Data = ''.
http_read_data(In, Fields, Data, Options) :-
http_read_data(In, Fields, Data, [to(atom)|Options]).

Expand Down Expand Up @@ -328,17 +331,16 @@
; sub_atom(ContentType, Len, 1, _, ';')
).

%! no_content_method(+Method) is semidet.
%! no_content_status(+Code) is semidet.
%
% The ``OPTIONS`` method has no content type. Some servers do not
% add a ``Content-length: 0`` to the headers, causing the client to
% read up to end-of-file. Unfortunately some servers also do not do
% the HTTPS end-of-file handshake correctly, which results in an SSL
% error on recent SSL versions.
% True when Code is an HTTP status code that carries no content.
%
% @see Issue#157

no_content_method(options).
no_content_status(Code) :-
between(100, 199, Code),
!.
no_content_status(204).

%! http_convert_data(+In, +Fields, -Data, +Options) is semidet.
%
Expand Down

0 comments on commit 17a093f

Please sign in to comment.