ibrowse-4.2.2/0000755000232200023220000000000012625271016013541 5ustar debalancedebalanceibrowse-4.2.2/LICENSE0000644000232200023220000000151112625271016014544 0ustar debalancedebalanceibrowse - a HTTP client written in erlang Copyright (C) 2005-2014 Chandrashekhar Mullaparthi This library is free software; you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation; either version 2.1 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with this library; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA ibrowse-4.2.2/rebar.config0000644000232200023220000000030712625271016016023 0ustar debalancedebalance{erl_opts, [debug_info, warnings_as_errors, warn_unused_vars, nowarn_shadow_vars, warn_unused_import]}. {xref_checks, [undefined_function_calls, deprecated_function_calls]}. {eunit_opts, [verbose]}. ibrowse-4.2.2/test/0000755000232200023220000000000012625271016014520 5ustar debalancedebalanceibrowse-4.2.2/test/ibrowse_lib_tests.erl0000644000232200023220000001277612625271016020763 0ustar debalancedebalance%%% File : ibrowse_lib.erl %%% Authors : Chandrashekhar Mullaparthi , %%% Filipe David Manana %%% Description : Tests for the module ibrowse_lib.erl %%% Created : 12 April 2011 by Filipe David Manana -module(ibrowse_lib_tests). -include_lib("eunit/include/eunit.hrl"). -include("../include/ibrowse.hrl"). parse_urls_test_() -> {timeout, 60, [fun parse_urls/0]}. parse_urls() -> ?assertMatch(#url{ abspath = "http://localhost", host = "localhost", host_type = hostname, port = 80, path = "/", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://localhost")), ?assertMatch(#url{ abspath = "http://localhost:80/", host = "localhost", host_type = hostname, port = 80, path = "/", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://localhost:80/")), ?assertMatch(#url{ abspath = "http://127.0.0.1:8000/", host = "127.0.0.1", host_type = ipv4_address, port = 8000, path = "/", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://127.0.0.1:8000/")), ?assertMatch(#url{ abspath = "https://foo:bar@127.0.0.1:8000/test", host = "127.0.0.1", host_type = ipv4_address, port = 8000, path = "/test", username = "foo", password = "bar", protocol = https }, ibrowse_lib:parse_url("https://foo:bar@127.0.0.1:8000/test")), ?assertMatch(#url{ abspath = "https://[::1]", host = "::1", host_type = ipv6_address, port = 443, path = "/", username = undefined, password = undefined, protocol = https }, ibrowse_lib:parse_url("https://[::1]")), ?assertMatch(#url{ abspath = "http://[::1]:8080", host = "::1", host_type = ipv6_address, port = 8080, path = "/", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://[::1]:8080")), ?assertMatch(#url{ abspath = "http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:8081/index.html", host = "FEDC:BA98:7654:3210:FEDC:BA98:7654:3210", host_type = ipv6_address, port = 8081, path = "/index.html", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:8081/index.html")), ?assertMatch(#url{ abspath = "http://[1080:0:0:0:8:800:200C:417A]/foo/bar", host = "1080:0:0:0:8:800:200C:417A", host_type = ipv6_address, port = 80, path = "/foo/bar", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://[1080:0:0:0:8:800:200C:417A]/foo/bar")), ?assertMatch(#url{ abspath = "http://[1080:0:0:0:8:800:200C:417A]:8080/foo/bar", host = "1080:0:0:0:8:800:200C:417A", host_type = ipv6_address, port = 8080, path = "/foo/bar", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://[1080:0:0:0:8:800:200C:417A]:8080/foo/bar")), ?assertMatch(#url{ abspath = "http://[::192.9.5.5]:6000/foo?q=bar", host = "::192.9.5.5", host_type = ipv6_address, port = 6000, path = "/foo?q=bar", username = undefined, password = undefined, protocol = http }, ibrowse_lib:parse_url("http://[::192.9.5.5]:6000/foo?q=bar")), ?assertMatch({error, invalid_uri}, ibrowse_lib:parse_url("http://[:1080:0:0:0:8:800:200C:417A:]:6000/foo?q=bar")), ?assertMatch({error, invalid_uri}, ibrowse_lib:parse_url("http://[12::z]")), ?assertMatch({error, invalid_uri}, ibrowse_lib:parse_url("http://foo[1080:0:0:0:8:800:200C:417A]:6000")), ?assertMatch({error, invalid_uri}, ibrowse_lib:parse_url("http://foo:[1080:0:0:0:8:800:200C:417A]:6000")), ok. ibrowse-4.2.2/test/ibrowse_functional_tests.erl0000644000232200023220000001524112625271016022345 0ustar debalancedebalance%%% File : ibrowse_functional_tests.erl %%% Authors : Benjamin Lee %%% Dan Schwabe %%% Brian Richards %%% Description : Functional tests of the ibrowse library using a live test HTTP server %%% Created : 18 November 2014 by Benjamin Lee -module(ibrowse_functional_tests). -include_lib("eunit/include/eunit.hrl"). -define(PER_TEST_TIMEOUT_SEC, 60). -define(TIMEDTEST(Desc, Fun), {Desc, {timeout, ?PER_TEST_TIMEOUT_SEC, fun Fun/0}}). -define(SERVER_PORT, 8181). -define(BASE_URL, "http://localhost:" ++ integer_to_list(?SERVER_PORT)). -define(SHORT_TIMEOUT_MS, 5000). -define(LONG_TIMEOUT_MS, 30000). -define(PAUSE_FOR_CONNECTIONS_MS, 2000). -compile(export_all). setup() -> application:start(crypto), application:start(public_key), application:start(ssl), ibrowse_test_server:start_server(?SERVER_PORT, tcp), ibrowse:start(), ok. teardown(_) -> ibrowse:stop(), ibrowse_test_server:stop_server(?SERVER_PORT), ok. running_server_fixture_test_() -> {foreach, fun setup/0, fun teardown/1, [ ?TIMEDTEST("Simple request can be honored", simple_request), ?TIMEDTEST("Slow server causes timeout", slow_server_timeout), ?TIMEDTEST("Pipeline depth goes down with responses", pipeline_depth), ?TIMEDTEST("Pipelines refill", pipeline_refill), ?TIMEDTEST("Timeout closes pipe", closing_pipes), ?TIMEDTEST("Requests are balanced over connections", balanced_connections), ?TIMEDTEST("Pipeline too small signals retries", small_pipeline), ?TIMEDTEST("Dest status can be gathered", status) ] }. simple_request() -> ?assertMatch({ok, "200", _, _}, ibrowse:send_req(?BASE_URL, [], get, [], [])). slow_server_timeout() -> ?assertMatch({error, req_timedout}, ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [], 5000)). pipeline_depth() -> MaxSessions = 2, MaxPipeline = 2, RequestsSent = 2, EmptyPipelineDepth = 0, ?assertEqual([], ibrowse_test_server:get_conn_pipeline_depth()), Fun = fun() -> ibrowse:send_req(?BASE_URL, [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS) end, times(RequestsSent, fun() -> spawn_link(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), Counts = [Count || {_Pid, Count} <- ibrowse_test_server:get_conn_pipeline_depth()], ?assertEqual(MaxSessions, length(Counts)), ?assertEqual(lists:duplicate(MaxSessions, EmptyPipelineDepth), Counts). pipeline_refill() -> MaxSessions = 2, MaxPipeline = 2, RequestsToFill = MaxSessions * MaxPipeline, %% Send off enough requests to fill sessions and pipelines in rappid succession Fun = fun() -> ibrowse:send_req(?BASE_URL, [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS) end, times(RequestsToFill, fun() -> spawn_link(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), % Verify that connections properly reported their completed responses and can still accept more ?assertMatch({ok, "200", _, _}, ibrowse:send_req(?BASE_URL, [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS)), % and do it again to make sure we really are clear times(RequestsToFill, fun() -> spawn_link(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), % Verify that connections properly reported their completed responses and can still accept more ?assertMatch({ok, "200", _, _}, ibrowse:send_req(?BASE_URL, [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS)). closing_pipes() -> MaxSessions = 2, MaxPipeline = 2, RequestsSent = 2, BalancedNumberOfRequestsPerConnection = 1, ?assertEqual([], ibrowse_test_server:get_conn_pipeline_depth()), Fun = fun() -> ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS) end, times(RequestsSent, fun() -> spawn_link(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), Counts = [Count || {_Pid, Count} <- ibrowse_test_server:get_conn_pipeline_depth()], ?assertEqual(MaxSessions, length(Counts)), ?assertEqual(lists:duplicate(MaxSessions, BalancedNumberOfRequestsPerConnection), Counts), timer:sleep(?SHORT_TIMEOUT_MS), ?assertEqual([], ibrowse_test_server:get_conn_pipeline_depth()). balanced_connections() -> MaxSessions = 4, MaxPipeline = 100, RequestsSent = 80, BalancedNumberOfRequestsPerConnection = 20, ?assertEqual([], ibrowse_test_server:get_conn_pipeline_depth()), Fun = fun() -> ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?LONG_TIMEOUT_MS) end, times(RequestsSent, fun() -> spawn_link(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), Counts = [Count || {_Pid, Count} <- ibrowse_test_server:get_conn_pipeline_depth()], ?assertEqual(MaxSessions, length(Counts)), ?assertEqual(lists:duplicate(MaxSessions, BalancedNumberOfRequestsPerConnection), Counts). small_pipeline() -> MaxSessions = 10, MaxPipeline = 10, RequestsSent = 100, FullRequestsPerConnection = 10, ?assertEqual([], ibrowse_test_server:get_conn_pipeline_depth()), Fun = fun() -> ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS) end, times(RequestsSent, fun() -> spawn(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), %% Wait for everyone to get in line ibrowse:show_dest_status("localhost", 8181), Counts = [Count || {_Pid, Count} <- ibrowse_test_server:get_conn_pipeline_depth()], ?assertEqual(MaxSessions, length(Counts)), ?assertEqual(lists:duplicate(MaxSessions, FullRequestsPerConnection), Counts), Response = ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS), ?assertEqual({error, retry_later}, Response). status() -> MaxSessions = 10, MaxPipeline = 10, RequestsSent = 100, Fun = fun() -> ibrowse:send_req(?BASE_URL ++ "/never_respond", [], get, [], [{max_sessions, MaxSessions}, {max_pipeline_size, MaxPipeline}], ?SHORT_TIMEOUT_MS) end, times(RequestsSent, fun() -> spawn(Fun) end), timer:sleep(?PAUSE_FOR_CONNECTIONS_MS), %% Wait for everyone to get in line ibrowse:show_dest_status(), ibrowse:show_dest_status("http://localhost:8181"). times(0, _) -> ok; times(X, Fun) -> Fun(), times(X - 1, Fun). ibrowse-4.2.2/test/ibrowse_load_test.erl0000644000232200023220000001663712625271016020751 0ustar debalancedebalance-module(ibrowse_load_test). -compile(export_all). -define(ibrowse_load_test_counters, ibrowse_load_test_counters). start(Num_workers, Num_requests, Max_sess) -> proc_lib:spawn(fun() -> start_1(Num_workers, Num_requests, Max_sess) end). query_state() -> ibrowse_load_test ! query_state. shutdown() -> ibrowse_load_test ! shutdown. start_1(Num_workers, Num_requests, Max_sess) -> register(ibrowse_load_test, self()), application:start(ibrowse), application:set_env(ibrowse, inactivity_timeout, 5000), Ulimit = os:cmd("ulimit -n"), case catch list_to_integer(string:strip(Ulimit, right, $\n)) of X when is_integer(X), X > 3000 -> ok; X -> io:format("Load test not starting. {insufficient_value_for_ulimit, ~p}~n", [X]), exit({insufficient_value_for_ulimit, X}) end, ets:new(?ibrowse_load_test_counters, [named_table, public]), ets:new(ibrowse_load_timings, [named_table, public]), try ets:insert(?ibrowse_load_test_counters, [{success, 0}, {failed, 0}, {timeout, 0}, {retry_later, 0}, {one_request_only, 0} ]), ibrowse:set_max_sessions("localhost", 8081, Max_sess), Start_time = os:timestamp(), Workers = spawn_workers(Num_workers, Num_requests), erlang:send_after(1000, self(), print_diagnostics), ok = wait_for_workers(Workers), End_time = os:timestamp(), Time_in_secs = trunc(round(timer:now_diff(End_time, Start_time) / 1000000)), Req_count = Num_workers * Num_requests, [{_, Success_count}] = ets:lookup(?ibrowse_load_test_counters, success), case Success_count == Req_count of true -> io:format("Test success. All requests succeeded~n", []); false when Success_count > 0 -> io:format("Test failed. Some successes~n", []); false -> io:format("Test failed. ALL requests FAILED~n", []) end, case Time_in_secs > 0 of true -> io:format("Reqs/sec achieved : ~p~n", [trunc(round(Success_count / Time_in_secs))]); false -> ok end, io:format("Load test results:~n~p~n", [ets:tab2list(?ibrowse_load_test_counters)]), io:format("Timings: ~p~n", [calculate_timings()]) catch Err -> io:format("Err: ~p~n", [Err]) after ets:delete(?ibrowse_load_test_counters), ets:delete(ibrowse_load_timings), unregister(ibrowse_load_test) end. calculate_timings() -> {Max, Min, Mean} = get_mmv(ets:first(ibrowse_load_timings), {0, 9999999, 0}), Variance = trunc(round(ets:foldl(fun({_, X}, X_acc) -> (X - Mean)*(X-Mean) + X_acc end, 0, ibrowse_load_timings) / ets:info(ibrowse_load_timings, size))), Std_dev = trunc(round(math:sqrt(Variance))), {ok, [{max, Max}, {min, Min}, {mean, Mean}, {variance, Variance}, {standard_deviation, Std_dev}]}. get_mmv('$end_of_table', {Max, Min, Total}) -> Mean = trunc(round(Total / ets:info(ibrowse_load_timings, size))), {Max, Min, Mean}; get_mmv(Key, {Max, Min, Total}) -> [{_, V}] = ets:lookup(ibrowse_load_timings, Key), get_mmv(ets:next(ibrowse_load_timings, Key), {max(Max, V), min(Min, V), Total + V}). spawn_workers(Num_w, Num_r) -> spawn_workers(Num_w, Num_r, self(), []). spawn_workers(0, _Num_requests, _Parent, Acc) -> lists:reverse(Acc); spawn_workers(Num_workers, Num_requests, Parent, Acc) -> Pid_ref = spawn_monitor(fun() -> random:seed(os:timestamp()), case catch worker_loop(Parent, Num_requests) of {'EXIT', Rsn} -> io:format("Worker crashed with reason: ~p~n", [Rsn]); _ -> ok end end), spawn_workers(Num_workers - 1, Num_requests, Parent, [Pid_ref | Acc]). wait_for_workers([]) -> ok; wait_for_workers([{Pid, Pid_ref} | T] = Pids) -> receive {done, Pid} -> wait_for_workers(T); {done, Some_pid} -> wait_for_workers([{Pid, Pid_ref} | lists:keydelete(Some_pid, 1, T)]); print_diagnostics -> io:format("~1000.p~n", [ibrowse:get_metrics()]), erlang:send_after(1000, self(), print_diagnostics), wait_for_workers(Pids); query_state -> io:format("Waiting for ~p~n", [Pids]), wait_for_workers(Pids); shutdown -> io:format("Shutting down on command. Still waiting for ~p workers~n", [length(Pids)]); {'DOWN', _, process, _, normal} -> wait_for_workers(Pids); {'DOWN', _, process, Down_pid, Rsn} -> io:format("Worker ~p died. Reason: ~p~n", [Down_pid, Rsn]), wait_for_workers(lists:keydelete(Down_pid, 1, Pids)); X -> io:format("Recvd unknown msg: ~p~n", [X]), wait_for_workers(Pids) end. worker_loop(Parent, 0) -> Parent ! {done, self()}; worker_loop(Parent, N) -> Delay = random:uniform(100), Url = case Delay rem 10 of %% Change 10 to some number between 0-9 depending on how %% much chaos you want to introduce into the server %% side. The higher the number, the more often the %% server will close a connection after serving the %% first request, thereby forcing the client to %% retry. Any number of 10 or higher will disable this %% chaos mechanism 10 -> ets:update_counter(?ibrowse_load_test_counters, one_request_only, 1), "http://localhost:8081/ibrowse_handle_one_request_only"; _ -> "http://localhost:8081/blah" end, Start_time = os:timestamp(), Res = ibrowse:send_req(Url, [], get), End_time = os:timestamp(), Time_taken = trunc(round(timer:now_diff(End_time, Start_time) / 1000)), ets:insert(ibrowse_load_timings, {os:timestamp(), Time_taken}), case Res of {ok, "200", _, _} -> ets:update_counter(?ibrowse_load_test_counters, success, 1); {error, req_timedout} -> ets:update_counter(?ibrowse_load_test_counters, timeout, 1); {error, retry_later} -> ets:update_counter(?ibrowse_load_test_counters, retry_later, 1); {error, Reason} -> update_unknown_counter(Reason, 1); _ -> io:format("~p -- Res: ~p~n", [self(), Res]), ets:update_counter(?ibrowse_load_test_counters, failed, 1) end, timer:sleep(Delay), worker_loop(Parent, N - 1). update_unknown_counter(Counter, Inc_val) -> case catch ets:update_counter(?ibrowse_load_test_counters, Counter, Inc_val) of {'EXIT', _} -> ets:insert_new(?ibrowse_load_test_counters, {Counter, 0}), update_unknown_counter(Counter, Inc_val); _ -> ok end. ibrowse-4.2.2/test/ibrowse_test_server.erl0000644000232200023220000002654312625271016021335 0ustar debalancedebalance%%% File : ibrowse_test_server.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : A server to simulate various test scenarios %%% Created : 17 Oct 2010 by Chandrashekhar Mullaparthi -module(ibrowse_test_server). -export([ start_server/2, stop_server/1, get_conn_pipeline_depth/0 ]). -record(request, {method, uri, version, headers = [], body = []}). -define(dec2hex(X), erlang:integer_to_list(X, 16)). -define(ACCEPT_TIMEOUT_MS, 1000). -define(CONN_PIPELINE_DEPTH, conn_pipeline_depth). start_server(Port, Sock_type) -> Fun = fun() -> Proc_name = server_proc_name(Port), case whereis(Proc_name) of undefined -> register(Proc_name, self()), ets:new(?CONN_PIPELINE_DEPTH, [named_table, public, set]), case do_listen(Sock_type, Port, [{active, false}, {reuseaddr, true}, {nodelay, true}, {packet, http}]) of {ok, Sock} -> do_trace("Server listening on port: ~p~n", [Port]), accept_loop(Sock, Sock_type); Err -> erlang:error( lists:flatten( io_lib:format( "Failed to start server on port ~p. ~p~n", [Port, Err]))), exit({listen_error, Err}) end; _X -> ok end end, spawn_link(Fun). stop_server(Port) -> server_proc_name(Port) ! stop, timer:sleep(2000), % wait for server to receive msg and unregister ok. get_conn_pipeline_depth() -> ets:tab2list(?CONN_PIPELINE_DEPTH). server_proc_name(Port) -> list_to_atom("ibrowse_test_server_"++integer_to_list(Port)). do_listen(tcp, Port, Opts) -> gen_tcp:listen(Port, Opts); do_listen(ssl, Port, Opts) -> application:start(crypto), application:start(ssl), ssl:listen(Port, Opts). do_accept(tcp, Listen_sock) -> gen_tcp:accept(Listen_sock, ?ACCEPT_TIMEOUT_MS); do_accept(ssl, Listen_sock) -> ssl:ssl_accept(Listen_sock, ?ACCEPT_TIMEOUT_MS). accept_loop(Sock, Sock_type) -> case do_accept(Sock_type, Sock) of {ok, Conn} -> Pid = spawn_link(fun() -> connection(Conn, Sock_type) end), set_controlling_process(Conn, Sock_type, Pid), Pid ! {setopts, [{active, true}]}, accept_loop(Sock, Sock_type); {error, timeout} -> receive stop -> ok after 10 -> accept_loop(Sock, Sock_type) end; Err -> Err end. connection(Conn, Sock_type) -> catch ets:insert(?CONN_PIPELINE_DEPTH, {self(), 0}), try server_loop(Conn, Sock_type, #request{}) after catch ets:delete(?CONN_PIPELINE_DEPTH, self()) end. set_controlling_process(Sock, tcp, Pid) -> gen_tcp:controlling_process(Sock, Pid); set_controlling_process(Sock, ssl, Pid) -> ssl:controlling_process(Sock, Pid). setopts(Sock, tcp, Opts) -> inet:setopts(Sock, Opts); setopts(Sock, ssl, Opts) -> ssl:setopts(Sock, Opts). server_loop(Sock, Sock_type, #request{headers = Headers} = Req) -> receive {http, Sock, {http_request, HttpMethod, HttpUri, HttpVersion}} -> catch ets:update_counter(?CONN_PIPELINE_DEPTH, self(), 1), server_loop(Sock, Sock_type, Req#request{method = HttpMethod, uri = HttpUri, version = HttpVersion}); {http, Sock, {http_header, _, _, _, _} = H} -> server_loop(Sock, Sock_type, Req#request{headers = [H | Headers]}); {http, Sock, http_eoh} -> case process_request(Sock, Sock_type, Req) of close_connection -> gen_tcp:shutdown(Sock, read_write); not_done -> ok; _ -> catch ets:update_counter(?CONN_PIPELINE_DEPTH, self(), -1) end, server_loop(Sock, Sock_type, #request{}); {http, Sock, {http_error, Err}} -> io:format("Error parsing HTTP request:~n" "Req so far : ~p~n" "Err : ~p", [Req, Err]), exit({http_error, Err}); {setopts, Opts} -> setopts(Sock, Sock_type, Opts), server_loop(Sock, Sock_type, Req); {tcp_closed, Sock} -> do_trace("Client closed connection~n", []), ok; Other -> io:format("Recvd unknown msg: ~p~n", [Other]), exit({unknown_msg, Other}) after 120000 -> do_trace("Timing out client connection~n", []), ok end. do_trace(Fmt, Args) -> do_trace(get(my_trace_flag), Fmt, Args). do_trace(true, Fmt, Args) -> io:format("~s -- " ++ Fmt, [ibrowse_lib:printable_date() | Args]); do_trace(_, _, _) -> ok. process_request(Sock, Sock_type, #request{method='GET', headers = Headers, uri = {abs_path, "/ibrowse_stream_once_chunk_pipeline_test"}} = Req) -> Req_id = case lists:keysearch("X-Ibrowse-Request-Id", 3, Headers) of false -> ""; {value, {http_header, _, _, _, Req_id_1}} -> Req_id_1 end, Req_id_header = ["x-ibrowse-request-id: ", Req_id, "\r\n"], do_trace("Recvd req: ~p~n", [Req]), Body = string:join([integer_to_list(X) || X <- lists:seq(1,100)], "-"), Chunked_body = chunk_request_body(Body, 50), Resp_1 = [<<"HTTP/1.1 200 OK\r\n">>, Req_id_header, <<"Transfer-Encoding: chunked\r\n\r\n">>], Resp_2 = Chunked_body, do_send(Sock, Sock_type, Resp_1), timer:sleep(100), do_send(Sock, Sock_type, Resp_2); process_request(Sock, Sock_type, #request{method='GET', headers = _Headers, uri = {abs_path, "/ibrowse_inac_timeout_test"}} = Req) -> do_trace("Recvd req: ~p. Sleeping for 30 secs...~n", [Req]), timer:sleep(3000), do_trace("...Sending response now.~n", []), Resp = <<"HTTP/1.1 200 OK\r\nContent-Length: 0\r\n\r\n">>, do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='HEAD', headers = _Headers, uri = {abs_path, "/ibrowse_head_transfer_enc"}}) -> Resp = <<"HTTP/1.1 400 Bad Request\r\nServer: Apache-Coyote/1.1\r\nContent-Length:5\r\nDate: Wed, 04 Apr 2012 16:53:49 GMT\r\n\r\nabcde">>, do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='GET', headers = Headers, uri = {abs_path, "/ibrowse_echo_header"}}) -> Tag = "x-binary", Headers_1 = [{to_lower(X), to_lower(Y)} || {http_header, _, X, _, Y} <- Headers], X_binary_header_val = case lists:keysearch(Tag, 1, Headers_1) of false -> "not_found"; {value, {_, V}} -> V end, Resp = [<<"HTTP/1.1 200 OK\r\n">>, <<"Server: ibrowse_test\r\n">>, Tag, ": ", X_binary_header_val, "\r\n", <<"Content-Length: 0\r\n\r\n">>], do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='HEAD', headers = _Headers, uri = {abs_path, "/ibrowse_head_test"}}) -> Resp = <<"HTTP/1.1 200 OK\r\nServer: Apache-Coyote/1.1\r\Date: Wed, 04 Apr 2012 16:53:49 GMT\r\nConnection: close\r\n\r\n">>, do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='POST', headers = _Headers, uri = {abs_path, "/ibrowse_303_no_body_test"}}) -> Resp = <<"HTTP/1.1 303 See Other\r\nLocation: http://example.org\r\n">>, do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='POST', headers = _Headers, uri = {abs_path, "/ibrowse_303_with_body_test"}}) -> Resp = <<"HTTP/1.1 303 See Other\r\nLocation: http://example.org\r\nContent-Length: 5\r\n\r\nabcde">>, do_send(Sock, Sock_type, Resp); process_request(Sock, Sock_type, #request{method='GET', headers = _Headers, uri = {abs_path, "/ibrowse_handle_one_request_only_with_delay"}}) -> timer:sleep(2000), Resp = <<"HTTP/1.1 200 OK\r\nServer: Apache-Coyote/1.1\r\nDate: Wed, 04 Apr 2012 16:53:49 GMT\r\nConnection: close\r\n\r\n">>, do_send(Sock, Sock_type, Resp), close_connection; process_request(Sock, Sock_type, #request{method='GET', headers = _Headers, uri = {abs_path, "/ibrowse_handle_one_request_only"}}) -> Resp = <<"HTTP/1.1 200 OK\r\nServer: Apache-Coyote/1.1\r\nDate: Wed, 04 Apr 2012 16:53:49 GMT\r\nConnection: close\r\n\r\n">>, do_send(Sock, Sock_type, Resp), close_connection; process_request(_Sock, _Sock_type, #request{uri = {abs_path, "/never_respond"} } ) -> not_done; process_request(Sock, Sock_type, Req) -> do_trace("Recvd req: ~p~n", [Req]), Resp = <<"HTTP/1.1 200 OK\r\nContent-Length: 0\r\n\r\n">>, do_send(Sock, Sock_type, Resp), timer:sleep(random:uniform(100)). do_send(Sock, tcp, Resp) -> gen_tcp:send(Sock, Resp); do_send(Sock, ssl, Resp) -> ssl:send(Sock, Resp). %%------------------------------------------------------------------------------ %% Utility functions %%------------------------------------------------------------------------------ chunk_request_body(Body, _ChunkSize) when is_tuple(Body) orelse is_function(Body) -> Body; chunk_request_body(Body, ChunkSize) -> chunk_request_body(Body, ChunkSize, []). chunk_request_body(Body, _ChunkSize, Acc) when Body == <<>>; Body == [] -> LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk | Acc]); chunk_request_body(Body, ChunkSize, Acc) when is_binary(Body), size(Body) >= ChunkSize -> <> = Body, Chunk = [?dec2hex(ChunkSize),"\r\n", ChunkBody, "\r\n"], chunk_request_body(Rest, ChunkSize, [Chunk | Acc]); chunk_request_body(Body, _ChunkSize, Acc) when is_binary(Body) -> BodySize = size(Body), Chunk = [?dec2hex(BodySize),"\r\n", Body, "\r\n"], LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk, Chunk | Acc]); chunk_request_body(Body, ChunkSize, Acc) when length(Body) >= ChunkSize -> {ChunkBody, Rest} = split_list_at(Body, ChunkSize), Chunk = [?dec2hex(ChunkSize),"\r\n", ChunkBody, "\r\n"], chunk_request_body(Rest, ChunkSize, [Chunk | Acc]); chunk_request_body(Body, _ChunkSize, Acc) when is_list(Body) -> BodySize = length(Body), Chunk = [?dec2hex(BodySize),"\r\n", Body, "\r\n"], LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk, Chunk | Acc]). split_list_at(List, N) -> split_list_at(List, N, []). split_list_at([], _, Acc) -> {lists:reverse(Acc), []}; split_list_at(List2, 0, List1) -> {lists:reverse(List1), List2}; split_list_at([H | List2], N, List1) -> split_list_at(List2, N-1, [H | List1]). to_lower(X) when is_atom(X) -> list_to_atom(to_lower(atom_to_list(X))); to_lower(X) when is_list(X) -> string:to_lower(X). ibrowse-4.2.2/test/ibrowse_test.erl0000644000232200023220000007421612625271016017747 0ustar debalancedebalance%%% File : ibrowse_test.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : Test ibrowse %%% Created : 14 Oct 2003 by Chandrashekhar Mullaparthi -module(ibrowse_test). -export([ load_test/3, send_reqs_1/3, do_send_req/2, local_unit_tests/0, unit_tests/0, unit_tests/2, unit_tests_1/3, ue_test/0, ue_test/1, verify_chunked_streaming/0, verify_chunked_streaming/1, test_chunked_streaming_once/0, i_do_async_req_list/4, test_stream_once/3, test_stream_once/4, test_20122010/0, test_20122010/1, test_pipeline_head_timeout/0, test_pipeline_head_timeout/1, do_test_pipeline_head_timeout/4, test_head_transfer_encoding/0, test_head_transfer_encoding/1, test_head_response_with_body/0, test_head_response_with_body/1, test_303_response_with_no_body/0, test_303_response_with_no_body/1, test_303_response_with_a_body/0, test_303_response_with_a_body/1, test_binary_headers/0, test_binary_headers/1, test_generate_body_0/0, test_retry_of_requests/0, test_retry_of_requests/1 ]). -include_lib("ibrowse/include/ibrowse.hrl"). test_stream_once(Url, Method, Options) -> test_stream_once(Url, Method, Options, 5000). test_stream_once(Url, Method, Options, Timeout) -> case ibrowse:send_req(Url, [], Method, [], [{stream_to, {self(), once}} | Options], Timeout) of {ibrowse_req_id, Req_id} -> case ibrowse:stream_next(Req_id) of ok -> test_stream_once(Req_id); Err -> Err end; Err -> Err end. test_stream_once(Req_id) -> receive {ibrowse_async_headers, Req_id, StatCode, Headers} -> io:format("Recvd headers~n~p~n", [{ibrowse_async_headers, Req_id, StatCode, Headers}]), case ibrowse:stream_next(Req_id) of ok -> test_stream_once(Req_id); Err -> Err end; {ibrowse_async_response, Req_id, {error, Err}} -> io:format("Recvd error: ~p~n", [Err]); {ibrowse_async_response, Req_id, Body_1} -> io:format("Recvd body part: ~n~p~n", [{ibrowse_async_response, Req_id, Body_1}]), case ibrowse:stream_next(Req_id) of ok -> test_stream_once(Req_id); Err -> Err end; {ibrowse_async_response_end, Req_id} -> ok end. %% Use ibrowse:set_max_sessions/3 and ibrowse:set_max_pipeline_size/3 to %% tweak settings before running the load test. The defaults are 10 and 10. load_test(Url, NumWorkers, NumReqsPerWorker) when is_list(Url), is_integer(NumWorkers), is_integer(NumReqsPerWorker), NumWorkers > 0, NumReqsPerWorker > 0 -> proc_lib:spawn(?MODULE, send_reqs_1, [Url, NumWorkers, NumReqsPerWorker]). send_reqs_1(Url, NumWorkers, NumReqsPerWorker) -> Start_time = os:timestamp(), ets:new(pid_table, [named_table, public]), ets:new(ibrowse_test_results, [named_table, public]), ets:new(ibrowse_errors, [named_table, public, ordered_set]), ets:new(ibrowse_counter, [named_table, public, ordered_set]), ets:insert(ibrowse_counter, {req_id, 1}), init_results(), process_flag(trap_exit, true), log_msg("Starting spawning of workers...~n", []), spawn_workers(Url, NumWorkers, NumReqsPerWorker), log_msg("Finished spawning workers...~n", []), do_wait(Url), End_time = os:timestamp(), log_msg("All workers are done...~n", []), log_msg("ibrowse_test_results table: ~n~p~n", [ets:tab2list(ibrowse_test_results)]), log_msg("Start time: ~1000.p~n", [calendar:now_to_local_time(Start_time)]), log_msg("End time : ~1000.p~n", [calendar:now_to_local_time(End_time)]), Elapsed_time_secs = trunc(timer:now_diff(End_time, Start_time) / 1000000), log_msg("Elapsed : ~p~n", [Elapsed_time_secs]), log_msg("Reqs/sec : ~p~n", [round(trunc((NumWorkers*NumReqsPerWorker) / Elapsed_time_secs))]), dump_errors(). init_results() -> ets:insert(ibrowse_test_results, {crash, 0}), ets:insert(ibrowse_test_results, {send_failed, 0}), ets:insert(ibrowse_test_results, {other_error, 0}), ets:insert(ibrowse_test_results, {success, 0}), ets:insert(ibrowse_test_results, {retry_later, 0}), ets:insert(ibrowse_test_results, {trid_mismatch, 0}), ets:insert(ibrowse_test_results, {success_no_trid, 0}), ets:insert(ibrowse_test_results, {failed, 0}), ets:insert(ibrowse_test_results, {timeout, 0}), ets:insert(ibrowse_test_results, {req_id, 0}). spawn_workers(_Url, 0, _) -> ok; spawn_workers(Url, NumWorkers, NumReqsPerWorker) -> Pid = proc_lib:spawn_link(?MODULE, do_send_req, [Url, NumReqsPerWorker]), ets:insert(pid_table, {Pid, []}), spawn_workers(Url, NumWorkers - 1, NumReqsPerWorker). do_wait(Url) -> receive {'EXIT', _, normal} -> catch ibrowse:show_dest_status(Url), catch ibrowse:show_dest_status(), do_wait(Url); {'EXIT', Pid, Reason} -> ets:delete(pid_table, Pid), ets:insert(ibrowse_errors, {Pid, Reason}), ets:update_counter(ibrowse_test_results, crash, 1), do_wait(Url); Msg -> io:format("Recvd unknown message...~p~n", [Msg]), do_wait(Url) after 1000 -> case ets:info(pid_table, size) of 0 -> done; _ -> catch ibrowse:show_dest_status(Url), catch ibrowse:show_dest_status(), do_wait(Url) end end. do_send_req(Url, NumReqs) -> do_send_req_1(Url, NumReqs). do_send_req_1(_Url, 0) -> ets:delete(pid_table, self()); do_send_req_1(Url, NumReqs) -> Counter = integer_to_list(ets:update_counter(ibrowse_test_results, req_id, 1)), case ibrowse:send_req(Url, [{"ib_req_id", Counter}], get, [], [], 10000) of {ok, _Status, Headers, _Body} -> case lists:keysearch("ib_req_id", 1, Headers) of {value, {_, Counter}} -> ets:update_counter(ibrowse_test_results, success, 1); {value, _} -> ets:update_counter(ibrowse_test_results, trid_mismatch, 1); false -> ets:update_counter(ibrowse_test_results, success_no_trid, 1) end; {error, req_timedout} -> ets:update_counter(ibrowse_test_results, timeout, 1); {error, send_failed} -> ets:update_counter(ibrowse_test_results, send_failed, 1); {error, retry_later} -> ets:update_counter(ibrowse_test_results, retry_later, 1); Err -> ets:insert(ibrowse_errors, {os:timestamp(), Err}), ets:update_counter(ibrowse_test_results, other_error, 1), ok end, do_send_req_1(Url, NumReqs-1). dump_errors() -> case ets:info(ibrowse_errors, size) of 0 -> ok; _ -> {A, B, C} = os:timestamp(), Filename = lists:flatten( io_lib:format("ibrowse_errors_~p_~p_~p.txt" , [A, B, C])), case file:open(Filename, [write, delayed_write, raw]) of {ok, Iod} -> dump_errors(ets:first(ibrowse_errors), Iod); Err -> io:format("failed to create file ~s. Reason: ~p~n", [Filename, Err]), ok end end. dump_errors('$end_of_table', Iod) -> file:close(Iod); dump_errors(Key, Iod) -> [{_, Term}] = ets:lookup(ibrowse_errors, Key), file:write(Iod, io_lib:format("~p~n", [Term])), dump_errors(ets:next(ibrowse_errors, Key), Iod). %%------------------------------------------------------------------------------ %% Unit Tests %%------------------------------------------------------------------------------ -define(LOCAL_TESTS, [ {local_test_fun, test_20122010, []}, {local_test_fun, test_pipeline_head_timeout, []}, {local_test_fun, test_head_transfer_encoding, []}, {local_test_fun, test_head_response_with_body, []}, {local_test_fun, test_303_response_with_a_body, []}, {local_test_fun, test_binary_headers, []}, {local_test_fun, test_retry_of_requests, []} ]). -define(TEST_LIST, [{"http://intranet/messenger", get}, {"http://www.google.co.uk", get}, {"http://www.google.com", get}, {"http://www.google.com", options}, {"https://mail.google.com", get}, {"http://www.sun.com", get}, {"http://www.oracle.com", get}, {"http://www.bbc.co.uk", get}, {"http://www.bbc.co.uk", trace}, {"http://www.bbc.co.uk", options}, {"http://yaws.hyber.org", get}, {"http://jigsaw.w3.org/HTTP/ChunkedScript", get}, {"http://jigsaw.w3.org/HTTP/TE/foo.txt", get}, {"http://jigsaw.w3.org/HTTP/TE/bar.txt", get}, {"http://jigsaw.w3.org/HTTP/connection.html", get}, {"http://jigsaw.w3.org/HTTP/cc.html", get}, {"http://jigsaw.w3.org/HTTP/cc-private.html", get}, {"http://jigsaw.w3.org/HTTP/cc-proxy-revalidate.html", get}, {"http://jigsaw.w3.org/HTTP/cc-nocache.html", get}, {"http://jigsaw.w3.org/HTTP/h-content-md5.html", get}, {"http://jigsaw.w3.org/HTTP/h-retry-after.html", get}, {"http://jigsaw.w3.org/HTTP/h-retry-after-date.html", get}, {"http://jigsaw.w3.org/HTTP/neg", get}, {"http://jigsaw.w3.org/HTTP/negbad", get}, {"http://jigsaw.w3.org/HTTP/400/toolong/", get}, {"http://jigsaw.w3.org/HTTP/300/", get}, {"http://jigsaw.w3.org/HTTP/Basic/", get, [{basic_auth, {"guest", "guest"}}]}, {"http://jigsaw.w3.org/HTTP/CL/", get}, {"http://www.httpwatch.com/httpgallery/chunked/", get}, {"https://github.com", get, [{ssl_options, [{depth, 2}]}]} ] ++ ?LOCAL_TESTS). local_unit_tests() -> unit_tests([], ?LOCAL_TESTS). unit_tests() -> error_logger:tty(false), unit_tests([], ?TEST_LIST), error_logger:tty(true). unit_tests(Options, Test_list) -> application:start(crypto), application:start(asn1), application:start(public_key), application:start(ssl), (catch ibrowse_test_server:start_server(8181, tcp)), application:start(ibrowse), Options_1 = Options ++ [{connect_timeout, 5000}], Test_timeout = proplists:get_value(test_timeout, Options, 60000), {Pid, Ref} = erlang:spawn_monitor(?MODULE, unit_tests_1, [self(), Options_1, Test_list]), receive {done, Pid} -> ok; {'DOWN', Ref, _, _, Info} -> io:format("Test process crashed: ~p~n", [Info]) after Test_timeout -> exit(Pid, kill), io:format("Timed out waiting for tests to complete~n", []) end, catch ibrowse_test_server:stop_server(8181), ok. unit_tests_1(Parent, Options, Test_list) -> lists:foreach(fun({local_test_fun, Fun_name, Args}) -> execute_req(local_test_fun, Fun_name, Args); ({Url, Method}) -> execute_req(Url, Method, Options); ({Url, Method, X_Opts}) -> execute_req(Url, Method, X_Opts ++ Options) end, Test_list), Parent ! {done, self()}. verify_chunked_streaming() -> verify_chunked_streaming([]). verify_chunked_streaming(Options) -> io:format("~nVerifying that chunked streaming is working...~n", []), Url = "http://www.httpwatch.com/httpgallery/chunked/", io:format(" URL: ~s~n", [Url]), io:format(" Fetching data without streaming...~n", []), Result_without_streaming = ibrowse:send_req( Url, [], get, [], [{response_format, binary} | Options]), io:format(" Fetching data with streaming as list...~n", []), Async_response_list = do_async_req_list( Url, get, [{response_format, list} | Options]), io:format(" Fetching data with streaming as binary...~n", []), Async_response_bin = do_async_req_list( Url, get, [{response_format, binary} | Options]), io:format(" Fetching data with streaming as binary, {active, once}...~n", []), Async_response_bin_once = do_async_req_list( Url, get, [once, {response_format, binary} | Options]), Res1 = compare_responses(Result_without_streaming, Async_response_list, Async_response_bin), Res2 = compare_responses(Result_without_streaming, Async_response_list, Async_response_bin_once), case {Res1, Res2} of {success, success} -> io:format(" Chunked streaming working~n", []); _ -> ok end. test_chunked_streaming_once() -> test_chunked_streaming_once([]). test_chunked_streaming_once(Options) -> io:format("~nTesting chunked streaming with the {stream_to, {Pid, once}} option...~n", []), Url = "http://www.httpwatch.com/httpgallery/chunked/", io:format(" URL: ~s~n", [Url]), io:format(" Fetching data with streaming as binary, {active, once}...~n", []), case do_async_req_list(Url, get, [once, {response_format, binary} | Options]) of {ok, _, _, _} -> io:format(" Success!~n", []); Err -> io:format(" Fail: ~p~n", [Err]) end. compare_responses({ok, St_code, _, Body}, {ok, St_code, _, Body}, {ok, St_code, _, Body}) -> success; compare_responses({ok, St_code, _, Body_1}, {ok, St_code, _, Body_2}, {ok, St_code, _, Body_3}) -> case Body_1 of Body_2 -> io:format("Body_1 and Body_2 match~n", []); Body_3 -> io:format("Body_1 and Body_3 match~n", []); _ when Body_2 == Body_3 -> io:format("Body_2 and Body_3 match~n", []); _ -> io:format("All three bodies are different!~n", []) end, io:format("Body_1 -> ~p~n", [Body_1]), io:format("Body_2 -> ~p~n", [Body_2]), io:format("Body_3 -> ~p~n", [Body_3]), fail_bodies_mismatch; compare_responses(R1, R2, R3) -> io:format("R1 -> ~p~n", [R1]), io:format("R2 -> ~p~n", [R2]), io:format("R3 -> ~p~n", [R3]), fail. %% do_async_req_list(Url) -> %% do_async_req_list(Url, get). %% do_async_req_list(Url, Method) -> %% do_async_req_list(Url, Method, [{stream_to, self()}, %% {stream_chunk_size, 1000}]). do_async_req_list(Url, Method, Options) -> {Pid,_} = erlang:spawn_monitor(?MODULE, i_do_async_req_list, [self(), Url, Method, Options ++ [{stream_chunk_size, 1000}]]), %% io:format("Spawned process ~p~n", [Pid]), wait_for_resp(Pid). wait_for_resp(Pid) -> receive {async_result, Pid, Res} -> Res; {async_result, Other_pid, _} -> io:format("~p: Waiting for result from ~p: got from ~p~n", [self(), Pid, Other_pid]), wait_for_resp(Pid); {'DOWN', _, _, Pid, Reason} -> {'EXIT', Reason}; {'DOWN', _, _, _, _} -> wait_for_resp(Pid); {'EXIT', _, normal} -> wait_for_resp(Pid); Msg -> io:format("Recvd unknown message: ~p~n", [Msg]), wait_for_resp(Pid) after 100000 -> {error, timeout} end. i_do_async_req_list(Parent, Url, Method, Options) -> Options_1 = case lists:member(once, Options) of true -> [{stream_to, {self(), once}} | (Options -- [once])]; false -> [{stream_to, self()} | Options] end, Res = ibrowse:send_req(Url, [], Method, [], Options_1), case Res of {ibrowse_req_id, Req_id} -> Result = wait_for_async_resp(Req_id, Options, undefined, undefined, []), Parent ! {async_result, self(), Result}; Err -> Parent ! {async_result, self(), Err} end. wait_for_async_resp(Req_id, Options, Acc_Stat_code, Acc_Headers, Body) -> receive {ibrowse_async_headers, Req_id, StatCode, Headers} -> %% io:format("Recvd headers...~n", []), maybe_stream_next(Req_id, Options), wait_for_async_resp(Req_id, Options, StatCode, Headers, Body); {ibrowse_async_response_end, Req_id} -> %% io:format("Recvd end of response.~n", []), Body_1 = list_to_binary(lists:reverse(Body)), {ok, Acc_Stat_code, Acc_Headers, Body_1}; {ibrowse_async_response, Req_id, Data} -> maybe_stream_next(Req_id, Options), %% io:format("Recvd data...~n", []), wait_for_async_resp(Req_id, Options, Acc_Stat_code, Acc_Headers, [Data | Body]); {ibrowse_async_response, Req_id, {error, _} = Err} -> {ok, Acc_Stat_code, Acc_Headers, Err}; Err -> {ok, Acc_Stat_code, Acc_Headers, Err} after 10000 -> {timeout, Acc_Stat_code, Acc_Headers, Body} end. maybe_stream_next(Req_id, Options) -> case lists:member(once, Options) of true -> ibrowse:stream_next(Req_id); false -> ok end. execute_req(local_test_fun, Method, Args) -> reset_ibrowse(), io:format(" ~-54.54w: ", [Method]), Result = (catch apply(?MODULE, Method, Args)), io:format("~p~n", [Result]); execute_req(Url, Method, Options) -> io:format("~7.7w, ~50.50s: ", [Method, Url]), Result = (catch ibrowse:send_req(Url, [], Method, [], Options)), case Result of {ok, SCode, _H, _B} -> io:format("Status code: ~p~n", [SCode]); Err -> io:format("~p~n", [Err]) end. ue_test() -> ue_test(lists:duplicate(1024, $?)). ue_test(Data) -> {Time, Res} = timer:tc(ibrowse_lib, url_encode, [Data]), io:format("Time -> ~p~n", [Time]), io:format("Data Length -> ~p~n", [length(Data)]), io:format("Res Length -> ~p~n", [length(Res)]). % io:format("Result -> ~s~n", [Res]). log_msg(Fmt, Args) -> io:format("~s -- " ++ Fmt, [ibrowse_lib:printable_date() | Args]). %%------------------------------------------------------------------------------ %% Test what happens when the response to a HEAD request is a %% Chunked-Encoding response with a non-empty body. Issue #67 on %% Github %% ------------------------------------------------------------------------------ test_head_transfer_encoding() -> clear_msg_q(), test_head_transfer_encoding("http://localhost:8181/ibrowse_head_test"). test_head_transfer_encoding(Url) -> case ibrowse:send_req(Url, [], head) of {ok, "200", _, _} -> success; Res -> {test_failed, Res} end. %%------------------------------------------------------------------------------ %% Test what happens when the response to a HEAD request is a %% Chunked-Encoding response with a non-empty body. Issue #67 on %% Github %% ------------------------------------------------------------------------------ test_binary_headers() -> clear_msg_q(), test_binary_headers("http://localhost:8181/ibrowse_echo_header"). test_binary_headers(Url) -> case ibrowse:send_req(Url, [{<<"x-binary">>, <<"x-header">>}], get) of {ok, "200", Headers, _} -> case proplists:get_value("x-binary", Headers) of "x-header" -> success; V -> {fail, V} end; Res -> {test_failed, Res} end. %%------------------------------------------------------------------------------ %% Test what happens when the response to a HEAD request is a %% Chunked-Encoding response with a non-empty body. Issue #67 on %% Github %% ------------------------------------------------------------------------------ test_head_response_with_body() -> clear_msg_q(), test_head_response_with_body("http://localhost:8181/ibrowse_head_transfer_enc"). test_head_response_with_body(Url) -> case ibrowse:send_req(Url, [], head, [], [{workaround, head_response_with_body}]) of {ok, "400", _, _} -> success; Res -> {test_failed, Res} end. %%------------------------------------------------------------------------------ %% Test what happens when a 303 response has no body %% Github issue #97 %% ------------------------------------------------------------------------------ test_303_response_with_no_body() -> clear_msg_q(), test_303_response_with_no_body("http://localhost:8181/ibrowse_303_no_body_test"). test_303_response_with_no_body(Url) -> ibrowse:add_config([{allow_303_with_no_body, true}]), case ibrowse:send_req(Url, [], post) of {ok, "303", _, _} -> success; Res -> {test_failed, Res} end. %% Make sure we don't break requests that do have a body. test_303_response_with_a_body() -> clear_msg_q(), test_303_response_with_no_body("http://localhost:8181/ibrowse_303_with_body_test"). test_303_response_with_a_body(Url) -> ibrowse:add_config([{allow_303_with_no_body, true}]), case ibrowse:send_req(Url, [], post) of {ok, "303", _, "abcde"} -> success; Res -> {test_failed, Res} end. %%------------------------------------------------------------------------------ %% Test that retry of requests happens correctly, and that ibrowse doesn't retry %% if there is not enough time left %%------------------------------------------------------------------------------ test_retry_of_requests() -> clear_msg_q(), test_retry_of_requests("http://localhost:8181/ibrowse_handle_one_request_only_with_delay"). test_retry_of_requests(Url) -> reset_ibrowse(), Timeout_1 = 2050, Res_1 = test_retry_of_requests(Url, Timeout_1), case lists:filter(fun({_Pid, {ok, "200", _, _}}) -> true; (_) -> false end, Res_1) of [_|_] = X -> Res_1_1 = Res_1 -- X, case lists:all( fun({_Pid, {error, retry_later}}) -> true; (_) -> false end, Res_1_1) of true -> ok; false -> exit({failed, Timeout_1, Res_1}) end; _ -> exit({failed, Timeout_1, Res_1}) end, Timeout_2 = 2200, Res_2 = test_retry_of_requests(Url, Timeout_2), case lists:filter(fun({_Pid, {ok, "200", _, _}}) -> true; (_) -> false end, Res_2) of [_|_] = Res_2_X -> Res_2_1 = Res_2 -- Res_2_X, case lists:all( fun({_Pid, {error, X_err_2}}) -> (X_err_2 == retry_later) orelse (X_err_2 == req_timedout); (_) -> false end, Res_2_1) of true -> ok; false -> exit({failed, {?MODULE, ?LINE}, Timeout_2, Res_2}) end; _ -> exit({failed, {?MODULE, ?LINE}, Timeout_2, Res_2}) end, success. test_retry_of_requests(Url, Timeout) -> #url{host = Host, port = Port} = ibrowse_lib:parse_url(Url), ibrowse:set_max_sessions(Host, Port, 1), Parent = self(), Pids = lists:map(fun(_) -> spawn(fun() -> Res = (catch ibrowse:send_req(Url, [], get, [], [], Timeout)), Parent ! {self(), Res} end) end, lists:seq(1,10)), accumulate_worker_resp(Pids). %%------------------------------------------------------------------------------ %% Test what happens when the request at the head of a pipeline times out %%------------------------------------------------------------------------------ test_pipeline_head_timeout() -> clear_msg_q(), test_pipeline_head_timeout("http://localhost:8181/ibrowse_inac_timeout_test"). test_pipeline_head_timeout(Url) -> {ok, Pid} = ibrowse:spawn_worker_process(Url), Fixed_timeout = 2000, Test_parent = self(), Fun = fun({fixed, Timeout}) -> X_pid = spawn(fun() -> do_test_pipeline_head_timeout(Url, Pid, Test_parent, Timeout) end), %% io:format("Pid ~p with a fixed timeout~n", [X_pid]), X_pid; (Timeout_mult) -> Timeout = Fixed_timeout + Timeout_mult*1000, X_pid = spawn(fun() -> do_test_pipeline_head_timeout(Url, Pid, Test_parent, Timeout) end), %% io:format("Pid ~p with a timeout of ~p~n", [X_pid, Timeout]), X_pid end, Pids = [Fun(X) || X <- [{fixed, Fixed_timeout} | lists:seq(1,10)]], Result = accumulate_worker_resp(Pids), case lists:all(fun({_, X_res}) -> (X_res == {error,req_timedout}) orelse (X_res == {error, connection_closed}) end, Result) of true -> success; false -> {test_failed, Result} end. do_test_pipeline_head_timeout(Url, Pid, Test_parent, Req_timeout) -> Resp = ibrowse:send_req_direct( Pid, Url, [], get, [], [{socket_options,[{keepalive,true}]}, {inactivity_timeout,180000}, {connect_timeout,180000}], Req_timeout), Test_parent ! {self(), Resp}. accumulate_worker_resp(Pids) -> accumulate_worker_resp(Pids, []). accumulate_worker_resp([_ | _] = Pids, Acc) -> receive {Pid, Res} when is_pid(Pid) -> accumulate_worker_resp(Pids -- [Pid], [{Pid, Res} | Acc]); Err -> io:format("Received unexpected: ~p~n", [Err]) end; accumulate_worker_resp([], Acc) -> lists:reverse(Acc). clear_msg_q() -> receive _ -> clear_msg_q() after 0 -> ok end. %%------------------------------------------------------------------------------ %% %%------------------------------------------------------------------------------ test_20122010() -> test_20122010("http://localhost:8181"). test_20122010(Url) -> {ok, Pid} = ibrowse:spawn_worker_process(Url), Expected_resp = <<"1-2-3-4-5-6-7-8-9-10-11-12-13-14-15-16-17-18-19-20-21-22-23-24-25-26-27-28-29-30-31-32-33-34-35-36-37-38-39-40-41-42-43-44-45-46-47-48-49-50-51-52-53-54-55-56-57-58-59-60-61-62-63-64-65-66-67-68-69-70-71-72-73-74-75-76-77-78-79-80-81-82-83-84-85-86-87-88-89-90-91-92-93-94-95-96-97-98-99-100">>, Test_parent = self(), Fun = fun() -> do_test_20122010(Url, Pid, Expected_resp, Test_parent) end, Pids = [erlang:spawn_monitor(Fun) || _ <- lists:seq(1,10)], wait_for_workers(Pids). wait_for_workers([{Pid, _Ref} | Pids]) -> receive {Pid, success} -> wait_for_workers(Pids) after 60000 -> test_failed end; wait_for_workers([]) -> success. do_test_20122010(Url, Pid, Expected_resp, Test_parent) -> do_test_20122010(10, Url, Pid, Expected_resp, Test_parent). do_test_20122010(0, _Url, _Pid, _Expected_resp, Test_parent) -> Test_parent ! {self(), success}; do_test_20122010(Rem_count, Url, Pid, Expected_resp, Test_parent) -> {ibrowse_req_id, Req_id} = ibrowse:send_req_direct( Pid, Url ++ "/ibrowse_stream_once_chunk_pipeline_test", [], get, [], [{stream_to, {self(), once}}, {inactivity_timeout, 10000}, {include_ibrowse_req_id, true}]), do_trace("~p -- sent request ~1000.p~n", [self(), Req_id]), Req_id_str = lists:flatten(io_lib:format("~1000.p",[Req_id])), receive {ibrowse_async_headers, Req_id, "200", Headers} -> case lists:keysearch("x-ibrowse-request-id", 1, Headers) of {value, {_, Req_id_str}} -> ok; {value, {_, Req_id_1}} -> do_trace("~p -- Sent req-id: ~1000.p. Recvd: ~1000.p~n", [self(), Req_id, Req_id_1]), exit(req_id_mismatch) end after 5000 -> do_trace("~p -- response headers not received~n", [self()]), exit({timeout, test_failed}) end, do_trace("~p -- response headers received~n", [self()]), ok = ibrowse:stream_next(Req_id), case do_test_20122010_1(Expected_resp, Req_id, []) of true -> do_test_20122010(Rem_count - 1, Url, Pid, Expected_resp, Test_parent); false -> Test_parent ! {self(), failed} end. do_test_20122010_1(Expected_resp, Req_id, Acc) -> receive {ibrowse_async_response, Req_id, Body_part} -> ok = ibrowse:stream_next(Req_id), do_test_20122010_1(Expected_resp, Req_id, [Body_part | Acc]); {ibrowse_async_response_end, Req_id} -> Acc_1 = list_to_binary(lists:reverse(Acc)), Result = Acc_1 == Expected_resp, do_trace("~p -- End of response. Result: ~p~n", [self(), Result]), Result after 1000 -> exit({timeout, test_failed}) end. %%------------------------------------------------------------------------------ %% Test requests where body is generated using a Fun %%------------------------------------------------------------------------------ test_generate_body_0() -> io:format("Testing that generation of body using fun works...~n", []), Tid = ets:new(ibrowse_test_state, [public]), try Body_1 = <<"Part 1 of the body">>, Body_2 = <<"Part 2 of the body\r\n\r\n">>, Size = size(Body_1) + size(Body_2), Body = list_to_binary([Body_1, Body_2]), Fun = fun() -> case ets:lookup(Tid, body_gen_state) of [] -> ets:insert(Tid, {body_gen_state, 1}), {ok, Body_1}; [{_, 1}]-> ets:insert(Tid, {body_gen_state, 2}), {ok, Body_2}; [{_, 2}] -> eof end end, case ibrowse:send_req("http://localhost:8181/echo_body", [{"Content-Length", Size}], post, Fun, [{response_format, binary}, {http_vsn, {1,0}}]) of {ok, "200", _, Body} -> io:format(" Success~n", []), success; Err -> io:format("Test failed : ~p~n", [Err]), {test_failed, Err} end after ets:delete(Tid) end. do_trace(Fmt, Args) -> do_trace(get(my_trace_flag), Fmt, Args). do_trace(true, Fmt, Args) -> io:format("~s -- " ++ Fmt, [ibrowse_lib:printable_date() | Args]); do_trace(_, _, _) -> ok. reset_ibrowse() -> application:stop(ibrowse), application:start(ibrowse). ibrowse-4.2.2/priv/0000755000232200023220000000000012625271016014521 5ustar debalancedebalanceibrowse-4.2.2/priv/ibrowse.conf0000644000232200023220000000124012625271016017037 0ustar debalancedebalance%% Configuration file for specifying settings for HTTP servers which this %% client will connect to. %% The format of each entry is (one per line) %% {dest, Hostname, Portnumber, MaxSessions, MaxPipelineSize, Options}. %% %% where Hostname = string() %% Portnumber = integer() %% MaxSessions = integer() %% MaxPipelineSize = integer() %% Options = [{Tag, Val} | ...] %% Tag = term() %% Value = term() %% e.g. %% {dest, "covig02", 8000, 10, 10, [{is_ssl, true}, {ssl_options, [option()]}]}. %% If SSL is to be used, both the options, is_ssl and ssl_options MUST be specified %% where option() is all options supported in the ssl module ibrowse-4.2.2/README.md0000644000232200023220000002256212625271016015027 0ustar debalancedebalance# ibrowse [![Build Status](https://secure.travis-ci.org/cmullaparthi/ibrowse.png)](http://travis-ci.org/cmullaparthi/ibrowse) ibrowse is a HTTP client written in erlang. **License:** ibrowse is available under two different licenses. LGPL or the BSD license. **Comments to:** chandrashekhar.mullaparthi@gmail.com **Current Version:** 4.2.2 **Latest Version:** git://github.com/cmullaparthi/ibrowse.git ## Features * [RFC2616](http://www.ietf.org/rfc/rfc2616.txt) compliant (AFAIK) * supports GET, POST, OPTIONS, HEAD, PUT, DELETE, TRACE, MKCOL, PROPFIND, PROPPATCH, LOCK, UNLOCK, MOVE and COPY * Understands HTTP/0.9, HTTP/1.0 and HTTP/1.1 * Understands chunked encoding * Can generate requests using [Chunked Transfer-Encoding](http://en.wikipedia.org/wiki/Chunked_transfer_encoding) * Pools of connections to each webserver * Pipelining support * Download to file * Asynchronous requests. Responses are streamed to a process * Basic authentication * Supports proxy authentication * Supports socks5 * Can talk to secure webservers using SSL * *Any other features in the code not listed here :)* ## Usage Examples Remember to start ibrowse first: ```erlang 5> ibrowse:start(). {ok,<0.94.0>} ``` ### Synchronous Requests A simple `GET` request: ```erlang 6> ibrowse:send_req("http://intranet/messenger/", [], get). {ok,"200", [{"Server","Microsoft-IIS/5.0"}, {"Content-Location","http://intranet/messenger/index.html"}, {"Date","Fri, 17 Dec 2004 15:16:19 GMT"}, {"Content-Type","text/html"}, {"Accept-Ranges","bytes"}, {"Last-Modified","Fri, 17 Dec 2004 08:38:21 GMT"}, {"Etag","\"aa7c9dc313e4c41:d77\""}, {"Content-Length","953"}], "..."} ``` A `GET` using a proxy: ```erlang 7> ibrowse:send_req("http://www.google.com/", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}], 1000). {ok,"302", [{"Date","Fri, 17 Dec 2004 15:22:56 GMT"}, {"Content-Length","217"}, {"Content-Type","text/html"}, {"Set-Cookie", "PREF=ID=f58155c797f9..."}, {"Server","GWS/2.1"}, {"Location", "http://www.google.co.uk/cxfer?c=PREF%3D:TM%3D110329..."}, {"Via","1.1 netapp01 (NetCache NetApp/5.5R2)"}], "...\r\n"} ``` A `GET` response saved to file. A temporary file is created and the filename returned. The response will only be saved to file if the status code is in the `200` range. The directory to download to can be set using the application env var `download_dir` - the default is the current working directory: ```erlang 8> ibrowse:send_req("http://www.erlang.se/", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {save_response_to_file, true}], 1000). {error,req_timedout} 9> ibrowse:send_req("http://www.erlang.se/", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {save_response_to_file, true}], 5000). {ok,"200", [{"Transfer-Encoding","chunked"}, {"Date","Fri, 17 Dec 2004 15:24:36 GMT"}, {"Content-Type","text/html"}, {"Server","Apache/1.3.9 (Unix)"}, {"Via","1.1 netapp01 (NetCache NetApp/5.5R2)"}], {file,"/Users/chandru/code/ibrowse/src/ibrowse_tmp_file_1103297041125854"}} ``` Setting the size of the connection pool and pipeline. This sets the number of maximum connections to the specified server to `10` and the pipeline size to `1`. Connections are assumed to be already setup. ```erlang 11> ibrowse:set_dest("www.hotmail.com", 80, [{max_sessions, 10}, {max_pipeline_size, 1}]). ok ``` Example using the `HEAD` method: ```erlang 56> ibrowse:send_req("http://www.erlang.org", [], head). {ok,"200", [{"Date","Mon, 28 Feb 2005 04:40:53 GMT"}, {"Server","Apache/1.3.9 (Unix)"}, {"Last-Modified","Thu, 10 Feb 2005 09:31:23 GMT"}, {"Etag","\"8d71d-1efa-420b29eb\""}, {"Accept-ranges","bytes"}, {"Content-Length","7930"}, {"Content-Type","text/html"}], []} ``` Example using the `OPTIONS` method: ```erlang 62> ibrowse:send_req("http://www.sun.com", [], options). {ok,"200", [{"Server","Sun Java System Web Server 6.1"}, {"Date","Mon, 28 Feb 2005 04:44:39 GMT"}, {"Content-Length","0"}, {"P3p", "policyref=\"http://www.sun.com/p3p/Sun_P3P_Policy.xml\", CP=\"CAO DSP COR CUR ADMa DEVa TAIa PSAa PSDa CONi TELi OUR SAMi PUBi IND PHY ONL PUR COM NAV INT DEM CNT STA POL PRE GOV\""}, {"Set-Cookie", "SUN_ID=X.X.X.X:169191109565879; EXPIRES=Wednesday, 31-Dec-2025 23:59:59 GMT; DOMAIN=.sun.com; PATH=/"}, {"Allow", "HEAD, GET, PUT, POST, DELETE, TRACE, OPTIONS, MOVE, INDEX, MKDIR, RMDIR"}], []} ``` ### Asynchronous Requests Example of an asynchronous `GET` request: ```erlang 18> ibrowse:send_req("http://www.google.com", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {stream_to, self()}]). {ibrowse_req_id,{1115,327256,389608}} 19> flush(). Shell got {ibrowse_async_headers,{1115,327256,389608}, "302", [{"Date","Thu, 05 May 2005 21:06:41 GMT"}, {"Content-Length","217"}, {"Content-Type","text/html"}, {"Set-Cookie", "PREF=ID=b601f16bfa32f071:CR=1:TM=1115327201:LM=1115327201:S=OX5hSB525AMjUUu7; expires=Sun, 17-Jan-2038 19:14:07 GMT; path=/; domain=.google.com"}, {"Server","GWS/2.1"}, {"Location", "http://www.google.co.uk/cxfer?c=PREF%3D:TM%3D1115327201:S%3DDS9pDJ4IHcAuZ_AS&prev=/"}, {"Via", "1.1 hatproxy01 (NetCache NetApp/5.6.2)"}]} Shell got {ibrowse_async_response,{1115,327256,389608}, "...\r\n"} Shell got {ibrowse_async_response_end,{1115,327256,389608}} ok ``` Another asynchronous `GET` request: ```erlang 24> ibrowse:send_req("http://yaws.hyber.org/simple_ex2.yaws", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {stream_to, self()}]). {ibrowse_req_id,{1115,327430,512314}} 25> flush(). Shell got {ibrowse_async_headers,{1115,327430,512314}, "200", [{"Date","Thu, 05 May 2005 20:58:08 GMT"}, {"Content-Length","64"}, {"Content-Type","text/html;charset="}, {"Server", "Yaws/1.54 Yet Another Web Server"}, {"Via", "1.1 hatproxy01 (NetCache NetApp/5.6.2)"}]} Shell got {ibrowse_async_response,{1115,327430,512314}, "...\n"} Shell got {ibrowse_async_response_end,{1115,327430,512314}} ``` Example of request which fails when using the async option. Here the `{ibrowse_req_id, ReqId}` is not returned. Instead the error code is returned. ```erlang 68> ibrowse:send_req("http://www.earlyriser.org", [], get, [], [{stream_to, self()}]). {error,conn_failed} ``` ### Other Examples Example of request using both Proxy-Authorization and authorization by the final webserver: ```erlang 17> ibrowse:send_req("http://www.erlang.se/lic_area/protected/patches/erl_756_otp_beam.README", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {basic_auth, {"XXXXX", "XXXXXX"}}]). {ok,"200", [{"Accept-Ranges","bytes"}, {"Date","Thu, 05 May 2005 21:02:09 GMT"}, {"Content-Length","2088"}, {"Content-Type","text/plain"}, {"Server","Apache/1.3.9 (Unix)"}, {"Last-Modified","Tue, 03 May 2005 15:08:18 GMT"}, {"ETag","\"1384c8-828-427793e2\""}, {"Via","1.1 hatproxy01 (NetCache NetApp/5.6.2)"}], "Patch Id:\t\terl_756_otp_beam\n..."} ``` Example of a `TRACE` request. Very interesting! yaws.hyber.org didn't support this. Nor did www.google.com. But good old BBC supports this: ```erlang 37> ibrowse:send_req("http://www.bbc.co.uk/", [], trace, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}]). {ok,"200", [{"Transfer-Encoding","chunked"}, {"Date","Thu, 05 May 2005 21:40:27 GMT"}, {"Content-Type","message/http"}, {"Server","Apache/2.0.51 (Unix)"}, {"Set-Cookie", "BBC-UID=7452e72a..."}, {"Set-Cookie", "BBC-UID=7452e72a..."}, {"Via","1.1 hatproxy01 (NetCache NetApp/5.6.2)"}], "TRACE / HTTP/1.1\r\nHost: www.bbc.co.uk\r\nConnection: keep-alive\r\nX-Forwarded-For: 172.24.28.29\r\nVia: 1.1 hatproxy01 (NetCache NetApp/5.6.2)\r\nCookie: BBC-UID=7452e...\r\n\r\n"} ``` A `GET` using a socks5: ```erlang ibrowse:send_req("http://google.com", [], get, [], [{socks5_host, "127.0.0.1"}, {socks5_port, 5335}]). ibrowse:send_req("http://google.com", [], get, [], [{socks5_host, "127.0.0.1"}, {socks5_port, 5335}, {socks5_user, "user4321"}, {socks5_pass, "pass7654"}]). ``` ibrowse-4.2.2/CONTRIBUTORS0000644000232200023220000000305612625271016015425 0ustar debalancedebalanceCONTRIBUTORS ============ The following people have helped maked ibrowse better by reporting bugs, supplying patches and also asking for new features. Please write to me if you have contributed and I've missed you out. In alphabetical order: Adam Kocoloski Andrew Tunnell-Jones Anthony Molinaro Benjamin P Lee (https://github.com/benjaminplee) Benoit Chesneau (https://github.com/benoitc) Brian Richards (http://github.com/richbria) Chris Newcombe Dan Kelley Dan Schwabe (https://github.com/dfschwabe) Derek Upham Eric Merritt Erik Reitsma Filipe David Manana Geoff Cant Jeroen Koops Jo?o Lopes Joseph Wayne Norton Karol Skocik Konstantin Nikiforov Kostis Sagonas Marcelo Gornstein (https://github.com/marcelog) Matthew Reilly Michael Terry Oscar Hellstr?m Paul J. Davis Peter Kristensen Ram Krishnan Richard Cameron Robert Newson (https://github.com/rnewson) Ryan Flynn Ryan Zezeski Sean Hinde Serge Polkovnikov (https://github.com/serge2) Sergey Samokhi Seth Falcon Steve Vinoski Thomas Lindgren Youn?s Hafri Yury Gargay (https://github.com/surik) fholzhauser (https://github.com/fholzhauser/) hyperthunk (https://github.com/hyperthunk/) Mistagrooves (https://github.com/Mistagrooves/) tholschuh (https://github.com/tholschuh/) https://github.com/apauley https://github.com/AeroNotix https://github.com/dis https://github.com/f355 https://github.com/flycodepl https://github.com/helllamer https://github.com/marutha https://github.com/nrdufour https://github.com/pib https://github.com/puzza007 https://github.com/rflynn https://github.com/Vagabond https://github.com/divolgin ibrowse-4.2.2/bootstrap_travis.sh0000755000232200023220000000013412625271016017503 0ustar debalancedebalance#!/bin/sh curl -O -L https://s3.amazonaws.com/rebar3/rebar3 chmod +x rebar3 ./rebar3 updateibrowse-4.2.2/doc/0000755000232200023220000000000012625271016014306 5ustar debalancedebalanceibrowse-4.2.2/doc/ibrowse_lib.html0000644000232200023220000001344212625271016017500 0ustar debalancedebalance Module ibrowse_lib

Module ibrowse_lib

Module with a few useful functions.

Description

Module with a few useful functions

Function Index

decode_base64/1Implements the base64 decoding algorithm.
decode_rfc822_date/1
do_trace/2
do_trace/3
do_trace/3
encode_base64/1Implements the base64 encoding algorithm.
get_trace_status/2
get_value/2
get_value/3
parse_url/1
printable_date/0
printable_date/1
status_code/1Given a status code, returns an atom describing the status code.
url_encode/1URL-encodes a string based on RFC 1738.

Function Details

decode_base64/1

decode_base64(List::In) -> Out | exit({error, invalid_input})

  • In = string() | binary()
  • Out = string() | binary()

Implements the base64 decoding algorithm. The output data type matches in the input data type.

decode_rfc822_date/1

decode_rfc822_date(String) -> any()

do_trace/2

do_trace(Fmt, Args) -> any()

do_trace/3

do_trace(X1, Fmt, Args) -> any()

do_trace/3

do_trace(X1, Fmt, Args) -> any()

encode_base64/1

encode_base64(List::In) -> Out

  • In = string() | binary()
  • Out = string() | binary()

Implements the base64 encoding algorithm. The output data type matches in the input data type.

get_trace_status/2

get_trace_status(Host, Port) -> any()

get_value/2

get_value(Tag, TVL) -> any()

get_value/3

get_value(Tag, TVL, DefVal) -> any()

parse_url/1

parse_url(Url) -> any()

printable_date/0

printable_date() -> any()

printable_date/1

printable_date(Now) -> any()

status_code/1

status_code(StatusCode::status_code()) -> StatusDescription

Given a status code, returns an atom describing the status code.

url_encode/1

url_encode(Str) -> UrlEncodedStr

  • Str = string()
  • UrlEncodedStr = string()

URL-encodes a string based on RFC 1738. Returns a flat list.


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/stylesheet.css0000644000232200023220000000154512625271016017216 0ustar debalancedebalance/* standard EDoc style sheet */ body { font-family: Verdana, Arial, Helvetica, sans-serif; margin-left: .25in; margin-right: .2in; margin-top: 0.2in; margin-bottom: 0.2in; color: #000000; background-color: #ffffff; } h1,h2 { margin-left: -0.2in; } div.navbar { background-color: #add8e6; padding: 0.2em; } h2.indextitle { padding: 0.4em; background-color: #add8e6; } h3.function,h3.typedecl { background-color: #add8e6; padding-left: 1em; } div.spec { margin-left: 2em; background-color: #eeeeee; } a.module { text-decoration:none } a.module:hover { background-color: #eeeeee; } ul.definitions { list-style-type: none; } ul.index { list-style-type: none; background-color: #eeeeee; } /* * Minor style tweaks */ ul { list-style-type: square; } table { border-collapse: collapse; } td { padding: 3 } ibrowse-4.2.2/doc/index.html0000644000232200023220000000074612625271016016312 0ustar debalancedebalance The ibrowse application <h2>This page uses frames</h2> <p>Your browser does not accept frames. <br>You should go to the <a href="overview-summary.html">non-frame version</a> instead. </p> ibrowse-4.2.2/doc/ibrowse_lb.html0000644000232200023220000000674512625271016017337 0ustar debalancedebalance Module ibrowse_lb

Module ibrowse_lb

Behaviours: gen_server.

Function Index

code_change/3
handle_call/3
handle_cast/2
handle_info/2
init/1
spawn_connection/6
start_link/1
stop/1
terminate/2

Function Details

code_change/3

code_change(OldVsn, State, Extra) -> any()

handle_call/3

handle_call(Request, From, State) -> any()

handle_cast/2

handle_cast(Msg, State) -> any()

handle_info/2

handle_info(Info, State) -> any()

init/1

init(X1) -> any()

spawn_connection/6

spawn_connection(Lb_pid, Url, Max_sessions, Max_pipeline_size, SSL_options, Process_options) -> any()

start_link/1

start_link(Args) -> any()

stop/1

stop(Lb_pid) -> any()

terminate/2

terminate(Reason, State) -> any()


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/ibrowse_app.html0000644000232200023220000000352412625271016017512 0ustar debalancedebalance Module ibrowse_app

Module ibrowse_app

Behaviours: application.

Function Index

start/2
stop/1

Function Details

start/2

start(Type, StartArgs) -> any()

stop/1

stop(State) -> any()


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/ibrowse_sup.html0000644000232200023220000000353112625271016017537 0ustar debalancedebalance Module ibrowse_sup

Module ibrowse_sup

Behaviours: supervisor.

Function Index

init/1
start_link/0

Function Details

init/1

init(X1) -> any()

start_link/0

start_link() -> any()


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/ibrowse_http_client.html0000644000232200023220000001005712625271016021246 0ustar debalancedebalance Module ibrowse_http_client

Module ibrowse_http_client

Behaviours: gen_server.

Function Index

code_change/3
handle_call/3
handle_cast/2
handle_info/2
init/1
send_req/7
start/1
start/2
start_link/1
start_link/2
stop/1
terminate/2

Function Details

code_change/3

code_change(OldVsn, State, Extra) -> any()

handle_call/3

handle_call(Request, From, State) -> any()

handle_cast/2

handle_cast(Msg, State) -> any()

handle_info/2

handle_info(Info, State) -> any()

init/1

init(Url) -> any()

send_req/7

send_req(Conn_Pid, Url, Headers, Method, Body, Options, Timeout) -> any()

start/1

start(Args) -> any()

start/2

start(Args, Options) -> any()

start_link/1

start_link(Args) -> any()

start_link/2

start_link(Args, Options) -> any()

stop/1

stop(Conn_pid) -> any()

terminate/2

terminate(Reason, State) -> any()


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/modules-frame.html0000644000232200023220000000202512625271016017733 0ustar debalancedebalance The ibrowse application

Modules

ibrowse
ibrowse_app
ibrowse_http_client
ibrowse_lb
ibrowse_lib
ibrowse_socks5
ibrowse_sup
ibrowse-4.2.2/doc/erlang.png0000644000232200023220000000407512625271016016272 0ustar debalancedebalance‰PNG  IHDR2*~ØŸ pHYs  šœtIMEÖ ,ó,ëÒÜIDATXÃ͘}PSWÀï{ùx !yˆ "–bø°¬»¢‹ºkù"»V]íì(ZÇaªÒ‘»Ê Åiwp·Ó®+™îRGÀu‹#ŒŽ”í‚ØdIB@ùàAxoÿH„yqªöüõæ¼{Ïû½sÎ=÷ž u~ù×®ÊA½Y±çÿ¹ E!É)“‰4™I&“¢ƒA}nç§Ÿuߺ㨓mþ%éÖèëô³*:‹®P§Î„ëtÝ¥U]_ß±õõ‚(ê¡XùûßM1 †Ûòó!Hœ²ýAQ­±wdVç-ÐÓç Ø#{w+E¦±¶¶úÝYOëmF5:6ªmÐ|Óäÿ»ØŸf2ÜÐe 2ihÚ;ß唂é9%ì8‚ç·âíœ!:B…ɪî¾ùÛžv80ÍÈ”eªç«Ú¦“6‡îJá‰V8ê`‡·bß;l‰„RJàøwùgGŸŒ,9€ µeuÖþÿR±Æ‹%Éoh1,7Œ!9H1|¦'šÊ–eÆ ˜õÍ] J“7À Ú"X¢Ä(žwE+CÚŒËhLû˜¢Aïðp.Êœ[y³O;©º àµV¹íï`yþ0vØ*ŠaûEÐXÅ}',.Ÿ!xëMêXÜ€n@øQE,Ó‚ûNAä†Èi¼VÁBdósË{ƒf2_/pÈ­°8bxíÂAæcyÑ×&œ±8€Áû)`±  +,…]ŸÔVüszÌôãB ¿IÈ«8²<ëxfçJÄI’à§'tƒÁ Óé~h˼½…B!€ ˆžž³Ù AH$òôôœ088800°zõjdAò÷ôô±Ùs§r“ɤÑhíã­V«Z­FQT2sCDoooCCÇ[»v­¨T*îŒdff’$I’ääädBB‚]éïïóæMrFòòò0 Óëõä)++ãr¹%%%ŽÊÚÚZ—››;==M’¤Z­ö÷÷?uê”ý-A|>ßÍÍ EQÿ7n$ Ûl6A®^½ÚÐÐpøðá¹ë+«U©T6662™Ì3gÎXgÎ8Ž›L‹ìQÓÓÓçγX,ÅÅÅ“““s=5e4 êêêL&ÇqæL&UVVæä䤦¦öõõ566ŠD¢ŠŠŠ‰‰ :†adFœj ‹%‰|}}q'âùÙÐÞÞÞÚÚšššzíÚµîîîÐÐP§ý `ÿþýuuuLçÞ½¸¸X"‘œ>}šÏçóùüêêj.—K§Óa€Á`HNNމ‰)--uœÓÙÙ¹sçÎÖÖÖ¤¤$ÇtYT.]º$ =ÊãñT*Õ¼·ééé!!!éééËÜ%ÑhÔét …ÂËËktt4+++???33³££`VTTTUUµcǧ*72rëÖ­”””#GŽÀðóz¤þþþëׯûùùY­Ö•+WÖÔÔ˜Íf碆”””¨Õêüüü©™c0—ËÅ0Ìd2Y­V‚ ´Zm}}}aa¡Á`€ís”J¥——S?µwïÞªªª¶¶¶yí«Åb±X,³‘­©©Ñh4Z­vÏž=ýýý]]]÷îÝ›±æí­R©ª««‡‡‡g[•ØØØæææšš Ã.^¼*‹år9 NKKÛ¾}û… æýbFFFËÎÎvü{‚ ãââ츋¥¼¼<((¨©©©©©éîÝ»<ïòå˶÷¹QQQ'Nœ`08ŽÛ5ö´Û½{w||ü•+W:$ iÙÙÙl6ÛÇÇÇÓÓ344488xÖŠ\.‹‹ öì™L&öõa˜T*•J¥ëÖ­óðð°X,:îàÁƒ …‚Ãá (Ša‚ ÑÑÑt:ÅbÉåò7òù|‚"""¤RiDD„½n!’œœÌápZZZPÍÌÌÜ·oNÿ?´ÏJJÕèIEND®B`‚ibrowse-4.2.2/doc/edoc-info0000644000232200023220000000023412625271016016073 0ustar debalancedebalance%% encoding: UTF-8 {application,ibrowse}. {modules,[ibrowse,ibrowse_app,ibrowse_http_client,ibrowse_lb,ibrowse_lib, ibrowse_socks5,ibrowse_sup]}. ibrowse-4.2.2/doc/ibrowse_socks5.html0000644000232200023220000000316112625271016020136 0ustar debalancedebalance Module ibrowse_socks5

Module ibrowse_socks5

Function Index

connect/5

Function Details

connect/5

connect(Host, Port, Options, SockOptions, Timeout) -> any()


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/short-desc0000644000232200023220000000005512625271016016304 0ustar debalancedebalanceA powerful HTTP/1.1 client written in erlang ibrowse-4.2.2/doc/ibrowse.html0000644000232200023220000006145512625271016016661 0ustar debalancedebalance Module ibrowse

Module ibrowse

The ibrowse application implements an HTTP 1.1 client in erlang.

Copyright © 2005-2014 Chandrashekhar Mullaparthi

Behaviours: gen_server.

Authors: Chandrashekhar Mullaparthi (chandrashekhar dot mullaparthi at gmail dot com).

Description

The ibrowse application implements an HTTP 1.1 client in erlang. This module implements the API of the HTTP client. There is one named process called 'ibrowse' which assists in load balancing and maintaining configuration. There is one load balancing process per unique webserver. There is one process to handle one TCP connection to a webserver (implemented in the module ibrowse_http_client). Multiple connections to a webserver are setup based on the settings for each webserver. The ibrowse process also determines which connection to pipeline a certain request on. The functions to call are send_req/3, send_req/4, send_req/5, send_req/6.

Here are a few sample invocations.

ibrowse:send_req("http://intranet/messenger/", [], get).

ibrowse:send_req("http://www.google.com/", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}], 1000).

ibrowse:send_req("http://www.erlang.org/download/otp_src_R10B-3.tar.gz", [], get, [], [{proxy_user, "XXXXX"}, {proxy_password, "XXXXX"}, {proxy_host, "proxy"}, {proxy_port, 8080}, {save_response_to_file, true}], 1000).

ibrowse:send_req("http://www.erlang.org", [], head).

ibrowse:send_req("http://www.sun.com", [], options).

ibrowse:send_req("http://www.bbc.co.uk", [], trace).

ibrowse:send_req("http://www.google.com", [], get, [], [{stream_to, self()}]).

Function Index

add_config/1Add additional configuration elements at runtime.
all_trace_off/0Turn Off ALL tracing.
code_change/3
get_config_value/1Internal export.
get_config_value/2Internal export.
get_metrics/0
get_metrics/2
handle_call/3
handle_cast/2
handle_info/2
init/1
rescan_config/0Clear current configuration for ibrowse and load from the file ibrowse.conf in the IBROWSE_EBIN/../priv directory.
rescan_config/1
send_req/3This is the basic function to send a HTTP request.
send_req/4Same as send_req/3.
send_req/5Same as send_req/4.
send_req/6Same as send_req/5.
send_req_direct/4Same as send_req/3 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2.
send_req_direct/5Same as send_req/4 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2.
send_req_direct/6Same as send_req/5 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2.
send_req_direct/7Same as send_req/6 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2.
set_dest/3Deprecated.
set_max_attempts/3Set the maximum attempts for each connection to a specific Host:Port.
set_max_pipeline_size/3Set the maximum pipeline size for each connection to a specific Host:Port.
set_max_sessions/3Set the maximum number of connections allowed to a specific Host:Port.
show_dest_status/0Shows some internal information about load balancing.
show_dest_status/1
show_dest_status/2Shows some internal information about load balancing to a specified Host:Port.
spawn_link_worker_process/1Same as spawn_worker_process/1 except the the calling process is linked to the worker process which is spawned.
spawn_link_worker_process/2Same as spawn_link_worker_process/1 except with Erlang process options.
spawn_worker_process/1Creates a HTTP client process to the specified Host:Port which is not part of the load balancing pool.
spawn_worker_process/2Same as spawn_worker_process/1 except with Erlang process options.
start/0Starts the ibrowse process without linking.
start_link/0Starts the ibrowse process linked to the calling process.
stop/0Stop the ibrowse process.
stop_worker_process/1Terminate a worker process spawned using spawn_worker_process/2 or spawn_link_worker_process/2.
stream_close/1Tell ibrowse to close the connection associated with the specified stream.
stream_next/1Tell ibrowse to stream the next chunk of data to the caller.
terminate/2
trace_off/0Turn tracing off for the ibrowse process.
trace_off/2Turn tracing OFF for all connections to the specified HTTP server.
trace_on/0Turn tracing on for the ibrowse process.
trace_on/2Turn tracing on for all connections to the specified HTTP server.

Function Details

add_config/1

add_config(Terms) -> any()

Add additional configuration elements at runtime.

all_trace_off/0

all_trace_off() -> ok

Turn Off ALL tracing

code_change/3

code_change(OldVsn, State, Extra) -> any()

get_config_value/1

get_config_value(Key) -> any()

Internal export

get_config_value/2

get_config_value(Key, DefVal) -> any()

Internal export

get_metrics/0

get_metrics() -> any()

get_metrics/2

get_metrics(Host, Port) -> any()

handle_call/3

handle_call(Request, From, State) -> any()

handle_cast/2

handle_cast(Msg, State) -> any()

handle_info/2

handle_info(Info, State) -> any()

init/1

init(X1) -> any()

rescan_config/0

rescan_config() -> any()

Clear current configuration for ibrowse and load from the file ibrowse.conf in the IBROWSE_EBIN/../priv directory. Current configuration is cleared only if the ibrowse.conf file is readable using file:consult/1

rescan_config/1

rescan_config(Terms) -> any()

send_req/3

send_req(Url::string(), Headers::headerList(), Method::method()) -> response()

This is the basic function to send a HTTP request. The Status return value indicates the HTTP status code returned by the webserver

send_req/4

send_req(Url, Headers, Method::method(), Body::body()) -> response()

Same as send_req/3. If a list is specified for the body it has to be a flat list. The body can also be a fun/0 or a fun/1.
If fun/0, the connection handling process will repeatdely call the fun until it returns an error or eof.

Fun() = {ok, Data} | eof

If fun/1, the connection handling process will repeatedly call the fun with the supplied state until it returns an error or eof.
Fun(State) = {ok, Data} | {ok, Data, NewState} | eof

send_req/5

send_req(Url::string(), Headers::headerList(), Method::method(), Body::body(), Options::optionList()) -> response()

  • optionList() = [option()]
  • option() = {max_sessions, integer()} | {response_format, response_format()} | {stream_chunk_size, integer()} | {max_pipeline_size, integer()} | {trace, boolean()} | {is_ssl, boolean()} | {ssl_options, [SSLOpt]} | {pool_name, atom()} | {proxy_host, string()} | {proxy_port, integer()} | {proxy_user, string()} | {proxy_password, string()} | {use_absolute_uri, boolean()} | {basic_auth, {username(), password()}} | {cookie, string()} | {content_length, integer()} | {content_type, string()} | {save_response_to_file, srtf()} | {stream_to, stream_to()} | {http_vsn, {MajorVsn, MinorVsn}} | {host_header, string()} | {inactivity_timeout, integer()} | {connect_timeout, integer()} | {socket_options, Sock_opts} | {transfer_encoding, {chunked, ChunkSize}} | {headers_as_is, boolean()} | {give_raw_headers, boolean()} | {preserve_chunked_encoding, boolean()} | {workaround, head_response_with_body} | {worker_process_options, list()} | {return_raw_request, true} | {max_attempts, integer()}
  • stream_to() = process() | {process(), once}
  • process() = pid() | atom()
  • username() = string()
  • password() = string()
  • SSLOpt = term()
  • Sock_opts = [Sock_opt]
  • Sock_opt = term()
  • ChunkSize = integer()
  • srtf() = boolean() | filename() | {append, filename()}
  • filename() = string()
  • response_format() = list | binary

Same as send_req/4.

send_req/6

send_req(Url, Headers::headerList(), Method::method(), Body::body(), Options::optionList(), Timeout) -> response()

  • Timeout = integer() | infinity

Same as send_req/5. All timeout values are in milliseconds.

send_req_direct/4

send_req_direct(Conn_pid, Url, Headers, Method) -> any()

Same as send_req/3 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2

send_req_direct/5

send_req_direct(Conn_pid, Url, Headers, Method, Body) -> any()

Same as send_req/4 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2

send_req_direct/6

send_req_direct(Conn_pid, Url, Headers, Method, Body, Options) -> any()

Same as send_req/5 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2

send_req_direct/7

send_req_direct(Conn_pid, Url, Headers, Method, Body, Options, Timeout) -> any()

Same as send_req/6 except that the first argument is the PID returned by spawn_worker_process/2 or spawn_link_worker_process/2

set_dest/3

set_dest(Host, Port, T) -> any()

Deprecated. Use set_max_sessions/3 and set_max_pipeline_size/3 for achieving the same effect.

set_max_attempts/3

set_max_attempts(Host::string(), Port::integer(), Max::integer()) -> ok

Set the maximum attempts for each connection to a specific Host:Port.

set_max_pipeline_size/3

set_max_pipeline_size(Host::string(), Port::integer(), Max::integer()) -> ok

Set the maximum pipeline size for each connection to a specific Host:Port.

set_max_sessions/3

set_max_sessions(Host::string(), Port::integer(), Max::integer()) -> ok

Set the maximum number of connections allowed to a specific Host:Port.

show_dest_status/0

show_dest_status() -> any()

Shows some internal information about load balancing. Info about workers spawned using spawn_worker_process/2 or spawn_link_worker_process/2 is not included.

show_dest_status/1

show_dest_status(Url) -> any()

show_dest_status/2

show_dest_status(Host, Port) -> any()

Shows some internal information about load balancing to a specified Host:Port. Info about workers spawned using spawn_worker_process/2 or spawn_link_worker_process/2 is not included.

spawn_link_worker_process/1

spawn_link_worker_process(Url::string() | {Host::string(), Port::integer()}) -> {ok, pid()}

Same as spawn_worker_process/1 except the the calling process is linked to the worker process which is spawned.

spawn_link_worker_process/2

spawn_link_worker_process(Host::string(), Port::integer()) -> {ok, pid()}

Same as spawn_link_worker_process/1 except with Erlang process options.

spawn_worker_process/1

spawn_worker_process(Url::string() | {Host::string(), Port::integer()}) -> {ok, pid()}

Creates a HTTP client process to the specified Host:Port which is not part of the load balancing pool. This is useful in cases where some requests to a webserver might take a long time whereas some might take a very short time. To avoid getting these quick requests stuck in the pipeline behind time consuming requests, use this function to get a handle to a connection process.
Note: Calling this function only creates a worker process. No connection is setup. The connection attempt is made only when the first request is sent via any of the send_req_direct/4,5,6,7 functions.
Note: It is the responsibility of the calling process to control pipeline size on such connections.

spawn_worker_process/2

spawn_worker_process(Host::string(), Port::integer()) -> {ok, pid()}

Same as spawn_worker_process/1 except with Erlang process options.

start/0

start() -> any()

Starts the ibrowse process without linking. Useful when testing using the shell

start_link/0

start_link() -> {ok, pid()}

Starts the ibrowse process linked to the calling process. Usually invoked by the supervisor ibrowse_sup

stop/0

stop() -> any()

Stop the ibrowse process. Useful when testing using the shell.

stop_worker_process/1

stop_worker_process(Conn_pid::pid()) -> ok

Terminate a worker process spawned using spawn_worker_process/2 or spawn_link_worker_process/2. Requests in progress will get the error response

{error, closing_on_request}

stream_close/1

stream_close(Req_id::req_id()) -> ok | {error, unknown_req_id}

Tell ibrowse to close the connection associated with the specified stream. Should be used in conjunction with the stream_to option. Note that all requests in progress on the connection which is serving this Req_id will be aborted, and an error returned.

stream_next/1

stream_next(Req_id::req_id()) -> ok | {error, unknown_req_id}

Tell ibrowse to stream the next chunk of data to the caller. Should be used in conjunction with the stream_to option

terminate/2

terminate(Reason, State) -> any()

trace_off/0

trace_off() -> any()

Turn tracing off for the ibrowse process

trace_off/2

trace_off(Host, Port) -> ok

Turn tracing OFF for all connections to the specified HTTP server.

trace_on/0

trace_on() -> any()

Turn tracing on for the ibrowse process

trace_on/2

trace_on(Host, Port) -> ok

  • Host = string()
  • Port = integer()

Turn tracing on for all connections to the specified HTTP server. Host is whatever is specified as the domain name in the URL


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/doc/overview-summary.html0000644000232200023220000000210612625271016020534 0ustar debalancedebalance The ibrowse application

The ibrowse application


Generated by EDoc, Nov 6 2015, 11:40:24.

ibrowse-4.2.2/.travis.yml0000644000232200023220000000024212625271016015650 0ustar debalancedebalancelanguage: erlang otp_release: - R16B - R16B03-1 - 17.0 - 17.1 - 18.0 - 18.1 before_script: - "./bootstrap_travis.sh" script: "./rebar3 eunit" ibrowse-4.2.2/include/0000755000232200023220000000000012625271016015164 5ustar debalancedebalanceibrowse-4.2.2/include/ibrowse.hrl0000644000232200023220000000113512625271016017345 0ustar debalancedebalance-ifndef(IBROWSE_HRL). -define(IBROWSE_HRL, "ibrowse.hrl"). -record(url, { abspath, host, port, username, password, path, protocol, host_type % 'hostname', 'ipv4_address' or 'ipv6_address' }). -record(lb_pid, {host_port, pid, ets_tid}). -record(client_conn, {key, cur_pipeline_size = 0, reqs_served = 0}). -record(ibrowse_conf, {key, value}). -define(CONNECTIONS_LOCAL_TABLE, ibrowse_lb). -define(LOAD_BALANCER_NAMED_TABLE, ibrowse_lb). -define(CONF_TABLE, ibrowse_conf). -define(STREAM_TABLE, ibrowse_stream). -endif. ibrowse-4.2.2/rebar.lock0000644000232200023220000000000412625271016015500 0ustar debalancedebalance[]. ibrowse-4.2.2/CHANGELOG0000644000232200023220000003706612625271016014767 0ustar debalancedebalanceCONTRIBUTIONS & CHANGE HISTORY ============================== 25-11-2015 - v4.2.2 * Fix to ibrowse.app.src to enable publishing using Hex 25-11-2015 - v4.2.1 * Merged pull request https://github.com/cmullaparthi/ibrowse/pull/132 * Merged pull request https://github.com/cmullaparthi/ibrowse/pull/137 28-09-2015 - v4.2 * Merged long pending improvements to pipelining https://github.com/cmullaparthi/ibrowse/pull/123 * Merged pull request https://github.com/cmullaparthi/ibrowse/pull/131 03-08-2015 - v4.1.2 * R18 compatibility fix https://github.com/cmullaparthi/ibrowse/issues/129 * Add max_attempts option https://github.com/cmullaparthi/ibrowse/pull/125 * Fix for https://github.com/cmullaparthi/ibrowse/pull/120 * Enhanced SOCKS5 support https://github.com/cmullaparthi/ibrowse/pull/117 10-07-2014 - v4.1.1 * Added support for accepting binaries as header names * Fix for https://github.com/cmullaparthi/ibrowse/issues/110 * Fix for https://github.com/cmullaparthi/ibrowse/issues/111 * Fix for https://github.com/cmullaparthi/ibrowse/issues/112 18-04-2013 - v4.1.0 * Fix for https://github.com/cmullaparthi/ibrowse/issues/101 * Support for https://github.com/cmullaparthi/ibrowse/issues/90 * Fix for https://github.com/cmullaparthi/ibrowse/issues/86 * Merged various contributions. Please see commit history for details * Introduced the return_raw_request option 09-04-2013 - v4.0.2 * Tagging master with new version to cover changes contributed over the past few months via various pull requests 07-08-2012 - v4.0.1 * Fix issue 67 properly. 03-08-2012 - v4.0.0 * Fixed a regression in handling HEAD. https://github.com/cmullaparthi/ibrowse/issues/67 * Fixed a bug in handling SSL requests through a proxy 06-04-2012 - v3.0.4 * Fix for the following issue https://github.com/cmullaparthi/ibrowse/issues/67 13-03-2012 - v3.0.3 * Fixes the following issues https://github.com/cmullaparthi/ibrowse/issues/64 https://github.com/cmullaparthi/ibrowse/issues/63 https://github.com/cmullaparthi/ibrowse/issues/62 31-01-2012 - v3.0.2 * Fixed bug when stopping ibrowse. Not service affecting. 23-01-2012 - v3.0.1 * Fixed bug highlighted by Dialyzer 23-01-2012 - v3.0.0 * Change to the way pipelining works. * Fixed various issues reported 13-04-2011 - v2.2.0 * Filipe David Manana added IPv6 support. This is a mjor new feature, Thank you Filipe! * Joseph Wayne Norton contributed tweaks to .gitignore 09-02-2011 - v2.1.4 * Fixed a bug reported by Ryan Zezeski with the save_response_to_file option. https://github.com/cmullaparthi/ibrowse/issues#issue/33 16-01-2011 - v2.1.3 * Fixed issues with streaming and chunked responses when using the 'caller controls socket' feature. See following links for details. Contributed by Filipe David Manana. https://github.com/cmullaparthi/ibrowse/pull/24 https://github.com/cmullaparthi/ibrowse/pull/25 https://github.com/cmullaparthi/ibrowse/pull/27 https://github.com/cmullaparthi/ibrowse/pull/28 https://github.com/cmullaparthi/ibrowse/pull/29 * Fix for issue 32 reported by fholzhauser https://github.com/cmullaparthi/ibrowse/issues#issue/32 * Fixed some dialyzer warnings. Thanks to Kostis for reporting them. 20-12-2010 - v2.1.2 * Pipelining wasn't working when used in conjunction with the {stream_to, {self(), once}} option. Bug report by Filipe David Manana. 10-12-2010 - v2.1.1 * Fix for https://github.com/cmullaparthi/ibrowse/issues/issue/20 by Filipe David Manana * Fix for https://github.com/cmullaparthi/ibrowse/issues/issue/21 by Filipe David Manana * Fix for https://github.com/cmullaparthi/ibrowse/issues/issue/23 by Filipe David Manana * Fix for bugs when using SSL by Jo?o Lopes 25-10-2010 - v2.1.0 * Fixed build on OpenSolaris. Bug report and patch from tholschuh. http://github.com/cmullaparthi/ibrowse/issues/issue/10 * Fixed behaviour of inactivity_timeout option. Reported by Jo?o Lopes. http://github.com/cmullaparthi/ibrowse/issues/issue/11 * Prevent atom table pollution when bogus URLs are input to ibrowse. Bug report by Jo?o Lopes. http://github.com/cmullaparthi/ibrowse/issues/issue/13 * Automatically do Chunked-Transfer encoding of request body when the body is generated by a fun. Patch provided by Filipe David Manana. http://github.com/cmullaparthi/ibrowse/issues/issue/14 * Depending on input options, ibrowse sometimes included multiple Content-Length headers. Bug reported by Paul J. Davis http://github.com/cmullaparthi/ibrowse/issues/issue/15 * Deal with webservers which do not provide a Reason-Phrase on the response Status-Line. Patch provided by Jeroen Koops. http://github.com/cmullaparthi/ibrowse/issues/issue/16 * Fixed http://github.com/cmullaparthi/ibrowse/issues/issue/17 This was reported by Filipe David Manana. * Fixed http://github.com/cmullaparthi/ibrowse/issues/issue/19 This was reported by Dan Kelley and Filipe David Manana. * Added ibrowse:stream_close/1 to close the connection associated with a certain response stream. Patch provided by Jo?o Lopes. * Prevent port number being included in the Host header when port 443 is intended. Bug reported by Andrew Tunnell-Jones 24-09-2010 - v2.0.1 * Removed a spurious io:format statement 22-09-2010 - v2.0.0. * Added option preserve_chunked_encoding. This allows the caller to get the raw HTTP response when the Transfer-Encoding is Chunked. This feature was requested by Benoit Chesneau who wanted to write a HTTP proxy using ibrowse. * Fixed bug with the {stream_to, {Pid, once}} option. Bug report and lot of help from Filipe David Manana. Thank you Filipe. * The {error, conn_failed} and {error, send_failed} return values are now of the form {error, {conn_failed, Err}} and {error, {send_failed, Err}}. This is so that the specific socket error can be returned to the caller. I think it looks a bit ugly, but that is the best compromise I could come up with. * Added application configuration parameters default_max_sessions and default_max_pipeline_size. These were previously hard coded to 10. * Versioning of ibrowse now follows the Semantic Versioning principles. See http://semver.org. Thanks to Anthony Molinaro for nudging me in this direction. * The connect_timeout option now only applies to the connection setup phase. In previous versions, the time taken to setup the connection was deducted from the specified timeout value for the request. 17-07-2010 - * Merged change made by Filipe David Manana to use the base64 module for encoding/decoding. 11-06-2010 - * Removed use of deprecated concat_binary. Patch supplied by Steve Vinoski 10-06-2010 - * Fixed bug in https requests not going via the proxy 12-05-2010 - * Added support for the CONNECT method to tunnel HTTPS through a proxy. When a https URL is requested through a proxy, ibrowse will automatically use the CONNECT method to first setup a tunnel through the proxy. Once this succeeds, the actual request is dispatched. Successfully tested with the new SSL implementation in R13B-03 * Added SSL support for direct connections. See ibrowse:spawn_worker_process/1 and ibrowse:spawn_link_worker_process/1 * Added option to return raw status line and raw unparsed headers 23-04-2010 - * Fixes to URL parsing by Karol Skocik 08-11-2009 - * Added option headers_as_is 04-10-2009 - * Patch from Kostis Sagonas to cleanup some code and suppress dialyzer warnings 24-09-2009 - * When a filename was supplied with the 'save_response_to_file' option, the option was being ignored. Bug report from Adam Kocoloski 05-09-2009 - * Introduced option to allow caller to set socket options. 29-07-2009 - * The ETS table created for load balancing of requests was not being deleted which led to the node not being able to create any more ETS tables if queries were made to many number of webservers. ibrowse now deletes the ETS table it creates once the last connection to a webserver is dropped. Reported by Seth Falcon. * Spurious data being returned at end of body in certain cases of chunked encoded responses from the server. Reported by Chris Newcombe. 03-07-2009 - Added option {stream_to, {Pid, once}} which allows the caller to control when it wants to receive more data. If this option is used, the call ibrowse:stream_next(Req_id) should be used to get more data. * Patch submitted by Steve Vinoski to remove compiler warnings about the use of obsolete guards 29-06-2009 - * Fixed following issues reported by Oscar Hellstr?m * Use {active, once} instead of {active, true} * Fix 'dodgy' timeout handling * Use binaries internally instead of lists to reduce memory consumption on 64 bit platforms. The default response format is still 'list' to maintain backwards compatibility. Use the option {response_format, binary} to get responses as binaries. * Fixed chunking bug (reported by Adam Kocoloski) * Added new option {inactivity_timeout, Milliseconds} to timeout requests if no data is received on the link for the specified interval. Useful when responses are large and links are flaky. * Added ibrowse:all_trace_off/0 to turn off all tracing * Change to the way responses to asynchronous requests are returned. The following messages have been removed. * {ibrowse_async_response, Req_id, {chunk_start, Chunk_size}} * {ibrowse_async_response, Req_id, chunk_end} * Fixed Makefiles as part of Debian packaging (thanks to Thomas Lindgren) * Moved repository from Sourceforge to Github 11-06-2009 - * Added option to control size of streamed chunks. Also added option for the client to receive responses in binary format. 21-05-2008 - * Fixed bug in reading some options from the ibrowse.conf file. Reported by Erik Reitsma on the erlyaws mailing list * Fixed bug when cleaning up closing connections 27-03-2008 - * Major rewrite of the load balancing feature. Additional module, ibrowse_lb.erl, introduced to achieve this. * Can now get a handle to a connection process which is not part of the load balancing pool. Useful when an application is making requests to a webserver which are time consuming (such as uploading a large file). Such requests can be put on a separate connection, and all other smaller/quicker requests can use the load balancing pool. See ibrowse:spawn_worker_process/2 and ibrowse:spawn_link_worker_process/2 * Ram Krishnan sent a patch to enable a client to send a lot of data in a request by providing a fun which is invoked by the connection handling process. This fun can fetch the data from any where. This is useful when trying to upload a large file to a webserver. * Use the TCP_NODELAY option on every socket by default * Rudimentary support for load testing of ibrowse. Undocumented, but see ibrowse_test:load_test/3. Use the source, Luke! * New function ibrowse:show_dest_status/2 to view state of connections/pipelines to a web server 20-02-2008 - Ram Krishnan sent another patch for another hidden bug in the save_response_to_file feature. 07-02-2008 - Ram Krishnan (kriyative _at_ gmail dot com) sent a simple patch to enable specifying the filename in the save_response_to_file option. When testing the patch, I realised that my original implementation of this feature was quite flaky and a lot of corner cases were not covered. Fixed all of them. Thanks Ram! 17-10-2007 - Matthew Reilly (matthew dot reilly _at_ sipphone dot com) sent a bug report and a fix. If the chunk trailer spans two TCP packets, then ibrowse fails to recognise that the chunked transfer has ended. 29-08-2007 - Bug report by Peter Kristensen(ptx _at_ daimi dot au dot dk). ibrowse crashes when the webserver returns just the Status line and nothing else. 28-06-2007 - Added host_header option to enable connection to secure sites via stunnel 20-04-2007 - Geoff Cant sent a patch to remove URL encoding for digits in ibrowse_lib:url_encode/1. ibrowse had a dependency on the inets application because the ibrowse_http_client.erl invoked httpd_util:encode_base64/1. This dependency is now removed and the encode_base64/1 has been implemented in ibrowse_lib.erl 06-03-2007 - Eric Merritt sent a patch to support WebDAV requests. 12-01-2007 - Derek Upham sent in a bug fix. The reset_state function was not behaving correctly when the transfer encoding was not chunked. 13-11-2006 - Youn?s Hafri reported a bug where ibrowse was not returning the temporary filename when the server was closing the connection after sending the data (as in HTTP/1.0). Released ibrowse under the BSD license 12-10-2006 - Chris Newcombe reported bug in dealing with requests where no body is expected in the response. The first request would succeed and the next request would hang. 24-May-2006 - Sean Hinde reported a bug. Async responses with pipelining was returning the wrong result. 08-Dec-2005 - Richard Cameron (camster@citeulike.org). Patch to ibrowse to prevent port number being included in the Host header when port 80 is intended. 22-Nov-2005 - Added ability to generate requests using the Chunked Transfer-Encoding. 08-May-2005 - Youn?s Hafri made a CRUX LINUX port of ibrowse. http://yhafri.club.fr/crux/index.html ibrowse-4.2.2/BSD_LICENSE0000644000232200023220000000273412625271016015244 0ustar debalancedebalanceCopyright (c) 2005-2014, Chandrashekhar Mullaparthi All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of the T-Mobile nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. ibrowse-4.2.2/src/0000755000232200023220000000000012625271016014330 5ustar debalancedebalanceibrowse-4.2.2/src/ibrowse_lb.erl0000644000232200023220000002002512625271016017162 0ustar debalancedebalance%%%------------------------------------------------------------------- %%% File : ibrowse_lb.erl %%% Author : chandru %%% Description : %%% %%% Created : 6 Mar 2008 by chandru %%%------------------------------------------------------------------- -module(ibrowse_lb). -author(chandru). -behaviour(gen_server). %%-------------------------------------------------------------------- %% Include files %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% External exports -export([ start_link/1, spawn_connection/6, stop/1 ]). %% gen_server callbacks -export([ init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3 ]). -record(state, {parent_pid, ets_tid, host, port, max_sessions, max_pipeline_size, proc_state }). -include("ibrowse.hrl"). %%==================================================================== %% External functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: start_link/0 %% Description: Starts the server %%-------------------------------------------------------------------- start_link(Args) -> gen_server:start_link(?MODULE, Args, []). %%==================================================================== %% Server functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: init/1 %% Description: Initiates the server %% Returns: {ok, State} | %% {ok, State, Timeout} | %% ignore | %% {stop, Reason} %%-------------------------------------------------------------------- init([Host, Port]) -> process_flag(trap_exit, true), Max_sessions = ibrowse:get_config_value({max_sessions, Host, Port}, 10), Max_pipe_sz = ibrowse:get_config_value({max_pipeline_size, Host, Port}, 10), put(my_trace_flag, ibrowse_lib:get_trace_status(Host, Port)), put(ibrowse_trace_token, ["LB: ", Host, $:, integer_to_list(Port)]), State = #state{parent_pid = whereis(ibrowse), host = Host, port = Port, max_pipeline_size = Max_pipe_sz, max_sessions = Max_sessions}, State_1 = maybe_create_ets(State), {ok, State_1}. spawn_connection(Lb_pid, Url, Max_sessions, Max_pipeline_size, SSL_options, Process_options) when is_pid(Lb_pid), is_record(Url, url), is_integer(Max_pipeline_size), is_integer(Max_sessions) -> gen_server:call(Lb_pid, {spawn_connection, Url, Max_sessions, Max_pipeline_size, SSL_options, Process_options}). stop(Lb_pid) -> case catch gen_server:call(Lb_pid, stop) of {'EXIT', {timeout, _}} -> exit(Lb_pid, kill); ok -> ok end. %%-------------------------------------------------------------------- %% Function: handle_call/3 %% Description: Handling call messages %% Returns: {reply, Reply, State} | %% {reply, Reply, State, Timeout} | %% {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, Reply, State} | (terminate/2 is called) %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_call(stop, _From, #state{ets_tid = undefined} = State) -> gen_server:reply(_From, ok), {stop, normal, State}; handle_call(stop, _From, #state{ets_tid = Tid} = State) -> stop_all_conn_procs(Tid), gen_server:reply(_From, ok), {stop, normal, State}; handle_call(_, _From, #state{proc_state = shutting_down} = State) -> {reply, {error, shutting_down}, State}; handle_call({spawn_connection, Url, Max_sess, Max_pipe, SSL_options, Process_options}, _From, State) -> State_1 = maybe_create_ets(State), Tid = State_1#state.ets_tid, Tid_size = ets:info(Tid, size), case Tid_size >= Max_sess of true -> Reply = find_best_connection(Tid, Max_pipe), {reply, Reply, State_1#state{max_sessions = Max_sess, max_pipeline_size = Max_pipe}}; false -> {ok, Pid} = ibrowse_http_client:start({Tid, Url, SSL_options}, Process_options), Ts = os:timestamp(), ets:insert(Tid, {{1, Ts, Pid}, []}), {reply, {ok, {1, Ts, Pid}}, State_1#state{max_sessions = Max_sess, max_pipeline_size = Max_pipe}} end; handle_call(Request, _From, State) -> Reply = {unknown_request, Request}, {reply, Reply, State}. %%-------------------------------------------------------------------- %% Function: handle_cast/2 %% Description: Handling cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_cast(_Msg, State) -> {noreply, State}. %%-------------------------------------------------------------------- %% Function: handle_info/2 %% Description: Handling all non call/cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_info({trace, Bool}, #state{ets_tid = undefined} = State) -> put(my_trace_flag, Bool), {noreply, State}; handle_info({trace, Bool}, #state{ets_tid = Tid} = State) -> ets:foldl(fun({{_, Pid}, _}, Acc) when is_pid(Pid) -> catch Pid ! {trace, Bool}, Acc; (_, Acc) -> Acc end, undefined, Tid), put(my_trace_flag, Bool), {noreply, State}; handle_info(timeout, State) -> %% We can't shutdown the process immediately because a request %% might be in flight. So we first remove the entry from the %% ibrowse_lb ets table, and then shutdown a couple of seconds %% later ets:delete(ibrowse_lb, {State#state.host, State#state.port}), erlang:send_after(2000, self(), shutdown), {noreply, State#state{proc_state = shutting_down}}; handle_info(shutdown, State) -> {stop, normal, State}; handle_info(_Info, State) -> {noreply, State}. %%-------------------------------------------------------------------- %% Function: terminate/2 %% Description: Shutdown the server %% Returns: any (ignored by gen_server) %%-------------------------------------------------------------------- terminate(_Reason, #state{host = Host, port = Port, ets_tid = Tid} = _State) -> catch ets:delete(ibrowse_lb, {Host, Port}), stop_all_conn_procs(Tid), ok. stop_all_conn_procs(Tid) -> ets:foldl(fun({{_, _, Pid}, _}, Acc) -> ibrowse_http_client:stop(Pid), Acc end, [], Tid). %%-------------------------------------------------------------------- %% Func: code_change/3 %% Purpose: Convert process state when code is changed %% Returns: {ok, NewState} %%-------------------------------------------------------------------- code_change(_OldVsn, State, _Extra) -> {ok, State}. %%-------------------------------------------------------------------- %%% Internal functions %%-------------------------------------------------------------------- find_best_connection(Tid, Max_pipe) -> case ets:first(Tid) of {Spec_size, Ts, Pid} = First when Spec_size < Max_pipe -> ets:delete(Tid, First), ets:insert(Tid, {{Spec_size + 1, Ts, Pid}, []}), {ok, First}; _ -> {error, retry_later} end. maybe_create_ets(#state{ets_tid = undefined, host = Host, port = Port} = State) -> Tid = ets:new(ibrowse_lb, [public, ordered_set]), ets:insert(ibrowse_lb, #lb_pid{host_port = {Host, Port}, pid = self(), ets_tid = Tid}), State#state{ets_tid = Tid}; maybe_create_ets(State) -> State. ibrowse-4.2.2/src/ibrowse.erl0000644000232200023220000012154112625271016016512 0ustar debalancedebalance%%%------------------------------------------------------------------- %%% File : ibrowse.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : Load balancer process for HTTP client connections. %%% %%% Created : 11 Oct 2003 by Chandrashekhar Mullaparthi %%%------------------------------------------------------------------- %% @author Chandrashekhar Mullaparthi %% @copyright 2005-2014 Chandrashekhar Mullaparthi %% @doc The ibrowse application implements an HTTP 1.1 client in erlang. This %% module implements the API of the HTTP client. There is one named %% process called 'ibrowse' which assists in load balancing and maintaining configuration. There is one load balancing process per unique webserver. There is %% one process to handle one TCP connection to a webserver %% (implemented in the module ibrowse_http_client). Multiple connections to a %% webserver are setup based on the settings for each webserver. The %% ibrowse process also determines which connection to pipeline a %% certain request on. The functions to call are send_req/3, %% send_req/4, send_req/5, send_req/6. %% %%

Here are a few sample invocations.

%% %% %% ibrowse:send_req("http://intranet/messenger/", [], get). %%

%% %% ibrowse:send_req("http://www.google.com/", [], get, [], %% [{proxy_user, "XXXXX"}, %% {proxy_password, "XXXXX"}, %% {proxy_host, "proxy"}, %% {proxy_port, 8080}], 1000). %%

%% %%ibrowse:send_req("http://www.erlang.org/download/otp_src_R10B-3.tar.gz", [], get, [], %% [{proxy_user, "XXXXX"}, %% {proxy_password, "XXXXX"}, %% {proxy_host, "proxy"}, %% {proxy_port, 8080}, %% {save_response_to_file, true}], 1000). %%

%% %% ibrowse:send_req("http://www.erlang.org", [], head). %% %%

%% ibrowse:send_req("http://www.sun.com", [], options). %% %%

%% ibrowse:send_req("http://www.bbc.co.uk", [], trace). %% %%

%% ibrowse:send_req("http://www.google.com", [], get, [], %% [{stream_to, self()}]). %%
%% -module(ibrowse). -behaviour(gen_server). %%-------------------------------------------------------------------- %% Include files %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% External exports -export([start_link/0, start/0, stop/0]). %% gen_server callbacks -export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3]). %% API interface -export([ rescan_config/0, rescan_config/1, add_config/1, get_config_value/1, get_config_value/2, spawn_worker_process/1, spawn_worker_process/2, spawn_link_worker_process/1, spawn_link_worker_process/2, stop_worker_process/1, send_req/3, send_req/4, send_req/5, send_req/6, send_req_direct/4, send_req_direct/5, send_req_direct/6, send_req_direct/7, stream_next/1, stream_close/1, set_max_sessions/3, set_max_pipeline_size/3, set_max_attempts/3, set_dest/3, trace_on/0, trace_off/0, trace_on/2, trace_off/2, all_trace_off/0, show_dest_status/0, show_dest_status/1, show_dest_status/2, get_metrics/0, get_metrics/2 ]). -ifdef(debug). -compile(export_all). -endif. -import(ibrowse_lib, [ parse_url/1, get_value/3, do_trace/2 ]). -record(state, {trace = false}). -include("ibrowse.hrl"). -include_lib("stdlib/include/ms_transform.hrl"). -define(DEF_MAX_SESSIONS,10). -define(DEF_MAX_PIPELINE_SIZE,10). -define(DEF_MAX_ATTEMPTS,3). %%==================================================================== %% External functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: start_link/0 %% Description: Starts the server %%-------------------------------------------------------------------- %% @doc Starts the ibrowse process linked to the calling process. Usually invoked by the supervisor ibrowse_sup %% @spec start_link() -> {ok, pid()} start_link() -> gen_server:start_link({local, ?MODULE}, ?MODULE, [], []). %% @doc Starts the ibrowse process without linking. Useful when testing using the shell start() -> gen_server:start({local, ?MODULE}, ?MODULE, [], [{debug, []}]). %% @doc Stop the ibrowse process. Useful when testing using the shell. stop() -> case catch gen_server:call(ibrowse, stop) of {'EXIT',{noproc,_}} -> ok; Res -> Res end. %% @doc This is the basic function to send a HTTP request. %% The Status return value indicates the HTTP status code returned by the webserver %% @spec send_req(Url::string(), Headers::headerList(), Method::method()) -> response() %% headerList() = [{header(), value()}] %% header() = atom() | string() | binary() %% value() = term() %% method() = get | post | head | options | put | delete | trace | mkcol | propfind | proppatch | lock | unlock | move | copy %% Status = string() %% ResponseHeaders = [respHeader()] %% respHeader() = {headerName(), headerValue()} %% headerName() = string() %% headerValue() = string() %% response() = {ok, Status, ResponseHeaders, ResponseBody} | {ibrowse_req_id, req_id() } | {error, Reason} %% req_id() = term() %% ResponseBody = string() | {file, Filename} %% Reason = term() send_req(Url, Headers, Method) -> send_req(Url, Headers, Method, [], []). %% @doc Same as send_req/3. %% If a list is specified for the body it has to be a flat list. The body can also be a fun/0 or a fun/1.
%% If fun/0, the connection handling process will repeatdely call the fun until it returns an error or eof.
Fun() = {ok, Data} | eof

%% If fun/1, the connection handling process will repeatedly call the fun with the supplied state until it returns an error or eof.
Fun(State) = {ok, Data} | {ok, Data, NewState} | eof
%% @spec send_req(Url, Headers, Method::method(), Body::body()) -> response() %% body() = [] | string() | binary() | fun_arity_0() | {fun_arity_1(), initial_state()} %% initial_state() = term() send_req(Url, Headers, Method, Body) -> send_req(Url, Headers, Method, Body, []). %% @doc Same as send_req/4. %% For a description of SSL Options, look in the ssl manpage. %% For a description of Process Options, look in the gen_server manpage. %% If the HTTP Version to use is not specified, the default is 1.1. %%
%%
    %%
  • The host_header option is useful in the case where ibrowse is %% connecting to a component such as stunnel which then sets up a %% secure connection to a webserver. In this case, the URL supplied to %% ibrowse must have the stunnel host/port details, but that won't %% make sense to the destination webserver. This option can then be %% used to specify what should go in the Host header in %% the request.
  • %%
  • The stream_to option can be used to have the HTTP %% response streamed to a process as messages as data arrives on the %% socket. If the calling process wishes to control the rate at which %% data is received from the server, the option {stream_to, %% {process(), once}} can be specified. The calling process %% will have to invoke ibrowse:stream_next(Request_id) to %% receive the next packet.
  • %% %%
  • When both the options save_response_to_file and stream_to %% are specified, the former takes precedence.
  • %% %%
  • For the save_response_to_file option, the response body is saved to %% file only if the status code is in the 200-299 range. If not, the response body is returned %% as a string.
  • %%
  • Whenever an error occurs in the processing of a request, ibrowse will return as much %% information as it has, such as HTTP Status Code and HTTP Headers. When this happens, the response %% is of the form {error, {Reason, {stat_code, StatusCode}, HTTP_headers}}
  • %% %%
  • The inactivity_timeout option is useful when %% dealing with large response bodies and/or slow links. In these %% cases, it might be hard to estimate how long a request will take to %% complete. In such cases, the client might want to timeout if no %% data has been received on the link for a certain time interval. %% %% This value is also used to close connections which are not in use for %% the specified timeout value. %%
  • %% %%
  • %% The connect_timeout option is to specify how long the %% client process should wait for connection establishment. This is %% useful in scenarios where connections to servers are usually setup %% very fast, but responses might take much longer compared to %% connection setup. In such cases, it is better for the calling %% process to timeout faster if there is a problem (DNS lookup %% delays/failures, network routing issues, etc). The total timeout %% value specified for the request will enforced. To illustrate using %% an example: %% %% ibrowse:send_req("http://www.example.com/cgi-bin/request", [], get, [], [{connect_timeout, 100}], 1000). %% %% In the above invocation, if the connection isn't established within %% 100 milliseconds, the request will fail with %% {error, conn_failed}.
    %% If connection setup succeeds, the total time allowed for the %% request to complete will be 1000 milliseconds minus the time taken %% for connection setup. %%
  • %% %%
  • The socket_options option can be used to set %% specific options on the socket. The {active, true | false | once} %% and {packet_type, Packet_type} will be filtered out by ibrowse.
  • %% %%
  • The headers_as_is option is to enable the caller %% to send headers exactly as specified in the request without ibrowse %% adding some of its own. Required for some picky servers apparently.
  • %% %%
  • The give_raw_headers option is to enable the %% caller to get access to the raw status line and raw unparsed %% headers. Not quite sure why someone would want this, but one of my %% users asked for it, so here it is.
  • %% %%
  • The preserve_status_line option is to get the raw status line as a custom header %% in the response. The status line is returned as a tuple {ibrowse_status_line, Status_line_binary} %% If both the give_raw_headers and preserve_status_line are specified %% in a request, only the give_raw_headers is honoured.
  • %% %%
  • The preserve_chunked_encoding option enables the caller %% to receive the raw data stream when the Transfer-Encoding of the server %% response is Chunked. %%
  • %%
  • The return_raw_request option enables the caller to get the exact request which was sent by ibrowse to the server, along with the response. When this option is used, the response for synchronous requests is a 5-tuple instead of the usual 4-tuple. For asynchronous requests, the calling process gets a message {ibrowse_async_raw_req, Raw_req}. %%
  • %%
%% %% @spec send_req(Url::string(), Headers::headerList(), Method::method(), Body::body(), Options::optionList()) -> response() %% optionList() = [option()] %% option() = {max_sessions, integer()} | %% {response_format,response_format()}| %% {stream_chunk_size, integer()} | %% {max_pipeline_size, integer()} | %% {trace, boolean()} | %% {is_ssl, boolean()} | %% {ssl_options, [SSLOpt]} | %% {pool_name, atom()} | %% {proxy_host, string()} | %% {proxy_port, integer()} | %% {proxy_user, string()} | %% {proxy_password, string()} | %% {use_absolute_uri, boolean()} | %% {basic_auth, {username(), password()}} | %% {cookie, string()} | %% {content_length, integer()} | %% {content_type, string()} | %% {save_response_to_file, srtf()} | %% {stream_to, stream_to()} | %% {http_vsn, {MajorVsn, MinorVsn}} | %% {host_header, string()} | %% {inactivity_timeout, integer()} | %% {connect_timeout, integer()} | %% {socket_options, Sock_opts} | %% {transfer_encoding, {chunked, ChunkSize}} | %% {headers_as_is, boolean()} | %% {give_raw_headers, boolean()} | %% {preserve_chunked_encoding,boolean()} | %% {workaround, head_response_with_body} | %% {worker_process_options, list()} | %% {return_raw_request, true} | %% {max_attempts, integer()} %% %% stream_to() = process() | {process(), once} %% process() = pid() | atom() %% username() = string() %% password() = string() %% SSLOpt = term() %% Sock_opts = [Sock_opt] %% Sock_opt = term() %% ChunkSize = integer() %% srtf() = boolean() | filename() | {append, filename()} %% filename() = string() %% response_format() = list | binary send_req(Url, Headers, Method, Body, Options) -> send_req(Url, Headers, Method, Body, Options, 30000). %% @doc Same as send_req/5. %% All timeout values are in milliseconds. %% @spec send_req(Url, Headers::headerList(), Method::method(), Body::body(), Options::optionList(), Timeout) -> response() %% Timeout = integer() | infinity send_req(Url, Headers, Method, Body, Options, Timeout) -> case catch parse_url(Url) of #url{host = Host, port = Port, protocol = Protocol} = Parsed_url -> Lb_pid = case ets:lookup(ibrowse_lb, {Host, Port}) of [] -> get_lb_pid(Parsed_url); [#lb_pid{pid = Lb_pid_1}] -> Lb_pid_1 end, Max_sessions = get_max_sessions(Host, Port, Options), Max_pipeline_size = get_max_pipeline_size(Host, Port, Options), Max_attempts = get_max_attempts(Host, Port, Options), Options_1 = merge_options(Host, Port, Options), {SSLOptions, IsSSL} = case (Protocol == https) orelse get_value(is_ssl, Options_1, false) of false -> {[], false}; true -> {get_value(ssl_options, Options_1, []), true} end, try_routing_request(Lb_pid, Parsed_url, Max_sessions, Max_pipeline_size, {SSLOptions, IsSSL}, Headers, Method, Body, Options_1, Timeout, Timeout, os:timestamp(), Max_attempts, 0); Err -> {error, {url_parsing_failed, Err}} end. try_routing_request(Lb_pid, Parsed_url, Max_sessions, Max_pipeline_size, {SSLOptions, IsSSL}, Headers, Method, Body, Options_1, Timeout, Ori_timeout, Req_start_time, Max_attempts, Try_count) when Try_count < Max_attempts -> ProcessOptions = get_value(worker_process_options, Options_1, []), case ibrowse_lb:spawn_connection(Lb_pid, Parsed_url, Max_sessions, Max_pipeline_size, {SSLOptions, IsSSL}, ProcessOptions) of {ok, {_Pid_cur_spec_size, _, Conn_Pid}} -> case do_send_req(Conn_Pid, Parsed_url, Headers, Method, Body, Options_1, Timeout) of {error, sel_conn_closed} -> Time_now = os:timestamp(), Time_taken_so_far = trunc(round(timer:now_diff(Time_now, Req_start_time)/1000)), Time_remaining = Ori_timeout - Time_taken_so_far, Time_remaining_percent = trunc(round((Time_remaining/Ori_timeout)*100)), %% io:format("~p -- Time_remaining: ~p (~p%)~n", [self(), Time_remaining, Time_remaining_percent]), case (Time_remaining > 0) andalso (Time_remaining_percent >= 5) of true -> try_routing_request(Lb_pid, Parsed_url, Max_sessions, Max_pipeline_size, {SSLOptions, IsSSL}, Headers, Method, Body, Options_1, Time_remaining, Ori_timeout, Req_start_time, Max_attempts, Try_count + 1); false -> {error, retry_later} end; Res -> Res end; Err -> Err end; try_routing_request(_, _, _, _, _, _, _, _, _, _, _, _, _, _) -> {error, retry_later}. merge_options(Host, Port, Options) -> Config_options = get_config_value({options, Host, Port}, []) ++ get_config_value({options, global}, []), lists:foldl( fun({Key, Val}, Acc) -> case lists:keysearch(Key, 1, Options) of false -> [{Key, Val} | Acc]; _ -> Acc end end, Options, Config_options). get_lb_pid(Url) -> gen_server:call(?MODULE, {get_lb_pid, Url}). get_max_sessions(Host, Port, Options) -> get_value(max_sessions, Options, get_config_value({max_sessions, Host, Port}, default_max_sessions())). get_max_pipeline_size(Host, Port, Options) -> get_value(max_pipeline_size, Options, get_config_value({max_pipeline_size, Host, Port}, default_max_pipeline_size())). get_max_attempts(Host, Port, Options) -> get_value(max_attempts, Options, get_config_value({max_attempts, Host, Port}, default_max_attempts())). default_max_sessions() -> safe_get_env(ibrowse, default_max_sessions, ?DEF_MAX_SESSIONS). default_max_pipeline_size() -> safe_get_env(ibrowse, default_max_pipeline_size, ?DEF_MAX_PIPELINE_SIZE). default_max_attempts() -> safe_get_env(ibrowse, default_max_attempts, ?DEF_MAX_ATTEMPTS). safe_get_env(App, Key, Def_val) -> case application:get_env(App, Key) of undefined -> Def_val; {ok, Val} -> Val end. %% @doc Deprecated. Use set_max_sessions/3 and set_max_pipeline_size/3 %% for achieving the same effect. set_dest(Host, Port, [{max_sessions, Max} | T]) -> set_max_sessions(Host, Port, Max), set_dest(Host, Port, T); set_dest(Host, Port, [{max_pipeline_size, Max} | T]) -> set_max_pipeline_size(Host, Port, Max), set_dest(Host, Port, T); set_dest(Host, Port, [{trace, Bool} | T]) when Bool == true; Bool == false -> ibrowse ! {trace, true, Host, Port}, set_dest(Host, Port, T); set_dest(_Host, _Port, [H | _]) -> exit({invalid_option, H}); set_dest(_, _, []) -> ok. %% @doc Set the maximum number of connections allowed to a specific Host:Port. %% @spec set_max_sessions(Host::string(), Port::integer(), Max::integer()) -> ok set_max_sessions(Host, Port, Max) when is_integer(Max), Max > 0 -> gen_server:call(?MODULE, {set_config_value, {max_sessions, Host, Port}, Max}). %% @doc Set the maximum pipeline size for each connection to a specific Host:Port. %% @spec set_max_pipeline_size(Host::string(), Port::integer(), Max::integer()) -> ok set_max_pipeline_size(Host, Port, Max) when is_integer(Max), Max > 0 -> gen_server:call(?MODULE, {set_config_value, {max_pipeline_size, Host, Port}, Max}). %% @doc Set the maximum attempts for each connection to a specific Host:Port. %% @spec set_max_attempts(Host::string(), Port::integer(), Max::integer()) -> ok set_max_attempts(Host, Port, Max) when is_integer(Max), Max > 0 -> gen_server:call(?MODULE, {set_config_value, {max_attempts, Host, Port}, Max}). do_send_req(Conn_Pid, Parsed_url, Headers, Method, Body, Options, Timeout) -> case catch ibrowse_http_client:send_req(Conn_Pid, Parsed_url, Headers, Method, ensure_bin(Body), Options, Timeout) of {'EXIT', {timeout, _}} -> P_info = case catch erlang:process_info(Conn_Pid, [messages, message_queue_len, backtrace]) of [_|_] = Conn_Pid_info_list -> Conn_Pid_info_list; _ -> process_info_not_available end, (catch lager:error("{ibrowse_http_client, send_req, ~1000.p} gen_server call timeout.~nProcess info: ~p~n", [[Conn_Pid, Parsed_url, Headers, Method, Body, Options, Timeout], P_info])), {error, req_timedout}; {'EXIT', {normal, _}} = Ex_rsn -> (catch lager:error("{ibrowse_http_client, send_req, ~1000.p} gen_server call got ~1000.p~n", [[Conn_Pid, Parsed_url, Headers, Method, Body, Options, Timeout], Ex_rsn])), {error, req_timedout}; {error, X} when X == connection_closed; X == {send_failed, {error, enotconn}}; X == {send_failed,{error,einval}}; X == {send_failed,{error,closed}}; X == connection_closing; ((X == connection_closed_no_retry) andalso ((Method == get) orelse (Method == head))) -> {error, sel_conn_closed}; {error, connection_closed_no_retry} -> {error, connection_closed}; {error, {'EXIT', {noproc, _}}} -> {error, sel_conn_closed}; {'EXIT', Reason} -> {error, {'EXIT', Reason}}; {ok, St_code, Headers, Body} = Ret when is_binary(Body) -> case get_value(response_format, Options, list) of list -> {ok, St_code, Headers, binary_to_list(Body)}; binary -> Ret end; {ok, St_code, Headers, Body, Req} = Ret when is_binary(Body) -> case get_value(response_format, Options, list) of list -> {ok, St_code, Headers, binary_to_list(Body), Req}; binary -> Ret end; Ret -> Ret end. ensure_bin(L) when is_list(L) -> list_to_binary(L); ensure_bin(B) when is_binary(B) -> B; ensure_bin(Fun) when is_function(Fun) -> Fun; ensure_bin({Fun}) when is_function(Fun) -> Fun; ensure_bin({Fun, _} = Body) when is_function(Fun) -> Body. %% @doc Creates a HTTP client process to the specified Host:Port which %% is not part of the load balancing pool. This is useful in cases %% where some requests to a webserver might take a long time whereas %% some might take a very short time. To avoid getting these quick %% requests stuck in the pipeline behind time consuming requests, use %% this function to get a handle to a connection process.
%% Note: Calling this function only creates a worker process. No connection %% is setup. The connection attempt is made only when the first %% request is sent via any of the send_req_direct/4,5,6,7 functions.
%% Note: It is the responsibility of the calling process to control %% pipeline size on such connections. %% @spec spawn_worker_process(Url::string() | {Host::string(), Port::integer()}) -> {ok, pid()} spawn_worker_process(Args) -> spawn_worker_process(Args, []). %% @doc Same as spawn_worker_process/1 except with Erlang process options. %% @spec spawn_worker_process(Host::string(), Port::integer()) -> {ok, pid()} spawn_worker_process(Host, Port) when is_list(Host), is_integer(Port) -> %% Convert old API calls to new API format. spawn_worker_process({Host, Port}, []); spawn_worker_process(Args, Options) -> ibrowse_http_client:start(Args, Options). %% @doc Same as spawn_worker_process/1 except the the calling process %% is linked to the worker process which is spawned. %% @spec spawn_link_worker_process(Url::string() | {Host::string(), Port::integer()}) -> {ok, pid()} spawn_link_worker_process(Args) -> spawn_link_worker_process(Args, []). %% @doc Same as spawn_link_worker_process/1 except with Erlang process options. %% @spec spawn_link_worker_process(Host::string(), Port::integer()) -> {ok, pid()} spawn_link_worker_process(Host, Port) when is_list(Host), is_integer(Port) -> %% Convert old API calls to new API format. spawn_link_worker_process({Host, Port}, []); spawn_link_worker_process(Args, Options) -> ibrowse_http_client:start_link(Args, Options). %% @doc Terminate a worker process spawned using %% spawn_worker_process/2 or spawn_link_worker_process/2. Requests in %% progress will get the error response
{error, closing_on_request}
%% @spec stop_worker_process(Conn_pid::pid()) -> ok stop_worker_process(Conn_pid) -> ibrowse_http_client:stop(Conn_pid). %% @doc Same as send_req/3 except that the first argument is the PID %% returned by spawn_worker_process/2 or spawn_link_worker_process/2 send_req_direct(Conn_pid, Url, Headers, Method) -> send_req_direct(Conn_pid, Url, Headers, Method, [], []). %% @doc Same as send_req/4 except that the first argument is the PID %% returned by spawn_worker_process/2 or spawn_link_worker_process/2 send_req_direct(Conn_pid, Url, Headers, Method, Body) -> send_req_direct(Conn_pid, Url, Headers, Method, Body, []). %% @doc Same as send_req/5 except that the first argument is the PID %% returned by spawn_worker_process/2 or spawn_link_worker_process/2 send_req_direct(Conn_pid, Url, Headers, Method, Body, Options) -> send_req_direct(Conn_pid, Url, Headers, Method, Body, Options, 30000). %% @doc Same as send_req/6 except that the first argument is the PID %% returned by spawn_worker_process/2 or spawn_link_worker_process/2 send_req_direct(Conn_pid, Url, Headers, Method, Body, Options, Timeout) -> case catch parse_url(Url) of #url{host = Host, port = Port} = Parsed_url -> Options_1 = merge_options(Host, Port, Options), case do_send_req(Conn_pid, Parsed_url, Headers, Method, Body, Options_1, Timeout) of {error, {'EXIT', {noproc, _}}} -> {error, worker_is_dead}; Ret -> Ret end; Err -> {error, {url_parsing_failed, Err}} end. %% @doc Tell ibrowse to stream the next chunk of data to the %% caller. Should be used in conjunction with the %% stream_to option %% @spec stream_next(Req_id :: req_id()) -> ok | {error, unknown_req_id} stream_next(Req_id) -> case ets:lookup(ibrowse_stream, {req_id_pid, Req_id}) of [] -> {error, unknown_req_id}; [{_, Pid}] -> catch Pid ! {stream_next, Req_id}, ok end. %% @doc Tell ibrowse to close the connection associated with the %% specified stream. Should be used in conjunction with the %% stream_to option. Note that all requests in progress on %% the connection which is serving this Req_id will be aborted, and an %% error returned. %% @spec stream_close(Req_id :: req_id()) -> ok | {error, unknown_req_id} stream_close(Req_id) -> case ets:lookup(ibrowse_stream, {req_id_pid, Req_id}) of [] -> {error, unknown_req_id}; [{_, Pid}] -> catch Pid ! {stream_close, Req_id}, ok end. %% @doc Turn tracing on for the ibrowse process trace_on() -> ibrowse ! {trace, true}. %% @doc Turn tracing off for the ibrowse process trace_off() -> ibrowse ! {trace, false}. %% @doc Turn tracing on for all connections to the specified HTTP %% server. Host is whatever is specified as the domain name in the URL %% @spec trace_on(Host, Port) -> ok %% Host = string() %% Port = integer() trace_on(Host, Port) -> ibrowse ! {trace, true, Host, Port}, ok. %% @doc Turn tracing OFF for all connections to the specified HTTP %% server. %% @spec trace_off(Host, Port) -> ok trace_off(Host, Port) -> ibrowse ! {trace, false, Host, Port}, ok. %% @doc Turn Off ALL tracing %% @spec all_trace_off() -> ok all_trace_off() -> ibrowse ! all_trace_off, ok. %% @doc Shows some internal information about load balancing. Info %% about workers spawned using spawn_worker_process/2 or %% spawn_link_worker_process/2 is not included. show_dest_status() -> io:format("~-40.40s | ~-5.5s | ~-10.10s | ~s~n", ["Server:port", "ETS", "Num conns", "LB Pid"]), io:format("~80.80.=s~n", [""]), Metrics = get_metrics(), lists:foreach( fun({Host, Port, {Lb_pid, _, Tid, Size, _}}) -> io:format("~40.40s | ~-5.5s | ~-5.5s | ~p~n", [Host ++ ":" ++ integer_to_list(Port), integer_to_list(Tid), integer_to_list(Size), Lb_pid]) end, Metrics). show_dest_status(Url) -> #url{host = Host, port = Port} = ibrowse_lib:parse_url(Url), show_dest_status(Host, Port). %% @doc Shows some internal information about load balancing to a %% specified Host:Port. Info about workers spawned using %% spawn_worker_process/2 or spawn_link_worker_process/2 is not %% included. show_dest_status(Host, Port) -> case get_metrics(Host, Port) of {Lb_pid, MsgQueueSize, Tid, Size, {{First_p_sz, First_p_sz}, {Last_p_sz, Last_p_sz}}} -> io:format("Load Balancer Pid : ~p~n" "LB process msg q size : ~p~n" "LB ETS table id : ~p~n" "Num Connections : ~p~n" "Smallest pipeline : ~p~n" "Largest pipeline : ~p~n", [Lb_pid, MsgQueueSize, Tid, Size, First_p_sz, Last_p_sz]); _Err -> io:format("Metrics not available~n", []) end. get_metrics() -> Dests = lists:filter( fun(#lb_pid{host_port = {Host, Port}}) when is_list(Host), is_integer(Port) -> true; (_) -> false end, ets:tab2list(ibrowse_lb)), lists:foldl( fun(#lb_pid{host_port = {X_host, X_port}}, X_acc) -> case get_metrics(X_host, X_port) of {_, _, _, _, _} = X_res -> [{X_host, X_port, X_res} | X_acc]; _X_res -> X_acc end end, [], Dests). get_metrics(Host, Port) -> case ets:lookup(ibrowse_lb, {Host, Port}) of [] -> no_active_processes; [#lb_pid{pid = Lb_pid, ets_tid = Tid}] -> MsgQueueSize = case (catch process_info(Lb_pid, message_queue_len)) of {message_queue_len, Msg_q_len} -> Msg_q_len; _ -> -1 end, case Tid of undefined -> {Lb_pid, MsgQueueSize, undefined, 0, {{0, 0}, {0, 0}}}; _ -> try Size = ets:info(Tid, size), case Size of 0 -> {Lb_pid, MsgQueueSize, Tid, 0, {{0, 0}, {0, 0}}}; _ -> {First_p_sz, _, _} = ets:first(Tid), {Last_p_sz, _, _} = ets:last(Tid), {Lb_pid, MsgQueueSize, Tid, Size, {{First_p_sz, First_p_sz}, {Last_p_sz, Last_p_sz}}} end catch _:_Err -> not_available end end end. %% @doc Clear current configuration for ibrowse and load from the file %% ibrowse.conf in the IBROWSE_EBIN/../priv directory. Current %% configuration is cleared only if the ibrowse.conf file is readable %% using file:consult/1 rescan_config() -> gen_server:call(?MODULE, rescan_config). %% Clear current configuration for ibrowse and load from the specified %% file. Current configuration is cleared only if the specified %% file is readable using file:consult/1 rescan_config([{_,_}|_]=Terms) -> gen_server:call(?MODULE, {rescan_config_terms, Terms}); rescan_config(File) when is_list(File) -> gen_server:call(?MODULE, {rescan_config, File}). %% @doc Add additional configuration elements at runtime. add_config([{_,_}|_]=Terms) -> gen_server:call(?MODULE, {add_config_terms, Terms}). %%==================================================================== %% Server functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: init/1 %% Description: Initiates the server %% Returns: {ok, State} | %% {ok, State, Timeout} | %% ignore | %% {stop, Reason} %%-------------------------------------------------------------------- init(_) -> process_flag(trap_exit, true), State = #state{}, put(my_trace_flag, State#state.trace), put(ibrowse_trace_token, "ibrowse"), ibrowse_lb = ets:new(ibrowse_lb, [named_table, public, {keypos, 2}]), ibrowse_conf = ets:new(ibrowse_conf, [named_table, protected, {keypos, 2}]), ibrowse_stream = ets:new(ibrowse_stream, [named_table, public]), import_config(), {ok, #state{}}. import_config() -> case code:priv_dir(ibrowse) of {error, _} -> ok; PrivDir -> Filename = filename:join(PrivDir, "ibrowse.conf"), import_config(Filename) end. import_config(Filename) -> case file:consult(Filename) of {ok, Terms} -> apply_config(Terms); _Err -> ok end. apply_config(Terms) -> ets:delete_all_objects(ibrowse_conf), insert_config(Terms). insert_config(Terms) -> Fun = fun({dest, Host, Port, MaxSess, MaxPipe, Options}) when is_list(Host), is_integer(Port), is_integer(MaxSess), MaxSess > 0, is_integer(MaxPipe), MaxPipe > 0, is_list(Options) -> I = [{{max_sessions, Host, Port}, MaxSess}, {{max_pipeline_size, Host, Port}, MaxPipe}, {{options, Host, Port}, Options}], lists:foreach( fun({X, Y}) -> ets:insert(ibrowse_conf, #ibrowse_conf{key = X, value = Y}) end, I); ({K, V}) -> ets:insert(ibrowse_conf, #ibrowse_conf{key = K, value = V}); (X) -> io:format("Skipping unrecognised term: ~p~n", [X]) end, lists:foreach(Fun, Terms). %% @doc Internal export get_config_value(Key) -> try [#ibrowse_conf{value = V}] = ets:lookup(ibrowse_conf, Key), V catch error:badarg -> throw({error, ibrowse_not_running}) end. %% @doc Internal export get_config_value(Key, DefVal) -> try case ets:lookup(ibrowse_conf, Key) of [] -> DefVal; [#ibrowse_conf{value = V}] -> V end catch error:badarg -> throw({error, ibrowse_not_running}) end. set_config_value(Key, Val) -> ets:insert(ibrowse_conf, #ibrowse_conf{key = Key, value = Val}). %%-------------------------------------------------------------------- %% Function: handle_call/3 %% Description: Handling call messages %% Returns: {reply, Reply, State} | %% {reply, Reply, State, Timeout} | %% {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, Reply, State} | (terminate/2 is called) %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_call({get_lb_pid, #url{host = Host, port = Port} = Url}, _From, State) -> Pid = do_get_connection(Url, ets:lookup(ibrowse_lb, {Host, Port})), {reply, Pid, State}; handle_call(stop, _From, State) -> do_trace("IBROWSE shutting down~n", []), ets:foldl(fun(#lb_pid{pid = Pid}, Acc) -> ibrowse_lb:stop(Pid), Acc end, [], ibrowse_lb), {stop, normal, ok, State}; handle_call({set_config_value, Key, Val}, _From, State) -> set_config_value(Key, Val), {reply, ok, State}; handle_call(rescan_config, _From, State) -> Ret = (catch import_config()), {reply, Ret, State}; handle_call({rescan_config, File}, _From, State) -> Ret = (catch import_config(File)), {reply, Ret, State}; handle_call({rescan_config_terms, Terms}, _From, State) -> Ret = (catch apply_config(Terms)), {reply, Ret, State}; handle_call({add_config_terms, Terms}, _From, State) -> Ret = (catch insert_config(Terms)), {reply, Ret, State}; handle_call(Request, _From, State) -> Reply = {unknown_request, Request}, {reply, Reply, State}. %%-------------------------------------------------------------------- %% Function: handle_cast/2 %% Description: Handling cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_cast(_Msg, State) -> {noreply, State}. %%-------------------------------------------------------------------- %% Function: handle_info/2 %% Description: Handling all non call/cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_info(all_trace_off, State) -> Mspec = [{{ibrowse_conf,{trace,'$1','$2'},true},[],[{{'$1','$2'}}]}], Trace_on_dests = ets:select(ibrowse_conf, Mspec), Fun = fun(#lb_pid{host_port = {H, P}, pid = Pid}, _) -> case lists:member({H, P}, Trace_on_dests) of false -> ok; true -> catch Pid ! {trace, false} end; (_, Acc) -> Acc end, ets:foldl(Fun, undefined, ibrowse_lb), ets:select_delete(ibrowse_conf, [{{ibrowse_conf,{trace,'$1','$2'},true},[],['true']}]), {noreply, State}; handle_info({trace, Bool}, State) -> put(my_trace_flag, Bool), {noreply, State}; handle_info({trace, Bool, Host, Port}, State) -> Fun = fun(#lb_pid{host_port = {H, P}, pid = Pid}, _) when H == Host, P == Port -> catch Pid ! {trace, Bool}; (_, Acc) -> Acc end, ets:foldl(Fun, undefined, ibrowse_lb), ets:insert(ibrowse_conf, #ibrowse_conf{key = {trace, Host, Port}, value = Bool}), {noreply, State}; handle_info(_Info, State) -> {noreply, State}. %%-------------------------------------------------------------------- %% Function: terminate/2 %% Description: Shutdown the server %% Returns: any (ignored by gen_server) %%-------------------------------------------------------------------- terminate(_Reason, _State) -> ok. %%-------------------------------------------------------------------- %% Func: code_change/3 %% Purpose: Convert process state when code is changed %% Returns: {ok, NewState} %%-------------------------------------------------------------------- code_change(_OldVsn, State, _Extra) -> {ok, State}. %%-------------------------------------------------------------------- %%% Internal functions %%-------------------------------------------------------------------- do_get_connection(#url{host = Host, port = Port}, []) -> {ok, Pid} = ibrowse_lb:start_link([Host, Port]), Pid; do_get_connection(_Url, [#lb_pid{pid = Pid}]) -> Pid. ibrowse-4.2.2/src/Emakefile.src0000644000232200023220000000023612625271016016724 0ustar debalancedebalance'../src/ibrowse'. '../src/ibrowse_http_client'. '../src/ibrowse_app'. '../src/ibrowse_sup'. '../src/ibrowse_lib'. '../src/ibrowse_lb'. '../src/ibrowse_test'. ibrowse-4.2.2/src/ibrowse.app.src0000644000232200023220000000064212625271016017274 0ustar debalancedebalance{application, ibrowse, [{description, "Erlang HTTP client application"}, {vsn, "4.2.2"}, {registered, [ibrowse_sup, ibrowse]}, {applications, [kernel,stdlib]}, {env, []}, {mod, {ibrowse_app, []}}, {maintainers, ["Chandrashekhar Mullaparthi"]}, {licenses, ["GPLv2", "BSD"]}, {links, [{"Github", "https://github.com/cmullaparthi/ibrowse"}]} ] }. ibrowse-4.2.2/src/ibrowse_socks5.erl0000644000232200023220000000676712625271016020015 0ustar debalancedebalance% Licensed under the Apache License, Version 2.0 (the "License"); you may not % use this file except in compliance with the License. You may obtain a copy of % the License at % % http://www.apache.org/licenses/LICENSE-2.0 % % Unless required by applicable law or agreed to in writing, software % distributed under the License is distributed on an "AS IS" BASIS, WITHOUT % WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. See the % License for the specific language governing permissions and limitations under % the License. -module(ibrowse_socks5). -define(VERSION, 5). -define(CONNECT, 1). -define(NO_AUTH, 0). -define(USERPASS, 2). -define(UNACCEPTABLE, 16#FF). -define(RESERVED, 0). -define(ATYP_IPV4, 1). -define(ATYP_DOMAINNAME, 3). -define(ATYP_IPV6, 4). -define(SUCCEEDED, 0). -export([connect/5]). -import(ibrowse_lib, [get_value/2, get_value/3]). connect(Host, Port, Options, SockOptions, Timeout) -> Socks5Host = get_value(socks5_host, Options), Socks5Port = get_value(socks5_port, Options), case gen_tcp:connect(Socks5Host, Socks5Port, SockOptions, Timeout) of {ok, Socket} -> case handshake(Socket, Options) of ok -> case connect(Host, Port, Socket) of ok -> {ok, Socket}; Else -> gen_tcp:close(Socket), Else end; Else -> gen_tcp:close(Socket), Else end; Else -> Else end. handshake(Socket, Options) when is_port(Socket) -> {Handshake, Success} = case get_value(socks5_user, Options, <<>>) of <<>> -> {<>, ?NO_AUTH}; User -> Password = get_value(socks5_password, Options, <<>>), {<>, ?USERPASS} end, ok = gen_tcp:send(Socket, Handshake), case gen_tcp:recv(Socket, 0) of {ok, <>} -> ok; {ok, <>} -> {error, unacceptable}; {error, Reason} -> {error, Reason} end. connect(Host, Port, Via) when is_list(Host) -> connect(list_to_binary(Host), Port, Via); connect(Host, Port, Via) when is_binary(Host), is_integer(Port), is_port(Via) -> {AddressType, Address} = case inet:parse_address(binary_to_list(Host)) of {ok, {IP1, IP2, IP3, IP4}} -> {?ATYP_IPV4, <>}; {ok, {IP1, IP2, IP3, IP4, IP5, IP6, IP7, IP8}} -> {?ATYP_IPV6, <>}; _ -> HostLength = byte_size(Host), {?ATYP_DOMAINNAME, <>} end, ok = gen_tcp:send(Via, <>), case gen_tcp:recv(Via, 0) of {ok, <>} -> ok; {ok, <>} -> {error, rep(Rep)}; {error, Reason} -> {error, Reason} end. rep(0) -> succeeded; rep(1) -> server_fail; rep(2) -> disallowed_by_ruleset; rep(3) -> network_unreachable; rep(4) -> host_unreachable; rep(5) -> connection_refused; rep(6) -> ttl_expired; rep(7) -> command_not_supported; rep(8) -> address_type_not_supported. ibrowse-4.2.2/src/ibrowse_lib.erl0000644000232200023220000003676312625271016017353 0ustar debalancedebalance%%% File : ibrowse_lib.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : %%% Created : 27 Feb 2004 by Chandrashekhar Mullaparthi %% @doc Module with a few useful functions -module(ibrowse_lib). -author('chandru'). -ifdef(debug). -compile(export_all). -endif. -include("ibrowse.hrl"). -ifdef(EUNIT). -include_lib("eunit/include/eunit.hrl"). -endif. -export([ get_trace_status/2, do_trace/2, do_trace/3, url_encode/1, decode_rfc822_date/1, status_code/1, encode_base64/1, decode_base64/1, get_value/2, get_value/3, parse_url/1, printable_date/0, printable_date/1 ]). get_trace_status(Host, Port) -> ibrowse:get_config_value({trace, Host, Port}, false). %% @doc URL-encodes a string based on RFC 1738. Returns a flat list. %% @spec url_encode(Str) -> UrlEncodedStr %% Str = string() %% UrlEncodedStr = string() url_encode(Str) when is_list(Str) -> url_encode_char(lists:reverse(Str), []). url_encode_char([X | T], Acc) when X >= $0, X =< $9 -> url_encode_char(T, [X | Acc]); url_encode_char([X | T], Acc) when X >= $a, X =< $z -> url_encode_char(T, [X | Acc]); url_encode_char([X | T], Acc) when X >= $A, X =< $Z -> url_encode_char(T, [X | Acc]); url_encode_char([X | T], Acc) when X == $-; X == $_; X == $. -> url_encode_char(T, [X | Acc]); url_encode_char([32 | T], Acc) -> url_encode_char(T, [$+ | Acc]); url_encode_char([X | T], Acc) -> url_encode_char(T, [$%, d2h(X bsr 4), d2h(X band 16#0f) | Acc]); url_encode_char([], Acc) -> Acc. d2h(N) when N<10 -> N+$0; d2h(N) -> N+$a-10. decode_rfc822_date(String) when is_list(String) -> case catch decode_rfc822_date_1(string:tokens(String, ", \t\r\n")) of {'EXIT', _} -> {error, invalid_date}; Res -> Res end. % TODO: Have to handle the Zone decode_rfc822_date_1([_,DayInt,Month,Year, Time,Zone]) -> decode_rfc822_date_1([DayInt,Month,Year, Time,Zone]); decode_rfc822_date_1([Day,Month,Year, Time,_Zone]) -> DayI = list_to_integer(Day), MonthI = month_int(Month), YearI = list_to_integer(Year), TimeTup = case string:tokens(Time, ":") of [H,M] -> {list_to_integer(H), list_to_integer(M), 0}; [H,M,S] -> {list_to_integer(H), list_to_integer(M), list_to_integer(S)} end, {{YearI,MonthI,DayI}, TimeTup}. month_int("Jan") -> 1; month_int("Feb") -> 2; month_int("Mar") -> 3; month_int("Apr") -> 4; month_int("May") -> 5; month_int("Jun") -> 6; month_int("Jul") -> 7; month_int("Aug") -> 8; month_int("Sep") -> 9; month_int("Oct") -> 10; month_int("Nov") -> 11; month_int("Dec") -> 12. %% @doc Given a status code, returns an atom describing the status code. %% @spec status_code(StatusCode::status_code()) -> StatusDescription %% status_code() = string() | integer() %% StatusDescription = atom() status_code(100) -> continue; status_code(101) -> switching_protocols; status_code(102) -> processing; status_code(200) -> ok; status_code(201) -> created; status_code(202) -> accepted; status_code(203) -> non_authoritative_information; status_code(204) -> no_content; status_code(205) -> reset_content; status_code(206) -> partial_content; status_code(207) -> multi_status; status_code(300) -> multiple_choices; status_code(301) -> moved_permanently; status_code(302) -> found; status_code(303) -> see_other; status_code(304) -> not_modified; status_code(305) -> use_proxy; status_code(306) -> unused; status_code(307) -> temporary_redirect; status_code(400) -> bad_request; status_code(401) -> unauthorized; status_code(402) -> payment_required; status_code(403) -> forbidden; status_code(404) -> not_found; status_code(405) -> method_not_allowed; status_code(406) -> not_acceptable; status_code(407) -> proxy_authentication_required; status_code(408) -> request_timeout; status_code(409) -> conflict; status_code(410) -> gone; status_code(411) -> length_required; status_code(412) -> precondition_failed; status_code(413) -> request_entity_too_large; status_code(414) -> request_uri_too_long; status_code(415) -> unsupported_media_type; status_code(416) -> requested_range_not_satisfiable; status_code(417) -> expectation_failed; status_code(422) -> unprocessable_entity; status_code(423) -> locked; status_code(424) -> failed_dependency; status_code(500) -> internal_server_error; status_code(501) -> not_implemented; status_code(502) -> bad_gateway; status_code(503) -> service_unavailable; status_code(504) -> gateway_timeout; status_code(505) -> http_version_not_supported; status_code(507) -> insufficient_storage; status_code(X) when is_list(X) -> status_code(list_to_integer(X)); status_code(_) -> unknown_status_code. %% @doc Implements the base64 encoding algorithm. The output data type matches in the input data type. %% @spec encode_base64(In) -> Out %% In = string() | binary() %% Out = string() | binary() encode_base64(List) when is_list(List) -> binary_to_list(base64:encode(List)); encode_base64(Bin) when is_binary(Bin) -> base64:encode(Bin). %% @doc Implements the base64 decoding algorithm. The output data type matches in the input data type. %% @spec decode_base64(In) -> Out | exit({error, invalid_input}) %% In = string() | binary() %% Out = string() | binary() decode_base64(List) when is_list(List) -> binary_to_list(base64:decode(List)); decode_base64(Bin) when is_binary(Bin) -> base64:decode(Bin). get_value(Tag, TVL, DefVal) -> case lists:keysearch(Tag, 1, TVL) of false -> DefVal; {value, {_, Val}} -> Val end. get_value(Tag, TVL) -> {value, {_, V}} = lists:keysearch(Tag,1,TVL), V. parse_url(Url) -> try case parse_url(Url, get_protocol, #url{abspath=Url}, []) of #url{host_type = undefined, host = Host} = UrlRec -> case inet_parse:address(Host) of {ok, {_, _, _, _, _, _, _, _}} -> UrlRec#url{host_type = ipv6_address}; {ok, {_, _, _, _}} -> UrlRec#url{host_type = ipv4_address}; _ -> UrlRec#url{host_type = hostname} end; #url{} = UrlRec -> UrlRec; _ -> {error, invalid_uri} end catch _:_ -> {error, invalid_uri} end. parse_url([$:, $/, $/ | _], get_protocol, Url, []) -> {invalid_uri_1, Url}; parse_url([$:, $/, $/ | T], get_protocol, Url, TmpAcc) -> Prot = list_to_existing_atom(lists:reverse(TmpAcc)), parse_url(T, get_username, Url#url{protocol = Prot}, []); parse_url([H | T], get_username, Url, TmpAcc) when H == $/; H == $? -> Path = case H of $/ -> [$/ | T]; $? -> [$/, $? | T] end, %% No username/password. No port number Url#url{host = lists:reverse(TmpAcc), port = default_port(Url#url.protocol), path = Path}; parse_url([$: | T], get_username, Url, TmpAcc) -> %% It is possible that no username/password has been %% specified. But we'll continue with the assumption that there is %% a username/password. If we encounter a '@' later on, there is a %% username/password indeed. If we encounter a '/', it was %% actually the hostname parse_url(T, get_password, Url#url{username = lists:reverse(TmpAcc)}, []); parse_url([$@ | T], get_username, Url, TmpAcc) -> parse_url(T, get_host, Url#url{username = lists:reverse(TmpAcc), password = ""}, []); parse_url([$[ | T], get_username, Url, []) -> % IPv6 address literals are enclosed by square brackets: % http://www.ietf.org/rfc/rfc2732.txt parse_url(T, get_ipv6_address, Url#url{host_type = ipv6_address}, []); parse_url([$[ | T], get_username, _Url, TmpAcc) -> {error, {invalid_username_or_host, lists:reverse(TmpAcc) ++ "[" ++ T}}; parse_url([$[ | _], get_password, _Url, []) -> {error, missing_password}; parse_url([$[ | T], get_password, Url, TmpAcc) -> % IPv6 address literals are enclosed by square brackets: % http://www.ietf.org/rfc/rfc2732.txt parse_url(T, get_ipv6_address, Url#url{host_type = ipv6_address, password = lists:reverse(TmpAcc)}, []); parse_url([$@ | T], get_password, Url, TmpAcc) -> parse_url(T, get_host, Url#url{password = lists:reverse(TmpAcc)}, []); parse_url([H | T], get_password, Url, TmpAcc) when H == $/; H == $? -> %% Ok, what we thought was the username/password was the hostname %% and portnumber #url{username=User} = Url, Port = list_to_integer(lists:reverse(TmpAcc)), Path = case H of $/ -> [$/ | T]; $? -> [$/, $? | T] end, Url#url{host = User, port = Port, username = undefined, password = undefined, path = Path}; parse_url([$] | T], get_ipv6_address, #url{protocol = Prot} = Url, TmpAcc) -> Addr = lists:reverse(TmpAcc), case inet_parse:address(Addr) of {ok, {_, _, _, _, _, _, _, _}} -> Url2 = Url#url{host = Addr, port = default_port(Prot)}, case T of [$: | T2] -> parse_url(T2, get_port, Url2, []); [$/ | T2] -> Url2#url{path = [$/ | T2]}; [$? | T2] -> Url2#url{path = [$/, $? | T2]}; [] -> Url2#url{path = "/"}; _ -> {error, {invalid_host, "[" ++ Addr ++ "]" ++ T}} end; _ -> {error, {invalid_ipv6_address, Addr}} end; parse_url([$[ | T], get_host, #url{} = Url, []) -> parse_url(T, get_ipv6_address, Url#url{host_type = ipv6_address}, []); parse_url([$: | T], get_host, #url{} = Url, TmpAcc) -> parse_url(T, get_port, Url#url{host = lists:reverse(TmpAcc)}, []); parse_url([H | T], get_host, #url{protocol=Prot} = Url, TmpAcc) when H == $/; H == $? -> Path = case H of $/ -> [$/ | T]; $? -> [$/, $? | T] end, Url#url{host = lists:reverse(TmpAcc), port = default_port(Prot), path = Path}; parse_url([H | T], get_port, #url{protocol=Prot} = Url, TmpAcc) when H == $/; H == $? -> Path = case H of $/ -> [$/ | T]; $? -> [$/, $? | T] end, Port = case TmpAcc of [] -> default_port(Prot); _ -> list_to_integer(lists:reverse(TmpAcc)) end, Url#url{port = Port, path = Path}; parse_url([H | T], State, Url, TmpAcc) -> parse_url(T, State, Url, [H | TmpAcc]); parse_url([], get_host, Url, TmpAcc) when TmpAcc /= [] -> Url#url{host = lists:reverse(TmpAcc), port = default_port(Url#url.protocol), path = "/"}; parse_url([], get_username, Url, TmpAcc) when TmpAcc /= [] -> Url#url{host = lists:reverse(TmpAcc), port = default_port(Url#url.protocol), path = "/"}; parse_url([], get_port, #url{protocol=Prot} = Url, TmpAcc) -> Port = case TmpAcc of [] -> default_port(Prot); _ -> list_to_integer(lists:reverse(TmpAcc)) end, Url#url{port = Port, path = "/"}; parse_url([], get_password, Url, TmpAcc) -> %% Ok, what we thought was the username/password was the hostname %% and portnumber #url{username=User} = Url, Port = case TmpAcc of [] -> default_port(Url#url.protocol); _ -> list_to_integer(lists:reverse(TmpAcc)) end, Url#url{host = User, port = Port, username = undefined, password = undefined, path = "/"}; parse_url([], State, Url, TmpAcc) -> {invalid_uri_2, State, Url, TmpAcc}. default_port(socks5) -> 1080; default_port(http) -> 80; default_port(https) -> 443; default_port(ftp) -> 21. printable_date() -> printable_date(os:timestamp()). printable_date(Now) -> {{Y,Mo,D},{H, M, S}} = calendar:now_to_local_time(Now), {_,_,MicroSecs} = Now, [integer_to_list(Y), $-, integer_to_list(Mo), $-, integer_to_list(D), $_, integer_to_list(H), $:, integer_to_list(M), $:, integer_to_list(S), $:, integer_to_list(MicroSecs div 1000)]. do_trace(Fmt, Args) -> do_trace(get(my_trace_flag), Fmt, Args). -ifdef(DEBUG). do_trace(_, Fmt, Args) -> io:format("~s -- (~s) - "++Fmt, [printable_date(), get(ibrowse_trace_token) | Args]). -else. do_trace(true, Fmt, Args) -> io:format("~s -- (~s) - "++Fmt, [printable_date(), get(ibrowse_trace_token) | Args]); do_trace(_, _, _) -> ok. -endif. -ifdef(EUNIT). parse_url_test() -> Urls = [{"http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:80/index.html", #url{abspath = "http://[FEDC:BA98:7654:3210:FEDC:BA98:7654:3210]:80/index.html", host = "FEDC:BA98:7654:3210:FEDC:BA98:7654:3210", port = 80, protocol = http, path = "/index.html", host_type = ipv6_address}}, {"http://[1080:0:0:0:8:800:200C:417A]/index.html", #url{abspath = "http://[1080:0:0:0:8:800:200C:417A]/index.html", host_type = ipv6_address, port = 80, protocol = http, host = "1080:0:0:0:8:800:200C:417A", path = "/index.html"}}, {"http://[3ffe:2a00:100:7031::1]", #url{abspath = "http://[3ffe:2a00:100:7031::1]", host_type = ipv6_address, port = 80, protocol = http, host = "3ffe:2a00:100:7031::1", path = "/"}}, {"http://[1080::8:800:200C:417A]/foo", #url{abspath = "http://[1080::8:800:200C:417A]/foo", host_type = ipv6_address, port = 80, protocol = http, host = "1080::8:800:200C:417A", path = "/foo"}}, {"http://[::192.9.5.5]/ipng", #url{abspath = "http://[::192.9.5.5]/ipng", host_type = ipv6_address, port = 80, protocol = http, host = "::192.9.5.5", path = "/ipng"}}, {"http://[::FFFF:129.144.52.38]:80/index.html", #url{abspath = "http://[::FFFF:129.144.52.38]:80/index.html", host_type = ipv6_address, port = 80, protocol = http, host = "::FFFF:129.144.52.38", path = "/index.html"}}, {"http://[2010:836B:4179::836B:4179]", #url{abspath = "http://[2010:836B:4179::836B:4179]", host_type = ipv6_address, port = 80, protocol = http, host = "2010:836B:4179::836B:4179", path = "/"}} ], lists:foreach( fun({Url, Expected_result}) -> ?assertMatch(Expected_result, parse_url(Url)) end, Urls). -endif. ibrowse-4.2.2/src/ibrowse_app.erl0000644000232200023220000000422012625271016017344 0ustar debalancedebalance%%%------------------------------------------------------------------- %%% File : ibrowse_app.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : %%% %%% Created : 15 Oct 2003 by Chandrashekhar Mullaparthi %%%------------------------------------------------------------------- -module(ibrowse_app). -behaviour(application). %%-------------------------------------------------------------------- %% Include files %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% External exports %%-------------------------------------------------------------------- -export([ start/2, stop/1 ]). %%-------------------------------------------------------------------- %% Internal exports %%-------------------------------------------------------------------- -export([ ]). %%-------------------------------------------------------------------- %% Macros %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% Records %%-------------------------------------------------------------------- %%==================================================================== %% External functions %%==================================================================== %%-------------------------------------------------------------------- %% Func: start/2 %% Returns: {ok, Pid} | %% {ok, Pid, State} | %% {error, Reason} %%-------------------------------------------------------------------- start(_Type, _StartArgs) -> case ibrowse_sup:start_link() of {ok, Pid} -> {ok, Pid}; Error -> Error end. %%-------------------------------------------------------------------- %% Func: stop/1 %% Returns: any %%-------------------------------------------------------------------- stop(_State) -> ok. %%==================================================================== %% Internal functions %%==================================================================== ibrowse-4.2.2/src/ibrowse_sup.erl0000644000232200023220000000474012625271016017402 0ustar debalancedebalance%%%------------------------------------------------------------------- %%% File : ibrowse_sup.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : %%% %%% Created : 15 Oct 2003 by Chandrashekhar Mullaparthi %%%------------------------------------------------------------------- -module(ibrowse_sup). -behaviour(supervisor). %%-------------------------------------------------------------------- %% Include files %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% External exports %%-------------------------------------------------------------------- -export([ start_link/0 ]). %%-------------------------------------------------------------------- %% Internal exports %%-------------------------------------------------------------------- -export([ init/1 ]). %%-------------------------------------------------------------------- %% Macros %%-------------------------------------------------------------------- -define(SERVER, ?MODULE). %%-------------------------------------------------------------------- %% Records %%-------------------------------------------------------------------- %%==================================================================== %% External functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: start_link/0 %% Description: Starts the supervisor %%-------------------------------------------------------------------- start_link() -> supervisor:start_link({local, ?SERVER}, ?MODULE, []). %%==================================================================== %% Server functions %%==================================================================== %%-------------------------------------------------------------------- %% Func: init/1 %% Returns: {ok, {SupFlags, [ChildSpec]}} | %% ignore | %% {error, Reason} %%-------------------------------------------------------------------- init([]) -> AChild = {ibrowse,{ibrowse,start_link,[]}, permanent,2000,worker,[ibrowse, ibrowse_http_client]}, {ok,{{one_for_all,10,1}, [AChild]}}. %%==================================================================== %% Internal functions %%==================================================================== ibrowse-4.2.2/src/ibrowse_http_client.erl0000644000232200023220000025626612625271016021124 0ustar debalancedebalance%%%------------------------------------------------------------------- %%% File : ibrowse_http_client.erl %%% Author : Chandrashekhar Mullaparthi %%% Description : The name says it all %%% %%% Created : 11 Oct 2003 by Chandrashekhar Mullaparthi %%%------------------------------------------------------------------- -module(ibrowse_http_client). -behaviour(gen_server). %%-------------------------------------------------------------------- %% Include files %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% External exports -export([ start_link/1, start_link/2, start/1, start/2, stop/1, send_req/7 ]). -ifdef(debug). -compile(export_all). -endif. %% gen_server callbacks -export([ init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3 ]). -include("ibrowse.hrl"). -include_lib("kernel/include/inet.hrl"). -record(state, {host, port, connect_timeout, inactivity_timer_ref, use_proxy = false, proxy_auth_basic, ssl_options = [], is_ssl = false, socket, proxy_tunnel_setup = false, tunnel_setup_queue = [], reqs=queue:new(), cur_req, status=idle, http_status_code, reply_buffer = <<>>, rep_buf_size=0, streamed_size = 0, recvd_headers=[], status_line, raw_headers, is_closing, content_length, deleted_crlf = false, transfer_encoding, chunk_size, chunk_size_buffer = <<>>, recvd_chunk_size, interim_reply_sent = false, lb_ets_tid, cur_pipeline_size = 0, prev_req_id, proc_state }). -record(request, {url, method, options, from, stream_to, caller_controls_socket = false, caller_socket_options = [], req_id, stream_chunk_size, save_response_to_file = false, tmp_file_name, tmp_file_fd, preserve_chunked_encoding, response_format, timer_ref, raw_req}). -import(ibrowse_lib, [ get_value/2, get_value/3, do_trace/2 ]). -define(DEFAULT_STREAM_CHUNK_SIZE, 1024*1024). -define(dec2hex(X), erlang:integer_to_list(X, 16)). %% Macros to prevent spelling mistakes causing bugs -define(dont_retry_pipelined_requests, dont_retry_pipelined_requests). -define(can_retry_pipelined_requests, can_retry_pipelined_requests). -define(dead_proc_walking, dead_proc_walking). %%==================================================================== %% External functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: start_link/0 %% Description: Starts the server %%-------------------------------------------------------------------- start(Args) -> start(Args, []). start(Args, Options) -> gen_server:start(?MODULE, Args, Options). start_link(Args) -> start_link(Args, []). start_link(Args, Options) -> gen_server:start_link(?MODULE, Args, Options). stop(Conn_pid) -> case catch gen_server:call(Conn_pid, stop) of {'EXIT', {timeout, _}} -> exit(Conn_pid, kill), ok; _ -> ok end. send_req(Conn_Pid, Url, Headers, Method, Body, Options, Timeout) -> case catch gen_server:call(Conn_Pid, {send_req, {Url, Headers, Method, Body, Options, Timeout}}, Timeout) of {'EXIT', {timeout, _}} -> {error, req_timedout}; {'EXIT', {noproc, _}} -> {error, connection_closed}; Res -> Res end. %%==================================================================== %% Server functions %%==================================================================== %%-------------------------------------------------------------------- %% Function: init/1 %% Description: Initiates the server %% Returns: {ok, State} | %% {ok, State, Timeout} | %% ignore | %% {stop, Reason} %%-------------------------------------------------------------------- init({Lb_Tid, #url{host = Host, port = Port}, {SSLOptions, Is_ssl}}) -> process_flag(trap_exit, true), State = #state{host = Host, port = Port, ssl_options = SSLOptions, is_ssl = Is_ssl, lb_ets_tid = Lb_Tid}, put(ibrowse_trace_token, [Host, $:, integer_to_list(Port)]), put(my_trace_flag, ibrowse_lib:get_trace_status(Host, Port)), {ok, set_inac_timer(State)}; init(Url) when is_list(Url) -> process_flag(trap_exit, true), case catch ibrowse_lib:parse_url(Url) of #url{protocol = Protocol} = Url_rec -> init({undefined, Url_rec, {[], Protocol == https}}); {'EXIT', _} -> {error, invalid_url} end; init({Host, Port}) -> process_flag(trap_exit, true), State = #state{host = Host, port = Port}, put(ibrowse_trace_token, [Host, $:, integer_to_list(Port)]), put(my_trace_flag, ibrowse_lib:get_trace_status(Host, Port)), {ok, set_inac_timer(State)}. %%-------------------------------------------------------------------- %% Function: handle_call/3 %% Description: Handling call messages %% Returns: {reply, Reply, State} | %% {reply, Reply, State, Timeout} | %% {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, Reply, State} | (terminate/2 is called) %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- %% Received a request when the remote server has already sent us a %% Connection: Close header handle_call({send_req, _}, _From, #state{is_closing = true} = State) -> {reply, {error, connection_closing}, State}; handle_call({send_req, _}, _From, #state{proc_state = ?dead_proc_walking} = State) -> shutting_down(State), {reply, {error, connection_closing}, State}; handle_call({send_req, {Url, Headers, Method, Body, Options, Timeout}}, From, State) -> send_req_1(From, Url, Headers, Method, Body, Options, Timeout, State); handle_call(stop, _From, State) -> do_close(State), do_error_reply(State, closing_on_request), {stop, normal, ok, State}; handle_call(Request, _From, State) -> Reply = {unknown_request, Request}, {reply, Reply, State}. %%-------------------------------------------------------------------- %% Function: handle_cast/2 %% Description: Handling cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_cast(_Msg, State) -> {noreply, State}. %%-------------------------------------------------------------------- %% Function: handle_info/2 %% Description: Handling all non call/cast messages %% Returns: {noreply, State} | %% {noreply, State, Timeout} | %% {stop, Reason, State} (terminate/2 is called) %%-------------------------------------------------------------------- handle_info({tcp, _Sock, Data}, #state{status = Status} = State) -> do_trace("Data recvd in state: ~p. Size: ~p. ~p~n~n", [Status, size(Data), Data]), handle_sock_data(Data, State); handle_info({ssl, _Sock, Data}, State) -> handle_sock_data(Data, State); handle_info({stream_next, Req_id}, #state{socket = Socket, cur_req = #request{req_id = Req_id}} = State) -> _ = do_setopts(Socket, [{active, once}], State), {noreply, set_inac_timer(State)}; handle_info({stream_next, _Req_id}, State) -> _Cur_req_id = case State#state.cur_req of #request{req_id = Cur} -> Cur; _ -> undefined end, {noreply, State}; handle_info({stream_close, _Req_id}, State) -> State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), do_close(State_1), do_error_reply(State_1, closing_on_request), delayed_stop_timer(), {noreply, State_1}; handle_info({tcp_closed, _Sock}, State) -> do_trace("TCP connection closed by peer!~n", []), State_1 = State#state{proc_state = ?dead_proc_walking}, handle_sock_closed(State_1, ?can_retry_pipelined_requests), delayed_stop_timer(), {noreply, State_1}; handle_info({ssl_closed, _Sock}, State) -> do_trace("SSL connection closed by peer!~n", []), State_1 = State#state{proc_state = ?dead_proc_walking}, handle_sock_closed(State_1, ?can_retry_pipelined_requests), delayed_stop_timer(), {noreply, State_1}; handle_info({tcp_error, _Sock, Reason}, State) -> do_trace("Error on connection to ~1000.p:~1000.p -> ~1000.p~n", [State#state.host, State#state.port, Reason]), State_1 = State#state{proc_state = ?dead_proc_walking}, handle_sock_closed(State_1, ?dont_retry_pipelined_requests), delayed_stop_timer(), {noreply, State_1}; handle_info({ssl_error, _Sock, Reason}, State) -> do_trace("Error on SSL connection to ~1000.p:~1000.p -> ~1000.p~n", [State#state.host, State#state.port, Reason]), State_1 = State#state{proc_state = ?dead_proc_walking}, handle_sock_closed(State_1, ?dont_retry_pipelined_requests), delayed_stop_timer(), {noreply, State_1}; handle_info({req_timedout, From}, State) -> case lists:keysearch(From, #request.from, queue:to_list(State#state.reqs)) of false -> {noreply, State}; {value, #request{stream_to = StreamTo, req_id = ReqId}} -> catch StreamTo ! {ibrowse_async_response_timeout, ReqId}, State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), do_error_reply(State_1, req_timedout), delayed_stop_timer(), {noreply, State_1} end; handle_info(timeout, State) -> do_trace("Inactivity timeout triggered. Shutting down connection~n", []), State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), do_error_reply(State_1, req_timedout), delayed_stop_timer(), {noreply, State_1}; handle_info({trace, Bool}, State) -> put(my_trace_flag, Bool), {noreply, State}; handle_info(delayed_stop, State) -> {stop, normal, State}; handle_info(Info, State) -> io:format("Unknown message recvd for ~1000.p:~1000.p -> ~p~n", [State#state.host, State#state.port, Info]), io:format("Recvd unknown message ~p when in state: ~p~n", [Info, State]), {noreply, State}. %%-------------------------------------------------------------------- %% Function: terminate/2 %% Description: Shutdown the server %% Returns: any (ignored by gen_server) %%-------------------------------------------------------------------- terminate(_Reason, #state{lb_ets_tid = Tid} = State) -> do_close(State), shutting_down(State), (catch ets:select_delete(Tid, [{{{'_','_','$1'},'_'},[{'==','$1',{const,self()}}],[true]}])), ok. %%-------------------------------------------------------------------- %% Func: code_change/3 %% Purpose: Convert process state when code is changed %% Returns: {ok, NewState} %%-------------------------------------------------------------------- code_change(_OldVsn, State, _Extra) -> {ok, State}. %%-------------------------------------------------------------------- %%% Internal functions %%-------------------------------------------------------------------- %%-------------------------------------------------------------------- %% Handles data recvd on the socket %%-------------------------------------------------------------------- handle_sock_data(Data, #state{status=idle}=State) -> do_trace("Data recvd on socket in state idle!. ~1000.p~n", [Data]), State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), do_error_reply(State_1, data_in_status_idle), do_close(State_1), delayed_stop_timer(), {noreply, State_1}; handle_sock_data(Data, #state{status = get_header}=State) -> case parse_response(Data, State) of {error, _Reason} -> State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), delayed_stop_timer(), {noreply, State_1}; #state{socket = Socket, status = Status, cur_req = CurReq} = State_1 -> _ = case {Status, CurReq} of {get_header, #request{caller_controls_socket = true}} -> do_setopts(Socket, [{active, once}], State_1); _ -> active_once(State_1) end, {noreply, set_inac_timer(State_1)} end; handle_sock_data(Data, #state{status = get_body, socket = Socket, content_length = CL, http_status_code = StatCode, recvd_headers = Headers, chunk_size = CSz} = State) -> case (CL == undefined) and (CSz == undefined) of true -> case accumulate_response(Data, State) of {error, Reason} -> State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), fail_pipelined_requests(State_1, {error, {Reason, {stat_code, StatCode}, Headers}}), delayed_stop_timer(), {noreply, State_1}; State_1 -> _ = active_once(State_1), State_2 = set_inac_timer(State_1), {noreply, State_2} end; _ -> case parse_11_response(Data, State) of {error, Reason} -> State_1 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_1), fail_pipelined_requests(State_1, {error, {Reason, {stat_code, StatCode}, Headers}}), delayed_stop_timer(), {noreply, State_1}; #state{cur_req = #request{caller_controls_socket = Ccs}, interim_reply_sent = Irs} = State_1 -> _ = case Irs of true -> active_once(State_1); false when Ccs == true -> do_setopts(Socket, [{active, once}], State); false -> active_once(State_1) end, State_2 = State_1#state{interim_reply_sent = false}, case Ccs of true -> cancel_timer(State_2#state.inactivity_timer_ref, {eat_message, timeout}), {noreply, State_2#state{inactivity_timer_ref = undefined}}; _ -> {noreply, set_inac_timer(State_2)} end; State_1 -> _ = active_once(State_1), State_2 = set_inac_timer(State_1), {noreply, State_2} end end. accumulate_response(Data, #state{ cur_req = #request{save_response_to_file = Srtf, tmp_file_fd = undefined} = CurReq, http_status_code=[$2 | _]}=State) when Srtf /= false -> TmpFilename = make_tmp_filename(Srtf), Mode = file_mode(Srtf), case file:open(TmpFilename, [Mode, delayed_write, raw]) of {ok, Fd} -> accumulate_response(Data, State#state{ cur_req = CurReq#request{ tmp_file_fd = Fd, tmp_file_name = TmpFilename}}); {error, Reason} -> {error, {file_open_error, Reason}} end; accumulate_response(Data, #state{cur_req = #request{save_response_to_file = Srtf, tmp_file_fd = Fd}, transfer_encoding=chunked, reply_buffer = Reply_buf, http_status_code=[$2 | _] } = State) when Srtf /= false -> case file:write(Fd, [Reply_buf, Data]) of ok -> State#state{reply_buffer = <<>>}; {error, Reason} -> {error, {file_write_error, Reason}} end; accumulate_response(Data, #state{cur_req = #request{save_response_to_file = Srtf, tmp_file_fd = Fd}, reply_buffer = RepBuf, http_status_code=[$2 | _] } = State) when Srtf /= false -> case file:write(Fd, [RepBuf, Data]) of ok -> State#state{reply_buffer = <<>>}; {error, Reason} -> {error, {file_write_error, Reason}} end; accumulate_response(Data, #state{reply_buffer = RepBuf, rep_buf_size = RepBufSize, streamed_size = Streamed_size, cur_req = CurReq}=State) -> #request{stream_to = StreamTo, req_id = ReqId, stream_chunk_size = Stream_chunk_size, response_format = Response_format, caller_controls_socket = Caller_controls_socket} = CurReq, RepBuf_1 = <>, New_data_size = RepBufSize - Streamed_size, case StreamTo of undefined -> State#state{reply_buffer = RepBuf_1}; _ when Caller_controls_socket == true -> do_interim_reply(StreamTo, Response_format, ReqId, RepBuf_1), State#state{reply_buffer = <<>>, interim_reply_sent = true, streamed_size = Streamed_size + size(RepBuf_1)}; _ when New_data_size >= Stream_chunk_size -> {Stream_chunk, Rem_data} = split_binary(RepBuf_1, Stream_chunk_size), do_interim_reply(StreamTo, Response_format, ReqId, Stream_chunk), State_1 = State#state{ reply_buffer = <<>>, interim_reply_sent = true, streamed_size = Streamed_size + Stream_chunk_size}, case Rem_data of <<>> -> State_1; _ -> accumulate_response(Rem_data, State_1) end; _ -> State#state{reply_buffer = RepBuf_1} end. make_tmp_filename(true) -> DownloadDir = ibrowse:get_config_value(download_dir, filename:absname("./")), {A,B,C} = os:timestamp(), filename:join([DownloadDir, "ibrowse_tmp_file_"++ integer_to_list(A) ++ integer_to_list(B) ++ integer_to_list(C)]); make_tmp_filename(File) when is_list(File) -> File; make_tmp_filename({append, File}) when is_list(File) -> File. file_mode({append, _File}) -> append; file_mode(_Srtf) -> write. %%-------------------------------------------------------------------- %% Handles the case when the server closes the socket %%-------------------------------------------------------------------- handle_sock_closed(#state{status=get_header} = State, _) -> shutting_down(State), do_error_reply(State, connection_closed_no_retry); handle_sock_closed(#state{cur_req=undefined} = State, _) -> shutting_down(State); %% We check for IsClosing because this the server could have sent a %% Connection-Close header and has closed the socket to indicate end %% of response. There maybe requests pipelined which need a response. handle_sock_closed(#state{reply_buffer = Buf, reqs = Reqs, http_status_code = SC, is_closing = IsClosing, cur_req = #request{tmp_file_name=TmpFilename, tmp_file_fd=Fd} = CurReq, status = get_body, recvd_headers = Headers, status_line = Status_line, raw_headers = Raw_headers }=State, Retry_state) -> #request{from=From, stream_to=StreamTo, req_id=ReqId, response_format = Resp_format, options = Options, raw_req = Raw_req } = CurReq, case IsClosing of true -> {_, Reqs_1} = queue:out(Reqs), Body = case TmpFilename of undefined -> Buf; _ -> ok = file:close(Fd), {file, TmpFilename} end, Give_raw_req = get_value(return_raw_request, Options, false), Reply = case get_value(give_raw_headers, Options, false) of true when Give_raw_req == false-> {ok, Status_line, Raw_headers, Body}; true -> {ok, Status_line, Raw_headers, Body, Raw_req}; false when Give_raw_req == false -> {ok, SC, Headers, Buf}; false -> {ok, SC, Headers, Buf, Raw_req} end, State_1 = do_reply(State, From, StreamTo, ReqId, Resp_format, Reply), case Retry_state of ?dont_retry_pipelined_requests -> ok = do_error_reply(State_1#state{reqs = Reqs_1}, connection_closed_no_retry); ?can_retry_pipelined_requests -> ok = do_error_reply(State_1#state{reqs = Reqs_1}, connection_closed) end, State_1; _ -> case Retry_state of ?dont_retry_pipelined_requests -> ok = do_error_reply(State, connection_closed_no_retry); ?can_retry_pipelined_requests -> ok = do_error_reply(State, connection_closed) end, State end. do_connect(Host, Port, Options, #state{is_ssl = true, use_proxy = false, ssl_options = SSLOptions}, Timeout) -> ssl:connect(Host, Port, get_sock_options(Host, Options, SSLOptions), Timeout); do_connect(Host, Port, Options, _State, Timeout) -> Socks5Host = get_value(socks5_host, Options, undefined), case Socks5Host of undefined -> gen_tcp:connect(Host, Port, get_sock_options(Host, Options, []), Timeout); _ -> catch ibrowse_socks5:connect(Host, Port, Options) end. get_sock_options(Host, Options, SSLOptions) -> Caller_socket_options = get_value(socket_options, Options, []), Ipv6Options = case is_ipv6_host(Host) of true -> [inet6]; false -> [] end, Other_sock_options = filter_sock_options(SSLOptions ++ Caller_socket_options ++ Ipv6Options), case lists:keysearch(nodelay, 1, Other_sock_options) of false -> [{nodelay, true}, binary, {active, false} | Other_sock_options]; {value, _} -> [binary, {active, false} | Other_sock_options] end. is_ipv6_host(Host) -> case inet_parse:address(Host) of {ok, {_, _, _, _, _, _, _, _}} -> true; {ok, {_, _, _, _}} -> false; _ -> case inet:gethostbyname(Host) of {ok, #hostent{h_addrtype = inet6}} -> true; _ -> false end end. %% We don't want the caller to specify certain options filter_sock_options(Opts) -> lists:filter(fun({active, _}) -> false; ({packet, _}) -> false; (list) -> false; (_) -> true end, Opts). do_send(Req, #state{socket = Sock, is_ssl = true, use_proxy = true, proxy_tunnel_setup = Pts}) when Pts /= done -> gen_tcp:send(Sock, Req); do_send(Req, #state{socket = Sock, is_ssl = true}) -> ssl:send(Sock, Req); do_send(Req, #state{socket = Sock, is_ssl = false}) -> gen_tcp:send(Sock, Req). do_send_body(Source, State, TE) when is_function(Source) -> do_send_body({Source}, State, TE); do_send_body({Source}, State, TE) when is_function(Source) -> do_send_body_1(generate_body(Source), State, TE, []); do_send_body({Source, Source_state}, State, TE) when is_function(Source) -> do_send_body_1(generate_body({Source, Source_state}), State, TE, []); do_send_body(Body, State, _TE) -> case do_send(Body, State) of ok -> {ok, Body}; Ret -> Ret end. generate_body({Source, Source_state} = In) when is_function(Source) -> case Source(Source_state) of {ok, Data, Source_state_1} -> {{ok, Data, Source_state_1}, Source}; {eof, Source_state_1} -> {{eof, Source_state_1}, Source}; eof -> {eof, Source}; Ret -> {Ret, In} end; generate_body(Source) when is_function(Source) -> {Source(), Source}. do_send_body_1({Resp, Source}, State, TE, Acc) when is_function(Source) -> case Resp of {ok, Data} when Data == []; Data == <<>> -> do_send_body_1(generate_body(Source), State, TE, Acc); {ok, Data} -> Acc_1 = case TE of true -> ok = do_send(maybe_chunked_encode(Data, TE), State), Acc; false -> [Data | Acc] end, do_send_body_1(generate_body(Source), State, TE, Acc_1); {ok, Data, New_source_state} when Data == []; Data == <<>> -> do_send_body_1(generate_body({Source, New_source_state}), State, TE, Acc); {ok, Data, New_source_state} -> Acc_1 = case TE of true -> ok = do_send(maybe_chunked_encode(Data, TE), State), Acc; false -> [Data | Acc] end, do_send_body_1(generate_body({Source, New_source_state}), State, TE, Acc_1); {eof, _New_source_state} -> case TE of true -> ok = do_send(<<"0\r\n\r\n">>, State), {ok, []}; _ -> Body = list_to_binary(lists:reverse(Acc)), ok = do_send(Body, State), {ok, Body} end; eof when TE == true -> ok = do_send(<<"0\r\n\r\n">>, State), {ok, []}; eof -> Body = list_to_binary(lists:reverse(Acc)), ok = do_send(Body, State), {ok, Body}; Err -> Err end. maybe_chunked_encode(Data, false) -> Data; maybe_chunked_encode(Data, true) -> [?dec2hex(iolist_size(Data)), "\r\n", Data, "\r\n"]. do_close(#state{socket = undefined}) -> ok; do_close(#state{socket = Sock, is_ssl = true, use_proxy = true, proxy_tunnel_setup = Pts }) when Pts /= done -> catch gen_tcp:close(Sock); do_close(#state{socket = Sock, is_ssl = true}) -> catch ssl:close(Sock); do_close(#state{socket = Sock, is_ssl = false}) -> catch gen_tcp:close(Sock). active_once(#state{cur_req = #request{caller_controls_socket = true}}) -> ok; active_once(#state{socket = Socket} = State) -> _ = do_setopts(Socket, [{active, once}], State). do_setopts(_Sock, [], _) -> ok; do_setopts(Sock, Opts, #state{is_ssl = true, use_proxy = true, proxy_tunnel_setup = Pts} ) when Pts /= done -> inet:setopts(Sock, Opts); do_setopts(Sock, Opts, #state{is_ssl = true}) -> ssl:setopts(Sock, Opts); do_setopts(Sock, Opts, _) -> inet:setopts(Sock, Opts). check_ssl_options(Options, State) -> case get_value(is_ssl, Options, false) of false -> State; true -> State#state{is_ssl=true, ssl_options=get_value(ssl_options, Options)} end. send_req_1(From, #url{host = Host, port = Port} = Url, Headers, Method, Body, Options, Timeout, #state{socket = undefined} = State) -> {Host_1, Port_1, State_1} = case get_value(proxy_host, Options, false) of false -> {Host, Port, State}; PHost -> ProxyUser = get_value(proxy_user, Options, []), ProxyPassword = get_value(proxy_password, Options, []), AuthBasic = http_auth_basic(ProxyUser, ProxyPassword), {PHost, get_value(proxy_port, Options, 80), State#state{use_proxy = true, proxy_auth_basic = AuthBasic}} end, State_2 = check_ssl_options(Options, State_1), do_trace("Connecting...~n", []), Conn_timeout = get_value(connect_timeout, Options, Timeout), case do_connect(Host_1, Port_1, Options, State_2, Conn_timeout) of {ok, Sock} -> do_trace("Connected! Socket: ~1000.p~n", [Sock]), State_3 = State_2#state{socket = Sock, connect_timeout = Conn_timeout}, send_req_1(From, Url, Headers, Method, Body, Options, Timeout, State_3); Err -> State_3 = State_2#state{proc_state = ?dead_proc_walking}, shutting_down(State_3), do_trace("Error connecting. Reason: ~1000.p~n", [Err]), gen_server:reply(From, {error, {conn_failed, Err}}), delayed_stop_timer(), {noreply, State_3} end; %% Send a CONNECT request. %% Wait for 200 OK %% Upgrade to SSL connection %% Then send request send_req_1(From, #url{ host = Server_host, port = Server_port } = Url, Headers, Method, Body, Options, Timeout, #state{ proxy_tunnel_setup = false, use_proxy = true, is_ssl = true} = State) -> Ref = case Timeout of infinity -> undefined; _ -> erlang:send_after(Timeout, self(), {req_timedout, From}) end, NewReq = #request{ method = connect, preserve_chunked_encoding = get_value(preserve_chunked_encoding, Options, false), options = Options, timer_ref = Ref }, State_1 = State#state{reqs=queue:in(NewReq, State#state.reqs)}, Pxy_auth_headers = maybe_modify_headers(Url, Method, Options, [], State_1), Path = [Server_host, $:, integer_to_list(Server_port)], {Req, Body_1} = make_request(connect, Pxy_auth_headers, Path, Path, [], Options, State_1, undefined), TE = is_chunked_encoding_specified(Options), trace_request(Req), case do_send(Req, State) of ok -> case do_send_body(Body_1, State_1, TE) of {ok, _Sent_body} -> trace_request_body(Body_1), _ = active_once(State_1), State_1_1 = inc_pipeline_counter(State_1), State_2 = State_1_1#state{status = get_header, cur_req = NewReq, proxy_tunnel_setup = in_progress, tunnel_setup_queue = [{From, Url, Headers, Method, Body, Options, Timeout}]}, State_3 = set_inac_timer(State_2), {noreply, State_3}; Err -> State_2 = State_1#state{proc_state = ?dead_proc_walking}, shutting_down(State_2), do_trace("Send failed... Reason: ~p~n", [Err]), gen_server:reply(From, {error, {send_failed, Err}}), delayed_stop_timer(), {noreply, State_2} end; Err -> State_2 = State_1#state{proc_state = ?dead_proc_walking}, shutting_down(State_2), do_trace("Send failed... Reason: ~p~n", [Err]), gen_server:reply(From, {error, {send_failed, Err}}), delayed_stop_timer(), {noreply, State_2} end; send_req_1(From, Url, Headers, Method, Body, Options, Timeout, #state{proxy_tunnel_setup = in_progress, tunnel_setup_queue = Q} = State) -> do_trace("Queued SSL request awaiting tunnel setup: ~n" "URL : ~s~n" "Method : ~p~n" "Headers : ~p~n", [Url, Method, Headers]), {noreply, State#state{tunnel_setup_queue = [{From, Url, Headers, Method, Body, Options, Timeout} | Q]}}; send_req_1(From, #url{abspath = AbsPath, path = RelPath} = Url, Headers, Method, Body, Options, Timeout, #state{status = Status, socket = Socket} = State) -> cancel_timer(State#state.inactivity_timer_ref, {eat_message, timeout}), ReqId = make_req_id(), Resp_format = get_value(response_format, Options, list), Caller_socket_options = get_value(socket_options, Options, []), {StreamTo, Caller_controls_socket} = case get_value(stream_to, Options, undefined) of {Caller, once} when is_pid(Caller) or is_atom(Caller) -> Async_pid_rec = {{req_id_pid, ReqId}, self()}, true = ets:insert(ibrowse_stream, Async_pid_rec), {Caller, true}; undefined -> {undefined, false}; Caller when is_pid(Caller) or is_atom(Caller) -> {Caller, false}; Stream_to_inv -> exit({invalid_option, {stream_to, Stream_to_inv}}) end, SaveResponseToFile = get_value(save_response_to_file, Options, false), Ref = case Timeout of infinity -> undefined; _ -> erlang:send_after(Timeout, self(), {req_timedout, From}) end, Headers_1 = maybe_modify_headers(Url, Method, Options, Headers, State), {Req, Body_1} = make_request(Method, Headers_1, AbsPath, RelPath, Body, Options, State, ReqId), NewReq = #request{url = Url, method = Method, stream_to = StreamTo, caller_controls_socket = Caller_controls_socket, caller_socket_options = Caller_socket_options, options = Options, req_id = ReqId, save_response_to_file = SaveResponseToFile, stream_chunk_size = get_stream_chunk_size(Options), response_format = Resp_format, from = From, preserve_chunked_encoding = get_value(preserve_chunked_encoding, Options, false), timer_ref = Ref }, trace_request(Req), ok = do_setopts(Socket, Caller_socket_options, State), TE = is_chunked_encoding_specified(Options), case do_send(Req, State) of ok -> case do_send_body(Body_1, State, TE) of {ok, Sent_body} -> trace_request_body(Sent_body), Raw_req = list_to_binary([Req, Sent_body]), NewReq_1 = NewReq#request{raw_req = Raw_req}, State_1 = State#state{reqs=queue:in(NewReq_1, State#state.reqs)}, State_2 = inc_pipeline_counter(State_1), _ = active_once(State_2), State_3 = case Status of idle -> State_2#state{ status = get_header, cur_req = NewReq_1}; _ -> State_2 end, case StreamTo of undefined -> ok; _ -> gen_server:reply(From, {ibrowse_req_id, ReqId}), case get_value(return_raw_request, Options, false) of false -> ok; true -> catch StreamTo ! {ibrowse_async_raw_req, Raw_req} end end, State_4 = set_inac_timer(State_3), {noreply, State_4}; Err -> State_2 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_2), do_trace("Send failed... Reason: ~p~n", [Err]), gen_server:reply(From, {error, {send_failed, Err}}), delayed_stop_timer(), {noreply, State_2} end; Err -> State_2 = State#state{proc_state = ?dead_proc_walking}, shutting_down(State_2), do_trace("Send failed... Reason: ~p~n", [Err]), gen_server:reply(From, {error, {send_failed, Err}}), delayed_stop_timer(), {noreply, State_2} end. maybe_modify_headers(#url{}, connect, _, Headers, State) -> add_proxy_auth_headers(State, Headers); maybe_modify_headers(#url{host = Host, port = Port} = Url, _Method, Options, Headers, State) -> case get_value(headers_as_is, Options, false) of false -> Headers_1 = add_auth_headers(Url, Options, Headers, State), HostHeaderValue = case lists:keysearch(host_header, 1, Options) of false -> case Port of 80 -> Host; 443 -> Host; _ -> [Host, ":", integer_to_list(Port)] end; {value, {_, Host_h_val}} -> Host_h_val end, [{"Host", HostHeaderValue} | Headers_1]; true -> Headers end. add_auth_headers(#url{username = User, password = UPw}, Options, Headers, State) -> Headers_1 = case User of undefined -> case get_value(basic_auth, Options, undefined) of undefined -> Headers; {U,P} -> [{"Authorization", ["Basic ", http_auth_basic(U, P)]} | Headers] end; _ -> [{"Authorization", ["Basic ", http_auth_basic(User, UPw)]} | Headers] end, add_proxy_auth_headers(State, Headers_1). add_proxy_auth_headers(#state{use_proxy = false}, Headers) -> Headers; add_proxy_auth_headers(#state{proxy_auth_basic = []}, Headers) -> Headers; add_proxy_auth_headers(#state{proxy_auth_basic = Auth_basic}, Headers) -> [{"Proxy-Authorization", ["Basic ", Auth_basic]} | Headers]. http_auth_basic([], []) -> []; http_auth_basic(Username, Password) -> ibrowse_lib:encode_base64(Username ++ [$: | Password]). make_request(Method, Headers, AbsPath, RelPath, Body, Options, #state{use_proxy = UseProxy, is_ssl = Is_ssl}, ReqId) -> HttpVsn = http_vsn_string(get_value(http_vsn, Options, {1,1})), Fun1 = fun({X, Y}) when is_atom(X) -> {to_lower(atom_to_list(X)), X, Y}; ({X, Y}) when is_list(X); is_binary(X) -> {to_lower(X), X, Y} end, Headers_0 = [Fun1(X) || X <- Headers], Headers_1 = case lists:keysearch("content-length", 1, Headers_0) of false when (Body =:= [] orelse Body =:= <<>>) andalso (Method =:= post orelse Method =:= put) -> [{"content-length", "Content-Length", "0"} | Headers_0]; false when is_binary(Body) orelse is_list(Body) -> [{"content-length", "Content-Length", integer_to_list(iolist_size(Body))} | Headers_0]; _ -> %% Content-Length is already specified or Body is a %% function or function/state pair Headers_0 end, {Headers_2, Body_1} = case is_chunked_encoding_specified(Options) of false -> {[{Y, Z} || {_, Y, Z} <- Headers_1], Body}; true -> Chunk_size_1 = case get_value(transfer_encoding, Options) of chunked -> 5120; {chunked, Chunk_size} -> Chunk_size end, {[{Y, Z} || {X, Y, Z} <- Headers_1, X /= "content-length"] ++ [{"Transfer-Encoding", "chunked"}], chunk_request_body(Body, Chunk_size_1)} end, Headers_3 = case lists:member({include_ibrowse_req_id, true}, Options) of true -> [{"x-ibrowse-request-id", io_lib:format("~1000.p",[ReqId])} | Headers_2]; false -> Headers_2 end, Headers_4 = cons_headers(Headers_3), Uri = case get_value(use_absolute_uri, Options, false) or UseProxy of true -> case Is_ssl of true -> RelPath; false -> AbsPath end; false -> RelPath end, {[method(Method), " ", Uri, " ", HttpVsn, crnl(), Headers_4, crnl()], Body_1}. is_chunked_encoding_specified(Options) -> case get_value(transfer_encoding, Options, false) of false -> false; {chunked, _} -> true; chunked -> true end. http_vsn_string({0,9}) -> "HTTP/0.9"; http_vsn_string({1,0}) -> "HTTP/1.0"; http_vsn_string({1,1}) -> "HTTP/1.1". cons_headers(Headers) -> cons_headers(Headers, []). cons_headers([], Acc) -> encode_headers(Acc); cons_headers([{basic_auth, {U,P}} | T], Acc) -> cons_headers(T, [{"Authorization", ["Basic ", ibrowse_lib:encode_base64(U++":"++P)]} | Acc]); cons_headers([{cookie, Cookie} | T], Acc) -> cons_headers(T, [{"Cookie", Cookie} | Acc]); cons_headers([{content_length, L} | T], Acc) -> cons_headers(T, [{"Content-Length", L} | Acc]); cons_headers([{content_type, L} | T], Acc) -> cons_headers(T, [{"Content-Type", L} | Acc]); cons_headers([H | T], Acc) -> cons_headers(T, [H | Acc]). encode_headers(L) -> encode_headers(L, []). encode_headers([{http_vsn, _Val} | T], Acc) -> encode_headers(T, Acc); encode_headers([{Name,Val} | T], Acc) when is_list(Name); is_binary(Name) -> encode_headers(T, [[Name, ": ", fmt_val(Val), crnl()] | Acc]); encode_headers([{Name,Val} | T], Acc) when is_atom(Name) -> encode_headers(T, [[atom_to_list(Name), ": ", fmt_val(Val), crnl()] | Acc]); encode_headers([], Acc) -> lists:reverse(Acc). chunk_request_body(Body, _ChunkSize) when is_tuple(Body) orelse is_function(Body) -> Body; chunk_request_body(Body, ChunkSize) -> chunk_request_body(Body, ChunkSize, []). chunk_request_body(Body, _ChunkSize, Acc) when Body == <<>>; Body == [] -> LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk | Acc]); chunk_request_body(Body, ChunkSize, Acc) when is_binary(Body), size(Body) >= ChunkSize -> <> = Body, Chunk = [?dec2hex(ChunkSize),"\r\n", ChunkBody, "\r\n"], chunk_request_body(Rest, ChunkSize, [Chunk | Acc]); chunk_request_body(Body, _ChunkSize, Acc) when is_binary(Body) -> BodySize = size(Body), Chunk = [?dec2hex(BodySize),"\r\n", Body, "\r\n"], LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk, Chunk | Acc]); chunk_request_body(Body, ChunkSize, Acc) when length(Body) >= ChunkSize -> {ChunkBody, Rest} = split_list_at(Body, ChunkSize), Chunk = [?dec2hex(ChunkSize),"\r\n", ChunkBody, "\r\n"], chunk_request_body(Rest, ChunkSize, [Chunk | Acc]); chunk_request_body(Body, _ChunkSize, Acc) when is_list(Body) -> BodySize = length(Body), Chunk = [?dec2hex(BodySize),"\r\n", Body, "\r\n"], LastChunk = "0\r\n", lists:reverse(["\r\n", LastChunk, Chunk | Acc]). parse_response(<<>>, #state{cur_req = undefined}=State) -> State#state{status = idle}; parse_response(Data, #state{cur_req = undefined}) -> do_trace("Data left to process when no pending request. ~1000.p~n", [Data]), {error, data_in_status_idle}; parse_response(Data, #state{reply_buffer = Acc, reqs = Reqs, cur_req = CurReq} = State) -> #request{from=From, stream_to=StreamTo, req_id=ReqId, method=Method, response_format = Resp_format, options = Options, timer_ref = T_ref, raw_req = Raw_req } = CurReq, MaxHeaderSize = ibrowse:get_config_value(max_headers_size, infinity), case scan_header(Acc, Data) of {yes, Headers, Data_1} -> do_trace("Recvd Header Data -> ~s~n----~n", [Headers]), do_trace("Recvd headers~n--- Headers Begin ---~n~s~n--- Headers End ---~n~n", [Headers]), {HttpVsn, StatCode, Headers_1, Status_line, Raw_headers} = parse_headers(Headers), do_trace("HttpVsn: ~p StatusCode: ~p Headers_1 -> ~1000.p~n", [HttpVsn, StatCode, Headers_1]), LCHeaders = [{to_lower(X), Y} || {X,Y} <- Headers_1], ConnClose = to_lower(get_header_value("connection", LCHeaders, "false")), IsClosing = is_connection_closing(HttpVsn, ConnClose), State_0 = case IsClosing of true -> shutting_down(State), State#state{is_closing = IsClosing}; false -> State end, Give_raw_headers = get_value(give_raw_headers, Options, false), Give_raw_req = get_value(return_raw_request, Options, false), State_1 = case Give_raw_headers of true -> State_0#state{recvd_headers=Headers_1, status=get_body, reply_buffer = <<>>, status_line = Status_line, raw_headers = Raw_headers, http_status_code=StatCode}; false -> State_0#state{recvd_headers=Headers_1, status=get_body, reply_buffer = <<>>, http_status_code=StatCode} end, put(conn_close, ConnClose), TransferEncodings = to_lower(get_header_value("transfer-encoding", LCHeaders, "false")), IsChunked = lists:any(fun(Enc) -> string:strip(Enc) =:= "chunked" end, string:tokens(TransferEncodings, ",")), Head_response_with_body = lists:member({workaround, head_response_with_body}, Options), case get_header_value("content-length", LCHeaders, undefined) of _ when Method == connect, hd(StatCode) == $2 -> {_, Reqs_1} = queue:out(Reqs), cancel_timer(T_ref), upgrade_to_ssl(set_cur_request(State_0#state{reqs = Reqs_1, recvd_headers = [], status = idle })); _ when Method == connect -> {_, Reqs_1} = queue:out(Reqs), do_error_reply(State#state{reqs = Reqs_1}, {error, proxy_tunnel_failed}), {error, proxy_tunnel_failed}; _ when Method =:= head, Head_response_with_body =:= false -> %% This (HEAD response with body) is not supposed %% to happen, but it does. An Apache server was %% observed to send an "empty" body, but in a %% Chunked-Transfer-Encoding way, which meant %% there was still a body. Issue #67 on Github {_, Reqs_1} = queue:out(Reqs), send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), Reply = case Give_raw_req of false -> {ok, StatCode, Headers_1, []}; true -> {ok, StatCode, Headers_1, [], Raw_req} end, State_1_1 = do_reply(State_1, From, StreamTo, ReqId, Resp_format, Reply), cancel_timer(T_ref, {eat_message, {req_timedout, From}}), State_2 = reset_state(State_1_1), State_3 = set_cur_request(State_2#state{reqs = Reqs_1}), parse_response(Data_1, State_3); _ when hd(StatCode) =:= $1 -> %% No message body is expected. Server may send %% one or more 1XX responses before a proper %% response. send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), do_trace("Recvd a status code of ~p. Ignoring and waiting for a proper response~n", [StatCode]), parse_response(Data_1, State_1#state{recvd_headers = [], status = get_header}); _ when StatCode =:= "204"; StatCode =:= "304" -> %% No message body is expected for these Status Codes. %% RFC2616 - Sec 4.4 {_, Reqs_1} = queue:out(Reqs), send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), Reply = case Give_raw_req of false -> {ok, StatCode, Headers_1, []}; true -> {ok, StatCode, Headers_1, [], Raw_req} end, State_1_1 = do_reply(State_1, From, StreamTo, ReqId, Resp_format, Reply), cancel_timer(T_ref, {eat_message, {req_timedout, From}}), State_2 = reset_state(State_1_1), State_3 = set_cur_request(State_2#state{reqs = Reqs_1}), parse_response(Data_1, State_3); _ when IsChunked -> do_trace("Chunked encoding detected...~n",[]), send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), case parse_11_response(Data_1, State_1#state{transfer_encoding=chunked, chunk_size=chunk_start, reply_buffer = <<>>}) of {error, Reason} -> fail_pipelined_requests(State_1, {error, {Reason, {stat_code, StatCode}, Headers_1}}), {error, Reason}; State_2 -> State_2 end; undefined when HttpVsn =:= "HTTP/1.0"; ConnClose =:= "close" -> send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), State_1#state{reply_buffer = Data_1}; undefined when StatCode =:= "303" -> %% Some servers send 303 requests without a body. %% RFC2616 says that they SHOULD, but they dont. case ibrowse:get_config_value(allow_303_with_no_body, false) of false -> fail_pipelined_requests(State_1, {error, {content_length_undefined, {stat_code, StatCode}, Headers}}), {error, content_length_undefined}; true -> {_, Reqs_1} = queue:out(Reqs), send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), State_1_1 = do_reply(State_1, From, StreamTo, ReqId, Resp_format, {ok, StatCode, Headers_1, []}), cancel_timer(T_ref, {eat_message, {req_timedout, From}}), State_2 = reset_state(State_1_1), State_3 = set_cur_request(State_2#state{reqs = Reqs_1}), parse_response(Data_1, State_3) end; undefined -> fail_pipelined_requests(State_1, {error, {content_length_undefined, {stat_code, StatCode}, Headers}}), {error, content_length_undefined}; V -> case catch list_to_integer(V) of V_1 when is_integer(V_1), V_1 >= 0 -> send_async_headers(ReqId, StreamTo, Give_raw_headers, State_1), do_trace("Recvd Content-Length of ~p~n", [V_1]), State_2 = State_1#state{rep_buf_size=0, reply_buffer = <<>>, content_length=V_1}, case parse_11_response(Data_1, State_2) of {error, Reason} -> fail_pipelined_requests(State_1, {error, {Reason, {stat_code, StatCode}, Headers_1}}), {error, Reason}; State_3 -> State_3 end; _ -> fail_pipelined_requests(State_1, {error, {content_length_undefined, {stat_code, StatCode}, Headers}}), {error, content_length_undefined} end end; {no, Acc_1} when MaxHeaderSize == infinity -> State#state{reply_buffer = Acc_1}; {no, Acc_1} when size(Acc_1) < MaxHeaderSize -> State#state{reply_buffer = Acc_1}; {no, _Acc_1} -> fail_pipelined_requests(State, {error, max_headers_size_exceeded}), {error, max_headers_size_exceeded} end. upgrade_to_ssl(#state{socket = Socket, connect_timeout = Conn_timeout, ssl_options = Ssl_options, tunnel_setup_queue = Q} = State) -> case ssl:connect(Socket, Ssl_options, Conn_timeout) of {ok, Ssl_socket} -> do_trace("Upgraded to SSL socket!!~n", []), State_1 = State#state{socket = Ssl_socket, proxy_tunnel_setup = done}, send_queued_requests(lists:reverse(Q), State_1); Err -> do_trace("Upgrade to SSL socket failed. Reson: ~p~n", [Err]), do_error_reply(State, {error, {send_failed, Err}}), {error, send_failed} end. send_queued_requests([], State) -> do_trace("Sent all queued requests via SSL connection~n", []), State#state{tunnel_setup_queue = []}; send_queued_requests([{From, Url, Headers, Method, Body, Options, Timeout} | Q], State) -> case send_req_1(From, Url, Headers, Method, Body, Options, Timeout, State) of {noreply, State_1} -> send_queued_requests(Q, State_1); Err -> do_trace("Error sending queued SSL request: ~n" "URL : ~s~n" "Method : ~p~n" "Headers : ~p~n", [Url, Method, Headers]), do_error_reply(State, {error, {send_failed, Err}}), {error, send_failed} end. is_connection_closing("HTTP/0.9", _) -> true; is_connection_closing(_, "close") -> true; is_connection_closing("HTTP/1.0", "false") -> true; is_connection_closing(_, _) -> false. %% This clause determines the chunk size when given data from the beginning of the chunk parse_11_response(DataRecvd, #state{transfer_encoding = chunked, chunk_size = chunk_start, chunk_size_buffer = Chunk_sz_buf } = State) -> case scan_crlf(Chunk_sz_buf, DataRecvd) of {yes, ChunkHeader, Data_1} -> State_1 = maybe_accumulate_ce_data(State, <>), ChunkSize = parse_chunk_header(ChunkHeader), %% %% Do we have to preserve the chunk encoding when %% streaming? NO. This should be transparent to the client %% process. Chunked encoding was only introduced to make %% it efficient for the server. %% RemLen = size(Data_1), do_trace("Determined chunk size: ~p. Already recvd: ~p~n", [ChunkSize, RemLen]), parse_11_response(Data_1, State_1#state{chunk_size_buffer = <<>>, deleted_crlf = true, recvd_chunk_size = 0, chunk_size = ChunkSize}); {no, Data_1} -> State#state{chunk_size_buffer = Data_1} end; %% This clause is to remove the CRLF between two chunks %% parse_11_response(DataRecvd, #state{transfer_encoding = chunked, chunk_size = tbd, chunk_size_buffer = Buf } = State) -> case scan_crlf(Buf, DataRecvd) of {yes, _, NextChunk} -> State_1 = maybe_accumulate_ce_data(State, <<$\r, $\n>>), State_2 = State_1#state{chunk_size = chunk_start, chunk_size_buffer = <<>>, deleted_crlf = true}, parse_11_response(NextChunk, State_2); {no, Data_1} -> State#state{chunk_size_buffer = Data_1} end; %% This clause deals with the end of a chunked transfer. ibrowse does %% not support Trailers in the Chunked Transfer encoding. Any trailer %% received is silently discarded. parse_11_response(DataRecvd, #state{transfer_encoding = chunked, chunk_size = 0, cur_req = CurReq, deleted_crlf = DelCrlf, chunk_size_buffer = Trailer, reqs = Reqs} = State) -> do_trace("Detected end of chunked transfer...~n", []), DataRecvd_1 = case DelCrlf of false -> DataRecvd; true -> <<$\r, $\n, DataRecvd/binary>> end, case scan_header(Trailer, DataRecvd_1) of {yes, TEHeaders, Rem} -> {_, Reqs_1} = queue:out(Reqs), State_1 = maybe_accumulate_ce_data(State, <>), State_2 = handle_response(CurReq, State_1#state{reqs = Reqs_1}), parse_response(Rem, reset_state(State_2)); {no, Rem} -> accumulate_response(<<>>, State#state{chunk_size_buffer = Rem, deleted_crlf = false}) end; %% This clause extracts a chunk, given the size. parse_11_response(DataRecvd, #state{transfer_encoding = chunked, chunk_size = CSz, recvd_chunk_size = Recvd_csz, rep_buf_size = RepBufSz} = State) -> NeedBytes = CSz - Recvd_csz, DataLen = size(DataRecvd), do_trace("Recvd more data: size: ~p. NeedBytes: ~p~n", [DataLen, NeedBytes]), case DataLen >= NeedBytes of true -> {RemChunk, RemData} = split_binary(DataRecvd, NeedBytes), do_trace("Recvd another chunk...~p~n", [RemChunk]), do_trace("RemData -> ~p~n", [RemData]), case accumulate_response(RemChunk, State) of {error, Reason} -> do_trace("Error accumulating response --> ~p~n", [Reason]), {error, Reason}; #state{} = State_1 -> State_2 = State_1#state{chunk_size=tbd}, parse_11_response(RemData, State_2) end; false -> accumulate_response(DataRecvd, State#state{rep_buf_size = RepBufSz + DataLen, recvd_chunk_size = Recvd_csz + DataLen}) end; %% This clause to extract the body when Content-Length is specified parse_11_response(DataRecvd, #state{content_length=CL, rep_buf_size=RepBufSz, reqs=Reqs}=State) -> NeedBytes = CL - RepBufSz, DataLen = size(DataRecvd), case DataLen >= NeedBytes of true -> {RemBody, Rem} = split_binary(DataRecvd, NeedBytes), {_, Reqs_1} = queue:out(Reqs), State_1 = accumulate_response(RemBody, State), State_2 = handle_response(State_1#state.cur_req, State_1#state{reqs=Reqs_1}), State_3 = reset_state(State_2), parse_response(Rem, State_3); false -> accumulate_response(DataRecvd, State#state{rep_buf_size = (RepBufSz+DataLen)}) end. maybe_accumulate_ce_data(#state{cur_req = #request{preserve_chunked_encoding = false}} = State, _) -> State; maybe_accumulate_ce_data(State, Data) -> accumulate_response(Data, State). handle_response(#request{from=From, stream_to=StreamTo, req_id=ReqId, response_format = Resp_format, save_response_to_file = SaveResponseToFile, tmp_file_name = TmpFilename, tmp_file_fd = Fd, options = Options, timer_ref = ReqTimer, raw_req = Raw_req }, #state{http_status_code = SCode, status_line = Status_line, raw_headers = Raw_headers, reply_buffer = RepBuf, recvd_headers = RespHeaders}=State) when SaveResponseToFile /= false -> Body = RepBuf, case Fd of undefined -> ok; _ -> ok = file:close(Fd) end, ResponseBody = case TmpFilename of undefined -> Body; _ -> {file, TmpFilename} end, {Resp_headers_1, Raw_headers_1} = maybe_add_custom_headers(Status_line, RespHeaders, Raw_headers, Options), Give_raw_req = get_value(return_raw_request, Options, false), Reply = case get_value(give_raw_headers, Options, false) of true when Give_raw_req == false -> {ok, Status_line, Raw_headers_1, ResponseBody}; true -> {ok, Status_line, Raw_headers_1, ResponseBody, Raw_req}; false when Give_raw_req == false -> {ok, SCode, Resp_headers_1, ResponseBody}; false -> {ok, SCode, Resp_headers_1, ResponseBody, Raw_req} end, State_1 = do_reply(State, From, StreamTo, ReqId, Resp_format, Reply), cancel_timer(ReqTimer, {eat_message, {req_timedout, From}}), set_cur_request(State_1); handle_response(#request{from=From, stream_to=StreamTo, req_id=ReqId, response_format = Resp_format, options = Options, timer_ref = ReqTimer, raw_req = Raw_req }, #state{http_status_code = SCode, status_line = Status_line, raw_headers = Raw_headers, recvd_headers = Resp_headers, reply_buffer = RepBuf } = State) -> Body = RepBuf, {Resp_headers_1, Raw_headers_1} = maybe_add_custom_headers(Status_line, Resp_headers, Raw_headers, Options), Give_raw_req = get_value(return_raw_request, Options, false), Reply = case get_value(give_raw_headers, Options, false) of true when Give_raw_req == false -> {ok, Status_line, Raw_headers_1, Body}; true -> {ok, Status_line, Raw_headers_1, Body, Raw_req}; false when Give_raw_req == false -> {ok, SCode, Resp_headers_1, Body}; false -> {ok, SCode, Resp_headers_1, Body, Raw_req} end, State_1 = do_reply(State, From, StreamTo, ReqId, Resp_format, Reply), cancel_timer(ReqTimer, {eat_message, {req_timedout, From}}), set_cur_request(State_1). reset_state(State) -> State#state{status = get_header, rep_buf_size = 0, streamed_size = 0, content_length = undefined, reply_buffer = <<>>, chunk_size_buffer = <<>>, recvd_headers = [], status_line = undefined, raw_headers = undefined, deleted_crlf = false, http_status_code = undefined, chunk_size = undefined, transfer_encoding = undefined }. set_cur_request(#state{reqs = Reqs, socket = Socket} = State) -> case queue:peek(Reqs) of empty -> State#state{cur_req = undefined}; {value, #request{caller_controls_socket = Ccs} = NextReq} -> _ = Ccs =:= true andalso do_setopts(Socket, [{active, once}], State), State#state{cur_req = NextReq} end. parse_headers(Headers) -> case scan_crlf(Headers) of {yes, StatusLine, T} -> parse_headers(StatusLine, T); {no, StatusLine} -> parse_headers(StatusLine, <<>>) end. parse_headers(StatusLine, Headers) -> Headers_1 = parse_headers_1(Headers), case parse_status_line(StatusLine) of {ok, HttpVsn, StatCode, _Msg} -> put(http_prot_vsn, HttpVsn), {HttpVsn, StatCode, Headers_1, StatusLine, Headers}; _ -> %% A HTTP 0.9 response? put(http_prot_vsn, "HTTP/0.9"), {"HTTP/0.9", undefined, Headers, StatusLine, Headers} end. % From RFC 2616 % % HTTP/1.1 header field values can be folded onto multiple lines if % the continuation line begins with a space or horizontal tab. All % linear white space, including folding, has the same semantics as % SP. A recipient MAY replace any linear white space with a single % SP before interpreting the field value or forwarding the message % downstream. parse_headers_1(B) when is_binary(B) -> parse_headers_1(binary_to_list(B)); parse_headers_1(String) -> parse_headers_1(String, [], []). parse_headers_1([$\n, H |T], [$\r | L], Acc) when H =:= 32; H =:= $\t -> parse_headers_1(lists:dropwhile(fun(X) -> is_whitespace(X) end, T), [32 | L], Acc); parse_headers_1([$\n, H |T], L, Acc) when H =:= 32; H =:= $\t -> parse_headers_1(lists:dropwhile(fun(X) -> is_whitespace(X) end, T), [32 | L], Acc); parse_headers_1([$\n|T], [$\r | L], Acc) -> case parse_header(lists:reverse(L)) of invalid -> parse_headers_1(T, [], Acc); NewHeader -> parse_headers_1(T, [], [NewHeader | Acc]) end; parse_headers_1([$\n|T], L, Acc) -> case parse_header(lists:reverse(L)) of invalid -> parse_headers_1(T, [], Acc); NewHeader -> parse_headers_1(T, [], [NewHeader | Acc]) end; parse_headers_1([H|T], L, Acc) -> parse_headers_1(T, [H|L], Acc); parse_headers_1([], [], Acc) -> lists:reverse(Acc); parse_headers_1([], L, Acc) -> Acc_1 = case parse_header(lists:reverse(L)) of invalid -> Acc; NewHeader -> [NewHeader | Acc] end, lists:reverse(Acc_1). parse_status_line(Line) when is_binary(Line) -> parse_status_line(binary_to_list(Line)); parse_status_line(Line) -> parse_status_line(Line, get_prot_vsn, [], []). parse_status_line([32 | T], get_prot_vsn, ProtVsn, StatCode) -> parse_status_line(T, get_status_code, ProtVsn, StatCode); parse_status_line([32 | T], get_status_code, ProtVsn, StatCode) -> {ok, lists:reverse(ProtVsn), lists:reverse(StatCode), T}; parse_status_line([], get_status_code, ProtVsn, StatCode) -> {ok, lists:reverse(ProtVsn), lists:reverse(StatCode), []}; parse_status_line([H | T], get_prot_vsn, ProtVsn, StatCode) -> parse_status_line(T, get_prot_vsn, [H|ProtVsn], StatCode); parse_status_line([H | T], get_status_code, ProtVsn, StatCode) -> parse_status_line(T, get_status_code, ProtVsn, [H | StatCode]); parse_status_line([], _, _, _) -> http_09. parse_header(L) -> parse_header(L, []). parse_header([$: | V], Acc) -> {lists:reverse(Acc), string:strip(V)}; parse_header([H | T], Acc) -> parse_header(T, [H | Acc]); parse_header([], _) -> invalid. scan_header(Bin) -> case get_crlf_crlf_pos(Bin, 0) of {yes, Pos} -> {Headers, <<_:4/binary, Body/binary>>} = split_binary(Bin, Pos), {yes, Headers, Body}; {yes_dodgy, Pos} -> {Headers, <<_:2/binary, Body/binary>>} = split_binary(Bin, Pos), {yes, Headers, Body}; no -> {no, Bin} end. scan_header(Bin1, Bin2) when size(Bin1) < 4 -> scan_header(<>); scan_header(Bin1, <<>>) -> scan_header(Bin1); scan_header(Bin1, Bin2) -> Bin1_already_scanned_size = size(Bin1) - 4, <> = Bin1, Bin_to_scan = <>, case get_crlf_crlf_pos(Bin_to_scan, 0) of {yes, Pos} -> {Headers_suffix, <<_:4/binary, Body/binary>>} = split_binary(Bin_to_scan, Pos), {yes, <>, Body}; {yes_dodgy, Pos} -> {Headers_suffix, <<_:2/binary, Body/binary>>} = split_binary(Bin_to_scan, Pos), {yes, <>, Body}; no -> {no, <>} end. get_crlf_crlf_pos(<<$\r, $\n, $\r, $\n, _/binary>>, Pos) -> {yes, Pos}; get_crlf_crlf_pos(<<$\n, $\n, _/binary>>, Pos) -> {yes_dodgy, Pos}; get_crlf_crlf_pos(<<_, Rest/binary>>, Pos) -> get_crlf_crlf_pos(Rest, Pos + 1); get_crlf_crlf_pos(<<>>, _) -> no. scan_crlf(Bin) -> case get_crlf_pos(Bin) of {yes, Offset, Pos} -> {Prefix, <<_:Offset/binary, Suffix/binary>>} = split_binary(Bin, Pos), {yes, Prefix, Suffix}; no -> {no, Bin} end. scan_crlf(<<>>, Bin2) -> scan_crlf(Bin2); scan_crlf(Bin1, Bin2) when size(Bin1) < 2 -> scan_crlf(<>); scan_crlf(Bin1, Bin2) -> scan_crlf_1(size(Bin1) - 2, Bin1, Bin2). scan_crlf_1(Bin1_head_size, Bin1, Bin2) -> <> = Bin1, Bin3 = <>, case get_crlf_pos(Bin3) of {yes, Offset, Pos} -> {Prefix, <<_:Offset/binary, Suffix/binary>>} = split_binary(Bin3, Pos), {yes, list_to_binary([Bin1_head, Prefix]), Suffix}; no -> {no, list_to_binary([Bin1, Bin2])} end. get_crlf_pos(Bin) -> get_crlf_pos(Bin, 0). get_crlf_pos(<<$\r, $\n, _/binary>>, Pos) -> {yes, 2, Pos}; get_crlf_pos(<<$\n, _/binary>>, Pos) -> {yes, 1, Pos}; get_crlf_pos(<<_, Rest/binary>>, Pos) -> get_crlf_pos(Rest, Pos + 1); get_crlf_pos(<<>>, _) -> no. fmt_val(L) when is_list(L) -> L; fmt_val(I) when is_integer(I) -> integer_to_list(I); fmt_val(A) when is_atom(A) -> atom_to_list(A); fmt_val(B) when is_binary(B) -> B; fmt_val(Term) -> io_lib:format("~p", [Term]). crnl() -> "\r\n". method(connect) -> "CONNECT"; method(delete) -> "DELETE"; method(get) -> "GET"; method(head) -> "HEAD"; method(options) -> "OPTIONS"; method(post) -> "POST"; method(put) -> "PUT"; method(trace) -> "TRACE"; %% webdav method(copy) -> "COPY"; method(lock) -> "LOCK"; method(mkcol) -> "MKCOL"; method(move) -> "MOVE"; method(propfind) -> "PROPFIND"; method(proppatch) -> "PROPPATCH"; method(search) -> "SEARCH"; method(unlock) -> "UNLOCK"; %% subversion %% method(report) -> "REPORT"; method(mkactivity) -> "MKACTIVITY"; method(checkout) -> "CHECKOUT"; method(merge) -> "MERGE"; %% upnp method(msearch) -> "MSEARCH"; method(notify) -> "NOTIFY"; method(subscribe) -> "SUBSCRIBE"; method(unsubscribe) -> "UNSUBSCRIBE"; %% rfc-5789 method(patch) -> "PATCH"; method(purge) -> "PURGE". %% From RFC 2616 %% % The chunked encoding modifies the body of a message in order to % transfer it as a series of chunks, each with its own size indicator, % followed by an OPTIONAL trailer containing entity-header % fields. This allows dynamically produced content to be transferred % along with the information necessary for the recipient to verify % that it has received the full message. % Chunked-Body = *chunk % last-chunk % trailer % CRLF % chunk = chunk-size [ chunk-extension ] CRLF % chunk-data CRLF % chunk-size = 1*HEX % last-chunk = 1*("0") [ chunk-extension ] CRLF % chunk-extension= *( ";" chunk-ext-name [ "=" chunk-ext-val ] ) % chunk-ext-name = token % chunk-ext-val = token | quoted-string % chunk-data = chunk-size(OCTET) % trailer = *(entity-header CRLF) % The chunk-size field is a string of hex digits indicating the size % of the chunk. The chunked encoding is ended by any chunk whose size % is zero, followed by the trailer, which is terminated by an empty % line. %% %% The parsing implemented here discards all chunk extensions. It also %% strips trailing spaces from the chunk size fields as Apache 1.3.27 was %% sending them. parse_chunk_header(ChunkHeader) -> parse_chunk_header(ChunkHeader, []). parse_chunk_header(<<$;, _/binary>>, Acc) -> hexlist_to_integer(lists:reverse(Acc)); parse_chunk_header(<>, Acc) -> case is_whitespace(H) of true -> parse_chunk_header(T, Acc); false -> parse_chunk_header(T, [H | Acc]) end; parse_chunk_header(<<>>, Acc) -> hexlist_to_integer(lists:reverse(Acc)). is_whitespace($\s) -> true; is_whitespace($\r) -> true; is_whitespace($\n) -> true; is_whitespace($\t) -> true; is_whitespace(_) -> false. send_async_headers(_ReqId, undefined, _, _State) -> ok; send_async_headers(ReqId, StreamTo, Give_raw_headers, #state{status_line = Status_line, raw_headers = Raw_headers, recvd_headers = Headers, http_status_code = StatCode, cur_req = #request{options = Opts} }) -> {Headers_1, Raw_headers_1} = maybe_add_custom_headers(Status_line, Headers, Raw_headers, Opts), case Give_raw_headers of false -> catch StreamTo ! {ibrowse_async_headers, ReqId, StatCode, Headers_1}; true -> catch StreamTo ! {ibrowse_async_headers, ReqId, Status_line, Raw_headers_1} end. maybe_add_custom_headers(Status_line, Headers, Raw_headers, Opts) -> Custom_headers = get_value(add_custom_headers, Opts, []), Headers_1 = Headers ++ Custom_headers, Raw_headers_1 = case Custom_headers of [_ | _] when is_binary(Raw_headers) -> Custom_headers_bin = list_to_binary(string:join([[X, $:, Y] || {X, Y} <- Custom_headers], "\r\n")), <>; _ -> Raw_headers end, case get_value(preserve_status_line, Opts, false) of true -> {[{ibrowse_status_line, Status_line} | Headers_1], Raw_headers_1}; false -> {Headers_1, Raw_headers_1} end. format_response_data(Resp_format, Body) -> case Resp_format of list when is_list(Body) -> flatten(Body); list when is_binary(Body) -> binary_to_list(Body); binary when is_list(Body) -> list_to_binary(Body); _ -> %% This is to cater for sending messages such as %% {chunk_start, _}, chunk_end etc Body end. do_reply(State, From, undefined, _, Resp_format, {ok, St_code, Headers, Body}) -> Msg_1 = {ok, St_code, Headers, format_response_data(Resp_format, Body)}, gen_server:reply(From, Msg_1), dec_pipeline_counter(State); do_reply(State, From, undefined, _, _, Msg) -> gen_server:reply(From, Msg), dec_pipeline_counter(State); do_reply(#state{prev_req_id = Prev_req_id} = State, _From, StreamTo, ReqId, Resp_format, {ok, _, _, Body}) -> State_1 = dec_pipeline_counter(State), case Body of [] -> ok; _ -> Body_1 = format_response_data(Resp_format, Body), catch StreamTo ! {ibrowse_async_response, ReqId, Body_1} end, catch StreamTo ! {ibrowse_async_response_end, ReqId}, %% We don't want to delete the Req-id to Pid mapping straightaway %% as the client may send a stream_next message just while we are %% sending back this ibrowse_async_response_end message. If we %% deleted this mapping straightaway, the caller will see a %% {error, unknown_req_id} when it calls ibrowse:stream_next/1. To %% get around this, we store the req id, and clear it after the %% next request. If there are wierd combinations of stream, %% stream_once and sync requests on the same connection, it will %% take a while for the req_id-pid mapping to get cleared, but it %% should do no harm. ets:delete(ibrowse_stream, {req_id_pid, Prev_req_id}), State_1#state{prev_req_id = ReqId}; do_reply(State, _From, StreamTo, ReqId, Resp_format, Msg) -> State_1 = dec_pipeline_counter(State), Msg_1 = format_response_data(Resp_format, Msg), catch StreamTo ! {ibrowse_async_response, ReqId, Msg_1}, State_1. do_interim_reply(undefined, _, _ReqId, _Msg) -> ok; do_interim_reply(StreamTo, Response_format, ReqId, Msg) -> Msg_1 = format_response_data(Response_format, Msg), catch StreamTo ! {ibrowse_async_response, ReqId, Msg_1}. do_error_reply(#state{reqs = Reqs, tunnel_setup_queue = Tun_q} = State, Err) -> ReqList = queue:to_list(Reqs), lists:foreach(fun(#request{from=From, stream_to=StreamTo, req_id=ReqId, response_format = Resp_format}) -> ets:delete(ibrowse_stream, {req_id_pid, ReqId}), do_reply(State, From, StreamTo, ReqId, Resp_format, {error, Err}) end, ReqList), lists:foreach( fun({From, _Url, _Headers, _Method, _Body, _Options, _Timeout}) -> do_reply(State, From, undefined, undefined, undefined, Err) end, Tun_q). fail_pipelined_requests(#state{reqs = Reqs, cur_req = CurReq} = State, Reply) -> {_, Reqs_1} = queue:out(Reqs), #request{from=From, stream_to=StreamTo, req_id=ReqId, response_format = Resp_format} = CurReq, State_1 = do_reply(State, From, StreamTo, ReqId, Resp_format, Reply), do_error_reply(State_1#state{reqs = Reqs_1}, previous_request_failed). split_list_at(List, N) -> split_list_at(List, N, []). split_list_at([], _, Acc) -> {lists:reverse(Acc), []}; split_list_at(List2, 0, List1) -> {lists:reverse(List1), List2}; split_list_at([H | List2], N, List1) -> split_list_at(List2, N-1, [H | List1]). hexlist_to_integer(List) -> hexlist_to_integer(lists:reverse(List), 1, 0). hexlist_to_integer([H | T], Multiplier, Acc) -> hexlist_to_integer(T, Multiplier*16, Multiplier*to_ascii(H) + Acc); hexlist_to_integer([], _, Acc) -> Acc. to_ascii($A) -> 10; to_ascii($a) -> 10; to_ascii($B) -> 11; to_ascii($b) -> 11; to_ascii($C) -> 12; to_ascii($c) -> 12; to_ascii($D) -> 13; to_ascii($d) -> 13; to_ascii($E) -> 14; to_ascii($e) -> 14; to_ascii($F) -> 15; to_ascii($f) -> 15; to_ascii($1) -> 1; to_ascii($2) -> 2; to_ascii($3) -> 3; to_ascii($4) -> 4; to_ascii($5) -> 5; to_ascii($6) -> 6; to_ascii($7) -> 7; to_ascii($8) -> 8; to_ascii($9) -> 9; to_ascii($0) -> 0. cancel_timer(undefined) -> ok; cancel_timer(Ref) -> _ = erlang:cancel_timer(Ref), ok. cancel_timer(Ref, {eat_message, Msg}) -> cancel_timer(Ref), receive Msg -> ok after 0 -> ok end. make_req_id() -> case catch erlang:unique_integer() of {'EXIT', _} -> erlang:apply(erlang, now, []); V -> V end. to_lower(Str) when is_binary(Str) -> to_lower(binary_to_list(Str)); to_lower(Str) -> to_lower(Str, []). to_lower([H|T], Acc) when H >= $A, H =< $Z -> to_lower(T, [H+32|Acc]); to_lower([H|T], Acc) -> to_lower(T, [H|Acc]); to_lower([], Acc) -> lists:reverse(Acc). shutting_down(#state{lb_ets_tid = undefined}) -> ok; shutting_down(#state{lb_ets_tid = Tid, cur_pipeline_size = _Sz}) -> (catch ets:select_delete(Tid, [{{{'_', '_', '$1'},'_'},[{'==','$1',{const,self()}}],[true]}])). inc_pipeline_counter(#state{is_closing = true} = State) -> State; inc_pipeline_counter(#state{lb_ets_tid = undefined} = State) -> State; inc_pipeline_counter(#state{cur_pipeline_size = Pipe_sz} = State) -> State#state{cur_pipeline_size = Pipe_sz + 1}. dec_pipeline_counter(#state{cur_pipeline_size = Pipe_sz, lb_ets_tid = Tid, proc_state = Proc_state} = State) when Tid /= undefined, Proc_state /= ?dead_proc_walking -> Ts = os:timestamp(), catch ets:insert(Tid, {{Pipe_sz - 1, os:timestamp(), self()}, []}), (catch ets:select_delete(Tid, [{{{'_', '$2', '$1'},'_'}, [{'==', '$1', {const,self()}}, {'<', '$2', {const,Ts}} ], [true]}])), State#state{cur_pipeline_size = Pipe_sz - 1}; dec_pipeline_counter(State) -> State. flatten([H | _] = L) when is_integer(H) -> L; flatten([H | _] = L) when is_list(H) -> lists:flatten(L); flatten([]) -> []. get_stream_chunk_size(Options) -> case lists:keysearch(stream_chunk_size, 1, Options) of {value, {_, V}} when V > 0 -> V; _ -> ?DEFAULT_STREAM_CHUNK_SIZE end. set_inac_timer(State) -> cancel_timer(State#state.inactivity_timer_ref), set_inac_timer(State#state{inactivity_timer_ref = undefined}, get_inac_timeout(State)). set_inac_timer(State, Timeout) when is_integer(Timeout) -> Ref = erlang:send_after(Timeout, self(), timeout), State#state{inactivity_timer_ref = Ref}; set_inac_timer(State, _) -> State. get_inac_timeout(#state{cur_req = #request{options = Opts}}) -> get_value(inactivity_timeout, Opts, infinity); get_inac_timeout(#state{cur_req = undefined}) -> case ibrowse:get_config_value(inactivity_timeout, undefined) of Val when is_integer(Val) -> Val; _ -> case application:get_env(ibrowse, inactivity_timeout) of {ok, Val} when is_integer(Val), Val > 0 -> Val; _ -> 10000 end end. trace_request(Req) -> case get(my_trace_flag) of true -> %%Avoid the binary operations if trace is not on... NReq = to_binary(Req), do_trace("Sending request: ~n" "--- Request Begin ---~n~s~n" "--- Request End ---~n", [NReq]); _ -> ok end. trace_request_body(Body) -> case get(my_trace_flag) of true -> %%Avoid the binary operations if trace is not on... NBody = to_binary(Body), case size(NBody) > 1024 of true -> ok; false -> do_trace("Sending request body: ~n" "--- Request Body Begin ---~n~s~n" "--- Request Body End ---~n", [NBody]) end; false -> ok end. to_binary({X, _}) when is_function(X) -> to_binary(X); to_binary(X) when is_function(X) -> <<"body generated by function">>; to_binary(X) when is_list(X) -> list_to_binary(X); to_binary(X) when is_binary(X) -> X. get_header_value(Name, Headers, Default_val) -> case lists:keysearch(Name, 1, Headers) of false -> Default_val; {value, {_, Val}} when is_binary(Val) -> binary_to_list(Val); {value, {_, Val}} -> Val end. delayed_stop_timer() -> erlang:send_after(500, self(), delayed_stop). ibrowse-4.2.2/Makefile0000644000232200023220000000103012625271016015173 0ustar debalancedebalanceIBROWSE_VSN = $(shell sed -n 's/.*{vsn,.*"\(.*\)"}.*/\1/p' src/ibrowse.app.src) DIALYZER_PLT=$(CURDIR)/.dialyzer_plt DIALYZER_APPS=erts kernel stdlib ssl crypto public_key REBAR ?= $(shell which rebar3) all: compile compile: $(REBAR) compile clean: $(REBAR) clean test: $(REBAR) eunit xref: all $(REBAR) xref docs: $(REBAR) edoc dialyzer: $(REBAR) dialyzer install: compile mkdir -p $(DESTDIR)/lib/ibrowse-$(IBROWSE_VSN)/ cp -r _build/lib/default/ibrowse/ebin $(DESTDIR)/lib/ibrowse-$(IBROWSE_VSN)/ .PHONY: test docs