~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/public_key/src/pubkey_pem.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

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
%%% Description: Reading and writing of PEM type encoded files.
 
19
%% PEM encoded files have the following structure:
 
20
%%
 
21
%%      <text>
 
22
%%      -----BEGIN SOMETHING-----<CR><LF>
 
23
%%      <Base64 encoding line><CR><LF>
 
24
%%      <Base64 encoding line><CR><LF>
 
25
%%      ...
 
26
%%      -----END SOMETHING-----<CR><LF>
 
27
%%      <text>
 
28
%%
 
29
%% A file can contain several BEGIN/END blocks. Text lines between
 
30
%% blocks are ignored.
 
31
%%
 
32
%% The encoding is divided into lines separated by <NL>, and each line
 
33
%% is precisely 64 characters long (excluding the <NL> characters,
 
34
%% except the last line which 64 characters long or shorter. <NL> may
 
35
%% follow the last line.
 
36
 
 
37
-module(pubkey_pem).
 
38
 
 
39
-export([read_file/1, read_file/2, write_file/2]).
 
40
-export([decode_key/2]).
 
41
 
 
42
-define(ENCODED_LINE_LENGTH, 64).
 
43
 
 
44
%%====================================================================
 
45
%% Internal application API
 
46
%%====================================================================
 
47
read_file(File) ->
 
48
    read_file(File, no_passwd).
 
49
 
 
50
read_file(File, Passwd) ->
 
51
    {ok, Bin} = file:read_file(File),
 
52
    Result = decode_file(split_bin(Bin), Passwd),    
 
53
    Result.
 
54
 
 
55
write_file(File, Ds) ->
 
56
    file:write_file(File, encode_file(Ds)).
 
57
 
 
58
decode_key({_Type, Bin, not_encrypted}, _) ->
 
59
    Bin;
 
60
decode_key({_Type, Bin, {Chipher,Salt}}, Password) ->
 
61
    decode_key(Bin, Password, Chipher, Salt).
 
62
 
 
63
%%--------------------------------------------------------------------
 
64
%%% Internal functions
 
65
%%--------------------------------------------------------------------
 
66
 
 
67
split_bin(Bin) ->
 
68
    split_bin(0, Bin).
 
69
 
 
70
split_bin(N, Bin) ->
 
71
    case Bin of
 
72
        <<Line:N/binary, "\r\n", Rest/binary>> ->
 
73
            [Line | split_bin(0, Rest)];
 
74
        <<Line:N/binary, "\n", Rest/binary>> ->
 
75
            [Line | split_bin(0, Rest)];
 
76
        <<Line:N/binary>> ->
 
77
            [Line];
 
78
        _ ->
 
79
            split_bin(N+1, Bin)
 
80
    end.
 
81
 
 
82
decode_file(Bin, Passwd) ->
 
83
    decode_file(Bin, [], [Passwd]).
 
84
 
 
85
decode_file([<<"-----BEGIN CERTIFICATE REQUEST-----", _/binary>>|Rest], Ens, Info) ->
 
86
    decode_file2(Rest, [], Ens, cert_req, Info);
 
87
decode_file([<<"-----BEGIN CERTIFICATE-----", _/binary>>|Rest], Ens, Info) ->
 
88
    decode_file2(Rest, [], Ens, cert, Info);
 
89
decode_file([<<"-----BEGIN RSA PRIVATE KEY-----", _/binary>>|Rest], Ens, Info) ->
 
90
    decode_file2(Rest, [], Ens, rsa_private_key, Info);
 
91
decode_file([<<"-----BEGIN DSA PRIVATE KEY-----", _/binary>>|Rest], Ens, Info) ->
 
92
    decode_file2(Rest, [], Ens, dsa_private_key, Info);
 
93
decode_file([<<"-----BEGIN DH PARAMETERS-----", _/binary>>|Rest], Ens, Info) ->
 
94
    decode_file2(Rest, [], Ens, dh_params, Info);
 
95
decode_file([_|Rest], Ens, Info) ->
 
96
    decode_file(Rest, Ens, Info);
 
97
decode_file([], Ens, _Info) ->
 
98
    {ok, lists:reverse(Ens)}.
 
99
 
 
100
decode_file2([<<"Proc-Type: 4,ENCRYPTED", _/binary>>| Rest0], RLs, Ens, Tag, Info0) ->
 
101
    [InfoLine|Rest] = Rest0,
 
102
    Info = dek_info(InfoLine, Info0),
 
103
    decode_file2(Rest, RLs, Ens, Tag, Info);
 
104
decode_file2([<<"-----END", _/binary>>| Rest], RLs, Ens, Tag, Info0) ->
 
105
    Cs = erlang:iolist_to_binary(lists:reverse(RLs)),
 
106
    Bin = base64:mime_decode(Cs),
 
107
    case Info0 of
 
108
        [Password, Cipher, SaltHex | Info1] ->
 
109
            Salt = unhex(SaltHex),
 
110
            Enc = {Cipher, Salt},
 
111
            Decoded = decode_key(Bin, Password, Cipher, Salt),
 
112
            decode_file(Rest, [{Tag, Decoded, Enc}| Ens], Info1);
 
113
        _ ->
 
114
            decode_file(Rest, [{Tag, Bin, not_encrypted}| Ens], Info0)
 
115
    end;
 
116
decode_file2([L|Rest], RLs, Ens, Tag, Info0) ->
 
117
    decode_file2(Rest, [L|RLs], Ens, Tag, Info0);
 
118
decode_file2([], _, Ens, _, _) ->
 
119
    {ok, lists:reverse(Ens)}.
 
120
 
 
121
%% TODO Support same as decode_file
 
122
encode_file(Ds) ->
 
123
    lists:map(
 
124
      fun({cert, Bin}) -> 
 
125
              %% PKIX (X.509)
 
126
              ["-----BEGIN CERTIFICATE-----\n",
 
127
               b64encode_and_split(Bin),
 
128
               "-----END CERTIFICATE-----\n\n"];
 
129
         ({cert_req, Bin}) -> 
 
130
              %% PKCS#10
 
131
              ["-----BEGIN CERTIFICATE REQUEST-----\n",
 
132
               b64encode_and_split(Bin),
 
133
               "-----END CERTIFICATE REQUEST-----\n\n"];
 
134
         ({rsa_private_key, Bin}) -> 
 
135
              %% PKCS#?
 
136
              ["XXX Following key assumed not encrypted\n",
 
137
               "-----BEGIN RSA PRIVATE KEY-----\n",
 
138
               b64encode_and_split(Bin),
 
139
               "-----END RSA PRIVATE KEY-----\n\n"]
 
140
      end, Ds).
 
141
 
 
142
dek_info(Line0, Info) ->
 
143
    Line = binary_to_list(Line0),
 
144
    [_, DekInfo0] = string:tokens(Line, ": "),
 
145
    DekInfo1 = string:tokens(DekInfo0, ",\n"), 
 
146
    Info ++ DekInfo1.
 
147
 
 
148
unhex(S) ->
 
149
    unhex(S, []).
 
150
 
 
151
unhex("", Acc) ->
 
152
    lists:reverse(Acc);
 
153
unhex([D1, D2 | Rest], Acc) ->
 
154
    unhex(Rest, [erlang:list_to_integer([D1, D2], 16) | Acc]).
 
155
 
 
156
decode_key(Data, no_passwd, _Alg, _Salt) ->
 
157
    Data;
 
158
decode_key(Data, Password, "DES-CBC", Salt) ->
 
159
    Key = password_to_key(Password, Salt, 8),
 
160
    IV = Salt,
 
161
    crypto:des_cbc_decrypt(Key, IV, Data);
 
162
decode_key(Data,  Password, "DES-EDE3-CBC", Salt) ->
 
163
    Key = password_to_key(Password, Salt, 24),
 
164
    IV = Salt,
 
165
    <<Key1:8/binary, Key2:8/binary, Key3:8/binary>> = Key,
 
166
    crypto:des_ede3_cbc_decrypt(Key1, Key2, Key3, IV, Data).
 
167
 
 
168
password_to_key(Data, Salt, KeyLen) ->
 
169
    <<Key:KeyLen/binary, _/binary>> = 
 
170
        password_to_key(<<>>, Data, Salt, KeyLen, <<>>),
 
171
    Key.
 
172
 
 
173
password_to_key(_, _, _, Len, Acc) when Len =< 0 ->
 
174
    Acc;
 
175
password_to_key(Prev, Data, Salt, Len, Acc) ->
 
176
    M = crypto:md5([Prev, Data, Salt]),
 
177
    password_to_key(M, Data, Salt, Len - size(M), <<Acc/binary, M/binary>>).
 
178
 
 
179
b64encode_and_split(Bin) ->
 
180
    split_lines(base64:encode(Bin)).
 
181
 
 
182
split_lines(<<Text:?ENCODED_LINE_LENGTH/binary, Rest/binary>>) ->
 
183
    [Text, $\n | split_lines(Rest)];
 
184
split_lines(Bin) ->
 
185
    [Bin, $\n].
 
186