Home | History | Annotate | Line # | Download | only in ksh
exec.c revision 1.26.2.1
      1  1.26.2.1  pgoyette /*	$NetBSD: exec.c,v 1.26.2.1 2018/05/21 04:35:48 pgoyette Exp $	*/
      2       1.2       tls 
      3       1.1       jtc /*
      4       1.1       jtc  * execute command tree
      5       1.1       jtc  */
      6       1.8       agc #include <sys/cdefs.h>
      7       1.8       agc 
      8       1.8       agc #ifndef lint
      9  1.26.2.1  pgoyette __RCSID("$NetBSD: exec.c,v 1.26.2.1 2018/05/21 04:35:48 pgoyette Exp $");
     10       1.8       agc #endif
     11       1.8       agc 
     12      1.22     kamil #include <sys/stat.h>
     13      1.22     kamil #include <ctype.h>
     14      1.23     kamil #include <stdbool.h>
     15       1.1       jtc 
     16       1.1       jtc #include "sh.h"
     17       1.1       jtc #include "c_test.h"
     18       1.1       jtc 
     19       1.1       jtc /* Does ps4 get parameter substitutions done? */
     20       1.1       jtc #ifdef KSH
     21       1.1       jtc # define PS4_SUBSTITUTE(s)	substitute((s), 0)
     22       1.1       jtc #else
     23       1.1       jtc # define PS4_SUBSTITUTE(s)	(s)
     24       1.1       jtc #endif /* KSH */
     25       1.1       jtc 
     26      1.11  christos static int	comexec	 ARGS((struct op *, struct tbl *volatile, char **,
     27      1.11  christos 			      int volatile));
     28      1.11  christos static void	scriptexec ARGS((struct op *, char **));
     29      1.11  christos static int	call_builtin ARGS((struct tbl *, char **));
     30      1.11  christos static int	iosetup ARGS((struct ioword *, struct tbl *));
     31      1.11  christos static int	herein ARGS((const char *, int));
     32       1.1       jtc #ifdef KSH
     33      1.24     joerg static char 	*do_selectargs(char **, bool);
     34       1.1       jtc #endif /* KSH */
     35       1.1       jtc #ifdef KSH
     36      1.11  christos static int	dbteste_isa ARGS((Test_env *, Test_meta));
     37      1.11  christos static const char *dbteste_getopnd ARGS((Test_env *, Test_op, int));
     38      1.11  christos static int	dbteste_eval ARGS((Test_env *, Test_op, const char *,
     39      1.11  christos 				const char *, int));
     40      1.11  christos static void	dbteste_error ARGS((Test_env *, int, const char *));
     41       1.1       jtc #endif /* KSH */
     42       1.1       jtc 
     43       1.1       jtc /*
     44       1.1       jtc  * handle systems that don't have F_SETFD
     45       1.1       jtc  */
     46       1.1       jtc #ifndef F_SETFD
     47       1.1       jtc # ifndef MAXFD
     48       1.1       jtc #   define  MAXFD 64
     49       1.1       jtc # endif
     50       1.1       jtc /* a bit field would be smaller, but this will work */
     51       1.1       jtc static char clexec_tab[MAXFD+1];
     52       1.1       jtc #endif
     53       1.1       jtc 
     54       1.1       jtc /*
     55       1.1       jtc  * we now use this function always.
     56       1.1       jtc  */
     57       1.1       jtc int
     58       1.1       jtc fd_clexec(fd)
     59       1.1       jtc     int fd;
     60       1.1       jtc {
     61       1.1       jtc #ifndef F_SETFD
     62       1.1       jtc 	if (fd >= 0 && fd < sizeof(clexec_tab)) {
     63       1.1       jtc 		clexec_tab[fd] = 1;
     64       1.1       jtc 		return 0;
     65       1.1       jtc 	}
     66       1.1       jtc 	return -1;
     67       1.1       jtc #else
     68       1.1       jtc 	return fcntl(fd, F_SETFD, 1);
     69       1.1       jtc #endif
     70       1.1       jtc }
     71       1.1       jtc 
     72       1.1       jtc 
     73       1.1       jtc /*
     74       1.1       jtc  * execute command tree
     75       1.1       jtc  */
     76       1.1       jtc int
     77       1.1       jtc execute(t, flags)
     78       1.1       jtc 	struct op * volatile t;
     79       1.1       jtc 	volatile int flags;	/* if XEXEC don't fork */
     80       1.1       jtc {
     81       1.1       jtc 	int i;
     82       1.1       jtc 	volatile int rv = 0;
     83       1.1       jtc 	int pv[2];
     84       1.1       jtc 	char ** volatile ap;
     85       1.1       jtc 	char *s, *cp;
     86       1.1       jtc 	struct ioword **iowp;
     87       1.1       jtc 	struct tbl *tp = NULL;
     88       1.1       jtc 
     89       1.1       jtc 	if (t == NULL)
     90       1.1       jtc 		return 0;
     91       1.1       jtc 
     92       1.1       jtc 	/* Is this the end of a pipeline?  If so, we want to evaluate the
     93       1.1       jtc 	 * command arguments
     94      1.23     kamil 	bool eval_done = false;
     95       1.1       jtc 	if ((flags&XFORK) && !(flags&XEXEC) && (flags&XPCLOSE)) {
     96      1.23     kamil 		eval_done = true;
     97       1.1       jtc 		tp = eval_execute_args(t, &ap);
     98       1.1       jtc 	}
     99       1.1       jtc 	 */
    100       1.1       jtc 	if ((flags&XFORK) && !(flags&XEXEC) && t->type != TPIPE)
    101       1.5   hubertf 		return exchild(t, flags & ~XTIME, -1); /* run in sub-process */
    102       1.1       jtc 
    103       1.1       jtc 	newenv(E_EXEC);
    104       1.1       jtc 	if (trap)
    105       1.1       jtc 		runtraps(0);
    106       1.9   mycroft 
    107       1.1       jtc 	if (t->type == TCOM) {
    108       1.1       jtc 		/* Clear subst_exstat before argument expansion.  Used by
    109       1.5   hubertf 		 * null commands (see comexec() and c_eval()) and by c_set().
    110       1.1       jtc 		 */
    111       1.1       jtc 		subst_exstat = 0;
    112       1.1       jtc 
    113       1.5   hubertf 		current_lineno = t->lineno;	/* for $LINENO */
    114       1.5   hubertf 
    115       1.1       jtc 		/* POSIX says expand command words first, then redirections,
    116       1.1       jtc 		 * and assignments last..
    117       1.1       jtc 		 */
    118       1.1       jtc 		ap = eval(t->args, t->u.evalflags | DOBLANK | DOGLOB | DOTILDE);
    119       1.5   hubertf 		if (flags & XTIME)
    120       1.5   hubertf 			/* Allow option parsing (bizarre, but POSIX) */
    121       1.5   hubertf 			timex_hook(t, &ap);
    122       1.1       jtc 		if (Flag(FXTRACE) && ap[0]) {
    123       1.1       jtc 			shf_fprintf(shl_out, "%s",
    124       1.1       jtc 				PS4_SUBSTITUTE(str_val(global("PS4"))));
    125       1.1       jtc 			for (i = 0; ap[i]; i++)
    126       1.1       jtc 				shf_fprintf(shl_out, "%s%s", ap[i],
    127       1.1       jtc 					ap[i + 1] ? space : newline);
    128       1.1       jtc 			shf_flush(shl_out);
    129       1.1       jtc 		}
    130       1.1       jtc 		if (ap[0])
    131       1.1       jtc 			tp = findcom(ap[0], FC_BI|FC_FUNC);
    132       1.1       jtc 	}
    133       1.5   hubertf 	flags &= ~XTIME;
    134       1.1       jtc 
    135       1.1       jtc 	if (t->ioact != NULL || t->type == TPIPE || t->type == TCOPROC) {
    136       1.1       jtc 		e->savefd = (short *) alloc(sizeofN(short, NUFILE), ATEMP);
    137       1.1       jtc 		/* initialize to not redirected */
    138       1.1       jtc 		memset(e->savefd, 0, sizeofN(short, NUFILE));
    139       1.1       jtc 	}
    140       1.1       jtc 
    141       1.1       jtc 	/* do redirection, to be restored in quitenv() */
    142       1.1       jtc 	if (t->ioact != NULL)
    143       1.1       jtc 		for (iowp = t->ioact; *iowp != NULL; iowp++) {
    144       1.1       jtc 			if (iosetup(*iowp, tp) < 0) {
    145       1.1       jtc 				exstat = rv = 1;
    146       1.1       jtc 				/* Redirection failures for special commands
    147       1.1       jtc 				 * cause (non-interactive) shell to exit.
    148       1.1       jtc 				 */
    149       1.1       jtc 				if (tp && tp->type == CSHELL
    150       1.1       jtc 				    && (tp->flag & SPEC_BI))
    151      1.14     joerg 					errorf("%s", null);
    152       1.1       jtc 				/* Deal with FERREXIT, quitenv(), etc. */
    153       1.1       jtc 				goto Break;
    154       1.1       jtc 			}
    155       1.1       jtc 		}
    156       1.1       jtc 
    157       1.1       jtc 	switch(t->type) {
    158       1.1       jtc 	  case TCOM:
    159       1.1       jtc 		rv = comexec(t, tp, ap, flags);
    160       1.1       jtc 		break;
    161       1.1       jtc 
    162       1.1       jtc 	  case TPAREN:
    163       1.1       jtc 		rv = execute(t->left, flags|XFORK);
    164       1.1       jtc 		break;
    165       1.1       jtc 
    166       1.1       jtc 	  case TPIPE:
    167       1.1       jtc 		flags |= XFORK;
    168       1.1       jtc 		flags &= ~XEXEC;
    169       1.1       jtc 		e->savefd[0] = savefd(0, 0);
    170      1.23     kamil 		(void) ksh_dup2(e->savefd[0], 0, false); /* stdin of first */
    171       1.1       jtc 		e->savefd[1] = savefd(1, 0);
    172       1.1       jtc 		while (t->type == TPIPE) {
    173       1.1       jtc 			openpipe(pv);
    174      1.23     kamil 			(void) ksh_dup2(pv[1], 1, false); /* stdout of curr */
    175       1.1       jtc 			/* Let exchild() close pv[0] in child
    176       1.1       jtc 			 * (if this isn't done, commands like
    177       1.1       jtc 			 *    (: ; cat /etc/termcap) | sleep 1
    178       1.1       jtc 			 *  will hang forever).
    179       1.1       jtc 			 */
    180       1.1       jtc 			exchild(t->left, flags|XPIPEO|XCCLOSE, pv[0]);
    181      1.23     kamil 			(void) ksh_dup2(pv[0], 0, false); /* stdin of next */
    182       1.1       jtc 			closepipe(pv);
    183       1.1       jtc 			flags |= XPIPEI;
    184       1.1       jtc 			t = t->right;
    185       1.1       jtc 		}
    186       1.1       jtc 		restfd(1, e->savefd[1]); /* stdout of last */
    187       1.1       jtc 		e->savefd[1] = 0; /* no need to re-restore this */
    188       1.1       jtc 		/* Let exchild() close 0 in parent, after fork, before wait */
    189       1.1       jtc 		i = exchild(t, flags|XPCLOSE, 0);
    190       1.1       jtc 		if (!(flags&XBGND) && !(flags&XXCOM))
    191       1.1       jtc 			rv = i;
    192       1.1       jtc 		break;
    193       1.1       jtc 
    194       1.1       jtc 	  case TLIST:
    195       1.1       jtc 		while (t->type == TLIST) {
    196       1.1       jtc 			execute(t->left, flags & XERROK);
    197       1.1       jtc 			t = t->right;
    198       1.1       jtc 		}
    199       1.1       jtc 		rv = execute(t, flags & XERROK);
    200       1.1       jtc 		break;
    201       1.1       jtc 
    202       1.1       jtc #ifdef KSH
    203       1.1       jtc 	  case TCOPROC:
    204       1.1       jtc 	  {
    205       1.1       jtc 		sigset_t	omask;
    206       1.1       jtc 
    207       1.1       jtc 		/* Block sigchild as we are using things changed in the
    208       1.1       jtc 		 * signal handler
    209       1.1       jtc 		 */
    210       1.1       jtc 		sigprocmask(SIG_BLOCK, &sm_sigchld, &omask);
    211       1.1       jtc 		e->type = E_ERRH;
    212       1.1       jtc 		i = ksh_sigsetjmp(e->jbuf, 0);
    213       1.1       jtc 		if (i) {
    214       1.1       jtc 			sigprocmask(SIG_SETMASK, &omask, (sigset_t *) 0);
    215       1.1       jtc 			quitenv();
    216       1.1       jtc 			unwind(i);
    217       1.1       jtc 			/*NOTREACHED*/
    218       1.1       jtc 		}
    219      1.21     kamil 
    220       1.1       jtc 		/* Already have a (live) co-process? */
    221       1.1       jtc 		if (coproc.job && coproc.write >= 0)
    222       1.1       jtc 			errorf("coprocess already exists");
    223       1.1       jtc 
    224       1.1       jtc 		/* Can we re-use the existing co-process pipe? */
    225      1.23     kamil 		coproc_cleanup(true);
    226       1.1       jtc 
    227       1.1       jtc 		/* do this before opening pipes, in case these fail */
    228       1.1       jtc 		e->savefd[0] = savefd(0, 0);
    229       1.1       jtc 		e->savefd[1] = savefd(1, 0);
    230       1.1       jtc 
    231       1.1       jtc 		openpipe(pv);
    232       1.9   mycroft 		if (pv[0] != 0) {
    233      1.23     kamil 			ksh_dup2(pv[0], 0, false);
    234       1.9   mycroft 			close(pv[0]);
    235       1.9   mycroft 		}
    236       1.1       jtc 		coproc.write = pv[1];
    237       1.1       jtc 		coproc.job = (void *) 0;
    238       1.1       jtc 
    239       1.1       jtc 		if (coproc.readw >= 0)
    240      1.23     kamil 			ksh_dup2(coproc.readw, 1, false);
    241       1.1       jtc 		else {
    242       1.1       jtc 			openpipe(pv);
    243       1.1       jtc 			coproc.read = pv[0];
    244      1.23     kamil 			ksh_dup2(pv[1], 1, false);
    245       1.1       jtc 			coproc.readw = pv[1];	 /* closed before first read */
    246       1.1       jtc 			coproc.njobs = 0;
    247       1.1       jtc 			/* create new coprocess id */
    248       1.1       jtc 			++coproc.id;
    249       1.1       jtc 		}
    250      1.21     kamil 
    251       1.1       jtc 		sigprocmask(SIG_SETMASK, &omask, (sigset_t *) 0);
    252       1.1       jtc 		e->type = E_EXEC; /* no more need for error handler */
    253       1.1       jtc 
    254       1.1       jtc 		/* exchild() closes coproc.* in child after fork,
    255       1.1       jtc 		 * will also increment coproc.njobs when the
    256       1.1       jtc 		 * job is actually created.
    257       1.1       jtc 		 */
    258       1.1       jtc 		flags &= ~XEXEC;
    259       1.1       jtc 		exchild(t->left, flags|XBGND|XFORK|XCOPROC|XCCLOSE,
    260       1.1       jtc 			coproc.readw);
    261       1.1       jtc 		break;
    262       1.1       jtc 	  }
    263       1.1       jtc #endif /* KSH */
    264       1.1       jtc 
    265       1.1       jtc 	  case TASYNC:
    266       1.1       jtc 		/* XXX non-optimal, I think - "(foo &)", forks for (),
    267       1.1       jtc 		 * forks again for async...  parent should optimize
    268       1.1       jtc 		 * this to "foo &"...
    269       1.1       jtc 		 */
    270       1.1       jtc 		rv = execute(t->left, (flags&~XEXEC)|XBGND|XFORK);
    271       1.1       jtc 		break;
    272       1.1       jtc 
    273       1.1       jtc 	  case TOR:
    274       1.1       jtc 	  case TAND:
    275       1.1       jtc 		rv = execute(t->left, XERROK);
    276       1.1       jtc 		if (t->right != NULL && (rv == 0) == (t->type == TAND))
    277       1.1       jtc 			rv = execute(t->right, flags & XERROK);
    278       1.1       jtc 		else
    279       1.1       jtc 			flags |= XERROK;
    280       1.1       jtc 		break;
    281       1.1       jtc 
    282       1.1       jtc 	  case TBANG:
    283       1.1       jtc 		rv = !execute(t->right, XERROK);
    284       1.1       jtc 		break;
    285       1.1       jtc 
    286       1.1       jtc #ifdef KSH
    287       1.1       jtc 	  case TDBRACKET:
    288       1.1       jtc 	    {
    289       1.1       jtc 		Test_env te;
    290       1.1       jtc 
    291       1.1       jtc 		te.flags = TEF_DBRACKET;
    292       1.1       jtc 		te.pos.wp = t->args;
    293       1.1       jtc 		te.isa = dbteste_isa;
    294       1.1       jtc 		te.getopnd = dbteste_getopnd;
    295       1.1       jtc 		te.eval = dbteste_eval;
    296       1.1       jtc 		te.error = dbteste_error;
    297       1.1       jtc 
    298       1.1       jtc 		rv = test_parse(&te);
    299       1.1       jtc 		break;
    300       1.1       jtc 	    }
    301       1.1       jtc #endif /* KSH */
    302       1.1       jtc 
    303       1.1       jtc 	  case TFOR:
    304       1.1       jtc #ifdef KSH
    305       1.1       jtc 	  case TSELECT:
    306       1.1       jtc 	    {
    307      1.23     kamil 		volatile bool is_first = true;
    308       1.1       jtc #endif /* KSH */
    309       1.1       jtc 		ap = (t->vars != NULL) ?
    310       1.1       jtc 			  eval(t->vars, DOBLANK|DOGLOB|DOTILDE)
    311       1.1       jtc 			: e->loc->argv + 1;
    312       1.1       jtc 		e->type = E_LOOP;
    313       1.1       jtc 		while (1) {
    314       1.1       jtc 			i = ksh_sigsetjmp(e->jbuf, 0);
    315       1.1       jtc 			if (!i)
    316       1.1       jtc 				break;
    317       1.1       jtc 			if ((e->flags&EF_BRKCONT_PASS)
    318       1.1       jtc 			    || (i != LBREAK && i != LCONTIN))
    319       1.1       jtc 			{
    320       1.1       jtc 				quitenv();
    321       1.1       jtc 				unwind(i);
    322       1.1       jtc 			} else if (i == LBREAK) {
    323       1.1       jtc 				rv = 0;
    324       1.1       jtc 				goto Break;
    325       1.1       jtc 			}
    326       1.1       jtc 		}
    327       1.1       jtc 		rv = 0; /* in case of a continue */
    328       1.1       jtc 		if (t->type == TFOR) {
    329       1.1       jtc 			while (*ap != NULL) {
    330       1.5   hubertf 				setstr(global(t->str), *ap++, KSH_UNWIND_ERROR);
    331       1.1       jtc 				rv = execute(t->left, flags & XERROK);
    332       1.1       jtc 			}
    333       1.1       jtc 		}
    334       1.1       jtc #ifdef KSH
    335       1.1       jtc 		else { /* TSELECT */
    336       1.1       jtc 			for (;;) {
    337       1.1       jtc 				if (!(cp = do_selectargs(ap, is_first))) {
    338       1.1       jtc 					rv = 1;
    339       1.1       jtc 					break;
    340       1.1       jtc 				}
    341      1.23     kamil 				is_first = false;
    342       1.5   hubertf 				setstr(global(t->str), cp, KSH_UNWIND_ERROR);
    343       1.1       jtc 				rv = execute(t->left, flags & XERROK);
    344       1.1       jtc 			}
    345       1.1       jtc 		}
    346       1.1       jtc 	    }
    347       1.1       jtc #endif /* KSH */
    348       1.1       jtc 		break;
    349       1.1       jtc 
    350       1.1       jtc 	  case TWHILE:
    351       1.1       jtc 	  case TUNTIL:
    352       1.1       jtc 		e->type = E_LOOP;
    353       1.1       jtc 		while (1) {
    354       1.1       jtc 			i = ksh_sigsetjmp(e->jbuf, 0);
    355       1.1       jtc 			if (!i)
    356       1.1       jtc 				break;
    357       1.1       jtc 			if ((e->flags&EF_BRKCONT_PASS)
    358       1.1       jtc 			    || (i != LBREAK && i != LCONTIN))
    359       1.1       jtc 			{
    360       1.1       jtc 				quitenv();
    361       1.1       jtc 				unwind(i);
    362       1.1       jtc 			} else if (i == LBREAK) {
    363       1.1       jtc 				rv = 0;
    364       1.1       jtc 				goto Break;
    365       1.1       jtc 			}
    366       1.1       jtc 		}
    367       1.1       jtc 		rv = 0; /* in case of a continue */
    368       1.1       jtc 		while ((execute(t->left, XERROK) == 0) == (t->type == TWHILE))
    369       1.1       jtc 			rv = execute(t->right, flags & XERROK);
    370       1.1       jtc 		break;
    371       1.1       jtc 
    372       1.1       jtc 	  case TIF:
    373       1.1       jtc 	  case TELIF:
    374       1.1       jtc 		if (t->right == NULL)
    375       1.1       jtc 			break;	/* should be error */
    376       1.1       jtc 		rv = execute(t->left, XERROK) == 0 ?
    377       1.1       jtc 			execute(t->right->left, flags & XERROK) :
    378       1.1       jtc 			execute(t->right->right, flags & XERROK);
    379       1.1       jtc 		break;
    380       1.1       jtc 
    381       1.1       jtc 	  case TCASE:
    382       1.1       jtc 		cp = evalstr(t->str, DOTILDE);
    383       1.1       jtc 		for (t = t->left; t != NULL && t->type == TPAT; t = t->right)
    384       1.1       jtc 		    for (ap = t->vars; *ap; ap++)
    385       1.1       jtc 			if ((s = evalstr(*ap, DOTILDE|DOPAT))
    386      1.23     kamil 			    && gmatch(cp, s, false))
    387       1.1       jtc 				goto Found;
    388       1.1       jtc 		break;
    389       1.1       jtc 	  Found:
    390       1.1       jtc 		rv = execute(t->left, flags & XERROK);
    391       1.1       jtc 		break;
    392       1.1       jtc 
    393       1.1       jtc 	  case TBRACE:
    394       1.1       jtc 		rv = execute(t->left, flags & XERROK);
    395       1.1       jtc 		break;
    396       1.1       jtc 
    397       1.1       jtc 	  case TFUNCT:
    398       1.1       jtc 		rv = define(t->str, t);
    399       1.1       jtc 		break;
    400       1.1       jtc 
    401       1.1       jtc 	  case TTIME:
    402       1.5   hubertf 		/* Clear XEXEC so nested execute() call doesn't exit
    403       1.5   hubertf 		 * (allows "ls -l | time grep foo").
    404       1.5   hubertf 		 */
    405       1.5   hubertf 		rv = timex(t, flags & ~XEXEC);
    406       1.1       jtc 		break;
    407       1.1       jtc 
    408       1.1       jtc 	  case TEXEC:		/* an eval'd TCOM */
    409       1.1       jtc 		s = t->args[0];
    410       1.1       jtc 		ap = makenv();
    411       1.1       jtc #ifndef F_SETFD
    412       1.1       jtc 		for (i = 0; i < sizeof(clexec_tab); i++)
    413       1.1       jtc 			if (clexec_tab[i]) {
    414       1.1       jtc 				close(i);
    415       1.1       jtc 				clexec_tab[i] = 0;
    416       1.1       jtc 			}
    417       1.1       jtc #endif
    418       1.1       jtc 		restoresigs();
    419       1.2       tls 		cleanup_proc_env();
    420      1.19     kamil 		execve(t->str, t->args, ap);
    421       1.1       jtc 		if (errno == ENOEXEC)
    422       1.1       jtc 			scriptexec(t, ap);
    423       1.1       jtc 		else
    424       1.1       jtc 			errorf("%s: %s", s, strerror(errno));
    425       1.1       jtc 	}
    426       1.1       jtc     Break:
    427       1.1       jtc 	exstat = rv;
    428       1.1       jtc 
    429       1.1       jtc 	quitenv();		/* restores IO */
    430       1.9   mycroft 	if ((flags&XEXEC))
    431       1.5   hubertf 		unwind(LEXIT);	/* exit child */
    432       1.9   mycroft 	if (rv != 0 && !(flags & XERROK)) {
    433       1.1       jtc 		if (Flag(FERREXIT))
    434       1.1       jtc 			unwind(LERROR);
    435       1.1       jtc 		trapsig(SIGERR_);
    436       1.1       jtc 	}
    437       1.1       jtc 	return rv;
    438       1.1       jtc }
    439       1.1       jtc 
    440       1.1       jtc /*
    441       1.1       jtc  * execute simple command
    442       1.1       jtc  */
    443       1.1       jtc 
    444       1.1       jtc static int
    445       1.1       jtc comexec(t, tp, ap, flags)
    446       1.1       jtc 	struct op *t;
    447       1.1       jtc 	struct tbl *volatile tp;
    448  1.26.2.1  pgoyette 	char **ap;
    449       1.1       jtc 	int volatile flags;
    450       1.1       jtc {
    451       1.1       jtc 	int i;
    452      1.15  christos 	int leave = LLEAVE;
    453       1.9   mycroft 	volatile int rv = 0;
    454  1.26.2.1  pgoyette 	char *cp;
    455  1.26.2.1  pgoyette 	char **lastp;
    456       1.1       jtc 	static struct op texec; /* Must be static (XXX but why?) */
    457       1.1       jtc 	int type_flags;
    458       1.1       jtc 	int keepasn_ok;
    459       1.1       jtc 	int fcflags = FC_BI|FC_FUNC|FC_PATH;
    460       1.9   mycroft 	int bourne_function_call = 0;
    461       1.1       jtc 
    462       1.5   hubertf #ifdef KSH
    463       1.1       jtc 	/* snag the last argument for $_ XXX not the same as at&t ksh,
    464       1.1       jtc 	 * which only seems to set $_ after a newline (but not in
    465       1.9   mycroft 	 * functions/dot scripts, but in interactive and script) -
    466       1.1       jtc 	 * perhaps save last arg here and set it in shell()?.
    467       1.1       jtc 	 */
    468       1.5   hubertf 	if (Flag(FTALKING) && *(lastp = ap)) {
    469       1.1       jtc 		while (*++lastp)
    470       1.1       jtc 			;
    471       1.5   hubertf 		/* setstr() can't fail here */
    472       1.5   hubertf 		setstr(typeset("_", LOCAL, 0, INTEGER, 0), *--lastp,
    473       1.5   hubertf 		       KSH_RETURN_ERROR);
    474       1.1       jtc 	}
    475       1.5   hubertf #endif /* KSH */
    476       1.1       jtc 
    477       1.1       jtc 	/* Deal with the shell builtins builtin, exec and command since
    478       1.1       jtc 	 * they can be followed by other commands.  This must be done before
    479       1.1       jtc 	 * we know if we should create a local block, which must be done
    480       1.1       jtc 	 * before we can do a path search (in case the assignments change
    481       1.1       jtc 	 * PATH).
    482       1.1       jtc 	 * Odd cases:
    483       1.1       jtc 	 *   FOO=bar exec > /dev/null		FOO is kept but not exported
    484       1.1       jtc 	 *   FOO=bar exec foobar		FOO is exported
    485       1.1       jtc 	 *   FOO=bar command exec > /dev/null	FOO is neither kept nor exported
    486       1.1       jtc 	 *   FOO=bar command			FOO is neither kept nor exported
    487       1.1       jtc 	 *   PATH=... foobar			use new PATH in foobar search
    488       1.1       jtc 	 */
    489       1.1       jtc 	keepasn_ok = 1;
    490       1.1       jtc 	while (tp && tp->type == CSHELL) {
    491       1.1       jtc 		fcflags = FC_BI|FC_FUNC|FC_PATH;/* undo effects of command */
    492       1.1       jtc 		if (tp->val.f == c_builtin) {
    493       1.1       jtc 			if ((cp = *++ap) == NULL) {
    494       1.1       jtc 				tp = NULL;
    495       1.1       jtc 				break;
    496       1.1       jtc 			}
    497       1.1       jtc 			tp = findcom(cp, FC_BI);
    498       1.1       jtc 			if (tp == NULL)
    499       1.1       jtc 				errorf("builtin: %s: not a builtin", cp);
    500       1.1       jtc 			continue;
    501       1.1       jtc 		} else if (tp->val.f == c_exec) {
    502       1.1       jtc 			if (ap[1] == NULL)
    503       1.1       jtc 				break;
    504       1.1       jtc 			ap++;
    505       1.1       jtc 			flags |= XEXEC;
    506       1.1       jtc 		} else if (tp->val.f == c_command) {
    507       1.1       jtc 			int optc, saw_p = 0;
    508       1.1       jtc 
    509       1.1       jtc 			/* Ugly dealing with options in two places (here and
    510       1.1       jtc 			 * in c_command(), but such is life)
    511       1.1       jtc 			 */
    512       1.1       jtc 			ksh_getopt_reset(&builtin_opt, 0);
    513       1.1       jtc 			while ((optc = ksh_getopt(ap, &builtin_opt, ":p"))
    514       1.1       jtc 									== 'p')
    515       1.1       jtc 				saw_p = 1;
    516       1.1       jtc 			if (optc != EOF)
    517       1.1       jtc 				break;	/* command -vV or something */
    518       1.1       jtc 			/* don't look for functions */
    519       1.1       jtc 			fcflags = FC_BI|FC_PATH;
    520       1.1       jtc 			if (saw_p) {
    521       1.1       jtc 				if (Flag(FRESTRICTED)) {
    522      1.23     kamil 					warningf(true,
    523       1.1       jtc 						"command -p: restricted");
    524       1.1       jtc 					rv = 1;
    525       1.1       jtc 					goto Leave;
    526       1.1       jtc 				}
    527       1.1       jtc 				fcflags |= FC_DEFPATH;
    528       1.1       jtc 			}
    529       1.1       jtc 			ap += builtin_opt.optind;
    530       1.2       tls 			/* POSIX says special builtins lose their status
    531       1.1       jtc 			 * if accessed using command.
    532       1.1       jtc 			 */
    533       1.1       jtc 			keepasn_ok = 0;
    534       1.1       jtc 			if (!ap[0]) {
    535       1.1       jtc 				/* ensure command with no args exits with 0 */
    536       1.1       jtc 				subst_exstat = 0;
    537       1.1       jtc 				break;
    538       1.1       jtc 			}
    539       1.1       jtc 		} else
    540       1.1       jtc 			break;
    541       1.1       jtc 		tp = findcom(ap[0], fcflags & (FC_BI|FC_FUNC));
    542       1.1       jtc 	}
    543       1.1       jtc 	if (keepasn_ok && (!ap[0] || (tp && (tp->flag & KEEPASN))))
    544       1.1       jtc 		type_flags = 0;
    545       1.1       jtc 	else {
    546       1.1       jtc 		/* create new variable/function block */
    547       1.1       jtc 		newblock();
    548       1.1       jtc 		/* ksh functions don't keep assignments, POSIX functions do. */
    549       1.1       jtc 		if (keepasn_ok && tp && tp->type == CFUNC
    550       1.9   mycroft 		    && !(tp->flag & FKSH)) {
    551       1.9   mycroft 			bourne_function_call = 1;
    552       1.1       jtc 			type_flags = 0;
    553       1.9   mycroft 		} else
    554       1.1       jtc 			type_flags = LOCAL|LOCAL_COPY|EXPORT;
    555       1.1       jtc 	}
    556       1.1       jtc 	if (Flag(FEXPORT))
    557       1.1       jtc 		type_flags |= EXPORT;
    558       1.1       jtc 	for (i = 0; t->vars[i]; i++) {
    559       1.1       jtc 		cp = evalstr(t->vars[i], DOASNTILDE);
    560       1.1       jtc 		if (Flag(FXTRACE)) {
    561       1.1       jtc 			if (i == 0)
    562       1.1       jtc 				shf_fprintf(shl_out, "%s",
    563       1.1       jtc 					PS4_SUBSTITUTE(str_val(global("PS4"))));
    564       1.1       jtc 			shf_fprintf(shl_out, "%s%s", cp,
    565       1.1       jtc 				t->vars[i + 1] ? space : newline);
    566       1.1       jtc 			if (!t->vars[i + 1])
    567       1.1       jtc 				shf_flush(shl_out);
    568       1.1       jtc 		}
    569       1.1       jtc 		typeset(cp, type_flags, 0, 0, 0);
    570       1.9   mycroft 		if (bourne_function_call && !(type_flags & EXPORT))
    571       1.9   mycroft 			typeset(cp, LOCAL|LOCAL_COPY|EXPORT, 0, 0, 0);
    572       1.1       jtc 	}
    573       1.1       jtc 
    574       1.1       jtc 	if ((cp = *ap) == NULL) {
    575       1.1       jtc 		rv = subst_exstat;
    576       1.1       jtc 		goto Leave;
    577       1.1       jtc 	} else if (!tp) {
    578       1.1       jtc 		if (Flag(FRESTRICTED) && ksh_strchr_dirsep(cp)) {
    579      1.23     kamil 			warningf(true, "%s: restricted", cp);
    580       1.1       jtc 			rv = 1;
    581       1.1       jtc 			goto Leave;
    582       1.1       jtc 		}
    583       1.1       jtc 		tp = findcom(cp, fcflags);
    584       1.1       jtc 	}
    585       1.1       jtc 
    586       1.1       jtc 	switch (tp->type) {
    587       1.1       jtc 	  case CSHELL:			/* shell built-in */
    588       1.1       jtc 		rv = call_builtin(tp, ap);
    589       1.1       jtc 		break;
    590       1.1       jtc 
    591       1.1       jtc 	  case CFUNC:			/* function call */
    592       1.1       jtc 	  {
    593       1.1       jtc 		volatile int old_xflag;
    594       1.1       jtc 		volatile Tflag old_inuse;
    595       1.1       jtc 		const char *volatile old_kshname;
    596       1.1       jtc 
    597       1.1       jtc 		if (!(tp->flag & ISSET)) {
    598       1.1       jtc 			struct tbl *ftp;
    599       1.1       jtc 
    600       1.1       jtc 			if (!tp->u.fpath) {
    601       1.1       jtc 				if (tp->u2.errno_) {
    602      1.23     kamil 					warningf(true,
    603       1.1       jtc 				"%s: can't find function definition file - %s",
    604       1.1       jtc 						cp, strerror(tp->u2.errno_));
    605       1.1       jtc 					rv = 126;
    606       1.1       jtc 				} else {
    607      1.23     kamil 					warningf(true,
    608       1.1       jtc 				"%s: can't find function definition file", cp);
    609       1.1       jtc 					rv = 127;
    610       1.1       jtc 				}
    611       1.1       jtc 				break;
    612       1.1       jtc 			}
    613       1.1       jtc 			if (include(tp->u.fpath, 0, (char **) 0, 0) < 0) {
    614      1.23     kamil 				warningf(true,
    615       1.1       jtc 			    "%s: can't open function definition file %s - %s",
    616       1.1       jtc 					cp, tp->u.fpath, strerror(errno));
    617       1.1       jtc 				rv = 127;
    618       1.1       jtc 				break;
    619       1.1       jtc 			}
    620      1.23     kamil 			if (!(ftp = findfunc(cp, hash(cp), false))
    621       1.1       jtc 			    || !(ftp->flag & ISSET))
    622       1.1       jtc 			{
    623      1.23     kamil 				warningf(true,
    624       1.1       jtc 					"%s: function not defined by %s",
    625       1.1       jtc 					cp, tp->u.fpath);
    626       1.1       jtc 				rv = 127;
    627       1.1       jtc 				break;
    628       1.1       jtc 			}
    629       1.1       jtc 			tp = ftp;
    630       1.1       jtc 		}
    631       1.1       jtc 
    632       1.1       jtc 		/* ksh functions set $0 to function name, POSIX functions leave
    633       1.1       jtc 		 * $0 unchanged.
    634       1.1       jtc 		 */
    635       1.1       jtc 		old_kshname = kshname;
    636       1.1       jtc 		if (tp->flag & FKSH)
    637       1.1       jtc 			kshname = ap[0];
    638       1.5   hubertf 		else
    639      1.11  christos 			ap[0] = (char *) __UNCONST(kshname);
    640       1.1       jtc 		e->loc->argv = ap;
    641       1.1       jtc 		for (i = 0; *ap++ != NULL; i++)
    642       1.1       jtc 			;
    643       1.1       jtc 		e->loc->argc = i - 1;
    644       1.5   hubertf 		/* ksh-style functions handle getopts sanely,
    645       1.5   hubertf 		 * bourne/posix functions are insane...
    646       1.5   hubertf 		 */
    647       1.5   hubertf 		if (tp->flag & FKSH) {
    648       1.5   hubertf 			e->loc->flags |= BF_DOGETOPTS;
    649       1.5   hubertf 			e->loc->getopts_state = user_opt;
    650       1.5   hubertf 			getopts_reset(1);
    651       1.5   hubertf 		}
    652       1.1       jtc 
    653       1.1       jtc 		old_xflag = Flag(FXTRACE);
    654      1.23     kamil 		Flag(FXTRACE) = tp->flag & TRACE ? true : false;
    655       1.1       jtc 
    656       1.1       jtc 		old_inuse = tp->flag & FINUSE;
    657       1.1       jtc 		tp->flag |= FINUSE;
    658       1.1       jtc 
    659       1.1       jtc 		e->type = E_FUNC;
    660       1.1       jtc 		i = ksh_sigsetjmp(e->jbuf, 0);
    661       1.1       jtc 		if (i == 0) {
    662       1.1       jtc 			/* seems odd to pass XERROK here, but at&t ksh does */
    663       1.1       jtc 			exstat = execute(tp->val.t, flags & XERROK);
    664       1.1       jtc 			i = LRETURN;
    665       1.1       jtc 		}
    666       1.1       jtc 		kshname = old_kshname;
    667       1.1       jtc 		Flag(FXTRACE) = old_xflag;
    668       1.1       jtc 		tp->flag = (tp->flag & ~FINUSE) | old_inuse;
    669       1.1       jtc 		/* Were we deleted while executing?  If so, free the execution
    670       1.1       jtc 		 * tree.  todo: Unfortunately, the table entry is never re-used
    671       1.1       jtc 		 * until the lookup table is expanded.
    672       1.1       jtc 		 */
    673       1.1       jtc 		if ((tp->flag & (FDELETE|FINUSE)) == FDELETE) {
    674       1.1       jtc 			if (tp->flag & ALLOC) {
    675       1.1       jtc 				tp->flag &= ~ALLOC;
    676       1.1       jtc 				tfree(tp->val.t, tp->areap);
    677       1.1       jtc 			}
    678       1.1       jtc 			tp->flag = 0;
    679       1.1       jtc 		}
    680       1.1       jtc 		switch (i) {
    681       1.1       jtc 		  case LRETURN:
    682       1.1       jtc 		  case LERROR:
    683       1.1       jtc 			rv = exstat;
    684       1.1       jtc 			break;
    685       1.1       jtc 		  case LINTR:
    686       1.1       jtc 		  case LEXIT:
    687       1.1       jtc 		  case LLEAVE:
    688       1.1       jtc 		  case LSHELL:
    689       1.1       jtc 			quitenv();
    690       1.1       jtc 			unwind(i);
    691       1.1       jtc 			/*NOTREACHED*/
    692       1.1       jtc 		  default:
    693       1.1       jtc 			quitenv();
    694       1.1       jtc 			internal_errorf(1, "CFUNC %d", i);
    695       1.1       jtc 		}
    696       1.1       jtc 		break;
    697       1.1       jtc 	  }
    698       1.1       jtc 
    699       1.1       jtc 	  case CEXEC:		/* executable command */
    700       1.1       jtc 	  case CTALIAS:		/* tracked alias */
    701       1.1       jtc 		if (!(tp->flag&ISSET)) {
    702       1.1       jtc 			/* errno_ will be set if the named command was found
    703       1.1       jtc 			 * but could not be executed (permissions, no execute
    704       1.1       jtc 			 * bit, directory, etc).  Print out a (hopefully)
    705       1.1       jtc 			 * useful error message and set the exit status to 126.
    706       1.1       jtc 			 */
    707       1.1       jtc 			if (tp->u2.errno_) {
    708      1.23     kamil 				warningf(true, "%s: cannot execute - %s", cp,
    709       1.1       jtc 					strerror(tp->u2.errno_));
    710       1.1       jtc 				rv = 126;	/* POSIX */
    711       1.1       jtc 			} else {
    712      1.23     kamil 				warningf(true, "%s: not found", cp);
    713       1.1       jtc 				rv = 127;
    714       1.1       jtc 			}
    715       1.1       jtc 			break;
    716       1.1       jtc 		}
    717       1.1       jtc 
    718       1.5   hubertf #ifdef KSH
    719       1.1       jtc 		/* set $_ to program's full path */
    720       1.5   hubertf 		/* setstr() can't fail here */
    721       1.9   mycroft 		setstr(typeset("_", LOCAL|EXPORT, 0, INTEGER, 0),
    722       1.9   mycroft 		       tp->val.s, KSH_RETURN_ERROR);
    723       1.5   hubertf #endif /* KSH */
    724       1.1       jtc 
    725       1.1       jtc 		if (flags&XEXEC) {
    726       1.1       jtc 			j_exit();
    727       1.1       jtc 			if (!(flags&XBGND) || Flag(FMONITOR)) {
    728       1.1       jtc 				setexecsig(&sigtraps[SIGINT], SS_RESTORE_ORIG);
    729       1.1       jtc 				setexecsig(&sigtraps[SIGQUIT], SS_RESTORE_ORIG);
    730       1.1       jtc 			}
    731       1.1       jtc 		}
    732       1.1       jtc 
    733       1.1       jtc 		/* to fork we set up a TEXEC node and call execute */
    734       1.1       jtc 		texec.type = TEXEC;
    735       1.1       jtc 		texec.left = t;	/* for tprint */
    736       1.1       jtc 		texec.str = tp->val.s;
    737       1.1       jtc 		texec.args = ap;
    738       1.1       jtc 		rv = exchild(&texec, flags, -1);
    739       1.1       jtc 		break;
    740       1.1       jtc 	}
    741      1.15  christos 	leave = LEXIT;
    742       1.1       jtc   Leave:
    743       1.1       jtc 	if (flags & XEXEC) {
    744       1.1       jtc 		exstat = rv;
    745      1.15  christos 		unwind(leave);
    746       1.1       jtc 	}
    747       1.1       jtc 	return rv;
    748       1.1       jtc }
    749       1.1       jtc 
    750       1.1       jtc static void
    751       1.1       jtc scriptexec(tp, ap)
    752  1.26.2.1  pgoyette 	struct op *tp;
    753  1.26.2.1  pgoyette 	char **ap;
    754       1.1       jtc {
    755      1.11  christos 	char *shellv;
    756       1.1       jtc 
    757      1.11  christos 	shellv = str_val(global(EXECSHELL_STR));
    758      1.11  christos 	if (shellv && *shellv)
    759      1.11  christos 		shellv = search(shellv, path, X_OK, (int *) 0);
    760      1.11  christos 	if (!shellv || !*shellv)
    761      1.11  christos 		shellv = __UNCONST(EXECSHELL);
    762       1.1       jtc 
    763       1.1       jtc 	*tp->args-- = tp->str;
    764      1.11  christos 	*tp->args = shellv;
    765       1.1       jtc 
    766      1.19     kamil 	execve(tp->args[0], tp->args, ap);
    767       1.1       jtc 
    768       1.1       jtc 	/* report both the program that was run and the bogus shell */
    769      1.11  christos 	errorf("%s: %s: %s", tp->str, shellv, strerror(errno));
    770       1.1       jtc }
    771       1.1       jtc 
    772       1.1       jtc int
    773       1.1       jtc shcomexec(wp)
    774  1.26.2.1  pgoyette 	char **wp;
    775       1.1       jtc {
    776  1.26.2.1  pgoyette 	struct tbl *tp;
    777       1.1       jtc 
    778      1.26     kamil 	tp = mytsearch(&builtins, *wp, hash(*wp));
    779       1.1       jtc 	if (tp == NULL)
    780       1.1       jtc 		internal_errorf(1, "shcomexec: %s", *wp);
    781       1.1       jtc 	return call_builtin(tp, wp);
    782       1.1       jtc }
    783       1.1       jtc 
    784       1.1       jtc /*
    785       1.1       jtc  * Search function tables for a function.  If create set, a table entry
    786       1.1       jtc  * is created if none is found.
    787       1.1       jtc  */
    788       1.1       jtc struct tbl *
    789       1.1       jtc findfunc(name, h, create)
    790       1.1       jtc 	const char *name;
    791       1.5   hubertf 	unsigned int h;
    792       1.5   hubertf 	int create;
    793       1.1       jtc {
    794       1.1       jtc 	struct block *l;
    795       1.1       jtc 	struct tbl *tp = (struct tbl *) 0;
    796       1.1       jtc 
    797       1.1       jtc 	for (l = e->loc; l; l = l->next) {
    798      1.26     kamil 		tp = mytsearch(&l->funs, name, h);
    799       1.1       jtc 		if (tp)
    800       1.1       jtc 			break;
    801       1.1       jtc 		if (!l->next && create) {
    802       1.1       jtc 			tp = tenter(&l->funs, name, h);
    803       1.1       jtc 			tp->flag = DEFINED;
    804       1.1       jtc 			tp->type = CFUNC;
    805       1.1       jtc 			tp->val.t = (struct op *) 0;
    806       1.1       jtc 			break;
    807       1.1       jtc 		}
    808       1.1       jtc 	}
    809       1.1       jtc 	return tp;
    810       1.1       jtc }
    811       1.1       jtc 
    812       1.1       jtc /*
    813       1.1       jtc  * define function.  Returns 1 if function is being undefined (t == 0) and
    814       1.1       jtc  * function did not exist, returns 0 otherwise.
    815       1.1       jtc  */
    816       1.1       jtc int
    817       1.1       jtc define(name, t)
    818       1.1       jtc 	const char *name;
    819       1.1       jtc 	struct op *t;
    820       1.1       jtc {
    821       1.1       jtc 	struct tbl *tp;
    822       1.1       jtc 	int was_set = 0;
    823       1.1       jtc 
    824       1.1       jtc 	while (1) {
    825      1.23     kamil 		tp = findfunc(name, hash(name), true);
    826       1.1       jtc 
    827       1.1       jtc 		if (tp->flag & ISSET)
    828       1.1       jtc 			was_set = 1;
    829       1.1       jtc 		/* If this function is currently being executed, we zap this
    830       1.1       jtc 		 * table entry so findfunc() won't see it
    831       1.1       jtc 		 */
    832       1.1       jtc 		if (tp->flag & FINUSE) {
    833       1.1       jtc 			tp->name[0] = '\0';
    834       1.1       jtc 			tp->flag &= ~DEFINED; /* ensure it won't be found */
    835       1.1       jtc 			tp->flag |= FDELETE;
    836       1.1       jtc 		} else
    837       1.1       jtc 			break;
    838       1.1       jtc 	}
    839       1.1       jtc 
    840       1.1       jtc 	if (tp->flag & ALLOC) {
    841       1.1       jtc 		tp->flag &= ~(ISSET|ALLOC);
    842       1.1       jtc 		tfree(tp->val.t, tp->areap);
    843       1.1       jtc 	}
    844       1.1       jtc 
    845       1.1       jtc 	if (t == NULL) {		/* undefine */
    846      1.25     kamil 		mytdelete(tp);
    847       1.1       jtc 		return was_set ? 0 : 1;
    848       1.1       jtc 	}
    849       1.1       jtc 
    850       1.1       jtc 	tp->val.t = tcopy(t->left, tp->areap);
    851       1.1       jtc 	tp->flag |= (ISSET|ALLOC);
    852       1.1       jtc 	if (t->u.ksh_func)
    853       1.5   hubertf 		tp->flag |= FKSH;
    854       1.1       jtc 
    855       1.1       jtc 	return 0;
    856       1.1       jtc }
    857       1.1       jtc 
    858       1.1       jtc /*
    859       1.1       jtc  * add builtin
    860       1.1       jtc  */
    861       1.1       jtc void
    862       1.1       jtc builtin(name, func)
    863       1.1       jtc 	const char *name;
    864       1.1       jtc 	int (*func) ARGS((char **));
    865       1.1       jtc {
    866  1.26.2.1  pgoyette 	struct tbl *tp;
    867       1.1       jtc 	Tflag flag;
    868       1.1       jtc 
    869       1.1       jtc 	/* see if any flags should be set for this builtin */
    870       1.1       jtc 	for (flag = 0; ; name++) {
    871       1.1       jtc 		if (*name == '=')	/* command does variable assignment */
    872       1.1       jtc 			flag |= KEEPASN;
    873       1.1       jtc 		else if (*name == '*')	/* POSIX special builtin */
    874       1.1       jtc 			flag |= SPEC_BI;
    875       1.1       jtc 		else if (*name == '+')	/* POSIX regular builtin */
    876       1.1       jtc 			flag |= REG_BI;
    877       1.1       jtc 		else
    878       1.1       jtc 			break;
    879       1.1       jtc 	}
    880       1.1       jtc 
    881       1.1       jtc 	tp = tenter(&builtins, name, hash(name));
    882       1.1       jtc 	tp->flag = DEFINED | flag;
    883       1.1       jtc 	tp->type = CSHELL;
    884       1.1       jtc 	tp->val.f = func;
    885       1.1       jtc }
    886       1.1       jtc 
    887       1.1       jtc /*
    888       1.1       jtc  * find command
    889       1.1       jtc  * either function, hashed command, or built-in (in that order)
    890       1.1       jtc  */
    891       1.1       jtc struct tbl *
    892       1.1       jtc findcom(name, flags)
    893       1.1       jtc 	const char *name;
    894       1.1       jtc 	int	flags;		/* FC_* */
    895       1.1       jtc {
    896       1.1       jtc 	static struct tbl temp;
    897       1.1       jtc 	unsigned int h = hash(name);
    898       1.1       jtc 	struct tbl *tp = NULL, *tbi;
    899       1.1       jtc 	int insert = Flag(FTRACKALL);	/* insert if not found */
    900       1.1       jtc 	char *fpath;			/* for function autoloading */
    901       1.1       jtc 	char *npath;
    902       1.1       jtc 
    903       1.1       jtc 	if (ksh_strchr_dirsep(name) != NULL) {
    904       1.1       jtc 		insert = 0;
    905       1.1       jtc 		/* prevent FPATH search below */
    906       1.1       jtc 		flags &= ~FC_FUNC;
    907       1.1       jtc 		goto Search;
    908       1.1       jtc 	}
    909      1.26     kamil 	tbi = (flags & FC_BI) ? mytsearch(&builtins, name, h) : NULL;
    910       1.1       jtc 	/* POSIX says special builtins first, then functions, then
    911       1.1       jtc 	 * POSIX regular builtins, then search path...
    912       1.1       jtc 	 */
    913       1.1       jtc 	if ((flags & FC_SPECBI) && tbi && (tbi->flag & SPEC_BI))
    914       1.1       jtc 		tp = tbi;
    915       1.1       jtc 	if (!tp && (flags & FC_FUNC)) {
    916      1.23     kamil 		tp = findfunc(name, h, false);
    917       1.1       jtc 		if (tp && !(tp->flag & ISSET)) {
    918       1.1       jtc 			if ((fpath = str_val(global("FPATH"))) == null) {
    919       1.1       jtc 				tp->u.fpath = (char *) 0;
    920       1.1       jtc 				tp->u2.errno_ = 0;
    921       1.1       jtc 			} else
    922       1.1       jtc 				tp->u.fpath = search(name, fpath, R_OK,
    923       1.1       jtc 					&tp->u2.errno_);
    924       1.1       jtc 		}
    925       1.1       jtc 	}
    926       1.1       jtc 	if (!tp && (flags & FC_REGBI) && tbi && (tbi->flag & REG_BI))
    927       1.1       jtc 		tp = tbi;
    928       1.1       jtc 	/* todo: posix says non-special/non-regular builtins must
    929       1.1       jtc 	 * be triggered by some user-controllable means like a
    930       1.1       jtc 	 * special directory in PATH.  Requires modifications to
    931       1.1       jtc 	 * the search() function.  Tracked aliases should be
    932       1.1       jtc 	 * modified to allow tracking of builtin commands.
    933       1.1       jtc 	 * This should be under control of the FPOSIX flag.
    934       1.1       jtc 	 * If this is changed, also change c_whence...
    935       1.1       jtc 	 */
    936       1.1       jtc 	if (!tp && (flags & FC_UNREGBI) && tbi)
    937       1.1       jtc 		tp = tbi;
    938       1.1       jtc 	if (!tp && (flags & FC_PATH) && !(flags & FC_DEFPATH)) {
    939      1.26     kamil 		tp = mytsearch(&taliases, name, h);
    940       1.1       jtc 		if (tp && (tp->flag & ISSET) && eaccess(tp->val.s, X_OK) != 0) {
    941       1.1       jtc 			if (tp->flag & ALLOC) {
    942       1.1       jtc 				tp->flag &= ~ALLOC;
    943       1.1       jtc 				afree(tp->val.s, APERM);
    944       1.1       jtc 			}
    945       1.1       jtc 			tp->flag &= ~ISSET;
    946       1.1       jtc 		}
    947       1.1       jtc 	}
    948       1.1       jtc 
    949       1.1       jtc   Search:
    950       1.1       jtc 	if ((!tp || (tp->type == CTALIAS && !(tp->flag&ISSET)))
    951       1.1       jtc 	    && (flags & FC_PATH))
    952       1.1       jtc 	{
    953       1.1       jtc 		if (!tp) {
    954       1.1       jtc 			if (insert && !(flags & FC_DEFPATH)) {
    955       1.1       jtc 				tp = tenter(&taliases, name, h);
    956       1.1       jtc 				tp->type = CTALIAS;
    957       1.1       jtc 			} else {
    958       1.1       jtc 				tp = &temp;
    959       1.1       jtc 				tp->type = CEXEC;
    960       1.1       jtc 			}
    961       1.1       jtc 			tp->flag = DEFINED;	/* make ~ISSET */
    962       1.1       jtc 		}
    963       1.1       jtc 		npath = search(name, flags & FC_DEFPATH ? def_path : path,
    964       1.1       jtc 				X_OK, &tp->u2.errno_);
    965       1.1       jtc 		if (npath) {
    966      1.13  christos 			if (tp == &temp) {
    967      1.13  christos 			    tp->val.s = npath;
    968      1.13  christos 			} else {
    969      1.13  christos 			    tp->val.s = str_save(npath, APERM);
    970      1.13  christos 			    afree(npath, ATEMP);
    971      1.13  christos 			}
    972       1.1       jtc 			tp->flag |= ISSET|ALLOC;
    973       1.1       jtc 		} else if ((flags & FC_FUNC)
    974       1.1       jtc 			   && (fpath = str_val(global("FPATH"))) != null
    975       1.1       jtc 			   && (npath = search(name, fpath, R_OK,
    976       1.1       jtc 					      &tp->u2.errno_)) != (char *) 0)
    977       1.1       jtc 		{
    978       1.1       jtc 			/* An undocumented feature of at&t ksh is that it
    979       1.1       jtc 			 * searches FPATH if a command is not found, even
    980       1.1       jtc 			 * if the command hasn't been set up as an autoloaded
    981       1.1       jtc 			 * function (ie, no typeset -uf).
    982       1.1       jtc 			 */
    983       1.1       jtc 			tp = &temp;
    984       1.1       jtc 			tp->type = CFUNC;
    985       1.1       jtc 			tp->flag = DEFINED; /* make ~ISSET */
    986       1.1       jtc 			tp->u.fpath = npath;
    987       1.1       jtc 		}
    988       1.1       jtc 	}
    989       1.1       jtc 	return tp;
    990       1.1       jtc }
    991       1.1       jtc 
    992       1.1       jtc /*
    993       1.1       jtc  * flush executable commands with relative paths
    994       1.1       jtc  */
    995       1.1       jtc void
    996       1.1       jtc flushcom(all)
    997       1.1       jtc 	int all;		/* just relative or all */
    998       1.1       jtc {
    999       1.1       jtc 	struct tbl *tp;
   1000       1.1       jtc 	struct tstate ts;
   1001       1.1       jtc 
   1002       1.1       jtc 	for (twalk(&ts, &taliases); (tp = tnext(&ts)) != NULL; )
   1003       1.1       jtc 		if ((tp->flag&ISSET) && (all || !ISDIRSEP(tp->val.s[0]))) {
   1004       1.1       jtc 			if (tp->flag&ALLOC) {
   1005       1.1       jtc 				tp->flag &= ~(ALLOC|ISSET);
   1006       1.1       jtc 				afree(tp->val.s, APERM);
   1007       1.1       jtc 			}
   1008       1.5   hubertf 			tp->flag &= ~ISSET;
   1009       1.1       jtc 		}
   1010       1.1       jtc }
   1011       1.1       jtc 
   1012       1.1       jtc /* Check if path is something we want to find.  Returns -1 for failure. */
   1013       1.1       jtc int
   1014      1.11  christos search_access(pathx, mode, errnop)
   1015      1.11  christos 	const char *pathx;
   1016       1.1       jtc 	int mode;
   1017       1.1       jtc 	int *errnop;		/* set if candidate found, but not suitable */
   1018       1.1       jtc {
   1019       1.1       jtc 	int ret, err = 0;
   1020       1.1       jtc 	struct stat statb;
   1021       1.1       jtc 
   1022      1.11  christos 	if (stat(pathx, &statb) < 0)
   1023       1.1       jtc 		return -1;
   1024      1.11  christos 	ret = eaccess(pathx, mode);
   1025       1.1       jtc 	if (ret < 0)
   1026       1.1       jtc 		err = errno; /* File exists, but we can't access it */
   1027       1.5   hubertf 	else if (mode == X_OK
   1028       1.5   hubertf 		 && (!S_ISREG(statb.st_mode)
   1029       1.5   hubertf 		     /* This 'cause access() says root can execute everything */
   1030       1.5   hubertf 		     || !(statb.st_mode & (S_IXUSR|S_IXGRP|S_IXOTH))))
   1031       1.1       jtc 	{
   1032       1.1       jtc 		ret = -1;
   1033       1.1       jtc 		err = S_ISDIR(statb.st_mode) ? EISDIR : EACCES;
   1034       1.1       jtc 	}
   1035       1.5   hubertf 	if (err && errnop && !*errnop)
   1036       1.1       jtc 		*errnop = err;
   1037       1.1       jtc 	return ret;
   1038       1.1       jtc }
   1039       1.1       jtc 
   1040       1.1       jtc /*
   1041       1.1       jtc  * search for command with PATH
   1042       1.1       jtc  */
   1043       1.1       jtc char *
   1044      1.11  christos search(name, pathx, mode, errnop)
   1045       1.1       jtc 	const char *name;
   1046      1.11  christos 	const char *pathx;
   1047       1.1       jtc 	int mode;		/* R_OK or X_OK */
   1048       1.1       jtc 	int *errnop;		/* set if candidate found, but not suitable */
   1049       1.1       jtc {
   1050       1.1       jtc 	const char *sp, *p;
   1051       1.1       jtc 	char *xp;
   1052       1.1       jtc 	XString xs;
   1053       1.1       jtc 	int namelen;
   1054       1.1       jtc 
   1055       1.1       jtc 	if (errnop)
   1056       1.1       jtc 		*errnop = 0;
   1057       1.1       jtc 
   1058       1.1       jtc 	if (ksh_strchr_dirsep(name)) {
   1059       1.1       jtc 		if (search_access(name, mode, errnop) == 0)
   1060      1.11  christos 			return (char *)__UNCONST(name);
   1061       1.1       jtc 		return NULL;
   1062       1.1       jtc 	}
   1063       1.1       jtc 
   1064       1.1       jtc 	namelen = strlen(name) + 1;
   1065       1.1       jtc 	Xinit(xs, xp, 128, ATEMP);
   1066       1.1       jtc 
   1067      1.11  christos 	sp = pathx;
   1068       1.1       jtc 	while (sp != NULL) {
   1069       1.1       jtc 		xp = Xstring(xs, xp);
   1070       1.1       jtc 		if (!(p = strchr(sp, PATHSEP)))
   1071       1.1       jtc 			p = sp + strlen(sp);
   1072       1.1       jtc 		if (p != sp) {
   1073       1.1       jtc 			XcheckN(xs, xp, p - sp);
   1074       1.1       jtc 			memcpy(xp, sp, p - sp);
   1075       1.1       jtc 			xp += p - sp;
   1076       1.1       jtc 			*xp++ = DIRSEP;
   1077       1.1       jtc 		}
   1078       1.1       jtc 		sp = p;
   1079       1.1       jtc 		XcheckN(xs, xp, namelen);
   1080       1.1       jtc 		memcpy(xp, name, namelen);
   1081       1.1       jtc  		if (search_access(Xstring(xs, xp), mode, errnop) == 0)
   1082       1.1       jtc 			return Xclose(xs, xp + namelen);
   1083       1.1       jtc 		if (*sp++ == '\0')
   1084       1.1       jtc 			sp = NULL;
   1085       1.1       jtc 	}
   1086       1.1       jtc 	Xfree(xs, xp);
   1087       1.1       jtc 	return NULL;
   1088       1.1       jtc }
   1089       1.1       jtc 
   1090       1.1       jtc static int
   1091       1.1       jtc call_builtin(tp, wp)
   1092       1.1       jtc 	struct tbl *tp;
   1093       1.1       jtc 	char **wp;
   1094       1.1       jtc {
   1095       1.1       jtc 	int rv;
   1096       1.1       jtc 
   1097       1.1       jtc 	builtin_argv0 = wp[0];
   1098       1.1       jtc 	builtin_flag = tp->flag;
   1099       1.1       jtc 	shf_reopen(1, SHF_WR, shl_stdout);
   1100       1.1       jtc 	shl_stdout_ok = 1;
   1101       1.1       jtc 	ksh_getopt_reset(&builtin_opt, GF_ERROR);
   1102       1.1       jtc 	rv = (*tp->val.f)(wp);
   1103       1.1       jtc 	shf_flush(shl_stdout);
   1104       1.1       jtc 	shl_stdout_ok = 0;
   1105       1.1       jtc 	builtin_flag = 0;
   1106       1.1       jtc 	builtin_argv0 = (char *) 0;
   1107       1.1       jtc 	return rv;
   1108       1.1       jtc }
   1109       1.1       jtc 
   1110       1.1       jtc /*
   1111       1.1       jtc  * set up redirection, saving old fd's in e->savefd
   1112       1.1       jtc  */
   1113       1.1       jtc static int
   1114       1.1       jtc iosetup(iop, tp)
   1115  1.26.2.1  pgoyette 	struct ioword *iop;
   1116       1.1       jtc 	struct tbl *tp;
   1117       1.1       jtc {
   1118  1.26.2.1  pgoyette 	int u = -1;
   1119       1.1       jtc 	char *cp = iop->name;
   1120       1.1       jtc 	int iotype = iop->flag & IOTYPE;
   1121       1.1       jtc 	int do_open = 1, do_close = 0, UNINITIALIZED(flags);
   1122       1.1       jtc 	struct ioword iotmp;
   1123       1.1       jtc 	struct stat statb;
   1124       1.1       jtc 
   1125       1.1       jtc 	if (iotype != IOHERE)
   1126       1.5   hubertf 		cp = evalonestr(cp, DOTILDE|(Flag(FTALKING_I) ? DOGLOB : 0));
   1127       1.1       jtc 
   1128       1.1       jtc 	/* Used for tracing and error messages to print expanded cp */
   1129       1.1       jtc 	iotmp = *iop;
   1130       1.1       jtc 	iotmp.name = (iotype == IOHERE) ? (char *) 0 : cp;
   1131       1.1       jtc 	iotmp.flag |= IONAMEXP;
   1132       1.1       jtc 
   1133       1.1       jtc 	if (Flag(FXTRACE))
   1134       1.1       jtc 		shellf("%s%s\n",
   1135       1.1       jtc 			PS4_SUBSTITUTE(str_val(global("PS4"))),
   1136       1.1       jtc 			snptreef((char *) 0, 32, "%R", &iotmp));
   1137       1.1       jtc 
   1138       1.1       jtc 	switch (iotype) {
   1139       1.1       jtc 	  case IOREAD:
   1140       1.1       jtc 		flags = O_RDONLY;
   1141       1.1       jtc 		break;
   1142       1.1       jtc 
   1143       1.1       jtc 	  case IOCAT:
   1144       1.1       jtc 		flags = O_WRONLY | O_APPEND | O_CREAT;
   1145       1.1       jtc 		break;
   1146       1.1       jtc 
   1147       1.1       jtc 	  case IOWRITE:
   1148       1.1       jtc 		flags = O_WRONLY | O_CREAT | O_TRUNC;
   1149       1.5   hubertf 		/* The stat() is here to allow redirections to
   1150       1.5   hubertf 		 * things like /dev/null without error.
   1151       1.5   hubertf 		 */
   1152       1.1       jtc 		if (Flag(FNOCLOBBER) && !(iop->flag & IOCLOB)
   1153       1.1       jtc 		    && (stat(cp, &statb) < 0 || S_ISREG(statb.st_mode)))
   1154       1.1       jtc 			flags |= O_EXCL;
   1155       1.1       jtc 		break;
   1156       1.1       jtc 
   1157       1.1       jtc 	  case IORDWR:
   1158       1.1       jtc 		flags = O_RDWR | O_CREAT;
   1159       1.1       jtc 		break;
   1160       1.1       jtc 
   1161       1.1       jtc 	  case IOHERE:
   1162       1.1       jtc 		do_open = 0;
   1163       1.1       jtc 		/* herein() returns -2 if error has been printed */
   1164       1.5   hubertf 		u = herein(iop->heredoc, iop->flag & IOEVAL);
   1165       1.1       jtc 		/* cp may have wrong name */
   1166       1.1       jtc 		break;
   1167       1.1       jtc 
   1168       1.1       jtc 	  case IODUP:
   1169       1.1       jtc 	  {
   1170       1.1       jtc 		const char *emsg;
   1171       1.1       jtc 
   1172       1.1       jtc 		do_open = 0;
   1173       1.1       jtc 		if (*cp == '-' && !cp[1]) {
   1174       1.1       jtc 			u = 1009;	 /* prevent error return below */
   1175       1.1       jtc 			do_close = 1;
   1176       1.1       jtc 		} else if ((u = check_fd(cp,
   1177       1.1       jtc 				X_OK | ((iop->flag & IORDUP) ? R_OK : W_OK),
   1178       1.1       jtc 				&emsg)) < 0)
   1179       1.1       jtc 		{
   1180      1.23     kamil 			warningf(true, "%s: %s",
   1181       1.1       jtc 				snptreef((char *) 0, 32, "%R", &iotmp), emsg);
   1182       1.1       jtc 			return -1;
   1183       1.1       jtc 		}
   1184       1.9   mycroft 		if (u == iop->unit)
   1185       1.9   mycroft 			return 0;		/* "dup from" == "dup to" */
   1186       1.1       jtc 		break;
   1187       1.1       jtc 	  }
   1188       1.1       jtc 	}
   1189       1.1       jtc 	if (do_open) {
   1190       1.1       jtc 		if (Flag(FRESTRICTED) && (flags & O_CREAT)) {
   1191      1.23     kamil 			warningf(true, "%s: restricted", cp);
   1192       1.1       jtc 			return -1;
   1193       1.1       jtc 		}
   1194       1.1       jtc 		u = open(cp, flags, 0666);
   1195       1.1       jtc 	}
   1196       1.1       jtc 	if (u < 0) {
   1197       1.1       jtc 		/* herein() may already have printed message */
   1198       1.1       jtc 		if (u == -1)
   1199      1.23     kamil 			warningf(true, "cannot %s %s: %s",
   1200       1.1       jtc 			       iotype == IODUP ? "dup"
   1201       1.1       jtc 				: (iotype == IOREAD || iotype == IOHERE) ?
   1202       1.1       jtc 				    "open" : "create", cp, strerror(errno));
   1203       1.1       jtc 		return -1;
   1204       1.1       jtc 	}
   1205       1.1       jtc 	/* Do not save if it has already been redirected (i.e. "cat >x >y"). */
   1206       1.9   mycroft 	if (e->savefd[iop->unit] == 0) {
   1207       1.9   mycroft 		/* If these are the same, it means unit was previously closed */
   1208       1.9   mycroft 		if (u == iop->unit)
   1209       1.9   mycroft 			e->savefd[iop->unit] = -1;
   1210       1.9   mycroft 		else
   1211       1.9   mycroft 			/* c_exec() assumes e->savefd[fd] set for any
   1212       1.9   mycroft 			 * redirections.  Ask savefd() not to close iop->unit;
   1213       1.9   mycroft 			 * this allows error messages to be seen if iop->unit
   1214       1.9   mycroft 			 * is 2; also means we can't lose the fd (eg, both
   1215       1.9   mycroft 			 * dup2 below and dup2 in restfd() failing).
   1216       1.9   mycroft 			 */
   1217       1.9   mycroft 			e->savefd[iop->unit] = savefd(iop->unit, 1);
   1218       1.9   mycroft 	}
   1219       1.1       jtc 
   1220       1.1       jtc 	if (do_close)
   1221       1.1       jtc 		close(iop->unit);
   1222       1.1       jtc 	else if (u != iop->unit) {
   1223      1.23     kamil 		if (ksh_dup2(u, iop->unit, true) < 0) {
   1224      1.23     kamil 			warningf(true,
   1225       1.1       jtc 				"could not finish (dup) redirection %s: %s",
   1226       1.1       jtc 				snptreef((char *) 0, 32, "%R", &iotmp),
   1227       1.1       jtc 				strerror(errno));
   1228       1.1       jtc 			if (iotype != IODUP)
   1229       1.1       jtc 				close(u);
   1230       1.1       jtc 			return -1;
   1231       1.1       jtc 		}
   1232       1.1       jtc 		if (iotype != IODUP)
   1233       1.1       jtc 			close(u);
   1234       1.1       jtc #ifdef KSH
   1235       1.1       jtc 		/* Touching any co-process fd in an empty exec
   1236       1.1       jtc 		 * causes the shell to close its copies
   1237       1.1       jtc 		 */
   1238       1.1       jtc 		else if (tp && tp->type == CSHELL && tp->val.f == c_exec) {
   1239       1.1       jtc 			if (iop->flag & IORDUP)	/* possible exec <&p */
   1240       1.1       jtc 				coproc_read_close(u);
   1241       1.1       jtc 			else			/* possible exec >&p */
   1242       1.1       jtc 				coproc_write_close(u);
   1243       1.1       jtc 		}
   1244       1.1       jtc #endif /* KSH */
   1245       1.1       jtc 	}
   1246       1.1       jtc 	if (u == 2) /* Clear any write errors */
   1247       1.1       jtc 		shf_reopen(2, SHF_WR, shl_out);
   1248       1.1       jtc 	return 0;
   1249       1.1       jtc }
   1250       1.1       jtc 
   1251       1.1       jtc /*
   1252       1.1       jtc  * open here document temp file.
   1253       1.1       jtc  * if unquoted here, expand here temp file into second temp file.
   1254       1.1       jtc  */
   1255       1.1       jtc static int
   1256       1.5   hubertf herein(content, sub)
   1257       1.5   hubertf 	const char *content;
   1258       1.1       jtc 	int sub;
   1259       1.1       jtc {
   1260       1.5   hubertf 	volatile int fd = -1;
   1261       1.5   hubertf 	struct source *s, *volatile osource;
   1262       1.5   hubertf 	struct shf *volatile shf;
   1263       1.5   hubertf 	struct temp *h;
   1264       1.5   hubertf 	int i;
   1265       1.1       jtc 
   1266       1.1       jtc 	/* ksh -c 'cat << EOF' can cause this... */
   1267       1.5   hubertf 	if (content == (char *) 0) {
   1268      1.23     kamil 		warningf(true, "here document missing");
   1269       1.1       jtc 		return -2; /* special to iosetup(): don't print error */
   1270       1.1       jtc 	}
   1271       1.5   hubertf 
   1272       1.5   hubertf 	/* Create temp file to hold content (done before newenv so temp
   1273       1.5   hubertf 	 * doesn't get removed too soon).
   1274       1.5   hubertf 	 */
   1275       1.5   hubertf 	h = maketemp(ATEMP, TT_HEREDOC_EXP, &e->temps);
   1276       1.5   hubertf 	if (!(shf = h->shf) || (fd = open(h->name, O_RDONLY, 0)) < 0) {
   1277      1.23     kamil 		warningf(true, "can't %s temporary file %s: %s",
   1278       1.5   hubertf 			!shf ? "create" : "open",
   1279       1.5   hubertf 			h->name, strerror(errno));
   1280       1.5   hubertf 		if (shf)
   1281       1.5   hubertf 			shf_close(shf);
   1282       1.5   hubertf 		return -2 /* special to iosetup(): don't print error */;
   1283       1.5   hubertf 	}
   1284       1.5   hubertf 
   1285       1.5   hubertf 	osource = source;
   1286       1.5   hubertf 	newenv(E_ERRH);
   1287       1.5   hubertf 	i = ksh_sigsetjmp(e->jbuf, 0);
   1288       1.5   hubertf 	if (i) {
   1289       1.5   hubertf 		source = osource;
   1290       1.5   hubertf 		quitenv();
   1291       1.5   hubertf 		shf_close(shf);	/* after quitenv */
   1292       1.5   hubertf 		close(fd);
   1293       1.5   hubertf 		return -2; /* special to iosetup(): don't print error */
   1294       1.5   hubertf 	}
   1295       1.1       jtc 	if (sub) {
   1296       1.5   hubertf 		/* Do substitutions on the content of heredoc */
   1297       1.5   hubertf 		s = pushs(SSTRING, ATEMP);
   1298       1.5   hubertf 		s->start = s->str = content;
   1299       1.1       jtc 		source = s;
   1300      1.12  christos 		if (yylex(ONEWORD|HEREDOC) != LWORD)
   1301       1.1       jtc 			internal_errorf(1, "herein: yylex");
   1302       1.5   hubertf 		source = osource;
   1303       1.5   hubertf 		shf_puts(evalstr(yylval.cp, 0), shf);
   1304       1.5   hubertf 	} else
   1305       1.5   hubertf 		shf_puts(content, shf);
   1306       1.5   hubertf 
   1307       1.5   hubertf 	quitenv();
   1308       1.5   hubertf 
   1309       1.5   hubertf 	if (shf_close(shf) == EOF) {
   1310       1.5   hubertf 		close(fd);
   1311      1.23     kamil 		warningf(true, "error writing %s: %s", h->name,
   1312       1.5   hubertf 			strerror(errno));
   1313       1.5   hubertf 		return -2; /* special to iosetup(): don't print error */
   1314       1.1       jtc 	}
   1315       1.1       jtc 
   1316       1.1       jtc 	return fd;
   1317       1.1       jtc }
   1318       1.1       jtc 
   1319       1.1       jtc #ifdef KSH
   1320       1.1       jtc /*
   1321       1.1       jtc  *	ksh special - the select command processing section
   1322       1.1       jtc  *	print the args in column form - assuming that we can
   1323       1.1       jtc  */
   1324       1.1       jtc static char *
   1325      1.24     joerg do_selectargs(char **ap, bool print_menu)
   1326       1.1       jtc {
   1327       1.1       jtc 	static const char *const read_args[] = {
   1328       1.1       jtc 					"read", "-r", "REPLY", (char *) 0
   1329       1.1       jtc 				    };
   1330       1.1       jtc 	char *s;
   1331       1.1       jtc 	int i, argct;
   1332       1.1       jtc 
   1333       1.1       jtc 	for (argct = 0; ap[argct]; argct++)
   1334       1.1       jtc 		;
   1335       1.1       jtc 	while (1) {
   1336       1.1       jtc 		/* Menu is printed if
   1337       1.1       jtc 		 *	- this is the first time around the select loop
   1338       1.1       jtc 		 *	- the user enters a blank line
   1339       1.1       jtc 		 *	- the REPLY parameter is empty
   1340       1.1       jtc 		 */
   1341       1.1       jtc 		if (print_menu || !*str_val(global("REPLY")))
   1342       1.1       jtc 			pr_menu(ap);
   1343       1.1       jtc 		shellf("%s", str_val(global("PS3")));
   1344      1.11  christos 		if (call_builtin(findcom("read", FC_BI),
   1345      1.11  christos 		    (char **) __UNCONST(read_args)))
   1346       1.1       jtc 			return (char *) 0;
   1347       1.1       jtc 		s = str_val(global("REPLY"));
   1348       1.1       jtc 		if (*s) {
   1349       1.1       jtc 			i = atoi(s);
   1350       1.1       jtc 			return (i >= 1 && i <= argct) ? ap[i - 1] : null;
   1351       1.1       jtc 		}
   1352       1.1       jtc 		print_menu = 1;
   1353       1.1       jtc 	}
   1354       1.1       jtc }
   1355       1.1       jtc 
   1356       1.1       jtc struct select_menu_info {
   1357       1.1       jtc 	char	*const *args;
   1358       1.1       jtc 	int	arg_width;
   1359       1.1       jtc 	int	num_width;
   1360       1.1       jtc } info;
   1361       1.1       jtc 
   1362       1.1       jtc static char *select_fmt_entry ARGS((void *arg, int i, char *buf, int buflen));
   1363       1.1       jtc 
   1364       1.1       jtc /* format a single select menu item */
   1365       1.1       jtc static char *
   1366       1.1       jtc select_fmt_entry(arg, i, buf, buflen)
   1367       1.1       jtc 	void *arg;
   1368       1.1       jtc 	int i;
   1369       1.1       jtc 	char *buf;
   1370       1.1       jtc 	int buflen;
   1371       1.1       jtc {
   1372       1.1       jtc 	struct select_menu_info *smi = (struct select_menu_info *) arg;
   1373       1.1       jtc 
   1374       1.1       jtc 	shf_snprintf(buf, buflen, "%*d) %s",
   1375       1.1       jtc 		smi->num_width, i + 1, smi->args[i]);
   1376       1.1       jtc 	return buf;
   1377       1.1       jtc }
   1378       1.1       jtc 
   1379       1.1       jtc /*
   1380       1.1       jtc  *	print a select style menu
   1381       1.1       jtc  */
   1382       1.1       jtc int
   1383       1.1       jtc pr_menu(ap)
   1384       1.1       jtc 	char *const *ap;
   1385       1.1       jtc {
   1386       1.1       jtc 	struct select_menu_info smi;
   1387       1.1       jtc 	char *const *pp;
   1388       1.1       jtc 	int nwidth, dwidth;
   1389       1.1       jtc 	int i, n;
   1390       1.1       jtc 
   1391       1.1       jtc 	/* Width/column calculations were done once and saved, but this
   1392       1.1       jtc 	 * means select can't be used recursively so we re-calculate each
   1393       1.1       jtc 	 * time (could save in a structure that is returned, but its probably
   1394       1.1       jtc 	 * not worth the bother).
   1395       1.1       jtc 	 */
   1396       1.1       jtc 
   1397       1.1       jtc 	/*
   1398       1.1       jtc 	 * get dimensions of the list
   1399       1.1       jtc 	 */
   1400       1.1       jtc 	for (n = 0, nwidth = 0, pp = ap; *pp; n++, pp++) {
   1401       1.1       jtc 		i = strlen(*pp);
   1402       1.1       jtc 		nwidth = (i > nwidth) ? i : nwidth;
   1403       1.1       jtc 	}
   1404       1.1       jtc 	/*
   1405       1.1       jtc 	 * we will print an index of the form
   1406       1.1       jtc 	 *	%d)
   1407       1.1       jtc 	 * in front of each entry
   1408       1.1       jtc 	 * get the max width of this
   1409       1.1       jtc 	 */
   1410       1.1       jtc 	for (i = n, dwidth = 1; i >= 10; i /= 10)
   1411       1.1       jtc 		dwidth++;
   1412       1.1       jtc 
   1413       1.1       jtc 	smi.args = ap;
   1414       1.1       jtc 	smi.arg_width = nwidth;
   1415       1.1       jtc 	smi.num_width = dwidth;
   1416       1.1       jtc 	print_columns(shl_out, n, select_fmt_entry, (void *) &smi,
   1417       1.7    provos 		dwidth + nwidth + 2, 1);
   1418       1.7    provos 
   1419       1.7    provos 	return n;
   1420       1.7    provos }
   1421       1.7    provos 
   1422       1.7    provos /* XXX: horrible kludge to fit within the framework */
   1423       1.7    provos 
   1424       1.7    provos static char *plain_fmt_entry ARGS((void *arg, int i, char *buf, int buflen));
   1425       1.7    provos 
   1426       1.7    provos static char *
   1427       1.7    provos plain_fmt_entry(arg, i, buf, buflen)
   1428       1.7    provos 	void *arg;
   1429       1.7    provos 	int i;
   1430       1.7    provos 	char *buf;
   1431       1.7    provos 	int buflen;
   1432       1.7    provos {
   1433       1.7    provos 	shf_snprintf(buf, buflen, "%s", ((char *const *)arg)[i]);
   1434       1.7    provos 	return buf;
   1435       1.7    provos }
   1436       1.7    provos 
   1437       1.7    provos int
   1438       1.7    provos pr_list(ap)
   1439       1.7    provos 	char *const *ap;
   1440       1.7    provos {
   1441       1.7    provos 	char *const *pp;
   1442       1.7    provos 	int nwidth;
   1443       1.7    provos 	int i, n;
   1444       1.7    provos 
   1445       1.7    provos 	for (n = 0, nwidth = 0, pp = ap; *pp; n++, pp++) {
   1446       1.7    provos 		i = strlen(*pp);
   1447       1.7    provos 		nwidth = (i > nwidth) ? i : nwidth;
   1448       1.7    provos 	}
   1449      1.11  christos 	print_columns(shl_out, n, plain_fmt_entry, (void *)__UNCONST(ap),
   1450      1.11  christos 	    nwidth + 1, 0);
   1451       1.1       jtc 
   1452       1.1       jtc 	return n;
   1453       1.1       jtc }
   1454       1.1       jtc #endif /* KSH */
   1455       1.1       jtc #ifdef KSH
   1456       1.1       jtc 
   1457       1.1       jtc /*
   1458       1.1       jtc  *	[[ ... ]] evaluation routines
   1459       1.1       jtc  */
   1460       1.1       jtc 
   1461       1.1       jtc extern const char *const dbtest_tokens[];
   1462       1.1       jtc extern const char db_close[];
   1463       1.1       jtc 
   1464       1.1       jtc /* Test if the current token is a whatever.  Accepts the current token if
   1465       1.1       jtc  * it is.  Returns 0 if it is not, non-zero if it is (in the case of
   1466       1.1       jtc  * TM_UNOP and TM_BINOP, the returned value is a Test_op).
   1467       1.1       jtc  */
   1468       1.1       jtc static int
   1469       1.1       jtc dbteste_isa(te, meta)
   1470       1.1       jtc 	Test_env *te;
   1471       1.1       jtc 	Test_meta meta;
   1472       1.1       jtc {
   1473       1.1       jtc 	int ret = 0;
   1474       1.1       jtc 	int uqword;
   1475       1.1       jtc 	char *p;
   1476       1.1       jtc 
   1477       1.1       jtc 	if (!*te->pos.wp)
   1478       1.1       jtc 		return meta == TM_END;
   1479       1.1       jtc 
   1480       1.1       jtc 	/* unquoted word? */
   1481       1.1       jtc 	for (p = *te->pos.wp; *p == CHAR; p += 2)
   1482       1.1       jtc 		;
   1483       1.1       jtc 	uqword = *p == EOS;
   1484       1.1       jtc 
   1485       1.1       jtc 	if (meta == TM_UNOP || meta == TM_BINOP) {
   1486       1.1       jtc 		if (uqword) {
   1487       1.1       jtc 			char buf[8];	/* longer than the longest operator */
   1488       1.1       jtc 			char *q = buf;
   1489       1.1       jtc 			for (p = *te->pos.wp; *p == CHAR
   1490       1.1       jtc 					      && q < &buf[sizeof(buf) - 1];
   1491       1.1       jtc 					      p += 2)
   1492       1.1       jtc 				*q++ = p[1];
   1493       1.1       jtc 			*q = '\0';
   1494       1.1       jtc 			ret = (int) test_isop(te, meta, buf);
   1495       1.1       jtc 		}
   1496       1.1       jtc 	} else if (meta == TM_END)
   1497       1.1       jtc 		ret = 0;
   1498       1.1       jtc 	else
   1499       1.1       jtc 		ret = uqword
   1500       1.1       jtc 			&& strcmp(*te->pos.wp, dbtest_tokens[(int) meta]) == 0;
   1501       1.1       jtc 
   1502       1.1       jtc 	/* Accept the token? */
   1503       1.1       jtc 	if (ret)
   1504       1.1       jtc 		te->pos.wp++;
   1505       1.1       jtc 
   1506       1.1       jtc 	return ret;
   1507       1.1       jtc }
   1508       1.1       jtc 
   1509       1.1       jtc static const char *
   1510       1.1       jtc dbteste_getopnd(te, op, do_eval)
   1511       1.1       jtc 	Test_env *te;
   1512       1.1       jtc 	Test_op op;
   1513       1.1       jtc 	int do_eval;
   1514       1.1       jtc {
   1515       1.1       jtc 	char *s = *te->pos.wp;
   1516       1.1       jtc 
   1517       1.1       jtc 	if (!s)
   1518       1.1       jtc 		return (char *) 0;
   1519       1.1       jtc 
   1520       1.1       jtc 	te->pos.wp++;
   1521       1.1       jtc 
   1522       1.1       jtc 	if (!do_eval)
   1523       1.1       jtc 		return null;
   1524       1.1       jtc 
   1525       1.1       jtc 	if (op == TO_STEQL || op == TO_STNEQ)
   1526       1.1       jtc 		s = evalstr(s, DOTILDE | DOPAT);
   1527       1.1       jtc 	else
   1528       1.1       jtc 		s = evalstr(s, DOTILDE);
   1529       1.1       jtc 
   1530       1.1       jtc 	return s;
   1531       1.1       jtc }
   1532       1.1       jtc 
   1533       1.1       jtc static int
   1534       1.1       jtc dbteste_eval(te, op, opnd1, opnd2, do_eval)
   1535       1.1       jtc 	Test_env *te;
   1536       1.1       jtc 	Test_op op;
   1537       1.1       jtc 	const char *opnd1;
   1538       1.1       jtc 	const char *opnd2;
   1539       1.1       jtc 	int do_eval;
   1540       1.1       jtc {
   1541       1.1       jtc 	return test_eval(te, op, opnd1, opnd2, do_eval);
   1542       1.1       jtc }
   1543       1.1       jtc 
   1544       1.1       jtc static void
   1545       1.1       jtc dbteste_error(te, offset, msg)
   1546       1.1       jtc 	Test_env *te;
   1547       1.1       jtc 	int offset;
   1548       1.1       jtc 	const char *msg;
   1549       1.1       jtc {
   1550       1.1       jtc 	te->flags |= TEF_ERROR;
   1551       1.1       jtc 	internal_errorf(0, "dbteste_error: %s (offset %d)", msg, offset);
   1552       1.1       jtc }
   1553       1.1       jtc #endif /* KSH */
   1554