123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395 |
- %% Copyright (c) 2018, Loïc Hoguin <essen@ninenines.eu>
- %%
- %% Permission to use, copy, modify, and/or distribute this software for any
- %% purpose with or without fee is hereby granted, provided that the above
- %% copyright notice and this permission notice appear in all copies.
- %%
- %% THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
- %% WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
- %% MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
- %% ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
- %% WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
- %% ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
- %% OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
- -module(sys_SUITE).
- -compile(export_all).
- -compile(nowarn_export_all).
- -import(ct_helper, [config/2]).
- -import(ct_helper, [doc/1]).
- -import(ct_helper, [get_parent_pid/1]).
- -import(ct_helper, [get_remote_pid_tcp/1]).
- -import(ct_helper, [get_remote_pid_tls/1]).
- -import(ct_helper, [is_process_down/1]).
- -import(cowboy_test, [gun_open/1]).
- all() ->
- [{group, sys}].
- groups() ->
- [{sys, [parallel], ct_helper:all(?MODULE)}].
- init_per_suite(Config) ->
- ProtoOpts = #{
- env => #{dispatch => init_dispatch(Config)},
- logger => ?MODULE
- },
- %% Clear listener.
- {ok, _} = cowboy:start_clear(clear, [{port, 0}], ProtoOpts),
- ClearPort = ranch:get_port(clear),
- %% TLS listener.
- TLSOpts = ct_helper:get_certs_from_ets(),
- {ok, _} = cowboy:start_tls(tls, TLSOpts ++ [{port, 0}], ProtoOpts),
- TLSPort = ranch:get_port(tls),
- [
- {clear_port, ClearPort},
- %% @todo Add the h2 stuff to the opts.
- {tls_opts, TLSOpts},
- {tls_port, TLSPort}
- |Config].
- end_per_suite(_) ->
- ok = cowboy:stop_listener(clear),
- ok = cowboy:stop_listener(tls).
- init_dispatch(_) ->
- cowboy_router:compile([{"[...]", [
- {"/", hello_h, []},
- {"/loop", long_polling_sys_h, []},
- {"/ws", ws_echo, []}
- ]}]).
- %% Logger function silencing the expected warnings.
- error(Format, Args) ->
- error_logger:error_msg(Format, Args).
- warning("Received EXIT signal " ++ _, [{'EXIT', _, {shutdown, ?MODULE}}|_]) ->
- ok;
- warning(Format, Args) ->
- error_logger:warning_msg(Format, Args).
- %% proc_lib.
- proc_lib_initial_call_clear(Config) ->
- doc("Confirm that clear connection processes are started using proc_lib."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {cowboy_clear, _, _} = proc_lib:initial_call(Pid),
- ok.
- proc_lib_initial_call_tls(Config) ->
- doc("Confirm that TLS connection processes are started using proc_lib."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config), config(tls_opts, Config)),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- {cowboy_tls, _, _} = proc_lib:initial_call(Pid),
- ok.
- %% System messages.
- %%
- %% Plain system messages are received as {system, From, Msg}.
- %% The content and meaning of this message are not interpreted by
- %% the receiving process module. When a system message is received,
- %% function handle_system_msg/6 is called to handle the request.
- bad_system_from_h1(Config) ->
- doc("h1: Sending a system message with a bad From value results in a process crash."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ct_helper_error_h:ignore(Pid, gen, reply, 2),
- Pid ! {system, bad, get_state},
- {error, closed} = gen_tcp:recv(Socket, 0, 1000),
- false = is_process_alive(Pid),
- ok.
- bad_system_from_h2(Config) ->
- doc("h2: Sending a system message with a bad From value results in a process crash."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- ct_helper_error_h:ignore(Pid, gen, reply, 2),
- Pid ! {system, bad, get_state},
- {error, closed} = ssl:recv(Socket, 0, 1000),
- false = is_process_alive(Pid),
- ok.
- bad_system_from_ws(Config) ->
- doc("ws: Sending a system message with a bad From value results in a process crash."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ct_helper_error_h:ignore(Pid, gen, reply, 2),
- Pid ! {system, bad, get_state},
- {error, closed} = gen_tcp:recv(Socket, 0, 1000),
- false = is_process_alive(Pid),
- ok.
- bad_system_from_loop(Config) ->
- doc("loop: Sending a system message with a bad From value results in a process crash."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- ct_helper_error_h:ignore(Pid, gen, reply, 2),
- Pid ! {system, bad, get_state},
- {ok, "HTTP/1.1 500 "} = gen_tcp:recv(Socket, 13, 1000),
- false = is_process_alive(Pid),
- ok.
- bad_system_message_h1(Config) ->
- doc("h1: Sending a system message with a bad Request value results in an error."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, hello},
- receive
- {Ref, {error, {unknown_system_msg, hello}}} ->
- ok
- after 1000 ->
- error(timeout)
- end.
- bad_system_message_h2(Config) ->
- doc("h2: Sending a system message with a bad Request value results in an error."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, hello},
- receive
- {Ref, {error, {unknown_system_msg, hello}}} ->
- ok
- after 1000 ->
- error(timeout)
- end.
- bad_system_message_ws(Config) ->
- doc("ws: Sending a system message with a bad Request value results in an error."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, hello},
- receive
- {Ref, {error, {unknown_system_msg, hello}}} ->
- ok
- after 1000 ->
- error(timeout)
- end.
- bad_system_message_loop(Config) ->
- doc("loop: Sending a system message with a bad Request value results in an error."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, hello},
- receive
- {Ref, {error, {unknown_system_msg, hello}}} ->
- ok
- after 1000 ->
- error(timeout)
- end.
- good_system_message_h1(Config) ->
- doc("h1: System messages are handled properly."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, get_state},
- receive
- {Ref, Result} when element(1, Result) =/= error ->
- ok
- after 1000 ->
- error(timeout)
- end.
- good_system_message_h2(Config) ->
- doc("h2: System messages are handled properly."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, get_state},
- receive
- {Ref, Result} when element(1, Result) =/= error ->
- ok
- after 1000 ->
- error(timeout)
- end.
- good_system_message_ws(Config) ->
- doc("ws: System messages are handled properly."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, get_state},
- receive
- {Ref, Result} when element(1, Result) =/= error ->
- ok
- after 1000 ->
- error(timeout)
- end.
- good_system_message_loop(Config) ->
- doc("loop: System messages are handled properly."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- Ref = make_ref(),
- Pid ! {system, {self(), Ref}, get_state},
- receive
- {Ref, Result} when element(1, Result) =/= error ->
- ok
- after 1000 ->
- error(timeout)
- end.
- %% 'EXIT'.
- %%
- %% Shutdown messages. If the process traps exits, it must be able
- %% to handle a shutdown request from its parent, the supervisor.
- %% The message {'EXIT', Parent, Reason} from the parent is an order
- %% to terminate. The process must terminate when this message is
- %% received, normally with the same Reason as Parent.
- trap_exit_parent_exit_h1(Config) ->
- doc("h1: A process trapping exits must stop when receiving "
- "an 'EXIT' message from its parent."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Parent = get_parent_pid(Pid),
- Pid ! {'EXIT', Parent, {shutdown, ?MODULE}},
- {error, closed} = gen_tcp:recv(Socket, 0, 1000),
- true = is_process_down(Pid),
- ok.
- trap_exit_parent_exit_h2(Config) ->
- doc("h2: A process trapping exits must stop when receiving "
- "an 'EXIT' message from its parent."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- Parent = get_parent_pid(Pid),
- Pid ! {'EXIT', Parent, {shutdown, ?MODULE}},
- {error, closed} = ssl:recv(Socket, 0, 1000),
- true = is_process_down(Pid),
- ok.
- trap_exit_parent_exit_ws(Config) ->
- doc("ws: A process trapping exits must stop when receiving "
- "an 'EXIT' message from its parent."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Parent = get_parent_pid(Pid),
- Pid ! {'EXIT', Parent, {shutdown, ?MODULE}},
- {error, closed} = gen_tcp:recv(Socket, 0, 1000),
- true = is_process_down(Pid),
- ok.
- trap_exit_parent_exit_loop(Config) ->
- doc("loop: A process trapping exits must stop when receiving "
- "an 'EXIT' message from its parent."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- Parent = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(Parent),
- Pid ! {'EXIT', Parent, {shutdown, ?MODULE}},
- %% We exit normally but didn't send a response.
- {ok, "HTTP/1.1 204 "} = gen_tcp:recv(Socket, 13, 1000),
- true = is_process_down(Pid),
- ok.
- trap_exit_other_exit_h1(Config) ->
- doc("h1: A process trapping exits must ignore "
- "'EXIT' messages from unknown processes."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Pid ! {'EXIT', self(), {shutdown, ?MODULE}},
- ok = gen_tcp:send(Socket,
- "GET / HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- {ok, "HTTP/1.1 200 "} = gen_tcp:recv(Socket, 13, 1000),
- true = is_process_alive(Pid),
- ok.
- trap_exit_other_exit_h2(Config) ->
- doc("h2: A process trapping exits must ignore "
- "'EXIT' messages from unknown processes."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- Pid ! {'EXIT', self(), {shutdown, ?MODULE}},
- %% Send a HEADERS frame as a request.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- %% Receive a HEADERS frame as a response.
- {ok, << _:24, 1:8, _:40 >>} = ssl:recv(Socket, 9, 6000),
- true = is_process_alive(Pid),
- ok.
- trap_exit_other_exit_ws(Config) ->
- doc("ws: A process trapping exits must ignore "
- "'EXIT' messages from unknown processes."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Pid ! {'EXIT', self(), {shutdown, ?MODULE}},
- %% The process stays alive.
- {error, timeout} = gen_tcp:recv(Socket, 0, 1000),
- true = is_process_alive(Pid),
- ok.
- trap_exit_other_exit_loop(Config) ->
- doc("loop: A process trapping exits must ignore "
- "'EXIT' messages from unknown processes."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- Parent = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(Parent),
- Pid ! {'EXIT', self(), {shutdown, ?MODULE}},
- %% The process stays alive.
- {ok, "HTTP/1.1 299 "} = gen_tcp:recv(Socket, 13, 1000),
- true = is_process_alive(Pid),
- ok.
- %% get_modules.
- %%
- %% If the modules used to implement the process change dynamically
- %% during runtime, the process must understand one more message.
- %% An example is the gen_event processes. The message is
- %% {_Label, {From, Ref}, get_modules}. The reply to this message is
- %% From ! {Ref, Modules}, where Modules is a list of the currently
- %% active modules in the process.
- %%
- %% For example:
- %%
- %% 1> application:start(sasl).
- %% ok
- %% 2> gen:call(alarm_handler, self(), get_modules).
- %% {ok,[alarm_handler]}
- %% 3> whereis(alarm_handler) ! {'$gen', {self(), make_ref()}, get_modules}.
- %% {'$gen',{<0.61.0>,#Ref<0.2900144977.374865921.142102>},
- %% get_modules}
- %% 4> flush().
- %% Shell got {#Ref<0.2900144977.374865921.142102>,[alarm_handler]}
- %%
- %% Cowboy's connection processes change dynamically: it starts with
- %% cowboy_clear or cowboy_tls, then becomes cowboy_http or cowboy_http2
- %% and may then become or involve cowboy_websocket. On top of that
- %% it has various callback modules in the form of stream handlers.
- %% @todo
- %get_modules_h1(Config) ->
- %get_modules_h2(Config) ->
- %get_modules_ws(Config) ->
- %get_modules_loop(Config) ->
- %% @todo On top of this we will want to make the supervisor calls
- %% in ranch_conns_sup return dynamic instead of a list of modules.
- %% sys:change_code/4,5.
- %%
- %% We do not actually change the module code, we just ensure that
- %% calling this function does not crash the process. The function
- %% Module:system_code_change/4 will be called within the process.
- sys_change_code_h1(Config) ->
- doc("h1: The sys:change_code/4 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:suspend(Pid),
- ok = gen_tcp:send(Socket,
- "GET / HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- {error, timeout} = gen_tcp:recv(Socket, 13, 500),
- ok = sys:change_code(Pid, cowboy_http, undefined, undefined),
- ok = sys:resume(Pid),
- {ok, "HTTP/1.1 200 "} = gen_tcp:recv(Socket, 13, 500),
- ok.
- sys_change_code_h2(Config) ->
- doc("h2: The sys:change_code/4 function works as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% Suspend the process and try to get a request in. The
- %% response will not come back until we resume the process.
- ok = sys:suspend(Pid),
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"http">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- %% Receive a HEADERS frame as a response.
- {error, timeout} = ssl:recv(Socket, 9, 500),
- ok = sys:change_code(Pid, cowboy_http2, undefined, undefined),
- ok = sys:resume(Pid),
- {ok, << _:24, 1:8, _:40 >>} = ssl:recv(Socket, 9, 6000),
- ok.
- sys_change_code_ws(Config) ->
- doc("ws: The sys:change_code/4 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:suspend(Pid),
- Mask = 16#37fa213d,
- MaskedHello = ws_SUITE:do_mask(<<"Hello">>, Mask, <<>>),
- ok = gen_tcp:send(Socket, << 1:1, 0:3, 1:4, 1:1, 5:7, Mask:32, MaskedHello/binary >>),
- {error, timeout} = gen_tcp:recv(Socket, 0, 500),
- ok = sys:change_code(Pid, cowboy_websocket, undefined, undefined),
- ok = sys:resume(Pid),
- {ok, << 1:1, 0:3, 1:4, 0:1, 5:7, "Hello" >>} = gen_tcp:recv(Socket, 0, 6000),
- ok.
- sys_change_code_loop(Config) ->
- doc("loop: The sys:change_code/4 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- %% The process sends a response 500ms after initializing.
- %% We expect to not receive it until we resume it.
- ok = sys:suspend(Pid),
- {error, timeout} = gen_tcp:recv(Socket, 13, 1000),
- ok = sys:change_code(Pid, cowboy_loop, undefined, undefined),
- ok = sys:resume(Pid),
- {ok, "HTTP/1.1 299 "} = gen_tcp:recv(Socket, 13, 500),
- ok.
- %% sys:get_state/1,2.
- %%
- %% None of the modules implement Module:system_get_state/1
- %% at this time so sys:get_state/1,2 returns the Misc value.
- sys_get_state_h1(Config) ->
- doc("h1: The sys:get_state/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {State, Buffer} = sys:get_state(Pid),
- state = element(1, State),
- true = is_binary(Buffer),
- ok.
- sys_get_state_h2(Config) ->
- doc("h2: The sys:get_state/1 function works as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- {State, Buffer} = sys:get_state(Pid),
- state = element(1, State),
- true = is_binary(Buffer),
- ok.
- sys_get_state_ws(Config) ->
- doc("ws: The sys:get_state/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {State, undefined, ParseState} = sys:get_state(Pid),
- state = element(1, State),
- case element(1, ParseState) of
- ps_header -> ok;
- ps_payload -> ok
- end.
- sys_get_state_loop(Config) ->
- doc("loop: The sys:get_state/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- {Req, Env, long_polling_sys_h, undefined} = sys:get_state(Pid),
- #{pid := _, streamid := _} = Req,
- #{dispatch := _} = Env,
- ok.
- %% sys:get_status/1,2.
- sys_get_status_h1(Config) ->
- doc("h1: The sys:get_status/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {status, Pid, {module, cowboy_http}, _} = sys:get_status(Pid),
- ok.
- sys_get_status_h2(Config) ->
- doc("h2: The sys:get_status/1 function works as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- {status, Pid, {module, cowboy_http2}, _} = sys:get_status(Pid),
- ok.
- sys_get_status_ws(Config) ->
- doc("ws: The sys:get_status/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {status, Pid, {module, cowboy_websocket}, _} = sys:get_status(Pid),
- ok.
- sys_get_status_loop(Config) ->
- doc("loop: The sys:get_status/1 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- {status, Pid, {module, cowboy_loop}, _} = sys:get_status(Pid),
- ok.
- %% sys:replace_state/2,3.
- %%
- %% None of the modules implement Module:system_replace_state/2
- %% at this time so sys:replace_state/2,3 handles the Misc value.
- %%
- %% We don't actually replace the state, we only care about
- %% whether the call executes as expected.
- sys_replace_state_h1(Config) ->
- doc("h1: The sys:replace_state/2 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {State, Buffer} = sys:replace_state(Pid, fun(S) -> S end),
- state = element(1, State),
- true = is_binary(Buffer),
- ok.
- sys_replace_state_h2(Config) ->
- doc("h2: The sys:replace_state/2 function works as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- {State, Buffer} = sys:replace_state(Pid, fun(S) -> S end),
- state = element(1, State),
- true = is_binary(Buffer),
- ok.
- sys_replace_state_ws(Config) ->
- doc("ws: The sys:replace_state/2 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {State, undefined, ParseState} = sys:replace_state(Pid, fun(S) -> S end),
- state = element(1, State),
- case element(1, ParseState) of
- ps_header -> ok;
- ps_payload -> ok
- end.
- sys_replace_state_loop(Config) ->
- doc("loop: The sys:replace_state/2 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- {Req, Env, long_polling_sys_h, undefined} = sys:replace_state(Pid, fun(S) -> S end),
- #{pid := _, streamid := _} = Req,
- #{dispatch := _} = Env,
- ok.
- %% sys:suspend/1 and sys:resume/1.
- sys_suspend_and_resume_h1(Config) ->
- doc("h1: The sys:suspend/1 and sys:resume/1 functions work as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:suspend(Pid),
- ok = gen_tcp:send(Socket,
- "GET / HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- {error, timeout} = gen_tcp:recv(Socket, 13, 500),
- ok = sys:resume(Pid),
- {ok, "HTTP/1.1 200 "} = gen_tcp:recv(Socket, 13, 500),
- ok.
- sys_suspend_and_resume_h2(Config) ->
- doc("h2: The sys:suspend/1 and sys:resume/1 functions work as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% Suspend the process and try to get a request in. The
- %% response will not come back until we resume the process.
- ok = sys:suspend(Pid),
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"http">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- %% Receive a HEADERS frame as a response.
- {error, timeout} = ssl:recv(Socket, 9, 500),
- ok = sys:resume(Pid),
- {ok, << _:24, 1:8, _:40 >>} = ssl:recv(Socket, 9, 6000),
- ok.
- sys_suspend_and_resume_ws(Config) ->
- doc("ws: The sys:suspend/1 and sys:resume/1 functions work as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:suspend(Pid),
- Mask = 16#37fa213d,
- MaskedHello = ws_SUITE:do_mask(<<"Hello">>, Mask, <<>>),
- ok = gen_tcp:send(Socket, << 1:1, 0:3, 1:4, 1:1, 5:7, Mask:32, MaskedHello/binary >>),
- {error, timeout} = gen_tcp:recv(Socket, 0, 500),
- ok = sys:resume(Pid),
- {ok, << 1:1, 0:3, 1:4, 0:1, 5:7, "Hello" >>} = gen_tcp:recv(Socket, 0, 6000),
- ok.
- sys_suspend_and_resume_loop(Config) ->
- doc("loop: The sys:suspend/1 and sys:resume/1 functions work as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- %% The process sends a response 500ms after initializing.
- %% We expect to not receive it until we resume it.
- ok = sys:suspend(Pid),
- {error, timeout} = gen_tcp:recv(Socket, 13, 1000),
- ok = sys:resume(Pid),
- {ok, "HTTP/1.1 299 "} = gen_tcp:recv(Socket, 13, 500),
- ok.
- %% sys:terminate/2,3.
- %%
- %% The callback Module:system_terminate/4 is used in all cases.
- sys_terminate_h1(Config) ->
- doc("h1: The sys:terminate/2,3 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:terminate(Pid, {shutdown, ?MODULE}),
- {error, closed} = gen_tcp:recv(Socket, 0, 500),
- ok.
- sys_terminate_h2(Config) ->
- doc("h2: The sys:terminate/2,3 function works as expected."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- %% Skip the SETTINGS frame.
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- timer:sleep(100),
- Pid = get_remote_pid_tls(Socket),
- ok = sys:terminate(Pid, {shutdown, ?MODULE}),
- {error, closed} = ssl:recv(Socket, 0, 500),
- ok.
- sys_terminate_ws(Config) ->
- doc("ws: The sys:terminate/2,3 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- ok = sys:terminate(Pid, {shutdown, ?MODULE}),
- {error, closed} = gen_tcp:recv(Socket, 0, 500),
- ok.
- sys_terminate_loop(Config) ->
- doc("loop: The sys:terminate/2,3 function works as expected."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config), [{active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- SupPid = get_remote_pid_tcp(Socket),
- [{_, Pid, _, _}] = supervisor:which_children(SupPid),
- %% We stop the process normally and therefore get a 204.
- ok = sys:terminate(Pid, {shutdown, ?MODULE}),
- {ok, "HTTP/1.1 204 "} = gen_tcp:recv(Socket, 13, 500),
- ok.
- %% @todo Debugging functionality from sys.
- %%
- %% The functions make references to a debug structure.
- %% The debug structure is a list of dbg_opt(), which is
- %% an internal data type used by the function handle_system_msg/6.
- %% No debugging is performed if it is an empty list.
- %%
- %% Cowboy currently does not implement sys debugging.
- %%
- %% The following functions are concerned:
- %%
- %% * sys:install/2,3
- %% * sys:log/2,3
- %% * sys:log_to_file/2,3
- %% * sys:no_debug/1,2
- %% * sys:remove/2,3
- %% * sys:statistics/2,3
- %% * sys:trace/2,3
- %% * call debug_options/1
- %% * call get_debug/3
- %% * call handle_debug/4
- %% * call print_log/1
- %% supervisor.
- %%
- %% The connection processes act as supervisors by default
- %% so they must handle the supervisor messages.
- %% supervisor:count_children/1.
- supervisor_count_children_h1(Config) ->
- doc("h1: The function supervisor:count_children/1 must work."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% No request was sent so there's no children.
- Counts1 = supervisor:count_children(Pid),
- 1 = proplists:get_value(specs, Counts1),
- 0 = proplists:get_value(active, Counts1),
- 0 = proplists:get_value(supervisors, Counts1),
- 0 = proplists:get_value(workers, Counts1),
- %% Send a request, observe that a children exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- Counts2 = supervisor:count_children(Pid),
- 1 = proplists:get_value(specs, Counts2),
- 1 = proplists:get_value(active, Counts2),
- 0 = proplists:get_value(supervisors, Counts2),
- 1 = proplists:get_value(workers, Counts2),
- ok.
- supervisor_count_children_h2(Config) ->
- doc("h2: The function supervisor:count_children/1 must work."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% No request was sent so there's no children.
- Counts1 = supervisor:count_children(Pid),
- 1 = proplists:get_value(specs, Counts1),
- 0 = proplists:get_value(active, Counts1),
- 0 = proplists:get_value(supervisors, Counts1),
- 0 = proplists:get_value(workers, Counts1),
- %% Send a request, observe that a children exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- Counts2 = supervisor:count_children(Pid),
- 1 = proplists:get_value(specs, Counts2),
- 1 = proplists:get_value(active, Counts2),
- 0 = proplists:get_value(supervisors, Counts2),
- 1 = proplists:get_value(workers, Counts2),
- ok.
- supervisor_count_children_ws(Config) ->
- doc("ws: The function supervisor:count_children/1 must work. "
- "Websocket connections never have children."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- Counts = supervisor:count_children(Pid),
- 1 = proplists:get_value(specs, Counts),
- 0 = proplists:get_value(active, Counts),
- 0 = proplists:get_value(supervisors, Counts),
- 0 = proplists:get_value(workers, Counts),
- ok.
- %% supervisor:delete_child/2.
- supervisor_delete_child_not_found_h1(Config) ->
- doc("h1: The function supervisor:delete_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:delete_child(Pid, cowboy_http),
- %% When a child exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- {error, not_found} = supervisor:delete_child(Pid, cowboy_http),
- ok.
- supervisor_delete_child_not_found_h2(Config) ->
- doc("h2: The function supervisor:delete_child/2 must return {error, not_found}."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:delete_child(Pid, cowboy_http2),
- %% When a child exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- {error, not_found} = supervisor:delete_child(Pid, cowboy_http2),
- ok.
- supervisor_delete_child_not_found_ws(Config) ->
- doc("ws: The function supervisor:delete_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, not_found} = supervisor:delete_child(Pid, cowboy_websocket),
- ok.
- %% supervisor:get_childspec/2.
- supervisor_get_childspec_not_found_h1(Config) ->
- doc("h1: The function supervisor:get_childspec/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:get_childspec(Pid, cowboy_http),
- %% When a child exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- {error, not_found} = supervisor:get_childspec(Pid, cowboy_http),
- ok.
- supervisor_get_childspec_not_found_h2(Config) ->
- doc("h2: The function supervisor:get_childspec/2 must return {error, not_found}."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:get_childspec(Pid, cowboy_http2),
- %% When a child exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- {error, not_found} = supervisor:get_childspec(Pid, cowboy_http2),
- ok.
- supervisor_get_childspec_not_found_ws(Config) ->
- doc("ws: The function supervisor:get_childspec/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, not_found} = supervisor:get_childspec(Pid, cowboy_websocket),
- ok.
- %% supervisor:restart_child/2.
- supervisor_restart_child_not_found_h1(Config) ->
- doc("h1: The function supervisor:restart_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:restart_child(Pid, cowboy_http),
- %% When a child exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- {error, not_found} = supervisor:restart_child(Pid, cowboy_http),
- ok.
- supervisor_restart_child_not_found_h2(Config) ->
- doc("h2: The function supervisor:restart_child/2 must return {error, not_found}."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:restart_child(Pid, cowboy_http2),
- %% When a child exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- {error, not_found} = supervisor:restart_child(Pid, cowboy_http2),
- ok.
- supervisor_restart_child_not_found_ws(Config) ->
- doc("ws: The function supervisor:restart_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, not_found} = supervisor:restart_child(Pid, cowboy_websocket),
- ok.
- %% supervisor:start_child/2 must return {error, start_child_disabled}
- supervisor_start_child_not_found_h1(Config) ->
- doc("h1: The function supervisor:start_child/2 must return {error, start_child_disabled}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, start_child_disabled} = supervisor:start_child(Pid, #{
- id => error,
- start => {error, error, []}
- }),
- ok.
- supervisor_start_child_not_found_h2(Config) ->
- doc("h2: The function supervisor:start_child/2 must return {error, start_child_disabled}."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- {error, start_child_disabled} = supervisor:start_child(Pid, #{
- id => error,
- start => {error, error, []}
- }),
- ok.
- supervisor_start_child_not_found_ws(Config) ->
- doc("ws: The function supervisor:start_child/2 must return {error, start_child_disabled}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, start_child_disabled} = supervisor:start_child(Pid, #{
- id => error,
- start => {error, error, []}
- }),
- ok.
- %% supervisor:terminate_child/2.
- supervisor_terminate_child_not_found_h1(Config) ->
- doc("h1: The function supervisor:terminate_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:terminate_child(Pid, cowboy_http),
- %% When a child exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- {error, not_found} = supervisor:terminate_child(Pid, cowboy_http),
- ok.
- supervisor_terminate_child_not_found_h2(Config) ->
- doc("h2: The function supervisor:terminate_child/2 must return {error, not_found}."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% When no children exist.
- {error, not_found} = supervisor:terminate_child(Pid, cowboy_http2),
- %% When a child exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- {error, not_found} = supervisor:terminate_child(Pid, cowboy_http2),
- ok.
- supervisor_terminate_child_not_found_ws(Config) ->
- doc("ws: The function supervisor:terminate_child/2 must return {error, not_found}."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- {error, not_found} = supervisor:terminate_child(Pid, cowboy_websocket),
- ok.
- %% supervisor:which_children/1.
- %%
- %% @todo The list of modules returned is probably wrong. This will
- %% need to be corrected when get_modules gets implemented.
- supervisor_which_children_h1(Config) ->
- doc("h1: The function supervisor:which_children/1 must work."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [{active, false}]),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- %% No request was sent so there's no children.
- [] = supervisor:which_children(Pid),
- %% Send a request, observe that a children exists.
- ok = gen_tcp:send(Socket,
- "GET /loop HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "\r\n"),
- timer:sleep(100),
- [{cowboy_http, Child, worker, [cowboy_http]}] = supervisor:which_children(Pid),
- true = is_pid(Child),
- ok.
- supervisor_which_children_h2(Config) ->
- doc("h2: The function supervisor:which_children/1 must work."),
- {ok, Socket} = ssl:connect("localhost", config(tls_port, Config),
- [{active, false}, binary, {alpn_advertised_protocols, [<<"h2">>]}]),
- do_http2_handshake(Socket),
- Pid = get_remote_pid_tls(Socket),
- %% No request was sent so there's no children.
- [] = supervisor:which_children(Pid),
- %% Send a request, observe that a children exists.
- {HeadersBlock, _} = cow_hpack:encode([
- {<<":method">>, <<"GET">>},
- {<<":scheme">>, <<"https">>},
- {<<":authority">>, <<"localhost">>}, %% @todo Correct port number.
- {<<":path">>, <<"/loop">>}
- ]),
- ok = ssl:send(Socket, cow_http2:headers(1, fin, HeadersBlock)),
- timer:sleep(100),
- [{cowboy_http2, Child, worker, [cowboy_http2]}] = supervisor:which_children(Pid),
- true = is_pid(Child),
- ok.
- supervisor_which_children_ws(Config) ->
- doc("ws: The function supervisor:which_children/1 must work. "
- "Websocket connections never have children."),
- {ok, Socket} = gen_tcp:connect("localhost", config(clear_port, Config),
- [binary, {active, false}]),
- ok = gen_tcp:send(Socket,
- "GET /ws HTTP/1.1\r\n"
- "Host: localhost\r\n"
- "Connection: Upgrade\r\n"
- "Origin: http://localhost\r\n"
- "Sec-WebSocket-Version: 13\r\n"
- "Sec-WebSocket-Key: dGhlIHNhbXBsZSBub25jZQ==\r\n"
- "Upgrade: websocket\r\n"
- "\r\n"),
- {ok, Handshake} = gen_tcp:recv(Socket, 0, 5000),
- {ok, {http_response, {1, 1}, 101, _}, _} = erlang:decode_packet(http, Handshake, []),
- timer:sleep(100),
- Pid = get_remote_pid_tcp(Socket),
- [] = supervisor:which_children(Pid),
- ok.
- %% Internal.
- do_http2_handshake(Socket) ->
- ok = ssl:send(Socket, "PRI * HTTP/2.0\r\n\r\nSM\r\n\r\n"),
- {ok, <<_,_,_,4,_/bits>>} = ssl:recv(Socket, 0, 1000),
- ok = ssl:send(Socket, [cow_http2:settings(#{}), cow_http2:settings_ack()]),
- {ok, << 0:24, 4:8, 1:8, 0:32 >>} = ssl:recv(Socket, 9, 1000),
- ok.
|