rtti.c revision 117395
1/* RunTime Type Identification
2   Copyright (C) 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002
3   Free Software Foundation, Inc.
4   Mostly written by Jason Merrill (jason@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#include "config.h"
25#include "system.h"
26#include "tree.h"
27#include "cp-tree.h"
28#include "flags.h"
29#include "output.h"
30#include "assert.h"
31#include "toplev.h"
32
33/* C++ returns type information to the user in struct type_info
34   objects. We also use type information to implement dynamic_cast and
35   exception handlers. Type information for a particular type is
36   indicated with an ABI defined structure derived from type_info.
37   This would all be very straight forward, but for the fact that the
38   runtime library provides the definitions of the type_info structure
39   and the ABI defined derived classes. We cannot build declarations
40   of them directly in the compiler, but we need to layout objects of
41   their type.  Somewhere we have to lie.
42
43   We define layout compatible POD-structs with compiler-defined names
44   and generate the appropriate initializations for them (complete
45   with explicit mention of their vtable). When we have to provide a
46   type_info to the user we reinterpret_cast the internal compiler
47   type to type_info.  A well formed program can only explicitly refer
48   to the type_infos of complete types (& cv void).  However, we chain
49   pointer type_infos to the pointed-to-type, and that can be
50   incomplete.  We only need the addresses of such incomplete
51   type_info objects for static initialization.
52
53   The type information VAR_DECL of a type is held on the
54   IDENTIFIER_GLOBAL_VALUE of the type's mangled name. That VAR_DECL
55   will be the internal type.  It will usually have the correct
56   internal type reflecting the kind of type it represents (pointer,
57   array, function, class, inherited class, etc).  When the type it
58   represents is incomplete, it will have the internal type
59   corresponding to type_info.  That will only happen at the end of
60   translation, when we are emitting the type info objects.  */
61
62/* Accessors for the type_info objects. We need to remember several things
63   about each of the type_info types. The global tree nodes such as
64   bltn_desc_type_node are TREE_LISTs, and these macros are used to access
65   the required information.  */
66/* The RECORD_TYPE of a type_info derived class.  */
67#define TINFO_PSEUDO_TYPE(NODE) TREE_TYPE (NODE)
68/* The VAR_DECL of the vtable for the type_info derived class.
69   This is only filled in at the end of the translation.  */
70#define TINFO_VTABLE_DECL(NODE) TREE_VALUE (NODE)
71/* The IDENTIFIER_NODE naming the real class.  */
72#define TINFO_REAL_NAME(NODE) TREE_PURPOSE (NODE)
73
74static tree build_headof PARAMS((tree));
75static tree ifnonnull PARAMS((tree, tree));
76static tree tinfo_name PARAMS((tree));
77static tree build_dynamic_cast_1 PARAMS((tree, tree));
78static tree throw_bad_cast PARAMS((void));
79static tree throw_bad_typeid PARAMS((void));
80static tree get_tinfo_decl_dynamic PARAMS((tree));
81static tree get_tinfo_ptr PARAMS((tree));
82static bool typeid_ok_p PARAMS((void));
83static int qualifier_flags PARAMS((tree));
84static int target_incomplete_p PARAMS((tree));
85static tree tinfo_base_init PARAMS((tree, tree));
86static tree generic_initializer PARAMS((tree, tree));
87static tree ptr_initializer PARAMS((tree, tree, int *));
88static tree ptm_initializer PARAMS((tree, tree, int *));
89static tree dfs_class_hint_mark PARAMS ((tree, void *));
90static tree dfs_class_hint_unmark PARAMS ((tree, void *));
91static int class_hint_flags PARAMS((tree));
92static tree class_initializer PARAMS((tree, tree, tree));
93static tree create_pseudo_type_info PARAMS((const char *, int, ...));
94static tree get_pseudo_ti_init PARAMS ((tree, tree, int *));
95static tree get_pseudo_ti_desc PARAMS((tree));
96static void create_tinfo_types PARAMS((void));
97static int typeinfo_in_lib_p PARAMS((tree));
98
99static int doing_runtime = 0;
100
101
102/* Declare language defined type_info type and a pointer to const
103   type_info.  This is incomplete here, and will be completed when
104   the user #includes <typeinfo>.  There are language defined
105   restrictions on what can be done until that is included.  Create
106   the internal versions of the ABI types.  */
107
108void
109init_rtti_processing ()
110{
111  push_namespace (std_identifier);
112  type_info_type_node
113    = xref_tag (class_type, get_identifier ("type_info"),
114		/*attributes=*/NULL_TREE, 1);
115  pop_namespace ();
116  type_info_ptr_type =
117    build_pointer_type
118     (build_qualified_type (type_info_type_node, TYPE_QUAL_CONST));
119
120  create_tinfo_types ();
121}
122
123/* Given the expression EXP of type `class *', return the head of the
124   object pointed to by EXP with type cv void*, if the class has any
125   virtual functions (TYPE_POLYMORPHIC_P), else just return the
126   expression.  */
127
128static tree
129build_headof (exp)
130     tree exp;
131{
132  tree type = TREE_TYPE (exp);
133  tree offset;
134  tree index;
135
136  my_friendly_assert (TREE_CODE (type) == POINTER_TYPE, 20000112);
137  type = TREE_TYPE (type);
138
139  if (!TYPE_POLYMORPHIC_P (type))
140    return exp;
141
142  /* We use this a couple of times below, protect it.  */
143  exp = save_expr (exp);
144
145  /* The offset-to-top field is at index -2 from the vptr.  */
146  index = build_int_2 (-2 * TARGET_VTABLE_DATA_ENTRY_DISTANCE, -1);
147
148  offset = build_vtbl_ref (build_indirect_ref (exp, NULL), index);
149
150  type = build_qualified_type (ptr_type_node,
151			       cp_type_quals (TREE_TYPE (exp)));
152  return build (PLUS_EXPR, type, exp,
153		cp_convert (ptrdiff_type_node, offset));
154}
155
156/* Get a bad_cast node for the program to throw...
157
158   See libstdc++/exception.cc for __throw_bad_cast */
159
160static tree
161throw_bad_cast ()
162{
163  tree fn = get_identifier ("__cxa_bad_cast");
164  if (IDENTIFIER_GLOBAL_VALUE (fn))
165    fn = IDENTIFIER_GLOBAL_VALUE (fn);
166  else
167    fn = push_throw_library_fn (fn, build_function_type (ptr_type_node,
168							 void_list_node));
169
170  return build_cxx_call (fn, NULL_TREE, NULL_TREE);
171}
172
173static tree
174throw_bad_typeid ()
175{
176  tree fn = get_identifier ("__cxa_bad_typeid");
177  if (IDENTIFIER_GLOBAL_VALUE (fn))
178    fn = IDENTIFIER_GLOBAL_VALUE (fn);
179  else
180    {
181      tree t = build_qualified_type (type_info_type_node, TYPE_QUAL_CONST);
182      t = build_function_type (build_reference_type (t), void_list_node);
183      fn = push_throw_library_fn (fn, t);
184    }
185
186  return build_cxx_call (fn, NULL_TREE, NULL_TREE);
187}
188
189/* Return a pointer to type_info function associated with the expression EXP.
190   If EXP is a reference to a polymorphic class, return the dynamic type;
191   otherwise return the static type of the expression.  */
192
193static tree
194get_tinfo_decl_dynamic (exp)
195     tree exp;
196{
197  tree type;
198
199  if (exp == error_mark_node)
200    return error_mark_node;
201
202  type = TREE_TYPE (exp);
203
204  /* peel back references, so they match.  */
205  if (TREE_CODE (type) == REFERENCE_TYPE)
206    type = TREE_TYPE (type);
207
208  /* Peel off cv qualifiers.  */
209  type = TYPE_MAIN_VARIANT (type);
210
211  if (!VOID_TYPE_P (type))
212    type = complete_type_or_else (type, exp);
213
214  if (!type)
215    return error_mark_node;
216
217  /* If exp is a reference to polymorphic type, get the real type_info.  */
218  if (TYPE_POLYMORPHIC_P (type) && ! resolves_to_fixed_type_p (exp, 0))
219    {
220      /* build reference to type_info from vtable.  */
221      tree t;
222      tree index;
223
224      /* The RTTI information is at index -1.  */
225      index = build_int_2 (-1 * TARGET_VTABLE_DATA_ENTRY_DISTANCE, -1);
226      t = build_vtbl_ref (exp, index);
227      TREE_TYPE (t) = type_info_ptr_type;
228      return t;
229    }
230
231  /* Otherwise return the type_info for the static type of the expr.  */
232  return get_tinfo_ptr (TYPE_MAIN_VARIANT (type));
233}
234
235static bool
236typeid_ok_p ()
237{
238  if (! flag_rtti)
239    {
240      error ("cannot use typeid with -fno-rtti");
241      return false;
242    }
243
244  if (!COMPLETE_TYPE_P (type_info_type_node))
245    {
246      error ("must #include <typeinfo> before using typeid");
247      return false;
248    }
249
250  return true;
251}
252
253tree
254build_typeid (exp)
255     tree exp;
256{
257  tree cond = NULL_TREE;
258  int nonnull = 0;
259
260  if (exp == error_mark_node || !typeid_ok_p ())
261    return error_mark_node;
262
263  if (processing_template_decl)
264    return build_min_nt (TYPEID_EXPR, exp);
265
266  if (TREE_CODE (exp) == INDIRECT_REF
267      && TREE_CODE (TREE_TYPE (TREE_OPERAND (exp, 0))) == POINTER_TYPE
268      && TYPE_POLYMORPHIC_P (TREE_TYPE (exp))
269      && ! resolves_to_fixed_type_p (exp, &nonnull)
270      && ! nonnull)
271    {
272      exp = stabilize_reference (exp);
273      cond = cp_convert (boolean_type_node, TREE_OPERAND (exp, 0));
274    }
275
276  exp = get_tinfo_decl_dynamic (exp);
277
278  if (exp == error_mark_node)
279    return error_mark_node;
280
281  exp = build_indirect_ref (exp, NULL);
282
283  if (cond)
284    {
285      tree bad = throw_bad_typeid ();
286
287      exp = build (COND_EXPR, TREE_TYPE (exp), cond, exp, bad);
288    }
289
290  return convert_from_reference (exp);
291}
292
293/* Generate the NTBS name of a type.  */
294static tree
295tinfo_name (type)
296     tree type;
297{
298  const char *name;
299  tree name_string;
300
301  name = mangle_type_string (type);
302  name_string = fix_string_type (build_string (strlen (name) + 1, name));
303  return name_string;
304}
305
306/* Return a VAR_DECL for the internal ABI defined type_info object for
307   TYPE. You must arrange that the decl is mark_used, if actually use
308   it --- decls in vtables are only used if the vtable is output.  */
309
310tree
311get_tinfo_decl (type)
312     tree type;
313{
314  tree name;
315  tree d;
316
317  if (COMPLETE_TYPE_P (type)
318      && TREE_CODE (TYPE_SIZE (type)) != INTEGER_CST)
319    {
320      error ("cannot create type information for type `%T' because its size is variable",
321	     type);
322      return error_mark_node;
323    }
324
325  if (TREE_CODE (type) == OFFSET_TYPE)
326    type = TREE_TYPE (type);
327  if (TREE_CODE (type) == METHOD_TYPE)
328    type = build_function_type (TREE_TYPE (type),
329				TREE_CHAIN (TYPE_ARG_TYPES (type)));
330
331  /* For a class type, the variable is cached in the type node
332     itself.  */
333  if (CLASS_TYPE_P (type))
334    {
335      d = CLASSTYPE_TYPEINFO_VAR (TYPE_MAIN_VARIANT (type));
336      if (d)
337	return d;
338    }
339
340  name = mangle_typeinfo_for_type (type);
341
342  d = IDENTIFIER_GLOBAL_VALUE (name);
343  if (!d)
344    {
345      tree var_desc = get_pseudo_ti_desc (type);
346
347      d = build_lang_decl (VAR_DECL, name, TINFO_PSEUDO_TYPE (var_desc));
348
349      DECL_ARTIFICIAL (d) = 1;
350      TREE_READONLY (d) = 1;
351      TREE_STATIC (d) = 1;
352      DECL_EXTERNAL (d) = 1;
353      SET_DECL_ASSEMBLER_NAME (d, name);
354      DECL_COMDAT (d) = 1;
355
356      pushdecl_top_level_and_finish (d, NULL_TREE);
357
358      if (CLASS_TYPE_P (type))
359	CLASSTYPE_TYPEINFO_VAR (TYPE_MAIN_VARIANT (type)) = d;
360
361      /* Remember the type it is for.  */
362      TREE_TYPE (name) = type;
363    }
364
365  return d;
366}
367
368/* Return a pointer to a type_info object describing TYPE, suitably
369   cast to the language defined type.  */
370
371static tree
372get_tinfo_ptr (type)
373     tree type;
374{
375  tree exp = get_tinfo_decl (type);
376
377   /* Convert to type_info type.  */
378  exp = build_unary_op (ADDR_EXPR, exp, 0);
379  exp = ocp_convert (type_info_ptr_type, exp, CONV_REINTERPRET, 0);
380
381  return exp;
382}
383
384/* Return the type_info object for TYPE.  */
385
386tree
387get_typeid (type)
388     tree type;
389{
390  if (type == error_mark_node || !typeid_ok_p ())
391    return error_mark_node;
392
393  if (processing_template_decl)
394    return build_min_nt (TYPEID_EXPR, type);
395
396  /* If the type of the type-id is a reference type, the result of the
397     typeid expression refers to a type_info object representing the
398     referenced type.  */
399  if (TREE_CODE (type) == REFERENCE_TYPE)
400    type = TREE_TYPE (type);
401
402  /* The top-level cv-qualifiers of the lvalue expression or the type-id
403     that is the operand of typeid are always ignored.  */
404  type = TYPE_MAIN_VARIANT (type);
405
406  if (!VOID_TYPE_P (type))
407    type = complete_type_or_else (type, NULL_TREE);
408
409  if (!type)
410    return error_mark_node;
411
412  return build_indirect_ref (get_tinfo_ptr (type), NULL);
413}
414
415/* Check whether TEST is null before returning RESULT.  If TEST is used in
416   RESULT, it must have previously had a save_expr applied to it.  */
417
418static tree
419ifnonnull (test, result)
420     tree test, result;
421{
422  return build (COND_EXPR, TREE_TYPE (result),
423		build (EQ_EXPR, boolean_type_node, test, integer_zero_node),
424		cp_convert (TREE_TYPE (result), integer_zero_node),
425		result);
426}
427
428/* Execute a dynamic cast, as described in section 5.2.6 of the 9/93 working
429   paper.  */
430
431static tree
432build_dynamic_cast_1 (type, expr)
433     tree type, expr;
434{
435  enum tree_code tc = TREE_CODE (type);
436  tree exprtype = TREE_TYPE (expr);
437  tree dcast_fn;
438  tree old_expr = expr;
439  const char *errstr = NULL;
440
441  /* T shall be a pointer or reference to a complete class type, or
442     `pointer to cv void''.  */
443  switch (tc)
444    {
445    case POINTER_TYPE:
446      if (TREE_CODE (TREE_TYPE (type)) == VOID_TYPE)
447	break;
448    case REFERENCE_TYPE:
449      if (! IS_AGGR_TYPE (TREE_TYPE (type)))
450	{
451	  errstr = "target is not pointer or reference to class";
452	  goto fail;
453	}
454      if (!COMPLETE_TYPE_P (complete_type (TREE_TYPE (type))))
455	{
456	  errstr = "target is not pointer or reference to complete type";
457	  goto fail;
458	}
459      break;
460
461    default:
462      errstr = "target is not pointer or reference";
463      goto fail;
464    }
465
466  if (TREE_CODE (expr) == OFFSET_REF)
467    {
468      expr = resolve_offset_ref (expr);
469      exprtype = TREE_TYPE (expr);
470    }
471
472  if (tc == POINTER_TYPE)
473    expr = convert_from_reference (expr);
474  else if (TREE_CODE (exprtype) != REFERENCE_TYPE)
475    {
476      /* Apply trivial conversion T -> T& for dereferenced ptrs.  */
477      exprtype = build_reference_type (exprtype);
478      expr = convert_to_reference (exprtype, expr, CONV_IMPLICIT,
479				   LOOKUP_NORMAL, NULL_TREE);
480    }
481
482  exprtype = TREE_TYPE (expr);
483
484  if (tc == POINTER_TYPE)
485    {
486      /* If T is a pointer type, v shall be an rvalue of a pointer to
487	 complete class type, and the result is an rvalue of type T.  */
488
489      if (TREE_CODE (exprtype) != POINTER_TYPE)
490	{
491	  errstr = "source is not a pointer";
492	  goto fail;
493	}
494      if (! IS_AGGR_TYPE (TREE_TYPE (exprtype)))
495	{
496	  errstr = "source is not a pointer to class";
497	  goto fail;
498	}
499      if (!COMPLETE_TYPE_P (complete_type (TREE_TYPE (exprtype))))
500	{
501	  errstr = "source is a pointer to incomplete type";
502	  goto fail;
503	}
504    }
505  else
506    {
507      /* T is a reference type, v shall be an lvalue of a complete class
508	 type, and the result is an lvalue of the type referred to by T.  */
509
510      if (! IS_AGGR_TYPE (TREE_TYPE (exprtype)))
511	{
512	  errstr = "source is not of class type";
513	  goto fail;
514	}
515      if (!COMPLETE_TYPE_P (complete_type (TREE_TYPE (exprtype))))
516	{
517	  errstr = "source is of incomplete class type";
518	  goto fail;
519	}
520
521    }
522
523  /* The dynamic_cast operator shall not cast away constness.  */
524  if (!at_least_as_qualified_p (TREE_TYPE (type),
525				TREE_TYPE (exprtype)))
526    {
527      errstr = "conversion casts away constness";
528      goto fail;
529    }
530
531  /* If *type is an unambiguous accessible base class of *exprtype,
532     convert statically.  */
533  {
534    tree binfo;
535
536    binfo = lookup_base (TREE_TYPE (exprtype), TREE_TYPE (type),
537			 ba_not_special, NULL);
538
539    if (binfo)
540      {
541	expr = build_base_path (PLUS_EXPR, convert_from_reference (expr),
542				binfo, 0);
543	if (TREE_CODE (exprtype) == POINTER_TYPE)
544	  expr = non_lvalue (expr);
545	return expr;
546      }
547  }
548
549  /* Otherwise *exprtype must be a polymorphic class (have a vtbl).  */
550  if (TYPE_POLYMORPHIC_P (TREE_TYPE (exprtype)))
551    {
552      tree expr1;
553      /* if TYPE is `void *', return pointer to complete object.  */
554      if (tc == POINTER_TYPE && VOID_TYPE_P (TREE_TYPE (type)))
555	{
556	  /* if b is an object, dynamic_cast<void *>(&b) == (void *)&b.  */
557	  if (TREE_CODE (expr) == ADDR_EXPR
558	      && TREE_CODE (TREE_OPERAND (expr, 0)) == VAR_DECL
559	      && TREE_CODE (TREE_TYPE (TREE_OPERAND (expr, 0))) == RECORD_TYPE)
560	    return build1 (NOP_EXPR, type, expr);
561
562	  /* Since expr is used twice below, save it.  */
563	  expr = save_expr (expr);
564
565	  expr1 = build_headof (expr);
566	  if (TREE_TYPE (expr1) != type)
567	    expr1 = build1 (NOP_EXPR, type, expr1);
568	  return ifnonnull (expr, expr1);
569	}
570      else
571	{
572	  tree retval;
573          tree result, td2, td3, elems;
574          tree static_type, target_type, boff;
575
576 	  /* If we got here, we can't convert statically.  Therefore,
577	     dynamic_cast<D&>(b) (b an object) cannot succeed.  */
578	  if (tc == REFERENCE_TYPE)
579	    {
580	      if (TREE_CODE (old_expr) == VAR_DECL
581		  && TREE_CODE (TREE_TYPE (old_expr)) == RECORD_TYPE)
582		{
583	          tree expr = throw_bad_cast ();
584		  warning ("dynamic_cast of `%#D' to `%#T' can never succeed",
585			      old_expr, type);
586	          /* Bash it to the expected type.  */
587	          TREE_TYPE (expr) = type;
588		  return expr;
589		}
590	    }
591	  /* Ditto for dynamic_cast<D*>(&b).  */
592	  else if (TREE_CODE (expr) == ADDR_EXPR)
593	    {
594	      tree op = TREE_OPERAND (expr, 0);
595	      if (TREE_CODE (op) == VAR_DECL
596		  && TREE_CODE (TREE_TYPE (op)) == RECORD_TYPE)
597		{
598		  warning ("dynamic_cast of `%#D' to `%#T' can never succeed",
599			      op, type);
600		  retval = build_int_2 (0, 0);
601		  TREE_TYPE (retval) = type;
602		  return retval;
603		}
604	    }
605
606	  target_type = TYPE_MAIN_VARIANT (TREE_TYPE (type));
607	  static_type = TYPE_MAIN_VARIANT (TREE_TYPE (exprtype));
608	  td2 = build_unary_op (ADDR_EXPR, get_tinfo_decl (target_type), 0);
609	  td3 = build_unary_op (ADDR_EXPR, get_tinfo_decl (static_type), 0);
610
611          /* Determine how T and V are related.  */
612          boff = get_dynamic_cast_base_type (static_type, target_type);
613
614	  /* Since expr is used twice below, save it.  */
615	  expr = save_expr (expr);
616
617	  expr1 = expr;
618	  if (tc == REFERENCE_TYPE)
619	    expr1 = build_unary_op (ADDR_EXPR, expr1, 0);
620
621	  elems = tree_cons
622	    (NULL_TREE, expr1, tree_cons
623	     (NULL_TREE, td3, tree_cons
624	      (NULL_TREE, td2, tree_cons
625	       (NULL_TREE, boff, NULL_TREE))));
626
627	  dcast_fn = dynamic_cast_node;
628	  if (!dcast_fn)
629	    {
630	      tree tmp;
631	      tree tinfo_ptr;
632	      tree ns = abi_node;
633	      const char *name;
634
635	      push_nested_namespace (ns);
636	      tinfo_ptr = xref_tag (class_type,
637				    get_identifier ("__class_type_info"),
638				    /*attributes=*/NULL_TREE,
639				    1);
640
641	      tinfo_ptr = build_pointer_type
642		(build_qualified_type
643		 (tinfo_ptr, TYPE_QUAL_CONST));
644	      name = "__dynamic_cast";
645	      tmp = tree_cons
646		(NULL_TREE, const_ptr_type_node, tree_cons
647		 (NULL_TREE, tinfo_ptr, tree_cons
648		  (NULL_TREE, tinfo_ptr, tree_cons
649		   (NULL_TREE, ptrdiff_type_node, void_list_node))));
650	      tmp = build_function_type (ptr_type_node, tmp);
651	      dcast_fn = build_library_fn_ptr (name, tmp);
652              pop_nested_namespace (ns);
653              dynamic_cast_node = dcast_fn;
654	    }
655          result = build_cxx_call (dcast_fn, elems, elems);
656
657	  if (tc == REFERENCE_TYPE)
658	    {
659	      tree bad = throw_bad_cast ();
660
661	      result = save_expr (result);
662	      return build (COND_EXPR, type, result, result, bad);
663	    }
664
665	  /* Now back to the type we want from a void*.  */
666	  result = cp_convert (type, result);
667          return ifnonnull (expr, result);
668	}
669    }
670  else
671    errstr = "source type is not polymorphic";
672
673 fail:
674  error ("cannot dynamic_cast `%E' (of type `%#T') to type `%#T' (%s)",
675	    expr, exprtype, type, errstr);
676  return error_mark_node;
677}
678
679tree
680build_dynamic_cast (type, expr)
681     tree type, expr;
682{
683  if (type == error_mark_node || expr == error_mark_node)
684    return error_mark_node;
685
686  if (processing_template_decl)
687    return build_min (DYNAMIC_CAST_EXPR, type, expr);
688
689  return convert_from_reference (build_dynamic_cast_1 (type, expr));
690}
691
692/* Return the runtime bit mask encoding the qualifiers of TYPE.  */
693
694static int
695qualifier_flags (type)
696     tree type;
697{
698  int flags = 0;
699  int quals = cp_type_quals (type);
700
701  if (quals & TYPE_QUAL_CONST)
702    flags |= 1;
703  if (quals & TYPE_QUAL_VOLATILE)
704    flags |= 2;
705  if (quals & TYPE_QUAL_RESTRICT)
706    flags |= 4;
707  return flags;
708}
709
710/* Return nonzero, if the pointer chain TYPE ends at an incomplete type, or
711   contains a pointer to member of an incomplete class.  */
712
713static int
714target_incomplete_p (type)
715     tree type;
716{
717  while (TREE_CODE (type) == POINTER_TYPE)
718    if (TYPE_PTRMEM_P (type))
719      {
720        if (!COMPLETE_TYPE_P (TYPE_PTRMEM_CLASS_TYPE (type)))
721          return 1;
722        type = TYPE_PTRMEM_POINTED_TO_TYPE (type);
723      }
724    else
725      type = TREE_TYPE (type);
726  if (!COMPLETE_OR_VOID_TYPE_P (type))
727    return 1;
728
729  return 0;
730}
731
732/* Return a CONSTRUCTOR for the common part of the type_info objects. This
733   is the vtable pointer and NTBS name.  The NTBS name is emitted as a
734   comdat const char array, so it becomes a unique key for the type. Generate
735   and emit that VAR_DECL here.  (We can't always emit the type_info itself
736   as comdat, because of pointers to incomplete.) */
737
738static tree
739tinfo_base_init (desc, target)
740     tree desc;
741     tree target;
742{
743  tree init = NULL_TREE;
744  tree name_decl;
745  tree vtable_ptr;
746
747  {
748    tree name_name;
749
750    /* Generate the NTBS array variable.  */
751    tree name_type = build_cplus_array_type
752                     (build_qualified_type (char_type_node, TYPE_QUAL_CONST),
753                     NULL_TREE);
754    tree name_string = tinfo_name (target);
755
756    name_name = mangle_typeinfo_string_for_type (target);
757    name_decl = build_lang_decl (VAR_DECL, name_name, name_type);
758
759    DECL_ARTIFICIAL (name_decl) = 1;
760    TREE_READONLY (name_decl) = 1;
761    TREE_STATIC (name_decl) = 1;
762    DECL_EXTERNAL (name_decl) = 0;
763    TREE_PUBLIC (name_decl) = 1;
764    comdat_linkage (name_decl);
765    /* External name of the string containing the type's name has a
766       special name.  */
767    SET_DECL_ASSEMBLER_NAME (name_decl,
768			     mangle_typeinfo_string_for_type (target));
769    DECL_INITIAL (name_decl) = name_string;
770    pushdecl_top_level_and_finish (name_decl, name_string);
771  }
772
773  vtable_ptr = TINFO_VTABLE_DECL (desc);
774  if (!vtable_ptr)
775    {
776      tree real_type;
777
778      push_nested_namespace (abi_node);
779      real_type = xref_tag (class_type, TINFO_REAL_NAME (desc),
780			    /*attributes=*/NULL_TREE, 1);
781      pop_nested_namespace (abi_node);
782
783      if (!COMPLETE_TYPE_P (real_type))
784	{
785          /* We never saw a definition of this type, so we need to
786	     tell the compiler that this is an exported class, as
787	     indeed all of the __*_type_info classes are.  */
788	  SET_CLASSTYPE_INTERFACE_KNOWN (real_type);
789	  CLASSTYPE_INTERFACE_ONLY (real_type) = 1;
790	}
791
792      vtable_ptr = get_vtable_decl (real_type, /*complete=*/1);
793      vtable_ptr = build_unary_op (ADDR_EXPR, vtable_ptr, 0);
794
795      /* We need to point into the middle of the vtable.  */
796      vtable_ptr = build
797	(PLUS_EXPR, TREE_TYPE (vtable_ptr), vtable_ptr,
798	 size_binop (MULT_EXPR,
799		     size_int (2 * TARGET_VTABLE_DATA_ENTRY_DISTANCE),
800		     TYPE_SIZE_UNIT (vtable_entry_type)));
801      TREE_CONSTANT (vtable_ptr) = 1;
802
803      TINFO_VTABLE_DECL (desc) = vtable_ptr;
804    }
805
806  init = tree_cons (NULL_TREE, vtable_ptr, init);
807
808  init = tree_cons (NULL_TREE, decay_conversion (name_decl), init);
809
810  init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, nreverse (init));
811  TREE_HAS_CONSTRUCTOR (init) = TREE_CONSTANT (init) = TREE_STATIC (init) = 1;
812  init = tree_cons (NULL_TREE, init, NULL_TREE);
813
814  return init;
815}
816
817/* Return the CONSTRUCTOR expr for a type_info of TYPE. DESC provides the
818   information about the particular type_info derivation, which adds no
819   additional fields to the type_info base.  */
820
821static tree
822generic_initializer (desc, target)
823     tree desc;
824     tree target;
825{
826  tree init = tinfo_base_init (desc, target);
827
828  init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, init);
829  TREE_HAS_CONSTRUCTOR (init) = TREE_CONSTANT (init) = TREE_STATIC (init) = 1;
830  return init;
831}
832
833/* Return the CONSTRUCTOR expr for a type_info of pointer TYPE.
834   DESC provides information about the particular type_info derivation,
835   which adds target type and qualifier flags members to the type_info base.  */
836
837static tree
838ptr_initializer (desc, target, non_public_ptr)
839     tree desc;
840     tree target;
841     int *non_public_ptr;
842{
843  tree init = tinfo_base_init (desc, target);
844  tree to = TREE_TYPE (target);
845  int flags = qualifier_flags (to);
846  int incomplete = target_incomplete_p (to);
847
848  if (incomplete)
849    {
850      flags |= 8;
851      *non_public_ptr = 1;
852    }
853  init = tree_cons (NULL_TREE, build_int_2 (flags, 0), init);
854  init = tree_cons (NULL_TREE,
855                    get_tinfo_ptr (TYPE_MAIN_VARIANT (to)),
856                    init);
857
858  init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, nreverse (init));
859  TREE_HAS_CONSTRUCTOR (init) = TREE_CONSTANT (init) = TREE_STATIC (init) = 1;
860  return init;
861}
862
863/* Return the CONSTRUCTOR expr for a type_info of pointer to member data TYPE.
864   DESC provides information about the particular type_info derivation,
865   which adds class, target type and qualifier flags members to the type_info
866   base.  */
867
868static tree
869ptm_initializer (desc, target, non_public_ptr)
870     tree desc;
871     tree target;
872     int *non_public_ptr;
873{
874  tree init = tinfo_base_init (desc, target);
875  tree to = TYPE_PTRMEM_POINTED_TO_TYPE (target);
876  tree klass = TYPE_PTRMEM_CLASS_TYPE (target);
877  int flags = qualifier_flags (to);
878  int incomplete = target_incomplete_p (to);
879
880  if (incomplete)
881    {
882      flags |= 0x8;
883      *non_public_ptr = 1;
884    }
885  if (!COMPLETE_TYPE_P (klass))
886    {
887      flags |= 0x10;
888      *non_public_ptr = 1;
889    }
890  init = tree_cons (NULL_TREE, build_int_2 (flags, 0), init);
891  init = tree_cons (NULL_TREE,
892		    get_tinfo_ptr (TYPE_MAIN_VARIANT (to)),
893                    init);
894  init = tree_cons (NULL_TREE,
895		    get_tinfo_ptr (klass),
896		    init);
897
898  init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, nreverse (init));
899  TREE_HAS_CONSTRUCTOR (init) = TREE_CONSTANT (init) = TREE_STATIC (init) = 1;
900  return init;
901}
902
903/* Check base BINFO to set hint flags in *DATA, which is really an int.
904   We use CLASSTYPE_MARKED to tag types we've found as non-virtual bases and
905   CLASSTYPE_MARKED2 to tag those which are virtual bases. Remember it is
906   possible for a type to be both a virtual and non-virtual base.  */
907
908static tree
909dfs_class_hint_mark (binfo, data)
910     tree binfo;
911     void *data;
912{
913  tree basetype = BINFO_TYPE (binfo);
914  int *hint = (int *) data;
915
916  if (TREE_VIA_VIRTUAL (binfo))
917    {
918      if (CLASSTYPE_MARKED (basetype))
919        *hint |= 1;
920      if (CLASSTYPE_MARKED2 (basetype))
921        *hint |= 2;
922      SET_CLASSTYPE_MARKED2 (basetype);
923    }
924  else
925    {
926      if (CLASSTYPE_MARKED (basetype) || CLASSTYPE_MARKED2 (basetype))
927        *hint |= 1;
928      SET_CLASSTYPE_MARKED (basetype);
929    }
930  if (!TREE_VIA_PUBLIC (binfo) && TYPE_BINFO (basetype) != binfo)
931    *hint |= 4;
932  return NULL_TREE;
933};
934
935/* Clear the base's dfs marks, after searching for duplicate bases.  */
936
937static tree
938dfs_class_hint_unmark (binfo, data)
939     tree binfo;
940     void *data ATTRIBUTE_UNUSED;
941{
942  tree basetype = BINFO_TYPE (binfo);
943
944  CLEAR_CLASSTYPE_MARKED (basetype);
945  CLEAR_CLASSTYPE_MARKED2 (basetype);
946  return NULL_TREE;
947}
948
949/* Determine the hint flags describing the features of a class's hierarchy.  */
950
951static int
952class_hint_flags (type)
953     tree type;
954{
955  int hint_flags = 0;
956  int i;
957
958  dfs_walk (TYPE_BINFO (type), dfs_class_hint_mark, NULL, &hint_flags);
959  dfs_walk (TYPE_BINFO (type), dfs_class_hint_unmark, NULL, NULL);
960
961  for (i = 0; i < CLASSTYPE_N_BASECLASSES (type); ++i)
962    {
963      tree base_binfo = BINFO_BASETYPE (TYPE_BINFO (type), i);
964
965      if (TREE_VIA_PUBLIC (base_binfo))
966        hint_flags |= 0x8;
967    }
968  return hint_flags;
969}
970
971/* Return the CONSTRUCTOR expr for a type_info of class TYPE.
972   DESC provides information about the particular __class_type_info derivation,
973   which adds hint flags and TRAIL initializers to the type_info base.  */
974
975static tree
976class_initializer (desc, target, trail)
977     tree desc;
978     tree target;
979     tree trail;
980{
981  tree init = tinfo_base_init (desc, target);
982
983  TREE_CHAIN (init) = trail;
984  init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, init);
985  TREE_HAS_CONSTRUCTOR (init) = TREE_CONSTANT (init) = TREE_STATIC (init) = 1;
986  return init;
987}
988
989/* Returns nonzero if the typeinfo for type should be placed in
990   the runtime library.  */
991
992static int
993typeinfo_in_lib_p (type)
994     tree type;
995{
996  /* The typeinfo objects for `T*' and `const T*' are in the runtime
997     library for simple types T.  */
998  if (TREE_CODE (type) == POINTER_TYPE
999      && (cp_type_quals (TREE_TYPE (type)) == TYPE_QUAL_CONST
1000	  || cp_type_quals (TREE_TYPE (type)) == TYPE_UNQUALIFIED))
1001    type = TREE_TYPE (type);
1002
1003  switch (TREE_CODE (type))
1004    {
1005    case INTEGER_TYPE:
1006    case BOOLEAN_TYPE:
1007    case CHAR_TYPE:
1008    case REAL_TYPE:
1009    case VOID_TYPE:
1010      return 1;
1011
1012    default:
1013      return 0;
1014    }
1015}
1016
1017/* Generate the initializer for the type info describing
1018   TYPE. VAR_DESC is a . NON_PUBLIC_P is set nonzero, if the VAR_DECL
1019   should not be exported from this object file.  This should only be
1020   called at the end of translation, when we know that no further
1021   types will be completed.  */
1022
1023static tree
1024get_pseudo_ti_init (type, var_desc, non_public_p)
1025     tree type;
1026     tree var_desc;
1027     int *non_public_p;
1028{
1029  my_friendly_assert (at_eof, 20021120);
1030  switch (TREE_CODE (type))
1031    {
1032    case POINTER_TYPE:
1033      if (TYPE_PTRMEM_P (type))
1034	return ptm_initializer (var_desc, type, non_public_p);
1035      else
1036	return ptr_initializer (var_desc, type, non_public_p);
1037      break;
1038    case ENUMERAL_TYPE:
1039      return generic_initializer (var_desc, type);
1040      break;
1041    case FUNCTION_TYPE:
1042      return generic_initializer (var_desc, type);
1043      break;
1044    case ARRAY_TYPE:
1045      return generic_initializer (var_desc, type);
1046      break;
1047    case UNION_TYPE:
1048    case RECORD_TYPE:
1049      if (TYPE_PTRMEMFUNC_P (type))
1050	return ptm_initializer (var_desc, type, non_public_p);
1051      else if (var_desc == class_desc_type_node)
1052        {
1053	  if (!COMPLETE_TYPE_P (type))
1054	    /* Emit a non-public class_type_info.  */
1055	    *non_public_p = 1;
1056	  return class_initializer (var_desc, type, NULL_TREE);
1057        }
1058      else if (var_desc == si_class_desc_type_node)
1059	{
1060          tree base_binfos = BINFO_BASETYPES (TYPE_BINFO (type));
1061	  tree base_binfo = TREE_VEC_ELT (base_binfos, 0);
1062	  tree tinfo = get_tinfo_ptr (BINFO_TYPE (base_binfo));
1063	  tree base_inits = tree_cons (NULL_TREE, tinfo, NULL_TREE);
1064
1065	  return class_initializer (var_desc, type, base_inits);
1066	}
1067      else
1068        {
1069	  int hint = class_hint_flags (type);
1070	  tree binfo = TYPE_BINFO (type);
1071          int nbases = BINFO_N_BASETYPES (binfo);
1072          tree base_binfos = BINFO_BASETYPES (binfo);
1073          tree base_inits = NULL_TREE;
1074          int ix;
1075
1076          /* Generate the base information initializer.  */
1077          for (ix = nbases; ix--;)
1078            {
1079              tree base_binfo = TREE_VEC_ELT (base_binfos, ix);
1080              tree base_init = NULL_TREE;
1081              int flags = 0;
1082              tree tinfo;
1083              tree offset;
1084
1085              if (TREE_PUBLIC (base_binfo))
1086                flags |= 2;
1087              tinfo = get_tinfo_ptr (BINFO_TYPE (base_binfo));
1088	      if (TREE_VIA_VIRTUAL (base_binfo))
1089		{
1090		   /* We store the vtable offset at which the virtual
1091       		      base offset can be found.  */
1092		  offset = BINFO_VPTR_FIELD
1093		    (binfo_for_vbase (BINFO_TYPE (base_binfo), type));
1094		  offset = convert (sizetype, offset);
1095		  flags |= 1;
1096		}
1097	      else
1098		offset = BINFO_OFFSET (base_binfo);
1099
1100              /* combine offset and flags into one field */
1101              offset = cp_build_binary_op (LSHIFT_EXPR, offset,
1102					   build_int_2 (8, 0));
1103              offset = cp_build_binary_op (BIT_IOR_EXPR, offset,
1104					   build_int_2 (flags, 0));
1105              base_init = tree_cons (NULL_TREE, offset, base_init);
1106              base_init = tree_cons (NULL_TREE, tinfo, base_init);
1107              base_init = build (CONSTRUCTOR, NULL_TREE, NULL_TREE, base_init);
1108	      TREE_HAS_CONSTRUCTOR (base_init) = 1;
1109              base_inits = tree_cons (NULL_TREE, base_init, base_inits);
1110            }
1111	  base_inits = build (CONSTRUCTOR,
1112			      NULL_TREE, NULL_TREE, base_inits);
1113	  TREE_HAS_CONSTRUCTOR (base_inits) = 1;
1114	  base_inits = tree_cons (NULL_TREE, base_inits, NULL_TREE);
1115	  /* Prepend the number of bases.  */
1116	  base_inits = tree_cons (NULL_TREE,
1117				  build_int_2 (nbases, 0), base_inits);
1118	  /* Prepend the hint flags.  */
1119	  base_inits = tree_cons (NULL_TREE,
1120				  build_int_2 (hint, 0), base_inits);
1121
1122          return class_initializer (var_desc, type, base_inits);
1123        }
1124      break;
1125
1126    default:
1127      return generic_initializer (var_desc, type);
1128    }
1129}
1130
1131/* Generate the RECORD_TYPE containing the data layout of a type_info
1132   derivative as used by the runtime. This layout must be consistent with
1133   that defined in the runtime support. Also generate the VAR_DECL for the
1134   type's vtable. We explicitly manage the vtable member, and name it for
1135   real type as used in the runtime. The RECORD type has a different name,
1136   to avoid collisions.  Return a TREE_LIST who's TINFO_PSEUDO_TYPE
1137   is the generated type and TINFO_VTABLE_NAME is the name of the
1138   vtable.  We have to delay generating the VAR_DECL of the vtable
1139   until the end of the translation, when we'll have seen the library
1140   definition, if there was one.
1141
1142   REAL_NAME is the runtime's name of the type. Trailing arguments are
1143   additional FIELD_DECL's for the structure. The final argument must be
1144   NULL.  */
1145
1146static tree
1147create_pseudo_type_info VPARAMS((const char *real_name, int ident, ...))
1148{
1149  tree pseudo_type;
1150  char *pseudo_name;
1151  int ix;
1152  tree fields[10];
1153  tree field_decl;
1154  tree result;
1155
1156  VA_OPEN (ap, ident);
1157  VA_FIXEDARG (ap, const char *, real_name);
1158  VA_FIXEDARG (ap, int, ident);
1159
1160  /* Generate the pseudo type name.  */
1161  pseudo_name = (char *)alloca (strlen (real_name) + 30);
1162  strcpy (pseudo_name, real_name);
1163  strcat (pseudo_name, "_pseudo");
1164  if (ident)
1165    sprintf (pseudo_name + strlen (pseudo_name), "%d", ident);
1166
1167  /* First field is the pseudo type_info base class.  */
1168  fields[0] = build_decl (FIELD_DECL, NULL_TREE, ti_desc_type_node);
1169
1170  /* Now add the derived fields.  */
1171  for (ix = 0; (field_decl = va_arg (ap, tree));)
1172    fields[++ix] = field_decl;
1173
1174  /* Create the pseudo type.  */
1175  pseudo_type = make_aggr_type (RECORD_TYPE);
1176  finish_builtin_type (pseudo_type, pseudo_name, fields, ix, ptr_type_node);
1177  CLASSTYPE_AS_BASE (pseudo_type) = pseudo_type;
1178
1179  result = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE);
1180  TINFO_REAL_NAME (result) = get_identifier (real_name);
1181  TINFO_PSEUDO_TYPE (result) =
1182    cp_build_qualified_type (pseudo_type, TYPE_QUAL_CONST);
1183
1184  VA_CLOSE (ap);
1185  return result;
1186}
1187
1188/* Return a pseudo type info type node used to describe TYPE.  TYPE
1189   must be a complete type (or cv void), except at the end of the
1190   translation unit.  */
1191
1192static tree
1193get_pseudo_ti_desc (type)
1194     tree type;
1195{
1196  switch (TREE_CODE (type))
1197    {
1198    case POINTER_TYPE:
1199      return TYPE_PTRMEM_P (type) ? ptm_desc_type_node : ptr_desc_type_node;
1200    case ENUMERAL_TYPE:
1201      return enum_desc_type_node;
1202    case FUNCTION_TYPE:
1203      return func_desc_type_node;
1204    case ARRAY_TYPE:
1205      return ary_desc_type_node;
1206    case UNION_TYPE:
1207    case RECORD_TYPE:
1208      if (TYPE_PTRMEMFUNC_P (type))
1209	return ptm_desc_type_node;
1210      else if (!COMPLETE_TYPE_P (type))
1211	{
1212	  if (!at_eof)
1213	    cxx_incomplete_type_error (NULL_TREE, type);
1214	  return class_desc_type_node;
1215	}
1216      else if (!CLASSTYPE_N_BASECLASSES (type))
1217	return class_desc_type_node;
1218      else
1219	{
1220	  tree base_binfo =
1221	    TREE_VEC_ELT (BINFO_BASETYPES (TYPE_BINFO (type)), 0);
1222	  int num_bases = BINFO_N_BASETYPES (TYPE_BINFO (type));
1223
1224	  if (num_bases == 1
1225	      && TREE_PUBLIC (base_binfo)
1226	      && !TREE_VIA_VIRTUAL (base_binfo)
1227	      && integer_zerop (BINFO_OFFSET (base_binfo)))
1228	    /* single non-virtual public.  */
1229	    return si_class_desc_type_node;
1230	  else
1231	    {
1232	      tree var_desc;
1233	      tree array_domain, base_array;
1234
1235	      if (TREE_VEC_LENGTH (vmi_class_desc_type_node) <= num_bases)
1236		{
1237		  int ix;
1238		  tree extend = make_tree_vec (num_bases + 5);
1239
1240		  for (ix = TREE_VEC_LENGTH (vmi_class_desc_type_node); ix--;)
1241		    TREE_VEC_ELT (extend, ix)
1242		      = TREE_VEC_ELT (vmi_class_desc_type_node, ix);
1243		  vmi_class_desc_type_node = extend;
1244		}
1245	      var_desc = TREE_VEC_ELT (vmi_class_desc_type_node, num_bases);
1246	      if (var_desc)
1247		return var_desc;
1248
1249	      /* Add number of bases and trailing array of
1250		 base_class_type_info.  */
1251	      array_domain = build_index_type (size_int (num_bases));
1252	      base_array =
1253		build_array_type (base_desc_type_node, array_domain);
1254
1255	      push_nested_namespace (abi_node);
1256	      var_desc = create_pseudo_type_info
1257		("__vmi_class_type_info", num_bases,
1258		 build_decl (FIELD_DECL, NULL_TREE, integer_type_node),
1259		 build_decl (FIELD_DECL, NULL_TREE, integer_type_node),
1260		 build_decl (FIELD_DECL, NULL_TREE, base_array),
1261		 NULL);
1262	      pop_nested_namespace (abi_node);
1263
1264	      TREE_VEC_ELT (vmi_class_desc_type_node, num_bases) = var_desc;
1265	      return var_desc;
1266	    }
1267	}
1268    default:
1269      return bltn_desc_type_node;
1270    }
1271}
1272
1273/* Make sure the required builtin types exist for generating the type_info
1274   varable definitions.  */
1275
1276static void
1277create_tinfo_types ()
1278{
1279  my_friendly_assert (!ti_desc_type_node, 20020609);
1280
1281  push_nested_namespace (abi_node);
1282
1283  /* Create the internal type_info structure. This is used as a base for
1284     the other structures.  */
1285  {
1286    tree fields[2];
1287
1288    ti_desc_type_node = make_aggr_type (RECORD_TYPE);
1289    fields[0] = build_decl (FIELD_DECL, NULL_TREE, const_ptr_type_node);
1290    fields[1] = build_decl (FIELD_DECL, NULL_TREE, const_string_type_node);
1291    finish_builtin_type (ti_desc_type_node, "__type_info_pseudo",
1292                         fields, 1, ptr_type_node);
1293    TYPE_HAS_CONSTRUCTOR (ti_desc_type_node) = 1;
1294  }
1295
1296  /* Fundamental type_info */
1297  bltn_desc_type_node = create_pseudo_type_info
1298      ("__fundamental_type_info", 0,
1299       NULL);
1300
1301  /* Array, function and enum type_info. No additional fields.  */
1302  ary_desc_type_node = create_pseudo_type_info
1303      ("__array_type_info", 0,
1304       NULL);
1305  func_desc_type_node = create_pseudo_type_info
1306       ("__function_type_info", 0,
1307        NULL);
1308  enum_desc_type_node = create_pseudo_type_info
1309       ("__enum_type_info", 0,
1310        NULL);
1311
1312  /* Class type_info. Add a flags field.  */
1313  class_desc_type_node = create_pseudo_type_info
1314        ("__class_type_info", 0,
1315         NULL);
1316
1317  /* Single public non-virtual base class. Add pointer to base class.
1318     This is really a descendant of __class_type_info.  */
1319  si_class_desc_type_node = create_pseudo_type_info
1320           ("__si_class_type_info", 0,
1321            build_decl (FIELD_DECL, NULL_TREE, type_info_ptr_type),
1322            NULL);
1323
1324  /* Base class internal helper. Pointer to base type, offset to base,
1325     flags.  */
1326  {
1327    tree fields[2];
1328
1329    fields[0] = build_decl (FIELD_DECL, NULL_TREE, type_info_ptr_type);
1330    fields[1] = build_decl (FIELD_DECL, NULL_TREE, integer_types[itk_long]);
1331    base_desc_type_node = make_aggr_type (RECORD_TYPE);
1332    finish_builtin_type (base_desc_type_node, "__base_class_type_info_pseudo",
1333                         fields, 1, ptr_type_node);
1334    TYPE_HAS_CONSTRUCTOR (base_desc_type_node) = 1;
1335  }
1336
1337  /* General hierarchy is created as necessary in this vector.  */
1338  vmi_class_desc_type_node = make_tree_vec (10);
1339
1340  /* Pointer type_info. Adds two fields, qualification mask
1341     and pointer to the pointed to type.  This is really a descendant of
1342     __pbase_type_info.  */
1343  ptr_desc_type_node = create_pseudo_type_info
1344      ("__pointer_type_info", 0,
1345       build_decl (FIELD_DECL, NULL_TREE, integer_type_node),
1346       build_decl (FIELD_DECL, NULL_TREE, type_info_ptr_type),
1347       NULL);
1348
1349  /* Pointer to member data type_info.  Add qualifications flags,
1350     pointer to the member's type info and pointer to the class.
1351     This is really a descendant of __pbase_type_info.  */
1352  ptm_desc_type_node = create_pseudo_type_info
1353       ("__pointer_to_member_type_info", 0,
1354        build_decl (FIELD_DECL, NULL_TREE, integer_type_node),
1355        build_decl (FIELD_DECL, NULL_TREE, type_info_ptr_type),
1356        build_decl (FIELD_DECL, NULL_TREE, type_info_ptr_type),
1357        NULL);
1358
1359  pop_nested_namespace (abi_node);
1360}
1361
1362/* Emit the type_info descriptors which are guaranteed to be in the runtime
1363   support.  Generating them here guarantees consistency with the other
1364   structures.  We use the following heuristic to determine when the runtime
1365   is being generated.  If std::__fundamental_type_info is defined, and its
1366   destructor is defined, then the runtime is being built.  */
1367
1368void
1369emit_support_tinfos ()
1370{
1371  static tree *const fundamentals[] =
1372  {
1373    &void_type_node,
1374    &boolean_type_node,
1375    &wchar_type_node,
1376    &char_type_node, &signed_char_type_node, &unsigned_char_type_node,
1377    &short_integer_type_node, &short_unsigned_type_node,
1378    &integer_type_node, &unsigned_type_node,
1379    &long_integer_type_node, &long_unsigned_type_node,
1380    &long_long_integer_type_node, &long_long_unsigned_type_node,
1381    &float_type_node, &double_type_node, &long_double_type_node,
1382    0
1383  };
1384  int ix;
1385  tree bltn_type, dtor;
1386
1387  push_nested_namespace (abi_node);
1388  bltn_type = xref_tag (class_type,
1389			get_identifier ("__fundamental_type_info"),
1390			/*attributes=*/NULL_TREE,
1391			1);
1392  pop_nested_namespace (abi_node);
1393  if (!COMPLETE_TYPE_P (bltn_type))
1394    return;
1395  dtor = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (bltn_type), 1);
1396  if (DECL_EXTERNAL (dtor))
1397    return;
1398  doing_runtime = 1;
1399  for (ix = 0; fundamentals[ix]; ix++)
1400    {
1401      tree bltn = *fundamentals[ix];
1402      tree bltn_ptr = build_pointer_type (bltn);
1403      tree bltn_const_ptr = build_pointer_type
1404              (build_qualified_type (bltn, TYPE_QUAL_CONST));
1405      tree tinfo;
1406
1407      tinfo = get_tinfo_decl (bltn);
1408      TREE_USED (tinfo) = 1;
1409      TREE_SYMBOL_REFERENCED (DECL_ASSEMBLER_NAME (tinfo)) = 1;
1410
1411      tinfo = get_tinfo_decl (bltn_ptr);
1412      TREE_USED (tinfo) = 1;
1413      TREE_SYMBOL_REFERENCED (DECL_ASSEMBLER_NAME (tinfo)) = 1;
1414
1415      tinfo = get_tinfo_decl (bltn_const_ptr);
1416      TREE_USED (tinfo) = 1;
1417      TREE_SYMBOL_REFERENCED (DECL_ASSEMBLER_NAME (tinfo)) = 1;
1418    }
1419}
1420
1421/* Return nonzero, iff T is a type_info variable which has not had a
1422   definition emitted for it.  */
1423
1424int
1425unemitted_tinfo_decl_p (t, data)
1426     tree t;
1427     void *data ATTRIBUTE_UNUSED;
1428{
1429  if (/* It's a var decl */
1430      TREE_CODE (t) == VAR_DECL
1431      /* whos name points back to itself */
1432      && IDENTIFIER_GLOBAL_VALUE (DECL_NAME (t)) == t
1433      /* whose name's type is non-null */
1434      && TREE_TYPE (DECL_NAME (t))
1435      /* and whose type is a struct */
1436      && TREE_CODE (TREE_TYPE (t)) == RECORD_TYPE
1437      /* with a field */
1438      && TYPE_FIELDS (TREE_TYPE (t))
1439      /* which is our pseudo type info */
1440      && TREE_TYPE (TYPE_FIELDS (TREE_TYPE (t))) == ti_desc_type_node)
1441    return 1;
1442  return 0;
1443}
1444
1445/* Finish a type info decl. DECL_PTR is a pointer to an unemitted
1446   tinfo decl.  Determine whether it needs emitting, and if so
1447   generate the initializer.  */
1448
1449int
1450emit_tinfo_decl (decl_ptr, data)
1451     tree *decl_ptr;
1452     void *data ATTRIBUTE_UNUSED;
1453{
1454  tree decl = *decl_ptr;
1455  tree type = TREE_TYPE (DECL_NAME (decl));
1456  int non_public;
1457  int in_library = typeinfo_in_lib_p (type);
1458  tree var_desc, var_init;
1459
1460  import_export_tinfo (decl, type, in_library);
1461  if (DECL_REALLY_EXTERN (decl) || !DECL_NEEDED_P (decl))
1462    return 0;
1463
1464  if (!doing_runtime && in_library)
1465    return 0;
1466
1467  non_public = 0;
1468  var_desc = get_pseudo_ti_desc (type);
1469  var_init = get_pseudo_ti_init (type, var_desc, &non_public);
1470
1471  DECL_EXTERNAL (decl) = 0;
1472  TREE_PUBLIC (decl) = !non_public;
1473  if (non_public)
1474    DECL_COMDAT (decl) = 0;
1475
1476  DECL_INITIAL (decl) = var_init;
1477  cp_finish_decl (decl, var_init, NULL_TREE, 0);
1478  /* cp_finish_decl will have dealt with linkage.  */
1479
1480  /* Say we've dealt with it.  */
1481  TREE_TYPE (DECL_NAME (decl)) = NULL_TREE;
1482
1483  return 1;
1484}
1485