1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2003-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 /*
22  * Description:	Memory allocation trace. The trace is sent over a
23  *              tcp/ip connection.
24  *
25  *              The trace format is not intended to be documented.
26  *              Instead a library for parsing the trace will be
27  *              distributed. This in order to more easily be able
28  *              to make changes in the trace format. The library
29  *              for parsing the trace is currently not included in
30  *              the OTP distribution, but will be in the future.
31  *
32  * Author: 	Rickard Green
33  */
34 
35 #ifdef HAVE_CONFIG_H
36 #  include "config.h"
37 #endif
38 
39 #include "sys.h"
40 #include "global.h"
41 #include "erl_sock.h"
42 #include "erl_threads.h"
43 #include "erl_memory_trace_protocol.h"
44 #include "erl_mtrace.h"
45 
46 #if defined(MAXHOSTNAMELEN) && MAXHOSTNAMELEN > 255
47 #  undef MAXHOSTNAMELEN
48 #endif
49 
50 #ifndef MAXHOSTNAMELEN
51 #  define MAXHOSTNAMELEN 255
52 #endif
53 
54 #define TRACE_PRINTOUTS 0
55 #ifdef TRACE_PRINTOUTS
56 #define MSB2BITS(X) ((((unsigned)(X))+1)*8)
57 #endif
58 
59 static erts_mtx_t mtrace_op_mutex;
60 static erts_mtx_t mtrace_buf_mutex;
61 
62 #define TRACE_BUF_SZ 				(16*1024)
63 
64 
65 #define UI8_MSB_EHF_SZ				ERTS_MT_UI8_MSB_EHDR_FLD_SZ
66 #define UI16_MSB_EHF_SZ				ERTS_MT_UI16_MSB_EHDR_FLD_SZ
67 #define UI32_MSB_EHF_SZ				ERTS_MT_UI32_MSB_EHDR_FLD_SZ
68 #define UI64_MSB_EHF_SZ				ERTS_MT_UI64_MSB_EHDR_FLD_SZ
69 #define UI_MSB_EHF_SZ				ERTS_MT_UI64_MSB_EHDR_FLD_SZ
70 #define TAG_EHF_SZ				ERTS_MT_TAG_EHDR_FLD_SZ
71 
72 #define UI8_MSB_EHF_MSK				ERTS_MT_UI8_MSB_EHDR_FLD_MSK
73 #define UI16_MSB_EHF_MSK			ERTS_MT_UI16_MSB_EHDR_FLD_MSK
74 #define UI32_MSB_EHF_MSK			ERTS_MT_UI32_MSB_EHDR_FLD_MSK
75 #define UI_MSB_EHF_MSK				ERTS_MT_UI64_MSB_EHDR_FLD_MSK
76 #define UI64_MSB_EHF_MSK			ERTS_MT_UI64_MSB_EHDR_FLD_MSK
77 #define TAG_EHF_MSK				ERTS_MT_TAG_EHDR_FLD_MSK
78 
79 #define UI8_SZ					(1)
80 #define UI16_SZ					(2)
81 #define UI32_SZ					(4)
82 #define UI64_SZ					(8)
83 #ifdef ARCH_64 /* XXX:PaN Halfword? (whole file...) */
84 #  define UI_SZ					UI64_SZ
85 #else
86 #  define UI_SZ					UI32_SZ
87 #endif
88 
89 #define WRITE_UI8(P, V) (*(P) = (byte) ((V) & 0xff))
90 
91 #define WRITE_UI16(P, V)						\
92   ((P)[0] = (byte) (((V) >>  8) & 0xff),				\
93    (P)[1] = (byte) ( (V)        & 0xff))
94 
95 #define WRITE_UI32(P, V)						\
96   ((P)[0] = (byte) (((V) >> 24) & 0xff),				\
97    (P)[1] = (byte) (((V) >> 16) & 0xff),				\
98    (P)[2] = (byte) (((V) >>  8) & 0xff),				\
99    (P)[3] = (byte) ( (V)        & 0xff))
100 
101 #define WRITE_UI64(P, V)						\
102   ((P)[0] = (byte) (((V) >> 56) & 0xff),				\
103    (P)[1] = (byte) (((V) >> 48) & 0xff),				\
104    (P)[2] = (byte) (((V) >> 40) & 0xff),				\
105    (P)[3] = (byte) (((V) >> 32) & 0xff),				\
106    (P)[4] = (byte) (((V) >> 24) & 0xff),				\
107    (P)[5] = (byte) (((V) >> 16) & 0xff),				\
108    (P)[6] = (byte) (((V) >>  8) & 0xff),				\
109    (P)[7] = (byte) ( (V)        & 0xff))
110 
111 #define PUT_UI8(P, V)  (WRITE_UI8((P),  (V)), (P) += UI8_SZ)
112 #define PUT_UI16(P, V) (WRITE_UI16((P), (V)), (P) += UI16_SZ)
113 #define PUT_UI32(P, V) (WRITE_UI32((P), (V)), (P) += UI32_SZ)
114 #define PUT_UI64(P, V) (WRITE_UI64((P), (V)), (P) += UI64_SZ)
115 
116 #define PUT_VSZ_UI16(P, M, V)						\
117 do {									\
118     Uint16 v__ = (Uint16) (V);						\
119     if (v__ >= (((Uint16) 1) << 8)) (M) = 1; else (M) = 0;		\
120     switch ((M)) {							\
121     case 1: *((P)++) = (byte) ((v__ >>  8) & 0xff);			\
122     case 0: *((P)++) = (byte) ( v__        & 0xff);			\
123     }									\
124 } while (0)
125 
126 #define PUT_VSZ_UI32(P, M, V)						\
127 do {									\
128     Uint32 v__ = (Uint32) (V);						\
129     if (v__ >= (((Uint32) 1) << 16)) {					\
130 	if (v__ >= (((Uint32) 1) << 24)) (M) = 3; else (M) = 2;		\
131     } else {								\
132 	if (v__ >= (((Uint32) 1) << 8)) (M) = 1; else (M) = 0;		\
133     }									\
134     switch ((M)) {							\
135     case 3: *((P)++) = (byte) ((v__ >> 24) & 0xff);			\
136     case 2: *((P)++) = (byte) ((v__ >> 16) & 0xff);			\
137     case 1: *((P)++) = (byte) ((v__ >>  8) & 0xff);			\
138     case 0: *((P)++) = (byte) ( v__        & 0xff);			\
139     }									\
140 } while (0)
141 
142 #ifdef ARCH_64
143 
144 #define PUT_VSZ_UI64(P, M, V)						\
145 do {									\
146     Uint64 v__ = (Uint64) (V);						\
147     if (v__ >= (((Uint64) 1) << 32)) {					\
148 	if (v__ >= (((Uint64) 1) << 48)) {				\
149 	    if (v__ >= (((Uint64) 1) << 56)) (M) = 7; else (M) = 6;	\
150 	} else {							\
151 	    if (v__ >= (((Uint64) 1) << 40)) (M) = 5; else (M) = 4;	\
152 	}								\
153     } else {								\
154 	if (v__ >= (((Uint64) 1) << 16)) {				\
155 	    if (v__ >= (((Uint64) 1) << 24)) (M) = 3; else (M) = 2;	\
156 	} else {							\
157 	    if (v__ >= (((Uint64) 1) << 8)) (M) = 1; else (M) = 0;	\
158 	}								\
159     }	    								\
160     switch ((M)) {							\
161     case 7: *((P)++) = (byte) ((v__ >> 56) & 0xff);			\
162     case 6: *((P)++) = (byte) ((v__ >> 48) & 0xff);			\
163     case 5: *((P)++) = (byte) ((v__ >> 40) & 0xff);			\
164     case 4: *((P)++) = (byte) ((v__ >> 32) & 0xff);			\
165     case 3: *((P)++) = (byte) ((v__ >> 24) & 0xff);			\
166     case 2: *((P)++) = (byte) ((v__ >> 16) & 0xff);			\
167     case 1: *((P)++) = (byte) ((v__ >>  8) & 0xff);			\
168     case 0: *((P)++) = (byte) ( v__        & 0xff);			\
169     }									\
170 } while (0)
171 
172 #define PUT_VSZ_UI	PUT_VSZ_UI64
173 #else /* #ifdef ARCH_64 */
174 #define PUT_VSZ_UI	PUT_VSZ_UI32
175 #endif /* #ifdef ARCH_64 */
176 
177 #define MAKE_TBUF_SZ(SZ)						\
178   (TRACE_BUF_SZ < (SZ)							\
179    ? (disable_trace(1, "Internal buffer overflow", 0), 0)		\
180    : (endp - tracep < (SZ) ? send_trace_buffer() : 1))
181 
182 
183 static void disable_trace(int error, char *reason, int eno);
184 static int send_trace_buffer(void);
185 
186 #ifdef DEBUG
187 void
188 check_alloc_entry(byte *sp, byte *ep,
189 		  byte tag,
190 		  Uint16 ct_no, int ct_no_n,
191 		  Uint16 type, int type_n,
192 		  UWord res, int res_n,
193 		  Uint size, int size_n,
194 		  Uint32 ti,int ti_n);
195 void
196 check_realloc_entry(byte *sp, byte *ep,
197 		    byte tag,
198 		    Uint16 ct_no, int ct_no_n,
199 		    Uint16 type, int type_n,
200 		    UWord res, int res_n,
201 		    UWord ptr, int ptr_n,
202 		    Uint size, int size_n,
203 		    Uint32 ti,int ti_n);
204 void
205 check_free_entry(byte *sp, byte *ep,
206 		 byte tag,
207 		 Uint16 ct_no, int ct_no_n,
208 		 Uint16 t_no, int t_no_n,
209 		 UWord ptr, int ptr_n,
210 		 Uint32 ti,int ti_n);
211 void
212 check_time_inc_entry(byte *sp, byte *ep,
213 		     Uint32 secs, int secs_n,
214 		     Uint32 usecs, int usecs_n);
215 #endif
216 
217 
218 
219 int erts_mtrace_enabled;
220 static erts_sock_t socket_desc;
221 static byte trace_buffer[TRACE_BUF_SZ];
222 static byte *tracep;
223 static byte *endp;
224 static SysTimeval last_tv;
225 
226 static ErtsAllocatorWrapper_t mtrace_wrapper;
227 
228 #if ERTS_MTRACE_SEGMENT_ID >= ERTS_ALC_A_MIN || ERTS_MTRACE_SEGMENT_ID < 0
229 #error ERTS_MTRACE_SEGMENT_ID >= ERTS_ALC_A_MIN || ERTS_MTRACE_SEGMENT_ID < 0
230 #endif
231 
232 char* erl_errno_id(int error);
233 
234 #define INVALID_TIME_INC (0xffffffff)
235 
236 static ERTS_INLINE Uint32
get_time_inc(void)237 get_time_inc(void)
238 {
239     Sint32 secs;
240     Sint32 usecs;
241     Uint32 res;
242     SysTimeval tv;
243     sys_gettimeofday(&tv);
244 
245     secs = tv.tv_sec - last_tv.tv_sec;
246     if (tv.tv_usec >= last_tv.tv_usec)
247 	usecs = tv.tv_usec - last_tv.tv_usec;
248     else {
249 	secs--;
250 	usecs = 1000000 + tv.tv_usec - last_tv.tv_usec;
251     }
252 
253     ASSERT(0 <= usecs);
254     ASSERT(usecs < 1000000);
255 
256     if (secs < 0) {
257 	/* Clock stepped backwards; we pretend that no time has past. */
258 	res = 0;
259     }
260     else if (secs < ERTS_MT_TIME_INC_SECS_MASK) {
261 	res = ((((Uint32) secs) << ERTS_MT_TIME_INC_SECS_SHIFT)
262 	       | (((Uint32) usecs) << ERTS_MT_TIME_INC_USECS_SHIFT));
263     }
264     else {
265 	/* Increment too large to fit in a 32-bit integer;
266 	   put a time inc entry in trace ... */
267 	if (MAKE_TBUF_SZ(UI8_SZ + UI16_SZ + 2*UI32_SZ)) {
268 	    byte *hdrp;
269 	    Uint16 hdr;
270 	    int secs_n, usecs_n;
271 
272 	    *(tracep++) = ERTS_MT_TIME_INC_BDY_TAG;
273 
274 	    hdrp = tracep;
275 	    tracep += 2;
276 
277 	    PUT_VSZ_UI32(tracep, secs_n,  secs);
278 	    PUT_VSZ_UI32(tracep, usecs_n, usecs);
279 
280 	    hdr = usecs_n;
281 
282 	    hdr <<= UI32_MSB_EHF_SZ;
283 	    hdr |= secs_n;
284 
285 	    WRITE_UI16(hdrp, hdr);
286 #ifdef DEBUG
287 	    check_time_inc_entry(hdrp-1, tracep,
288 				 (Uint32) secs, secs_n,
289 				 (Uint32) usecs, usecs_n);
290 #endif
291 	    res = 0;
292 	}
293 	else {
294 	    res = INVALID_TIME_INC;
295 	}
296     }
297 
298     last_tv = tv;
299     return res;
300 }
301 
302 
303 static void
disable_trace(int error,char * reason,int eno)304 disable_trace(int error, char *reason, int eno)
305 {
306     char *mt_dis = "Memory trace disabled";
307     char *eno_str;
308 
309     erts_mtrace_enabled = 0;
310     erts_sock_close(socket_desc);
311     socket_desc = ERTS_SOCK_INVALID_SOCKET;
312 
313     if (eno == 0)
314 	erts_fprintf(stderr, "%s: %s\n", mt_dis, reason);
315     else {
316 	eno_str = erl_errno_id(eno);
317 	if (sys_strcmp(eno_str, "unknown") == 0)
318 	    erts_fprintf(stderr, "%s: %s: %d\n", mt_dis, reason, eno);
319 	else
320 	    erts_fprintf(stderr, "%s: %s: %s\n", mt_dis, reason, eno_str);
321     }
322 }
323 
324 static int
send_trace_buffer(void)325 send_trace_buffer(void)
326 {
327     ssize_t ssz;
328     size_t sz;
329 
330     sz = tracep - trace_buffer;
331     tracep = trace_buffer;
332 
333     do {
334 	ssz = erts_sock_send(socket_desc, (void  *) tracep, sz);
335 	if (ssz < 0) {
336 	    int socket_errno = erts_sock_errno();
337 
338 #ifdef EINTR
339 	    if (socket_errno == EINTR)
340 		continue;
341 #endif
342 	    disable_trace(0, "Connection lost", socket_errno);
343 	    return 0;
344 	}
345 	if (ssz > sz) {
346 	    disable_trace(1, "Unexpected error", 0);
347 	    return 0;
348 	}
349 	tracep += ssz;
350 	sz -= ssz;
351     } while (sz);
352 
353     tracep = trace_buffer;
354     return 1;
355 }
356 
357 #if ERTS_ALC_N_MAX >= (1 << 16)
358 #error "Excessively large type numbers"
359 #endif
360 
361 
362 static int
write_trace_header(char * nodename,char * pid,char * hostname)363 write_trace_header(char *nodename, char *pid, char *hostname)
364 {
365 #ifdef DEBUG
366     byte *startp;
367 #endif
368     Uint16 entry_sz;
369     Uint32 flags, n_len, h_len, p_len, hdr_prolog_len;
370     int i, no, str_len;
371     const char *str;
372     struct {
373 	Uint32 gsec;
374 	Uint32 sec;
375 	Uint32 usec;
376     } start_time;
377 
378     sys_gettimeofday(&last_tv);
379 
380     start_time.gsec = (Uint32) (last_tv.tv_sec / 1000000000);
381     start_time.sec  = (Uint32) (last_tv.tv_sec % 1000000000);
382     start_time.usec = (Uint32) last_tv.tv_usec;
383 
384     if (!MAKE_TBUF_SZ(3*UI32_SZ))
385 	return 0;
386 
387     flags = 0;
388 #ifdef ARCH_64
389     flags |= ERTS_MT_64_BIT_FLAG;
390 #endif
391     flags |= ERTS_MT_CRR_INFO;
392 #ifdef ERTS_CAN_TRACK_MALLOC
393     flags |= ERTS_MT_SEG_CRR_INFO;
394 #endif
395 
396     /*
397      * The following 3 ui32 words *always* have to come
398      * first in the trace.
399      */
400     PUT_UI32(tracep, ERTS_MT_START_WORD);
401     PUT_UI32(tracep, ERTS_MT_MAJOR_VSN);
402     PUT_UI32(tracep, ERTS_MT_MINOR_VSN);
403 
404     n_len = sys_strlen(nodename);
405     h_len = sys_strlen(hostname);
406     p_len = sys_strlen(pid);
407     hdr_prolog_len = (2*UI32_SZ
408 		      + 3*UI16_SZ
409 		      + 3*UI32_SZ
410 		      + 3*UI8_SZ
411 		      + n_len
412 		      + h_len
413 		      + p_len);
414 
415     if (!MAKE_TBUF_SZ(hdr_prolog_len))
416 	return 0;
417 
418     /*
419      * New stuff can be added at the end the of header prolog
420      * (EOHP). The reader should skip stuff at the end, that it
421      * doesn't understand.
422      */
423 
424 #ifdef DEBUG
425     startp = tracep;
426 #endif
427 
428     PUT_UI32(tracep, hdr_prolog_len);
429     PUT_UI32(tracep, flags);
430     PUT_UI16(tracep, ERTS_MTRACE_SEGMENT_ID);
431     PUT_UI16(tracep, ERTS_ALC_A_MAX);
432     PUT_UI16(tracep, ERTS_ALC_N_MAX);
433 
434     PUT_UI32(tracep, start_time.gsec);
435     PUT_UI32(tracep, start_time.sec);
436     PUT_UI32(tracep, start_time.usec);
437 
438     PUT_UI8(tracep, (byte) n_len);
439     sys_memcpy((void *) tracep, (void *) nodename, n_len);
440     tracep += n_len;
441 
442     PUT_UI8(tracep, (byte) h_len);
443     sys_memcpy((void *) tracep, (void *) hostname, h_len);
444     tracep += h_len;
445 
446     PUT_UI8(tracep, (byte) p_len);
447     sys_memcpy((void *) tracep, (void *) pid, p_len);
448     tracep += p_len;
449 
450     ASSERT(startp + hdr_prolog_len == tracep);
451 
452     /*
453      * EOHP
454      */
455 
456     /*
457      * All tags from here on should be followed by an Uint16 size
458      * field containing the total size of the entry.
459      *
460      * New stuff can eigther be added at the end of an entry, or
461      * as a new tagged entry. The reader should skip stuff at the
462      * end, that it doesn't understand.
463      */
464 
465     for (i = ERTS_ALC_A_MIN; i <= ERTS_ALC_A_MAX; i++) {
466 	Uint16 aflags = 0;
467 
468 #ifndef ERTS_CAN_TRACK_MALLOC
469 	if (i != ERTS_ALC_A_SYSTEM)
470 #endif
471 	    aflags |= ERTS_MT_ALLCTR_USD_CRR_INFO;
472 
473 	str = ERTS_ALC_A2AD(i);
474 	ASSERT(str);
475 	str_len = sys_strlen(str);
476 	if (str_len >= (1 << 8)) {
477 	    disable_trace(1, "Excessively large allocator string", 0);
478 	    return 0;
479 	}
480 
481 	entry_sz = UI8_SZ + 3*UI16_SZ + UI8_SZ;
482 	entry_sz += (erts_allctrs_info[i].alloc_util ? 2 : 1)*UI16_SZ;
483 	entry_sz += UI8_SZ + str_len;
484 
485 	if (!MAKE_TBUF_SZ(entry_sz))
486 	    return 0;
487 
488 #ifdef DEBUG
489 	startp = tracep;
490 #endif
491 	PUT_UI8(tracep, ERTS_MT_ALLOCATOR_HDR_TAG);
492 	PUT_UI16(tracep, entry_sz);
493 	PUT_UI16(tracep, aflags);
494 	PUT_UI16(tracep, (Uint16) i);
495 	PUT_UI8( tracep, (byte) str_len);
496 	sys_memcpy((void *) tracep, (void *) str, str_len);
497 	tracep += str_len;
498 	if (erts_allctrs_info[i].alloc_util) {
499 	    PUT_UI8(tracep, 2);
500 	    PUT_UI16(tracep, ERTS_MTRACE_SEGMENT_ID);
501 	    PUT_UI16(tracep, ERTS_ALC_A_SYSTEM);
502 	}
503 	else {
504 	    PUT_UI8(tracep, 1);
505 	    switch (i) {
506 	    case ERTS_ALC_A_SYSTEM:
507 		PUT_UI16(tracep, ERTS_MTRACE_SEGMENT_ID);
508 		break;
509 	    default:
510 		PUT_UI16(tracep, ERTS_MTRACE_SEGMENT_ID);
511 		break;
512 	    }
513 	}
514 	ASSERT(startp + entry_sz == tracep);
515     }
516 
517     for (i = ERTS_ALC_N_MIN; i <= ERTS_ALC_N_MAX; i++) {
518 	Uint16 nflags = 0;
519 	str = ERTS_ALC_N2TD(i);
520 	ASSERT(str);
521 
522 	str_len = sys_strlen(str);
523 	if (str_len >= (1 << 8)) {
524 	    disable_trace(1, "Excessively large type string", 0);
525 	    return 0;
526 	}
527 
528 	no = ERTS_ALC_T2A(ERTS_ALC_N2T(i));
529 	if (!erts_allctrs_info[no].enabled)
530 	    no = ERTS_ALC_A_SYSTEM;
531 	ASSERT(ERTS_ALC_A_MIN <= no && no <= ERTS_ALC_A_MAX);
532 
533 	entry_sz = UI8_SZ + 3*UI16_SZ + UI8_SZ + str_len + UI16_SZ;
534 
535 	if (!MAKE_TBUF_SZ(entry_sz))
536 	    return 0;
537 
538 #ifdef DEBUG
539 	startp = tracep;
540 #endif
541 	PUT_UI8(tracep, ERTS_MT_BLOCK_TYPE_HDR_TAG);
542 	PUT_UI16(tracep, entry_sz);
543 	PUT_UI16(tracep, nflags);
544 	PUT_UI16(tracep, (Uint16) i);
545 	PUT_UI8(tracep, (byte) str_len);
546 	sys_memcpy((void *) tracep, (void *) str, str_len);
547 	tracep += str_len;
548 	PUT_UI16(tracep, no);
549 	ASSERT(startp + entry_sz == tracep);
550     }
551 
552     entry_sz = UI8_SZ + UI16_SZ;
553     if (!MAKE_TBUF_SZ(entry_sz))
554 	return 0;
555     PUT_UI8(tracep, ERTS_MT_END_OF_HDR_TAG);
556     PUT_UI16(tracep, entry_sz);
557 
558     return 1;
559 }
560 
561 static void mtrace_pre_lock(void);
562 static void mtrace_pre_unlock(void);
563 static void *mtrace_alloc(ErtsAlcType_t, void *, Uint);
564 static void *mtrace_realloc(ErtsAlcType_t, void *, void *, Uint);
565 static void mtrace_free(ErtsAlcType_t, void *, void *);
566 
567 static ErtsAllocatorFunctions_t real_allctrs[ERTS_ALC_A_MAX+1];
568 
erts_mtrace_pre_init(void)569 void erts_mtrace_pre_init(void)
570 {
571 }
572 
erts_mtrace_init(char * receiver,char * nodename)573 void erts_mtrace_init(char *receiver, char *nodename)
574 {
575     char hostname[MAXHOSTNAMELEN + 1];
576     char pid[21]; /* enough for a 64 bit number */
577 
578     socket_desc = ERTS_SOCK_INVALID_SOCKET;
579     erts_mtrace_enabled = receiver != NULL;
580 
581     if (erts_mtrace_enabled) {
582 	unsigned a, b, c, d, p;
583 	byte ip_addr[4];
584 	Uint16 port;
585 
586         erts_mtx_init(&mtrace_buf_mutex, "mtrace_buf", NIL,
587             ERTS_LOCK_FLAGS_PROPERTY_STATIC | ERTS_LOCK_FLAGS_CATEGORY_DEBUG);
588         erts_mtx_init(&mtrace_op_mutex, "mtrace_op", NIL,
589             ERTS_LOCK_FLAGS_PROPERTY_STATIC | ERTS_LOCK_FLAGS_CATEGORY_DEBUG);
590 
591 	socket_desc = erts_sock_open();
592 	if (socket_desc == ERTS_SOCK_INVALID_SOCKET) {
593 	    disable_trace(1, "Failed to open socket", erts_sock_errno());
594 	    return;
595 	}
596 
597 	if (5 != sscanf(receiver, "%u.%u.%u.%u:%u", &a, &b, &c, &d, &p)
598 	    || a >= (1 << 8) || b >= (1 << 8)|| c >= (1 << 8) || d >= (1 << 8)
599 	    || p >= (1 << 16)) {
600 	    disable_trace(1, "Invalid receiver address", 0);
601 	    return;
602 	}
603 
604 	ip_addr[0] = (byte) a;
605 	ip_addr[1] = (byte) b;
606 	ip_addr[2] = (byte) c;
607 	ip_addr[3] = (byte) d;
608 
609 	port = (Uint16) p;
610 
611 	if (!erts_sock_connect(socket_desc, ip_addr, 4, port)) {
612 	    disable_trace(1, "Failed to connect to receiver",
613 			  erts_sock_errno());
614 	    return;
615 	}
616 	tracep = trace_buffer;
617 	endp = trace_buffer + TRACE_BUF_SZ;
618         /* gethostname requires that the len is max(hostname) + 1 */
619 	if (erts_sock_gethostname(hostname, MAXHOSTNAMELEN + 1) != 0)
620 	    hostname[0] = '\0';
621 	hostname[MAXHOSTNAMELEN] = '\0';
622 	sys_get_pid(pid, sizeof(pid));
623 	write_trace_header(nodename ? nodename : "", pid, hostname);
624 	erts_mtrace_update_heap_size();
625     }
626 }
627 
628 void
erts_mtrace_install_wrapper_functions(void)629 erts_mtrace_install_wrapper_functions(void)
630 {
631     if (erts_mtrace_enabled) {
632 	int i;
633 	/* Install trace functions */
634 	ERTS_CT_ASSERT(sizeof(erts_allctrs) == sizeof(real_allctrs));
635 
636 	sys_memcpy((void *) real_allctrs,
637 		   (void *) erts_allctrs,
638 		   sizeof(erts_allctrs));
639 
640 	for (i = ERTS_ALC_A_MIN; i <= ERTS_ALC_A_MAX; i++) {
641 	    erts_allctrs[i].alloc	= mtrace_alloc;
642 	    erts_allctrs[i].realloc	= mtrace_realloc;
643 	    erts_allctrs[i].free	= mtrace_free;
644 	    erts_allctrs[i].extra	= (void *) &real_allctrs[i];
645 	}
646 	mtrace_wrapper.lock = mtrace_pre_lock;
647 	mtrace_wrapper.unlock = mtrace_pre_unlock;
648 	erts_allctr_wrapper_prelock_init(&mtrace_wrapper);
649     }
650 }
651 
652 void
erts_mtrace_stop(void)653 erts_mtrace_stop(void)
654 {
655     ASSERT(!erts_is_allctr_wrapper_prelocked());
656     erts_mtx_lock(&mtrace_op_mutex);
657     erts_mtx_lock(&mtrace_buf_mutex);
658     if (erts_mtrace_enabled) {
659 	Uint32 ti = get_time_inc();
660 
661 	if (ti != INVALID_TIME_INC
662 	    && MAKE_TBUF_SZ(UI8_SZ + UI16_SZ + UI32_SZ)) {
663 	    byte *hdrp;
664 	    Uint16 hdr;
665 	    int ti_n;
666 
667 	    *(tracep++) = ERTS_MT_STOP_BDY_TAG;
668 
669 	    hdrp = tracep;
670 	    tracep += 2;
671 
672 	    PUT_VSZ_UI32(tracep, ti_n,  ti);
673 
674 	    hdr = ti_n;
675 
676 	    WRITE_UI16(hdrp, hdr);
677 
678 	    if(send_trace_buffer()) {
679 		erts_mtrace_enabled = 0;
680 		erts_sock_close(socket_desc);
681 		socket_desc = ERTS_SOCK_INVALID_SOCKET;
682 	    }
683 	}
684     }
685     erts_mtx_unlock(&mtrace_buf_mutex);
686     erts_mtx_unlock(&mtrace_op_mutex);
687 }
688 
689 void
erts_mtrace_exit(Uint32 exit_value)690 erts_mtrace_exit(Uint32 exit_value)
691 {
692     ASSERT(!erts_is_allctr_wrapper_prelocked());
693     erts_mtx_lock(&mtrace_op_mutex);
694     erts_mtx_lock(&mtrace_buf_mutex);
695     if (erts_mtrace_enabled) {
696 	Uint32 ti = get_time_inc();
697 
698 	if (ti != INVALID_TIME_INC
699 	    && MAKE_TBUF_SZ(UI8_SZ + UI16_SZ + 2*UI32_SZ)) {
700 	    byte *hdrp;
701 	    Uint16 hdr;
702 	    int ti_n, exit_value_n;
703 
704 	    *(tracep++) = ERTS_MT_EXIT_BDY_TAG;
705 
706 	    hdrp = tracep;
707 	    tracep += 2;
708 
709 	    PUT_VSZ_UI32(tracep, exit_value_n,  exit_value);
710 	    PUT_VSZ_UI32(tracep, ti_n,  ti);
711 
712 	    hdr = ti_n;
713 
714 	    hdr <<= UI32_MSB_EHF_SZ;
715 	    hdr |= exit_value_n;
716 
717 	    WRITE_UI16(hdrp, hdr);
718 
719 	    if(send_trace_buffer()) {
720 		erts_mtrace_enabled = 0;
721 		erts_sock_close(socket_desc);
722 		socket_desc = ERTS_SOCK_INVALID_SOCKET;
723 	    }
724 	}
725     }
726     erts_mtx_unlock(&mtrace_buf_mutex);
727     erts_mtx_unlock(&mtrace_op_mutex);
728 }
729 
730 static ERTS_INLINE void
write_alloc_entry(byte tag,void * res,ErtsAlcType_t x,ErtsAlcType_t y,Uint size)731 write_alloc_entry(byte tag,
732 		  void *res,
733 		  ErtsAlcType_t x,
734 		  ErtsAlcType_t y,
735 		  Uint size)
736 {
737     erts_mtx_lock(&mtrace_buf_mutex);
738     if (erts_mtrace_enabled) {
739 	Uint32 ti = get_time_inc();
740 
741 	if (ti != INVALID_TIME_INC
742 	    && MAKE_TBUF_SZ(UI8_SZ + 2*UI16_SZ + 2*UI_SZ + UI32_SZ)) {
743 	    Uint16 hdr, t_no = (Uint16) x, ct_no = (Uint16) y;
744 	    byte *hdrp;
745 	    int t_no_n, ct_no_n = 0, res_n, size_n, ti_n;
746 
747 	    *(tracep++) = tag;
748 
749 	    hdrp = tracep;
750 	    tracep += 2;
751 
752 	    if (tag == ERTS_MT_CRR_ALLOC_BDY_TAG) {
753 		PUT_VSZ_UI16(tracep, ct_no_n, ct_no);
754 	    }
755 	    PUT_VSZ_UI16(tracep, t_no_n, t_no);
756 	    PUT_VSZ_UI(  tracep, res_n, res);
757 	    PUT_VSZ_UI(  tracep, size_n, size);
758 	    PUT_VSZ_UI32(tracep, ti_n, ti);
759 
760 	    hdr = ti_n;
761 
762 	    hdr <<= UI_MSB_EHF_SZ;
763 	    hdr |= size_n;
764 
765 	    hdr <<= UI_MSB_EHF_SZ;
766 	    hdr |= res_n;
767 
768 	    hdr <<= UI16_MSB_EHF_SZ;
769 	    hdr |= t_no_n;
770 
771 	    if (tag == ERTS_MT_CRR_ALLOC_BDY_TAG) {
772 		hdr <<= UI16_MSB_EHF_SZ;
773 		hdr |= ct_no_n;
774 	    }
775 
776 	    WRITE_UI16(hdrp, hdr);
777 
778 #if TRACE_PRINTOUTS
779 	    print_trace_entry(tag,
780 			      ct_no, ct_no_n,
781 			      t_no, t_no_n,
782 			      (Uint) res, res_n,
783 			      0, 0,
784 			      size, size_n,
785 			      ti, ti_n);
786 #endif
787 
788 #ifdef DEBUG
789 	    check_alloc_entry(hdrp-1, tracep,
790 			      tag,
791 			      ct_no, ct_no_n,
792 			      t_no, t_no_n,
793 			      (UWord) res, res_n,
794 			      size, size_n,
795 			      ti, ti_n);
796 #endif
797 
798 	}
799 
800     }
801     erts_mtx_unlock(&mtrace_buf_mutex);
802 
803 }
804 
805 static ERTS_INLINE void
write_realloc_entry(byte tag,void * res,ErtsAlcType_t x,ErtsAlcType_t y,void * ptr,Uint size)806 write_realloc_entry(byte tag,
807 		    void *res,
808 		    ErtsAlcType_t x,
809 		    ErtsAlcType_t y,
810 		    void *ptr,
811 		    Uint size)
812 {
813     erts_mtx_lock(&mtrace_buf_mutex);
814     if (erts_mtrace_enabled) {
815 	Uint32 ti = get_time_inc();
816 
817 	if (ti != INVALID_TIME_INC
818 	    && MAKE_TBUF_SZ(UI8_SZ + 2*UI16_SZ + 3*UI_SZ + UI32_SZ)) {
819 	    Uint16 hdr, t_no = (Uint16) x, ct_no = (Uint16) y;
820 	    byte *hdrp;
821 	    int t_no_n, ct_no_n = 0, res_n, ptr_n, size_n, ti_n;
822 
823 	    *(tracep++) = tag;
824 
825 	    hdrp = tracep;
826 	    tracep += 2;
827 
828 	    if (tag == ERTS_MT_CRR_REALLOC_BDY_TAG) {
829 		PUT_VSZ_UI16(tracep, ct_no_n, ct_no);
830 	    }
831 	    PUT_VSZ_UI16(tracep, t_no_n, t_no);
832 	    PUT_VSZ_UI(  tracep, res_n, res);
833 	    PUT_VSZ_UI(  tracep, ptr_n, ptr);
834 	    PUT_VSZ_UI(  tracep, size_n, size);
835 	    PUT_VSZ_UI32(tracep, ti_n, ti);
836 
837 	    hdr = ti_n;
838 
839 	    hdr <<= UI_MSB_EHF_SZ;
840 	    hdr |= size_n;
841 
842 	    hdr <<= UI_MSB_EHF_SZ;
843 	    hdr |= ptr_n;
844 
845 	    hdr <<= UI_MSB_EHF_SZ;
846 	    hdr |= res_n;
847 
848 	    hdr <<= UI16_MSB_EHF_SZ;
849 	    hdr |= t_no_n;
850 
851 	    if (tag == ERTS_MT_CRR_REALLOC_BDY_TAG) {
852 		hdr <<= UI16_MSB_EHF_SZ;
853 		hdr |= ct_no_n;
854 	    }
855 
856 	    WRITE_UI16(hdrp, hdr);
857 
858 #if TRACE_PRINTOUTS
859 	    print_trace_entry(tag,
860 			      ct_no, ct_no_n,
861 			      t_no, t_no_n,
862 			      (Uint) res, res_n,
863 			      (Uint) ptr, ptr_n,
864 			      size, size_n,
865 			      ti, ti_n);
866 #endif
867 
868 #ifdef DEBUG
869 	    check_realloc_entry(hdrp-1, tracep,
870 				tag,
871 				ct_no, ct_no_n,
872 				t_no, t_no_n,
873 				(UWord) res, res_n,
874 				(UWord) ptr, ptr_n,
875 				size, size_n,
876 				ti, ti_n);
877 #endif
878 
879 	}
880     }
881     erts_mtx_unlock(&mtrace_buf_mutex);
882 }
883 
884 static ERTS_INLINE void
write_free_entry(byte tag,ErtsAlcType_t x,ErtsAlcType_t y,void * ptr)885 write_free_entry(byte tag,
886 		 ErtsAlcType_t x,
887 		 ErtsAlcType_t y,
888 		 void *ptr)
889 {
890     erts_mtx_lock(&mtrace_buf_mutex);
891     if (erts_mtrace_enabled) {
892 	Uint32 ti = get_time_inc();
893 
894 	if (ti != INVALID_TIME_INC
895 	    && MAKE_TBUF_SZ(UI8_SZ + 2*UI16_SZ + UI_SZ + UI32_SZ)) {
896 	    Uint16 hdr, t_no = (Uint16) x, ct_no = (Uint16) y;
897 	    byte *hdrp;
898 	    int t_no_n, ct_no_n = 0, ptr_n, ti_n;
899 
900 	    *(tracep++) = tag;
901 
902 	    hdrp = tracep;
903 	    tracep += 2;
904 
905 	    if (tag == ERTS_MT_CRR_FREE_BDY_TAG) {
906 		PUT_VSZ_UI16(tracep, ct_no_n, ct_no);
907 	    }
908 	    PUT_VSZ_UI16(tracep, t_no_n, t_no);
909 	    PUT_VSZ_UI(  tracep, ptr_n,  ptr);
910 	    PUT_VSZ_UI32(tracep, ti_n,   ti);
911 
912 	    hdr = ti_n;
913 
914 	    hdr <<= UI_MSB_EHF_SZ;
915 	    hdr |= ptr_n;
916 
917 	    hdr <<= UI16_MSB_EHF_SZ;
918 	    hdr |= t_no_n;
919 
920 	    if (tag == ERTS_MT_CRR_FREE_BDY_TAG) {
921 		hdr <<= UI16_MSB_EHF_SZ;
922 		hdr |= ct_no_n;
923 	    }
924 
925 	    WRITE_UI16(hdrp, hdr);
926 
927 #if TRACE_PRINTOUTS
928 	    print_trace_entry(tag,
929 			      ct_no, ct_no_n,
930 			      t_no, t_no_n,
931 			      (Uint) 0, 0,
932 			      (Uint) ptr, ptr_n,
933 			      0, 0,
934 			      ti, ti_n);
935 #endif
936 
937 #ifdef DEBUG
938 	    check_free_entry(hdrp-1, tracep,
939 			     tag,
940 			     ct_no, ct_no_n,
941 			     t_no, t_no_n,
942 			     (UWord) ptr, ptr_n,
943 			     ti, ti_n);
944 #endif
945 	}
946 
947     }
948     erts_mtx_unlock(&mtrace_buf_mutex);
949 }
950 
mtrace_pre_lock(void)951 static void mtrace_pre_lock(void)
952 {
953     erts_mtx_lock(&mtrace_op_mutex);
954 }
955 
mtrace_pre_unlock(void)956 static void mtrace_pre_unlock(void)
957 {
958     erts_mtx_unlock(&mtrace_op_mutex);
959 }
960 
961 
962 static void *
mtrace_alloc(ErtsAlcType_t n,void * extra,Uint size)963 mtrace_alloc(ErtsAlcType_t n, void *extra, Uint size)
964 {
965     ErtsAllocatorFunctions_t *real_af = (ErtsAllocatorFunctions_t *) extra;
966     void *res;
967 
968     if (!erts_is_allctr_wrapper_prelocked()) {
969 	erts_mtx_lock(&mtrace_op_mutex);
970     }
971 
972     res = (*real_af->alloc)(n, real_af->extra, size);
973     write_alloc_entry(ERTS_MT_ALLOC_BDY_TAG, res, n, 0, size);
974 
975     if (!erts_is_allctr_wrapper_prelocked()) {
976 	erts_mtx_unlock(&mtrace_op_mutex);
977     }
978 
979     return res;
980 }
981 
982 static void *
mtrace_realloc(ErtsAlcType_t n,void * extra,void * ptr,Uint size)983 mtrace_realloc(ErtsAlcType_t n, void *extra, void *ptr, Uint size)
984 {
985     ErtsAllocatorFunctions_t *real_af = (ErtsAllocatorFunctions_t *) extra;
986     void *res;
987 
988     if (!erts_is_allctr_wrapper_prelocked()) {
989 	erts_mtx_lock(&mtrace_op_mutex);
990     }
991 
992     res = (*real_af->realloc)(n, real_af->extra, ptr, size);
993     write_realloc_entry(ERTS_MT_REALLOC_BDY_TAG, res, n, 0, ptr, size);
994 
995     if (!erts_is_allctr_wrapper_prelocked()) {
996 	erts_mtx_unlock(&mtrace_op_mutex);
997     }
998 
999     return res;
1000 
1001 }
1002 
1003 static void
mtrace_free(ErtsAlcType_t n,void * extra,void * ptr)1004 mtrace_free(ErtsAlcType_t n, void *extra, void *ptr)
1005 {
1006     ErtsAllocatorFunctions_t *real_af = (ErtsAllocatorFunctions_t *) extra;
1007 
1008     if (!erts_is_allctr_wrapper_prelocked()) {
1009 	erts_mtx_lock(&mtrace_op_mutex);
1010     }
1011 
1012     (*real_af->free)(n, real_af->extra, ptr);
1013     if (!erts_is_allctr_wrapper_prelocked()) {
1014 	write_free_entry(ERTS_MT_FREE_BDY_TAG, n, 0, ptr);
1015     }
1016 
1017     erts_mtx_unlock(&mtrace_op_mutex);
1018 }
1019 
1020 
1021 void
erts_mtrace_crr_alloc(void * res,ErtsAlcType_t n,ErtsAlcType_t m,Uint size)1022 erts_mtrace_crr_alloc(void *res, ErtsAlcType_t n, ErtsAlcType_t m, Uint size)
1023 {
1024     write_alloc_entry(ERTS_MT_CRR_ALLOC_BDY_TAG, res, n, m, size);
1025 }
1026 
1027 void
erts_mtrace_crr_realloc(void * res,ErtsAlcType_t n,ErtsAlcType_t m,void * ptr,Uint size)1028 erts_mtrace_crr_realloc(void *res, ErtsAlcType_t n, ErtsAlcType_t m, void *ptr,
1029 			Uint size)
1030 {
1031     write_realloc_entry(ERTS_MT_CRR_REALLOC_BDY_TAG, res, n, m, ptr, size);
1032 }
1033 
1034 void
erts_mtrace_crr_free(ErtsAlcType_t n,ErtsAlcType_t m,void * ptr)1035 erts_mtrace_crr_free(ErtsAlcType_t n, ErtsAlcType_t m, void *ptr)
1036 {
1037     write_free_entry(ERTS_MT_CRR_FREE_BDY_TAG, n, m, ptr);
1038 }
1039 
1040 
1041 #if TRACE_PRINTOUTS
1042 static void
print_trace_entry(byte tag,Uint16 t_no,int t_no_n,Uint16 ct_no,int ct_no_n,Uint res,int res_n,Uint ptr,int ptr_n,Uint size,int size_n,Uint32 ti,int ti_n)1043 print_trace_entry(byte tag,
1044 		  Uint16 t_no, int t_no_n,
1045 		  Uint16 ct_no, int ct_no_n,
1046 		  Uint res, int res_n,
1047 		  Uint ptr, int ptr_n,
1048 		  Uint size, int size_n,
1049 		  Uint32 ti,int ti_n)
1050 {
1051     switch (tag) {
1052     case ERTS_MT_ALLOC_BDY_TAG:
1053 	fprintf(stderr,
1054 		"{alloc, {%lu, %lu, %lu}, {%u, %u, %u, %u}}\n\r",
1055 
1056 		(unsigned long) t_no, (unsigned long) res,
1057 		(unsigned long) size,
1058 
1059 		MSB2BITS(t_no_n), MSB2BITS(res_n),
1060 		MSB2BITS(size_n), MSB2BITS(ti_n));
1061 	break;
1062     case ERTS_MT_REALLOC_BDY_TAG:
1063 	fprintf(stderr,
1064 		"{realloc, {%lu, %lu, %lu, %lu}, {%u, %u, %u, %u, %u}}\n\r",
1065 
1066 		(unsigned long) t_no, (unsigned long) res,
1067 		(unsigned long) ptr, (unsigned long) size,
1068 
1069 		MSB2BITS(t_no_n), MSB2BITS(res_n),
1070 		MSB2BITS(ptr_n), MSB2BITS(size_n), MSB2BITS(ti_n));
1071 	break;
1072     case ERTS_MT_FREE_BDY_TAG:
1073 	fprintf(stderr,
1074 		"{free, {%lu, %lu}, {%u, %u, %u, %u, %u}}\n\r",
1075 
1076 		(unsigned long) t_no, (unsigned long) ptr,
1077 
1078 		MSB2BITS(t_no_n), MSB2BITS(ptr_n), MSB2BITS(ti_n));
1079 	break;
1080     case ERTS_MT_CRR_ALLOC_BDY_TAG:
1081 	fprintf(stderr,
1082 		"{crr_alloc, {%lu, %lu, %lu, %lu}, {%u, %u, %u, %u, %u}}\n\r",
1083 
1084 		(unsigned long) ct_no, (unsigned long) t_no,
1085 		(unsigned long) res, (unsigned long) size,
1086 
1087 		MSB2BITS(ct_no_n), MSB2BITS(t_no_n),
1088 		MSB2BITS(res_n), MSB2BITS(size_n),
1089 		MSB2BITS(ti_n));
1090 	break;
1091     case ERTS_MT_CRR_REALLOC_BDY_TAG:
1092 	fprintf(stderr,
1093 		"{crr_realloc, {%lu, %lu, %lu, %lu, %lu}, "
1094 		"{%u, %u, %u, %u, %u, %u}}\n\r",
1095 
1096 		(unsigned long) ct_no, (unsigned long) t_no,
1097 		(unsigned long) res, (unsigned long) ptr,
1098 		(unsigned long) size,
1099 
1100 		MSB2BITS(ct_no_n), MSB2BITS(t_no_n),
1101 		MSB2BITS(res_n), MSB2BITS(ptr_n),
1102 		MSB2BITS(size_n), MSB2BITS(ti_n));
1103 	break;
1104     case ERTS_MT_CRR_FREE_BDY_TAG:
1105 	fprintf(stderr,
1106 		"{crr_free, {%lu, %lu, %lu}, {%u, %u, %u, %u}}\n\r",
1107 
1108 		(unsigned long) ct_no, (unsigned long) t_no,
1109 		(unsigned long) ptr,
1110 
1111 		MSB2BITS(ct_no_n), MSB2BITS(t_no_n),
1112 		MSB2BITS(ptr_n), MSB2BITS(ti_n));
1113 	break;
1114     default:
1115 	fprintf(stderr, "{'\?\?\?'}\n\r");
1116 	break;
1117     }
1118 }
1119 
1120 #endif /* #if TRACE_PRINTOUTS */
1121 
1122 #ifdef DEBUG
1123 
1124 #define GET_UI16(P) ((P) += UI16_SZ, \
1125 		     (((Uint16) (*((P) - 2) << 8)) | ((Uint16) (*((P) - 1)))))
1126 
1127 static void
check_ui(Uint16 * hdrp,byte ** pp,Uint ui,int msb,Uint16 f_mask,Uint16 f_size)1128 check_ui(Uint16 *hdrp, byte **pp, Uint ui, int msb,
1129 	 Uint16 f_mask, Uint16 f_size)
1130 {
1131     Uint x;
1132     int n;
1133 
1134     ASSERT((msb & ~f_mask) == 0);
1135 
1136     n = (int) (*hdrp & f_mask);
1137 
1138     ASSERT(n == msb);
1139 
1140     *hdrp >>= f_size;
1141 
1142     x = 0;
1143     switch (n) {
1144 #ifdef ARCH_64
1145     case 7: x |= *((*pp)++); x <<= 8;
1146     case 6: x |= *((*pp)++); x <<= 8;
1147     case 5: x |= *((*pp)++); x <<= 8;
1148     case 4: x |= *((*pp)++); x <<= 8;
1149 #endif
1150     case 3: x |= *((*pp)++); x <<= 8;
1151     case 2: x |= *((*pp)++); x <<= 8;
1152     case 1: x |= *((*pp)++); x <<= 8;
1153     case 0: x |= *((*pp)++); break;
1154     default: ASSERT(0);
1155     }
1156 
1157     ASSERT(x == ui);
1158 }
1159 
1160 
1161 void
check_alloc_entry(byte * sp,byte * ep,byte tag,Uint16 ct_no,int ct_no_n,Uint16 t_no,int t_no_n,UWord res,int res_n,Uint size,int size_n,Uint32 ti,int ti_n)1162 check_alloc_entry(byte *sp, byte *ep,
1163 		  byte tag,
1164 		  Uint16 ct_no, int ct_no_n,
1165 		  Uint16 t_no, int t_no_n,
1166 		  UWord res, int res_n,
1167 		  Uint size, int size_n,
1168 		  Uint32 ti,int ti_n)
1169 {
1170     byte *p = sp;
1171     Uint16 hdr;
1172 
1173     ASSERT(*p == tag);
1174     p++;
1175 
1176     hdr = GET_UI16(p);
1177 
1178     if (tag == ERTS_MT_CRR_ALLOC_BDY_TAG)
1179 	check_ui(&hdr, &p, ct_no, ct_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1180     check_ui(&hdr, &p, t_no, t_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1181     check_ui(&hdr, &p, res,  res_n,  UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1182     check_ui(&hdr, &p, size, size_n, UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1183     check_ui(&hdr, &p, ti,   ti_n,   UI32_MSB_EHF_MSK, UI32_MSB_EHF_SZ);
1184 
1185     ASSERT(hdr == 0);
1186     ASSERT(p == ep);
1187 }
1188 
1189 void
check_realloc_entry(byte * sp,byte * ep,byte tag,Uint16 ct_no,int ct_no_n,Uint16 t_no,int t_no_n,UWord res,int res_n,UWord ptr,int ptr_n,Uint size,int size_n,Uint32 ti,int ti_n)1190 check_realloc_entry(byte *sp, byte *ep,
1191 		    byte tag,
1192 		    Uint16 ct_no, int ct_no_n,
1193 		    Uint16 t_no, int t_no_n,
1194 		    UWord res, int res_n,
1195 		    UWord ptr, int ptr_n,
1196 		    Uint size, int size_n,
1197 		    Uint32 ti,int ti_n)
1198 {
1199     byte *p = sp;
1200     Uint16 hdr;
1201 
1202     ASSERT(*p == tag);
1203     p++;
1204 
1205     hdr = GET_UI16(p);
1206 
1207     if (tag == ERTS_MT_CRR_REALLOC_BDY_TAG)
1208 	check_ui(&hdr, &p, ct_no, ct_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1209     check_ui(&hdr, &p, t_no, t_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1210     check_ui(&hdr, &p, res,  res_n,  UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1211     check_ui(&hdr, &p, ptr,  ptr_n,  UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1212     check_ui(&hdr, &p, size, size_n, UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1213     check_ui(&hdr, &p, ti,   ti_n,   UI32_MSB_EHF_MSK, UI32_MSB_EHF_SZ);
1214 
1215     ASSERT(hdr == 0);
1216     ASSERT(p == ep);
1217 }
1218 
1219 void
check_free_entry(byte * sp,byte * ep,byte tag,Uint16 ct_no,int ct_no_n,Uint16 t_no,int t_no_n,UWord ptr,int ptr_n,Uint32 ti,int ti_n)1220 check_free_entry(byte *sp, byte *ep,
1221 		 byte tag,
1222 		 Uint16 ct_no, int ct_no_n,
1223 		 Uint16 t_no, int t_no_n,
1224 		 UWord ptr, int ptr_n,
1225 		 Uint32 ti,int ti_n)
1226 {
1227     byte *p = sp;
1228     Uint16 hdr;
1229 
1230     ASSERT(*p == tag);
1231     p++;
1232 
1233     hdr = GET_UI16(p);
1234 
1235     if (tag == ERTS_MT_CRR_FREE_BDY_TAG)
1236 	check_ui(&hdr, &p, ct_no, ct_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1237     check_ui(&hdr, &p, t_no, t_no_n, UI16_MSB_EHF_MSK, UI16_MSB_EHF_SZ);
1238     check_ui(&hdr, &p, ptr,  ptr_n,  UI_MSB_EHF_MSK,   UI_MSB_EHF_SZ);
1239     check_ui(&hdr, &p, ti,   ti_n,   UI32_MSB_EHF_MSK, UI32_MSB_EHF_SZ);
1240 
1241     ASSERT(hdr == 0);
1242     ASSERT(p == ep);
1243 
1244 }
1245 
1246 void
check_time_inc_entry(byte * sp,byte * ep,Uint32 secs,int secs_n,Uint32 usecs,int usecs_n)1247 check_time_inc_entry(byte *sp, byte *ep,
1248 		     Uint32 secs, int secs_n,
1249 		     Uint32 usecs, int usecs_n)
1250 {
1251     byte *p = sp;
1252     Uint16 hdr;
1253 
1254     ASSERT(*p == ERTS_MT_TIME_INC_BDY_TAG);
1255     p++;
1256 
1257     hdr = GET_UI16(p);
1258 
1259     check_ui(&hdr, &p, secs,  secs_n,  UI32_MSB_EHF_MSK, UI32_MSB_EHF_SZ);
1260     check_ui(&hdr, &p, usecs, usecs_n, UI32_MSB_EHF_MSK, UI32_MSB_EHF_SZ);
1261 
1262     ASSERT(hdr == 0);
1263     ASSERT(p == ep);
1264 
1265 }
1266 
1267 #endif /* #ifdef DEBUG */
1268 
1269