1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 1996-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  * Module: to_erl.c
22  *
23  * This module implements a process that opens two specified FIFOs, one
24  * for reading and one for writing; reads from its stdin, and writes what
25  * it has read to the write FIF0; reads from the read FIFO, and writes to
26  * its stdout.
27  *
28   ________                            _________
29  |        |--<-- pipe.r (fifo1) --<--|         |
30  | to_erl |                          | run_erl | (parent)
31  |________|-->-- pipe.w (fifo2) -->--|_________|
32                                           ^ master pty
33                                           |
34                                           | slave pty
35                                       ____V____
36                                      |         |
37                                      |  "erl"  | (child)
38                                      |_________|
39  */
40 #ifdef HAVE_CONFIG_H
41 #  include "config.h"
42 #endif
43 
44 #include <sys/types.h>
45 #include <sys/stat.h>
46 #include <sys/time.h>
47 #include <sys/types.h>
48 #include <fcntl.h>
49 #include <unistd.h>
50 #include <stdio.h>
51 #include <stdlib.h>
52 #include <string.h>
53 #include <termios.h>
54 #include <dirent.h>
55 #include <signal.h>
56 #include <errno.h>
57 #ifdef HAVE_SYS_IOCTL_H
58 #  include <sys/ioctl.h>
59 #endif
60 
61 #include "run_erl.h"
62 #include "safe_string.h"   /* strn_cpy, strn_catf, sn_printf, etc. */
63 
64 #ifdef __clang_analyzer__
65    /* CodeChecker does not seem to understand inline asm in FD_ZERO */
66 #  undef FD_ZERO
67 #  define FD_ZERO(FD_SET_PTR) memset(FD_SET_PTR, 0, sizeof(fd_set))
68 #endif
69 
70 #if defined(O_NONBLOCK)
71 # define DONT_BLOCK_PLEASE O_NONBLOCK
72 #else
73 # define DONT_BLOCK_PLEASE O_NDELAY
74 # if !defined(EAGAIN)
75 #  define EAGAIN -3898734
76 # endif
77 #endif
78 
79 #ifdef HAVE_STRERROR
80 #  define STRERROR(x) strerror(x)
81 #else
82 #  define STRERROR(x) ""
83 #endif
84 
85 #define noDEBUG
86 
87 #define PIPE_DIR        "/tmp/"
88 #define PIPE_STUBNAME   "erlang.pipe"
89 #define PIPE_STUBLEN    strlen(PIPE_STUBNAME)
90 
91 #ifdef DEBUG
92 #define STATUS(s)  { fprintf(stderr, (s)); fflush(stderr); }
93 #else
94 #define STATUS(s)
95 #endif
96 
97 #ifndef FILENAME_MAX
98 #define FILENAME_MAX 250
99 #endif
100 
101 static struct termios tty_smode, tty_rmode;
102 static int tty_eof = 0;
103 static int recv_sig = 0;
104 static int protocol_ver = RUN_ERL_LO_VER; /* assume lowest to begin with */
105 
106 static int write_all(int fd, const char* buf, int len);
107 static int window_size_seq(char* buf, size_t bufsz);
108 static int version_handshake(char* buf, int len, int wfd);
109 #ifdef DEBUG
110 static void show_terminal_settings(struct termios *);
111 #endif
112 
handle_ctrlc(int sig)113 static void handle_ctrlc(int sig)
114 {
115     /* Reinstall the handler, and signal break flag */
116     signal(SIGINT,handle_ctrlc);
117     recv_sig = SIGINT;
118 }
119 
handle_sigwinch(int sig)120 static void handle_sigwinch(int sig)
121 {
122     recv_sig = SIGWINCH;
123 }
124 
usage(char * pname)125 static void usage(char *pname)
126 {
127     fprintf(stderr, "Usage: %s [-h|-F] [pipe_name|pipe_dir/]\n", pname);
128     fprintf(stderr, "\t-h\tThis help text.\n");
129     fprintf(stderr, "\t-F\tForce connection even though pipe is locked by other to_erl process.\n");
130 }
131 
main(int argc,char ** argv)132 int main(int argc, char **argv)
133 {
134     char  FIFO1[FILENAME_MAX], FIFO2[FILENAME_MAX];
135     int i, len, wfd, rfd;
136     fd_set readfds;
137     char buf[BUFSIZ];
138     char pipename[FILENAME_MAX];
139     int pipeIx = 1;
140     int force_lock = 0;
141     int got_some = 0;
142 
143     if (argc >= 2 && argv[1][0]=='-') {
144 	switch (argv[1][1]) {
145 	case 'h':
146 	    usage(argv[0]);
147 	    exit(1);
148 	case 'F':
149 	    force_lock = 1;
150 	    break;
151 	default:
152 	    fprintf(stderr,"Invalid option '%s'\n",argv[1]);
153 	    exit(1);
154 	}
155 	pipeIx = 2;
156     }
157 
158 #ifdef DEBUG
159     fprintf(stderr, "%s: pid is : %d\n", argv[0], (int)getpid());
160 #endif
161 
162     strn_cpy(pipename, sizeof(pipename),
163 	     (argv[pipeIx] ? argv[pipeIx] : PIPE_DIR));
164 
165     if(*pipename && pipename[strlen(pipename)-1] == '/') {
166 	/* The user wishes us to find a pipe name in the specified */
167 	/* directory */
168 	int highest_pipe_num = 0;
169 	DIR *dirp;
170 	struct dirent *direntp;
171 
172 	dirp = opendir(pipename);
173 	if(!dirp) {
174 	    fprintf(stderr, "Can't access pipe directory %s: %s\n", pipename, strerror(errno));
175 	    exit(1);
176 	}
177 
178 	/* Check the directory for existing pipes */
179 
180 	while((direntp=readdir(dirp)) != NULL) {
181 	    if(strncmp(direntp->d_name,PIPE_STUBNAME,PIPE_STUBLEN)==0) {
182 		int num = atoi(direntp->d_name+PIPE_STUBLEN+1);
183 		if(num > highest_pipe_num)
184 		    highest_pipe_num = num;
185 	    }
186 	}
187 	closedir(dirp);
188 	strn_catf(pipename, sizeof(pipename), (highest_pipe_num?"%s.%d":"%s"),
189 		  PIPE_STUBNAME, highest_pipe_num);
190     } /* if */
191 
192     /* read FIFO */
193     sn_printf(FIFO1,sizeof(FIFO1),"%s.r",pipename);
194     /* write FIFO */
195     sn_printf(FIFO2,sizeof(FIFO2),"%s.w",pipename);
196 
197     /* Check that nobody is running to_erl on this pipe already */
198     if ((wfd = open (FIFO1, O_WRONLY|DONT_BLOCK_PLEASE, 0)) >= 0) {
199 	/* Open as server succeeded -- to_erl is already running! */
200 	close(wfd);
201 	fprintf(stderr, "Another to_erl process already attached to pipe "
202 			"%s.\n", pipename);
203 	if (force_lock) {
204 	    fprintf(stderr, "But we proceed anyway by force (-F).\n");
205 	}
206 	else {
207 	    exit(1);
208 	}
209     }
210 
211     if ((rfd = open (FIFO1, O_RDONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
212 #ifdef DEBUG
213 	fprintf(stderr, "Could not open FIFO %s for reading.\n", FIFO1);
214 #endif
215 	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
216 	exit(1);
217     }
218 #ifdef DEBUG
219     fprintf(stderr, "to_erl: %s opened for reading\n", FIFO1);
220 #endif
221 
222     if ((wfd = open (FIFO2, O_WRONLY|DONT_BLOCK_PLEASE, 0)) < 0) {
223 #ifdef DEBUG
224 	fprintf(stderr, "Could not open FIFO %s for writing.\n", FIFO2);
225 #endif
226 	fprintf(stderr, "No running Erlang on pipe %s: %s\n", pipename, strerror(errno));
227 	close(rfd);
228 	exit(1);
229     }
230 #ifdef DEBUG
231     fprintf(stderr, "to_erl: %s opened for writing\n", FIFO2);
232 #endif
233 
234     fprintf(stderr, "Attaching to %s (^D to exit)\n\n", pipename);
235 
236     /* Set break handler to our handler */
237     signal(SIGINT,handle_ctrlc);
238 
239     /*
240      * Save the current state of the terminal, and set raw mode.
241      */
242     if (tcgetattr(0, &tty_rmode) , 0) {
243 	fprintf(stderr, "Cannot get terminals current mode\n");
244 	exit(-1);
245     }
246     tty_smode = tty_rmode;
247     tty_eof = '\004'; /* Ctrl+D to exit */
248 #ifdef DEBUG
249     show_terminal_settings(&tty_rmode);
250 #endif
251     tty_smode.c_iflag =
252 	1*BRKINT |/*Signal interrupt on break.*/
253         1*IGNPAR |/*Ignore characters with parity errors.*/
254         0;
255 
256 #if 0
257 0*IGNBRK |/*Ignore break condition.*/
258 0*PARMRK |/*Mark parity errors.*/
259 0*INPCK  |/*Enable input parity check.*/
260 0*INLCR  |/*Map NL to CR on input.*/
261 0*IGNCR  |/*Ignore CR.*/
262 0*ICRNL  |/*Map CR to NL on input.*/
263 0*IUCLC  |/*Map upper-case to lower-case on input.*/
264 0*IXON   |/*Enable start/stop output control.*/
265 0*IXANY  |/*Enable any character to restart output.*/
266 0*IXOFF  |/*Enable start/stop input control.*/
267 0*IMAXBEL|/*Echo BEL on input line too long.*/
268 #endif
269 
270     tty_smode.c_oflag =
271     OPOST    |/*Post-process output.*/
272     0*ONLCR  |/*Map NL to CR-NL on output.*/
273 #ifdef XTABS
274     1*XTABS  |/*Expand tabs to spaces. (Linux)*/
275 #endif
276 #ifdef OXTABS
277     1*OXTABS |/*Expand tabs to spaces. (FreeBSD)*/
278 #endif
279 #ifdef NL0
280     1*NL0    |/*Select newline delays*/
281 #endif
282 #ifdef CR0
283     1*CR0    |/*Select carriage-return delays*/
284 #endif
285 #ifdef TAB0
286     1*TAB0   |/*Select horizontal tab delays*/
287 #endif
288 #ifdef BS0
289     1*BS0    |/*Select backspace delays*/
290 #endif
291 #ifdef VT0
292     1*VT0    |/*Select vertical tab delays*/
293 #endif
294 #ifdef FF0
295     1*FF0    |/*Select form feed delays*/
296 #endif
297 											    0;
298 
299 #if 0
300 0*OLCUC  |/*Map lower case to upper on output.*/
301 0*OCRNL  |/*Map CR to NL on output.*/
302 0*ONOCR  |/*No CR output at column 0.*/
303 0*ONLRET |/*NL performs CR function.*/
304 0*OFILL  |/*Use fill characters for delay.*/
305 0*OFDEL  |/*Fill is DEL, else NULL.*/
306 0*NL1    |
307 0*CR1    |
308 0*CR2    |
309 0*CR3    |
310 0*TAB1   |
311 0*TAB2   |
312 0*TAB3   |/*Expand tabs to spaces.*/
313 0*BS1    |
314 0*VT1    |
315 0*FF1    |
316 #endif
317 
318     /* JALI: removed setting the tty_smode.c_cflag flags, since this is not */
319     /* advisable if this is a *real* terminal, such as the console. In fact */
320     /* this may hang the entire machine, deep, deep down (signalling break */
321     /* or toggling the abort switch doesn't help) */
322 
323     tty_smode.c_lflag =
324 									0;
325 
326 #if 0
327 0*ISIG   |/*Enable signals.*/
328 0*ICANON |/*Canonical input (erase and kill processing).*/
329 0*XCASE  |/*Canonical upper/lower presentation.*/
330 0*ECHO   |/*Enable echo.*/
331 0*ECHOE  |/*Echo erase character as BS-SP-BS.*/
332 0*ECHOK  |/*Echo NL after kill character.*/
333 0*ECHONL |/*Echo NL.*/
334 0*NOFLSH |/*Disable flush after interrupt or quit.*/
335 0*TOSTOP |/*Send SIGTTOU for background output.*/
336 0*ECHOCTL|/*Echo control characters as ^char, delete as ^?.*/
337 0*ECHOPRT|/*Echo erase character as character erased.*/
338 0*ECHOKE |/*BS-SP-BS erase entire line on line kill.*/
339 0*FLUSHO |/*Output is being flushed.*/
340 0*PENDIN |/*Retype pending input at next read or input character.*/
341 0*IEXTEN |/*Enable extended (implementation-defined) functions.*/
342 #endif
343 
344     tty_smode.c_cc[VMIN]      =0;/* Note that VMIN is the same as VEOF! */
345     tty_smode.c_cc[VTIME]     =0;/* Note that VTIME is the same as VEOL! */
346     tty_smode.c_cc[VINTR]     =3;
347 
348     tcsetattr(0, TCSADRAIN, &tty_smode);
349 
350 #ifdef DEBUG
351     show_terminal_settings(&tty_smode);
352 #endif
353     /*
354      * 	 "Write a ^L to the FIFO which causes the other end to redisplay
355      *    the input line."
356      * This does not seem to work as was intended in old comment above.
357      * However, this control character is now (R12B-3) used by run_erl
358      * to trigger the version handshaking between to_erl and run_erl
359      * at the start of every new to_erl-session.
360      */
361 
362     if (write(wfd, "\014", 1) < 0) {
363 	fprintf(stderr, "Error in writing ^L to FIFO.\n");
364     }
365 
366     /*
367      * read and write
368      */
369     while (1) {
370 	FD_ZERO(&readfds);
371 	FD_SET(0, &readfds);
372 	FD_SET(rfd, &readfds);
373 	if (select(rfd + 1, &readfds, NULL, NULL, NULL) < 0) {
374 	    if (recv_sig) {
375 		FD_ZERO(&readfds);
376 	    }
377 	    else {
378 		fprintf(stderr, "Error in select.\n");
379 		break;
380 	    }
381 	}
382 	len = 0;
383 
384 	/*
385 	 * Read from terminal and write to FIFO
386          */
387 	if (recv_sig) {
388 	    switch (recv_sig) {
389 	    case SIGINT:
390 		fprintf(stderr, "[Break]\n\r");
391 		buf[0] = '\003';
392 		len = 1;
393 		break;
394 	    case SIGWINCH:
395 		len = window_size_seq(buf,sizeof(buf));
396 		break;
397 	    default:
398 		fprintf(stderr,"Unexpected signal: %u\n",recv_sig);
399 	    }
400 	    recv_sig = 0;
401 	}
402 	else if (FD_ISSET(0, &readfds)) {
403 	    len = read(0, buf, sizeof(buf));
404 	    if (len <= 0) {
405 		close(rfd);
406 		close(wfd);
407 		if (len < 0) {
408 		    fprintf(stderr, "Error in reading from stdin.\n");
409 		} else {
410 		    fprintf(stderr, "[EOF]\n\r");
411 		}
412 		break;
413 	    }
414 	    /* check if there is an eof character in input */
415 	    for (i = 0; i < len && buf[i] != tty_eof; i++);
416 	    if (buf[i] == tty_eof) {
417 		fprintf(stderr, "[Quit]\n\r");
418 		break;
419 	    }
420 	}
421 
422 	if (len) {
423 #ifdef DEBUG
424 	    write_all(1, buf, len);
425 #endif
426 	    if (write_all(wfd, buf, len) != len) {
427 		fprintf(stderr, "Error in writing to FIFO.\n");
428 		close(rfd);
429 		close(wfd);
430 		break;
431 	    }
432 	    STATUS("\" OK\r\n");
433 	}
434 
435 	/*
436 	 * Read from FIFO, write to terminal.
437 	 */
438 	if (FD_ISSET(rfd, &readfds)) {
439 	    STATUS("FIFO read: ");
440 	    len = read(rfd, buf, BUFSIZ);
441 	    if (len < 0 && errno == EAGAIN) {
442 		/*
443 		 * No data this time, but the writing end of the FIFO is still open.
444 		 * Do nothing.
445 		 */
446 		;
447 	    } else if (len <= 0) {
448 		/*
449 		 * Either an error or end of file. In either case, break out
450 		 * of the loop.
451 		 */
452 		close(rfd);
453 		close(wfd);
454 		if (len < 0) {
455 		    fprintf(stderr, "Error in reading from FIFO.\n");
456 		} else
457 		    fprintf(stderr, "[End]\n\r");
458 		break;
459 	    } else {
460 		if (!got_some) {
461 		    if ((len=version_handshake(buf,len,wfd)) < 0) {
462 			close(rfd);
463 			close(wfd);
464 			break;
465 		    }
466 		    if (protocol_ver >= 1) {
467 			/* Tell run_erl size of terminal window */
468 			signal(SIGWINCH, handle_sigwinch);
469 			raise(SIGWINCH);
470 		    }
471 		    got_some = 1;
472 		}
473 
474 		/*
475 		 * We successfully read at least one character. Write what we got.
476 		 */
477 		STATUS("Terminal write: \"");
478 		if (write_all(1, buf, len) != len) {
479 		    fprintf(stderr, "Error in writing to terminal.\n");
480 		    close(rfd);
481 		    close(wfd);
482 		    break;
483 		}
484 		STATUS("\" OK\r\n");
485 	    }
486 	}
487     }
488 
489     /*
490      * Reset terminal characterstics
491      * XXX
492      */
493     tcsetattr(0, TCSADRAIN, &tty_rmode);
494     return 0;
495 }
496 
497 /* Call write() until entire buffer has been written or error.
498  * Return len or -1.
499  */
write_all(int fd,const char * buf,int len)500 static int write_all(int fd, const char* buf, int len)
501 {
502     int left = len;
503     int written;
504     while (left) {
505 	written = write(fd,buf,left);
506 	if (written < 0) {
507 	    return -1;
508 	}
509 	left -= written;
510 	buf += written;
511     }
512     return len;
513 }
514 
window_size_seq(char * buf,size_t bufsz)515 static int window_size_seq(char* buf, size_t bufsz)
516 {
517 #ifdef TIOCGWINSZ
518     struct winsize ws;
519     static const char prefix[] = "\033_";
520     static const char suffix[] = "\033\\";
521     /* This Esc sequence is called "Application Program Command"
522        and seems suitable to use for our own customized stuff. */
523 
524     if (ioctl(STDIN_FILENO, TIOCGWINSZ, &ws) == 0) {
525 	int len = sn_printf(buf, bufsz, "%swinsize=%u,%u%s",
526 			    prefix, ws.ws_col, ws.ws_row, suffix);
527 	return len;
528     }
529 #endif /* TIOCGWINSZ */
530     return 0;
531 }
532 
533 /*   to_erl                     run_erl
534  *     |                           |
535  *     |---------- '\014' -------->| (session start)
536  *     |                           |
537  *     |<---- "[run_erl v1-0]" ----| (version interval)
538  *     |                           |
539  *     |--- Esc_"version=1"Esc\ -->| (common version)
540  *     |                           |
541  */
version_handshake(char * buf,int len,int wfd)542 static int version_handshake(char* buf, int len, int wfd)
543 {
544     unsigned re_high=0, re_low;
545     char *end = find_str(buf,len,"]\n");
546 
547     if (end && sscanf(buf,"[run_erl v%u-%u",&re_high,&re_low)==2) {
548 	char wbuf[30];
549 	int wlen;
550 
551 	if (re_low > RUN_ERL_HI_VER || re_high < RUN_ERL_LO_VER) {
552 	    fprintf(stderr,"Incompatible versions: to_erl=v%u-%u run_erl=v%u-%u\n",
553 		    RUN_ERL_HI_VER, RUN_ERL_LO_VER, re_high, re_low);
554 	    return -1;
555 	}
556 	/* Choose highest common version */
557 	protocol_ver = re_high < RUN_ERL_HI_VER ? re_high : RUN_ERL_HI_VER;
558 
559 	wlen = sn_printf(wbuf, sizeof(wbuf), "\033_version=%u\033\\",
560 			 protocol_ver);
561 	if (write_all(wfd, wbuf, wlen) < 0) {
562 	    fprintf(stderr,"Failed to send version handshake\n");
563 	    return -1;
564 	}
565 	end += 2;
566 	len -= (end-buf);
567 	memmove(buf,end,len);
568 
569     }
570     else {  /* we assume old run_erl without version handshake */
571 	protocol_ver = 0;
572     }
573 
574     if (re_high != RUN_ERL_HI_VER) {
575 	fprintf(stderr,"run_erl has different version, "
576 		"using common protocol level %u\n", protocol_ver);
577     }
578 
579     return len;
580 }
581 
582 
583 #ifdef DEBUG
584 #define S(x)  ((x) > 0 ? 1 : 0)
585 
show_terminal_settings(struct termios * t)586 static void show_terminal_settings(struct termios *t)
587 {
588   fprintf(stderr,"c_iflag:\n");
589   fprintf(stderr,"Signal interrupt on break:   BRKINT  %d\n", S(t->c_iflag & BRKINT));
590   fprintf(stderr,"Map CR to NL on input:       ICRNL   %d\n", S(t->c_iflag & ICRNL));
591   fprintf(stderr,"Ignore break condition:      IGNBRK  %d\n", S(t->c_iflag & IGNBRK));
592   fprintf(stderr,"Ignore CR:                   IGNCR   %d\n", S(t->c_iflag & IGNCR));
593   fprintf(stderr,"Ignore char with par. err's: IGNPAR  %d\n", S(t->c_iflag & IGNPAR));
594   fprintf(stderr,"Map NL to CR on input:       INLCR   %d\n", S(t->c_iflag & INLCR));
595   fprintf(stderr,"Enable input parity check:   INPCK   %d\n", S(t->c_iflag & INPCK));
596   fprintf(stderr,"Strip character              ISTRIP  %d\n", S(t->c_iflag & ISTRIP));
597   fprintf(stderr,"Enable start/stop input ctrl IXOFF   %d\n", S(t->c_iflag & IXOFF));
598   fprintf(stderr,"ditto output ctrl            IXON    %d\n", S(t->c_iflag & IXON));
599   fprintf(stderr,"Mark parity errors           PARMRK  %d\n", S(t->c_iflag & PARMRK));
600   fprintf(stderr,"\n");
601   fprintf(stderr,"c_oflag:\n");
602   fprintf(stderr,"Perform output processing    OPOST   %d\n", S(t->c_oflag & OPOST));
603   fprintf(stderr,"\n");
604   fprintf(stderr,"c_cflag:\n");
605   fprintf(stderr,"Ignore modem status lines    CLOCAL  %d\n", S(t->c_cflag & CLOCAL));
606   fprintf(stderr,"\n");
607   fprintf(stderr,"c_local:\n");
608   fprintf(stderr,"Enable echo                  ECHO    %d\n", S(t->c_lflag & ECHO));
609   fprintf(stderr,"\n");
610   fprintf(stderr,"c_cc:\n");
611   fprintf(stderr,"c_cc[VEOF]                           %d\n", t->c_cc[VEOF]);
612 }
613 #endif
614