1/***********************************************************************
2*                                                                      *
3*               This software is part of the ast package               *
4*          Copyright (c) 1982-2012 AT&T Intellectual Property          *
5*                      and is licensed under the                       *
6*                 Eclipse Public License, Version 1.0                  *
7*                    by AT&T Intellectual Property                     *
8*                                                                      *
9*                A copy of the License is available at                 *
10*          http://www.eclipse.org/org/documents/epl-v10.html           *
11*         (with md5 checksum b35adb5213ca9657e911e9befb180842)         *
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 *   Create and manage subshells avoiding forks when possible
23 *
24 *   David Korn
25 *   AT&T Labs
26 *
27 */
28
29#include	"defs.h"
30#include	<ls.h>
31#include	"io.h"
32#include	"fault.h"
33#include	"shnodes.h"
34#include	"shlex.h"
35#include	"jobs.h"
36#include	"variables.h"
37#include	"path.h"
38
39#ifndef PIPE_BUF
40#   define PIPE_BUF	512
41#endif
42
43#ifndef O_SEARCH
44#   ifdef O_PATH
45#	define O_SEARCH	O_PATH
46#   else
47#	define O_SEARCH	0
48#   endif
49#endif
50
51/*
52 * Note that the following structure must be the same
53 * size as the Dtlink_t structure
54 */
55struct Link
56{
57	struct Link	*next;
58	Namval_t	*child;
59	Dt_t		*dict;
60	Namval_t	*node;
61};
62
63/*
64 * The following structure is used for command substitution and (...)
65 */
66static struct subshell
67{
68	Shell_t		*shp;	/* shell interpreter */
69	struct subshell	*prev;	/* previous subshell data */
70	struct subshell	*pipe;	/* subshell where output goes to pipe on fork */
71	Dt_t		*var;	/* variable table at time of subshell */
72	struct Link	*svar;	/* save shell variable table */
73	Dt_t		*sfun;	/* function scope for subshell */
74	Dt_t		*salias;/* alias scope for subshell */
75	Pathcomp_t	*pathlist; /* for PATH variable */
76#if (ERROR_VERSION >= 20030214L)
77	struct Error_context_s *errcontext;
78#else
79	struct errorcontext *errcontext;
80#endif
81	Shopt_t		options;/* save shell options */
82	pid_t		subpid;	/* child process id */
83	Sfio_t*	saveout;/*saved standard output */
84	char		*pwd;	/* present working directory */
85	const char	*shpwd;	/* saved pointer to sh.pwd */
86	void		*jobs;	/* save job info */
87	int		pwdfd;	/* file descritor for pwd */
88	mode_t		mask;	/* saved umask */
89	short		tmpfd;	/* saved tmp file descriptor */
90	short		pipefd;	/* read fd if pipe is created */
91	char		jobcontrol;
92	char		monitor;
93	unsigned char	fdstatus;
94	int		fdsaved; /* bit make for saved files */
95	int		sig;	/* signal for $$ */
96	pid_t		bckpid;
97	pid_t		cpid;
98	int		coutpipe;
99	int		cpipe;
100	int		nofork;
101	int		subdup;
102	char		subshare;
103	char		comsub;
104	char		pwdclose;
105#if SHOPT_COSHELL
106	void		*coshell;
107#endif /* SHOPT_COSHELL */
108} *subshell_data;
109
110static int subenv;
111
112
113/*
114 * This routine will turn the sftmp() file into a real /tmp file or pipe
115 * if the /tmp file create fails
116 */
117void	sh_subtmpfile(Shell_t *shp)
118{
119	if(sfset(sfstdout,0,0)&SF_STRING)
120	{
121		register int fd;
122		register struct checkpt	*pp = (struct checkpt*)shp->jmplist;
123		register struct subshell *sp = subshell_data->pipe;
124		/* save file descriptor 1 if open */
125		if((sp->tmpfd = fd = fcntl(1,F_DUPFD,10)) >= 0)
126		{
127			fcntl(fd,F_SETFD,FD_CLOEXEC);
128			shp->fdstatus[fd] = shp->fdstatus[1]|IOCLEX;
129			close(1);
130		}
131		else if(errno!=EBADF)
132			errormsg(SH_DICT,ERROR_system(1),e_toomany);
133		/* popping a discipline forces a /tmp file create */
134		sfdisc(sfstdout,SF_POPDISC);
135		if((fd=sffileno(sfstdout))<0)
136		{
137			/* unable to create the /tmp file so use a pipe */
138			int fds[3];
139			Sfoff_t off;
140			fds[2] = 0;
141			sh_pipe(fds);
142			sp->pipefd = fds[0];
143			sh_fcntl(sp->pipefd,F_SETFD,FD_CLOEXEC);
144			/* write the data to the pipe */
145			if(off = sftell(sfstdout))
146				write(fds[1],sfsetbuf(sfstdout,(Void_t*)sfstdout,0),(size_t)off);
147			sfclose(sfstdout);
148			if((sh_fcntl(fds[1],F_DUPFD, 1)) != 1)
149				errormsg(SH_DICT,ERROR_system(1),e_file+4);
150			sh_close(fds[1]);
151		}
152		else
153		{
154			shp->fdstatus[fd] = IOREAD|IOWRITE;
155			sfsync(sfstdout);
156			if(fd==1)
157				fcntl(1,F_SETFD,0);
158			else
159			{
160				sfsetfd(sfstdout,1);
161				shp->fdstatus[1] = shp->fdstatus[fd];
162				shp->fdstatus[fd] = IOCLOSE;
163			}
164		}
165		sh_iostream(shp,1);
166		sfset(sfstdout,SF_SHARE|SF_PUBLIC,1);
167		sfpool(sfstdout,shp->outpool,SF_WRITE);
168		if(pp && pp->olist  && pp->olist->strm == sfstdout)
169			pp->olist->strm = 0;
170	}
171}
172
173
174/*
175 * This routine creates a temp file if necessary and creates a subshell.
176 * The parent routine longjmps back to sh_subshell()
177 * The child continues possibly with its standard output replaced by temp file
178 */
179void sh_subfork(void)
180{
181	register struct subshell *sp = subshell_data;
182	Shell_t	*shp = sp->shp;
183	int	curenv = shp->curenv;
184	pid_t pid;
185	char *trap = shp->st.trapcom[0];
186	if(trap)
187		trap = strdup(trap);
188	/* see whether inside $(...) */
189	if(sp->pipe)
190		sh_subtmpfile(shp);
191	shp->curenv = 0;
192	shp->savesig = -1;
193	if(pid = sh_fork(shp,FSHOWME,NIL(int*)))
194	{
195		shp->curenv = curenv;
196		/* this is the parent part of the fork */
197		if(sp->subpid==0)
198			sp->subpid = pid;
199		if(trap)
200			free((void*)trap);
201		siglongjmp(*shp->jmplist,SH_JMPSUB);
202	}
203	else
204	{
205		/* this is the child part of the fork */
206		/* setting subpid to 1 causes subshell to exit when reached */
207		sh_onstate(SH_FORKED);
208		sh_onstate(SH_NOLOG);
209		sh_offoption(SH_MONITOR);
210		sh_offstate(SH_MONITOR);
211		subshell_data = 0;
212		shp->subshell = 0;
213		shp->comsub = 0;
214		SH_SUBSHELLNOD->nvalue.s = 0;
215		sp->subpid=0;
216		shp->st.trapcom[0] = trap;
217		shp->savesig = 0;
218	}
219}
220
221int nv_subsaved(register Namval_t *np)
222{
223	register struct subshell	*sp;
224	register struct Link		*lp;
225	for(sp = (struct subshell*)subshell_data; sp; sp=sp->prev)
226	{
227		for(lp=sp->svar; lp; lp = lp->next)
228		{
229			if(lp->node==np)
230				return(1);
231		}
232	}
233	return(0);
234}
235
236/*
237 * This routine will make a copy of the given node in the
238 * layer created by the most recent subshell_fork if the
239 * node hasn't already been copied
240 */
241Namval_t *sh_assignok(register Namval_t *np,int add)
242{
243	register Namval_t	*mp;
244	register struct Link	*lp;
245	register struct subshell *sp = (struct subshell*)subshell_data;
246	Shell_t			*shp = sp->shp;
247	Dt_t			*dp= shp->var_tree;
248	Namval_t		*mpnext;
249	Namarr_t		*ap;
250	int			save;
251	/* don't bother with this */
252	if(!sp->shpwd || np==SH_LEVELNOD || np==L_ARGNOD || np==SH_SUBSCRNOD || np==SH_NAMENOD)
253		return(np);
254	/* don't bother to save if in newer scope */
255	if(sp->var!=shp->var_tree && sp->var!=shp->var_base && shp->last_root==shp->var_tree)
256		return(np);
257	if((ap=nv_arrayptr(np)) && (mp=nv_opensub(np)))
258	{
259		shp->last_root = ap->table;
260		sh_assignok(mp,add);
261		if(!add || array_assoc(ap))
262			return(np);
263	}
264	for(lp=sp->svar; lp;lp = lp->next)
265	{
266		if(lp->node==np)
267			return(np);
268	}
269	/* first two pointers use linkage from np */
270	lp = (struct Link*)malloc(sizeof(*np)+2*sizeof(void*));
271	memset(lp,0, sizeof(*mp)+2*sizeof(void*));
272	lp->node = np;
273	if(!add &&  nv_isvtree(np))
274	{
275		Namval_t	fake;
276		Dt_t		*walk, *root=shp->var_tree;
277		char		*name = nv_name(np);
278		size_t		len = strlen(name);
279		fake.nvname = name;
280		mpnext = dtnext(root,&fake);
281		dp = root->walk?root->walk:root;
282		while(mp=mpnext)
283		{
284			walk = root->walk?root->walk:root;
285			mpnext = dtnext(root,mp);
286			if(memcmp(name,mp->nvname,len) || mp->nvname[len]!='.')
287				break;
288			nv_delete(mp,walk,NV_NOFREE);
289			*((Namval_t**)mp) = lp->child;
290			lp->child = mp;
291
292		}
293	}
294	lp->dict = dp;
295	mp = (Namval_t*)&lp->dict;
296	lp->next = subshell_data->svar;
297	subshell_data->svar = lp;
298	save = shp->subshell;
299	shp->subshell = 0;
300	mp->nvname = np->nvname;
301	if(nv_isattr(np,NV_NOFREE))
302		nv_onattr(mp,NV_IDENT);
303	nv_clone(np,mp,(add?(nv_isnull(np)?0:NV_NOFREE)|NV_ARRAY:NV_MOVE));
304	shp->subshell = save;
305	return(np);
306}
307
308/*
309 * restore the variables
310 */
311static void nv_restore(struct subshell *sp)
312{
313	register struct Link *lp, *lq;
314	register Namval_t *mp, *np;
315	const char *save = sp->shpwd;
316	Namval_t	*mpnext;
317	int		flags,nofree;
318	sp->shpwd = 0;	/* make sure sh_assignok doesn't save with nv_unset() */
319	for(lp=sp->svar; lp; lp=lq)
320	{
321		np = (Namval_t*)&lp->dict;
322		lq = lp->next;
323		mp = lp->node;
324		if(!mp->nvname)
325			continue;
326		flags = 0;
327		if(nv_isattr(mp,NV_MINIMAL) && !nv_isattr(np,NV_EXPORT))
328			flags |= NV_MINIMAL;
329		if(nv_isarray(mp))
330			 nv_putsub(mp,NIL(char*),ARRAY_SCAN);
331		nofree = mp->nvfun?mp->nvfun->nofree:0;
332		_nv_unset(mp,NV_RDONLY|NV_CLONE);
333		if(nv_isarray(np))
334		{
335			nv_clone(np,mp,NV_MOVE);
336			goto skip;
337		}
338		nv_setsize(mp,nv_size(np));
339		if(!(flags&NV_MINIMAL))
340			mp->nvenv = np->nvenv;
341		if(!nofree)
342			mp->nvfun = np->nvfun;
343		if(nv_isattr(np,NV_IDENT))
344		{
345			nv_offattr(np,NV_IDENT);
346			flags |= NV_NOFREE;
347		}
348		mp->nvflag = np->nvflag|(flags&NV_MINIMAL);
349		if(nv_cover(mp))
350			nv_putval(mp, nv_getval(np),np->nvflag|NV_NOFREE|NV_RDONLY);
351		else
352			mp->nvalue.cp = np->nvalue.cp;
353		if(nofree && np->nvfun && !np->nvfun->nofree)
354			free((char*)np->nvfun);
355		np->nvfun = 0;
356		if(nv_isattr(mp,NV_EXPORT))
357		{
358			char *name = nv_name(mp);
359			sh_envput(sp->shp->env,mp);
360			if(*name=='_' && strcmp(name,"_AST_FEATURES")==0)
361				astconf(NiL, NiL, NiL);
362		}
363		else if(nv_isattr(np,NV_EXPORT))
364			env_delete(sp->shp->env,nv_name(mp));
365		nv_onattr(mp,flags);
366	skip:
367		for(mp=lp->child; mp; mp=mpnext)
368		{
369			mpnext = *((Namval_t**)mp);
370			dtinsert(lp->dict,mp);
371		}
372		free((void*)lp);
373		sp->svar = lq;
374	}
375	sp->shpwd=save;
376}
377
378/*
379 * return pointer to alias tree
380 * create new one if in a subshell and one doesn't exist and create is non-zero
381 */
382Dt_t *sh_subaliastree(int create)
383{
384	register struct subshell *sp = subshell_data;
385	if(!sp || sp->shp->curenv==0)
386		return(sh.alias_tree);
387	if(!sp->salias && create)
388	{
389		sp->salias = dtopen(&_Nvdisc,Dtoset);
390		dtview(sp->salias,sp->shp->alias_tree);
391		sp->shp->alias_tree = sp->salias;
392	}
393	return(sp->salias);
394}
395
396/*
397 * return pointer to function tree
398 * create new one if in a subshell and one doesn't exist and create is non-zero
399 */
400Dt_t *sh_subfuntree(int create)
401{
402	register struct subshell *sp = subshell_data;
403	if(!sp || sp->shp->curenv==0)
404		return(sh.fun_tree);
405	if(!sp->sfun && create)
406	{
407		sp->sfun = dtopen(&_Nvdisc,Dtoset);
408		dtview(sp->sfun,sp->shp->fun_tree);
409		sp->shp->fun_tree = sp->sfun;
410	}
411	return(sp->shp->fun_tree);
412}
413
414static void table_unset(register Dt_t *root,int fun)
415{
416	register Namval_t *np,*nq;
417	int flag;
418	for(np=(Namval_t*)dtfirst(root);np;np=nq)
419	{
420		nq = (Namval_t*)dtnext(root,np);
421		flag=0;
422		if(fun && np->nvalue.rp && np->nvalue.rp->fname && *np->nvalue.rp->fname=='/')
423		{
424			np->nvalue.rp->fdict = 0;
425			flag = NV_NOFREE;
426		}
427		else
428			_nv_unset(np,NV_RDONLY);
429		nv_delete(np,root,flag|NV_FUNCTION);
430	}
431}
432
433int sh_subsavefd(register int fd)
434{
435	register struct subshell *sp = subshell_data;
436	register int old=0;
437	if(sp)
438	{
439		old = !(sp->fdsaved&(1<<(fd-1)));
440		sp->fdsaved |= (1<<(fd-1));
441	}
442	return(old);
443}
444
445void sh_subjobcheck(pid_t pid)
446{
447	register struct subshell *sp = subshell_data;
448	while(sp)
449	{
450		if(sp->cpid==pid)
451		{
452			sh_close(sp->coutpipe);
453			sh_close(sp->cpipe);
454			sp->coutpipe = sp->cpipe = -1;
455			return;
456		}
457		sp = sp->prev;
458	}
459}
460
461/*
462 * Run command tree <t> in a virtual sub-shell
463 * If comsub is not null, then output will be placed in temp file (or buffer)
464 * If comsub is not null, the return value will be a stream consisting of
465 * output of command <t>.  Otherwise, NULL will be returned.
466 */
467
468Sfio_t *sh_subshell(Shell_t *shp,Shnode_t *t, volatile int flags, int comsub)
469{
470	struct subshell sub_data;
471	register struct subshell *sp = &sub_data;
472	int jmpval,nsig=0,duped=0;
473	int savecurenv = shp->curenv;
474	int savejobpgid = job.curpgid;
475	int *saveexitval = job.exitval;
476	int16_t subshell;
477	char *savsig;
478	Sfio_t *iop=0;
479	struct checkpt buff;
480	struct sh_scoped savst;
481	struct dolnod   *argsav=0;
482	int argcnt;
483	memset((char*)sp, 0, sizeof(*sp));
484	sfsync(shp->outpool);
485	sh_sigcheck(shp);
486	shp->savesig = -1;
487	if(argsav = sh_arguse(shp))
488		argcnt = argsav->dolrefcnt;
489	if(shp->curenv==0)
490	{
491		subshell_data=0;
492		subenv = 0;
493	}
494	shp->curenv = ++subenv;
495	savst = shp->st;
496	sh_pushcontext(shp,&buff,SH_JMPSUB);
497	subshell = shp->subshell+1;
498	SH_SUBSHELLNOD->nvalue.s = subshell;
499	shp->subshell = subshell;
500	sp->prev = subshell_data;
501	sp->shp = shp;
502	sp->sig = 0;
503	subshell_data = sp;
504	sp->errcontext = &buff.err;
505	sp->var = shp->var_tree;
506	sp->options = shp->options;
507	sp->jobs = job_subsave();
508	sp->subdup = shp->subdup;
509#if SHOPT_COSHELL
510	sp->coshell = shp->coshell;
511	shp->coshell = 0;
512#endif /* SHOPT_COSHELL */
513	/* make sure initialization has occurred */
514	if(!shp->pathlist)
515	{
516		shp->pathinit = 1;
517		path_get(shp,".");
518		shp->pathinit = 0;
519	}
520	sp->pathlist = path_dup((Pathcomp_t*)shp->pathlist);
521	sp->pwdfd = -1;
522	if(!shp->pwd)
523		path_pwd(shp,0);
524	sp->bckpid = shp->bckpid;
525	if(comsub)
526		sh_stats(STAT_COMSUB);
527	else
528		job.curpgid = 0;
529	sp->subshare = shp->subshare;
530	sp->comsub = shp->comsub;
531	shp->subshare = comsub==2 ||  (comsub==1 && sh_isoption(SH_SUBSHARE));
532	if(comsub)
533		shp->comsub = comsub;
534	if(!comsub || !shp->subshare)
535	{
536		struct subshell *xp;
537		sp->shpwd = shp->pwd;
538#ifdef _lib_fchdir
539		for(xp=sp->prev; xp; xp=xp->prev)
540		{
541			if(xp->pwdfd>0 && strcmp(xp->pwd,shp->pwd)==0)
542			{
543				sp->pwdfd = xp->pwdfd;
544				break;
545			}
546		}
547		if(sp->pwdfd<0)
548		{
549			int n = open(".",O_RDONLY);
550			if(O_SEARCH && errno==EACCES)
551				n =  open(".",O_RDONLY);
552			if(n>=0)
553			{
554				sp->pwdfd = n;
555				if(n<10)
556				{
557					sp->pwdfd =  fcntl(n,F_DUPFD,10);
558					close(n);
559				}
560				if(sp->pwdfd>0)
561				{
562					fcntl(sp->pwdfd,F_SETFD,FD_CLOEXEC);
563					sp->pwdclose = 1;
564				}
565			}
566		}
567#endif
568		sp->pwd = (shp->pwd?strdup(shp->pwd):0);
569		sp->mask = shp->mask;
570		sh_stats(STAT_SUBSHELL);
571		/* save trap table */
572		shp->st.otrapcom = 0;
573		shp->st.otrap = savst.trap;
574		if((nsig=shp->st.trapmax*sizeof(char*))>0 || shp->st.trapcom[0])
575		{
576			nsig += sizeof(char*);
577			memcpy(savsig=malloc(nsig),(char*)&shp->st.trapcom[0],nsig);
578			/* this nonsense needed for $(trap) */
579			shp->st.otrapcom = (char**)savsig;
580		}
581		sp->cpid = shp->cpid;
582		sp->coutpipe = shp->coutpipe;
583		sp->cpipe = shp->cpipe[1];
584		shp->cpid = 0;
585		sh_sigreset(0);
586	}
587	jmpval = sigsetjmp(buff.buff,0);
588	if(jmpval==0)
589	{
590		if(comsub)
591		{
592			/* disable job control */
593			shp->spid = 0;
594			sp->jobcontrol = job.jobcontrol;
595			sp->monitor = (sh_isstate(SH_MONITOR)!=0);
596			job.jobcontrol=0;
597			sh_offstate(SH_MONITOR);
598			sp->pipe = sp;
599			/* save sfstdout and status */
600			sp->saveout = sfswap(sfstdout,NIL(Sfio_t*));
601			sp->fdstatus = shp->fdstatus[1];
602			sp->tmpfd = -1;
603			sp->pipefd = -1;
604			/* use sftmp() file for standard output */
605			if(!(iop = sftmp(PIPE_BUF)))
606			{
607				sfswap(sp->saveout,sfstdout);
608				errormsg(SH_DICT,ERROR_system(1),e_tmpcreate);
609			}
610			sfswap(iop,sfstdout);
611			sfset(sfstdout,SF_READ,0);
612			shp->fdstatus[1] = IOWRITE;
613			if(!(sp->nofork = sh_state(SH_NOFORK)))
614				sh_onstate(SH_NOFORK);
615			flags |= sh_state(SH_NOFORK);
616		}
617		else if(sp->prev)
618		{
619			sp->pipe = sp->prev->pipe;
620			flags &= ~sh_state(SH_NOFORK);
621		}
622		if(shp->savesig < 0)
623		{
624			shp->savesig = 0;
625			sh_exec(t,flags);
626		}
627	}
628	if(comsub!=2 && jmpval!=SH_JMPSUB && shp->st.trapcom[0] && shp->subshell)
629	{
630		/* trap on EXIT not handled by child */
631		char *trap=shp->st.trapcom[0];
632		shp->st.trapcom[0] = 0;	/* prevent recursion */
633		shp->oldexit = shp->exitval;
634		sh_trap(trap,0);
635		free(trap);
636	}
637	sh_popcontext(shp,&buff);
638	if(shp->subshell==0)	/* must be child process */
639	{
640		subshell_data = sp->prev;
641		if(jmpval==SH_JMPSCRIPT)
642			siglongjmp(*shp->jmplist,jmpval);
643		shp->exitval &= SH_EXITMASK;
644		sh_done(shp,0);
645	}
646	if(!shp->savesig)
647		shp->savesig = -1;
648	nv_restore(sp);
649	if(comsub)
650	{
651		/* re-enable job control */
652		if(!sp->nofork)
653			sh_offstate(SH_NOFORK);
654		job.jobcontrol = sp->jobcontrol;
655		if(sp->monitor)
656			sh_onstate(SH_MONITOR);
657		if(sp->pipefd>=0)
658		{
659			/* sftmp() file has been returned into pipe */
660			iop = sh_iostream(shp,sp->pipefd);
661			sfclose(sfstdout);
662		}
663		else
664		{
665			/* move tmp file to iop and restore sfstdout */
666			iop = sfswap(sfstdout,NIL(Sfio_t*));
667			if(!iop)
668			{
669				/* maybe locked try again */
670				sfclrlock(sfstdout);
671				iop = sfswap(sfstdout,NIL(Sfio_t*));
672			}
673			if(iop && sffileno(iop)==1)
674			{
675				int fd=sfsetfd(iop,3);
676				if(fd<0)
677				{
678					shp->toomany = 1;
679					((struct checkpt*)shp->jmplist)->mode = SH_JMPERREXIT;
680					errormsg(SH_DICT,ERROR_system(1),e_toomany);
681				}
682				if(fd >= shp->gd->lim.open_max)
683					sh_iovalidfd(shp,fd);
684				shp->sftable[fd] = iop;
685				fcntl(fd,F_SETFD,FD_CLOEXEC);
686				shp->fdstatus[fd] = (shp->fdstatus[1]|IOCLEX);
687				shp->fdstatus[1] = IOCLOSE;
688			}
689			sfset(iop,SF_READ,1);
690		}
691		sfswap(sp->saveout,sfstdout);
692		/*  check if standard output was preserved */
693		if(sp->tmpfd>=0)
694		{
695			close(1);
696			if (fcntl(sp->tmpfd,F_DUPFD,1) != 1)
697				duped++;
698			sh_close(sp->tmpfd);
699		}
700		shp->fdstatus[1] = sp->fdstatus;
701	}
702	path_delete((Pathcomp_t*)shp->pathlist);
703	shp->pathlist = (void*)sp->pathlist;
704	job_subrestore(sp->jobs);
705	shp->jobenv = savecurenv;
706	job.curpgid = savejobpgid;
707	job.exitval = saveexitval;
708	shp->bckpid = sp->bckpid;
709	if(sp->shpwd)	/* restore environment if saved */
710	{
711		int n;
712		shp->options = sp->options;
713		if(sp->salias)
714		{
715			shp->alias_tree = dtview(sp->salias,0);
716			table_unset(sp->salias,0);
717			dtclose(sp->salias);
718		}
719		if(sp->sfun)
720		{
721			shp->fun_tree = dtview(sp->sfun,0);
722			table_unset(sp->sfun,1);
723			dtclose(sp->sfun);
724		}
725		n = shp->st.trapmax-savst.trapmax;
726		sh_sigreset(1);
727		if(n>0)
728			memset(&shp->st.trapcom[savst.trapmax],0,n*sizeof(char*));
729		shp->st = savst;
730		shp->curenv = savecurenv;
731		shp->st.otrap = 0;
732		if(nsig)
733		{
734			memcpy((char*)&shp->st.trapcom[0],savsig,nsig);
735			free((void*)savsig);
736		}
737		shp->options = sp->options;
738		if(!shp->pwd || strcmp(sp->pwd,shp->pwd))
739		{
740			/* restore PWDNOD */
741			Namval_t *pwdnod = sh_scoped(shp,PWDNOD);
742			if(shp->pwd)
743			{
744				if(sp->pwdfd >=0)
745				{
746					if(fchdir(sp->pwdfd)<0)
747						chdir(sp->pwd);
748				}
749				else
750					chdir(sp->pwd);
751				shp->pwd=sp->pwd;
752				path_newdir(shp,shp->pathlist);
753			}
754			if(nv_isattr(pwdnod,NV_NOFREE))
755				pwdnod->nvalue.cp = (const char*)sp->pwd;
756		}
757		else if(sp->shpwd != shp->pwd)
758		{
759			shp->pwd = sp->pwd;
760			if(PWDNOD->nvalue.cp==sp->shpwd)
761				PWDNOD->nvalue.cp = sp->pwd;
762		}
763		else
764			free((void*)sp->pwd);
765		if(sp->pwdclose)
766			close(sp->pwdfd);
767		if(sp->mask!=shp->mask)
768			umask(shp->mask=sp->mask);
769		if(shp->coutpipe!=sp->coutpipe)
770		{
771			sh_close(shp->coutpipe);
772			sh_close(shp->cpipe[1]);
773		}
774		shp->cpid = sp->cpid;
775		shp->cpipe[1] = sp->cpipe;
776		shp->coutpipe = sp->coutpipe;
777	}
778	shp->subshare = sp->subshare;
779	shp->comsub = sp->comsub;
780	shp->subdup = sp->subdup;
781#if SHOPT_COSHELL
782	shp->coshell = sp->coshell;
783#endif /* SHOPT_COSHELL */
784	if(shp->subshell)
785		SH_SUBSHELLNOD->nvalue.s = --shp->subshell;
786	subshell = shp->subshell;
787	subshell_data = sp->prev;
788	if(!argsav  ||  argsav->dolrefcnt==argcnt)
789		sh_argfree(shp,argsav,0);
790	if(shp->topfd != buff.topfd)
791		sh_iorestore(shp,buff.topfd|IOSUBSHELL,jmpval);
792	if(sp->sig)
793	{
794		if(sp->prev)
795			sp->prev->sig = sp->sig;
796		else
797		{
798			kill(getpid(),sp->sig);
799			sh_chktrap(shp);
800		}
801	}
802	sh_sigcheck(shp);
803	shp->trapnote = 0;
804	nsig = shp->savesig;
805	shp->savesig = 0;
806	if(nsig>0)
807		kill(getpid(),nsig);
808	if(sp->subpid)
809		job_wait(sp->subpid);
810	if(comsub && iop && sp->pipefd<0)
811		sfseek(iop,(off_t)0,SEEK_SET);
812	if(shp->trapnote)
813		sh_chktrap(shp);
814	if(shp->exitval > SH_EXITSIG)
815	{
816		int sig = shp->exitval&SH_EXITMASK;
817		if(sig==SIGINT || sig== SIGQUIT)
818			kill(getpid(),sig);
819	}
820	if(duped)
821	{
822		((struct checkpt*)shp->jmplist)->mode = SH_JMPERREXIT;
823		shp->toomany = 1;
824		errormsg(SH_DICT,ERROR_system(1),e_redirect);
825	}
826	if(shp->ignsig)
827		kill(getpid(),shp->ignsig);
828	if(jmpval==SH_JMPSUB && shp->lastsig)
829		kill(getpid(),shp->lastsig);
830	if(jmpval && shp->toomany)
831		siglongjmp(*shp->jmplist,jmpval);
832	return(iop);
833}
834