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