diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl index ad8b8319852c..736ab045056f 100644 --- a/lib/ssh/src/ssh.hrl +++ b/lib/ssh/src/ssh.hrl @@ -1221,6 +1221,7 @@ Experimental options that should not to be used in products. recv_ext_info, %% Expect ext-info from peer kex_strict_negotiated = false, + ignore_next_kex_message = false, %% RFC 4253 section 7, peer's guess was wrong algorithms, %% #alg{} diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl index 319d9fd71239..d49f8276a3ad 100644 --- a/lib/ssh/src/ssh_fsm_kexinit.erl +++ b/lib/ssh/src/ssh_fsm_kexinit.erl @@ -81,6 +81,27 @@ handle_event(internal, {#ssh_msg_kexinit{}=Kex, Payload}, {kexinit,Role,ReNeg}, {next_state, {key_exchange,Role,ReNeg}, D#data{ssh_params=Ssh}}; %%% ######## {key_exchange, client|server, init|renegotiate} #### +%%%---- RFC 4253 section 7 guess was wrong +handle_event(internal, Msg, {key_exchange,server,_ReNeg}, + D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when + is_record(Msg, ssh_msg_kexdh_init); + is_record(Msg, ssh_msg_kex_dh_gex_request); + is_record(Msg, ssh_msg_kex_dh_gex_request_old); + is_record(Msg, ssh_msg_kex_ecdh_init) -> + DebugMsg = ["server ignored ", element(1, Msg), " message due to wrong guess."], + logger:debug(lists:concat(DebugMsg)), + Ssh = Ssh0#ssh{ignore_next_kex_message = false}, + {keep_state, D#data{ssh_params = Ssh}}; +handle_event(internal, Msg, {key_exchange,client,_ReNeg}, + D = #data{ssh_params = Ssh0 = #ssh{ignore_next_kex_message = true}}) when + is_record(Msg, ssh_msg_kexdh_reply); + is_record(Msg, ssh_msg_kex_dh_gex_group); + is_record(Msg, ssh_msg_kex_dh_gex_reply); + is_record(Msg, ssh_msg_kex_ecdh_reply) -> + DebugMsg = ["client ignored ", element(1, Msg), " message due to wrong guess."], + logger:debug(lists:concat(DebugMsg)), + Ssh = Ssh0#ssh{ignore_next_kex_message = false}, + {keep_state, D#data{ssh_params = Ssh}}; %%%---- diffie-hellman handle_event(internal, #ssh_msg_kexdh_init{} = Msg, {key_exchange,server,ReNeg}, D) -> ok = check_kex_strict(Msg, D), diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl index 4e6578d681c6..765782937158 100644 --- a/lib/ssh/src/ssh_transport.erl +++ b/lib/ssh/src/ssh_transport.erl @@ -397,7 +397,7 @@ new_keys_message(Ssh0) -> {ok, SshPacket, Ssh}. -handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, +handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own, #ssh{role = client} = Ssh, ReNeg) -> try {ok, Algorithms} = @@ -407,8 +407,9 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, Algorithms of Algos -> + IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own), key_exchange_first_msg(Algos#alg.kex, - Ssh#ssh{algorithms = Algos}) + Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong}) catch Class:Reason0 -> Reason = ssh_lib:trim_reason(Reason0), @@ -416,7 +417,7 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg) end; -handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, +handle_kexinit_msg(#ssh_msg_kexinit{first_kex_packet_follows = CounterGuess} = CounterPart, #ssh_msg_kexinit{} = Own, #ssh{role = server} = Ssh, ReNeg) -> try {ok, Algorithms} = @@ -426,7 +427,8 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, Algorithms of Algos -> - {ok, Ssh#ssh{algorithms = Algos}} + IsGuessWrong = is_guess_wrong(CounterGuess, CounterPart, Own), + {ok, Ssh#ssh{algorithms = Algos, ignore_next_kex_message = IsGuessWrong}} catch Class:Reason0 -> Reason = ssh_lib:trim_reason(Reason0), @@ -434,6 +436,35 @@ handle_kexinit_msg(#ssh_msg_kexinit{} = CounterPart, #ssh_msg_kexinit{} = Own, ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, Msg) end. +%% RFC 4253 section 7 check if guess is wrong +is_guess_wrong(false, _, _) -> + false; +is_guess_wrong(true, CounterPart, Own) -> + CounterPreferredKexAlgo = get_preferred_kex_algorithm(CounterPart), + OwnPreferredKexAlgo = get_preferred_kex_algorithm(Own), + CounterPreferredHostKeyAlgo = get_preferred_host_key_algorithm(CounterPart), + OwnPreferredHostKeyAlgo = get_preferred_host_key_algorithm(Own), + + is_different_algorithm(CounterPreferredKexAlgo, OwnPreferredKexAlgo) orelse + is_different_algorithm(CounterPreferredHostKeyAlgo, OwnPreferredHostKeyAlgo). + +is_different_algorithm(none, none) -> + false; +is_different_algorithm(Same, Same) -> + false; +is_different_algorithm(_, _) -> + true. + +get_preferred_kex_algorithm(#ssh_msg_kexinit{kex_algorithms = [Preferred | _]}) -> + Preferred; +get_preferred_kex_algorithm(_) -> + none. + +get_preferred_host_key_algorithm(#ssh_msg_kexinit{server_host_key_algorithms = [Preferred | _]}) -> + Preferred; +get_preferred_host_key_algorithm(_) -> + none. + kexinit_error(Class, Error, Role, Own, CounterPart, Ssh) -> {Fmt,Args} = case {Class,Error} of @@ -2211,7 +2242,11 @@ parallell_gen_key(Ssh = #ssh{keyex_key = {x, {G, P}}, generate_key(ecdh, Args) -> crypto:generate_key(ecdh, Args); generate_key(dh, [P,G,Sz2]) -> - {Public,Private} = crypto:generate_key(dh, [P, G, max(Sz2,?MIN_DH_KEY_SIZE)] ), + BitSize = fun(N) -> bit_size(binary:encode_unsigned(N)) end, + {Public,Private} = + crypto:generate_key(dh, + [P, G, max(min(BitSize(P)-1, Sz2), + ?MIN_DH_KEY_SIZE)]), {crypto:bytes_to_integer(Public), crypto:bytes_to_integer(Private)}. diff --git a/lib/ssh/test/ssh_compat_SUITE.erl b/lib/ssh/test/ssh_compat_SUITE.erl index e81f4ec40aac..b00cd57c5808 100644 --- a/lib/ssh/test/ssh_compat_SUITE.erl +++ b/lib/ssh/test/ssh_compat_SUITE.erl @@ -54,17 +54,19 @@ -define(USER,"sshtester"). -define(PASSWD, "foobar"). -define(BAD_PASSWD, "NOT-"?PASSWD). --define(DOCKER_PFX, "ssh_compat_suite-ssh"). +-define(DOCKER_PFX, "ssh_compat_suite_img-ssh"). +-define(VERSIONS_FILE, "versions.txt"). +-define(DEFAULT_TIMETRAP, {minutes, 2}). +-define(IMAGE_BUILD_TIMETRAP, {minutes, 10}). %%-------------------------------------------------------------------- %% Common Test interface functions ----------------------------------- %%-------------------------------------------------------------------- suite() -> - [{timetrap,{seconds,90}}]. + [{timetrap, ?DEFAULT_TIMETRAP}]. all() -> -%% [check_docker_present] ++ [{group,G} || G <- ssh_image_versions()]. groups() -> @@ -78,21 +80,19 @@ groups() -> [{G, [], [{group,otp_client}, {group,otp_server}]} || G <- ssh_image_versions()] ]. - ssh_image_versions() -> - try - %% Find all useful containers in such a way that undefined command, too low - %% privileges, no containers and containers found give meaningful result: - L0 = ["REPOSITORY"++_|_] = string:tokens(os:cmd("docker images"), "\r\n"), - [["REPOSITORY","TAG"|_]|L1] = [string:tokens(E, " ") || E<-L0], - [list_to_atom(V) || [?DOCKER_PFX,V|_] <- L1] - of - Vs -> - lists:sort(Vs) - catch - error:{badmatch,_} -> - [] - end. + Path = filename:join([code:lib_dir(ssh), "test", "ssh_compat_SUITE_data", ?VERSIONS_FILE]), + {ok, Content} = file:read_file(Path), + Vs = string:lexemes(Content, "\n"), + ListVs = lists:filtermap(fun(Line) -> + case {string:is_empty(Line), string:prefix(Line, "#")} of + {false, nomatch} -> + {true, binary_to_atom(Line)}; + _ -> + false + end + end, Vs), + lists:sort(ListVs). %%-------------------------------------------------------------------- init_per_suite(Config) -> @@ -123,71 +123,75 @@ init_per_group(otp_server, Config) -> SSHver = proplists:get_value(ssh_version, Config, ""), {skip,"No "++SSHver++ " client found in docker"}; _ -> - Config + [{role, server} | Config] end; init_per_group(otp_client, Config) -> - Config; + [{role, client} | Config]; init_per_group(G, Config0) -> case lists:member(G, ssh_image_versions()) of - true -> + true -> %% This group is for one of the images - Vssh = atom_to_list(G), - Cmnt = io_lib:format("+++ ~s +++",[Vssh]), - ct:comment("~s",[Cmnt]), - try start_docker(G) of - {ok,ID} -> - ct:log("==> ~p started",[G]), - %% Find the algorithms that both client and server supports: - {IP,Port} = ip_port([{id,ID}]), - ct:log("Try contact ~p:~p",[IP,Port]), - Config1 = [{id,ID}, - {ssh_version,Vssh} - | Config0], - try common_algs(Config1, IP, Port) of - {ok, ServerHello, RemoteServerCommon, ClientHello, RemoteClientCommon} -> - case chk_hellos([ServerHello,ClientHello], Cmnt) of - Cmnt -> - ok; - NewCmnt -> - ct:comment("~s",[NewCmnt]) - end, - AuthMethods = - %% This should be obtained by querying the peer, but that - %% is a bit hard. It is possible with ssh_protocol_SUITE - %% techniques, but it can wait. - case Vssh of - "dropbear" ++ _ -> - [password, publickey]; - _ -> - [password, 'keyboard-interactive', publickey] - end, - [{common_remote_server_algs,RemoteServerCommon}, - {common_remote_client_algs,RemoteClientCommon}, - {common_authmethods,AuthMethods} - |Config1]; - Other -> - ct:log("Error in init_per_group: ~p",[Other]), - stop_docker(ID), - {fail, "Can't contact docker sshd"} + case build_image(Config0, G) of + ok -> + Vssh = atom_to_list(G), + Cmnt = io_lib:format("+++ ~s +++",[Vssh]), + ct:comment("~s",[Cmnt]), + try start_docker(G) of + {ok,ID} -> + ct:log("==> ~p started",[G]), + %% Find the algorithms that both client and server supports: + {IP,Port} = ip_port([{id,ID}]), + ct:log("Try contact ~p:~p",[IP,Port]), + Config1 = [{id,ID}, + {ssh_version,Vssh} + | Config0], + try common_algs(Config1, IP, Port) of + {ok, ServerHello, RemoteServerCommon, ClientHello, RemoteClientCommon} -> + case chk_hellos([ServerHello,ClientHello], Cmnt) of + Cmnt -> + ok; + NewCmnt -> + ct:comment("~s",[NewCmnt]) + end, + AuthMethods = + %% This should be obtained by querying the peer, but that + %% is a bit hard. It is possible with ssh_protocol_SUITE + %% techniques, but it can wait. + case Vssh of + "dropbear" ++ _ -> + [password, publickey]; + _ -> + [password, 'keyboard-interactive', publickey] + end, + [{common_remote_server_algs,RemoteServerCommon}, + {common_remote_client_algs,RemoteClientCommon}, + {common_authmethods,AuthMethods} + |Config1]; + Other -> + ct:log("Error in init_per_group: ~p",[Other]), + stop_docker(ID), + {fail, "Can't contact docker sshd"} + catch + Class:Exc:ST -> + ct:log("common_algs: ~p:~p~n~p",[Class,Exc,ST]), + stop_docker(ID), + {fail, "Failed during setup"} + end catch - Class:Exc:ST -> - ct:log("common_algs: ~p:~p~n~p",[Class,Exc,ST]), - stop_docker(ID), - {fail, "Failed during setup"} - end - catch - cant_start_docker -> - {skip, "Can't start docker"}; + cant_start_docker -> + {skip, "Can't start docker"}; - C:E:ST -> - ct:log("No ~p~n~p:~p~n~p",[G,C,E,ST]), - {skip, "Can't start docker"} + C:E:ST -> + ct:log("No ~p~n~p:~p~n~p",[G,C,E,ST]), + {skip, "Can't start docker"} + end; + Other -> + Other end; - - false -> - Config0 + false -> + Config0 end. end_per_group(G, Config) -> @@ -198,16 +202,14 @@ end_per_group(G, Config) -> ok end. - -init_per_testcase(TC, Config) when TC==login_otp_is_client ; - TC==all_algorithms_sftp_exec_reneg_otp_is_client -> - case proplists:get_value(ssh_version, Config) of - "openssh4.4p1-openssl0.9.8c" -> {skip, "Not tested"}; - "openssh4.5p1-openssl0.9.8m" -> {skip, "Not tested"}; - "openssh5.0p1-openssl0.9.8za" -> {skip, "Not tested"}; - "openssh6.2p2-openssl0.9.8c" -> {skip, "Not tested"}; - "openssh6.3p1-openssl0.9.8zh" -> {skip, "Not tested"}; - "openssh6.6p1-openssl1.0.2n" -> {skip, "Not tested"}; +init_per_testcase(all_algorithms_sftp_exec_reneg_otp_is_client, Config) -> + case get_list_version(proplists:get_value(ssh_version, Config)) of + ["openssh", "6.2p2", "openssl", "0.9.8c", "16.04"] -> + {skip, "Openssh 6.x disabled diffie-hellman-group1-sha1 but 6.2p2 still advertises it."}; + ["openssh", "6.3p1", "openssl", "0.9.8zh", "16.04"] -> + {skip, "Openssh 6.x disabled diffie-hellman-group1-sha1 but 6.3p1 still advertises it."}; + ["dropbear", "2025.88", "22.04"] -> + {skip, "Fails with error \"No common compress algorithm\""}; _ -> Config end; @@ -521,7 +523,7 @@ exec_from_docker(C, DestIP, DestPort, Command, Expects, ExtraSshArg, Config) whe ["sshpass -p ",?PASSWD," " | case proplists:get_value(ssh_version,Config) of "dropbear" ++ _ -> - ["dbclient -y -y -p ",DestPort," ",ExtraSshArg," ",iptoa(DestIP)," "]; + ["/buildroot/ssh/bin/dbclient -y -y -p ",DestPort," ",ExtraSshArg," ",iptoa(DestIP)," "]; _ -> %% OpenSSH or compatible ["/buildroot/ssh/bin/ssh -o 'CheckHostIP=no' -o 'StrictHostKeyChecking=no' ", @@ -641,11 +643,11 @@ setup_local_hostdirs(KeyAlgs, HostDir, Config) -> setup_local_hostdir(KeyAlg, Config) -> setup_local_hostdir(KeyAlg, new_dir(Config), Config). setup_local_hostdir(KeyAlg, HostDir, Config) -> - {ok, {Priv,Publ}} = host_priv_pub_keys(Config, KeyAlg), + {ok, {Pub, PrivOpenSsh, _Priv}} = host_priv_pub_keys(Config, KeyAlg), %% Local private and public key DstFile = filename:join(HostDir, dst_filename(host,KeyAlg)), - ok = file:write_file(DstFile, Priv), - ok = file:write_file(DstFile++".pub", Publ), + ok = file:write_file(DstFile, PrivOpenSsh), + ok = file:write_file(DstFile++".pub", Pub), HostDir. @@ -654,11 +656,11 @@ setup_remote_auth_keys_and_local_priv(KeyAlg, Config) -> setup_remote_auth_keys_and_local_priv(KeyAlg, IP, Port, new_dir(Config), Config). setup_remote_auth_keys_and_local_priv(KeyAlg, IP, Port, UserDir, Config) -> - {ok, {Priv,Publ}} = user_priv_pub_keys(Config, KeyAlg), + {ok, {Pub, PrivOpenSsh, _Priv}} = user_priv_pub_keys(Config, KeyAlg), %% Local private and public keys DstFile = filename:join(UserDir, dst_filename(user,KeyAlg)), - ok = file:write_file(DstFile, Priv), - ok = file:write_file(DstFile++".pub", Publ), + ok = file:write_file(DstFile, PrivOpenSsh), + ok = file:write_file(DstFile++".pub", Pub), %% Remote auth_methods with public key {ok,Ch,Cc} = ssh_sftp:start_channel(IP, Port, [{user, ?USER }, {password, ?PASSWD }, @@ -669,7 +671,7 @@ setup_remote_auth_keys_and_local_priv(KeyAlg, IP, Port, UserDir, Config) -> {user_interaction,false} ]), _ = ssh_sftp:make_dir(Ch, ".ssh"), - ok = ssh_sftp:write_file(Ch, ".ssh/authorized_keys", Publ), + ok = ssh_sftp:write_file(Ch, ".ssh/authorized_keys", Pub), ok = ssh_sftp:write_file_info(Ch, ".ssh/authorized_keys", #file_info{mode=8#700}), ok = ssh_sftp:write_file_info(Ch, ".ssh", #file_info{mode=8#700}), ok = ssh_sftp:stop_channel(Ch), @@ -682,10 +684,10 @@ setup_remote_priv_and_local_auth_keys(KeyAlg, Config) -> setup_remote_priv_and_local_auth_keys(KeyAlg, IP, Port, new_dir(Config), Config). setup_remote_priv_and_local_auth_keys(KeyAlg, IP, Port, UserDir, Config) -> - {ok, {Priv,Publ}} = user_priv_pub_keys(Config, KeyAlg), + {ok, {Pub, PrivOpenSsh, Priv}} = user_priv_pub_keys(Config, KeyAlg), %% Local auth_methods with public key AuthKeyFile = filename:join(UserDir, "authorized_keys"), - ok = file:write_file(AuthKeyFile, Publ), + ok = file:write_file(AuthKeyFile, Pub), %% Remote private and public key {ok,Ch,Cc} = ssh_sftp:start_channel(IP, Port, [{user, ?USER }, {password, ?PASSWD }, @@ -696,11 +698,19 @@ setup_remote_priv_and_local_auth_keys(KeyAlg, IP, Port, UserDir, Config) -> ]), rm_id_in_remote_dir(Ch, ".ssh"), _ = ssh_sftp:make_dir(Ch, ".ssh"), - DstFile = filename:join(".ssh", dst_filename(user,KeyAlg)), - ok = ssh_sftp:write_file(Ch, DstFile, Priv), + DstFile = filename:join(".ssh", dst_filename(user, KeyAlg)), + ok = ssh_sftp:write_file(Ch, DstFile, PrivOpenSsh), ok = ssh_sftp:write_file_info(Ch, DstFile, #file_info{mode=8#700}), - ok = ssh_sftp:write_file(Ch, DstFile++".pub", Publ), + ok = ssh_sftp:write_file(Ch, DstFile++".pub", Pub), ok = ssh_sftp:write_file_info(Ch, ".ssh", #file_info{mode=8#700}), + case proplists:get_value(ssh_version, Config) of + "dropbear" ++ _ -> + DropbearDstFile = filename:join(".ssh", "id_dropbear"), + ok = ssh_sftp:write_file(Ch, DropbearDstFile, Priv), + ok = ssh_sftp:write_file_info(Ch, DropbearDstFile, #file_info{mode=8#700}); + _ -> + ok + end, ok = ssh_sftp:stop_channel(Ch), ok = ssh:close(Cc), UserDir. @@ -722,9 +732,29 @@ host_priv_pub_keys(Config, KeyAlg) -> priv_pub_keys("host_keys", host, Config, priv_pub_keys(KeySubDir, Type, Config, KeyAlg) -> KeyDir = filename:join(proplists:get_value(data_dir,Config), KeySubDir), - {ok,Priv} = file:read_file(filename:join(KeyDir,src_filename(Type,KeyAlg))), - {ok,Publ} = file:read_file(filename:join(KeyDir,src_filename(Type,KeyAlg)++".pub")), - {ok, {Priv,Publ}}. + SshVersion = proplists:get_value(ssh_version, Config), + case {Type, SshVersion} of + {user, "dropbear" ++ _} -> + {ok, Pub} = file:read_file(filename:join([KeyDir, "dropbear", src_filename(Type, KeyAlg) ++ ".pub"])), + {ok, PrivOpenSsh} = file:read_file(filename:join([KeyDir, "dropbear", src_filename(Type, KeyAlg) ++ "_openssh"])), + {ok, Priv} = file:read_file(filename:join([KeyDir, "dropbear", src_filename(Type, KeyAlg)])), + {ok, {remove_comment(Pub), remove_comment(PrivOpenSsh), remove_comment(Priv)}}; + {user, "openssh" ++ _} -> + {ok, Pub} = file:read_file(filename:join([KeyDir, "openssh", src_filename(Type, KeyAlg) ++ ".pub"])), + {ok, Priv} = file:read_file(filename:join([KeyDir, "openssh", src_filename(Type, KeyAlg)])), + PrivNoComment = remove_comment(Priv), + {ok, {remove_comment(Pub), PrivNoComment, PrivNoComment}}; + _ -> + {ok, Pub} = file:read_file(filename:join([KeyDir, src_filename(Type, KeyAlg) ++ ".pub"])), + {ok, Priv} = file:read_file(filename:join([KeyDir, src_filename(Type, KeyAlg)])), + PrivNoComment = remove_comment(Priv), + {ok, {remove_comment(Pub), PrivNoComment, PrivNoComment}} + end. + +remove_comment(Bin) -> + Lines = string:split(Bin, "\n", all), + FilteredLines = [L || L <- Lines, string:prefix(L, "#") == nomatch], + lists:join("\n", FilteredLines). %%%---------------- The default filenames @@ -804,9 +834,9 @@ format_result_table_use_all_algos(FunctionName, Config, CommonAlgs, Failed) -> %% Docker handling: start_docker/1 and stop_docker/1 %% start_docker(Ver) -> - Cmnd = lists:concat(["docker run -itd --rm -p 1234 ",?DOCKER_PFX,":",Ver]), - Id0 = os:cmd(Cmnd), - ct:log("Ver = ~p, Cmnd ~p~n-> ~p",[Ver,Cmnd,Id0]), + Cmd = lists:concat(["docker run -itd --rm -p 1234 ",?DOCKER_PFX,":",get_docker_version(Ver)]), + Id0 = os:cmd(Cmd), + ct:log("Ver = ~p, Cmd ~p~n-> ~p",[Ver,Cmd,Id0]), case is_docker_sha(Id0) of true -> Id = hd(string:tokens(Id0, "\n")), @@ -819,8 +849,8 @@ start_docker(Ver) -> stop_docker({_Ver,_,Id}) -> - Cmnd = lists:concat(["docker kill ",Id]), - os:cmd(Cmnd). + Cmd = lists:concat(["docker kill ",Id]), + os:cmd(Cmd). is_docker_sha(L) -> lists:all(fun(C) when $a =< C,C =< $z -> true; @@ -838,10 +868,10 @@ ip_port(Config) -> {IP,Port}. ip(Id) -> - Cmnd = lists:concat(["docker inspect --format='{{range .NetworkSettings.Networks}}{{.IPAddress}}{{end}}' ", + Cmd = lists:concat(["docker inspect --format='{{range .NetworkSettings.Networks}}{{.IPAddress}}{{end}}' ", Id]), - IPstr0 = os:cmd(Cmnd), - ct:log("Cmnd ~p~n-> ~p",[Cmnd,IPstr0]), + IPstr0 = os:cmd(Cmd), + ct:log("Cmd ~p~n-> ~p",[Cmd,IPstr0]), IPstr = hd(string:tokens(IPstr0, "\n")), {ok,IP} = inet:parse_address(IPstr), IP. @@ -850,13 +880,31 @@ ip(Id) -> %% %% Normalize the host returned from ssh_test_lib +iptoa({0,0,0,0,0,0,0,0}) -> inet_parse:ntoa(host_ip()); iptoa({0,0,0,0}) -> inet_parse:ntoa(host_ip()); iptoa(IP) -> inet_parse:ntoa(IP). host_ip() -> - {ok,Name} = inet:gethostname(), - {ok,IP} = inet:ip(Name), - IP. + DockerAddr = get_docker_if_address(inet:getifaddrs()), + case inet:is_ip_address(DockerAddr) of + true -> + DockerAddr; + false -> + {ok, Name} = inet:gethostname(), + {ok, IP} = inet:ip(Name), + IP + end. + +get_docker_if_address({ok, Addrs}) -> + Fun = fun({Name, _}) -> string:prefix(Name, "docker") /= nomatch end, + get_docker_if_address_from_opts(lists:search(Fun, Addrs)); +get_docker_if_address(Other) -> + Other. + +get_docker_if_address_from_opts({value, {_Name, Opts}}) -> + proplists:get_value(addr, Opts); +get_docker_if_address_from_opts(Other) -> + Other. %%-------------------------------------------------------------------- %% @@ -1105,7 +1153,7 @@ receive_kexinit(_S, <>) -> ct:log("Has all ~p packet bytes",[PacketLen]), PayloadLen = PacketLen - PaddingLen - 1, - <> = PayloadAndPadding, + Payload = binary:part(PayloadAndPadding, 0, PayloadLen), ssh_message:decode(Payload); receive_kexinit(S, Ack) -> @@ -1222,8 +1270,14 @@ call_sftp_in_docker(Config, ServerIP, ServerPort, Cmnds, UserDir, Ref) -> {user_interaction,false} ]), - %% Make commands for "expect" in the docker: - PreExpectCmnds = ["spawn /buildroot/ssh/bin/sftp -oPort="++integer_to_list(ServerPort)++ + SftpPath = case proplists:get_value(ssh_version, Config) of + "dropbear" ++ _ -> + "/usr/bin/sftp"; + "openssh" ++ _ -> + "/buildroot/ssh/bin/sftp" + end, + + PreExpectCmnds = ["spawn "++SftpPath++" -oPort="++integer_to_list(ServerPort)++ " -oCheckHostIP=no -oStrictHostKeyChecking=no " ++ iptoa(ServerIP)++"\n" ], @@ -1491,10 +1545,10 @@ renegotiate_test(Kex1, ConnectionRef) -> end. %%%---------------------------------------------------------------- -%% ImageVersions = ['dropbearv2016.72', -%% 'openssh4.4p1-openssl0.9.8c', +%% ImageVersions = ['dropbear v2016.72 22.04', +%% 'openssh 4.4p1 openssl 0.9.8c 16.04', %% ... -%% 'openssh8.8p1-openssl1.1.1l'] +%% 'openssh 8.8p1 openssl 1.1.1l 22.04'] log_image_versions(ImageVersions, Config) -> case true == (catch @@ -1525,14 +1579,59 @@ fix_entry(HostPfx) -> end. fix_version(E) -> - case string:tokens(atom_to_list(E), "-") of - ["openssh"++Vs, "openssl"++Vc ] -> lists:concat(["OpenSSH_",Vs," OpenSSL ",Vc]); - ["openssh"++Vs, "libressl"++Vc] -> lists:concat(["OpenSSH_",Vs," LibreSSL ",Vc]); - _ -> atom_to_list(E) + case get_list_version(E) of + ["openssh", Vs, "openssl", Vc, BaseVer] -> lists:concat(["OpenSSH_", Vs," OpenSSL ", Vc, " ", BaseVer]); + ["openssh", Vs, "libressl", Vc, BaseVer] -> lists:concat(["OpenSSH_", Vs," LibreSSL ", Vc, " ", BaseVer]); + ["dropbear", Vs, BaseVer] -> lists:concat(["Dropbear ", Vs, " ", BaseVer]) end. +get_list_version(Line) when is_atom(Line) -> + get_list_version(atom_to_list(Line)); +get_list_version(Line) -> + Split = string:split(Line, " ", all), + lists:filter(fun(Word) -> Word /= "" end, Split). + hostname() -> case inet:gethostname() of {ok,Name} -> string:to_lower(Name); _ -> "undefined" end. + +image_exists(Ver) -> + Cmd = lists:concat(["docker images -q ", ?DOCKER_PFX, ":", Ver, " 2>/dev/null"]), + os:cmd(Cmd) /= "". + +build_image(Config, Ver) -> + DockerVer = get_docker_version(Ver), + case image_exists(DockerVer) of + true -> + ct:log("Image ~p is already built.~n", [Ver]), + ok; + false -> + ct:timetrap(?IMAGE_BUILD_TIMETRAP), + try + DataDir = proplists:get_value(data_dir, Config), + BuildAll = filename:join([DataDir, "build_scripts", "create_all"]), + Cmd = lists:concat([BuildAll, " build_one ", Ver]), + ct:pal("Building ~p...~n", [Ver]), + ct:log("Cmd: ~p~n", [Cmd]), + os:cmd(Cmd, #{exception_on_failure => true}), + ct:pal("Built ~p.~n", [Ver]), + ok + catch + error : {command_failed, Reason, ExitCode} : _ST -> + ct:log("Cannot build image, exit code: ~p, output:~n~ts~n", [ExitCode, Reason]), + {skip, io_lib:format("Cannot build image, exit code: ~p", [ExitCode])} + after + ct:timetrap(?DEFAULT_TIMETRAP) + end + end. + +get_docker_version(Line) -> + case get_list_version(Line) of + ["openssh", SshVer, SslType, SslVer, BaseVer] -> + lists:concat(["openssh", SshVer, "-", SslType, SslVer, "-", BaseVer]); + ["dropbear", SshVer, BaseVer] -> + lists:concat(["dropbear", SshVer, "-", BaseVer]) + end. + diff --git a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/create-base-image b/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/create-base-image index 44df8fe54567..747e7c6c63af 100755 --- a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/create-base-image +++ b/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/create-base-image @@ -1,4 +1,4 @@ -#!/bin/sh +#!/bin/bash # %CopyrightBegin% # # SPDX-License-Identifier: Apache-2.0 @@ -17,6 +17,8 @@ # limitations under the License. # # %CopyrightEnd% +# +# ./create-base-image UBUNTU_VER=${1:-16.04} @@ -24,22 +26,23 @@ USER=sshtester PWD=foobar docker build \ - -t ssh_compat_suite-ubuntu \ + -t ssh_compat_suite_img-ubuntu:$UBUNTU_VER \ --build-arg https_proxy=$HTTPS_PROXY \ --build-arg http_proxy=$HTTP_PROXY \ - < /dev/null) == "" ]] ; then + echo "Building $BASE_IMG..." + if ! ./create-base-image $BASE_VER; then + echo "Create base failed." >&2 + exit 1 + fi +fi + +# This way of fetching the tar-file separate from the docker commands makes +# http-proxy handling way easier. The wget command handles the $https_proxy +# variable while the docker command must have /etc/docker/something changed +# and the docker server restarted. That is not possible without root access. + +# Make a Dockerfile. This method simplifies env variable handling considerably: +cat - > TempDockerFile < TempDockerFile < TempDockerFile < TempDockerFile < TempDockerFile <> /buildroot/ssh/etc/sshd_config @@ -74,26 +84,28 @@ cat - > TempDockerFile < /dev/null) == "" ]] ; then + echo "Building $BASE_IMG..." + if ! ./create-base-image $BASE_VER; then + echo "Create base failed." >&2 + exit 1 + fi +fi + +case $FAM$VER in openssl0.9.8[a-l]) CONFIG_FLAGS=no-asm - ;; + ;; *) - CONFIG_FLAGS= - ;; + CONFIG_FLAGS= + ;; esac - # This way of fetching the tar-file separate from the docker commands makes # http-proxy handling way easier. The wget command handles the $https_proxy # variable while the docker command must have /etc/docker/something changed @@ -62,7 +83,8 @@ esac # Make a Dockerfile. This method simplifies env variable handling considerably: cat - > TempDockerFile < /dev/null && pwd ) WHAT_TO_DO=$1 @@ -58,58 +26,88 @@ function create_one_image () { SSH_FAM=$1 SSH_VER=$2 - SSL_FAM=$3 - SSL_VER=$4 - [ "x$SKIP_CREATE_BASE" == "xtrue" ] || ./create-base-image || (echo "Create base failed." >&2; exit 1) - ./create-ssl-image $SSL_FAM $SSL_VER \ - || (echo "Create $SSL_FAM $SSL_VER failed." >&2; exit 2) + pushd ${SCRIPT_DIR} - ./create-ssh-image $SSH_FAM $SSH_VER $SSL_FAM $SSL_VER \ - || (echo "Create $SSH_FAM $SSH_VER on $SSL_FAM $SSL_VER failed." >&2; exit 3) + case $SSH_FAM in + openssh) + SSL_FAM=$3 + SSL_VER=$4 + BASE_VER=$5 + if ./create-ssl-image $SSL_FAM $SSL_VER $BASE_VER; then + if ./create-ssh-image $SSH_FAM $SSH_VER $SSL_FAM $SSL_VER $BASE_VER; then + popd + else + echo "Create $SSH_FAM $SSH_VER on $SSL_FAM $SSL_VER failed." >&2 + popd + exit 3 + fi + else + echo "Create $SSL_FAM $SSL_VER failed." >&2 + popd + exit 2 + fi + ;; + dropbear) + BASE_VER=$3 + if ! ./create-dropbear-image $SSH_FAM $SSH_VER $BASE_VER; then + echo "Create $SSH_FAM $SSH_VER failed." >&2 + popd + exit 2 + fi + popd + ;; + *) + echo "Unsupported: $1" + popd + exit + esac } case ${WHAT_TO_DO} in list) - ;; + ;; listatoms) - PRE="[" - POST="]" - C=\' - COMMA=, - ;; + PRE="[" + POST="]" + C=\' + COMMA=, + ;; build_one) - if [ $# != 5 ] - then - echo "$0 build_one openssh SSH_ver openssl SSL_ver " && exit - else - create_one_image $2 $3 $4 $5 - exit - fi - ;; + if [[ $# == 6 ]]; then + create_one_image $2 $3 $4 $5 $6 + exit + elif [[ $# == 4 ]]; then + create_one_image $2 $3 $4 + exit + else + echo "$0 build_one openssh SSH_ver openssl SSL_ver BASE_ver | build_one dropbear SSH_ver BASE_ver" + exit + fi + ;; build_all) - ;; + ;; *) - echo "$0 [-b] list | listatoms | build_one openssh SSH_ver openssl SSL_ver | build_all" && exit - ;; + echo "$0 list | listatoms | build_one openssh SSH_ver openssl SSL_ver BASE_ver | build_one dropbear SSH_ver BASE_ver | build_all" + exit + ;; esac - -echo -n $PRE -i=0 -while [ "x${SSH_SSL_VERSIONS[i]}" != "x" ] -do - case ${WHAT_TO_DO} in - list*) - [ $i -eq 0 ] || echo $COMMA - echo -n $C${SSH_SSL_VERSIONS[$i]}${SSH_SSL_VERSIONS[$(( $i + 1 ))]}-${SSH_SSL_VERSIONS[$(( $i + 2 ))]}${SSH_SSL_VERSIONS[$(( $i + 3 ))]}$C - ;; - build_all) - create_one_image ${SSH_SSL_VERSIONS[$i]} ${SSH_SSL_VERSIONS[$(( $i + 1 ))]} ${SSH_SSL_VERSIONS[$(( $i + 2 ))]} ${SSH_SSL_VERSIONS[$(( $i + 3 ))]} - ;; - esac - i=$(( $i + 4 )) -done +echo -n $PRE +FIRST=true +while read LINE; do + [[ "$LINE" == \#* || "$LINE" == "" ]] && continue + case ${WHAT_TO_DO} in + list*) + $FIRST || echo $COMMA + echo -n $C$LINE$C + FIRST=false + ;; + build_all) + create_one_image $LINE + ;; + esac +done < ${SCRIPT_DIR}/../versions.txt echo $POST diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa new file mode 100644 index 000000000000..0aa3560c9f0a Binary files /dev/null and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa.pub new file mode 100644 index 000000000000..a9d381559fcb --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ssh-dss AAAAB3NzaC1kc3MAAACBAIUWLe9m8Fi7DvhEt/1IpOnZbuf1ccqR1KciYr0HrnAIXiS9G+qiFqUR6/iTDQBdJAmrhRb1BTHb3W3h/Ct31Mt0nrm0kPhrGNM7OWs8RXiND4GQfy8UFwB4tv0oGds7b8bScwL+TV/50eAd5xi02WT2bwQ1NsJlb/hsbqzZnXlNAAAAFQD4JVVdR7I/b4q/emFxNP0l2nK/NwAAAIBy88SQuVqCeC/3Ir/P0Od54Jskq5LHwq1DezhwsyDUOp8yGpCQuRtXRCE1GlIkVB2vegvkX28LbGQyxfk6Gwmgx0ixjinKwezE+592biFyl45I46FJWgKnSIMYV3mW9OFRqsAXIWAR+GL0VAD7ky1XNzJ1QXTuSNsnKFr6pl1c6AAAAIADD3kRzsKRJ10ZRfR2Nkw6mvyBU2Ld65ml4/5TgCX7qSqcQY9RwOPbAcpd+fOLUmVGh71v6OvzE3xLjBI3S66/h0zUFG37d9oqhNnUIxAaXgnPhQtuBlNbTD28Wo64PFTTRFyA/rrEonvpGimUHvdxxWYf5GoagRr2ya7j6wirNQ== sshtester@host \ No newline at end of file diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa_openssh b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa_openssh new file mode 100644 index 000000000000..b7b66a6c2064 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_dsa_openssh @@ -0,0 +1,30 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +-----BEGIN DSA PRIVATE KEY----- +MIIBuwIBAAKBgQCFFi3vZvBYuw74RLf9SKTp2W7n9XHKkdSnImK9B65wCF4kvRvq +ohalEev4kw0AXSQJq4UW9QUx291t4fwrd9TLdJ65tJD4axjTOzlrPEV4jQ+BkH8v +FBcAeLb9KBnbO2/G0nMC/k1f+dHgHecYtNlk9m8ENTbCZW/4bG6s2Z15TQIVAPgl +VV1Hsj9vir96YXE0/SXacr83AoGAcvPEkLlagngv9yK/z9DneeCbJKuSx8KtQ3s4 +cLMg1DqfMhqQkLkbV0QhNRpSJFQdr3oL5F9vC2xkMsX5OhsJoMdIsY4pysHsxPuf +dm4hcpeOSOOhSVoCp0iDGFd5lvThUarAFyFgEfhi9FQA+5MtVzcydUF07kjbJyha ++qZdXOgCgYADD3kRzsKRJ10ZRfR2Nkw6mvyBU2Ld65ml4/5TgCX7qSqcQY9RwOPb +Acpd+fOLUmVGh71v6OvzE3xLjBI3S66/h0zUFG37d9oqhNnUIxAaXgnPhQtuBlNb +TD28Wo64PFTTRFyA/rrEonvpGimUHvdxxWYf5GoagRr2ya7j6wirNQIVAKzhYvit +UQ4TvEkaNQ5daZh1p/Tw +-----END DSA PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/DF b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256 similarity index 81% rename from lib/ssh/test/ssh_compat_SUITE_data/build_scripts/DF rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256 index 8d6b1d3bd5af..ed5c04f91e8d 100644 Binary files a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/DF and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256 differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256.pub new file mode 100644 index 000000000000..758bc31004d4 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ecdsa-sha2-nistp256 AAAAE2VjZHNhLXNoYTItbmlzdHAyNTYAAAAIbmlzdHAyNTYAAABBBOtgW7lBNdJvxQC02AxWMOfU7ilHjIkuQF29ZOhoLPwXfKce1cLh9qFDJ3N+ZpU86qj5MnVXEkMkJa2jlT02ICA= sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/MOVE.howto b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256_openssh similarity index 56% rename from lib/ssh/test/ssh_compat_SUITE_data/build_scripts/MOVE.howto rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256_openssh index 5224248dd9cf..dd6d6b4ca8fd 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/build_scripts/MOVE.howto +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa256_openssh @@ -16,27 +16,12 @@ # limitations under the License. # # %CopyrightEnd% - -To move an image, do: - -On src machine: - -$ docker run -itd --rm -p 1234 REPOSITORY:TAG -$ docker export XYZ -o FIL -$ scp FIL hans@laura.otp.ericsson.se:/ldisk/hans/docker -$ docker kill THE_DOCKER_REF - -On dst machine: - -hans$ chmod a+r FIL -$ docker import FIL ssh_compat:bld -$ docker build -t REPOSITORY:TAG -f DF . -$ docker rmi ssh_compat:bld - -(DF contains: -FROM ssh_compat:bld - -# Start the daemon, but keep it in foreground to avoid killing the container -CMD /buildroot/ssh/sbin/sshd -D -p 1234 - -) +-----BEGIN OPENSSH PRIVATE KEY----- +b3BlbnNzaC1rZXktdjEAAAAABG5vbmUAAAAEbm9uZQAAAAAAAAABAAAAaAAAABNl +Y2RzYS1zaGEyLW5pc3RwMjU2AAAACG5pc3RwMjU2AAAAQQTrYFu5QTXSb8UAtNgM +VjDn1O4pR4yJLkBdvWToaCz8F3ynHtXC4fahQydzfmaVPOqo+TJ1VxJDJCWto5U9 +NiAgAAAAoAAAAAAAAAAAAAAAE2VjZHNhLXNoYTItbmlzdHAyNTYAAAAIbmlzdHAy +NTYAAABBBOtgW7lBNdJvxQC02AxWMOfU7ilHjIkuQF29ZOhoLPwXfKce1cLh9qFD +J3N+ZpU86qj5MnVXEkMkJa2jlT02ICAAAAAhAMCU65eff8Kn9ItMCdlfrDNmFbvH +0Rybf7wxrYs8S5wyAAAAAAECAwQFBgc= +-----END OPENSSH PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384 new file mode 100644 index 000000000000..8caa10078768 Binary files /dev/null and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384 differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384.pub new file mode 100644 index 000000000000..f8d45b534356 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ecdsa-sha2-nistp384 AAAAE2VjZHNhLXNoYTItbmlzdHAzODQAAAAIbmlzdHAzODQAAABhBEtQ3YstAR5lqtXXcTj+L2mqizQGgymGv2vEGjrZXTan6Dva6DViCDgYjMWFtI2J2JwRqlftRRQw6BNoGTu2iDrw8Oq/CEiPMgQ6hRZQRarPJtkwBGC1fNl5wfKnEgkBVQ== sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384_openssh b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384_openssh new file mode 100644 index 000000000000..075cd076aa9b --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa384_openssh @@ -0,0 +1,29 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +-----BEGIN OPENSSH PRIVATE KEY----- +b3BlbnNzaC1rZXktdjEAAAAABG5vbmUAAAAEbm9uZQAAAAAAAAABAAAAiAAAABNl +Y2RzYS1zaGEyLW5pc3RwMzg0AAAACG5pc3RwMzg0AAAAYQRLUN2LLQEeZarV13E4 +/i9pqos0BoMphr9rxBo62V02p+g72ug1Ygg4GIzFhbSNidicEapX7UUUMOgTaBk7 +tog68PDqvwhIjzIEOoUWUEWqzybZMARgtXzZecHypxIJAVUAAADQAAAAAAAAAAAA +AAATZWNkc2Etc2hhMi1uaXN0cDM4NAAAAAhuaXN0cDM4NAAAAGEES1Ddiy0BHmWq +1ddxOP4vaaqLNAaDKYa/a8QaOtldNqfoO9roNWIIOBiMxYW0jYnYnBGqV+1FFDDo +E2gZO7aIOvDw6r8ISI8yBDqFFlBFqs8m2TAEYLV82XnB8qcSCQFVAAAAMQDeh5Uc +Pcj7XnxEEbHR6IMablYNE+svIUDmVzltLfEu+PKLJTg/frONAJJvZsJ+XwIAAAAA +AQIDBAUGBw== +-----END OPENSSH PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521 similarity index 72% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521 index 83c6cd7c044a..11f85d704fec 100644 Binary files a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521 differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521.pub new file mode 100644 index 000000000000..dcd586632855 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ecdsa-sha2-nistp521 AAAAE2VjZHNhLXNoYTItbmlzdHA1MjEAAAAIbmlzdHA1MjEAAACFBAAXr5jJ8Nuy81qeTFyez3hj3SHBHVEocuhNaIN2cy/QEivggTqNyheWpcp27gDugSlCdo4tFVAe0XonUoru5Fgy2gDivGzGOxdf/Y6KjJvazLSeDSYMbtGwz1gTxy7EgcG7Qi/hE3sG8kZUkrxk234y5RXwZkFIs0iyuvWELHKArJzZGQ== sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521_openssh b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521_openssh new file mode 100644 index 000000000000..0231271979af --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ecdsa521_openssh @@ -0,0 +1,30 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +-----BEGIN OPENSSH PRIVATE KEY----- +b3BlbnNzaC1rZXktdjEAAAAABG5vbmUAAAAEbm9uZQAAAAAAAAABAAAArAAAABNl +Y2RzYS1zaGEyLW5pc3RwNTIxAAAACG5pc3RwNTIxAAAAhQQAF6+YyfDbsvNankxc +ns94Y90hwR1RKHLoTWiDdnMv0BIr4IE6jcoXlqXKdu4A7oEpQnaOLRVQHtF6J1KK +7uRYMtoA4rxsxjsXX/2Oioyb2sy0ng0mDG7RsM9YE8cuxIHBu0Iv4RN7BvJGVJK8 +ZNt+MuUV8GZBSLNIsrr1hCxygKyc2RkAAAEAAAAAAAAAAAAAAAATZWNkc2Etc2hh +Mi1uaXN0cDUyMQAAAAhuaXN0cDUyMQAAAIUEABevmMnw27LzWp5MXJ7PeGPdIcEd +UShy6E1og3ZzL9ASK+CBOo3KF5alynbuAO6BKUJ2ji0VUB7ReidSiu7kWDLaAOK8 +bMY7F1/9joqMm9rMtJ4NJgxu0bDPWBPHLsSBwbtCL+ETewbyRlSSvGTbfjLlFfBm +QUizSLK69YQscoCsnNkZAAAAQgDhiD93TsQOWDb0yBFxRAktoM6d6IcqQz5VwfTI +R4I8XeV8VvxEOOFPTy+WZih44y3yKMkgMAw6Ri1UbjMC8Xeo4QAAAAABAg== +-----END OPENSSH PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519 new file mode 100644 index 000000000000..cbd3c34c05d1 Binary files /dev/null and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519 differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519.pub new file mode 100644 index 000000000000..b6f4f1d04760 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAILk8PqKB1H4+7HIcVZRG7HT02FIZ1TVOsV5XfOfX8j2G sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519_openssh b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519_openssh new file mode 100644 index 000000000000..20b48b01ad2f --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_ed25519_openssh @@ -0,0 +1,25 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +-----BEGIN OPENSSH PRIVATE KEY----- +b3BlbnNzaC1rZXktdjEAAAAABG5vbmUAAAAEbm9uZQAAAAAAAAABAAAAMwAAAAtz +c2gtZWQyNTUxOQAAACC5PD6igdR+PuxyHFWURux09NhSGdU1TrFeV3zn1/I9hgAA +AIgAAAAAAAAAAAAAAAtzc2gtZWQyNTUxOQAAACC5PD6igdR+PuxyHFWURux09NhS +GdU1TrFeV3zn1/I9hgAAAEDrYdUy6SRa+ENlJJpshN1zE0n4vdxHVDz8NT+MhOEN +cLk8PqKB1H4+7HIcVZRG7HT02FIZ1TVOsV5XfOfX8j2GAAAAAAECAwQF +-----END OPENSSH PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa new file mode 100644 index 000000000000..c96a11a203d2 Binary files /dev/null and b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa differ diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa.pub new file mode 100644 index 000000000000..a3eb8031e514 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa.pub @@ -0,0 +1,19 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +ssh-rsa AAAAB3NzaC1yc2EAAAADAQABAAABAQCq5sYEIwGywu/faJ35+ZwqBiHITZyntnp3WNrYD4T0ZeiuAr83zZugbG43rAsEvXg4dDNDWQBqawlEKOVw7KziT3j3ulIdB3kJIGYr5J7NW2Woeq/y/fUjFjKB+mFkwz6wgVw6XBz9s5gl/T9mwLrq6ER02RzBGWTFlzQemfK3z2O58tdaU67VGZj6bXjM+WjIIArWPgtZf3cgqiCept6lWGOd94v4uIMWlKdNVMVDM/ciEMiGIBWUJEU8Men5+P1EK5j7FJCSwtJCZywPcWk4PhjTtdWWd64bI6A7ZJnbii32rf3lESsboJu1cyuHnj6Evp0v6OuKqZ03pGb/yUPl sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa_openssh b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa_openssh new file mode 100644 index 000000000000..4680539c678d --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/dropbear/id_rsa_openssh @@ -0,0 +1,47 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% +-----BEGIN OPENSSH PRIVATE KEY----- +b3BlbnNzaC1rZXktdjEAAAAABG5vbmUAAAAEbm9uZQAAAAAAAAABAAABFwAAAAdz +c2gtcnNhAAAAAwEAAQAAAQEAqubGBCMBssLv32id+fmcKgYhyE2cp7Z6d1ja2A+E +9GXorgK/N82boGxuN6wLBL14OHQzQ1kAamsJRCjlcOys4k9497pSHQd5CSBmK+Se +zVtlqHqv8v31IxYygfphZMM+sIFcOlwc/bOYJf0/ZsC66uhEdNkcwRlkxZc0Hpny +t89jufLXWlOu1RmY+m14zPloyCAK1j4LWX93IKognqbepVhjnfeL+LiDFpSnTVTF +QzP3IhDIhiAVlCRFPDHp+fj9RCuY+xSQksLSQmcsD3FpOD4Y07XVlneuGyOgO2SZ +24ot9q395RErG6CbtXMrh54+hL6dL+jriqmdN6Rm/8lD5QAAA7gAAAAAAAAAAAAA +AAdzc2gtcnNhAAABAQCq5sYEIwGywu/faJ35+ZwqBiHITZyntnp3WNrYD4T0Zeiu +Ar83zZugbG43rAsEvXg4dDNDWQBqawlEKOVw7KziT3j3ulIdB3kJIGYr5J7NW2Wo +eq/y/fUjFjKB+mFkwz6wgVw6XBz9s5gl/T9mwLrq6ER02RzBGWTFlzQemfK3z2O5 +8tdaU67VGZj6bXjM+WjIIArWPgtZf3cgqiCept6lWGOd94v4uIMWlKdNVMVDM/ci +EMiGIBWUJEU8Men5+P1EK5j7FJCSwtJCZywPcWk4PhjTtdWWd64bI6A7ZJnbii32 +rf3lESsboJu1cyuHnj6Evp0v6OuKqZ03pGb/yUPlAAAAAwEAAQAAAQAXfauTt30d +BXsDxiVKzjLXOusLVZG2ItjADWRdZPq1PknGm2WNxdMBsM3QlLMaBnIfLme6duId +/pLyPb3V8Q5NeDeMM53kVBngtYWdvGnQl+LIDv8e4yX+Gee84n3fJBA6ojlbYzxv +6e78r8v2c4Dt15nLRumTKEqn90Hof+gzOBK/6yUweJxtbRhyTaPBhllUBTAv20sA +zal4rRSP4cR2CWm95Eg3rA3XrQo9TYWQmdpQmRmrt99xTzMjsvr4oh8P7+hukzKV +xI3E0ilajboK0hGBRrXcKmpegMXRLTkWudp7UGl7K/ssFHz9jHRrN91b/eZguE8G +M3xeb7iRkgIJAAAAgHi+R05tHEKLYqQ+mhYGt2lW4v4bwTDCs1Mq5eeeq2SVZXSk +WCIkP0lnmoKCMDYtS9PQrR7zzgLjQtUnTRj4Zqh/tBD2sgFBf30+oJfDEJdMrd2r +StIaaalAwbenPrzsuN+0avtBNTBAq+cMY5Ly+O7Dw2+2oFenz3IHa8RChUolAAAA +gQDPiTYrzZb15Sgslqr/1ggCl25HqGGPKmEDmRTWlcxJJBustQQ90V5MT71uQGj/ +7z8pl8SxvSi/H4dGi8H/r2O9u9VzKo9OLCVYfaDEu4mqPDfz9/xkB+IY79DIZAcF +d2FB6dydyAxrmdf5eKxbPtrI0XSFcmtDpcFPG1lqnkauGQAAAIEA0s9/1JNULl49 +xeVzn75zic1bf+W28skVykKTITZvR9X4XhC+Glr7HITJFkybNVtckWTjBpIEmPE5 +T8xVYbzbm0eZqpto9QwFPL5j1Fd6AXQo3KxCcd2xe0EEW0yRp+qH4FDMNYh6BzKe +ppH2WfWWynvNYA3zxRul6SDCV808Ja0AAAAAAQID +-----END OPENSSH PRIVATE KEY----- diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_dsa b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_dsa similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_dsa rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_dsa diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_dsa.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_dsa.pub similarity index 97% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_dsa.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_dsa.pub index 39e4eff9ce16..37739f504f76 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_dsa.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_dsa.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ssh-dss AAAAB3NzaC1kc3MAAACBAL3tedxANpr09BgRYruWUHFlDay5VhPPV5p3DYe1j5jxkp1QEt30tRDaXKZQL3KrrqtvmkEFHXeT/1lxu7wjSdp+tlPjAngfRgYPo5vk7gdHgQeM7mqGCcwnXt7VefMjfUxbnEC4AdMssKU2+cbTlPWNpT61ECxVIIeKff6w56ejAAAAFQDEngDQb8O35ufi8Ps4jgBz43mM0QAAAIEAuRYIakqaUnrkXdj9FyjCcdC+ysMCWXMoX9pxJ+uIJVU/mpVncByHbxln0EUSdETZIqpWzIECJx5v/4hKW7wKooS++g0gwkC7mtQzBmH494c3gRLq1ZPAEYDC7ziR7o3gGBX7pDiqRzLLAexPmhTQR1VufbPMBnDxzu8GluwnUqwAAACABraHWqSFhaX4+GHmtKwXZFVRKh/4R6GR2LpkFzGm3Ixv+eo9K5CITjiBYiVMrWH23G1LiDuJyMGqHEnIef+sorNfNzdnwq+8qRCTS6mbpRXkUt9p1arJMIKmosS+GFhTN6Z85gCwC51S2EDC4GW7J4ViHKacr1FwJSw9RC9F+Ws= uabhnil@elxadlj3q32 +ssh-dss AAAAB3NzaC1kc3MAAACBAL3tedxANpr09BgRYruWUHFlDay5VhPPV5p3DYe1j5jxkp1QEt30tRDaXKZQL3KrrqtvmkEFHXeT/1lxu7wjSdp+tlPjAngfRgYPo5vk7gdHgQeM7mqGCcwnXt7VefMjfUxbnEC4AdMssKU2+cbTlPWNpT61ECxVIIeKff6w56ejAAAAFQDEngDQb8O35ufi8Ps4jgBz43mM0QAAAIEAuRYIakqaUnrkXdj9FyjCcdC+ysMCWXMoX9pxJ+uIJVU/mpVncByHbxln0EUSdETZIqpWzIECJx5v/4hKW7wKooS++g0gwkC7mtQzBmH494c3gRLq1ZPAEYDC7ziR7o3gGBX7pDiqRzLLAexPmhTQR1VufbPMBnDxzu8GluwnUqwAAACABraHWqSFhaX4+GHmtKwXZFVRKh/4R6GR2LpkFzGm3Ixv+eo9K5CITjiBYiVMrWH23G1LiDuJyMGqHEnIef+sorNfNzdnwq+8qRCTS6mbpRXkUt9p1arJMIKmosS+GFhTN6Z85gCwC51S2EDC4GW7J4ViHKacr1FwJSw9RC9F+Ws= sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa256 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa256 similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa256 rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa256 diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa256.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa256.pub similarity index 93% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa256.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa256.pub index 0f6d2d717264..57cb61df137a 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa256.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa256.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ecdsa-sha2-nistp256 AAAAE2VjZHNhLXNoYTItbmlzdHAyNTYAAAAIbmlzdHAyNTYAAABBBAtyeX0PPvMULKNJYQXaC3bw9eKErEIjLsHl6vg8tvuDI3cNv228NAr2xNviljXIMMUS8nDRnDAgXX/3DoDchpA= sshtester@elxadlj3q32 +ecdsa-sha2-nistp256 AAAAE2VjZHNhLXNoYTItbmlzdHAyNTYAAAAIbmlzdHAyNTYAAABBBAtyeX0PPvMULKNJYQXaC3bw9eKErEIjLsHl6vg8tvuDI3cNv228NAr2xNviljXIMMUS8nDRnDAgXX/3DoDchpA= sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa384 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa384 similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa384 rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa384 diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa384.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa384.pub similarity index 96% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa384.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa384.pub index c5ace380636a..b263fb398258 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa384.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa384.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ecdsa-sha2-nistp384 AAAAE2VjZHNhLXNoYTItbmlzdHAzODQAAAAIbmlzdHAzODQAAABhBNTDqlP9RbYe9NbqUvYEZjs19QYRfbzldWL0BxNcfUr5M56RsaZylKKuUbNJvXlbJxqOmZpp7m8DMfWee9xV3cVg4NV0NdMeBX8V5dD69rDsJmcQApmyvyaNdFfd8TI7UQ== uabhnil@elxadlj3q32 +ecdsa-sha2-nistp384 AAAAE2VjZHNhLXNoYTItbmlzdHAzODQAAAAIbmlzdHAzODQAAABhBNTDqlP9RbYe9NbqUvYEZjs19QYRfbzldWL0BxNcfUr5M56RsaZylKKuUbNJvXlbJxqOmZpp7m8DMfWee9xV3cVg4NV0NdMeBX8V5dD69rDsJmcQApmyvyaNdFfd8TI7UQ== sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa521 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa521 similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa521 rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa521 diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa521.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa521.pub similarity index 90% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa521.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa521.pub index dea935a6351b..3600927e5213 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ecdsa521.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ecdsa521.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ecdsa-sha2-nistp521 AAAAE2VjZHNhLXNoYTItbmlzdHA1MjEAAAAIbmlzdHA1MjEAAACFBAGHqfHF9u8FD8OaTWMBZFkF6ydhkpJjvIh8JFierK0Wsv7Bd1qDxf3cg1cphYIq7bEkyfg9LnseKqYTjicZHdWH/gDR7wxTfS6Ab24LTS00SZabjSwnVkJbfphJzzAxjFfx1hx4s+/5lhPl1FSHEI4Zubr9DmyP8K6GRLq1zBhIU4rNyw== uabhnil@elxadlj3q32 +ecdsa-sha2-nistp521 AAAAE2VjZHNhLXNoYTItbmlzdHA1MjEAAAAIbmlzdHA1MjEAAACFBAGHqfHF9u8FD8OaTWMBZFkF6ydhkpJjvIh8JFierK0Wsv7Bd1qDxf3cg1cphYIq7bEkyfg9LnseKqYTjicZHdWH/gDR7wxTfS6Ab24LTS00SZabjSwnVkJbfphJzzAxjFfx1hx4s+/5lhPl1FSHEI4Zubr9DmyP8K6GRLq1zBhIU4rNyw== sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed25519 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed25519 similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed25519 rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed25519 diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed25519.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed25519.pub similarity index 94% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed25519.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed25519.pub index f6abc6dfe135..49ed18f768e0 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed25519.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed25519.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAIOb0/z+ALQg4qbActK+SYS1LZfHRFGpQOoLrBjpSANWf uabhnil@elxadlj3q32 +ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAIOb0/z+ALQg4qbActK+SYS1LZfHRFGpQOoLrBjpSANWf sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed448 b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed448 similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed448 rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed448 diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed448.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed448.pub similarity index 91% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed448.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed448.pub index 7cd45ca1c09d..5c8abeb7b43a 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_ed448.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_ed448.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ssh-ed448 AAAACXNzaC1lZDQ0OAAAADnc6p5481ob80magxsQuGyQqsAc2EtnoBCbVaNukyix42X84WHXHOcTGlQ+pMtffp8diwBpZEcAFAA= uabhnil@elxadlj3q32 +ssh-ed448 AAAACXNzaC1lZDQ0OAAAADnc6p5481ob80magxsQuGyQqsAc2EtnoBCbVaNukyix42X84WHXHOcTGlQ+pMtffp8diwBpZEcAFAA= sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_rsa b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_rsa similarity index 100% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_rsa rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_rsa diff --git a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_rsa.pub b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_rsa.pub similarity index 92% rename from lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_rsa.pub rename to lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_rsa.pub index fae222c8f382..e5a20bddb6ba 100644 --- a/lib/ssh/test/ssh_compat_SUITE_data/users_keys/id_rsa.pub +++ b/lib/ssh/test/ssh_compat_SUITE_data/users_keys/openssh/id_rsa.pub @@ -16,4 +16,4 @@ # limitations under the License. # # %CopyrightEnd% -ssh-rsa AAAAB3NzaC1yc2EAAAADAQABAAABAQDv4LeAuh+UrJurgj5yVuDZJZ/pxfIemcs0Odl4y8hs7PZf8J5dSbXsMV57FNpUGz1mr1bAMU4WQtCFu5eCm8HSyFJjSev4SbsidEzwCJEvE97S3EyYUWEv6/Tzd1jCBok6jU+2E0z+0ZFkm77SxAOquY3sK6wUd1mDY1PNPNvBao+K4/+Z/ejtbgJaoNMHNthOClaUfu9Fl/0VjBPiiflhbMsDxO87ZPAEZN9MwrmezAf76I6/iMp5ygTDIEUxRIqpn1RgcbD+SyEduW0zrlh7/GNcRfQbEN3G7xnJUpd3hpw1skk/S1zE3gbMomJHrM1jALMOGOoMRszmoIaFKGGB uabhnil@elxadlj3q32 +ssh-rsa AAAAB3NzaC1yc2EAAAADAQABAAABAQDv4LeAuh+UrJurgj5yVuDZJZ/pxfIemcs0Odl4y8hs7PZf8J5dSbXsMV57FNpUGz1mr1bAMU4WQtCFu5eCm8HSyFJjSev4SbsidEzwCJEvE97S3EyYUWEv6/Tzd1jCBok6jU+2E0z+0ZFkm77SxAOquY3sK6wUd1mDY1PNPNvBao+K4/+Z/ejtbgJaoNMHNthOClaUfu9Fl/0VjBPiiflhbMsDxO87ZPAEZN9MwrmezAf76I6/iMp5ygTDIEUxRIqpn1RgcbD+SyEduW0zrlh7/GNcRfQbEN3G7xnJUpd3hpw1skk/S1zE3gbMomJHrM1jALMOGOoMRszmoIaFKGGB sshtester@host diff --git a/lib/ssh/test/ssh_compat_SUITE_data/versions.txt b/lib/ssh/test/ssh_compat_SUITE_data/versions.txt new file mode 100644 index 000000000000..c8b6a0e07ae4 --- /dev/null +++ b/lib/ssh/test/ssh_compat_SUITE_data/versions.txt @@ -0,0 +1,52 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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. +# +# %CopyrightEnd% + +openssh 4.4p1 openssl 0.9.8c 16.04 +openssh 4.5p1 openssl 0.9.8m 16.04 +openssh 5.0p1 openssl 0.9.8zh 16.04 +openssh 6.2p2 openssl 0.9.8c 16.04 +openssh 6.3p1 openssl 0.9.8zh 16.04 +openssh 7.1p1 openssl 1.0.0a 16.04 +openssh 7.1p1 openssl 1.0.1p 16.04 +openssh 6.6p1 openssl 1.0.2n 16.04 +openssh 7.1p1 openssl 1.0.2n 16.04 +openssh 7.6p1 openssl 1.0.2n 16.04 +openssh 7.6p1 libressl 2.6.4 16.04 +openssh 7.7p1 openssl 1.0.2p 16.04 +openssh 7.8p1 openssl 1.0.2p 16.04 +openssh 7.9p1 openssl 1.0.2p 16.04 +openssh 7.9p1 libressl 2.6.4 16.04 +openssh 8.2p1 openssl 1.0.2p 22.04 +openssh 9.5p1 openssl 1.1.1w 22.04 +openssh 9.5p1 libressl 3.5.0 22.04 +openssh 9.9p2 openssl 1.1.1w 22.04 +openssh 9.9p2 libressl 3.9.2 22.04 +openssh 10.2p1 libressl 4.2.1 22.04 +openssh 10.2p1 openssl 1.1.1w 22.04 +openssh 10.2p1 openssl 3.0.18 22.04 +openssh 10.2p1 openssl 3.1.8 22.04 +openssh 10.2p1 openssl 3.2.6 22.04 +openssh 10.2p1 openssl 3.3.5 22.04 +openssh 10.2p1 openssl 3.4.3 22.04 +openssh 10.2p1 openssl 3.5.4 22.04 +openssh 10.2p1 openssl 3.6.0 22.04 +dropbear 2020.81 22.04 +dropbear 2022.83 22.04 +dropbear 2024.86 22.04 +dropbear 2025.88 22.04