OSDN Git Service

Move scheduling visualization code to separate file.
[pf3gnuchains/gcc-fork.git] / gcc / java / parse.h
1 /* Language parser definitions for the GNU compiler for the Java(TM) language.
2    Copyright (C) 1997, 1998, 1999, 2000 Free Software Foundation, Inc.
3    Contributed by Alexandre Petit-Bianco (apbianco@cygnus.com)
4
5 This file is part of GNU CC.
6
7 GNU CC is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2, or (at your option)
10 any later version.
11
12 GNU CC is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with GNU CC; see the file COPYING.  If not, write to
19 the Free Software Foundation, 59 Temple Place - Suite 330,
20 Boston, MA 02111-1307, USA.
21
22 Java and all Java-based marks are trademarks or registered trademarks
23 of Sun Microsystems, Inc. in the United States and other countries.
24 The Free Software Foundation is independent of Sun Microsystems, Inc.  */
25
26 #ifndef JV_LANG_H
27 #define JV_LANG_H
28
29 #include "lex.h"
30
31 /* Extern global variable declarations */
32 extern int java_error_count;
33 extern struct obstack temporary_obstack;
34 extern struct obstack permanent_obstack;
35 extern int quiet_flag;
36
37 #ifndef JC1_LITE
38 /* Function extern to java/ */
39 extern int int_fits_type_p PARAMS ((tree, tree));
40 extern tree stabilize_reference PARAMS ((tree));
41 #endif
42
43 /* Macros for verbose debug info  */
44 #ifdef  VERBOSE_SKELETON
45 #define RULE( rule ) printf ( "jv_yacc:%d: rule %s\n", lineno, rule )
46 #else
47 #define RULE( rule )
48 #endif
49
50 #ifdef VERBOSE_SKELETON
51 #undef SOURCE_FRONTEND_DEBUG
52 #define SOURCE_FRONTEND_DEBUG(X)                                \
53   {if (!quiet_flag) {printf ("* "); printf X; putchar ('\n');} }
54 #else
55 #define SOURCE_FRONTEND_DEBUG(X)
56 #endif
57
58 /* Macro for error recovering  */
59 #ifdef YYDEBUG
60 #define RECOVERED                                       \
61   { if (!quiet_flag) {printf ("** Recovered\n");} }
62 #define DRECOVERED(s)                                           \
63   { if (!quiet_flag) {printf ("** Recovered (%s)\n", #s);}}
64 #else
65 #define RECOVERED
66 #define DRECOVERED(s)
67 #endif
68
69 #define DRECOVER(s) {yyerrok; DRECOVERED(s);}
70 #define RECOVER     {yyerrok; RECOVERED;}
71
72 #define YYERROR_NOW ctxp->java_error_flag = 1
73 #define YYNOT_TWICE if (ctxp->prevent_ese != lineno)
74
75 /* Accepted modifiers */
76 #define CLASS_MODIFIERS ACC_PUBLIC|ACC_ABSTRACT|ACC_FINAL
77 #define FIELD_MODIFIERS ACC_PUBLIC|ACC_PROTECTED|ACC_PRIVATE|ACC_FINAL| \
78                         ACC_STATIC|ACC_TRANSIENT|ACC_VOLATILE
79 #define METHOD_MODIFIERS ACC_PUBLIC|ACC_PROTECTED|ACC_PRIVATE|ACC_ABSTRACT| \
80                          ACC_STATIC|ACC_FINAL|ACC_SYNCHRONIZED|ACC_NATIVE
81 #define INTERFACE_MODIFIERS ACC_PUBLIC|ACC_ABSTRACT
82 #define INTERFACE_INNER_MODIFIERS ACC_PUBLIC|ACC_PROTECTED|ACC_PRIVATE|ACC_ABSTRACT|ACC_STATIC
83 #define INTERFACE_METHOD_MODIFIERS ACC_PUBLIC|ACC_ABSTRACT
84 #define INTERFACE_FIELD_MODIFIERS ACC_PUBLIC|ACC_STATIC|ACC_FINAL
85
86 /* Getting a modifier WFL */
87 #define MODIFIER_WFL(M)   (ctxp->modifier_ctx [(M) - PUBLIC_TK])
88
89 /* Check on modifiers */
90 #define THIS_MODIFIER_ONLY(f, m, v, count, l)                           \
91   if ((f) & (m))                                                        \
92     {                                                                   \
93       tree node = MODIFIER_WFL (v);                                     \
94       if ((l)                                                           \
95           && ((EXPR_WFL_COLNO (node) > EXPR_WFL_COLNO (l))              \
96               || (EXPR_WFL_LINENO (node) > EXPR_WFL_LINENO (l))))       \
97         l = node;                                                       \
98       else if (!(l))                                                    \
99         l = node;                                                       \
100       count++;                                                          \
101     }
102
103 #define ABSTRACT_CHECK(FLAG, V, CL, S)                          \
104   if ((FLAG) & (V))                                             \
105     parse_error_context ((CL), "%s method can't be abstract", (S));
106
107 #define JCONSTRUCTOR_CHECK(FLAG, V, CL, S)                      \
108   if ((FLAG) & (V))                                             \
109     parse_error_context ((CL), "Constructor can't be %s", (S)); \
110       
111 /* Misc. */
112 #define exit_java_complete_class()              \
113   {                                             \
114     return;                                     \
115   }
116
117 #define CLASS_OR_INTERFACE(decl, s1, s2)                        \
118    (decl ?                                                      \
119     ((get_access_flags_from_decl (TYPE_NAME (TREE_TYPE (decl))) \
120       & ACC_INTERFACE) ?                                        \
121      s2 : s1) : ((s1 [0]=='S'|| s1 [0]=='s') ?                  \
122                  (s1 [0]=='S' ? "Supertype" : "supertype") :    \
123                  (s1 [0] > 'A' ? "Type" : "type")))
124
125 #define GET_REAL_TYPE(TYPE)                                     \
126   (TREE_CODE (TYPE) == TREE_LIST ? TREE_PURPOSE (TYPE) : TYPE)
127
128 #define GET_METHOD_NAME(METHOD)                                 \
129   (TREE_CODE (DECL_NAME (METHOD)) == EXPR_WITH_FILE_LOCATION ?  \
130    EXPR_WFL_NODE (DECL_NAME (METHOD)) : DECL_NAME (METHOD))
131
132 /* Get TYPE name string, regardless whether TYPE is a class or an
133    array. */
134 #define GET_TYPE_NAME(TYPE)                             \
135   (TREE_CODE (TYPE_NAME (TYPE)) == IDENTIFIER_NODE ?    \
136    IDENTIFIER_POINTER (TYPE_NAME (TYPE)) :              \
137    IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (TYPE))))
138
139 /* Pedantic warning on obsolete modifiers. Note: when cl is NULL,
140    flags was set artificially, such as for a interface method */
141 #define OBSOLETE_MODIFIER_WARNING(cl, flags, __modifier, arg)                \
142   {                                                                          \
143     if (flag_redundant && (cl) && ((flags) & (__modifier)))                  \
144       parse_warning_context (cl,                                             \
145      "Discouraged redundant use of `%s' modifier in declaration of %s",      \
146                              java_accstring_lookup (__modifier), arg);       \
147   }
148 #define OBSOLETE_MODIFIER_WARNING2(cl, flags, __modifier, arg1, arg2)        \
149   {                                                                          \
150     if (flag_redundant && (cl) && ((flags) & (__modifier)))                  \
151       parse_warning_context (cl,                                             \
152      "Discouraged redundant use of `%s' modifier in declaration of %s `%s'", \
153                              java_accstring_lookup (__modifier), arg1, arg2);\
154   }
155
156 /* Quickly build a temporary pointer on hypothetical type NAME. */
157 #define BUILD_PTR_FROM_NAME(ptr, name)          \
158   do {                                          \
159     ptr = build (POINTER_TYPE, NULL_TREE);      \
160     TYPE_NAME (ptr) = name;                     \
161   } while (0)
162
163 #define INCOMPLETE_TYPE_P(NODE)                         \
164   ((TREE_CODE (NODE) == POINTER_TYPE)                   \
165    && !TREE_TYPE (NODE)                                 \
166    && TREE_CODE (TYPE_NAME (NODE)) == IDENTIFIER_NODE)
167
168 /* Set the EMIT_LINE_NOTE flag of a EXPR_WLF to 1 if debug information
169    are requested. Works in the context of a parser rule. */
170 #define JAVA_MAYBE_GENERATE_DEBUG_INFO(node)            \
171   (debug_info_level != DINFO_LEVEL_NONE ?               \
172     EXPR_WFL_EMIT_LINE_NOTE (node) = 1, node : node)
173
174 /* Types classification, according to the JLS, section 4.2 */
175 #define JFLOAT_TYPE_P(TYPE)      (TYPE && TREE_CODE ((TYPE)) == REAL_TYPE)
176 #define JINTEGRAL_TYPE_P(TYPE)   ((TYPE)                                   \
177                                   && (TREE_CODE ((TYPE)) == INTEGER_TYPE   \
178                                       || TREE_CODE ((TYPE)) == CHAR_TYPE))
179 #define JNUMERIC_TYPE_P(TYPE)    ((TYPE)                                \
180                                   && (JFLOAT_TYPE_P ((TYPE))            \
181                                       || JINTEGRAL_TYPE_P ((TYPE))))
182 #define JPRIMITIVE_TYPE_P(TYPE)  ((TYPE)                                  \
183                                   && (JNUMERIC_TYPE_P ((TYPE))            \
184                                   || TREE_CODE ((TYPE)) == BOOLEAN_TYPE))
185
186 #define JBSC_TYPE_P(TYPE) ((TYPE) && (((TYPE) == byte_type_node)        \
187                                       || ((TYPE) == short_type_node)    \
188                                       || ((TYPE) == char_type_node)))
189
190 /* Not defined in the LRM */
191 #define JSTRING_TYPE_P(TYPE) ((TYPE)                                       \
192                               && ((TYPE) == string_type_node ||            \
193                                   (TREE_CODE (TYPE) == POINTER_TYPE &&     \
194                                    TREE_TYPE (TYPE) == string_type_node)))
195 #define JSTRING_P(NODE) ((NODE)                                         \
196                          && (TREE_CODE (NODE) == STRING_CST             \
197                              || IS_CRAFTED_STRING_BUFFER_P (NODE)       \
198                              || JSTRING_TYPE_P (TREE_TYPE (NODE))))
199
200 #define JREFERENCE_TYPE_P(TYPE) ((TYPE)                                       \
201                                  && (TREE_CODE (TYPE) == RECORD_TYPE          \
202                                      || (TREE_CODE (TYPE) == POINTER_TYPE     \
203                                          &&  TREE_CODE (TREE_TYPE (TYPE)) ==  \
204                                          RECORD_TYPE)))
205 #define JNULLP_TYPE_P(TYPE) ((TYPE) && (TREE_CODE (TYPE) == POINTER_TYPE) \
206                              && (TYPE) == TREE_TYPE (null_pointer_node))
207
208 /* Other predicates */
209 #define JDECL_P(NODE) (NODE && (TREE_CODE (NODE) == PARM_DECL           \
210                                 || TREE_CODE (NODE) == VAR_DECL         \
211                                 || TREE_CODE (NODE) == FIELD_DECL))
212
213 #define TYPE_INTERFACE_P(TYPE)                                  \
214   (CLASS_P (TYPE) && CLASS_INTERFACE (TYPE_NAME (TYPE)))
215
216 #define TYPE_CLASS_P(TYPE) (CLASS_P (TYPE)                              \
217                             && !CLASS_INTERFACE (TYPE_NAME (TYPE)))
218
219 /* Identifier business related to 1.1 language extensions.  */
220
221 #define IDENTIFIER_INNER_CLASS_OUTER_FIELD_ACCESS(NODE) \
222   (TREE_CODE (NODE) == IDENTIFIER_NODE &&               \
223    IDENTIFIER_LENGTH (NODE) >= 8 &&                     \
224    IDENTIFIER_POINTER (NODE)[7] != '0')
225
226 /* Build the string val$<O> and store it into N. The is used to
227    construct the name of inner class hidden fields used to alias outer
228    scope local variables.  */
229 #define MANGLE_OUTER_LOCAL_VARIABLE_NAME(N, O)                          \
230   {                                                                     \
231     char *mangled_name;                                                 \
232     obstack_grow (&temporary_obstack, "val$", 4);                       \
233     obstack_grow (&temporary_obstack,                                   \
234                   IDENTIFIER_POINTER ((O)), IDENTIFIER_LENGTH ((O)));   \
235     obstack_1grow (&temporary_obstack, '\0');                           \
236     mangled_name = obstack_finish (&temporary_obstack);                 \
237     (N) = get_identifier (mangled_name);                                \
238     obstack_free (&temporary_obstack, mangled_name);                    \
239   }
240
241 /* Build the string parm$<O> and store in into the identifier N. This
242    is used to contruct the name of hidden parameters used to
243    initialize outer scope aliases.  */
244 #define MANGLE_ALIAS_INITIALIZER_PARAMETER_NAME_ID(N, O)                \
245   {                                                                     \
246     char *mangled_name;                                                 \
247     obstack_grow (&temporary_obstack, "parm$", 5);                      \
248     obstack_grow (&temporary_obstack,                                   \
249                   IDENTIFIER_POINTER ((O)), IDENTIFIER_LENGTH ((O)));   \
250     obstack_1grow (&temporary_obstack, '\0');                           \
251     mangled_name = obstack_finish (&temporary_obstack);                 \
252     (N) = get_identifier (mangled_name);                                \
253     obstack_free (&temporary_obstack, mangled_name);                    \
254   }
255
256 #define MANGLE_ALIAS_INITIALIZER_PARAMETER_NAME_STR(N, S)       \
257   {                                                             \
258     char *mangled_name;                                                 \
259     obstack_grow (&temporary_obstack, "parm$", 5);              \
260     obstack_grow (&temporary_obstack, (S), strlen ((S)));       \
261     obstack_1grow (&temporary_obstack, '\0');                   \
262     mangled_name = obstack_finish (&temporary_obstack);                 \
263     (N) = get_identifier (mangled_name);                                \
264     obstack_free (&temporary_obstack, mangled_name);                    \
265   }
266
267 /* Skip THIS and artificial parameters found in function decl M and
268    assign the result to C. We don't do that for $finit$, since it's
269    knowingly called with artificial parms.  */
270 #define SKIP_THIS_AND_ARTIFICIAL_PARMS(C,M)                     \
271   {                                                             \
272     int i;                                                      \
273     (C) = TYPE_ARG_TYPES (TREE_TYPE ((M)));                     \
274     if (!METHOD_STATIC ((M)))                                   \
275       (C) = TREE_CHAIN (C);                                     \
276     if (DECL_CONSTRUCTOR_P ((M))                                \
277         && PURE_INNER_CLASS_TYPE_P (DECL_CONTEXT ((M))))        \
278       (C) = TREE_CHAIN (C);                                     \
279     if (!DECL_FINIT_P ((M)))                                    \
280       for (i = DECL_FUNCTION_NAP ((M)); i; i--)                 \
281        (C) = TREE_CHAIN (C);                                    \
282   }
283
284 /* Mark final parameters in method M, by comparison of the argument
285    list L. This macro is used to set the flag once the method has been
286    build.  */
287 #define MARK_FINAL_PARMS(M, L)                                          \
288   {                                                                     \
289     tree current = TYPE_ARG_TYPES (TREE_TYPE ((M)));                    \
290     tree list = (L);                                                    \
291     if (!METHOD_STATIC ((M)))                                           \
292       current = TREE_CHAIN (current);                                   \
293     for (; current !=  end_params_node;                                 \
294          current = TREE_CHAIN (current), list = TREE_CHAIN (list))      \
295       ARG_FINAL_P (current) = ARG_FINAL_P (list);                       \
296     if (current != list)                                                \
297       fatal ("MARK_FINAL_PARMS");                                       \
298   }
299
300 /* Reset the ARG_FINAL_P that might have been set in method M args.  */
301 #define UNMARK_FINAL_PARMS(M)                                           \
302   {                                                                     \
303     tree current;                                                       \
304     for (current = TYPE_ARG_TYPES (TREE_TYPE ((M)));                    \
305          current != end_params_node; current = TREE_CHAIN (current))    \
306       ARG_FINAL_P (current) = 0;                                        \
307   }
308
309 /* Reverse a crafted parameter list as required.  */
310 #define CRAFTED_PARAM_LIST_FIXUP(P)             \
311   {                                             \
312     if ((P))                                    \
313       {                                         \
314         tree last = (P);                        \
315         (P) = nreverse (P);                     \
316         TREE_CHAIN (last) = end_params_node;    \
317       }                                         \
318     else                                        \
319       (P) = end_params_node;                    \
320   }
321
322 /* Modes governing the creation of a alias initializer parameter
323    lists. AIPL stands for Alias Initializer Parameter List.  */
324 enum {
325   AIPL_FUNCTION_CREATION,         /* Suitable for artificial method creation */
326   AIPL_FUNCTION_DECLARATION,      /* Suitable for declared methods */
327   AIPL_FUNCTION_CTOR_INVOCATION,  /* Invocation of constructors */
328   AIPL_FUNCTION_FINIT_INVOCATION  /* Invocation of $finit$ */
329 };
330
331 /* Standard error messages */
332 #define ERROR_CANT_CONVERT_TO_BOOLEAN(OPERATOR, NODE, TYPE)             \
333   parse_error_context ((OPERATOR),                                      \
334     "Incompatible type for `%s'. Can't convert `%s' to boolean",        \
335     operator_string ((NODE)), lang_printable_name ((TYPE),0))
336
337 #define ERROR_CANT_CONVERT_TO_NUMERIC(OPERATOR, NODE, TYPE)             \
338   parse_error_context ((OPERATOR),                                      \
339       "Incompatible type for `%s'. Can't convert `%s' to numeric type", \
340       operator_string ((NODE)), lang_printable_name ((TYPE), 0))
341
342 #define ERROR_CAST_NEEDED_TO_INTEGRAL(OPERATOR, NODE, TYPE)             \
343 do {                                                                    \
344   tree _operator = (OPERATOR), _node = (NODE), _type = (TYPE);          \
345   if (JPRIMITIVE_TYPE_P (_type))                                        \
346     parse_error_context (_operator,                                     \
347 "Incompatible type for `%s'. Explicit cast needed to convert `%s' to integral",\
348                          operator_string(_node),                        \
349                          lang_printable_name (_type, 0));               \
350   else                                                                  \
351     parse_error_context (_operator,                                     \
352       "Incompatible type for `%s'. Can't convert `%s' to integral",     \
353                          operator_string(_node),                        \
354                          lang_printable_name (_type, 0));               \
355 } while (0)
356
357 #define ERROR_VARIABLE_NOT_INITIALIZED(WFL, V)                  \
358   parse_error_context                                           \
359     ((WFL), "Variable `%s' may not have been initialized",      \
360      IDENTIFIER_POINTER (V))
361
362 /* Definition for loop handling. This is Java's own definition of a
363    loop body. See parse.y for documentation. It's valid once you hold
364    a loop's body (LOOP_EXPR_BODY) */
365
366 /* The loop main block is the one hold the condition and the loop body */
367 #define LOOP_EXPR_BODY_MAIN_BLOCK(NODE) TREE_OPERAND (NODE, 0)
368 /* And then there is the loop update block */
369 #define LOOP_EXPR_BODY_UPDATE_BLOCK(NODE) TREE_OPERAND (NODE, 1)
370
371 /* Inside the loop main block, there is the loop condition and the
372    loop body. They may be reversed if the loop being described is a
373    do-while loop. NOTE: if you use a WFL around the EXIT_EXPR so you
374    can issue debug info for it, the EXIT_EXPR will be one operand
375    further. */
376 #define LOOP_EXPR_BODY_CONDITION_EXPR(NODE, R)                  \
377   TREE_OPERAND (LOOP_EXPR_BODY_MAIN_BLOCK (NODE), (R ? 1 : 0))
378
379 /* Here is the labeled block the loop real body is encapsulated in */
380 #define LOOP_EXPR_BODY_LABELED_BODY(NODE, R)                    \
381   TREE_OPERAND (LOOP_EXPR_BODY_MAIN_BLOCK (NODE), (R ? 0 : 1))
382 /* And here is the loop's real body */
383 #define LOOP_EXPR_BODY_BODY_EXPR(NODE, R)                       \
384   LABELED_BLOCK_BODY (LOOP_EXPR_BODY_LABELED_BODY(NODE, R))
385
386 #define PUSH_LABELED_BLOCK(B)                           \
387   {                                                     \
388     TREE_CHAIN (B) = ctxp->current_labeled_block;       \
389     ctxp->current_labeled_block = (B);                  \
390   }
391 #define POP_LABELED_BLOCK()                                             \
392   ctxp->current_labeled_block = TREE_CHAIN (ctxp->current_labeled_block)
393
394 #define PUSH_LOOP(L)                            \
395   {                                             \
396     TREE_CHAIN (L) = ctxp->current_loop;        \
397     ctxp->current_loop = (L);                   \
398   }
399 #define POP_LOOP() ctxp->current_loop = TREE_CHAIN (ctxp->current_loop)
400
401 #define PUSH_EXCEPTIONS(E)                                      \
402   currently_caught_type_list =                                  \
403     tree_cons (NULL_TREE, (E), currently_caught_type_list);
404
405 #define POP_EXCEPTIONS()                                                \
406   currently_caught_type_list = TREE_CHAIN (currently_caught_type_list)
407
408 /* Check that we're inside a try block.  */
409 #define IN_TRY_BLOCK_P()                                \
410   (currently_caught_type_list                           \
411    && ((TREE_VALUE (currently_caught_type_list) !=      \
412         DECL_FUNCTION_THROWS (current_function_decl))   \
413        || TREE_CHAIN (currently_caught_type_list)))
414
415 /* Check that we have exceptions in E.  */
416 #define EXCEPTIONS_P(E) ((E) ? TREE_VALUE (E) : NULL_TREE)
417
418 /* Anonymous array access */
419 #define ANONYMOUS_ARRAY_BASE_TYPE(N)   TREE_OPERAND ((N), 0)
420 #define ANONYMOUS_ARRAY_DIMS_SIG(N)    TREE_OPERAND ((N), 1)
421 #define ANONYMOUS_ARRAY_INITIALIZER(N) TREE_OPERAND ((N), 2)
422
423 /* Invocation modes, as returned by invocation_mode (). */
424 enum {
425   INVOKE_STATIC,
426   INVOKE_NONVIRTUAL,
427   INVOKE_SUPER,
428   INVOKE_INTERFACE,
429   INVOKE_VIRTUAL
430 };
431
432 /* We need the resolution stuff only if we compile jc1 */
433 #ifndef JC1_LITE
434
435 /* Unresolved type identifiers handling. When we process the source
436    code, we blindly accept an unknown type identifier and try to
437    resolve it later. When an unknown type identifier is encountered
438    and used, we record in a struct jdep element what the incomplete
439    type is and what it should patch. Later, java_complete_class will
440    process all classes known to have unresolved type
441    dependencies. Within each of these classes, this routine will
442    process unresolved type dependencies (JDEP_TO_RESOLVE), patch what
443    needs to be patched in the dependent tree node (JDEP_GET_PATCH,
444    JDEP_APPLY_PATCH) and perform other actions dictated by the context
445    of the patch (JDEP_KIND). The ideas are: we patch only what needs
446    to be patched, and with java_complete_class called at the right
447    time, we will start processing incomplete function bodies tree
448    nodes with everything external to function's bodies already
449    completed, it makes things much simpler. */
450
451 enum jdep_code {
452   JDEP_NO_PATCH,                /* Must be first */
453   JDEP_SUPER,                   /* Patch the type of one type
454                                    supertype. Requires some check
455                                    before it's done */
456   JDEP_FIELD,                   /* Patch the type of a class field */
457
458   /* JDEP_{METHOD,METHOD_RETURN,METHOD_END} to be kept in order */
459   JDEP_METHOD,                  /* Mark the beginning of the patching
460                                    of a method declaration, including
461                                    it's arguments */
462   JDEP_METHOD_RETURN,           /* Mark the beginning of the patching
463                                    of a method declaration. Arguments
464                                    aren't patched, only the returned
465                                    type is */
466   JDEP_METHOD_END,              /* Mark the end of the patching of a
467                                    method declaration. It indicates
468                                    that it's time to compute and
469                                    install a new signature */
470
471   JDEP_INTERFACE,               /* Patch the type of a Class/interface
472                                    extension */
473   JDEP_VARIABLE,                /* Patch the type of a variable declaration */
474   JDEP_PARM,                    /* Patch the type of a parm declaration */
475   JDEP_TYPE,                    /* Patch a random tree node type,
476                                    without the need for any specific
477                                    actions */
478   JDEP_EXCEPTION,               /* Patch exceptions specified by `throws' */
479   JDEP_ANONYMOUS                /* Patch anonymous classes
480                                    (implementation or extension.) */
481
482 };
483
484 typedef struct _jdep {
485   ENUM_BITFIELD(jdep_code) kind : 8; /* Type of patch */
486
487   int  flag0 : 1;               /* Some flags */
488   tree decl;                    /* Tied decl/or WFL */
489   tree solv;                    /* What to solve */
490   tree wfl;                     /* Where thing to resolve where found */
491   tree misc;                    /* Miscellaneous info (optional). */
492   tree enclosing;               /* The enclosing (current) class */
493   tree *patch;                  /* Address of a location to patch */
494   struct _jdep *next;           /* Linked list */
495 } jdep;
496
497
498 #define JDEP_DECL(J)          ((J)->decl)
499 #define JDEP_DECL_WFL(J)      ((J)->decl)
500 #define JDEP_KIND(J)          ((J)->kind)
501 #define JDEP_SOLV(J)          ((J)->solv)
502 #define JDEP_WFL(J)           ((J)->wfl)
503 #define JDEP_MISC(J)          ((J)->misc)
504 #define JDEP_ENCLOSING(J)     ((J)->enclosing)
505 #define JDEP_CLASS(J)         ((J)->class)
506 #define JDEP_APPLY_PATCH(J,P) (*(J)->patch = (P))
507 #define JDEP_GET_PATCH(J)     ((J)->patch)
508 #define JDEP_CHAIN(J)         ((J)->next)
509 #define JDEP_TO_RESOLVE(J)    ((J)->solv)
510 #define JDEP_RESOLVED_DECL(J) ((J)->solv)
511 #define JDEP_RESOLVED(J, D)   ((J)->solv = D)
512 #define JDEP_RESOLVED_P(J)    \
513         (!(J)->solv || TREE_CODE ((J)->solv) != POINTER_TYPE)
514
515 typedef struct _jdeplist {
516   jdep *first;
517   jdep *last;
518   struct _jdeplist *next;
519 } jdeplist;
520
521 #endif /* JC1_LITE */
522
523 #define CLASSD_FIRST(CD) ((CD)->first)
524 #define CLASSD_LAST(CD)  ((CD)->last)
525 #define CLASSD_CHAIN(CD) ((CD)->next)
526
527 #define JDEP_INSERT(L,J)                        \
528   {                                             \
529     if (!(L)->first)                            \
530       (L)->last = (L)->first = (J);             \
531     else                                        \
532       {                                         \
533         JDEP_CHAIN ((L)->last) = (J);           \
534         (L)->last = (J);                        \
535       }                                         \
536   }
537
538 /* if TYPE can't be resolved, obtain something suitable for its
539    resolution (TYPE is saved in SAVE before being changed). and set
540    CHAIN to 1. Otherwise, type is set to something usable. CHAIN is
541    usually used to determine that a new DEP must be installed on TYPE.
542    Note that when compiling java.lang.Object, references to Object are
543    java.lang.Object.  */
544 #define SET_TYPE_FOR_RESOLUTION(TYPE, SAVE, CHAIN)                      \
545   {                                                                     \
546     tree _returned_type;                                                \
547     (CHAIN) = 0;                                                        \
548     if (TREE_TYPE (GET_CPC ()) == object_type_node                      \
549         && TREE_CODE (TYPE) == EXPR_WITH_FILE_LOCATION                  \
550         && EXPR_WFL_NODE (TYPE) == unqualified_object_id_node)          \
551       (TYPE) = object_type_node;                                        \
552     else                                                                \
553       {                                                                 \
554         if (unresolved_type_p (type, &_returned_type))                  \
555           {                                                             \
556             if (_returned_type)                                         \
557               (TYPE) = _returned_type;                                  \
558             else                                                        \
559               {                                                         \
560                 tree _type;                                             \
561                 WFL_STRIP_BRACKET (_type, TYPE);                        \
562                 (SAVE) = (_type);                                       \
563                 (TYPE) = obtain_incomplete_type (TYPE);                 \
564                 CHAIN = 1;                                              \
565               }                                                         \
566           }                                                             \
567       }                                                                 \
568   }
569
570 #define WFL_STRIP_BRACKET(TARGET, TYPE)                                 \
571 {                                                                       \
572   tree __type = (TYPE);                                                 \
573   if (TYPE && TREE_CODE (TYPE) == EXPR_WITH_FILE_LOCATION)              \
574     {                                                                   \
575       tree _node = EXPR_WFL_NODE (TYPE);                                \
576       const char *_ptr = IDENTIFIER_POINTER (_node);                    \
577       const char *_ref = _ptr;                                          \
578       while (_ptr[0] == '[')                                            \
579           _ptr++;                                                       \
580       if (_ref != _ptr)                                                 \
581         {                                                               \
582           tree _new = copy_node (TYPE);                                 \
583           EXPR_WFL_NODE (_new) = get_identifier (_ptr);                 \
584           __type = _new;                                                \
585         }                                                               \
586     }                                                                   \
587   (TARGET) = __type;                                                    \
588 }
589
590 /* Promote a type if it won't be registered as a patch */
591 #define PROMOTE_RECORD_IF_COMPLETE(TYPE, IS_INCOMPLETE)         \
592   {                                                             \
593     if (!(IS_INCOMPLETE) && TREE_CODE (TYPE) == RECORD_TYPE)    \
594       (TYPE) = promote_type (TYPE);                             \
595   }
596
597 /* Insert a DECL in the current block */
598 #define BLOCK_CHAIN_DECL(NODE)                                              \
599   {                                                                         \
600     TREE_CHAIN ((NODE)) =                                                   \
601       BLOCK_EXPR_DECLS (GET_CURRENT_BLOCK (current_function_decl));         \
602     BLOCK_EXPR_DECLS (GET_CURRENT_BLOCK (current_function_decl)) = (NODE);  \
603   }
604
605 /* Return the current block, either found in the body of the currently
606    declared function or in the current static block being defined. */
607 #define GET_CURRENT_BLOCK(F) ((F) ? DECL_FUNCTION_BODY ((F)) :  \
608                              current_static_block)
609
610 /* For an artificial BLOCK (created to house a local variable declaration not
611    at the start of an existing block), the parent block;  otherwise NULL. */
612 #define BLOCK_EXPR_ORIGIN(NODE) BLOCK_ABSTRACT_ORIGIN(NODE)
613
614 /* Merge an other line to the source line number of a decl. Used to
615    remember function's end. */
616 #define DECL_SOURCE_LINE_MERGE(DECL,NO) DECL_SOURCE_LINE(DECL) |= (NO << 16)
617
618 /* Retrieve those two info separately. */
619 #define DECL_SOURCE_LINE_FIRST(DECL)    (DECL_SOURCE_LINE(DECL) & 0x0000ffff)
620 #define DECL_SOURCE_LINE_LAST(DECL)     (DECL_SOURCE_LINE(DECL) >> 16)
621
622 /* Retrieve line/column from a WFL. */
623 #define EXPR_WFL_GET_LINECOL(V,LINE,COL)        \
624   {                                             \
625      (LINE) = (V) >> 12;                        \
626      (COL) = (V) & 0xfff;                       \
627    }
628 /* Add X to the column number information */
629 #define EXPR_WFL_ADD_COL(V, X)                                  \
630   (V) = (((V) & 0xfffff000) | ((((V) & 0xfff) + (X)) & 0xfff))
631
632 /* Build a WFL for expression nodes */
633 #define BUILD_EXPR_WFL(NODE, WFL)                                       \
634   build_expr_wfl ((NODE), input_filename, EXPR_WFL_LINENO ((WFL)),      \
635                   EXPR_WFL_COLNO ((WFL)))
636
637 #define EXPR_WFL_QUALIFICATION(WFL) TREE_OPERAND ((WFL), 2)
638 #define QUAL_WFL(NODE) TREE_PURPOSE (NODE)
639 #define QUAL_RESOLUTION(NODE) TREE_VALUE (NODE)
640 #define QUAL_DECL_TYPE(NODE) GET_SKIP_TYPE (NODE)
641
642 #define GET_SKIP_TYPE(NODE)                             \
643   (TREE_CODE (TREE_TYPE (NODE)) == POINTER_TYPE ?       \
644    TREE_TYPE (TREE_TYPE (NODE)): TREE_TYPE (NODE))
645
646 /* Handy macros for the walk operation */
647 #define COMPLETE_CHECK_OP(NODE, N)                      \
648 {                                                       \
649   TREE_OPERAND ((NODE), (N)) =                          \
650     java_complete_tree (TREE_OPERAND ((NODE), (N)));    \
651   if (TREE_OPERAND ((NODE), (N)) == error_mark_node)    \
652     return error_mark_node;                             \
653 }
654 #define COMPLETE_CHECK_OP_0(NODE) COMPLETE_CHECK_OP(NODE, 0)
655 #define COMPLETE_CHECK_OP_1(NODE) COMPLETE_CHECK_OP(NODE, 1)
656 #define COMPLETE_CHECK_OP_2(NODE) COMPLETE_CHECK_OP(NODE, 2)
657
658 /* Building invocations: append(ARG) and StringBuffer(ARG) */
659 #define BUILD_APPEND(ARG)                                                     \
660   ((JSTRING_TYPE_P (TREE_TYPE (ARG)) || JPRIMITIVE_TYPE_P (TREE_TYPE (ARG)))  \
661    ? build_method_invocation (wfl_append,                                     \
662                               ARG ? build_tree_list (NULL, (ARG)) : NULL_TREE)\
663    : build_method_invocation (wfl_append,                                     \
664                               ARG ? build_tree_list (NULL,                    \
665                                                      build1 (CONVERT_EXPR,    \
666                                                              object_type_node,\
667                                                              (ARG)))          \
668                               : NULL_TREE))
669 #define BUILD_STRING_BUFFER(ARG)                                              \
670   build_new_invocation (wfl_string_buffer,                                    \
671                         (ARG ? build_tree_list (NULL, (ARG)) : NULL_TREE))
672
673 /* For exception handling, build diverse function calls */
674 #define BUILD_ASSIGN_EXCEPTION_INFO(WHERE, TO)          \
675   {                                                     \
676     (WHERE) = build (MODIFY_EXPR, void_type_node, (TO), \
677                      soft_exceptioninfo_call_node);     \
678     TREE_SIDE_EFFECTS (WHERE) = 1;                      \
679   }
680
681 #define BUILD_THROW(WHERE, WHAT)                                            \
682   {                                                                         \
683     (WHERE) =                                                               \
684       build (CALL_EXPR, void_type_node,                                     \
685              build_address_of (throw_node[exceptions_via_longjmp ? 1 : 0]), \
686              build_tree_list (NULL_TREE, (WHAT)), NULL_TREE);               \
687     TREE_SIDE_EFFECTS ((WHERE)) = 1;                                        \
688   }
689
690 /* Set wfl_operator for the most accurate error location */
691 #define SET_WFL_OPERATOR(WHICH, NODE, WFL)              \
692   EXPR_WFL_LINECOL (WHICH) =                            \
693     (TREE_CODE (WFL) == EXPR_WITH_FILE_LOCATION ?       \
694      EXPR_WFL_LINECOL (WFL) : EXPR_WFL_LINECOL (NODE))
695
696 #define PATCH_METHOD_RETURN_ERROR()             \
697   {                                             \
698     if (ret_decl)                               \
699       *ret_decl = NULL_TREE;                    \
700     return error_mark_node;                     \
701   }
702
703 /* Convenient macro to check. Assumes that CLASS is a CLASS_DECL.  */
704 #define CHECK_METHODS(CLASS)                    \
705   {                                             \
706     if (CLASS_INTERFACE ((CLASS)))              \
707       java_check_abstract_methods ((CLASS));    \
708     else                                        \
709       java_check_regular_methods ((CLASS));     \
710   }
711
712 /* Using and reseting the @deprecated tag flag */
713 #define CHECK_DEPRECATED(DECL)                  \
714   {                                             \
715     if (ctxp->deprecated)                       \
716       DECL_DEPRECATED (DECL) = 1;               \
717     ctxp->deprecated = 0;                       \
718   }
719
720 /* Register an import */
721 #define REGISTER_IMPORT(WHOLE, NAME)                                    \
722 {                                                                       \
723   IS_A_SINGLE_IMPORT_CLASSFILE_NAME_P ((NAME)) = 1;                     \
724   ctxp->import_list = chainon (ctxp->import_list,                       \
725                                build_tree_list ((WHOLE), (NAME)));      \
726 }
727
728 /* Macro to access the osb (opening square bracket) count */
729 #define CURRENT_OSB(C) (C)->osb_number [(C)->osb_depth]
730
731 /* Macro for the xreferencer */
732 #define DECL_END_SOURCE_LINE(DECL)       DECL_FRAME_SIZE (DECL)
733 #define DECL_INHERITED_SOURCE_LINE(DECL) (DECL_CHECK (DECL)->decl.u2.i)
734      
735 /* Parser context data structure. */
736 struct parser_ctxt {
737
738   const char *filename;             /* Current filename */
739   struct parser_ctxt *next;
740
741   java_lexer *lexer;                 /* Current lexer state */
742   char marker_begining;              /* Marker. Should be a sub-struct */
743   struct java_line *p_line, *c_line; /* Previous and current line */
744   java_lc elc;                       /* Error's line column info */
745   int ccb_indent;                    /* Keep track of {} indent, lexer */
746   int first_ccb_indent1;             /* First { at ident level 1 */
747   int last_ccb_indent1;              /* Last } at ident level 1 */
748   int parser_ccb_indent;             /* Keep track of {} indent, parser */
749   int osb_depth;                     /* Current depth of [ in an expression */
750   int osb_limit;                     /* Limit of this depth */
751   int *osb_number;                   /* Keep track of ['s */
752   int lineno;                        /* Current lineno */
753   char marker_end;                   /* End marker. Should be a sub-struct */
754
755   /* The flags section */
756
757   /* Indicates a context used for saving the parser status. The
758      context must be popped when the status is restored. */
759   unsigned saved_data_ctx:1;    
760   /* Indicates that a context already contains saved data and that the
761      next save operation will require a new context to be created. */
762   unsigned saved_data:1;
763   /* Integral literal overflow */
764   unsigned minus_seen:1;
765   /* Report error when true */
766   unsigned java_error_flag:1;
767   /* @deprecated tag seen */
768   unsigned deprecated:1;
769   /* Flag to report certain errors (fix this documentation. FIXME) */
770   unsigned class_err:1;
771
772   /* This section is defined only if we compile jc1 */
773 #ifndef JC1_LITE
774   tree modifier_ctx [11];           /* WFL of modifiers */
775   tree class_type;                  /* Current class */
776   tree function_decl;               /* Current function decl, save/restore */
777
778   struct JCF *current_jcf;          /* CU jcf */
779
780   int prevent_ese;                  /* Prevent expression statement error */
781
782   int formal_parameter_number;      /* Number of parameters found */
783   int interface_number;             /* # itfs declared to extend an itf def */
784
785   tree package;                     /* Defined package ID */
786
787   /* Those two list are saved accross file traversal */
788   tree  incomplete_class;           /* List of non-complete classes */
789   tree  gclass_list;                /* All classes seen from source code */
790
791   /* These two lists won't survive file traversal */
792   tree  class_list;                 /* List of classes in a CU */
793   jdeplist *classd_list;            /* Classe dependencies in a CU */
794   
795   tree  current_parsed_class;       /* Class currently parsed */
796   tree  current_parsed_class_un;    /* Curr. parsed class unqualified name */
797
798   tree non_static_initialized;      /* List of non static initialized fields */
799   tree static_initialized;          /* List of static non final initialized */
800   tree instance_initializers;       /* List of instancei initializers stmts */
801
802   tree import_list;                 /* List of import */
803   tree import_demand_list;          /* List of import on demand */
804
805   tree current_loop;                /* List of the currently nested 
806                                        loops/switches */
807   tree current_labeled_block;       /* List of currently nested
808                                        labeled blocks. */
809
810   int pending_block;                /* Pending block to close */
811
812   int explicit_constructor_p;       /* >0 when processing an explicit
813                                        constructor. This flag is used to trap
814                                        illegal argument usage during an
815                                        explicit constructor invocation. */
816 #endif /* JC1_LITE */
817 };
818
819 /* A set of macros to push/pop/access the currently parsed class.  */
820 #define GET_CPC_LIST()     ctxp->current_parsed_class
821
822 /* Currently class being parsed is an inner class if an enclosing
823    class has been already pushed. This truth value is only valid prior
824    an inner class is pushed. After, use FIXME. */
825 #define CPC_INNER_P() GET_CPC_LIST ()
826
827 /* Get the currently parsed class DECL_TYPE node.  */
828 #define GET_CPC() TREE_VALUE (GET_CPC_LIST ())
829
830 /* Get the currently parsed class unqualified IDENTIFIER_NODE.  */
831 #define GET_CPC_UN() TREE_PURPOSE (GET_CPC_LIST ())
832
833 /* Get a parsed class unqualified IDENTIFIER_NODE from its CPC node.  */
834 #define GET_CPC_UN_NODE(N) TREE_PURPOSE (N)
835
836 /* Get the currently parsed class DECL_TYPE from its CPC node.  */
837 #define GET_CPC_DECL_NODE(N) TREE_VALUE (N)
838
839 /* The currently parsed enclosing currently parsed TREE_LIST node.  */
840 #define GET_ENCLOSING_CPC() TREE_CHAIN (GET_CPC_LIST ())
841
842 /* Get the next enclosing context.  */
843 #define GET_NEXT_ENCLOSING_CPC(C) TREE_CHAIN (C)
844
845 /* The DECL_TYPE node of the enclosing currently parsed
846    class. NULL_TREE if the currently parsed class isn't an inner
847    class.  */
848 #define GET_ENCLOSING_CPC_CONTEXT() (GET_ENCLOSING_CPC () ?                   \
849                                      TREE_VALUE (GET_ENCLOSING_CPC ()) :      \
850                                      NULL_TREE)
851
852 /* Make sure that innerclass T sits in an appropriate enclosing
853    context.  */
854 #define INNER_ENCLOSING_SCOPE_CHECK(T)                                        \
855   (INNER_CLASS_TYPE_P ((T)) && !ANONYMOUS_CLASS_P ((T))                       \
856    && ((current_this                                                          \
857         /* We have a this and it's not the right one */                       \
858         && (DECL_CONTEXT (TYPE_NAME ((T)))                                    \
859             != TYPE_NAME (TREE_TYPE (TREE_TYPE (current_this))))              \
860         && !inherits_from_p (TREE_TYPE (TREE_TYPE (current_this)),            \
861                              TREE_TYPE (DECL_CONTEXT (TYPE_NAME (T))))        \
862         && !common_enclosing_context_p (TREE_TYPE (TREE_TYPE (current_this)), \
863                                         (T))                                  \
864         && INNER_CLASS_TYPE_P (TREE_TYPE (TREE_TYPE (current_this)))          \
865         && !inherits_from_p                                                   \
866               (TREE_TYPE (DECL_CONTEXT                                        \
867                           (TYPE_NAME (TREE_TYPE (TREE_TYPE (current_this))))),\
868                TREE_TYPE (DECL_CONTEXT (TYPE_NAME (T)))))                     \
869        /* We don't have a this. */                                            \
870        || !current_this))
871
872 /* Push macro. First argument to PUSH_CPC is a DECL_TYPE, second
873    argument is the unqualified currently parsed class name.  */
874 #define PUSH_CPC(C,R) {                                         \
875                         ctxp->current_parsed_class =            \
876                         tree_cons ((R), (C), GET_CPC_LIST ());  \
877                       }
878
879 /* In case of an error, push an error.  */
880 #define PUSH_ERROR() PUSH_CPC (error_mark_node, error_mark_node)
881
882 /* Pop macro. Before we pop, we link the current inner class decl (if any)
883    to its enclosing class.  */
884 #define POP_CPC() {                                     \
885                     link_nested_class_to_enclosing ();  \
886                     ctxp->current_parsed_class =        \
887                       TREE_CHAIN (GET_CPC_LIST ());     \
888                   }
889
890 #define DEBUG_CPC()                                             \
891   do                                                            \
892     {                                                           \
893       tree tmp =  ctxp->current_parsed_class;                   \
894       while (tmp)                                               \
895         {                                                       \
896           fprintf (stderr, "%s ",                               \
897                    IDENTIFIER_POINTER (TREE_PURPOSE (tmp)));    \
898           tmp = TREE_CHAIN (tmp);                               \
899         }                                                       \
900     }                                                           \
901   while (0);
902
903 /* Access to the various initializer statement lists */
904 #define CPC_INITIALIZER_LIST(C)          ((C)->non_static_initialized)
905 #define CPC_STATIC_INITIALIZER_LIST(C)   ((C)->static_initialized)
906 #define CPC_INSTANCE_INITIALIZER_LIST(C) ((C)->instance_initializers)
907
908 /* Access to the various initializer statements */
909 #define CPC_INITIALIZER_STMT(C) (TREE_PURPOSE (CPC_INITIALIZER_LIST (C)))
910 #define CPC_STATIC_INITIALIZER_STMT(C) \
911   (TREE_PURPOSE (CPC_STATIC_INITIALIZER_LIST (C)))
912 #define CPC_INSTANCE_INITIALIZER_STMT(C) \
913   (TREE_PURPOSE (CPC_INSTANCE_INITIALIZER_LIST (C)))
914
915 /* Set various initializer statements */
916 #define SET_CPC_INITIALIZER_STMT(C,S)                   \
917   if (CPC_INITIALIZER_LIST (C))                         \
918     TREE_PURPOSE (CPC_INITIALIZER_LIST (C)) = (S);
919 #define SET_CPC_STATIC_INITIALIZER_STMT(C,S)                    \
920   if (CPC_STATIC_INITIALIZER_LIST (C))                          \
921     TREE_PURPOSE (CPC_STATIC_INITIALIZER_LIST (C)) = (S);
922 #define SET_CPC_INSTANCE_INITIALIZER_STMT(C,S)                  \
923   if (CPC_INSTANCE_INITIALIZER_LIST(C))                         \
924     TREE_PURPOSE (CPC_INSTANCE_INITIALIZER_LIST (C)) = (S);
925
926 #ifndef JC1_LITE
927 void java_complete_class PARAMS ((void));
928 void java_check_circular_reference PARAMS ((void));
929 void java_fix_constructors PARAMS ((void));
930 void java_layout_classes PARAMS ((void));
931 void java_reorder_fields PARAMS ((void));
932 tree java_method_add_stmt PARAMS ((tree, tree));
933 void java_expand_switch PARAMS ((tree));
934 int java_report_errors PARAMS ((void));
935 extern tree do_resolve_class PARAMS ((tree, tree, tree, tree));
936 #endif
937 char *java_get_line_col PARAMS ((const char *, int, int));
938 extern void reset_report PARAMS ((void));
939
940 /* Always in use, no matter what you compile */
941 void java_push_parser_context PARAMS ((void));
942 void java_pop_parser_context PARAMS ((int));
943 void java_init_lex PARAMS ((FILE *, const char *));
944 extern void java_parser_context_save_global PARAMS ((void));
945 extern void java_parser_context_restore_global PARAMS ((void));
946 int yyparse PARAMS ((void));
947 extern int java_parse PARAMS ((void));
948 extern void yyerror PARAMS ((const char *))
949 #ifdef JC1_LITE
950 ATTRIBUTE_NORETURN
951 #endif
952 ;
953 extern void java_expand_classes PARAMS ((void));
954 #endif