Added upstream from http://ftp.icm.edu.pl/pub/loglan/
[loglan.git] / loglan96 / loglan93 / syntax.y
1 //****************************************************************
2 //*                                                              *
3 //*     Syntax.y : Grammar for the LOGLAN-82 and the LOGLAN-93   *
4 //*                languages.                                    *
5 //*                                                              *
6 //* (c) LITA, university of PAU (France), summer 1993.           *
7 //****************************************************************
8
9 %{
10
11 #ifdef RULES_DEBUG
12
13 #define RULES_DEBUG_printf(a) fprintf(stderr,a)
14 #define RULES_ERROR_DEBUG
15
16 #else
17
18 #define RULES_DEBUG_printf(a)
19
20 #endif
21
22 #ifdef RULES_ERROR_DEBUG
23
24 #define RULES_ERROR_printf(a) fprintf(stderr,a)
25
26 #else
27
28 #define RULES_ERROR_printf(a)
29
30 #endif
31
32 #ifndef SYNTAX_ONLY
33
34 #define SEMANTIC(a) a
35
36 #include <math.h>
37 #include <String.h>
38 #include <iostream.h>
39 #include "Objects.h"
40 #include "Expr.h"
41 #include "Instr.h"
42
43 extern int BeginningOfLine;
44
45 #else
46
47 #define SEMANTIC(a)
48
49 #endif
50
51 void initialize( void );
52 int  yylex( void );
53 int  line_number;
54 int  yyerror( void );
55 int  yyerror( char * );
56
57 %}
58
59 %union {
60   Expression  *Expr;
61   Instruction *Instr;
62   Block       *ThisBlock;
63   Location    *ThisLoc;
64   BoolOpType   bool;
65   ArithOpType  arith;
66   ObjOpType    object;
67   OneArgJob    ThisArgJob;
68   LocInt       ThisInt;
69   LocDouble    ThisReal;
70   LocChar      ThisChar;
71   LocStr       ThisString;
72   LocBool      ThisBool;
73 }
74
75 %type <bool>       binary_operator
76 %type <arith>      arith_operator  arith_operator2
77 %type <ThisReal>   opt_Num_const
78 %type <ThisInt>    opt_prefix_sign
79 %type <Expr>       factor          expression      expression_in_bracket
80 %type <Expr>       NumberConst     object_factor   composed_expr2
81 %type <Expr>       composed_expr   logic_expr      variable
82 %type <Expr>       object          generator       r_value
83 %type <Expr>       one_or_more_logic_factor one_or_more_logic_term
84 %type <Expr>       one_or_more_factor       one_or_more_term
85 %type <Expr>       non_prefixed_variable    non_prefixed_generator
86 %type <Expr>       short_or_and_list
87 %type <object>     object_operator
88 %type <Instr>      affectation_instruction  instruction
89 %type <Instr>      single_instruction       complex_instruction
90 %type <Instr>      condition_instruction    loop_instruction
91 %type <ThisArgJob> parameter_job_instruction
92 %type <ThisBlock>  instructions opt_instructions opt_else loop_body
93
94 // Main
95
96 %token <ThisLoc> PROGRAM BLOCK PREF
97
98 // Module definition
99
100 %token <ThisLoc>    UNIT CLASS PROCEDURE FUNCTION
101 %token <ThisLoc>    COROUTINE PROCESS VIRTUAL SHARED ENUM
102
103 // Parameters transmission mode
104
105 %token <ThisLoc>    INPUT OUTPUT INOUT TAKEN CLOSE HIDDEN
106
107 // Sub-parts of module
108
109 %token <ThisLoc>    HANDLERS SIGNAL Begin END
110
111 // Variable and constants declarations
112
113 %token <ThisLoc>    VAR CONST
114 %token <ThisString> IDENTIFIER
115 %token <ThisLoc>    INTEGER TYPE REAL BOOLEAN CHARACTER
116 %token <ThisLoc>    STRING File ARRAY
117
118 //Punctuation
119
120 %token <ThisLoc>    LIST_SEPARATOR VARSEPARATOR OPENINGBRACKET
121 %token <ThisLoc>    CLOSINGBRACKET ENDSENTENCE POINT
122
123 //Operators
124
125 %token <ThisLoc>    STAR DIVIDE DIV MOD PLUS MINUS
126 %token <ThisLoc>    LESS LESSOREQUAL EQUAL NEQUAL
127 %token <ThisLoc>    GREATER GREATEROREQUAL
128 %token <ThisLoc>    OR AND NOT ANDIF ORIF
129 %token <ThisLoc>    AFFECTATION
130 %token <ThisLoc>    QUA THIS IS IN NEW COPY ARRAY_OF
131 %token <ThisLoc>    NONE
132
133 // Constants
134
135 %token <ThisString> TEXTCONST
136 %token <ThisChar>   CHARCONST
137 %token <ThisInt>    DIGITSEQUENCE
138 %token <ThisBool>   BOOLCONST
139
140 //Keywords for Instructions
141
142 %token <ThisLoc>    IF THEN ELSE FI
143 %token <ThisLoc>    CASE WHEN OTHERWISE ESAC
144 %token <ThisLoc>    WHILE FOR STEP TO DOWNTO DO OD
145 %token <ThisLoc>    ATTACH DETACH RESUME STOP TERMINATE
146 %token <ThisLoc>    RESULT
147 %token <ThisLoc>    GET PUT READ READLN WRITE WRITELN
148 %token <ThisLoc>    DIM
149 %token <ThisLoc>    RAISE KILL
150 %token <ThisLoc>    CALL RETURN
151 %token <ThisLoc>    EXIT REPEAT
152 %token <ThisLoc>    INNER WIND
153
154 %%
155
156 // We begin with the main rule that initialize the variables analyse the
157 //  program and then go on is compilation.
158
159 but: initloglan program endprogram analyse
160         { RULES_DEBUG_printf(" but -> initloglan program analyse \n");} ;
161
162 // This rule is empty. Is only use is for side-effect.
163
164 initloglan:     { initialize(); }
165         ;
166
167 // This one too...
168
169 analyse:
170         ;
171
172 program: program_module
173         {RULES_DEBUG_printf("program -> program_module.\n"); }
174         | block_module
175         {RULES_DEBUG_printf("program -> block_module.\n"); }
176         | unit_module
177         {RULES_DEBUG_printf("program -> unit_module.\n"); }
178         ;
179
180 program_module: PROGRAM IDENTIFIER endsentence module_body
181         { RULES_DEBUG_printf("program_module -> PROGRAM IDENTIFIER endsentence module_body.\n"); }
182         |       PROGRAM error module_body
183         { RULES_ERROR_printf(" error: program name missing.\n"); }
184         ;
185
186 block_module:   BLOCK module_body
187         { RULES_DEBUG_printf("block_module -> BLOCK module_body.\n"); }
188         |       error
189         { RULES_ERROR_printf(" error : BLOCK or PROGRAM expected.\n"); }
190         ;
191
192 unit_module:    module_header module_body
193         { RULES_DEBUG_printf("unit_module -> module_header module_body.\n"); }
194         ;
195
196 module_body:    opt_declarations module_code
197         { RULES_DEBUG_printf("module_body -> opt_declarations module_code.\n"); }
198         ;
199 module_header:  UNIT opt_virtual IDENTIFIER VARSEPARATOR prefix_list module_type parameters endsentence opt_visibility_declarations
200         { RULES_DEBUG_printf("module_header -> UNIT opt_virtual IDENTIFIER VARSEPARATOR prefix_list modul_type parameters endsentence opt_visibility_declarations.\n"); }
201         |       UNIT opt_virtual IDENTIFIER VARSEPARATOR ENUM OPENINGBRACKET identifier_list CLOSINGBRACKET endsentence
202         { RULES_DEBUG_printf("module_header -> UNIT opt_virtual IDENTIFIER VARSEPARATOR ENUM OPENINGBRACKET identifier_list CLOSINGBRACKET endsentence.\n"); }
203         ;
204
205 prefix_list:
206         { RULES_DEBUG_printf("prefix_list -> .\n"); }
207         |       list_prefix
208         { RULES_DEBUG_printf("prefix_list -> list_prefix.\n"); };
209
210 list_prefix:    opt_shared identifier_path
211         { RULES_DEBUG_printf("list_prefix -> identifier_path .\n"); }
212         |       opt_shared identifier_path LIST_SEPARATOR prefix_list
213         { RULES_DEBUG_printf("list_prefix -> identifier_path LIST_SEPARATOR prefix_list.\n"); }
214         ;
215
216 opt_shared: SHARED
217         { RULES_DEBUG_printf("opt_shared -> SHARED.\n"); }
218         |
219         { RULES_DEBUG_printf("opt_shared -> .\n"); }
220         ;
221
222 opt_virtual: VIRTUAL
223         { RULES_DEBUG_printf("opt_virtual -> VIRTUAL.\n"); }
224         |
225         { RULES_DEBUG_printf("opt_virtual -> .\n"); }
226         ;
227
228 identifier_path:
229                 IDENTIFIER
230         { RULES_DEBUG_printf("identifier_path -> IDENTIFIER.\n"); }
231         |       IDENTIFIER VARSEPARATOR identifier_path
232         { RULES_DEBUG_printf("identifier_path -> IDENTIFIER VARSEPARATOR identifier_path.\n"); }
233         ;
234
235 module_type:    CLASS
236         { RULES_DEBUG_printf("module_type -> CLASS.\n"); }
237         |       PROCEDURE
238         { RULES_DEBUG_printf("module_type -> PROCEDURE.\n"); }
239         |       FUNCTION
240         { RULES_DEBUG_printf("module_type -> FUNCTION.\n"); }
241         |       COROUTINE
242         { RULES_DEBUG_printf("module_type -> COROUTINE.\n"); }
243         |       PROCESS
244         { RULES_DEBUG_printf("module_type -> PROCESS.\n"); }
245         ;
246
247 parameters:     OPENINGBRACKET formal_parameters_list opt_endsentence CLOSINGBRACKET end_parameters
248         { RULES_DEBUG_printf("parameters -> OPENINGBRACKET formal_parameters_list opt_endsentence CLOSINGBRACKET end_parameters.\n"); }
249         |       end_parameters
250         { RULES_DEBUG_printf("parameters -> end_parameters.\n"); }
251         ;
252
253 end_parameters: VARSEPARATOR typeident
254         { RULES_DEBUG_printf("end_parameters -> VARSEPARATOR IDENTIFIER.\n"); }
255         |
256         { RULES_DEBUG_printf("end_parameters -> .\n"); }
257         ;
258
259 formal_parameters_list: formal_parameters_list endsentence formal_parameter
260         { RULES_DEBUG_printf("formal_parameters_list -> formal_parameters_list endsentence formal_parameter.\n"); }
261         |       formal_parameter
262         { RULES_DEBUG_printf("formal_parameters_list -> formal_parameter.\n"); }
263         ;
264
265 formal_parameter:       parametertype var_param_list
266         { RULES_DEBUG_printf("formal_parameter -> parametertype var_param_list.\n"); }
267         |       TYPE    IDENTIFIER
268         { RULES_DEBUG_printf("formal_parameter -> TYPE IDENTIFIER.\n"); }
269         |       callable_module
270         { RULES_DEBUG_printf("formal_parameter -> callable_module.\n"); }
271         ;
272
273 parametertype: INPUT
274         { RULES_DEBUG_printf("parametertype -> INPUT.\n"); }
275         | OUTPUT
276         { RULES_DEBUG_printf("parametertype -> OUTPUT.\n"); }
277         | INOUT
278         { RULES_DEBUG_printf("parametertype -> INOUT.\n"); }
279         |
280         { RULES_DEBUG_printf("parametertype -> .\n"); }
281         ;
282
283 var_param_list: var_param_list LIST_SEPARATOR var_declaration
284         { RULES_DEBUG_printf("var_param_list -> var_param_list LIST_SEPARATOR var_declaration.\n"); }
285         |       var_declaration
286         { RULES_DEBUG_printf("var_param_list -> var_declaration.\n"); }
287         ;
288
289 var_declaration:        identifier_list VARSEPARATOR typeident
290         { RULES_DEBUG_printf("var_declaration -> identifier_list VARSEPARATOR typeident.\n"); }
291         ;
292
293 identifier_list: identifier_list LIST_SEPARATOR IDENTIFIER
294         { RULES_DEBUG_printf("identifier_list -> identifier_list LIST_SEPARATOR IDENTIFIER.\n"); }
295         |       IDENTIFIER
296         { RULES_DEBUG_printf("identifier_list -> IDENTIFIER.\n"); }
297         ;
298
299 typeident:      list_arrayof definedtype
300         { RULES_DEBUG_printf(" typeident -> list_arrayof definedtype .\n"); }
301         |       definedtype
302         { RULES_DEBUG_printf(" typeident -> definedtype .\n"); }
303         ;
304
305 list_arrayof:   list_arrayof ARRAY_OF
306         { RULES_DEBUG_printf(" list_arrayof -> list_arrayof ARRAY_OF .\n"); }
307         |       ARRAY_OF
308         { RULES_DEBUG_printf(" list_arrayof -> .\n"); }
309         ;
310
311 definedtype:    predefinedtype
312         |       IDENTIFIER
313         ;
314
315 predefinedtype: INTEGER
316         { RULES_DEBUG_printf(" predefinedtype -> INTEGER .\n"); }
317         |       REAL
318         { RULES_DEBUG_printf(" predefinedtype -> REAL.\n"); }
319         |       BOOLEAN
320         { RULES_DEBUG_printf(" predefinedtype -> BOOLEAN.\n"); }
321         |       CHARACTER
322         { RULES_DEBUG_printf(" predefinedtype -> CHARACTER.\n"); }
323         |       STRING
324         { RULES_DEBUG_printf(" predefinedtype -> STRING.\n"); }
325         |       File
326         { RULES_DEBUG_printf(" predefinedtype -> FILE.\n"); }
327         |       PROCESS
328         { RULES_DEBUG_printf(" predefinedtype -> PROCESS.\n"); }
329         |       COROUTINE
330         { RULES_DEBUG_printf(" predefinedtype -> PROCESS.\n"); }
331         ;
332
333 callable_module: function_callable
334         { RULES_DEBUG_printf("callable_module -> function_callable.\n"); }
335         |       procedure_callable
336         { RULES_DEBUG_printf("callable_module -> procedure_callable.\n"); }
337         ;
338
339 function_callable:      FUNCTION IDENTIFIER parameters
340         { RULES_DEBUG_printf("function_callable -> FUNCTION IDENTIFIER parameters.\n"); }
341         ;
342
343 procedure_callable:     PROCEDURE IDENTIFIER parameters
344         { RULES_DEBUG_printf("procedure_callable -> PROCEDURE IDENTIFIER parameters.\n"); }
345         ;
346
347 handlers_declaration: HANDLERS handlers_body END HANDLERS opt_endsentence
348         { RULES_DEBUG_printf("handlers_declaration -> HANDLERS handlers_body END HANDLERS opt_endsentence.\n"); }
349         ;
350
351 opt_endsentence: ENDSENTENCE
352         { RULES_DEBUG_printf("opt_endsentence -> ENDSENTENCE.\n"); }
353         |
354         { RULES_DEBUG_printf("opt_endsentence -> .\n"); }
355         ;
356
357 endsentence:    ENDSENTENCE
358         { RULES_DEBUG_printf("endsentence -> ENDSENTENCE.\n"); }
359         |       error
360         { RULES_ERROR_printf("error : ';' expected.\n"); }
361
362 handlers_body: when_list opt_others
363         { RULES_DEBUG_printf("handlers_body -> when_list opt_others.\n"); }
364         ;
365
366 when_list: when_list when_unique
367         { RULES_DEBUG_printf("when_list -> when_list when_unique.\n"); }
368         |       when_unique
369         { RULES_DEBUG_printf("when_list -> when_unique.\n"); }
370         ;
371
372 when_unique: WHEN identifier_list VARSEPARATOR instructions
373         { RULES_DEBUG_printf("when_unique -> WHEN identifier_list VARSEPARATOR instructions.\n"); }
374         ;
375
376 opt_others:     OTHERWISE VARSEPARATOR instructions
377         { RULES_DEBUG_printf("opt_others -> OTHERWISE VARSEPARATOR instructions.\n"); }
378         |
379         { RULES_DEBUG_printf("opt_others -> .\n"); }
380         ;
381
382 module_code:    Begin opt_instructions END module_code_end
383         {
384           RULES_DEBUG_printf("module_code -> BEGIN opt_instructions END module_code_end.\n");
385           SEMANTIC(
386           {
387             if ($<ThisBlock>2)
388               $<ThisBlock>2->Print( cout );
389           });
390         }
391         |       END module_code_end
392         { RULES_DEBUG_printf("module_code -> END module_code_end.\n"); }
393         ;
394
395 opt_instructions: instructions
396         {
397           RULES_DEBUG_printf("opt_instructions -> instructions opt_endsentence.\n");
398           SEMANTIC(( $<ThisBlock>$ = $<ThisBlock>1 ));
399         }
400         |
401         {
402           RULES_DEBUG_printf("opt_instructions ->.\n");
403           SEMANTIC(( $<ThisBlock>$ = NULL ));
404         }
405         ;
406
407 module_code_end:
408                 IDENTIFIER
409         { RULES_DEBUG_printf("module_code_end -> IDENTIFIER .\n"); }
410         |
411         { RULES_DEBUG_printf("module_code_end -> .\n"); }
412         ;
413
414 opt_declarations:
415         { RULES_DEBUG_printf("opt_declarations -> .\n"); }
416         |       declarations handlers_declaration
417         { RULES_DEBUG_printf("opt_declarations -> declarations handlers_declaration.\n"); }
418         |       handlers_declaration
419         { RULES_DEBUG_printf("opt_declarations -> handlers_declaration.\n"); }
420         |       declarations
421         { RULES_DEBUG_printf("opt_declarations -> declarations .\n"); }
422         ;
423
424 declarations:   declarations declaration endsentence
425         { RULES_DEBUG_printf("declarations -> declarations declaration endsentence.\n"); }
426         |       declaration endsentence
427         { RULES_DEBUG_printf("declarations -> declaration endsentence. \n"); }
428         ;
429
430 declaration:    const_declaration
431         { RULES_DEBUG_printf("declaration -> const_declaration.\n"); }
432         |       variables_declaration
433         { RULES_DEBUG_printf("declaration -> variables_declaration.\n"); }
434         |       unit_module
435         { RULES_DEBUG_printf("declaration -> unit_module.\n"); }
436         |       signal_declaration
437         { RULES_DEBUG_printf("declarations -> signal_declaration.\n"); }
438         ;
439
440 opt_visibility_declarations:
441                 visibility_declarations
442         { RULES_DEBUG_printf("opt_visibility_declarations -> visibility_declarations.\n"); }
443         |
444         { RULES_DEBUG_printf("opt_visibility_declarations -> .\n"); }
445         ;
446
447 visibility_declarations:
448                 visibility_declarations visibility_declaration endsentence
449         { RULES_DEBUG_printf("visibility_declarations -> visibility_declarations visibility_declaration endsentence.\n"); }
450         |       visibility_declaration endsentence
451         { RULES_DEBUG_printf("visibility_declarations ->visibility_declaration endsentence.\n"); }
452         ;
453
454 visibility_declaration:
455                 visibility_keyword identifier_list
456         { RULES_DEBUG_printf("visibility_declaration -> visibility_keyword identifier_list.\n"); }
457         ;
458
459 visibility_keyword:
460                 TAKEN
461         { RULES_DEBUG_printf("visibility_keyword -> TAKEN.\n"); }
462         |       CLOSE
463         { RULES_DEBUG_printf("visibility_declarations -> CLOSE.\n"); }
464         |       HIDDEN
465         { RULES_DEBUG_printf("visibility_declarations -> HIDDEN.\n"); }
466         ;
467
468 variables_declaration: VAR vars_list
469         { RULES_DEBUG_printf("variables_declaration -> VAR vars_list.\n"); }
470         ;
471
472 const_declaration: CONST const_list
473         { RULES_DEBUG_printf("variables_declaration -> CONST const_list.\n"); }
474         ;
475
476 signal_declaration: SIGNAL IDENTIFIER parameters
477         { RULES_DEBUG_printf("signal_declaration -> SIGNAL IDENTIFIER parameters.\n");}
478         ;
479
480 // instructions are composed of juxtaposition of several instruction.
481 instructions:   instruction
482         {
483           RULES_DEBUG_printf("instructions -> instruction.\n");
484           SEMANTIC(( $<ThisBlock>$ = new Block( $<Instr>1 ) ));
485         }
486         |       instructions instruction
487         {
488           RULES_DEBUG_printf("instructions -> instructions instruction.\n");
489           SEMANTIC(( *$<ThisBlock>1 += $<Instr>2 ));
490         }
491         ;
492
493 // An Instruction could be a single instruction (like WRITE or STOP)
494 // or a complex instruction (i.e. composed ) (like IF FOR WHILE CASE ... )
495 instruction:    single_instruction endsentence
496         {
497           RULES_DEBUG_printf("instruction -> single_instruction endsentence.\n");
498           SEMANTIC(( $<Instr>$ = $<Instr>1 ));
499         }
500         |       complex_instruction
501         {
502           RULES_DEBUG_printf("instruction -> complex_instruction.\n");
503           SEMANTIC(( $<Instr>$ = $<Instr>1 ));
504         }
505         ;
506
507 // List of every single instruction available
508 single_instruction:
509                 affectation_instruction
510         {
511           RULES_DEBUG_printf("instruction -> affectation_instruction.\n");
512           SEMANTIC(( $<Instr>$ = $<Instr>1 ));
513         }
514         |       job_instruction
515         {
516           RULES_DEBUG_printf("instruction -> job_instruction.\n");
517           SEMANTIC(( $<Instr>$ = $<Instr>1 ));
518         }
519         |       io_instruction
520         { RULES_DEBUG_printf("instruction -> io_instruction.\n"); }
521         |       signal_instruction
522         { RULES_DEBUG_printf("instruction -> signal_instruction.\n"); }
523         |       array_instruction
524         { RULES_DEBUG_printf("instruction -> array_instruction.\n"); }
525         |       object_instruction
526         { RULES_DEBUG_printf("instruction -> object_instruction.\n"); }
527         |       CALL variable
528         { RULES_DEBUG_printf("instruction -> CALL variable.\n"); }
529         |       RETURN
530         { RULES_DEBUG_printf("instruction -> RETURN.\n"); }
531         |       exit_instruction
532         { RULES_DEBUG_printf("instruction -> exit_instruction.\n"); }
533         ;
534
535 // Subdivision of complex instructions :
536 //   instruction declaring a loop
537 //   instruction declaring a condition
538 //   instruction declaring a sub-block
539 complex_instruction:
540                 loop_instruction
541         {
542           RULES_DEBUG_printf("complex_instruction -> loop_instruction.\n");
543           $<Instr>$ = $<Instr>1;
544         }
545         |       condition_instruction
546         { RULES_DEBUG_printf("complex_instruction -> condition_instruction.\n"); }
547         |       block_instruction
548         { RULES_DEBUG_printf("complex_instruction -> block_instruction.\n"); }
549         |       case_instruction
550         { RULES_DEBUG_printf("complex_instruction -> case_instruction.\n"); }
551         ;
552
553 vars_list: vars_list LIST_SEPARATOR var_declaration
554         { RULES_DEBUG_printf("vars_list -> vars_list LIST_SEPARATOR var_declaration .\n"); }
555         | var_declaration
556         { RULES_DEBUG_printf("vars_list -> var_declaration .\n"); }
557         ;
558
559 const_list: const_list LIST_SEPARATOR one_const
560         { RULES_DEBUG_printf("const_list -> const_list LISTSEPARATOR one_const.\n");}
561         |       one_const
562         { RULES_DEBUG_printf("const_list -> one_const.\n");}
563         ;
564
565 one_const:      IDENTIFIER EQUAL expression
566         {
567           RULES_DEBUG_printf("one_const -> IDENTIFIER EQUAL expression. \n");
568         }
569         ;
570
571 expression:     one_or_more_logic_term
572         {
573           RULES_DEBUG_printf("expression -> one_or_more_logic_term.\n");
574           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
575         }
576         ;
577
578 one_or_more_logic_term:
579                 one_or_more_logic_factor
580         {
581           RULES_DEBUG_printf("one_or_more_logic_term -> one_or_more_logic_term.\n");
582           SEMANTIC(( $<Expr>$ = $<Expr>1 )) ;
583         }
584         |       one_or_more_logic_term OR one_or_more_logic_factor
585         {
586           RULES_DEBUG_printf("one_or_more_logic_term -> one_or_more_logic_term OR one_or_more_logic_factor.\n");
587           SEMANTIC(( $<Expr>$ = new BoolOperator( $<Expr>1, $<Expr>3 , Or, $<ThisLoc>2 ) ));
588         }
589         ;
590
591 one_or_more_logic_factor:
592                 composed_expr
593         {
594           RULES_DEBUG_printf("one_or_more_logic_factor -> composed_expr.\n");
595           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
596         }
597         |       one_or_more_logic_factor AND composed_expr
598         {
599           RULES_DEBUG_printf("one_or_more_logic_factor -> one_or_more_logic_factor AND composed_expr.\n");
600           SEMANTIC(( $<Expr>$ = new BoolOperator( $<Expr>1, $<Expr>3, And, $<ThisLoc>2 ) ));
601         }
602         ;
603
604 composed_expr:  NOT composed_expr2
605         {
606           RULES_DEBUG_printf("composed_expr -> NOT composed_expr2.\n");
607           SEMANTIC(( $<Expr>$ = new Not( $<Expr>2,$<ThisLoc>1 ) ));
608         }
609         |       composed_expr2
610         {
611           RULES_DEBUG_printf("composed_expr -> composed_expr2.\n");
612           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
613         }
614         ;
615
616 composed_expr2: logic_expr
617         {
618           RULES_DEBUG_printf("composed_expr2 -> logic_expr.\n");
619           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
620         }
621         |       logic_expr binary_operator logic_expr
622         {
623           RULES_DEBUG_printf("composed_expr2 -> logic_expr binary_operator logic_expr.\n");
624           SEMANTIC(( $<Expr>$ = new BoolOperator( $<Expr>1 , $<Expr>3 , $<bool>2 ) ));
625         }
626         |       logic_expr object_operator object
627         {
628           RULES_DEBUG_printf("composed_expr2 -> logic_expr object_operator logic_expr.\n");
629           SEMANTIC(( $<Expr>$ = new ObjOperator( $<Expr>1 , $<Expr>3 , $<object>2 ) ));
630         }
631         ;
632
633 binary_operator:
634                 EQUAL
635         {
636           RULES_DEBUG_printf("binary_operator -> EQUAL.\n");
637           SEMANTIC(($<bool>$ = Equal));
638         }
639         |       NEQUAL
640         {
641           RULES_DEBUG_printf("binary_operator -> NEQUAL.\n");
642           SEMANTIC(($<bool>$ = NotEqual));
643         }
644         |       LESS
645         {
646           RULES_DEBUG_printf("binary_operator -> LESS.\n");
647           SEMANTIC(($<bool>$ = Less));
648         }
649         |       LESSOREQUAL
650         {
651           RULES_DEBUG_printf("binary_operator -> LESSOREQUAL.\n");
652           SEMANTIC(($<bool>$ = LessOrEqual));
653         }
654         |       GREATER
655         {
656           RULES_DEBUG_printf("binary_operator -> GREATER.\n");
657           SEMANTIC(($<bool>$ = Greater));
658         }
659         |       GREATEROREQUAL
660         {
661           RULES_DEBUG_printf("binary_operator -> GREATEROREQUAL.\n");
662           SEMANTIC(($<bool>$ = GreaterOrEqual));
663         }
664         ;
665
666 object_operator:
667                 IS
668         {
669           RULES_DEBUG_printf("object_operator -> IS.\n");
670           SEMANTIC(( $<object>$ = Is ));
671         }
672         |       IN
673         {
674           RULES_DEBUG_printf("object_operator -> IN.\n");
675           SEMANTIC(( $<object>$ = In ));
676         }
677         ;
678
679 object:         COROUTINE
680         { RULES_DEBUG_printf("object -> COROUTINE.\n"); }
681         |       PROCESS
682         { RULES_DEBUG_printf("object -> PROCESS.\n"); }
683         |       IDENTIFIER
684         {
685           RULES_DEBUG_printf("object -> IDENTIFIER.\n");
686           SEMANTIC(( $<Expr>$ = new Identifier( $<ThisString>1.Str, $<ThisString>1.Loc ) ));
687         }
688         |       error
689         {
690           RULES_ERROR_printf("error : bad object.\n");
691           SEMANTIC(( $<Expr>$ = new Error( new Location( ThisPlace ) ));
692         }
693         ;
694
695 logic_expr:     opt_prefix_sign one_or_more_term
696         {
697           RULES_DEBUG_printf("expression -> opt_prefix_sign one_or_more_term.\n");
698 // To be modified, must take care of the optionnal prefix sign.
699           SEMANTIC(( $<Expr>$ = $<Expr>2 )); 
700         }
701         ;
702
703 // The optionnal prefixing sign: +a, -a, a
704 opt_prefix_sign:
705                 PLUS
706         {
707           RULES_DEBUG_printf("opt_prefix_sign -> PLUS.\n");
708           SEMANTIC(( $<ThisInt>$.Int = 1 ));
709           SEMANTIC(( $<ThisInt>$.Loc = $<ThisLoc>1 ));
710         }
711         |       MINUS
712         {
713           RULES_DEBUG_printf("opt_prefix_sign -> MINUS.\n");
714           SEMANTIC(( $<ThisInt>$.Int = -1 ));
715           SEMANTIC(( $<ThisInt>$.Loc = $<ThisLoc>1));
716         }
717         |
718         {
719           RULES_DEBUG_printf("opt_prefix_sign -> .\n");
720           SEMANTIC(( $<ThisInt>$.Int =  1 ));
721           SEMANTIC(( $<ThisInt>$.Loc =  new Location(ThisPlace) ));
722         }
723         ;
724
725 one_or_more_term:
726                 one_or_more_factor
727         {
728           RULES_DEBUG_printf("one_or_more_term -> one_or_more_factor.\n");
729           SEMANTIC(($<Expr>$ = $<Expr>1));
730         }
731         |       one_or_more_term arith_operator one_or_more_factor
732         {
733           RULES_DEBUG_printf("one_or_more_term -> one_or_more_term arith_operator one_or_more_factor.\n");
734           SEMANTIC(( $<Expr>$ = new ArithOperator( $<Expr>1 , $<Expr>3 , $<arith>2 ) ));
735         }
736         ;
737
738 one_or_more_factor:
739                 factor
740         {
741           RULES_DEBUG_printf("one_or_more_factor -> factor.\n");
742           SEMANTIC(($<Expr>$ = $<Expr>1));
743         }
744         |       one_or_more_factor arith_operator2 factor
745         {
746           RULES_DEBUG_printf("one_or_more_factor -> one_or_more_factor arith_operator2 factor.\n");
747           SEMANTIC(( $<Expr>$ = new ArithOperator( $<Expr>1 , $<Expr>3 , $<arith>2 ) ));
748         }
749         ;
750
751 arith_operator:
752                 PLUS
753         {
754           RULES_DEBUG_printf("arith_operator -> PLUS.\n");
755           SEMANTIC(($<arith>$ = Plus));
756         }
757         |       MINUS
758         {
759           RULES_DEBUG_printf("arith_operator -> MINUS.\n");
760           SEMANTIC(($<arith>$ = Minus));
761         }
762         ;
763
764 arith_operator2:
765                 STAR
766         {
767           RULES_DEBUG_printf("arith_operator2 -> STAR.\n");
768           SEMANTIC(($<arith>$ = Multiply));
769         }
770         |       DIVIDE
771         {
772           RULES_DEBUG_printf("arith_operator2 -> DIVIDE.\n");
773           SEMANTIC(($<arith>$ = Divide));
774         }
775         |       DIV
776         {
777           RULES_DEBUG_printf("arith_operator2 -> DIV.\n");
778           SEMANTIC(($<arith>$ = IntDivide));
779         }
780         |       MOD
781         {
782           RULES_DEBUG_printf("arith_operator2 -> MOD.\n");
783           SEMANTIC(($<arith>$ = Modulo));
784         }
785         ;
786 factor:         NumberConst
787         {
788           RULES_DEBUG_printf("factor -> NumberConst.\n");
789           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
790         }
791         |       TEXTCONST
792         {
793           RULES_DEBUG_printf("factor -> TextConst.\n");
794           SEMANTIC(( $<Expr>$ = new StringConstant ( $<ThisString>1.Str,
795                                                      $<ThisString>1.Loc ) ));
796         }
797         |       CHARCONST
798         {
799           RULES_DEBUG_printf("factor -> CharConst.\n");
800           SEMANTIC(( $<Expr>$ = new CharConstant( $<ThisChar>1.Str,
801                                                   $<ThisChar>1.Loc ) ));
802         }
803         |       BOOLCONST
804         {
805           RULES_DEBUG_printf("factor -> BOOLCONST.\n");
806           SEMANTIC(( $<Expr>$ = new BoolConstant( $<ThisBool>1.Bool,
807                                                   $<ThisBool>1.Loc ) ));
808         }
809         |       variable
810         {
811           RULES_DEBUG_printf("factor -> variable.\n");
812           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
813         }
814         |       object_factor
815         {
816           RULES_DEBUG_printf("factor -> object_factor.\n");
817           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
818         }
819         |       generator
820         {
821           RULES_DEBUG_printf("factor -> generator.\n");
822           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
823         }
824         |       expression_in_bracket
825         {
826           RULES_DEBUG_printf("factor -> expression_in_bracket.\n");
827           SEMANTIC(($<Expr>$ = $<Expr>1));
828         }
829         |       error
830         {
831           RULES_ERROR_printf(" error : bad factor.\n");
832           SEMANTIC(($<Expr>$ = new Error ));
833         }
834         ;
835
836 // Two results possible : an Integer constant if syntaxic string looks like
837 // 1000 or 1E3.
838 //                      or a Real constant if it looks like
839 // 1.3 1E-3, etc...
840 NumberConst:    DIGITSEQUENCE opt_Num_const
841         {
842           RULES_DEBUG_printf("NumberConst -> DIGITSEQUENCE opt_Num_const.\n");
843           SEMANTIC(
844           {
845             if ($<ThisReal>2 >= 1)
846             {
847               $<Expr>$ = new IntegerConstant((int)($<ThisInt>1.Int * $<ThisReal>2.Real),
848                                              new Location(*$<ThisInt>1.Loc + *$<ThisReal>2.Loc));
849             }
850             else
851             {
852               $<Expr>$ = new RealConstant( $<ThisInt>1 * $<ThisReal>2,
853                                            new Location(*$<ThisInt>1.Loc + *$<ThisReal>2.Loc));
854             }
855           })
856         }
857         |       DIGITSEQUENCE POINT DIGITSEQUENCE opt_Num_const
858         {
859           RULES_DEBUG_printf("NumberConst -> DIGITSEQUENCE POINT DIGITSEQUENCE opt_Num_const.\n");
860           SEMANTIC(
861           {
862             double dec = $<ThisInt>3.Int;
863
864             while (dec > 1) dec /= 10;
865             dec += $<ThisInt>1;
866
867             $<Expr>$ = new RealConstant( dec * $<ThisReal>4 );
868           })
869         }
870         |       DIGITSEQUENCE POINT opt_Num_const
871         {
872           RULES_DEBUG_printf("NumberConst -> DIGITSEQUENCE POINT opt_Num_const.\n");
873           SEMANTIC(
874           {
875             printf("Valeur numerique : ");
876             $<Expr>$ = new RealConstant( $<ThisInt>1 * $<ThisReal>3 );
877           })
878         }
879         |       POINT DIGITSEQUENCE opt_Num_const
880         {
881           RULES_DEBUG_printf("NumberConst -> POINT DIGITSEQUENCE opt_Num_const.\n");
882           SEMANTIC(
883           {
884             double dec = $<ThisInt>2;
885
886             while (dec > 1) dec /= 10;
887
888             $<Expr>$ = new RealConstant( dec * $<ThisReal>3 );
889           })
890         }
891         ;
892
893 // The IDENTIFIER must be the E letter for the analyse of an sci notated value
894 // ( for example 1E-2 ).
895
896 opt_Num_const:  IDENTIFIER opt_prefix_sign DIGITSEQUENCE
897         {
898           RULES_DEBUG_printf("opt_Num_const -> IDENTIFIER opt_prefix_sign DIGITSEQUENCE.\n");
899           SEMANTIC(
900           {
901             if ( *$<ThisString>1 == "E" )
902               $<ThisReal>$ = pow( 10 , (double) $<ThisInt>3 * $<ThisInt>2 );
903             else
904              printf("Error : E was expected.\n");
905           })
906         }
907         |
908         {
909           RULES_DEBUG_printf("opt_Num_const -> .\n");
910           SEMANTIC(( $<ThisReal>$ = 1 ));
911         }
912         |       IDENTIFIER error
913         {
914           RULES_DEBUG_printf(" error : exponant value expected.\n");
915           SEMANTIC(( $<ThisReal>$ = 1 ));
916         }
917         ;
918
919 object_factor:  NONE
920         {
921           RULES_DEBUG_printf("object_factor -> NONE.\n");
922           SEMANTIC(( $<Expr>$ = new NoneObject ));
923         }
924         |       THIS IDENTIFIER
925         {
926           RULES_DEBUG_printf("object_factor -> THIS IDENTIFIER.\n");
927           SEMANTIC(( $<Expr>$ = new This( new Identifier ($<ThisString>2 ) ) ));
928         }
929         |       THIS error
930         { RULES_ERROR_printf(" error : IDENTIFIER expected.\n"); }
931         ;
932
933 qualifier_expr: non_prefixed_variable
934         { RULES_DEBUG_printf("qualifier_expr -> non_prefixed_variable.\n"); }
935         |       non_prefixed_generator
936         { RULES_DEBUG_printf("qualifier_expr -> non_prefixed_generator.\n"); }
937         ;
938
939 opt_qualifier:  qualifier_expr opt_qua_list POINT
940         { RULES_DEBUG_printf("opt_qualifier -> qualifier_expr opt_qua_list POINT.\n"); }
941         |       THIS IDENTIFIER opt_qua_list POINT
942         { RULES_DEBUG_printf("opt_qualifier -> THIS IDENTIFIER opt_qua_list POINT.\n"); }
943         |       THIS error
944         { RULES_DEBUG_printf(" error : IDENTIFIER expected.\n"); }
945         ;
946
947 opt_qua_list:   opt_qua_list QUA IDENTIFIER
948         { RULES_DEBUG_printf("opt_qua_list -> QUA IDENTIFIER.\n"); }
949         |
950         { RULES_DEBUG_printf("opt_qua_list -> .\n"); }
951         |       opt_qua_list QUA error
952         { RULES_ERROR_printf(" error : bad qua list (IDENTIFIER is missing).\n"); }
953         ;
954
955 opt_list_qualifier:
956                 opt_list_qualifier opt_qualifier
957         { RULES_DEBUG_printf("opt_list_qualifier -> opt_list_qualifier opt_qualifier.\n"); }
958         |       opt_qualifier
959         { RULES_DEBUG_printf("opt_list_qualifier -> opt_qualifier.\n"); }
960         ;
961
962 variable:       opt_list_qualifier non_prefixed_variable
963         {
964           RULES_DEBUG_printf("variable -> opt_list_qualifier non_prefixed_variable.\n");
965           SEMANTIC(( $<Expr>$ = $<Expr>2 ));
966         }
967         |       non_prefixed_variable
968         {
969           RULES_DEBUG_printf("variable -> non_prefixed_variable.\n");
970           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
971         }
972         ;
973
974 non_prefixed_variable:  RESULT
975         {
976           RULES_DEBUG_printf("non_prefixed_variable -> RESULT.\n");
977           SEMANTIC(( $<Expr>$ = new Result ));
978         }
979         |       identifier_path
980         {
981           RULES_DEBUG_printf("non_prefixed_variable -> identifier_path.\n");
982           SEMANTIC(( $<Expr>$ = new Identifier( $<ThisString>1 ) ));
983         }
984         |       identifier_path OPENINGBRACKET one_or_more_expression CLOSINGBRACKET
985         {
986           RULES_DEBUG_printf("non_prefixed_variable -> identifier_path OPENINGBRACKET one_or_more_expression CLOSINGBRACKET.\n");
987           SEMANTIC(( $<Expr>$ = new Identifier( $<ThisString>1 ) ));
988         }
989         ;
990
991 one_or_more_expression:
992                 expression
993         { RULES_DEBUG_printf("one_or_more_expression -> expression.\n"); }
994         |       one_or_more_expression LIST_SEPARATOR expression
995         { RULES_DEBUG_printf("one_or_more_expression -> one_or_more_expression LIST_SEPARATOR expression.\n"); }
996         ;
997
998 generator:      opt_list_qualifier non_prefixed_generator
999         {
1000           RULES_DEBUG_printf("generator -> opt_list_qualifier non_prefixed_generator.\n");
1001           SEMANTIC(( $<Expr>$ = $<Expr>2 ));
1002         }
1003         |       non_prefixed_generator
1004         {
1005           RULES_DEBUG_printf("generator -> non_prefixed_generator.\n");
1006           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
1007         }
1008         ;
1009
1010 non_prefixed_generator: NEW identifier_path actual_parameters
1011         {
1012           RULES_DEBUG_printf(" non_prefixed_generator -> NEW identifier_path actual_paramters.\n");
1013           SEMANTIC(( $<Expr>$ = new New( new Identifier( $<ThisString>2 ) ) ));
1014         }
1015         |       NEW ARRAY OPENINGBRACKET expression LIST_SEPARATOR expression CLOSINGBRACKET
1016         {
1017           RULES_DEBUG_printf("non_prefixed_generator -> NEW ARRAY OPENINGBRACKET expression VARSEPARATOR expression CLOSINGBRACKET");
1018           SEMANTIC(( $<Expr>$ = new Error ));
1019         }
1020         |       NEW error
1021         { RULES_DEBUG_printf(" error : IDENTIFIER or ARRAY expected.\n"); }
1022         |       NEW ARRAY error
1023         { RULES_DEBUG_printf(" error : syntax error in array definition.\n"); }
1024         ;
1025
1026 actual_parameters:
1027         |       OPENINGBRACKET actual_parameters_list CLOSINGBRACKET
1028         { RULES_DEBUG_printf(" actual_parameters -> OPENINGBRACKET actual_parameters_list CLOSINGBRACKET.\n"); }
1029         ;
1030
1031 actual_parameters_list:
1032                 actual_parameter
1033         { RULES_DEBUG_printf("actual_paramters_list -> actual_parameter.\n"); }
1034         |       actual_parameters_list LIST_SEPARATOR actual_parameter
1035         { RULES_DEBUG_printf("actual_parameters_list -> actual_parameters_list LIST_SEPARATOR actual_parameter.\n"); }
1036         ;
1037
1038 actual_parameter:
1039                 expression
1040         { RULES_DEBUG_printf("actual_parameter -> expression.\n"); }
1041         |       predefinedtype
1042         { RULES_DEBUG_printf("actual_parameter -> predefinedtype.\n"); }
1043         ;
1044
1045 affectation_instruction:
1046                 l_identifiers_list AFFECTATION  r_value
1047         {
1048           RULES_DEBUG_printf("affectation_instruction -> l_identifiers_list AFFECTATION r_value.\n");
1049           SEMANTIC(( $<Instr>$ = new Affectation( $<Expr>1 , $<Expr>3 ) ));
1050         }
1051         |       l_identifiers_list error r_value
1052         {
1053           RULES_ERROR_printf("error : ':=' expected.\n");
1054           SEMANTIC(( $<Instr>$ = new Affectation( $<Expr>1 , $<Expr>3 ) ));
1055         }
1056         ;
1057
1058 //** Warning !!! Theses actions are to be replaced by something right 
1059 //** It's just Test Code .
1060
1061 l_identifiers_list:     variable
1062         {
1063           RULES_DEBUG_printf("l_identifiers_list -> variable.\n");
1064           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
1065         }
1066         |       l_identifiers_list LIST_SEPARATOR variable
1067         {
1068           RULES_DEBUG_printf("l_identifiers_list -> l_identifiers_list LIST_SEPARATOR variable.\n");
1069           SEMANTIC(( $<Expr>$ = $<Expr>3 ));
1070         }
1071         ;
1072
1073 r_value:        expression
1074         {
1075           RULES_DEBUG_printf("r_value -> expression .\n");
1076           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
1077         }
1078         |       COPY expression_in_bracket
1079         {
1080           RULES_DEBUG_printf("r_value -> COPY expression_in_bracket .\n");
1081           SEMANTIC(( $<Expr>$ = new Copy( $<Expr>2 ) ));
1082         }
1083         ;
1084
1085 job_instruction:
1086                 parameter_job_instruction OPENINGBRACKET expression CLOSINGBRACKET
1087         {
1088           RULES_DEBUG_printf("job_instruction -> parameter_job_instruction ( expression ).\n");
1089           SEMANTIC(
1090           {
1091             switch($<ThisArgJob>1)
1092             {
1093               case AttachInstr:
1094                 $<Instr>$ = new Attach( $<Expr>3 );
1095                 break;
1096               case ResumeInstr:
1097                 $<Instr>$ = new Resume( $<Expr>3 );
1098                 break;
1099               case StopInstr:
1100                 $<Instr>$ = new Stop( $<Expr>3 );
1101                 break;
1102             }
1103           });
1104         }
1105         |       DETACH
1106         {
1107           RULES_DEBUG_printf("job_instruction -> DETACH.\n");
1108           SEMANTIC(( $<Instr>$ = new Detach ));
1109         }
1110         |       STOP
1111         {
1112           RULES_DEBUG_printf("job_instruction -> STOP.\n");
1113           SEMANTIC(( $<Instr>$ = new Stop ));
1114         }
1115         |       TERMINATE
1116         {
1117           RULES_DEBUG_printf("job_instruction -> TERMINATE.\n");
1118           SEMANTIC(( $<Instr>$ = new Terminate ));
1119         }
1120         ;
1121
1122 parameter_job_instruction:
1123                 ATTACH
1124         {
1125           RULES_DEBUG_printf("parameter_job_instruction -> ATTACH.\n");
1126           SEMANTIC(( $<ThisArgJob>$ = AttachInstr ));
1127         }
1128         |       RESUME
1129         {
1130           RULES_DEBUG_printf("parameter_job_instruction -> RESUME.\n");
1131           SEMANTIC(( $<ThisArgJob>$ = ResumeInstr ));
1132         }
1133         |       STOP
1134         {
1135           RULES_DEBUG_printf("parameter_job_instruction -> STOP.\n");
1136           SEMANTIC(( $<ThisArgJob>$ = StopInstr ));
1137         }
1138         ;
1139
1140 io_instruction:
1141                 file_io_instruction
1142         { RULES_DEBUG_printf("io_instruction -> file_io_instruction .\n"); }
1143         |       input_instruction
1144         { RULES_DEBUG_printf("io_instruction -> input_instruction .\n"); }
1145         |       output_instruction
1146         { RULES_DEBUG_printf("io_instruction -> output_instruction .\n"); }
1147         ;
1148
1149 file_io_instruction:
1150                 file_io_keyword OPENINGBRACKET expression LIST_SEPARATOR one_or_more_expression CLOSINGBRACKET
1151         { RULES_DEBUG_printf("file_io_instruction -> file_io_keyword ( expression LIST_SEPARATOR one_or_more_expression ).\n"); }
1152         ;
1153
1154 file_io_keyword:
1155                 PUT
1156         { RULES_DEBUG_printf("file_io_keyword -> PUT.\n"); }
1157         |       GET
1158         { RULES_DEBUG_printf("file_io_keyword -> GET.\n"); }
1159         ;
1160
1161 input_instruction:
1162                 input_keyword OPENINGBRACKET l_identifiers_list CLOSINGBRACKET
1163         { RULES_DEBUG_printf("input_instruction -> input_keyword ( l_identifiers_list ).\n"); }
1164         |       READLN
1165         { RULES_DEBUG_printf("input_instruction -> READLN.\n"); }
1166         ;
1167
1168 input_keyword:
1169                 READ
1170         { RULES_DEBUG_printf("input_keyword -> READ.\n"); }
1171         |       READLN
1172         { RULES_DEBUG_printf("input_keyword -> READLN.\n"); }
1173         ;
1174
1175 output_instruction:
1176                 output_keyword OPENINGBRACKET l_formated_identifiers_list CLOSINGBRACKET
1177         { RULES_DEBUG_printf("output_instructions -> output_keyword ( l_formated_identifiers_list ).\n"); }
1178         |       WRITELN
1179         { RULES_DEBUG_printf("output_instructions -> WRITELN.\n"); }
1180         ;
1181
1182 output_keyword:
1183                 WRITE
1184         { RULES_DEBUG_printf("output_keyword -> WRITE.\n"); }
1185         |       WRITELN
1186         { RULES_DEBUG_printf("output_keyword -> WRITELN.\n"); }
1187         ;
1188
1189 l_formated_identifiers_list:
1190                 expression opt_modifiers
1191         { RULES_DEBUG_printf("l_formatted_identifiers_list -> expression opt_modifiers.\n"); }
1192         |       l_formated_identifiers_list LIST_SEPARATOR expression opt_modifiers
1193         { RULES_DEBUG_printf("l_formatted_identifiers_list -> l_formated_identifiers_list LIST_SEPARATOR expression opt_modifiers.\n"); }
1194         ;
1195
1196 opt_modifiers:  VARSEPARATOR NumberConst opt_modifiers2
1197         { RULES_DEBUG_printf(" opt_modifiers -> VARSEPARATOR NumberConst opt_modifiers2.\n");}
1198         |
1199         { RULES_DEBUG_printf(" opt_modifiers -> .\n");}
1200         ;
1201 opt_modifiers2: VARSEPARATOR NumberConst
1202         { RULES_DEBUG_printf(" opt_modifiers2 -> VARSEPARATOR NumberConst.\n");}
1203         |
1204         { RULES_DEBUG_printf(" opt_modifiers2 -> .\n");}
1205         ;
1206
1207 signal_instruction:
1208                 RAISE IDENTIFIER actual_parameters
1209         { RULES_DEBUG_printf("signal_instruction -> RAISE IDENTIFIER actual_parameters.\n"); }
1210         ;
1211
1212 array_instruction:
1213                 ARRAY variable DIM OPENINGBRACKET expression VARSEPARATOR expression CLOSINGBRACKET
1214         { RULES_DEBUG_printf("array_instruction -> ARRAY variable DIM OPENINGBRACKET expression VARSEPARATOR expression CLOSINGBRACKET.\n"); }
1215         ;
1216
1217 exit_instruction:
1218                 exit_list opt_repeat
1219         { RULES_DEBUG_printf("exit_instruction -> opt_exit_list opt_repeat.\n");}
1220         |       REPEAT
1221         { RULES_DEBUG_printf("exit_instruction -> REPEAT.\n");}
1222         ;
1223 exit_list:      exit_list EXIT
1224         { RULES_DEBUG_printf("opt_exit_list -> opt_exit_list EXIT.\n");}
1225         |       EXIT
1226         { RULES_DEBUG_printf("opt_exit_list -> EXIT .\n");}
1227         ;
1228
1229 opt_repeat:     REPEAT
1230         { RULES_DEBUG_printf("opt_repeat -> REPEAT.\n");}
1231         |
1232         { RULES_DEBUG_printf("opt_repeat -> .\n");}
1233         ;
1234
1235 loop_instruction:
1236                 WHILE expression loop_body
1237         {
1238           RULES_DEBUG_printf("loop_header -> WHILE expression loop_body.\n");
1239           SEMANTIC(( $<Instr>$ = new While( $<Expr>2, $<ThisBlock>3 ) ));
1240         }
1241         |       FOR variable AFFECTATION expression DOWNTO expression loop_body
1242         {
1243           RULES_DEBUG_printf("loop_header -> FOR variable AFFECTATION expression DOWNTO expression loop_body.\n");
1244           SEMANTIC(( $<Instr>$ = new For( $<Expr>2,
1245                                           $<Expr>4, $<Expr>6,
1246                                           new IntegerConstant( -1 ),
1247                                           $<ThisBlock>7 ) ));
1248         }
1249         |       FOR variable AFFECTATION expression TO expression loop_body
1250         {
1251           RULES_DEBUG_printf("loop_header -> FOR variable AFFECTATION expression TO expression loop_body.\n");
1252           SEMANTIC(( $<Instr>$ = new For( $<Expr>2,
1253                                           $<Expr>4, $<Expr>6,
1254                                           new IntegerConstant( 1 ),
1255                                           $<ThisBlock>7 ) ));
1256         }
1257         |       FOR variable AFFECTATION expression TO expression STEP expression loop_body
1258         {
1259           RULES_DEBUG_printf("loop_header -> FOR variable AFFECTATION expression TO expression STEP expression loop_body.\n");
1260           SEMANTIC(( $<Instr>$ = new For( $<Expr>2,
1261                                           $<Expr>4, $<Expr>6,
1262                                           $<Expr>8,
1263                                           $<ThisBlock>9 ) ));
1264         }
1265         ;
1266
1267 loop_body:
1268                 DO opt_instructions OD
1269         {
1270           RULES_DEBUG_printf("loop_body -> DO opt_instructions OD.\n");
1271           SEMANTIC(( $<ThisBlock>$ = $<ThisBlock>2 ));
1272         }
1273         |       DO opt_instructions error
1274         {
1275           RULES_ERROR_printf("error OD expected.\n");
1276           SEMANTIC(( $<ThisBlock>$ = NULL ));
1277         }
1278         ;
1279
1280 condition_instruction:
1281                 IF short_or_and_list THEN opt_instructions opt_else FI
1282         {
1283           RULES_DEBUG_printf("condition_instruction -> IF short_or_and_list THEN opt_instructions opt_else FI.\n");
1284           SEMANTIC(( $<Instr>$ = new ConditionIf( $<Expr>2, $<ThisBlock>4, $<ThisBlock>5 ) ));
1285         }
1286         |       IF short_or_and_list error
1287         { RULES_ERROR_printf("error : THEN expected.\n"); }
1288         |       IF short_or_and_list THEN opt_instructions opt_else error
1289         { RULES_ERROR_printf("error : FI or ELSE expected.\n"); }
1290         ;
1291
1292 short_or_and_list:      expression
1293         {
1294           RULES_DEBUG_printf("short_or_and_list -> expression.\n");
1295           SEMANTIC(( $<Expr>$ = $<Expr>1 ));
1296         }
1297 // The two next rules are wrong because ORIF and ANDIF are supposed to have
1298 // the same priority. This has to be fixed.
1299         |       short_or_and_list ORIF expression
1300         {
1301           RULES_DEBUG_printf("short_or_and_list -> short_or_and_list ORIF expression.\n");
1302           SEMANTIC(( $<Expr>$ = new BoolOperator( $<Expr>1, $<Expr>3, Or ) ));
1303         }
1304         |       short_or_and_list ANDIF expression
1305         {
1306           RULES_DEBUG_printf("short_or_and_list -> short_or_and_list ANDIF expression.\n");
1307           SEMANTIC(( $<Expr>$ = new BoolOperator( $<Expr>1, $<Expr>3, And ) ));
1308         }
1309         ;
1310
1311 opt_else:       ELSE opt_instructions
1312         {
1313           RULES_DEBUG_printf("opt_else -> ELSE opt_instructions. \n");
1314           SEMANTIC(( $<ThisBlock>$ = $<ThisBlock>2 ));
1315         }
1316         |
1317         {
1318           RULES_DEBUG_printf("opt_else -> . \n");
1319           SEMANTIC(( $<ThisBlock>$ = NULL ));
1320         }
1321         ;
1322
1323 case_instruction:
1324                 CASE expression case_when_list opt_case_otherwise ESAC
1325         { RULES_DEBUG_printf("case_instruction -> CASE expression case_when_list opt_case_otherwise ESAC.\n"); }
1326         ;
1327
1328 opt_case_otherwise:
1329                 OTHERWISE opt_instructions
1330         { RULES_DEBUG_printf("opt_case_otherwise -> OTHERWISE opt_instructions.\n"); }
1331         |
1332         { RULES_DEBUG_printf("opt_case_otherwise -> .\n"); }
1333         ;
1334
1335 case_when_list:
1336                 one_when_case
1337         { RULES_DEBUG_printf("case_when_list -> one_when_case.\n"); }
1338         |       case_when_list one_when_case
1339         { RULES_DEBUG_printf("case_when_list -> case_when_list one_when_case.\n"); }
1340         ;
1341
1342 one_when_case:  WHEN expression VARSEPARATOR opt_instructions
1343         { RULES_DEBUG_printf("one_when_case -> WHEN expression VARSEPARATOR opt_instructions.\n"); }
1344         ;
1345
1346 object_instruction:
1347                 WIND
1348         { RULES_DEBUG_printf("object_instruction -> WIND.\n"); }
1349         |       INNER
1350         { RULES_DEBUG_printf("object_instruction -> INNER.\n"); }
1351         |       KILL expression_in_bracket
1352         { RULES_DEBUG_printf("object_instruction -> KILL expression_in_bracket.\n"); }
1353         |       generator
1354         { RULES_DEBUG_printf("object_instruction -> generator.\n"); }
1355         ;
1356
1357 block_instruction:
1358                 PREF IDENTIFIER actual_parameters BLOCK opt_block_taken module_body endsentence
1359         { RULES_DEBUG_printf("block_instruction -> PREF IDENTIFIER actual_parameters BLOCK opt_block_taken module_body endsentence.\n"); }
1360         ;
1361
1362 opt_block_taken:
1363                 TAKEN identifier_list endsentence
1364         { RULES_DEBUG_printf("opt_block_taken -> TAKEN identifier_list endsentence.\n"); }
1365         |
1366         { RULES_DEBUG_printf("opt_block_taken -> .\n"); }
1367         ;
1368 expression_in_bracket:
1369                 OPENINGBRACKET expression CLOSINGBRACKET
1370         {
1371           RULES_DEBUG_printf("expression_in_bracket -> OPENINGBRACKET expression CLOSINGBRACKET.\n");
1372           SEMANTIC(( $<Expr>$ = $<Expr>2 ));
1373         }
1374         |       OPENINGBRACKET expression error
1375         { RULES_ERROR_printf("error : unbalanced bracket. \n"); }
1376         ;
1377
1378 endprogram:     ENDSENTENCE
1379         { RULES_DEBUG_printf("endprogram -> ENDSENTENCE.\n"); }
1380         |       POINT
1381         { RULES_DEBUG_printf("endprogram -> POINT.\n"); }
1382         |       error
1383         { RULES_ERROR_printf("error : ';' or '.' expected.\n"); }
1384         ;
1385 %%
1386 void initialize( void )
1387 {
1388   BeginningOfLine = 1;
1389 }
1390
1391 main()
1392 {
1393         yyparse();
1394 }
1395
1396 int yyerror( void )
1397 {
1398         printf("Syntax error at line %d.\n",line_number);
1399         return 0;
1400 }
1401
1402 int yyerror( char *s )
1403 {
1404         printf("%s",s);
1405         return 0;
1406 }