1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2010-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 #include "hash.h"
22 #include "digest.h"
23 
24 #ifdef HAVE_MD5
25 #  define MD5_CTX_LEN       (sizeof(MD5_CTX))
26 #endif
27 #ifdef HAVE_MD4
28 #  define MD4_CTX_LEN       (sizeof(MD4_CTX))
29 #endif
30 #ifdef HAVE_RIPEMD160
31 #  define RIPEMD160_CTX_LEN (sizeof(RIPEMD160_CTX))
32 #endif
33 
34 #if OPENSSL_VERSION_NUMBER >= PACKED_OPENSSL_VERSION_PLAIN(1,0,0)
35 struct evp_md_ctx {
36     EVP_MD_CTX* ctx;
37 };
38 
39 /* Define resource types for OpenSSL context structures. */
40 static ErlNifResourceType* evp_md_ctx_rtype;
41 
evp_md_ctx_dtor(ErlNifEnv * env,struct evp_md_ctx * ctx)42 static void evp_md_ctx_dtor(ErlNifEnv* env, struct evp_md_ctx *ctx) {
43     if (ctx == NULL)
44         return;
45 
46     if (ctx->ctx)
47         EVP_MD_CTX_free(ctx->ctx);
48 }
49 #endif
50 
init_hash_ctx(ErlNifEnv * env)51 int init_hash_ctx(ErlNifEnv* env) {
52 #if OPENSSL_VERSION_NUMBER >= PACKED_OPENSSL_VERSION_PLAIN(1,0,0)
53     evp_md_ctx_rtype = enif_open_resource_type(env, NULL, "EVP_MD_CTX",
54                                                (ErlNifResourceDtor*) evp_md_ctx_dtor,
55                                                ERL_NIF_RT_CREATE|ERL_NIF_RT_TAKEOVER,
56                                                NULL);
57     if (evp_md_ctx_rtype == NULL)
58         goto err;
59 #endif
60 
61     return 1;
62 
63 #if OPENSSL_VERSION_NUMBER >= PACKED_OPENSSL_VERSION_PLAIN(1,0,0)
64  err:
65     PRINTF_ERR0("CRYPTO: Could not open resource type 'EVP_MD_CTX'");
66     return 0;
67 #endif
68 }
69 
hash_info_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])70 ERL_NIF_TERM hash_info_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
71 {/* (Type) */
72     struct digest_type_t *digp = NULL;
73     const EVP_MD         *md;
74     ERL_NIF_TERM         ret;
75 
76     ASSERT(argc == 1);
77 
78     if ((digp = get_digest_type(argv[0])) == NULL)
79         return enif_make_badarg(env);
80 
81     if ((md = digp->md.p) == NULL)
82         return atom_notsup;
83 
84     ret = enif_make_new_map(env);
85 
86     enif_make_map_put(env, ret, atom_type,
87         enif_make_int(env, EVP_MD_type(md)), &ret);
88     enif_make_map_put(env, ret, atom_size,
89         enif_make_int(env, EVP_MD_size(md)), &ret);
90     enif_make_map_put(env, ret, atom_block_size,
91         enif_make_int(env, EVP_MD_block_size(md)), &ret);
92 
93     return ret;
94 }
95 
hash_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])96 ERL_NIF_TERM hash_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
97 {/* (Type, Data) */
98     struct digest_type_t *digp = NULL;
99     const EVP_MD         *md;
100     ErlNifBinary         data;
101     ERL_NIF_TERM         ret;
102     unsigned             ret_size;
103     unsigned char        *outp;
104 
105     ASSERT(argc == 2);
106 
107     if ((digp = get_digest_type(argv[0])) == NULL)
108         goto bad_arg;
109     if (!enif_inspect_iolist_as_binary(env, argv[1], &data))
110         goto bad_arg;
111 
112     if ((md = digp->md.p) == NULL)
113         goto err;
114 
115     ret_size = (unsigned)EVP_MD_size(md);
116     ASSERT(0 < ret_size && ret_size <= EVP_MAX_MD_SIZE);
117 
118     if ((outp = enif_make_new_binary(env, ret_size, &ret)) == NULL)
119         goto err;
120     if (EVP_Digest(data.data, data.size, outp, &ret_size, md, NULL) != 1)
121         goto err;
122 
123     ASSERT(ret_size == (unsigned)EVP_MD_size(md));
124 
125     CONSUME_REDS(env, data);
126     return ret;
127 
128  bad_arg:
129     return enif_make_badarg(env);
130 
131  err:
132     return atom_notsup;
133 }
134 
135 #if OPENSSL_VERSION_NUMBER >= PACKED_OPENSSL_VERSION_PLAIN(1,0,0)
136 
hash_init_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])137 ERL_NIF_TERM hash_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
138 {/* (Type) */
139     struct digest_type_t *digp = NULL;
140     struct evp_md_ctx    *ctx = NULL;
141     ERL_NIF_TERM         ret;
142 
143     ASSERT(argc == 1);
144 
145     if ((digp = get_digest_type(argv[0])) == NULL)
146         goto bad_arg;
147     if (digp->md.p == NULL)
148         goto err;
149 
150     if ((ctx = enif_alloc_resource(evp_md_ctx_rtype, sizeof(struct evp_md_ctx))) == NULL)
151         goto err;
152     if ((ctx->ctx = EVP_MD_CTX_new()) == NULL)
153         goto err;
154     if (EVP_DigestInit(ctx->ctx, digp->md.p) != 1)
155         goto err;
156 
157     ret = enif_make_resource(env, ctx);
158     goto done;
159 
160  bad_arg:
161     return enif_make_badarg(env);
162 
163  err:
164     ret = atom_notsup;
165 
166  done:
167     if (ctx)
168         enif_release_resource(ctx);
169     return ret;
170 }
171 
hash_update_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])172 ERL_NIF_TERM hash_update_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
173 {/* (Context, Data) */
174     struct evp_md_ctx   *ctx, *new_ctx = NULL;
175     ErlNifBinary data;
176     ERL_NIF_TERM ret;
177 
178     ASSERT(argc == 2);
179 
180     if (!enif_get_resource(env, argv[0], evp_md_ctx_rtype, (void**)&ctx))
181         goto bad_arg;
182     if (!enif_inspect_iolist_as_binary(env, argv[1], &data))
183         goto bad_arg;
184 
185     if ((new_ctx = enif_alloc_resource(evp_md_ctx_rtype, sizeof(struct evp_md_ctx))) == NULL)
186         goto err;
187     if ((new_ctx->ctx = EVP_MD_CTX_new()) == NULL)
188         goto err;
189     if (EVP_MD_CTX_copy(new_ctx->ctx, ctx->ctx) != 1)
190         goto err;
191     if (EVP_DigestUpdate(new_ctx->ctx, data.data, data.size) != 1)
192         goto err;
193 
194     ret = enif_make_resource(env, new_ctx);
195     CONSUME_REDS(env, data);
196     goto done;
197 
198  bad_arg:
199     return enif_make_badarg(env);
200 
201  err:
202     ret = atom_notsup;
203 
204  done:
205     if (new_ctx)
206         enif_release_resource(new_ctx);
207     return ret;
208 }
209 
hash_final_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])210 ERL_NIF_TERM hash_final_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
211 {/* (Context) */
212     struct evp_md_ctx *ctx;
213     EVP_MD_CTX        *new_ctx;
214     ERL_NIF_TERM  ret;
215     unsigned      ret_size;
216     unsigned char     *outp;
217 
218     ASSERT(argc == 1);
219 
220     if (!enif_get_resource(env, argv[0], evp_md_ctx_rtype, (void**)&ctx))
221         goto bad_arg;
222 
223     ret_size = (unsigned)EVP_MD_CTX_size(ctx->ctx);
224     ASSERT(0 < ret_size && ret_size <= EVP_MAX_MD_SIZE);
225 
226     if ((new_ctx = EVP_MD_CTX_new()) == NULL)
227         goto err;
228     if (EVP_MD_CTX_copy(new_ctx, ctx->ctx) != 1)
229         goto err;
230     if ((outp = enif_make_new_binary(env, ret_size, &ret)) == NULL)
231         goto err;
232     if (EVP_DigestFinal(new_ctx, outp, &ret_size) != 1)
233         goto err;
234 
235     ASSERT(ret_size == (unsigned)EVP_MD_CTX_size(ctx->ctx));
236     goto done;
237 
238  bad_arg:
239     return enif_make_badarg(env);
240 
241  err:
242     ret = atom_notsup;
243 
244  done:
245     if (new_ctx)
246         EVP_MD_CTX_free(new_ctx);
247     return ret;
248 }
249 
250 #else /* if OPENSSL_VERSION_NUMBER < 1.0 */
251 
hash_init_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])252 ERL_NIF_TERM hash_init_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
253 {/* (Type) */
254     typedef int (*init_fun)(unsigned char*);
255     struct digest_type_t *digp = NULL;
256     ERL_NIF_TERM         ctx;
257     size_t               ctx_size = 0;
258     init_fun             ctx_init = 0;
259     unsigned char        *outp;
260 
261     ASSERT(argc == 1);
262 
263     if ((digp = get_digest_type(argv[0])) == NULL)
264         goto bad_arg;
265     if (digp->md.p == NULL)
266         goto err;
267 
268     switch (EVP_MD_type(digp->md.p))
269     {
270 #ifdef HAVE_MD4
271     case NID_md4:
272         ctx_size = MD4_CTX_LEN;
273         ctx_init = (init_fun)(&MD4_Init);
274         break;
275 #endif
276 #ifdef HAVE_MD5
277     case NID_md5:
278         ctx_size = MD5_CTX_LEN;
279         ctx_init = (init_fun)(&MD5_Init);
280         break;
281 #endif
282 #ifdef HAVE_RIPEMD160
283     case NID_ripemd160:
284         ctx_size = RIPEMD160_CTX_LEN;
285         ctx_init = (init_fun)(&RIPEMD160_Init);
286         break;
287 #endif
288     case NID_sha1:
289         ctx_size = sizeof(SHA_CTX);
290         ctx_init = (init_fun)(&SHA1_Init);
291         break;
292 #ifdef HAVE_SHA224
293     case NID_sha224:
294         ctx_size = sizeof(SHA256_CTX);
295         ctx_init = (init_fun)(&SHA224_Init);
296         break;
297 #endif
298 #ifdef HAVE_SHA256
299     case NID_sha256:
300         ctx_size = sizeof(SHA256_CTX);
301         ctx_init = (init_fun)(&SHA256_Init);
302         break;
303 #endif
304 #ifdef HAVE_SHA384
305     case NID_sha384:
306         ctx_size = sizeof(SHA512_CTX);
307         ctx_init = (init_fun)(&SHA384_Init);
308         break;
309 #endif
310 #ifdef HAVE_SHA512
311     case NID_sha512:
312         ctx_size = sizeof(SHA512_CTX);
313         ctx_init = (init_fun)(&SHA512_Init);
314         break;
315 #endif
316     default:
317         goto err;
318     }
319     ASSERT(ctx_size);
320     ASSERT(ctx_init);
321 
322     if ((outp = enif_make_new_binary(env, ctx_size, &ctx)) == NULL)
323         goto err;
324 
325     if (ctx_init(outp) != 1)
326         goto err;
327 
328     return enif_make_tuple2(env, argv[0], ctx);
329 
330  bad_arg:
331     return enif_make_badarg(env);
332 
333  err:
334     return atom_notsup;
335 }
336 
hash_update_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])337 ERL_NIF_TERM hash_update_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
338 {/* ({Type, Context}, Data) */
339     typedef int (*update_fun)(unsigned char*, const unsigned char*, size_t);
340     ERL_NIF_TERM         new_ctx;
341     ErlNifBinary         ctx, data;
342     const ERL_NIF_TERM   *tuple;
343     int                  arity;
344     struct digest_type_t *digp = NULL;
345     unsigned char        *ctx_buff;
346     size_t               ctx_size   = 0;
347     update_fun           ctx_update = 0;
348 
349     ASSERT(argc == 2);
350 
351     if (!enif_get_tuple(env, argv[0], &arity, &tuple))
352         goto bad_arg;
353     if (arity != 2)
354         goto bad_arg;
355     if ((digp = get_digest_type(tuple[0])) == NULL)
356         goto bad_arg;
357     if (!enif_inspect_binary(env, tuple[1], &ctx))
358         goto bad_arg;
359     if (!enif_inspect_iolist_as_binary(env, argv[1], &data))
360         goto bad_arg;
361 
362     if (digp->md.p == NULL)
363         goto err;
364 
365     switch (EVP_MD_type(digp->md.p))
366     {
367 #ifdef HAVE_MD4
368     case NID_md4:
369         ctx_size   = MD4_CTX_LEN;
370         ctx_update = (update_fun)(&MD4_Update);
371         break;
372 #endif
373 #ifdef HAVE_MD5
374     case NID_md5:
375         ctx_size   = MD5_CTX_LEN;
376         ctx_update = (update_fun)(&MD5_Update);
377         break;
378 #endif
379 #ifdef HAVE_RIPEMD160
380     case NID_ripemd160:
381         ctx_size   = RIPEMD160_CTX_LEN;
382         ctx_update = (update_fun)(&RIPEMD160_Update);
383         break;
384 #endif
385     case NID_sha1:
386         ctx_size   = sizeof(SHA_CTX);
387         ctx_update = (update_fun)(&SHA1_Update);
388         break;
389 #ifdef HAVE_SHA224
390     case NID_sha224:
391         ctx_size   = sizeof(SHA256_CTX);
392         ctx_update = (update_fun)(&SHA224_Update);
393         break;
394 #endif
395 #ifdef HAVE_SHA256
396     case NID_sha256:
397         ctx_size   = sizeof(SHA256_CTX);
398         ctx_update = (update_fun)(&SHA256_Update);
399         break;
400 #endif
401 #ifdef HAVE_SHA384
402     case NID_sha384:
403         ctx_size   = sizeof(SHA512_CTX);
404         ctx_update = (update_fun)(&SHA384_Update);
405         break;
406 #endif
407 #ifdef HAVE_SHA512
408     case NID_sha512:
409         ctx_size   = sizeof(SHA512_CTX);
410         ctx_update = (update_fun)(&SHA512_Update);
411         break;
412 #endif
413     default:
414         goto err;
415     }
416     ASSERT(ctx_size);
417     ASSERT(ctx_update);
418 
419     if (ctx.size != ctx_size)
420         goto bad_arg;
421 
422     if ((ctx_buff = enif_make_new_binary(env, ctx_size, &new_ctx)) == NULL)
423         goto err;
424     memcpy(ctx_buff, ctx.data, ctx_size);
425 
426     if (ctx_update(ctx_buff, data.data, data.size) != 1)
427         goto err;
428 
429     CONSUME_REDS(env, data);
430     return enif_make_tuple2(env, tuple[0], new_ctx);
431 
432  bad_arg:
433     return enif_make_badarg(env);
434 
435  err:
436     return atom_notsup;
437 }
438 
hash_final_nif(ErlNifEnv * env,int argc,const ERL_NIF_TERM argv[])439 ERL_NIF_TERM hash_final_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
440 {/* ({Type, Context}) */
441     typedef int (*final_fun)(unsigned char*, void*);
442     ERL_NIF_TERM         ret;
443     ErlNifBinary         ctx;
444     const ERL_NIF_TERM   *tuple;
445     int                  arity;
446     struct digest_type_t *digp = NULL;
447     const EVP_MD         *md;
448     void                 *new_ctx = NULL;
449     size_t               ctx_size  = 0;
450     final_fun            ctx_final = 0;
451     unsigned char        *outp;
452 
453     ASSERT(argc == 1);
454 
455     if (!enif_get_tuple(env, argv[0], &arity, &tuple))
456         goto bad_arg;
457     if (arity != 2)
458         goto bad_arg;
459     if ((digp = get_digest_type(tuple[0])) == NULL)
460         goto bad_arg;
461     if (!enif_inspect_binary(env, tuple[1], &ctx))
462         goto bad_arg;
463 
464     if ((md = digp->md.p) == NULL)
465         goto err;
466 
467     switch (EVP_MD_type(md))
468     {
469 #ifdef HAVE_MD4
470     case NID_md4:
471         ctx_size  = MD4_CTX_LEN;
472         ctx_final = (final_fun)(&MD4_Final);
473         break;
474 #endif
475 #ifdef HAVE_MD5
476     case NID_md5:
477         ctx_size  = MD5_CTX_LEN;
478         ctx_final = (final_fun)(&MD5_Final);
479         break;
480 #endif
481 #ifdef HAVE_RIPEMD160
482    case NID_ripemd160:
483         ctx_size  = RIPEMD160_CTX_LEN;
484         ctx_final = (final_fun)(&RIPEMD160_Final);
485         break;
486 #endif
487     case NID_sha1:
488         ctx_size  = sizeof(SHA_CTX);
489         ctx_final = (final_fun)(&SHA1_Final);
490         break;
491 #ifdef HAVE_SHA224
492     case NID_sha224:
493         ctx_size  = sizeof(SHA256_CTX);
494         ctx_final = (final_fun)(&SHA224_Final);
495         break;
496 #endif
497 #ifdef HAVE_SHA256
498     case NID_sha256:
499         ctx_size  = sizeof(SHA256_CTX);
500         ctx_final = (final_fun)(&SHA256_Final);
501         break;
502 #endif
503 #ifdef HAVE_SHA384
504     case NID_sha384:
505         ctx_size  = sizeof(SHA512_CTX);
506         ctx_final = (final_fun)(&SHA384_Final);
507         break;
508 #endif
509 #ifdef HAVE_SHA512
510     case NID_sha512:
511         ctx_size  = sizeof(SHA512_CTX);
512         ctx_final = (final_fun)(&SHA512_Final);
513         break;
514 #endif
515     default:
516         goto err;
517     }
518     ASSERT(ctx_size);
519     ASSERT(ctx_final);
520 
521     if (ctx.size != ctx_size)
522         goto bad_arg;
523 
524     if ((new_ctx = enif_alloc(ctx_size)) == NULL)
525         goto err;
526 
527     memcpy(new_ctx, ctx.data, ctx_size);
528 
529     if ((outp = enif_make_new_binary(env, (size_t)EVP_MD_size(md), &ret)) == NULL)
530         goto err;
531 
532     if (ctx_final(outp, new_ctx) != 1)
533         goto err;
534 
535     goto done;
536 
537  bad_arg:
538     return enif_make_badarg(env);
539 
540  err:
541     ret = atom_notsup;
542 
543  done:
544     if (new_ctx)
545         enif_free(new_ctx);
546     return ret;
547 }
548 
549 #endif  /* OPENSSL_VERSION_NUMBER < 1.0 */
550