118334Speter/* Separate lexical analyzer for GNU C++.
290075Sobrien   Copyright (C) 1987, 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3169689Skan   1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
418334Speter   Hacked by Michael Tiemann (tiemann@cygnus.com)
518334Speter
6132718SkanThis file is part of GCC.
718334Speter
8132718SkanGCC is free software; you can redistribute it and/or modify
918334Speterit under the terms of the GNU General Public License as published by
1018334Speterthe Free Software Foundation; either version 2, or (at your option)
1118334Speterany later version.
1218334Speter
13132718SkanGCC is distributed in the hope that it will be useful,
1418334Speterbut WITHOUT ANY WARRANTY; without even the implied warranty of
1518334SpeterMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
1618334SpeterGNU General Public License for more details.
1718334Speter
1818334SpeterYou should have received a copy of the GNU General Public License
19132718Skanalong with GCC; see the file COPYING.  If not, write to
20169689Skanthe Free Software Foundation, 51 Franklin Street, Fifth Floor,
21169689SkanBoston, MA 02110-1301, USA.  */
2218334Speter
2318334Speter
2418334Speter/* This file is the lexical analyzer for GNU C++.  */
2518334Speter
2650397Sobrien#include "config.h"
2750397Sobrien#include "system.h"
28132718Skan#include "coretypes.h"
29132718Skan#include "tm.h"
3018334Speter#include "input.h"
3118334Speter#include "tree.h"
3290075Sobrien#include "cp-tree.h"
3390075Sobrien#include "cpplib.h"
3418334Speter#include "flags.h"
3518334Speter#include "c-pragma.h"
3650397Sobrien#include "toplev.h"
3750397Sobrien#include "output.h"
3890075Sobrien#include "tm_p.h"
3990075Sobrien#include "timevar.h"
4018334Speter
41132718Skanstatic int interface_strcmp (const char *);
42132718Skanstatic void init_cp_pragma (void);
4318334Speter
44132718Skanstatic tree parse_strconst_pragma (const char *, int);
45132718Skanstatic void handle_pragma_vtable (cpp_reader *);
46132718Skanstatic void handle_pragma_unit (cpp_reader *);
47132718Skanstatic void handle_pragma_interface (cpp_reader *);
48132718Skanstatic void handle_pragma_implementation (cpp_reader *);
49132718Skanstatic void handle_pragma_java_exceptions (cpp_reader *);
5018334Speter
51132718Skanstatic void init_operators (void);
52132718Skanstatic void copy_lang_type (tree);
5350397Sobrien
5490075Sobrien/* A constraint that can be tested at compile time.  */
5590075Sobrien#define CONSTRAINT(name, expr) extern int constraint_##name [(expr) ? 1 : -1]
5618334Speter
5790075Sobrien/* Functions and data structures for #pragma interface.
5818334Speter
5990075Sobrien   `#pragma implementation' means that the main file being compiled
6090075Sobrien   is considered to implement (provide) the classes that appear in
6190075Sobrien   its main body.  I.e., if this is file "foo.cc", and class `bar'
6290075Sobrien   is defined in "foo.cc", then we say that "foo.cc implements bar".
6390075Sobrien
6490075Sobrien   All main input files "implement" themselves automagically.
6590075Sobrien
6690075Sobrien   `#pragma interface' means that unless this file (of the form "foo.h"
6790075Sobrien   is not presently being included by file "foo.cc", the
6890075Sobrien   CLASSTYPE_INTERFACE_ONLY bit gets set.  The effect is that none
6990075Sobrien   of the vtables nor any of the inline functions defined in foo.h
7090075Sobrien   will ever be output.
7190075Sobrien
7290075Sobrien   There are cases when we want to link files such as "defs.h" and
7390075Sobrien   "main.cc".  In this case, we give "defs.h" a `#pragma interface',
7490075Sobrien   and "main.cc" has `#pragma implementation "defs.h"'.  */
7590075Sobrien
7690075Sobrienstruct impl_files
7790075Sobrien{
7890075Sobrien  const char *filename;
7990075Sobrien  struct impl_files *next;
8090075Sobrien};
8190075Sobrien
8290075Sobrienstatic struct impl_files *impl_file_chain;
8390075Sobrien
8418334Speter
8550397Sobrienvoid
86132718Skancxx_finish (void)
8718334Speter{
8890075Sobrien  c_common_finish ();
8918334Speter}
9018334Speter
9190075Sobrien/* A mapping from tree codes to operator name information.  */
9290075Sobrienoperator_name_info_t operator_name_info[(int) LAST_CPLUS_TREE_CODE];
9390075Sobrien/* Similar, but for assignment operators.  */
9490075Sobrienoperator_name_info_t assignment_operator_name_info[(int) LAST_CPLUS_TREE_CODE];
9590075Sobrien
9690075Sobrien/* Initialize data structures that keep track of operator names.  */
9790075Sobrien
9890075Sobrien#define DEF_OPERATOR(NAME, C, M, AR, AP) \
9990075Sobrien CONSTRAINT (C, sizeof "operator " + sizeof NAME <= 256);
10090075Sobrien#include "operators.def"
10190075Sobrien#undef DEF_OPERATOR
10290075Sobrien
10390075Sobrienstatic void
104132718Skaninit_operators (void)
10550397Sobrien{
10690075Sobrien  tree identifier;
10790075Sobrien  char buffer[256];
10890075Sobrien  struct operator_name_info_t *oni;
10918334Speter
11090075Sobrien#define DEF_OPERATOR(NAME, CODE, MANGLING, ARITY, ASSN_P)		    \
11190075Sobrien  sprintf (buffer, ISALPHA (NAME[0]) ? "operator %s" : "operator%s", NAME); \
11290075Sobrien  identifier = get_identifier (buffer);					    \
11390075Sobrien  IDENTIFIER_OPNAME_P (identifier) = 1;					    \
11490075Sobrien									    \
11590075Sobrien  oni = (ASSN_P								    \
11690075Sobrien	 ? &assignment_operator_name_info[(int) CODE]			    \
11790075Sobrien	 : &operator_name_info[(int) CODE]);				    \
11890075Sobrien  oni->identifier = identifier;						    \
11990075Sobrien  oni->name = NAME;							    \
120169689Skan  oni->mangled_name = MANGLING;						    \
121117395Skan  oni->arity = ARITY;
12218334Speter
12390075Sobrien#include "operators.def"
12490075Sobrien#undef DEF_OPERATOR
12552284Sobrien
12690075Sobrien  operator_name_info[(int) ERROR_MARK].identifier
12790075Sobrien    = get_identifier ("<invalid operator>");
12852284Sobrien
12990075Sobrien  /* Handle some special cases.  These operators are not defined in
13090075Sobrien     the language, but can be produced internally.  We may need them
13190075Sobrien     for error-reporting.  (Eventually, we should ensure that this
13290075Sobrien     does not happen.  Error messages involving these operators will
13390075Sobrien     be confusing to users.)  */
13452284Sobrien
13590075Sobrien  operator_name_info [(int) INIT_EXPR].name
13690075Sobrien    = operator_name_info [(int) MODIFY_EXPR].name;
13790075Sobrien  operator_name_info [(int) EXACT_DIV_EXPR].name = "(ceiling /)";
13890075Sobrien  operator_name_info [(int) CEIL_DIV_EXPR].name = "(ceiling /)";
13990075Sobrien  operator_name_info [(int) FLOOR_DIV_EXPR].name = "(floor /)";
14090075Sobrien  operator_name_info [(int) ROUND_DIV_EXPR].name = "(round /)";
14190075Sobrien  operator_name_info [(int) CEIL_MOD_EXPR].name = "(ceiling %)";
14290075Sobrien  operator_name_info [(int) FLOOR_MOD_EXPR].name = "(floor %)";
14390075Sobrien  operator_name_info [(int) ROUND_MOD_EXPR].name = "(round %)";
14490075Sobrien  operator_name_info [(int) ABS_EXPR].name = "abs";
14590075Sobrien  operator_name_info [(int) TRUTH_AND_EXPR].name = "strict &&";
14690075Sobrien  operator_name_info [(int) TRUTH_OR_EXPR].name = "strict ||";
14790075Sobrien  operator_name_info [(int) RANGE_EXPR].name = "...";
148169689Skan  operator_name_info [(int) UNARY_PLUS_EXPR].name = "+";
14950397Sobrien
15090075Sobrien  assignment_operator_name_info [(int) EXACT_DIV_EXPR].name
15190075Sobrien    = "(exact /=)";
15290075Sobrien  assignment_operator_name_info [(int) CEIL_DIV_EXPR].name
15390075Sobrien    = "(ceiling /=)";
15490075Sobrien  assignment_operator_name_info [(int) FLOOR_DIV_EXPR].name
15590075Sobrien    = "(floor /=)";
15690075Sobrien  assignment_operator_name_info [(int) ROUND_DIV_EXPR].name
15790075Sobrien    = "(round /=)";
15890075Sobrien  assignment_operator_name_info [(int) CEIL_MOD_EXPR].name
15990075Sobrien    = "(ceiling %=)";
16090075Sobrien  assignment_operator_name_info [(int) FLOOR_MOD_EXPR].name
16190075Sobrien    = "(floor %=)";
16290075Sobrien  assignment_operator_name_info [(int) ROUND_MOD_EXPR].name
16390075Sobrien    = "(round %=)";
16490075Sobrien}
16550397Sobrien
16690075Sobrien/* The reserved keyword table.  */
16790075Sobrienstruct resword
16890075Sobrien{
16990075Sobrien  const char *const word;
170132718Skan  ENUM_BITFIELD(rid) const rid : 16;
17190075Sobrien  const unsigned int disable   : 16;
17290075Sobrien};
17318334Speter
17490075Sobrien/* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
17590075Sobrien   _true_.  */
17690075Sobrien#define D_EXT		0x01	/* GCC extension */
17790075Sobrien#define D_ASM		0x02	/* in C99, but has a switch to turn it off */
178169689Skan#define D_OBJC		0x04	/* Objective C++ only */
17918334Speter
18090075SobrienCONSTRAINT(ridbits_fit, RID_LAST_MODIFIER < sizeof(unsigned long) * CHAR_BIT);
18118334Speter
18290075Sobrienstatic const struct resword reswords[] =
18390075Sobrien{
18490075Sobrien  { "_Complex",		RID_COMPLEX,	0 },
18590075Sobrien  { "__FUNCTION__",	RID_FUNCTION_NAME, 0 },
18690075Sobrien  { "__PRETTY_FUNCTION__", RID_PRETTY_FUNCTION_NAME, 0 },
187169689Skan  { "__alignof",	RID_ALIGNOF,	0 },
18890075Sobrien  { "__alignof__",	RID_ALIGNOF,	0 },
18990075Sobrien  { "__asm",		RID_ASM,	0 },
19090075Sobrien  { "__asm__",		RID_ASM,	0 },
19190075Sobrien  { "__attribute",	RID_ATTRIBUTE,	0 },
19290075Sobrien  { "__attribute__",	RID_ATTRIBUTE,	0 },
193169689Skan  { "__builtin_offsetof", RID_OFFSETOF, 0 },
19490075Sobrien  { "__builtin_va_arg",	RID_VA_ARG,	0 },
19590075Sobrien  { "__complex",	RID_COMPLEX,	0 },
19690075Sobrien  { "__complex__",	RID_COMPLEX,	0 },
19790075Sobrien  { "__const",		RID_CONST,	0 },
19890075Sobrien  { "__const__",	RID_CONST,	0 },
19990075Sobrien  { "__extension__",	RID_EXTENSION,	0 },
20090075Sobrien  { "__func__",		RID_C99_FUNCTION_NAME,	0 },
20190075Sobrien  { "__imag",		RID_IMAGPART,	0 },
20290075Sobrien  { "__imag__",		RID_IMAGPART,	0 },
20390075Sobrien  { "__inline",		RID_INLINE,	0 },
20490075Sobrien  { "__inline__",	RID_INLINE,	0 },
20590075Sobrien  { "__label__",	RID_LABEL,	0 },
20690075Sobrien  { "__null",		RID_NULL,	0 },
20790075Sobrien  { "__real",		RID_REALPART,	0 },
20890075Sobrien  { "__real__",		RID_REALPART,	0 },
20990075Sobrien  { "__restrict",	RID_RESTRICT,	0 },
21090075Sobrien  { "__restrict__",	RID_RESTRICT,	0 },
21190075Sobrien  { "__signed",		RID_SIGNED,	0 },
21290075Sobrien  { "__signed__",	RID_SIGNED,	0 },
213117395Skan  { "__thread",		RID_THREAD,	0 },
21490075Sobrien  { "__typeof",		RID_TYPEOF,	0 },
21590075Sobrien  { "__typeof__",	RID_TYPEOF,	0 },
21690075Sobrien  { "__volatile",	RID_VOLATILE,	0 },
21790075Sobrien  { "__volatile__",	RID_VOLATILE,	0 },
21890075Sobrien  { "asm",		RID_ASM,	D_ASM },
21990075Sobrien  { "auto",		RID_AUTO,	0 },
22090075Sobrien  { "bool",		RID_BOOL,	0 },
22190075Sobrien  { "break",		RID_BREAK,	0 },
22290075Sobrien  { "case",		RID_CASE,	0 },
22390075Sobrien  { "catch",		RID_CATCH,	0 },
22490075Sobrien  { "char",		RID_CHAR,	0 },
22590075Sobrien  { "class",		RID_CLASS,	0 },
22690075Sobrien  { "const",		RID_CONST,	0 },
22790075Sobrien  { "const_cast",	RID_CONSTCAST,	0 },
22890075Sobrien  { "continue",		RID_CONTINUE,	0 },
22990075Sobrien  { "default",		RID_DEFAULT,	0 },
23090075Sobrien  { "delete",		RID_DELETE,	0 },
23190075Sobrien  { "do",		RID_DO,		0 },
23290075Sobrien  { "double",		RID_DOUBLE,	0 },
23390075Sobrien  { "dynamic_cast",	RID_DYNCAST,	0 },
23490075Sobrien  { "else",		RID_ELSE,	0 },
23590075Sobrien  { "enum",		RID_ENUM,	0 },
23690075Sobrien  { "explicit",		RID_EXPLICIT,	0 },
23790075Sobrien  { "export",		RID_EXPORT,	0 },
23890075Sobrien  { "extern",		RID_EXTERN,	0 },
23990075Sobrien  { "false",		RID_FALSE,	0 },
24090075Sobrien  { "float",		RID_FLOAT,	0 },
24190075Sobrien  { "for",		RID_FOR,	0 },
24290075Sobrien  { "friend",		RID_FRIEND,	0 },
24390075Sobrien  { "goto",		RID_GOTO,	0 },
24490075Sobrien  { "if",		RID_IF,		0 },
24590075Sobrien  { "inline",		RID_INLINE,	0 },
24690075Sobrien  { "int",		RID_INT,	0 },
24790075Sobrien  { "long",		RID_LONG,	0 },
24890075Sobrien  { "mutable",		RID_MUTABLE,	0 },
24990075Sobrien  { "namespace",	RID_NAMESPACE,	0 },
25090075Sobrien  { "new",		RID_NEW,	0 },
25190075Sobrien  { "operator",		RID_OPERATOR,	0 },
25290075Sobrien  { "private",		RID_PRIVATE,	0 },
25390075Sobrien  { "protected",	RID_PROTECTED,	0 },
25490075Sobrien  { "public",		RID_PUBLIC,	0 },
25590075Sobrien  { "register",		RID_REGISTER,	0 },
25690075Sobrien  { "reinterpret_cast",	RID_REINTCAST,	0 },
25790075Sobrien  { "return",		RID_RETURN,	0 },
25890075Sobrien  { "short",		RID_SHORT,	0 },
25990075Sobrien  { "signed",		RID_SIGNED,	0 },
26090075Sobrien  { "sizeof",		RID_SIZEOF,	0 },
26190075Sobrien  { "static",		RID_STATIC,	0 },
26290075Sobrien  { "static_cast",	RID_STATCAST,	0 },
26390075Sobrien  { "struct",		RID_STRUCT,	0 },
26490075Sobrien  { "switch",		RID_SWITCH,	0 },
26590075Sobrien  { "template",		RID_TEMPLATE,	0 },
26690075Sobrien  { "this",		RID_THIS,	0 },
26790075Sobrien  { "throw",		RID_THROW,	0 },
26890075Sobrien  { "true",		RID_TRUE,	0 },
26990075Sobrien  { "try",		RID_TRY,	0 },
27090075Sobrien  { "typedef",		RID_TYPEDEF,	0 },
27190075Sobrien  { "typename",		RID_TYPENAME,	0 },
27290075Sobrien  { "typeid",		RID_TYPEID,	0 },
27390075Sobrien  { "typeof",		RID_TYPEOF,	D_ASM|D_EXT },
27490075Sobrien  { "union",		RID_UNION,	0 },
27590075Sobrien  { "unsigned",		RID_UNSIGNED,	0 },
27690075Sobrien  { "using",		RID_USING,	0 },
27790075Sobrien  { "virtual",		RID_VIRTUAL,	0 },
27890075Sobrien  { "void",		RID_VOID,	0 },
27990075Sobrien  { "volatile",		RID_VOLATILE,	0 },
280169689Skan  { "wchar_t",		RID_WCHAR,	0 },
28190075Sobrien  { "while",		RID_WHILE,	0 },
28218334Speter
283169689Skan  /* The remaining keywords are specific to Objective-C++.  NB:
284169689Skan     All of them will remain _disabled_, since they are context-
285169689Skan     sensitive.  */
286169689Skan
287169689Skan  /* These ObjC keywords are recognized only immediately after
288169689Skan     an '@'.  NB: The following C++ keywords double as
289169689Skan     ObjC keywords in this context: RID_CLASS, RID_PRIVATE,
290169689Skan     RID_PROTECTED, RID_PUBLIC, RID_THROW, RID_TRY and RID_CATCH.  */
291169689Skan  { "compatibility_alias", RID_AT_ALIAS,	D_OBJC },
292169689Skan  { "defs",		RID_AT_DEFS,		D_OBJC },
293169689Skan  { "encode",		RID_AT_ENCODE,		D_OBJC },
294169689Skan  { "end",		RID_AT_END,		D_OBJC },
295169689Skan  { "implementation",	RID_AT_IMPLEMENTATION,	D_OBJC },
296169689Skan  { "interface",	RID_AT_INTERFACE,	D_OBJC },
297169689Skan  { "protocol",		RID_AT_PROTOCOL,	D_OBJC },
298169689Skan  { "selector",		RID_AT_SELECTOR,	D_OBJC },
299169689Skan  { "finally",		RID_AT_FINALLY,		D_OBJC },
300169689Skan  { "synchronized",	RID_AT_SYNCHRONIZED,	D_OBJC },
301169689Skan  /* These are recognized only in protocol-qualifier context.  */
302169689Skan  { "bycopy",		RID_BYCOPY,		D_OBJC },
303169689Skan  { "byref",		RID_BYREF,		D_OBJC },
304169689Skan  { "in",		RID_IN,			D_OBJC },
305169689Skan  { "inout",		RID_INOUT,		D_OBJC },
306169689Skan  { "oneway",		RID_ONEWAY,		D_OBJC },
307169689Skan  { "out",		RID_OUT,		D_OBJC },
30890075Sobrien};
30918334Speter
31090075Sobrienvoid
311132718Skaninit_reswords (void)
31290075Sobrien{
31390075Sobrien  unsigned int i;
31490075Sobrien  tree id;
315117395Skan  int mask = ((flag_no_asm ? D_ASM : 0)
316169689Skan	      | D_OBJC
31790075Sobrien	      | (flag_no_gnu_keywords ? D_EXT : 0));
31890075Sobrien
319169689Skan  ridpointers = GGC_CNEWVEC (tree, (int) RID_MAX);
320117395Skan  for (i = 0; i < ARRAY_SIZE (reswords); i++)
32118334Speter    {
32290075Sobrien      id = get_identifier (reswords[i].word);
32390075Sobrien      C_RID_CODE (id) = reswords[i].rid;
32490075Sobrien      ridpointers [(int) reswords[i].rid] = id;
32590075Sobrien      if (! (reswords[i].disable & mask))
32690075Sobrien	C_IS_RESERVED_WORD (id) = 1;
32718334Speter    }
32890075Sobrien}
32918334Speter
33090075Sobrienstatic void
331132718Skaninit_cp_pragma (void)
33290075Sobrien{
333132718Skan  c_register_pragma (0, "vtable", handle_pragma_vtable);
334132718Skan  c_register_pragma (0, "unit", handle_pragma_unit);
335132718Skan  c_register_pragma (0, "interface", handle_pragma_interface);
336132718Skan  c_register_pragma (0, "implementation", handle_pragma_implementation);
337132718Skan  c_register_pragma ("GCC", "interface", handle_pragma_interface);
338132718Skan  c_register_pragma ("GCC", "implementation", handle_pragma_implementation);
339132718Skan  c_register_pragma ("GCC", "java_exceptions", handle_pragma_java_exceptions);
34090075Sobrien}
341132718Skan
342169689Skan/* TRUE if a code represents a statement.  */
343169689Skan
344169689Skanbool statement_code_p[MAX_TREE_CODES];
345169689Skan
34690075Sobrien/* Initialize the C++ front end.  This function is very sensitive to
34790075Sobrien   the exact order that things are done here.  It would be nice if the
34890075Sobrien   initialization done by this routine were moved to its subroutines,
34990075Sobrien   and the ordering dependencies clarified and reduced.  */
350132718Skanbool
351132718Skancxx_init (void)
35290075Sobrien{
353169689Skan  unsigned int i;
354132718Skan  static const enum tree_code stmt_codes[] = {
355169689Skan   CTOR_INITIALIZER,	TRY_BLOCK,	HANDLER,
356169689Skan   EH_SPEC_BLOCK,	USING_STMT,	TAG_DEFN,
357169689Skan   IF_STMT,		CLEANUP_STMT,	FOR_STMT,
358169689Skan   WHILE_STMT,		DO_STMT,	BREAK_STMT,
359169689Skan   CONTINUE_STMT,	SWITCH_STMT,	EXPR_STMT
360132718Skan  };
36190075Sobrien
362169689Skan  memset (&statement_code_p, 0, sizeof (statement_code_p));
363169689Skan  for (i = 0; i < ARRAY_SIZE (stmt_codes); i++)
364169689Skan    statement_code_p[stmt_codes[i]] = true;
365132718Skan
366132718Skan  /* We cannot just assign to input_filename because it has already
367132718Skan     been initialized and will be used later as an N_BINCL for stabs+
368132718Skan     debugging.  */
369169689Skan#ifdef USE_MAPPED_LOCATION
370169689Skan  push_srcloc (BUILTINS_LOCATION);
371169689Skan#else
372169689Skan  push_srcloc ("<built-in>", 0);
373169689Skan#endif
374132718Skan
37590075Sobrien  init_reswords ();
37690075Sobrien  init_tree ();
37790075Sobrien  init_cp_semantics ();
37890075Sobrien  init_operators ();
37918334Speter  init_method ();
38018334Speter  init_error ();
38118334Speter
38218334Speter  current_function_decl = NULL;
38318334Speter
384132718Skan  class_type_node = ridpointers[(int) RID_CLASS];
38518334Speter
38690075Sobrien  cxx_init_decl_processing ();
38718334Speter
388169689Skan  /* The fact that G++ uses COMDAT for many entities (inline
389169689Skan     functions, template instantiations, virtual tables, etc.) mean
390169689Skan     that it is fundamentally unreliable to try to make decisions
391169689Skan     about whether or not to output a particular entity until the end
392169689Skan     of the compilation.  However, the inliner requires that functions
393169689Skan     be provided to the back end if they are to be inlined.
394169689Skan     Therefore, we always use unit-at-a-time mode; in that mode, we
395169689Skan     can provide entities to the back end and it will decide what to
396169689Skan     emit based on what is actually needed.  */
397169689Skan  flag_unit_at_a_time = 1;
39850397Sobrien
399132718Skan  if (c_common_init () == false)
400132718Skan    {
401132718Skan      pop_srcloc();
402132718Skan      return false;
403132718Skan    }
40418334Speter
40590075Sobrien  init_cp_pragma ();
40618334Speter
407169689Skan  init_repo ();
40818334Speter
409132718Skan  pop_srcloc();
410132718Skan  return true;
41118334Speter}
41218334Speter
41318334Speter/* Return nonzero if S is not considered part of an
41418334Speter   INTERFACE/IMPLEMENTATION pair.  Otherwise, return 0.  */
41550397Sobrien
41618334Speterstatic int
417132718Skaninterface_strcmp (const char* s)
41818334Speter{
41918334Speter  /* Set the interface/implementation bits for this scope.  */
42018334Speter  struct impl_files *ifiles;
42152284Sobrien  const char *s1;
42218334Speter
42318334Speter  for (ifiles = impl_file_chain; ifiles; ifiles = ifiles->next)
42418334Speter    {
42552284Sobrien      const char *t1 = ifiles->filename;
42618334Speter      s1 = s;
42718334Speter
42818334Speter      if (*s1 != *t1 || *s1 == 0)
42918334Speter	continue;
43018334Speter
43118334Speter      while (*s1 == *t1 && *s1 != 0)
43218334Speter	s1++, t1++;
43318334Speter
43418334Speter      /* A match.  */
43518334Speter      if (*s1 == *t1)
43618334Speter	return 0;
43718334Speter
43818334Speter      /* Don't get faked out by xxx.yyy.cc vs xxx.zzz.cc.  */
43990075Sobrien      if (strchr (s1, '.') || strchr (t1, '.'))
44018334Speter	continue;
44118334Speter
44218334Speter      if (*s1 == '\0' || s1[-1] != '.' || t1[-1] != '.')
44318334Speter	continue;
44418334Speter
44518334Speter      /* A match.  */
44618334Speter      return 0;
44718334Speter    }
44818334Speter
44918334Speter  /* No matches.  */
45018334Speter  return 1;
45118334Speter}
45218334Speter
45318334Speter
45418334Speter
45590075Sobrien/* Parse a #pragma whose sole argument is a string constant.
45690075Sobrien   If OPT is true, the argument is optional.  */
45790075Sobrienstatic tree
458132718Skanparse_strconst_pragma (const char* name, int opt)
45918334Speter{
46090075Sobrien  tree result, x;
46190075Sobrien  enum cpp_ttype t;
46290075Sobrien
463169689Skan  t = pragma_lex (&result);
46490075Sobrien  if (t == CPP_STRING)
46518334Speter    {
466169689Skan      if (pragma_lex (&x) != CPP_EOF)
467169689Skan	warning (0, "junk at end of #pragma %s", name);
46890075Sobrien      return result;
46918334Speter    }
47018334Speter
47190075Sobrien  if (t == CPP_EOF && opt)
472169689Skan    return NULL_TREE;
47318334Speter
47490075Sobrien  error ("invalid #pragma %s", name);
475169689Skan  return error_mark_node;
47618334Speter}
47718334Speter
47890075Sobrienstatic void
479132718Skanhandle_pragma_vtable (cpp_reader* dfile ATTRIBUTE_UNUSED )
48052284Sobrien{
48190075Sobrien  parse_strconst_pragma ("vtable", 0);
48290075Sobrien  sorry ("#pragma vtable no longer supported");
48352284Sobrien}
48452284Sobrien
48552284Sobrienstatic void
486132718Skanhandle_pragma_unit (cpp_reader* dfile ATTRIBUTE_UNUSED )
48752284Sobrien{
48890075Sobrien  /* Validate syntax, but don't do anything.  */
48990075Sobrien  parse_strconst_pragma ("unit", 0);
49052284Sobrien}
49152284Sobrien
49290075Sobrienstatic void
493132718Skanhandle_pragma_interface (cpp_reader* dfile ATTRIBUTE_UNUSED )
49418334Speter{
49590075Sobrien  tree fname = parse_strconst_pragma ("interface", 1);
49690075Sobrien  struct c_fileinfo *finfo;
497169689Skan  const char *filename;
49818334Speter
499169689Skan  if (fname == error_mark_node)
50090075Sobrien    return;
50190075Sobrien  else if (fname == 0)
502169689Skan    filename = lbasename (input_filename);
50390075Sobrien  else
504169689Skan    filename = ggc_strdup (TREE_STRING_POINTER (fname));
50518334Speter
50690075Sobrien  finfo = get_fileinfo (input_filename);
50718334Speter
50890075Sobrien  if (impl_file_chain == 0)
50918334Speter    {
51090075Sobrien      /* If this is zero at this point, then we are
51190075Sobrien	 auto-implementing.  */
51290075Sobrien      if (main_input_filename == 0)
51390075Sobrien	main_input_filename = input_filename;
51418334Speter    }
51518334Speter
516169689Skan  finfo->interface_only = interface_strcmp (filename);
517169689Skan  /* If MULTIPLE_SYMBOL_SPACES is set, we cannot assume that we can see
518169689Skan     a definition in another file.  */
519169689Skan  if (!MULTIPLE_SYMBOL_SPACES || !finfo->interface_only)
520169689Skan    finfo->interface_unknown = 0;
52190075Sobrien}
52218334Speter
52390075Sobrien/* Note that we have seen a #pragma implementation for the key MAIN_FILENAME.
52490075Sobrien   We used to only allow this at toplevel, but that restriction was buggy
52590075Sobrien   in older compilers and it seems reasonable to allow it in the headers
52690075Sobrien   themselves, too.  It only needs to precede the matching #p interface.
52718334Speter
528169689Skan   We don't touch finfo->interface_only or finfo->interface_unknown;
529169689Skan   the user must specify a matching #p interface for this to have
530169689Skan   any effect.  */
53118334Speter
53290075Sobrienstatic void
533132718Skanhandle_pragma_implementation (cpp_reader* dfile ATTRIBUTE_UNUSED )
53490075Sobrien{
53590075Sobrien  tree fname = parse_strconst_pragma ("implementation", 1);
536169689Skan  const char *filename;
53790075Sobrien  struct impl_files *ifiles = impl_file_chain;
53818334Speter
539169689Skan  if (fname == error_mark_node)
54090075Sobrien    return;
54118334Speter
54290075Sobrien  if (fname == 0)
54318334Speter    {
54490075Sobrien      if (main_input_filename)
545169689Skan	filename = main_input_filename;
54618334Speter      else
547169689Skan	filename = input_filename;
548169689Skan      filename = lbasename (filename);
54918334Speter    }
55018334Speter  else
55118334Speter    {
552169689Skan      filename = ggc_strdup (TREE_STRING_POINTER (fname));
553169689Skan#if 0
554169689Skan      /* We currently cannot give this diagnostic, as we reach this point
555169689Skan	 only after cpplib has scanned the entire translation unit, so
556169689Skan	 cpp_included always returns true.  A plausible fix is to compare
557169689Skan	 the current source-location cookie with the first source-location
558169689Skan	 cookie (if any) of the filename, but this requires completing the
559169689Skan	 --enable-mapped-location project first.  See PR 17577.  */
560169689Skan      if (cpp_included (parse_in, filename))
561169689Skan	warning (0, "#pragma implementation for %qs appears after "
562169689Skan		 "file is included", filename);
563169689Skan#endif
56418334Speter    }
56518334Speter
56690075Sobrien  for (; ifiles; ifiles = ifiles->next)
56750397Sobrien    {
568169689Skan      if (! strcmp (ifiles->filename, filename))
56990075Sobrien	break;
57050397Sobrien    }
57190075Sobrien  if (ifiles == 0)
57250397Sobrien    {
573169689Skan      ifiles = XNEW (struct impl_files);
574169689Skan      ifiles->filename = filename;
57590075Sobrien      ifiles->next = impl_file_chain;
57690075Sobrien      impl_file_chain = ifiles;
57750397Sobrien    }
57890075Sobrien}
57952284Sobrien
58090075Sobrien/* Indicate that this file uses Java-personality exception handling.  */
58190075Sobrienstatic void
582169689Skanhandle_pragma_java_exceptions (cpp_reader* dfile ATTRIBUTE_UNUSED)
58390075Sobrien{
58490075Sobrien  tree x;
585169689Skan  if (pragma_lex (&x) != CPP_EOF)
586169689Skan    warning (0, "junk at end of #pragma GCC java_exceptions");
58752284Sobrien
58890075Sobrien  choose_personality_routine (lang_java);
58918334Speter}
59018334Speter
591117395Skan/* Issue an error message indicating that the lookup of NAME (an
592132718Skan   IDENTIFIER_NODE) failed.  Returns the ERROR_MARK_NODE.  */
593117395Skan
594132718Skantree
595117395Skanunqualified_name_lookup_error (tree name)
596117395Skan{
597117395Skan  if (IDENTIFIER_OPNAME_P (name))
598117395Skan    {
599117395Skan      if (name != ansi_opname (ERROR_MARK))
600169689Skan	error ("%qD not defined", name);
601117395Skan    }
602117395Skan  else
603117395Skan    {
604169689Skan      error ("%qD was not declared in this scope", name);
605161651Skan      /* Prevent repeated error messages by creating a VAR_DECL with
606161651Skan	 this NAME in the innermost block scope.  */
607161651Skan      if (current_function_decl)
608117395Skan	{
609161651Skan	  tree decl;
610161651Skan	  decl = build_decl (VAR_DECL, name, error_mark_node);
611161651Skan	  DECL_CONTEXT (decl) = current_function_decl;
612161651Skan	  push_local_binding (name, decl, 0);
613169689Skan	  /* Mark the variable as used so that we do not get warnings
614169689Skan	     about it being unused later.  */
615169689Skan	  TREE_USED (decl) = 1;
616117395Skan	}
617117395Skan    }
618132718Skan
619132718Skan  return error_mark_node;
620117395Skan}
621117395Skan
622132718Skan/* Like unqualified_name_lookup_error, but NAME is an unqualified-id
623132718Skan   used as a function.  Returns an appropriate expression for
624132718Skan   NAME.  */
62518334Speter
62618334Spetertree
627132718Skanunqualified_fn_lookup_error (tree name)
62850397Sobrien{
629132718Skan  if (processing_template_decl)
63050397Sobrien    {
631132718Skan      /* In a template, it is invalid to write "f()" or "f(3)" if no
632132718Skan	 declaration of "f" is available.  Historically, G++ and most
633132718Skan	 other compilers accepted that usage since they deferred all name
634132718Skan	 lookup until instantiation time rather than doing unqualified
635169689Skan	 name lookup at template definition time; explain to the user what
636132718Skan	 is going wrong.
63750397Sobrien
638132718Skan	 Note that we have the exact wording of the following message in
639132718Skan	 the manual (trouble.texi, node "Name lookup"), so they need to
640132718Skan	 be kept in synch.  */
641169689Skan      pedwarn ("there are no arguments to %qD that depend on a template "
642169689Skan	       "parameter, so a declaration of %qD must be available",
643132718Skan	       name, name);
644169689Skan
645132718Skan      if (!flag_permissive)
64650397Sobrien	{
647132718Skan	  static bool hint;
648132718Skan	  if (!hint)
649132718Skan	    {
650169689Skan	      error ("(if you use %<-fpermissive%>, G++ will accept your "
651169689Skan		     "code, but allowing the use of an undeclared name is "
652132718Skan		     "deprecated)");
653132718Skan	      hint = true;
654132718Skan	    }
65550397Sobrien	}
656132718Skan      return name;
65750397Sobrien    }
65850397Sobrien
659132718Skan  return unqualified_name_lookup_error (name);
66018334Speter}
66118334Speter
66218334Spetertree
663132718Skanbuild_lang_decl (enum tree_code code, tree name, tree type)
66418334Speter{
66590075Sobrien  tree t;
66690075Sobrien
66790075Sobrien  t = build_decl (code, name, type);
66852284Sobrien  retrofit_lang_decl (t);
66990075Sobrien
670169689Skan  /* All nesting of C++ functions is lexical; there is never a "static
671169689Skan     chain" in the sense of GNU C nested functions.  */
672169689Skan  if (code == FUNCTION_DECL)
673169689Skan    DECL_NO_STATIC_CHAIN (t) = 1;
674169689Skan
67552284Sobrien  return t;
67652284Sobrien}
67752284Sobrien
67852284Sobrien/* Add DECL_LANG_SPECIFIC info to T.  Called from build_lang_decl
67952284Sobrien   and pushdecl (for functions generated by the backend).  */
68052284Sobrien
68152284Sobrienvoid
682132718Skanretrofit_lang_decl (tree t)
68352284Sobrien{
68490075Sobrien  struct lang_decl *ld;
68590075Sobrien  size_t size;
68618334Speter
68790075Sobrien  if (CAN_HAVE_FULL_LANG_DECL_P (t))
68890075Sobrien    size = sizeof (struct lang_decl);
68918334Speter  else
69090075Sobrien    size = sizeof (struct lang_decl_flags);
69118334Speter
692169689Skan  ld = GGC_CNEWVAR (struct lang_decl, size);
69318334Speter
694117395Skan  ld->decl_flags.can_be_full = CAN_HAVE_FULL_LANG_DECL_P (t) ? 1 : 0;
695117395Skan  ld->decl_flags.u1sel = TREE_CODE (t) == NAMESPACE_DECL ? 1 : 0;
696117395Skan  ld->decl_flags.u2sel = 0;
697117395Skan  if (ld->decl_flags.can_be_full)
698117395Skan    ld->u.f.u3sel = TREE_CODE (t) == FUNCTION_DECL ? 1 : 0;
699117395Skan
70090075Sobrien  DECL_LANG_SPECIFIC (t) = ld;
701132718Skan  if (current_lang_name == lang_name_cplusplus
702132718Skan      || decl_linkage (t) == lk_none)
70390075Sobrien    SET_DECL_LANGUAGE (t, lang_cplusplus);
70418334Speter  else if (current_lang_name == lang_name_c)
70590075Sobrien    SET_DECL_LANGUAGE (t, lang_c);
70650397Sobrien  else if (current_lang_name == lang_name_java)
70790075Sobrien    SET_DECL_LANGUAGE (t, lang_java);
708169689Skan  else
709169689Skan    gcc_unreachable ();
71018334Speter
71118334Speter#ifdef GATHER_STATISTICS
71218334Speter  tree_node_counts[(int)lang_decl] += 1;
71390075Sobrien  tree_node_sizes[(int)lang_decl] += size;
71418334Speter#endif
71518334Speter}
71618334Speter
71790075Sobrienvoid
718132718Skancxx_dup_lang_specific_decl (tree node)
71918334Speter{
72090075Sobrien  int size;
72190075Sobrien  struct lang_decl *ld;
72218334Speter
72390075Sobrien  if (! DECL_LANG_SPECIFIC (node))
72490075Sobrien    return;
72518334Speter
72690075Sobrien  if (!CAN_HAVE_FULL_LANG_DECL_P (node))
72790075Sobrien    size = sizeof (struct lang_decl_flags);
72818334Speter  else
72990075Sobrien    size = sizeof (struct lang_decl);
730169689Skan  ld = GGC_NEWVAR (struct lang_decl, size);
73190075Sobrien  memcpy (ld, DECL_LANG_SPECIFIC (node), size);
73290075Sobrien  DECL_LANG_SPECIFIC (node) = ld;
73318334Speter
73490075Sobrien#ifdef GATHER_STATISTICS
73590075Sobrien  tree_node_counts[(int)lang_decl] += 1;
73690075Sobrien  tree_node_sizes[(int)lang_decl] += size;
73790075Sobrien#endif
73890075Sobrien}
73918334Speter
74090075Sobrien/* Copy DECL, including any language-specific parts.  */
74190075Sobrien
74290075Sobrientree
743132718Skancopy_decl (tree decl)
74490075Sobrien{
74590075Sobrien  tree copy;
74690075Sobrien
74790075Sobrien  copy = copy_node (decl);
748117395Skan  cxx_dup_lang_specific_decl (copy);
74990075Sobrien  return copy;
75018334Speter}
75118334Speter
75290075Sobrien/* Replace the shared language-specific parts of NODE with a new copy.  */
75390075Sobrien
75490075Sobrienstatic void
755132718Skancopy_lang_type (tree node)
75618334Speter{
75718334Speter  int size;
75890075Sobrien  struct lang_type *lt;
75918334Speter
76090075Sobrien  if (! TYPE_LANG_SPECIFIC (node))
76150397Sobrien    return;
76250397Sobrien
763117395Skan  if (TYPE_LANG_SPECIFIC (node)->u.h.is_lang_type_class)
764117395Skan    size = sizeof (struct lang_type);
765117395Skan  else
766117395Skan    size = sizeof (struct lang_type_ptrmem);
767169689Skan  lt = GGC_NEWVAR (struct lang_type, size);
76890075Sobrien  memcpy (lt, TYPE_LANG_SPECIFIC (node), size);
76990075Sobrien  TYPE_LANG_SPECIFIC (node) = lt;
77090075Sobrien
77190075Sobrien#ifdef GATHER_STATISTICS
77290075Sobrien  tree_node_counts[(int)lang_type] += 1;
77390075Sobrien  tree_node_sizes[(int)lang_type] += size;
77490075Sobrien#endif
77518334Speter}
77618334Speter
77790075Sobrien/* Copy TYPE, including any language-specific parts.  */
77890075Sobrien
77918334Spetertree
780132718Skancopy_type (tree type)
78190075Sobrien{
78290075Sobrien  tree copy;
78390075Sobrien
78490075Sobrien  copy = copy_node (type);
78590075Sobrien  copy_lang_type (copy);
78690075Sobrien  return copy;
78790075Sobrien}
78890075Sobrien
78990075Sobrientree
790132718Skancxx_make_type (enum tree_code code)
79118334Speter{
792132718Skan  tree t = make_node (code);
79318334Speter
79490075Sobrien  /* Create lang_type structure.  */
79590075Sobrien  if (IS_AGGR_TYPE_CODE (code)
79690075Sobrien      || code == BOUND_TEMPLATE_TEMPLATE_PARM)
79752284Sobrien    {
798169689Skan      struct lang_type *pi = GGC_CNEW (struct lang_type);
79918334Speter
80090075Sobrien      TYPE_LANG_SPECIFIC (t) = pi;
801117395Skan      pi->u.c.h.is_lang_type_class = 1;
80218334Speter
80390075Sobrien#ifdef GATHER_STATISTICS
80490075Sobrien      tree_node_counts[(int)lang_type] += 1;
80590075Sobrien      tree_node_sizes[(int)lang_type] += sizeof (struct lang_type);
80690075Sobrien#endif
80790075Sobrien    }
80818334Speter
80990075Sobrien  /* Set up some flags that give proper default behavior.  */
81090075Sobrien  if (IS_AGGR_TYPE_CODE (code))
81190075Sobrien    {
812169689Skan      struct c_fileinfo *finfo = get_fileinfo (input_filename);
813169689Skan      SET_CLASSTYPE_INTERFACE_UNKNOWN_X (t, finfo->interface_unknown);
814169689Skan      CLASSTYPE_INTERFACE_ONLY (t) = finfo->interface_only;
81552284Sobrien    }
81618334Speter
81718334Speter  return t;
81818334Speter}
81918334Speter
82090075Sobrientree
821132718Skanmake_aggr_type (enum tree_code code)
82218334Speter{
823117395Skan  tree t = cxx_make_type (code);
82418334Speter
82590075Sobrien  if (IS_AGGR_TYPE_CODE (code))
82690075Sobrien    SET_IS_AGGR_TYPE (t, 1);
82718334Speter
82890075Sobrien  return t;
82918334Speter}
830220150Smm
831220150Smm/* Returns true if we are currently in the main source file, or in a
832220150Smm   template instantiation started from the main source file.  */
833220150Smm
834220150Smmbool
835220150Smmin_main_input_context (void)
836220150Smm{
837220150Smm  tree tl = outermost_tinst_level();
838220150Smm
839220150Smm  if (tl)
840220150Smm    return strcmp (main_input_filename,
841220150Smm		   LOCATION_FILE (TINST_LOCATION (tl))) == 0;
842220150Smm  else
843220150Smm    return strcmp (main_input_filename, input_filename) == 0;
844220150Smm}
845