File 3091-Add-SSH-agent-support-for-the-ssh-application.patch of Package erlang
From aa47d377de1fd606055008dd9ea472f434f612f3 Mon Sep 17 00:00:00 2001
From: Paul Meinhardt <paul@bitcrowd.net>
Date: Sun, 26 May 2019 15:33:20 +0200
Subject: [PATCH] Add SSH agent support for the ssh application
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
- Add ssh_agent module
- Modify ssh_auth to support pub key sign requests
- Add optional callback sign/3 to ssh_client_key_api behaviour
- Added a ssh_agent_mock_server module for testing this
Co-authored-by: Malte Rohde <malte@bitcrowd.net>
Co-authored-by: Andreas Knöpfle <andi@bitcrowd.net>
---
lib/ssh/doc/src/Makefile | 1 +
lib/ssh/doc/src/ref_man.xml | 2 +-
lib/ssh/doc/src/specs.xml | 3 +-
lib/ssh/doc/src/ssh_agent.xml | 134 ++++++++++++++++++
lib/ssh/src/Makefile | 4 +-
lib/ssh/src/ssh.app.src | 1 +
lib/ssh/src/ssh_agent.erl | 149 ++++++++++++++++++++
lib/ssh/src/ssh_agent.hrl | 106 +++++++++++++++
lib/ssh/src/ssh_auth.erl | 54 +++++---
lib/ssh/src/ssh_client_key_api.erl | 17 ++-
lib/ssh/test/Makefile | 2 +
lib/ssh/test/ssh_agent_SUITE.erl | 134 ++++++++++++++++++
lib/ssh/test/ssh_agent_SUITE_data/authorized_keys | 1 +
lib/ssh/test/ssh_agent_SUITE_data/id_rsa | 27 ++++
lib/ssh/test/ssh_agent_SUITE_data/ssh_host_rsa_key | 27 ++++
lib/ssh/test/ssh_agent_mock_server.erl | 151 +++++++++++++++++++++
16 files changed, 785 insertions(+), 28 deletions(-)
create mode 100644 lib/ssh/doc/src/ssh_agent.xml
create mode 100644 lib/ssh/src/ssh_agent.erl
create mode 100644 lib/ssh/src/ssh_agent.hrl
create mode 100644 lib/ssh/test/ssh_agent_SUITE.erl
create mode 100644 lib/ssh/test/ssh_agent_SUITE_data/authorized_keys
create mode 100644 lib/ssh/test/ssh_agent_SUITE_data/id_rsa
create mode 100644 lib/ssh/test/ssh_agent_SUITE_data/ssh_host_rsa_key
create mode 100644 lib/ssh/test/ssh_agent_mock_server.erl
diff --git a/lib/ssh/doc/src/Makefile b/lib/ssh/doc/src/Makefile
index 4e6af79a1a..60aa881f1f 100644
--- a/lib/ssh/doc/src/Makefile
+++ b/lib/ssh/doc/src/Makefile
@@ -41,6 +41,7 @@ XML_REF3_FILES = \
ssh_server_channel.xml \
ssh_server_key_api.xml \
ssh_file.xml \
+ ssh_agent.xml \
ssh_sftp.xml \
ssh_sftpd.xml \
diff --git a/lib/ssh/doc/src/ref_man.xml b/lib/ssh/doc/src/ref_man.xml
index 60572b985b..1ecc561e92 100644
--- a/lib/ssh/doc/src/ref_man.xml
+++ b/lib/ssh/doc/src/ref_man.xml
@@ -41,7 +41,7 @@
<xi:include href="ssh_client_key_api.xml"/>
<xi:include href="ssh_server_key_api.xml"/>
<xi:include href="ssh_file.xml"/>
+ <xi:include href="ssh_agent.xml"/>
<xi:include href="ssh_sftp.xml"/>
<xi:include href="ssh_sftpd.xml"/>
</application>
-
diff --git a/lib/ssh/doc/src/specs.xml b/lib/ssh/doc/src/specs.xml
index a6517f3660..a4e7301a95 100644
--- a/lib/ssh/doc/src/specs.xml
+++ b/lib/ssh/doc/src/specs.xml
@@ -7,8 +7,7 @@
<xi:include href="../specs/specs_ssh_server_channel.xml"/>
<xi:include href="../specs/specs_ssh_server_key_api.xml"/>
<xi:include href="../specs/specs_ssh_file.xml"/>
+ <xi:include href="../specs/specs_ssh_agent.xml"/>
<xi:include href="../specs/specs_ssh_sftp.xml"/>
<xi:include href="../specs/specs_ssh_sftpd.xml"/>
</specs>
-
-
diff --git a/lib/ssh/doc/src/ssh_agent.xml b/lib/ssh/doc/src/ssh_agent.xml
new file mode 100644
index 0000000000..6e7ee7a5c0
--- /dev/null
+++ b/lib/ssh/doc/src/ssh_agent.xml
@@ -0,0 +1,134 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE erlref SYSTEM "erlref.dtd">
+
+<erlref>
+ <header>
+ <copyright>
+ <year>2018</year><year>2018</year>
+ <holder>Ericsson AB. All Rights Reserved.</holder>
+ </copyright>
+ <legalnotice>
+ 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.
+
+ </legalnotice>
+
+ <title>ssh_agent</title>
+ <prepared></prepared>
+ <docno></docno>
+ <date></date>
+ <rev></rev>
+ </header>
+ <module since="OTP 23.0">ssh_agent</module>
+ <modulesummary>Callback module for using an SSH agent instead of the default ssh_file callback.</modulesummary>
+ <description>
+ <p>
+ This module defines a callback handler for the communication with an
+ <url href="https://tools.ietf.org/html/draft-miller-ssh-agent-02">SSH Agent</url>
+ and can be used to replace the <seealso marker="ssh:ssh_file">default callback</seealso>.
+ This allows to issue signing requests to an agent that stores SSH private keys to perform
+ authentication.
+ </p>
+ <p>
+ Ssh_agent implements the <seealso marker="ssh:ssh_client_key_api">ssh_client_key_api</seealso>, to
+ allow it to be used by setting the option
+ <seealso marker="ssh:ssh#type-key_cb_common_option"><c>key_cb</c></seealso>
+ when starting a client (with for example
+ <seealso marker="ssh:ssh#connect-3">ssh:connect</seealso>,
+ <seealso marker="ssh:ssh#shell-1">ssh:shell</seealso>
+ ).
+ </p>
+ <code type="erl">
+ {key_cb, {ssh_agent, []}}
+ </code>
+ <p>
+ The agent communication is established through a UNIX domain socket. By default, the socket path
+ will be fetched from the <c>SSH_AUTH_SOCK</c> enviroment variable, which is the default socket path in the agent
+ implementation of
+ <url href="http://www.openssh.com">OpenSSH</url>.
+ </p>
+ <p>
+ <marker id="SOCKET_PATH"/>
+ In order to set a different socket path the <c>socket_path</c> option can be set.
+ </p>
+ <code type="erl">
+ {key_cb, {ssh_agent, [{socket_path, SocketPath}]}}
+ </code>
+
+ <note>
+ <p>The functions are <i>Callbacks</i> for the SSH app. They are not intended to be called from the user's code!
+ </p>
+ </note>
+ </description>
+
+ <datatypes>
+ <datatype_title>Options for the ssh_agent callback module</datatype_title>
+ <datatype>
+ <name name="socket_path_option"/>
+ <desc>
+ <p>Sets the <seealso marker="#SOCKET_PATH">socket path</seealso> for the communication with the agent.</p>
+ </desc>
+ </datatype>
+
+ <datatype>
+ <name name="timeout_option"/>
+ <desc>
+ <p>
+ Sets the time-out in milliseconds when communicating with the agent via the socket.
+ The default value is <c>1000</c>.
+ </p>
+ </desc>
+ </datatype>
+ <datatype>
+ <name name="call_ssh_file_option"/>
+ <desc>
+ <p>
+ The module which the <c>add_host_key</c> and <c>is_host_key</c> callbacks are delegated to. Defaults to the
+ <seealso marker="ssh:ssh_file">ssh_file</seealso> module.
+ </p>
+ </desc>
+ </datatype>
+ </datatypes>
+
+ <funcs>
+ <func>
+ <name since="OTP 23.0">add_host_key(HostNames, PublicHostKey, ConnectOptions) -> ok | {error, Reason}</name>
+ <fsummary></fsummary>
+ <desc>
+ <p>
+ This callback is delegated to the <seealso marker="ssh:ssh_file#add_host_key-3">ssh_file</seealso> module.
+ </p>
+ </desc>
+ </func>
+
+ <func>
+ <name since="OTP 23.0">is_host_key(Key, Host, Algorithm, ConnectOptions) -> Result</name>
+ <fsummary></fsummary>
+ <desc>
+ <p>
+ This callback is delegated to the <seealso marker="ssh:ssh_file#is_host_key-4">ssh_file</seealso> module.
+ </p>
+ </desc>
+ </func>
+
+ <func>
+ <name since="OTP 23.0">user_key(Algorithm, ConnectOptions) -> {ok, {ssh2_pubkey, PublicKey}} | {error, Reason}</name>
+ <fsummary></fsummary>
+ <desc>
+ <p><strong>Types and description</strong></p>
+ <p>See the api description in
+ <seealso marker="ssh:ssh_client_key_api#Module:user_key-2">ssh_client_key_api, Module:user_key/2</seealso>.
+ </p>
+ </desc>
+ </func>
+ </funcs>
+</erlref>
diff --git a/lib/ssh/src/Makefile b/lib/ssh/src/Makefile
index 68d7fd13e7..2b7e9131f7 100644
--- a/lib/ssh/src/Makefile
+++ b/lib/ssh/src/Makefile
@@ -58,6 +58,7 @@ MODULES= \
ssh \
ssh_acceptor \
ssh_acceptor_sup \
+ ssh_agent \
ssh_app \
ssh_auth\
ssh_bits \
@@ -107,7 +108,7 @@ APP_TARGET= $(EBIN)/$(APP_FILE)
APPUP_SRC= $(APPUP_FILE).src
APPUP_TARGET= $(EBIN)/$(APPUP_FILE)
-INTERNAL_HRL_FILES = ssh_auth.hrl ssh_connect.hrl ssh_transport.hrl ssh.hrl ssh_xfer.hrl
+INTERNAL_HRL_FILES = ssh_agent.hrl ssh_auth.hrl ssh_connect.hrl ssh_transport.hrl ssh.hrl ssh_xfer.hrl
# ----------------------------------------------------
# FLAGS
@@ -183,6 +184,7 @@ $(EBIN)/ssh_subsystem_sup.$(EMULATOR): ssh_subsystem_sup.erl
$(EBIN)/ssh_server_channel_sup.$(EMULATOR): ssh_server_channel_sup.erl
$(EBIN)/ssh_acceptor_sup.$(EMULATOR): ssh_acceptor_sup.erl ssh.hrl
$(EBIN)/ssh_acceptor.$(EMULATOR): ssh_acceptor.erl ssh.hrl
+$(EBIN)/ssh_agent.$(EMULATOR): ssh_agent.erl ssh.hrl ssh_agent.hrl
$(EBIN)/ssh_app.$(EMULATOR): ssh_app.erl
$(EBIN)/ssh_auth.$(EMULATOR): ssh_auth.erl \
../../public_key/include/public_key.hrl \
diff --git a/lib/ssh/src/ssh.app.src b/lib/ssh/src/ssh.app.src
index fda507727a..5ed3dc3285 100644
--- a/lib/ssh/src/ssh.app.src
+++ b/lib/ssh/src/ssh.app.src
@@ -8,6 +8,7 @@
ssh_acceptor,
ssh_acceptor_sup,
ssh_options,
+ ssh_agent,
ssh_auth,
ssh_message,
ssh_bits,
diff --git a/lib/ssh/src/ssh_agent.erl b/lib/ssh/src/ssh_agent.erl
new file mode 100644
index 0000000000..9f82f6ccae
--- /dev/null
+++ b/lib/ssh/src/ssh_agent.erl
@@ -0,0 +1,149 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019. All Rights Reserved.
+%%
+%% 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%
+%%
+
+%% Reference: https://tools.ietf.org/html/draft-miller-ssh-agent-02
+
+-module(ssh_agent).
+
+-behaviour(ssh_client_key_api).
+
+-include("ssh.hrl").
+-include("ssh_agent.hrl").
+
+-export([send/2]).
+-export([add_host_key/3, is_host_key/4, user_key/2, sign/3]).
+
+-export_type([socket_path_option/0, timeout_option/0, call_ssh_file_option/0]).
+
+-type socket_path_option() :: {socket_path, string()}.
+-type timeout_option() :: {timeout, integer()}.
+-type call_ssh_file_option() :: {call_ssh_file, atom()}.
+
+%% ssh_client_key_api implementation
+
+add_host_key(Host, Key, Opts) ->
+ KeyCbOpts = proplists:get_value(key_cb_private, Opts, []),
+ SshFileCb = proplists:get_value(call_ssh_file, KeyCbOpts, ssh_file),
+ SshFileCb:add_host_key(Host, Key, Opts).
+
+is_host_key(Key, PeerName, Algorithm, Opts) ->
+ KeyCbOpts = proplists:get_value(key_cb_private, Opts, []),
+ SshFileCb = proplists:get_value(call_ssh_file, KeyCbOpts, ssh_file),
+ SshFileCb:is_host_key(Key, PeerName, Algorithm, Opts).
+
+user_key(Algorithm, Opts) ->
+ KeyCbOpts = proplists:get_value(key_cb_private, Opts, []),
+
+ Request = #ssh_agent_identities_request{},
+ Response = ssh_agent:send(Request, KeyCbOpts),
+
+ #ssh_agent_identities_response{keys = Keys} = Response,
+
+ AlgorithmStr = atom_to_list(Algorithm),
+ MatchingKeys = lists:filter(fun(Key) -> has_key_type(Key, AlgorithmStr) end, Keys),
+
+ % The "client_key_api" behaviour only allows returning a single user key,
+ % so we simply select the first one returned from the SSH agent here. This
+ % means that if a user adds multiple keys for the same algorithm, only the
+ % first one added will be used.
+ case MatchingKeys of
+ [#ssh_agent_key{blob = PubKeyBlob} | _OtherKeys] ->
+ {ok, {ssh2_pubkey, PubKeyBlob}};
+ _ ->
+ {error, enoent}
+ end.
+
+sign(PubKeyBlob, SigData, Opts) ->
+ KeyCbOpts = proplists:get_value(key_cb_private, Opts, []),
+ % OpenSSH does not seem to care when these flags are set for
+ % signature algorithms other than RSA, so we always send them.
+ SignFlags = ?SSH_AGENT_RSA_SHA2_256 bor ?SSH_AGENT_RSA_SHA2_512,
+ SignRequest = #ssh_agent_sign_request{key_blob = PubKeyBlob, data = SigData, flags = SignFlags},
+ SignResponse = ssh_agent:send(SignRequest, KeyCbOpts),
+ #ssh_agent_sign_response{signature = #ssh_agent_signature{blob = Blob}} = SignResponse,
+ Blob.
+
+%% Utility functions
+
+has_key_type(#ssh_agent_key{blob = KeyBlob}, Type) ->
+ <<?DEC_BIN(KeyType, _KeyTypeLen), _KeyBlobRest/binary>> = KeyBlob,
+ binary_to_list(KeyType) == Type.
+
+%% Agent communication
+
+send(Request, Opts) ->
+ SocketPath = proplists:get_value(socket_path, Opts, os:getenv("SSH_AUTH_SOCK")),
+ Timeout = proplists:get_value(timeout, Opts, 1000),
+
+ ConnectOpts = [binary, {packet, 0}, {active, false}],
+ {ok, Socket} = gen_tcp:connect({local, SocketPath}, 0, ConnectOpts, Timeout),
+
+ BinRequest = pack(encode(Request)),
+ ok = gen_tcp:send(Socket, BinRequest),
+
+ {ok, BinResponse} = gen_tcp:recv(Socket, 0, Timeout),
+
+ ok = gen_tcp:close(Socket),
+
+ Response = decode(unpack(BinResponse)),
+
+ Response.
+
+%% Message packing and unpacking
+
+pack(Data) ->
+ <<(size(Data)):32/unsigned-big-integer, Data/binary>>.
+
+unpack(<<Len:32/unsigned-big-integer, Data:Len/binary>>) ->
+ Data.
+
+%% SSH Agent message encoding
+
+encode(#ssh_agent_identities_request{}) ->
+ <<?Ebyte(?SSH_AGENTC_REQUEST_IDENTITIES)>>;
+
+encode(#ssh_agent_sign_request{key_blob = KeyBlob, data = Data, flags = Flags}) ->
+ <<?Ebyte(?SSH_AGENTC_SIGN_REQUEST), ?Estring(KeyBlob), ?Estring(Data), ?Euint32(Flags)>>.
+
+%% SSH Agent message decoding
+
+decode_keys(<<>>, Acc, 0) ->
+ lists:reverse(Acc);
+
+decode_keys(<<?DEC_BIN(KeyBlob, _KeyBlobLen), ?DEC_BIN(Comment, _CommentLen), Rest/binary>>, Acc, N) ->
+ Key = #ssh_agent_key{blob = KeyBlob, comment = Comment},
+ decode_keys(Rest, [Key | Acc], N - 1).
+
+decode_signature(<<?DEC_BIN(Format, _FormatLen), Blob/binary>>) ->
+ % Decode signature according to https://tools.ietf.org/html/rfc4253#section-6.6
+ <<?DEC_BIN(SignatureBlob, _SignatureBlobLen)>> = Blob,
+ #ssh_agent_signature{format = Format, blob = SignatureBlob}.
+
+decode(<<?BYTE(?SSH_AGENT_SUCCESS)>>) ->
+ #ssh_agent_success{};
+
+decode(<<?BYTE(?SSH_AGENT_FAILURE)>>) ->
+ #ssh_agent_failure{};
+
+decode(<<?BYTE(?SSH_AGENT_IDENTITIES_ANSWER), ?UINT32(NumKeys), KeyData/binary>>) ->
+ #ssh_agent_identities_response{keys = decode_keys(KeyData, [], NumKeys)};
+
+decode(<<?BYTE(?SSH_AGENT_SIGN_RESPONSE), ?DEC_BIN(Signature, _SignatureLen)>>) ->
+ #ssh_agent_sign_response{signature = decode_signature(Signature)}.
diff --git a/lib/ssh/src/ssh_agent.hrl b/lib/ssh/src/ssh_agent.hrl
new file mode 100644
index 0000000000..687a982e59
--- /dev/null
+++ b/lib/ssh/src/ssh_agent.hrl
@@ -0,0 +1,106 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019. All Rights Reserved.
+%%
+%% 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%
+%%
+
+%% Reference: https://tools.ietf.org/html/draft-miller-ssh-agent-02
+
+%% SSH Agent message numbers
+%%
+%% Reference: https://tools.ietf.org/html/draft-miller-ssh-agent-02#section-5.1
+
+%% The following numbers are used for requests from the client to the agent.
+
+-define(SSH_AGENTC_REQUEST_IDENTITIES, 11).
+-define(SSH_AGENTC_SIGN_REQUEST, 13).
+-define(SSH_AGENTC_ADD_IDENTITY, 17).
+-define(SSH_AGENTC_REMOVE_IDENTITY, 18).
+-define(SSH_AGENTC_REMOVE_ALL_IDENTITIES, 19).
+-define(SSH_AGENTC_ADD_ID_CONSTRAINED, 25).
+-define(SSH_AGENTC_ADD_SMARTCARD_KEY, 20).
+-define(SSH_AGENTC_REMOVE_SMARTCARD_KEY, 21).
+-define(SSH_AGENTC_LOCK, 22).
+-define(SSH_AGENTC_UNLOCK, 23).
+-define(SSH_AGENTC_ADD_SMARTCARD_KEY_CONSTRAINED, 26).
+-define(SSH_AGENTC_EXTENSION, 27).
+
+%% The following numbers are used for replies from the agent to the client.
+
+-define(SSH_AGENT_FAILURE, 5).
+-define(SSH_AGENT_SUCCESS, 6).
+-define(SSH_AGENT_EXTENSION_FAILURE, 28).
+-define(SSH_AGENT_IDENTITIES_ANSWER, 12).
+-define(SSH_AGENT_SIGN_RESPONSE, 14).
+
+%% SSH Agent signature flags
+%%
+%% Reference: https://tools.ietf.org/html/draft-miller-ssh-agent-02#section-5.3
+
+-define(SSH_AGENT_RSA_SHA2_256, 2).
+-define(SSH_AGENT_RSA_SHA2_512, 4).
+
+%% SSH Agent messages
+%%
+%% Reference: https://tools.ietf.org/html/draft-miller-ssh-agent-02#section-4
+
+%% 4.1 Generic server responses
+
+-record(ssh_agent_success,
+ {
+ }).
+
+-record(ssh_agent_failure,
+ {
+ }).
+
+%% 4.4 Requesting a list of keys
+
+-record(ssh_agent_identities_request,
+ {
+ }).
+
+-record(ssh_agent_key,
+ {
+ blob, % string
+ comment % string
+ }).
+
+-record(ssh_agent_identities_response,
+ {
+ keys % list of ssh_agent_key records
+ }).
+
+%% 4.5 Private key operations
+
+-record(ssh_agent_sign_request,
+ {
+ key_blob, % string
+ data, % string
+ flags % integer
+ }).
+
+-record(ssh_agent_signature,
+ {
+ format, % string
+ blob % binary
+ }).
+
+-record(ssh_agent_sign_response,
+ {
+ signature % ssh_agent_signature
+ }).
diff --git a/lib/ssh/src/ssh_auth.erl b/lib/ssh/src/ssh_auth.erl
index bb3bec9c7c..c49119a81b 100644
--- a/lib/ssh/src/ssh_auth.erl
+++ b/lib/ssh/src/ssh_auth.erl
@@ -26,6 +26,7 @@
-include("ssh.hrl").
-include("ssh_auth.hrl").
+-include("ssh_agent.hrl").
-include("ssh_transport.hrl").
-export([get_public_key/2,
@@ -140,6 +141,9 @@ keyboard_interactive_msg([#ssh{user = User,
get_public_key(SigAlg, #ssh{opts = Opts}) ->
KeyAlg = key_alg(SigAlg),
case ssh_transport:call_KeyCb(user_key, [KeyAlg], Opts) of
+ {ok, {ssh2_pubkey, PubKeyBlob}} ->
+ {ok, {ssh2_pubkey, PubKeyBlob}};
+
{ok, PrivKey} ->
try
%% Check the key - the KeyCb may be a buggy plugin
@@ -147,40 +151,50 @@ get_public_key(SigAlg, #ssh{opts = Opts}) ->
Key = ssh_transport:extract_public_key(PrivKey),
ssh_message:ssh2_pubkey_encode(Key)
of
- PubKeyBlob -> {ok,{PrivKey,PubKeyBlob}}
+ PubKeyBlob -> {ok, {PrivKey, PubKeyBlob}}
catch
_:_ ->
not_ok
end;
- _Error ->
- not_ok
+ _Error ->
+ not_ok
end.
publickey_msg([SigAlg, #ssh{user = User,
- session_id = SessionId,
- service = Service} = Ssh]) ->
+ session_id = SessionId,
+ service = Service,
+ opts = Opts} = Ssh]) ->
case get_public_key(SigAlg, Ssh) of
- {ok, {PrivKey,PubKeyBlob}} ->
+ {ok, {_, PubKeyBlob} = Key} ->
SigAlgStr = atom_to_list(SigAlg),
- SigData = build_sig_data(SessionId, User, Service,
- PubKeyBlob, SigAlgStr),
- Hash = ssh_transport:sha(SigAlg),
- Sig = ssh_transport:sign(SigData, Hash, PrivKey),
+ SigData = build_sig_data(SessionId, User, Service, PubKeyBlob, SigAlgStr),
+
+ Sig = case Key of
+ {ssh2_pubkey, PubKeyBlob} ->
+ ssh_transport:call_KeyCb(sign, [PubKeyBlob, SigData], Opts);
+
+ {PrivKey, PubKeyBlob} ->
+ Hash = ssh_transport:sha(SigAlg),
+ ssh_transport:sign(SigData, Hash, PrivKey)
+ end,
+
SigBlob = list_to_binary([?string(SigAlgStr),
?binary(Sig)]),
+
ssh_transport:ssh_packet(
- #ssh_msg_userauth_request{user = User,
- service = Service,
- method = "publickey",
- data = [?TRUE,
- ?string(SigAlgStr),
- ?binary(PubKeyBlob),
- ?binary(SigBlob)]},
- Ssh);
- _ ->
- {not_ok, Ssh}
+ #ssh_msg_userauth_request{user = User,
+ service = Service,
+ method = "publickey",
+ data = [?TRUE,
+ ?string(SigAlgStr),
+ ?binary(PubKeyBlob),
+ ?binary(SigBlob)]},
+ Ssh);
+
+ _ ->
+ {not_ok, Ssh}
end.
%%%----------------------------------------------------------------
diff --git a/lib/ssh/src/ssh_client_key_api.erl b/lib/ssh/src/ssh_client_key_api.erl
index 384740b786..3a1a1fbbde 100644
--- a/lib/ssh/src/ssh_client_key_api.erl
+++ b/lib/ssh/src/ssh_client_key_api.erl
@@ -25,11 +25,11 @@
-export_type([client_key_cb_options/0]).
--type client_key_cb_options() :: [{key_cb_private,term()} | ssh:client_option()].
+-type client_key_cb_options() :: [{key_cb_private, term()} | ssh:client_option()].
-callback is_host_key(Key :: public_key:public_key(),
Host :: string(),
- Algorithm :: ssh:pubkey_alg(),
+ Algorithm :: ssh:pubkey_alg(),
Options :: client_key_cb_options()
) ->
boolean().
@@ -37,11 +37,20 @@
-callback user_key(Algorithm :: ssh:pubkey_alg(),
Options :: client_key_cb_options()
) ->
- {ok, PrivateKey :: public_key:private_key()} | {error, string()}.
+ {ok, PrivateKey :: public_key:private_key()} |
+ {ok, {ssh2_pubkey, PubKeyBlob :: binary()}} |
+ {error, string()}.
-callback add_host_key(Host :: string(),
PublicKey :: public_key:public_key(),
Options :: client_key_cb_options()
) ->
- ok | {error, Error::term()}.
+ ok | {error, Error :: term()}.
+
+-callback sign(PubKeyBlob :: binary(),
+ SigData :: binary(),
+ Options :: client_key_cb_options()) ->
+ Blob :: binary().
+
+-optional_callbacks([sign/3]).
diff --git a/lib/ssh/test/Makefile b/lib/ssh/test/Makefile
index ee8480dfdb..aafec6566e 100644
--- a/lib/ssh/test/Makefile
+++ b/lib/ssh/test/Makefile
@@ -39,6 +39,8 @@ MODULES= \
ssh_chan_behaviours_SUITE \
ssh_compat_SUITE \
ssh_connection_SUITE \
+ ssh_agent_mock_server \
+ ssh_agent_SUITE \
ssh_dbg_SUITE \
ssh_engine_SUITE \
ssh_protocol_SUITE \
diff --git a/lib/ssh/test/ssh_agent_SUITE.erl b/lib/ssh/test/ssh_agent_SUITE.erl
new file mode 100644
index 0000000000..f7ac016844
--- /dev/null
+++ b/lib/ssh/test/ssh_agent_SUITE.erl
@@ -0,0 +1,134 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019. All Rights Reserved.
+%%
+%% 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%
+%%
+
+%%
+
+-module(ssh_agent_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+-include_lib("ssh/src/ssh.hrl").
+-include_lib("ssh/src/ssh_agent.hrl").
+-include("ssh_test_lib.hrl").
+
+-compile(export_all).
+
+%% Test configuration
+
+suite() ->
+ [{timetrap, {seconds, 30}}].
+
+all() ->
+ [request_identities, sign_request, connect_with_ssh_agent].
+
+init_per_suite(Config) ->
+ ?CHECK_CRYPTO(
+ begin
+ ok = ssh:start(),
+ ssh_agent_mock_server:check_mktemp(Config)
+ end
+ ).
+
+end_per_suite(_Config) ->
+ ok = ssh:stop().
+
+init_per_testcase(_TestCase, Config) ->
+ Config.
+
+end_per_testcase(_TestCase, _Config) ->
+ ok.
+
+%% Test cases
+
+request_identities() ->
+ [{doc, "Request a list of identities"}].
+
+request_identities(_Config) ->
+ Request = #ssh_agent_identities_request{},
+
+ SocketPath =
+ ssh_agent_mock_server:respond(
+ <<?UINT32(41), % message length
+ ?BYTE(12), % message type (1 byte)
+ ?UINT32(2), % number of keys (4 bytes)
+ ?STRING(<<"key-1">>), % key 1 blob (4 + 5 bytes)
+ ?STRING(<<"lorem">>), % key 1 comment (4 + 5 bytes)
+ ?STRING(<<"key-2">>), % key 2 blob (4 + 5 bytes)
+ ?STRING(<<"ipsum">>) % key 2 comment (4 + 5 bytes)
+ >>
+ ),
+
+ Opts = [{socket_path, SocketPath}],
+ Response = ssh_agent:send(Request, Opts),
+
+ #ssh_agent_identities_response{keys = Keys} = Response,
+
+ [{ssh_agent_key,<<"key-1">>,<<"lorem">>},
+ {ssh_agent_key,<<"key-2">>,<<"ipsum">>}] = Keys,
+
+ ok.
+
+sign_request() ->
+ [{doc, "Request a signature on a binary blob"}].
+
+sign_request(_Config) ->
+ PubKeyBlob = <<"key">>,
+ SigData = <<"data">>,
+
+ SignFlags = ?SSH_AGENT_RSA_SHA2_256 bor ?SSH_AGENT_RSA_SHA2_512,
+ SignRequest = #ssh_agent_sign_request{key_blob = PubKeyBlob, data = SigData, flags = SignFlags},
+
+ SocketPath =
+ ssh_agent_mock_server:respond(
+ <<?UINT32(29), % message length
+ ?BYTE(14), % message type (1 byte)
+ ?STRING(
+ <<?STRING(<<"ssh-rsa">>), % signature format (4 + 7 bytes)
+ ?STRING(<<"signature">>) % signature blob (4 + 9 bytes)
+ >>
+ ) % signature total (4 + 24 bytes)
+ >>
+ ),
+
+ Opts = [{socket_path, SocketPath}],
+ SignResponse = ssh_agent:send(SignRequest, Opts),
+
+ #ssh_agent_sign_response{signature = #ssh_agent_signature{format = Format, blob = Sig}} = SignResponse,
+ Format = <<"ssh-rsa">>,
+ Sig = <<"signature">>,
+
+ ok.
+
+connect_with_ssh_agent() ->
+ [{doc, "Connect with RSA key from SSH agent"}].
+
+connect_with_ssh_agent(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ {ok, SocketPath} = ssh_agent_mock_server:start_link(DataDir),
+ {Pid, Host, Port} = ssh_test_lib:daemon([{system_dir, DataDir},
+ {user_dir, DataDir}]),
+ ConnectionRef = ssh_test_lib:connect(Host, Port, [{user_dir, DataDir},
+ {silently_accept_hosts, true},
+ {user_interaction, false},
+ {auth_methods, "publickey"},
+ {key_cb, {ssh_agent, [{socket_path, SocketPath}]}}
+ ]),
+ ssh:close(ConnectionRef),
+ ssh:stop_daemon(Pid),
+ ssh_agent_mock_server:stop(SocketPath).
diff --git a/lib/ssh/test/ssh_agent_SUITE_data/authorized_keys b/lib/ssh/test/ssh_agent_SUITE_data/authorized_keys
new file mode 100644
index 0000000000..418e1fa64a
--- /dev/null
+++ b/lib/ssh/test/ssh_agent_SUITE_data/authorized_keys
@@ -0,0 +1 @@
+ssh-rsa AAAAB3NzaC1yc2EAAAADAQABAAABAQC2d3XMIA8GTEQcUFCOm31M5jt6lGjN61ZYGnXBVBjEcyJynB7Y3C437cDpjmvbSWF1oSVVDTwMERwnXzixLG//7w8K7i6aJLKpHKtS91qnrQidmrUWDnQ4kx8AZxaN46nhSsf+cZ0nKp03ZjjR5WxeDimiDLsSUbdDmFE6ZsL2+k5OStvcqu/skUVfPe+FGTGJgIw3DyErxM7J72jUkLJXMiZkYbB1QD05k3g2LOiPqJ73QoJVGgj7YagTSA3Lgy3s/6U7IMHMV4lsaXShv1Lk/eCfIJVSaVXQRjV9KKM3wgg6PmWqwGkAO36w3eJiW1kmYKfnAM/+I5Gfo/TiNZTX uabhnil@elxadlj3q32
\ No newline at end of file
diff --git a/lib/ssh/test/ssh_agent_SUITE_data/id_rsa b/lib/ssh/test/ssh_agent_SUITE_data/id_rsa
new file mode 100644
index 0000000000..fa5190c0f2
--- /dev/null
+++ b/lib/ssh/test/ssh_agent_SUITE_data/id_rsa
@@ -0,0 +1,27 @@
+-----BEGIN RSA PRIVATE KEY-----
+MIIEowIBAAKCAQEAtnd1zCAPBkxEHFBQjpt9TOY7epRozetWWBp1wVQYxHMicpwe
+2NwuN+3A6Y5r20lhdaElVQ08DBEcJ184sSxv/+8PCu4umiSyqRyrUvdap60InZq1
+Fg50OJMfAGcWjeOp4UrH/nGdJyqdN2Y40eVsXg4pogy7ElG3Q5hROmbC9vpOTkrb
+3Krv7JFFXz3vhRkxiYCMNw8hK8TOye9o1JCyVzImZGGwdUA9OZN4Nizoj6ie90KC
+VRoI+2GoE0gNy4Mt7P+lOyDBzFeJbGl0ob9S5P3gnyCVUmlV0EY1fSijN8IIOj5l
+qsBpADt+sN3iYltZJmCn5wDP/iORn6P04jWU1wIDAQABAoIBAHlncHw5lGWXVvYT
+xhWshSkmQsrjdfwUqmWCbXkNkFEdXf0tvSSDE0lpKqL7fO3xnCPc7W7ymFJbDAVy
+SNExhO+fyr12DpHG+wykI6XXKH1KFuJuLjCXu2JtGQJ2lL4hjUV2MS0twOdvZh2X
+KRUW9gx6ld7ZY5rjvfD+poUaHHygnN6f0+PiyBpUZaL+ZTj/6CpHiCxdZtOCf0o6
+bU7TaPNcZ3vf3Qhk4jk140vEDLJQnPF8stBqPWa9HfmM7CNjWBdmhQXHtHw8CtF6
+aba9BRC/FMYx43itE9hkg6p3JrSqAN/gZ6RCXLog6mQYttJV+y8oLTXvblT2Y3c9
+YjnigGkCgYEA2Y4+sjsGw3l5HnQ9CNuUQvJZgloVd/NTw8/UXXkV1QudI6tzmMJn
+XAxCCtt2DVlPBqFJ74uwdWpY0nwFJslEp4sV6VPv2TpBmAOPDB6QtQ8SXhFWQ7vj
+BVh5kwl3LUDVI+NIACoaMyZuS6N97Fp4a/mKtgj+ucOkfr15+IF7L/UCgYEA1rXd
+ATBFQlLoPuv3VglU1LLgaLs/3qzoBH9DzwPPyEFdWYQUCuMHsL9eEfDZMsG/GeZb
+Fch/CR0R2Qt+ZlcxcRichgMw3ydzIBqCvLe444lBzxdLWFqS5gCnSh5iage2QRs0
++6QD9O16HJER6HmBwR6DtwpP3N4dHxLXJRjDrhsCgYEAl3/M/UTJkvpWc/SyRCbU
++kHWP0YIST2ziVqDIoydvXyW8y4EE87dN2Z53yGw9d7Jf252FFCMk1d5fypKVBY4
+rwvWOGPxVK6S2w8vYFswnkVenw8nqYd/sktIbjJbQbIyOwmdLDAlipUqnZW+rQbb
+cSWXiOh+qlIpjPDZrUpNxLkCgYAMPjiI7dC1NHcLx3bGECgnLMABGNROhTuBriQW
+tNfvSlLhXNeru0BgArmBemNYMpYMCwecmV8tDNxMrQwbF9O46DdcqOfrgZtd9EUK
+L8u6JcR7448nTZrcxKLFZjAkbaYl1kBSLQsQt03kPR1xTSRp96x5Dnx5Uq0EbZWZ
+Bu15iwKBgAlSiCUqCNir3fdd0wE2+MIczam3YshQmnS3/XEk+7Bmfmb7Rxdwk94l
+P/SaQYZ3buCKoBTz5OveBl4aEdiyvEqBkeJoUbzwFILyo0RNncqULcrYAPIJtbKK
+H0o0naCZUgUJGsX0/DdJsEE27KMljc1A1Fpd3qQ2qqVLFfDTrsuB
+-----END RSA PRIVATE KEY-----
\ No newline at end of file
diff --git a/lib/ssh/test/ssh_agent_SUITE_data/ssh_host_rsa_key b/lib/ssh/test/ssh_agent_SUITE_data/ssh_host_rsa_key
new file mode 100644
index 0000000000..15d2205302
--- /dev/null
+++ b/lib/ssh/test/ssh_agent_SUITE_data/ssh_host_rsa_key
@@ -0,0 +1,27 @@
+-----BEGIN RSA PRIVATE KEY-----
+MIIEogIBAAKCAQEArrzkBUAMYvAso4hR79vmNbxNbLYt7QocukbiCWOq29HQvqbS
+zj/OSE1Qg6C/aTbghvdpvxbaFt3aqdWroF0PhVVoEsJY76bI7RsobIe9zI/Z3dkQ
+RmW3IyjHvpVBwy84fKZ05A8Bd10kca1GfrQXi7LkFZ5FRjxarFzMojGVesWcZLag
+ThPG0QAjSw2sG+oql4YoIeagSdf3tzOOF+04vcpgqCRugsscw17lI1Rwq0nM3thU
+BgSWDRbjzmkWo9i5Wpc9ZKS1z4ANET+I2hGW7PEA6XAXJKC6nIWdVIie0GN02C/m
+i45NyTPn52I/TJKFAtIoZ8fbrHEepX7V/Dt7DQIDAQABAoIBAA1yJY2t3wYh+x1e
+WQe/ARjzc3XBEwmhdJJ07+HPFI+ztn9lMOWEDWiM4nwue2wqN97K3Q1CQefujGvz
+MDC32IDnEIoZAGT4jY+JPnQTgexiyV4D3Pe9zfjbo3sr2xKc6JjW6jm+WduIhExn
+C/yl+QXb7ycmtafw7v1CatC0Rg9bUtE8nMHKYVPazn30wlHdPl6TyTtEXoZCKMg2
+OTxrva80x5JboUqLZXX41VqVmqqoakEO3NOGlhrIzIOB866py8d+f6wilN/rUcGe
+MJwB8aTrYPxLkCYl9PGeMDMLARvhjMm53f6UQFDpL2rY0XpnaqrZqS9KrbJoTQDW
+lMj3OiECgYEA4FL3fba4FYGzf7T/m2xRSC5qrpr0gNn1mZJ5oUWGiHBwjAHC7EVW
+apcjskac7WrznIBJiV2ozzxQOgIymuYO9LX95G6b3nrkWhVXqUiyCkpdMSE/YVfA
+iMc3Z0QNz+I/cbEPUKZ7osKPZm4BRpUNvJwj4Vvt5jXwTZlPmVmpNHUCgYEAx2lx
+q6HO+Grba0Azg7wobnnZ8uZZvdZ+QpxgGhH1Rx9862KM+uVYrJ7xEUlNTYfBtdpq
+JXQnGlpzjGPeziZjJxv7AgWbJA80aXtTH/oE9E0KMmGRzE2bQNR8kUZHU5S2e0u+
+x1DUyvKqyKSRByxUp8wj5QZGPOH4MPvCHVZF+TkCgYAg52qQERYtaWn36Ie5t4iw
+qsZROD93CwGAdkDLDBSwvLV1g+igmYcUeXjt9HeeR5rWMOcYdBmH1FP8PkhH+kjl
+UjCcqjDI0IPgRtMl7JjY85F53GOclq+SII6a4huYi5o8xfj2HoVyGVHJd4dOYBy0
+tr54lvBtXSoTZ9KKLuGn5QKBgBUy4XGkfvMrsO3C4ncTrpyn+YJ3+HxU7BE6vICo
+/hE0iLwhOumFLhsTvn7e8wfV8cLaWERpB6smiHgZOdtie1HyCIobfHWl5CV+hcS1
+eIdcFURr2OsGKQYIUMHE3dpFyexrjfl0X1q/12YDEKPZk5pO+lXjh937C75xVR53
+SHMJAoGAS57QNKLFaWZunoMNuvvNAj7Z0q1JrFuLEwfnkG28g5+ov3wIBinPtlrr
+3HaK6sny0hHLPoRP+fa6BVRaQhDzeeKDu6PqNEkNnocWPi79lxfk531EJQHOgQgX
+yt7Ruq0TlBYs5wGrmtYXLKAGvcfyx9EoFs2Km1iNKqu6b/dbQXc=
+-----END RSA PRIVATE KEY-----
\ No newline at end of file
diff --git a/lib/ssh/test/ssh_agent_mock_server.erl b/lib/ssh/test/ssh_agent_mock_server.erl
new file mode 100644
index 0000000000..9c17e639ab
--- /dev/null
+++ b/lib/ssh/test/ssh_agent_mock_server.erl
@@ -0,0 +1,151 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2005-2018. All Rights Reserved.
+%%
+%% 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%
+%%
+
+%%
+
+%%% Description: ssh-agent mock
+-module(ssh_agent_mock_server).
+
+-behaviour(gen_server).
+
+-include_lib("ssh/src/ssh.hrl").
+-include_lib("ssh/src/ssh_agent.hrl").
+
+-export([respond/1, check_mktemp/1]).
+-export([start_link/1, stop/1]).
+-export([init/1, handle_info/2, handle_cast/2, handle_call/3, terminate/2]).
+
+-record(state, {socket, priv_key, pub_key, socket_path}).
+
+-define(SIG_ALG, 'ssh-rsa').
+
+start_link(PrivKeyDir) ->
+ {ok, PrivKey} =ssh_file:user_key(?SIG_ALG, [{user_dir, PrivKeyDir}]),
+
+ %% We cannot use priv_dir because unix socket paths are limited to 108 bytes.
+ SocketPath = string:chomp(os:cmd("mktemp -u")),
+ PubKey = extract_pubkey(PrivKey),
+
+ InitialState = #state{socket_path=SocketPath, priv_key=PrivKey, pub_key=PubKey},
+ {ok, _} = gen_server:start_link(?MODULE, InitialState, []),
+ {ok, SocketPath}.
+
+stop(SocketPath) ->
+ ConnectOpts = [binary, {packet, 0}, {active, false}],
+ {ok, Socket} = gen_tcp:connect({local, SocketPath}, 0, ConnectOpts, 1000),
+ ok = gen_tcp:send(Socket, <<0>>),
+ ok = gen_tcp:close(Socket).
+
+init(InitialState = #state{socket_path=SocketPath}) ->
+ Address = {local, SocketPath},
+ ConnectOpts = [local, binary, {ip, Address}, {packet, 0}],
+
+ {ok, Socket} = gen_tcp:listen(0, ConnectOpts),
+ gen_server:cast(self(), accept),
+ {ok, InitialState#state{socket=Socket}}.
+
+handle_cast(accept, State = #state{socket=Socket}) ->
+ {ok, _} = gen_tcp:accept(Socket),
+ {noreply, State};
+
+handle_cast(_, State) ->
+ {noreply, State}.
+
+handle_call(_E, _From, State) -> {noreply, State}.
+
+handle_info({tcp, Socket, <<Len:32/unsigned-big-integer, Data:Len/binary>>}, State) ->
+ Response = handle_request(Data, State),
+ ok = gen_tcp:send(Socket, Response),
+ {noreply, State};
+
+handle_info({tcp, _, <<0>>}, State) ->
+ {stop, normal, State};
+
+handle_info({tcp_closed, _Socket}, State) ->
+ gen_server:cast(self(), accept),
+ {noreply, State}.
+
+handle_request(<<11>>, #state{pub_key=PubKey}) ->
+ %% REQUEST_IDENTITIES
+ PubKeyLen = byte_size(PubKey),
+ <<?UINT32(18 + PubKeyLen), % message length
+ ?BYTE(12), % message type (1 byte)
+ ?UINT32(1), % number of keys (4 bytes)
+ ?STRING(PubKey), % PubKey (4 + PubKeyLen bytes)
+ ?STRING(<<"lorem">>) % key 1 comment (4 + 5 bytes)
+ >>;
+
+handle_request(<<13, Rest/binary>>, #state{priv_key=PrivKey, pub_key=PubKey}) ->
+ Flags = ?SSH_AGENT_RSA_SHA2_256 bor ?SSH_AGENT_RSA_SHA2_512,
+ <<?DEC_BIN(PubKey, _KeyBlobLen), ?DEC_BIN(Data, _DataLen), ?Euint32(Flags)>> = Rest,
+
+ Hash = ssh_transport:sha(?SIG_ALG),
+ Sig = ssh_transport:sign(Data, Hash, PrivKey),
+ SigLen = byte_size(Sig),
+ <<?UINT32(20 + SigLen), % message length
+ ?BYTE(14), % message type (1 byte)
+ ?STRING( % nested string (4 bytes)
+ <<?STRING(<<"ssh-rsa">>), % signature format (4 + 7 bytes)
+ ?STRING(Sig) % signature blob (4 + SigLen bytes)
+ >>
+ )
+ >>.
+
+terminate(_Reason, #state{socket_path=SocketPath, socket=Socket}) ->
+ ok = gen_tcp:close(Socket),
+ ok = file:delete(SocketPath).
+
+respond(BinResponse) ->
+ %% We cannot use priv_dir because unix socket paths are limited to 108 bytes.
+ SocketPath = string:chomp(os:cmd("mktemp -u")),
+
+ Parent = self(),
+
+ spawn(fun() ->
+ Address = {local, SocketPath},
+ ConnectOpts = [local, binary, {ip, Address}, {packet, 0}, {active, false}],
+
+ {ok, ListenSocket} = gen_tcp:listen(0, ConnectOpts),
+ Parent ! listening,
+
+ {ok, Socket} = gen_tcp:accept(ListenSocket),
+ {ok, _BinRequest} = gen_tcp:recv(Socket, 0),
+
+ ok = gen_tcp:send(Socket, BinResponse),
+ ok = gen_tcp:close(Socket),
+ ok = gen_tcp:close(ListenSocket),
+ ok = file:delete(SocketPath)
+ end),
+
+ receive
+ listening -> SocketPath
+ end.
+
+check_mktemp(Config) ->
+ case os:find_executable("mktemp") of
+ false ->
+ {skip, "Can't find mktemp in your $PATH"};
+ _ ->
+ Config
+ end.
+
+extract_pubkey(PrivKey) ->
+ PubKey = ssh_transport:extract_public_key(PrivKey),
+ ssh_message:ssh2_pubkey_encode(PubKey).
--
2.16.4