1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2008-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%
22
23%%% Description: Reading and writing of PEM type encoded files.
24%% PEM encoded files have the following structure:
25%%
26%%	<text>
27%%	-----BEGIN SOMETHING-----<CR><LF>
28%%	<Base64 encoding line><CR><LF>
29%%	<Base64 encoding line><CR><LF>
30%%	...
31%%	-----END SOMETHING-----<CR><LF>
32%%	<text>
33%%
34%% A file can contain several BEGIN/END blocks. Text lines between
35%% blocks are ignored.
36%%
37%% The encoding is divided into lines separated by <NL>, and each line
38%% is precisely 64 characters long (excluding the <NL> characters,
39%% except the last line which 64 characters long or shorter. <NL> may
40%% follow the last line.
41
42-module(pubkey_pem).
43
44-include("public_key.hrl").
45
46-export([encode/1, decode/1, decipher/2, cipher/3]).
47
48-define(ENCODED_LINE_LENGTH, 64).
49
50%%====================================================================
51%% Internal application API
52%%====================================================================
53
54%%--------------------------------------------------------------------
55-spec decode(binary()) -> [public_key:pem_entry()].
56%%
57%% Description: Decodes a PEM binary.
58%%--------------------------------------------------------------------
59decode(Bin) ->
60    decode_pem_entries(
61        binary:split(Bin, [<<"\r\n">>, <<"\r">>, <<"\n">>], [global]), []).
62
63%%--------------------------------------------------------------------
64-spec encode([public_key:pem_entry()]) -> iolist().
65%%
66%% Description: Encodes a list of PEM entries.
67%%--------------------------------------------------------------------
68encode(PemEntries) ->
69    encode_pem_entries(PemEntries).
70
71%%--------------------------------------------------------------------
72-spec decipher({public_key:pki_asn1_type(), DerEncrypted::binary(),
73		{Cipher :: string(), Salt :: iodata() | #'PBES2-params'{}
74					   | {#'PBEParameter'{}, atom()}}},
75	       string()) -> Der::binary().
76%%
77%% Description: Deciphers a decrypted pem entry.
78%%--------------------------------------------------------------------
79decipher({_, DecryptDer, {Cipher, KeyDevParams}}, Password) ->
80    pubkey_pbe:decode(DecryptDer, Password, Cipher, KeyDevParams).
81
82%%--------------------------------------------------------------------
83-spec cipher(Der::binary(), {Cipher :: string(), Salt :: iodata() | #'PBES2-params'{}
84						       | {#'PBEParameter'{}, atom()}},
85	     string()) -> binary().
86%%
87%% Description: Ciphers a PEM entry
88%%--------------------------------------------------------------------
89cipher(Der, {Cipher, KeyDevParams}, Password)->
90    pubkey_pbe:encode(Der, Password, Cipher, KeyDevParams).
91
92%%--------------------------------------------------------------------
93%%% Internal functions
94%%--------------------------------------------------------------------
95encode_pem_entries(Entries) ->
96    [encode_pem_entry(Entry) || Entry <- Entries].
97
98encode_pem_entry({Type, Der, not_encrypted}) ->
99    StartStr = pem_start(Type),
100    [StartStr, "\n", b64encode_and_split(Der), "\n", pem_end(StartStr) ,"\n\n"];
101encode_pem_entry({'PrivateKeyInfo', Der, EncParams}) ->
102    EncDer = encode_encrypted_private_keyinfo(Der, EncParams),
103    StartStr = pem_start('EncryptedPrivateKeyInfo'),
104    [StartStr, "\n", b64encode_and_split(EncDer), "\n", pem_end(StartStr) ,"\n\n"];
105encode_pem_entry({Type, Decrypted, {Cipher, Salt}}) ->
106    StartStr = pem_start(Type),
107    [StartStr,"\n", pem_decrypt(),"\n", pem_decrypt_info(Cipher, Salt),"\n\n",
108     b64encode_and_split(Decrypted), "\n", pem_end(StartStr) ,"\n\n"].
109
110decode_pem_entries([], Entries) ->
111    lists:reverse(Entries);
112decode_pem_entries([<<>>], Entries) ->
113   lists:reverse(Entries);
114decode_pem_entries([<<>> | Lines], Entries) ->
115    decode_pem_entries(Lines, Entries);
116decode_pem_entries([StartLine | Lines], Entries) ->
117    Start = strip_tail_whitespace(StartLine),
118    case pem_end(Start) of
119	undefined ->
120	    decode_pem_entries(Lines, Entries);
121	_End ->
122	    {Entry, RestLines} = join_entry(Lines, []),
123	    decode_pem_entries(RestLines, [decode_pem_entry(Start, Entry) | Entries])
124    end.
125
126strip_tail_whitespace(Bin) when is_binary(Bin) ->
127    strip_tail_whitespace(lists:reverse(binary:bin_to_list(Bin)));
128strip_tail_whitespace([Char|Rest])
129  when Char == $ ;
130       Char == $\t;
131       Char == $\v;
132       Char == $\f;
133       Char == $\r;
134       Char == $\n ->
135    strip_tail_whitespace(Rest);
136strip_tail_whitespace(List) ->
137    binary:list_to_bin(
138        lists:reverse(List)).
139
140decode_pem_entry(Start, [<<"Proc-Type: 4,ENCRYPTED", _/binary>>, Line | Lines]) ->
141    Type = asn1_type(Start),
142    Cs = erlang:iolist_to_binary(Lines),
143    Decoded = base64:mime_decode(Cs),
144    [_, DekInfo0] = string:tokens(binary_to_list(Line), ": "),
145    [Cipher, Salt] = string:tokens(DekInfo0, ","),
146    {Type, Decoded, {Cipher, unhex(Salt)}};
147decode_pem_entry(Start, Lines) ->
148    Type = asn1_type(Start),
149    Cs = erlang:iolist_to_binary(Lines),
150    Decoded = base64:mime_decode(Cs),
151    case Type of
152	'EncryptedPrivateKeyInfo'->
153	    decode_encrypted_private_keyinfo(Decoded);
154	_ ->
155	    {Type, Decoded, not_encrypted}
156    end.
157
158decode_encrypted_private_keyinfo(Der) ->
159    #'EncryptedPrivateKeyInfo'{encryptionAlgorithm = AlgorithmInfo,
160			       encryptedData = Data} =
161	public_key:der_decode('EncryptedPrivateKeyInfo', Der),
162    DecryptParams = pubkey_pbe:decrypt_parameters(AlgorithmInfo),
163    {'PrivateKeyInfo', Data, DecryptParams}.
164
165encode_encrypted_private_keyinfo(EncData, EncryptParmams) ->
166    AlgorithmInfo = pubkey_pbe:encrypt_parameters(EncryptParmams),
167    public_key:der_encode('EncryptedPrivateKeyInfo',
168			  #'EncryptedPrivateKeyInfo'{encryptionAlgorithm = AlgorithmInfo,
169						     encryptedData = EncData}).
170b64encode_and_split(Bin) ->
171    split_lines(base64:encode(Bin)).
172
173split_lines(<<Text:?ENCODED_LINE_LENGTH/binary>>) ->
174    [Text];
175split_lines(<<Text:?ENCODED_LINE_LENGTH/binary, Rest/binary>>) ->
176    [Text, $\n | split_lines(Rest)];
177split_lines(Bin) ->
178    [Bin].
179
180%% Ignore white space at end of line
181join_entry([<<"-----END ", _/binary>>| Lines], Entry) ->
182    {lists:reverse(Entry), Lines};
183join_entry([<<"-----END X509 CRL-----", _/binary>>| Lines], Entry) ->
184    {lists:reverse(Entry), Lines};
185join_entry([Line | Lines], Entry) ->
186    join_entry(Lines, [Line | Entry]).
187
188unhex(S) ->
189    unhex(S, []).
190
191unhex("", Acc) ->
192    list_to_binary(lists:reverse(Acc));
193unhex([D1, D2 | Rest], Acc) ->
194    unhex(Rest, [erlang:list_to_integer([D1, D2], 16) | Acc]).
195
196hexify(L) -> [[hex_byte(B)] || B <- binary_to_list(L)].
197
198hex_byte(B) when B < 16#10 -> ["0", erlang:integer_to_list(B, 16)];
199hex_byte(B) -> erlang:integer_to_list(B, 16).
200
201pem_start('Certificate') ->
202    <<"-----BEGIN CERTIFICATE-----">>;
203pem_start('RSAPrivateKey') ->
204    <<"-----BEGIN RSA PRIVATE KEY-----">>;
205pem_start('RSAPublicKey') ->
206    <<"-----BEGIN RSA PUBLIC KEY-----">>;
207pem_start('SubjectPublicKeyInfo') ->
208    <<"-----BEGIN PUBLIC KEY-----">>;
209pem_start('DSAPrivateKey') ->
210    <<"-----BEGIN DSA PRIVATE KEY-----">>;
211pem_start('DHParameter') ->
212    <<"-----BEGIN DH PARAMETERS-----">>;
213pem_start('PrivateKeyInfo') ->
214    <<"-----BEGIN PRIVATE KEY-----">>;
215pem_start('OneAsymmetricKey') ->
216    <<"-----BEGIN PRIVATE KEY-----">>;
217pem_start('EncryptedPrivateKeyInfo') ->
218    <<"-----BEGIN ENCRYPTED PRIVATE KEY-----">>;
219pem_start('CertificationRequest') ->
220    <<"-----BEGIN CERTIFICATE REQUEST-----">>;
221pem_start('ContentInfo') ->
222    <<"-----BEGIN PKCS7-----">>;
223pem_start('CertificateList') ->
224     <<"-----BEGIN X509 CRL-----">>;
225pem_start('EcpkParameters') ->
226    <<"-----BEGIN EC PARAMETERS-----">>;
227pem_start('ECPrivateKey') ->
228    <<"-----BEGIN EC PRIVATE KEY-----">>;
229pem_start({no_asn1, new_openssh}) ->  %% Temporarily in the prototype of this format
230    <<"-----BEGIN OPENSSH PRIVATE KEY-----">>.
231
232pem_end(<<"-----BEGIN CERTIFICATE-----">>) ->
233    <<"-----END CERTIFICATE-----">>;
234pem_end(<<"-----BEGIN RSA PRIVATE KEY-----">>) ->
235    <<"-----END RSA PRIVATE KEY-----">>;
236pem_end(<<"-----BEGIN RSA PUBLIC KEY-----">>) ->
237    <<"-----END RSA PUBLIC KEY-----">>;
238pem_end(<<"-----BEGIN PUBLIC KEY-----">>) ->
239    <<"-----END PUBLIC KEY-----">>;
240pem_end(<<"-----BEGIN DSA PRIVATE KEY-----">>) ->
241    <<"-----END DSA PRIVATE KEY-----">>;
242pem_end(<<"-----BEGIN DH PARAMETERS-----">>) ->
243    <<"-----END DH PARAMETERS-----">>;
244pem_end(<<"-----BEGIN PRIVATE KEY-----">>) ->
245    <<"-----END PRIVATE KEY-----">>;
246pem_end(<<"-----BEGIN ENCRYPTED PRIVATE KEY-----">>) ->
247    <<"-----END ENCRYPTED PRIVATE KEY-----">>;
248pem_end(<<"-----BEGIN CERTIFICATE REQUEST-----">>) ->
249    <<"-----END CERTIFICATE REQUEST-----">>;
250pem_end(<<"-----BEGIN PKCS7-----">>) ->
251    <<"-----END PKCS7-----">>;
252pem_end(<<"-----BEGIN X509 CRL-----">>) ->
253    <<"-----END X509 CRL-----">>;
254pem_end(<<"-----BEGIN EC PARAMETERS-----">>) ->
255    <<"-----END EC PARAMETERS-----">>;
256pem_end(<<"-----BEGIN EC PRIVATE KEY-----">>) ->
257    <<"-----END EC PRIVATE KEY-----">>;
258pem_end(<<"-----BEGIN OPENSSH PRIVATE KEY-----">>) ->
259    <<"-----END OPENSSH PRIVATE KEY-----">>;
260pem_end(_) ->
261    undefined.
262
263asn1_type(<<"-----BEGIN CERTIFICATE-----">>) ->
264    'Certificate';
265asn1_type(<<"-----BEGIN RSA PRIVATE KEY-----">>) ->
266    'RSAPrivateKey';
267asn1_type(<<"-----BEGIN RSA PUBLIC KEY-----">>) ->
268    'RSAPublicKey';
269asn1_type(<<"-----BEGIN PUBLIC KEY-----">>) ->
270    'SubjectPublicKeyInfo';
271asn1_type(<<"-----BEGIN DSA PRIVATE KEY-----">>) ->
272    'DSAPrivateKey';
273asn1_type(<<"-----BEGIN DH PARAMETERS-----">>) ->
274    'DHParameter';
275asn1_type(<<"-----BEGIN PRIVATE KEY-----">>) ->
276    'PrivateKeyInfo';
277asn1_type(<<"-----BEGIN ENCRYPTED PRIVATE KEY-----">>) ->
278    'EncryptedPrivateKeyInfo';
279asn1_type(<<"-----BEGIN CERTIFICATE REQUEST-----">>) ->
280    'CertificationRequest';
281asn1_type(<<"-----BEGIN PKCS7-----">>) ->
282    'ContentInfo';
283asn1_type(<<"-----BEGIN X509 CRL-----">>) ->
284    'CertificateList';
285asn1_type(<<"-----BEGIN EC PARAMETERS-----">>) ->
286    'EcpkParameters';
287asn1_type(<<"-----BEGIN EC PRIVATE KEY-----">>) ->
288    'ECPrivateKey';
289asn1_type(<<"-----BEGIN OPENSSH PRIVATE KEY-----">>) ->
290    {no_asn1, new_openssh}. %% Temporarily in the prototype of this format
291
292
293pem_decrypt() ->
294    <<"Proc-Type: 4,ENCRYPTED">>.
295
296pem_decrypt_info(Cipher, Salt) ->
297    io_lib:format("DEK-Info: ~s,~s", [Cipher, lists:flatten(hexify(Salt))]).
298