1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2008-2018. 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 #ifdef HAVE_CONFIG_H
22 #  include "config.h"
23 #endif
24 #include "sys.h"
25 #include "erl_vm.h"
26 #include "global.h"
27 #include "erl_process.h"
28 #include "error.h"
29 #include "bif.h"
30 #include "erl_binary.h"
31 #include "big.h"
32 #include "zlib.h"
33 
34 
35 typedef void (*ChksumFun)(void *sum_in_out, unsigned char *buf,
36 			  unsigned buflen);
37 
38 /* Hidden trap target */
39 static BIF_RETTYPE md5_2(BIF_ALIST_2);
40 
41 static Export chksum_md5_2_exp;
42 
erts_init_bif_chksum(void)43 void erts_init_bif_chksum(void)
44 {
45     /* Non visual BIF to trap to. */
46     erts_init_trap_export(&chksum_md5_2_exp,
47 			  am_erlang, ERTS_MAKE_AM("md5_trap"), 2,
48 			  &md5_2);
49 }
50 
51 
do_chksum(ChksumFun sumfun,Process * p,Eterm ioterm,int left,void * sum,int * res,int * err)52 static Eterm do_chksum(ChksumFun sumfun, Process *p, Eterm ioterm, int left,
53 		       void *sum, int *res, int *err)
54 {
55     Eterm *objp;
56     Eterm obj;
57     int c;
58     DECLARE_ESTACK(stack);
59     unsigned char *bytes = NULL;
60     int numbytes = 0;
61 
62     *err = 0;
63     if (left <= 0 || is_nil(ioterm)) {
64 	DESTROY_ESTACK(stack);
65 	*res = 0;
66 	return ioterm;
67     }
68     if(is_binary(ioterm)) {
69 	Uint bitoffs;
70 	Uint bitsize;
71 	Uint size;
72 	Eterm res_term = NIL;
73 	unsigned char *bytes;
74 	byte *temp_alloc = NULL;
75 
76 	ERTS_GET_BINARY_BYTES(ioterm, bytes, bitoffs, bitsize);
77 	if (bitsize != 0) {
78 	    *res = 0;
79 	    *err = 1;
80 	    DESTROY_ESTACK(stack);
81 	    return NIL;
82 	}
83 	if (bitoffs != 0) {
84 	    bytes = erts_get_aligned_binary_bytes(ioterm, &temp_alloc);
85 	    /* The call to erts_get_aligned_binary_bytes cannot fail as
86 	       we'we already checked bitsize and that this is a binary */
87 	}
88 
89 	size = binary_size(ioterm);
90 
91 
92 	if (size > left) {
93 	    Eterm *hp;
94 	    ErlSubBin *sb;
95 	    Eterm orig;
96 	    Uint offset;
97 	    /* Split the binary in two parts, of which we
98 	       only process the first */
99 	    hp = HAlloc(p, ERL_SUB_BIN_SIZE);
100 	    sb = (ErlSubBin *) hp;
101 	    ERTS_GET_REAL_BIN(ioterm, orig, offset, bitoffs, bitsize);
102 	    sb->thing_word = HEADER_SUB_BIN;
103 	    sb->size = size - left;
104 	    sb->offs = offset + left;
105 	    sb->orig = orig;
106 	    sb->bitoffs = bitoffs;
107 	    sb->bitsize = bitsize;
108 	    sb->is_writable = 0;
109 	    res_term = make_binary(sb);
110 	    size = left;
111 	}
112 	(*sumfun)(sum, bytes, size);
113 	*res = size;
114 	DESTROY_ESTACK(stack);
115 	erts_free_aligned_binary_bytes(temp_alloc);
116 	return res_term;
117     }
118 
119     if (!is_list(ioterm)) {
120 	*res = 0;
121 	*err = 1;
122 	DESTROY_ESTACK(stack);
123 	return NIL;
124     }
125 
126     /* OK a list, needs to be processed in order, handling each flat list-level
127        as they occur, just like io_list_to_binary would */
128     *res = 0;
129     ESTACK_PUSH(stack,ioterm);
130     while (!ESTACK_ISEMPTY(stack) && left) {
131 	ioterm = ESTACK_POP(stack);
132 	if (is_nil(ioterm)) {
133 	    /* ignore empty lists */
134 	    continue;
135 	}
136 	if(is_list(ioterm)) {
137 L_Again:   /* Restart with sublist, old listend was pushed on stack */
138 	    objp = list_val(ioterm);
139 	    obj = CAR(objp);
140 	    for(;;) { /* loop over one flat list of bytes and binaries
141 		         until sublist or list end is encountered */
142 		if (is_byte(obj)) {
143 		    int bsize = 0;
144 		    for(;;) {
145 			if (bsize >= numbytes) {
146 			    if (!bytes) {
147 				bytes = erts_alloc(ERTS_ALC_T_TMP,
148 						   numbytes = 500);
149 			    } else {
150 				if (numbytes > left) {
151 				    numbytes += left;
152 				} else {
153 				    numbytes *= 2;
154 				}
155 				bytes = erts_realloc(ERTS_ALC_T_TMP, bytes,
156 						     numbytes);
157 			    }
158 			}
159 			bytes[bsize++] = (unsigned char) unsigned_val(obj);
160 			--left;
161 			ioterm = CDR(objp);
162 			if (!is_list(ioterm)) {
163 			    break;
164 			}
165 			objp = list_val(ioterm);
166 			obj = CAR(objp);
167 			if (!is_byte(obj))
168 			    break;
169 			if (!left) {
170 			    break;
171 			}
172 		    }
173 		    (*sumfun)(sum, bytes, bsize);
174 		    *res += bsize;
175 		} else if (is_nil(obj)) {
176 		    ioterm = CDR(objp);
177 		    if (!is_list(ioterm)) {
178 			break;
179 		    }
180 		    objp = list_val(ioterm);
181 		    obj = CAR(objp);
182 		} else if (is_list(obj)) {
183 		    /* push rest of list for later processing, start
184 		       again with sublist */
185 		    ESTACK_PUSH(stack,CDR(objp));
186 		    ioterm = obj;
187 		    goto L_Again;
188 		} else if (is_binary(obj)) {
189 		    int sres, serr;
190 		    Eterm rest_term;
191 		    rest_term = do_chksum(sumfun, p, obj, left, sum, &sres,
192 					  &serr);
193 		    *res += sres;
194 		    if (serr != 0) {
195 			*err = 1;
196 			DESTROY_ESTACK(stack);
197 			if (bytes != NULL)
198 			    erts_free(ERTS_ALC_T_TMP, bytes);
199 			return NIL;
200 		    }
201 		    left -= sres;
202 		    if (rest_term != NIL) {
203 			Eterm *hp;
204 			hp = HAlloc(p, 2);
205 			obj = CDR(objp);
206 			ioterm = CONS(hp, rest_term, obj);
207 			left = 0;
208 			break;
209 		    }
210 		    ioterm = CDR(objp);
211 		    if (is_list(ioterm)) {
212 			/* objp and obj need to be updated if
213 			   loop is to continue */
214 			objp = list_val(ioterm);
215 			obj = CAR(objp);
216 		    }
217 		} else {
218 		    *err = 1;
219 		    DESTROY_ESTACK(stack);
220 		    if (bytes != NULL)
221 			erts_free(ERTS_ALC_T_TMP, bytes);
222 		    return NIL;
223 		}
224 		if (!left || is_nil(ioterm) || !is_list(ioterm)) {
225 		    break;
226 		}
227 	    } /* for(;;) */
228 	} /* is_list(ioterm) */
229 
230 	if (!left) {
231 #ifdef ALLOW_BYTE_TAIL
232 	    if (is_byte(ioterm)) {
233 		/* inproper list with byte tail*/
234 		Eterm *hp;
235 		hp = HAlloc(p, 2);
236 		ioterm = CONS(hp, ioterm, NIL);
237 	    }
238 #else
239 	    ;
240 #endif
241 	} else if (!is_list(ioterm) && !is_nil(ioterm)) {
242 	    /* inproper list end */
243 #ifdef ALLOW_BYTE_TAIL
244 	    if (is_byte(ioterm)) {
245 		unsigned char b[1];
246 		b[0] = (unsigned char) unsigned_val(ioterm);
247 		(*sumfun)(sum, b, 1);
248 		++(*res);
249 		--left;
250 		ioterm = NIL;
251 	    } else
252 #endif
253 	    if is_binary(ioterm) {
254 		int sres, serr;
255 		ioterm = do_chksum(sumfun, p, ioterm, left, sum, &sres, &serr);
256 		*res +=sres;
257 		if (serr != 0) {
258 		    *err = 1;
259 		    DESTROY_ESTACK(stack);
260 		    if (bytes != NULL)
261 			erts_free(ERTS_ALC_T_TMP, bytes);
262 		    return NIL;
263 		}
264 		left -= sres;
265 	    } else {
266 		*err = 1;
267 		DESTROY_ESTACK(stack);
268 		if (bytes != NULL)
269 		    erts_free(ERTS_ALC_T_TMP, bytes);
270 		return NIL;
271 	    }
272 	}
273     } /* while left and not estack empty */
274     c = ESTACK_COUNT(stack);
275     if (c > 0) {
276 	Eterm *hp = HAlloc(p,2*c);
277 	while(!ESTACK_ISEMPTY(stack)) {
278 	    Eterm st = ESTACK_POP(stack);
279 	    ioterm = CONS(hp, ioterm, st);
280 	    hp += 2;
281 	}
282     }
283     DESTROY_ESTACK(stack);
284     if (bytes != NULL)
285 	erts_free(ERTS_ALC_T_TMP, bytes);
286     return ioterm;
287 }
288 
adler32_wrap(void * vsum,unsigned char * buf,unsigned buflen)289 static void adler32_wrap(void *vsum, unsigned char *buf, unsigned buflen)
290 {
291     unsigned long sum = *((unsigned long *) vsum);
292     sum = adler32(sum,buf,buflen);
293     *((unsigned long *) vsum) = sum;
294 }
295 
crc32_wrap(void * vsum,unsigned char * buf,unsigned buflen)296 static void crc32_wrap(void *vsum, unsigned char *buf, unsigned buflen)
297 {
298     unsigned long sum = *((unsigned long *) vsum);
299     sum = crc32(sum,buf,buflen);
300     *((unsigned long *) vsum) = sum;
301 }
302 
md5_wrap(void * vsum,unsigned char * buf,unsigned buflen)303 static void md5_wrap(void *vsum, unsigned char *buf, unsigned buflen)
304 {
305     MD5_CTX *ctx = ((MD5_CTX *) vsum);
306     MD5Update(ctx,buf,buflen);
307 }
308 
309 #define BYTES_PER_REDUCTION 10
310 #define CHUNK_PER_SCHEDULE (BYTES_PER_REDUCTION * CONTEXT_REDS)
311 
312 BIF_RETTYPE
crc32_1(BIF_ALIST_1)313 crc32_1(BIF_ALIST_1)
314 {
315     unsigned long chksum;
316     int res, err;
317     Eterm rest,res_sum;
318     chksum = crc32(0,NULL,0);
319 
320     rest = do_chksum(&crc32_wrap,BIF_P,BIF_ARG_1,CHUNK_PER_SCHEDULE,
321 		     (void *) &chksum,&res,
322 		     &err);
323     BUMP_REDS(BIF_P,res / BYTES_PER_REDUCTION);
324     if (err != 0) {
325 	BIF_ERROR(BIF_P, BADARG);
326     }
327     res_sum = erts_make_integer(chksum,BIF_P);
328     if (rest != NIL) {
329 	BUMP_ALL_REDS(BIF_P);
330 	BIF_TRAP2(BIF_TRAP_EXPORT(BIF_crc32_2), BIF_P, res_sum, rest);
331     }
332     BIF_RET(res_sum);
333 }
334 
335 BIF_RETTYPE
crc32_2(BIF_ALIST_2)336 crc32_2(BIF_ALIST_2)
337 {
338     unsigned long chksum;
339     int res, err;
340     Eterm rest,res_sum;
341     Uint u;
342     if (!term_to_Uint(BIF_ARG_1, &u) || ((u >> 16) >> 16) != 0) {
343 	BIF_ERROR(BIF_P, BADARG);
344     }
345     chksum = (unsigned long) u;
346 
347     rest = do_chksum(&crc32_wrap,BIF_P,BIF_ARG_2,CHUNK_PER_SCHEDULE,
348 		     (void *) &chksum,&res,
349 		     &err);
350     BUMP_REDS(BIF_P,res / BYTES_PER_REDUCTION);
351     if (err != 0) {
352 	BIF_ERROR(BIF_P, BADARG);
353     }
354     res_sum = erts_make_integer(chksum,BIF_P);
355     if (rest != NIL) {
356 	BUMP_ALL_REDS(BIF_P);
357 	BIF_TRAP2(BIF_TRAP_EXPORT(BIF_crc32_2), BIF_P, res_sum, rest);
358     }
359     BIF_RET(res_sum);
360 }
361 
362 BIF_RETTYPE
crc32_combine_3(BIF_ALIST_3)363 crc32_combine_3(BIF_ALIST_3)
364 {
365     unsigned long chksum1,chksum2;
366     z_off_t length;
367     Uint32 res;
368     Eterm res_sum;
369     Uint u;
370 
371     if (!term_to_Uint(BIF_ARG_1, &u) || ((u >> 16) >> 16) != 0) {
372 	BIF_ERROR(BIF_P, BADARG);
373     }
374     chksum1 = (unsigned long) u;
375 
376     if (!term_to_Uint(BIF_ARG_2, &u) || ((u >> 16) >> 16) != 0) {
377 	BIF_ERROR(BIF_P, BADARG);
378     }
379     chksum2 = (unsigned long) u;
380 
381     if (!term_to_Uint(BIF_ARG_3, &u) || ((u >> 16) >> 16) != 0) {
382 	BIF_ERROR(BIF_P, BADARG);
383     }
384     length = (z_off_t) u;
385 
386     res = (Uint32) crc32_combine(chksum1,chksum2,length);
387 
388     res_sum = erts_make_integer(res,BIF_P);
389     BIF_RET(res_sum);
390 }
391 
392 BIF_RETTYPE
adler32_1(BIF_ALIST_1)393 adler32_1(BIF_ALIST_1)
394 {
395     unsigned long chksum;
396     int res, err;
397     Eterm rest,res_sum;
398     chksum = adler32(0,NULL,0);
399 
400     rest = do_chksum(&adler32_wrap,BIF_P,BIF_ARG_1,CHUNK_PER_SCHEDULE,
401 		     (void *) &chksum,&res,
402 		     &err);
403     BUMP_REDS(BIF_P,res / BYTES_PER_REDUCTION);
404     if (err != 0) {
405 	BIF_ERROR(BIF_P, BADARG);
406     }
407     res_sum = erts_make_integer(chksum,BIF_P);
408     if (rest != NIL) {
409 	BUMP_ALL_REDS(BIF_P);
410 	BIF_TRAP2(BIF_TRAP_EXPORT(BIF_adler32_2), BIF_P, res_sum, rest);
411     }
412     BIF_RET(res_sum);
413 }
414 
415 BIF_RETTYPE
adler32_2(BIF_ALIST_2)416 adler32_2(BIF_ALIST_2)
417 {
418     unsigned long chksum;
419     int res, err;
420     Eterm rest,res_sum;
421     Uint u;
422     if (!term_to_Uint(BIF_ARG_1, &u) || ((u >> 16) >> 16) != 0) {
423 	BIF_ERROR(BIF_P, BADARG);
424     }
425     chksum = (unsigned long) u;
426 
427     rest = do_chksum(&adler32_wrap,BIF_P,BIF_ARG_2,CHUNK_PER_SCHEDULE,
428 		     (void *) &chksum,&res,
429 		     &err);
430     BUMP_REDS(BIF_P,res / BYTES_PER_REDUCTION);
431     if (err != 0) {
432 	BIF_ERROR(BIF_P, BADARG);
433     }
434     res_sum = erts_make_integer(chksum,BIF_P);
435     if (rest != NIL) {
436 	BUMP_ALL_REDS(BIF_P);
437 	BIF_TRAP2(BIF_TRAP_EXPORT(BIF_adler32_2), BIF_P, res_sum, rest);
438     }
439     BIF_RET(res_sum);
440 }
441 
442 BIF_RETTYPE
adler32_combine_3(BIF_ALIST_3)443 adler32_combine_3(BIF_ALIST_3)
444 {
445     unsigned long chksum1,chksum2;
446     z_off_t length;
447     Uint32 res;
448     Eterm res_sum;
449     Uint u;
450 
451     if (!term_to_Uint(BIF_ARG_1, &u) || ((u >> 16) >> 16) != 0) {
452 	BIF_ERROR(BIF_P, BADARG);
453     }
454     chksum1 = (unsigned long) u;
455 
456     if (!term_to_Uint(BIF_ARG_2, &u) || ((u >> 16) >> 16) != 0) {
457 	BIF_ERROR(BIF_P, BADARG);
458     }
459     chksum2 = (unsigned long) u;
460 
461     if (!term_to_Uint(BIF_ARG_3, &u) || ((u >> 16) >> 16) != 0) {
462 	BIF_ERROR(BIF_P, BADARG);
463     }
464     length = (z_off_t) u;
465 
466     if (length == 0) { /* Workaround for unexpected behaviour in zlib. */
467 	res = (Uint32) chksum1;
468     } else {
469 	res = (Uint32) adler32_combine(chksum1,chksum2,length);
470     }
471 
472     res_sum = erts_make_integer(res,BIF_P);
473     BIF_RET(res_sum);
474 }
475 
476 
477 BIF_RETTYPE
md5_1(BIF_ALIST_1)478 md5_1(BIF_ALIST_1)
479 {
480     Eterm bin;
481     byte* bytes;
482     Eterm rest;
483     int res, err;
484 
485     MD5_CTX context;
486     MD5Init(&context);
487 
488     rest = do_chksum(&md5_wrap,BIF_P,BIF_ARG_1,100,(void *) &context,&res,
489 		     &err);
490     if (err != 0) {
491 	BUMP_REDS(BIF_P,res);
492 	BIF_ERROR(BIF_P, BADARG);
493     }
494     if (rest != NIL) {
495 	BUMP_ALL_REDS(BIF_P);
496 	 bin = new_binary(BIF_P, (byte *) &context, sizeof(MD5_CTX));
497 	 BIF_TRAP2(&chksum_md5_2_exp, BIF_P, bin, rest);
498     }
499     BUMP_REDS(BIF_P,res);
500     bin = new_binary(BIF_P, (byte *)NULL, 16);
501     bytes = binary_bytes(bin);
502     MD5Final(bytes, &context);
503     BIF_RET(bin);
504 }
505 
506 /* Hidden trap target */
507 static BIF_RETTYPE
md5_2(BIF_ALIST_2)508 md5_2(BIF_ALIST_2)
509 {
510     byte *bytes;
511     MD5_CTX context;
512     Eterm rest;
513     Eterm bin;
514     int res, err;
515 
516     /* No need to check context, this function cannot be called with unaligned
517        or badly sized context as it's always trapped to. */
518     bytes = binary_bytes(BIF_ARG_1);
519     sys_memcpy(&context,bytes,sizeof(MD5_CTX));
520     rest = do_chksum(&md5_wrap,BIF_P,BIF_ARG_2,100,(void *) &context,&res,
521 		     &err);
522     if (err != 0) {
523 	BUMP_REDS(BIF_P,res);
524 	BIF_ERROR(BIF_P, BADARG);
525     }
526     if (rest != NIL) {
527 	BUMP_ALL_REDS(BIF_P);
528 	bin = new_binary(BIF_P, (byte *) &context, sizeof(MD5_CTX));
529 	BIF_TRAP2(&chksum_md5_2_exp, BIF_P, bin, rest);
530     }
531     BUMP_REDS(BIF_P,res);
532     bin = new_binary(BIF_P, (byte *)NULL, 16);
533     bytes = binary_bytes(bin);
534     MD5Final(bytes, &context);
535     BIF_RET(bin);
536 }
537 
538 BIF_RETTYPE
md5_init_0(BIF_ALIST_0)539 md5_init_0(BIF_ALIST_0)
540 {
541     Eterm bin;
542     byte* bytes;
543 
544     bin = erts_new_heap_binary(BIF_P, (byte *)NULL, sizeof(MD5_CTX), &bytes);
545     MD5Init((MD5_CTX *)bytes);
546     BIF_RET(bin);
547 }
548 
549 BIF_RETTYPE
md5_update_2(BIF_ALIST_2)550 md5_update_2(BIF_ALIST_2)
551 {
552     byte *bytes;
553     MD5_CTX context;
554     Eterm rest;
555     Eterm bin;
556     int res, err;
557     byte *temp_alloc = NULL;
558 
559     if ((bytes = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc)) == NULL) {
560 	erts_free_aligned_binary_bytes(temp_alloc);
561 	BIF_ERROR(BIF_P, BADARG);
562     }
563     if (binary_size(BIF_ARG_1) != sizeof(MD5_CTX)) {
564 	erts_free_aligned_binary_bytes(temp_alloc);
565 	BIF_ERROR(BIF_P, BADARG);
566     }
567     sys_memcpy(&context,bytes,sizeof(MD5_CTX));
568     erts_free_aligned_binary_bytes(temp_alloc);
569     rest = do_chksum(&md5_wrap,BIF_P,BIF_ARG_2,100,(void *) &context,&res,
570 		     &err);
571     if (err != 0) {
572 	BUMP_REDS(BIF_P,res);
573 	BIF_ERROR(BIF_P, BADARG);
574     }
575     bin = new_binary(BIF_P, (byte *) &context, sizeof(MD5_CTX));
576     if (rest != NIL) {
577 	BUMP_ALL_REDS(BIF_P);
578 	BIF_TRAP2(BIF_TRAP_EXPORT(BIF_md5_update_2), BIF_P, bin, rest);
579     }
580     BUMP_REDS(BIF_P,res);
581     BIF_RET(bin);
582 }
583 
584 BIF_RETTYPE
md5_final_1(BIF_ALIST_1)585 md5_final_1(BIF_ALIST_1)
586 {
587     Eterm bin;
588     byte* context;
589     byte* result;
590     MD5_CTX ctx_copy;
591     byte* temp_alloc = NULL;
592 
593     if ((context = erts_get_aligned_binary_bytes(BIF_ARG_1, &temp_alloc)) == NULL) {
594     error:
595 	erts_free_aligned_binary_bytes(temp_alloc);
596 	BIF_ERROR(BIF_P, BADARG);
597     }
598     if (binary_size(BIF_ARG_1) != sizeof(MD5_CTX)) {
599 	goto error;
600     }
601     bin = erts_new_heap_binary(BIF_P, (byte *)NULL, 16, &result);
602     sys_memcpy(&ctx_copy, context, sizeof(MD5_CTX));
603     erts_free_aligned_binary_bytes(temp_alloc);
604     MD5Final(result, &ctx_copy);
605     BIF_RET(bin);
606 }
607