Browse Source

Set transport options without suspend

Lift the restriction that a listener must be suspended before
transport options can be changed.

* Changes to the `max_connections`, `handshake_timeout` and `shutdown`
  options will take effect immediately.
* Changes to the `num_acceptors`, `num_listen_sockets` and `socket_opts`
  options will take effect when a listener is suspended and resumed, or
  when the acceptors supervisor restarts.
* Changes to the `num_conns_sups` and `connection_type` options will only
  take effect when the connections super-supervisor restarts.
* Changes to the `logger` option will never take effect, unless a listener
  is stopped and started with fresh transport options.

The fetching and handing down of transport options changes with this
commit, to ensure consistency between the individual components in the
hierarchy.

* The `num_acceptors` option is handed down from the listener supervisor to
  the acceptors supervisor in the child spec, while the `num_listen_sockets`
  and `socket_opts` options are read inside the acceptors supervisor itself.
  This way, the `num_acceptors` option will only take effect when the listener
  supervisor restarts, whereas the other two options will take effect
  when acceptors supervisor restarts. This commit moves the fetching of
  the `num_acceptors` option into the acceptors supervisor as well.
* The `logger` option is read in multiple places throughout the hierarchy.
  This way it may happen that processes that suffered a crash and restart
  may use a different logger than other processes that did not. This commit
  reads the `logger` from the transport options given to the listener supervisor
  start function, and hands it down from there.
* The `connection_type` option is read individually by each connection supervisor.
  This way, a restart of an individual connection supervisor may cause them
  to use a different connection type than the others. This commit reads the
  transport options in the connections super-supervisor, and hands them down to
  the individual connections supervisors.
* The `num_conns_sups` is handed down from the listener supervisor to the
  connections super-supervisor. This way, a change to this option will only
  take effect when the listener supervisor restarts. This commit moves
  the fetching of this option inside the connections super-supervisor. This
  change is merely for structural consistency, it is not necessary for operational
  consistency.
juhlig 6 years ago
parent
commit
f13ea02525

+ 17 - 8
doc/src/guide/listeners.asciidoc

@@ -358,14 +358,23 @@ Opts = ranch:get_protocol_options(tcp_echo).
 
 
 === Changing transport options
 === Changing transport options
 
 
-Ranch allows you to change the transport options of a listener, for
-example to make it listen on a different port.
-
-To change transport options, the listener has to be suspended first.
-Then you are allowed to change the transport options by calling
-`ranch:set_transport_options/2` with the listener name and the new
-transport options as arguments.
-After that, you can resume the listener.
+Ranch allows you to change the transport options of a listener with
+the `ranch:set_transport_options/2` function, for example to change the
+number of acceptors or to make it listen on a different port.
+
+Changes to the following options will take effect...
+
+* immediately:
+** `max_connections`
+** `handshake_timeout`
+** `shutdown`
+* only after the listener has been suspended and resumed:
+** `num_acceptors`
+** `num_listen_sockets`
+** `socket_opts`
+* only when the entire listener is restarted:
+** `num_conns_sups`
+** `logger`
 
 
 .Changing the transport options
 .Changing the transport options
 
 

+ 20 - 6
doc/src/manual/ranch.set_transport_options.asciidoc

@@ -9,16 +9,25 @@ ranch:set_transport_options - Set the transport options
 [source,erlang]
 [source,erlang]
 ----
 ----
 set_transport_options(Ref       :: ranch:ref(),
 set_transport_options(Ref       :: ranch:ref(),
-                      TransOpts :: any())
-    -> ok | {error, running}
+                      TransOpts :: ranch:opts())
+    -> ok | {error, Reason :: term()}
 ----
 ----
 
 
 Set the transport options.
 Set the transport options.
 
 
-The listener must be suspended for this call to succeed.
-If the listener is running, `{error, running}` will be returned.
+Changes to the following options will take effect...
 
 
-The change will take effect when the listener resumes.
+* immediately:
+** `max_connections`
+** `handshake_timeout`
+** `shutdown`
+* only after the listener has been suspended and resumed:
+** `num_acceptors`
+** `num_listen_sockets`
+** `socket_opts`
+* only when the entire listener is restarted:
+** `num_conns_sups`
+** `logger`
 
 
 == Arguments
 == Arguments
 
 
@@ -32,10 +41,15 @@ The new transport options.
 
 
 == Return value
 == Return value
 
 
-The atom `ok` is always returned. It can be safely ignored.
+The atom `ok` is returned on success.
+
+An error tuple is returned on failure, for example if the given
+transport options contain invalid values.
 
 
 == Changelog
 == Changelog
 
 
+* *2.0*: The restriction that the listener must be suspended
+         has been removed.
 * *2.0*: The `TransOpts` argument must no longer contain
 * *2.0*: The `TransOpts` argument must no longer contain
          Ranch-specific options if given as a list. Use a map.
          Ranch-specific options if given as a list. Use a map.
 
 

+ 12 - 6
src/ranch.erl

@@ -291,16 +291,22 @@ set_max_connections(Ref, MaxConnections) ->
 get_transport_options(Ref) ->
 get_transport_options(Ref) ->
 	ranch_server:get_transport_options(Ref).
 	ranch_server:get_transport_options(Ref).
 
 
--spec set_transport_options(ref(), opts()) -> ok | {error, running}.
+-spec set_transport_options(ref(), opts()) -> ok | {error, term()}.
 set_transport_options(Ref, TransOpts0) ->
 set_transport_options(Ref, TransOpts0) ->
 	TransOpts = normalize_opts(TransOpts0),
 	TransOpts = normalize_opts(TransOpts0),
-	case get_status(Ref) of
-		suspended ->
-			ok = ranch_server:set_transport_options(Ref, TransOpts);
-		running ->
-			{error, running}
+	case validate_transport_opts(TransOpts) of
+		ok ->
+			ok = ranch_server:set_transport_options(Ref, TransOpts),
+			ok = apply_transport_options(Ref, TransOpts);
+		TransOptsError ->
+			TransOptsError
 	end.
 	end.
 
 
+apply_transport_options(Ref, TransOpts) ->
+	_ = [ConnsSup ! {set_transport_options, TransOpts}
+		|| {_, ConnsSup} <- ranch_server:get_connections_sups(Ref)],
+	ok.
+
 -spec get_protocol_options(ref()) -> any().
 -spec get_protocol_options(ref()) -> any().
 get_protocol_options(Ref) ->
 get_protocol_options(Ref) ->
 	ranch_server:get_protocol_options(Ref).
 	ranch_server:get_protocol_options(Ref).

+ 5 - 5
src/ranch_acceptors_sup.erl

@@ -18,15 +18,15 @@
 -export([start_link/3]).
 -export([start_link/3]).
 -export([init/1]).
 -export([init/1]).
 
 
--spec start_link(ranch:ref(), pos_integer(), module())
+-spec start_link(ranch:ref(), module(), module())
 	-> {ok, pid()}.
 	-> {ok, pid()}.
-start_link(Ref, NumAcceptors, Transport) ->
-	supervisor:start_link(?MODULE, [Ref, NumAcceptors, Transport]).
+start_link(Ref, Transport, Logger) ->
+	supervisor:start_link(?MODULE, [Ref, Transport, Logger]).
 
 
 -spec init([term()]) -> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
 -spec init([term()]) -> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
-init([Ref, NumAcceptors, Transport]) ->
+init([Ref, Transport, Logger]) ->
 	TransOpts = ranch_server:get_transport_options(Ref),
 	TransOpts = ranch_server:get_transport_options(Ref),
-	Logger = maps:get(logger, TransOpts, logger),
+	NumAcceptors = maps:get(num_acceptors, TransOpts, 10),
 	NumListenSockets = maps:get(num_listen_sockets, TransOpts, 1),
 	NumListenSockets = maps:get(num_listen_sockets, TransOpts, 1),
 	%% We temporarily put the logger in the process dictionary
 	%% We temporarily put the logger in the process dictionary
 	%% so that it can be used from ranch:filter_options. The
 	%% so that it can be used from ranch:filter_options. The

+ 25 - 10
src/ranch_conns_sup.erl

@@ -18,12 +18,12 @@
 -module(ranch_conns_sup).
 -module(ranch_conns_sup).
 
 
 %% API.
 %% API.
--export([start_link/4]).
+-export([start_link/6]).
 -export([start_protocol/3]).
 -export([start_protocol/3]).
 -export([active_connections/1]).
 -export([active_connections/1]).
 
 
 %% Supervisor internals.
 %% Supervisor internals.
--export([init/5]).
+-export([init/7]).
 -export([system_continue/3]).
 -export([system_continue/3]).
 -export([system_terminate/4]).
 -export([system_terminate/4]).
 -export([system_code_change/4]).
 -export([system_code_change/4]).
@@ -46,10 +46,10 @@
 
 
 %% API.
 %% API.
 
 
--spec start_link(ranch:ref(), pos_integer(), module(), module()) -> {ok, pid()}.
-start_link(Ref, Id, Transport, Protocol) ->
+-spec start_link(ranch:ref(), pos_integer(), module(), any(), module(), module()) -> {ok, pid()}.
+start_link(Ref, Id, Transport, TransOpts, Protocol, Logger) ->
 	proc_lib:start_link(?MODULE, init,
 	proc_lib:start_link(?MODULE, init,
-		[self(), Ref, Id, Transport, Protocol]).
+		[self(), Ref, Id, Transport, TransOpts, Protocol, Logger]).
 
 
 %% We can safely assume we are on the same node as the supervisor.
 %% We can safely assume we are on the same node as the supervisor.
 %%
 %%
@@ -99,16 +99,14 @@ active_connections(SupPid) ->
 
 
 %% Supervisor internals.
 %% Supervisor internals.
 
 
--spec init(pid(), ranch:ref(), pos_integer(), module(), module()) -> no_return().
-init(Parent, Ref, Id, Transport, Protocol) ->
+-spec init(pid(), ranch:ref(), pos_integer(), module(), any(), module(), module()) -> no_return().
+init(Parent, Ref, Id, Transport, TransOpts, Protocol, Logger) ->
 	process_flag(trap_exit, true),
 	process_flag(trap_exit, true),
 	ok = ranch_server:set_connections_sup(Ref, Id, self()),
 	ok = ranch_server:set_connections_sup(Ref, Id, self()),
 	MaxConns = ranch_server:get_max_connections(Ref),
 	MaxConns = ranch_server:get_max_connections(Ref),
-	TransOpts = ranch_server:get_transport_options(Ref),
 	ConnType = maps:get(connection_type, TransOpts, worker),
 	ConnType = maps:get(connection_type, TransOpts, worker),
 	Shutdown = maps:get(shutdown, TransOpts, 5000),
 	Shutdown = maps:get(shutdown, TransOpts, 5000),
 	HandshakeTimeout = maps:get(handshake_timeout, TransOpts, 5000),
 	HandshakeTimeout = maps:get(handshake_timeout, TransOpts, 5000),
-	Logger = maps:get(logger, TransOpts, logger),
 	ProtoOpts = ranch_server:get_protocol_options(Ref),
 	ProtoOpts = ranch_server:get_protocol_options(Ref),
 	ok = proc_lib:init_ack(Parent, {ok, self()}),
 	ok = proc_lib:init_ack(Parent, {ok, self()}),
 	loop(#state{parent=Parent, ref=Ref, conn_type=ConnType,
 	loop(#state{parent=Parent, ref=Ref, conn_type=ConnType,
@@ -166,8 +164,11 @@ loop(State=#state{parent=Parent, ref=Ref, conn_type=ConnType,
 		{set_max_conns, MaxConns2} ->
 		{set_max_conns, MaxConns2} ->
 			loop(State#state{max_conns=MaxConns2},
 			loop(State#state{max_conns=MaxConns2},
 				CurConns, NbChildren, Sleepers);
 				CurConns, NbChildren, Sleepers);
+		%% Upgrade the transport options.
+		{set_transport_options, TransOpts} ->
+			set_transport_options(State, CurConns, NbChildren, Sleepers, TransOpts);
 		%% Upgrade the protocol options.
 		%% Upgrade the protocol options.
-		{set_opts, Opts2} ->
+		{set_protocol_options, Opts2} ->
 			loop(State#state{opts=Opts2},
 			loop(State#state{opts=Opts2},
 				CurConns, NbChildren, Sleepers);
 				CurConns, NbChildren, Sleepers);
 		{'EXIT', Parent, Reason} ->
 		{'EXIT', Parent, Reason} ->
@@ -250,6 +251,20 @@ handshake(State=#state{ref=Ref, transport=Transport, handshake_timeout=Handshake
 			loop(State, CurConns, NbChildren, Sleepers)
 			loop(State, CurConns, NbChildren, Sleepers)
 	end.
 	end.
 
 
+set_transport_options(State=#state{max_conns=MaxConns0}, CurConns, NbChildren, Sleepers0, TransOpts) ->
+	MaxConns1 = maps:get(max_connections, TransOpts, 1024),
+	HandshakeTimeout = maps:get(handshake_timeout, TransOpts, 5000),
+	Shutdown = maps:get(shutdown, TransOpts, 5000),
+	Sleepers1 = case MaxConns1 > MaxConns0 of
+		true ->
+			_ = [To ! self() || To <- Sleepers0],
+			[];
+		false ->
+			Sleepers0
+	end,
+	loop(State#state{max_conns=MaxConns1, handshake_timeout=HandshakeTimeout, shutdown=Shutdown},
+		CurConns, NbChildren, Sleepers1).
+
 -spec terminate(#state{}, any(), non_neg_integer()) -> no_return().
 -spec terminate(#state{}, any(), non_neg_integer()) -> no_return().
 terminate(#state{shutdown=brutal_kill}, Reason, _) ->
 terminate(#state{shutdown=brutal_kill}, Reason, _) ->
 	kill_children(get_keys(active)),
 	kill_children(get_keys(active)),

+ 9 - 6
src/ranch_conns_sup_sup.erl

@@ -19,19 +19,22 @@
 -export([start_link/4]).
 -export([start_link/4]).
 -export([init/1]).
 -export([init/1]).
 
 
--spec start_link(ranch:ref(), pos_integer(), ranch:opts(), module()) -> {ok, pid()}.
-start_link(Ref, NumConnsSups, Transport, Protocol) ->
+-spec start_link(ranch:ref(), module(), module(), module()) -> {ok, pid()}.
+start_link(Ref, Transport, Protocol, Logger) ->
 	ok = ranch_server:cleanup_connections_sups(Ref),
 	ok = ranch_server:cleanup_connections_sups(Ref),
 	supervisor:start_link(?MODULE, {
 	supervisor:start_link(?MODULE, {
-		Ref, NumConnsSups, Transport, Protocol
+		Ref, Transport, Protocol, Logger
 	}).
 	}).
 
 
--spec init({ranch:ref(), pos_integer(), module(), module()})
+-spec init({ranch:ref(), module(), module(), module()})
 	-> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
 	-> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
-init({Ref, NumConnsSups, Transport, Protocol}) ->
+init({Ref, Transport, Protocol, Logger}) ->
+	TransOpts = ranch_server:get_transport_options(Ref),
+	NumAcceptors = maps:get(num_acceptors, TransOpts, 10),
+	NumConnsSups = maps:get(num_conns_sups, TransOpts, NumAcceptors),
 	ChildSpecs = [#{
 	ChildSpecs = [#{
 		id => {ranch_conns_sup, N},
 		id => {ranch_conns_sup, N},
-		start => {ranch_conns_sup, start_link, [Ref, N, Transport, Protocol]},
+		start => {ranch_conns_sup, start_link, [Ref, N, Transport, TransOpts, Protocol, Logger]},
 		type => supervisor
 		type => supervisor
 	} || N <- lists:seq(1, NumConnsSups)],
 	} || N <- lists:seq(1, NumConnsSups)],
 	{ok, {#{intensity => 1 + ceil(math:log2(NumConnsSups))}, ChildSpecs}}.
 	{ok, {#{intensity => 1 + ceil(math:log2(NumConnsSups))}, ChildSpecs}}.

+ 6 - 7
src/ranch_listener_sup.erl

@@ -21,28 +21,27 @@
 -spec start_link(ranch:ref(), module(), any(), module(), any())
 -spec start_link(ranch:ref(), module(), any(), module(), any())
 	-> {ok, pid()}.
 	-> {ok, pid()}.
 start_link(Ref, Transport, TransOpts, Protocol, ProtoOpts) ->
 start_link(Ref, Transport, TransOpts, Protocol, ProtoOpts) ->
-	NumAcceptors = maps:get(num_acceptors, TransOpts, 10),
-	NumConnsSups = maps:get(num_conns_sups, TransOpts, NumAcceptors),
 	MaxConns = maps:get(max_connections, TransOpts, 1024),
 	MaxConns = maps:get(max_connections, TransOpts, 1024),
+	Logger = maps:get(logger, TransOpts, logger),
 	ranch_server:set_new_listener_opts(Ref, MaxConns, TransOpts, ProtoOpts,
 	ranch_server:set_new_listener_opts(Ref, MaxConns, TransOpts, ProtoOpts,
 		[Ref, Transport, TransOpts, Protocol, ProtoOpts]),
 		[Ref, Transport, TransOpts, Protocol, ProtoOpts]),
 	supervisor:start_link(?MODULE, {
 	supervisor:start_link(?MODULE, {
-		Ref, NumAcceptors, NumConnsSups, Transport, Protocol
+		Ref, Transport, Protocol, Logger
 	}).
 	}).
 
 
--spec init({ranch:ref(), pos_integer(), pos_integer(), module(), module()})
+-spec init({ranch:ref(), module(), module(), module()})
 	-> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
 	-> {ok, {supervisor:sup_flags(), [supervisor:child_spec()]}}.
-init({Ref, NumAcceptors, NumConnsSups, Transport, Protocol}) ->
+init({Ref, Transport, Protocol, Logger}) ->
 	ok = ranch_server:set_listener_sup(Ref, self()),
 	ok = ranch_server:set_listener_sup(Ref, self()),
 	ChildSpecs = [
 	ChildSpecs = [
 		#{
 		#{
 			id => ranch_conns_sup_sup,
 			id => ranch_conns_sup_sup,
-			start => {ranch_conns_sup_sup, start_link, [Ref, NumConnsSups, Transport, Protocol]},
+			start => {ranch_conns_sup_sup, start_link, [Ref, Transport, Protocol, Logger]},
 			type => supervisor
 			type => supervisor
 		},
 		},
 		#{
 		#{
 			id => ranch_acceptors_sup,
 			id => ranch_acceptors_sup,
-			start => {ranch_acceptors_sup, start_link, [Ref, NumAcceptors, Transport]},
+			start => {ranch_acceptors_sup, start_link, [Ref, Transport, Logger]},
 			type => supervisor
 			type => supervisor
 		}
 		}
 	],
 	],

+ 1 - 1
src/ranch_server.erl

@@ -202,7 +202,7 @@ handle_call({set_trans_opts, Ref, Opts}, _, State) ->
 	{reply, ok, State};
 	{reply, ok, State};
 handle_call({set_proto_opts, Ref, Opts}, _, State) ->
 handle_call({set_proto_opts, Ref, Opts}, _, State) ->
 	ets:insert(?TAB, {{proto_opts, Ref}, Opts}),
 	ets:insert(?TAB, {{proto_opts, Ref}, Opts}),
-	_ = [ConnsSup ! {set_opts, Opts} || {_, ConnsSup} <- get_connections_sups(Ref)],
+	_ = [ConnsSup ! {set_protocol_options, Opts} || {_, ConnsSup} <- get_connections_sups(Ref)],
 	{reply, ok, State};
 	{reply, ok, State};
 handle_call(_Request, _From, State) ->
 handle_call(_Request, _From, State) ->
 	{reply, ignore, State}.
 	{reply, ignore, State}.

+ 23 - 8
test/acceptor_SUITE.erl

@@ -73,6 +73,7 @@ groups() ->
 		misc_info,
 		misc_info,
 		misc_info_embedded,
 		misc_info_embedded,
 		misc_opts_logger,
 		misc_opts_logger,
+		misc_set_transport_options,
 		misc_wait_for_connections
 		misc_wait_for_connections
 	]}, {supervisor, [
 	]}, {supervisor, [
 		connection_type_supervisor,
 		connection_type_supervisor,
@@ -323,6 +324,28 @@ misc_repeated_remove(_) ->
 	true = lists:all(fun ({_, ConnsSup}) -> erlang:is_process_alive(ConnsSup) end, ConnsSups),
 	true = lists:all(fun ({_, ConnsSup}) -> erlang:is_process_alive(ConnsSup) end, ConnsSups),
 	ok = ranch:stop_listener(Name).
 	ok = ranch:stop_listener(Name).
 
 
+misc_set_transport_options(_) ->
+	doc(""),
+	Name = name(),
+	{ok, ListenerSupPid} = ranch:start_listener(Name, ranch_tcp, #{max_connections => 10,
+		handshake_timeout => 5000, shutdown => 1000, num_acceptors => 1,
+		socket_opts => [{send_timeout, 5000}]}, echo_protocol, []),
+	ok = ranch:set_transport_options(Name, #{max_connections => 20, handshake_timeout => 5001,
+		num_acceptors => 2, shutdown => 1001, socket_opts => [{send_timeout, 5002}]}),
+	ConnsSups = [ConnsSup || {_, ConnsSup} <- ranch_server:get_connections_sups(Name)],
+	_ = [begin
+		{State, _, _, _} = sys:get_state(ConnsSup),
+		20 = element(10, State),
+		5001 = element(9, State),
+		1001 = element(5, State)
+	end || ConnsSup <- ConnsSups],
+	ok = ranch:suspend_listener(Name),
+	ok = ranch:resume_listener(Name),
+	2 = length(ranch:procs(Name, acceptors)),
+	LSocket = do_get_listener_socket(ListenerSupPid),
+	{ok, [{send_timeout, 5002}]} = ranch_tcp:getopts(LSocket, [send_timeout]),
+	ok = ranch:stop_listener(Name).
+
 misc_wait_for_connections(_) ->
 misc_wait_for_connections(_) ->
 	doc("Ensure wait for connections works."),
 	doc("Ensure wait for connections works."),
 	Name = name(),
 	Name = name(),
@@ -621,8 +644,6 @@ ssl_graceful(_) ->
 		[binary, {active, false}, {packet, raw}]),
 		[binary, {active, false}, {packet, raw}]),
 	ok = ssl:send(Socket1, <<"SSL with fresh listener">>),
 	ok = ssl:send(Socket1, <<"SSL with fresh listener">>),
 	{ok, <<"SSL with fresh listener">>} = ssl:recv(Socket1, 23, 1000),
 	{ok, <<"SSL with fresh listener">>} = ssl:recv(Socket1, 23, 1000),
-	%% Make sure transport options cannot be changed on a running listener.
-	{error, running} = ranch:set_transport_options(Name, #{socket_opts => [{port, Port}|Opts]}),
 	%% Suspend listener, make sure established connections keep running.
 	%% Suspend listener, make sure established connections keep running.
 	ok = ranch:suspend_listener(Name),
 	ok = ranch:suspend_listener(Name),
 	suspended = ranch:get_status(Name),
 	suspended = ranch:get_status(Name),
@@ -640,8 +661,6 @@ ssl_graceful(_) ->
 		[binary, {active, false}, {packet, raw}]),
 		[binary, {active, false}, {packet, raw}]),
 	ok = ssl:send(Socket2, <<"SSL with resumed listener">>),
 	ok = ssl:send(Socket2, <<"SSL with resumed listener">>),
 	{ok, <<"SSL with resumed listener">>} = ssl:recv(Socket2, 25, 1000),
 	{ok, <<"SSL with resumed listener">>} = ssl:recv(Socket2, 25, 1000),
-	%% Make sure transport options cannot be changed on resumed listener.
-	{error, running} = ranch:set_transport_options(Name, #{socket_opts => [{port, Port}|Opts]}),
 	ok = ranch:stop_listener(Name),
 	ok = ranch:stop_listener(Name),
 	{error, closed} = ssl:recv(Socket1, 0, 1000),
 	{error, closed} = ssl:recv(Socket1, 0, 1000),
 	{error, closed} = ssl:recv(Socket2, 0, 1000),
 	{error, closed} = ssl:recv(Socket2, 0, 1000),
@@ -860,8 +879,6 @@ tcp_graceful(_) ->
 		[binary, {active, false}, {packet, raw}]),
 		[binary, {active, false}, {packet, raw}]),
 	ok = gen_tcp:send(Socket1, <<"TCP with fresh listener">>),
 	ok = gen_tcp:send(Socket1, <<"TCP with fresh listener">>),
 	{ok, <<"TCP with fresh listener">>} = gen_tcp:recv(Socket1, 23, 1000),
 	{ok, <<"TCP with fresh listener">>} = gen_tcp:recv(Socket1, 23, 1000),
-	%% Make sure transport options cannot be changed on a running listener.
-	{error, running} = ranch:set_transport_options(Name, [{port, Port}]),
 	%% Suspend listener, make sure established connections keep running.
 	%% Suspend listener, make sure established connections keep running.
 	ok = ranch:suspend_listener(Name),
 	ok = ranch:suspend_listener(Name),
 	suspended = ranch:get_status(Name),
 	suspended = ranch:get_status(Name),
@@ -879,8 +896,6 @@ tcp_graceful(_) ->
 		[binary, {active, false}, {packet, raw}]),
 		[binary, {active, false}, {packet, raw}]),
 	ok = gen_tcp:send(Socket2, <<"TCP with resumed listener">>),
 	ok = gen_tcp:send(Socket2, <<"TCP with resumed listener">>),
 	{ok, <<"TCP with resumed listener">>} = gen_tcp:recv(Socket2, 25, 1000),
 	{ok, <<"TCP with resumed listener">>} = gen_tcp:recv(Socket2, 25, 1000),
-	%% Make sure transport options cannot be changed on resumed listener.
-	{error, running} = ranch:set_transport_options(Name, [{port, Port}]),
 	ok = ranch:stop_listener(Name),
 	ok = ranch:stop_listener(Name),
 	{error, closed} = gen_tcp:recv(Socket1, 0, 1000),
 	{error, closed} = gen_tcp:recv(Socket1, 0, 1000),
 	{error, closed} = gen_tcp:recv(Socket2, 0, 1000),
 	{error, closed} = gen_tcp:recv(Socket2, 0, 1000),