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

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_file.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 file handling
 
20
 
 
21
-module(ssh_file).
 
22
 
 
23
-include("ssh.hrl").
 
24
-include("PKCS-1.hrl").
 
25
-include("DSS.hrl").
 
26
 
 
27
-export([public_host_dsa_key/2,private_host_dsa_key/2,
 
28
         public_host_rsa_key/2,private_host_rsa_key/2,
 
29
         public_host_key/2,private_host_key/2,
 
30
         lookup_host_key/3, add_host_key/3, del_host_key/2,
 
31
         lookup_user_key/3, ssh_dir/2, file_name/3]).
 
32
 
 
33
-export([private_identity_key/2]).
 
34
%% , public_identity_key/2,
 
35
%%       identity_keys/2]).
 
36
 
 
37
-export([encode_public_key/1, decode_public_key_v2/2]).
 
38
 
 
39
-import(lists, [reverse/1, append/1]).
 
40
 
 
41
-define(DBG_PATHS, true).
 
42
 
 
43
%% API
 
44
public_host_dsa_key(Type, Opts) ->
 
45
    File = file_name(Type, "ssh_host_dsa_key.pub", Opts),
 
46
    read_public_key_v2(File, "ssh-dss").
 
47
 
 
48
private_host_dsa_key(Type, Opts) ->
 
49
    File = file_name(Type, "ssh_host_dsa_key", Opts),
 
50
    read_private_key_v2(File, "ssh-dss").
 
51
 
 
52
public_host_rsa_key(Type, Opts) ->
 
53
    File = file_name(Type, "ssh_host_rsa_key.pub", Opts),
 
54
    read_public_key_v2(File, "ssh-rsa").
 
55
 
 
56
private_host_rsa_key(Type, Opts) ->
 
57
    File = file_name(Type, "ssh_host_rsa_key", Opts),
 
58
    read_private_key_v2(File, "ssh-rsa").
 
59
 
 
60
public_host_key(Type, Opts) ->
 
61
    File = file_name(Type, "ssh_host_key", Opts),
 
62
    case read_private_key_v1(File,public) of
 
63
        {error, enoent} ->      
 
64
            read_public_key_v1(File++".pub");
 
65
        Result ->
 
66
            Result
 
67
    end.
 
68
            
 
69
 
 
70
private_host_key(Type, Opts) ->
 
71
    File = file_name(Type, "ssh_host_key", Opts),
 
72
    read_private_key_v1(File,private).
 
73
 
 
74
 
 
75
 
 
76
%% in: "host" out: "host,1.2.3.4.
 
77
add_ip(Host)                                                             ->
 
78
    case inet:getaddr(Host, inet) of
 
79
        {ok, Addr} ->
 
80
            case ssh_cm:encode_ip(Addr) of
 
81
                false -> Host;
 
82
                IPString -> Host ++ "," ++ IPString
 
83
            end;
 
84
        _ -> Host
 
85
    end.    
 
86
 
 
87
replace_localhost("localhost") ->
 
88
    {ok, Hostname} = inet:gethostname(),
 
89
    Hostname;
 
90
replace_localhost(Host) ->
 
91
    Host.
 
92
 
 
93
%% lookup_host_key
 
94
%% return {ok, Key(s)} or {error, not_found}
 
95
%%
 
96
 
 
97
lookup_host_key(Host, Alg, Opts) ->
 
98
    case replace_localhost(Host) of
 
99
        Host ->
 
100
            do_lookup_host_key(Host, Alg, Opts);
 
101
        Host1 ->
 
102
            case do_lookup_host_key(Host, Alg, Opts) of
 
103
                {error, not_found} ->
 
104
                    do_lookup_host_key(Host1, Alg, Opts);
 
105
                Other ->
 
106
                    Other
 
107
            end
 
108
    end.
 
109
            
 
110
do_lookup_host_key(Host, Alg, Opts) ->
 
111
    case file:open(file_name(user, "known_hosts", Opts), [read]) of
 
112
        {ok, Fd} ->
 
113
            Res = lookup_host_key_fd(Fd, Host, Alg),
 
114
            file:close(Fd),
 
115
            Res;
 
116
        {error, enoent} -> {error, not_found};
 
117
        Error -> Error
 
118
    end.
 
119
 
 
120
add_host_key(Host, Key, Opts) ->
 
121
    Host1 = add_ip(replace_localhost(Host)),
 
122
    case file:open(file_name(user, "known_hosts", Opts),[write,append]) of
 
123
        {ok, Fd} ->
 
124
            Res = add_key_fd(Fd, Host1, Key),
 
125
            file:close(Fd),
 
126
            Res;
 
127
        Error ->
 
128
            Error
 
129
    end.
 
130
 
 
131
del_host_key(Host, Opts) ->
 
132
    Host1 = replace_localhost(Host),
 
133
    case file:open(file_name(user, "known_hosts", Opts),[write,read]) of
 
134
        {ok, Fd} ->
 
135
            Res = del_key_fd(Fd, Host1),
 
136
            file:close(Fd),
 
137
            Res;
 
138
        Error ->
 
139
            Error
 
140
    end.
 
141
 
 
142
identity_key_filename("ssh-dss") -> "id_dsa";
 
143
identity_key_filename("ssh-rsa") -> "id_rsa".
 
144
 
 
145
private_identity_key(Alg, Opts) ->
 
146
    Path = file_name(user, identity_key_filename(Alg), Opts),
 
147
    read_private_key_v2(Path, Alg).
 
148
 
 
149
read_public_key_v2(File, Type) ->
 
150
    case file:read_file(File) of
 
151
        {ok,Bin} ->
 
152
            List = binary_to_list(Bin),
 
153
            case lists:prefix(Type, List) of
 
154
                true ->
 
155
                    List1 = lists:nthtail(length(Type), List),
 
156
                    K_S = ssh_bits:b64_decode(List1),
 
157
                    decode_public_key_v2(K_S, Type);
 
158
                false ->
 
159
                    {error, bad_format}
 
160
            end;
 
161
        Error ->
 
162
            Error
 
163
    end.
 
164
 
 
165
decode_public_key_v2(K_S, "ssh-rsa") ->
 
166
    case ssh_bits:decode(K_S,[string,mpint,mpint]) of
 
167
        ["ssh-rsa", E, N] ->
 
168
            {ok, #ssh_key { type = rsa,
 
169
                            public = {N,E},
 
170
                            comment=""}};
 
171
        _ ->
 
172
            {error, bad_format}
 
173
    end;
 
174
decode_public_key_v2(K_S, "ssh-dss") ->
 
175
    case ssh_bits:decode(K_S,[string,mpint,mpint,mpint,mpint]) of
 
176
        ["ssh-dss",P,Q,G,Y] ->
 
177
            {ok,#ssh_key { type = dsa,
 
178
                           public = {P,Q,G,Y}
 
179
                          }};
 
180
        _A ->
 
181
            {error, bad_format}
 
182
    end;
 
183
decode_public_key_v2(_, _) ->
 
184
    {error, bad_format}.
 
185
    
 
186
 
 
187
read_public_key_v1(File) ->
 
188
    case file:read_file(File) of
 
189
        {ok,Bin} ->
 
190
            List = binary_to_list(Bin),
 
191
            case io_lib:fread("~d ~d ~d ~s", List) of
 
192
                {ok,[_Sz,E,N,Comment],_} ->
 
193
                    {ok,#ssh_key { type = rsa,
 
194
                                   public ={N,E},
 
195
                                   comment = Comment }};
 
196
                _Error ->
 
197
                    {error, bad_format}
 
198
            end;
 
199
        Error ->
 
200
            Error
 
201
    end.
 
202
 
 
203
pem_type("ssh-dss") -> "DSA";
 
204
pem_type("ssh-rsa") -> "RSA".
 
205
 
 
206
read_private_key_v2(File, Type) ->
 
207
    case file:read_file(File) of
 
208
        {ok,Bin} ->
 
209
            case read_pem(binary_to_list(Bin), pem_type(Type)) of
 
210
                {ok,Bin1} ->
 
211
                    decode_private_key_v2(Bin1, Type);
 
212
                Error ->
 
213
                    Error
 
214
            end;
 
215
        Error ->
 
216
            Error
 
217
    end.
 
218
 
 
219
decode_private_key_v2(Private,"ssh-rsa") ->
 
220
    case asn1rt:decode('PKCS-1', 'RSAPrivateKey', Private) of
 
221
        {ok,RSA} -> %% FIXME Check for two-prime version
 
222
            {ok, #ssh_key { type = rsa,
 
223
                            public = {RSA#'RSAPrivateKey'.modulus,
 
224
                                      RSA#'RSAPrivateKey'.publicExponent},
 
225
                            private = {RSA#'RSAPrivateKey'.modulus,
 
226
                                       RSA#'RSAPrivateKey'.privateExponent}
 
227
                            }};
 
228
        Error ->
 
229
            Error
 
230
    end;
 
231
decode_private_key_v2(Private, "ssh-dss") ->
 
232
    case asn1rt:decode('DSS', 'DSAPrivateKey', Private) of
 
233
        {ok,DSA} -> %% FIXME Check for two-prime version
 
234
            {ok, #ssh_key { type = dsa,
 
235
                            public = {DSA#'DSAPrivateKey'.p,
 
236
                                      DSA#'DSAPrivateKey'.q,
 
237
                                      DSA#'DSAPrivateKey'.g,
 
238
                                      DSA#'DSAPrivateKey'.y},
 
239
                            private= {DSA#'DSAPrivateKey'.p,
 
240
                                      DSA#'DSAPrivateKey'.q,
 
241
                                      DSA#'DSAPrivateKey'.g,
 
242
                                      DSA#'DSAPrivateKey'.x}
 
243
                           }};
 
244
        _ ->
 
245
            {error,bad_format}
 
246
    end.
 
247
 
 
248
%% SSH1 private key format
 
249
%%  <<"SSH PRIVATE KEY FILE FORMATE 1.1\n" 0:8 
 
250
%%    CipherNum:8, Reserved:32,
 
251
%%    NSz/uint32, N/bignum, E/bignum, Comment/string,
 
252
%%
 
253
%% [ R0:8 R1:8 R0:8 R1:8, D/bignum, IQMP/bignum, Q/bignum, P/bignum, Pad(8)]>>
 
254
%%
 
255
%% where [ ] is encrypted using des3 (ssh1 version) and
 
256
%% a posssibly empty pass phrase using md5(passphase) as key
 
257
%% 
 
258
 
 
259
read_private_key_v1(File, Type) ->
 
260
    case file:read_file(File) of
 
261
        {ok,<<"SSH PRIVATE KEY FILE FORMAT 1.1\n",0,
 
262
             CipherNum,_Resereved:32,Bin/binary>>} ->
 
263
            decode_private_key_v1(Bin, CipherNum,Type);
 
264
        {ok,_} ->
 
265
            {error, bad_format};
 
266
        Error ->
 
267
            Error
 
268
    end.
 
269
 
 
270
decode_private_key_v1(Bin, CipherNum, Type) ->
 
271
    case ssh_bits:decode(Bin,0,[uint32, bignum, bignum, string]) of
 
272
        {Offset,[_NSz,N,E,Comment]} ->
 
273
            if Type == public ->
 
274
                    {ok,#ssh_key { type=rsa,
 
275
                                   public={N,E},
 
276
                                   comment=Comment}};
 
277
               Type == private ->
 
278
                    <<_:Offset/binary, Encrypted/binary>> = Bin,
 
279
                    case ssh_bits:decode(decrypt1(Encrypted, CipherNum),0,
 
280
                                         [uint32, bignum, bignum, 
 
281
                                          bignum, bignum,{pad,8}]) of
 
282
                        {_,[_,D,IQMP,Q,P]} ->
 
283
                            {ok,#ssh_key { type=rsa,
 
284
                                           public={N,E},
 
285
                                           private={D,IQMP,Q,P},
 
286
                                           comment=Comment}};
 
287
                        _ ->
 
288
                            {error,bad_format}
 
289
                    end
 
290
            end;
 
291
        _ ->
 
292
            {error,bad_format}
 
293
    end.
 
294
 
 
295
 
 
296
decrypt1(Bin, CipherNum) ->
 
297
    decrypt1(Bin, CipherNum,"").
 
298
 
 
299
decrypt1(Bin, CipherNum, Phrase) ->
 
300
    if CipherNum == ?SSH_CIPHER_NONE; Phrase == "" ->
 
301
            Bin;
 
302
       CipherNum == ?SSH_CIPHER_3DES ->
 
303
            <<K1:8/binary, K2:8/binary>> = erlang:md5(Phrase),
 
304
            K3 = K1,
 
305
            IV = <<0,0,0,0,0,0,0,0>>,
 
306
            Bin1 = crypto:des_cbc_decrypt(K3,IV,Bin),
 
307
            Bin2 = crypto:des_cbc_encrypt(K2,IV,Bin1),
 
308
            crypto:des_cbc_decrypt(K1,IV,Bin2)
 
309
    end.
 
310
 
 
311
%% encrypt1(Bin, CipherNum) ->
 
312
%%     encrypt1(Bin, CipherNum,"").
 
313
 
 
314
%% encrypt1(Bin, CipherNum, Phrase) ->
 
315
%%     if CipherNum == ?SSH_CIPHER_NONE; Phrase == "" ->
 
316
%%          Bin;
 
317
%%        CipherNum == ?SSH_CIPHER_3DES ->
 
318
%%          <<K1:8/binary, K2:8/binary>> = erlang:md5(Phrase),
 
319
%%          K3 = K1,
 
320
%%          IV = <<0,0,0,0,0,0,0,0>>,
 
321
%%          Bin1 = crypto:des_cbc_encrypt(K1,IV,Bin),
 
322
%%          Bin2 = crypto:des_cbc_decrypt(K2,IV,Bin1),
 
323
%%          crypto:des_cbc_encrypt(K3,IV,Bin2)
 
324
%%     end.
 
325
 
 
326
lookup_host_key_fd(Fd, Host, Alg) ->
 
327
    case io:get_line(Fd, '') of
 
328
        eof ->
 
329
            {error, not_found};
 
330
        Line ->
 
331
            case string:tokens(Line, " ") of
 
332
                [HostList, Alg, KeyData] ->
 
333
                    %%              io:format("lookup_host_key_fd: HostList ~p Alg ~p KeyData ~p\n",
 
334
                    %%                        [HostList, Alg, KeyData]),
 
335
                    case lists:member(Host, string:tokens(HostList, ",")) of
 
336
                        true ->
 
337
                            decode_public_key_v2(ssh_bits:b64_decode(KeyData), Alg);
 
338
                        false ->
 
339
                            lookup_host_key_fd(Fd, Host, Alg)
 
340
                    end;
 
341
                _ ->
 
342
                    lookup_host_key_fd(Fd, Host, Alg)
 
343
            end
 
344
    end.
 
345
 
 
346
 
 
347
 
 
348
del_key_fd(Fd, Host) ->
 
349
    del_key_fd(Fd, Host, 0, 0).
 
350
 
 
351
del_key_fd(Fd, Host, ReadPos0, WritePos0) ->
 
352
    case io:get_line(Fd, '') of
 
353
        eof ->
 
354
            if ReadPos0 == WritePos0 ->
 
355
                    ok;
 
356
               true ->
 
357
                    file:truncate(Fd)
 
358
            end;
 
359
        Line ->
 
360
            {ok,ReadPos1} = file:position(Fd, cur),
 
361
            case string:tokens(Line, " ") of
 
362
                [HostList, _Type, _KeyData] ->
 
363
                    case lists:member(Host, string:tokens(HostList, ",")) of
 
364
                        true ->
 
365
                            del_key_fd(Fd, Host, ReadPos1, WritePos0);
 
366
                        false ->
 
367
                            if ReadPos0 == WritePos0 ->
 
368
                                    del_key_fd(Fd, Host, ReadPos1, ReadPos1);
 
369
                               true ->
 
370
                                    file:position(Fd, WritePos0),
 
371
                                    file:write(Fd, Line),
 
372
                                    {ok,WritePos1} = file:position(Fd,cur),
 
373
                                    del_key_fd(Fd, Host, ReadPos1, WritePos1)
 
374
                            end
 
375
                    end;
 
376
                _ ->
 
377
                    if ReadPos0 == WritePos0 ->
 
378
                            del_key_fd(Fd, Host, ReadPos1, ReadPos1);
 
379
                       true ->
 
380
                            file:position(Fd, WritePos0),
 
381
                            file:write(Fd, Line),
 
382
                            {ok,WritePos1} = file:position(Fd,cur),
 
383
                            del_key_fd(Fd, Host, ReadPos1, WritePos1)
 
384
                    end             
 
385
            end
 
386
    end.
 
387
 
 
388
 
 
389
add_key_fd(Fd, Host, Key) ->
 
390
    case Key#ssh_key.type of
 
391
        rsa ->
 
392
            {N,E} = Key#ssh_key.public,
 
393
            DK = ssh_bits:b64_encode(
 
394
                   ssh_bits:encode(["ssh-rsa",E,N],
 
395
                                   [string,mpint,mpint])),
 
396
            file:write(Fd, [Host, " ssh-rsa ", DK, "\n"]);
 
397
        dsa ->
 
398
            {P,Q,G,Y} = Key#ssh_key.public,
 
399
            DK = ssh_bits:b64_encode(
 
400
                   ssh_bits:encode(["ssh-dss",P,Q,G,Y],
 
401
                                   [string,mpint,mpint,mpint,mpint])),
 
402
            file:write(Fd, [Host, " ssh-dss ", DK, "\n"])
 
403
    end.
 
404
 
 
405
 
 
406
read_pem(Cs, Type) ->
 
407
    case read_line(Cs) of
 
408
        {"-----BEGIN "++Rest,Cs1} ->
 
409
            case string:tokens(Rest, " ") of
 
410
                [Type, "PRIVATE", "KEY-----"] ->
 
411
                    read_pem64(Cs1, [], Type);
 
412
                _ ->
 
413
                    {error, bad_format}
 
414
            end;
 
415
        {"",Cs1} when Cs1 =/= "" ->
 
416
            read_pem(Cs1,Type);
 
417
        {_,""} ->
 
418
            {error, bad_format}
 
419
    end.
 
420
 
 
421
read_pem64(Cs, Acc, Type) ->
 
422
    case read_line(Cs) of
 
423
        {"-----END "++Rest,_Cs1} ->
 
424
            case string:tokens(Rest, " ") of
 
425
                [Type, "PRIVATE", "KEY-----"] ->
 
426
                    {ok,ssh_bits:b64_decode(append(reverse(Acc)))};
 
427
                Toks ->
 
428
                    error_logger:format("ssh: TOKENS=~p\n", [Toks]),
 
429
                    {error, bad_format}
 
430
            end;
 
431
        {B64, Cs1} when Cs1 =/= "" ->
 
432
            read_pem64(Cs1, [B64|Acc], Type);
 
433
        _What ->
 
434
            {error, bad_format}
 
435
    end.
 
436
 
 
437
 
 
438
read_line(Cs) -> read_line(Cs,[]).
 
439
read_line([$\r,$\n|T], Acc) -> {reverse(Acc), T};
 
440
read_line([$\n|T], Acc) -> {reverse(Acc), T};
 
441
read_line([C|T], Acc) -> read_line(T,[C|Acc]);
 
442
read_line([], Acc) -> {reverse(Acc),[]}.
 
443
 
 
444
lookup_user_key(User, Alg, Opts) ->
 
445
    SshDir = ssh_dir({remoteuser,User}, Opts),
 
446
    case lookup_user_key_f(User, SshDir, Alg, "authorized_keys", Opts) of
 
447
        {ok, Key} ->
 
448
            {ok, Key};
 
449
        _ ->
 
450
            lookup_user_key_f(User, SshDir, Alg,  "authorized_keys2", Opts)
 
451
    end.
 
452
 
 
453
lookup_user_key_f(_User, [], _Alg, _F, _Opts) ->
 
454
    {error, nouserdir};
 
455
lookup_user_key_f(_User, nouserdir, _Alg, _F, _Opts) ->
 
456
    {error, nouserdir};
 
457
lookup_user_key_f(_User, Dir, Alg, F, _Opts) ->
 
458
    FileName = filename:join(Dir, F),
 
459
    case file:open(FileName, [read]) of
 
460
        {ok, Fd} ->
 
461
            Res = lookup_user_key_fd(Fd, Alg),
 
462
            file:close(Fd),
 
463
            Res;
 
464
        {error, Reason} ->
 
465
            {error, {{openerr, Reason}, {file, FileName}}}
 
466
    end.
 
467
 
 
468
lookup_user_key_fd(Fd, Alg) ->
 
469
    case io:get_line(Fd, '') of
 
470
        eof ->
 
471
            {error, not_found};
 
472
        Line ->
 
473
            case string:tokens(Line, " ") of
 
474
                [Alg, KeyData, _] ->
 
475
                    %%              io:format("lookup_user_key_fd: HostList ~p Alg ~p KeyData ~p\n",
 
476
                    %%                        [HostList, Alg, KeyData]),
 
477
                    decode_public_key_v2(ssh_bits:b64_decode(KeyData), Alg);
 
478
                _Other ->
 
479
                    ?dbg(false, "key_fd Other: ~w ~w\n", [Alg, _Other]),
 
480
                    lookup_user_key_fd(Fd, Alg)
 
481
            end
 
482
    end.
 
483
 
 
484
 
 
485
encode_public_key(#ssh_key{type = rsa, public = {N, E}}) ->
 
486
    ssh_bits:encode(["ssh-rsa",E,N],
 
487
                    [string,mpint,mpint]);
 
488
encode_public_key(#ssh_key{type = dsa, public = {P,Q,G,Y}}) ->
 
489
    ssh_bits:encode(["ssh-dss",P,Q,G,Y],
 
490
                    [string,mpint,mpint,mpint,mpint]).
 
491
 
 
492
%%
 
493
%% Utils
 
494
%%
 
495
 
 
496
%% server use this to find individual keys for
 
497
%% an individual user when user tries to login
 
498
%% with publickey
 
499
ssh_dir({remoteuser, User}, Opts) ->
 
500
    case proplists:get_value(user_dir_fun, Opts) of
 
501
        undefined ->
 
502
            filename:join(["/home/",User,".ssh"]);
 
503
        FUN ->
 
504
            FUN(User)
 
505
    end;
 
506
 
 
507
%% client use this to find client ssh keys
 
508
ssh_dir(user, Opts) ->
 
509
    Default = filename:join(os:getenv("HOME"), ".ssh"),
 
510
    proplists:get_value(user_dir, Opts, Default);
 
511
%% server use this to find server host keys
 
512
ssh_dir(system, Opts) ->
 
513
    proplists:get_value(system_dir, Opts, "/etc/ssh").
 
514
 
 
515
file_name(Type, Name, Opts) ->
 
516
    FN = filename:join(ssh_dir(Type, Opts), Name),
 
517
    ?dbg(?DBG_PATHS, "file_name: ~p\n", [FN]),
 
518
    FN.