1/***********************************************************************
2*                                                                      *
3*               This software is part of the ast package               *
4*          Copyright (c) 1982-2011 AT&T Intellectual Property          *
5*                      and is licensed under the                       *
6*                  Common Public License, Version 1.0                  *
7*                    by AT&T Intellectual Property                     *
8*                                                                      *
9*                A copy of the License is available at                 *
10*            http://www.opensource.org/licenses/cpl1.0.txt             *
11*         (with md5 checksum 059e8cd6165cb4c31e351f2b69388fd9)         *
12*                                                                      *
13*              Information and Software Systems Research               *
14*                            AT&T Research                             *
15*                           Florham Park NJ                            *
16*                                                                      *
17*                  David Korn <dgk@research.att.com>                   *
18*                                                                      *
19***********************************************************************/
20#pragma prototyped
21/*
22 * UNIX shell parse tree executer
23 *
24 *   David Korn
25 *   AT&T Labs
26 *
27 */
28
29#include	"defs.h"
30#include	<fcin.h>
31#include	"variables.h"
32#include	"path.h"
33#include	"name.h"
34#include	"io.h"
35#include	"shnodes.h"
36#include	"jobs.h"
37#include	"test.h"
38#include	"builtins.h"
39#include	"FEATURE/time"
40#include	"FEATURE/externs"
41#include	"FEATURE/locale"
42#include	"streval.h"
43
44#if !_std_malloc
45#   include	<vmalloc.h>
46#endif
47
48#if     _lib_vfork
49#   include     <ast_vfork.h>
50#else
51#   define vfork()      fork()
52#endif
53
54#define SH_NTFORK	SH_TIMING
55#define NV_BLTPFSH	NV_ARRAY
56
57#if _lib_nice
58    extern int	nice(int);
59#endif /* _lib_nice */
60#if !_lib_spawnveg
61#   define spawnveg(a,b,c,d)    spawnve(a,b,c)
62#endif /* !_lib_spawnveg */
63#if SHOPT_SPAWN
64    static pid_t sh_ntfork(Shell_t*,const Shnode_t*,char*[],int*,int);
65#endif /* SHOPT_SPAWN */
66
67static void	sh_funct(Shell_t *,Namval_t*, int, char*[], struct argnod*,int);
68static int	trim_eq(const char*, const char*);
69static void	coproc_init(Shell_t*, int pipes[]);
70
71static void	*timeout;
72static char	pipejob;
73static char	nopost;
74
75struct funenv
76{
77	Namval_t	*node;
78	struct argnod	*env;
79	Namval_t	**nref;
80};
81
82/* ========	command execution	========*/
83
84/*
85 * The following two functions allow command substituion for non-builtins
86 * to use a pipe and to wait for the pipe to close before restoring to a
87 * temp file.
88 */
89static int	subpipe[3] = {-1};
90static int	subdup,tsetio,usepipe;
91static void iousepipe(Shell_t *shp)
92{
93	int i;
94	usepipe++;
95	fcntl(subpipe[0],F_SETFD,FD_CLOEXEC);
96	subpipe[2] = fcntl(1,F_DUPFD,10);
97	shp->fdstatus[subpipe[2]] = shp->fdstatus[1];
98	close(1);
99	fcntl(subpipe[1],F_DUPFD,1);
100	shp->fdstatus[1] = shp->fdstatus[subpipe[1]];
101	sh_close(subpipe[1]);
102	if(subdup=shp->subdup) for(i=0; i < 10; i++)
103	{
104		if(subdup&(1<<i))
105		{
106			sh_close(i);
107			fcntl(1,F_DUPFD,i);
108			shp->fdstatus[i] = shp->fdstatus[1];
109		}
110	}
111}
112
113static void iounpipe(Shell_t *shp)
114{
115	int n;
116	char buff[SF_BUFSIZE];
117	usepipe = 0;
118	close(1);
119	fcntl(subpipe[2], F_DUPFD, 1);
120	shp->fdstatus[1] = shp->fdstatus[subpipe[2]];
121	if(subdup) for(n=0; n < 10; n++)
122	{
123		if(subdup&(1<<n))
124		{
125			sh_close(n);
126			fcntl(1, F_DUPFD, n);
127			shp->fdstatus[n] = shp->fdstatus[1];
128		}
129	}
130	shp->subdup = 0;
131	sh_close(subpipe[2]);
132	while((n = read(subpipe[0],buff,sizeof(buff)))!=0)
133	{
134		if(n>0)
135			sfwrite(sfstdout,buff,n);
136		else if(errno!=EINTR)
137			break;
138	}
139	sh_close(subpipe[0]);
140	subpipe[0] = -1;
141	tsetio = 0;
142}
143
144/*
145 * print time <t> in h:m:s format with precision <p>
146 */
147static void     l_time(Sfio_t *outfile,register clock_t t,int p)
148{
149	register int  min, sec, frac;
150	register int hr;
151	if(p)
152	{
153		frac = t%shgd->lim.clk_tck;
154		frac = (frac*100)/shgd->lim.clk_tck;
155	}
156	t /= shgd->lim.clk_tck;
157	sec = t%60;
158	t /= 60;
159	min = t%60;
160	if(hr=t/60)
161		sfprintf(outfile,"%dh",hr);
162	if(p)
163		sfprintf(outfile,"%dm%d%c%0*ds",min,sec,GETDECIMAL(0),p,frac);
164	else
165		sfprintf(outfile,"%dm%ds",min,sec);
166}
167
168static int p_time(Shell_t *shp, Sfio_t *out, const char *format, clock_t *tm)
169{
170	int		c,p,l,n,offset = staktell();
171	const char	*first;
172	double		d;
173	Stk_t		*stkp = shp->stk;
174	for(first=format ; c= *format; format++)
175	{
176		if(c!='%')
177			continue;
178		sfwrite(stkp, first, format-first);
179		n = l = 0;
180		p = 3;
181		if((c= *++format) == '%')
182		{
183			first = format;
184			continue;
185		}
186		if(c>='0' && c <='9')
187		{
188			p = (c>'3')?3:(c-'0');
189			c = *++format;
190		}
191		else if(c=='P')
192		{
193			if(d=tm[0])
194				d = 100.*(((double)(tm[1]+tm[2]))/d);
195			p = 2;
196			goto skip;
197		}
198		if(c=='l')
199		{
200			l = 1;
201			c = *++format;
202		}
203		if(c=='U')
204			n = 1;
205		else if(c=='S')
206			n = 2;
207		else if(c!='R')
208		{
209			stkseek(stkp,offset);
210			errormsg(SH_DICT,ERROR_exit(0),e_badtformat,c);
211			return(0);
212		}
213		d = (double)tm[n]/shp->gd->lim.clk_tck;
214	skip:
215		if(l)
216			l_time(stkp, tm[n], p);
217		else
218			sfprintf(stkp,"%.*f",p, d);
219		first = format+1;
220	}
221	if(format>first)
222		sfwrite(stkp,first, format-first);
223	sfputc(stkp,'\n');
224	n = stktell(stkp)-offset;
225	sfwrite(out,stkptr(stkp,offset),n);
226	stkseek(stkp,offset);
227	return(n);
228}
229
230#if SHOPT_OPTIMIZE
231/*
232 * clear argument pointers that point into the stack
233 */
234static int p_arg(struct argnod*,int);
235static int p_switch(struct regnod*);
236static int p_comarg(register struct comnod *com)
237{
238	Namval_t *np=com->comnamp;
239	int n = p_arg(com->comset,ARG_ASSIGN);
240	if(com->comarg && (com->comtyp&COMSCAN))
241		n+= p_arg(com->comarg,0);
242	if(com->comstate  && np)
243	{
244		/* call builtin to cleanup state */
245		Shbltin_t *bp = &sh.bltindata;
246		void  *save_ptr = bp->ptr;
247		void  *save_data = bp->data;
248		bp->bnode = np;
249		bp->vnode = com->comnamq;
250		bp->ptr = nv_context(np);
251		bp->data = com->comstate;
252		bp->flags = SH_END_OPTIM;
253		(*funptr(np))(0,(char**)0, bp);
254		bp->ptr = save_ptr;
255		bp->data = save_data;
256	}
257	com->comstate = 0;
258	if(com->comarg && !np)
259		n++;
260	return(n);
261}
262
263extern void sh_optclear(Shell_t*, void*);
264
265static int sh_tclear(register Shnode_t *t)
266{
267	int n=0;
268	if(!t)
269		return(0);
270	switch(t->tre.tretyp&COMMSK)
271	{
272		case TTIME:
273		case TPAR:
274			return(sh_tclear(t->par.partre));
275		case TCOM:
276			return(p_comarg((struct comnod*)t));
277		case TSETIO:
278		case TFORK:
279			return(sh_tclear(t->fork.forktre));
280		case TIF:
281			n=sh_tclear(t->if_.iftre);
282			n+=sh_tclear(t->if_.thtre);
283			n+=sh_tclear(t->if_.eltre);
284			return(n);
285		case TWH:
286			if(t->wh.whinc)
287				n=sh_tclear((Shnode_t*)(t->wh.whinc));
288			n+=sh_tclear(t->wh.whtre);
289			n+=sh_tclear(t->wh.dotre);
290			return(n);
291		case TLST:
292		case TAND:
293		case TORF:
294		case TFIL:
295			n=sh_tclear(t->lst.lstlef);
296			return(n+sh_tclear(t->lst.lstrit));
297		case TARITH:
298			return(p_arg(t->ar.arexpr,ARG_ARITH));
299		case TFOR:
300			n=sh_tclear(t->for_.fortre);
301			return(n+sh_tclear((Shnode_t*)t->for_.forlst));
302		case TSW:
303			n=p_arg(t->sw.swarg,0);
304			return(n+p_switch(t->sw.swlst));
305		case TFUN:
306			n=sh_tclear(t->funct.functtre);
307			return(n+sh_tclear((Shnode_t*)t->funct.functargs));
308		case TTST:
309			if((t->tre.tretyp&TPAREN)==TPAREN)
310				return(sh_tclear(t->lst.lstlef));
311			else
312			{
313				n=p_arg(&(t->lst.lstlef->arg),0);
314				if(t->tre.tretyp&TBINARY)
315					n+=p_arg(&(t->lst.lstrit->arg),0);
316			}
317	}
318	return(n);
319}
320
321static int p_arg(register struct argnod *arg,int flag)
322{
323	while(arg)
324	{
325		if(strlen(arg->argval) || (arg->argflag==ARG_RAW))
326			arg->argchn.ap = 0;
327		else if(flag==0)
328			sh_tclear((Shnode_t*)arg->argchn.ap);
329		else
330			sh_tclear(((struct fornod*)arg->argchn.ap)->fortre);
331		arg = arg->argnxt.ap;
332	}
333	return(0);
334}
335
336static int p_switch(register struct regnod *reg)
337{
338	int n=0;
339	while(reg)
340	{
341		n+=p_arg(reg->regptr,0);
342		n+=sh_tclear(reg->regcom);
343		reg = reg->regnxt;
344	}
345	return(n);
346}
347#   define OPTIMIZE_FLAG	(ARG_OPTIMIZE)
348#   define OPTIMIZE		(flags&OPTIMIZE_FLAG)
349#else
350#   define OPTIMIZE_FLAG	(0)
351#   define OPTIMIZE		(0)
352#   define sh_tclear(x)
353#endif /* SHOPT_OPTIMIZE */
354
355static void out_pattern(Sfio_t *iop, register const char *cp, int n)
356{
357	register int c;
358	do
359	{
360		switch(c= *cp)
361		{
362		    case 0:
363			if(n<0)
364				return;
365			c = n;
366			break;
367		    case '\n':
368			sfputr(iop,"$'\\n",'\'');
369			continue;
370		    case '\\':
371			if (!(c = *++cp))
372				c = '\\';
373			/*FALLTHROUGH*/
374		    case ' ':
375		    case '<': case '>': case ';':
376		    case '$': case '`': case '\t':
377			sfputc(iop,'\\');
378			break;
379		}
380		sfputc(iop,c);
381	}
382	while(*cp++);
383}
384
385static void out_string(Sfio_t *iop, register const char *cp, int c, int quoted)
386{
387	if(quoted)
388	{
389		int n = stktell(stkstd);
390		cp = sh_fmtq(cp);
391		if(iop==stkstd && cp==stkptr(stkstd,n))
392		{
393			*stkptr(stkstd,stktell(stkstd)-1) = c;
394			return;
395		}
396	}
397	sfputr(iop,cp,c);
398}
399
400struct Level
401{
402	Namfun_t	hdr;
403	short		maxlevel;
404};
405
406/*
407 * this is for a debugger but it hasn't been tested yet
408 * if a debug script sets .sh.level it should set up the scope
409 *  as if you were executing in that level
410 */
411static void put_level(Namval_t* np,const char *val,int flags,Namfun_t *fp)
412{
413	Shscope_t	*sp;
414	struct Level *lp = (struct Level*)fp;
415	int16_t level, oldlevel = (int16_t)nv_getnum(np);
416	nv_putv(np,val,flags,fp);
417	if(!val)
418	{
419		fp = nv_stack(np, NIL(Namfun_t*));
420		if(fp && !fp->nofree)
421			free((void*)fp);
422		return;
423	}
424	level = nv_getnum(np);
425	if(level<0 || level > lp->maxlevel)
426	{
427		nv_putv(np, (char*)&oldlevel, NV_INT16, fp);
428		/* perhaps this should be an error */
429		return;
430	}
431	if(level==oldlevel)
432		return;
433	if(sp = sh_getscope(level,SEEK_SET))
434	{
435		sh_setscope(sp);
436		error_info.id = sp->cmdname;
437
438	}
439}
440
441static const Namdisc_t level_disc = {  sizeof(struct Level), put_level };
442
443static struct Level *init_level(Shell_t *shp,int level)
444{
445	struct Level *lp = newof(NiL,struct Level,1,0);
446	lp->maxlevel = level;
447	_nv_unset(SH_LEVELNOD,0);
448	nv_onattr(SH_LEVELNOD,NV_INT16|NV_NOFREE);
449	shp->last_root = nv_dict(DOTSHNOD);
450	nv_putval(SH_LEVELNOD,(char*)&lp->maxlevel,NV_INT16);
451	lp->hdr.disc = &level_disc;
452	nv_disc(SH_LEVELNOD,&lp->hdr,NV_FIRST);
453	return(lp);
454}
455
456/*
457 * write the current command on the stack and make it available as .sh.command
458 */
459int sh_debug(Shell_t *shp, const char *trap, const char *name, const char *subscript, char *const argv[], int flags)
460{
461	Stk_t			*stkp=shp->stk;
462	struct sh_scoped	savst;
463	Namval_t		*np = SH_COMMANDNOD;
464	char			*sav = stkptr(stkp,0);
465	int			n=4, offset=stktell(stkp);
466	const char		*cp = "+=( ";
467	Sfio_t			*iop = stkstd;
468	short			level;
469	if(shp->indebug)
470		return(0);
471	shp->indebug = 1;
472	if(name)
473	{
474		sfputr(iop,name,-1);
475		if(subscript)
476		{
477			sfputc(iop,'[');
478			out_string(iop,subscript,']',1);
479		}
480		if(!(flags&ARG_APPEND))
481			cp+=1, n-=1;
482		if(!(flags&ARG_ASSIGN))
483			n -= 2;
484		sfwrite(iop,cp,n);
485	}
486	if(*argv && !(flags&ARG_RAW))
487		out_string(iop, *argv++,' ', 0);
488	n = (flags&ARG_ARITH);
489	while(cp = *argv++)
490	{
491		if((flags&ARG_EXP) && argv[1]==0)
492			out_pattern(iop, cp,' ');
493		else
494			out_string(iop, cp,' ',n?0: (flags&(ARG_RAW|ARG_NOGLOB))||*argv);
495	}
496	if(flags&ARG_ASSIGN)
497		sfputc(iop,')');
498	else if(iop==stkstd)
499		*stkptr(stkp,stktell(stkp)-1) = 0;
500	np->nvalue.cp = stkfreeze(stkp,1);
501	/* now setup .sh.level variable */
502	shp->st.lineno = error_info.line;
503	level  = shp->fn_depth+shp->dot_depth;
504	shp->last_root = nv_dict(DOTSHNOD);
505	if(!SH_LEVELNOD->nvfun || !SH_LEVELNOD->nvfun->disc || nv_isattr(SH_LEVELNOD,NV_INT16|NV_NOFREE)!=(NV_INT16|NV_NOFREE))
506		init_level(shp,level);
507	else
508		nv_putval(SH_LEVELNOD,(char*)&level,NV_INT16);
509	savst = shp->st;
510	shp->st.trap[SH_DEBUGTRAP] = 0;
511	n = sh_trap(trap,0);
512	np->nvalue.cp = 0;
513	shp->indebug = 0;
514	if(shp->st.cmdname)
515		error_info.id = shp->st.cmdname;
516	nv_putval(SH_PATHNAMENOD,shp->st.filename,NV_NOFREE);
517	nv_putval(SH_FUNNAMENOD,shp->st.funname,NV_NOFREE);
518	shp->st = savst;
519	if(sav != stkptr(stkp,0))
520		stkset(stkp,sav,0);
521	else
522		stkseek(stkp,offset);
523	return(n);
524}
525
526/*
527 * Given stream <iop> compile and execute
528 */
529int sh_eval(register Sfio_t *iop, int mode)
530{
531	register Shnode_t *t;
532	Shell_t  *shp = sh_getinterp();
533	struct slnod *saveslp = shp->st.staklist;
534	int jmpval;
535	struct checkpt *pp = (struct checkpt*)shp->jmplist;
536	struct checkpt buff;
537	static Sfio_t *io_save;
538	volatile int traceon=0, lineno=0;
539	int binscript=shp->binscript;
540	io_save = iop; /* preserve correct value across longjmp */
541	shp->binscript = 0;
542#define SH_TOPFUN	0x8000	/* this is a temporary tksh hack */
543	if (mode & SH_TOPFUN)
544	{
545		mode ^= SH_TOPFUN;
546		shp->fn_reset = 1;
547	}
548	sh_pushcontext(shp,&buff,SH_JMPEVAL);
549	buff.olist = pp->olist;
550	jmpval = sigsetjmp(buff.buff,0);
551	while(jmpval==0)
552	{
553		if(mode&SH_READEVAL)
554		{
555			lineno = shp->inlineno;
556			if(traceon=sh_isoption(SH_XTRACE))
557				sh_offoption(SH_XTRACE);
558		}
559		t = (Shnode_t*)sh_parse(shp,iop,(mode&(SH_READEVAL|SH_FUNEVAL))?mode&SH_FUNEVAL:SH_NL);
560		if(!(mode&SH_FUNEVAL) || !sfreserve(iop,0,0))
561		{
562			if(!(mode&SH_READEVAL))
563				sfclose(iop);
564			io_save = 0;
565			mode &= ~SH_FUNEVAL;
566		}
567		mode &= ~SH_READEVAL;
568		if(!sh_isoption(SH_VERBOSE))
569			sh_offstate(SH_VERBOSE);
570		if((mode&~SH_FUNEVAL) && shp->gd->hist_ptr)
571		{
572			hist_flush(shp->gd->hist_ptr);
573			mode = sh_state(SH_INTERACTIVE);
574		}
575		sh_exec(t,sh_isstate(SH_ERREXIT)|sh_isstate(SH_NOFORK)|(mode&~SH_FUNEVAL));
576		if(!(mode&SH_FUNEVAL))
577			break;
578	}
579	sh_popcontext(shp,&buff);
580	shp->binscript = binscript;
581	if(traceon)
582		sh_onoption(SH_XTRACE);
583	if(lineno)
584		shp->inlineno = lineno;
585	if(io_save)
586		sfclose(io_save);
587	sh_freeup(shp);
588	shp->st.staklist = saveslp;
589	shp->fn_reset = 0;
590	if(jmpval>SH_JMPEVAL)
591		siglongjmp(*shp->jmplist,jmpval);
592	return(shp->exitval);
593}
594
595/*
596 * returns 1 when option -<c> is specified
597 */
598static int checkopt(char *argv[], int c)
599{
600	char *cp;
601	while(cp = *++argv)
602	{
603		if(*cp=='+')
604			continue;
605		if(*cp!='-' || cp[1]=='-')
606			break;
607		if(strchr(++cp,c))
608			return(1);
609		if(*cp=='h' && cp[1]==0 && *++argv==0)
610			break;
611	}
612	return(0);
613}
614
615static void free_list(struct openlist *olist)
616{
617	struct openlist *item,*next;
618	for(item=olist;item;item=next)
619	{
620		next = item->next;
621		free((void*)item);
622	}
623}
624
625/*
626 * set ${.sh.name} and ${.sh.subscript}
627 * set _ to reference for ${.sh.name}[$.sh.subscript]
628 */
629static int set_instance(Shell_t *shp,Namval_t *nq, Namval_t *node, struct Namref *nr)
630{
631	char		*sp=0,*cp;
632	Namarr_t	*ap;
633	Namval_t	*np;
634	if(!nv_isattr(nq,NV_MINIMAL|NV_EXPORT|NV_ARRAY) && (np=(Namval_t*)nq->nvenv) && nv_isarray(np))
635		nq = np;
636	cp = nv_name(nq);
637	memset(nr,0,sizeof(*nr));
638	nr->np = nq;
639	nr->root = shp->var_tree;
640	nr->table = shp->last_table;
641#if SHOPT_NAMESPACE
642	if(!nr->table && shp->namespace)
643		nr->table = shp->namespace;
644#endif /* SHOPT_NAMESPACE */
645	shp->instance = 1;
646	if((ap=nv_arrayptr(nq)) && (sp = nv_getsub(nq)))
647		sp = strdup(sp);
648	shp->instance = 0;
649	if(shp->var_tree!=shp->var_base && !nv_search((char*)nq,nr->root,HASH_BUCKET|HASH_NOSCOPE))
650	{
651#if SHOPT_NAMESPACE
652		nr->root = shp->namespace?nv_dict(shp->namespace):shp->var_base;
653#else
654		nr->root = shp->var_base;
655#endif /* SHOPT_NAMESPACE */
656	}
657	nv_putval(SH_NAMENOD, cp, NV_NOFREE);
658	memcpy(node,L_ARGNOD,sizeof(*node));
659	L_ARGNOD->nvalue.nrp = nr;
660	L_ARGNOD->nvflag = NV_REF|NV_NOFREE;
661	L_ARGNOD->nvfun = 0;
662	L_ARGNOD->nvenv = 0;
663	if(sp)
664	{
665		nv_putval(SH_SUBSCRNOD,nr->sub=sp,NV_NOFREE);
666		return(ap->nelem&ARRAY_SCAN);
667	}
668	return(0);
669}
670
671static void unset_instance(Namval_t *nq, Namval_t *node, struct Namref *nr,long mode)
672{
673	L_ARGNOD->nvalue.nrp = node->nvalue.nrp;
674	L_ARGNOD->nvflag = node->nvflag;
675	L_ARGNOD->nvfun = node->nvfun;
676	if(nr->sub)
677	{
678		nv_putsub(nr->np, nr->sub, mode);
679		free((void*)nr->sub);
680	}
681	_nv_unset(SH_NAMENOD,0);
682	_nv_unset(SH_SUBSCRNOD,0);
683}
684
685#if SHOPT_COSHELL
686unsigned long long	coused;
687/*
688 * print out function definition
689 */
690static void print_fun(register Namval_t* np, void *data)
691{
692	register char *format;
693	NOT_USED(data);
694	if(!is_afunction(np) || !np->nvalue.ip)
695		return;
696	if(nv_isattr(np,NV_FPOSIX))
697		format="%s()\n{ ";
698	else
699		format="function %s\n{ ";
700	sfprintf(sfstdout,format,nv_name(np));
701	sh_deparse(sfstdout,(Shnode_t*)(nv_funtree(np)),0);
702	sfwrite(sfstdout,"}\n",2);
703}
704
705static void *sh_coinit(Shell_t *shp,char **argv)
706{
707	struct cosh	*csp = job.colist;
708	const char 	*name = argv?argv[0]:0;
709	int  		id, open=1;
710	if(!name)
711		return(0);
712	if(*name=='-')
713	{
714		name++;
715		open=0;
716	}
717	nv_open(name,shp->var_tree,NV_IDENT|NV_NOADD);
718	while(csp)
719	{
720		if(strcmp(name,csp->name)==0)
721		{
722			if(open)
723			{
724				coattr(csp->coshell,argv[1]);
725				return((void*)csp);
726			}
727			coclose(csp->coshell);
728			return(0);
729		}
730		csp = csp->next;
731	}
732	if(!open)
733		errormsg(SH_DICT,ERROR_exit(1),"%s: unknown namespace",name);
734	environ[0][2]=0;
735	csp = newof(0,struct cosh,1,strlen(name)+1);
736	if(!(csp->coshell = coopen(NULL,CO_SHELL|CO_SILENT,argv[1])))
737	{
738		free((void*)csp);
739		errormsg(SH_DICT,ERROR_exit(1),"%s: unable to create namespace",name);
740	}
741	csp->coshell->data = (void*)csp;
742	csp->name = (char*)(csp+1);
743	strcpy(csp->name,name);
744	for(id=0; coused&(1<<id); id++);
745	coused |= (1<<id);
746	csp->id = id;
747	csp->next = job.colist;
748	job.colist = csp;
749	return((void*)csp);
750}
751
752int sh_coaddfile(Shell_t *shp, char *name)
753{
754	Namval_t *np = dtmatch(shp->inpool,name);
755	if(!np)
756	{
757		np = (Namval_t*)stakalloc(sizeof(Dtlink_t)+sizeof(char*));
758		np->nvname = name;
759		(Namval_t*)dtinsert(shp->inpool,np);
760		shp->poolfiles++;
761		return(1);
762	}
763	return(0);
764}
765
766static int sh_coexec(Shell_t *shp,const Shnode_t *t, int filt)
767{
768	struct cosh	*csp = ((struct cosh*)shp->coshell);
769	Cojob_t		*cjp;
770	char		*str,*trap,host[PATH_MAX];
771	int		lineno,sig,trace = sh_isoption(SH_XTRACE);
772	int		verbose = sh_isoption(SH_VERBOSE);
773	sh_offoption(SH_XTRACE);
774	sh_offoption(SH_VERBOSE);
775	if(!shp->strbuf2)
776		shp->strbuf2 = sfstropen();
777	sfswap(shp->strbuf2,sfstdout);
778	sh_trap("typeset -p\nprint cd \"$PWD\"\nprint .sh.dollar=$$\nprint umask $(umask)",0);
779	for(sig=shp->st.trapmax;--sig>0;)
780	{
781		if((trap=shp->st.trapcom[sig]) && *trap==0)
782			sfprintf(sfstdout,"trap '' %d\n",sig);
783	}
784	if(t->tre.tretyp==TFIL)
785		lineno = ((struct forknod*)t->lst.lstlef)->forkline;
786	else
787		lineno = t->fork.forkline;
788	if(filt)
789	{
790		if(gethostname(host,sizeof(host)) < 0)
791			errormsg(SH_DICT,ERROR_system(1),e_pipe);
792		if(shp->inpipe[2]>=20000)
793			sfprintf(sfstdout,"command exec < /dev/tcp/%s/%d || print -u2 'cannot create pipe'\n",host,shp->inpipe[2]);
794		sfprintf(sfstdout,"command exec > /dev/tcp/%s/%d || print -u2 'cannot create pipe'\n",host,shp->outpipe[2]);
795		if(filt==3)
796			t = t->fork.forktre;
797	}
798	else
799		t = t->fork.forktre;
800	nv_scan(shp->fun_tree, print_fun, (void*)0,0, 0);
801	if(1)
802	{
803		Dt_t *top = shp->var_tree;
804		sh_scope(shp,(struct argnod*)0,0);
805		shp->inpool = dtopen(&_Nvdisc,Dtset);
806		sh_exec(t,filt==1||filt==2?SH_NOFORK:0);
807		if(shp->poolfiles)
808		{
809			Namval_t *np;
810			sfprintf(sfstdout,"[[ ${.sh} == *pool* ]] && .sh.pool.files=(\n");
811			for(np=(Namval_t*)dtfirst(shp->inpool);np;np=(Namval_t*)dtnext(shp->inpool,np))
812			{
813				sfprintf(sfstdout,"\t%s\n",sh_fmtq(np->nvname));
814			}
815			sfputr(sfstdout,")",'\n');
816			;
817		}
818		dtclose(shp->inpool);
819		shp->inpool = 0;
820		shp->poolfiles = 0;
821		sh_unscope(shp);
822		shp->var_tree = top;
823	}
824	sfprintf(sfstdout,"typeset -f .sh.pool.init && .sh.pool.init\n");
825	sfprintf(sfstdout,"LINENO=%d\n",lineno);
826	if(trace)
827		sh_onoption(SH_XTRACE);
828	if(verbose)
829		sh_onoption(SH_VERBOSE);
830	sh_trap("set +o",0);
831	sh_deparse(sfstdout,t,filt==1||filt==2?FALTPIPE:0);
832	sfputc(sfstdout,0);
833	sfswap(shp->strbuf2,sfstdout);
834	str = sfstruse(shp->strbuf2);
835	if(cjp=coexec(csp->coshell,str,0,NULL,NULL,NULL))
836	{
837		csp->cojob = cjp;
838		cjp->local = shp->coshell;
839		if(filt)
840		{
841			if(filt>1)
842				sh_coaccept(shp,shp->inpipe,1);
843			sh_coaccept(shp,shp->outpipe,0);
844			if(filt > 2)
845			{
846				shp->coutpipe = shp->inpipe[1];
847				shp->fdptrs[shp->coutpipe] = &shp->coutpipe;
848			}
849		}
850		return(sh_copid(csp));
851	}
852	return(-1);
853}
854#endif /*SHOPT_COSHELL*/
855
856int sh_exec(register const Shnode_t *t, int flags)
857{
858	register Shell_t	*shp = sh_getinterp();
859	Stk_t			*stkp = shp->stk;
860	sh_sigcheck(shp);
861	if(t && !shp->st.execbrk && !sh_isoption(SH_NOEXEC))
862	{
863		register int 	type = flags;
864		register char	*com0 = 0;
865		int 		errorflg = (type&sh_state(SH_ERREXIT))|OPTIMIZE;
866		int 		execflg = (type&sh_state(SH_NOFORK));
867		int 		execflg2 = (type&sh_state(SH_FORKED));
868		int 		mainloop = (type&sh_state(SH_INTERACTIVE));
869#if SHOPT_AMP || SHOPT_SPAWN
870		int		ntflag = (type&sh_state(SH_NTFORK));
871#else
872		int		ntflag = 0;
873#endif
874		int		topfd = shp->topfd;
875		char 		*sav=stkptr(stkp,0);
876		char		*cp=0, **com=0, *comn;
877		int		argn;
878		int 		skipexitset = 0;
879		int		was_interactive = 0;
880		int		was_errexit = sh_isstate(SH_ERREXIT);
881		int		was_monitor = sh_isstate(SH_MONITOR);
882		int		echeck = 0;
883		if(flags&sh_state(SH_INTERACTIVE))
884		{
885			if(pipejob==2)
886				job_unlock();
887			pipejob = 0;
888			job.curpgid = 0;
889			flags &= ~sh_state(SH_INTERACTIVE);
890		}
891		sh_offstate(SH_ERREXIT);
892		sh_offstate(SH_DEFPATH);
893		if(was_errexit&flags)
894			sh_onstate(SH_ERREXIT);
895		if(was_monitor&flags)
896			sh_onstate(SH_MONITOR);
897		type = t->tre.tretyp;
898		if(!shp->intrap)
899			shp->oldexit=shp->exitval;
900		shp->exitval=0;
901		shp->lastsig = 0;
902		shp->lastpath = 0;
903		switch(type&COMMSK)
904		{
905		    case TCOM:
906		    {
907			register struct argnod	*argp;
908			char		*trap;
909			Namval_t	*np, *nq, *last_table;
910			struct ionod	*io;
911			int		command=0, flgs=NV_ASSIGN;
912			shp->bltindata.invariant = type>>(COMBITS+2);
913			type &= (COMMSK|COMSCAN);
914			sh_stats(STAT_SCMDS);
915			error_info.line = t->com.comline-shp->st.firstline;
916			com = sh_argbuild(shp,&argn,&(t->com),OPTIMIZE);
917			echeck = 1;
918			if(t->tre.tretyp&COMSCAN)
919			{
920				argp = t->com.comarg;
921				if(argp && *com && !(argp->argflag&ARG_RAW))
922					sh_sigcheck(shp);
923			}
924			np = (Namval_t*)(t->com.comnamp);
925			nq = (Namval_t*)(t->com.comnamq);
926			com0 = com[0];
927			shp->xargexit = 0;
928			while(np==SYSCOMMAND)
929			{
930				register int n = b_command(0,com,&shp->bltindata);
931				if(n==0)
932					break;
933				command += n;
934				np = 0;
935				if(!(com0= *(com+=n)))
936					break;
937				np = nv_bfsearch(com0, shp->bltin_tree, &nq, &cp);
938			}
939			if(shp->xargexit)
940			{
941				shp->xargmin -= command;
942				shp->xargmax -= command;
943			}
944			else
945				shp->xargmin = 0;
946			argn -= command;
947#if SHOPT_COSHELL
948			if(argn && shp->inpool)
949			{
950				if(io=t->tre.treio)
951					sh_redirect(shp,io,0);
952				if(!np || !is_abuiltin(np) || *np->nvname=='/' || np==SYSCD)
953				{
954					char **argv, *cp;
955					for(argv=com+1; cp= *argv; argv++)
956					{
957						if(cp && *cp && *cp!='-')
958							sh_coaddfile(shp,*argv);
959					}
960					break;
961				}
962				if(np!=SYSTYPESET)
963					break;
964			}
965			if(t->tre.tretyp&FAMP)
966			{
967				shp->coshell = sh_coinit(shp,com);
968				com0 = 0;
969				break;
970			}
971#endif /* SHOPT_COSHELL */
972			if(np && is_abuiltin(np))
973			{
974				if(!command)
975				{
976					Namval_t *mp;
977#if SHOPT_NAMESPACE
978					if(shp->namespace && (mp=sh_fsearch(shp,np->nvname,0)))
979						np = mp;
980					else
981#endif /* SHOPT_NAMESPACE */
982					np = dtsearch(shp->fun_tree,np);
983				}
984#if SHOPT_PFSH
985				if(sh_isoption(SH_PFSH) && nv_isattr(np,NV_BLTINOPT) && !nv_isattr(np,NV_BLTPFSH))
986				{
987					if(path_xattr(shp,np->nvname,(char*)0))
988					{
989						dtdelete(shp->bltin_tree,np);
990						np = 0;
991					}
992					else
993						nv_onattr(np,NV_BLTPFSH);
994
995				}
996#endif /* SHOPT_PFSH */
997			}
998			if(com0)
999			{
1000				if(!np && !strchr(com0,'/'))
1001				{
1002					Dt_t *root = command?shp->bltin_tree:shp->fun_tree;
1003					np = nv_bfsearch(com0, root, &nq, &cp);
1004#if SHOPT_NAMESPACE
1005					if(shp->namespace && !nq && !cp)
1006						np = sh_fsearch(shp,com0,0);
1007#endif /* SHOPT_NAMESPACE */
1008				}
1009				comn = com[argn-1];
1010			}
1011			io = t->tre.treio;
1012			if(shp->envlist = argp = t->com.comset)
1013			{
1014				if(argn==0 || (np && nv_isattr(np,BLT_SPC)))
1015				{
1016					Namval_t *tp=0;
1017					if(argn)
1018					{
1019						if(checkopt(com,'A'))
1020							flgs |= NV_ARRAY;
1021						else if(checkopt(com,'a'))
1022							flgs |= NV_IARRAY;
1023					}
1024#if SHOPT_BASH
1025					if(np==SYSLOCAL)
1026					{
1027						if(!nv_getval(SH_FUNNAMENOD))
1028							errormsg(SH_DICT,ERROR_exit(1),"%s: can only be used in a function",com0);
1029						if(!shp->st.var_local)
1030						{
1031							sh_scope(shp,(struct argnod*)0,0);
1032							shp->st.var_local = shp->var_tree;
1033						}
1034
1035					}
1036					if(np==SYSTYPESET || np==SYSLOCAL)
1037#else
1038					if(np==SYSTYPESET ||  (np && np->nvalue.bfp==SYSTYPESET->nvalue.bfp))
1039#endif
1040					{
1041						if(np!=SYSTYPESET)
1042						{
1043							shp->typeinit = np;
1044							tp = nv_type(np);
1045						}
1046						if(checkopt(com,'C'))
1047							flgs |= NV_COMVAR;
1048						if(checkopt(com,'S'))
1049							flgs |= NV_STATIC;
1050						if(checkopt(com,'n'))
1051							flgs |= NV_NOREF;
1052						else if(!shp->typeinit && (checkopt(com,'L') || checkopt(com,'R') || checkopt(com,'Z')))
1053							flgs |= NV_UNJUST;
1054#if SHOPT_TYPEDEF
1055						else if(argn>=3 && checkopt(com,'T'))
1056						{
1057							shp->prefix = NV_CLASS;
1058							flgs |= NV_TYPE;
1059
1060						}
1061#endif /* SHOPT_TYPEDEF */
1062						if((shp->fn_depth && !shp->prefix) || np==SYSLOCAL)
1063							flgs |= NV_NOSCOPE;
1064					}
1065					else if(np==SYSEXPORT)
1066						flgs |= NV_EXPORT;
1067					if(flgs&(NV_EXPORT|NV_NOREF))
1068						flgs |= NV_IDENT;
1069					else
1070						flgs |= NV_VARNAME;
1071#if 0
1072					if(OPTIMIZE)
1073						flgs |= NV_TAGGED;
1074#endif
1075					nv_setlist(argp,flgs,tp);
1076					if(np==shp->typeinit)
1077						shp->typeinit = 0;
1078					shp->envlist = argp;
1079					argp = NULL;
1080				}
1081			}
1082			last_table = shp->last_table;
1083			shp->last_table = 0;
1084			if((io||argn))
1085			{
1086				Shbltin_t *bp=0;
1087				static char *argv[1];
1088				int tflags = 1;
1089				if(np &&  nv_isattr(np,BLT_DCL))
1090					tflags |= 2;
1091				if(argn==0)
1092				{
1093					/* fake 'true' built-in */
1094					np = SYSTRUE;
1095					*argv = nv_name(np);
1096					com = argv;
1097				}
1098				/* set +x doesn't echo */
1099				else if((t->tre.tretyp&FSHOWME) && sh_isoption(SH_SHOWME))
1100				{
1101					int ison = sh_isoption(SH_XTRACE);
1102					if(!ison)
1103						sh_onoption(SH_XTRACE);
1104					sh_trace(shp,com-command,tflags);
1105					if(io)
1106						sh_redirect(shp,io,SH_SHOWME);
1107					if(!ison)
1108						sh_offoption(SH_XTRACE);
1109					break;
1110				}
1111				else if((np!=SYSSET) && sh_isoption(SH_XTRACE))
1112					sh_trace(shp,com-command,tflags);
1113				if(trap=shp->st.trap[SH_DEBUGTRAP])
1114				{
1115					int n = sh_debug(shp,trap,(char*)0,(char*)0, com, ARG_RAW);
1116					if(n==255 && shp->fn_depth+shp->dot_depth)
1117					{
1118						np = SYSRETURN;
1119						argn = 1;
1120						com[0] = np->nvname;
1121						com[1] = 0;
1122						io = 0;
1123						argp = 0;
1124					}
1125					else if(n==2)
1126						break;
1127				}
1128				if(io)
1129					sfsync(shp->outpool);
1130				shp->lastpath = 0;
1131				if(!np  && !strchr(com0,'/'))
1132				{
1133					if(path_search(shp,com0,NIL(Pathcomp_t**),1))
1134					{
1135						error_info.line = t->com.comline-shp->st.firstline;
1136#if SHOPT_NAMESPACE
1137						if(!shp->namespace || !(np=sh_fsearch(shp,com0,0)))
1138#endif /* SHOPT_NAMESPACE */
1139							np=nv_search(com0,shp->fun_tree,0);
1140						if(!np && !np->nvalue.ip)
1141						{
1142							Namval_t *mp=nv_search(com0,shp->bltin_tree,0);
1143							if(mp)
1144								np = mp;
1145						}
1146					}
1147					else
1148					{
1149						if((np=nv_search(com0,shp->track_tree,0)) && !nv_isattr(np,NV_NOALIAS) && np->nvalue.cp)
1150							np=nv_search(nv_getval(np),shp->bltin_tree,0);
1151						else
1152							np = 0;
1153					}
1154				}
1155				if(np && pipejob==2)
1156				{
1157					job_unlock();
1158					pipejob = 1;
1159				}
1160				/* check for builtins */
1161				if(np && is_abuiltin(np))
1162				{
1163					volatile int scope=0, share=0;
1164					volatile void *save_ptr;
1165					volatile void *save_data;
1166					int jmpval, save_prompt;
1167					int was_nofork = execflg?sh_isstate(SH_NOFORK):0;
1168					struct checkpt buff;
1169					unsigned long was_vi=0, was_emacs=0, was_gmacs=0;
1170					struct stat statb;
1171					bp = &shp->bltindata;
1172					save_ptr = bp->ptr;
1173					save_data = bp->data;
1174					memset(&statb, 0, sizeof(struct stat));
1175					if(strchr(nv_name(np),'/'))
1176					{
1177						/*
1178						 * disable editors for built-in
1179						 * versions of commands on PATH
1180						 */
1181						was_vi = sh_isoption(SH_VI);
1182						was_emacs = sh_isoption(SH_EMACS);
1183						was_gmacs = sh_isoption(SH_GMACS);
1184						sh_offoption(SH_VI);
1185						sh_offoption(SH_EMACS);
1186						sh_offoption(SH_GMACS);
1187					}
1188					if(execflg)
1189						sh_onstate(SH_NOFORK);
1190					sh_pushcontext(shp,&buff,SH_JMPCMD);
1191					jmpval = sigsetjmp(buff.buff,1);
1192					if(jmpval == 0)
1193					{
1194						if(!(nv_isattr(np,BLT_ENV)))
1195							error_info.flags |= ERROR_SILENT;
1196						errorpush(&buff.err,0);
1197						if(io)
1198						{
1199							struct openlist *item;
1200							if(np==SYSLOGIN)
1201								type=1;
1202							else if(np==SYSEXEC)
1203								type=1+!com[1];
1204							else
1205								type = (execflg && !shp->subshell && !shp->st.trapcom[0]);
1206							sh_redirect(shp,io,type);
1207							for(item=buff.olist;item;item=item->next)
1208								item->strm=0;
1209						}
1210						if(!(nv_isattr(np,BLT_ENV)))
1211						{
1212							if(bp->nosfio)
1213							{
1214								if(!shp->pwd)
1215									path_pwd(shp,0);
1216								if(shp->pwd)
1217									stat(".",&statb);
1218							}
1219							sfsync(NULL);
1220							share = sfset(sfstdin,SF_SHARE,0);
1221							sh_onstate(SH_STOPOK);
1222							sfpool(sfstderr,NIL(Sfio_t*),SF_WRITE);
1223							sfset(sfstderr,SF_LINE,1);
1224							save_prompt = shp->nextprompt;
1225							shp->nextprompt = 0;
1226						}
1227						if(argp)
1228						{
1229							scope++;
1230							sh_scope(shp,argp,0);
1231						}
1232						opt_info.index = opt_info.offset = 0;
1233						opt_info.disc = 0;
1234						error_info.id = *com;
1235						if(argn)
1236							shp->exitval = 0;
1237						shp->bltinfun = funptr(np);
1238						bp->bnode = np;
1239						bp->vnode = nq;
1240						bp->ptr = nv_context(np);
1241						bp->data = t->com.comstate;
1242						bp->sigset = 0;
1243						bp->notify = 0;
1244						bp->flags = (OPTIMIZE!=0);
1245						if(shp->subshell && nv_isattr(np,BLT_NOSFIO))
1246							sh_subtmpfile(shp);
1247						if(execflg && !shp->subshell &&
1248							!shp->st.trapcom[0] && !shp->st.trap[SH_ERRTRAP] && shp->fn_depth==0 && !nv_isattr(np,BLT_ENV))
1249						{
1250							/* do close-on-exec */
1251							int fd;
1252							for(fd=0; fd < shp->gd->lim.open_max; fd++)
1253								if((shp->fdstatus[fd]&IOCLEX)&&fd!=shp->infd)
1254									sh_close(fd);
1255						}
1256						if(argn)
1257							shp->exitval = (*shp->bltinfun)(argn,com,(void*)bp);
1258						if(error_info.flags&ERROR_INTERACTIVE)
1259							tty_check(ERRIO);
1260						((Shnode_t*)t)->com.comstate = shp->bltindata.data;
1261						bp->data = (void*)save_data;
1262						if(!nv_isattr(np,BLT_EXIT) && shp->exitval!=SH_RUNPROG)
1263							shp->exitval &= SH_EXITMASK;
1264					}
1265					else
1266					{
1267						struct openlist *item;
1268						for(item=buff.olist;item;item=item->next)
1269						{
1270							if(item->strm)
1271							{
1272								sfclrlock(item->strm);
1273								if(shp->gd->hist_ptr && item->strm == shp->gd->hist_ptr->histfp)
1274									hist_close(shp->gd->hist_ptr);
1275								else
1276									sfclose(item->strm);
1277							}
1278						}
1279						if(shp->bltinfun && (error_info.flags&ERROR_NOTIFY))
1280							(*shp->bltinfun)(-2,com,(void*)bp);
1281						/* failure on special built-ins fatal */
1282						if(jmpval<=SH_JMPCMD  && (!nv_isattr(np,BLT_SPC) || command))
1283							jmpval=0;
1284					}
1285					if(bp && bp->ptr!= nv_context(np))
1286						np->nvfun = (Namfun_t*)bp->ptr;
1287					if(execflg && !was_nofork)
1288						sh_offstate(SH_NOFORK);
1289					if(!(nv_isattr(np,BLT_ENV)))
1290					{
1291						if(bp->nosfio && shp->pwd)
1292						{
1293							struct stat stata;
1294							stat(".",&stata);
1295							/* restore directory changed */
1296							if(statb.st_ino!=stata.st_ino || statb.st_dev!=stata.st_dev)
1297								chdir(shp->pwd);
1298						}
1299						sh_offstate(SH_STOPOK);
1300						if(share&SF_SHARE)
1301							sfset(sfstdin,SF_PUBLIC|SF_SHARE,1);
1302						sfset(sfstderr,SF_LINE,0);
1303						sfpool(sfstderr,shp->outpool,SF_WRITE);
1304						sfpool(sfstdin,NIL(Sfio_t*),SF_WRITE);
1305						shp->nextprompt = save_prompt;
1306					}
1307					sh_popcontext(shp,&buff);
1308					errorpop(&buff.err);
1309					error_info.flags &= ~(ERROR_SILENT|ERROR_NOTIFY);
1310					shp->bltinfun = 0;
1311					if(buff.olist)
1312						free_list(buff.olist);
1313					if(was_vi)
1314						sh_onoption(SH_VI);
1315					else if(was_emacs)
1316						sh_onoption(SH_EMACS);
1317					else if(was_gmacs)
1318						sh_onoption(SH_GMACS);
1319					if(scope)
1320						sh_unscope(shp);
1321					bp->ptr = (void*)save_ptr;
1322					bp->data = (void*)save_data;
1323					/* don't restore for subshell exec */
1324					if((shp->topfd>topfd) && !(shp->subshell && np==SYSEXEC))
1325						sh_iorestore(shp,topfd,jmpval);
1326					if(jmpval)
1327						siglongjmp(*shp->jmplist,jmpval);
1328#if 0
1329					if(flgs&NV_STATIC)
1330						((Shnode_t*)t)->com.comset = 0;
1331#endif
1332					if(shp->exitval >=0)
1333						goto setexit;
1334					np = 0;
1335					type=0;
1336				}
1337				/* check for functions */
1338				if(!command && np && nv_isattr(np,NV_FUNCTION))
1339				{
1340					volatile int indx;
1341					int jmpval=0;
1342					struct checkpt buff;
1343					Namval_t node;
1344					struct Namref	nr;
1345					long		mode;
1346					register struct slnod *slp;
1347					if(!np->nvalue.ip)
1348					{
1349						indx = path_search(shp,com0,NIL(Pathcomp_t**),0);
1350						if(indx==1)
1351						{
1352#if SHOPT_NAMESPACE
1353							if(shp->namespace)
1354								np = sh_fsearch(shp,com0,0);
1355							else
1356#endif /* SHOPT_NAMESPACE */
1357							np = nv_search(com0,shp->fun_tree,HASH_NOSCOPE);
1358						}
1359
1360						if(!np->nvalue.ip)
1361						{
1362							if(indx==1)
1363							{
1364								errormsg(SH_DICT,ERROR_exit(0),e_defined,com0);
1365								shp->exitval = ERROR_NOEXEC;
1366							}
1367							else
1368							{
1369								errormsg(SH_DICT,ERROR_exit(0),e_found,"function");
1370								shp->exitval = ERROR_NOENT;
1371							}
1372							goto setexit;
1373						}
1374					}
1375					/* increase refcnt for unset */
1376					slp = (struct slnod*)np->nvenv;
1377					sh_funstaks(slp->slchild,1);
1378					staklink(slp->slptr);
1379					if(nq)
1380					{
1381						Namval_t *mp=0;
1382						if(nv_isattr(np,NV_STATICF) && (mp=nv_type(nq)))
1383							nq = mp;
1384						shp->last_table = last_table;
1385						mode = set_instance(shp,nq,&node,&nr);
1386					}
1387					if(io)
1388					{
1389						indx = shp->topfd;
1390						sh_pushcontext(shp,&buff,SH_JMPCMD);
1391						jmpval = sigsetjmp(buff.buff,0);
1392					}
1393					if(jmpval == 0)
1394					{
1395						if(io)
1396							indx = sh_redirect(shp,io,execflg);
1397						sh_funct(shp,np,argn,com,t->com.comset,(flags&~OPTIMIZE_FLAG));
1398					}
1399					if(io)
1400					{
1401						if(buff.olist)
1402							free_list(buff.olist);
1403						sh_popcontext(shp,&buff);
1404						sh_iorestore(shp,indx,jmpval);
1405					}
1406					if(nq)
1407						unset_instance(nq,&node,&nr,mode);
1408					sh_funstaks(slp->slchild,-1);
1409					stakdelete(slp->slptr);
1410					if(jmpval > SH_JMPFUN)
1411						siglongjmp(*shp->jmplist,jmpval);
1412					goto setexit;
1413				}
1414			}
1415			else if(!io)
1416			{
1417			setexit:
1418				exitset();
1419				break;
1420			}
1421		    }
1422		    case TFORK:
1423		    {
1424			register pid_t parent;
1425			int no_fork,jobid;
1426			int pipes[3];
1427#if SHOPT_COSHELL
1428			if(shp->inpool)
1429			{
1430				sh_exec(t->fork.forktre,0);
1431				break;
1432			}
1433#endif /* SHOPT_COSHELL */
1434			if(shp->subshell)
1435			{
1436				sh_subtmpfile(shp);
1437				if(!usepipe)
1438				{
1439					subpipe[0] = -1;
1440					if(shp->comsub==1 && !(shp->fdstatus[1]&IONOSEEK) && sh_pipe(subpipe)>=0)
1441						iousepipe(shp);
1442				}
1443				if((type&(FAMP|TFORK))==(FAMP|TFORK))
1444					sh_subfork();
1445			}
1446			no_fork = !ntflag && !(type&(FAMP|FPOU)) &&
1447			    !(shp->st.trapcom[SIGINT] && *shp->st.trapcom[SIGINT]) &&
1448			    !shp->st.trapcom[0] && !shp->st.trap[SH_ERRTRAP] &&
1449				((struct checkpt*)shp->jmplist)->mode!=SH_JMPEVAL &&
1450				(execflg2 || (execflg &&
1451				!shp->subshell && shp->fn_depth==0 &&
1452				!(pipejob && sh_isoption(SH_PIPEFAIL))
1453			    ));
1454			if(sh_isstate(SH_PROFILE) || shp->dot_depth)
1455			{
1456				/* disable foreground job monitor */
1457				if(!(type&FAMP))
1458					sh_offstate(SH_MONITOR);
1459#if SHOPT_DEVFD
1460				else if(!(type&FINT))
1461					sh_offstate(SH_MONITOR);
1462#endif /* SHOPT_DEVFD */
1463			}
1464			if(no_fork)
1465				job.parent=parent=0;
1466			else
1467			{
1468#ifdef SHOPT_BGX
1469				int maxjob;
1470				if(((type&(FAMP|FINT)) == (FAMP|FINT)) && (maxjob=nv_getnum(JOBMAXNOD))>0)
1471				{
1472					while(job.numbjob >= maxjob)
1473					{
1474						job_lock();
1475						job_reap(0);
1476						job_unlock();
1477					}
1478				}
1479#endif /* SHOPT_BGX */
1480				nv_getval(RANDNOD);
1481				if(type&FCOOP)
1482				{
1483					pipes[2] = 0;
1484#if SHOPT_COSHELL
1485					if(shp->coshell)
1486					{
1487						if(shp->cpipe[0]<0 || shp->cpipe[1] < 0)
1488						{
1489							sh_copipe(shp,shp->outpipe=shp->cpipe,0);
1490							shp->fdptrs[shp->cpipe[0]] = shp->cpipe;
1491						}
1492						sh_copipe(shp,shp->inpipe=pipes,0);
1493						parent = sh_coexec(shp,t,3);
1494						shp->cpid = parent;
1495						jobid = job_post(shp,parent,0);
1496						goto skip;
1497					}
1498#endif /* SHOPT_COSHELL */
1499					coproc_init(shp,pipes);
1500				}
1501#if SHOPT_COSHELL
1502				if((type&(FAMP|FINT)) == (FAMP|FINT))
1503				{
1504					if(shp->coshell)
1505					{
1506						parent = sh_coexec(shp,t,0);
1507						jobid = job_post(shp,parent,0);
1508						goto skip;
1509					}
1510				}
1511#endif /* SHOPT_COSHELL */
1512#if SHOPT_AMP
1513				if((type&(FAMP|FINT)) == (FAMP|FINT))
1514					parent = sh_ntfork(shp,t,com,&jobid,ntflag);
1515				else
1516					parent = sh_fork(shp,type,&jobid);
1517				if(parent<0)
1518				{
1519					if(shp->comsub==1 && subpipe[0]>=0)
1520						iounpipe(shp);
1521					break;
1522				}
1523#else
1524#if SHOPT_SPAWN
1525#   ifdef _lib_fork
1526				if(com)
1527					parent = sh_ntfork(shp,t,com,&jobid,ntflag);
1528				else
1529					parent = sh_fork(shp,type,&jobid);
1530#   else
1531				if((parent = sh_ntfork(shp,t,com,&jobid,ntflag))<=0)
1532					break;
1533#   endif /* _lib_fork */
1534				if(parent<0)
1535				{
1536					if(shp->comsub==1 && subpipe[0]>=0)
1537						iounpipe(shp);
1538					break;
1539				}
1540#else
1541				parent = sh_fork(shp,type,&jobid);
1542#endif /* SHOPT_SPAWN */
1543#endif
1544			}
1545#if SHOPT_COSHELL
1546		skip:
1547#endif /* SHOPT_COSHELL */
1548			if(job.parent=parent)
1549			/* This is the parent branch of fork
1550			 * It may or may not wait for the child
1551			 */
1552			{
1553				if(pipejob==2)
1554				{
1555					pipejob = 1;
1556					job_unlock();
1557				}
1558				if(type&FPCL)
1559					sh_close(shp->inpipe[0]);
1560				if(type&(FCOOP|FAMP))
1561					shp->bckpid = parent;
1562				else if(!(type&(FAMP|FPOU)))
1563				{
1564					if(shp->topfd > topfd)
1565						sh_iorestore(shp,topfd,0);
1566					if(!sh_isoption(SH_MONITOR))
1567					{
1568						if(!(shp->sigflag[SIGINT]&(SH_SIGFAULT|SH_SIGOFF)))
1569							sh_sigtrap(SIGINT);
1570						shp->trapnote |= SH_SIGIGNORE;
1571					}
1572					if(shp->pipepid)
1573						shp->pipepid = parent;
1574					else
1575						job_wait(parent);
1576					if(usepipe && tsetio &&  subdup)
1577						iounpipe(shp);
1578					if(!sh_isoption(SH_MONITOR))
1579					{
1580						shp->trapnote &= ~SH_SIGIGNORE;
1581						if(shp->exitval == (SH_EXITSIG|SIGINT))
1582							sh_fault(SIGINT);
1583					}
1584				}
1585				if(type&FAMP)
1586				{
1587					if(sh_isstate(SH_PROFILE) || sh_isstate(SH_INTERACTIVE))
1588					{
1589						/* print job number */
1590#ifdef JOBS
1591#   if SHOPT_COSHELL
1592						sfprintf(sfstderr,"[%d]\t%s\n",jobid,sh_pid2str(shp,parent));
1593#   else
1594						sfprintf(sfstderr,"[%d]\t%d\n",jobid,parent);
1595#   endif /* SHOPT_COSHELL */
1596#else
1597						sfprintf(sfstderr,"%d\n",parent);
1598#endif /* JOBS */
1599					}
1600				}
1601				break;
1602			}
1603			else
1604			/*
1605			 * this is the FORKED branch (child) of execute
1606			 */
1607			{
1608				volatile int jmpval;
1609				struct checkpt buff;
1610				if(no_fork)
1611					sh_sigreset(2);
1612				sh_pushcontext(shp,&buff,SH_JMPEXIT);
1613				jmpval = sigsetjmp(buff.buff,0);
1614				if(jmpval)
1615					goto done;
1616				if((type&FINT) && !sh_isstate(SH_MONITOR))
1617				{
1618					/* default std input for & */
1619					signal(SIGINT,SIG_IGN);
1620					signal(SIGQUIT,SIG_IGN);
1621					if(!shp->st.ioset)
1622					{
1623						if(sh_close(0)>=0)
1624							sh_chkopen(e_devnull);
1625					}
1626				}
1627				sh_offstate(SH_MONITOR);
1628				/* pipe in or out */
1629#ifdef _lib_nice
1630				if((type&FAMP) && sh_isoption(SH_BGNICE))
1631					nice(4);
1632#endif /* _lib_nice */
1633				if(type&FPIN)
1634				{
1635#if SHOPT_COSHELL
1636					if(shp->inpipe[2]>20000)
1637						sh_coaccept(shp,shp->inpipe,0);
1638#endif /* SHOPT_COSHELL */
1639					sh_iorenumber(shp,shp->inpipe[0],0);
1640					if(!(type&FPOU) || (type&FCOOP))
1641						sh_close(shp->inpipe[1]);
1642				}
1643				if(type&FPOU)
1644				{
1645#if SHOPT_COSHELL
1646					if(shp->outpipe[2]>20000)
1647						sh_coaccept(shp,shp->outpipe,1);
1648#endif /* SHOPT_COSHELL */
1649					sh_iorenumber(shp,shp->outpipe[1],1);
1650					sh_pclose(shp->outpipe);
1651				}
1652				if((type&COMMSK)!=TCOM)
1653					error_info.line = t->fork.forkline-shp->st.firstline;
1654				if(shp->topfd)
1655					sh_iounsave(shp);
1656				topfd = shp->topfd;
1657				sh_redirect(shp,t->tre.treio,1);
1658				if(shp->topfd > topfd)
1659				{
1660					job_lock();
1661					while((parent = vfork()) < 0)
1662						_sh_fork(shp,parent, 0, (int*)0);
1663					job_fork(parent);
1664					if(parent)
1665					{
1666						job_clear();
1667						job_post(shp,parent,0);
1668						job_wait(parent);
1669						sh_iorestore(shp,topfd,SH_JMPCMD);
1670						sh_done(shp,(shp->exitval&SH_EXITSIG)?(shp->exitval&SH_EXITMASK):0);
1671
1672					}
1673				}
1674				if((type&COMMSK)!=TCOM)
1675				{
1676					/* don't clear job table for out
1677					   pipes so that jobs comand can
1678					   be used in a pipeline
1679					 */
1680					if(!no_fork && !(type&FPOU))
1681						job_clear();
1682					sh_exec(t->fork.forktre,flags|sh_state(SH_NOFORK)|sh_state(SH_FORKED));
1683				}
1684				else if(com0)
1685				{
1686					sh_offoption(SH_ERREXIT);
1687					sh_freeup(shp);
1688					path_exec(shp,com0,com,t->com.comset);
1689				}
1690			done:
1691				sh_popcontext(shp,&buff);
1692				if(jmpval>SH_JMPEXIT)
1693					siglongjmp(*shp->jmplist,jmpval);
1694				sh_done(shp,0);
1695			}
1696		    }
1697
1698		    case TSETIO:
1699		    {
1700		    /*
1701		     * don't create a new process, just
1702		     * save and restore io-streams
1703		     */
1704			pid_t	pid;
1705			int 	jmpval, waitall;
1706			int 	simple = (t->fork.forktre->tre.tretyp&COMMSK)==TCOM;
1707			struct checkpt buff;
1708#if SHOPT_COSHELL
1709			if(shp->inpool)
1710			{
1711				sh_redirect(shp,t->fork.forkio,0);
1712				sh_exec(t->fork.forktre,0);
1713				break;
1714			}
1715#endif /*SHOPT_COSHELL */
1716			if(shp->subshell)
1717				execflg = 0;
1718			sh_pushcontext(shp,&buff,SH_JMPIO);
1719			if(type&FPIN)
1720			{
1721				was_interactive = sh_isstate(SH_INTERACTIVE);
1722				sh_offstate(SH_INTERACTIVE);
1723				sh_iosave(shp,0,shp->topfd,(char*)0);
1724				shp->pipepid = simple;
1725				sh_iorenumber(shp,shp->inpipe[0],0);
1726				/*
1727				 * if read end of pipe is a simple command
1728				 * treat as non-sharable to improve performance
1729				 */
1730				if(simple)
1731					sfset(sfstdin,SF_PUBLIC|SF_SHARE,0);
1732				waitall = job.waitall;
1733				job.waitall = 0;
1734				pid = job.parent;
1735			}
1736			else
1737				error_info.line = t->fork.forkline-shp->st.firstline;
1738			jmpval = sigsetjmp(buff.buff,0);
1739			if(jmpval==0)
1740			{
1741				if(shp->comsub==1)
1742					tsetio = 1;
1743				sh_redirect(shp,t->fork.forkio,execflg);
1744				(t->fork.forktre)->tre.tretyp |= t->tre.tretyp&FSHOWME;
1745				sh_exec(t->fork.forktre,flags&~simple);
1746			}
1747			else
1748				sfsync(shp->outpool);
1749			sh_popcontext(shp,&buff);
1750			sh_iorestore(shp,buff.topfd,jmpval);
1751			if(buff.olist)
1752				free_list(buff.olist);
1753			if(type&FPIN)
1754			{
1755				job.waitall = waitall;
1756				type = shp->exitval;
1757				if(!(type&SH_EXITSIG))
1758				{
1759					/* wait for remainder of pipline */
1760					if(shp->pipepid>1)
1761					{
1762						job_wait(shp->pipepid);
1763						type = shp->exitval;
1764					}
1765					else
1766						job_wait(waitall?pid:0);
1767					if(type || !sh_isoption(SH_PIPEFAIL))
1768						shp->exitval = type;
1769				}
1770				if(shp->comsub==1 && subpipe[0]>=0)
1771					iounpipe(shp);
1772				shp->pipepid = 0;
1773				shp->st.ioset = 0;
1774				if(simple && was_errexit)
1775				{
1776					echeck = 1;
1777					sh_onstate(SH_ERREXIT);
1778				}
1779			}
1780			if(jmpval>SH_JMPIO)
1781				siglongjmp(*shp->jmplist,jmpval);
1782			break;
1783		    }
1784
1785		    case TPAR:
1786#if SHOPT_COSHELL
1787			if(shp->inpool)
1788			{
1789				sh_exec(t->par.partre,0);
1790				break;
1791			}
1792#endif /* SHOPT_COSHELL */
1793			echeck = 1;
1794			flags &= ~OPTIMIZE_FLAG;
1795			if(!shp->subshell && !shp->st.trapcom[0] && !shp->st.trap[SH_ERRTRAP] && (flags&sh_state(SH_NOFORK)))
1796			{
1797				char *savsig;
1798				int nsig,jmpval;
1799				struct checkpt buff;
1800				shp->st.otrapcom = 0;
1801				if((nsig=shp->st.trapmax*sizeof(char*))>0 || shp->st.trapcom[0])
1802				{
1803					nsig += sizeof(char*);
1804					memcpy(savsig=malloc(nsig),(char*)&shp->st.trapcom[0],nsig);
1805					shp->st.otrapcom = (char**)savsig;
1806				}
1807				sh_sigreset(0);
1808				sh_pushcontext(shp,&buff,SH_JMPEXIT);
1809				jmpval = sigsetjmp(buff.buff,0);
1810				if(jmpval==0)
1811					sh_exec(t->par.partre,flags);
1812				sh_popcontext(shp,&buff);
1813				if(jmpval > SH_JMPEXIT)
1814					siglongjmp(*shp->jmplist,jmpval);
1815				if(shp->exitval > 256)
1816					shp->exitval -= 128;
1817				sh_done(shp,0);
1818			}
1819			else if(((type=t->par.partre->tre.tretyp)&FAMP) && ((type&COMMSK)==TFORK))
1820			{
1821				pid_t	pid;
1822				sfsync(NIL(Sfio_t*));
1823				while((pid=fork())< 0)
1824					_sh_fork(shp,pid,0,0);
1825				if(pid==0)
1826				{
1827					sh_exec(t->par.partre,flags);
1828					shp->st.trapcom[0]=0;
1829					sh_done(shp,0);
1830				}
1831			}
1832			else
1833				sh_subshell(shp,t->par.partre,flags,0);
1834			break;
1835
1836		    case TFIL:
1837		    {
1838		    /*
1839		     * This code sets up a pipe.
1840		     * All elements of the pipe are started by the parent.
1841		     * The last element executes in current environment
1842		     */
1843			int	pvo[3];	/* old pipe for multi-stage */
1844			int	pvn[3];	/* current set up pipe */
1845			int	savepipe = pipejob;
1846			int	showme = t->tre.tretyp&FSHOWME;
1847			pid_t	savepgid = job.curpgid;
1848#if SHOPT_COSHELL
1849			int	copipe=0;
1850			Shnode_t	*tt;
1851			if(shp->inpool)
1852			{
1853				do
1854				{
1855					sh_exec(t->lst.lstlef, 0);
1856					t = t->lst.lstrit;
1857					if(flags && (t->tre.tretyp!=TFIL || !(t->lst.lstlef->tre.tretyp&FALTPIPE)))
1858						goto coskip1;
1859				}
1860				while(t->tre.tretyp==TFIL);
1861				sh_exec(t,0);
1862			coskip1:
1863				break;
1864			}
1865			pvo[2] = pvn[2] = 0;
1866#endif /* SHOPT_COSHELL */
1867			job.curpgid = 0;
1868			if(shp->subshell)
1869			{
1870				sh_subtmpfile(shp);
1871				if(!usepipe)
1872				{
1873					subpipe[0] = -1;
1874					if(shp->comsub==1 && !(shp->fdstatus[1]&IONOSEEK) && sh_pipe(subpipe)>=0)
1875						iousepipe(shp);
1876				}
1877			}
1878			shp->inpipe = pvo;
1879			shp->outpipe = pvn;
1880			pvo[1] = -1;
1881			if(sh_isoption(SH_PIPEFAIL))
1882				job.waitall = 1;
1883			else
1884				job.waitall |= !pipejob && sh_isstate(SH_MONITOR);
1885			job_lock();
1886			do
1887			{
1888				/* create the pipe */
1889#if SHOPT_COSHELL
1890				tt = t->lst.lstrit;
1891				if(shp->coshell && !showme)
1892				{
1893					if(t->lst.lstlef->tre.tretyp&FALTPIPE)
1894					{
1895						sh_copipe(shp,pvn,0);
1896						type = sh_coexec(shp,t,1+copipe);
1897						pvn[1] = -1;
1898						pipejob=1;
1899						if(type>0)
1900						{
1901							job_post(shp,type,0);
1902							type = 0;
1903						}
1904						copipe = 1;
1905						pvo[0] = pvn[0];
1906						while(tt->tre.tretyp==TFIL && tt->lst.lstlef->tre.tretyp&FALTPIPE)
1907							tt = tt->lst.lstrit;
1908						t = tt;
1909						continue;
1910					}
1911					else if(tt->tre.tretyp==TFIL && tt->lst.lstlef->tre.tretyp&FALTPIPE)
1912					{
1913						sh_copipe(shp,pvn,0);
1914						pvo[2] = pvn[2];
1915						copipe = 0;
1916						goto coskip2;
1917					}
1918				}
1919#endif /* SHOPT_COSHELL */
1920				sh_pipe(pvn);
1921#if SHOPT_COSHELL
1922				pvn[2] = 0;
1923			coskip2:
1924#endif /* SHOPT_COSHELL */
1925				/* execute out part of pipe no wait */
1926				(t->lst.lstlef)->tre.tretyp |= showme;
1927				type = sh_exec(t->lst.lstlef, errorflg);
1928				/* close out-part of pipe */
1929				sh_close(pvn[1]);
1930				pipejob=1;
1931				/* save the pipe stream-ids */
1932				pvo[0] = pvn[0];
1933				/* pipeline all in one process group */
1934				t = t->lst.lstrit;
1935			}
1936			/* repeat until end of pipeline */
1937			while(!type && t->tre.tretyp==TFIL);
1938			shp->inpipe = pvn;
1939			shp->outpipe = 0;
1940			pipejob = 2;
1941			if(type == 0)
1942			{
1943				/*
1944				 * execute last element of pipeline
1945				 * in the current process
1946				 */
1947				((Shnode_t*)t)->tre.tretyp |= showme;
1948				sh_exec(t,flags);
1949			}
1950			else
1951				/* execution failure, close pipe */
1952				sh_pclose(pvn);
1953			if(pipejob==2)
1954				job_unlock();
1955			pipejob = savepipe;
1956#ifdef SIGTSTP
1957			if(!pipejob && sh_isstate(SH_MONITOR))
1958				tcsetpgrp(JOBTTY,shp->gd->pid);
1959#endif /*SIGTSTP */
1960			job.curpgid = savepgid;
1961			break;
1962		    }
1963
1964		    case TLST:
1965		    {
1966			/*  a list of commands are executed here */
1967			do
1968			{
1969				sh_exec(t->lst.lstlef,errorflg|OPTIMIZE);
1970				t = t->lst.lstrit;
1971			}
1972			while(t->tre.tretyp == TLST);
1973			sh_exec(t,flags);
1974			break;
1975		    }
1976
1977		    case TAND:
1978#if SHOPT_COSHELL
1979			if(shp->inpool)
1980			{
1981			andor:
1982				sh_exec(t->lst.lstlef,0);
1983				sh_exec(t->lst.lstrit,0);
1984				break;
1985			}
1986#endif /* SHOPT_COSHELL */
1987			if(type&TTEST)
1988				skipexitset++;
1989			if(sh_exec(t->lst.lstlef,OPTIMIZE)==0)
1990				sh_exec(t->lst.lstrit,flags);
1991			break;
1992
1993		    case TORF:
1994#if SHOPT_COSHELL
1995			if(shp->inpool)
1996				goto andor;
1997#endif /* SHOPT_COSHELL */
1998			if(type&TTEST)
1999				skipexitset++;
2000			if(sh_exec(t->lst.lstlef,OPTIMIZE)!=0)
2001				sh_exec(t->lst.lstrit,flags);
2002			break;
2003
2004		    case TFOR: /* for and select */
2005		    {
2006			register char **args;
2007			register int nargs;
2008			register Namval_t *np;
2009			int flag = errorflg|OPTIMIZE_FLAG;
2010			struct dolnod	*argsav=0;
2011			struct comnod	*tp;
2012			char *cp, *trap, *nullptr = 0;
2013			int nameref, refresh=1;
2014			char *av[5];
2015#if SHOPT_COSHELL
2016			int poolfiles;
2017#endif /* SHOPT_COSHELL */
2018#if SHOPT_OPTIMIZE
2019			int  jmpval = ((struct checkpt*)shp->jmplist)->mode;
2020			struct checkpt buff;
2021			void *optlist = shp->optlist;
2022			shp->optlist = 0;
2023			sh_tclear(t->for_.fortre);
2024			sh_pushcontext(shp,&buff,jmpval);
2025			jmpval = sigsetjmp(buff.buff,0);
2026			if(jmpval)
2027				goto endfor;
2028#endif /* SHOPT_OPTIMIZE */
2029			error_info.line = t->for_.forline-shp->st.firstline;
2030			if(!(tp=t->for_.forlst))
2031			{
2032				args=shp->st.dolv+1;
2033				nargs = shp->st.dolc;
2034				argsav=sh_arguse(shp);
2035			}
2036			else
2037			{
2038				args=sh_argbuild(shp,&argn,tp,0);
2039				nargs = argn;
2040			}
2041			np = nv_open(t->for_.fornam, shp->var_tree,NV_NOASSIGN|NV_NOARRAY|NV_VARNAME|NV_NOREF);
2042			nameref = nv_isref(np)!=0;
2043			shp->st.loopcnt++;
2044			cp = *args;
2045			if(sh_isoption(SH_INTERACTIVE))
2046				sh_offstate(SH_MONITOR);
2047			while(cp && shp->st.execbrk==0)
2048			{
2049				if(t->tre.tretyp&COMSCAN)
2050				{
2051					char *val;
2052					int save_prompt;
2053					/* reuse register */
2054					if(refresh)
2055					{
2056						sh_menu(sfstderr,nargs,args);
2057						refresh = 0;
2058					}
2059					save_prompt = shp->nextprompt;
2060					shp->nextprompt = 3;
2061					shp->timeout = 0;
2062					shp->exitval=sh_readline(shp,&nullptr,0,1,1000*shp->st.tmout);
2063					shp->nextprompt = save_prompt;
2064					if(shp->exitval||sfeof(sfstdin)||sferror(sfstdin))
2065					{
2066						shp->exitval = 1;
2067						break;
2068					}
2069					if(!(val=nv_getval(sh_scoped(shp,REPLYNOD))))
2070						continue;
2071					else
2072					{
2073						if(*(cp=val) == 0)
2074						{
2075							refresh++;
2076							goto check;
2077						}
2078						while(type = *cp++)
2079							if(type < '0' && type > '9')
2080								break;
2081						if(type!=0)
2082							type = nargs;
2083						else
2084							type = (int)strtol(val, (char**)0, 10)-1;
2085						if(type<0 || type >= nargs)
2086							cp = "";
2087						else
2088							cp = args[type];
2089					}
2090				}
2091				if(nameref)
2092					nv_offattr(np,NV_REF);
2093				else if(nv_isattr(np, NV_ARRAY))
2094					nv_putsub(np,NIL(char*),0L);
2095				nv_putval(np,cp,0);
2096				if(nameref)
2097					nv_setref(np,(Dt_t*)0,NV_VARNAME);
2098				if(trap=shp->st.trap[SH_DEBUGTRAP])
2099				{
2100					av[0] = (t->tre.tretyp&COMSCAN)?"select":"for";
2101					av[1] = t->for_.fornam;
2102					av[2] = "in";
2103					av[3] = cp;
2104					av[4] = 0;
2105					sh_debug(shp,trap,(char*)0,(char*)0,av,0);
2106				}
2107#if SHOPT_COSHELL
2108				if(shp->inpool)
2109				{
2110					poolfiles = shp->poolfiles;
2111					sh_exec(t->for_.fortre,0);
2112					if(poolfiles==shp->poolfiles)
2113						break;
2114				}
2115#endif /* SHOPT_COSHELL */
2116				sh_exec(t->for_.fortre,flag);
2117				flag &= ~OPTIMIZE_FLAG;
2118				if(t->tre.tretyp&COMSCAN)
2119				{
2120					if((cp=nv_getval(sh_scoped(shp,REPLYNOD))) && *cp==0)
2121						refresh++;
2122				}
2123				else
2124					cp = *++args;
2125			check:
2126				if(shp->st.breakcnt<0)
2127					shp->st.execbrk = (++shp->st.breakcnt !=0);
2128			}
2129#if SHOPT_OPTIMIZE
2130		endfor:
2131			sh_popcontext(shp,&buff);
2132			sh_tclear(t->for_.fortre);
2133			sh_optclear(shp,optlist);
2134			if(jmpval)
2135				siglongjmp(*shp->jmplist,jmpval);
2136#endif /*SHOPT_OPTIMIZE */
2137			if(shp->st.breakcnt>0)
2138				shp->st.execbrk = (--shp->st.breakcnt !=0);
2139			shp->st.loopcnt--;
2140			sh_argfree(shp,argsav,0);
2141			nv_close(np);
2142			break;
2143		    }
2144
2145		    case TWH: /* while and until */
2146		    {
2147			volatile int 	r=0;
2148			int first = OPTIMIZE_FLAG;
2149			Shnode_t *tt = t->wh.whtre;
2150#if SHOPT_FILESCAN
2151			Sfio_t *iop=0;
2152			int savein,fd;
2153#endif /*SHOPT_FILESCAN*/
2154#if SHOPT_OPTIMIZE
2155			int  jmpval = ((struct checkpt*)shp->jmplist)->mode;
2156			struct checkpt buff;
2157			void *optlist = shp->optlist;
2158#endif /* SHOPT_OPTIMIZE */
2159#if SHOPT_COSHELL
2160			if(shp->inpool)
2161			{
2162				int poolfiles;
2163#   if SHOPT_FILESCAN
2164				if(type==TWH && tt->tre.tretyp==TCOM && !tt->com.comarg && tt->com.comio)
2165				{
2166					sh_redirect(shp,tt->com.comio,0);
2167					break;
2168				}
2169#   endif /* SHOPT_FILESCAN */
2170				sh_exec(tt,0);
2171				do
2172				{
2173					if((sh_exec(tt,0)==0)!=(type==TWH))
2174						break;
2175					poolfiles = shp->poolfiles;
2176					sh_exec(t->wh.dotre,0);
2177					if(t->wh.whinc)
2178						sh_exec((Shnode_t*)t->wh.whinc,0);
2179				}
2180				while(poolfiles != shp->poolfiles);
2181				break;
2182			}
2183#endif /*SHOPT_COSHELL */
2184#if SHOPT_OPTIMIZE
2185			shp->optlist = 0;
2186			sh_tclear(t->wh.whtre);
2187			sh_tclear(t->wh.dotre);
2188			sh_pushcontext(shp,&buff,jmpval);
2189			jmpval = sigsetjmp(buff.buff,0);
2190			if(jmpval)
2191				goto endwhile;
2192#endif /* SHOPT_OPTIMIZE */
2193#if SHOPT_FILESCAN
2194			if(type==TWH && tt->tre.tretyp==TCOM && !tt->com.comarg && tt->com.comio)
2195			{
2196				fd = sh_redirect(shp,tt->com.comio,3);
2197				savein = dup(0);
2198				if(fd==0)
2199					fd = savein;
2200				iop = sfnew(NULL,NULL,SF_UNBOUND,fd,SF_READ);
2201				close(0);
2202				open(e_devnull,O_RDONLY);
2203				shp->offsets[0] = -1;
2204				shp->offsets[1] = 0;
2205				if(tt->com.comset)
2206					nv_setlist(tt->com.comset,NV_IDENT|NV_ASSIGN,0);
2207			}
2208#endif /*SHOPT_FILESCAN */
2209			shp->st.loopcnt++;
2210			if(sh_isoption(SH_INTERACTIVE))
2211				sh_offstate(SH_MONITOR);
2212			while(shp->st.execbrk==0)
2213			{
2214#if SHOPT_FILESCAN
2215				if(iop)
2216				{
2217					if(!(shp->cur_line=sfgetr(iop,'\n',SF_STRING)))
2218						break;
2219				}
2220				else
2221#endif /*SHOPT_FILESCAN */
2222				if((sh_exec(tt,first)==0)!=(type==TWH))
2223					break;
2224				r = sh_exec(t->wh.dotre,first|errorflg);
2225				if(shp->st.breakcnt<0)
2226					shp->st.execbrk = (++shp->st.breakcnt !=0);
2227				/* This is for the arithmetic for */
2228				if(shp->st.execbrk==0 && t->wh.whinc)
2229					sh_exec((Shnode_t*)t->wh.whinc,first);
2230				first = 0;
2231				errorflg &= ~OPTIMIZE_FLAG;
2232#if SHOPT_FILESCAN
2233				shp->offsets[0] = -1;
2234				shp->offsets[1] = 0;
2235#endif /*SHOPT_FILESCAN */
2236			}
2237#if SHOPT_OPTIMIZE
2238		endwhile:
2239			sh_popcontext(shp,&buff);
2240			sh_tclear(t->wh.whtre);
2241			sh_tclear(t->wh.dotre);
2242			sh_optclear(shp,optlist);
2243			if(jmpval)
2244				siglongjmp(*shp->jmplist,jmpval);
2245#endif /*SHOPT_OPTIMIZE */
2246			if(shp->st.breakcnt>0)
2247				shp->st.execbrk = (--shp->st.breakcnt !=0);
2248			shp->st.loopcnt--;
2249			shp->exitval= r;
2250#if SHOPT_FILESCAN
2251			if(iop)
2252			{
2253				sfclose(iop);
2254				close(0);
2255				dup(savein);
2256				shp->cur_line = 0;
2257			}
2258#endif /*SHOPT_FILESCAN */
2259			break;
2260		    }
2261		    case TARITH: /* (( expression )) */
2262		    {
2263			register char *trap;
2264			char *arg[4];
2265			error_info.line = t->ar.arline-shp->st.firstline;
2266			arg[0] = "((";
2267			if(!(t->ar.arexpr->argflag&ARG_RAW))
2268				arg[1] = sh_macpat(shp,t->ar.arexpr,OPTIMIZE|ARG_ARITH);
2269			else
2270				arg[1] = t->ar.arexpr->argval;
2271			arg[2] = "))";
2272			arg[3] = 0;
2273			if(trap=shp->st.trap[SH_DEBUGTRAP])
2274				sh_debug(shp,trap,(char*)0, (char*)0, arg, ARG_ARITH);
2275			if(sh_isoption(SH_XTRACE))
2276			{
2277				sh_trace(shp,NIL(char**),0);
2278				sfprintf(sfstderr,"((%s))\n",arg[1]);
2279			}
2280			if(t->ar.arcomp)
2281				shp->exitval  = !arith_exec((Arith_t*)t->ar.arcomp);
2282			else
2283				shp->exitval = !sh_arith(shp,arg[1]);
2284			break;
2285		    }
2286
2287		    case TIF:
2288#if SHOPT_COSHELL
2289			if(shp->inpool)
2290			{
2291				sh_exec(t->if_.thtre,0);
2292				if(t->if_.eltre)
2293					sh_exec(t->if_.eltre, 0);
2294				break;
2295			}
2296#endif /*SHOPT_COSHELL */
2297			if(sh_exec(t->if_.iftre,OPTIMIZE)==0)
2298				sh_exec(t->if_.thtre,flags);
2299			else if(t->if_.eltre)
2300				sh_exec(t->if_.eltre, flags);
2301			else
2302				shp->exitval=0; /* force zero exit for if-then-fi */
2303			break;
2304
2305		    case TSW:
2306		    {
2307			Shnode_t *tt = (Shnode_t*)t;
2308			char *trap, *r = sh_macpat(shp,tt->sw.swarg,OPTIMIZE);
2309			error_info.line = t->sw.swline-shp->st.firstline;
2310			t= (Shnode_t*)(tt->sw.swlst);
2311			if(trap=shp->st.trap[SH_DEBUGTRAP])
2312			{
2313				char *av[4];
2314				av[0] = "case";
2315				av[1] = r;
2316				av[2] = "in";
2317				av[3] = 0;
2318				sh_debug(shp,trap, (char*)0, (char*)0, av, 0);
2319			}
2320			while(t)
2321			{
2322				register struct argnod	*rex=(struct argnod*)t->reg.regptr;
2323#if SHOPT_COSHELL
2324				if(shp->inpool)
2325				{
2326					sh_exec(t->reg.regcom,0);
2327					continue;
2328				}
2329#endif /*SHOPT_COSHELL */
2330				while(rex)
2331				{
2332					register char *s;
2333					if(rex->argflag&ARG_MAC)
2334					{
2335						s = sh_macpat(shp,rex,OPTIMIZE|ARG_EXP);
2336						while(*s=='\\' && s[1]==0)
2337							s+=2;
2338					}
2339					else
2340						s = rex->argval;
2341					type = (rex->argflag&ARG_RAW);
2342					if((type && strcmp(r,s)==0) ||
2343						(!type && (strmatch(r,s)
2344						|| trim_eq(r,s))))
2345					{
2346						do	sh_exec(t->reg.regcom,(t->reg.regflag?0:flags));
2347						while(t->reg.regflag &&
2348							(t=(Shnode_t*)t->reg.regnxt));
2349						t=0;
2350						break;
2351					}
2352					else
2353						rex=rex->argnxt.ap;
2354				}
2355				if(t)
2356					t=(Shnode_t*)t->reg.regnxt;
2357			}
2358			break;
2359		    }
2360
2361		    case TTIME:
2362		    {
2363			/* time the command */
2364			struct tms before,after;
2365			const char *format = e_timeformat;
2366			clock_t at, tm[3];
2367#ifdef timeofday
2368			struct timeval tb,ta;
2369#else
2370			clock_t bt;
2371#endif	/* timeofday */
2372#if SHOPT_COSHELL
2373			if(shp->inpool)
2374			{
2375				if(t->par.partre)
2376					sh_exec(t->par.partre,0);
2377				break;
2378			}
2379#endif /*SHOPT_COSHELL */
2380			if(type!=TTIME)
2381			{
2382				sh_exec(t->par.partre,OPTIMIZE);
2383				shp->exitval = !shp->exitval;
2384				break;
2385			}
2386			if(t->par.partre)
2387			{
2388				long timer_on;
2389				if(shp->subshell && shp->comsub==1)
2390					sh_subfork();
2391				timer_on = sh_isstate(SH_TIMING);
2392#ifdef timeofday
2393				timeofday(&tb);
2394				times(&before);
2395#else
2396				bt = times(&before);
2397#endif	/* timeofday */
2398				job.waitall = 1;
2399				sh_onstate(SH_TIMING);
2400				sh_exec(t->par.partre,OPTIMIZE);
2401				if(!timer_on)
2402					sh_offstate(SH_TIMING);
2403				job.waitall = 0;
2404			}
2405			else
2406			{
2407#ifndef timeofday
2408				bt = 0;
2409#endif	/* timeofday */
2410				before.tms_utime = before.tms_cutime = 0;
2411				before.tms_stime = before.tms_cstime = 0;
2412			}
2413#ifdef timeofday
2414			times(&after);
2415			timeofday(&ta);
2416			at = shp->gd->lim.clk_tck*(ta.tv_sec-tb.tv_sec);
2417			at +=  ((shp->gd->lim.clk_tck*(((1000000L/2)/shp->gd->lim.clk_tck)+(ta.tv_usec-tb.tv_usec)))/1000000L);
2418#else
2419			at = times(&after) - bt;
2420#endif	/* timeofday */
2421			tm[0] = at;
2422			if(t->par.partre)
2423			{
2424				Namval_t *np = nv_open("TIMEFORMAT",shp->var_tree,NV_NOADD);
2425				if(np)
2426				{
2427					format = nv_getval(np);
2428					nv_close(np);
2429				}
2430				if(!format)
2431					format = e_timeformat;
2432			}
2433			else
2434				format = strchr(format+1,'\n')+1;
2435			tm[1] = after.tms_utime - before.tms_utime;
2436			tm[1] += after.tms_cutime - before.tms_cutime;
2437			tm[2] = after.tms_stime - before.tms_stime;
2438			tm[2] += after.tms_cstime - before.tms_cstime;
2439			if(format && *format)
2440				p_time(shp,sfstderr,sh_translate(format),tm);
2441			break;
2442		    }
2443		    case TFUN:
2444		    {
2445			register Namval_t *np=0;
2446			register struct slnod *slp;
2447			register char *fname = ((struct functnod*)t)->functnam;
2448			register char *cp = strrchr(fname,'.');
2449			register Namval_t *npv=0,*mp;
2450#if SHOPT_COSHELL
2451			if(shp->inpool)
2452			{
2453				sh_exec(t->funct.functtre,0);
2454				break;
2455			}
2456#endif /* SHOPT_COSHELL */
2457#if SHOPT_NAMESPACE
2458			if(t->tre.tretyp==TNSPACE)
2459			{
2460				Dt_t *root,*oldroot, *bot=0;
2461				Namval_t *oldnspace = shp->namespace;
2462				int offset = stktell(stkp);
2463				long optindex = shp->st.optindex;
2464				int	flags=NV_NOASSIGN|NV_NOARRAY|NV_VARNAME;
2465				if(cp)
2466					errormsg(SH_DICT,ERROR_exit(1),e_ident,fname);
2467				if(!shp->namespace)
2468					sfputc(stkp,'.');
2469				else
2470					flags |= NV_NOSCOPE;
2471				sfputr(stkp,fname,0);
2472				np = nv_open(stkptr(stkp,offset),shp->var_tree,flags);
2473				offset = stktell(stkp);
2474				shp->namespace = np;
2475				if(nv_istable(np))
2476					root = nv_dict(np);
2477				else
2478				{
2479					root = dtopen(&_Nvdisc,Dtoset);
2480					nv_mount(np, (char*)0, root);
2481					np->nvalue.cp = Empty;
2482					shp->st.optindex = 1;
2483				}
2484				if(oldnspace && dtvnext(dtvnext(shp->var_tree)))
2485					bot = dtview(shp->var_tree,0);
2486				else if(dtvnext(shp->var_tree))
2487					bot = dtview(shp->var_tree,0);
2488				oldroot = shp->var_tree;
2489				dtview(root,shp->var_base);
2490				shp->var_tree = root;
2491				if(bot)
2492					dtview(shp->var_tree,bot);
2493				sh_exec(t->for_.fortre,flags|sh_state(SH_ERREXIT));
2494				if(dtvnext(shp->var_tree))
2495					bot = dtview(shp->var_tree,0);
2496				shp->var_tree = oldroot;
2497				if(bot)
2498					dtview(shp->var_tree,bot);
2499				shp->namespace = oldnspace;
2500				shp->st.optindex = optindex;
2501				break;
2502			}
2503#endif /* SHOPT_NAMESPACE */
2504			/* look for discipline functions */
2505			error_info.line = t->funct.functline-shp->st.firstline;
2506			/* Function names cannot be special builtin */
2507			if(cp || shp->prefix)
2508			{
2509				int offset = stktell(stkp);
2510				if(shp->prefix)
2511				{
2512					cp = shp->prefix;
2513					shp->prefix = 0;
2514					npv = nv_open(cp,shp->var_tree,NV_NOASSIGN|NV_NOARRAY|NV_VARNAME);
2515					shp->prefix = cp;
2516					cp = fname;
2517				}
2518				else
2519				{
2520					sfwrite(stkp,fname,cp++-fname);
2521					sfputc(stkp,0);
2522					npv = nv_open(stkptr(stkp,offset),shp->var_tree,NV_NOASSIGN|NV_NOARRAY|NV_VARNAME);
2523				}
2524				offset = stktell(stkp);
2525				sfprintf(stkp,"%s.%s%c",nv_name(npv),cp,0);
2526				fname = stkptr(stkp,offset);
2527			}
2528			else if((mp=nv_search(fname,shp->bltin_tree,0)) && nv_isattr(mp,BLT_SPC))
2529				errormsg(SH_DICT,ERROR_exit(1),e_badfun,fname);
2530#if SHOPT_NAMESPACE
2531			if(shp->namespace && !shp->prefix && *fname!='.')
2532				np = sh_fsearch(shp,fname,NV_ADD|HASH_NOSCOPE);
2533			if(!np)
2534#endif /* SHOPT_NAMESPACE */
2535			np = nv_open(fname,sh_subfuntree(1),NV_NOASSIGN|NV_NOARRAY|NV_VARNAME|NV_NOSCOPE);
2536			if(npv)
2537			{
2538				if(!shp->mktype)
2539					cp = nv_setdisc(npv,cp,np,(Namfun_t*)npv);
2540				if(!cp)
2541					errormsg(SH_DICT,ERROR_exit(1),e_baddisc,fname);
2542			}
2543			if(np->nvalue.rp)
2544			{
2545				struct Ufunction *rp = np->nvalue.rp;
2546				slp = (struct slnod*)np->nvenv;
2547				sh_funstaks(slp->slchild,-1);
2548				stakdelete(slp->slptr);
2549				if(shp->funload)
2550				{
2551					free((void*)np->nvalue.rp);
2552					np->nvalue.rp = 0;
2553				}
2554				if(rp->sdict)
2555				{
2556					Namval_t *mp, *nq;
2557					shp->last_root = rp->sdict;
2558					for(mp=(Namval_t*)dtfirst(rp->sdict);mp;mp=nq)
2559					{
2560						nq = dtnext(rp->sdict,mp);
2561						_nv_unset(mp,NV_RDONLY);
2562						nv_delete(mp,rp->sdict,0);
2563					}
2564					dtclose(rp->sdict);
2565					rp->sdict = 0;
2566				}
2567			}
2568			if(!np->nvalue.rp)
2569			{
2570				np->nvalue.rp = new_of(struct Ufunction,shp->funload?sizeof(Dtlink_t):0);
2571				memset((void*)np->nvalue.rp,0,sizeof(struct Ufunction));
2572			}
2573			if(t->funct.functstak)
2574			{
2575				static Dtdisc_t		_Rpdisc =
2576				{
2577				        offsetof(struct Ufunction,fname), -1, sizeof(struct Ufunction)
2578				};
2579				struct functnod *fp;
2580				struct comnod *ac = t->funct.functargs;
2581				slp = t->funct.functstak;
2582				sh_funstaks(slp->slchild,1);
2583				staklink(slp->slptr);
2584				np->nvenv = (char*)slp;
2585				nv_funtree(np) = (int*)(t->funct.functtre);
2586				np->nvalue.rp->hoffset = t->funct.functloc;
2587				np->nvalue.rp->lineno = t->funct.functline;
2588				np->nvalue.rp->nspace = shp->namespace;
2589				np->nvalue.rp->fname = 0;
2590				np->nvalue.rp->argv = ac?((struct dolnod*)ac->comarg)->dolval+1:0;
2591				np->nvalue.rp->argc = ac?((struct dolnod*)ac->comarg)->dolnum:0;
2592				np->nvalue.rp->fdict = shp->fun_tree;
2593				fp = (struct functnod*)(slp+1);
2594				if(fp->functtyp==(TFUN|FAMP))
2595					np->nvalue.rp->fname = fp->functnam;
2596				nv_setsize(np,fp->functline);
2597				nv_offattr(np,NV_FPOSIX);
2598				if(shp->funload)
2599				{
2600					struct Ufunction *rp = np->nvalue.rp;
2601					rp->np = np;
2602					if(!shp->fpathdict)
2603						shp->fpathdict = dtopen(&_Rpdisc,Dtobag);
2604					if(shp->fpathdict)
2605						dtinsert(shp->fpathdict,rp);
2606				}
2607			}
2608			else
2609				_nv_unset(np,0);
2610			if(type&FPOSIX)
2611				nv_onattr(np,NV_FUNCTION|NV_FPOSIX);
2612			else
2613				nv_onattr(np,NV_FUNCTION);
2614			if(type&FPIN)
2615				nv_onattr(np,NV_FTMP);
2616			if(type&FOPTGET)
2617				nv_onattr(np,NV_OPTGET);
2618			break;
2619		    }
2620
2621		    /* new test compound command */
2622		    case TTST:
2623		    {
2624			register int n;
2625			register char *left;
2626			int negate = (type&TNEGATE)!=0;
2627#if SHOPT_COSHELL
2628			if(shp->inpool)
2629				break;
2630#endif /* SHOPT_COSHELL */
2631			if(type&TTEST)
2632				skipexitset++;
2633			error_info.line = t->tst.tstline-shp->st.firstline;
2634			echeck = 1;
2635			if((type&TPAREN)==TPAREN)
2636			{
2637				sh_exec(t->lst.lstlef,OPTIMIZE);
2638				n = !shp->exitval;
2639			}
2640			else
2641			{
2642				register int traceon=0;
2643				register char *right;
2644				register char *trap;
2645				char *argv[6];
2646				n = type>>TSHIFT;
2647				left = sh_macpat(shp,&(t->lst.lstlef->arg),OPTIMIZE);
2648				if(type&TBINARY)
2649					right = sh_macpat(shp,&(t->lst.lstrit->arg),((n==TEST_PEQ||n==TEST_PNE)?ARG_EXP:0)|OPTIMIZE);
2650				if(trap=shp->st.trap[SH_DEBUGTRAP])
2651					argv[0] = (type&TNEGATE)?((char*)e_tstbegin):"[[";
2652				if(sh_isoption(SH_XTRACE))
2653				{
2654					traceon = sh_trace(shp,NIL(char**),0);
2655					sfwrite(sfstderr,e_tstbegin,(type&TNEGATE?5:3));
2656				}
2657				if(type&TUNARY)
2658				{
2659					if(traceon)
2660						sfprintf(sfstderr,"-%c %s",n,sh_fmtq(left));
2661					if(trap)
2662					{
2663						char unop[3];
2664						unop[0] = '-';
2665						unop[1] = n;
2666						unop[2] = 0;
2667						argv[1] = unop;
2668						argv[2] = left;
2669						argv[3] = "]]";
2670						argv[4] = 0;
2671						sh_debug(shp,trap,(char*)0,(char*)0,argv, 0);
2672					}
2673					n = test_unop(shp,n,left);
2674				}
2675				else if(type&TBINARY)
2676				{
2677					char *op;
2678					int pattern = 0;
2679					if(trap || traceon)
2680						op = (char*)(shtab_testops+(n&037)-1)->sh_name;
2681					type >>= TSHIFT;
2682					if(type==TEST_PEQ || type==TEST_PNE)
2683						pattern=ARG_EXP;
2684					if(trap)
2685					{
2686						argv[1] = left;
2687						argv[2] = op;
2688						argv[3] = right;
2689						argv[4] = "]]";
2690						argv[5] = 0;
2691						sh_debug(shp,trap,(char*)0,(char*)0,argv, pattern);
2692					}
2693					n = test_binop(shp,n,left,right);
2694					if(traceon)
2695					{
2696						sfprintf(sfstderr,"%s %s ",sh_fmtq(left),op);
2697						if(pattern)
2698							out_pattern(sfstderr,right,-1);
2699						else
2700							sfputr(sfstderr,sh_fmtq(right),-1);
2701					}
2702				}
2703				if(traceon)
2704					sfwrite(sfstderr,e_tstend,4);
2705			}
2706			shp->exitval = ((!n)^negate);
2707			if(!skipexitset)
2708				exitset();
2709			break;
2710		    }
2711		}
2712		if(shp->trapnote || (shp->exitval && sh_isstate(SH_ERREXIT)) &&
2713			t && echeck)
2714			sh_chktrap(shp);
2715		/* set $_ */
2716		if(mainloop && com0)
2717		{
2718			/* store last argument here if it fits */
2719			static char	lastarg[32];
2720			if(sh_isstate(SH_FORKED))
2721				sh_done(shp,0);
2722			if(shp->lastarg!= lastarg && shp->lastarg)
2723				free(shp->lastarg);
2724			if(strlen(comn) < sizeof(lastarg))
2725			{
2726				nv_onattr(L_ARGNOD,NV_NOFREE);
2727				shp->lastarg = strcpy(lastarg,comn);
2728			}
2729			else
2730			{
2731				nv_offattr(L_ARGNOD,NV_NOFREE);
2732				shp->lastarg = strdup(comn);
2733			}
2734		}
2735		if(!skipexitset)
2736			exitset();
2737#if SHOPT_COSHELL
2738		if(!shp->inpool && !(OPTIMIZE))
2739#else
2740		if(!(OPTIMIZE))
2741#endif /* SHOPT_COSHELL */
2742		{
2743			if(sav != stkptr(stkp,0))
2744				stkset(stkp,sav,0);
2745			else if(stktell(stkp))
2746				stkseek(stkp,0);
2747		}
2748		if(shp->trapnote&SH_SIGSET)
2749			sh_exit(SH_EXITSIG|shp->lastsig);
2750		if(was_interactive)
2751			sh_onstate(SH_INTERACTIVE);
2752		if(was_monitor && sh_isoption(SH_MONITOR))
2753			sh_onstate(SH_MONITOR);
2754		if(was_errexit)
2755			sh_onstate(SH_ERREXIT);
2756	}
2757	return(shp->exitval);
2758}
2759
2760int sh_run(int argn, char *argv[])
2761{
2762	Shell_t		*shp = sh_getinterp();
2763	register struct dolnod	*dp;
2764	register struct comnod	*t = (struct comnod*)stakalloc(sizeof(struct comnod));
2765	int			savtop = staktell();
2766	char			*savptr = stakfreeze(0);
2767	Opt_t			*op, *np = optctx(0, 0);
2768	Shbltin_t		bltindata;
2769	bltindata = shp->bltindata;
2770	op = optctx(np, 0);
2771	memset(t, 0, sizeof(struct comnod));
2772	dp = (struct dolnod*)stakalloc((unsigned)sizeof(struct dolnod) + ARG_SPARE*sizeof(char*) + argn*sizeof(char*));
2773	dp->dolnum = argn;
2774	dp->dolbot = ARG_SPARE;
2775	memcpy(dp->dolval+ARG_SPARE, argv, (argn+1)*sizeof(char*));
2776	t->comarg = (struct argnod*)dp;
2777	if(!strchr(argv[0],'/'))
2778		t->comnamp = (void*)nv_bfsearch(argv[0],shp->fun_tree,(Namval_t**)&t->comnamq,(char**)0);
2779	argn=sh_exec((Shnode_t*)t,sh_isstate(SH_ERREXIT));
2780	optctx(op,np);
2781	shp->bltindata = bltindata;
2782	if(savptr!=stakptr(0))
2783		stakset(savptr,savtop);
2784	else
2785		stakseek(savtop);
2786	return(argn);
2787}
2788
2789/*
2790 * test for equality with second argument trimmed
2791 * returns 1 if r == trim(s) otherwise 0
2792 */
2793
2794static int trim_eq(register const char *r,register const char *s)
2795{
2796	register char c;
2797	while(c = *s++)
2798	{
2799		if(c=='\\')
2800			c = *s++;
2801		if(c && c != *r++)
2802			return(0);
2803	}
2804	return(*r==0);
2805}
2806
2807/*
2808 * print out the command line if set -x is on
2809 */
2810
2811int sh_trace(Shell_t *shp,register char *argv[], register int nl)
2812{
2813	register char *cp;
2814	register int bracket = 0;
2815	int decl = (nl&2);
2816	nl &= ~2;
2817	if(sh_isoption(SH_XTRACE))
2818	{
2819		/* make this trace atomic */
2820		sfset(sfstderr,SF_SHARE|SF_PUBLIC,0);
2821		if(!(cp=nv_getval(sh_scoped(shp,PS4NOD))))
2822			cp = "+ ";
2823		else
2824		{
2825			sh_offoption(SH_XTRACE);
2826			cp = sh_mactry(shp,cp);
2827			sh_onoption(SH_XTRACE);
2828		}
2829		if(*cp)
2830			sfputr(sfstderr,cp,-1);
2831		if(argv)
2832		{
2833			char *argv0 = *argv;
2834			nl = (nl?'\n':-1);
2835			/* don't quote [ and [[ */
2836			if(*(cp=argv[0])=='[' && (!cp[1] || !cp[2]&&cp[1]=='['))
2837			{
2838				sfputr(sfstderr,cp,*++argv?' ':nl);
2839				bracket = 1;
2840			}
2841			while(cp = *argv++)
2842			{
2843				if(bracket==0 || *argv || *cp!=']')
2844					cp = sh_fmtq(cp);
2845				if(decl && shp->prefix && cp!=argv0 && *cp!='-')
2846				{
2847					if(*cp=='.' && cp[1]==0)
2848						cp = shp->prefix;
2849					else
2850						sfputr(sfstderr,shp->prefix,'.');
2851				}
2852				sfputr(sfstderr,cp,*argv?' ':nl);
2853			}
2854			sfset(sfstderr,SF_SHARE|SF_PUBLIC,1);
2855		}
2856		return(1);
2857	}
2858	return(0);
2859}
2860
2861/*
2862 * This routine creates a subshell by calling fork() or vfork()
2863 * If ((flags&COMASK)==TCOM), then vfork() is permitted
2864 * If fork fails, the shell sleeps for exponentially longer periods
2865 *   and tries again until a limit is reached.
2866 * SH_FORKLIM is the max period between forks - power of 2 usually.
2867 * Currently shell tries after 2,4,8,16, and 32 seconds and then quits
2868 * Failures cause the routine to error exit.
2869 * Parent links to here-documents are removed by the child
2870 * Traps are reset by the child
2871 * The process-id of the child is returned to the parent, 0 to the child.
2872 */
2873
2874static void timed_out(void *handle)
2875{
2876	NOT_USED(handle);
2877	timeout = 0;
2878}
2879
2880
2881/*
2882 * called by parent and child after fork by sh_fork()
2883 */
2884pid_t _sh_fork(Shell_t *shp,register pid_t parent,int flags,int *jobid)
2885{
2886	static long forkcnt = 1000L;
2887	pid_t	curpgid = job.curpgid;
2888	pid_t	postid = (flags&FAMP)?0:curpgid;
2889	int	sig,nochild;
2890	if(parent<0)
2891	{
2892		sh_sigcheck(shp);
2893		if((forkcnt *= 2) > 1000L*SH_FORKLIM)
2894		{
2895			forkcnt=1000L;
2896			errormsg(SH_DICT,ERROR_system(ERROR_NOEXEC),e_nofork);
2897		}
2898		timeout = (void*)sh_timeradd(forkcnt, 0, timed_out, NIL(void*));
2899		nochild = job_wait((pid_t)1);
2900		if(timeout)
2901		{
2902			if(nochild)
2903				pause();
2904			else if(forkcnt>1000L)
2905				forkcnt /= 2;
2906			timerdel(timeout);
2907			timeout = 0;
2908		}
2909		return(-1);
2910	}
2911	forkcnt = 1000L;
2912	if(parent)
2913	{
2914		int myjob,waitall=job.waitall;
2915		shp->gd->nforks++;
2916		if(job.toclear)
2917			job_clear();
2918		job.waitall = waitall;
2919#ifdef JOBS
2920		/* first process defines process group */
2921		if(sh_isstate(SH_MONITOR))
2922		{
2923			/*
2924			 * errno==EPERM means that an earlier processes
2925			 * completed.  Make parent the job group id.
2926			 */
2927			if(postid==0)
2928				job.curpgid = parent;
2929			if(job.jobcontrol || (flags&FAMP))
2930			{
2931				if(setpgid(parent,job.curpgid)<0 && errno==EPERM)
2932					setpgid(parent,parent);
2933			}
2934		}
2935#endif /* JOBS */
2936		if(!sh_isstate(SH_MONITOR) && job.waitall && postid==0)
2937			job.curpgid = parent;
2938		if(flags&FCOOP)
2939			shp->cpid = parent;
2940#ifdef SHOPT_BGX
2941		if(!postid && (flags&(FAMP|FINT)) == (FAMP|FINT))
2942			postid = 1;
2943		myjob = job_post(shp,parent,postid);
2944		if(postid==1)
2945			postid = 0;
2946#else
2947		myjob = job_post(shp,parent,postid);
2948#endif /* SHOPT_BGX */
2949		if(flags&FAMP)
2950			job.curpgid = curpgid;
2951		if(jobid)
2952			*jobid = myjob;
2953		if(shp->comsub==1 && subpipe[0]>=0)
2954		{
2955			if(!tsetio || !subdup)
2956				iounpipe(shp);
2957		}
2958		return(parent);
2959	}
2960#if !_std_malloc
2961	vmtrace(-1);
2962#endif
2963	shp->outpipepid = ((flags&FPOU)?getpid():0);
2964	/* This is the child process */
2965	if(shp->trapnote&SH_SIGTERM)
2966		sh_exit(SH_EXITSIG|SIGTERM);
2967	shp->gd->nforks=0;
2968	timerdel(NIL(void*));
2969#ifdef JOBS
2970	if(!job.jobcontrol && !(flags&FAMP))
2971		sh_offstate(SH_MONITOR);
2972	if(sh_isstate(SH_MONITOR))
2973	{
2974		parent = getpid();
2975		if(postid==0)
2976			job.curpgid = parent;
2977		while(setpgid(0,job.curpgid)<0 && job.curpgid!=parent)
2978			job.curpgid = parent;
2979#   ifdef SIGTSTP
2980		if(job.curpgid==parent &&  !(flags&FAMP))
2981			tcsetpgrp(job.fd,job.curpgid);
2982#   endif /* SIGTSTP */
2983	}
2984#   ifdef SIGTSTP
2985	if(job.jobcontrol)
2986	{
2987		signal(SIGTTIN,SIG_DFL);
2988		signal(SIGTTOU,SIG_DFL);
2989		signal(SIGTSTP,SIG_DFL);
2990	}
2991#   endif /* SIGTSTP */
2992	job.jobcontrol = 0;
2993#endif /* JOBS */
2994	job.toclear = 1;
2995	shp->login_sh = 0;
2996	sh_offoption(SH_LOGIN_SHELL);
2997	sh_onstate(SH_FORKED);
2998	sh_onstate(SH_NOLOG);
2999	if (shp->fn_reset)
3000		shp->fn_depth = shp->fn_reset = 0;
3001#if SHOPT_ACCT
3002	sh_accsusp();
3003#endif	/* SHOPT_ACCT */
3004	/* Reset remaining signals to parent */
3005	/* except for those `lost' by trap   */
3006	if(!(flags&FSHOWME))
3007		sh_sigreset(2);
3008	shp->subshell = 0;
3009	shp->comsub = 0;
3010	shp->spid = 0;
3011	if((flags&FAMP) && shp->coutpipe>1)
3012		sh_close(shp->coutpipe);
3013	sig = shp->savesig;
3014	shp->savesig = 0;
3015	if(sig>0)
3016		sh_fault(sig);
3017	sh_sigcheck(shp);
3018	usepipe=0;
3019	return(0);
3020}
3021
3022pid_t sh_fork(Shell_t *shp,int flags, int *jobid)
3023{
3024	register pid_t parent;
3025	register int sig;
3026	if(!shp->pathlist)
3027		path_get(shp,"");
3028	sfsync(NIL(Sfio_t*));
3029	shp->trapnote &= ~SH_SIGTERM;
3030	job_fork(-1);
3031	shp->savesig = -1;
3032	while(_sh_fork(shp,parent=fork(),flags,jobid) < 0);
3033	sh_stats(STAT_FORKS);
3034	if(!shp->subshell)
3035	{
3036		sig = shp->savesig;
3037		shp->savesig = 0;
3038		if(sig>0)
3039			sh_fault(sig);
3040	}
3041	job_fork(parent);
3042	return(parent);
3043}
3044
3045struct Tdata
3046{
3047        Shell_t         *sh;
3048        Namval_t        *tp;
3049	void		*extra[2];
3050};
3051
3052/*
3053 * add exports from previous scope to the new scope
3054 */
3055static void  local_exports(register Namval_t *np, void *data)
3056{
3057	Shell_t			*shp = ((struct Tdata*)data)->sh;
3058	register Namval_t	*mp;
3059	register char		*cp;
3060	if(nv_isarray(np))
3061		nv_putsub(np,NIL(char*),0);
3062	if((cp = nv_getval(np)) && (mp = nv_search(nv_name(np), shp->var_tree, NV_ADD|HASH_NOSCOPE)) && nv_isnull(mp))
3063		nv_putval(mp, cp, 0);
3064}
3065
3066/*
3067 * This routine executes .sh.math functions from within ((...)))
3068*/
3069Sfdouble_t sh_mathfun(Shell_t *shp,void *fp, int nargs, Sfdouble_t *arg)
3070{
3071	Sfdouble_t	d;
3072	Namval_t	node,*mp,*np, *nref[9], **nr=nref;
3073	char		*argv[2];
3074	struct funenv	funenv;
3075	int		i;
3076	np = (Namval_t*)fp;
3077	funenv.node = np;
3078	funenv.nref = nref;
3079	funenv.env = 0;
3080	memcpy(&node,SH_VALNOD,sizeof(node));
3081	SH_VALNOD->nvfun = 0;
3082	SH_VALNOD->nvenv = 0;
3083	SH_VALNOD->nvflag = NV_LDOUBLE|NV_NOFREE;
3084	SH_VALNOD->nvalue.ldp = 0;
3085	for(i=0; i < nargs; i++)
3086	{
3087		*nr++ = mp = nv_namptr(shp->mathnodes,i);
3088		mp->nvalue.ldp = arg++;
3089	}
3090	*nr = 0;
3091	SH_VALNOD->nvalue.ldp = &d;
3092	argv[0] =  np->nvname;
3093	argv[1] = 0;
3094	sh_funscope(1,argv,0,&funenv,0);
3095	while(mp= *nr++)
3096		mp->nvalue.ldp = 0;
3097	SH_VALNOD->nvfun = node.nvfun;
3098	SH_VALNOD->nvflag = node.nvflag;
3099	SH_VALNOD->nvenv = node.nvenv;
3100	SH_VALNOD->nvalue.ldp = node.nvalue.ldp;
3101	return(d);
3102}
3103
3104/*
3105 * This routine is used to execute the given function <fun> in a new scope
3106 * If <fun> is NULL, then arg points to a structure containing a pointer
3107 *  to a function that will be executed in the current environment.
3108 */
3109int sh_funscope(int argn, char *argv[],int(*fun)(void*),void *arg,int execflg)
3110{
3111	register char		*trap;
3112	register int		nsig;
3113	register Shell_t	*shp =  sh_getinterp();
3114	struct dolnod		*argsav=0,*saveargfor;
3115	struct sh_scoped	savst, *prevscope = shp->st.self;
3116	struct argnod		*envlist=0;
3117	int			jmpval;
3118	volatile int		r = 0;
3119	int			n;
3120	char 			*savstak;
3121	struct funenv		*fp = 0;
3122	struct checkpt		buff;
3123	Namval_t		*nspace = shp->namespace;
3124	Dt_t			*last_root = shp->last_root;
3125	Shopt_t			options = shp->options;
3126#if SHOPT_NAMESPACE
3127	Namval_t		*np;
3128#endif /* SHOPT_NAMESPACE */
3129	if(shp->fn_depth==0)
3130		shp->glob_options =  shp->options;
3131	else
3132		shp->options = shp->glob_options;
3133#if 0
3134	shp->st.lineno = error_info.line;
3135#endif
3136	*prevscope = shp->st;
3137	sh_offoption(SH_ERREXIT);
3138	shp->st.prevst = prevscope;
3139	shp->st.self = &savst;
3140	shp->topscope = (Shscope_t*)shp->st.self;
3141	shp->st.opterror = shp->st.optchar = 0;
3142	shp->st.optindex = 1;
3143	shp->st.loopcnt = 0;
3144	if(!fun)
3145	{
3146		fp = (struct funenv*)arg;
3147		shp->st.real_fun = (fp->node)->nvalue.rp;
3148		envlist = fp->env;
3149	}
3150	prevscope->save_tree = shp->var_tree;
3151	n = dtvnext(prevscope->save_tree)!= (shp->namespace?shp->var_base:0);
3152#if SHOPT_NAMESPACE
3153	if(n && fp && (np=(fp->node)->nvalue.rp->nspace) && np!=shp->namespace)
3154		shp->namespace = np;
3155#endif /* SHOPT_NAMESPACE */
3156	sh_scope(shp,envlist,1);
3157	if(n)
3158	{
3159		struct Tdata tdata;
3160		memset(&tdata,0,sizeof(tdata));
3161		tdata.sh = shp;
3162		/* eliminate parent scope */
3163		nv_scan(prevscope->save_tree, local_exports,&tdata, NV_EXPORT, NV_EXPORT|NV_NOSCOPE);
3164	}
3165	shp->st.save_tree = shp->var_tree;
3166	if(!fun)
3167	{
3168		if(nv_isattr(fp->node,NV_TAGGED))
3169			sh_onoption(SH_XTRACE);
3170		else
3171			sh_offoption(SH_XTRACE);
3172	}
3173	shp->st.cmdname = argv[0];
3174	/* save trap table */
3175	if((nsig=shp->st.trapmax*sizeof(char*))>0 || shp->st.trapcom[0])
3176	{
3177		nsig += sizeof(char*);
3178		memcpy(savstak=stakalloc(nsig),(char*)&shp->st.trapcom[0],nsig);
3179	}
3180	sh_sigreset(0);
3181	argsav = sh_argnew(shp,argv,&saveargfor);
3182	sh_pushcontext(shp,&buff,SH_JMPFUN);
3183	errorpush(&buff.err,0);
3184	error_info.id = argv[0];
3185	shp->st.var_local = shp->var_tree;
3186	jmpval = sigsetjmp(buff.buff,0);
3187	if(!fun)
3188	{
3189		shp->st.filename = fp->node->nvalue.rp->fname;
3190		shp->st.funname = nv_name(fp->node);
3191		shp->last_root = nv_dict(DOTSHNOD);
3192		nv_putval(SH_PATHNAMENOD,shp->st.filename,NV_NOFREE);
3193		nv_putval(SH_FUNNAMENOD,shp->st.funname,NV_NOFREE);
3194	}
3195	if(jmpval == 0)
3196	{
3197		if(shp->fn_depth++ > MAXDEPTH)
3198		{
3199			shp->toomany = 1;
3200			siglongjmp(*shp->jmplist,SH_JMPERRFN);
3201		}
3202		else if(fun)
3203			r= (*fun)(arg);
3204		else
3205		{
3206			char		**arg = shp->st.real_fun->argv;
3207			Namval_t	*np, *nq, **nref;
3208			if(nref=fp->nref)
3209			{
3210				shp->last_root = 0;
3211				for(r=0; arg[r]; r++)
3212				{
3213					np = nv_search(arg[r],shp->var_tree,HASH_NOSCOPE|NV_ADD);
3214					if(np && (nq=*nref++))
3215					{
3216						np->nvalue.nrp = newof(0,struct Namref,1,0);
3217						np->nvalue.nrp->np = nq;
3218						nv_onattr(np,NV_REF|NV_NOFREE);
3219					}
3220				}
3221			}
3222			sh_exec((Shnode_t*)(nv_funtree((fp->node))),execflg|SH_ERREXIT);
3223			r = shp->exitval;
3224		}
3225	}
3226	if(--shp->fn_depth==1 && jmpval==SH_JMPERRFN)
3227		errormsg(SH_DICT,ERROR_exit(1),e_toodeep,argv[0]);
3228	sh_popcontext(shp,&buff);
3229	if (shp->st.self != &savst)
3230		shp->var_tree = (Dt_t*)savst.save_tree;
3231	sh_unscope(shp);
3232	shp->namespace = nspace;
3233	shp->var_tree = (Dt_t*)prevscope->save_tree;
3234	if(shp->topscope != (Shscope_t*)shp->st.self)
3235		sh_setscope(shp->topscope);
3236	sh_argreset(shp,argsav,saveargfor);
3237	trap = shp->st.trapcom[0];
3238	shp->st.trapcom[0] = 0;
3239	sh_sigreset(1);
3240	if (shp->st.self != &savst)
3241		*shp->st.self = shp->st;
3242	shp->st = *prevscope;
3243	shp->topscope = (Shscope_t*)prevscope;
3244	nv_getval(sh_scoped(shp,IFSNOD));
3245	if(nsig)
3246		memcpy((char*)&shp->st.trapcom[0],savstak,nsig);
3247	shp->trapnote=0;
3248	if(nsig)
3249		stakset(savstak,0);
3250	shp->options = options;
3251	shp->last_root = last_root;
3252	if(jmpval == SH_JMPSUB)
3253		siglongjmp(*shp->jmplist,jmpval);
3254	if(trap)
3255	{
3256		sh_trap(trap,0);
3257		free(trap);
3258	}
3259	if(jmpval)
3260		r=shp->exitval;
3261	if(r>SH_EXITSIG && ((r&SH_EXITMASK)==SIGINT || ((r&SH_EXITMASK)==SIGQUIT)))
3262		sh_fault(r&SH_EXITMASK);
3263	if(jmpval > SH_JMPFUN)
3264	{
3265		sh_chktrap(shp);
3266		siglongjmp(*shp->jmplist,jmpval);
3267	}
3268	return(r);
3269}
3270
3271static void sh_funct(Shell_t *shp,Namval_t *np,int argn, char *argv[],struct argnod *envlist,int execflg)
3272{
3273	struct funenv fun;
3274	char *fname = nv_getval(SH_FUNNAMENOD);
3275	struct Level	*lp =(struct Level*)(SH_LEVELNOD->nvfun);
3276	int		level, pipepid=shp->pipepid;
3277	shp->pipepid = 0;
3278	sh_stats(STAT_FUNCT);
3279	if(!lp->hdr.disc)
3280		lp = init_level(shp,0);
3281	if((struct sh_scoped*)shp->topscope != shp->st.self)
3282		sh_setscope(shp->topscope);
3283	level = lp->maxlevel = shp->dot_depth + shp->fn_depth+1;
3284	SH_LEVELNOD->nvalue.s = lp->maxlevel;
3285	shp->st.lineno = error_info.line;
3286	if(nv_isattr(np,NV_FPOSIX))
3287	{
3288		char *save;
3289		int loopcnt = shp->st.loopcnt;
3290		shp->posix_fun = np;
3291		save = argv[-1];
3292		argv[-1] = 0;
3293		shp->st.funname = nv_name(np);
3294		shp->last_root = nv_dict(DOTSHNOD);
3295		nv_putval(SH_FUNNAMENOD, nv_name(np),NV_NOFREE);
3296		opt_info.index = opt_info.offset = 0;
3297		error_info.errors = 0;
3298		shp->st.loopcnt = 0;
3299		b_dot_cmd(argn+1,argv-1,&shp->bltindata);
3300		shp->st.loopcnt = loopcnt;
3301		argv[-1] = save;
3302	}
3303	else
3304	{
3305		fun.env = envlist;
3306		fun.node = np;
3307		fun.nref = 0;
3308		sh_funscope(argn,argv,0,&fun,execflg);
3309	}
3310	if(level-- != nv_getnum(SH_LEVELNOD))
3311	{
3312		Shscope_t *sp = sh_getscope(0,SEEK_END);
3313		sh_setscope(sp);
3314	}
3315	lp->maxlevel = level;
3316	SH_LEVELNOD->nvalue.s = lp->maxlevel;
3317	shp->last_root = nv_dict(DOTSHNOD);
3318#if 0
3319	nv_putval(SH_FUNNAMENOD,shp->st.funname,NV_NOFREE);
3320#else
3321	nv_putval(SH_FUNNAMENOD,fname,NV_NOFREE);
3322#endif
3323	nv_putval(SH_PATHNAMENOD,shp->st.filename,NV_NOFREE);
3324	shp->pipepid = pipepid;
3325}
3326
3327/*
3328 * external interface to execute a function without arguments
3329 * <np> is the function node
3330 * If <nq> is not-null, then sh.name and sh.subscript will be set
3331 */
3332int sh_fun(Namval_t *np, Namval_t *nq, char *argv[])
3333{
3334	Shell_t		*shp = sh_getinterp();
3335	register int offset;
3336	register char *base;
3337	Namval_t node;
3338	struct Namref	nr;
3339	long		mode;
3340	char		*prefix = shp->prefix;
3341	int n=0;
3342	char *av[3];
3343	Fcin_t save;
3344	fcsave(&save);
3345	if((offset=staktell())>0)
3346		base=stakfreeze(0);
3347	shp->prefix = 0;
3348	if(!argv)
3349	{
3350		argv = av+1;
3351		argv[1]=0;
3352	}
3353	argv[0] = nv_name(np);
3354	while(argv[n])
3355		n++;
3356	if(nq)
3357		mode = set_instance(shp,nq,&node, &nr);
3358	if(is_abuiltin(np))
3359	{
3360		int jmpval;
3361		struct checkpt buff;
3362		Shbltin_t *bp = &shp->bltindata;
3363		sh_pushcontext(shp,&buff,SH_JMPCMD);
3364		jmpval = sigsetjmp(buff.buff,1);
3365		if(jmpval == 0)
3366		{
3367			bp->bnode = np;
3368			bp->ptr = nv_context(np);
3369			errorpush(&buff.err,0);
3370			error_info.id = argv[0];
3371			opt_info.index = opt_info.offset = 0;
3372			opt_info.disc = 0;
3373			shp->exitval = 0;
3374			shp->exitval = (*funptr(np))(n,argv,(void*)bp);
3375		}
3376		sh_popcontext(shp,&buff);
3377		if(jmpval>SH_JMPCMD)
3378			siglongjmp(*shp->jmplist,jmpval);
3379	}
3380	else
3381		sh_funct(shp,np,n,argv,(struct argnod*)0,sh_isstate(SH_ERREXIT));
3382	if(nq)
3383		unset_instance(nq, &node, &nr, mode);
3384	fcrestore(&save);
3385	if(offset>0)
3386		stakset(base,offset);
3387	shp->prefix = prefix;
3388	return(shp->exitval);
3389}
3390
3391/*
3392 * This dummy routine is called by built-ins that do recursion
3393 * on the file system (chmod, chgrp, chown).  It causes
3394 * the shell to invoke the non-builtin version in this case
3395 */
3396int cmdrecurse(int argc, char* argv[], int ac, char* av[])
3397{
3398	NOT_USED(argc);
3399	NOT_USED(argv[0]);
3400	NOT_USED(ac);
3401	NOT_USED(av[0]);
3402	return(SH_RUNPROG);
3403}
3404
3405/*
3406 * set up pipe for cooperating process
3407 */
3408static void coproc_init(Shell_t *shp, int pipes[])
3409{
3410	int outfd;
3411	if(shp->coutpipe>=0 && shp->cpid)
3412		errormsg(SH_DICT,ERROR_exit(1),e_pexists);
3413	shp->cpid = 0;
3414	if(shp->cpipe[0]<=0 || shp->cpipe[1]<=0)
3415	{
3416		/* first co-process */
3417		sh_pclose(shp->cpipe);
3418		sh_pipe(shp->cpipe);
3419		if((outfd=shp->cpipe[1]) < 10)
3420		{
3421		        int fd=fcntl(shp->cpipe[1],F_DUPFD,10);
3422			if(fd>=10)
3423			{
3424			        shp->fdstatus[fd] = (shp->fdstatus[outfd]&~IOCLEX);
3425				close(outfd);
3426			        shp->fdstatus[outfd] = IOCLOSE;
3427				shp->cpipe[1] = fd;
3428			}
3429		}
3430		if(fcntl(*shp->cpipe,F_SETFD,FD_CLOEXEC)>=0)
3431			shp->fdstatus[shp->cpipe[0]] |= IOCLEX;
3432		shp->fdptrs[shp->cpipe[0]] = shp->cpipe;
3433
3434		if(fcntl(shp->cpipe[1],F_SETFD,FD_CLOEXEC) >=0)
3435			shp->fdstatus[shp->cpipe[1]] |= IOCLEX;
3436	}
3437	shp->outpipe = shp->cpipe;
3438	sh_pipe(shp->inpipe=pipes);
3439	shp->coutpipe = shp->inpipe[1];
3440	shp->fdptrs[shp->coutpipe] = &shp->coutpipe;
3441	if(fcntl(shp->outpipe[0],F_SETFD,FD_CLOEXEC)>=0)
3442		shp->fdstatus[shp->outpipe[0]] |= IOCLEX;
3443}
3444
3445#if SHOPT_SPAWN
3446
3447
3448#if SHOPT_AMP || !defined(_lib_fork)
3449
3450/*
3451 * create a shell script consisting of t->fork.forktre and execute it
3452 */
3453static int run_subshell(Shell_t *shp,const Shnode_t *t,pid_t grp)
3454{
3455	static const char prolog[] = "(print $(typeset +A);set; typeset -p; print .sh.dollar=$$;set +o)";
3456	register int i, fd, trace = sh_isoption(SH_XTRACE);
3457	int pin,pout;
3458	pid_t pid;
3459	char *arglist[2], *envlist[2], devfd[12], *cp;
3460	Sfio_t *sp = sftmp(0);
3461	envlist[0] = "_=" SH_ID;
3462	envlist[1] = 0;
3463	arglist[0] = error_info.id?error_info.id:shp->shname;
3464	if(*arglist[0]=='-')
3465		arglist[0]++;
3466	arglist[1] = devfd;
3467	strncpy(devfd,e_devfdNN,sizeof(devfd));
3468	arglist[2] = 0;
3469	sfstack(sfstdout,sp);
3470	if(trace)
3471		sh_offoption(SH_XTRACE);
3472	sfwrite(sfstdout,"typeset -A -- ",14);
3473	sh_trap(prolog,0);
3474	nv_scan(shp->fun_tree, print_fun, (void*)0,0, 0);
3475	if(shp->st.dolc>0)
3476	{
3477		/* pass the positional parameters */
3478		char **argv = shp->st.dolv+1;
3479		sfwrite(sfstdout,"set --",6);
3480		while(*argv)
3481			sfprintf(sfstdout," %s",sh_fmtq(*argv++));
3482		sfputc(sfstdout,'\n');
3483	}
3484	pin = (shp->inpipe?shp->inpipe[1]:0);
3485	pout = (shp->outpipe?shp->outpipe[0]:0);
3486	for(i=3; i < 10; i++)
3487	{
3488		if(shp->fdstatus[i]&IOCLEX && i!=pin && i!=pout)
3489		{
3490			sfprintf(sfstdout,"exec %d<&%d\n",i,i);
3491			fcntl(i,F_SETFD,0);
3492		}
3493	}
3494	sfprintf(sfstdout,"LINENO=%d\n",t->fork.forkline);
3495	if(trace)
3496	{
3497		sfwrite(sfstdout,"set -x\n",7);
3498		sh_onoption(SH_XTRACE);
3499	}
3500	sfstack(sfstdout,NIL(Sfio_t*));
3501	sh_deparse(sp,t->fork.forktre,0);
3502	sfseek(sp,(Sfoff_t)0,SEEK_SET);
3503	fd = sh_dup(sffileno(sp));
3504	cp = devfd+8;
3505	if(fd>9)
3506		*cp++ = '0' + (fd/10);
3507	*cp++ = '0' + fd%10;
3508	*cp = 0;
3509	sfclose(sp);
3510	sfsync(NIL(Sfio_t*));
3511	if(!shp->gd->shpath)
3512		shp->gd->shpath = pathshell();
3513	pid = spawnveg(shp->shpath,arglist,envlist,grp);
3514	close(fd);
3515	for(i=3; i < 10; i++)
3516	{
3517		if(shp->fdstatus[i]&IOCLEX && i!=pin && i!=pout)
3518			fcntl(i,F_SETFD,FD_CLOEXEC);
3519	}
3520	if(pid <=0)
3521		errormsg(SH_DICT,ERROR_system(ERROR_NOEXEC),e_exec,arglist[0]);
3522	return(pid);
3523}
3524#endif /* !_lib_fork */
3525
3526static void sigreset(Shell_t *shp,int mode)
3527{
3528	register char   *trap;
3529	register int sig=shp->st.trapmax;
3530	while(sig-- > 0)
3531	{
3532		if(sig==SIGCHLD)
3533			continue;
3534		if((trap=shp->st.trapcom[sig]) && *trap==0)
3535			signal(sig,mode?sh_fault:SIG_IGN);
3536	}
3537}
3538
3539/*
3540 * A combined fork/exec for systems with slow or non-existent fork()
3541 */
3542static pid_t sh_ntfork(Shell_t *shp,const Shnode_t *t,char *argv[],int *jobid,int flag)
3543{
3544	static pid_t	spawnpid;
3545	static int	savetype;
3546	static int	savejobid;
3547	struct checkpt	buff;
3548	int		otype=0, jmpval;
3549	volatile int	jobwasset=0, scope=0, sigwasset=0;
3550	char		**arge, *path;
3551	volatile pid_t	grp = 0;
3552	Pathcomp_t	*pp;
3553	if(flag)
3554	{
3555		otype = savetype;
3556		savetype=0;
3557	}
3558#   if SHOPT_AMP || !defined(_lib_fork)
3559	if(!argv)
3560	{
3561		register Shnode_t *tchild = t->fork.forktre;
3562		int optimize=0;
3563		otype = t->tre.tretyp;
3564		savetype = otype;
3565		spawnpid = 0;
3566#	ifndef _lib_fork
3567		if((tchild->tre.tretyp&COMMSK)==TCOM)
3568		{
3569			Namval_t *np = (Namval_t*)(tchild->com.comnamp);
3570			if(np)
3571			{
3572				path = nv_name(np);
3573				if(!nv_isattr(np,BLT_ENV))
3574					np=0;
3575				else if(strcmp(path,"echo")==0 || memcmp(path,"print",5)==0)
3576					np=0;
3577			}
3578			else if(!tchild->com.comarg)
3579				optimize=1;
3580			else if(tchild->com.comtyp&COMSCAN)
3581			{
3582				if(tchild->com.comarg->argflag&ARG_RAW)
3583					path = tchild->com.comarg->argval;
3584				else
3585					path = 0;
3586			}
3587			else
3588				path = ((struct dolnod*)tchild->com.comarg)->dolval[ARG_SPARE];
3589			if(!np && path && !nv_search(path,shp->fun_tree,0))
3590				optimize=1;
3591		}
3592#	endif
3593		sh_pushcontext(shp,&buff,SH_JMPIO);
3594		jmpval = sigsetjmp(buff.buff,0);
3595		{
3596			if((otype&FINT) && !sh_isstate(SH_MONITOR))
3597			{
3598				signal(SIGQUIT,SIG_IGN);
3599				signal(SIGINT,SIG_IGN);
3600				if(!shp->st.ioset)
3601				{
3602					sh_iosave(shp,0,buff.topfd,(char*)0);
3603					sh_iorenumber(shp,sh_chkopen(e_devnull),0);
3604				}
3605			}
3606			if(otype&FPIN)
3607			{
3608				int fd = shp->inpipe[1];
3609				sh_iosave(shp,0,buff.topfd,(char*)0);
3610				sh_iorenumber(shp,shp->inpipe[0],0);
3611				if(fd>=0 && (!(otype&FPOU) || (otype&FCOOP)) && fcntl(fd,F_SETFD,FD_CLOEXEC)>=0)
3612					shp->fdstatus[fd] |= IOCLEX;
3613			}
3614			if(otype&FPOU)
3615			{
3616#if SHOPT_COSHELL
3617					if(shp->outpipe[2] > 20000)
3618						sh_coaccept(shp,shp->outpipe,1);
3619#endif /* SHOPT_COSHELL */
3620				sh_iosave(shp,1,buff.topfd,(char*)0);
3621				sh_iorenumber(shp,sh_dup(shp->outpipe[1]),1);
3622				if(fcntl(shp->outpipe[0],F_SETFD,FD_CLOEXEC)>=0)
3623					shp->fdstatus[shp->outpipe[0]] |= IOCLEX;
3624			}
3625
3626			if(t->fork.forkio)
3627				sh_redirect(shp,t->fork.forkio,0);
3628			if(optimize==0)
3629			{
3630#ifdef SIGTSTP
3631				if(job.jobcontrol)
3632				{
3633					signal(SIGTTIN,SIG_DFL);
3634					signal(SIGTTOU,SIG_DFL);
3635				}
3636#endif /* SIGTSTP */
3637#ifdef JOBS
3638				if(sh_isstate(SH_MONITOR) && (job.jobcontrol || (otype&FAMP)))
3639				{
3640					if((otype&FAMP) || job.curpgid==0)
3641						grp = 1;
3642					else
3643						grp = job.curpgid;
3644				}
3645#endif /* JOBS */
3646				spawnpid = run_subshell(shp,t,grp);
3647			}
3648			else
3649			{
3650				sh_exec(tchild,SH_NTFORK);
3651				if(jobid)
3652					*jobid = savejobid;
3653			}
3654		}
3655		sh_popcontext(shp,&buff);
3656		if((otype&FINT) && !sh_isstate(SH_MONITOR))
3657		{
3658			signal(SIGQUIT,sh_fault);
3659			signal(SIGINT,sh_fault);
3660		}
3661		if((otype&FPIN) && (!(otype&FPOU) || (otype&FCOOP)) && fcntl(shp->inpipe[1],F_SETFD,FD_CLOEXEC)>=0)
3662			shp->fdstatus[shp->inpipe[1]] &= ~IOCLEX;
3663		if(t->fork.forkio || otype)
3664			sh_iorestore(shp,buff.topfd,jmpval);
3665		if(optimize==0)
3666		{
3667#ifdef SIGTSTP
3668			if(job.jobcontrol)
3669			{
3670				signal(SIGTTIN,SIG_IGN);
3671				signal(SIGTTOU,SIG_IGN);
3672			}
3673#endif /* SIGTSTP */
3674			if(spawnpid>0)
3675				_sh_fork(shp,spawnpid,otype,jobid);
3676			if(grp>0 && !(otype&FAMP))
3677			{
3678				while(tcsetpgrp(job.fd,job.curpgid)<0 && job.curpgid!=spawnpid)
3679					job.curpgid = spawnpid;
3680			}
3681		}
3682		savetype=0;
3683		if(jmpval>SH_JMPIO)
3684			siglongjmp(*shp->jmplist,jmpval);
3685		if(spawnpid<0 && (otype&FCOOP))
3686		{
3687			sh_close(shp->coutpipe);
3688			sh_close(shp->cpipe[1]);
3689			shp->cpipe[1] = -1;
3690			shp->coutpipe = -1;
3691		}
3692		shp->exitval = 0;
3693		return(spawnpid);
3694	}
3695#   endif /* !_lib_fork */
3696	sh_pushcontext(shp,&buff,SH_JMPCMD);
3697	errorpush(&buff.err,ERROR_SILENT);
3698	jmpval = sigsetjmp(buff.buff,0);
3699	if(jmpval == 0)
3700	{
3701		if((otype&FINT) && !sh_isstate(SH_MONITOR))
3702		{
3703			signal(SIGQUIT,SIG_IGN);
3704			signal(SIGINT,SIG_IGN);
3705		}
3706		spawnpid = -1;
3707		if(t->com.comio)
3708			sh_redirect(shp,t->com.comio,0);
3709		error_info.id = *argv;
3710		if(t->com.comset)
3711		{
3712			scope++;
3713			sh_scope(shp,t->com.comset,0);
3714		}
3715		if(!strchr(path=argv[0],'/'))
3716		{
3717			Namval_t *np;
3718			if((np=nv_search(path,shp->track_tree,0)) && !nv_isattr(np,NV_NOALIAS) && np->nvalue.cp)
3719				path = nv_getval(np);
3720			else if(path_absolute(shp,path,NIL(Pathcomp_t*)))
3721			{
3722			path = stkptr(shp->stk,PATH_OFFSET);
3723			stkfreeze(shp->stk,0);
3724		}
3725		else
3726		{
3727			pp=path_get(shp,path);
3728			while(pp)
3729			{
3730				if(pp->len==1 && *pp->name=='.')
3731					break;
3732				pp = pp->next;
3733			}
3734			if(!pp)
3735				path = 0;
3736		}
3737	}
3738	else if(sh_isoption(SH_RESTRICTED))
3739		errormsg(SH_DICT,ERROR_exit(1),e_restricted,path);
3740	if(!path)
3741	{
3742		spawnpid = -1;
3743		goto fail;
3744	}
3745	arge = sh_envgen();
3746	shp->exitval = 0;
3747#ifdef SIGTSTP
3748		if(job.jobcontrol)
3749		{
3750			signal(SIGTTIN,SIG_DFL);
3751			signal(SIGTTOU,SIG_DFL);
3752			jobwasset++;
3753		}
3754#endif /* SIGTSTP */
3755#ifdef JOBS
3756		if(sh_isstate(SH_MONITOR) && (job.jobcontrol || (otype&FAMP)))
3757		{
3758			if((otype&FAMP) || job.curpgid==0)
3759				grp = 1;
3760			else
3761				grp = job.curpgid;
3762		}
3763#endif /* JOBS */
3764
3765		sfsync(NIL(Sfio_t*));
3766		sigreset(shp,0);	/* set signals to ignore */
3767		sigwasset++;
3768	        /* find first path that has a library component */
3769		for(pp=path_get(shp,argv[0]); pp && !pp->lib ; pp=pp->next);
3770		spawnpid = path_spawn(shp,path,argv,arge,pp,(grp<<1)|1);
3771		if(spawnpid < 0 && errno==ENOEXEC)
3772		{
3773			char *devfd;
3774			int fd = open(path,O_RDONLY);
3775			argv[-1] = argv[0];
3776			argv[0] = path;
3777			if(fd>=0)
3778			{
3779				struct stat statb;
3780				sfprintf(shp->strbuf,"/dev/fd/%d",fd);
3781				if(stat(devfd=sfstruse(shp->strbuf),&statb)>=0)
3782					argv[0] =  devfd;
3783			}
3784			if(!shp->gd->shpath)
3785				shp->gd->shpath = pathshell();
3786			spawnpid = path_spawn(shp,shp->gd->shpath,&argv[-1],arge,pp,(grp<<1)|1);
3787			if(fd>=0)
3788				close(fd);
3789			argv[0] = argv[-1];
3790		}
3791	fail:
3792		if(spawnpid < 0) switch(errno=shp->path_err)
3793		{
3794		    case ENOENT:
3795			errormsg(SH_DICT,ERROR_system(ERROR_NOENT),e_found+4);
3796		    default:
3797			errormsg(SH_DICT,ERROR_system(ERROR_NOEXEC),e_exec+4);
3798		}
3799	}
3800	else
3801		exitset();
3802	sh_popcontext(shp,&buff);
3803	if(buff.olist)
3804		free_list(buff.olist);
3805#ifdef SIGTSTP
3806	if(jobwasset)
3807	{
3808		signal(SIGTTIN,SIG_IGN);
3809		signal(SIGTTOU,SIG_IGN);
3810	}
3811#endif /* SIGTSTP */
3812	if(sigwasset)
3813		sigreset(shp,1);	/* restore ignored signals */
3814	if(scope)
3815	{
3816		sh_unscope(shp);
3817		if(jmpval==SH_JMPSCRIPT)
3818			nv_setlist(t->com.comset,NV_EXPORT|NV_IDENT|NV_ASSIGN,0);
3819	}
3820	if(t->com.comio)
3821		sh_iorestore(shp,buff.topfd,jmpval);
3822	if(jmpval>SH_JMPCMD)
3823		siglongjmp(*shp->jmplist,jmpval);
3824	if(spawnpid>0)
3825	{
3826		_sh_fork(shp,spawnpid,otype,jobid);
3827#ifdef JOBS
3828		if(grp==1)
3829			job.curpgid = spawnpid;
3830#   ifdef SIGTSTP
3831		if(grp>0 && !(otype&FAMP))
3832		{
3833			while(tcsetpgrp(job.fd,job.curpgid)<0 && job.curpgid!=spawnpid)
3834				job.curpgid = spawnpid;
3835		}
3836#   endif /* SIGTSTP */
3837#endif /* JOBS */
3838		savejobid = *jobid;
3839		if(otype)
3840			return(0);
3841	}
3842	return(spawnpid);
3843}
3844
3845#   ifdef _was_lib_fork
3846#	define _lib_fork	1
3847#   endif
3848#   ifndef _lib_fork
3849	pid_t fork(void)
3850	{
3851		errormsg(SH_DICT,ERROR_exit(3),e_notimp,"fork");
3852		return(-1);
3853	}
3854#   endif /* _lib_fork */
3855#endif /* SHOPT_SPAWN */
3856