source: git/Singular/grammar.y @ d18870

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