lex.c revision 102780
1/* Separate lexical analyzer for GNU C++.
2   Copyright (C) 1987, 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
4   Hacked by Michael Tiemann (tiemann@cygnus.com)
5
6This file is part of GNU CC.
7
8GNU CC is free software; you can redistribute it and/or modify
9it under the terms of the GNU General Public License as published by
10the Free Software Foundation; either version 2, or (at your option)
11any later version.
12
13GNU CC is distributed in the hope that it will be useful,
14but WITHOUT ANY WARRANTY; without even the implied warranty of
15MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16GNU General Public License for more details.
17
18You should have received a copy of the GNU General Public License
19along with GNU CC; see the file COPYING.  If not, write to
20the Free Software Foundation, 59 Temple Place - Suite 330,
21Boston, MA 02111-1307, USA.  */
22
23
24/* This file is the lexical analyzer for GNU C++.  */
25
26/* Cause the `yydebug' variable to be defined.  */
27#define YYDEBUG 1
28
29#include "config.h"
30#include "system.h"
31#include "input.h"
32#include "tree.h"
33#include "cp-tree.h"
34#include "cpplib.h"
35#include "c-lex.h"
36#include "lex.h"
37#include "parse.h"
38#include "flags.h"
39#include "c-pragma.h"
40#include "toplev.h"
41#include "output.h"
42#include "ggc.h"
43#include "tm_p.h"
44#include "timevar.h"
45#include "diagnostic.h"
46
47#ifdef MULTIBYTE_CHARS
48#include "mbchar.h"
49#include <locale.h>
50#endif
51
52extern void yyprint PARAMS ((FILE *, int, YYSTYPE));
53
54static int interface_strcmp PARAMS ((const char *));
55static int *init_cpp_parse PARAMS ((void));
56static void init_cp_pragma PARAMS ((void));
57
58static tree parse_strconst_pragma PARAMS ((const char *, int));
59static void handle_pragma_vtable PARAMS ((cpp_reader *));
60static void handle_pragma_unit PARAMS ((cpp_reader *));
61static void handle_pragma_interface PARAMS ((cpp_reader *));
62static void handle_pragma_implementation PARAMS ((cpp_reader *));
63static void handle_pragma_java_exceptions PARAMS ((cpp_reader *));
64
65#ifdef GATHER_STATISTICS
66#ifdef REDUCE_LENGTH
67static int reduce_cmp PARAMS ((int *, int *));
68static int token_cmp PARAMS ((int *, int *));
69#endif
70#endif
71static int is_global PARAMS ((tree));
72static void init_operators PARAMS ((void));
73static void copy_lang_type PARAMS ((tree));
74
75/* A constraint that can be tested at compile time.  */
76#ifdef __STDC__
77#define CONSTRAINT(name, expr) extern int constraint_##name [(expr) ? 1 : -1]
78#else
79#define CONSTRAINT(name, expr) extern int constraint_/**/name [(expr) ? 1 : -1]
80#endif
81
82#include "cpplib.h"
83
84extern int yychar;		/*  the lookahead symbol		*/
85extern YYSTYPE yylval;		/*  the semantic value of the		*/
86				/*  lookahead symbol			*/
87
88/* These flags are used by c-lex.c.  In C++, they're always off and on,
89   respectively.  */
90int warn_traditional = 0;
91int flag_digraphs = 1;
92
93/* the declaration found for the last IDENTIFIER token read in.
94   yylex must look this up to detect typedefs, which get token type TYPENAME,
95   so it is left around in case the identifier is not a typedef but is
96   used in a context which makes it a reference to a variable.  */
97tree lastiddecl;
98
99/* Array for holding counts of the numbers of tokens seen.  */
100extern int *token_count;
101
102/* Functions and data structures for #pragma interface.
103
104   `#pragma implementation' means that the main file being compiled
105   is considered to implement (provide) the classes that appear in
106   its main body.  I.e., if this is file "foo.cc", and class `bar'
107   is defined in "foo.cc", then we say that "foo.cc implements bar".
108
109   All main input files "implement" themselves automagically.
110
111   `#pragma interface' means that unless this file (of the form "foo.h"
112   is not presently being included by file "foo.cc", the
113   CLASSTYPE_INTERFACE_ONLY bit gets set.  The effect is that none
114   of the vtables nor any of the inline functions defined in foo.h
115   will ever be output.
116
117   There are cases when we want to link files such as "defs.h" and
118   "main.cc".  In this case, we give "defs.h" a `#pragma interface',
119   and "main.cc" has `#pragma implementation "defs.h"'.  */
120
121struct impl_files
122{
123  const char *filename;
124  struct impl_files *next;
125};
126
127static struct impl_files *impl_file_chain;
128
129
130/* Return something to represent absolute declarators containing a *.
131   TARGET is the absolute declarator that the * contains.
132   CV_QUALIFIERS is a list of modifiers such as const or volatile
133   to apply to the pointer type, represented as identifiers.
134
135   We return an INDIRECT_REF whose "contents" are TARGET
136   and whose type is the modifier list.  */
137
138tree
139make_pointer_declarator (cv_qualifiers, target)
140     tree cv_qualifiers, target;
141{
142  if (target && TREE_CODE (target) == IDENTIFIER_NODE
143      && ANON_AGGRNAME_P (target))
144    error ("type name expected before `*'");
145  target = build_nt (INDIRECT_REF, target);
146  TREE_TYPE (target) = cv_qualifiers;
147  return target;
148}
149
150/* Return something to represent absolute declarators containing a &.
151   TARGET is the absolute declarator that the & contains.
152   CV_QUALIFIERS is a list of modifiers such as const or volatile
153   to apply to the reference type, represented as identifiers.
154
155   We return an ADDR_EXPR whose "contents" are TARGET
156   and whose type is the modifier list.  */
157
158tree
159make_reference_declarator (cv_qualifiers, target)
160     tree cv_qualifiers, target;
161{
162  if (target)
163    {
164      if (TREE_CODE (target) == ADDR_EXPR)
165	{
166	  error ("cannot declare references to references");
167	  return target;
168	}
169      if (TREE_CODE (target) == INDIRECT_REF)
170	{
171	  error ("cannot declare pointers to references");
172	  return target;
173	}
174      if (TREE_CODE (target) == IDENTIFIER_NODE && ANON_AGGRNAME_P (target))
175	  error ("type name expected before `&'");
176    }
177  target = build_nt (ADDR_EXPR, target);
178  TREE_TYPE (target) = cv_qualifiers;
179  return target;
180}
181
182tree
183make_call_declarator (target, parms, cv_qualifiers, exception_specification)
184     tree target, parms, cv_qualifiers, exception_specification;
185{
186  target = build_nt (CALL_EXPR, target,
187		     tree_cons (parms, cv_qualifiers, NULL_TREE),
188		     /* The third operand is really RTL.  We
189			shouldn't put anything there.  */
190		     NULL_TREE);
191  CALL_DECLARATOR_EXCEPTION_SPEC (target) = exception_specification;
192  return target;
193}
194
195void
196set_quals_and_spec (call_declarator, cv_qualifiers, exception_specification)
197     tree call_declarator, cv_qualifiers, exception_specification;
198{
199  CALL_DECLARATOR_QUALS (call_declarator) = cv_qualifiers;
200  CALL_DECLARATOR_EXCEPTION_SPEC (call_declarator) = exception_specification;
201}
202
203int interface_only;		/* whether or not current file is only for
204				   interface definitions.  */
205int interface_unknown;		/* whether or not we know this class
206				   to behave according to #pragma interface.  */
207
208/* Tree code classes. */
209
210#define DEFTREECODE(SYM, NAME, TYPE, LENGTH) TYPE,
211
212static const char cplus_tree_code_type[] = {
213  'x',
214#include "cp-tree.def"
215};
216#undef DEFTREECODE
217
218/* Table indexed by tree code giving number of expression
219   operands beyond the fixed part of the node structure.
220   Not used for types or decls.  */
221
222#define DEFTREECODE(SYM, NAME, TYPE, LENGTH) LENGTH,
223
224static const int cplus_tree_code_length[] = {
225  0,
226#include "cp-tree.def"
227};
228#undef DEFTREECODE
229
230/* Names of tree components.
231   Used for printing out the tree and error messages.  */
232#define DEFTREECODE(SYM, NAME, TYPE, LEN) NAME,
233
234static const char *const cplus_tree_code_name[] = {
235  "@@dummy",
236#include "cp-tree.def"
237};
238#undef DEFTREECODE
239
240/* Initialization before switch parsing.  */
241void
242cxx_init_options ()
243{
244  c_common_init_options (clk_cplusplus);
245
246  /* Default exceptions on.  */
247  flag_exceptions = 1;
248  /* By default wrap lines at 80 characters.  Is getenv ("COLUMNS")
249     preferable?  */
250  diagnostic_line_cutoff (global_dc) = 80;
251  /* By default, emit location information once for every
252     diagnostic message.  */
253  diagnostic_prefixing_rule (global_dc) = DIAGNOSTICS_SHOW_PREFIX_ONCE;
254}
255
256void
257cxx_finish ()
258{
259  c_common_finish ();
260}
261
262static int *
263init_cpp_parse ()
264{
265#ifdef GATHER_STATISTICS
266#ifdef REDUCE_LENGTH
267  reduce_count = (int *) xcalloc (sizeof (int), (REDUCE_LENGTH + 1));
268  reduce_count += 1;
269  token_count = (int *) xcalloc (sizeof (int), (TOKEN_LENGTH + 1));
270  token_count += 1;
271#endif
272#endif
273  return token_count;
274}
275
276/* A mapping from tree codes to operator name information.  */
277operator_name_info_t operator_name_info[(int) LAST_CPLUS_TREE_CODE];
278/* Similar, but for assignment operators.  */
279operator_name_info_t assignment_operator_name_info[(int) LAST_CPLUS_TREE_CODE];
280
281/* Initialize data structures that keep track of operator names.  */
282
283#define DEF_OPERATOR(NAME, C, M, AR, AP) \
284 CONSTRAINT (C, sizeof "operator " + sizeof NAME <= 256);
285#include "operators.def"
286#undef DEF_OPERATOR
287
288static void
289init_operators ()
290{
291  tree identifier;
292  char buffer[256];
293  struct operator_name_info_t *oni;
294
295#define DEF_OPERATOR(NAME, CODE, MANGLING, ARITY, ASSN_P)		    \
296  sprintf (buffer, ISALPHA (NAME[0]) ? "operator %s" : "operator%s", NAME); \
297  identifier = get_identifier (buffer);					    \
298  IDENTIFIER_OPNAME_P (identifier) = 1;					    \
299									    \
300  oni = (ASSN_P								    \
301	 ? &assignment_operator_name_info[(int) CODE]			    \
302	 : &operator_name_info[(int) CODE]);				    \
303  oni->identifier = identifier;						    \
304  oni->name = NAME;							    \
305  oni->mangled_name = MANGLING;
306
307#include "operators.def"
308#undef DEF_OPERATOR
309
310  operator_name_info[(int) ERROR_MARK].identifier
311    = get_identifier ("<invalid operator>");
312
313  /* Handle some special cases.  These operators are not defined in
314     the language, but can be produced internally.  We may need them
315     for error-reporting.  (Eventually, we should ensure that this
316     does not happen.  Error messages involving these operators will
317     be confusing to users.)  */
318
319  operator_name_info [(int) INIT_EXPR].name
320    = operator_name_info [(int) MODIFY_EXPR].name;
321  operator_name_info [(int) EXACT_DIV_EXPR].name = "(ceiling /)";
322  operator_name_info [(int) CEIL_DIV_EXPR].name = "(ceiling /)";
323  operator_name_info [(int) FLOOR_DIV_EXPR].name = "(floor /)";
324  operator_name_info [(int) ROUND_DIV_EXPR].name = "(round /)";
325  operator_name_info [(int) CEIL_MOD_EXPR].name = "(ceiling %)";
326  operator_name_info [(int) FLOOR_MOD_EXPR].name = "(floor %)";
327  operator_name_info [(int) ROUND_MOD_EXPR].name = "(round %)";
328  operator_name_info [(int) ABS_EXPR].name = "abs";
329  operator_name_info [(int) FFS_EXPR].name = "ffs";
330  operator_name_info [(int) BIT_ANDTC_EXPR].name = "&~";
331  operator_name_info [(int) TRUTH_AND_EXPR].name = "strict &&";
332  operator_name_info [(int) TRUTH_OR_EXPR].name = "strict ||";
333  operator_name_info [(int) IN_EXPR].name = "in";
334  operator_name_info [(int) RANGE_EXPR].name = "...";
335  operator_name_info [(int) CONVERT_EXPR].name = "+";
336
337  assignment_operator_name_info [(int) EXACT_DIV_EXPR].name
338    = "(exact /=)";
339  assignment_operator_name_info [(int) CEIL_DIV_EXPR].name
340    = "(ceiling /=)";
341  assignment_operator_name_info [(int) FLOOR_DIV_EXPR].name
342    = "(floor /=)";
343  assignment_operator_name_info [(int) ROUND_DIV_EXPR].name
344    = "(round /=)";
345  assignment_operator_name_info [(int) CEIL_MOD_EXPR].name
346    = "(ceiling %=)";
347  assignment_operator_name_info [(int) FLOOR_MOD_EXPR].name
348    = "(floor %=)";
349  assignment_operator_name_info [(int) ROUND_MOD_EXPR].name
350    = "(round %=)";
351}
352
353/* The reserved keyword table.  */
354struct resword
355{
356  const char *const word;
357  const ENUM_BITFIELD(rid) rid : 16;
358  const unsigned int disable   : 16;
359};
360
361/* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
362   _true_.  */
363#define D_EXT		0x01	/* GCC extension */
364#define D_ASM		0x02	/* in C99, but has a switch to turn it off */
365#define D_OPNAME	0x04	/* operator names */
366
367CONSTRAINT(ridbits_fit, RID_LAST_MODIFIER < sizeof(unsigned long) * CHAR_BIT);
368
369static const struct resword reswords[] =
370{
371  { "_Complex",		RID_COMPLEX,	0 },
372  { "__FUNCTION__",	RID_FUNCTION_NAME, 0 },
373  { "__PRETTY_FUNCTION__", RID_PRETTY_FUNCTION_NAME, 0 },
374  { "__alignof", 	RID_ALIGNOF,	0 },
375  { "__alignof__",	RID_ALIGNOF,	0 },
376  { "__asm",		RID_ASM,	0 },
377  { "__asm__",		RID_ASM,	0 },
378  { "__attribute",	RID_ATTRIBUTE,	0 },
379  { "__attribute__",	RID_ATTRIBUTE,	0 },
380  { "__builtin_va_arg",	RID_VA_ARG,	0 },
381  { "__complex",	RID_COMPLEX,	0 },
382  { "__complex__",	RID_COMPLEX,	0 },
383  { "__const",		RID_CONST,	0 },
384  { "__const__",	RID_CONST,	0 },
385  { "__extension__",	RID_EXTENSION,	0 },
386  { "__func__",		RID_C99_FUNCTION_NAME,	0 },
387  { "__imag",		RID_IMAGPART,	0 },
388  { "__imag__",		RID_IMAGPART,	0 },
389  { "__inline",		RID_INLINE,	0 },
390  { "__inline__",	RID_INLINE,	0 },
391  { "__label__",	RID_LABEL,	0 },
392  { "__null",		RID_NULL,	0 },
393  { "__real",		RID_REALPART,	0 },
394  { "__real__",		RID_REALPART,	0 },
395  { "__restrict",	RID_RESTRICT,	0 },
396  { "__restrict__",	RID_RESTRICT,	0 },
397  { "__signed",		RID_SIGNED,	0 },
398  { "__signed__",	RID_SIGNED,	0 },
399  { "__typeof",		RID_TYPEOF,	0 },
400  { "__typeof__",	RID_TYPEOF,	0 },
401  { "__volatile",	RID_VOLATILE,	0 },
402  { "__volatile__",	RID_VOLATILE,	0 },
403  { "asm",		RID_ASM,	D_ASM },
404  { "and",		RID_AND,	D_OPNAME },
405  { "and_eq",		RID_AND_EQ,	D_OPNAME },
406  { "auto",		RID_AUTO,	0 },
407  { "bitand",		RID_BITAND,	D_OPNAME },
408  { "bitor",		RID_BITOR,	D_OPNAME },
409  { "bool",		RID_BOOL,	0 },
410  { "break",		RID_BREAK,	0 },
411  { "case",		RID_CASE,	0 },
412  { "catch",		RID_CATCH,	0 },
413  { "char",		RID_CHAR,	0 },
414  { "class",		RID_CLASS,	0 },
415  { "compl",		RID_COMPL,	D_OPNAME },
416  { "const",		RID_CONST,	0 },
417  { "const_cast",	RID_CONSTCAST,	0 },
418  { "continue",		RID_CONTINUE,	0 },
419  { "default",		RID_DEFAULT,	0 },
420  { "delete",		RID_DELETE,	0 },
421  { "do",		RID_DO,		0 },
422  { "double",		RID_DOUBLE,	0 },
423  { "dynamic_cast",	RID_DYNCAST,	0 },
424  { "else",		RID_ELSE,	0 },
425  { "enum",		RID_ENUM,	0 },
426  { "explicit",		RID_EXPLICIT,	0 },
427  { "export",		RID_EXPORT,	0 },
428  { "extern",		RID_EXTERN,	0 },
429  { "false",		RID_FALSE,	0 },
430  { "float",		RID_FLOAT,	0 },
431  { "for",		RID_FOR,	0 },
432  { "friend",		RID_FRIEND,	0 },
433  { "goto",		RID_GOTO,	0 },
434  { "if",		RID_IF,		0 },
435  { "inline",		RID_INLINE,	0 },
436  { "int",		RID_INT,	0 },
437  { "long",		RID_LONG,	0 },
438  { "mutable",		RID_MUTABLE,	0 },
439  { "namespace",	RID_NAMESPACE,	0 },
440  { "new",		RID_NEW,	0 },
441  { "not",		RID_NOT,	D_OPNAME },
442  { "not_eq",		RID_NOT_EQ,	D_OPNAME },
443  { "operator",		RID_OPERATOR,	0 },
444  { "or",		RID_OR,		D_OPNAME },
445  { "or_eq",		RID_OR_EQ,	D_OPNAME },
446  { "private",		RID_PRIVATE,	0 },
447  { "protected",	RID_PROTECTED,	0 },
448  { "public",		RID_PUBLIC,	0 },
449  { "register",		RID_REGISTER,	0 },
450  { "reinterpret_cast",	RID_REINTCAST,	0 },
451  { "return",		RID_RETURN,	0 },
452  { "short",		RID_SHORT,	0 },
453  { "signed",		RID_SIGNED,	0 },
454  { "sizeof",		RID_SIZEOF,	0 },
455  { "static",		RID_STATIC,	0 },
456  { "static_cast",	RID_STATCAST,	0 },
457  { "struct",		RID_STRUCT,	0 },
458  { "switch",		RID_SWITCH,	0 },
459  { "template",		RID_TEMPLATE,	0 },
460  { "this",		RID_THIS,	0 },
461  { "throw",		RID_THROW,	0 },
462  { "true",		RID_TRUE,	0 },
463  { "try",		RID_TRY,	0 },
464  { "typedef",		RID_TYPEDEF,	0 },
465  { "typename",		RID_TYPENAME,	0 },
466  { "typeid",		RID_TYPEID,	0 },
467  { "typeof",		RID_TYPEOF,	D_ASM|D_EXT },
468  { "union",		RID_UNION,	0 },
469  { "unsigned",		RID_UNSIGNED,	0 },
470  { "using",		RID_USING,	0 },
471  { "virtual",		RID_VIRTUAL,	0 },
472  { "void",		RID_VOID,	0 },
473  { "volatile",		RID_VOLATILE,	0 },
474  { "wchar_t",          RID_WCHAR,	0 },
475  { "while",		RID_WHILE,	0 },
476  { "xor",		RID_XOR,	D_OPNAME },
477  { "xor_eq",		RID_XOR_EQ,	D_OPNAME },
478
479};
480#define N_reswords (sizeof reswords / sizeof (struct resword))
481
482/* Table mapping from RID_* constants to yacc token numbers.
483   Unfortunately we have to have entries for all the keywords in all
484   three languages.  */
485const short rid_to_yy[RID_MAX] =
486{
487  /* RID_STATIC */	SCSPEC,
488  /* RID_UNSIGNED */	TYPESPEC,
489  /* RID_LONG */	TYPESPEC,
490  /* RID_CONST */	CV_QUALIFIER,
491  /* RID_EXTERN */	SCSPEC,
492  /* RID_REGISTER */	SCSPEC,
493  /* RID_TYPEDEF */	SCSPEC,
494  /* RID_SHORT */	TYPESPEC,
495  /* RID_INLINE */	SCSPEC,
496  /* RID_VOLATILE */	CV_QUALIFIER,
497  /* RID_SIGNED */	TYPESPEC,
498  /* RID_AUTO */	SCSPEC,
499  /* RID_RESTRICT */	CV_QUALIFIER,
500
501  /* C extensions.  Bounded pointers are not yet in C++ */
502  /* RID_BOUNDED */	0,
503  /* RID_UNBOUNDED */	0,
504  /* RID_COMPLEX */	TYPESPEC,
505
506  /* C++ */
507  /* RID_FRIEND */	SCSPEC,
508  /* RID_VIRTUAL */	SCSPEC,
509  /* RID_EXPLICIT */	SCSPEC,
510  /* RID_EXPORT */	EXPORT,
511  /* RID_MUTABLE */	SCSPEC,
512
513  /* ObjC */
514  /* RID_IN */		0,
515  /* RID_OUT */		0,
516  /* RID_INOUT */	0,
517  /* RID_BYCOPY */	0,
518  /* RID_BYREF */	0,
519  /* RID_ONEWAY */	0,
520
521  /* C */
522  /* RID_INT */		TYPESPEC,
523  /* RID_CHAR */	TYPESPEC,
524  /* RID_FLOAT */	TYPESPEC,
525  /* RID_DOUBLE */	TYPESPEC,
526  /* RID_VOID */	TYPESPEC,
527  /* RID_ENUM */	ENUM,
528  /* RID_STRUCT */	AGGR,
529  /* RID_UNION */	AGGR,
530  /* RID_IF */		IF,
531  /* RID_ELSE */	ELSE,
532  /* RID_WHILE */	WHILE,
533  /* RID_DO */		DO,
534  /* RID_FOR */		FOR,
535  /* RID_SWITCH */	SWITCH,
536  /* RID_CASE */	CASE,
537  /* RID_DEFAULT */	DEFAULT,
538  /* RID_BREAK */	BREAK,
539  /* RID_CONTINUE */	CONTINUE,
540  /* RID_RETURN */	RETURN_KEYWORD,
541  /* RID_GOTO */	GOTO,
542  /* RID_SIZEOF */	SIZEOF,
543
544  /* C extensions */
545  /* RID_ASM */		ASM_KEYWORD,
546  /* RID_TYPEOF */	TYPEOF,
547  /* RID_ALIGNOF */	ALIGNOF,
548  /* RID_ATTRIBUTE */	ATTRIBUTE,
549  /* RID_VA_ARG */	VA_ARG,
550  /* RID_EXTENSION */	EXTENSION,
551  /* RID_IMAGPART */	IMAGPART,
552  /* RID_REALPART */	REALPART,
553  /* RID_LABEL */	LABEL,
554  /* RID_PTRBASE */	0,
555  /* RID_PTREXTENT */	0,
556  /* RID_PTRVALUE */	0,
557  /* RID_CHOOSE_EXPR */	0,
558  /* RID_TYPES_COMPATIBLE_P */ 0,
559
560  /* RID_FUNCTION_NAME */	VAR_FUNC_NAME,
561  /* RID_PRETTY_FUNCTION_NAME */ VAR_FUNC_NAME,
562  /* RID_c99_FUNCTION_NAME */	VAR_FUNC_NAME,
563
564  /* C++ */
565  /* RID_BOOL */	TYPESPEC,
566  /* RID_WCHAR */	TYPESPEC,
567  /* RID_CLASS */	AGGR,
568  /* RID_PUBLIC */	VISSPEC,
569  /* RID_PRIVATE */	VISSPEC,
570  /* RID_PROTECTED */	VISSPEC,
571  /* RID_TEMPLATE */	TEMPLATE,
572  /* RID_NULL */	CONSTANT,
573  /* RID_CATCH */	CATCH,
574  /* RID_DELETE */	DELETE,
575  /* RID_FALSE */	CXX_FALSE,
576  /* RID_NAMESPACE */	NAMESPACE,
577  /* RID_NEW */		NEW,
578  /* RID_OPERATOR */	OPERATOR,
579  /* RID_THIS */	THIS,
580  /* RID_THROW */	THROW,
581  /* RID_TRUE */	CXX_TRUE,
582  /* RID_TRY */		TRY,
583  /* RID_TYPENAME */	TYPENAME_KEYWORD,
584  /* RID_TYPEID */	TYPEID,
585  /* RID_USING */	USING,
586
587  /* casts */
588  /* RID_CONSTCAST */	CONST_CAST,
589  /* RID_DYNCAST */	DYNAMIC_CAST,
590  /* RID_REINTCAST */	REINTERPRET_CAST,
591  /* RID_STATCAST */	STATIC_CAST,
592
593  /* alternate spellings */
594  /* RID_AND */		ANDAND,
595  /* RID_AND_EQ */	ASSIGN,
596  /* RID_NOT */		'!',
597  /* RID_NOT_EQ */	EQCOMPARE,
598  /* RID_OR */		OROR,
599  /* RID_OR_EQ */	ASSIGN,
600  /* RID_XOR */		'^',
601  /* RID_XOR_EQ */	ASSIGN,
602  /* RID_BITAND */	'&',
603  /* RID_BITOR */	'|',
604  /* RID_COMPL */	'~',
605
606  /* Objective C */
607  /* RID_ID */			0,
608  /* RID_AT_ENCODE */		0,
609  /* RID_AT_END */		0,
610  /* RID_AT_CLASS */		0,
611  /* RID_AT_ALIAS */		0,
612  /* RID_AT_DEFS */		0,
613  /* RID_AT_PRIVATE */		0,
614  /* RID_AT_PROTECTED */	0,
615  /* RID_AT_PUBLIC */		0,
616  /* RID_AT_PROTOCOL */		0,
617  /* RID_AT_SELECTOR */		0,
618  /* RID_AT_INTERFACE */	0,
619  /* RID_AT_IMPLEMENTATION */	0
620};
621
622void
623init_reswords ()
624{
625  unsigned int i;
626  tree id;
627  int mask = ((flag_operator_names ? 0 : D_OPNAME)
628	      | (flag_no_asm ? D_ASM : 0)
629	      | (flag_no_gnu_keywords ? D_EXT : 0));
630
631  /* It is not necessary to register ridpointers as a GC root, because
632     all the trees it points to are permanently interned in the
633     get_identifier hash anyway.  */
634  ridpointers = (tree *) xcalloc ((int) RID_MAX, sizeof (tree));
635  for (i = 0; i < N_reswords; i++)
636    {
637      id = get_identifier (reswords[i].word);
638      C_RID_CODE (id) = reswords[i].rid;
639      ridpointers [(int) reswords[i].rid] = id;
640      if (! (reswords[i].disable & mask))
641	C_IS_RESERVED_WORD (id) = 1;
642    }
643}
644
645static void
646init_cp_pragma ()
647{
648  cpp_register_pragma (parse_in, 0, "vtable", handle_pragma_vtable);
649  cpp_register_pragma (parse_in, 0, "unit", handle_pragma_unit);
650
651  cpp_register_pragma (parse_in, 0, "interface", handle_pragma_interface);
652  cpp_register_pragma (parse_in, 0, "implementation",
653		       handle_pragma_implementation);
654
655  cpp_register_pragma (parse_in, "GCC", "interface", handle_pragma_interface);
656  cpp_register_pragma (parse_in, "GCC", "implementation",
657		       handle_pragma_implementation);
658  cpp_register_pragma (parse_in, "GCC", "java_exceptions",
659		       handle_pragma_java_exceptions);
660}
661
662/* Initialize the C++ front end.  This function is very sensitive to
663   the exact order that things are done here.  It would be nice if the
664   initialization done by this routine were moved to its subroutines,
665   and the ordering dependencies clarified and reduced.  */
666const char *
667cxx_init (filename)
668     const char *filename;
669{
670  decl_printable_name = lang_printable_name;
671  input_filename = "<internal>";
672
673  init_reswords ();
674  init_spew ();
675  init_tree ();
676  init_cplus_expand ();
677  init_cp_semantics ();
678
679  add_c_tree_codes ();
680
681  memcpy (tree_code_type + (int) LAST_C_TREE_CODE,
682	  cplus_tree_code_type,
683	  (int)LAST_CPLUS_TREE_CODE - (int)LAST_C_TREE_CODE);
684  memcpy (tree_code_length + (int) LAST_C_TREE_CODE,
685	  cplus_tree_code_length,
686	  (LAST_CPLUS_TREE_CODE - (int)LAST_C_TREE_CODE) * sizeof (int));
687  memcpy (tree_code_name + (int) LAST_C_TREE_CODE,
688	  cplus_tree_code_name,
689	  (LAST_CPLUS_TREE_CODE - (int)LAST_C_TREE_CODE) * sizeof (char *));
690
691  init_operators ();
692  init_method ();
693  init_error ();
694
695  current_function_decl = NULL;
696
697  class_type_node = build_int_2 (class_type, 0);
698  TREE_TYPE (class_type_node) = class_type_node;
699  ridpointers[(int) RID_CLASS] = class_type_node;
700
701  record_type_node = build_int_2 (record_type, 0);
702  TREE_TYPE (record_type_node) = record_type_node;
703  ridpointers[(int) RID_STRUCT] = record_type_node;
704
705  union_type_node = build_int_2 (union_type, 0);
706  TREE_TYPE (union_type_node) = union_type_node;
707  ridpointers[(int) RID_UNION] = union_type_node;
708
709  enum_type_node = build_int_2 (enum_type, 0);
710  TREE_TYPE (enum_type_node) = enum_type_node;
711  ridpointers[(int) RID_ENUM] = enum_type_node;
712
713  cxx_init_decl_processing ();
714
715  /* Create the built-in __null node.  */
716  null_node = build_int_2 (0, 0);
717  TREE_TYPE (null_node) = type_for_size (POINTER_SIZE, 0);
718  ridpointers[RID_NULL] = null_node;
719
720  token_count = init_cpp_parse ();
721  interface_unknown = 1;
722
723  filename = c_common_init (filename);
724
725  init_cp_pragma ();
726
727  init_repo (filename);
728
729  return filename;
730}
731
732inline void
733yyprint (file, yychar, yylval)
734     FILE *file;
735     int yychar;
736     YYSTYPE yylval;
737{
738  tree t;
739  switch (yychar)
740    {
741    case IDENTIFIER:
742    case TYPENAME:
743    case TYPESPEC:
744    case PTYPENAME:
745    case PFUNCNAME:
746    case IDENTIFIER_DEFN:
747    case TYPENAME_DEFN:
748    case PTYPENAME_DEFN:
749    case SCSPEC:
750    case PRE_PARSED_CLASS_DECL:
751      t = yylval.ttype;
752      if (TREE_CODE (t) == TYPE_DECL || TREE_CODE (t) == TEMPLATE_DECL)
753	{
754	  fprintf (file, " `%s'", IDENTIFIER_POINTER (DECL_NAME (t)));
755	  break;
756	}
757      my_friendly_assert (TREE_CODE (t) == IDENTIFIER_NODE, 224);
758      if (IDENTIFIER_POINTER (t))
759	  fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
760      break;
761
762    case AGGR:
763      if (yylval.ttype == class_type_node)
764	fprintf (file, " `class'");
765      else if (yylval.ttype == record_type_node)
766	fprintf (file, " `struct'");
767      else if (yylval.ttype == union_type_node)
768	fprintf (file, " `union'");
769      else if (yylval.ttype == enum_type_node)
770	fprintf (file, " `enum'");
771      else
772	abort ();
773      break;
774
775    case CONSTANT:
776      t = yylval.ttype;
777      if (TREE_CODE (t) == INTEGER_CST)
778	fprintf (file,
779#if HOST_BITS_PER_WIDE_INT == 64
780#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_INT
781		 " 0x%x%016x",
782#else
783#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_LONG
784		 " 0x%lx%016lx",
785#else
786		 " 0x%llx%016llx",
787#endif
788#endif
789#else
790#if HOST_BITS_PER_WIDE_INT != HOST_BITS_PER_INT
791		 " 0x%lx%08lx",
792#else
793		 " 0x%x%08x",
794#endif
795#endif
796		 TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
797      break;
798    }
799}
800
801#if defined(GATHER_STATISTICS) && defined(REDUCE_LENGTH)
802static int *reduce_count;
803#endif
804
805int *token_count;
806
807#if 0
808#define REDUCE_LENGTH (sizeof (yyr2) / sizeof (yyr2[0]))
809#define TOKEN_LENGTH (256 + sizeof (yytname) / sizeof (yytname[0]))
810#endif
811
812#ifdef GATHER_STATISTICS
813#ifdef REDUCE_LENGTH
814void
815yyhook (yyn)
816     int yyn;
817{
818  reduce_count[yyn] += 1;
819}
820
821static int
822reduce_cmp (p, q)
823     int *p, *q;
824{
825  return reduce_count[*q] - reduce_count[*p];
826}
827
828static int
829token_cmp (p, q)
830     int *p, *q;
831{
832  return token_count[*q] - token_count[*p];
833}
834#endif
835#endif
836
837void
838print_parse_statistics ()
839{
840#ifdef GATHER_STATISTICS
841#ifdef REDUCE_LENGTH
842#if YYDEBUG != 0
843  int i;
844  int maxlen = REDUCE_LENGTH;
845  unsigned *sorted;
846
847  if (reduce_count[-1] == 0)
848    return;
849
850  if (TOKEN_LENGTH > REDUCE_LENGTH)
851    maxlen = TOKEN_LENGTH;
852  sorted = (unsigned *) alloca (sizeof (int) * maxlen);
853
854  for (i = 0; i < TOKEN_LENGTH; i++)
855    sorted[i] = i;
856  qsort (sorted, TOKEN_LENGTH, sizeof (int), token_cmp);
857  for (i = 0; i < TOKEN_LENGTH; i++)
858    {
859      int idx = sorted[i];
860      if (token_count[idx] == 0)
861	break;
862      if (token_count[idx] < token_count[-1])
863	break;
864      fprintf (stderr, "token %d, `%s', count = %d\n",
865	       idx, yytname[YYTRANSLATE (idx)], token_count[idx]);
866    }
867  fprintf (stderr, "\n");
868  for (i = 0; i < REDUCE_LENGTH; i++)
869    sorted[i] = i;
870  qsort (sorted, REDUCE_LENGTH, sizeof (int), reduce_cmp);
871  for (i = 0; i < REDUCE_LENGTH; i++)
872    {
873      int idx = sorted[i];
874      if (reduce_count[idx] == 0)
875	break;
876      if (reduce_count[idx] < reduce_count[-1])
877	break;
878      fprintf (stderr, "rule %d, line %d, count = %d\n",
879	       idx, yyrline[idx], reduce_count[idx]);
880    }
881  fprintf (stderr, "\n");
882#endif
883#endif
884#endif
885}
886
887/* Sets the value of the 'yydebug' variable to VALUE.
888   This is a function so we don't have to have YYDEBUG defined
889   in order to build the compiler.  */
890
891void
892cxx_set_yydebug (value)
893     int value;
894{
895#if YYDEBUG != 0
896  extern int yydebug;
897  yydebug = value;
898#else
899  warning ("YYDEBUG not defined");
900#endif
901}
902
903/* Helper function to load global variables with interface
904   information.  */
905
906void
907extract_interface_info ()
908{
909  struct c_fileinfo *finfo = 0;
910
911  if (flag_alt_external_templates)
912    {
913      tree til = tinst_for_decl ();
914
915      if (til)
916	finfo = get_fileinfo (TINST_FILE (til));
917    }
918  if (!finfo)
919    finfo = get_fileinfo (input_filename);
920
921  interface_only = finfo->interface_only;
922  interface_unknown = finfo->interface_unknown;
923}
924
925/* Return nonzero if S is not considered part of an
926   INTERFACE/IMPLEMENTATION pair.  Otherwise, return 0.  */
927
928static int
929interface_strcmp (s)
930     const char *s;
931{
932  /* Set the interface/implementation bits for this scope.  */
933  struct impl_files *ifiles;
934  const char *s1;
935
936  for (ifiles = impl_file_chain; ifiles; ifiles = ifiles->next)
937    {
938      const char *t1 = ifiles->filename;
939      s1 = s;
940
941      if (*s1 != *t1 || *s1 == 0)
942	continue;
943
944      while (*s1 == *t1 && *s1 != 0)
945	s1++, t1++;
946
947      /* A match.  */
948      if (*s1 == *t1)
949	return 0;
950
951      /* Don't get faked out by xxx.yyy.cc vs xxx.zzz.cc.  */
952      if (strchr (s1, '.') || strchr (t1, '.'))
953	continue;
954
955      if (*s1 == '\0' || s1[-1] != '.' || t1[-1] != '.')
956	continue;
957
958      /* A match.  */
959      return 0;
960    }
961
962  /* No matches.  */
963  return 1;
964}
965
966/* Heuristic to tell whether the user is missing a semicolon
967   after a struct or enum declaration.  Emit an error message
968   if we know the user has blown it.  */
969
970void
971check_for_missing_semicolon (type)
972     tree type;
973{
974  if (yychar < 0)
975    yychar = yylex ();
976
977  if ((yychar > 255
978       && yychar != SCSPEC
979       && yychar != IDENTIFIER
980       && yychar != TYPENAME
981       && yychar != CV_QUALIFIER
982       && yychar != SELFNAME)
983      || yychar == 0  /* EOF */)
984    {
985      if (TYPE_ANONYMOUS_P (type))
986	error ("semicolon missing after %s declaration",
987	       TREE_CODE (type) == ENUMERAL_TYPE ? "enum" : "struct");
988      else
989	error ("semicolon missing after declaration of `%T'", type);
990      shadow_tag (build_tree_list (0, type));
991    }
992  /* Could probably also hack cases where class { ... } f (); appears.  */
993  clear_anon_tags ();
994}
995
996void
997note_got_semicolon (type)
998     tree type;
999{
1000  if (!TYPE_P (type))
1001    abort ();
1002  if (CLASS_TYPE_P (type))
1003    CLASSTYPE_GOT_SEMICOLON (type) = 1;
1004}
1005
1006void
1007note_list_got_semicolon (declspecs)
1008     tree declspecs;
1009{
1010  tree link;
1011
1012  for (link = declspecs; link; link = TREE_CHAIN (link))
1013    {
1014      tree type = TREE_VALUE (link);
1015      if (type && TYPE_P (type))
1016	note_got_semicolon (type);
1017    }
1018  clear_anon_tags ();
1019}
1020
1021
1022/* Parse a #pragma whose sole argument is a string constant.
1023   If OPT is true, the argument is optional.  */
1024static tree
1025parse_strconst_pragma (name, opt)
1026     const char *name;
1027     int opt;
1028{
1029  tree result, x;
1030  enum cpp_ttype t;
1031
1032  t = c_lex (&x);
1033  if (t == CPP_STRING)
1034    {
1035      result = x;
1036      if (c_lex (&x) != CPP_EOF)
1037	warning ("junk at end of #pragma %s", name);
1038      return result;
1039    }
1040
1041  if (t == CPP_EOF && opt)
1042    return 0;
1043
1044  error ("invalid #pragma %s", name);
1045  return (tree)-1;
1046}
1047
1048static void
1049handle_pragma_vtable (dfile)
1050     cpp_reader *dfile ATTRIBUTE_UNUSED;
1051{
1052  parse_strconst_pragma ("vtable", 0);
1053  sorry ("#pragma vtable no longer supported");
1054}
1055
1056static void
1057handle_pragma_unit (dfile)
1058     cpp_reader *dfile ATTRIBUTE_UNUSED;
1059{
1060  /* Validate syntax, but don't do anything.  */
1061  parse_strconst_pragma ("unit", 0);
1062}
1063
1064static void
1065handle_pragma_interface (dfile)
1066     cpp_reader *dfile ATTRIBUTE_UNUSED;
1067{
1068  tree fname = parse_strconst_pragma ("interface", 1);
1069  struct c_fileinfo *finfo;
1070  const char *main_filename;
1071
1072  if (fname == (tree)-1)
1073    return;
1074  else if (fname == 0)
1075    main_filename = lbasename (input_filename);
1076  else
1077    main_filename = TREE_STRING_POINTER (fname);
1078
1079  finfo = get_fileinfo (input_filename);
1080
1081  if (impl_file_chain == 0)
1082    {
1083      /* If this is zero at this point, then we are
1084	 auto-implementing.  */
1085      if (main_input_filename == 0)
1086	main_input_filename = input_filename;
1087    }
1088
1089  interface_only = interface_strcmp (main_filename);
1090#ifdef MULTIPLE_SYMBOL_SPACES
1091  if (! interface_only)
1092#endif
1093    interface_unknown = 0;
1094
1095  finfo->interface_only = interface_only;
1096  finfo->interface_unknown = interface_unknown;
1097}
1098
1099/* Note that we have seen a #pragma implementation for the key MAIN_FILENAME.
1100   We used to only allow this at toplevel, but that restriction was buggy
1101   in older compilers and it seems reasonable to allow it in the headers
1102   themselves, too.  It only needs to precede the matching #p interface.
1103
1104   We don't touch interface_only or interface_unknown; the user must specify
1105   a matching #p interface for this to have any effect.  */
1106
1107static void
1108handle_pragma_implementation (dfile)
1109     cpp_reader *dfile ATTRIBUTE_UNUSED;
1110{
1111  tree fname = parse_strconst_pragma ("implementation", 1);
1112  const char *main_filename;
1113  struct impl_files *ifiles = impl_file_chain;
1114
1115  if (fname == (tree)-1)
1116    return;
1117
1118  if (fname == 0)
1119    {
1120      if (main_input_filename)
1121	main_filename = main_input_filename;
1122      else
1123	main_filename = input_filename;
1124      main_filename = lbasename (main_filename);
1125    }
1126  else
1127    {
1128      main_filename = TREE_STRING_POINTER (fname);
1129      if (cpp_included (parse_in, main_filename))
1130	warning ("#pragma implementation for %s appears after file is included",
1131		 main_filename);
1132    }
1133
1134  for (; ifiles; ifiles = ifiles->next)
1135    {
1136      if (! strcmp (ifiles->filename, main_filename))
1137	break;
1138    }
1139  if (ifiles == 0)
1140    {
1141      ifiles = (struct impl_files*) xmalloc (sizeof (struct impl_files));
1142      ifiles->filename = main_filename;
1143      ifiles->next = impl_file_chain;
1144      impl_file_chain = ifiles;
1145    }
1146}
1147
1148/* Indicate that this file uses Java-personality exception handling.  */
1149static void
1150handle_pragma_java_exceptions (dfile)
1151     cpp_reader *dfile ATTRIBUTE_UNUSED;
1152{
1153  tree x;
1154  if (c_lex (&x) != CPP_EOF)
1155    warning ("junk at end of #pragma GCC java_exceptions");
1156
1157  choose_personality_routine (lang_java);
1158}
1159
1160void
1161do_pending_lang_change ()
1162{
1163  for (; pending_lang_change > 0; --pending_lang_change)
1164    push_lang_context (lang_name_c);
1165  for (; pending_lang_change < 0; ++pending_lang_change)
1166    pop_lang_context ();
1167}
1168
1169/* Return true if d is in a global scope. */
1170
1171static int
1172is_global (d)
1173  tree d;
1174{
1175  while (1)
1176    switch (TREE_CODE (d))
1177      {
1178      case ERROR_MARK:
1179	return 1;
1180
1181      case OVERLOAD: d = OVL_FUNCTION (d); continue;
1182      case TREE_LIST: d = TREE_VALUE (d); continue;
1183      default:
1184        my_friendly_assert (DECL_P (d), 980629);
1185
1186	return DECL_NAMESPACE_SCOPE_P (d);
1187      }
1188}
1189
1190tree
1191do_identifier (token, parsing, args)
1192     register tree token;
1193     int parsing;
1194     tree args;
1195{
1196  register tree id;
1197  int lexing = (parsing == 1);
1198
1199  if (! lexing)
1200    id = lookup_name (token, 0);
1201  else
1202    id = lastiddecl;
1203
1204  if (lexing && id && TREE_DEPRECATED (id))
1205    warn_deprecated_use (id);
1206
1207  /* Do Koenig lookup if appropriate (inside templates we build lookup
1208     expressions instead).
1209
1210     [basic.lookup.koenig]: If the ordinary unqualified lookup of the name
1211     finds the declaration of a class member function, the associated
1212     namespaces and classes are not considered.  */
1213
1214  if (args && !current_template_parms && (!id || is_global (id)))
1215    id = lookup_arg_dependent (token, id, args);
1216
1217  /* Remember that this name has been used in the class definition, as per
1218     [class.scope0] */
1219  if (id && parsing)
1220    maybe_note_name_used_in_class (token, id);
1221
1222  if (id == error_mark_node)
1223    {
1224      /* lookup_name quietly returns error_mark_node if we're parsing,
1225	 as we don't want to complain about an identifier that ends up
1226	 being used as a declarator.  So we call it again to get the error
1227	 message.  */
1228      id = lookup_name (token, 0);
1229      return error_mark_node;
1230    }
1231
1232  if (!id || (TREE_CODE (id) == FUNCTION_DECL
1233	      && DECL_ANTICIPATED (id)))
1234    {
1235      if (current_template_parms)
1236	return build_min_nt (LOOKUP_EXPR, token);
1237      else if (IDENTIFIER_OPNAME_P (token))
1238	{
1239	  if (token != ansi_opname (ERROR_MARK))
1240	    error ("`%D' not defined", token);
1241	  id = error_mark_node;
1242	}
1243      else if (current_function_decl == 0)
1244	{
1245	  error ("`%D' was not declared in this scope", token);
1246	  id = error_mark_node;
1247	}
1248      else
1249	{
1250	  if (IDENTIFIER_NAMESPACE_VALUE (token) != error_mark_node
1251	      || IDENTIFIER_ERROR_LOCUS (token) != current_function_decl)
1252	    {
1253	      static int undeclared_variable_notice;
1254
1255	      error ("`%D' undeclared (first use this function)", token);
1256
1257	      if (! undeclared_variable_notice)
1258		{
1259		  error ("(Each undeclared identifier is reported only once for each function it appears in.)");
1260		  undeclared_variable_notice = 1;
1261		}
1262	    }
1263	  id = error_mark_node;
1264	  /* Prevent repeated error messages.  */
1265	  SET_IDENTIFIER_NAMESPACE_VALUE (token, error_mark_node);
1266	  SET_IDENTIFIER_ERROR_LOCUS (token, current_function_decl);
1267	}
1268    }
1269
1270  if (TREE_CODE (id) == VAR_DECL && DECL_DEAD_FOR_LOCAL (id))
1271    {
1272      tree shadowed = DECL_SHADOWED_FOR_VAR (id);
1273      while (shadowed != NULL_TREE && TREE_CODE (shadowed) == VAR_DECL
1274	     && DECL_DEAD_FOR_LOCAL (shadowed))
1275	shadowed = DECL_SHADOWED_FOR_VAR (shadowed);
1276      if (!shadowed)
1277	shadowed = IDENTIFIER_NAMESPACE_VALUE (DECL_NAME (id));
1278      if (shadowed)
1279	{
1280	  if (!DECL_ERROR_REPORTED (id))
1281	    {
1282	      warning ("name lookup of `%s' changed",
1283		       IDENTIFIER_POINTER (token));
1284	      cp_warning_at ("  matches this `%D' under ISO standard rules",
1285			     shadowed);
1286	      cp_warning_at ("  matches this `%D' under old rules", id);
1287	      DECL_ERROR_REPORTED (id) = 1;
1288	    }
1289	  id = shadowed;
1290	}
1291      else if (!DECL_ERROR_REPORTED (id))
1292	{
1293	  DECL_ERROR_REPORTED (id) = 1;
1294	  if (TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (id)))
1295	    {
1296	      error ("name lookup of `%s' changed for new ISO `for' scoping",
1297		     IDENTIFIER_POINTER (token));
1298	      cp_error_at ("  cannot use obsolete binding at `%D' because it has a destructor", id);
1299	      id = error_mark_node;
1300	    }
1301	  else
1302	    {
1303	      pedwarn ("name lookup of `%s' changed for new ISO `for' scoping",
1304		       IDENTIFIER_POINTER (token));
1305	      cp_pedwarn_at ("  using obsolete binding at `%D'", id);
1306	    }
1307	}
1308    }
1309  /* TREE_USED is set in `hack_identifier'.  */
1310  if (TREE_CODE (id) == CONST_DECL)
1311    {
1312      /* Check access.  */
1313      if (IDENTIFIER_CLASS_VALUE (token) == id)
1314	enforce_access (CP_DECL_CONTEXT(id), id);
1315      if (!processing_template_decl || DECL_TEMPLATE_PARM_P (id))
1316	id = DECL_INITIAL (id);
1317    }
1318  else
1319    id = hack_identifier (id, token);
1320
1321  /* We must look up dependent names when the template is
1322     instantiated, not while parsing it.  For now, we don't
1323     distinguish between dependent and independent names.  So, for
1324     example, we look up all overloaded functions at
1325     instantiation-time, even though in some cases we should just use
1326     the DECL we have here.  We also use LOOKUP_EXPRs to find things
1327     like local variables, rather than creating TEMPLATE_DECLs for the
1328     local variables and then finding matching instantiations.  */
1329  if (current_template_parms
1330      && (is_overloaded_fn (id)
1331	  || (TREE_CODE (id) == VAR_DECL
1332	      && CP_DECL_CONTEXT (id)
1333	      && TREE_CODE (CP_DECL_CONTEXT (id)) == FUNCTION_DECL)
1334	  || TREE_CODE (id) == PARM_DECL
1335	  || TREE_CODE (id) == RESULT_DECL
1336	  || TREE_CODE (id) == USING_DECL))
1337    id = build_min_nt (LOOKUP_EXPR, token);
1338
1339  return id;
1340}
1341
1342tree
1343do_scoped_id (token, parsing)
1344     tree token;
1345     int parsing;
1346{
1347  tree id;
1348  /* during parsing, this is ::name. Otherwise, it is black magic. */
1349  if (parsing)
1350    {
1351      id = make_node (CPLUS_BINDING);
1352      if (!qualified_lookup_using_namespace (token, global_namespace, id, 0))
1353	id = NULL_TREE;
1354      else
1355	id = BINDING_VALUE (id);
1356    }
1357  else
1358    id = IDENTIFIER_GLOBAL_VALUE (token);
1359  if (parsing && yychar == YYEMPTY)
1360    yychar = yylex ();
1361  if (!id || (TREE_CODE (id) == FUNCTION_DECL
1362	      && DECL_ANTICIPATED (id)))
1363    {
1364      if (processing_template_decl)
1365	{
1366	  id = build_min_nt (LOOKUP_EXPR, token);
1367	  LOOKUP_EXPR_GLOBAL (id) = 1;
1368	  return id;
1369	}
1370      if (IDENTIFIER_NAMESPACE_VALUE (token) != error_mark_node)
1371        error ("`::%D' undeclared (first use here)", token);
1372      id = error_mark_node;
1373      /* Prevent repeated error messages.  */
1374      SET_IDENTIFIER_NAMESPACE_VALUE (token, error_mark_node);
1375    }
1376  else
1377    {
1378      if (TREE_CODE (id) == ADDR_EXPR)
1379	mark_used (TREE_OPERAND (id, 0));
1380      else if (TREE_CODE (id) != OVERLOAD)
1381	mark_used (id);
1382    }
1383  if (TREE_CODE (id) == CONST_DECL && ! processing_template_decl)
1384    {
1385      /* XXX CHS - should we set TREE_USED of the constant? */
1386      id = DECL_INITIAL (id);
1387      /* This is to prevent an enum whose value is 0
1388	 from being considered a null pointer constant.  */
1389      id = build1 (NOP_EXPR, TREE_TYPE (id), id);
1390      TREE_CONSTANT (id) = 1;
1391    }
1392
1393  if (processing_template_decl)
1394    {
1395      if (is_overloaded_fn (id))
1396	{
1397	  id = build_min_nt (LOOKUP_EXPR, token);
1398	  LOOKUP_EXPR_GLOBAL (id) = 1;
1399	  return id;
1400	}
1401      /* else just use the decl */
1402    }
1403  return convert_from_reference (id);
1404}
1405
1406tree
1407identifier_typedecl_value (node)
1408     tree node;
1409{
1410  tree t, type;
1411  type = IDENTIFIER_TYPE_VALUE (node);
1412  if (type == NULL_TREE)
1413    return NULL_TREE;
1414
1415  if (IDENTIFIER_BINDING (node))
1416    {
1417      t = IDENTIFIER_VALUE (node);
1418      if (t && TREE_CODE (t) == TYPE_DECL && TREE_TYPE (t) == type)
1419	return t;
1420    }
1421  if (IDENTIFIER_NAMESPACE_VALUE (node))
1422    {
1423      t = IDENTIFIER_NAMESPACE_VALUE (node);
1424      if (t && TREE_CODE (t) == TYPE_DECL && TREE_TYPE (t) == type)
1425	return t;
1426    }
1427
1428  /* Will this one ever happen?  */
1429  if (TYPE_MAIN_DECL (type))
1430    return TYPE_MAIN_DECL (type);
1431
1432  /* We used to do an internal error of 62 here, but instead we will
1433     handle the return of a null appropriately in the callers.  */
1434  return NULL_TREE;
1435}
1436
1437#ifdef GATHER_STATISTICS
1438/* The original for tree_node_kind is in the toplevel tree.c; changes there
1439   need to be brought into here, unless this were actually put into a header
1440   instead.  */
1441/* Statistics-gathering stuff.  */
1442typedef enum
1443{
1444  d_kind,
1445  t_kind,
1446  b_kind,
1447  s_kind,
1448  r_kind,
1449  e_kind,
1450  c_kind,
1451  id_kind,
1452  op_id_kind,
1453  perm_list_kind,
1454  temp_list_kind,
1455  vec_kind,
1456  x_kind,
1457  lang_decl,
1458  lang_type,
1459  all_kinds
1460} tree_node_kind;
1461
1462extern int tree_node_counts[];
1463extern int tree_node_sizes[];
1464#endif
1465
1466tree
1467build_lang_decl (code, name, type)
1468     enum tree_code code;
1469     tree name;
1470     tree type;
1471{
1472  tree t;
1473
1474  t = build_decl (code, name, type);
1475  retrofit_lang_decl (t);
1476
1477  return t;
1478}
1479
1480/* Add DECL_LANG_SPECIFIC info to T.  Called from build_lang_decl
1481   and pushdecl (for functions generated by the backend).  */
1482
1483void
1484retrofit_lang_decl (t)
1485     tree t;
1486{
1487  struct lang_decl *ld;
1488  size_t size;
1489
1490  if (CAN_HAVE_FULL_LANG_DECL_P (t))
1491    size = sizeof (struct lang_decl);
1492  else
1493    size = sizeof (struct lang_decl_flags);
1494
1495  ld = (struct lang_decl *) ggc_alloc_cleared (size);
1496
1497  DECL_LANG_SPECIFIC (t) = ld;
1498  if (current_lang_name == lang_name_cplusplus)
1499    SET_DECL_LANGUAGE (t, lang_cplusplus);
1500  else if (current_lang_name == lang_name_c)
1501    SET_DECL_LANGUAGE (t, lang_c);
1502  else if (current_lang_name == lang_name_java)
1503    SET_DECL_LANGUAGE (t, lang_java);
1504  else abort ();
1505
1506#ifdef GATHER_STATISTICS
1507  tree_node_counts[(int)lang_decl] += 1;
1508  tree_node_sizes[(int)lang_decl] += size;
1509#endif
1510}
1511
1512void
1513copy_lang_decl (node)
1514     tree node;
1515{
1516  int size;
1517  struct lang_decl *ld;
1518
1519  if (! DECL_LANG_SPECIFIC (node))
1520    return;
1521
1522  if (!CAN_HAVE_FULL_LANG_DECL_P (node))
1523    size = sizeof (struct lang_decl_flags);
1524  else
1525    size = sizeof (struct lang_decl);
1526  ld = (struct lang_decl *) ggc_alloc (size);
1527  memcpy (ld, DECL_LANG_SPECIFIC (node), size);
1528  DECL_LANG_SPECIFIC (node) = ld;
1529
1530#ifdef GATHER_STATISTICS
1531  tree_node_counts[(int)lang_decl] += 1;
1532  tree_node_sizes[(int)lang_decl] += size;
1533#endif
1534}
1535
1536/* Copy DECL, including any language-specific parts.  */
1537
1538tree
1539copy_decl (decl)
1540     tree decl;
1541{
1542  tree copy;
1543
1544  copy = copy_node (decl);
1545  copy_lang_decl (copy);
1546  return copy;
1547}
1548
1549/* Replace the shared language-specific parts of NODE with a new copy.  */
1550
1551static void
1552copy_lang_type (node)
1553     tree node;
1554{
1555  int size;
1556  struct lang_type *lt;
1557
1558  if (! TYPE_LANG_SPECIFIC (node))
1559    return;
1560
1561  size = sizeof (struct lang_type);
1562  lt = (struct lang_type *) ggc_alloc (size);
1563  memcpy (lt, TYPE_LANG_SPECIFIC (node), size);
1564  TYPE_LANG_SPECIFIC (node) = lt;
1565
1566#ifdef GATHER_STATISTICS
1567  tree_node_counts[(int)lang_type] += 1;
1568  tree_node_sizes[(int)lang_type] += size;
1569#endif
1570}
1571
1572/* Copy TYPE, including any language-specific parts.  */
1573
1574tree
1575copy_type (type)
1576     tree type;
1577{
1578  tree copy;
1579
1580  copy = copy_node (type);
1581  copy_lang_type (copy);
1582  return copy;
1583}
1584
1585tree
1586cp_make_lang_type (code)
1587     enum tree_code code;
1588{
1589  register tree t = make_node (code);
1590
1591  /* Create lang_type structure.  */
1592  if (IS_AGGR_TYPE_CODE (code)
1593      || code == BOUND_TEMPLATE_TEMPLATE_PARM)
1594    {
1595      struct lang_type *pi;
1596
1597      pi = ((struct lang_type *)
1598	    ggc_alloc_cleared (sizeof (struct lang_type)));
1599
1600      TYPE_LANG_SPECIFIC (t) = pi;
1601
1602#ifdef GATHER_STATISTICS
1603      tree_node_counts[(int)lang_type] += 1;
1604      tree_node_sizes[(int)lang_type] += sizeof (struct lang_type);
1605#endif
1606    }
1607
1608  /* Set up some flags that give proper default behavior.  */
1609  if (IS_AGGR_TYPE_CODE (code))
1610    {
1611      SET_CLASSTYPE_INTERFACE_UNKNOWN_X (t, interface_unknown);
1612      CLASSTYPE_INTERFACE_ONLY (t) = interface_only;
1613
1614      /* Make sure this is laid out, for ease of use later.  In the
1615	 presence of parse errors, the normal was of assuring this
1616	 might not ever get executed, so we lay it out *immediately*.  */
1617      build_pointer_type (t);
1618    }
1619  else
1620    /* We use TYPE_ALIAS_SET for the CLASSTYPE_MARKED bits.  But,
1621       TYPE_ALIAS_SET is initialized to -1 by default, so we must
1622       clear it here.  */
1623    TYPE_ALIAS_SET (t) = 0;
1624
1625  /* We need to allocate a TYPE_BINFO even for TEMPLATE_TYPE_PARMs
1626     since they can be virtual base types, and we then need a
1627     canonical binfo for them.  Ideally, this would be done lazily for
1628     all types.  */
1629  if (IS_AGGR_TYPE_CODE (code) || code == TEMPLATE_TYPE_PARM
1630      || code == BOUND_TEMPLATE_TEMPLATE_PARM
1631      || code == TYPENAME_TYPE)
1632    TYPE_BINFO (t) = make_binfo (size_zero_node, t, NULL_TREE, NULL_TREE);
1633
1634  return t;
1635}
1636
1637tree
1638make_aggr_type (code)
1639     enum tree_code code;
1640{
1641  tree t = cp_make_lang_type (code);
1642
1643  if (IS_AGGR_TYPE_CODE (code))
1644    SET_IS_AGGR_TYPE (t, 1);
1645
1646  return t;
1647}
1648
1649void
1650compiler_error VPARAMS ((const char *msg, ...))
1651{
1652  char buf[1024];
1653
1654  VA_OPEN (ap, msg);
1655  VA_FIXEDARG (ap, const char *, msg);
1656
1657  vsprintf (buf, msg, ap);
1658  VA_CLOSE (ap);
1659
1660  error_with_file_and_line (input_filename, lineno, "%s (compiler error)", buf);
1661}
1662
1663/* Return the type-qualifier corresponding to the identifier given by
1664   RID.  */
1665
1666int
1667cp_type_qual_from_rid (rid)
1668     tree rid;
1669{
1670  if (rid == ridpointers[(int) RID_CONST])
1671    return TYPE_QUAL_CONST;
1672  else if (rid == ridpointers[(int) RID_VOLATILE])
1673    return TYPE_QUAL_VOLATILE;
1674  else if (rid == ridpointers[(int) RID_RESTRICT])
1675    return TYPE_QUAL_RESTRICT;
1676
1677  abort ();
1678  return TYPE_UNQUALIFIED;
1679}
1680