Home | History | Annotate | Download | only in src
      1 /*	$OpenBSD: eval.c,v 1.35 2010/03/24 08:27:26 fgsch Exp $	*/
      2 
      3 /*-
      4  * Copyright (c) 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
      5  *	Thorsten Glaser <tg (at) mirbsd.org>
      6  *
      7  * Provided that these terms and disclaimer and all copyright notices
      8  * are retained or reproduced in an accompanying document, permission
      9  * is granted to deal in this work without restriction, including un-
     10  * limited rights to use, publicly perform, distribute, sell, modify,
     11  * merge, give away, or sublicence.
     12  *
     13  * This work is provided "AS IS" and WITHOUT WARRANTY of any kind, to
     14  * the utmost extent permitted by applicable law, neither express nor
     15  * implied; without malicious intent or gross negligence. In no event
     16  * may a licensor, author or contributor be held liable for indirect,
     17  * direct, other damage, loss, or other issues arising in any way out
     18  * of dealing in the work, even if advised of the possibility of such
     19  * damage or existence of a defect, except proven that it results out
     20  * of said person's immediate fault when using the work as intended.
     21  */
     22 
     23 #include "sh.h"
     24 
     25 __RCSID("$MirOS: src/bin/mksh/eval.c,v 1.90 2010/07/17 22:09:33 tg Exp $");
     26 
     27 /*
     28  * string expansion
     29  *
     30  * first pass: quoting, IFS separation, ~, ${}, $() and $(()) substitution.
     31  * second pass: alternation ({,}), filename expansion (*?[]).
     32  */
     33 
     34 /* expansion generator state */
     35 typedef struct Expand {
     36 	/* int type; */			/* see expand() */
     37 	const char *str;		/* string */
     38 	union {
     39 		const char **strv;	/* string[] */
     40 		struct shf *shf;	/* file */
     41 	} u;				/* source */
     42 	struct tbl *var;		/* variable in ${var..} */
     43 	short split;			/* split "$@" / call waitlast $() */
     44 } Expand;
     45 
     46 #define	XBASE		0	/* scanning original */
     47 #define	XSUB		1	/* expanding ${} string */
     48 #define	XARGSEP		2	/* ifs0 between "$*" */
     49 #define	XARG		3	/* expanding $*, $@ */
     50 #define	XCOM		4	/* expanding $() */
     51 #define XNULLSUB	5	/* "$@" when $# is 0 (don't generate word) */
     52 #define XSUBMID		6	/* middle of expanding ${} */
     53 
     54 /* States used for field splitting */
     55 #define IFS_WORD	0	/* word has chars (or quotes) */
     56 #define IFS_WS		1	/* have seen IFS white-space */
     57 #define IFS_NWS		2	/* have seen IFS non-white-space */
     58 
     59 static int varsub(Expand *, const char *, const char *, int *, int *);
     60 static int comsub(Expand *, const char *);
     61 static char *trimsub(char *, char *, int);
     62 static void glob(char *, XPtrV *, int);
     63 static void globit(XString *, char **, char *, XPtrV *, int);
     64 static const char *maybe_expand_tilde(const char *, XString *, char **, int);
     65 static char *tilde(char *);
     66 #ifndef MKSH_NOPWNAM
     67 static char *homedir(char *);
     68 #endif
     69 static void alt_expand(XPtrV *, char *, char *, char *, int);
     70 static size_t utflen(const char *);
     71 static void utfincptr(const char *, mksh_ari_t *);
     72 
     73 /* UTFMODE functions */
     74 static size_t
     75 utflen(const char *s)
     76 {
     77 	size_t n;
     78 
     79 	if (UTFMODE) {
     80 		n = 0;
     81 		while (*s) {
     82 			s += utf_ptradj(s);
     83 			++n;
     84 		}
     85 	} else
     86 		n = strlen(s);
     87 	return (n);
     88 }
     89 
     90 static void
     91 utfincptr(const char *s, mksh_ari_t *lp)
     92 {
     93 	const char *cp = s;
     94 
     95 	while ((*lp)--)
     96 		cp += utf_ptradj(cp);
     97 	*lp = cp - s;
     98 }
     99 
    100 /* compile and expand word */
    101 char *
    102 substitute(const char *cp, int f)
    103 {
    104 	struct source *s, *sold;
    105 
    106 	sold = source;
    107 	s = pushs(SWSTR, ATEMP);
    108 	s->start = s->str = cp;
    109 	source = s;
    110 	if (yylex(ONEWORD) != LWORD)
    111 		internal_errorf("substitute");
    112 	source = sold;
    113 	afree(s, ATEMP);
    114 	return (evalstr(yylval.cp, f));
    115 }
    116 
    117 /*
    118  * expand arg-list
    119  */
    120 char **
    121 eval(const char **ap, int f)
    122 {
    123 	XPtrV w;
    124 
    125 	if (*ap == NULL) {
    126 		union mksh_ccphack vap;
    127 
    128 		vap.ro = ap;
    129 		return (vap.rw);
    130 	}
    131 	XPinit(w, 32);
    132 	XPput(w, NULL);		/* space for shell name */
    133 	while (*ap != NULL)
    134 		expand(*ap++, &w, f);
    135 	XPput(w, NULL);
    136 	return ((char **)XPclose(w) + 1);
    137 }
    138 
    139 /*
    140  * expand string
    141  */
    142 char *
    143 evalstr(const char *cp, int f)
    144 {
    145 	XPtrV w;
    146 	char *dp = null;
    147 
    148 	XPinit(w, 1);
    149 	expand(cp, &w, f);
    150 	if (XPsize(w))
    151 		dp = *XPptrv(w);
    152 	XPfree(w);
    153 	return (dp);
    154 }
    155 
    156 /*
    157  * expand string - return only one component
    158  * used from iosetup to expand redirection files
    159  */
    160 char *
    161 evalonestr(const char *cp, int f)
    162 {
    163 	XPtrV w;
    164 	char *rv;
    165 
    166 	XPinit(w, 1);
    167 	expand(cp, &w, f);
    168 	switch (XPsize(w)) {
    169 	case 0:
    170 		rv = null;
    171 		break;
    172 	case 1:
    173 		rv = (char *) *XPptrv(w);
    174 		break;
    175 	default:
    176 		rv = evalstr(cp, f&~DOGLOB);
    177 		break;
    178 	}
    179 	XPfree(w);
    180 	return (rv);
    181 }
    182 
    183 /* for nested substitution: ${var:=$var2} */
    184 typedef struct SubType {
    185 	struct tbl *var;	/* variable for ${var..} */
    186 	struct SubType *prev;	/* old type */
    187 	struct SubType *next;	/* poped type (to avoid re-allocating) */
    188 	short	stype;		/* [=+-?%#] action after expanded word */
    189 	short	base;		/* begin position of expanded word */
    190 	short	f;		/* saved value of f (DOPAT, etc) */
    191 	uint8_t	quotep;		/* saved value of quote (for ${..[%#]..}) */
    192 	uint8_t	quotew;		/* saved value of quote (for ${..[+-=]..}) */
    193 } SubType;
    194 
    195 void
    196 expand(const char *cp,	/* input word */
    197     XPtrV *wp,		/* output words */
    198     int f)		/* DO* flags */
    199 {
    200 	int c = 0;
    201 	int type;		/* expansion type */
    202 	int quote = 0;		/* quoted */
    203 	XString ds;		/* destination string */
    204 	char *dp;		/* destination */
    205 	const char *sp;		/* source */
    206 	int fdo, word;		/* second pass flags; have word */
    207 	int doblank;		/* field splitting of parameter/command subst */
    208 	Expand x = {		/* expansion variables */
    209 		NULL, { NULL }, NULL, 0
    210 	};
    211 	SubType st_head, *st;
    212 	int newlines = 0; /* For trailing newlines in COMSUB */
    213 	int saw_eq, tilde_ok;
    214 	int make_magic;
    215 	size_t len;
    216 
    217 	if (cp == NULL)
    218 		internal_errorf("expand(NULL)");
    219 	/* for alias, readonly, set, typeset commands */
    220 	if ((f & DOVACHECK) && is_wdvarassign(cp)) {
    221 		f &= ~(DOVACHECK|DOBLANK|DOGLOB|DOTILDE);
    222 		f |= DOASNTILDE;
    223 	}
    224 	if (Flag(FNOGLOB))
    225 		f &= ~DOGLOB;
    226 	if (Flag(FMARKDIRS))
    227 		f |= DOMARKDIRS;
    228 	if (Flag(FBRACEEXPAND) && (f & DOGLOB))
    229 		f |= DOBRACE_;
    230 
    231 	Xinit(ds, dp, 128, ATEMP);	/* init dest. string */
    232 	type = XBASE;
    233 	sp = cp;
    234 	fdo = 0;
    235 	saw_eq = 0;
    236 	tilde_ok = (f & (DOTILDE|DOASNTILDE)) ? 1 : 0; /* must be 1/0 */
    237 	doblank = 0;
    238 	make_magic = 0;
    239 	word = (f&DOBLANK) ? IFS_WS : IFS_WORD;
    240 	/* clang doesn't know OSUBST comes before CSUBST */
    241 	memset(&st_head, 0, sizeof(st_head));
    242 	st = &st_head;
    243 
    244 	while (1) {
    245 		Xcheck(ds, dp);
    246 
    247 		switch (type) {
    248 		case XBASE:	/* original prefixed string */
    249 			c = *sp++;
    250 			switch (c) {
    251 			case EOS:
    252 				c = 0;
    253 				break;
    254 			case CHAR:
    255 				c = *sp++;
    256 				break;
    257 			case QCHAR:
    258 				quote |= 2; /* temporary quote */
    259 				c = *sp++;
    260 				break;
    261 			case OQUOTE:
    262 				word = IFS_WORD;
    263 				tilde_ok = 0;
    264 				quote = 1;
    265 				continue;
    266 			case CQUOTE:
    267 				quote = st->quotew;
    268 				continue;
    269 			case COMSUB:
    270 				tilde_ok = 0;
    271 				if (f & DONTRUNCOMMAND) {
    272 					word = IFS_WORD;
    273 					*dp++ = '$'; *dp++ = '(';
    274 					while (*sp != '\0') {
    275 						Xcheck(ds, dp);
    276 						*dp++ = *sp++;
    277 					}
    278 					*dp++ = ')';
    279 				} else {
    280 					type = comsub(&x, sp);
    281 					if (type == XCOM && (f&DOBLANK))
    282 						doblank++;
    283 					sp = strnul(sp) + 1;
    284 					newlines = 0;
    285 				}
    286 				continue;
    287 			case EXPRSUB:
    288 				word = IFS_WORD;
    289 				tilde_ok = 0;
    290 				if (f & DONTRUNCOMMAND) {
    291 					*dp++ = '$'; *dp++ = '('; *dp++ = '(';
    292 					while (*sp != '\0') {
    293 						Xcheck(ds, dp);
    294 						*dp++ = *sp++;
    295 					}
    296 					*dp++ = ')'; *dp++ = ')';
    297 				} else {
    298 					struct tbl v;
    299 					char *p;
    300 
    301 					v.flag = DEFINED|ISSET|INTEGER;
    302 					v.type = 10; /* not default */
    303 					v.name[0] = '\0';
    304 					v_evaluate(&v, substitute(sp, 0),
    305 					    KSH_UNWIND_ERROR, true);
    306 					sp = strnul(sp) + 1;
    307 					for (p = str_val(&v); *p; ) {
    308 						Xcheck(ds, dp);
    309 						*dp++ = *p++;
    310 					}
    311 				}
    312 				continue;
    313 			case OSUBST: {	/* ${{#}var{:}[=+-?#%]word} */
    314 			/* format is:
    315 			 *	OSUBST [{x] plain-variable-part \0
    316 			 *	    compiled-word-part CSUBST [}x]
    317 			 * This is where all syntax checking gets done...
    318 			 */
    319 				const char *varname = ++sp; /* skip the { or x (}) */
    320 				int stype;
    321 				int slen = 0;
    322 
    323 				sp = cstrchr(sp, '\0') + 1; /* skip variable */
    324 				type = varsub(&x, varname, sp, &stype, &slen);
    325 				if (type < 0) {
    326 					char *beg, *end, *str;
    327 
    328  unwind_substsyn:
    329 					sp = varname - 2; /* restore sp */
    330 					end = (beg = wdcopy(sp, ATEMP)) +
    331 					    (wdscan(sp, CSUBST) - sp);
    332 					/* ({) the } or x is already skipped */
    333 					if (end < wdscan(beg, EOS))
    334 						*end = EOS;
    335 					str = snptreef(NULL, 64, "%S", beg);
    336 					afree(beg, ATEMP);
    337 					errorf("%s: bad substitution", str);
    338 				}
    339 				if (f & DOBLANK)
    340 					doblank++;
    341 				tilde_ok = 0;
    342 				if (type == XBASE) {	/* expand? */
    343 					if (!st->next) {
    344 						SubType *newst;
    345 
    346 						newst = alloc(sizeof(SubType), ATEMP);
    347 						newst->next = NULL;
    348 						newst->prev = st;
    349 						st->next = newst;
    350 					}
    351 					st = st->next;
    352 					st->stype = stype;
    353 					st->base = Xsavepos(ds, dp);
    354 					st->f = f;
    355 					st->var = x.var;
    356 					st->quotew = st->quotep = quote;
    357 					/* skip qualifier(s) */
    358 					if (stype)
    359 						sp += slen;
    360 					switch (stype & 0x7f) {
    361 					case '0': {
    362 						char *beg, *mid, *end, *stg;
    363 						mksh_ari_t from = 0, num = -1, flen, finc = 0;
    364 
    365 						beg = wdcopy(sp, ATEMP);
    366 						mid = beg + (wdscan(sp, ADELIM) - sp);
    367 						stg = beg + (wdscan(sp, CSUBST) - sp);
    368 						if (mid >= stg)
    369 							goto unwind_substsyn;
    370 						mid[-2] = EOS;
    371 						if (mid[-1] == /*{*/'}') {
    372 							sp += mid - beg - 1;
    373 							end = NULL;
    374 						} else {
    375 							end = mid +
    376 							    (wdscan(mid, ADELIM) - mid);
    377 							if (end >= stg)
    378 								goto unwind_substsyn;
    379 							end[-2] = EOS;
    380 							sp += end - beg - 1;
    381 						}
    382 						evaluate(substitute(stg = wdstrip(beg, false, false), 0),
    383 						    &from, KSH_UNWIND_ERROR, true);
    384 						afree(stg, ATEMP);
    385 						if (end) {
    386 							evaluate(substitute(stg = wdstrip(mid, false, false), 0),
    387 							    &num, KSH_UNWIND_ERROR, true);
    388 							afree(stg, ATEMP);
    389 						}
    390 						afree(beg, ATEMP);
    391 						beg = str_val(st->var);
    392 						flen = utflen(beg);
    393 						if (from < 0) {
    394 							if (-from < flen)
    395 								finc = flen + from;
    396 						} else
    397 							finc = from < flen ? from : flen;
    398 						if (UTFMODE)
    399 							utfincptr(beg, &finc);
    400 						beg += finc;
    401 						flen = utflen(beg);
    402 						if (num < 0 || num > flen)
    403 							num = flen;
    404 						if (UTFMODE)
    405 							utfincptr(beg, &num);
    406 						strndupx(x.str, beg, num, ATEMP);
    407 						goto do_CSUBST;
    408 					}
    409 					case '/': {
    410 						char *s, *p, *d, *sbeg, *end;
    411 						char *pat, *rrep;
    412 						char *tpat0, *tpat1, *tpat2;
    413 
    414 						s = wdcopy(sp, ATEMP);
    415 						p = s + (wdscan(sp, ADELIM) - sp);
    416 						d = s + (wdscan(sp, CSUBST) - sp);
    417 						if (p >= d)
    418 							goto unwind_substsyn;
    419 						p[-2] = EOS;
    420 						if (p[-1] == /*{*/'}')
    421 							d = NULL;
    422 						else
    423 							d[-2] = EOS;
    424 						sp += (d ? d : p) - s - 1;
    425 						tpat0 = wdstrip(s, true, true);
    426 						pat = substitute(tpat0, 0);
    427 						if (d) {
    428 							d = wdstrip(p, true, false);
    429 							rrep = substitute(d, 0);
    430 							afree(d, ATEMP);
    431 						} else
    432 							rrep = null;
    433 						afree(s, ATEMP);
    434 						s = d = pat;
    435 						while (*s)
    436 							if (*s != '\\' ||
    437 							    s[1] == '%' ||
    438 							    s[1] == '#' ||
    439 							    s[1] == '\0' ||
    440 				/* XXX really? */	    s[1] == '\\' ||
    441 							    s[1] == '/')
    442 								*d++ = *s++;
    443 							else
    444 								s++;
    445 						*d = '\0';
    446 						afree(tpat0, ATEMP);
    447 
    448 						/* reject empty pattern */
    449 						if (!*pat || gmatchx("", pat, false))
    450 							goto no_repl;
    451 
    452 						/* prepare string on which to work */
    453 						strdupx(s, str_val(st->var), ATEMP);
    454 						sbeg = s;
    455 
    456 						/* first see if we have any match at all */
    457 						tpat0 = pat;
    458 						if (*pat == '#') {
    459 							/* anchor at the beginning */
    460 							tpat1 = shf_smprintf("%s%c*", ++tpat0, MAGIC);
    461 							tpat2 = tpat1;
    462 						} else if (*pat == '%') {
    463 							/* anchor at the end */
    464 							tpat1 = shf_smprintf("%c*%s", MAGIC, ++tpat0);
    465 							tpat2 = tpat0;
    466 						} else {
    467 							/* float */
    468 							tpat1 = shf_smprintf("%c*%s%c*", MAGIC, pat, MAGIC);
    469 							tpat2 = tpat1 + 2;
    470 						}
    471  again_repl:
    472 						/* this would not be necessary if gmatchx would return
    473 						 * the start and end values of a match found, like re*
    474 						 */
    475 						if (!gmatchx(sbeg, tpat1, false))
    476 							goto end_repl;
    477 						end = strnul(s);
    478 						/* now anchor the beginning of the match */
    479 						if (*pat != '#')
    480 							while (sbeg <= end) {
    481 								if (gmatchx(sbeg, tpat2, false))
    482 									break;
    483 								else
    484 									sbeg++;
    485 							}
    486 						/* now anchor the end of the match */
    487 						p = end;
    488 						if (*pat != '%')
    489 							while (p >= sbeg) {
    490 								bool gotmatch;
    491 
    492 								c = *p; *p = '\0';
    493 								gotmatch = gmatchx(sbeg, tpat0, false);
    494 								*p = c;
    495 								if (gotmatch)
    496 									break;
    497 								p--;
    498 							}
    499 						strndupx(end, s, sbeg - s, ATEMP);
    500 						d = shf_smprintf("%s%s%s", end, rrep, p);
    501 						afree(end, ATEMP);
    502 						sbeg = d + (sbeg - s) + strlen(rrep);
    503 						afree(s, ATEMP);
    504 						s = d;
    505 						if (stype & 0x80)
    506 							goto again_repl;
    507  end_repl:
    508 						afree(tpat1, ATEMP);
    509 						x.str = s;
    510  no_repl:
    511 						afree(pat, ATEMP);
    512 						if (rrep != null)
    513 							afree(rrep, ATEMP);
    514 						goto do_CSUBST;
    515 					}
    516 					case '#':
    517 					case '%':
    518 						/* ! DOBLANK,DOBRACE_,DOTILDE */
    519 						f = DOPAT | (f&DONTRUNCOMMAND) |
    520 						    DOTEMP_;
    521 						st->quotew = quote = 0;
    522 						/* Prepend open pattern (so |
    523 						 * in a trim will work as
    524 						 * expected)
    525 						 */
    526 						*dp++ = MAGIC;
    527 						*dp++ = (char)('@' | 0x80);
    528 						break;
    529 					case '=':
    530 						/* Enabling tilde expansion
    531 						 * after :s here is
    532 						 * non-standard ksh, but is
    533 						 * consistent with rules for
    534 						 * other assignments. Not
    535 						 * sure what POSIX thinks of
    536 						 * this.
    537 						 * Not doing tilde expansion
    538 						 * for integer variables is a
    539 						 * non-POSIX thing - makes
    540 						 * sense though, since ~ is
    541 						 * a arithmetic operator.
    542 						 */
    543 						if (!(x.var->flag & INTEGER))
    544 							f |= DOASNTILDE|DOTILDE;
    545 						f |= DOTEMP_;
    546 						/* These will be done after the
    547 						 * value has been assigned.
    548 						 */
    549 						f &= ~(DOBLANK|DOGLOB|DOBRACE_);
    550 						tilde_ok = 1;
    551 						break;
    552 					case '?':
    553 						f &= ~DOBLANK;
    554 						f |= DOTEMP_;
    555 						/* FALLTHROUGH */
    556 					default:
    557 						/* Enable tilde expansion */
    558 						tilde_ok = 1;
    559 						f |= DOTILDE;
    560 					}
    561 				} else
    562 					/* skip word */
    563 					sp += wdscan(sp, CSUBST) - sp;
    564 				continue;
    565 			}
    566 			case CSUBST: /* only get here if expanding word */
    567  do_CSUBST:
    568 				sp++; /* ({) skip the } or x */
    569 				tilde_ok = 0;	/* in case of ${unset:-} */
    570 				*dp = '\0';
    571 				quote = st->quotep;
    572 				f = st->f;
    573 				if (f&DOBLANK)
    574 					doblank--;
    575 				switch (st->stype&0x7f) {
    576 				case '#':
    577 				case '%':
    578 					/* Append end-pattern */
    579 					*dp++ = MAGIC; *dp++ = ')'; *dp = '\0';
    580 					dp = Xrestpos(ds, dp, st->base);
    581 					/* Must use st->var since calling
    582 					 * global would break things
    583 					 * like x[i+=1].
    584 					 */
    585 					x.str = trimsub(str_val(st->var),
    586 						dp, st->stype);
    587 					if (x.str[0] != '\0' || st->quotep)
    588 						type = XSUB;
    589 					else
    590 						type = XNULLSUB;
    591 					if (f&DOBLANK)
    592 						doblank++;
    593 					st = st->prev;
    594 					continue;
    595 				case '=':
    596 					/* Restore our position and substitute
    597 					 * the value of st->var (may not be
    598 					 * the assigned value in the presence
    599 					 * of integer/right-adj/etc attributes).
    600 					 */
    601 					dp = Xrestpos(ds, dp, st->base);
    602 					/* Must use st->var since calling
    603 					 * global would cause with things
    604 					 * like x[i+=1] to be evaluated twice.
    605 					 */
    606 					/* Note: not exported by FEXPORT
    607 					 * in AT&T ksh.
    608 					 */
    609 					/* XXX POSIX says readonly is only
    610 					 * fatal for special builtins (setstr
    611 					 * does readonly check).
    612 					 */
    613 					len = strlen(dp) + 1;
    614 					setstr(st->var,
    615 					    debunk(alloc(len, ATEMP),
    616 					    dp, len), KSH_UNWIND_ERROR);
    617 					x.str = str_val(st->var);
    618 					type = XSUB;
    619 					if (f&DOBLANK)
    620 						doblank++;
    621 					st = st->prev;
    622 					continue;
    623 				case '?': {
    624 					char *s = Xrestpos(ds, dp, st->base);
    625 
    626 					errorf("%s: %s", st->var->name,
    627 					    dp == s ?
    628 					    "parameter null or not set" :
    629 					    (debunk(s, s, strlen(s) + 1), s));
    630 				}
    631 				case '0':
    632 				case '/':
    633 					dp = Xrestpos(ds, dp, st->base);
    634 					type = XSUB;
    635 					if (f&DOBLANK)
    636 						doblank++;
    637 					st = st->prev;
    638 					continue;
    639 				}
    640 				st = st->prev;
    641 				type = XBASE;
    642 				continue;
    643 
    644 			case OPAT: /* open pattern: *(foo|bar) */
    645 				/* Next char is the type of pattern */
    646 				make_magic = 1;
    647 				c = *sp++ + 0x80;
    648 				break;
    649 
    650 			case SPAT: /* pattern separator (|) */
    651 				make_magic = 1;
    652 				c = '|';
    653 				break;
    654 
    655 			case CPAT: /* close pattern */
    656 				make_magic = 1;
    657 				c = /*(*/ ')';
    658 				break;
    659 			}
    660 			break;
    661 
    662 		case XNULLSUB:
    663 			/* Special case for "$@" (and "${foo[@]}") - no
    664 			 * word is generated if $# is 0 (unless there is
    665 			 * other stuff inside the quotes).
    666 			 */
    667 			type = XBASE;
    668 			if (f&DOBLANK) {
    669 				doblank--;
    670 				/* not really correct: x=; "$x$@" should
    671 				 * generate a null argument and
    672 				 * set A; "${@:+}" shouldn't.
    673 				 */
    674 				if (dp == Xstring(ds, dp))
    675 					word = IFS_WS;
    676 			}
    677 			continue;
    678 
    679 		case XSUB:
    680 		case XSUBMID:
    681 			if ((c = *x.str++) == 0) {
    682 				type = XBASE;
    683 				if (f&DOBLANK)
    684 					doblank--;
    685 				continue;
    686 			}
    687 			break;
    688 
    689 		case XARGSEP:
    690 			type = XARG;
    691 			quote = 1;
    692 		case XARG:
    693 			if ((c = *x.str++) == '\0') {
    694 				/* force null words to be created so
    695 				 * set -- '' 2 ''; foo "$@" will do
    696 				 * the right thing
    697 				 */
    698 				if (quote && x.split)
    699 					word = IFS_WORD;
    700 				if ((x.str = *x.u.strv++) == NULL) {
    701 					type = XBASE;
    702 					if (f&DOBLANK)
    703 						doblank--;
    704 					continue;
    705 				}
    706 				c = ifs0;
    707 				if (c == 0) {
    708 					if (quote && !x.split)
    709 						continue;
    710 					c = ' ';
    711 				}
    712 				if (quote && x.split) {
    713 					/* terminate word for "$@" */
    714 					type = XARGSEP;
    715 					quote = 0;
    716 				}
    717 			}
    718 			break;
    719 
    720 		case XCOM:
    721 			if (newlines) {		/* Spit out saved NLs */
    722 				c = '\n';
    723 				--newlines;
    724 			} else {
    725 				while ((c = shf_getc(x.u.shf)) == 0 || c == '\n')
    726 					if (c == '\n')
    727 						/* Save newlines */
    728 						newlines++;
    729 				if (newlines && c != EOF) {
    730 					shf_ungetc(c, x.u.shf);
    731 					c = '\n';
    732 					--newlines;
    733 				}
    734 			}
    735 			if (c == EOF) {
    736 				newlines = 0;
    737 				shf_close(x.u.shf);
    738 				if (x.split)
    739 					subst_exstat = waitlast();
    740 				type = XBASE;
    741 				if (f&DOBLANK)
    742 					doblank--;
    743 				continue;
    744 			}
    745 			break;
    746 		}
    747 
    748 		/* check for end of word or IFS separation */
    749 		if (c == 0 || (!quote && (f & DOBLANK) && doblank &&
    750 		    !make_magic && ctype(c, C_IFS))) {
    751 			/* How words are broken up:
    752 			 *			|	value of c
    753 			 *	word		|	ws	nws	0
    754 			 *	-----------------------------------
    755 			 *	IFS_WORD		w/WS	w/NWS	w
    756 			 *	IFS_WS			-/WS	w/NWS	-
    757 			 *	IFS_NWS			-/NWS	w/NWS	w
    758 			 * (w means generate a word)
    759 			 * Note that IFS_NWS/0 generates a word (AT&T ksh
    760 			 * doesn't do this, but POSIX does).
    761 			 */
    762 			if (word == IFS_WORD ||
    763 			    (!ctype(c, C_IFSWS) && c && word == IFS_NWS)) {
    764 				char *p;
    765 
    766 				*dp++ = '\0';
    767 				p = Xclose(ds, dp);
    768 				if (fdo & DOBRACE_)
    769 					/* also does globbing */
    770 					alt_expand(wp, p, p,
    771 					    p + Xlength(ds, (dp - 1)),
    772 					    fdo | (f & DOMARKDIRS));
    773 				else if (fdo & DOGLOB)
    774 					glob(p, wp, f & DOMARKDIRS);
    775 				else if ((f & DOPAT) || !(fdo & DOMAGIC_))
    776 					XPput(*wp, p);
    777 				else
    778 					XPput(*wp, debunk(p, p, strlen(p) + 1));
    779 				fdo = 0;
    780 				saw_eq = 0;
    781 				tilde_ok = (f & (DOTILDE|DOASNTILDE)) ? 1 : 0;
    782 				if (c != 0)
    783 					Xinit(ds, dp, 128, ATEMP);
    784 			}
    785 			if (c == 0)
    786 				return;
    787 			if (word != IFS_NWS)
    788 				word = ctype(c, C_IFSWS) ? IFS_WS : IFS_NWS;
    789 		} else {
    790 			if (type == XSUB) {
    791 				if (word == IFS_NWS &&
    792 				    Xlength(ds, dp) == 0) {
    793 					char *p;
    794 
    795 					*(p = alloc(1, ATEMP)) = '\0';
    796 					XPput(*wp, p);
    797 				}
    798 				type = XSUBMID;
    799 			}
    800 
    801 			/* age tilde_ok info - ~ code tests second bit */
    802 			tilde_ok <<= 1;
    803 			/* mark any special second pass chars */
    804 			if (!quote)
    805 				switch (c) {
    806 				case '[':
    807 				case NOT:
    808 				case '-':
    809 				case ']':
    810 					/* For character classes - doesn't hurt
    811 					 * to have magic !,-,]s outside of
    812 					 * [...] expressions.
    813 					 */
    814 					if (f & (DOPAT | DOGLOB)) {
    815 						fdo |= DOMAGIC_;
    816 						if (c == '[')
    817 							fdo |= f & DOGLOB;
    818 						*dp++ = MAGIC;
    819 					}
    820 					break;
    821 				case '*':
    822 				case '?':
    823 					if (f & (DOPAT | DOGLOB)) {
    824 						fdo |= DOMAGIC_ | (f & DOGLOB);
    825 						*dp++ = MAGIC;
    826 					}
    827 					break;
    828 				case OBRACE:
    829 				case ',':
    830 				case CBRACE:
    831 					if ((f & DOBRACE_) && (c == OBRACE ||
    832 					    (fdo & DOBRACE_))) {
    833 						fdo |= DOBRACE_|DOMAGIC_;
    834 						*dp++ = MAGIC;
    835 					}
    836 					break;
    837 				case '=':
    838 					/* Note first unquoted = for ~ */
    839 					if (!(f & DOTEMP_) && !saw_eq &&
    840 					    (Flag(FBRACEEXPAND) ||
    841 					    (f & DOASNTILDE))) {
    842 						saw_eq = 1;
    843 						tilde_ok = 1;
    844 					}
    845 					break;
    846 				case ':': /* : */
    847 					/* Note unquoted : for ~ */
    848 					if (!(f & DOTEMP_) && (f & DOASNTILDE))
    849 						tilde_ok = 1;
    850 					break;
    851 				case '~':
    852 					/* tilde_ok is reset whenever
    853 					 * any of ' " $( $(( ${ } are seen.
    854 					 * Note that tilde_ok must be preserved
    855 					 * through the sequence ${A=a=}~
    856 					 */
    857 					if (type == XBASE &&
    858 					    (f & (DOTILDE|DOASNTILDE)) &&
    859 					    (tilde_ok & 2)) {
    860 						const char *p;
    861 						char *dp_x;
    862 
    863 						dp_x = dp;
    864 						p = maybe_expand_tilde(sp,
    865 						    &ds, &dp_x,
    866 						    f & DOASNTILDE);
    867 						if (p) {
    868 							if (dp != dp_x)
    869 								word = IFS_WORD;
    870 							dp = dp_x;
    871 							sp = p;
    872 							continue;
    873 						}
    874 					}
    875 					break;
    876 				}
    877 			else
    878 				quote &= ~2; /* undo temporary */
    879 
    880 			if (make_magic) {
    881 				make_magic = 0;
    882 				fdo |= DOMAGIC_ | (f & DOGLOB);
    883 				*dp++ = MAGIC;
    884 			} else if (ISMAGIC(c)) {
    885 				fdo |= DOMAGIC_;
    886 				*dp++ = MAGIC;
    887 			}
    888 			*dp++ = c; /* save output char */
    889 			word = IFS_WORD;
    890 		}
    891 	}
    892 }
    893 
    894 /*
    895  * Prepare to generate the string returned by ${} substitution.
    896  */
    897 static int
    898 varsub(Expand *xp, const char *sp, const char *word,
    899     int *stypep,	/* becomes qualifier type */
    900     int *slenp)		/* " " len (=, :=, etc.) valid iff *stypep != 0 */
    901 {
    902 	int c;
    903 	int state;	/* next state: XBASE, XARG, XSUB, XNULLSUB */
    904 	int stype;	/* substitution type */
    905 	int slen;
    906 	const char *p;
    907 	struct tbl *vp;
    908 	bool zero_ok = false;
    909 
    910 	if ((stype = sp[0]) == '\0')	/* Bad variable name */
    911 		return (-1);
    912 
    913 	xp->var = NULL;
    914 
    915 	/*-
    916 	 * ${#var}, string length (-U: characters, +U: octets) or array size
    917 	 * ${%var}, string width (-U: screen columns, +U: octets)
    918 	 */
    919 	c = sp[1];
    920 	if (stype == '%' && c == '\0')
    921 		return (-1);
    922 	if ((stype == '#' || stype == '%') && c != '\0') {
    923 		/* Can't have any modifiers for ${#...} or ${%...} */
    924 		if (*word != CSUBST)
    925 			return (-1);
    926 		sp++;
    927 		/* Check for size of array */
    928 		if ((p = cstrchr(sp, '[')) && (p[1] == '*' || p[1] == '@') &&
    929 		    p[2] == ']') {
    930 			int n = 0;
    931 
    932 			if (stype != '#')
    933 				return (-1);
    934 			vp = global(arrayname(sp));
    935 			if (vp->flag & (ISSET|ARRAY))
    936 				zero_ok = true;
    937 			for (; vp; vp = vp->u.array)
    938 				if (vp->flag & ISSET)
    939 					n++;
    940 			c = n;
    941 		} else if (c == '*' || c == '@') {
    942 			if (stype != '#')
    943 				return (-1);
    944 			c = e->loc->argc;
    945 		} else {
    946 			p = str_val(global(sp));
    947 			zero_ok = p != null;
    948 			if (stype == '#')
    949 				c = utflen(p);
    950 			else {
    951 				/* partial utf_mbswidth reimplementation */
    952 				const char *s = p;
    953 				unsigned int wc;
    954 				size_t len;
    955 				int cw;
    956 
    957 				c = 0;
    958 				while (*s) {
    959 					if (!UTFMODE || (len = utf_mbtowc(&wc,
    960 					    s)) == (size_t)-1)
    961 						/* not UTFMODE or not UTF-8 */
    962 						wc = (unsigned char)(*s++);
    963 					else
    964 						/* UTFMODE and UTF-8 */
    965 						s += len;
    966 					/* wc == char or wchar at s++ */
    967 					if ((cw = utf_wcwidth(wc)) == -1) {
    968 						/* 646, 8859-1, 10646 C0/C1 */
    969 						c = -1;
    970 						break;
    971 					}
    972 					c += cw;
    973 				}
    974 			}
    975 		}
    976 		if (Flag(FNOUNSET) && c == 0 && !zero_ok)
    977 			errorf("%s: parameter not set", sp);
    978 		*stypep = 0; /* unqualified variable/string substitution */
    979 		xp->str = shf_smprintf("%d", c);
    980 		return (XSUB);
    981 	}
    982 
    983 	/* Check for qualifiers in word part */
    984 	stype = 0;
    985 	c = word[slen = 0] == CHAR ? word[1] : 0;
    986 	if (c == ':') {
    987 		slen += 2;
    988 		stype = 0x80;
    989 		c = word[slen + 0] == CHAR ? word[slen + 1] : 0;
    990 	}
    991 	if (!stype && c == '/') {
    992 		slen += 2;
    993 		stype = c;
    994 		if (word[slen] == ADELIM) {
    995 			slen += 2;
    996 			stype |= 0x80;
    997 		}
    998 	} else if (stype == 0x80 && (c == ' ' || c == '0')) {
    999 		stype |= '0';
   1000 	} else if (ctype(c, C_SUBOP1)) {
   1001 		slen += 2;
   1002 		stype |= c;
   1003 	} else if (ctype(c, C_SUBOP2)) { /* Note: ksh88 allows :%, :%%, etc */
   1004 		slen += 2;
   1005 		stype = c;
   1006 		if (word[slen + 0] == CHAR && c == word[slen + 1]) {
   1007 			stype |= 0x80;
   1008 			slen += 2;
   1009 		}
   1010 	} else if (stype)	/* : is not ok */
   1011 		return (-1);
   1012 	if (!stype && *word != CSUBST)
   1013 		return (-1);
   1014 	*stypep = stype;
   1015 	*slenp = slen;
   1016 
   1017 	c = sp[0];
   1018 	if (c == '*' || c == '@') {
   1019 		switch (stype & 0x7f) {
   1020 		case '=':	/* can't assign to a vector */
   1021 		case '%':	/* can't trim a vector (yet) */
   1022 		case '#':
   1023 		case '0':
   1024 		case '/':
   1025 			return (-1);
   1026 		}
   1027 		if (e->loc->argc == 0) {
   1028 			xp->str = null;
   1029 			xp->var = global(sp);
   1030 			state = c == '@' ? XNULLSUB : XSUB;
   1031 		} else {
   1032 			xp->u.strv = (const char **)e->loc->argv + 1;
   1033 			xp->str = *xp->u.strv++;
   1034 			xp->split = c == '@'; /* $@ */
   1035 			state = XARG;
   1036 		}
   1037 		zero_ok = true;	/* POSIX 2009? */
   1038 	} else {
   1039 		if ((p = cstrchr(sp, '[')) && (p[1] == '*' || p[1] == '@') &&
   1040 		    p[2] == ']') {
   1041 			XPtrV wv;
   1042 
   1043 			switch (stype & 0x7f) {
   1044 			case '=':	/* can't assign to a vector */
   1045 			case '%':	/* can't trim a vector (yet) */
   1046 			case '#':
   1047 			case '?':
   1048 			case '0':
   1049 			case '/':
   1050 				return (-1);
   1051 			}
   1052 			XPinit(wv, 32);
   1053 			if ((c = sp[0]) == '!')
   1054 				++sp;
   1055 			vp = global(arrayname(sp));
   1056 			for (; vp; vp = vp->u.array) {
   1057 				if (!(vp->flag&ISSET))
   1058 					continue;
   1059 				XPput(wv, c == '!' ? shf_smprintf("%lu",
   1060 				    arrayindex(vp)) :
   1061 				    str_val(vp));
   1062 			}
   1063 			if (XPsize(wv) == 0) {
   1064 				xp->str = null;
   1065 				state = p[1] == '@' ? XNULLSUB : XSUB;
   1066 				XPfree(wv);
   1067 			} else {
   1068 				XPput(wv, 0);
   1069 				xp->u.strv = (const char **)XPptrv(wv);
   1070 				xp->str = *xp->u.strv++;
   1071 				xp->split = p[1] == '@'; /* ${foo[@]} */
   1072 				state = XARG;
   1073 			}
   1074 		} else {
   1075 			/* Can't assign things like $! or $1 */
   1076 			if ((stype & 0x7f) == '=' &&
   1077 			    ctype(*sp, C_VAR1 | C_DIGIT))
   1078 				return (-1);
   1079 			if (*sp == '!' && sp[1]) {
   1080 				++sp;
   1081 				xp->var = global(sp);
   1082 				if (cstrchr(sp, '[')) {
   1083 					if (xp->var->flag & ISSET)
   1084 						xp->str = shf_smprintf("%lu",
   1085 						    arrayindex(xp->var));
   1086 					else
   1087 						xp->str = null;
   1088 				} else if (xp->var->flag & ISSET)
   1089 					xp->str = xp->var->name;
   1090 				else
   1091 					xp->str = "0";	/* ksh93 compat */
   1092 			} else {
   1093 				xp->var = global(sp);
   1094 				xp->str = str_val(xp->var);
   1095 			}
   1096 			state = XSUB;
   1097 		}
   1098 	}
   1099 
   1100 	c = stype&0x7f;
   1101 	/* test the compiler's code generator */
   1102 	if (ctype(c, C_SUBOP2) || stype == (0x80 | '0') || c == '/' ||
   1103 	    (((stype&0x80) ? *xp->str=='\0' : xp->str==null) ? /* undef? */
   1104 	    c == '=' || c == '-' || c == '?' : c == '+'))
   1105 		state = XBASE;	/* expand word instead of variable value */
   1106 	if (Flag(FNOUNSET) && xp->str == null && !zero_ok &&
   1107 	    (ctype(c, C_SUBOP2) || (state != XBASE && c != '+')))
   1108 		errorf("%s: parameter not set", sp);
   1109 	return (state);
   1110 }
   1111 
   1112 /*
   1113  * Run the command in $(...) and read its output.
   1114  */
   1115 static int
   1116 comsub(Expand *xp, const char *cp)
   1117 {
   1118 	Source *s, *sold;
   1119 	struct op *t;
   1120 	struct shf *shf;
   1121 
   1122 	s = pushs(SSTRING, ATEMP);
   1123 	s->start = s->str = cp;
   1124 	sold = source;
   1125 	t = compile(s);
   1126 	afree(s, ATEMP);
   1127 	source = sold;
   1128 
   1129 	if (t == NULL)
   1130 		return (XBASE);
   1131 
   1132 	if (t != NULL && t->type == TCOM && /* $(<file) */
   1133 	    *t->args == NULL && *t->vars == NULL && t->ioact != NULL) {
   1134 		struct ioword *io = *t->ioact;
   1135 		char *name;
   1136 
   1137 		if ((io->flag&IOTYPE) != IOREAD)
   1138 			errorf("funny $() command: %s",
   1139 			    snptreef(NULL, 32, "%R", io));
   1140 		shf = shf_open(name = evalstr(io->name, DOTILDE), O_RDONLY, 0,
   1141 			SHF_MAPHI|SHF_CLEXEC);
   1142 		if (shf == NULL)
   1143 			errorf("%s: cannot open $() input", name);
   1144 		xp->split = 0;	/* no waitlast() */
   1145 	} else {
   1146 		int ofd1, pv[2];
   1147 		openpipe(pv);
   1148 		shf = shf_fdopen(pv[0], SHF_RD, NULL);
   1149 		ofd1 = savefd(1);
   1150 		if (pv[1] != 1) {
   1151 			ksh_dup2(pv[1], 1, false);
   1152 			close(pv[1]);
   1153 		}
   1154 		execute(t, XFORK|XXCOM|XPIPEO, NULL);
   1155 		restfd(1, ofd1);
   1156 		startlast();
   1157 		xp->split = 1;	/* waitlast() */
   1158 	}
   1159 
   1160 	xp->u.shf = shf;
   1161 	return (XCOM);
   1162 }
   1163 
   1164 /*
   1165  * perform #pattern and %pattern substitution in ${}
   1166  */
   1167 
   1168 static char *
   1169 trimsub(char *str, char *pat, int how)
   1170 {
   1171 	char *end = strnul(str);
   1172 	char *p, c;
   1173 
   1174 	switch (how & 0xFF) {
   1175 	case '#':		/* shortest at beginning */
   1176 		for (p = str; p <= end; p += utf_ptradj(p)) {
   1177 			c = *p; *p = '\0';
   1178 			if (gmatchx(str, pat, false)) {
   1179 				*p = c;
   1180 				return (p);
   1181 			}
   1182 			*p = c;
   1183 		}
   1184 		break;
   1185 	case '#'|0x80:		/* longest match at beginning */
   1186 		for (p = end; p >= str; p--) {
   1187 			c = *p; *p = '\0';
   1188 			if (gmatchx(str, pat, false)) {
   1189 				*p = c;
   1190 				return (p);
   1191 			}
   1192 			*p = c;
   1193 		}
   1194 		break;
   1195 	case '%':		/* shortest match at end */
   1196 		p = end;
   1197 		while (p >= str) {
   1198 			if (gmatchx(p, pat, false))
   1199 				goto trimsub_match;
   1200 			if (UTFMODE) {
   1201 				char *op = p;
   1202 				while ((p-- > str) && ((*p & 0xC0) == 0x80))
   1203 					;
   1204 				if ((p < str) || (p + utf_ptradj(p) != op))
   1205 					p = op - 1;
   1206 			} else
   1207 				--p;
   1208 		}
   1209 		break;
   1210 	case '%'|0x80:		/* longest match at end */
   1211 		for (p = str; p <= end; p++)
   1212 			if (gmatchx(p, pat, false)) {
   1213  trimsub_match:
   1214 				strndupx(end, str, p - str, ATEMP);
   1215 				return (end);
   1216 			}
   1217 		break;
   1218 	}
   1219 
   1220 	return (str);		/* no match, return string */
   1221 }
   1222 
   1223 /*
   1224  * glob
   1225  * Name derived from V6's /etc/glob, the program that expanded filenames.
   1226  */
   1227 
   1228 /* XXX cp not const 'cause slashes are temporarily replaced with NULs... */
   1229 static void
   1230 glob(char *cp, XPtrV *wp, int markdirs)
   1231 {
   1232 	int oldsize = XPsize(*wp);
   1233 
   1234 	if (glob_str(cp, wp, markdirs) == 0)
   1235 		XPput(*wp, debunk(cp, cp, strlen(cp) + 1));
   1236 	else
   1237 		qsort(XPptrv(*wp) + oldsize, XPsize(*wp) - oldsize,
   1238 		    sizeof(void *), xstrcmp);
   1239 }
   1240 
   1241 #define GF_NONE		0
   1242 #define GF_EXCHECK	BIT(0)		/* do existence check on file */
   1243 #define GF_GLOBBED	BIT(1)		/* some globbing has been done */
   1244 #define GF_MARKDIR	BIT(2)		/* add trailing / to directories */
   1245 
   1246 /* Apply file globbing to cp and store the matching files in wp. Returns
   1247  * the number of matches found.
   1248  */
   1249 int
   1250 glob_str(char *cp, XPtrV *wp, int markdirs)
   1251 {
   1252 	int oldsize = XPsize(*wp);
   1253 	XString xs;
   1254 	char *xp;
   1255 
   1256 	Xinit(xs, xp, 256, ATEMP);
   1257 	globit(&xs, &xp, cp, wp, markdirs ? GF_MARKDIR : GF_NONE);
   1258 	Xfree(xs, xp);
   1259 
   1260 	return (XPsize(*wp) - oldsize);
   1261 }
   1262 
   1263 static void
   1264 globit(XString *xs,	/* dest string */
   1265     char **xpp,		/* ptr to dest end */
   1266     char *sp,		/* source path */
   1267     XPtrV *wp,		/* output list */
   1268     int check)		/* GF_* flags */
   1269 {
   1270 	char *np;		/* next source component */
   1271 	char *xp = *xpp;
   1272 	char *se;
   1273 	char odirsep;
   1274 
   1275 	/* This to allow long expansions to be interrupted */
   1276 	intrcheck();
   1277 
   1278 	if (sp == NULL) {	/* end of source path */
   1279 		/* We only need to check if the file exists if a pattern
   1280 		 * is followed by a non-pattern (eg, foo*x/bar; no check
   1281 		 * is needed for foo* since the match must exist) or if
   1282 		 * any patterns were expanded and the markdirs option is set.
   1283 		 * Symlinks make things a bit tricky...
   1284 		 */
   1285 		if ((check & GF_EXCHECK) ||
   1286 		    ((check & GF_MARKDIR) && (check & GF_GLOBBED))) {
   1287 #define stat_check()	(stat_done ? stat_done : \
   1288 			    (stat_done = stat(Xstring(*xs, xp), &statb) < 0 \
   1289 				? -1 : 1))
   1290 			struct stat lstatb, statb;
   1291 			int stat_done = 0;	 /* -1: failed, 1 ok */
   1292 
   1293 			if (lstat(Xstring(*xs, xp), &lstatb) < 0)
   1294 				return;
   1295 			/* special case for systems which strip trailing
   1296 			 * slashes from regular files (eg, /etc/passwd/).
   1297 			 * SunOS 4.1.3 does this...
   1298 			 */
   1299 			if ((check & GF_EXCHECK) && xp > Xstring(*xs, xp) &&
   1300 			    xp[-1] == '/' && !S_ISDIR(lstatb.st_mode) &&
   1301 			    (!S_ISLNK(lstatb.st_mode) ||
   1302 			    stat_check() < 0 || !S_ISDIR(statb.st_mode)))
   1303 				return;
   1304 			/* Possibly tack on a trailing / if there isn't already
   1305 			 * one and if the file is a directory or a symlink to a
   1306 			 * directory
   1307 			 */
   1308 			if (((check & GF_MARKDIR) && (check & GF_GLOBBED)) &&
   1309 			    xp > Xstring(*xs, xp) && xp[-1] != '/' &&
   1310 			    (S_ISDIR(lstatb.st_mode) ||
   1311 			    (S_ISLNK(lstatb.st_mode) && stat_check() > 0 &&
   1312 			    S_ISDIR(statb.st_mode)))) {
   1313 				*xp++ = '/';
   1314 				*xp = '\0';
   1315 			}
   1316 		}
   1317 		strndupx(np, Xstring(*xs, xp), Xlength(*xs, xp), ATEMP);
   1318 		XPput(*wp, np);
   1319 		return;
   1320 	}
   1321 
   1322 	if (xp > Xstring(*xs, xp))
   1323 		*xp++ = '/';
   1324 	while (*sp == '/') {
   1325 		Xcheck(*xs, xp);
   1326 		*xp++ = *sp++;
   1327 	}
   1328 	np = strchr(sp, '/');
   1329 	if (np != NULL) {
   1330 		se = np;
   1331 		odirsep = *np;	/* don't assume '/', can be multiple kinds */
   1332 		*np++ = '\0';
   1333 	} else {
   1334 		odirsep = '\0'; /* keep gcc quiet */
   1335 		se = sp + strlen(sp);
   1336 	}
   1337 
   1338 
   1339 	/* Check if sp needs globbing - done to avoid pattern checks for strings
   1340 	 * containing MAGIC characters, open [s without the matching close ],
   1341 	 * etc. (otherwise opendir() will be called which may fail because the
   1342 	 * directory isn't readable - if no globbing is needed, only execute
   1343 	 * permission should be required (as per POSIX)).
   1344 	 */
   1345 	if (!has_globbing(sp, se)) {
   1346 		XcheckN(*xs, xp, se - sp + 1);
   1347 		debunk(xp, sp, Xnleft(*xs, xp));
   1348 		xp += strlen(xp);
   1349 		*xpp = xp;
   1350 		globit(xs, xpp, np, wp, check);
   1351 	} else {
   1352 		DIR *dirp;
   1353 		struct dirent *d;
   1354 		char *name;
   1355 		int len;
   1356 		int prefix_len;
   1357 
   1358 		/* xp = *xpp;	copy_non_glob() may have re-alloc'd xs */
   1359 		*xp = '\0';
   1360 		prefix_len = Xlength(*xs, xp);
   1361 		dirp = opendir(prefix_len ? Xstring(*xs, xp) : ".");
   1362 		if (dirp == NULL)
   1363 			goto Nodir;
   1364 		while ((d = readdir(dirp)) != NULL) {
   1365 			name = d->d_name;
   1366 			if (name[0] == '.' &&
   1367 			    (name[1] == 0 || (name[1] == '.' && name[2] == 0)))
   1368 				continue; /* always ignore . and .. */
   1369 			if ((*name == '.' && *sp != '.') ||
   1370 			    !gmatchx(name, sp, true))
   1371 				continue;
   1372 
   1373 			len = strlen(d->d_name) + 1;
   1374 			XcheckN(*xs, xp, len);
   1375 			memcpy(xp, name, len);
   1376 			*xpp = xp + len - 1;
   1377 			globit(xs, xpp, np, wp,
   1378 				(check & GF_MARKDIR) | GF_GLOBBED
   1379 				| (np ? GF_EXCHECK : GF_NONE));
   1380 			xp = Xstring(*xs, xp) + prefix_len;
   1381 		}
   1382 		closedir(dirp);
   1383  Nodir:
   1384 		;
   1385 	}
   1386 
   1387 	if (np != NULL)
   1388 		*--np = odirsep;
   1389 }
   1390 
   1391 /* remove MAGIC from string */
   1392 char *
   1393 debunk(char *dp, const char *sp, size_t dlen)
   1394 {
   1395 	char *d;
   1396 	const char *s;
   1397 
   1398 	if ((s = cstrchr(sp, MAGIC))) {
   1399 		if (s - sp >= (ssize_t)dlen)
   1400 			return (dp);
   1401 		memmove(dp, sp, s - sp);
   1402 		for (d = dp + (s - sp); *s && (d - dp < (ssize_t)dlen); s++)
   1403 			if (!ISMAGIC(*s) || !(*++s & 0x80) ||
   1404 			    !vstrchr("*+?@! ", *s & 0x7f))
   1405 				*d++ = *s;
   1406 			else {
   1407 				/* extended pattern operators: *+?@! */
   1408 				if ((*s & 0x7f) != ' ')
   1409 					*d++ = *s & 0x7f;
   1410 				if (d - dp < (ssize_t)dlen)
   1411 					*d++ = '(';
   1412 			}
   1413 		*d = '\0';
   1414 	} else if (dp != sp)
   1415 		strlcpy(dp, sp, dlen);
   1416 	return (dp);
   1417 }
   1418 
   1419 /* Check if p is an unquoted name, possibly followed by a / or :. If so
   1420  * puts the expanded version in *dcp,dp and returns a pointer in p just
   1421  * past the name, otherwise returns 0.
   1422  */
   1423 static const char *
   1424 maybe_expand_tilde(const char *p, XString *dsp, char **dpp, int isassign)
   1425 {
   1426 	XString ts;
   1427 	char *dp = *dpp;
   1428 	char *tp;
   1429 	const char *r;
   1430 
   1431 	Xinit(ts, tp, 16, ATEMP);
   1432 	/* : only for DOASNTILDE form */
   1433 	while (p[0] == CHAR && p[1] != '/' && (!isassign || p[1] != ':'))
   1434 	{
   1435 		Xcheck(ts, tp);
   1436 		*tp++ = p[1];
   1437 		p += 2;
   1438 	}
   1439 	*tp = '\0';
   1440 	r = (p[0] == EOS || p[0] == CHAR || p[0] == CSUBST) ?
   1441 	    tilde(Xstring(ts, tp)) : NULL;
   1442 	Xfree(ts, tp);
   1443 	if (r) {
   1444 		while (*r) {
   1445 			Xcheck(*dsp, dp);
   1446 			if (ISMAGIC(*r))
   1447 				*dp++ = MAGIC;
   1448 			*dp++ = *r++;
   1449 		}
   1450 		*dpp = dp;
   1451 		r = p;
   1452 	}
   1453 	return (r);
   1454 }
   1455 
   1456 /*
   1457  * tilde expansion
   1458  *
   1459  * based on a version by Arnold Robbins
   1460  */
   1461 
   1462 static char *
   1463 tilde(char *cp)
   1464 {
   1465 	char *dp = null;
   1466 
   1467 	if (cp[0] == '\0')
   1468 		dp = str_val(global("HOME"));
   1469 	else if (cp[0] == '+' && cp[1] == '\0')
   1470 		dp = str_val(global("PWD"));
   1471 	else if (cp[0] == '-' && cp[1] == '\0')
   1472 		dp = str_val(global("OLDPWD"));
   1473 #ifndef MKSH_NOPWNAM
   1474 	else
   1475 		dp = homedir(cp);
   1476 #endif
   1477 	/* If HOME, PWD or OLDPWD are not set, don't expand ~ */
   1478 	return (dp == null ? NULL : dp);
   1479 }
   1480 
   1481 #ifndef MKSH_NOPWNAM
   1482 /*
   1483  * map userid to user's home directory.
   1484  * note that 4.3's getpw adds more than 6K to the shell,
   1485  * and the YP version probably adds much more.
   1486  * we might consider our own version of getpwnam() to keep the size down.
   1487  */
   1488 static char *
   1489 homedir(char *name)
   1490 {
   1491 	struct tbl *ap;
   1492 
   1493 	ap = ktenter(&homedirs, name, hash(name));
   1494 	if (!(ap->flag & ISSET)) {
   1495 		struct passwd *pw;
   1496 
   1497 		pw = getpwnam(name);
   1498 		if (pw == NULL)
   1499 			return (NULL);
   1500 		strdupx(ap->val.s, pw->pw_dir, APERM);
   1501 		ap->flag |= DEFINED|ISSET|ALLOC;
   1502 	}
   1503 	return (ap->val.s);
   1504 }
   1505 #endif
   1506 
   1507 static void
   1508 alt_expand(XPtrV *wp, char *start, char *exp_start, char *end, int fdo)
   1509 {
   1510 	int count = 0;
   1511 	char *brace_start, *brace_end, *comma = NULL;
   1512 	char *field_start;
   1513 	char *p;
   1514 
   1515 	/* search for open brace */
   1516 	for (p = exp_start; (p = strchr(p, MAGIC)) && p[1] != OBRACE; p += 2)
   1517 		;
   1518 	brace_start = p;
   1519 
   1520 	/* find matching close brace, if any */
   1521 	if (p) {
   1522 		comma = NULL;
   1523 		count = 1;
   1524 		for (p += 2; *p && count; p++) {
   1525 			if (ISMAGIC(*p)) {
   1526 				if (*++p == OBRACE)
   1527 					count++;
   1528 				else if (*p == CBRACE)
   1529 					--count;
   1530 				else if (*p == ',' && count == 1)
   1531 					comma = p;
   1532 			}
   1533 		}
   1534 	}
   1535 	/* no valid expansions... */
   1536 	if (!p || count != 0) {
   1537 		/* Note that given a{{b,c} we do not expand anything (this is
   1538 		 * what AT&T ksh does. This may be changed to do the {b,c}
   1539 		 * expansion. }
   1540 		 */
   1541 		if (fdo & DOGLOB)
   1542 			glob(start, wp, fdo & DOMARKDIRS);
   1543 		else
   1544 			XPput(*wp, debunk(start, start, end - start));
   1545 		return;
   1546 	}
   1547 	brace_end = p;
   1548 	if (!comma) {
   1549 		alt_expand(wp, start, brace_end, end, fdo);
   1550 		return;
   1551 	}
   1552 
   1553 	/* expand expression */
   1554 	field_start = brace_start + 2;
   1555 	count = 1;
   1556 	for (p = brace_start + 2; p != brace_end; p++) {
   1557 		if (ISMAGIC(*p)) {
   1558 			if (*++p == OBRACE)
   1559 				count++;
   1560 			else if ((*p == CBRACE && --count == 0) ||
   1561 			    (*p == ',' && count == 1)) {
   1562 				char *news;
   1563 				int l1, l2, l3;
   1564 
   1565 				l1 = brace_start - start;
   1566 				l2 = (p - 1) - field_start;
   1567 				l3 = end - brace_end;
   1568 				news = alloc(l1 + l2 + l3 + 1, ATEMP);
   1569 				memcpy(news, start, l1);
   1570 				memcpy(news + l1, field_start, l2);
   1571 				memcpy(news + l1 + l2, brace_end, l3);
   1572 				news[l1 + l2 + l3] = '\0';
   1573 				alt_expand(wp, news, news + l1,
   1574 				    news + l1 + l2 + l3, fdo);
   1575 				field_start = p + 1;
   1576 			}
   1577 		}
   1578 	}
   1579 	return;
   1580 }
   1581