~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_pem.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%
2
 
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
5
 
%% 
6
 
%% The contents of this file are subject to the Erlang Public License,
7
 
%% Version 1.1, (the "License"); you may not use this file except in
8
 
%% compliance with the License. You should have received a copy of the
9
 
%% Erlang Public License along with this software. If not, it can be
10
 
%% retrieved online at http://www.erlang.org/.
11
 
%% 
12
 
%% Software distributed under the License is distributed on an "AS IS"
13
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
 
%% the License for the specific language governing rights and limitations
15
 
%% under the License.
16
 
%% 
17
 
%% %CopyrightEnd%
18
 
%%
19
 
 
20
 
%%
21
 
 
22
 
-module(ssl_pem).
23
 
 
24
 
%%% Purpose: Reading and writing of PEM type encoded files for SSL.
25
 
 
26
 
%% NB write_file/2 is only preliminary.
27
 
 
28
 
%% PEM encoded files have the following structure:
29
 
%%
30
 
%%      <text>
31
 
%%      -----BEGIN SOMETHING-----<CR><LF>
32
 
%%      <Base64 encoding line><CR><LF>
33
 
%%      <Base64 encoding line><CR><LF>
34
 
%%      ...
35
 
%%      -----END SOMETHING-----<CR><LF>
36
 
%%      <text>
37
 
%%
38
 
%% A file can contain several BEGIN/END blocks. Text lines between
39
 
%% blocks are ignored.
40
 
 
41
 
-export([read_file/1, read_file/2, write_file/2]).
42
 
 
43
 
%% Read a PEM file and return each decoding as a binary. 
44
 
 
45
 
read_file(File) ->
46
 
    read_file(File, no_passwd).
47
 
 
48
 
read_file(File, Passwd) ->
49
 
    {ok, Fd} = file:open(File, [read]),
50
 
    Result = decode_file(Fd, Passwd),
51
 
    file:close(Fd),
52
 
    Result.
53
 
 
54
 
decode_file(Fd, Passwd) ->
55
 
    decode_file(Fd, [], [], notag, [Passwd]).
56
 
 
57
 
decode_file(Fd, _RLs, Ens, notag, Info) ->
58
 
    case io:get_line(Fd, "") of
59
 
        "-----BEGIN CERTIFICATE REQUEST-----" ++ _ ->
60
 
            decode_file(Fd, [], Ens, cert_req, Info);
61
 
        "-----BEGIN CERTIFICATE-----" ++ _ ->
62
 
            decode_file(Fd, [], Ens, cert, Info);
63
 
        "-----BEGIN RSA PRIVATE KEY-----" ++ _ ->
64
 
            decode_file(Fd, [], Ens, rsa_private_key, Info);
65
 
        eof ->
66
 
            {ok, lists:reverse(Ens)};
67
 
        _ ->
68
 
            decode_file(Fd, [], Ens, notag, Info)
69
 
    end;
70
 
decode_file(Fd, RLs, Ens, Tag, Info0) ->
71
 
    case io:get_line(Fd, "") of
72
 
        "Proc-Type: 4,ENCRYPTED"++_ ->
73
 
            Info = dek_info(Fd, Info0),
74
 
            decode_file(Fd, RLs, Ens, Tag, Info);
75
 
        "-----END" ++ _ ->                      % XXX sloppy
76
 
            Cs = lists:flatten(lists:reverse(RLs)),
77
 
            Bin = ssl_base64:join_decode(Cs),
78
 
            case Info0 of
79
 
                [Password, Cipher, SaltHex | Info1] ->
80
 
                    Decoded = decode_key(Bin, Password, Cipher, unhex(SaltHex)),
81
 
                    decode_file(Fd, [], [{Tag, Decoded}| Ens], notag, Info1);
82
 
                _ ->
83
 
                    decode_file(Fd, [], [{Tag, Bin}| Ens], notag, Info0)
84
 
            end;
85
 
        eof ->
86
 
            {ok, lists:reverse(Ens)};
87
 
        L ->
88
 
            decode_file(Fd, [L|RLs], Ens, Tag, Info0)
89
 
    end.
90
 
 
91
 
dek_info(Fd, Info) ->
92
 
    Line = io:get_line(Fd, ""),
93
 
    [_, DekInfo0] = string:tokens(Line, ": "),
94
 
    DekInfo1 = string:tokens(DekInfo0, ",\n"), 
95
 
    Info ++ DekInfo1.
96
 
 
97
 
unhex(S) ->
98
 
    unhex(S, []).
99
 
 
100
 
unhex("", Acc) ->
101
 
    lists:reverse(Acc);
102
 
unhex([D1, D2 | Rest], Acc) ->
103
 
    unhex(Rest, [erlang:list_to_integer([D1, D2], 16) | Acc]).
104
 
 
105
 
decode_key(Data, Password, "DES-CBC", Salt) ->
106
 
    Key = password_to_key(Password, Salt, 8),
107
 
    IV = Salt,
108
 
    crypto:des_cbc_decrypt(Key, IV, Data);
109
 
decode_key(Data,  Password, "DES-EDE3-CBC", Salt) ->
110
 
    Key = password_to_key(Password, Salt, 24),
111
 
    IV = Salt,
112
 
    <<Key1:8/binary, Key2:8/binary, Key3:8/binary>> = Key,
113
 
    crypto:des_ede3_cbc_decrypt(Key1, Key2, Key3, IV, Data).
114
 
 
115
 
write_file(File, Ds) ->
116
 
    file:write_file(File, encode_file(Ds)).
117
 
 
118
 
encode_file(Ds) ->
119
 
    [encode_file_1(D) || D <- Ds].
120
 
 
121
 
encode_file_1({cert, Bin}) -> 
122
 
    %% PKIX (X.509)
123
 
    ["-----BEGIN CERTIFICATE-----\n",
124
 
     ssl_base64:encode_split(Bin),
125
 
     "-----END CERTIFICATE-----\n\n"];
126
 
encode_file_1({cert_req, Bin}) -> 
127
 
    %% PKCS#10
128
 
    ["-----BEGIN CERTIFICATE REQUEST-----\n",
129
 
     ssl_base64:encode_split(Bin),
130
 
     "-----END CERTIFICATE REQUEST-----\n\n"];
131
 
encode_file_1({rsa_private_key, Bin}) -> 
132
 
    %% PKCS#?
133
 
    ["XXX Following key assumed not encrypted\n",
134
 
     "-----BEGIN RSA PRIVATE KEY-----\n",
135
 
     ssl_base64:encode_split(Bin),
136
 
     "-----END RSA PRIVATE KEY-----\n\n"].
137
 
 
138
 
password_to_key(Data, Salt, KeyLen) ->
139
 
    <<Key:KeyLen/binary, _/binary>> = 
140
 
        password_to_key(<<>>, Data, Salt, KeyLen, <<>>),
141
 
    Key.
142
 
 
143
 
password_to_key(_, _, _, Len, Acc) when Len =< 0 ->
144
 
    Acc;
145
 
password_to_key(Prev, Data, Salt, Len, Acc) ->
146
 
    M = crypto:md5([Prev, Data, Salt]),
147
 
    password_to_key(M, Data, Salt, Len - byte_size(M), <<Acc/binary, M/binary>>).