Skip to content

Commit

Permalink
httpc: add option to do automatic chunked transfer-encoding
Browse files Browse the repository at this point in the history
This is specially useful when a client doesn't know in advance the
length of the payload (so that it can't set the
Content-Length header).

Example:

-module(httpc_post_stream_test).
-compile(export_all).

prepare_data() ->
    crypto:start(),
    {ok, Fd} = file:open("test_data.dat", [binary, write]),
    ok = file:write(Fd, lists:duplicate(crypto:rand_uniform(8182, 32768), "1")),
    ok = file:close(Fd).

test() ->
    inets:start(),
    ok = prepare_data(),
    {ok, Fd1} = file:open("test_data.dat", [binary, read]),
    BodyFun = fun(Fd) ->
        case file:read(Fd, 512) of
        eof ->
            eof;
        {ok, Data} ->
            {ok, Data, Fd}
        end
    end,
    %% header 'Transfer-Encoding: chunked' is added by httpc
    {ok, {{_,200,_}, _, _}} = httpc:request(post, {"http://localhost:8888",
        [], "text/plain", {chunkify, BodyFun, Fd1}}, [], []),
    ok = file:close(Fd1).
  • Loading branch information
fdmanana authored and bjorng committed Oct 5, 2010
1 parent f9ec3cb commit 2809acd
Showing 1 changed file with 28 additions and 3 deletions.
31 changes: 28 additions & 3 deletions lib/inets/src/http_client/httpc.erl
Expand Up @@ -428,11 +428,20 @@ service_info(Pid) ->

handle_request(Method, Url,
{Scheme, UserInfo, Host, Port, Path, Query},
Headers, ContentType, Body,
Headers0, ContentType, Body0,
HTTPOptions0, Options0, Profile) ->

Started = http_util:timestamp(),
NewHeaders = [{http_util:to_lower(Key), Val} || {Key, Val} <- Headers],
NewHeaders0 = [{http_util:to_lower(Key), Val} || {Key, Val} <- Headers0],

{NewHeaders, Body} = case Body0 of
{chunkify, BodyFun, Acc} ->
NewHeaders1 = lists:keystore("transfer-encoding", 1,
NewHeaders0, {"transfer-encoding", "chunked"}),
{NewHeaders1, {chunkify_fun(BodyFun), Acc}};
_ ->
{NewHeaders0, Body0}
end,

try
begin
Expand All @@ -456,7 +465,7 @@ handle_request(Method, Url,
abs_uri = Url,
userinfo = UserInfo,
stream = Stream,
headers_as_is = headers_as_is(Headers, Options),
headers_as_is = headers_as_is(Headers0, Options),
socket_opts = SocketOpts,
started = Started},
case httpc_manager:request(Request, profile_name(Profile)) of
Expand All @@ -473,6 +482,22 @@ handle_request(Method, Url,
Error
end.

chunkify_fun(BodyFun) ->
fun(eof_body_fun) ->
eof;
(Acc) ->
case BodyFun(Acc) of
eof ->
{ok, <<"0\r\n\r\n">>, eof_body_fun};
{ok, Data, NewAcc} ->
Bin = iolist_to_binary(Data),
Chunk = [hex_size(Bin), "\r\n", Bin, "\r\n"],
{ok, iolist_to_binary(Chunk), NewAcc}
end
end.

hex_size(Bin) ->
hd(io_lib:format("~.16B", [size(Bin)])).

handle_answer(RequestId, false, _) ->
{ok, RequestId};
Expand Down

0 comments on commit 2809acd

Please sign in to comment.