1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 1996-2016. 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  *  Purpose:  Portprogram for supervision of memory usage.
23  *
24  *  Synopsis: memsup
25  *
26  *  PURPOSE OF THIS PROGRAM
27  *
28  *  This program supervises the memory status of the entire system, and
29  *  sends status reports upon request from the Erlang system
30  *
31  *  SPAWNING FROM ERLANG
32  *
33  *  This program is started from Erlang as follows,
34  *
35  *      Port = open_port({spawn, 'memsup'}, [{packet,1}]) for UNIX
36  *
37  *  Erlang sends one of the request condes defined in memsup.h and this program
38  *  answers in one of two ways:
39  *  * If the request is for simple memory data (which is used periodically
40  *    for monitoring) the answer is simply sent in two packets.
41  *  * If the request is for the system specific data, the answer is delivered
42  *    in two packets per value, first a tag value, then the actual
43  *    value. The values are delivered "as is", this interface is
44  *    mainly for VxWorks.
45  *  All numbers are sent as strings of hexadecimal digits.
46  *
47  *  SUNOS FAKING
48  *
49  *  When using SunOS 4, the memory report is faked. The total physical memory
50  *  is always reported to be 256MB, and the used fraction to be 128MB.
51  *
52  *  If capabilities, such as sysconf or procfs, is not defined on the system
53  *  memsup will fake memory usage as well.
54  *
55  *  Following ordering is defined for extended memory,
56  *  Linux:	procfs -> sysinfo -> sysconf -> fake
57  *  Sunos:	sysconf -> fake
58  *  other:	arch specific
59  *
60  *  Todo:
61  *  Memory retrieval should be defined by capabilities and not by archs.
62  *  Ordering should be defined arch.
63  *
64  *  STANDARD INPUT, OUTPUT AND ERROR
65  *
66  *  This program communicates with Erlang through the standard
67  *  input and output file descriptors (0 and 1). These descriptors
68  *  (and the standard error descriptor 2) must NOT be closed
69  *  explicitely by this program at termination (in UNIX it is
70  *  taken care of by the operating system itself; in VxWorks
71  *  it is taken care of by the spawn driver part of the Emulator).
72  *
73  *  END OF FILE
74  *
75  *  If a read from a file descriptor returns zero (0), it means
76  *  that there is no process at the other end of the connection
77  *  having the connection open for writing (end-of-file).
78  *
79  */
80 
81 #if defined(sgi) || defined(__sgi) || defined(__sgi__)
82 #include <sys/types.h>
83 #include <sys/sysmp.h>
84 #endif
85 
86 #include <stdio.h>
87 #include <stddef.h>
88 #include <stdlib.h>
89 
90 #include <unistd.h>
91 
92 #if (defined(__unix__) || defined(unix)) && !defined(USG)
93 #include <sys/param.h>
94 #endif
95 
96 #include <stdarg.h>
97 
98 #include <string.h>
99 #include <time.h>
100 #include <errno.h>
101 
102 #ifdef BSD4_4
103 #include <sys/types.h>
104 #include <sys/sysctl.h>
105 #if !defined (__OpenBSD__) && !defined (__NetBSD__)
106 #include <vm/vm_param.h>
107 #endif
108 #if defined (__FreeBSD__) || defined(__DragonFly__) || defined (__NetBSD__) || defined(__OpenBSD__)
109 #include <sys/vmmeter.h>
110 #endif
111 #endif
112 
113 #if defined (__linux__)
114 #include <sys/sysinfo.h>
115 #endif
116 
117 #if defined(__APPLE__)
118 #include <mach/mach.h>
119 static mach_port_t mach_host_port;
120 static vm_size_t mach_page_size;
121 static uint64_t total_memory_size;
122 #endif
123 
124 /* commands */
125 #include "memsup.h"
126 
127 #define CMD_SIZE      1
128 #define MAX_CMD_BUF   10
129 #define ERLIN_FD      0
130 #define ERLOUT_FD     1
131 
132 
133 /* procfs */
134 #if defined(__linux__)
135 #include <fcntl.h>
136 #define MEMINFO "/proc/meminfo"
137 #endif
138 
139 /*  prototypes */
140 
141 static void print_error(const char *,...);
142 
143 #define MAIN main
144 
145 /*
146  * example, we want procfs information, now give them something equivalent:
147  *
148  * MemTotal:      4029352 kB	old 	HighTotal + LowTotal
149  * MemFree:       1674168 kB	old	HighFree + LowFree
150  * MemShared:           0 kB    old 	now always zero; not calculated
151  * Buffers:        417164 kB	old	temporary storage for raw disk blocks
152  * Cached:         371312 kB	old	in-memory cache for files read from the disk (the page cache)
153 
154  * Active:        1408492 kB	new
155 
156  * Inact_dirty:      7772 kB    new
157  * Inact_clean:      2008 kB    new
158  * Inact_target:        0 kB    new
159  * Inact_laundry:       0 kB    new, and might be missing too
160 
161  * HighTotal:           0 kB
162  * HighFree:            0 kB		memory area for userspace programs or for the pagecache
163  * LowTotal:      4029352 kB
164  * LowFree:       1674168 kB		Highmem + kernel stuff, slab allocates here
165 
166  * SwapTotal:     4194296 kB	old	total amount of swap space available
167  * SwapFree:      4194092 kB	old	Memory which has been evicted from RAM
168  * Inactive:       549224 kB	2.5.41+
169  * Dirty:             872 kB	2.5.41+	Memory which is waiting to get written back to the disk
170  * Writeback:           0 kB	2.5.41+	Memory which is actively being written back to the disk
171  * AnonPages:      787616 kB	??
172  * Mapped:         113612 kB	2.5.41+	files which have been mmaped, such as libraries
173  * Slab:           342864 kB	2.5.41+	in-kernel data structures cache
174  * CommitLimit:   6208972 kB	??
175  * Committed_AS:  1141444 kB	2.5.41+
176  * PageTables:       9368 kB	2.5.41+
177  * VmallocTotal: 34359738367 kB	??	total size of vmalloc memory area
178  * VmallocUsed:     57376 kB	??	amount of vmalloc area which is used
179  * VmallocChunk: 34359677947 kB	??	largest contigious block of vmalloc area which is free
180  * ReverseMaps:      5738       2.5.41+	number of rmap pte chains
181  * SwapCached:          0 kB	2.5.??+
182  * HugePages_Total:     0	2.5.??+
183  * HugePages_Free:      0	2.5.??+
184  * HugePages_Rsvd:      0	2.5.??+
185  * Hugepagesize:     2048 kB	2.5.??
186  *
187  * This information should be generalized for generic platform i.e. erlang.
188  */
189 
190 
191 
192 #define F_MEM_TOTAL   (1 << 0)
193 #define F_MEM_FREE    (1 << 1)
194 #define F_MEM_BUFFERS (1 << 2)
195 #define F_MEM_CACHED  (1 << 3)
196 #define F_MEM_SHARED  (1 << 4)
197 #define F_SWAP_TOTAL  (1 << 5)
198 #define F_SWAP_FREE   (1 << 6)
199 #define F_MEM_AVAIL   (1 << 7)
200 #define F_MEM_CACHED_X (1 << 8)
201 
202 typedef struct {
203     unsigned int flag;
204     unsigned long pagesize;
205     unsigned long total;
206     unsigned long free;
207     unsigned long available;
208     unsigned long buffered;
209     unsigned long cached;
210     unsigned long cached_x;
211     unsigned long shared;
212     unsigned long total_swap;
213     unsigned long free_swap;
214 } memory_ext;
215 
216 typedef struct mem_table_struct {
217   const char *name;     /* memory type name */
218   unsigned long *slot; /* slot in return struct */
219 } mem_table_struct;
220 
221 
222 /*  static variables */
223 
224 static char *program_name;
225 
226 static void
send(unsigned long value,unsigned long pagesize)227 send(unsigned long value, unsigned long pagesize) {
228     char buf[32];
229     int left, bytes, res;
230     int hex_zeroes;
231 
232     for (hex_zeroes = 0; (pagesize % 16) == 0; pagesize /= 16) {
233 	hex_zeroes++;
234     }
235 
236     sprintf(buf+1, "%lx", value*pagesize);
237     bytes = strlen(buf+1);
238     while (hex_zeroes-- > 0) {
239 	bytes++;
240 	buf[bytes] = '0';
241     }
242     buf[0] = (char) bytes;
243     left = ++bytes;
244 
245     while (left > 0) {
246 	res = write(ERLOUT_FD, buf+bytes-left, left);
247 	if (res <= 0){
248 	    perror("Error writing to pipe");
249 	    exit(1);
250 	}
251 	left -= res;
252     }
253 }
254 
255 static void
send_tag(int value)256 send_tag(int value){
257     unsigned char buf[2];
258     int res,left;
259 
260     buf[0] = 1U;
261     buf[1] = (unsigned char) value;
262     left = 2;
263     while(left > 0) {
264 	if((res = write(ERLOUT_FD, buf+left-2,left)) <= 0){
265 	    perror("Error writing to pipe");
266 	    exit(1);
267 	} else {
268 	    left -= res;
269 	}
270     }
271 }
272 
273 #ifdef BSD4_4
274 static int
get_vmtotal(struct vmtotal * vt)275 get_vmtotal(struct vmtotal *vt) {
276 	static int vmtotal_mib[] = {CTL_VM, VM_METER};
277 	size_t size = sizeof *vt;
278 
279 	return sysctl(vmtotal_mib, 2, vt, &size, NULL, 0) != -1;
280 }
281 #endif
282 
283 #if defined(__linux__)
284 
285 
286 static int
get_mem_procfs(memory_ext * me)287 get_mem_procfs(memory_ext *me){
288     int fd, nread;
289     char buffer[4097];
290     char *bp;
291     unsigned long value;
292 
293     me->flag = 0;
294 
295     if ( (fd = open(MEMINFO, O_RDONLY)) < 0) return -1;
296 
297     if ( (nread = read(fd, buffer, 4096)) < 0) {
298         close(fd);
299 	return -1;
300     }
301     close(fd);
302 
303     buffer[nread] = '\0';
304 
305     /* Total and free is NEEDED! */
306 
307     bp = strstr(buffer, "MemTotal:");
308     if (bp != NULL && sscanf(bp, "MemTotal: %lu kB\n", &(me->total)))  me->flag |= F_MEM_TOTAL;
309 
310     bp = strstr(buffer, "MemFree:");
311     if (bp != NULL && sscanf(bp, "MemFree: %lu kB\n", &(me->free)))    me->flag |= F_MEM_FREE;
312 
313     /* Extensions */
314 
315     bp = strstr(buffer, "Buffers:");
316     if (bp != NULL && sscanf(bp, "Buffers: %lu kB\n", &(me->buffered))) me->flag |= F_MEM_BUFFERS;
317 
318     bp = strstr(buffer, "Cached:");
319     if (bp != NULL && sscanf(bp, "Cached: %lu kB\n", &(me->cached)))   me->flag |= F_MEM_CACHED;
320 
321     bp = strstr(buffer, "SReclaimable:");
322     if (bp != NULL && sscanf(bp, "SReclaimable: %lu kB\n", &me->cached_x)) me->flag |= F_MEM_CACHED_X;
323 
324     bp = strstr(buffer, "MemAvailable:");
325     if (bp != NULL && sscanf(bp, "MemAvailable: %lu kB\n", &me->available)) me->flag |= F_MEM_AVAIL;
326 
327     /* Swap */
328 
329     bp = strstr(buffer, "SwapTotal:");
330     if (bp != NULL && sscanf(bp, "SwapTotal: %lu kB\n", &(me->total_swap))) me->flag |= F_SWAP_TOTAL;
331 
332     bp = strstr(buffer, "SwapFree:");
333     if (bp != NULL && sscanf(bp, "SwapFree: %lu kB\n", &(me->free_swap))) me->flag |= F_SWAP_FREE;
334 
335     me->pagesize = 1024; /* procfs defines its size in kB */
336 
337     return 1;
338 }
339 #endif
340 
341 
342 /* arch specific functions */
343 
344 #if defined(__linux__) && !defined(__ANDROID__)/* ifdef SYSINFO */
345 /* sysinfo does not include cached memory which is a problem. */
346 static int
get_extended_mem_sysinfo(memory_ext * me)347 get_extended_mem_sysinfo(memory_ext *me) {
348     struct sysinfo info;
349     me->flag = 0;
350     if (sysinfo(&info) < 0) return -1;
351     me->pagesize   = 1;
352     me->total      = info.totalram;
353     me->free       = info.freeram;
354     me->buffered   = info.bufferram;
355     me->shared     = info.sharedram;
356     me->total_swap = info.totalswap;
357     me->free_swap  = info.freeswap;
358 
359     me->flag = F_MEM_TOTAL | F_MEM_FREE | F_MEM_SHARED | F_MEM_BUFFERS | F_SWAP_TOTAL | F_SWAP_FREE;
360 
361     return 1;
362 }
363 #endif
364 
365 
366 #if defined(_SC_AVPHYS_PAGES)
367 static int
get_extended_mem_sysconf(memory_ext * me)368 get_extended_mem_sysconf(memory_ext *me) {
369     me->total      = sysconf(_SC_PHYS_PAGES);
370     me->free       = sysconf(_SC_AVPHYS_PAGES);
371     me->pagesize   = sysconf(_SC_PAGESIZE);
372 
373     me->flag = F_MEM_TOTAL | F_MEM_FREE;
374 
375     return 1;
376 }
377 #endif
378 
379 #if defined(BSD4_4)
380 static int
get_extended_mem_bsd4(memory_ext * me)381 get_extended_mem_bsd4(memory_ext *me) {
382     struct vmtotal vt;
383     long pgsz;
384 
385     if (!get_vmtotal(&vt)) return 0;
386     if ((pgsz = sysconf(_SC_PAGESIZE)) == -1) return 0;
387 
388     me->total      = (vt.t_free + vt.t_rm);
389     me->free       = vt.t_free;
390     me->pagesize   = pgsz;
391 
392     me->flag = F_MEM_TOTAL | F_MEM_FREE;
393 
394     return 1;
395 }
396 #endif
397 
398 #if defined(sgi) || defined(__sgi) || defined(__sgi__)
399 static int
get_extended_mem_sgi(memory_ext * me)400 get_extended_mem_sgi(memory_ext *me) {
401     struct rminfo rmi;
402     if (sysmp(MP_SAGET, MPSA_RMINFO, &rmi, sizeof(rmi)) < 0)  return -1;
403 
404     me->total    = (unsigned long)(rmi.physmem);
405     me->free     = (unsigned long)(rmi.freemem);
406     me->pagesize = (unsigned long)getpagesize();
407     me->flag = F_MEM_TOTAL | F_MEM_FREE;
408 
409     return 1;
410 }
411 #endif
412 
413 #if defined(__APPLE__)
414 static void
init_apple(void)415 init_apple(void) {
416     kern_return_t kr;
417     mach_msg_type_number_t count;
418     host_basic_info_data_t hinfo;
419 
420     mach_host_port = mach_host_self();
421 
422     count = HOST_BASIC_INFO_COUNT;
423     kr = host_info(mach_host_port, HOST_BASIC_INFO, (host_info_t) &hinfo, &count);
424     if (kr != KERN_SUCCESS) {
425         abort();
426     }
427     total_memory_size = hinfo.max_mem;
428 
429     kr = host_page_size(mach_host_port, &mach_page_size);
430     if (kr != KERN_SUCCESS) {
431         abort();
432     }
433 }
434 
435 static void
get_extended_mem_apple(memory_ext * me)436 get_extended_mem_apple(memory_ext *me) {
437     kern_return_t kr;
438     host_basic_info_data_t hinfo;
439     mach_msg_type_number_t count;
440     vm_statistics_data_t vm_stat;
441 
442     count = HOST_VM_INFO_COUNT;
443     kr = host_statistics(mach_host_port, HOST_VM_INFO, (host_info_t)&vm_stat, &count);
444     if (kr != KERN_SUCCESS) {
445         return;
446     }
447 
448     me->free = vm_stat.free_count * mach_page_size;
449     me->total = total_memory_size;
450     me->pagesize = 1;
451     me->flag = F_MEM_TOTAL | F_MEM_FREE;
452 }
453 #endif
454 
455 static void
get_extended_mem(memory_ext * me)456 get_extended_mem(memory_ext *me) {
457 /* android */
458 #if defined(__ANDROID__)
459     if (get_mem_procfs(me))  return;
460 
461 /* linux */
462 #elif defined(__linux__)
463     if (get_mem_procfs(me))  return;
464     if (get_extended_mem_sysinfo(me)) return;
465 
466 /* bsd */
467 #elif defined(BSD4_4)
468     if (get_extended_mem_bsd4(me))    return;
469 
470 /* sgi */
471 #elif defined(sgi) || defined(__sgi) || defined(__sgi__)
472     if (get_extended_mem_sgi(me))     return;
473 #endif
474 
475 /* Does this exist on others than Solaris2? */
476 #if defined(_SC_AVPHYS_PAGES)
477     if (get_extended_mem_sysconf(me)) return;
478 
479 #elif defined(__APPLE__)
480     get_extended_mem_apple(me);
481 
482 /* We fake the rest */
483 /* SunOS4 (for example) */
484 #else
485     me->free     = (1<<27);	       	/* Fake! 128 MB used */
486     me->total    = (1<<28);		/* Fake! 256 MB total */
487     me->pagesize = 1;
488     me->flag = F_MEM_TOTAL | F_MEM_FREE;
489 #endif
490 }
491 
492 
493 static void
get_basic_mem(unsigned long * tot,unsigned long * used,unsigned long * pagesize)494 get_basic_mem(unsigned long *tot, unsigned long *used, unsigned long *pagesize){
495 #if defined(_SC_AVPHYS_PAGES)	/* Does this exist on others than Solaris2? */
496     unsigned long avPhys, phys, pgSz;
497 
498     phys = sysconf(_SC_PHYS_PAGES);
499     avPhys = sysconf(_SC_AVPHYS_PAGES);
500     *used = (phys - avPhys);
501     *tot = phys;
502     *pagesize = sysconf(_SC_PAGESIZE);
503 #elif defined(__linux__) && !defined(_SC_AVPHYS_PAGES)
504     memory_ext me;
505     if (get_mem_procfs(&me) < 0) {
506         print_error("ProcFS read error");
507         exit(1);
508     }
509     *tot      = me.total;
510     *pagesize = me.pagesize;
511     *used     = me.total - me.free;
512 #elif defined(BSD4_4)
513     struct vmtotal vt;
514     long pgsz;
515 
516     if (!get_vmtotal(&vt)) goto fail;
517     if ((pgsz = sysconf(_SC_PAGESIZE)) == -1) goto fail;
518     *tot = (vt.t_free + vt.t_rm);
519     *used = vt.t_rm;
520     *pagesize = pgsz;
521     return;
522 fail:
523     print_error("%s", strerror(errno));
524     exit(1);
525 #elif defined(sgi) || defined(__sgi) || defined(__sgi__)
526     struct rminfo rmi;
527     if (sysmp(MP_SAGET, MPSA_RMINFO, &rmi, sizeof(rmi)) != -1) {
528 	*tot = (unsigned long)(rmi.physmem);
529 	*used = (unsigned long)(rmi.physmem - rmi.freemem);
530 	*pagesize = (unsigned long)getpagesize();
531     } else {
532 	print_error("%s", strerror(errno));
533 	exit(1);
534     }
535 #elif defined(__APPLE__)
536     {
537         memory_ext me;
538         me.free = 0;
539         get_extended_mem_apple(&me);
540         *used = me.total - me.free;
541         *tot = total_memory_size;
542         *pagesize = 1;
543     }
544 #else  /* SunOS4 */
545     *used = (1<<27);	       	/* Fake! 128 MB used */
546     *tot = (1<<28);		/* Fake! 256 MB total */
547     *pagesize = 1;
548 #endif
549 }
550 
551 static void
simple_show_mem(void)552 simple_show_mem(void){
553     unsigned long tot, used, pagesize;
554     get_basic_mem(&tot, &used, &pagesize);
555     send(used, pagesize);
556     send(tot, pagesize);
557 }
558 
559 static void
extended_show_mem(void)560 extended_show_mem(void){
561     memory_ext me;
562     unsigned long ps;
563 
564     get_extended_mem(&me);
565     ps = me.pagesize;
566 
567     if (me.flag & F_MEM_TOTAL)  { send_tag(MEM_TOTAL);        send(me.total, ps);      }
568     if (me.flag & F_MEM_FREE)   { send_tag(MEM_FREE);         send(me.free, ps);       }
569 
570     /* extensions */
571     if (me.flag & F_MEM_BUFFERS){ send_tag(MEM_BUFFERS);      send(me.buffered, ps);   }
572     if (me.flag & F_MEM_CACHED) { send_tag(MEM_CACHED);       send(me.cached, ps);     }
573     if (me.flag & F_MEM_CACHED_X){ send_tag(MEM_CACHED_X);    send(me.cached_x, ps);     }
574     if (me.flag & F_MEM_SHARED) { send_tag(MEM_SHARED);       send(me.shared, ps);     }
575     if (me.flag & F_MEM_AVAIL)  { send_tag(MEM_AVAIL);        send(me.available, ps);     }
576 
577     /* swap */
578     if (me.flag & F_SWAP_TOTAL) { send_tag(SWAP_TOTAL);       send(me.total_swap, ps); }
579     if (me.flag & F_SWAP_FREE)  { send_tag(SWAP_FREE);        send(me.free_swap, ps);  }
580 
581     /* total is system total*/
582     if (me.flag & F_MEM_TOTAL)  { send_tag(MEM_SYSTEM_TOTAL); send(me.total, ps);     }
583     send_tag(SHOW_SYSTEM_MEM_END);
584 }
585 
586 static void
message_loop(int erlin_fd)587 message_loop(int erlin_fd)
588 {
589     char cmdLen, cmd;
590     int res;
591 
592     while (1){
593 	/*
594 	 *  Wait for command from Erlang
595 	 */
596 	if ((res = read(erlin_fd, &cmdLen, 1)) < 0) {
597 	    print_error("Error reading from Erlang");
598 	    return;
599 	}
600 
601 	if (res == 1) {		/* Exactly one byte read ? */
602 	    if (cmdLen == 1){	/* Should be! */
603 		switch (read(erlin_fd, &cmd, 1)){
604 		case 1:
605 		    switch (cmd){
606 		    case SHOW_MEM:
607 			simple_show_mem();
608 			break;
609 		    case SHOW_SYSTEM_MEM:
610 			extended_show_mem();
611 			break;
612 		    default:	/* ignore all other messages */
613 			break;
614 		    }
615 		  break;
616 
617 		case 0:
618 		  print_error("Erlang has closed");
619 		  return;
620 
621 		default:
622 		  print_error("Error reading from Erlang");
623 		  return;
624 		} /* switch() */
625 	    } else { /* cmdLen != 1 */
626 		print_error("Invalid command length (%d) received", cmdLen);
627 		return;
628 	    }
629 	} else {		/* Erlang end closed */
630 	    print_error("Erlang has closed");
631 	    return;
632 	}
633     }
634 }
635 
636 /*
637  *  main
638  */
639 int
MAIN(int argc,char ** argv)640 MAIN(int argc, char **argv)
641 {
642 #ifdef __APPLE__
643     init_apple();
644 #endif
645 
646   program_name = argv[0];
647 
648   message_loop(ERLIN_FD);
649   return 0;
650 }
651 
652 
653 /*
654  *  print_error
655  *
656  */
657 static void
print_error(const char * format,...)658 print_error(const char *format,...)
659 {
660   va_list args;
661   char buffer[256];
662 
663   va_start(args, format);
664   vsnprintf(buffer, 256, format, args);
665   va_end(args);
666   /* try to use one write only */
667   fprintf(stderr, "[os_mon] memory supervisor port (memsup): %s\r\n", buffer);
668   fflush(stderr);
669 }
670