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/*
23 * D. G. Korn
24 * AT&T Labs
25 *
26 * arithmetic expression evaluator
27 *
28 * this version compiles the expression onto a stack
29 *	 and has a separate executor
30 */
31
32#include	"streval.h"
33#include	<ctype.h>
34#include	<error.h>
35#include	<stak.h>
36#include	"FEATURE/externs"
37#include	"defs.h"	/* for sh.decomma */
38
39#ifndef ERROR_dictionary
40#   define ERROR_dictionary(s)	(s)
41#endif
42#ifndef SH_DICT
43#   define SH_DICT	"libshell"
44#endif
45
46#define MAXLEVEL	9
47#define SMALL_STACK	12
48
49/*
50 * The following are used with tokenbits() macro
51 */
52#define T_OP		0x3f		/* mask for operator number */
53#define T_BINARY	0x40		/* binary operators */
54#define T_NOFLOAT	0x80		/* non floating point operator */
55#define A_LVALUE	(2*MAXPREC+2)
56
57#define pow2size(x)		((x)<=2?2:(x)<=4?4:(x)<=8?8:(x)<=16?16:(x)<=32?32:64)
58#define round(x,size)		(((x)+(size)-1)&~((size)-1))
59#define stakpush(v,val,type)	((((v)->offset=round(staktell(),pow2size(sizeof(type)))),\
60				stakseek((v)->offset+sizeof(type)), \
61				*((type*)stakptr((v)->offset)) = (val)),(v)->offset)
62#define roundptr(ep,cp,type)	(((unsigned char*)(ep))+round(cp-((unsigned char*)(ep)),pow2size(sizeof(type))))
63
64static int level;
65
66struct vars				/* vars stacked per invocation */
67{
68	Shell_t		*shp;
69	const char	*expr;		/* current expression */
70	const char	*nextchr;	/* next char in current expression */
71	const char	*errchr; 	/* next char after error	*/
72	const char	*errstr;	/* error string			*/
73	struct lval	errmsg;	 	/* error message text		*/
74	int		offset;		/* offset for pushchr macro	*/
75	int		staksize;	/* current stack size needed	*/
76	int		stakmaxsize;	/* maximum stack size needed	*/
77	unsigned char	paren;	 	/* parenthesis level		*/
78	char		infun;	/* incremented by comma inside function	*/
79	int		emode;
80	Sfdouble_t	(*convert)(const char**,struct lval*,int,Sfdouble_t);
81};
82
83typedef Sfdouble_t (*Math_f)(Sfdouble_t,...);
84typedef Sfdouble_t (*Math_1f_f)(Sfdouble_t);
85typedef int	   (*Math_1i_f)(Sfdouble_t);
86typedef Sfdouble_t (*Math_2f_f)(Sfdouble_t,Sfdouble_t);
87typedef Sfdouble_t (*Math_2f_i)(Sfdouble_t,int);
88typedef int        (*Math_2i_f)(Sfdouble_t,Sfdouble_t);
89typedef Sfdouble_t (*Math_3f_f)(Sfdouble_t,Sfdouble_t,Sfdouble_t);
90typedef int        (*Math_3i_f)(Sfdouble_t,Sfdouble_t,Sfdouble_t);
91
92#define getchr(vp)	(*(vp)->nextchr++)
93#define peekchr(vp)	(*(vp)->nextchr)
94#define ungetchr(vp)	((vp)->nextchr--)
95
96#if ('a'==97)	/* ASCII encodings */
97#   define getop(c)	(((c) >= sizeof(strval_states))? \
98				((c)=='|'?A_OR:((c)=='^'?A_XOR:((c)=='~'?A_TILDE:A_REG))):\
99				strval_states[(c)])
100#else
101#   define getop(c)	(isdigit(c)?A_DIG:((c==' '||c=='\t'||c=='\n'||c=='"')?0: \
102			(c=='<'?A_LT:(c=='>'?A_GT:(c=='='?A_ASSIGN: \
103			(c=='+'?A_PLUS:(c=='-'?A_MINUS:(c=='*'?A_TIMES: \
104			(c=='/'?A_DIV:(c=='%'?A_MOD:(c==','?A_COMMA: \
105			(c=='&'?A_AND:(c=='!'?A_NOT:(c=='('?A_LPAR: \
106			(c==')'?A_RPAR:(c==0?A_EOF:(c==':'?A_COLON: \
107			(c=='?'?A_QUEST:(c=='|'?A_OR:(c=='^'?A_XOR: \
108			(c=='\''?A_LIT: \
109			(c=='.'?A_DOT:(c=='~'?A_TILDE:A_REG)))))))))))))))))))))))
110#endif
111
112#define seterror(v,msg)		_seterror(v,ERROR_dictionary(msg))
113#define ERROR(vp,msg)		return(seterror((vp),msg))
114
115/*
116 * set error message string and return(0)
117 */
118static int _seterror(struct vars *vp,const char *msg)
119{
120	if(!vp->errmsg.value)
121		vp->errmsg.value = (char*)msg;
122	vp->errchr = vp->nextchr;
123	vp->nextchr = "";
124	level = 0;
125	return(0);
126}
127
128
129static void arith_error(const char *message,const char *expr, int mode)
130{
131        level = 0;
132	mode = (mode&3)!=0;
133        errormsg(SH_DICT,ERROR_exit(mode),message,expr);
134}
135
136#if _ast_no_um2fm
137static Sfdouble_t U2F(Sfulong_t u)
138{
139	Sflong_t	s = u;
140	Sfdouble_t	f;
141
142	if (s >= 0)
143		return s;
144	s = u / 2;
145	f = s;
146	f *= 2;
147	if (u & 1)
148		f++;
149	return f;
150}
151#else
152#define U2F(x)		x
153#endif
154
155Sfdouble_t	arith_exec(Arith_t *ep)
156{
157	register Sfdouble_t num=0,*dp,*sp;
158	register unsigned char *cp = ep->code;
159	register int c,type=0;
160	register char *tp;
161	Sfdouble_t small_stack[SMALL_STACK+1],arg[9];
162	const char *ptr = "";
163	char	*lastval=0;
164	int	lastsub;
165	Math_f fun;
166	struct lval node;
167	Shell_t	*shp = ep->shp;
168	node.shp = shp;
169	node.emode = ep->emode;
170	node.expr = ep->expr;
171	node.elen = ep->elen;
172	node.value = 0;
173	node.nosub = 0;
174	node.ptr = 0;
175	node.eflag = 0;
176	if(level++ >=MAXLEVEL)
177	{
178		arith_error(e_recursive,ep->expr,ep->emode);
179		return(0);
180	}
181	if(ep->staksize < SMALL_STACK)
182		sp = small_stack;
183	else
184		sp = (Sfdouble_t*)stakalloc(ep->staksize*(sizeof(Sfdouble_t)+1));
185	tp = (char*)(sp+ep->staksize);
186	tp--,sp--;
187	while(c = *cp++)
188	{
189		if(c&T_NOFLOAT)
190		{
191			if(type==1 || ((c&T_BINARY) && (c&T_OP)!=A_MOD  && tp[-1]==1))
192				arith_error(e_incompatible,ep->expr,ep->emode);
193		}
194		switch(c&T_OP)
195		{
196		    case A_JMP: case A_JMPZ: case A_JMPNZ:
197			c &= T_OP;
198			cp = roundptr(ep,cp,short);
199			if((c==A_JMPZ && num) || (c==A_JMPNZ &&!num))
200				cp += sizeof(short);
201			else
202				cp = (unsigned char*)ep + *((short*)cp);
203			continue;
204		    case A_NOTNOT:
205			num = (num!=0);
206			type=0;
207			break;
208		    case A_PLUSPLUS:
209			node.nosub = -1;
210			(*ep->fun)(&ptr,&node,ASSIGN,num+1);
211			break;
212		    case A_MINUSMINUS:
213			node.nosub = -1;
214			(*ep->fun)(&ptr,&node,ASSIGN,num-1);
215			break;
216		    case A_INCR:
217			num = num+1;
218			node.nosub = -1;
219			num = (*ep->fun)(&ptr,&node,ASSIGN,num);
220			break;
221		    case A_DECR:
222			num = num-1;
223			node.nosub = -1;
224			num = (*ep->fun)(&ptr,&node,ASSIGN,num);
225			break;
226		    case A_SWAP:
227			num = sp[-1];
228			sp[-1] = *sp;
229			type = tp[-1];
230			tp[-1] = *tp;
231			break;
232		    case A_POP:
233			sp--;
234			continue;
235		    case A_ASSIGNOP1:
236			node.emode |= ARITH_ASSIGNOP;
237		    case A_PUSHV:
238			cp = roundptr(ep,cp,Sfdouble_t*);
239			dp = *((Sfdouble_t**)cp);
240			cp += sizeof(Sfdouble_t*);
241			c = *(short*)cp;
242			cp += sizeof(short);
243			lastval = node.value = (char*)dp;
244			if(node.flag = c)
245				lastval = 0;
246			node.isfloat=0;
247			node.level = level;
248			node.nosub = 0;
249			num = (*ep->fun)(&ptr,&node,VALUE,num);
250			if(node.emode&ARITH_ASSIGNOP)
251			{
252				lastsub = node.nosub;
253				node.nosub = 0;
254				node.emode &= ~ARITH_ASSIGNOP;
255			}
256			if(node.value != (char*)dp)
257				arith_error(node.value,ptr,ep->emode);
258			*++sp = num;
259			type = node.isfloat;
260			if(num > LDBL_ULLONG_MAX || num < LDBL_LLONG_MIN)
261				type = 1;
262			else
263			{
264				Sfdouble_t d=num;
265				if(num > LDBL_LLONG_MAX && num <= LDBL_ULLONG_MAX)
266				{
267					type = 2;
268					d -= LDBL_LLONG_MAX;
269				}
270				if((Sflong_t)d!=d)
271					type = 1;
272			}
273			*++tp = type;
274			c = 0;
275			break;
276		    case A_ENUM:
277			node.eflag = 1;
278			continue;
279		    case A_ASSIGNOP:
280			node.nosub = lastsub;
281		    case A_STORE:
282			cp = roundptr(ep,cp,Sfdouble_t*);
283			dp = *((Sfdouble_t**)cp);
284			cp += sizeof(Sfdouble_t*);
285			c = *(short*)cp;
286			if(c<0)
287				c = 0;
288			cp += sizeof(short);
289			node.value = (char*)dp;
290			node.flag = c;
291			if(lastval)
292				node.eflag = 1;
293			node.ptr = 0;
294			num = (*ep->fun)(&ptr,&node,ASSIGN,num);
295			if(lastval && node.ptr)
296			{
297				Sfdouble_t r;
298				node.flag = 0;
299				node.value = lastval;
300				r =  (*ep->fun)(&ptr,&node,VALUE,num);
301				if(r!=num)
302				{
303					node.flag=c;
304					node.value = (char*)dp;
305					num = (*ep->fun)(&ptr,&node,ASSIGN,r);
306				}
307
308			}
309			lastval = 0;
310			c=0;
311			break;
312		    case A_PUSHF:
313			cp = roundptr(ep,cp,Math_f);
314			*++sp = (Sfdouble_t)(cp-ep->code);
315			cp += sizeof(Math_f);
316			*++tp = *cp++;
317			continue;
318		    case A_PUSHN:
319			cp = roundptr(ep,cp,Sfdouble_t);
320			num = *((Sfdouble_t*)cp);
321			cp += sizeof(Sfdouble_t);
322			*++sp = num;
323			*++tp = type = *cp++;
324			break;
325		    case A_NOT:
326			type=0;
327			num = !num;
328			break;
329		    case A_UMINUS:
330			num = -num;
331			break;
332		    case A_TILDE:
333			num = ~((Sflong_t)(num));
334			break;
335		    case A_PLUS:
336			num += sp[-1];
337			break;
338		    case A_MINUS:
339			num = sp[-1] - num;
340			break;
341		    case A_TIMES:
342			num *= sp[-1];
343			break;
344		    case A_POW:
345			num = pow(sp[-1],num);
346			break;
347		    case A_MOD:
348			if(!(Sflong_t)num)
349				arith_error(e_divzero,ep->expr,ep->emode);
350			if(type==2 || tp[-1]==2)
351				num = U2F((Sfulong_t)(sp[-1]) % (Sfulong_t)(num));
352			else
353				num = (Sflong_t)(sp[-1]) % (Sflong_t)(num);
354			break;
355		    case A_DIV:
356			if(type==1 || tp[-1]==1)
357			{
358				num = sp[-1]/num;
359				type = 1;
360			}
361			else if((Sfulong_t)(num)==0)
362				arith_error(e_divzero,ep->expr,ep->emode);
363			else if(type==2 || tp[-1]==2)
364				num = U2F((Sfulong_t)(sp[-1]) / (Sfulong_t)(num));
365			else
366				num = (Sflong_t)(sp[-1]) / (Sflong_t)(num);
367			break;
368		    case A_LSHIFT:
369			if(tp[-1]==2)
370				num = U2F((Sfulong_t)(sp[-1]) << (long)(num));
371			else
372				num = (Sflong_t)(sp[-1]) << (long)(num);
373			break;
374		    case A_RSHIFT:
375			if(tp[-1]==2)
376				num = U2F((Sfulong_t)(sp[-1]) >> (long)(num));
377			else
378				num = (Sflong_t)(sp[-1]) >> (long)(num);
379			break;
380		    case A_XOR:
381			if(type==2 || tp[-1]==2)
382				num = U2F((Sfulong_t)(sp[-1]) ^ (Sfulong_t)(num));
383			else
384				num = (Sflong_t)(sp[-1]) ^ (Sflong_t)(num);
385			break;
386		    case A_OR:
387			if(type==2 || tp[-1]==2)
388				num = U2F((Sfulong_t)(sp[-1]) | (Sfulong_t)(num));
389			else
390				num = (Sflong_t)(sp[-1]) | (Sflong_t)(num);
391			break;
392		    case A_AND:
393			if(type==2 || tp[-1]==2)
394				num = U2F((Sfulong_t)(sp[-1]) & (Sfulong_t)(num));
395			else
396				num = (Sflong_t)(sp[-1]) & (Sflong_t)(num);
397			break;
398		    case A_EQ:
399			num = (sp[-1]==num);
400			type=0;
401			break;
402		    case A_NEQ:
403			num = (sp[-1]!=num);
404			type=0;
405			break;
406		    case A_LE:
407			num = (sp[-1]<=num);
408			type=0;
409			break;
410		    case A_GE:
411			num = (sp[-1]>=num);
412			type=0;
413			break;
414		    case A_GT:
415			num = (sp[-1]>num);
416			type=0;
417			break;
418		    case A_LT:
419			num = (sp[-1]<num);
420			type=0;
421			break;
422		    case A_CALL1F:
423			sp--,tp--;
424			fun = *((Math_f*)(ep->code+(int)(*sp)));
425			type = *tp;
426			if(c&T_BINARY)
427			{
428				c &= ~T_BINARY;
429				arg[0] = num;
430				arg[1] = 0;
431				num = sh_mathfun(shp,(void*)fun,1,arg);
432				break;
433			}
434			num = (*((Math_1f_f)fun))(num);
435			break;
436		    case A_CALL1I:
437			sp--,tp--;
438			fun = *((Math_f*)(ep->code+(int)(*sp)));
439			type = *tp;
440			num = (*((Math_1i_f)fun))(num);
441			break;
442		    case A_CALL2F:
443			sp-=2,tp-=2;
444			fun = *((Math_f*)(ep->code+(int)(*sp)));
445			type = *tp;
446			if(c&T_BINARY)
447			{
448				c &= ~T_BINARY;
449				arg[0] = sp[1];
450				arg[1] = num;
451				arg[2] = 0;
452				num = sh_mathfun(shp,(void*)fun,2,arg);
453				break;
454			}
455			if(c&T_NOFLOAT)
456				num = (*((Math_2f_i)fun))(sp[1],(int)num);
457			else
458				num = (*((Math_2f_f)fun))(sp[1],num);
459			break;
460		    case A_CALL2I:
461			sp-=2,tp-=2;
462			fun = *((Math_f*)(ep->code+(int)(*sp)));
463			type = *tp;
464			num = (*((Math_2i_f)fun))(sp[1],num);
465			break;
466		    case A_CALL3F:
467			sp-=3,tp-=3;
468			fun = *((Math_f*)(ep->code+(int)(*sp)));
469			type = *tp;
470			if(c&T_BINARY)
471			{
472				c &= ~T_BINARY;
473				arg[0] = sp[1];
474				arg[1] = sp[2];
475				arg[2] = num;
476				arg[3] = 0;
477				num = sh_mathfun(shp,(void*)fun,3,arg);
478				break;
479			}
480			num = (*((Math_3f_f)fun))(sp[1],sp[2],num);
481			break;
482		}
483		if(c)
484			lastval = 0;
485		if(c&T_BINARY)
486		{
487			node.ptr = 0;
488			sp--,tp--;
489			type  |= (*tp!=0);
490		}
491		*sp = num;
492		*tp = type;
493	}
494	if(level>0)
495		level--;
496	return(num);
497}
498
499/*
500 * This returns operator tokens or A_REG or A_NUM
501 */
502static int gettok(register struct vars *vp)
503{
504	register int c,op;
505	vp->errchr = vp->nextchr;
506	while(1)
507	{
508		c = getchr(vp);
509		switch(op=getop(c))
510		{
511		    case 0:
512			vp->errchr = vp->nextchr;
513			continue;
514		    case A_EOF:
515			vp->nextchr--;
516			break;
517		    case A_COMMA:
518			if(vp->shp->decomma && (c=peekchr(vp))>='0' && c<='9')
519			{
520				op = A_DIG;
521		    		goto keep;
522			}
523			break;
524		    case A_DOT:
525			if((c=peekchr(vp))>='0' && c<='9')
526				op = A_DIG;
527			else
528				op = A_REG;
529			/*FALL THRU*/
530		    case A_DIG: case A_REG: case A_LIT:
531		    keep:
532			ungetchr(vp);
533			break;
534		    case A_QUEST:
535			if(peekchr(vp)==':')
536			{
537				getchr(vp);
538				op = A_QCOLON;
539			}
540			break;
541		    case A_LT:	case A_GT:
542			if(peekchr(vp)==c)
543			{
544				getchr(vp);
545				op -= 2;
546				break;
547			}
548			/* FALL THRU */
549		    case A_NOT:	case A_COLON:
550			c = '=';
551			/* FALL THRU */
552		    case A_ASSIGN:
553		    case A_TIMES:
554		    case A_PLUS:	case A_MINUS:
555		    case A_OR:	case A_AND:
556			if(peekchr(vp)==c)
557			{
558				getchr(vp);
559				op--;
560			}
561		}
562		return(op);
563	}
564}
565
566/*
567 * evaluate a subexpression with precedence
568 */
569
570static int expr(register struct vars *vp,register int precedence)
571{
572	register int	c, op;
573	int		invalid,wasop=0;
574	struct lval	lvalue,assignop;
575	const char	*pos;
576	Sfdouble_t	d;
577
578	lvalue.value = 0;
579	lvalue.nargs = 0;
580	lvalue.fun = 0;
581	lvalue.shp =  vp->shp;
582again:
583	op = gettok(vp);
584	c = 2*MAXPREC+1;
585	switch(op)
586	{
587	    case A_PLUS:
588		goto again;
589	    case A_EOF:
590		if(precedence>2)
591			ERROR(vp,e_moretokens);
592		return(1);
593	    case A_MINUS:
594		op =  A_UMINUS;
595		goto common;
596	    case A_NOT:
597		goto common;
598	    case A_MINUSMINUS:
599		c = A_LVALUE;
600		op = A_DECR|T_NOFLOAT;
601		goto common;
602	    case A_PLUSPLUS:
603		c = A_LVALUE;
604		op = A_INCR|T_NOFLOAT;
605		/* FALL THRU */
606	    case A_TILDE:
607		op |= T_NOFLOAT;
608	    common:
609		if(!expr(vp,c))
610			return(0);
611		stakputc(op);
612		break;
613	    default:
614		vp->nextchr = vp->errchr;
615		wasop = 1;
616	}
617	invalid = wasop;
618	while(1)
619	{
620		assignop.value = 0;
621		op = gettok(vp);
622		if(op==A_DIG || op==A_REG || op==A_LIT)
623		{
624			if(!wasop)
625				ERROR(vp,e_synbad);
626			goto number;
627		}
628		if(wasop++ && op!=A_LPAR)
629			ERROR(vp,e_synbad);
630		/* check for assignment operation */
631		if(peekchr(vp)== '=' && !(strval_precedence[op]&NOASSIGN))
632		{
633			if((!lvalue.value || precedence > 3))
634				ERROR(vp,e_notlvalue);
635			if(precedence==3)
636				precedence = 2;
637			assignop = lvalue;
638			getchr(vp);
639			c = 3;
640		}
641		else
642		{
643			c = (strval_precedence[op]&PRECMASK);
644			if(c==MAXPREC || op==A_POW)
645				c++;
646			c *= 2;
647		}
648		/* from here on c is the new precedence level */
649		if(lvalue.value && (op!=A_ASSIGN))
650		{
651			if(vp->staksize++>=vp->stakmaxsize)
652				vp->stakmaxsize = vp->staksize;
653			if(op==A_EQ || op==A_NEQ)
654				stakputc(A_ENUM);
655			stakputc(assignop.value?A_ASSIGNOP1:A_PUSHV);
656			stakpush(vp,lvalue.value,char*);
657			if(lvalue.flag<0)
658				lvalue.flag = 0;
659			stakpush(vp,lvalue.flag,short);
660			if(vp->nextchr==0)
661				ERROR(vp,e_badnum);
662			if(!(strval_precedence[op]&SEQPOINT))
663				lvalue.value = 0;
664			invalid = 0;
665		}
666		else if(precedence==A_LVALUE)
667			ERROR(vp,e_notlvalue);
668		if(invalid && op>A_ASSIGN)
669			ERROR(vp,e_synbad);
670		if(precedence >= c)
671			goto done;
672		if(strval_precedence[op]&RASSOC)
673			c--;
674		if((c < (2*MAXPREC+1)) && !(strval_precedence[op]&SEQPOINT))
675		{
676			wasop = 0;
677			if(!expr(vp,c))
678				return(0);
679		}
680		switch(op)
681		{
682		case A_RPAR:
683			if(!vp->paren)
684				ERROR(vp,e_paren);
685			if(invalid)
686				ERROR(vp,e_synbad);
687			goto done;
688
689		case A_COMMA:
690			wasop = 0;
691			if(vp->infun)
692				vp->infun++;
693			else
694			{
695				stakputc(A_POP);
696				vp->staksize--;
697			}
698			if(!expr(vp,c))
699			{
700				stakseek(staktell()-1);
701				return(0);
702			}
703			lvalue.value = 0;
704			break;
705
706		case A_LPAR:
707		{
708			int	infun = vp->infun;
709			int	userfun=0;
710			Sfdouble_t (*fun)(Sfdouble_t,...);
711			int nargs = lvalue.nargs;
712			if(nargs<0)
713				nargs = -nargs;
714			fun = lvalue.fun;
715			lvalue.fun = 0;
716			if(fun)
717			{
718				if(vp->staksize++>=vp->stakmaxsize)
719					vp->stakmaxsize = vp->staksize;
720				vp->infun=1;
721				if((int)lvalue.nargs<0)
722					userfun = T_BINARY;
723				else if((int)lvalue.nargs&040)
724					userfun = T_NOFLOAT;
725				stakputc(A_PUSHF);
726				stakpush(vp,fun,Math_f);
727				stakputc(1);
728			}
729			else
730				vp->infun = 0;
731			if(!invalid)
732				ERROR(vp,e_synbad);
733			vp->paren++;
734			if(!expr(vp,1))
735				return(0);
736			vp->paren--;
737			if(fun)
738			{
739				int  x= (nargs&010)?2:-1;
740				nargs &= 7;
741				if(vp->infun != nargs)
742					ERROR(vp,e_argcount);
743				if((vp->staksize+=nargs)>=vp->stakmaxsize)
744					vp->stakmaxsize = vp->staksize+nargs;
745				stakputc(A_CALL1F+userfun+nargs+x);
746				vp->staksize -= nargs;
747			}
748			vp->infun = infun;
749			if (gettok(vp) != A_RPAR)
750				ERROR(vp,e_paren);
751			wasop = 0;
752			break;
753		}
754
755		case A_PLUSPLUS:
756		case A_MINUSMINUS:
757			wasop=0;
758			op |= T_NOFLOAT;
759		case A_ASSIGN:
760			if(!lvalue.value)
761				ERROR(vp,e_notlvalue);
762			if(op==A_ASSIGN)
763			{
764				stakputc(A_STORE);
765				stakpush(vp,lvalue.value,char*);
766				stakpush(vp,lvalue.flag,short);
767				vp->staksize--;
768			}
769			else
770				stakputc(op);
771			lvalue.value = 0;
772			break;
773
774		case A_QUEST:
775		{
776			int offset1,offset2;
777			stakputc(A_JMPZ);
778			offset1 = stakpush(vp,0,short);
779			stakputc(A_POP);
780			if(!expr(vp,1))
781				return(0);
782			if(gettok(vp)!=A_COLON)
783				ERROR(vp,e_questcolon);
784			stakputc(A_JMP);
785			offset2 = stakpush(vp,0,short);
786			*((short*)stakptr(offset1)) = staktell();
787			stakputc(A_POP);
788			if(!expr(vp,3))
789				return(0);
790			*((short*)stakptr(offset2)) = staktell();
791			lvalue.value = 0;
792			wasop = 0;
793			break;
794		}
795
796		case A_COLON:
797			ERROR(vp,e_badcolon);
798			break;
799
800		case A_QCOLON:
801		case A_ANDAND:
802		case A_OROR:
803		{
804			int offset;
805			if(op==A_ANDAND)
806				op = A_JMPZ;
807			else
808				op = A_JMPNZ;
809			stakputc(op);
810			offset = stakpush(vp,0,short);
811			stakputc(A_POP);
812			if(!expr(vp,c))
813				return(0);
814			*((short*)stakptr(offset)) = staktell();
815			if(op!=A_QCOLON)
816				stakputc(A_NOTNOT);
817			lvalue.value = 0;
818			wasop=0;
819			break;
820		}
821		case A_AND:	case A_OR:	case A_XOR:	case A_LSHIFT:
822		case A_RSHIFT:	case A_MOD:
823			op |= T_NOFLOAT;
824			/* FALL THRU */
825		case A_PLUS:	case A_MINUS:	case A_TIMES:	case A_DIV:
826		case A_EQ:	case A_NEQ:	case A_LT:	case A_LE:
827		case A_GT:	case A_GE:	case A_POW:
828			stakputc(op|T_BINARY);
829			vp->staksize--;
830			break;
831		case A_NOT: case A_TILDE:
832		default:
833			ERROR(vp,e_synbad);
834		number:
835			wasop = 0;
836			if(*vp->nextchr=='L' && vp->nextchr[1]=='\'')
837			{
838				vp->nextchr++;
839				op = A_LIT;
840			}
841			pos = vp->nextchr;
842			lvalue.isfloat = 0;
843			lvalue.expr = vp->expr;
844			lvalue.emode = vp->emode;
845			if(op==A_LIT)
846			{
847				/* character constants */
848				if(pos[1]=='\\' && pos[2]=='\'' && pos[3]!='\'')
849				{
850					d = '\\';
851					vp->nextchr +=2;
852				}
853				else
854					d = chresc(pos+1,(char**)&vp->nextchr);
855				/* posix allows the trailing ' to be optional */
856				if(*vp->nextchr=='\'')
857					vp->nextchr++;
858			}
859			else
860				d = (*vp->convert)(&vp->nextchr, &lvalue, LOOKUP, 0);
861			if (vp->nextchr == pos)
862			{
863				if(vp->errmsg.value = lvalue.value)
864					vp->errstr = pos;
865				ERROR(vp,op==A_LIT?e_charconst:e_synbad);
866			}
867			if(op==A_DIG || op==A_LIT)
868			{
869				stakputc(A_PUSHN);
870				if(vp->staksize++>=vp->stakmaxsize)
871					vp->stakmaxsize = vp->staksize;
872				stakpush(vp,d,Sfdouble_t);
873				stakputc(lvalue.isfloat);
874			}
875
876			/* check for function call */
877			if(lvalue.fun)
878				continue;
879			break;
880		}
881		invalid = 0;
882		if(assignop.value)
883		{
884			if(vp->staksize++>=vp->stakmaxsize)
885				vp->stakmaxsize = vp->staksize;
886			if(assignop.flag<0)
887				assignop.flag = 0;
888			stakputc(c&1?A_ASSIGNOP:A_STORE);
889			stakpush(vp,assignop.value,char*);
890			stakpush(vp,assignop.flag,short);
891		}
892	}
893 done:
894	vp->nextchr = vp->errchr;
895	return(1);
896}
897
898Arith_t *arith_compile(Shell_t *shp,const char *string,char **last,Sfdouble_t(*fun)(const char**,struct lval*,int,Sfdouble_t),int emode)
899{
900	struct vars cur;
901	register Arith_t *ep;
902	int offset;
903	memset((void*)&cur,0,sizeof(cur));
904	cur.shp = shp;
905     	cur.expr = cur.nextchr = string;
906	cur.convert = fun;
907	cur.emode = emode;
908	cur.errmsg.value = 0;
909	cur.errmsg.emode = emode;
910	stakseek(sizeof(Arith_t));
911	if(!expr(&cur,0) && cur.errmsg.value)
912        {
913		if(cur.errstr)
914			string = cur.errstr;
915		if((*fun)( &string , &cur.errmsg, MESSAGE, 0) < 0)
916		{
917			stakseek(0);
918			*last = (char*)Empty;
919			return(0);
920		}
921		cur.nextchr = cur.errchr;
922	}
923	stakputc(0);
924	offset = staktell();
925	ep = (Arith_t*)stakfreeze(0);
926	ep->shp = shp;
927	ep->expr = string;
928	ep->elen = strlen(string);
929	ep->code = (unsigned char*)(ep+1);
930	ep->fun = fun;
931	ep->emode = emode;
932	ep->size = offset - sizeof(Arith_t);
933	ep->staksize = cur.stakmaxsize+1;
934	if(last)
935		*last = (char*)(cur.nextchr);
936	return(ep);
937}
938
939/*
940 * evaluate an integer arithmetic expression in s
941 *
942 * (Sfdouble_t)(*convert)(char** end, struct lval* string, int type, Sfdouble_t value)
943 *     is a user supplied conversion routine that is called when unknown
944 *     chars are encountered.
945 * *end points to the part to be converted and must be adjusted by convert to
946 * point to the next non-converted character; if typ is MESSAGE then string
947 * points to an error message string
948 *
949 * NOTE: (*convert)() may call strval()
950 */
951
952Sfdouble_t strval(Shell_t *shp,const char *s,char **end,Sfdouble_t(*conv)(const char**,struct lval*,int,Sfdouble_t),int emode)
953{
954	Arith_t *ep;
955	Sfdouble_t d;
956	char *sp=0;
957	int offset;
958	if(offset=staktell())
959		sp = stakfreeze(1);
960	ep = arith_compile(shp,s,end,conv,emode);
961	ep->emode = emode;
962	d = arith_exec(ep);
963	stakset(sp?sp:(char*)ep,offset);
964	return(d);
965}
966
967#if _mem_name__exception
968#undef	_mem_name_exception
969#define	_mem_name_exception	1
970#undef	exception
971#define	exception		_exception
972#undef	matherr
973#endif
974
975#if _mem_name_exception
976
977#undef	error
978
979#if _BLD_shell && defined(__EXPORT__)
980#define extern			__EXPORT__
981#endif
982
983#ifndef DOMAIN
984#define DOMAIN			_DOMAIN
985#endif
986#ifndef OVERFLOW
987#define OVERFLOW		_OVERFLOW
988#endif
989#ifndef SING
990#define SING			_SING
991#endif
992
993    extern int matherr(struct exception *ep)
994    {
995	const char *message;
996	switch(ep->type)
997	{
998#ifdef DOMAIN
999	    case DOMAIN:
1000		message = ERROR_dictionary(e_domain);
1001		break;
1002#endif
1003#ifdef OVERFLOW
1004	    case OVERFLOW:
1005		message = ERROR_dictionary(e_overflow);
1006		break;
1007#endif
1008#ifdef SING
1009	    case SING:
1010		message = ERROR_dictionary(e_singularity);
1011		break;
1012#endif
1013	    default:
1014		return(1);
1015	}
1016	level=0;
1017	errormsg(SH_DICT,ERROR_exit(1),message,ep->name);
1018	return(0);
1019    }
1020
1021#undef	extern
1022
1023#endif /* _mem_name_exception */
1024