Skip to content

Commit d9578b6

Browse files
committed
ssh: tcpip_tunnel_in callback function
allow/deny/log "direct-tcpip" channel open in daemon
1 parent ce5fa40 commit d9578b6

File tree

4 files changed

+74
-5
lines changed

4 files changed

+74
-5
lines changed

lib/ssh/src/ssh.hrl

+3-1
Original file line numberDiff line numberDiff line change
@@ -889,9 +889,11 @@ connection out of a [server](`daemon/2`). Disabled per default.
889889
-doc """
890890
Enables (`true`) or disables (`false`) the possibility to tunnel a TCP/IP
891891
connection in to a [server](`daemon/2`). Disabled per default.
892+
893+
Set `Callback` function to allow/deny/log tunnel connections.
892894
""".
893895
-doc(#{group => <<"Daemon Options">>}).
894-
-type tcpip_tunnel_in_daemon_option() :: {tcpip_tunnel_in, boolean()} .
896+
-type tcpip_tunnel_in_daemon_option() :: {tcpip_tunnel_in, boolean() | Callback::fun((HostName::string(), inet:port_number()) -> boolean() | denied)} .
895897

896898
-doc """
897899
Make the server (daemon) tell the client that the server accepts extension

lib/ssh/src/ssh_connection.erl

+13-3
Original file line numberDiff line numberDiff line change
@@ -946,17 +946,27 @@ handle_msg(#ssh_msg_channel_open{channel_type = "direct-tcpip",
946946
connection_supervisor = ConnectionSup
947947
} = C,
948948
server, _SSH) ->
949+
HostName = binary_to_list(HostToConnect),
950+
Allowed = case ?GET_OPT(tcpip_tunnel_in, Options) of
951+
T when is_boolean(T) -> T;
952+
AllowedFun when is_function(AllowedFun, 2) -> AllowedFun(HostName, PortToConnect)
953+
end,
949954
{ReplyMsg, NextChId} =
950-
case ?GET_OPT(tcpip_tunnel_in, Options) of
951-
%% May add more to the option, like allowed ip/port pairs to connect to
955+
case Allowed of
956+
denied ->
957+
{channel_open_failure_msg(RemoteId,
958+
?SSH_OPEN_ADMINISTRATIVELY_PROHIBITED,
959+
"Not allowed", "en"),
960+
ChId};
961+
952962
false ->
953963
{channel_open_failure_msg(RemoteId,
954964
?SSH_OPEN_CONNECT_FAILED,
955965
"Forwarding disabled", "en"),
956966
ChId};
957967

958968
true ->
959-
case gen_tcp:connect(binary_to_list(HostToConnect), PortToConnect,
969+
case gen_tcp:connect(HostName, PortToConnect,
960970
[{active,false}, binary]) of
961971
{ok,Sock} ->
962972
{ok,Pid} = ssh_connection_sup:start_channel(server, ConnectionSup, self(),

lib/ssh/src/ssh_options.erl

+1-1
Original file line numberDiff line numberDiff line change
@@ -454,7 +454,7 @@ default(server) ->
454454

455455
tcpip_tunnel_in =>
456456
#{default => false,
457-
chk => fun(V) -> erlang:is_boolean(V) end,
457+
chk => fun(V) -> check_function2(V) orelse erlang:is_boolean(V) end,
458458
class => user_option
459459
},
460460

lib/ssh/test/ssh_to_openssh_SUITE.erl

+57
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,8 @@
4545
exec_direct_with_io_in_sshc/1,
4646
exec_with_io_in_sshc/1,
4747
tunnel_in_erlclient_erlserver/1,
48+
tunnel_in_erlclient_erlserver_allowed/1,
49+
tunnel_in_erlclient_erlserver_denied/1,
4850
tunnel_in_erlclient_openssh_server/1,
4951
tunnel_in_non_erlclient_erlserver/1,
5052
tunnel_out_erlclient_erlserver/1,
@@ -74,6 +76,8 @@ all() ->
7476

7577
groups() ->
7678
[{erlang_client, [], [tunnel_in_erlclient_erlserver,
79+
tunnel_in_erlclient_erlserver_allowed,
80+
tunnel_in_erlclient_erlserver_denied,
7781
tunnel_out_erlclient_erlserver,
7882
{group, tunnel_distro_server},
7983
erlang_shell_client_openssh_server,
@@ -414,6 +418,59 @@ tunnel_in_erlclient_erlserver(Config) ->
414418

415419
test_tunneling(ToSock, ListenHost, ListenPort).
416420

421+
%%--------------------------------------------------------------------
422+
tunnel_in_erlclient_erlserver_allowed(Config) ->
423+
SystemDir = proplists:get_value(data_dir, Config),
424+
UserDir = proplists:get_value(priv_dir, Config),
425+
{ToSock, ToHost, ToPort} = tunneling_listner(),
426+
Self = self(),
427+
AllowedFun = fun(HostToConnect, PortToConnect) ->
428+
Self ! {allowed, {HostToConnect, PortToConnect}},
429+
true
430+
end,
431+
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_in, AllowedFun},
432+
{system_dir, SystemDir},
433+
{user_dir, UserDir},
434+
{user_passwords, [{"foo", "bar"}]},
435+
{failfun, fun ssh_test_lib:failfun/2}]),
436+
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
437+
{user_dir, UserDir},
438+
{user,"foo"},{password,"bar"},
439+
{user_interaction, false}]),
440+
441+
ListenHost = inet:ntoa({127,0,0,1}),
442+
{ok,ListenPort} = ssh:tcpip_tunnel_to_server(C, ListenHost,0, ToHost, ToPort, 2000),
443+
test_tunneling(ToSock, ListenHost, ListenPort),
444+
{allowed, {ListenHost, ToPort}} = receive X -> X after 500 -> timeout end,
445+
{allowed, {ListenHost, ToPort}} = receive Y -> Y after 500 -> timeout end.
446+
447+
%%--------------------------------------------------------------------
448+
tunnel_in_erlclient_erlserver_denied(Config) ->
449+
SystemDir = proplists:get_value(data_dir, Config),
450+
UserDir = proplists:get_value(priv_dir, Config),
451+
{ToSock, ToHost, ToPort} = tunneling_listner(),
452+
Self = self(),
453+
DeniedFun = fun(HostToConnect, PortToConnect) ->
454+
Self ! {denied, {HostToConnect, PortToConnect}},
455+
denied
456+
end,
457+
{_Pid, Host, Port} = ssh_test_lib:daemon([{tcpip_tunnel_in, AllowedFun},
458+
{system_dir, SystemDir},
459+
{user_dir, UserDir},
460+
{user_passwords, [{"foo", "bar"}]},
461+
{failfun, fun ssh_test_lib:failfun/2}]),
462+
C = ssh_test_lib:connect(Host, Port, [{silently_accept_hosts, true},
463+
{user_dir, UserDir},
464+
{user,"foo"},{password,"bar"},
465+
{user_interaction, false}]),
466+
467+
ListenHost = inet:ntoa({127,0,0,1}),
468+
{ok,ListenPort} = ssh:tcpip_tunnel_to_server(C, ListenHost,0, ToHost, ToPort, 2000),
469+
{ok, Sock} = gen_tcp:connect(ListenHost, ListenPort, [{active, false}]),
470+
{denied, {ListenHost, ToPort}} = receive Y -> Y after 500 -> timeout end,
471+
{error, timeout} = gen_tcp:accept(ToSock, 2000),
472+
{error, closed} = gen_tcp:recv(Sock, 0, 5000).
473+
417474
%%--------------------------------------------------------------------
418475
tunnel_in_erlclient_openssh_server(_Config) ->
419476
C = ssh_test_lib:connect(?SSH_DEFAULT_PORT, []),

0 commit comments

Comments
 (0)