1%% -*- mode: erlang; tab-width: 4; indent-tabs-mode: 1; st-rulers: [70] -*-
2%% vim: ts=4 sw=4 ft=erlang noet
3%%%-------------------------------------------------------------------
4%%% @author Andrew Bennett <potatosaladx@gmail.com>
5%%% @copyright 2014-2015, Andrew Bennett
6%%% @doc PKCS #1: RSA Cryptography Specifications Version 2.1
7%%% See RFC 3447: [https://tools.ietf.org/html/rfc3447]
8%%% @end
9%%% Created :  28 Jul 2015 by Andrew Bennett <potatosaladx@gmail.com>
10%%%-------------------------------------------------------------------
11-module(jose_jwa_pkcs1).
12
13-include_lib("public_key/include/public_key.hrl").
14
15%% Public Key API
16-export([decrypt_private/3]).
17-export([encrypt_public/3]).
18-export([sign/4]).
19-export([verify/5]).
20%% API
21-export([eme_oaep_decode/4]).
22-export([eme_oaep_encode/5]).
23-export([eme_pkcs1_decode/2]).
24-export([eme_pkcs1_encode/2]).
25-export([emsa_pkcs1_encode/4]).
26-export([emsa_pss_encode/3]).
27-export([emsa_pss_encode/4]).
28-export([emsa_pss_verify/4]).
29-export([emsa_pss_verify/5]).
30-export([mgf1/3]).
31-export([rsaes_oaep_decrypt/3]).
32-export([rsaes_oaep_decrypt/4]).
33-export([rsaes_oaep_encrypt/3]).
34-export([rsaes_oaep_encrypt/4]).
35-export([rsaes_oaep_encrypt/5]).
36-export([rsaes_pkcs1_decrypt/2]).
37-export([rsaes_pkcs1_encrypt/2]).
38-export([rsassa_pkcs1_sign/3]).
39-export([rsassa_pkcs1_sign/4]).
40-export([rsassa_pkcs1_verify/4]).
41-export([rsassa_pkcs1_verify/5]).
42-export([rsassa_pss_sign/3]).
43-export([rsassa_pss_sign/4]).
44-export([rsassa_pss_verify/4]).
45-export([rsassa_pss_verify/5]).
46
47%% Types
48-type rsa_digest_type() :: 'md5' | 'sha' | 'sha224' | 'sha256' | 'sha384' | 'sha512'.
49-type rsa_hash_fun()    :: rsa_digest_type() | {hmac, rsa_digest_type(), iodata()} | fun((iodata()) -> binary()).
50-type rsa_public_key()  :: #'RSAPublicKey'{}.
51-type rsa_private_key() :: #'RSAPrivateKey'{}.
52
53-define(PSS_TRAILER_FIELD, 16#BC).
54
55%%====================================================================
56%% Public Key API functions
57%%====================================================================
58
59decrypt_private(CipherText, RSAPrivateKey=#'RSAPrivateKey'{}, Options)
60		when is_list(Options) ->
61	case proplists:get_value(rsa_padding, Options) of
62		rsa_pkcs1_oaep_padding ->
63			Hash = proplists:get_value(rsa_oaep_md, Options, sha),
64			Label = proplists:get_value(rsa_oaep_label, Options, <<>>),
65			rsaes_oaep_decrypt(Hash, CipherText, Label, RSAPrivateKey);
66		rsa_pkcs1_padding ->
67			rsaes_pkcs1_decrypt(CipherText, RSAPrivateKey);
68		_ ->
69			erlang:error(notsup)
70	end;
71decrypt_private(CipherText, PrivateKey, Options) ->
72	erlang:error(badarg, [CipherText, PrivateKey, Options]).
73
74encrypt_public(PlainText, RSAPublicKey=#'RSAPublicKey'{}, Options)
75		when is_list(Options) ->
76	Res = case proplists:get_value(rsa_padding, Options) of
77		rsa_pkcs1_oaep_padding ->
78			Hash = proplists:get_value(rsa_oaep_md, Options, sha),
79			Label = proplists:get_value(rsa_oaep_label, Options, <<>>),
80			rsaes_oaep_encrypt(Hash, PlainText, Label, RSAPublicKey);
81		rsa_pkcs1_padding ->
82			rsaes_pkcs1_encrypt(PlainText, RSAPublicKey);
83		_ ->
84			erlang:error(notsup)
85	end,
86	case Res of
87		{ok, Signature} ->
88			Signature;
89		{error, Reason} ->
90			erlang:error(Reason)
91	end;
92encrypt_public(PlainText, PublicKey, Options) ->
93	erlang:error(badarg, [PlainText, PublicKey, Options]).
94
95sign(Message, DigestType, RSAPrivateKey=#'RSAPrivateKey'{}, Options)
96		when is_list(Options) ->
97	Res = case proplists:get_value(rsa_padding, Options) of
98		rsa_pkcs1_pss_padding ->
99			SaltLen = proplists:get_value(rsa_pss_saltlen, Options, -1),
100			rsassa_pss_sign(DigestType, Message, SaltLen, RSAPrivateKey);
101		rsa_pkcs1_padding ->
102			rsassa_pkcs1_sign(DigestType, Message, RSAPrivateKey);
103		_ ->
104			erlang:error(notsup)
105	end,
106	case Res of
107		{ok, Signature} ->
108			Signature;
109		{error, Reason} ->
110			erlang:error(Reason)
111	end;
112sign(Message, DigestType, PrivateKey, Options) ->
113	erlang:error(badarg, [Message, DigestType, PrivateKey, Options]).
114
115verify(Message, DigestType, Signature, RSAPublicKey=#'RSAPublicKey'{}, Options)
116		when is_list(Options) ->
117	case proplists:get_value(rsa_padding, Options) of
118		rsa_pkcs1_pss_padding ->
119			SaltLen = proplists:get_value(rsa_pss_saltlen, Options, -1),
120			rsassa_pss_verify(DigestType, Message, Signature, SaltLen, RSAPublicKey);
121		rsa_pkcs1_padding ->
122			rsassa_pkcs1_verify(DigestType, Message, Signature, RSAPublicKey);
123		_ ->
124			erlang:error(notsup)
125	end;
126verify(Message, DigestType, Signature, PublicKey, Options) ->
127	erlang:error(badarg, [Message, DigestType, Signature, PublicKey, Options]).
128
129%%====================================================================
130%% API functions
131%%====================================================================
132
133%% See [https://tools.ietf.org/html/rfc3447#section-7.1.2]
134-spec eme_oaep_decode(Hash, EM, Label, K) -> M | error
135	when
136		Hash  :: rsa_hash_fun(),
137		EM    :: binary(),
138		Label :: binary(),
139		K     :: integer(),
140		M     :: binary().
141eme_oaep_decode(Hash, EM, Label, K)
142		when is_function(Hash, 1)
143		andalso is_binary(EM)
144		andalso is_binary(Label)
145		andalso is_integer(K) ->
146	HLen = byte_size(Hash(<<>>)),
147	LHash = Hash(Label),
148	MaskedDBLen = K - HLen - 1,
149	case EM of
150		<< Y, MaskedSeed:HLen/binary, MaskedDB:MaskedDBLen/binary >> ->
151			case mgf1(Hash, MaskedDB, HLen) of
152				{ok, SeedMask} ->
153					Seed = crypto:exor(MaskedSeed, SeedMask),
154					case mgf1(Hash, Seed, K - HLen - 1) of
155						{ok, DBMask} ->
156							DB = crypto:exor(MaskedDB, DBMask),
157							case DB of
158								<< LHashPrime:HLen/binary, DBRight/binary >> ->
159									case {Y, unpad_zero(DBRight), LHashPrime} of
160										{16#00, << 16#01, M/binary >>, LHash} ->
161											M;
162										_BadPS ->
163											error
164									end;
165								_BadDB ->
166									error
167							end;
168						_DBMaskMGF1Error ->
169							error
170					end;
171				_SeedMGF1Error ->
172					error
173			end;
174		_BadEM ->
175			error
176	end;
177eme_oaep_decode(Hash, EM, Label, K)
178		when is_tuple(Hash)
179		orelse is_atom(Hash) ->
180	HashFun = resolve_hash(Hash),
181	eme_oaep_decode(HashFun, EM, Label, K).
182
183%% See [https://tools.ietf.org/html/rfc3447#section-7.1.1]
184-spec eme_oaep_encode(Hash, DM, Label, Seed, K) -> {ok, EM} | {error, Reason}
185	when
186		Hash   :: rsa_hash_fun(),
187		DM     :: binary(),
188		Label  :: binary(),
189		Seed   :: binary(),
190		K      :: integer(),
191		EM     :: binary(),
192		Reason :: term().
193eme_oaep_encode(Hash, DM, Label, Seed, K)
194		when is_function(Hash, 1)
195		andalso is_binary(DM)
196		andalso is_binary(Label)
197		andalso is_binary(Seed)
198		andalso is_integer(K) ->
199	HLen = byte_size(Hash(<<>>)),
200	MLen = byte_size(DM),
201	LHash = Hash(Label),
202	PSLen = ((K - MLen - (2 * HLen) - 2) * 8),
203	PS = case PSLen > 0 of
204		true ->
205			<< 0:PSLen >>;
206		false ->
207			<<>>
208	end,
209	DB = << LHash/binary, PS/binary, 16#01, DM/binary >>,
210	case mgf1(Hash, Seed, K - HLen - 1) of
211		{ok, DBMask} ->
212			MaskedDB = crypto:exor(DB, DBMask),
213			case mgf1(Hash, MaskedDB, HLen) of
214				{ok, SeedMask} ->
215					MaskedSeed = crypto:exor(Seed, SeedMask),
216					EM = << 16#00, MaskedSeed/binary, MaskedDB/binary >>,
217					{ok, EM};
218				MGF1SeedError ->
219					MGF1SeedError
220			end;
221		MGF1Error ->
222			MGF1Error
223	end;
224eme_oaep_encode(Hash, DM, Label, Seed, K)
225		when is_tuple(Hash)
226		orelse is_atom(Hash) ->
227	HashFun = resolve_hash(Hash),
228	eme_oaep_encode(HashFun, DM, Label, Seed, K).
229
230%% See [https://tools.ietf.org/html/rfc3447#section-7.2.2]
231-spec eme_pkcs1_decode(EM, K) -> M | error
232	when
233		EM     :: binary(),
234		K      :: integer(),
235		M      :: binary().
236eme_pkcs1_decode(<< 16#00, 16#02, Rest/binary >>, K)
237		when is_integer(K) ->
238	case binary:split(Rest, << 16#00 >>) of
239		[PS, M] when byte_size(PS) >= 8 ->
240			M;
241		_ ->
242			error
243	end;
244eme_pkcs1_decode(EM, K)
245		when is_binary(EM)
246		andalso is_integer(K) ->
247	error.
248
249%% See [https://tools.ietf.org/html/rfc3447#section-7.2.1]
250-spec eme_pkcs1_encode(DM, K) -> {ok, EM} | {error, Reason}
251	when
252		DM     :: binary(),
253		K      :: integer(),
254		EM     :: binary(),
255		Reason :: term().
256eme_pkcs1_encode(DM, K)
257		when is_binary(DM)
258		andalso is_integer(K) ->
259	MLen = byte_size(DM),
260	PSLen = K - MLen - 3,
261	PS = non_zero_strong_random_bytes(PSLen),
262	EM = << 16#00, 16#02, PS/binary, 16#00, DM/binary >>,
263	{ok, EM}.
264
265%% See [https://tools.ietf.org/html/rfc3447#section-9.2]
266-spec emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits) -> {ok, EM} | {error, Reason}
267	when
268		Hash      :: rsa_hash_fun(),
269		Algorithm :: md5 | sha | sha1 | sha256 | sha384 | sha512 | binary(),
270		Message   :: binary(),
271		EMBits    :: integer(),
272		EM        :: binary(),
273		Reason    :: term().
274emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits)
275		when is_function(Hash, 1)
276		andalso is_binary(Algorithm)
277		andalso is_binary(Message)
278		andalso is_integer(EMBits) ->
279	H = Hash(Message),
280	T = << Algorithm/binary, H/binary >>,
281	TLen = byte_size(T),
282	EMLen = ceiling(EMBits / 8),
283	case EMLen < (TLen + 11) of
284		false ->
285			PSLen = EMLen - TLen - 3,
286			PS = binary:copy(<< 16#FF >>, PSLen),
287			EM = << 16#00, 16#01, PS/binary, 16#00, T/binary >>,
288			{ok, EM};
289		true ->
290			{error, modulus_too_short}
291	end;
292emsa_pkcs1_encode(Hash, md5, Message, EMBits) ->
293	Algorithm = <<
294		16#30, 16#20, 16#30, 16#0c, 16#06, 16#08, 16#2a, 16#86,
295		16#48, 16#86, 16#f7, 16#0d, 16#02, 16#05, 16#05, 16#00,
296		16#04
297	>>,
298	emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits);
299emsa_pkcs1_encode(Hash, sha, Message, EMBits) ->
300	emsa_pkcs1_encode(Hash, sha1, Message, EMBits);
301emsa_pkcs1_encode(Hash, sha1, Message, EMBits) ->
302	Algorithm = <<
303		16#30, 16#21, 16#30, 16#09, 16#06, 16#05, 16#2b, 16#0e,
304		16#03, 16#02, 16#1a, 16#05, 16#00, 16#04, 16#14
305	>>,
306	emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits);
307emsa_pkcs1_encode(Hash, sha256, Message, EMBits) ->
308	Algorithm = <<
309		16#30, 16#31, 16#30, 16#0d, 16#06, 16#09, 16#60, 16#86,
310		16#48, 16#01, 16#65, 16#03, 16#04, 16#02, 16#01, 16#05,
311		16#00, 16#04, 16#20
312	>>,
313	emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits);
314emsa_pkcs1_encode(Hash, sha384, Message, EMBits) ->
315	Algorithm = <<
316		16#30, 16#41, 16#30, 16#0d, 16#06, 16#09, 16#60, 16#86,
317		16#48, 16#01, 16#65, 16#03, 16#04, 16#02, 16#02, 16#05,
318		16#00, 16#04, 16#30
319	>>,
320	emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits);
321emsa_pkcs1_encode(Hash, sha512, Message, EMBits) ->
322	Algorithm = <<
323		16#30, 16#51, 16#30, 16#0d, 16#06, 16#09, 16#60, 16#86,
324		16#48, 16#01, 16#65, 16#03, 16#04, 16#02, 16#03, 16#05,
325		16#00, 16#04, 16#40
326	>>,
327	emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits);
328emsa_pkcs1_encode(Hash, Algorithm, Message, EMBits)
329		when is_atom(Hash) ->
330	HashFun = resolve_hash(Hash),
331	emsa_pkcs1_encode(HashFun, Algorithm, Message, EMBits).
332
333%% See [https://tools.ietf.org/html/rfc3447#section-9.1.1]
334-spec emsa_pss_encode(Hash, Message, EMBits) -> {ok, EM} | {error, Reason}
335	when
336		Hash    :: rsa_hash_fun(),
337		Message :: binary(),
338		EMBits  :: integer(),
339		EM      :: binary(),
340		Reason  :: term().
341emsa_pss_encode(Hash, Message, EMBits)
342		when is_function(Hash, 1)
343		andalso is_binary(Message)
344		andalso is_integer(EMBits) ->
345	emsa_pss_encode(Hash, Message, -2, EMBits);
346emsa_pss_encode(Hash, Message, EMBits)
347		when is_tuple(Hash)
348		orelse is_atom(Hash) ->
349	HashFun = resolve_hash(Hash),
350	emsa_pss_encode(HashFun, Message, EMBits).
351
352%% See [https://tools.ietf.org/html/rfc3447#section-9.1.1]
353-spec emsa_pss_encode(Hash, Message, Salt, EMBits) -> {ok, EM} | {error, Reason}
354	when
355		Hash    :: rsa_hash_fun(),
356		Message :: binary(),
357		Salt    :: binary() | integer(),
358		EMBits  :: integer(),
359		EM      :: binary(),
360		Reason  :: term().
361emsa_pss_encode(Hash, Message, Salt, EMBits)
362		when is_function(Hash, 1)
363		andalso is_binary(Message)
364		andalso is_binary(Salt)
365		andalso is_integer(EMBits) ->
366	MHash = Hash(Message),
367	HashLen = byte_size(MHash),
368	SaltLen = byte_size(Salt),
369	EMLen = ceiling(EMBits / 8),
370	case EMLen < (HashLen + SaltLen + 2) of
371		false ->
372			MPrime = << 0:64, MHash/binary, Salt/binary >>,
373			H = Hash(MPrime),
374			PS = << 0:((EMLen - SaltLen - HashLen - 2) * 8) >>,
375			DB = << PS/binary, 16#01, Salt/binary >>,
376			case mgf1(Hash, H, EMLen - HashLen - 1) of
377				{ok, DBMask} ->
378					LeftBits = (EMLen * 8) - EMBits,
379					<< _:LeftBits/bitstring, MaskedDBRight/bitstring >> = crypto:exor(DB, DBMask),
380					MaskedDB = << 0:LeftBits, MaskedDBRight/bitstring >>,
381					EM = << MaskedDB/binary, H/binary, ?PSS_TRAILER_FIELD >>,
382					{ok, EM};
383				MGF1Error ->
384					MGF1Error
385			end;
386		true ->
387			{error, encoding_error}
388	end;
389emsa_pss_encode(Hash, Message, -2, EMBits)
390		when is_function(Hash, 1)
391		andalso is_integer(EMBits) ->
392	HashLen = byte_size(Hash(<<>>)),
393	EMLen = ceiling(EMBits / 8),
394	SaltLen = EMLen - HashLen - 2,
395	case SaltLen < 0 of
396		false ->
397			emsa_pss_encode(Hash, Message, SaltLen, EMBits);
398		true ->
399			{error, encoding_error}
400	end;
401emsa_pss_encode(Hash, Message, -1, EMBits)
402		when is_function(Hash, 1) ->
403	HashLen = byte_size(Hash(<<>>)),
404	SaltLen = HashLen,
405	emsa_pss_encode(Hash, Message, SaltLen, EMBits);
406emsa_pss_encode(Hash, Message, SaltLen, EMBits)
407		when is_integer(SaltLen)
408		andalso SaltLen >= 0 ->
409	Salt = crypto:strong_rand_bytes(SaltLen),
410	emsa_pss_encode(Hash, Message, Salt, EMBits);
411emsa_pss_encode(Hash, Message, Salt, EMBits)
412		when is_tuple(Hash)
413		orelse is_atom(Hash) ->
414	HashFun = resolve_hash(Hash),
415	emsa_pss_encode(HashFun, Message, Salt, EMBits).
416
417%% See [https://tools.ietf.org/html/rfc3447#section-9.1.2]
418-spec emsa_pss_verify(Hash, Message, EM, EMBits) -> boolean()
419	when
420		Hash    :: rsa_hash_fun(),
421		Message :: binary(),
422		EM      :: binary(),
423		EMBits  :: integer().
424emsa_pss_verify(Hash, Message, EM, EMBits)
425		when is_function(Hash, 1)
426		andalso is_binary(Message)
427		andalso is_binary(EM)
428		andalso is_integer(EMBits) ->
429	emsa_pss_verify(Hash, Message, EM, -2, EMBits);
430emsa_pss_verify(Hash, Message, EM, EMBits)
431		when is_tuple(Hash)
432		orelse is_atom(Hash) ->
433	HashFun = resolve_hash(Hash),
434	emsa_pss_verify(HashFun, Message, EM, EMBits).
435
436%% See [https://tools.ietf.org/html/rfc3447#section-9.1.2]
437-spec emsa_pss_verify(Hash, Message, EM, SaltLen, EMBits) -> boolean()
438	when
439		Hash    :: rsa_hash_fun(),
440		Message :: binary(),
441		EM      :: binary(),
442		SaltLen :: integer(),
443		EMBits  :: integer().
444emsa_pss_verify(Hash, Message, EM, SaltLen, EMBits)
445		when is_function(Hash, 1)
446		andalso is_binary(Message)
447		andalso is_integer(SaltLen)
448		andalso SaltLen >= 0
449		andalso is_integer(EMBits) ->
450	MHash = Hash(Message),
451	HashLen = byte_size(MHash),
452	EMLen = ceiling(EMBits / 8),
453	MaskedDBLen = (EMLen - HashLen - 1),
454	case {EMLen < (HashLen + SaltLen + 2), byte_size(EM), EM} of
455		{false, EMLen, << MaskedDB:MaskedDBLen/binary, H:HashLen/binary, ?PSS_TRAILER_FIELD >>} ->
456			LeftBits = ((EMLen * 8) - EMBits),
457			case MaskedDB of
458				<< 0:LeftBits, _/bitstring >> ->
459					case mgf1(Hash, H, EMLen - HashLen - 1) of
460						{ok, DBMask} ->
461							<< _:LeftBits/bitstring, DBRight/bitstring >> = crypto:exor(MaskedDB, DBMask),
462							DB = << 0:LeftBits, DBRight/bitstring >>,
463							PSLen = ((EMLen - HashLen - SaltLen - 2) * 8),
464							case DB of
465								<< 0:PSLen, 16#01, Salt:SaltLen/binary >> ->
466									MPrime = << 0:64, MHash/binary, Salt/binary >>,
467									HPrime = Hash(MPrime),
468									H =:= HPrime;
469								_BadDB ->
470									false
471							end;
472						_MGF1Error ->
473							false
474					end;
475				_BadMaskedDB ->
476					false
477			end;
478		_BadEMLen ->
479			false
480	end;
481emsa_pss_verify(Hash, Message, EM, -2, EMBits)
482		when is_function(Hash, 1)
483		andalso is_integer(EMBits) ->
484	HashLen = byte_size(Hash(<<>>)),
485	EMLen = ceiling(EMBits / 8),
486	SaltLen = EMLen - HashLen - 2,
487	case SaltLen < 0 of
488		false ->
489			emsa_pss_verify(Hash, Message, EM, SaltLen, EMBits);
490		true ->
491			false
492	end;
493emsa_pss_verify(Hash, Message, EM, -1, EMBits)
494		when is_function(Hash, 1) ->
495	HashLen = byte_size(Hash(<<>>)),
496	SaltLen = HashLen,
497	emsa_pss_verify(Hash, Message, EM, SaltLen, EMBits).
498
499%% See [https://tools.ietf.org/html/rfc3447#appendix-B.2]
500-spec mgf1(Hash, Seed, MaskLen) -> {ok, binary()} | {error, mask_too_long}
501	when
502		Hash    :: rsa_hash_fun(),
503		Seed    :: binary(),
504		MaskLen :: pos_integer().
505mgf1(Hash, Seed, MaskLen)
506		when is_function(Hash, 1)
507		andalso is_binary(Seed)
508		andalso is_integer(MaskLen)
509		andalso MaskLen >= 0 ->
510	HashLen = byte_size(Hash(<<>>)),
511	case MaskLen > (16#FFFFFFFF * HashLen) of
512		false ->
513			Reps = ceiling(MaskLen / HashLen),
514			{ok, derive_mgf1(Hash, 0, Reps, Seed, MaskLen, <<>>)};
515		true ->
516			{error, mask_too_long}
517	end;
518mgf1(Hash, Seed, MaskLen)
519		when is_tuple(Hash)
520		orelse is_atom(Hash) ->
521	HashFun = resolve_hash(Hash),
522	mgf1(HashFun, Seed, MaskLen).
523
524%% See [https://tools.ietf.org/html/rfc3447#section-7.1.2]
525-spec rsaes_oaep_decrypt(Hash, CipherText, RSAPrivateKey) -> PlainText
526	when
527		Hash          :: rsa_hash_fun(),
528		CipherText    :: binary(),
529		RSAPrivateKey :: rsa_private_key(),
530		PlainText     :: binary().
531rsaes_oaep_decrypt(Hash, CipherText, RSAPrivateKey=#'RSAPrivateKey'{})
532		when is_function(Hash, 1)
533		andalso is_binary(CipherText) ->
534	rsaes_oaep_decrypt(Hash, CipherText, <<>>, RSAPrivateKey);
535rsaes_oaep_decrypt(Hash, CipherText, RSAPrivateKey)
536		when is_tuple(Hash)
537		orelse is_atom(Hash) ->
538	HashFun = resolve_hash(Hash),
539	rsaes_oaep_decrypt(HashFun, CipherText, RSAPrivateKey).
540
541%% See [https://tools.ietf.org/html/rfc3447#section-7.1.2]
542-spec rsaes_oaep_decrypt(Hash, CipherText, Label, RSAPrivateKey) -> PlainText
543	when
544		Hash          :: rsa_hash_fun(),
545		CipherText    :: binary(),
546		Label         :: binary(),
547		RSAPrivateKey :: rsa_private_key(),
548		PlainText     :: binary().
549rsaes_oaep_decrypt(Hash, CipherText, Label, RSAPrivateKey=#'RSAPrivateKey'{modulus=N})
550		when is_function(Hash, 1)
551		andalso is_binary(CipherText)
552		andalso is_binary(Label) ->
553	HLen = byte_size(Hash(<<>>)),
554	K = int_to_byte_size(N),
555	case {byte_size(CipherText), K < ((2 * HLen) + 2)} of
556		{K, false} ->
557			EM = pad_to_key_size(K, dp(CipherText, RSAPrivateKey)),
558			eme_oaep_decode(Hash, EM, Label, K);
559		_BadSize ->
560			{error, {badsize, _BadSize}}
561	end;
562rsaes_oaep_decrypt(Hash, CipherText, Label, RSAPrivateKey)
563		when is_tuple(Hash)
564		orelse is_atom(Hash) ->
565	HashFun = resolve_hash(Hash),
566	rsaes_oaep_decrypt(HashFun, CipherText, Label, RSAPrivateKey).
567
568%% See [https://tools.ietf.org/html/rfc3447#section-7.1.1]
569-spec rsaes_oaep_encrypt(Hash, PlainText, RSAPublicKey) -> CipherText
570	when
571		Hash         :: rsa_hash_fun(),
572		PlainText    :: binary(),
573		RSAPublicKey :: rsa_public_key(),
574		CipherText   :: binary().
575rsaes_oaep_encrypt(Hash, PlainText, RSAPublicKey=#'RSAPublicKey'{})
576		when is_function(Hash, 1)
577		andalso is_binary(PlainText) ->
578	rsaes_oaep_encrypt(Hash, PlainText, <<>>, RSAPublicKey);
579rsaes_oaep_encrypt(Hash, PlainText, RSAPublicKey)
580		when is_tuple(Hash)
581		orelse is_atom(Hash) ->
582	HashFun = resolve_hash(Hash),
583	rsaes_oaep_encrypt(HashFun, PlainText, RSAPublicKey).
584
585%% See [https://tools.ietf.org/html/rfc3447#section-7.1.1]
586-spec rsaes_oaep_encrypt(Hash, PlainText, Label, RSAPublicKey) -> CipherText
587	when
588		Hash         :: rsa_hash_fun(),
589		PlainText    :: binary(),
590		Label        :: binary(),
591		RSAPublicKey :: rsa_public_key(),
592		CipherText   :: binary().
593rsaes_oaep_encrypt(Hash, PlainText, Label, RSAPublicKey=#'RSAPublicKey'{})
594		when is_function(Hash, 1)
595		andalso is_binary(PlainText)
596		andalso is_binary(Label) ->
597	HLen = byte_size(Hash(<<>>)),
598	Seed = crypto:strong_rand_bytes(HLen),
599	rsaes_oaep_encrypt(Hash, PlainText, Label, Seed, RSAPublicKey);
600rsaes_oaep_encrypt(Hash, PlainText, Label, RSAPublicKey)
601		when is_tuple(Hash)
602		orelse is_atom(Hash) ->
603	HashFun = resolve_hash(Hash),
604	rsaes_oaep_encrypt(HashFun, PlainText, Label, RSAPublicKey).
605
606%% See [https://tools.ietf.org/html/rfc3447#section-7.1.1]
607-spec rsaes_oaep_encrypt(Hash, PlainText, Label, Seed, RSAPublicKey) -> CipherText
608	when
609		Hash         :: rsa_hash_fun(),
610		PlainText    :: binary(),
611		Label        :: binary(),
612		Seed         :: binary(),
613		RSAPublicKey :: rsa_public_key(),
614		CipherText   :: binary().
615rsaes_oaep_encrypt(Hash, PlainText, Label, Seed, RSAPublicKey=#'RSAPublicKey'{modulus=N})
616		when is_function(Hash, 1)
617		andalso is_binary(PlainText)
618		andalso is_binary(Label)
619		andalso is_binary(Seed) ->
620	HLen = byte_size(Hash(<<>>)),
621	MLen = byte_size(PlainText),
622	K = int_to_byte_size(N),
623	case MLen > (K - (2 * HLen) - 2) of
624		false ->
625			case eme_oaep_encode(Hash, PlainText, Label, Seed, K) of
626				{ok, EM} ->
627					C = pad_to_key_size(K, ep(EM, RSAPublicKey)),
628					{ok, C};
629				EncodingError ->
630					EncodingError
631			end;
632		true ->
633			{error, message_too_long}
634	end;
635rsaes_oaep_encrypt(Hash, PlainText, Label, Seed, RSAPublicKey)
636		when is_tuple(Hash)
637		orelse is_atom(Hash) ->
638	HashFun = resolve_hash(Hash),
639	rsaes_oaep_encrypt(HashFun, PlainText, Label, Seed, RSAPublicKey).
640
641%% See [https://tools.ietf.org/html/rfc3447#section-7.2.2]
642-spec rsaes_pkcs1_decrypt(CipherText, RSAPrivateKey) -> PlainText
643	when
644		CipherText    :: binary(),
645		RSAPrivateKey :: rsa_private_key(),
646		PlainText     :: binary().
647rsaes_pkcs1_decrypt(CipherText, RSAPrivateKey=#'RSAPrivateKey'{modulus=N})
648		when is_binary(CipherText) ->
649	K = int_to_byte_size(N),
650	case {byte_size(CipherText), K < 11} of
651		{K, false} ->
652			EM = pad_to_key_size(K, dp(CipherText, RSAPrivateKey)),
653			eme_pkcs1_decode(EM, K);
654		_BadSize ->
655			{error, {badsize, _BadSize}}
656	end.
657
658%% See [https://tools.ietf.org/html/rfc3447#section-7.2.1]
659-spec rsaes_pkcs1_encrypt(PlainText, RSAPublicKey) -> CipherText
660	when
661		PlainText    :: binary(),
662		RSAPublicKey :: rsa_public_key(),
663		CipherText   :: binary().
664rsaes_pkcs1_encrypt(PlainText, RSAPublicKey=#'RSAPublicKey'{modulus=N})
665		when is_binary(PlainText) ->
666	MLen = byte_size(PlainText),
667	K = int_to_byte_size(N),
668	case MLen > (K - 11) of
669		false ->
670			case eme_pkcs1_encode(PlainText, K) of
671				{ok, EM} ->
672					C = pad_to_key_size(K, ep(EM, RSAPublicKey)),
673					{ok, C};
674				EncodingError ->
675					EncodingError
676			end;
677		true ->
678			{error, message_too_long}
679	end.
680
681%% See [https://tools.ietf.org/html/rfc3447#section-8.1.1]
682-spec rsassa_pkcs1_sign(Hash, Message, RSAPrivateKey) -> {ok, Signature} | {error, Reason}
683	when
684		Hash          :: rsa_hash_fun(),
685		Message       :: binary(),
686		RSAPrivateKey :: rsa_private_key(),
687		Signature     :: binary(),
688		Reason        :: term().
689rsassa_pkcs1_sign(Hash, Message, RSAPrivateKey)
690		when is_atom(Hash) ->
691	rsassa_pkcs1_sign(Hash, Hash, Message, RSAPrivateKey).
692
693%% See [https://tools.ietf.org/html/rfc3447#section-8.1.1]
694-spec rsassa_pkcs1_sign(Hash, Algorithm, Message, RSAPrivateKey) -> {ok, Signature} | {error, Reason}
695	when
696		Hash          :: rsa_hash_fun(),
697		Algorithm     :: md5 | sha | sha1 | sha256 | sha384 | sha512 | binary(),
698		Message       :: binary(),
699		RSAPrivateKey :: rsa_private_key(),
700		Signature     :: binary(),
701		Reason        :: term().
702rsassa_pkcs1_sign(Hash, Algorithm, Message, RSAPrivateKey=#'RSAPrivateKey'{modulus=Modulus})
703		when is_function(Hash, 1)
704		andalso (is_atom(Algorithm) orelse is_binary(Algorithm))
705		andalso is_binary(Message) ->
706	ModBits = int_to_bit_size(Modulus),
707	case emsa_pkcs1_encode(Hash, Algorithm, Message, ModBits - 1) of
708		{ok, EM} ->
709			ModBytes = int_to_byte_size(Modulus),
710			S = pad_to_key_size(ModBytes, dp(EM, RSAPrivateKey)),
711			{ok, S};
712		EncodingError ->
713			EncodingError
714	end;
715rsassa_pkcs1_sign(Hash, Algorithm, Message, RSAPrivateKey=#'RSAPrivateKey'{})
716		when is_atom(Hash) ->
717	HashFun = resolve_hash(Hash),
718	rsassa_pkcs1_sign(HashFun, Algorithm, Message, RSAPrivateKey).
719
720%% See [https://tools.ietf.org/html/rfc3447#section-8.2.2]
721-spec rsassa_pkcs1_verify(Hash, Message, Signature, RSAPublicKey) -> boolean()
722	when
723		Hash         :: rsa_hash_fun(),
724		Message      :: binary(),
725		Signature    :: binary(),
726		RSAPublicKey :: rsa_public_key().
727rsassa_pkcs1_verify(Hash, Message, Signature, RSAPublicKey)
728		when is_atom(Hash) ->
729	rsassa_pkcs1_verify(Hash, Hash, Message, Signature, RSAPublicKey).
730
731%% See [https://tools.ietf.org/html/rfc3447#section-8.2.2]
732-spec rsassa_pkcs1_verify(Hash, Algorithm, Message, Signature, RSAPublicKey) -> boolean()
733	when
734		Hash         :: rsa_hash_fun(),
735		Algorithm    :: md5 | sha | sha1 | sha256 | sha384 | sha512 | binary(),
736		Message      :: binary(),
737		Signature    :: binary(),
738		RSAPublicKey :: rsa_public_key().
739rsassa_pkcs1_verify(Hash, Algorithm, Message, Signature, RSAPublicKey=#'RSAPublicKey'{modulus=Modulus})
740		when is_function(Hash, 1)
741		andalso is_binary(Message)
742		andalso is_binary(Signature) ->
743	ModBytes = int_to_byte_size(Modulus),
744	case byte_size(Signature) =:= ModBytes of
745		true ->
746			ModBits = int_to_bit_size(Modulus),
747			EM = pad_to_key_size(ceiling((ModBits - 1) / 8), ep(Signature, RSAPublicKey)),
748			case emsa_pkcs1_encode(Hash, Algorithm, Message, ModBits - 1) of
749				{ok, EMPrime} ->
750					jose_jwa:constant_time_compare(EM, EMPrime);
751				_ ->
752					false
753			end;
754		false ->
755			false
756	end;
757rsassa_pkcs1_verify(Hash, Algorithm, Message, Signature, RSAPublicKey=#'RSAPublicKey'{})
758		when is_atom(Hash) ->
759	HashFun = resolve_hash(Hash),
760	rsassa_pkcs1_verify(HashFun, Algorithm, Message, Signature, RSAPublicKey).
761
762%% See [https://tools.ietf.org/html/rfc3447#section-8.1.1]
763-spec rsassa_pss_sign(Hash, Message, RSAPrivateKey) -> {ok, Signature} | {error, Reason}
764	when
765		Hash          :: rsa_hash_fun(),
766		Message       :: binary(),
767		RSAPrivateKey :: rsa_private_key(),
768		Signature     :: binary(),
769		Reason        :: term().
770rsassa_pss_sign(Hash, Message, RSAPrivateKey=#'RSAPrivateKey'{modulus=Modulus})
771		when is_function(Hash, 1)
772		andalso is_binary(Message) ->
773	ModBits = int_to_bit_size(Modulus),
774	case emsa_pss_encode(Hash, Message, ModBits - 1) of
775		{ok, EM} ->
776			ModBytes = int_to_byte_size(Modulus),
777			S = pad_to_key_size(ModBytes, dp(EM, RSAPrivateKey)),
778			{ok, S};
779		EncodingError ->
780			EncodingError
781	end;
782rsassa_pss_sign(Hash, Message, RSAPrivateKey=#'RSAPrivateKey'{})
783		when is_tuple(Hash)
784		orelse is_atom(Hash) ->
785	HashFun = resolve_hash(Hash),
786	rsassa_pss_sign(HashFun, Message, RSAPrivateKey).
787
788%% See [https://tools.ietf.org/html/rfc3447#section-8.1.1]
789-spec rsassa_pss_sign(Hash, Message, Salt, RSAPrivateKey) -> {ok, Signature} | {error, Reason}
790	when
791		Hash          :: rsa_hash_fun(),
792		Message       :: binary(),
793		Salt          :: binary() | integer(),
794		RSAPrivateKey :: rsa_private_key(),
795		Signature     :: binary(),
796		Reason        :: term().
797rsassa_pss_sign(Hash, Message, Salt, RSAPrivateKey=#'RSAPrivateKey'{modulus=Modulus})
798		when is_function(Hash, 1)
799		andalso is_binary(Message)
800		andalso (is_binary(Salt) orelse is_integer(Salt)) ->
801	ModBits = int_to_bit_size(Modulus),
802	case emsa_pss_encode(Hash, Message, Salt, ModBits - 1) of
803		{ok, EM} ->
804			ModBytes = int_to_byte_size(Modulus),
805			S = pad_to_key_size(ModBytes, dp(EM, RSAPrivateKey)),
806			{ok, S};
807		EncodingError ->
808			EncodingError
809	end;
810rsassa_pss_sign(Hash, Message, Salt, RSAPrivateKey=#'RSAPrivateKey'{})
811		when is_tuple(Hash)
812		orelse is_atom(Hash) ->
813	HashFun = resolve_hash(Hash),
814	rsassa_pss_sign(HashFun, Message, Salt, RSAPrivateKey).
815
816%% See [https://tools.ietf.org/html/rfc3447#section-8.1.2]
817-spec rsassa_pss_verify(Hash, Message, Signature, RSAPublicKey) -> boolean()
818	when
819		Hash         :: rsa_hash_fun(),
820		Message      :: binary(),
821		Signature    :: binary(),
822		RSAPublicKey :: rsa_public_key().
823rsassa_pss_verify(Hash, Message, Signature, RSAPublicKey=#'RSAPublicKey'{modulus=Modulus})
824		when is_function(Hash, 1)
825		andalso is_binary(Message)
826		andalso is_binary(Signature) ->
827	ModBytes = int_to_byte_size(Modulus),
828	case byte_size(Signature) =:= ModBytes of
829		true ->
830			ModBits = int_to_bit_size(Modulus),
831			EM = pad_to_key_size(ceiling((ModBits - 1) / 8), ep(Signature, RSAPublicKey)),
832			emsa_pss_verify(Hash, Message, EM, ModBits - 1);
833		false ->
834			false
835	end;
836rsassa_pss_verify(Hash, Message, Signature, RSAPublicKey=#'RSAPublicKey'{})
837		when is_tuple(Hash)
838		orelse is_atom(Hash) ->
839	HashFun = resolve_hash(Hash),
840	rsassa_pss_verify(HashFun, Message, Signature, RSAPublicKey).
841
842%% See [https://tools.ietf.org/html/rfc3447#section-8.1.2]
843-spec rsassa_pss_verify(Hash, Message, Signature, SaltLen, RSAPublicKey) -> boolean()
844	when
845		Hash         :: rsa_hash_fun(),
846		Message      :: binary(),
847		Signature    :: binary(),
848		SaltLen      :: integer(),
849		RSAPublicKey :: rsa_public_key().
850rsassa_pss_verify(Hash, Message, Signature, SaltLen, RSAPublicKey=#'RSAPublicKey'{modulus=Modulus})
851		when is_function(Hash, 1)
852		andalso is_binary(Message)
853		andalso is_binary(Signature)
854		andalso is_integer(SaltLen) ->
855	ModBytes = int_to_byte_size(Modulus),
856	case byte_size(Signature) =:= ModBytes of
857		true ->
858			ModBits = int_to_bit_size(Modulus),
859			EM = pad_to_key_size(ceiling((ModBits - 1) / 8), ep(Signature, RSAPublicKey)),
860			emsa_pss_verify(Hash, Message, EM, SaltLen, ModBits - 1);
861		false ->
862			false
863	end;
864rsassa_pss_verify(Hash, Message, Signature, SaltLen, RSAPublicKey=#'RSAPublicKey'{})
865		when is_tuple(Hash)
866		orelse is_atom(Hash) ->
867	HashFun = resolve_hash(Hash),
868	rsassa_pss_verify(HashFun, Message, Signature, SaltLen, RSAPublicKey).
869
870%%%-------------------------------------------------------------------
871%%% Internal functions
872%%%-------------------------------------------------------------------
873
874%% @private
875ceiling(X) when X < 0 ->
876	trunc(X);
877ceiling(X) ->
878	T = trunc(X),
879	case X - T == 0 of
880		false ->
881			T + 1;
882		true ->
883			T
884	end.
885
886%% @private
887derive_mgf1(_Hash, Reps, Reps, _Seed, MaskLen, T) ->
888	binary:part(T, 0, MaskLen);
889derive_mgf1(Hash, Counter, Reps, Seed, MaskLen, T) ->
890	CounterBin = << Counter:8/unsigned-big-integer-unit:4 >>,
891	NewT = << T/binary, (Hash(<< Seed/binary, CounterBin/binary >>))/binary >>,
892	derive_mgf1(Hash, Counter + 1, Reps, Seed, MaskLen, NewT).
893
894%% @private
895dp(B, #'RSAPrivateKey'{modulus=N, privateExponent=E}) ->
896	crypto:mod_pow(B, E, N).
897
898%% @private
899ep(B, #'RSAPublicKey'{modulus=N, publicExponent=E}) ->
900	crypto:mod_pow(B, E, N).
901
902%% @private
903int_to_bit_size(I) ->
904	int_to_bit_size(I, 0).
905
906%% @private
907int_to_bit_size(0, B) ->
908	B;
909int_to_bit_size(I, B) ->
910	int_to_bit_size(I bsr 1, B + 1).
911
912%% @private
913int_to_byte_size(I) ->
914	int_to_byte_size(I, 0).
915
916%% @private
917int_to_byte_size(0, B) ->
918	B;
919int_to_byte_size(I, B) ->
920	int_to_byte_size(I bsr 8, B + 1).
921
922%% @private
923non_zero_strong_random_byte() ->
924	case crypto:strong_rand_bytes(1) of
925		<< 0 >> ->
926			non_zero_strong_random_byte();
927		Byte ->
928			Byte
929	end.
930
931%% @private
932non_zero_strong_random_bytes(N) ->
933	<<
934		<< (case C of
935			0 ->
936				<< (non_zero_strong_random_byte())/binary >>;
937			_ ->
938				<< C >>
939		end)/binary >> || << C >> <= crypto:strong_rand_bytes(N)
940	>>.
941
942%% @private
943pad_to_key_size(Bytes, Data) when byte_size(Data) < Bytes ->
944	pad_to_key_size(Bytes, << 0, Data/binary >>);
945pad_to_key_size(_Bytes, Data) ->
946	Data.
947
948%% @private
949resolve_hash(HashFun) when is_function(HashFun, 1) ->
950	HashFun;
951resolve_hash(DigestType) when is_atom(DigestType) ->
952	fun(Data) ->
953		crypto:hash(DigestType, Data)
954	end;
955resolve_hash({hmac, DigestType, Key}) when is_atom(DigestType) ->
956	fun(Data) ->
957		jose_crypto_compat:mac(hmac, DigestType, Key, Data)
958	end.
959
960%% @private
961unpad_zero(<< 0, Rest/binary >>) ->
962	unpad_zero(Rest);
963unpad_zero(Rest) ->
964	Rest.
965