source: git/Singular/grammar.y @ ecf019

fieker-DuValspielwiese
Last change on this file since ecf019 was 1f03aba, checked in by Hans Schoenemann <hannes@…>, 12 years ago
fix(from master): bug in memeroy management of mpr_base.cc chg(from master): introduce RING_DECL_LIST
  • Property mode set to 100644
File size: 41.8 KB
RevLine 
[0e1846]1/****************************************
2*  Computer Algebra System SINGULAR     *
3****************************************/
[341696]4/* $Id$ */
[0e1846]5/*
6* ABSTRACT: SINGULAR shell grammatik
7*/
8%{
9
10#include <stdio.h>
11#include <stddef.h>
12#include <stdlib.h>
13#include <stdarg.h>
14#include <string.h>
15
[b1dfaf]16#include <kernel/mod2.h>
[e7d5ef]17#include <misc/mylimits.h>
[b1dfaf]18#include <omalloc/omalloc.h>
[599326]19#include <Singular/tok.h>
[0fb34ba]20#include <misc/options.h>
[599326]21#include <Singular/stype.h>
[db45a2]22#include <Singular/fehelp.h>
[599326]23#include <Singular/ipid.h>
[0fb34ba]24#include <misc/intvec.h>
[599326]25#include <kernel/febase.h>
[0fb34ba]26#include <polys/matpol.h>
27#include <polys/monomials/ring.h>
[599326]28#include <kernel/kstd1.h>
29#include <Singular/subexpr.h>
30#include <Singular/ipshell.h>
31#include <Singular/ipconv.h>
32#include <Singular/sdb.h>
33#include <kernel/ideals.h>
[0fb34ba]34#include <coeffs/numbers.h>
[737a68]35#include <kernel/polys.h>
[599326]36#include <kernel/stairc.h>
37#include <kernel/timer.h>
38#include <Singular/cntrlc.h>
[0fb34ba]39#include <polys/monomials/maps.h>
[599326]40#include <kernel/syz.h>
41#include <Singular/lists.h>
42#include <kernel/longrat.h>
43#include <Singular/libparse.h>
[0e1846]44
[458a2f]45#if 0
46void debug_list(leftv v)
47{
48  idhdl r=basePackHdl;
49  idhdl h;
50  BOOLEAN found=FALSE;
51  const char *nn=v->name;
52  h=IDROOT->get(nn,myynest);
53  if (h!=NULL)
54  {
55     Print("Curr::%s, (%s)\n",nn,Tok2Cmdname((int)IDTYP(h)));
56     found=TRUE;
57  }
58  else         Print("`%s` not found in IDROOT\n",nn);
59  while (r!=NULL)
60  {
61    if ((IDTYP(r)==PACKAGE_CMD)
62    || (IDTYP(r)==RING_CMD)
63    || (IDTYP(r)==QRING_CMD))
64    {
65      h=IDPACKAGE(r)->idroot->get(nn,myynest);
66      if (h!=NULL)
67      {
68        Print("%s::%s, (%s)\n",r->id,nn,Tok2Cmdname((int)IDTYP(h)));
69        found=TRUE;
70      }
71      else         Print("%s::%s not found\n",r->id,nn);
72    }
73    if (r==basePackHdl) r=IDPACKAGE(r)->idroot;
74    r=r->next;
75   if (r==basePackHdl) break;
76  }
77  if (!found)
78  {
79    listall(TRUE);
80  }
81}
82#endif
83
[e16182]84/* From the bison docu:
[97f271]85
[e16182]86     By defining the macro `YYMAXDEPTH', you can control how deep the
87parser stack can become before a stack overflow occurs.  Define the
88macro with a value that is an integer.  This value is the maximum number
89of tokens that can be shifted (and not reduced) before overflow.  It
90must be a constant expression whose value is known at compile time.
[0e1846]91
[e16182]92   The stack space allowed is not necessarily allocated.  If you
93specify a large value for `YYMAXDEPTH', the parser actually allocates a
94small stack at first, and then makes it bigger by stages as needed.
95This increasing allocation happens automatically and silently.
96Therefore, you do not need to make `YYMAXDEPTH' painfully small merely
97to save space for ordinary inputs that do not need much stack.
98
99   The default value of `YYMAXDEPTH', if you do not define it, is 10000.
100*/
[e554162]101#define YYMAXDEPTH MAX_INT_VAL
[97f271]102
[0e1846]103extern int   yylineno;
104extern FILE* yyin;
105
[85e68dd]106const  char *  currid;
[34fbd93]107BOOLEAN    yyInRingConstruction=FALSE;
[0e1846]108BOOLEAN    expected_parms;
109int        cmdtok;
110int        inerror = 0;
111
112#define TESTSETINT(a,i)                                \
113   if ((a).Typ() != INT_CMD)                           \
114   {                                                   \
115     WerrorS("no int expression");                     \
116     YYERROR;                                          \
117   }                                                   \
[7447d8]118   (i) = (int)((long)(a).Data());
[0e1846]119
120#define MYYERROR(a) { WerrorS(a); YYERROR; }
121
[85e68dd]122void yyerror(const char * fmt)
[0e1846]123{
124
125  BOOLEAN old_errorreported=errorreported;
126  errorreported = TRUE;
127  if (currid!=NULL)
128  {
[46d09b]129    killid(currid,&IDROOT);
[0e1846]130    currid = NULL;
131  }
[bcd557]132  if(inerror==0)
[0e1846]133  {
[6227ad]134    {
[4ccf665]135      if ((strlen(fmt)>1)
136      && (strncmp(fmt,"parse",5)!=0)
137      && (strncmp(fmt,"syntax",6)!=0))
[f0cc3ed]138        WerrorS(fmt);
[f58aa6]139      Werror( "error occurred in or before %s line %d: `%s`"
[6227ad]140             ,VoiceName(), yylineno, my_yylinebuf);
141    }
[0e1846]142    if (cmdtok!=0)
143    {
[85e68dd]144      const char *s=Tok2Cmdname(cmdtok);
[0e1846]145      if (expected_parms)
146      {
147        Werror("expected %s-expression. type \'help %s;\'",s,s);
148      }
149      else
150      {
151        Werror("wrong type declaration. type \'help %s;\'",s);
152      }
153    }
154    if (!old_errorreported && (lastreserved!=NULL))
155    {
156      Werror("last reserved name was `%s`",lastreserved);
157    }
[bcd557]158    inerror=1;
[0e1846]159  }
[057e93c]160  if ((currentVoice!=NULL)
161  && (currentVoice->prev!=NULL)
[ad4bc9]162  && (myynest>0)
[50cbdc]163#ifdef HAVE_SDB
164  && ((sdb_flags &1)==0)
165#endif
166  )
[0e1846]167  {
168    Werror("leaving %s",VoiceName());
169  }
[5348866]170#ifdef HAVE_FACTORY
[d3e630]171  // libfac:
[5348866]172#ifdef HAVE_LIBFAC
[7326166]173  extern int libfac_interruptflag;
174  libfac_interruptflag=0;
[5348866]175#endif // #ifdef HAVE_LIBFAC
176#endif
[0e1846]177}
178
179%}
180
181/* %expect 22 */
182%pure_parser
183
184/* special symbols */
185%token DOTDOT
186%token EQUAL_EQUAL
187%token GE
188%token LE
189%token MINUSMINUS
190%token NOT
191%token NOTEQUAL
192%token PLUSPLUS
[057e93c]193%token COLONCOLON
[0e1846]194
195/* types, part 1 (ring indep.)*/
[48a2a7]196%token <i> GRING_CMD
[0e1846]197%token <i> INTMAT_CMD
198%token <i> PROC_CMD
199%token <i> RING_CMD
200
201/* valid when ring defined ! */
202%token <i> BEGIN_RING
203/* types, part 2 */
204%token <i> IDEAL_CMD
205%token <i> MAP_CMD
206%token <i> MATRIX_CMD
207%token <i> MODUL_CMD
208%token <i> NUMBER_CMD
209%token <i> POLY_CMD
[dfc6b54]210%token <i> RESOLUTION_CMD
[0e1846]211%token <i> VECTOR_CMD
212/* end types */
213
214/* ring dependent cmd:*/
215%token <i> BETTI_CMD
216%token <i> COEFFS_CMD
217%token <i> COEF_CMD
218%token <i> CONTRACT_CMD
219%token <i> DEGREE_CMD
220%token <i> DEG_CMD
221%token <i> DIFF_CMD
222%token <i> DIM_CMD
[1bf317]223%token <i> DIVISION_CMD
[0e1846]224%token <i> ELIMINATION_CMD
225%token <i> E_CMD
[3149a5]226%token <i> FAREY_CMD
[0e1846]227%token <i> FETCH_CMD
228%token <i> FREEMODULE_CMD
229%token <i> KEEPRING_CMD
230%token <i> HILBERT_CMD
231%token <i> HOMOG_CMD
232%token <i> IMAP_CMD
233%token <i> INDEPSET_CMD
234%token <i> INTERRED_CMD
235%token <i> INTERSECT_CMD
236%token <i> JACOB_CMD
237%token <i> JET_CMD
238%token <i> KBASE_CMD
239%token <i> KOSZUL_CMD
240%token <i> LEADCOEF_CMD
241%token <i> LEADEXP_CMD
242%token <i> LEAD_CMD
[7df2ef]243%token <i> LEADMONOM_CMD
[0e1846]244%token <i> LIFTSTD_CMD
245%token <i> LIFT_CMD
246%token <i> MAXID_CMD
247%token <i> MINBASE_CMD
248%token <i> MINOR_CMD
249%token <i> MINRES_CMD
250%token <i> MODULO_CMD
[4b3ef4b]251%token <i> MONOM_CMD
[0e1846]252%token <i> MRES_CMD
253%token <i> MULTIPLICITY_CMD
254%token <i> ORD_CMD
255%token <i> PAR_CMD
256%token <i> PARDEG_CMD
257%token <i> PREIMAGE_CMD
258%token <i> QUOTIENT_CMD
259%token <i> QHWEIGHT_CMD
260%token <i> REDUCE_CMD
261%token <i> REGULARITY_CMD
262%token <i> RES_CMD
263%token <i> SIMPLIFY_CMD
264%token <i> SORTVEC_CMD
265%token <i> SRES_CMD
266%token <i> STD_CMD
267%token <i> SUBST_CMD
268%token <i> SYZYGY_CMD
269%token <i> VAR_CMD
270%token <i> VDIM_CMD
271%token <i> WEDGE_CMD
272%token <i> WEIGHT_CMD
273
274/*system variables in ring block*/
275%token <i> VALTVARS
276%token <i> VMAXDEG
277%token <i> VMAXMULT
278%token <i> VNOETHER
279%token <i> VMINPOLY
280
281%token <i> END_RING
282/* end of ring definitions */
283
284%token <i> CMD_1
285%token <i> CMD_2
286%token <i> CMD_3
287%token <i> CMD_12
[7b4121]288%token <i> CMD_13
[0e1846]289%token <i> CMD_23
290%token <i> CMD_123
291%token <i> CMD_M
292%token <i> ROOT_DECL
293        /* put variables of this type into the idroot list */
294%token <i> ROOT_DECL_LIST
295        /* put variables of this type into the idroot list */
296%token <i> RING_DECL
297        /* put variables of this type into the currRing list */
[1f03aba]298%token <i> RING_DECL_LIST
299        /* put variables of this type into the currRing list */
[0e1846]300%token <i> EXAMPLE_CMD
301%token <i> EXPORT_CMD
302%token <i> HELP_CMD
303%token <i> KILL_CMD
304%token <i> LIB_CMD
305%token <i> LISTVAR_CMD
306%token <i> SETRING_CMD
307%token <i> TYPE_CMD
308
309%token <name> STRINGTOK BLOCKTOK INT_CONST
310%token <name> UNKNOWN_IDENT RINGVAR PROC_DEF
311
312/* control */
313%token <i> BREAK_CMD
314%token <i> CONTINUE_CMD
315%token <i> ELSE_CMD
316%token <i> EVAL
317%token <i> QUOTE
318%token <i> FOR_CMD
319%token <i> IF_CMD
320%token <i> SYS_BREAK
321%token <i> WHILE_CMD
322%token <i> RETURN
323%token <i> PARAMETER
324
325/* system variables */
326%token <i> SYSVAR
327
328%type <name> extendedid
329%type <lv>   rlist ordering OrderingList orderelem
330%type <name> stringexpr
331%type <lv>   expr elemexpr exprlist expr_arithmetic
332%type <lv>   declare_ip_variable left_value
333%type <i>    ordername
334%type <i>    cmdeq
335%type <i>    setrings
336%type <i>    ringcmd1
337
[2c89d2]338%type <i>    '=' '<' '>' '+' '-' COLONCOLON
[7b3094]339%type <i>    '/' '[' ']' '^' ',' ';'
[0e1846]340
341
342/*%nonassoc '=' PLUSEQUAL DOTDOT*/
[0a3ddd]343/*%nonassoc '=' DOTDOT COLONCOLON*/
[2c89d2]344%nonassoc '=' DOTDOT
[ae35b67]345%left ','
[7b3094]346%left '&'
[0e1846]347%left EQUAL_EQUAL NOTEQUAL
[7b3094]348%left '<'
[68c1c4]349%left '+' '-' ':'
350%left '/' '*'
[ed3c47]351%left UMINUS NOT
[0e1846]352%left  '^'
353%left '[' ']'
354%left '(' ')'
[ae35b67]355%left PLUSPLUS MINUSMINUS
[2c89d2]356%left COLONCOLON
[1cb879]357%left '.'
[0e1846]358
359%%
360lines:
361        /**/
362        | lines pprompt
363          {
[8141412]364            if (timerv)
[0e1846]365            {
366              writeTime("used time:");
367              startTimer();
368            }
[8141412]369            if (rtimerv)
[34ab5de]370            {
371              writeRTime("used real time:");
372              startRTimer();
373            }
[0e1846]374            prompt_char = '>';
[50cbdc]375#ifdef HAVE_SDB
[cf74099]376            if (sdb_flags & 2) { sdb_flags=1; YYERROR; }
[50cbdc]377#endif
[58bbda]378            if(siCntrlc)
379            {
[41bef1]380              WerrorS("abort...");
381              while((currentVoice!=NULL) && (currentVoice->prev!=NULL)) exitVoice();
382              if (currentVoice!=NULL) currentVoice->ifsw=0;
[057e93c]383            }
[41bef1]384            if (errorreported) /* also catches abort... */
[0e1846]385            {
386              yyerror("");
387            }
388            if (inerror==2) PrintLn();
389            errorreported = inerror = cmdtok = 0;
[bcd557]390            lastreserved = currid = NULL;
[eb84e2]391            expected_parms = siCntrlc = FALSE;
[0e1846]392          }
393        ;
394
395pprompt:
[58bbda]396        flowctrl                       /* if, while, for, proc */
[0e1846]397        | command ';'                  /* commands returning no value */
[057e93c]398          {currentVoice->ifsw=0;}
[0e1846]399        | declare_ip_variable ';'      /* default initialization */
[057e93c]400          { $1.CleanUp(); currentVoice->ifsw=0;}
[0e1846]401        | returncmd
402          {
403            YYACCEPT;
404          }
405        | SYS_BREAK
406          {
[057e93c]407            currentVoice->ifsw=0;
[8141412]408            iiDebug();
[0e1846]409          }
410        | ';'                    /* ignore empty statements */
[057e93c]411          {currentVoice->ifsw=0;}
[0e1846]412        | error ';'
413          {
414            #ifdef SIQ
415            siq=0;
416            #endif
[cf74099]417            yyInRingConstruction = FALSE;
[057e93c]418            currentVoice->ifsw=0;
[bcd557]419            if (inerror)
[ae35b67]420            {
[cde708]421/*  bison failed here*/
[ae35b67]422              if ((inerror!=3) && ($1.i<UMINUS) && ($1.i>' '))
[bcd557]423              {
424                // 1: yyerror called
425                // 2: scanner put actual string
426                // 3: error rule put token+\n
427                inerror=3;
428                Print(" error at token `%s`\n",iiTwoOps($1.i));
[ae35b67]429              }
[cde708]430/**/
431
[0e1846]432            }
433            if (!errorreported) WerrorS("...parse error");
434            yyerror("");
435            yyerrok;
[50cbdc]436#ifdef HAVE_SDB
[cf74099]437            if ((sdb_flags & 1) && currentVoice->pi!=NULL)
438            {
439              currentVoice->pi->trace_flag |=1;
440            }
441            else
[50cbdc]442#endif
[0e1846]443            if (myynest>0)
444            {
[bcd557]445              feBufferTypes t=currentVoice->Typ();
[057e93c]446              //PrintS("leaving yyparse\n");
[ae35b67]447              exitBuffer(BT_proc);
[057e93c]448              if (t==BT_example)
449                YYACCEPT;
450              else
451                YYABORT;
[0e1846]452            }
[057e93c]453            else if (currentVoice->prev!=NULL)
[0e1846]454            {
[057e93c]455              exitVoice();
[0e1846]456            }
[50cbdc]457#ifdef HAVE_SDB
[cf74099]458            if (sdb_flags &2) sdb_flags=1;
[50cbdc]459#endif
[0e1846]460          }
461        ;
462
463flowctrl: ifcmd
464          | whilecmd
[4b1f71]465          | example_dummy
[0e1846]466          | forcmd
467          | proccmd
[057e93c]468          | filecmd
469          | helpcmd
[c04b94]470          | examplecmd
[428906]471            {if (currentVoice!=NULL) currentVoice->ifsw=0;}
[0e1846]472        ;
473
[c232af]474example_dummy : EXAMPLE_CMD BLOCKTOK { omFree((ADDRESS)$2); }
[cf0863]475        ;
[4b1f71]476
[057e93c]477command: assign
478         | exportcmd
479         | killcmd
480         | listcmd
481         | parametercmd
482         | ringcmd
483         | scriptcmd
484         | setringcmd
485         | typecmd
[0e1846]486         ;
487
488assign: left_value exprlist
489          {
490            if(iiAssign(&$1,&$2)) YYERROR;
491          }
492        ;
493
494elemexpr:
495        RINGVAR
496          {
[8141412]497            if (currRing==NULL) MYYERROR("no ring active");
[c232af]498            syMake(&$$,omStrDup($1));
[0e1846]499          }
500        | extendedid
501          {
502            syMake(&$$,$1);
503          }
[2c89d2]504        | elemexpr COLONCOLON elemexpr
505          {
506            if(iiExprArith2(&$$, &$1, COLONCOLON, &$3)) YYERROR;
507          }
[1cb879]508        | elemexpr '.' elemexpr
509          {
510            if(iiExprArith2(&$$, &$1, '.', &$3)) YYERROR;
511          }
[da2bd0]512        | elemexpr '('  ')'
[0e1846]513          {
514            if(iiExprArith1(&$$,&$1,'(')) YYERROR;
515          }
[da2bd0]516        | elemexpr '(' exprlist ')'
[0e1846]517          {
[c44371]518            if ($1.rtyp==UNKNOWN)
[37dc41]519            { // for x(i)(j)
520              if(iiExprArith2(&$$,&$1,'(',&$3)) YYERROR;
521            }
522            else
523            {
524              $1.next=(leftv)omAllocBin(sleftv_bin);
525              memcpy($1.next,&$3,sizeof(sleftv));
526              if(iiExprArithM(&$$,&$1,'(')) YYERROR;
527            }
[0e1846]528          }
529        | '[' exprlist ']'
530          {
531            if (currRingHdl==NULL) MYYERROR("no ring active");
532            int j = 0;
533            memset(&$$,0,sizeof(sleftv));
534            $$.rtyp=VECTOR_CMD;
535            leftv v = &$2;
536            while (v!=NULL)
537            {
[3074334]538              int i,t;
539              sleftv tmp;
540              memset(&tmp,0,sizeof(tmp));
541              i=iiTestConvert((t=v->Typ()),POLY_CMD);
[cf74099]542              if((i==0) || (iiConvert(t /*v->Typ()*/,POLY_CMD,i,v,&tmp)))
[3074334]543              {
544                pDelete((poly *)&$$.data);
545                $2.CleanUp();
546                MYYERROR("expected '[poly,...'");
547              }
[2166ad3]548              poly p = (poly)tmp.CopyD(POLY_CMD);
[9dfc1bc]549              pSetCompP(p,++j);
550              $$.data = (void *)pAdd((poly)$$.data,p);
[3074334]551              v->next=tmp.next;tmp.next=NULL;
552              tmp.CleanUp();
[0e1846]553              v=v->next;
554            }
555            $2.CleanUp();
556          }
[922e4d]557        | INT_CONST
[0e1846]558          {
559            memset(&$$,0,sizeof($$));
[922e4d]560            int i = atoi($1);
[c232af]561            /*remember not to omFree($1)
[408aed]562            *because it is a part of the scanner buffer*/
563            $$.rtyp  = INT_CMD;
[09bbf5]564            $$.data = (void *)(long)i;
[922e4d]565
566            /* check: out of range input */
567            int l = strlen($1)+2;
[db5523]568            number n;
[922e4d]569            if (l >= MAX_INT_LEN)
570            {
[a4c74f]571              char tmp[MAX_INT_LEN+5];
[922e4d]572              sprintf(tmp,"%d",i);
573              if (strcmp(tmp,$1)!=0)
574              {
[db45a2]575                n_Read($1,&n,coeffs_BIGINT);
[db5523]576                $$.rtyp=BIGINT_CMD;
577                $$.data = n;
[922e4d]578              }
579            }
[0e1846]580          }
581        | SYSVAR
582          {
583            memset(&$$,0,sizeof($$));
584            $$.rtyp = $1;
585            $$.data = $$.Data();
586          }
587        | stringexpr
588          {
589            memset(&$$,0,sizeof($$));
590            $$.rtyp  = STRING_CMD;
591            $$.data = $1;
592          }
[da2bd0]593        | PROC_CMD '(' expr ')'
594          {
595            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
596          }
[0e1846]597        ;
598
599exprlist:
[74d2017]600        exprlist ',' expr
[0e1846]601          {
602            leftv v = &$1;
603            while (v->next!=NULL)
604            {
605              v=v->next;
606            }
[c232af]607            v->next = (leftv)omAllocBin(sleftv_bin);
[0e1846]608            memcpy(v->next,&($3),sizeof(sleftv));
609            $$ = $1;
610          }
611        | expr
612          {
613            $$ = $1;
614          }
615        ;
616
617expr:   expr_arithmetic
618          {
619            /*if ($1.typ == eunknown) YYERROR;*/
620            $$ = $1;
621          }
[c56606]622        | elemexpr       { $$ = $1; }
[ae35b67]623        | '(' exprlist ')'    { $$ = $2; }
[0e1846]624        | expr '[' expr ',' expr ']'
625          {
626            if(iiExprArith3(&$$,'[',&$1,&$3,&$5)) YYERROR;
627          }
628        | expr '[' expr ']'
629          {
630            if(iiExprArith2(&$$,&$1,'[',&$3)) YYERROR;
631          }
632        | ROOT_DECL '(' expr ')'
633          {
634            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
635          }
636        | ROOT_DECL_LIST '(' exprlist ')'
637          {
638            if(iiExprArithM(&$$,&$3,$1)) YYERROR;
639          }
640        | ROOT_DECL_LIST '(' ')'
641          {
642            if(iiExprArithM(&$$,NULL,$1)) YYERROR;
643          }
644        | RING_DECL '(' expr ')'
645          {
646            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
647          }
[1f03aba]648        | RING_DECL_LIST '(' exprlist ')'
[0e1846]649          {
650            if(iiExprArithM(&$$,&$3,$1)) YYERROR;
651          }
[1f03aba]652        | RING_DECL_LIST '(' ')'
[0e1846]653          {
654            if(iiExprArithM(&$$,NULL,$1)) YYERROR;
655          }
656        | CMD_1 '(' expr ')'
657          {
658            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
659          }
660        | CMD_2 '(' expr ',' expr ')'
661          {
662            if(iiExprArith2(&$$,&$3,$1,&$5,TRUE)) YYERROR;
663          }
664        | CMD_3 '(' expr ',' expr ',' expr ')'
665          {
666            if(iiExprArith3(&$$,$1,&$3,&$5,&$7)) YYERROR;
667          }
668        | CMD_23 '(' expr ',' expr ')'
669          {
670            if(iiExprArith2(&$$,&$3,$1,&$5,TRUE)) YYERROR;
671          }
672        | CMD_23 '(' expr ',' expr ',' expr ')'
673          {
674            if(iiExprArith3(&$$,$1,&$3,&$5,&$7)) YYERROR;
675          }
676        | CMD_12 '(' expr ')'
677          {
678            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
679          }
[7b4121]680        | CMD_13 '(' expr ')'
681          {
682            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
683          }
[0e1846]684        | CMD_12 '(' expr ',' expr ')'
685          {
686            if(iiExprArith2(&$$,&$3,$1,&$5,TRUE)) YYERROR;
687          }
688        | CMD_123 '(' expr ')'
689          {
690            if(iiExprArith1(&$$,&$3,$1)) YYERROR;
691          }
692        | CMD_123 '(' expr ',' expr ')'
693          {
694            if(iiExprArith2(&$$,&$3,$1,&$5,TRUE)) YYERROR;
695          }
[7b4121]696        | CMD_13 '(' expr ',' expr ',' expr ')'
697          {
698            if(iiExprArith3(&$$,$1,&$3,&$5,&$7)) YYERROR;
699          }
[0e1846]700        | CMD_123 '(' expr ',' expr ',' expr ')'
701          {
702            if(iiExprArith3(&$$,$1,&$3,&$5,&$7)) YYERROR;
703          }
[64d729]704        | CMD_M '(' ')'
705          {
706            if(iiExprArithM(&$$,NULL,$1)) YYERROR;
707          }
708        | CMD_M '(' exprlist ')'
709          {
710            if(iiExprArithM(&$$,&$3,$1)) YYERROR;
711          }
[0e1846]712        | MATRIX_CMD '(' expr ',' expr ',' expr ')'
713          {
714            if(iiExprArith3(&$$,MATRIX_CMD,&$3,&$5,&$7)) YYERROR;
715          }
716        | MATRIX_CMD '(' expr ')'
717          {
718            if(iiExprArith1(&$$,&$3,MATRIX_CMD)) YYERROR;
719          }
[4b2155]720        | INTMAT_CMD '(' expr ',' expr ',' expr ')'
721          {
722            if(iiExprArith3(&$$,INTMAT_CMD,&$3,&$5,&$7)) YYERROR;
723          }
[0e1846]724        | INTMAT_CMD '(' expr ')'
725          {
726            if(iiExprArith1(&$$,&$3,INTMAT_CMD)) YYERROR;
727          }
[cf74099]728        | RING_CMD '(' rlist ',' rlist ',' ordering ')'
729          {
730            if(iiExprArith3(&$$,RING_CMD,&$3,&$5,&$7)) YYERROR;
731          }
732        | RING_CMD '(' expr ')'
733          {
734            if(iiExprArith1(&$$,&$3,RING_CMD)) YYERROR;
735          }
[0e1846]736        | quote_start expr quote_end
737          {
738            $$=$2;
739          }
740        | quote_start expr '=' expr quote_end
741          {
742            #ifdef SIQ
743            siq++;
744            if (siq>0)
745            { if (iiExprArith2(&$$,&$2,'=',&$4)) YYERROR; }
746            else
747            #endif
748            {
749              memset(&$$,0,sizeof($$));
750              $$.rtyp=NONE;
751              if (iiAssign(&$2,&$4)) YYERROR;
752            }
753            #ifdef SIQ
754            siq--;
755            #endif
756          }
757        | EVAL  '('
758          {
759            #ifdef SIQ
760            siq--;
761            #endif
762          }
763          expr ')'
764          {
765            #ifdef SIQ
766            if (siq<=0) $4.Eval();
767            #endif
768            $$=$4;
769            #ifdef SIQ
770            siq++;
771            #endif
772          }
773          ;
774
775quote_start:    QUOTE  '('
776          {
777            #ifdef SIQ
778            siq++;
779            #endif
780          }
781          ;
782
783quote_end: ')'
784          {
785            #ifdef SIQ
786            siq--;
787            #endif
788          }
789          ;
790
791expr_arithmetic:
[c56606]792          expr PLUSPLUS     %prec PLUSPLUS
[0e1846]793          {
794            if(iiExprArith1(&$$,&$1,PLUSPLUS)) YYERROR;
795          }
[c56606]796        | expr MINUSMINUS   %prec MINUSMINUS
[0e1846]797          {
798            if(iiExprArith1(&$$,&$1,MINUSMINUS)) YYERROR;
799          }
[c56606]800        | expr '+' expr
[0e1846]801          {
802            if(iiExprArith2(&$$,&$1,'+',&$3)) YYERROR;
803          }
[c56606]804        | expr '-' expr
[0e1846]805          {
806            if(iiExprArith2(&$$,&$1,'-',&$3)) YYERROR;
807          }
[c56606]808        | expr '/' expr
[0e1846]809          {
[db28cee]810            if(iiExprArith2(&$$,&$1,$<i>2,&$3)) YYERROR;
[c56606]811          }
812        | expr '^' expr
[0e1846]813          {
814            if(iiExprArith2(&$$,&$1,'^',&$3)) YYERROR;
815          }
[c56606]816        | expr '<' expr
[0e1846]817          {
[7b3094]818            if(iiExprArith2(&$$,&$1,$<i>2,&$3)) YYERROR;
[0e1846]819          }
[c56606]820        | expr '&' expr
[0e1846]821          {
[7b3094]822            if(iiExprArith2(&$$,&$1,$<i>2,&$3)) YYERROR;
[0e1846]823          }
[c56606]824        | expr NOTEQUAL expr
[0e1846]825          {
826            if(iiExprArith2(&$$,&$1,NOTEQUAL,&$3)) YYERROR;
827          }
[c56606]828        | expr EQUAL_EQUAL expr
[0e1846]829          {
830            if(iiExprArith2(&$$,&$1,EQUAL_EQUAL,&$3)) YYERROR;
831          }
832        | expr DOTDOT expr
833          {
834            if(iiExprArith2(&$$,&$1,DOTDOT,&$3)) YYERROR;
835          }
[62b87d]836        | expr ':' expr
837          {
838            if(iiExprArith2(&$$,&$1,':',&$3)) YYERROR;
839          }
[b77927]840        | NOT expr
[0e1846]841          {
842            memset(&$$,0,sizeof($$));
[ed3c47]843            int i; TESTSETINT($2,i);
[0e1846]844            $$.rtyp  = INT_CMD;
[09bbf5]845            $$.data = (void *)(long)(i == 0 ? 1 : 0);
[0e1846]846          }
847        | '-' expr %prec UMINUS
848          {
849            if(iiExprArith1(&$$,&$2,'-')) YYERROR;
850          }
851        ;
852
853left_value:
854        declare_ip_variable cmdeq  { $$ = $1; }
[057e93c]855        | exprlist '='
856          {
[3c1510]857            if ($1.rtyp==0)
[057e93c]858            {
[0a3ddd]859              Werror("`%s` is undefined",$1.Fullname());
[057e93c]860              YYERROR;
[3c1510]861            }
[254a326]862            else if (($1.rtyp==MODUL_CMD)
863            // matrix m; m[2]=...
864            && ($1.e!=NULL) && ($1.e->next==NULL))
865            {
866              MYYERROR("matrix must have 2 indices");
867            }
[057e93c]868            $$ = $1;
[3c1510]869          }
[0e1846]870        ;
871
872
873extendedid:
874        UNKNOWN_IDENT
875        | '`' expr '`'
876          {
877            if ($2.Typ()!=STRING_CMD)
878            {
879              MYYERROR("string expression expected");
880            }
[2166ad3]881            $$ = (char *)$2.CopyD(STRING_CMD);
[0e1846]882            $2.CleanUp();
883          }
884        ;
885
886declare_ip_variable:
887        ROOT_DECL elemexpr
888          {
[bd4cb92]889            if (iiDeclCommand(&$$,&$2,myynest,$1,&($2.req_packhdl->idroot)))
890              YYERROR;
[0e1846]891          }
892        | ROOT_DECL_LIST elemexpr
893          {
[bd4cb92]894            if (iiDeclCommand(&$$,&$2,myynest,$1,&($2.req_packhdl->idroot)))
895              YYERROR;
[0e1846]896          }
897        | RING_DECL elemexpr
898          {
[0a3ddd]899            if (iiDeclCommand(&$$,&$2,myynest,$1,&(currRing->idroot), TRUE)) YYERROR;
[0e1846]900          }
[1f03aba]901        | RING_DECL_LIST elemexpr
[0e1846]902          {
[0a3ddd]903            if (iiDeclCommand(&$$,&$2,myynest,$1,&(currRing->idroot), TRUE)) YYERROR;
[0e1846]904          }
905        | MATRIX_CMD elemexpr '[' expr ']' '[' expr ']'
906          {
[0a3ddd]907            if (iiDeclCommand(&$$,&$2,myynest,$1,&(currRing->idroot), TRUE)) YYERROR;
[8141412]908            int r; TESTSETINT($4,r);
909            int c; TESTSETINT($7,c);
910            if (r < 1)
911              MYYERROR("rows must be greater than 0");
912            if (c < 0)
913              MYYERROR("cols must be greater than -1");
914            leftv v=&$$;
915            //while (v->next!=NULL) { v=v->next; }
916            idhdl h=(idhdl)v->data;
917            idDelete(&IDIDEAL(h));
918            IDMATRIX(h) = mpNew(r,c);
919            if (IDMATRIX(h)==NULL) YYERROR;
[0e1846]920          }
921        | MATRIX_CMD elemexpr
922          {
[0a3ddd]923            if (iiDeclCommand(&$$,&$2,myynest,$1,&(currRing->idroot), TRUE)) YYERROR;
[0e1846]924          }
925        | INTMAT_CMD elemexpr '[' expr ']' '[' expr ']'
926          {
[8141412]927            int r; TESTSETINT($4,r);
928            int c; TESTSETINT($7,c);
929            if (r < 1)
930              MYYERROR("rows must be greater than 0");
931            if (c < 0)
932              MYYERROR("cols must be greater than -1");
[bd4cb92]933            if (iiDeclCommand(&$$,&$2,myynest,$1,&($2.req_packhdl->idroot)))
934              YYERROR;
[8141412]935            leftv v=&$$;
936            idhdl h=(idhdl)v->data;
937            delete IDINTVEC(h);
[c232af]938            IDINTVEC(h) = new intvec(r,c,0);
[8141412]939            if (IDINTVEC(h)==NULL) YYERROR;
[0e1846]940          }
941        | INTMAT_CMD elemexpr
942          {
[bd4cb92]943            if (iiDeclCommand(&$$,&$2,myynest,$1,&($2.req_packhdl->idroot)))
944              YYERROR;
[0e1846]945            leftv v=&$$;
946            idhdl h;
947            do
948            {
949               h=(idhdl)v->data;
950               delete IDINTVEC(h);
[c232af]951               IDINTVEC(h) = new intvec(1,1,0);
[0e1846]952               v=v->next;
953            } while (v!=NULL);
954          }
955        | declare_ip_variable ',' elemexpr
956          {
957            int t=$1.Typ();
958            sleftv r;
959            memset(&r,0,sizeof(sleftv));
960            if ((BEGIN_RING<t) && (t<END_RING))
961            {
[bd4cb92]962              if (iiDeclCommand(&r,&$3,myynest,t,&(currRing->idroot), TRUE))
963                YYERROR;
[0e1846]964            }
965            else
966            {
[bd4cb92]967              if (iiDeclCommand(&r,&$3,myynest,t,&($3.req_packhdl->idroot)))
968                YYERROR;
[0e1846]969            }
970            leftv v=&$1;
971            while (v->next!=NULL) v=v->next;
[c232af]972            v->next=(leftv)omAllocBin(sleftv_bin);
[0e1846]973            memcpy(v->next,&r,sizeof(sleftv));
974            $$=$1;
975          }
[58bbda]976        | PROC_CMD elemexpr
977          {
[bd4cb92]978            if (iiDeclCommand(&$$,&$2,myynest,$1,&($2.req_packhdl->idroot)))
979              YYERROR;
[58bbda]980          }
[0e1846]981        ;
982
983stringexpr:
984        STRINGTOK
985        ;
986
987rlist:
988        expr
989        | '(' expr ',' exprlist ')'
990          {
991            leftv v = &$2;
992            while (v->next!=NULL)
993            {
994              v=v->next;
995            }
[c232af]996            v->next = (leftv)omAllocBin(sleftv_bin);
[0e1846]997            memcpy(v->next,&($4),sizeof(sleftv));
998            $$ = $2;
999          }
1000        ;
1001
1002ordername:
1003        UNKNOWN_IDENT
1004        {
[cf74099]1005          // let rInit take care of any errors
[7df2ef]1006          $$=rOrderName($1);
[0e1846]1007        }
1008        ;
1009
1010orderelem:
1011        ordername
1012          {
1013            memset(&$$,0,sizeof($$));
[c232af]1014            intvec *iv = new intvec(2);
[0e1846]1015            (*iv)[0] = 1;
1016            (*iv)[1] = $1;
1017            $$.rtyp = INTVEC_CMD;
1018            $$.data = (void *)iv;
1019          }
1020        | ordername '(' exprlist ')'
1021          {
1022            memset(&$$,0,sizeof($$));
1023            leftv sl = &$3;
1024            int slLength;
1025            {
1026              slLength =  exprlist_length(sl);
1027              int l = 2 +  slLength;
[c232af]1028              intvec *iv = new intvec(l);
[0e1846]1029              (*iv)[0] = slLength;
1030              (*iv)[1] = $1;
1031
1032              int i = 2;
1033              while ((i<l) && (sl!=NULL))
1034              {
1035                if (sl->Typ() == INT_CMD)
1036                {
[7447d8]1037                  (*iv)[i++] = (int)((long)(sl->Data()));
[0e1846]1038                }
1039                else if ((sl->Typ() == INTVEC_CMD)
1040                ||(sl->Typ() == INTMAT_CMD))
1041                {
1042                  intvec *ivv = (intvec *)(sl->Data());
1043                  int ll = 0,l = ivv->length();
1044                  for (; l>0; l--)
1045                  {
1046                    (*iv)[i++] = (*ivv)[ll++];
1047                  }
1048                }
1049                else
1050                {
1051                  delete iv;
1052                  $3.CleanUp();
1053                  MYYERROR("wrong type in ordering");
1054                }
1055                sl = sl->next;
1056              }
1057              $$.rtyp = INTVEC_CMD;
1058              $$.data = (void *)iv;
1059            }
1060            $3.CleanUp();
1061          }
1062        ;
1063
1064OrderingList:
1065        orderelem
1066        |  orderelem ',' OrderingList
1067          {
1068            $$ = $1;
[c232af]1069            $$.next = (sleftv *)omAllocBin(sleftv_bin);
[0e1846]1070            memcpy($$.next,&$3,sizeof(sleftv));
1071          }
1072        ;
1073
1074ordering:
1075        orderelem
1076        | '(' OrderingList ')'
1077          {
1078            $$ = $2;
1079          }
1080        ;
1081
1082cmdeq:  '='
1083          {
1084            expected_parms = TRUE;
1085          }
1086        ;
1087
1088
1089/* --------------------------------------------------------------------*/
1090/* section of pure commands                                            */
1091/* --------------------------------------------------------------------*/
1092
1093filecmd:
[057e93c]1094        '<' stringexpr
[7b3094]1095          { if ($<i>1 != '<') YYERROR;
[97f271]1096            if((feFilePending=feFopen($2,"r",NULL,TRUE))==NULL) YYERROR; }
[057e93c]1097        ';'
1098          { newFile($2,feFilePending); }
[0e1846]1099        ;
1100
1101helpcmd:
[057e93c]1102        HELP_CMD STRINGTOK ';'
[0e1846]1103          {
[9c35ef]1104            feHelp($2);
[c232af]1105            omFree((ADDRESS)$2);
[0e1846]1106          }
[057e93c]1107        | HELP_CMD ';'
[0e1846]1108          {
[9c35ef]1109            feHelp(NULL);
[0e1846]1110          }
1111        ;
1112
[c04b94]1113examplecmd:
1114        EXAMPLE_CMD STRINGTOK ';'
1115          {
1116            singular_example($2);
[c232af]1117            omFree((ADDRESS)$2);
[c04b94]1118          }
1119       ;
1120
[0e1846]1121exportcmd:
1122        EXPORT_CMD exprlist
1123        {
[9eefa5]1124          if (basePack!=$2.req_packhdl)
1125          {
[a443dd]1126            if(iiExport(&$2,0,currPackHdl)) YYERROR;
[9eefa5]1127          }
1128          else
[573da6]1129            if (iiExport(&$2,0)) YYERROR;
1130        }
[0e1846]1131        ;
1132
1133killcmd:
[7b913ac]1134        KILL_CMD elemexpr
[b77927]1135        {
[7b913ac]1136          leftv v=&$2;
1137          if (v->rtyp!=IDHDL)
1138          {
1139            if (v->name!=NULL)
1140            {
1141               Werror("`%s` is undefined in kill",v->name);
1142            }
1143            else               WerrorS("kill what ?");
1144          }
1145          else
1146          {
1147            killhdl((idhdl)v->data,v->req_packhdl);
1148          }
[9eefa5]1149        }
[7b913ac]1150        | killcmd ',' elemexpr
[9eefa5]1151        {
[7b913ac]1152          leftv v=&$3;
1153          if (v->rtyp!=IDHDL)
1154          {
1155            if (v->name!=NULL)
1156            {
1157               Werror("`%s` is undefined in kill",v->name);
1158            }
1159            else               WerrorS("kill what ?");
1160          }
1161          else
1162          {
1163            killhdl((idhdl)v->data,v->req_packhdl);
1164          }
[b77927]1165        }
[0e1846]1166        ;
1167
1168listcmd:
1169        LISTVAR_CMD '(' ROOT_DECL ')'
1170          {
1171            list_cmd($3,NULL,"// ",TRUE);
1172          }
1173        | LISTVAR_CMD '(' ROOT_DECL_LIST ')'
1174          {
1175            list_cmd($3,NULL,"// ",TRUE);
1176          }
1177        | LISTVAR_CMD '(' RING_DECL ')'
1178          {
1179            if ($3==QRING_CMD) $3=RING_CMD;
1180            list_cmd($3,NULL,"// ",TRUE);
1181          }
[1f03aba]1182        | LISTVAR_CMD '(' RING_DECL_LIST ')'
[0e1846]1183          {
1184            list_cmd($3,NULL,"// ",TRUE);
1185          }
1186        | LISTVAR_CMD '(' RING_CMD ')'
1187          {
1188            list_cmd(RING_CMD,NULL,"// ",TRUE);
1189          }
1190        | LISTVAR_CMD '(' MATRIX_CMD ')'
1191          {
1192            list_cmd(MATRIX_CMD,NULL,"// ",TRUE);
1193           }
1194        | LISTVAR_CMD '(' INTMAT_CMD ')'
1195          {
1196            list_cmd(INTMAT_CMD,NULL,"// ",TRUE);
1197          }
1198        | LISTVAR_CMD '(' PROC_CMD ')'
1199          {
1200            list_cmd(PROC_CMD,NULL,"// ",TRUE);
1201          }
1202        | LISTVAR_CMD '(' elemexpr ')'
1203          {
[ad0463]1204            list_cmd(0,$3.Fullname(),"// ",TRUE);
[0a3ddd]1205            $3.CleanUp();
1206          }
1207        | LISTVAR_CMD '(' elemexpr ',' ROOT_DECL ')'
1208          {
[ad0463]1209            if($3.Typ() == PACKAGE_CMD)
[0a3ddd]1210              list_cmd($5,NULL,"// ",TRUE);
1211            $3.CleanUp();
1212          }
1213        | LISTVAR_CMD '(' elemexpr ',' ROOT_DECL_LIST ')'
1214          {
[ad0463]1215            if($3.Typ() == PACKAGE_CMD)
[0a3ddd]1216              list_cmd($5,NULL,"// ",TRUE);
1217            $3.CleanUp();
1218          }
1219        | LISTVAR_CMD '(' elemexpr ',' RING_DECL ')'
1220          {
[ad0463]1221            if($3.Typ() == PACKAGE_CMD)
[0a3ddd]1222              list_cmd($5,NULL,"// ",TRUE);
1223            $3.CleanUp();
1224          }
[1f03aba]1225        | LISTVAR_CMD '(' elemexpr ',' RING_DECL_LIST ')'
[0a3ddd]1226          {
[ad0463]1227            if($3.Typ() == PACKAGE_CMD)
[0a3ddd]1228              list_cmd($5,NULL,"// ",TRUE);
1229            $3.CleanUp();
1230          }
1231        | LISTVAR_CMD '(' elemexpr ',' RING_CMD ')'
1232          {
[ad0463]1233            if($3.Typ() == PACKAGE_CMD)
1234              list_cmd($5,NULL,"// ",TRUE);
[0a3ddd]1235            $3.CleanUp();
1236          }
1237        | LISTVAR_CMD '(' elemexpr ',' MATRIX_CMD ')'
1238          {
[ad0463]1239            if($3.Typ() == PACKAGE_CMD)
1240              list_cmd($5,NULL,"// ",TRUE);
[0a3ddd]1241            $3.CleanUp();
1242          }
1243        | LISTVAR_CMD '(' elemexpr ',' INTMAT_CMD ')'
1244          {
[ad0463]1245            if($3.Typ() == PACKAGE_CMD)
1246              list_cmd($5,NULL,"// ",TRUE);
[0a3ddd]1247            $3.CleanUp();
1248          }
1249        | LISTVAR_CMD '(' elemexpr ',' PROC_CMD ')'
1250          {
[ad0463]1251            if($3.Typ() == PACKAGE_CMD)
1252              list_cmd($5,NULL,"// ",TRUE);
[0a3ddd]1253            $3.CleanUp();
1254          }
[d721b0]1255        //| LISTVAR_CMD '(' elemexpr ',' elemexpr ')'
1256        //  {
1257        //    //if($3.Typ() == PACKAGE_CMD)
1258        //    //  list_cmd($5,NULL,"// ",TRUE);
1259        //    $3.CleanUp();
1260        //  }
[0e1846]1261        | LISTVAR_CMD '(' ')'
1262          {
1263            list_cmd(-1,NULL,"// ",TRUE);
1264          }
1265        ;
1266
1267ringcmd1:
[34fbd93]1268       RING_CMD { yyInRingConstruction = TRUE; }
[0e1846]1269       ;
1270
1271ringcmd:
1272        ringcmd1
1273          elemexpr cmdeq
1274          rlist     ','      /* description of coeffs */
1275          rlist     ','      /* var names */
1276          ordering           /* list of (multiplier ordering (weight(s))) */
1277          {
[85e68dd]1278            const char *ring_name = $2.name;
[cf74099]1279            ring b=
1280            rInit(&$4,            /* characteristik and list of parameters*/
[c4b69a]1281                  &$6,            /* names of ringvariables */
[73877a]1282                  &$8);            /* ordering */
[cf74099]1283            idhdl newRingHdl=NULL;
[d721b0]1284
[cf74099]1285            if (b!=NULL)
1286            {
[74bb49]1287              newRingHdl=enterid(ring_name, myynest, RING_CMD,
[16566b]1288                                   &($2.req_packhdl->idroot),FALSE);
[3b1a83c]1289              $2.CleanUp();
[cf74099]1290              if (newRingHdl!=NULL)
1291              {
1292                IDRING(newRingHdl)=b;
1293              }
1294              else
1295              {
1296                rKill(b);
1297              }
1298            }
1299            yyInRingConstruction = FALSE;
1300            if (newRingHdl==NULL)
[c4b69a]1301            {
1302              MYYERROR("cannot make ring");
1303            }
[7df2ef]1304            else
1305            {
[cf74099]1306              rSetHdl(newRingHdl);
[7df2ef]1307            }
[0e1846]1308          }
1309        | ringcmd1 elemexpr
1310          {
[85e68dd]1311            const char *ring_name = $2.name;
[0a3ddd]1312            if (!inerror) rDefault(ring_name);
[cf74099]1313            yyInRingConstruction = FALSE;
[3b1a83c]1314            $2.CleanUp();
[0e1846]1315          }
1316        ;
1317
1318scriptcmd:
[d87eb0]1319         SYSVAR stringexpr
1320          {
[22ed4c]1321            if (($1!=LIB_CMD)||(iiLibCmd($2,TRUE,TRUE,TRUE)))
[d87eb0]1322            //if ($1==LIB_CMD)
1323            //{
1324            //  sleftv tmp;
1325            //  if(iiExprArith1(&tmp,&$2,LIB_CMD)) YYERROR;
1326            //}
1327            //else
1328                YYERROR;
[0e1846]1329          }
1330        ;
1331
1332setrings:  SETRING_CMD | KEEPRING_CMD ;
1333
1334setringcmd:
1335        setrings expr
1336          {
1337            if (($1==KEEPRING_CMD) && (myynest==0))
1338               MYYERROR("only inside a proc allowed");
1339            const char * n=$2.Name();
1340            if ((($2.Typ()==RING_CMD)||($2.Typ()==QRING_CMD))
1341            && ($2.rtyp==IDHDL))
1342            {
1343              idhdl h=(idhdl)$2.data;
[6d281ac]1344              if ($2.e!=NULL) h=rFindHdl((ring)$2.Data(),NULL, NULL);
[a3bc95e]1345              //Print("setring %s lev %d (ptr:%x)\n",IDID(h),IDLEV(h),IDRING(h));
[0e1846]1346              if ($1==KEEPRING_CMD)
1347              {
1348                if (h!=NULL)
1349                {
1350                  if (IDLEV(h)!=0)
1351                  {
1352                    if (iiExport(&$2,myynest-1)) YYERROR;
[9bc0b8]1353#if 1
[1db74ad]1354                    idhdl p=IDRING(h)->idroot;
1355                    idhdl root=p;
1356                    int prevlev=myynest-1;
1357                    while (p!=NULL)
1358                    {
1359                      if (IDLEV(p)==myynest)
[0e1846]1360                      {
[1db74ad]1361                        idhdl old=root->get(IDID(p),prevlev);
1362                        if (old!=NULL)
[b77927]1363                        {
[1db74ad]1364                          if (BVERBOSE(V_REDEFINE))
1365                            Warn("redefining %s",IDID(p));
1366                          killhdl2(old,&root,IDRING(h));
1367                          IDRING(h)->idroot=root;
[b77927]1368                        }
[1db74ad]1369                        IDLEV(p)=prevlev;
[0e1846]1370                      }
[1db74ad]1371                      p=IDNEXT(p);
1372                    }
[9bc0b8]1373#endif
[0e1846]1374                  }
[77ff8e]1375#ifdef USE_IILOCALRING
[0e1846]1376                  iiLocalRing[myynest-1]=IDRING(h);
[a3bc95e]1377#endif
[573da6]1378                  procstack->cRing=IDRING(h);
1379                  procstack->cRingHdl=h;
[0e1846]1380                }
1381                else
1382                {
1383                  Werror("%s is no identifier",n);
1384                  $2.CleanUp();
1385                  YYERROR;
1386                }
1387              }
[cf42ab1]1388              if (h!=NULL) rSetHdl(h);
[0e1846]1389              else
1390              {
1391                Werror("cannot find the name of the basering %s",n);
1392                $2.CleanUp();
1393                YYERROR;
1394              }
1395              $2.CleanUp();
1396            }
1397            else
1398            {
1399              Werror("%s is no name of a ring/qring",n);
1400              $2.CleanUp();
1401              YYERROR;
1402            }
1403          }
1404        ;
1405
1406typecmd:
1407        TYPE_CMD expr
1408          {
[103560]1409            type_cmd(&($2));
[0e1846]1410          }
1411        | exprlist
1412          {
1413            //Print("typ is %d, rtyp:%d\n",$1.Typ(),$1.rtyp);
1414            #ifdef SIQ
1415            if ($1.rtyp!=COMMAND)
1416            {
1417            #endif
1418              if ($1.Typ()==UNKNOWN)
1419              {
1420                if ($1.name!=NULL)
1421                {
1422                  Werror("`%s` is undefined",$1.name);
[c232af]1423                  omFree((ADDRESS)$1.name);
[0e1846]1424                }
1425                YYERROR;
1426              }
1427            #ifdef SIQ
1428            }
1429            #endif
1430            $1.Print(&sLastPrinted);
[73194e]1431            $1.CleanUp(currRing);
[ae35b67]1432            if (errorreported) YYERROR;
[0e1846]1433          }
1434        ;
1435
1436/* --------------------------------------------------------------------*/
1437/* section of flow control                                             */
1438/* --------------------------------------------------------------------*/
1439
1440ifcmd: IF_CMD '(' expr ')' BLOCKTOK
1441          {
[8141412]1442            int i; TESTSETINT($3,i);
1443            if (i!=0)
[0e1846]1444            {
1445              newBuffer( $5, BT_if);
1446            }
1447            else
1448            {
[c232af]1449              omFree((ADDRESS)$5);
[057e93c]1450              currentVoice->ifsw=1;
[0e1846]1451            }
1452          }
1453        | ELSE_CMD BLOCKTOK
1454          {
[057e93c]1455            if (currentVoice->ifsw==1)
[0e1846]1456            {
[057e93c]1457              currentVoice->ifsw=0;
[8141412]1458              newBuffer( $2, BT_else);
[0e1846]1459            }
1460            else
1461            {
[057e93c]1462              if (currentVoice->ifsw!=2)
[0e1846]1463              {
[8141412]1464                Warn("`else` without `if` in level %d",myynest);
[0e1846]1465              }
[c232af]1466              omFree((ADDRESS)$2);
[0e1846]1467            }
[057e93c]1468            currentVoice->ifsw=0;
[0e1846]1469          }
1470        | IF_CMD '(' expr ')' BREAK_CMD
1471          {
[8141412]1472            int i; TESTSETINT($3,i);
1473            if (i)
[0e1846]1474            {
[8141412]1475              if (exitBuffer(BT_break)) YYERROR;
[0e1846]1476            }
[057e93c]1477            currentVoice->ifsw=0;
[0e1846]1478          }
1479        | BREAK_CMD
1480          {
[8141412]1481            if (exitBuffer(BT_break)) YYERROR;
[057e93c]1482            currentVoice->ifsw=0;
[0e1846]1483          }
1484        | CONTINUE_CMD
1485          {
[057e93c]1486            if (contBuffer(BT_break)) YYERROR;
1487            currentVoice->ifsw=0;
[0e1846]1488          }
1489      ;
1490
1491whilecmd:
1492        WHILE_CMD STRINGTOK BLOCKTOK
1493          {
1494            /* -> if(!$2) break; $3; continue;*/
[c232af]1495            char * s = (char *)omAlloc( strlen($2) + strlen($3) + 36);
[0e1846]1496            sprintf(s,"whileif (!(%s)) break;\n%scontinue;\n " ,$2,$3);
1497            newBuffer(s,BT_break);
[c232af]1498            omFree((ADDRESS)$2);
1499            omFree((ADDRESS)$3);
[0e1846]1500          }
1501        ;
1502
1503forcmd:
1504        FOR_CMD STRINGTOK STRINGTOK STRINGTOK BLOCKTOK
1505          {
1506            /* $2 */
1507            /* if (!$3) break; $5; $4; continue; */
[c232af]1508            char * s = (char *)omAlloc( strlen($3)+strlen($4)+strlen($5)+36);
[0e1846]1509            sprintf(s,"forif (!(%s)) break;\n%s%s;\ncontinue;\n "
1510                   ,$3,$5,$4);
[c232af]1511            omFree((ADDRESS)$3);
1512            omFree((ADDRESS)$4);
1513            omFree((ADDRESS)$5);
[0e1846]1514            newBuffer(s,BT_break);
[c232af]1515            s = (char *)omAlloc( strlen($2) + 3);
[0e1846]1516            sprintf(s,"%s;\n",$2);
[c232af]1517            omFree((ADDRESS)$2);
[0e1846]1518            newBuffer(s,BT_if);
1519          }
1520        ;
1521
1522proccmd:
1523        PROC_CMD extendedid BLOCKTOK
1524          {
[057e93c]1525            procinfov pi;
[f7ac05]1526            idhdl h = enterid($2,myynest,PROC_CMD,&IDROOT,TRUE);
[3b1a83c]1527            if (h==NULL) {omFree((ADDRESS)$2);omFree((ADDRESS)$3); YYERROR;}
[057e93c]1528            iiInitSingularProcinfo(IDPROC(h),"", $2, 0, 0);
[c232af]1529            IDPROC(h)->data.s.body = (char *)omAlloc(strlen($3)+31);;
[057e93c]1530            sprintf(IDPROC(h)->data.s.body,"parameter list #;\n%s;return();\n\n",$3);
[c232af]1531            omFree((ADDRESS)$3);
[3b1a83c]1532            omFree((ADDRESS)$2);
[0e1846]1533          }
1534        | PROC_DEF STRINGTOK BLOCKTOK
[057e93c]1535          {
[f7ac05]1536            idhdl h = enterid($1,myynest,PROC_CMD,&IDROOT,TRUE);
[0e1846]1537            if (h==NULL)
1538            {
[3b1a83c]1539              omFree((ADDRESS)$1);
[c232af]1540              omFree((ADDRESS)$2);
1541              omFree((ADDRESS)$3);
[0e1846]1542              YYERROR;
1543            }
1544            char *args=iiProcArgs($2,FALSE);
[c232af]1545            omFree((ADDRESS)$2);
[509f7da]1546            procinfov pi;
[057e93c]1547            iiInitSingularProcinfo(IDPROC(h),"", $1, 0, 0);
[c232af]1548            IDPROC(h)->data.s.body = (char *)omAlloc(strlen($3)+strlen(args)+14);;
[057e93c]1549            sprintf(IDPROC(h)->data.s.body,"%s\n%s;return();\n\n",args,$3);
[c232af]1550            omFree((ADDRESS)args);
1551            omFree((ADDRESS)$3);
[3b1a83c]1552            omFree((ADDRESS)$1);
[0e1846]1553          }
[a7fc7dd]1554        | PROC_DEF STRINGTOK STRINGTOK BLOCKTOK
1555          {
[c232af]1556            omFree((ADDRESS)$3);
[509f7da]1557            idhdl h = enterid($1,myynest,PROC_CMD,&IDROOT,TRUE);
[a7fc7dd]1558            if (h==NULL)
1559            {
[3b1a83c]1560              omFree((ADDRESS)$1);
[c232af]1561              omFree((ADDRESS)$2);
1562              omFree((ADDRESS)$4);
[a7fc7dd]1563              YYERROR;
1564            }
1565            char *args=iiProcArgs($2,FALSE);
[c232af]1566            omFree((ADDRESS)$2);
[509f7da]1567            procinfov pi;
[a7fc7dd]1568            iiInitSingularProcinfo(IDPROC(h),"", $1, 0, 0);
[3b1a83c]1569            omFree((ADDRESS)$1);
[c232af]1570            IDPROC(h)->data.s.body = (char *)omAlloc(strlen($4)+strlen(args)+14);;
[a7fc7dd]1571            sprintf(IDPROC(h)->data.s.body,"%s\n%s;return();\n\n",args,$4);
[c232af]1572            omFree((ADDRESS)args);
1573            omFree((ADDRESS)$4);
[a7fc7dd]1574          }
[0e1846]1575        ;
1576
1577parametercmd:
1578        PARAMETER declare_ip_variable
1579          {
[ea947e]1580            // decl. of type proc p(int i)
1581            if ($1==PARAMETER)  { if (iiParameter(&$2)) YYERROR; }
1582            else                { if (iiAlias(&$2)) YYERROR; }
[0e1846]1583          }
1584        | PARAMETER expr
1585          {
[ea947e]1586            // decl. of type proc p(i)
[0e1846]1587            sleftv tmp_expr;
[ea947e]1588            if ($1==ALIAS_CMD) MYYERROR("alias requires a type");
[46d09b]1589            if ((iiDeclCommand(&tmp_expr,&$2,myynest,DEF_CMD,&IDROOT))
[8141412]1590            || (iiParameter(&tmp_expr)))
1591              YYERROR;
[0e1846]1592          }
1593        ;
1594
1595returncmd:
1596        RETURN '(' exprlist ')'
1597          {
[057e93c]1598            if(iiRETURNEXPR==NULL) YYERROR;
[0e1846]1599            iiRETURNEXPR[myynest].Copy(&$3);
1600            $3.CleanUp();
1601            if (exitBuffer(BT_proc)) YYERROR;
1602          }
1603        | RETURN '(' ')'
1604          {
[e13573]1605            if ($1==RETURN)
1606            {
1607              if(iiRETURNEXPR==NULL) YYERROR;
1608              iiRETURNEXPR[myynest].Init();
1609              iiRETURNEXPR[myynest].rtyp=NONE;
1610              if (exitBuffer(BT_proc)) YYERROR;
1611            }
[0e1846]1612          }
1613        ;
Note: See TracBrowser for help on using the repository browser.