~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_transport.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
 
 
19
%%% Description: SSH transport protocol
 
20
 
 
21
-module(ssh_transport).
 
22
 
 
23
-import(lists, [reverse/1, map/2, foreach/2, foldl/3]).
 
24
 
 
25
-include("ssh.hrl").
 
26
-include_lib("kernel/include/inet.hrl").
 
27
 
 
28
-export([connect/1, connect/2, connect/3, close/1]).
 
29
-export([listen/2, listen/3, listen/4, stop_listener/1]).
 
30
-export([debug/2, debug/3, debug/4]).
 
31
-export([ignore/2]).
 
32
-export([disconnect/2, disconnect/3, disconnect/4]).
 
33
 
 
34
-export([client_init/4, server_init/4]).
 
35
 
 
36
-export([ssh_init/3]). % , server_hello/4]).
 
37
 
 
38
-export([service_request/2, service_accept/2]).
 
39
 
 
40
-export([get_session_id/1]).
 
41
-export([peername/1]).
 
42
 
 
43
%% io wrappers
 
44
-export([yes_no/2, read_password/2]).
 
45
 
 
46
 
 
47
-define(DEFAULT_TIMEOUT, 5000).
 
48
 
 
49
%% debug flags
 
50
-define(DBG_ALG,     true).
 
51
-define(DBG_KEX,     false).
 
52
-define(DBG_CRYPTO,  false).
 
53
-define(DBG_PACKET,  false).
 
54
-define(DBG_MESSAGE, true).
 
55
-define(DBG_BIN_MESSAGE, false).
 
56
-define(DBG_MAC,     false).
 
57
-define(DBG_ZLIB,    true).
 
58
 
 
59
-record(alg,
 
60
        {
 
61
          kex,
 
62
          hkey,
 
63
          send_mac,
 
64
          recv_mac,
 
65
          encrypt,
 
66
          decrypt,
 
67
          compress,
 
68
          decompress,
 
69
          c_lng,
 
70
          s_lng
 
71
         }).
 
72
          
 
73
-record(ssh,
 
74
        {
 
75
          state,        %% what it's waiting for
 
76
 
 
77
          role,         %% client | server
 
78
          peer,         %% string version of peer address 
 
79
 
 
80
          c_vsn,        %% client version {Major,Minor}
 
81
          s_vsn,        %% server version {Major,Minor}
 
82
 
 
83
          c_version,    %% client version string
 
84
          s_version,    %% server version string
 
85
 
 
86
          c_keyinit,    %% binary payload of kexinit packet
 
87
          s_keyinit,    %% binary payload of kexinit packet
 
88
 
 
89
          algorithms,   %% new algorithms (SSH_MSG_KEXINIT)
 
90
          
 
91
          kex,          %% key exchange algorithm
 
92
          hkey,         %% host key algorithm
 
93
          key_cb,       %% Private/Public key callback module
 
94
          io_cb,        %% Interaction callback module
 
95
 
 
96
          send_mac=none, %% send MAC algorithm
 
97
          send_mac_key,  %% key used in send MAC algorithm
 
98
          send_mac_size = 0,
 
99
 
 
100
          recv_mac=none, %% recv MAC algorithm
 
101
          recv_mac_key,  %% key used in recv MAC algorithm
 
102
          recv_mac_size = 0,
 
103
 
 
104
          encrypt = none,       %% encrypt algorithm
 
105
          encrypt_keys,         %% encrypt keys
 
106
          encrypt_block_size = 8,
 
107
 
 
108
          decrypt = none,       %% decrypt algorithm
 
109
          decrypt_keys,         %% decrypt keys
 
110
          decrypt_block_size = 8,
 
111
 
 
112
          compress = none,
 
113
          decompress = none,
 
114
 
 
115
          c_lng=none,   %% client to server languages
 
116
          s_lng=none,   %% server to client languages
 
117
 
 
118
          user_ack    = true,   %% client
 
119
          timeout     = infinity,
 
120
 
 
121
          shared_secret,        %% K from key exchange
 
122
          exchanged_hash,       %% H from key exchange
 
123
          session_id,           %% same as FIRST exchanged_hash
 
124
          
 
125
          opts = []
 
126
         }).
 
127
 
 
128
 
 
129
transport_messages()                                                     ->
 
130
    [ {ssh_msg_disconnect, ?SSH_MSG_DISCONNECT, 
 
131
       [uint32,string,string]},
 
132
      
 
133
      {ssh_msg_ignore, ?SSH_MSG_IGNORE,
 
134
       [string]},
 
135
 
 
136
      {ssh_msg_unimplemented, ?SSH_MSG_UNIMPLEMENTED,
 
137
       [uint32]},
 
138
 
 
139
      {ssh_msg_debug, ?SSH_MSG_DEBUG,
 
140
       [boolean, string, string]},
 
141
 
 
142
      {ssh_msg_service_request, ?SSH_MSG_SERVICE_REQUEST,
 
143
       [string]},
 
144
 
 
145
      {ssh_msg_service_accept, ?SSH_MSG_SERVICE_ACCEPT,
 
146
       [string]},
 
147
 
 
148
      {ssh_msg_kexinit, ?SSH_MSG_KEXINIT,
 
149
       [cookie,
 
150
        name_list, name_list, 
 
151
        name_list, name_list, 
 
152
        name_list, name_list,
 
153
        name_list, name_list,
 
154
        name_list, name_list,
 
155
        boolean, 
 
156
        uint32]},
 
157
 
 
158
      {ssh_msg_newkeys, ?SSH_MSG_NEWKEYS,
 
159
       []}
 
160
     ].
 
161
 
 
162
 
 
163
kexdh_messages()                                                         ->
 
164
    [ {ssh_msg_kexdh_init, ?SSH_MSG_KEXDH_INIT,
 
165
       [mpint]},
 
166
      
 
167
      {ssh_msg_kexdh_reply, ?SSH_MSG_KEXDH_REPLY,
 
168
       [binary, mpint, binary]}
 
169
     ].
 
170
 
 
171
 
 
172
kex_dh_gex_messages()                                                    ->
 
173
    [ {ssh_msg_kex_dh_gex_request, ?SSH_MSG_KEX_DH_GEX_REQUEST,
 
174
       [uint32, uint32, uint32]},
 
175
 
 
176
      {ssh_msg_kex_dh_gex_request_old, ?SSH_MSG_KEX_DH_GEX_REQUEST_OLD,
 
177
       [uint32]},
 
178
      
 
179
      {ssh_msg_kex_dh_gex_group, ?SSH_MSG_KEX_DH_GEX_GROUP,
 
180
       [mpint, mpint]},
 
181
 
 
182
      {ssh_msg_kex_dh_gex_init, ?SSH_MSG_KEX_DH_GEX_INIT,
 
183
       [mpint]},
 
184
      
 
185
      {ssh_msg_kex_dh_gex_reply, ?SSH_MSG_KEX_DH_GEX_REPLY,
 
186
       [binary, mpint, binary]}
 
187
     ].
 
188
 
 
189
yes_no(SSH, Prompt) when pid(SSH)                                        ->
 
190
    {ok, CB} = call(SSH, {get_cb, io}),
 
191
    CB:yes_no(Prompt);
 
192
yes_no(SSH, Prompt) when record(SSH,ssh)                                 ->
 
193
    (SSH#ssh.io_cb):yes_no(Prompt).
 
194
 
 
195
read_password(SSH, Prompt) when pid(SSH)                                 ->
 
196
    {ok, CB} = call(SSH, {get_cb, io}),
 
197
    CB:read_password(Prompt);
 
198
read_password(SSH, Prompt) when record(SSH,ssh)                          ->
 
199
    (SSH#ssh.io_cb):read_password(Prompt).
 
200
 
 
201
%% read_line(SSH, Prompt) when pid(SSH) ->
 
202
%%     {ok, CB} = call(SSH, {get_cb, io}),
 
203
%%     CB:read_line(Prompt);
 
204
%% read_line(SSH, Prompt) when record(SSH,ssh) ->
 
205
%%     (SSH#ssh.io_cb):read_line(Prompt).
 
206
 
 
207
peername(SSH) ->
 
208
    call(SSH, peername).
 
209
 
 
210
call(SSH, Req)                                                           ->
 
211
    Ref = make_ref(),
 
212
    SSH ! {ssh_call, [self()|Ref], Req},
 
213
    receive
 
214
        {Ref, Reply} ->
 
215
            Reply
 
216
    end.
 
217
 
 
218
connect(Host)                                                            ->
 
219
    connect(Host, []).
 
220
 
 
221
connect(Host, Opts)                                                      ->
 
222
    connect(Host, 22, Opts).
 
223
 
 
224
connect(Host,Port,Opts)                                                  ->
 
225
    Pid = spawn_link(?MODULE, client_init, [self(), Host, Port, Opts]),
 
226
    receive
 
227
        {Pid, Reply} ->
 
228
            Reply
 
229
    end.
 
230
 
 
231
listen(UserFun, Port) ->
 
232
    listen(UserFun, Port, []).
 
233
 
 
234
listen(UserFun, Port, Opts) ->
 
235
    listen(UserFun, any, Port, Opts).
 
236
 
 
237
listen(UserFun, Addr, Port, Opts) ->
 
238
    case spawn_link(?MODULE, server_init, [UserFun, Addr, Port, Opts]) of
 
239
        Pid when is_pid(Pid) -> {ok, Pid};
 
240
        Error -> Error
 
241
    end.
 
242
 
 
243
stop_listener(Pid) when is_pid(Pid) ->
 
244
    Ref = erlang:monitor(process, Pid),
 
245
    Pid ! {Pid, stop},
 
246
    receive
 
247
        {'DOWN', Ref, process, Pid, normal} ->
 
248
            ok;
 
249
        {'DOWN', Ref, process, Pid, Error} ->
 
250
            {error, Error}
 
251
    after 2000 ->
 
252
            {error, timeout}
 
253
    end.            
 
254
 
 
255
debug(SSH, Message) ->
 
256
    debug(SSH, true, Message, "en").
 
257
 
 
258
debug(SSH, Message, Lang) ->
 
259
    debug(SSH, true, Message, Lang).
 
260
 
 
261
debug(SSH, Display, Message, Lang) ->
 
262
    SSH ! {ssh_msg, self(), #ssh_msg_debug { always_display = Display,
 
263
                                             message = Message,
 
264
                                             language = Lang }}.
 
265
 
 
266
ignore(SSH, Data) ->
 
267
    SSH ! {ssh_msg, self(), #ssh_msg_ignore { data = Data }}.
 
268
 
 
269
disconnect(SSH, Code) ->
 
270
    disconnect(SSH, Code, "", "").
 
271
 
 
272
disconnect(SSH, Code, _Msg) ->
 
273
    disconnect(SSH, Code, "", "").
 
274
 
 
275
disconnect(SSH, Code, Msg, Lang) ->
 
276
    SSH ! {ssh_msg, self(), #ssh_msg_disconnect { code = Code,
 
277
                                                  description = Msg,
 
278
                                                  language = Lang }}.
 
279
 
 
280
close(SSH) ->
 
281
    call(SSH, close).
 
282
 
 
283
 
 
284
service_accept(SSH, Name)                                                ->
 
285
    SSH ! {ssh_msg, self(), #ssh_msg_service_accept { name = Name }}.
 
286
 
 
287
service_request(SSH, Name)                                               ->
 
288
    SSH ! {ssh_msg, self(), #ssh_msg_service_request { name = Name}},
 
289
    receive
 
290
        {ssh_msg, SSH, R} when record(R, ssh_msg_service_accept) ->
 
291
            ok;
 
292
        {ssh_msg, SSH, R} when record(R, ssh_msg_disconnect) ->
 
293
            {error, R};
 
294
        Other ->
 
295
            {error, Other}
 
296
    end.    
 
297
    
 
298
    
 
299
client_init(User, Host, Port, Opts) ->
 
300
    IfAddr = proplists:get_value(ifaddr, Opts, any),
 
301
    Tmo    = proplists:get_value(connect_timeout, Opts, ?DEFAULT_TIMEOUT),
 
302
    NoDelay= proplists:get_value(tcp_nodelay, Opts, false),
 
303
    case gen_tcp:connect(Host, Port, [{packet,line},
 
304
                                      {active,once},
 
305
                                      {nodelay, NoDelay},
 
306
                                      {ifaddr,IfAddr}], Tmo) of
 
307
        {ok, S} ->
 
308
            SSH = ssh_init(S, client, Opts),
 
309
            Peer = if tuple(Host) -> inet_parse:ntoa(Host);
 
310
                      atom(Host) -> atom_to_list(Host);
 
311
                      list(Host) -> Host
 
312
                   end,
 
313
            case client_hello(S, User, SSH#ssh { peer = Peer }, Tmo) of
 
314
                {error, E} ->
 
315
                    User ! {self(), {error, E}};
 
316
                _ ->
 
317
                    ok
 
318
            end;
 
319
        Error ->
 
320
            User ! {self(), Error}
 
321
    end.
 
322
 
 
323
 
 
324
server_init(UserFun, Addr, Port, Opts) ->
 
325
    Serv = fun(S) ->
 
326
                   SSH = ssh_init(S, server, Opts),
 
327
                   Self = self(),
 
328
                   User = UserFun(Self),
 
329
                   server_hello(S, User, SSH,
 
330
                                proplists:get_value(timeout, Opts,
 
331
                                                    ?DEFAULT_TIMEOUT))
 
332
           end,
 
333
    NoDelay = proplists:get_value(tcp_nodelay, Opts, false),
 
334
    ssh_tcp_wrap:server(Port, [{packet,line}, {active,once},
 
335
                               {ifaddr,Addr}, {reuseaddr,true},
 
336
                               {nodelay, NoDelay}],
 
337
                        Serv).
 
338
 
 
339
%%
 
340
%% Initialize basic ssh system
 
341
%%
 
342
ssh_init(S, Role, Opts) ->
 
343
    ssh_bits:install_messages(transport_messages()),
 
344
    {A,B,C} = erlang:now(),
 
345
    random:seed(A, B, C),
 
346
    put(send_sequence, 0),
 
347
    put(recv_sequence, 0),
 
348
    case Role of
 
349
        client ->
 
350
            Vsn = proplists:get_value(vsn, Opts, {2,0}),
 
351
            Version = format_version(Vsn),
 
352
            send_version(S, Version),
 
353
            #ssh { role = Role,
 
354
                   c_vsn = Vsn,
 
355
                   c_version=Version,
 
356
                   key_cb = proplists:get_value(key_cb, Opts, ssh_file),
 
357
                   io_cb = case proplists:get_value(user_interaction, Opts, true) of
 
358
                               true -> ssh_io;
 
359
                               false -> ssh_no_io
 
360
                           end,
 
361
                   opts = Opts };
 
362
        server  ->
 
363
            Vsn = proplists:get_value(vsn, Opts, {1,99}),
 
364
            Version = format_version(Vsn),
 
365
            send_version(S, Version),
 
366
            #ssh { role = Role,
 
367
                   s_vsn = Vsn,
 
368
                   s_version=Version,
 
369
                   key_cb = proplists:get_value(key_cb, Opts, ssh_file),
 
370
                   io_cb = proplists:get_value(io_cb, Opts, ssh_io),
 
371
                   opts = Opts  }
 
372
    end.
 
373
 
 
374
ssh_setopts(NewOpts, SSH) ->
 
375
    Opts = SSH#ssh.opts,
 
376
    SSH#ssh { opts = NewOpts ++ Opts }.
 
377
 
 
378
format_version({Major,Minor})                                            ->
 
379
    "SSH-"++integer_to_list(Major)++"."++integer_to_list(Minor)++"-Erlang".
 
380
    
 
381
 
 
382
%% choose algorithms
 
383
kex_init(SSH)                                                            ->
 
384
    Random = ssh_bits:random(16),
 
385
    Comp = case proplists:get_value(compression, SSH#ssh.opts, none) of
 
386
               zlib -> ["zlib", "none"];
 
387
               none -> ["none", "zlib"]
 
388
           end,
 
389
    case SSH#ssh.role of
 
390
        client ->
 
391
            #ssh_msg_kexinit { 
 
392
          cookie = Random,
 
393
          kex_algorithms = ["diffie-hellman-group1-sha1"],
 
394
          server_host_key_algorithms = ["ssh-rsa", "ssh-dss"],
 
395
          encryption_algorithms_client_to_server = ["3des-cbc"],
 
396
          encryption_algorithms_server_to_client = ["3des-cbc"],
 
397
          mac_algorithms_client_to_server = ["hmac-sha1"],
 
398
          mac_algorithms_server_to_client = ["hmac-sha1"],
 
399
          compression_algorithms_client_to_server = Comp,
 
400
          compression_algorithms_server_to_client = Comp,
 
401
          languages_client_to_server = [],
 
402
          languages_server_to_client = []
 
403
         };
 
404
        server ->
 
405
            #ssh_msg_kexinit {
 
406
          cookie = Random,
 
407
          kex_algorithms = ["diffie-hellman-group1-sha1"],
 
408
          server_host_key_algorithms = ["ssh-dss"],
 
409
          encryption_algorithms_client_to_server = ["3des-cbc"],
 
410
          encryption_algorithms_server_to_client = ["3des-cbc"],
 
411
          mac_algorithms_client_to_server = ["hmac-sha1"],
 
412
          mac_algorithms_server_to_client = ["hmac-sha1"],
 
413
          compression_algorithms_client_to_server = Comp,
 
414
          compression_algorithms_server_to_client = Comp,
 
415
          languages_client_to_server = [],
 
416
          languages_server_to_client = []
 
417
         }
 
418
    end.
 
419
 
 
420
 
 
421
server_hello(S, User, SSH, Timeout) ->
 
422
    receive
 
423
        {tcp, S, V = "SSH-"++_} ->
 
424
            Version = trim_tail(V),
 
425
            ?dbg(true, "client version: ~p\n",[Version]),
 
426
            case string:tokens(Version, "-") of
 
427
                [_, "2.0" | _] ->
 
428
                    negotiate(S, User, SSH#ssh { c_vsn = {2,0},
 
429
                                                 c_version = Version}, false);
 
430
                [_, "1.99" | _] ->
 
431
                    negotiate(S, User, SSH#ssh { c_vsn = {2,0},
 
432
                                                 c_version = Version}, false);
 
433
                [_, "1.3" | _] ->
 
434
                    negotiate(S, User, SSH#ssh { c_vsn = {1,3}, 
 
435
                                                 c_version = Version}, false);
 
436
                [_, "1.5" | _] ->
 
437
                    negotiate(S, User, SSH#ssh { c_vsn = {1,5}, 
 
438
                                                 c_version = Version}, false);
 
439
                _ ->
 
440
                    exit(unknown_version)
 
441
            end;
 
442
        {tcp, S, _Line} ->
 
443
            ?dbg(true, "info: ~p\n", [_Line]),
 
444
            inet:setopts(S, [{active, once}]),
 
445
            server_hello(S, User, SSH, Timeout)
 
446
    after Timeout ->
 
447
            ?dbg(true, "server_hello timeout ~p\n", [Timeout]),
 
448
            gen_tcp:close(S),
 
449
            {error, timeout}
 
450
    end.
 
451
 
 
452
client_hello(S, User, SSH, Timeout) ->
 
453
    receive
 
454
        {tcp, S, V = "SSH-"++_} ->
 
455
            Version = trim_tail(V),
 
456
            ?dbg(true, "server version: ~p\n",[Version]),
 
457
            case string:tokens(Version, "-") of
 
458
                [_, "2.0" | _] ->
 
459
                    negotiate(S, User, SSH#ssh { s_vsn = {2,0},
 
460
                                                 s_version = Version }, true);
 
461
                [_, "1.99" | _] -> %% compatible server
 
462
                    negotiate(S, User, SSH#ssh { s_vsn = {2,0}, 
 
463
                                                 s_version = Version }, true);
 
464
                [_, "1.3" | _] ->
 
465
                    negotiate(S, User, SSH#ssh { s_vsn = {1,3}, 
 
466
                                                 s_version = Version }, true);
 
467
                [_, "1.5" | _] ->
 
468
                    negotiate(S, User, SSH#ssh { s_vsn = {1,5}, 
 
469
                                                 s_version = Version }, true);
 
470
                _ ->
 
471
                    exit(unknown_version)
 
472
            end;
 
473
        {tcp, S, _Line} ->
 
474
            ?dbg(true, "info: ~p\n", [_Line]),
 
475
            inet:setopts(S, [{active, once}]),
 
476
            client_hello(S, User, SSH, Timeout);
 
477
        {tcp_error, S, Reason} ->
 
478
            ?dbg(true, "client_hello got tcp error ~p\n", [Reason]),
 
479
            {error, {tcp_error, Reason}};
 
480
        {tcp_closed, S} ->
 
481
            ?dbg(true, "client_hello: tcp_closed\n", []),
 
482
            {error, tcp_closed};
 
483
        Other ->
 
484
            io:format("Other ~p\n", [Other])
 
485
    after Timeout ->
 
486
            ?dbg(true, "client_hello timeout ~p\n", [Timeout]),
 
487
            gen_tcp:close(S),
 
488
            {error, timeout}
 
489
    end.
 
490
 
 
491
%% Determine the version and algorithms
 
492
negotiate(S, User, SSH, UserAck) ->
 
493
    inet:setopts(S, [{packet,0},{mode,binary}]),
 
494
    send_negotiate(S, User, SSH, UserAck).
 
495
 
 
496
%% We start re-negotiate
 
497
send_negotiate(S, User, SSH, UserAck) ->
 
498
    SendAlg = kex_init(SSH),
 
499
    {ok, SendPdu} = send_algorithms(S, SSH, SendAlg),
 
500
    {ok, {RecvPdu,RecvAlg}} = recv_algorithms(S, SSH),
 
501
    kex_negotiate(S, User, SSH, UserAck, SendAlg, SendPdu, RecvAlg, RecvPdu).
 
502
 
 
503
%% Other side started re-negotiate
 
504
recv_negotiate(S, User, SSH, RecvAlg, UserAck)                           ->
 
505
    RecvPdu = ssh_bits:encode(RecvAlg),
 
506
    SendAlg = kex_init(SSH),
 
507
    {ok, SendPdu} = send_algorithms(S, SSH, SendAlg),
 
508
    send_msg(S, SSH, SendAlg),
 
509
    kex_negotiate(S, User, SSH, UserAck, SendAlg, SendPdu, RecvAlg, RecvPdu).
 
510
 
 
511
%% Select algorithms
 
512
kex_negotiate(S, User, SSH, UserAck, SendAlg, SendPdu, RecvAlg, RecvPdu) ->
 
513
    case SSH#ssh.role of
 
514
        client ->
 
515
            SSH1 = SSH#ssh { c_keyinit = SendPdu, s_keyinit = RecvPdu },
 
516
            case select_algorithm(SSH1, #alg {}, SendAlg, RecvAlg) of
 
517
                {ok, SSH2} ->
 
518
                    ALG = SSH2#ssh.algorithms,
 
519
                    case client_kex(S, SSH2, ALG#alg.kex) of
 
520
                        {ok, SSH3} ->
 
521
                            newkeys(S, User, SSH3, UserAck);
 
522
                        Error ->
 
523
                            kexfailed(S, User, UserAck, Error)
 
524
                    end;
 
525
                Error ->
 
526
                    kexfailed(S, User, UserAck, Error)
 
527
            end;
 
528
 
 
529
        server ->
 
530
            SSH1 = SSH#ssh { c_keyinit = RecvPdu, s_keyinit = SendPdu }, 
 
531
            case select_algorithm(SSH1, #alg {}, RecvAlg, SendAlg) of
 
532
                {ok,SSH2} ->
 
533
                    ALG = SSH2#ssh.algorithms,
 
534
                    case server_kex(S, SSH2, ALG#alg.kex) of
 
535
                        {ok, SSH3} ->
 
536
                            newkeys(S, User, SSH3, UserAck);
 
537
                        Error ->
 
538
                            kexfailed(S, User, UserAck, Error)
 
539
                    end;
 
540
                Error ->
 
541
                    kexfailed(S, User, UserAck, Error)
 
542
            end
 
543
    end.
 
544
    
 
545
newkeys(S, User, SSH, UserAck)                                           ->
 
546
    %% Send new keys and wait for newkeys
 
547
    send_msg(S, SSH, #ssh_msg_newkeys {}),
 
548
    case recv_msg(S, SSH) of
 
549
        {ok, M} when record(M, ssh_msg_newkeys) ->
 
550
            SSH1 = install_alg(SSH),
 
551
            if UserAck == true ->
 
552
                    User ! {self(), {ok, self()}},
 
553
                    inet:setopts(S, [{active, once}]),
 
554
                    ssh_main(S, User, SSH1);
 
555
               true ->
 
556
                    inet:setopts(S, [{active, once}]),
 
557
                    ssh_main(S, User, SSH1)
 
558
            end;
 
559
        {ok,_} ->
 
560
            {error, bad_message};
 
561
        Error ->
 
562
            Error
 
563
    end.
 
564
 
 
565
 
 
566
 
 
567
client_kex(S, SSH, 'diffie-hellman-group1-sha1')                         ->
 
568
    ssh_bits:install_messages(kexdh_messages()),
 
569
    {G,P} = dh_group1(),
 
570
    {Private, Public} = dh_gen_key(G,P,1024),
 
571
    ?dbg(?DBG_KEX, "public: ~.16B\n", [Public]),
 
572
    send_msg(S, SSH, #ssh_msg_kexdh_init { e = Public }),
 
573
    case recv_msg(S, SSH) of
 
574
        {ok, R} when record(R, ssh_msg_kexdh_reply) ->
 
575
            K_S = R#ssh_msg_kexdh_reply.public_host_key,
 
576
            F = R#ssh_msg_kexdh_reply.f,
 
577
            K = ssh_math:ipow(F, Private, P),
 
578
            H = kex_h(SSH, K_S, Public, F, K),
 
579
            H_SIG = R#ssh_msg_kexdh_reply.h_sig,
 
580
            ?dbg(?DBG_KEX, "shared_secret: ~s\n", [fmt_binary(K, 16, 4)]),
 
581
            ?dbg(?DBG_KEX, "hash: ~s\n", [fmt_binary(H, 16, 4)]),
 
582
            case verify_host_key(S, SSH, K_S, H, H_SIG) of
 
583
                ok ->
 
584
                    {ok, SSH#ssh { shared_secret  = K,
 
585
                                   exchanged_hash = H,
 
586
                                   session_id = H }};
 
587
                Error ->
 
588
                    Error
 
589
            end;
 
590
        {ok,_} ->
 
591
            {error, bad_message};
 
592
        Error ->
 
593
            Error
 
594
    end;
 
595
client_kex(S, SSH, 'diffie-hellman-group-exchange-sha1')                 ->
 
596
    ssh_bits:install_messages(kex_dh_gex_messages()),
 
597
    Min = 512,
 
598
    NBits = 1024,
 
599
    Max = 4096,
 
600
    send_msg(S, SSH, #ssh_msg_kex_dh_gex_request { min = Min,
 
601
                                                   n   = NBits,
 
602
                                                   max = Max }),
 
603
    case recv_msg(S, SSH) of
 
604
        {ok, RG} when record(RG, ssh_msg_kex_dh_gex_group) ->
 
605
            P = RG#ssh_msg_kex_dh_gex_group.p,
 
606
            G = RG#ssh_msg_kex_dh_gex_group.g,
 
607
            {Private, Public} = dh_gen_key(G,P, 1024),
 
608
            ?dbg(?DBG_KEX, "public: ~.16B\n", [Public]),
 
609
            send_msg(S, SSH, #ssh_msg_kex_dh_gex_init { e = Public }),
 
610
            case recv_msg(S, SSH) of
 
611
                {ok, R} when record(R, ssh_msg_kex_dh_gex_reply) ->
 
612
                    K_S = R#ssh_msg_kex_dh_gex_reply.public_host_key,
 
613
                    F = R#ssh_msg_kex_dh_gex_reply.f,
 
614
                    K = ssh_math:ipow(F, Private, P),
 
615
                    H = kex_h(SSH, K_S, Min, NBits, Max, P, G, Public, F, K),
 
616
                    H_SIG = R#ssh_msg_kex_dh_gex_reply.h_sig,
 
617
                    ?dbg(?DBG_KEX, "shared_secret: ~s\n",
 
618
                         [fmt_binary(K, 16, 4)]),
 
619
                    ?dbg(?DBG_KEX, "hash: ~s\n", 
 
620
                         [fmt_binary(H, 16, 4)]),
 
621
                    case verify_host_key(S, SSH, K_S, H, H_SIG) of
 
622
                        ok ->
 
623
                            {ok,  SSH#ssh { shared_secret  = K,
 
624
                                            exchanged_hash = H,
 
625
                                            session_id = H }};
 
626
                        Error ->
 
627
                            Error
 
628
                    end;
 
629
                {ok,_} ->
 
630
                    {error, bad_message};
 
631
                Error ->
 
632
                    Error
 
633
            end;
 
634
        {ok,_} ->
 
635
            {error, bad_message};
 
636
        Error ->
 
637
            Error
 
638
    end;
 
639
client_kex(_S, _SSH, Kex)                                                ->
 
640
    {error, {bad_kex_algorithm, Kex}}.
 
641
 
 
642
 
 
643
server_kex(S, SSH, 'diffie-hellman-group1-sha1')                         ->
 
644
    ssh_bits:install_messages(kexdh_messages()),
 
645
    {G,P} = dh_group1(),
 
646
    {Private, Public} = dh_gen_key(G,P,1024),
 
647
    ?dbg(?DBG_KEX, "public: ~.16B\n", [Public]),
 
648
    case recv_msg(S, SSH) of
 
649
        {ok, R} when record(R, ssh_msg_kexdh_init) ->
 
650
            E = R#ssh_msg_kexdh_init.e,
 
651
            K = ssh_math:ipow(E, Private, P),
 
652
            {Key,K_S} = get_host_key(SSH),
 
653
            H = kex_h(SSH, K_S, E, Public, K),
 
654
            H_SIG = sign_host_key(S, SSH, Key, H),
 
655
            send_msg(S, SSH,
 
656
                     #ssh_msg_kexdh_reply { public_host_key = K_S,
 
657
                                            f = Public,
 
658
                                            h_sig = H_SIG
 
659
                                           }),
 
660
            ?dbg(?DBG_KEX, "shared_secret: ~s\n", [fmt_binary(K, 16, 4)]),
 
661
            ?dbg(?DBG_KEX, "hash: ~s\n", [fmt_binary(H, 16, 4)]),
 
662
            {ok, SSH#ssh { shared_secret = K,
 
663
                           exchanged_hash = H,
 
664
                           session_id = H }};
 
665
        {ok,_} ->
 
666
            {error, bad_message};
 
667
        Error ->
 
668
            Error
 
669
    end;
 
670
server_kex(S, SSH, 'diffie-hellman-group-exchange-sha1')                 ->
 
671
    ssh_bits:install_messages(kex_dh_gex_messages()),
 
672
    R0 = recv_msg(S, SSH),
 
673
    #ssh_msg_kex_dh_gex_request { min = Min,
 
674
                                  n   = NBits,
 
675
                                  max = Max } = R0,
 
676
    {G,P} = dh_group1(), %% FIX ME!!!
 
677
    send_msg(S, SSH, #ssh_msg_kex_dh_gex_group { p = P, g = G }),
 
678
    {Private, Public} = dh_gen_key(G,P,1024),
 
679
    ?dbg(?DBG_KEX, "public: ~.16B\n", [Public]),
 
680
    case recv_msg(S, SSH) of
 
681
        {ok, R} when record(R, ssh_msg_kex_dh_gex_init) ->
 
682
            E = R#ssh_msg_kex_dh_gex_init.e,
 
683
            K = ssh_math:ipow(E, Private, P),
 
684
            {Key,K_S} = get_host_key(SSH),
 
685
            H = kex_h(SSH, K_S, Min, NBits, Max, P, G, E, Public, K),
 
686
            H_SIG = sign_host_key(S, SSH, Key, H),
 
687
            send_msg(S, SSH,
 
688
                     #ssh_msg_kex_dh_gex_reply { public_host_key = K_S,
 
689
                                                 f = Public,
 
690
                                                 h_sig = H_SIG
 
691
                                                }),
 
692
            ?dbg(?DBG_KEX, "shared_secret: ~s\n", [fmt_binary(K, 16, 4)]),
 
693
            ?dbg(?DBG_KEX, "hash: ~s\n", [fmt_binary(H, 16, 4)]),
 
694
            {ok, SSH#ssh { shared_secret = K,
 
695
                           exchanged_hash = H,
 
696
                           session_id = H }};
 
697
        {ok,_} ->
 
698
            {error, bad_message};
 
699
        Error ->
 
700
            Error
 
701
    end;
 
702
server_kex(_S, _SSH, Kex) ->
 
703
    {error, {bad_kex_algorithm, Kex}}.
 
704
 
 
705
ssh_main(S, User, SSH) ->
 
706
    receive
 
707
        {tcp, S, Data} ->
 
708
            %% This is a lazy way of gettting events without block
 
709
            ?dbg(?DBG_PACKET, "UNRECEIVE: ~w BYTES\n", [size(Data)]),
 
710
            gen_tcp:unrecv(S, Data),
 
711
            case recv_msg(S, SSH) of
 
712
                {ok, M} when record(M, ssh_msg_unimplemented) ->
 
713
                    ?dbg(true, "UNIMPLEMENTED: ~p\n",
 
714
                         [M#ssh_msg_unimplemented.sequence]),
 
715
                    inet:setopts(S, [{active, once}]),
 
716
                    ssh_main(S, User, SSH);
 
717
                {ok,M} when record(M, ssh_msg_disconnect) ->
 
718
                    User ! {ssh_msg, self(), M},
 
719
                    ?dbg(true, "DISCONNECT: ~w ~s\n",
 
720
                         [M#ssh_msg_disconnect.code,
 
721
                          M#ssh_msg_disconnect.description]),
 
722
                    gen_tcp:close(S);
 
723
 
 
724
                {ok,M} when record(M, ssh_msg_kexinit) ->
 
725
                    recv_negotiate(S, User, SSH, M, false);
 
726
 
 
727
                {ok,M} ->
 
728
                    User ! {ssh_msg, self(), M},
 
729
                    inet:setopts(S, [{active, once}]),
 
730
                    ssh_main(S, User, SSH);
 
731
                {error, unimplemented} ->
 
732
                    send_msg(S, SSH, 
 
733
                             #ssh_msg_unimplemented { sequence =
 
734
                                                      get(recv_sequence)-1}),
 
735
                    inet:setopts(S, [{active, once}]),
 
736
                    ssh_main(S, User, SSH);
 
737
                {error, _Other} ->
 
738
                    inet:setopts(S, [{active, once}]),
 
739
                    %% send disconnect!
 
740
                    ssh_main(S, User, SSH)
 
741
            end;
 
742
 
 
743
        {tcp_closed, S} ->
 
744
            User ! {ssh_msg, self(),
 
745
                    #ssh_msg_disconnect { code=?SSH_DISCONNECT_CONNECTION_LOST,
 
746
                                          description = "Connection closed",
 
747
                                          language = "" }},
 
748
            gen_tcp:close(S), %% CHECK ME, is this needed ?
 
749
            ok;
 
750
 
 
751
        {ssh_msg, User, Msg} ->
 
752
            send_msg(S, SSH, Msg),
 
753
            if record(Msg, ssh_msg_disconnect) ->
 
754
                    ok;
 
755
               true ->
 
756
                    ssh_main(S, User, SSH)
 
757
            end;
 
758
 
 
759
        {ssh_install, Table} ->
 
760
            ssh_bits:install_messages(Table),
 
761
            ssh_main(S, User, SSH);
 
762
 
 
763
        {ssh_uninstall, Table} ->
 
764
            ssh_bits:uninstall_messages(Table),
 
765
            ssh_main(S, User, SSH);
 
766
 
 
767
        {ssh_renegotiate, UserAck, Opts} ->
 
768
            %% Of some reason, the socket is still active, once when we
 
769
            %% get here, which yelds EINVAL when doing recv. This might be a bug...
 
770
            inet:setopts(S, [{active, false}]),
 
771
            send_negotiate(S, User, ssh_setopts(Opts, SSH), UserAck);
 
772
 
 
773
        {ssh_call, From, close} ->      
 
774
            ?dbg(true, "Call: close from ~p\n", [From]),
 
775
            gen_tcp:close(S),
 
776
            reply(From, ok),
 
777
            ok;
 
778
 
 
779
        {ssh_call, From, peername} ->
 
780
            P = inet:peername(S),
 
781
            io:format("peername~p\n", [P]),
 
782
            reply(From, P),
 
783
            ssh_main(S, User, SSH);
 
784
 
 
785
        {ssh_call, From, Req} ->
 
786
            ?dbg(true, "Call: ~p from ~p\n", [Req,From]),
 
787
            SSH1 = handle_call(Req, From, SSH),
 
788
            ssh_main(S, User, SSH1);
 
789
 
 
790
        _Other ->
 
791
            ?dbg(true, "ssh_loop: got ~p\n", [_Other]),
 
792
            ssh_main(S, User, SSH)
 
793
    end.
 
794
 
 
795
%%
 
796
%% Handle call's to ssh_transport
 
797
%%
 
798
handle_call({get_cb,io}, From, SSH) ->
 
799
    reply(From, {ok, SSH#ssh.io_cb}),
 
800
    SSH;
 
801
handle_call({get_cb,key}, From, SSH) ->
 
802
    reply(From, {ok, SSH#ssh.key_cb}),
 
803
    SSH;
 
804
handle_call(get_session_id, From, SSH) ->
 
805
    reply(From, {ok, SSH#ssh.session_id}),
 
806
    SSH;
 
807
handle_call(_Other, From, SSH) ->
 
808
    reply(From, {error, bad_call}),
 
809
    SSH.
 
810
 
 
811
reply([Pid|Ref], Reply) ->
 
812
    ?dbg(true, "Reply: ~p\n", [Reply]),
 
813
    Pid ! {Ref, Reply}.
 
814
 
 
815
 
 
816
%%
 
817
%% The host key should be read from storage
 
818
%%
 
819
get_host_key(SSH) ->
 
820
    #ssh{key_cb = Mod, opts = Opts, algorithms = ALG} = SSH,
 
821
    Scope = proplists:get_value(key_scope, Opts, system),
 
822
    case ALG#alg.hkey of
 
823
        'ssh-rsa' ->
 
824
            case Mod:private_host_rsa_key(Scope, Opts) of
 
825
                {ok,Key=#ssh_key { public={N,E}} } ->
 
826
                    ?dbg(true, "x~n", []),
 
827
                    {Key,
 
828
                     ssh_bits:encode(["ssh-rsa",E,N],[string,mpint,mpint])};
 
829
                Error ->
 
830
                    ?dbg(true, "y~n", []),
 
831
                    exit(Error)
 
832
            end;
 
833
        'ssh-dss' ->
 
834
            case Mod:private_host_dsa_key(Scope, Opts) of
 
835
                {ok,Key=#ssh_key { public={P,Q,G,Y}}} ->
 
836
                    {Key, ssh_bits:encode(["ssh-dss",P,Q,G,Y],
 
837
                                          [string,mpint,mpint,mpint,mpint])};
 
838
                Error ->
 
839
                    exit(Error)
 
840
            end;
 
841
        _ ->
 
842
            exit({error, bad_key_type})
 
843
    end.
 
844
 
 
845
sign_host_key(_S, SSH, Private, H)                                       ->
 
846
    ALG = SSH#ssh.algorithms,
 
847
    Module = case ALG#alg.hkey of
 
848
                 'ssh-rsa' -> ssh_rsa;
 
849
                 'ssh-dss' -> ssh_dsa;
 
850
                 A -> A
 
851
             end,
 
852
    case catch Module:sign(Private, H) of
 
853
        {'EXIT', Reason} ->
 
854
            error_logger:format("SIGN FAILED: ~p\n", [Reason]),
 
855
            {error, Reason};
 
856
        SIG ->
 
857
            ssh_bits:encode([Module:alg_name() ,SIG],[string,binary])
 
858
    end.    
 
859
 
 
860
verify_host_key(_S, SSH, K_S, H, H_SIG)                                  ->
 
861
    ALG = SSH#ssh.algorithms,
 
862
    case ALG#alg.hkey of
 
863
        'ssh-rsa' ->
 
864
            case ssh_bits:decode(K_S,[string,mpint,mpint]) of
 
865
                ["ssh-rsa", E, N] ->
 
866
                    ["ssh-rsa",SIG] = ssh_bits:decode(H_SIG,[string,binary]),
 
867
                    Public = #ssh_key { type=rsa, public={N,E} },
 
868
                    case catch ssh_rsa:verify(Public, H, SIG) of
 
869
                        {'EXIT', Reason} ->
 
870
                            error_logger:format("VERIFY FAILED: ~p\n", [Reason]),
 
871
                            {error, bad_signature};
 
872
                        ok ->
 
873
                            known_host_key(SSH, Public, "ssh-rsa")
 
874
                    end;
 
875
                _ ->
 
876
                    {error, bad_format}
 
877
            end;
 
878
        'ssh-dss' ->
 
879
            case ssh_bits:decode(K_S,[string,mpint,mpint,mpint,mpint]) of
 
880
                ["ssh-dss",P,Q,G,Y] ->
 
881
                    ["ssh-dss",SIG] = ssh_bits:decode(H_SIG,[string,binary]),
 
882
                    Public = #ssh_key { type=dsa, public={P,Q,G,Y} },
 
883
                    case catch ssh_dsa:verify(Public, H, SIG) of
 
884
                        {'EXIT', Reason} ->
 
885
                            error_logger:format("VERIFY FAILED: ~p\n", [Reason]),
 
886
                            {error, bad_signature};
 
887
                        ok ->
 
888
                            known_host_key(SSH, Public, "ssh-dss")
 
889
                    end;
 
890
                _ ->
 
891
                    {error, bad_host_key_format}
 
892
            end;
 
893
        _ ->
 
894
            {error, bad_host_key_algorithm}
 
895
    end.
 
896
 
 
897
accepted_host(SSH, Peer, Opts) ->
 
898
    case proplists:get_value(silently_accept_hosts, Opts, false) of
 
899
        true ->
 
900
            yes;
 
901
        false ->
 
902
            yes_no(SSH, "New host "++Peer++" accept")
 
903
    end.
 
904
 
 
905
known_host_key(SSH, Public, Alg) ->
 
906
    #ssh{opts = Opts, key_cb = Mod, peer = Peer} = SSH,
 
907
    case Mod:lookup_host_key(Peer, Alg, Opts) of
 
908
        {ok, Public} ->
 
909
            ok;
 
910
        {ok, BadPublic} ->
 
911
            error_logger:format("known_host_key: Public ~p BadPublic ~p\n", [Public, BadPublic]),
 
912
            {error, bad_public_key};
 
913
        {error, not_found} ->
 
914
            case accepted_host(SSH, Peer, Opts) of
 
915
                yes ->
 
916
                    Mod:add_host_key(Peer, Public, Opts);
 
917
                no ->
 
918
                    {error, rejected}
 
919
            end
 
920
    end.
 
921
            
 
922
send_algorithms(S, SSH, KexInit) ->
 
923
    Payload = ssh_bits:encode(KexInit),
 
924
    ?dbg(?DBG_MESSAGE, "SEND_MSG: ~70p\n", [KexInit]),
 
925
    Res = send_packet(S, SSH, Payload),
 
926
    {Res,Payload}.
 
927
                       
 
928
 
 
929
recv_algorithms(S, SSH) ->
 
930
    case recv_packet(S, SSH) of
 
931
        {ok, Packet} ->
 
932
            case ssh_bits:decode(Packet) of
 
933
                {ok, R} ->
 
934
                    ?dbg(?DBG_MESSAGE, "RECV_MSG: ~70p\n", [R]),
 
935
                    {ok, {Packet, R}};
 
936
                Error ->
 
937
                    Error
 
938
            end;
 
939
        Error ->
 
940
            ?dbg(?DBG_MESSAGE, "RECV_MSG: ~p\n", [Error]),
 
941
            Error
 
942
    end.
 
943
 
 
944
%%   Each of the algorithm strings MUST be a comma-separated list of
 
945
%%   algorithm names (see ''Algorithm Naming'' in [SSH-ARCH]).  Each
 
946
%%   supported (allowed) algorithm MUST be listed in order of preference.
 
947
%%
 
948
%%   The first algorithm in each list MUST be the preferred (guessed)
 
949
%%   algorithm.  Each string MUST contain at least one algorithm name.
 
950
 
 
951
select_algorithm(SSH, ALG, C, S) ->
 
952
    %% find out the selected algorithm
 
953
    C_Enc = select(C#ssh_msg_kexinit.encryption_algorithms_client_to_server,
 
954
                   S#ssh_msg_kexinit.encryption_algorithms_client_to_server),
 
955
 
 
956
    C_Mac = select(C#ssh_msg_kexinit.mac_algorithms_client_to_server,
 
957
                   S#ssh_msg_kexinit.mac_algorithms_client_to_server),
 
958
 
 
959
    C_Cmp = select(C#ssh_msg_kexinit.compression_algorithms_client_to_server,
 
960
                   S#ssh_msg_kexinit.compression_algorithms_client_to_server),
 
961
 
 
962
    C_Lng = select(C#ssh_msg_kexinit.languages_client_to_server,
 
963
                   S#ssh_msg_kexinit.languages_client_to_server),
 
964
 
 
965
    S_Enc = select(C#ssh_msg_kexinit.encryption_algorithms_server_to_client,
 
966
                   S#ssh_msg_kexinit.encryption_algorithms_server_to_client),
 
967
 
 
968
    S_Mac = select(C#ssh_msg_kexinit.mac_algorithms_server_to_client,
 
969
                   S#ssh_msg_kexinit.mac_algorithms_server_to_client),
 
970
 
 
971
    S_Cmp = select(C#ssh_msg_kexinit.compression_algorithms_server_to_client,
 
972
                   S#ssh_msg_kexinit.compression_algorithms_server_to_client),
 
973
 
 
974
    S_Lng = select(C#ssh_msg_kexinit.languages_server_to_client,
 
975
                   S#ssh_msg_kexinit.languages_server_to_client),
 
976
 
 
977
    HKey = select_all(C#ssh_msg_kexinit.server_host_key_algorithms,
 
978
                      S#ssh_msg_kexinit.server_host_key_algorithms),
 
979
    HK = case HKey of
 
980
             [] -> undefined;
 
981
             [HK0|_] -> HK0
 
982
         end,
 
983
    %% Fixme verify Kex against HKey list and algorithms
 
984
    
 
985
    Kex = select(C#ssh_msg_kexinit.kex_algorithms,
 
986
                 S#ssh_msg_kexinit.kex_algorithms),
 
987
 
 
988
    ALG1 = ALG#alg { kex = Kex, hkey = HK },
 
989
 
 
990
    ALG2 = save_alg(SSH#ssh.role, 
 
991
                   ALG1,
 
992
                   [{c_enc, C_Enc},
 
993
                    {c_mac, C_Mac},
 
994
                    {c_cmp, C_Cmp},
 
995
                    {c_lng, C_Lng},
 
996
                    {s_enc, S_Enc},
 
997
                    {s_mac, S_Mac},
 
998
                    {s_cmp, S_Cmp},
 
999
                    {s_lng, S_Lng}]),
 
1000
    {ok, SSH#ssh { algorithms = ALG2 }}.
 
1001
 
 
1002
 
 
1003
save_alg(Role, ALG, [{Key,A} | As]) ->
 
1004
    if A == undefined ->
 
1005
            save_alg(Role, ALG, As);
 
1006
       true ->
 
1007
            case Key of
 
1008
                c_enc ->
 
1009
                    case Role of
 
1010
                        client ->
 
1011
                            save_alg(Role,ALG#alg { encrypt = A }, As);
 
1012
                        server ->
 
1013
                            save_alg(Role,ALG#alg { decrypt = A }, As)
 
1014
                    end;
 
1015
 
 
1016
                s_enc -> 
 
1017
                    case Role of
 
1018
                        server -> 
 
1019
                            save_alg(Role,ALG#alg { encrypt = A }, As);
 
1020
                        client ->
 
1021
                            save_alg(Role,ALG#alg { decrypt = A }, As)
 
1022
                    end;
 
1023
 
 
1024
                c_mac ->
 
1025
                    case Role of
 
1026
                        client ->
 
1027
                            save_alg(Role,ALG#alg { send_mac=A }, As);
 
1028
                        server ->
 
1029
                            save_alg(Role,ALG#alg { recv_mac=A }, As)
 
1030
                    end;
 
1031
 
 
1032
                s_mac -> 
 
1033
                    case Role of
 
1034
                        server -> 
 
1035
                            save_alg(Role,ALG#alg { send_mac = A }, As); 
 
1036
                        client ->
 
1037
                            save_alg(Role,ALG#alg { recv_mac = A }, As)
 
1038
                    end;
 
1039
 
 
1040
                c_cmp -> 
 
1041
                    case Role of
 
1042
                        client ->
 
1043
                            save_alg(Role,ALG#alg { compress = A }, As);
 
1044
                        server ->
 
1045
                            save_alg(Role,ALG#alg { decompress = A }, As)
 
1046
                    end;
 
1047
                            
 
1048
                s_cmp -> 
 
1049
                    case Role of
 
1050
                        server ->
 
1051
                            save_alg(Role, ALG#alg { compress = A }, As);
 
1052
                        client ->
 
1053
                            save_alg(Role, ALG#alg { decompress = A }, As)
 
1054
                    end;
 
1055
                c_lng -> save_alg(Role, ALG#alg { c_lng = A }, As);
 
1056
                s_lng -> save_alg(Role, ALG#alg { s_lng = A }, As)
 
1057
            end
 
1058
    end;
 
1059
save_alg(_Role, ALG, []) ->
 
1060
    ALG.
 
1061
 
 
1062
install_alg(SSH) ->
 
1063
    SSH1 = alg_final(SSH),
 
1064
    SSH2 = alg_setup(SSH1),
 
1065
    alg_init(SSH2).
 
1066
 
 
1067
alg_setup(SSH) ->
 
1068
    ALG = SSH#ssh.algorithms,
 
1069
    ?dbg(?DBG_ALG, "ALG: setup ~p\n", [ALG]),
 
1070
    SSH#ssh { kex       = ALG#alg.kex,
 
1071
              hkey      = ALG#alg.hkey,
 
1072
              encrypt = ALG#alg.encrypt,
 
1073
              decrypt = ALG#alg.decrypt,
 
1074
              send_mac = ALG#alg.send_mac,
 
1075
              send_mac_size = mac_digest_size(ALG#alg.send_mac),
 
1076
              recv_mac = ALG#alg.recv_mac,
 
1077
              recv_mac_size = mac_digest_size(ALG#alg.recv_mac),
 
1078
              compress = ALG#alg.compress,
 
1079
              decompress = ALG#alg.decompress,
 
1080
              c_lng = ALG#alg.c_lng,
 
1081
              s_lng = ALG#alg.s_lng,
 
1082
              algorithms = undefined
 
1083
              }.
 
1084
 
 
1085
alg_init(SSH0) ->
 
1086
    ?dbg(?DBG_ALG, "ALG: init\n", []),
 
1087
    {ok,SSH1} = send_mac_init(SSH0),
 
1088
    {ok,SSH2} = recv_mac_init(SSH1),
 
1089
    {ok,SSH3} = encrypt_init(SSH2),
 
1090
    {ok,SSH4} = decrypt_init(SSH3),
 
1091
    {ok,SSH5} = compress_init(SSH4),
 
1092
    {ok,SSH6} = decompress_init(SSH5),
 
1093
    SSH6.
 
1094
 
 
1095
alg_final(SSH0) ->
 
1096
    ?dbg(?DBG_ALG, "ALG: final\n", []),
 
1097
    {ok,SSH1} = send_mac_final(SSH0),
 
1098
    {ok,SSH2} = recv_mac_final(SSH1),
 
1099
    {ok,SSH3} = encrypt_final(SSH2),
 
1100
    {ok,SSH4} = decrypt_final(SSH3),
 
1101
    {ok,SSH5} = compress_final(SSH4),
 
1102
    {ok,SSH6} = decompress_final(SSH5),
 
1103
    SSH6.
 
1104
 
 
1105
 
 
1106
 
 
1107
select_all(CL, SL) ->
 
1108
    A = CL -- SL,  %% algortihms only used by client
 
1109
    %% algorithms used by client and server (client pref)
 
1110
    map(fun(ALG) -> list_to_atom(ALG) end, (CL -- A)).
 
1111
 
 
1112
select([], []) ->
 
1113
    none;
 
1114
select(CL, SL) ->
 
1115
    C = case select_all(CL,SL) of
 
1116
            [] -> undefined;
 
1117
            [ALG|_] -> ALG
 
1118
        end,
 
1119
    ?dbg(?DBG_ALG, "ALG: select: ~p ~p = ~p\n", [CL, SL, C]),
 
1120
    C.
 
1121
            
 
1122
send_version(S, Version) ->
 
1123
    gen_tcp:send(S, [Version,"\r\n"]).
 
1124
 
 
1125
 
 
1126
send_msg(S, SSH, Record) ->
 
1127
    ?dbg(?DBG_MESSAGE, "SEND_MSG: ~70p\n", [Record]),
 
1128
    Bin = ssh_bits:encode(Record),
 
1129
    ?dbg(?DBG_BIN_MESSAGE, "Encoded: ~70p\n", [Bin]),
 
1130
    send_packet(S, SSH, Bin).
 
1131
 
 
1132
 
 
1133
%%
 
1134
%% TotalLen = 4 + 1 + size(Data) + size(Padding)
 
1135
%% PaddingLen = TotalLen - (size(Data)+4+1)
 
1136
%% 
 
1137
send_packet(S, SSH, Data0) when binary(Data0) ->
 
1138
    Data = compress(SSH, Data0),
 
1139
    BlockSize = SSH#ssh.encrypt_block_size,
 
1140
    PL = (BlockSize - ((4 + 1 + size(Data)) rem BlockSize)) rem BlockSize,
 
1141
    PaddingLen = if PL <  4 -> PL+BlockSize;
 
1142
                    true -> PL
 
1143
                 end,
 
1144
    Padding = ssh_bits:random(PaddingLen),
 
1145
    PacketLen = 1 + PaddingLen + size(Data),
 
1146
    Packet = <<?UINT32(PacketLen),?BYTE(PaddingLen), 
 
1147
              Data/binary, Padding/binary>>,
 
1148
    EncPacket = encrypt(SSH, Packet),
 
1149
    Seq = get(send_sequence),
 
1150
    MAC = send_mac(SSH, Packet, Seq),
 
1151
    ?dbg(?DBG_PACKET, "SEND_PACKET:~w len=~p,payload=~p,padding=~p,mac=~p\n",
 
1152
         [Seq, PacketLen, size(Data), PaddingLen, MAC]),
 
1153
    Res = gen_tcp:send(S, [EncPacket, MAC]),
 
1154
    put(send_sequence, (Seq+1) band 16#ffffffff),
 
1155
    Res.
 
1156
 
 
1157
recv_msg(S, SSH) ->
 
1158
    case recv_packet(S, SSH) of
 
1159
        {ok, Packet} ->
 
1160
            case ssh_bits:decode(Packet) of
 
1161
                {ok, M} when record(M, ssh_msg_debug) ->
 
1162
                    if M#ssh_msg_debug.always_display == true ->
 
1163
                            io:format("DEBUG: ~p\n",
 
1164
                                      [M#ssh_msg_debug.message]);
 
1165
                       true ->
 
1166
                            ?dbg(true, "DEBUG: ~p\n",
 
1167
                                 [M#ssh_msg_debug.message])
 
1168
                    end,
 
1169
                    inet:setopts(S, [{active, once}]),
 
1170
                    recv_msg(S, SSH);
 
1171
                {ok, M} when record(M, ssh_msg_ignore) ->
 
1172
                    inet:setopts(S, [{active, once}]),
 
1173
                    recv_msg(S, SSH);
 
1174
                {ok, Msg} ->
 
1175
                    ?dbg(?DBG_MESSAGE, "RECV_MSG: ~70p\n", [Msg]),
 
1176
                    {ok, Msg};
 
1177
                Error ->
 
1178
                    %% Fixme (send disconnect...)
 
1179
                    Error
 
1180
            end;
 
1181
        Error ->
 
1182
            ?dbg(?DBG_MESSAGE, "RECV_MSG: ~70p\n", [Error]),
 
1183
            Error
 
1184
    end.
 
1185
 
 
1186
%% receive ONE packet
 
1187
recv_packet(S, SSH) ->
 
1188
    BlockSize = SSH#ssh.decrypt_block_size,
 
1189
    case gen_tcp:recv(S, BlockSize) of
 
1190
        {ok, EncData0} ->
 
1191
            Data0 = decrypt(SSH, EncData0),
 
1192
            <<?UINT32(PacketLen), _/binary>> = Data0,
 
1193
            if PacketLen < 5; PacketLen > ?SSH_MAX_PACKET_SIZE ->
 
1194
                    terminate(S, SSH, ?SSH_DISCONNECT_PROTOCOL_ERROR,
 
1195
                              "Bad packet length "++
 
1196
                              integer_to_list(PacketLen));
 
1197
               true ->
 
1198
                    case gen_tcp:recv(S, (PacketLen - BlockSize)+4) of
 
1199
                        {ok, EncData1} ->
 
1200
                            Data1 = decrypt(SSH, EncData1),
 
1201
                            Data = <<Data0/binary, Data1/binary>>,
 
1202
                            recv_packet_data(S, SSH, PacketLen, Data);
 
1203
                        Error ->
 
1204
                            Error
 
1205
                    end
 
1206
            end;
 
1207
        Error ->
 
1208
            Error
 
1209
    end.
 
1210
 
 
1211
recv_packet_data(S, SSH, PacketLen, Data) ->
 
1212
    Seq = get(recv_sequence),
 
1213
    Res = valid_mac(SSH, S, Data, Seq),
 
1214
    put(recv_sequence, (Seq+1) band 16#ffffffff),
 
1215
    case Res of
 
1216
        true ->
 
1217
            <<_:32, PaddingLen:8, _/binary>> = Data,
 
1218
            PayloadLen = PacketLen - PaddingLen - 1,
 
1219
            <<_:32, _:8, Payload:PayloadLen/binary, 
 
1220
             _:PaddingLen/binary>> = Data,
 
1221
            ?dbg(?DBG_PACKET, 
 
1222
                 "RECV_PACKET:~w, len=~p,payload=~w,padding=~w\n", 
 
1223
                 [Seq,PacketLen,PayloadLen,PaddingLen]),
 
1224
            {ok, decompress(SSH, Payload)};
 
1225
        false ->
 
1226
            ?dbg(?DBG_PACKET, "RECV_PACKET:~w, len=~p\n", 
 
1227
                 [Seq,PacketLen]),
 
1228
            terminate(S, SSH, ?SSH_DISCONNECT_MAC_ERROR,
 
1229
                      "Bad MAC #"++ integer_to_list(Seq))
 
1230
    end.
 
1231
 
 
1232
 
 
1233
kexfailed(S, User, UserAck, Error) ->
 
1234
    Description =
 
1235
        case Error of
 
1236
            {error, bad_message} ->
 
1237
                "key exchanged failed: bad message received";
 
1238
            _ ->
 
1239
                "key exchanged failed"
 
1240
        end,
 
1241
    M = #ssh_msg_disconnect { code = ?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
 
1242
                              description = Description,
 
1243
                              language = "en"},
 
1244
    if UserAck == true ->
 
1245
            User ! {self(), Error};
 
1246
       true ->
 
1247
            User ! {ssh_msg, self(), M}
 
1248
    end,
 
1249
    gen_tcp:close(S),
 
1250
    Error.
 
1251
 
 
1252
 
 
1253
 
 
1254
%% Send a disconnect message
 
1255
terminate(S, SSH, Code, Message) ->
 
1256
    M = #ssh_msg_disconnect { code=Code, 
 
1257
                              description=Message,
 
1258
                              language = "en" },
 
1259
    send_msg(S, SSH, M),
 
1260
    gen_tcp:close(S),
 
1261
    {error, M}.
 
1262
 
 
1263
    
 
1264
 
 
1265
    
 
1266
 
 
1267
%% public key algorithms
 
1268
%%
 
1269
%%   ssh-dss              REQUIRED     sign    Raw DSS Key
 
1270
%%   ssh-rsa              RECOMMENDED  sign    Raw RSA Key
 
1271
%%   x509v3-sign-rsa      OPTIONAL     sign    X.509 certificates (RSA key)
 
1272
%%   x509v3-sign-dss      OPTIONAL     sign    X.509 certificates (DSS key)
 
1273
%%   spki-sign-rsa        OPTIONAL     sign    SPKI certificates (RSA key)
 
1274
%%   spki-sign-dss        OPTIONAL     sign    SPKI certificates (DSS key)
 
1275
%%   pgp-sign-rsa         OPTIONAL     sign    OpenPGP certificates (RSA key)
 
1276
%%   pgp-sign-dss         OPTIONAL     sign    OpenPGP certificates (DSS key)
 
1277
%%
 
1278
 
 
1279
%% key exchange
 
1280
%%
 
1281
%%     diffie-hellman-group1-sha1       REQUIRED
 
1282
%%
 
1283
%%
 
1284
 
 
1285
    
 
1286
 
 
1287
 
 
1288
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1289
%% Encryption
 
1290
%%   context stored in dictionary as 'encrypt_ctx'
 
1291
%%
 
1292
%% chiphers
 
1293
%%
 
1294
%%       3des-cbc         REQUIRED          
 
1295
%%       three-key 3DES in CBC mode
 
1296
%%       blowfish-cbc     OPTIONAL          Blowfish in CBC mode
 
1297
%%       twofish256-cbc   OPTIONAL          Twofish in CBC mode,
 
1298
%%                                          with 256-bit key
 
1299
%%       twofish-cbc      OPTIONAL          alias for "twofish256-cbc" (this
 
1300
%%                                          is being retained for
 
1301
%%                                          historical reasons)
 
1302
%%       twofish192-cbc   OPTIONAL          Twofish with 192-bit key
 
1303
%%       twofish128-cbc   OPTIONAL          Twofish with 128-bit key
 
1304
%%       aes256-cbc       OPTIONAL          AES in CBC mode,
 
1305
%%                                          with 256-bit key
 
1306
%%       aes192-cbc       OPTIONAL          AES with 192-bit key
 
1307
%%       aes128-cbc       RECOMMENDED       AES with 128-bit key
 
1308
%%       serpent256-cbc   OPTIONAL          Serpent in CBC mode, with
 
1309
%%                                          256-bit key
 
1310
%%       serpent192-cbc   OPTIONAL          Serpent with 192-bit key
 
1311
%%       serpent128-cbc   OPTIONAL          Serpent with 128-bit key
 
1312
%%       arcfour          OPTIONAL          the ARCFOUR stream cipher
 
1313
%%       idea-cbc         OPTIONAL          IDEA in CBC mode
 
1314
%%       cast128-cbc      OPTIONAL          CAST-128 in CBC mode
 
1315
%%       none             OPTIONAL          no encryption; NOT RECOMMENDED
 
1316
%%  
 
1317
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1318
 
 
1319
encrypt_init(SSH) ->
 
1320
    case SSH#ssh.encrypt of
 
1321
        none ->
 
1322
            {ok,SSH};
 
1323
        '3des-cbc' ->
 
1324
            {IV,KD} = 
 
1325
                case SSH#ssh.role of
 
1326
                    client ->
 
1327
                        {hash(SSH, "A", 64),
 
1328
                         hash(SSH, "C", 192)};
 
1329
                    server ->
 
1330
                        {hash(SSH, "B", 64),
 
1331
                         hash(SSH, "D", 192)}
 
1332
                end,
 
1333
            <<K1:8/binary, K2:8/binary, K3:8/binary>> = KD,
 
1334
            put(encrypt_ctx,  IV),
 
1335
            {ok,SSH#ssh { encrypt_keys = {K1,K2,K3},
 
1336
                          encrypt_block_size = 8 }};
 
1337
        _ ->
 
1338
            exit({bad_algorithm,SSH#ssh.encrypt})
 
1339
    end.
 
1340
 
 
1341
encrypt_final(SSH) ->
 
1342
    erase(encrypt_ctx),
 
1343
    {ok, SSH#ssh { encrypt = none, 
 
1344
                   encrypt_keys = undefined,
 
1345
                   encrypt_block_size = 8
 
1346
                  }}.
 
1347
 
 
1348
 
 
1349
encrypt(SSH, Data) ->
 
1350
    case SSH#ssh.encrypt of
 
1351
        none -> 
 
1352
            Data;
 
1353
        '3des-cbc' ->
 
1354
            {K1,K2,K3} = SSH#ssh.encrypt_keys,
 
1355
            IV0 = get(encrypt_ctx),
 
1356
            ?dbg(?DBG_CRYPTO, "encrypt: IV=~p K1=~p, K2=~p, K3=~p\n",
 
1357
                 [IV0,K1,K2,K3]),
 
1358
            Enc = crypto:des3_cbc_encrypt(K1,K2,K3,IV0,Data),
 
1359
            ?dbg(?DBG_CRYPTO, "encrypt: ~p -> ~p\n", [Data, Enc]),
 
1360
            %% Enc = list_to_binary(E0),
 
1361
            IV = crypto:des_cbc_ivec(Enc),
 
1362
            put(encrypt_ctx, IV),
 
1363
            Enc;
 
1364
        _ ->
 
1365
            exit({bad_algorithm,SSH#ssh.encrypt})
 
1366
    end.
 
1367
 
 
1368
 
 
1369
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1370
%% Decryption
 
1371
%%   context stored in dictionary as 'decrypt_ctx'
 
1372
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1373
 
 
1374
decrypt_init(SSH) ->
 
1375
    case SSH#ssh.decrypt of
 
1376
        none ->
 
1377
            {ok,SSH};
 
1378
        '3des-cbc' ->
 
1379
            {IV,KD} = case SSH#ssh.role of
 
1380
                          client ->
 
1381
                              {hash(SSH, "B", 64),
 
1382
                               hash(SSH, "D", 192)};
 
1383
                          server -> 
 
1384
                              {hash(SSH, "A", 64),
 
1385
                               hash(SSH, "C", 192)}
 
1386
                      end,
 
1387
            <<K1:8/binary, K2:8/binary, K3:8/binary>> = KD,
 
1388
            put(decrypt_ctx,  IV),
 
1389
            {ok,SSH#ssh{ decrypt_keys = {K1,K2,K3},
 
1390
                         decrypt_block_size = 8 }};
 
1391
        _ ->
 
1392
            exit({bad_algorithm,SSH#ssh.decrypt})
 
1393
    end.
 
1394
 
 
1395
decrypt_final(SSH) ->
 
1396
    erase(decrypt_ctx),
 
1397
    {ok, SSH#ssh { decrypt = none, 
 
1398
                   decrypt_keys = undefined,
 
1399
                   decrypt_block_size = 8 }}.
 
1400
 
 
1401
decrypt(SSH, Data) ->
 
1402
    case SSH#ssh.decrypt of
 
1403
        none -> 
 
1404
            Data;
 
1405
        '3des-cbc' ->
 
1406
            {K1,K2,K3} = SSH#ssh.decrypt_keys,
 
1407
            IV0 = get(decrypt_ctx),
 
1408
            ?dbg(?DBG_CRYPTO, "decrypt: IV=~p K1=~p, K2=~p, K3=~p\n",
 
1409
                 [IV0,K1,K2,K3]),
 
1410
            Dec = crypto:des3_cbc_decrypt(K1,K2,K3,IV0,Data),
 
1411
            %% Enc = list_to_binary(E0),
 
1412
            ?dbg(?DBG_CRYPTO, "decrypt: ~p -> ~p\n", [Data, Dec]),
 
1413
            IV = crypto:des_cbc_ivec(Data),
 
1414
            put(decrypt_ctx, IV),
 
1415
            Dec;
 
1416
        _ ->
 
1417
            exit({bad_algorithm,SSH#ssh.decrypt})
 
1418
    end.
 
1419
 
 
1420
 
 
1421
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1422
%% Compression
 
1423
%%   context stored in dictionary as 'compress_ctx'
 
1424
%%
 
1425
%%     none     REQUIRED        no compression
 
1426
%%     zlib     OPTIONAL        ZLIB (LZ77) compression
 
1427
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1428
 
 
1429
compress_init(SSH) ->
 
1430
    compress_init(SSH, 1).
 
1431
compress_init(SSH, Level) ->
 
1432
    Compress = SSH#ssh.compress,
 
1433
    ?dbg(?DBG_ZLIB, "compress_init: ~p Level ~p\n", [Compress, Level]),
 
1434
    case Compress of
 
1435
        none ->
 
1436
            {ok,SSH};
 
1437
        zlib ->
 
1438
            Z = zlib:open(),
 
1439
            case zlib:deflateInit(Z, Level) of
 
1440
                ok ->
 
1441
                    put(compress_ctx, Z),
 
1442
                    {ok, SSH};
 
1443
                Error ->
 
1444
                    zlib:close(Z),
 
1445
                    Error
 
1446
            end;
 
1447
        _ ->
 
1448
            exit({bad_algorithm,SSH#ssh.compress})
 
1449
    end.
 
1450
 
 
1451
compress_final(SSH) ->
 
1452
    case SSH#ssh.compress of
 
1453
        none ->
 
1454
            {ok, SSH};
 
1455
        zlib ->
 
1456
            zlib:close(get(compress_ctx)),
 
1457
            erase(compress_ctx),
 
1458
            {ok, SSH#ssh { compress = none }};
 
1459
        _ ->
 
1460
            exit({bad_algorithm,SSH#ssh.compress})
 
1461
    end.
 
1462
 
 
1463
compress(SSH, Data) ->
 
1464
    case SSH#ssh.compress of
 
1465
        none ->
 
1466
            Data;
 
1467
        zlib ->
 
1468
            Compressed = zlib:deflate(get(compress_ctx), Data, sync),
 
1469
            ?dbg(?DBG_ZLIB, "deflate: ~p -> ~p\n", [Data, Compressed]),
 
1470
            list_to_binary(Compressed);
 
1471
        _ ->
 
1472
            exit({bad_algorithm,SSH#ssh.compress})
 
1473
    end.    
 
1474
 
 
1475
    
 
1476
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1477
%% Decompression
 
1478
%%   context stored in dictionary as 'decompress_ctx'
 
1479
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1480
 
 
1481
decompress_init(SSH) ->
 
1482
    case SSH#ssh.decompress of
 
1483
        none ->
 
1484
            {ok,SSH};
 
1485
        zlib ->
 
1486
            Z = zlib:open(),
 
1487
            case zlib:inflateInit(Z) of
 
1488
                ok ->
 
1489
                    put(decompress_ctx, Z),
 
1490
                    {ok,SSH};
 
1491
                Error ->
 
1492
                    zlib:close(Z),
 
1493
                    Error
 
1494
            end;
 
1495
        _ ->
 
1496
            exit({bad_algorithm,SSH#ssh.decompress})
 
1497
    end.
 
1498
 
 
1499
decompress_final(SSH) ->
 
1500
    case SSH#ssh.decompress of
 
1501
        none ->
 
1502
            {ok, SSH};
 
1503
        zlib ->
 
1504
            zlib:close(get(decompress_ctx)),
 
1505
            erase(decompress_ctx),
 
1506
            {ok, SSH#ssh { decompress = none }};
 
1507
        _ ->
 
1508
            exit({bad_algorithm,SSH#ssh.decompress})
 
1509
    end.
 
1510
    
 
1511
decompress(SSH, Data) ->
 
1512
    case SSH#ssh.decompress of
 
1513
        none ->
 
1514
            Data;
 
1515
        zlib ->
 
1516
            Decompressed = zlib:inflate(get(decompress_ctx), Data),
 
1517
            ?dbg(?DBG_ZLIB, "inflate: ~p -> ~p\n", [Data, Decompressed]),
 
1518
            list_to_binary(Decompressed);
 
1519
        _ ->
 
1520
            exit({bad_algorithm,SSH#ssh.decompress})
 
1521
    end.
 
1522
 
 
1523
%%
 
1524
%% macs
 
1525
%%
 
1526
%%     hmac-sha1    REQUIRED        HMAC-SHA1 (digest length = key
 
1527
%%                                  length = 20)
 
1528
%%     hmac-sha1-96 RECOMMENDED     first 96 bits of HMAC-SHA1 (digest
 
1529
%%                                  length = 12, key length = 20)
 
1530
%%     hmac-md5     OPTIONAL        HMAC-MD5 (digest length = key
 
1531
%%                                  length = 16)
 
1532
%%     hmac-md5-96  OPTIONAL        first 96 bits of HMAC-MD5 (digest
 
1533
%%                                  length = 12, key length = 16)
 
1534
%%     none         OPTIONAL        no MAC; NOT RECOMMENDED
 
1535
%%
 
1536
 
 
1537
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1538
%% MAC calculation
 
1539
%%
 
1540
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1541
 
 
1542
send_mac_init(SSH) ->
 
1543
    case SSH#ssh.role of
 
1544
        client ->
 
1545
            Key = hash(SSH, "E", mac_key_size(SSH#ssh.send_mac)),
 
1546
            {ok, SSH#ssh { send_mac_key = Key }};
 
1547
        server ->
 
1548
            Key = hash(SSH, "F", mac_key_size(SSH#ssh.send_mac)),
 
1549
            {ok, SSH#ssh { send_mac_key = Key }}
 
1550
    end.
 
1551
 
 
1552
send_mac_final(SSH) ->
 
1553
    {ok, SSH#ssh {  send_mac = none, send_mac_key = undefined }}.
 
1554
 
 
1555
send_mac(SSH, Data, Seq) ->
 
1556
    case SSH#ssh.send_mac of
 
1557
        none -> 
 
1558
            <<>>;
 
1559
        'hmac-sha1' ->
 
1560
            crypto:sha_mac(SSH#ssh.send_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1561
        'hmac-sha1-96' ->
 
1562
            crypto:sha_mac_96(SSH#ssh.send_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1563
        'hmac-md5' ->
 
1564
            crypto:md5_mac(SSH#ssh.send_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1565
        'hmac-md5-96' ->
 
1566
            crypto:md5_mac_96(SSH#ssh.send_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1567
        _ ->
 
1568
            exit({bad_algorithm,SSH#ssh.send_mac})
 
1569
    end.
 
1570
        
 
1571
 
 
1572
recv_mac_init(SSH) ->
 
1573
    case SSH#ssh.role of
 
1574
        client ->
 
1575
            Key = hash(SSH, "F", mac_key_size(SSH#ssh.recv_mac)),
 
1576
            {ok, SSH#ssh { recv_mac_key = Key }};
 
1577
        server ->
 
1578
            Key = hash(SSH, "E", mac_key_size(SSH#ssh.recv_mac)),
 
1579
            {ok, SSH#ssh { recv_mac_key = Key }}
 
1580
    end.
 
1581
 
 
1582
recv_mac_final(SSH) ->
 
1583
    {ok, SSH#ssh { recv_mac = none, recv_mac_key = undefined }}.
 
1584
 
 
1585
recv_mac(SSH, Data, Seq) ->
 
1586
    case SSH#ssh.recv_mac of
 
1587
        none -> 
 
1588
            <<>>;
 
1589
        'hmac-sha1' ->
 
1590
            crypto:sha_mac(SSH#ssh.recv_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1591
        'hmac-sha1-96' ->
 
1592
            crypto:sha_mac_96(SSH#ssh.recv_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1593
        'hmac-md5' ->
 
1594
            crypto:md5_mac(SSH#ssh.recv_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1595
        'hmac-md5-96' ->
 
1596
            crypto:md5_mac_96(SSH#ssh.recv_mac_key, [<<?UINT32(Seq)>>, Data]);
 
1597
        _ ->
 
1598
            exit({bad_algorithm,SSH#ssh.recv_mac})
 
1599
    end.
 
1600
 
 
1601
 
 
1602
%% return N hash bytes (HASH)
 
1603
hash(SSH, Char, Bits) ->
 
1604
    HASH =
 
1605
        case SSH#ssh.kex of
 
1606
            'diffie-hellman-group1-sha1' ->
 
1607
                fun(Data) -> crypto:sha(Data) end;
 
1608
            'diffie-hellman-group-exchange-sha1' ->
 
1609
                fun(Data) -> crypto:sha(Data) end;
 
1610
            _ ->
 
1611
                exit({bad_algorithm,SSH#ssh.kex})
 
1612
        end,
 
1613
    hash(SSH, Char, Bits, HASH).
 
1614
 
 
1615
hash(_SSH, _Char, 0, _HASH) ->
 
1616
    <<>>;
 
1617
hash(SSH, Char, N, HASH) ->
 
1618
    K = ssh_bits:mpint(SSH#ssh.shared_secret),
 
1619
    H = SSH#ssh.exchanged_hash,
 
1620
    SessionID = SSH#ssh.session_id,
 
1621
    K1 = HASH([K, H, Char, SessionID]),
 
1622
    Sz = N div 8,
 
1623
    <<Key:Sz/binary, _/binary>> = hash(K, H, K1, N-128, HASH),
 
1624
    ?dbg(?DBG_KEX, "Key ~s: ~s\n", [Char, fmt_binary(Key, 16, 4)]),
 
1625
    Key.
 
1626
 
 
1627
hash(_K, _H, Ki, N, _HASH) when N =< 0 ->
 
1628
    Ki;
 
1629
hash(K, H, Ki, N, HASH) ->
 
1630
    Kj = HASH([K, H, Ki]),
 
1631
    hash(K, H, <<Ki/binary, Kj/binary>>, N-128, HASH).
 
1632
%%
 
1633
%% calcuation of H (diffie-hellman-group1-sha1)
 
1634
%% Must use ssh#ssh.algorithms here because new algorithms
 
1635
%% are not install at this point
 
1636
%%
 
1637
kex_h(SSH, K_S, E, F, K) ->
 
1638
    L = ssh_bits:encode([SSH#ssh.c_version, SSH#ssh.s_version,
 
1639
                         SSH#ssh.c_keyinit, SSH#ssh.s_keyinit,
 
1640
                         K_S, E,F,K],
 
1641
                        [string,string,string,string,string,
 
1642
                         mpint,mpint,mpint]),
 
1643
    crypto:sha(L).
 
1644
 
 
1645
kex_h(SSH, K_S, Min, NBits, Max, Prime, Gen, E, F, K) ->
 
1646
    L = if Min==-1; Max==-1 ->
 
1647
                Ts = [string,string,string,string,string,
 
1648
                      uint32,
 
1649
                      mpint,mpint,mpint,mpint,mpint],
 
1650
                ssh_bits:encode([SSH#ssh.c_version,SSH#ssh.s_version,
 
1651
                                 SSH#ssh.c_keyinit,SSH#ssh.s_keyinit,
 
1652
                                 K_S, NBits, Prime, Gen, E,F,K],
 
1653
                                Ts);
 
1654
           true ->
 
1655
                Ts = [string,string,string,string,string,
 
1656
                      uint32,uint32,uint32,
 
1657
                      mpint,mpint,mpint,mpint,mpint],
 
1658
                ssh_bits:encode([SSH#ssh.c_version,SSH#ssh.s_version,
 
1659
                                 SSH#ssh.c_keyinit,SSH#ssh.s_keyinit,
 
1660
                                 K_S, Min, NBits, Max,
 
1661
                                 Prime, Gen, E,F,K], Ts)
 
1662
        end,
 
1663
    crypto:sha(L).
 
1664
    
 
1665
    
 
1666
 
 
1667
 
 
1668
mac_key_size('hmac-sha1')    -> 20*8;
 
1669
mac_key_size('hmac-sha1-96') -> 20*8;
 
1670
mac_key_size('hmac-md5')     -> 16*8;
 
1671
mac_key_size('hmac-md5-96')  -> 16*8;
 
1672
mac_key_size(none) -> 0;
 
1673
mac_key_size(_) -> exit(bad_algoritm).
 
1674
 
 
1675
mac_digest_size('hmac-sha1')    -> 20;
 
1676
mac_digest_size('hmac-sha1-96') -> 12;
 
1677
mac_digest_size('hmac-md5')    -> 20;
 
1678
mac_digest_size('hmac-md5-96') -> 12;
 
1679
mac_digest_size(none) -> 0;
 
1680
mac_digest_size(_) -> exit(bad_algoritm).
 
1681
 
 
1682
%% integrity_char(send, client) -> "E";
 
1683
%% integrity_char(recv, server) -> "E";
 
1684
%% integrity_char(send, server) -> "F";
 
1685
%% integrity_char(recv, client) -> "F".
 
1686
    
 
1687
valid_mac(SSH, S, Data, Seq) ->
 
1688
    if SSH#ssh.recv_mac_size == 0 ->
 
1689
            true;
 
1690
       true ->
 
1691
            {ok,MAC0} = gen_tcp:recv(S, SSH#ssh.recv_mac_size),
 
1692
            ?dbg(?DBG_MAC, "~p: MAC0=~p\n", [Seq, MAC0]),
 
1693
            MAC1 = recv_mac(SSH, Data, Seq),
 
1694
            ?dbg(?DBG_MAC, "~p: MAC1=~p\n", [Seq, MAC1]),
 
1695
             MAC0 == MAC1
 
1696
    end.
 
1697
 
 
1698
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1699
%%
 
1700
%% Diffie-Hellman utils
 
1701
%%
 
1702
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1703
 
 
1704
dh_group1() ->
 
1705
    {2, 16#FFFFFFFFFFFFFFFFC90FDAA22168C234C4C6628B80DC1CD129024E088A67CC74020BBEA63B139B22514A08798E3404DDEF9519B3CD3A431B302B0A6DF25F14374FE1356D6D51C245E485B576625E7EC6F44C42E9A637ED6B0BFF5CB6F406B7EDEE386BFB5A899FA5AE9F24117C4B1FE649286651ECE65381FFFFFFFFFFFFFFFF}.
 
1706
 
 
1707
dh_gen_key(G,P, _Bits) ->
 
1708
    Private = ssh_bits:irandom(ssh_bits:isize(P)-1, 1, 1),
 
1709
    Public = ssh_math:ipow(G, Private, P),
 
1710
    {Private,Public}.
 
1711
 
 
1712
%% trim(Str) ->
 
1713
%%     reverse(trim_head(reverse(trim_head(Str)))).
 
1714
 
 
1715
trim_tail(Str) ->
 
1716
    reverse(trim_head(reverse(Str))).
 
1717
 
 
1718
trim_head([$\s|Cs]) -> trim_head(Cs);
 
1719
trim_head([$\t|Cs]) -> trim_head(Cs);
 
1720
trim_head([$\n|Cs]) -> trim_head(Cs);
 
1721
trim_head([$\r|Cs]) -> trim_head(Cs);
 
1722
trim_head(Cs) -> Cs.
 
1723
 
 
1724
%%
 
1725
%% DEBUG utils
 
1726
%% Format integers and binaries as hex blocks
 
1727
%%
 
1728
-ifdef(debug).
 
1729
%% fmt_binary(B) ->
 
1730
%%     fmt_binary(B, 0, 0).
 
1731
 
 
1732
%% fmt_binary(B, BlockSize) ->
 
1733
%%     fmt_binary(B, BlockSize, 0).
 
1734
 
 
1735
fmt_binary(B, BlockSize, GroupSize) ->
 
1736
    fmt_block(fmt_bin(B), BlockSize, GroupSize).
 
1737
 
 
1738
fmt_block(Bin, BlockSize, GroupSize) ->
 
1739
    fmt_block(Bin, BlockSize, 0, GroupSize).
 
1740
    
 
1741
 
 
1742
fmt_block(Bin, 0, _I, _G) ->
 
1743
    binary_to_list(Bin);
 
1744
fmt_block(Bin, Sz, G, G) when G =/= 0 ->
 
1745
    ["\n" | fmt_block(Bin, Sz, 0, G)];
 
1746
fmt_block(Bin, Sz, I, G) ->
 
1747
    case Bin of
 
1748
        <<Block:Sz/binary, Tail/binary>> ->
 
1749
            if Tail == <<>> ->
 
1750
                    [binary_to_list(Block)];
 
1751
               true ->
 
1752
                    [binary_to_list(Block), " " | fmt_block(Tail, Sz, I+1, G)]
 
1753
            end;
 
1754
        <<>> ->
 
1755
            [];
 
1756
        _ -> 
 
1757
            [binary_to_list(Bin)]
 
1758
    end.
 
1759
 
 
1760
%% Format integer or binary as hex
 
1761
fmt_bin(X) when integer(X) ->
 
1762
    list_to_binary(io_lib:format("~.16B", [X]));
 
1763
fmt_bin(X) when binary(X) ->
 
1764
    Sz = size(X)*8,
 
1765
    <<Y:Sz/unsigned-big>> = X,
 
1766
    Fmt = "~"++integer_to_list(size(X)*2)++".16.0B",
 
1767
    list_to_binary(io_lib:format(Fmt, [Y])).
 
1768
 
 
1769
-endif.
 
1770
 
 
1771
%% Retrieve session_id from ssh, needed by public-key auth
 
1772
get_session_id(SSH) ->
 
1773
    {ok, SessionID} = call(SSH, get_session_id),
 
1774
    SessionID.