118334Speter/* Breadth-first and depth-first routines for
218334Speter   searching multiple-inheritance lattice for GNU C++.
390075Sobrien   Copyright (C) 1987, 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
4169689Skan   1999, 2000, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
518334Speter   Contributed by Michael Tiemann (tiemann@cygnus.com)
618334Speter
7132718SkanThis file is part of GCC.
818334Speter
9132718SkanGCC is free software; you can redistribute it and/or modify
1018334Speterit under the terms of the GNU General Public License as published by
1118334Speterthe Free Software Foundation; either version 2, or (at your option)
1218334Speterany later version.
1318334Speter
14132718SkanGCC is distributed in the hope that it will be useful,
1518334Speterbut WITHOUT ANY WARRANTY; without even the implied warranty of
1618334SpeterMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
1718334SpeterGNU General Public License for more details.
1818334Speter
1918334SpeterYou should have received a copy of the GNU General Public License
20132718Skanalong with GCC; see the file COPYING.  If not, write to
21169689Skanthe Free Software Foundation, 51 Franklin Street, Fifth Floor,
22169689SkanBoston, MA 02110-1301, USA.  */
2318334Speter
2450397Sobrien/* High-level class interface.  */
2518334Speter
2618334Speter#include "config.h"
2750397Sobrien#include "system.h"
28132718Skan#include "coretypes.h"
29132718Skan#include "tm.h"
3018334Speter#include "tree.h"
3118334Speter#include "cp-tree.h"
3218334Speter#include "obstack.h"
3318334Speter#include "flags.h"
3418334Speter#include "rtl.h"
3518334Speter#include "output.h"
3650397Sobrien#include "toplev.h"
3718334Speter
38146895Skanstatic int is_subobject_of_p (tree, tree);
39169689Skanstatic tree dfs_lookup_base (tree, void *);
40169689Skanstatic tree dfs_dcast_hint_pre (tree, void *);
41169689Skanstatic tree dfs_dcast_hint_post (tree, void *);
42132718Skanstatic tree dfs_debug_mark (tree, void *);
43169689Skanstatic tree dfs_walk_once_r (tree, tree (*pre_fn) (tree, void *),
44169689Skan			     tree (*post_fn) (tree, void *), void *data);
45169689Skanstatic void dfs_unmark_r (tree);
46169689Skanstatic int check_hidden_convs (tree, int, int, tree, tree, tree);
47169689Skanstatic tree split_conversions (tree, tree, tree, tree);
48169689Skanstatic int lookup_conversions_r (tree, int, int,
49169689Skan				 tree, tree, tree, tree, tree *, tree *);
50132718Skanstatic int look_for_overrides_r (tree, tree);
51132718Skanstatic tree lookup_field_r (tree, void *);
52169689Skanstatic tree dfs_accessible_post (tree, void *);
53169689Skanstatic tree dfs_walk_once_accessible_r (tree, bool, bool,
54169689Skan					tree (*pre_fn) (tree, void *),
55169689Skan					tree (*post_fn) (tree, void *),
56169689Skan					void *data);
57169689Skanstatic tree dfs_walk_once_accessible (tree, bool,
58169689Skan				      tree (*pre_fn) (tree, void *),
59169689Skan				      tree (*post_fn) (tree, void *),
60169689Skan				      void *data);
61132718Skanstatic tree dfs_access_in_type (tree, void *);
62132718Skanstatic access_kind access_in_type (tree, tree);
63132718Skanstatic int protected_accessible_p (tree, tree, tree);
64132718Skanstatic int friend_accessible_p (tree, tree, tree);
65132718Skanstatic int template_self_reference_p (tree, tree);
66132718Skanstatic tree dfs_get_pure_virtuals (tree, void *);
6718334Speter
6818334Speter
6918334Speter/* Variables for gathering statistics.  */
7050397Sobrien#ifdef GATHER_STATISTICS
7118334Speterstatic int n_fields_searched;
7218334Speterstatic int n_calls_lookup_field, n_calls_lookup_field_1;
7318334Speterstatic int n_calls_lookup_fnfields, n_calls_lookup_fnfields_1;
7418334Speterstatic int n_calls_get_base_type;
7518334Speterstatic int n_outer_fields_searched;
7618334Speterstatic int n_contexts_saved;
7750397Sobrien#endif /* GATHER_STATISTICS */
7818334Speter
7918334Speter
80169689Skan/* Data for lookup_base and its workers.  */
8150397Sobrien
82169689Skanstruct lookup_base_data_s
83169689Skan{
84169689Skan  tree t;		/* type being searched.  */
85169689Skan  tree base;		/* The base type we're looking for.  */
86169689Skan  tree binfo;		/* Found binfo.  */
87169689Skan  bool via_virtual;	/* Found via a virtual path.  */
88169689Skan  bool ambiguous;	/* Found multiply ambiguous */
89169689Skan  bool repeated_base;	/* Whether there are repeated bases in the
90169689Skan			    hierarchy.  */
91169689Skan  bool want_any;	/* Whether we want any matching binfo.  */
92169689Skan};
9352284Sobrien
94169689Skan/* Worker function for lookup_base.  See if we've found the desired
95169689Skan   base and update DATA_ (a pointer to LOOKUP_BASE_DATA_S).  */
9690075Sobrien
97169689Skanstatic tree
98169689Skandfs_lookup_base (tree binfo, void *data_)
9918334Speter{
100169689Skan  struct lookup_base_data_s *data = (struct lookup_base_data_s *) data_;
101169689Skan
102169689Skan  if (SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), data->base))
10318334Speter    {
104169689Skan      if (!data->binfo)
10590075Sobrien	{
106169689Skan	  data->binfo = binfo;
107169689Skan	  data->via_virtual
108169689Skan	    = binfo_via_virtual (data->binfo, data->t) != NULL_TREE;
10918334Speter
110169689Skan	  if (!data->repeated_base)
111169689Skan	    /* If there are no repeated bases, we can stop now.  */
112169689Skan	    return binfo;
11318334Speter
114169689Skan	  if (data->want_any && !data->via_virtual)
115169689Skan	    /* If this is a non-virtual base, then we can't do
116169689Skan	       better.  */
117169689Skan	    return binfo;
118169689Skan
119169689Skan	  return dfs_skip_bases;
120169689Skan	}
121169689Skan      else
12290075Sobrien	{
123169689Skan	  gcc_assert (binfo != data->binfo);
124117395Skan
125169689Skan	  /* We've found more than one matching binfo.  */
126169689Skan	  if (!data->want_any)
127169689Skan	    {
128169689Skan	      /* This is immediately ambiguous.  */
129169689Skan	      data->binfo = NULL_TREE;
130169689Skan	      data->ambiguous = true;
131169689Skan	      return error_mark_node;
132169689Skan	    }
133169689Skan
134169689Skan	  /* Prefer one via a non-virtual path.  */
135169689Skan	  if (!binfo_via_virtual (binfo, data->t))
136169689Skan	    {
137169689Skan	      data->binfo = binfo;
138169689Skan	      data->via_virtual = false;
139169689Skan	      return binfo;
140169689Skan	    }
141169689Skan
142169689Skan	  /* There must be repeated bases, otherwise we'd have stopped
143169689Skan	     on the first base we found.  */
144169689Skan	  return dfs_skip_bases;
14590075Sobrien	}
14618334Speter    }
147169689Skan
148169689Skan  return NULL_TREE;
14918334Speter}
15018334Speter
151119256Skan/* Returns true if type BASE is accessible in T.  (BASE is known to be
152169689Skan   a (possibly non-proper) base class of T.)  If CONSIDER_LOCAL_P is
153169689Skan   true, consider any special access of the current scope, or access
154169689Skan   bestowed by friendship.  */
155119256Skan
156119256Skanbool
157169689Skanaccessible_base_p (tree t, tree base, bool consider_local_p)
158119256Skan{
159119256Skan  tree decl;
160119256Skan
161119256Skan  /* [class.access.base]
162119256Skan
163119256Skan     A base class is said to be accessible if an invented public
164169689Skan     member of the base class is accessible.
165132718Skan
166132718Skan     If BASE is a non-proper base, this condition is trivially
167132718Skan     true.  */
168132718Skan  if (same_type_p (t, base))
169132718Skan    return true;
170119256Skan  /* Rather than inventing a public member, we use the implicit
171119256Skan     public typedef created in the scope of every class.  */
172119256Skan  decl = TYPE_FIELDS (base);
173119256Skan  while (!DECL_SELF_REFERENCE_P (decl))
174119256Skan    decl = TREE_CHAIN (decl);
175119256Skan  while (ANON_AGGR_TYPE_P (t))
176119256Skan    t = TYPE_CONTEXT (t);
177169689Skan  return accessible_p (t, decl, consider_local_p);
178119256Skan}
179119256Skan
18090075Sobrien/* Lookup BASE in the hierarchy dominated by T.  Do access checking as
181132718Skan   ACCESS specifies.  Return the binfo we discover.  If KIND_PTR is
182132718Skan   non-NULL, fill with information about what kind of base we
183132718Skan   discovered.
18452284Sobrien
185117395Skan   If the base is inaccessible, or ambiguous, and the ba_quiet bit is
186117395Skan   not set in ACCESS, then an error is issued and error_mark_node is
187117395Skan   returned.  If the ba_quiet bit is set, then no error is issued and
188117395Skan   NULL_TREE is returned.  */
18950397Sobrien
19018334Spetertree
191132718Skanlookup_base (tree t, tree base, base_access access, base_kind *kind_ptr)
19218334Speter{
193169689Skan  tree binfo;
194169689Skan  tree t_binfo;
19590075Sobrien  base_kind bk;
196169689Skan
19790075Sobrien  if (t == error_mark_node || base == error_mark_node)
19818334Speter    {
19990075Sobrien      if (kind_ptr)
20090075Sobrien	*kind_ptr = bk_not_base;
20118334Speter      return error_mark_node;
20218334Speter    }
203169689Skan  gcc_assert (TYPE_P (base));
204169689Skan
205117395Skan  if (!TYPE_P (t))
206117395Skan    {
207117395Skan      t_binfo = t;
208117395Skan      t = BINFO_TYPE (t);
209117395Skan    }
210169689Skan  else
211169689Skan    {
212169689Skan      t = complete_type (TYPE_MAIN_VARIANT (t));
213169689Skan      t_binfo = TYPE_BINFO (t);
214169689Skan    }
215117395Skan
21690075Sobrien  base = complete_type (TYPE_MAIN_VARIANT (base));
21790075Sobrien
218169689Skan  if (t_binfo)
219169689Skan    {
220169689Skan      struct lookup_base_data_s data;
221169689Skan
222169689Skan      data.t = t;
223169689Skan      data.base = base;
224169689Skan      data.binfo = NULL_TREE;
225169689Skan      data.ambiguous = data.via_virtual = false;
226169689Skan      data.repeated_base = CLASSTYPE_REPEATED_BASE_P (t);
227169689Skan      data.want_any = access == ba_any;
228169689Skan
229169689Skan      dfs_walk_once (t_binfo, dfs_lookup_base, NULL, &data);
230169689Skan      binfo = data.binfo;
231169689Skan
232169689Skan      if (!binfo)
233169689Skan	bk = data.ambiguous ? bk_ambig : bk_not_base;
234169689Skan      else if (binfo == t_binfo)
235169689Skan	bk = bk_same_type;
236169689Skan      else if (data.via_virtual)
237169689Skan	bk = bk_via_virtual;
238169689Skan      else
239169689Skan	bk = bk_proper_base;
240169689Skan    }
241169689Skan  else
242169689Skan    {
243169689Skan      binfo = NULL_TREE;
244169689Skan      bk = bk_not_base;
245169689Skan    }
246169689Skan
247117395Skan  /* Check that the base is unambiguous and accessible.  */
248117395Skan  if (access != ba_any)
249117395Skan    switch (bk)
250117395Skan      {
251117395Skan      case bk_not_base:
252117395Skan	break;
253117395Skan
254117395Skan      case bk_ambig:
255117395Skan	if (!(access & ba_quiet))
256117395Skan	  {
257169689Skan	    error ("%qT is an ambiguous base of %qT", base, t);
258117395Skan	    binfo = error_mark_node;
259117395Skan	  }
260117395Skan	break;
261117395Skan
262117395Skan      default:
263169689Skan	if ((access & ba_check_bit)
264117395Skan	    /* If BASE is incomplete, then BASE and TYPE are probably
265117395Skan	       the same, in which case BASE is accessible.  If they
266117395Skan	       are not the same, then TYPE is invalid.  In that case,
267117395Skan	       there's no need to issue another error here, and
268117395Skan	       there's no implicit typedef to use in the code that
269117395Skan	       follows, so we skip the check.  */
270119256Skan	    && COMPLETE_TYPE_P (base)
271169689Skan	    && !accessible_base_p (t, base, !(access & ba_ignore_scope)))
272117395Skan	  {
273119256Skan	    if (!(access & ba_quiet))
274117395Skan	      {
275169689Skan		error ("%qT is an inaccessible base of %qT", base, t);
276119256Skan		binfo = error_mark_node;
277117395Skan	      }
278119256Skan	    else
279119256Skan	      binfo = NULL_TREE;
280119256Skan	    bk = bk_inaccessible;
281117395Skan	  }
282117395Skan	break;
283117395Skan      }
284117395Skan
28590075Sobrien  if (kind_ptr)
28690075Sobrien    *kind_ptr = bk;
287169689Skan
28890075Sobrien  return binfo;
28918334Speter}
29018334Speter
291169689Skan/* Data for dcast_base_hint walker.  */
29250397Sobrien
293169689Skanstruct dcast_data_s
29418334Speter{
295169689Skan  tree subtype;   /* The base type we're looking for.  */
296169689Skan  int virt_depth; /* Number of virtual bases encountered from most
297169689Skan		     derived.  */
298169689Skan  tree offset;    /* Best hint offset discovered so far.  */
299169689Skan  bool repeated_base;  /* Whether there are repeated bases in the
300169689Skan			  hierarchy.  */
301169689Skan};
302169689Skan
303169689Skan/* Worker for dcast_base_hint.  Search for the base type being cast
304169689Skan   from.  */
305169689Skan
306169689Skanstatic tree
307169689Skandfs_dcast_hint_pre (tree binfo, void *data_)
308169689Skan{
309169689Skan  struct dcast_data_s *data = (struct dcast_data_s *) data_;
310169689Skan
311169689Skan  if (BINFO_VIRTUAL_P (binfo))
312169689Skan    data->virt_depth++;
313169689Skan
314169689Skan  if (SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), data->subtype))
31518334Speter    {
316169689Skan      if (data->virt_depth)
317169689Skan	{
318169689Skan	  data->offset = ssize_int (-1);
319169689Skan	  return data->offset;
320169689Skan	}
321169689Skan      if (data->offset)
322169689Skan	data->offset = ssize_int (-3);
32352284Sobrien      else
324169689Skan	data->offset = BINFO_OFFSET (binfo);
325169689Skan
326169689Skan      return data->repeated_base ? dfs_skip_bases : data->offset;
32718334Speter    }
328169689Skan
329169689Skan  return NULL_TREE;
33018334Speter}
33118334Speter
332169689Skan/* Worker for dcast_base_hint.  Track the virtual depth.  */
333169689Skan
334169689Skanstatic tree
335169689Skandfs_dcast_hint_post (tree binfo, void *data_)
336169689Skan{
337169689Skan  struct dcast_data_s *data = (struct dcast_data_s *) data_;
338169689Skan
339169689Skan  if (BINFO_VIRTUAL_P (binfo))
340169689Skan    data->virt_depth--;
341169689Skan
342169689Skan  return NULL_TREE;
343169689Skan}
344169689Skan
34590075Sobrien/* The dynamic cast runtime needs a hint about how the static SUBTYPE type
34690075Sobrien   started from is related to the required TARGET type, in order to optimize
34790075Sobrien   the inheritance graph search. This information is independent of the
34890075Sobrien   current context, and ignores private paths, hence get_base_distance is
34990075Sobrien   inappropriate. Return a TREE specifying the base offset, BOFF.
35090075Sobrien   BOFF >= 0, there is only one public non-virtual SUBTYPE base at offset BOFF,
35190075Sobrien      and there are no public virtual SUBTYPE bases.
35290075Sobrien   BOFF == -1, SUBTYPE occurs as multiple public virtual or non-virtual bases.
35390075Sobrien   BOFF == -2, SUBTYPE is not a public base.
35490075Sobrien   BOFF == -3, SUBTYPE occurs as multiple public non-virtual bases.  */
35518334Speter
35690075Sobrientree
357169689Skandcast_base_hint (tree subtype, tree target)
35818334Speter{
359169689Skan  struct dcast_data_s data;
360169689Skan
361169689Skan  data.subtype = subtype;
362169689Skan  data.virt_depth = 0;
363169689Skan  data.offset = NULL_TREE;
364169689Skan  data.repeated_base = CLASSTYPE_REPEATED_BASE_P (target);
365169689Skan
366169689Skan  dfs_walk_once_accessible (TYPE_BINFO (target), /*friends=*/false,
367169689Skan			    dfs_dcast_hint_pre, dfs_dcast_hint_post, &data);
368169689Skan  return data.offset ? data.offset : ssize_int (-2);
36918334Speter}
37018334Speter
371132718Skan/* Search for a member with name NAME in a multiple inheritance
372132718Skan   lattice specified by TYPE.  If it does not exist, return NULL_TREE.
37318334Speter   If the member is ambiguously referenced, return `error_mark_node'.
374132718Skan   Otherwise, return a DECL with the indicated name.  If WANT_TYPE is
375132718Skan   true, type declarations are preferred.  */
37618334Speter
37718334Speter/* Do a 1-level search for NAME as a member of TYPE.  The caller must
37818334Speter   figure out whether it can access this field.  (Since it is only one
37918334Speter   level, this is reasonable.)  */
38050397Sobrien
381117395Skantree
382117395Skanlookup_field_1 (tree type, tree name, bool want_type)
38318334Speter{
384132718Skan  tree field;
38518334Speter
38650397Sobrien  if (TREE_CODE (type) == TEMPLATE_TYPE_PARM
38790075Sobrien      || TREE_CODE (type) == BOUND_TEMPLATE_TEMPLATE_PARM
38890075Sobrien      || TREE_CODE (type) == TYPENAME_TYPE)
389169689Skan    /* The TYPE_FIELDS of a TEMPLATE_TYPE_PARM and
39090075Sobrien       BOUND_TEMPLATE_TEMPLATE_PARM are not fields at all;
39150397Sobrien       instead TYPE_FIELDS is the TEMPLATE_PARM_INDEX.  (Miraculously,
39250397Sobrien       the code often worked even when we treated the index as a list
39390075Sobrien       of fields!)
39490075Sobrien       The TYPE_FIELDS of TYPENAME_TYPE is its TYPENAME_TYPE_FULLNAME.  */
39550397Sobrien    return NULL_TREE;
39650397Sobrien
39790075Sobrien  if (TYPE_NAME (type)
39890075Sobrien      && DECL_LANG_SPECIFIC (TYPE_NAME (type))
39990075Sobrien      && DECL_SORTED_FIELDS (TYPE_NAME (type)))
40090075Sobrien    {
401132718Skan      tree *fields = &DECL_SORTED_FIELDS (TYPE_NAME (type))->elts[0];
402132718Skan      int lo = 0, hi = DECL_SORTED_FIELDS (TYPE_NAME (type))->len;
40390075Sobrien      int i;
40490075Sobrien
40590075Sobrien      while (lo < hi)
40690075Sobrien	{
40790075Sobrien	  i = (lo + hi) / 2;
40890075Sobrien
40990075Sobrien#ifdef GATHER_STATISTICS
41090075Sobrien	  n_fields_searched++;
41190075Sobrien#endif /* GATHER_STATISTICS */
41290075Sobrien
41390075Sobrien	  if (DECL_NAME (fields[i]) > name)
41490075Sobrien	    hi = i;
41590075Sobrien	  else if (DECL_NAME (fields[i]) < name)
41690075Sobrien	    lo = i + 1;
41790075Sobrien	  else
41890075Sobrien	    {
419117395Skan	      field = NULL_TREE;
420117395Skan
42190075Sobrien	      /* We might have a nested class and a field with the
42290075Sobrien		 same name; we sorted them appropriately via
423117395Skan		 field_decl_cmp, so just look for the first or last
424117395Skan		 field with this name.  */
425117395Skan	      if (want_type)
426117395Skan		{
427117395Skan		  do
428117395Skan		    field = fields[i--];
429117395Skan		  while (i >= lo && DECL_NAME (fields[i]) == name);
430117395Skan		  if (TREE_CODE (field) != TYPE_DECL
431117395Skan		      && !DECL_CLASS_TEMPLATE_P (field))
432117395Skan		    field = NULL_TREE;
433117395Skan		}
434117395Skan	      else
435117395Skan		{
436117395Skan		  do
437117395Skan		    field = fields[i++];
438117395Skan		  while (i < hi && DECL_NAME (fields[i]) == name);
439117395Skan		}
440117395Skan	      return field;
44190075Sobrien	    }
44290075Sobrien	}
44390075Sobrien      return NULL_TREE;
44490075Sobrien    }
44590075Sobrien
44650397Sobrien  field = TYPE_FIELDS (type);
44750397Sobrien
44818334Speter#ifdef GATHER_STATISTICS
44918334Speter  n_calls_lookup_field_1++;
45050397Sobrien#endif /* GATHER_STATISTICS */
451117395Skan  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
45218334Speter    {
45318334Speter#ifdef GATHER_STATISTICS
45418334Speter      n_fields_searched++;
45550397Sobrien#endif /* GATHER_STATISTICS */
456169689Skan      gcc_assert (DECL_P (field));
45718334Speter      if (DECL_NAME (field) == NULL_TREE
45890075Sobrien	  && ANON_AGGR_TYPE_P (TREE_TYPE (field)))
45918334Speter	{
460117395Skan	  tree temp = lookup_field_1 (TREE_TYPE (field), name, want_type);
46118334Speter	  if (temp)
46218334Speter	    return temp;
46318334Speter	}
46452284Sobrien      if (TREE_CODE (field) == USING_DECL)
465169689Skan	{
466169689Skan	  /* We generally treat class-scope using-declarations as
467169689Skan	     ARM-style access specifications, because support for the
468169689Skan	     ISO semantics has not been implemented.  So, in general,
469169689Skan	     there's no reason to return a USING_DECL, and the rest of
470169689Skan	     the compiler cannot handle that.  Once the class is
471169689Skan	     defined, USING_DECLs are purged from TYPE_FIELDS; see
472169689Skan	     handle_using_decl.  However, we make special efforts to
473169689Skan	     make using-declarations in class templates and class
474169689Skan	     template partial specializations work correctly.  */
475169689Skan	  if (!DECL_DEPENDENT_P (field))
476169689Skan	    continue;
477169689Skan	}
478117395Skan
479117395Skan      if (DECL_NAME (field) == name
480169689Skan	  && (!want_type
481117395Skan	      || TREE_CODE (field) == TYPE_DECL
482117395Skan	      || DECL_CLASS_TEMPLATE_P (field)))
48390075Sobrien	return field;
48418334Speter    }
48518334Speter  /* Not found.  */
48690075Sobrien  if (name == vptr_identifier)
48718334Speter    {
48818334Speter      /* Give the user what s/he thinks s/he wants.  */
48990075Sobrien      if (TYPE_POLYMORPHIC_P (type))
49090075Sobrien	return TYPE_VFIELD (type);
49118334Speter    }
49218334Speter  return NULL_TREE;
49318334Speter}
49418334Speter
495169689Skan/* Return the FUNCTION_DECL, RECORD_TYPE, UNION_TYPE, or
496169689Skan   NAMESPACE_DECL corresponding to the innermost non-block scope.  */
497169689Skan
498169689Skantree
499169689Skancurrent_scope (void)
500169689Skan{
501169689Skan  /* There are a number of cases we need to be aware of here:
50218334Speter			 current_class_type	current_function_decl
50350397Sobrien     global			NULL			NULL
50450397Sobrien     fn-local			NULL			SET
50550397Sobrien     class-local		SET			NULL
50650397Sobrien     class->fn			SET			SET
50750397Sobrien     fn->class			SET			SET
50818334Speter
509169689Skan     Those last two make life interesting.  If we're in a function which is
510169689Skan     itself inside a class, we need decls to go into the fn's decls (our
511169689Skan     second case below).  But if we're in a class and the class itself is
512169689Skan     inside a function, we need decls to go into the decls for the class.  To
513169689Skan     achieve this last goal, we must see if, when both current_class_ptr and
514169689Skan     current_function_decl are set, the class was declared inside that
515169689Skan     function.  If so, we know to put the decls into the class's scope.  */
516169689Skan  if (current_function_decl && current_class_type
517169689Skan      && ((DECL_FUNCTION_MEMBER_P (current_function_decl)
518169689Skan	   && same_type_p (DECL_CONTEXT (current_function_decl),
519169689Skan			   current_class_type))
520169689Skan	  || (DECL_FRIEND_CONTEXT (current_function_decl)
521169689Skan	      && same_type_p (DECL_FRIEND_CONTEXT (current_function_decl),
522169689Skan			      current_class_type))))
523169689Skan    return current_function_decl;
524169689Skan  if (current_class_type)
52518334Speter    return current_class_type;
526169689Skan  if (current_function_decl)
52718334Speter    return current_function_decl;
528169689Skan  return current_namespace;
52918334Speter}
53018334Speter
531117395Skan/* Returns nonzero if we are currently in a function scope.  Note
53290075Sobrien   that this function returns zero if we are within a local class, but
53390075Sobrien   not within a member function body of the local class.  */
53490075Sobrien
53590075Sobrienint
536132718Skanat_function_scope_p (void)
53790075Sobrien{
53890075Sobrien  tree cs = current_scope ();
53990075Sobrien  return cs && TREE_CODE (cs) == FUNCTION_DECL;
54090075Sobrien}
54190075Sobrien
542117395Skan/* Returns true if the innermost active scope is a class scope.  */
543117395Skan
544117395Skanbool
545132718Skanat_class_scope_p (void)
546117395Skan{
547117395Skan  tree cs = current_scope ();
548117395Skan  return cs && TYPE_P (cs);
549117395Skan}
550117395Skan
551132718Skan/* Returns true if the innermost active scope is a namespace scope.  */
552132718Skan
553132718Skanbool
554132718Skanat_namespace_scope_p (void)
555132718Skan{
556169689Skan  tree cs = current_scope ();
557169689Skan  return cs && TREE_CODE (cs) == NAMESPACE_DECL;
558132718Skan}
559132718Skan
56052284Sobrien/* Return the scope of DECL, as appropriate when doing name-lookup.  */
56118334Speter
56290075Sobrientree
563132718Skancontext_for_name_lookup (tree decl)
56452284Sobrien{
56552284Sobrien  /* [class.union]
566169689Skan
56752284Sobrien     For the purposes of name lookup, after the anonymous union
56852284Sobrien     definition, the members of the anonymous union are considered to
56990075Sobrien     have been defined in the scope in which the anonymous union is
570169689Skan     declared.  */
57190075Sobrien  tree context = DECL_CONTEXT (decl);
57218334Speter
57390075Sobrien  while (context && TYPE_P (context) && ANON_AGGR_TYPE_P (context))
57452284Sobrien    context = TYPE_CONTEXT (context);
57552284Sobrien  if (!context)
57652284Sobrien    context = global_namespace;
57718334Speter
57852284Sobrien  return context;
57952284Sobrien}
58018334Speter
58190075Sobrien/* The accessibility routines use BINFO_ACCESS for scratch space
582132718Skan   during the computation of the accessibility of some declaration.  */
58390075Sobrien
58490075Sobrien#define BINFO_ACCESS(NODE) \
585132718Skan  ((access_kind) ((TREE_PUBLIC (NODE) << 1) | TREE_PRIVATE (NODE)))
58690075Sobrien
58790075Sobrien/* Set the access associated with NODE to ACCESS.  */
58890075Sobrien
58990075Sobrien#define SET_BINFO_ACCESS(NODE, ACCESS)			\
590132718Skan  ((TREE_PUBLIC (NODE) = ((ACCESS) & 2) != 0),	\
591132718Skan   (TREE_PRIVATE (NODE) = ((ACCESS) & 1) != 0))
59290075Sobrien
59352284Sobrien/* Called from access_in_type via dfs_walk.  Calculate the access to
59452284Sobrien   DATA (which is really a DECL) in BINFO.  */
59518334Speter
59652284Sobrienstatic tree
597132718Skandfs_access_in_type (tree binfo, void *data)
59852284Sobrien{
59952284Sobrien  tree decl = (tree) data;
60052284Sobrien  tree type = BINFO_TYPE (binfo);
60190075Sobrien  access_kind access = ak_none;
60218334Speter
60352284Sobrien  if (context_for_name_lookup (decl) == type)
60418334Speter    {
605132718Skan      /* If we have descended to the scope of DECL, just note the
60652284Sobrien	 appropriate access.  */
60752284Sobrien      if (TREE_PRIVATE (decl))
60890075Sobrien	access = ak_private;
60952284Sobrien      else if (TREE_PROTECTED (decl))
61090075Sobrien	access = ak_protected;
61118334Speter      else
61290075Sobrien	access = ak_public;
61318334Speter    }
614169689Skan  else
61518334Speter    {
61652284Sobrien      /* First, check for an access-declaration that gives us more
61752284Sobrien	 access to the DECL.  The CONST_DECL for an enumeration
61852284Sobrien	 constant will not have DECL_LANG_SPECIFIC, and thus no
61952284Sobrien	 DECL_ACCESS.  */
62090075Sobrien      if (DECL_LANG_SPECIFIC (decl) && !DECL_DISCRIMINATOR_P (decl))
62118334Speter	{
62290075Sobrien	  tree decl_access = purpose_member (type, DECL_ACCESS (decl));
623169689Skan
62490075Sobrien	  if (decl_access)
625132718Skan	    {
626132718Skan	      decl_access = TREE_VALUE (decl_access);
627169689Skan
628132718Skan	      if (decl_access == access_public_node)
629132718Skan		access = ak_public;
630132718Skan	      else if (decl_access == access_protected_node)
631132718Skan		access = ak_protected;
632132718Skan	      else if (decl_access == access_private_node)
633132718Skan		access = ak_private;
634132718Skan	      else
635169689Skan		gcc_unreachable ();
636132718Skan	    }
63718334Speter	}
63818334Speter
63952284Sobrien      if (!access)
64018334Speter	{
64152284Sobrien	  int i;
642169689Skan	  tree base_binfo;
643169689Skan	  VEC(tree,gc) *accesses;
644169689Skan
64552284Sobrien	  /* Otherwise, scan our baseclasses, and pick the most favorable
64652284Sobrien	     access.  */
647169689Skan	  accesses = BINFO_BASE_ACCESSES (binfo);
648169689Skan	  for (i = 0; BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
64952284Sobrien	    {
650169689Skan	      tree base_access = VEC_index (tree, accesses, i);
651132718Skan	      access_kind base_access_now = BINFO_ACCESS (base_binfo);
65218334Speter
653132718Skan	      if (base_access_now == ak_none || base_access_now == ak_private)
65452284Sobrien		/* If it was not accessible in the base, or only
65552284Sobrien		   accessible as a private member, we can't access it
65652284Sobrien		   all.  */
657132718Skan		base_access_now = ak_none;
658132718Skan	      else if (base_access == access_protected_node)
659132718Skan		/* Public and protected members in the base become
66052284Sobrien		   protected here.  */
661132718Skan		base_access_now = ak_protected;
662132718Skan	      else if (base_access == access_private_node)
663132718Skan		/* Public and protected members in the base become
66452284Sobrien		   private here.  */
665132718Skan		base_access_now = ak_private;
66618334Speter
66752284Sobrien	      /* See if the new access, via this base, gives more
66852284Sobrien		 access than our previous best access.  */
669132718Skan	      if (base_access_now != ak_none
670132718Skan		  && (access == ak_none || base_access_now < access))
67152284Sobrien		{
672132718Skan		  access = base_access_now;
67352284Sobrien
67452284Sobrien		  /* If the new access is public, we can't do better.  */
67590075Sobrien		  if (access == ak_public)
67652284Sobrien		    break;
67752284Sobrien		}
67818334Speter	    }
67918334Speter	}
68018334Speter    }
68118334Speter
68252284Sobrien  /* Note the access to DECL in TYPE.  */
68390075Sobrien  SET_BINFO_ACCESS (binfo, access);
68418334Speter
68552284Sobrien  return NULL_TREE;
68652284Sobrien}
68752284Sobrien
68852284Sobrien/* Return the access to DECL in TYPE.  */
68952284Sobrien
69090075Sobrienstatic access_kind
691132718Skanaccess_in_type (tree type, tree decl)
69252284Sobrien{
69352284Sobrien  tree binfo = TYPE_BINFO (type);
69452284Sobrien
69552284Sobrien  /* We must take into account
69652284Sobrien
69752284Sobrien       [class.paths]
69852284Sobrien
69952284Sobrien       If a name can be reached by several paths through a multiple
70052284Sobrien       inheritance graph, the access is that of the path that gives
701169689Skan       most access.
70252284Sobrien
70352284Sobrien    The algorithm we use is to make a post-order depth-first traversal
70452284Sobrien    of the base-class hierarchy.  As we come up the tree, we annotate
70552284Sobrien    each node with the most lenient access.  */
706169689Skan  dfs_walk_once (binfo, NULL, dfs_access_in_type, decl);
70752284Sobrien
70890075Sobrien  return BINFO_ACCESS (binfo);
70952284Sobrien}
71052284Sobrien
711117395Skan/* Returns nonzero if it is OK to access DECL through an object
712132718Skan   indicated by BINFO in the context of DERIVED.  */
71352284Sobrien
71452284Sobrienstatic int
715132718Skanprotected_accessible_p (tree decl, tree derived, tree binfo)
71652284Sobrien{
71790075Sobrien  access_kind access;
71852284Sobrien
71952284Sobrien  /* We're checking this clause from [class.access.base]
72052284Sobrien
72152284Sobrien       m as a member of N is protected, and the reference occurs in a
72252284Sobrien       member or friend of class N, or in a member or friend of a
72352284Sobrien       class P derived from N, where m as a member of P is private or
724169689Skan       protected.
72552284Sobrien
72690075Sobrien    Here DERIVED is a possible P and DECL is m.  accessible_p will
72790075Sobrien    iterate over various values of N, but the access to m in DERIVED
72890075Sobrien    does not change.
72990075Sobrien
73090075Sobrien    Note that I believe that the passage above is wrong, and should read
73190075Sobrien    "...is private or protected or public"; otherwise you get bizarre results
73290075Sobrien    whereby a public using-decl can prevent you from accessing a protected
73390075Sobrien    member of a base.  (jason 2000/02/28)  */
73490075Sobrien
73590075Sobrien  /* If DERIVED isn't derived from m's class, then it can't be a P.  */
73690075Sobrien  if (!DERIVED_FROM_P (context_for_name_lookup (decl), derived))
73752284Sobrien    return 0;
73852284Sobrien
73952284Sobrien  access = access_in_type (derived, decl);
74090075Sobrien
74190075Sobrien  /* If m is inaccessible in DERIVED, then it's not a P.  */
74290075Sobrien  if (access == ak_none)
74352284Sobrien    return 0;
744169689Skan
74552284Sobrien  /* [class.protected]
74618334Speter
74752284Sobrien     When a friend or a member function of a derived class references
74852284Sobrien     a protected nonstatic member of a base class, an access check
74952284Sobrien     applies in addition to those described earlier in clause
75090075Sobrien     _class.access_) Except when forming a pointer to member
75152284Sobrien     (_expr.unary.op_), the access must be through a pointer to,
75252284Sobrien     reference to, or object of the derived class itself (or any class
75352284Sobrien     derived from that class) (_expr.ref_).  If the access is to form
75452284Sobrien     a pointer to member, the nested-name-specifier shall name the
75552284Sobrien     derived class (or any class derived from that class).  */
75652284Sobrien  if (DECL_NONSTATIC_MEMBER_P (decl))
75752284Sobrien    {
75852284Sobrien      /* We can tell through what the reference is occurring by
75952284Sobrien	 chasing BINFO up to the root.  */
76052284Sobrien      tree t = binfo;
76152284Sobrien      while (BINFO_INHERITANCE_CHAIN (t))
76252284Sobrien	t = BINFO_INHERITANCE_CHAIN (t);
763169689Skan
76452284Sobrien      if (!DERIVED_FROM_P (derived, BINFO_TYPE (t)))
76552284Sobrien	return 0;
76652284Sobrien    }
76718334Speter
76852284Sobrien  return 1;
76952284Sobrien}
77018334Speter
771117395Skan/* Returns nonzero if SCOPE is a friend of a type which would be able
77290075Sobrien   to access DECL through the object indicated by BINFO.  */
77352284Sobrien
77452284Sobrienstatic int
775132718Skanfriend_accessible_p (tree scope, tree decl, tree binfo)
77652284Sobrien{
77752284Sobrien  tree befriending_classes;
77852284Sobrien  tree t;
77952284Sobrien
78052284Sobrien  if (!scope)
78152284Sobrien    return 0;
78252284Sobrien
78352284Sobrien  if (TREE_CODE (scope) == FUNCTION_DECL
78452284Sobrien      || DECL_FUNCTION_TEMPLATE_P (scope))
78552284Sobrien    befriending_classes = DECL_BEFRIENDING_CLASSES (scope);
78652284Sobrien  else if (TYPE_P (scope))
78752284Sobrien    befriending_classes = CLASSTYPE_BEFRIENDING_CLASSES (scope);
78852284Sobrien  else
78952284Sobrien    return 0;
79052284Sobrien
79152284Sobrien  for (t = befriending_classes; t; t = TREE_CHAIN (t))
79290075Sobrien    if (protected_accessible_p (decl, TREE_VALUE (t), binfo))
79352284Sobrien      return 1;
79452284Sobrien
795169689Skan  /* Nested classes have the same access as their enclosing types, as
796169689Skan     per DR 45 (this is a change from the standard).  */
79790075Sobrien  if (TYPE_P (scope))
79890075Sobrien    for (t = TYPE_CONTEXT (scope); t && TYPE_P (t); t = TYPE_CONTEXT (t))
79990075Sobrien      if (protected_accessible_p (decl, t, binfo))
80090075Sobrien	return 1;
80190075Sobrien
80252284Sobrien  if (TREE_CODE (scope) == FUNCTION_DECL
80352284Sobrien      || DECL_FUNCTION_TEMPLATE_P (scope))
80452284Sobrien    {
805169689Skan      /* Perhaps this SCOPE is a member of a class which is a
806169689Skan	 friend.  */
807169689Skan      if (DECL_CLASS_SCOPE_P (scope)
80890075Sobrien	  && friend_accessible_p (DECL_CONTEXT (scope), decl, binfo))
80952284Sobrien	return 1;
81052284Sobrien
81152284Sobrien      /* Or an instantiation of something which is a friend.  */
81252284Sobrien      if (DECL_TEMPLATE_INFO (scope))
813146895Skan	{
814146895Skan	  int ret;
815146895Skan	  /* Increment processing_template_decl to make sure that
816146895Skan	     dependent_type_p works correctly.  */
817146895Skan	  ++processing_template_decl;
818146895Skan	  ret = friend_accessible_p (DECL_TI_TEMPLATE (scope), decl, binfo);
819146895Skan	  --processing_template_decl;
820146895Skan	  return ret;
821146895Skan	}
82252284Sobrien    }
823169689Skan
824169689Skan  return 0;
825169689Skan}
826169689Skan
827169689Skan/* Called via dfs_walk_once_accessible from accessible_p */
828169689Skan
829169689Skanstatic tree
830169689Skandfs_accessible_post (tree binfo, void *data ATTRIBUTE_UNUSED)
831169689Skan{
832169689Skan  if (BINFO_ACCESS (binfo) != ak_none)
833146895Skan    {
834169689Skan      tree scope = current_scope ();
835169689Skan      if (scope && TREE_CODE (scope) != NAMESPACE_DECL
836169689Skan	  && is_friend (BINFO_TYPE (binfo), scope))
837169689Skan	return binfo;
838146895Skan    }
83952284Sobrien
840169689Skan  return NULL_TREE;
84118334Speter}
84290075Sobrien
84352284Sobrien/* DECL is a declaration from a base class of TYPE, which was the
844117395Skan   class used to name DECL.  Return nonzero if, in the current
84552284Sobrien   context, DECL is accessible.  If TYPE is actually a BINFO node,
84652284Sobrien   then we can tell in what context the access is occurring by looking
847169689Skan   at the most derived class along the path indicated by BINFO.  If
848169689Skan   CONSIDER_LOCAL is true, do consider special access the current
849169689Skan   scope or friendship thereof we might have.  */
85018334Speter
851169689Skanint
852169689Skanaccessible_p (tree type, tree decl, bool consider_local_p)
85352284Sobrien{
85452284Sobrien  tree binfo;
855132718Skan  tree scope;
856132718Skan  access_kind access;
85752284Sobrien
858117395Skan  /* Nonzero if it's OK to access DECL if it has protected
85952284Sobrien     accessibility in TYPE.  */
86052284Sobrien  int protected_ok = 0;
86152284Sobrien
86252284Sobrien  /* If this declaration is in a block or namespace scope, there's no
86352284Sobrien     access control.  */
86452284Sobrien  if (!TYPE_P (context_for_name_lookup (decl)))
86552284Sobrien    return 1;
86652284Sobrien
867132718Skan  /* There is no need to perform access checks inside a thunk.  */
868132718Skan  scope = current_scope ();
869132718Skan  if (scope && DECL_THUNK_P (scope))
870132718Skan    return 1;
871132718Skan
872132718Skan  /* In a template declaration, we cannot be sure whether the
873132718Skan     particular specialization that is instantiated will be a friend
874132718Skan     or not.  Therefore, all access checks are deferred until
875161651Skan     instantiation.  However, PROCESSING_TEMPLATE_DECL is set in the
876161651Skan     parameter list for a template (because we may see dependent types
877161651Skan     in default arguments for template parameters), and access
878169689Skan     checking should be performed in the outermost parameter list.  */
879169689Skan  if (processing_template_decl
880161651Skan      && (!processing_template_parmlist || processing_template_decl > 1))
881132718Skan    return 1;
882132718Skan
88352284Sobrien  if (!TYPE_P (type))
88452284Sobrien    {
88552284Sobrien      binfo = type;
88652284Sobrien      type = BINFO_TYPE (type);
88752284Sobrien    }
88852284Sobrien  else
88952284Sobrien    binfo = TYPE_BINFO (type);
89052284Sobrien
89152284Sobrien  /* [class.access.base]
89252284Sobrien
89352284Sobrien     A member m is accessible when named in class N if
89452284Sobrien
89552284Sobrien     --m as a member of N is public, or
89652284Sobrien
89752284Sobrien     --m as a member of N is private, and the reference occurs in a
89852284Sobrien       member or friend of class N, or
89952284Sobrien
90052284Sobrien     --m as a member of N is protected, and the reference occurs in a
90152284Sobrien       member or friend of class N, or in a member or friend of a
90252284Sobrien       class P derived from N, where m as a member of P is private or
90352284Sobrien       protected, or
90452284Sobrien
90552284Sobrien     --there exists a base class B of N that is accessible at the point
906169689Skan       of reference, and m is accessible when named in class B.
90752284Sobrien
90852284Sobrien    We walk the base class hierarchy, checking these conditions.  */
90952284Sobrien
910169689Skan  if (consider_local_p)
911169689Skan    {
912169689Skan      /* Figure out where the reference is occurring.  Check to see if
913169689Skan	 DECL is private or protected in this scope, since that will
914169689Skan	 determine whether protected access is allowed.  */
915169689Skan      if (current_class_type)
916169689Skan	protected_ok = protected_accessible_p (decl,
917169689Skan					       current_class_type, binfo);
91852284Sobrien
919169689Skan      /* Now, loop through the classes of which we are a friend.  */
920169689Skan      if (!protected_ok)
921169689Skan	protected_ok = friend_accessible_p (scope, decl, binfo);
922169689Skan    }
92352284Sobrien
92490075Sobrien  /* Standardize the binfo that access_in_type will use.  We don't
92590075Sobrien     need to know what path was chosen from this point onwards.  */
92652284Sobrien  binfo = TYPE_BINFO (type);
92752284Sobrien
92852284Sobrien  /* Compute the accessibility of DECL in the class hierarchy
92952284Sobrien     dominated by type.  */
930132718Skan  access = access_in_type (type, decl);
931132718Skan  if (access == ak_public
932132718Skan      || (access == ak_protected && protected_ok))
93318334Speter    return 1;
934117395Skan
935169689Skan  if (!consider_local_p)
936169689Skan    return 0;
937169689Skan
938169689Skan  /* Walk the hierarchy again, looking for a base class that allows
939169689Skan     access.  */
940169689Skan  return dfs_walk_once_accessible (binfo, /*friends=*/true,
941169689Skan				   NULL, dfs_accessible_post, NULL)
942169689Skan    != NULL_TREE;
94318334Speter}
94418334Speter
94552284Sobrienstruct lookup_field_info {
94652284Sobrien  /* The type in which we're looking.  */
94752284Sobrien  tree type;
94852284Sobrien  /* The name of the field for which we're looking.  */
94952284Sobrien  tree name;
95052284Sobrien  /* If non-NULL, the current result of the lookup.  */
95152284Sobrien  tree rval;
95252284Sobrien  /* The path to RVAL.  */
95352284Sobrien  tree rval_binfo;
95452284Sobrien  /* If non-NULL, the lookup was ambiguous, and this is a list of the
95552284Sobrien     candidates.  */
95652284Sobrien  tree ambiguous;
957117395Skan  /* If nonzero, we are looking for types, not data members.  */
95852284Sobrien  int want_type;
95952284Sobrien  /* If something went wrong, a message indicating what.  */
96052284Sobrien  const char *errstr;
96152284Sobrien};
96218334Speter
96390075Sobrien/* Within the scope of a template class, you can refer to the to the
96490075Sobrien   current specialization with the name of the template itself.  For
96590075Sobrien   example:
966169689Skan
96752284Sobrien     template <typename T> struct S { S* sp; }
96852284Sobrien
969117395Skan   Returns nonzero if DECL is such a declaration in a class TYPE.  */
97052284Sobrien
97152284Sobrienstatic int
972132718Skantemplate_self_reference_p (tree type, tree decl)
97352284Sobrien{
97452284Sobrien  return  (CLASSTYPE_USE_TEMPLATE (type)
97552284Sobrien	   && PRIMARY_TEMPLATE_P (CLASSTYPE_TI_TEMPLATE (type))
97652284Sobrien	   && TREE_CODE (decl) == TYPE_DECL
97752284Sobrien	   && DECL_ARTIFICIAL (decl)
97852284Sobrien	   && DECL_NAME (decl) == constructor_name (type));
97952284Sobrien}
98052284Sobrien
98190075Sobrien/* Nonzero for a class member means that it is shared between all objects
98290075Sobrien   of that class.
98390075Sobrien
98490075Sobrien   [class.member.lookup]:If the resulting set of declarations are not all
98590075Sobrien   from sub-objects of the same type, or the set has a  nonstatic  member
98690075Sobrien   and  includes members from distinct sub-objects, there is an ambiguity
98790075Sobrien   and the program is ill-formed.
98890075Sobrien
98990075Sobrien   This function checks that T contains no nonstatic members.  */
99090075Sobrien
991146895Skanint
992132718Skanshared_member_p (tree t)
99390075Sobrien{
99490075Sobrien  if (TREE_CODE (t) == VAR_DECL || TREE_CODE (t) == TYPE_DECL \
99590075Sobrien      || TREE_CODE (t) == CONST_DECL)
99690075Sobrien    return 1;
99790075Sobrien  if (is_overloaded_fn (t))
99890075Sobrien    {
99990075Sobrien      for (; t; t = OVL_NEXT (t))
100090075Sobrien	{
100190075Sobrien	  tree fn = OVL_CURRENT (t);
100290075Sobrien	  if (DECL_NONSTATIC_MEMBER_FUNCTION_P (fn))
100390075Sobrien	    return 0;
100490075Sobrien	}
100590075Sobrien      return 1;
100690075Sobrien    }
100790075Sobrien  return 0;
100890075Sobrien}
100990075Sobrien
1010146895Skan/* Routine to see if the sub-object denoted by the binfo PARENT can be
1011146895Skan   found as a base class and sub-object of the object denoted by
1012146895Skan   BINFO.  */
1013146895Skan
1014146895Skanstatic int
1015146895Skanis_subobject_of_p (tree parent, tree binfo)
1016146895Skan{
1017146895Skan  tree probe;
1018169689Skan
1019146895Skan  for (probe = parent; probe; probe = BINFO_INHERITANCE_CHAIN (probe))
1020146895Skan    {
1021146895Skan      if (probe == binfo)
1022146895Skan	return 1;
1023169689Skan      if (BINFO_VIRTUAL_P (probe))
1024169689Skan	return (binfo_for_vbase (BINFO_TYPE (probe), BINFO_TYPE (binfo))
1025146895Skan		!= NULL_TREE);
1026146895Skan    }
1027146895Skan  return 0;
1028146895Skan}
1029146895Skan
103052284Sobrien/* DATA is really a struct lookup_field_info.  Look for a field with
103152284Sobrien   the name indicated there in BINFO.  If this function returns a
103252284Sobrien   non-NULL value it is the result of the lookup.  Called from
103352284Sobrien   lookup_field via breadth_first_search.  */
103452284Sobrien
103552284Sobrienstatic tree
1036132718Skanlookup_field_r (tree binfo, void *data)
103752284Sobrien{
103852284Sobrien  struct lookup_field_info *lfi = (struct lookup_field_info *) data;
103952284Sobrien  tree type = BINFO_TYPE (binfo);
104052284Sobrien  tree nval = NULL_TREE;
104152284Sobrien
1042169689Skan  /* If this is a dependent base, don't look in it.  */
1043169689Skan  if (BINFO_DEPENDENT_BASE_P (binfo))
1044169689Skan    return NULL_TREE;
1045169689Skan
1046169689Skan  /* If this base class is hidden by the best-known value so far, we
1047169689Skan     don't need to look.  */
1048169689Skan  if (lfi->rval_binfo && BINFO_INHERITANCE_CHAIN (binfo) == lfi->rval_binfo
1049169689Skan      && !BINFO_VIRTUAL_P (binfo))
1050169689Skan    return dfs_skip_bases;
1051169689Skan
105252284Sobrien  /* First, look for a function.  There can't be a function and a data
105352284Sobrien     member with the same name, and if there's a function and a type
105452284Sobrien     with the same name, the type is hidden by the function.  */
105552284Sobrien  if (!lfi->want_type)
105652284Sobrien    {
105790075Sobrien      int idx = lookup_fnfields_1 (type, lfi->name);
105852284Sobrien      if (idx >= 0)
1059169689Skan	nval = VEC_index (tree, CLASSTYPE_METHOD_VEC (type), idx);
106052284Sobrien    }
106152284Sobrien
106252284Sobrien  if (!nval)
106352284Sobrien    /* Look for a data member or type.  */
1064117395Skan    nval = lookup_field_1 (type, lfi->name, lfi->want_type);
106552284Sobrien
106652284Sobrien  /* If there is no declaration with the indicated name in this type,
106752284Sobrien     then there's nothing to do.  */
106852284Sobrien  if (!nval)
1069169689Skan    goto done;
107052284Sobrien
107152284Sobrien  /* If we're looking up a type (as with an elaborated type specifier)
107252284Sobrien     we ignore all non-types we find.  */
107390075Sobrien  if (lfi->want_type && TREE_CODE (nval) != TYPE_DECL
107490075Sobrien      && !DECL_CLASS_TEMPLATE_P (nval))
107552284Sobrien    {
107690075Sobrien      if (lfi->name == TYPE_IDENTIFIER (type))
107790075Sobrien	{
107890075Sobrien	  /* If the aggregate has no user defined constructors, we allow
107990075Sobrien	     it to have fields with the same name as the enclosing type.
108090075Sobrien	     If we are looking for that name, find the corresponding
108190075Sobrien	     TYPE_DECL.  */
108290075Sobrien	  for (nval = TREE_CHAIN (nval); nval; nval = TREE_CHAIN (nval))
108390075Sobrien	    if (DECL_NAME (nval) == lfi->name
108490075Sobrien		&& TREE_CODE (nval) == TYPE_DECL)
108590075Sobrien	      break;
108690075Sobrien	}
108790075Sobrien      else
108890075Sobrien	nval = NULL_TREE;
1089132718Skan      if (!nval && CLASSTYPE_NESTED_UTDS (type) != NULL)
109090075Sobrien	{
1091169689Skan	  binding_entry e = binding_table_find (CLASSTYPE_NESTED_UTDS (type),
1092169689Skan						lfi->name);
1093117395Skan	  if (e != NULL)
1094117395Skan	    nval = TYPE_MAIN_DECL (e->type);
1095169689Skan	  else
1096169689Skan	    goto done;
109790075Sobrien	}
109852284Sobrien    }
109952284Sobrien
110052284Sobrien  /* You must name a template base class with a template-id.  */
1101169689Skan  if (!same_type_p (type, lfi->type)
110252284Sobrien      && template_self_reference_p (type, nval))
1103169689Skan    goto done;
110452284Sobrien
110552284Sobrien  /* If the lookup already found a match, and the new value doesn't
110652284Sobrien     hide the old one, we might have an ambiguity.  */
1107146895Skan  if (lfi->rval_binfo
1108146895Skan      && !is_subobject_of_p (lfi->rval_binfo, binfo))
1109169689Skan
111052284Sobrien    {
111190075Sobrien      if (nval == lfi->rval && shared_member_p (nval))
111252284Sobrien	/* The two things are really the same.  */
111352284Sobrien	;
1114146895Skan      else if (is_subobject_of_p (binfo, lfi->rval_binfo))
111552284Sobrien	/* The previous value hides the new one.  */
111652284Sobrien	;
111752284Sobrien      else
111852284Sobrien	{
111952284Sobrien	  /* We have a real ambiguity.  We keep a chain of all the
112052284Sobrien	     candidates.  */
112152284Sobrien	  if (!lfi->ambiguous && lfi->rval)
112252284Sobrien	    {
112352284Sobrien	      /* This is the first time we noticed an ambiguity.  Add
112452284Sobrien		 what we previously thought was a reasonable candidate
112552284Sobrien		 to the list.  */
112690075Sobrien	      lfi->ambiguous = tree_cons (NULL_TREE, lfi->rval, NULL_TREE);
112752284Sobrien	      TREE_TYPE (lfi->ambiguous) = error_mark_node;
112852284Sobrien	    }
112952284Sobrien
113052284Sobrien	  /* Add the new value.  */
113190075Sobrien	  lfi->ambiguous = tree_cons (NULL_TREE, nval, lfi->ambiguous);
113252284Sobrien	  TREE_TYPE (lfi->ambiguous) = error_mark_node;
1133169689Skan	  lfi->errstr = "request for member %qD is ambiguous";
113452284Sobrien	}
113552284Sobrien    }
113652284Sobrien  else
113752284Sobrien    {
113852284Sobrien      lfi->rval = nval;
113952284Sobrien      lfi->rval_binfo = binfo;
114052284Sobrien    }
114152284Sobrien
1142169689Skan done:
1143169689Skan  /* Don't look for constructors or destructors in base classes.  */
1144169689Skan  if (IDENTIFIER_CTOR_OR_DTOR_P (lfi->name))
1145169689Skan    return dfs_skip_bases;
114652284Sobrien  return NULL_TREE;
114752284Sobrien}
114852284Sobrien
1149169689Skan/* Return a "baselink" with BASELINK_BINFO, BASELINK_ACCESS_BINFO,
1150117395Skan   BASELINK_FUNCTIONS, and BASELINK_OPTYPE set to BINFO, ACCESS_BINFO,
1151117395Skan   FUNCTIONS, and OPTYPE respectively.  */
1152117395Skan
1153117395Skantree
1154117395Skanbuild_baselink (tree binfo, tree access_binfo, tree functions, tree optype)
1155117395Skan{
1156117395Skan  tree baselink;
1157117395Skan
1158169689Skan  gcc_assert (TREE_CODE (functions) == FUNCTION_DECL
1159169689Skan	      || TREE_CODE (functions) == TEMPLATE_DECL
1160169689Skan	      || TREE_CODE (functions) == TEMPLATE_ID_EXPR
1161169689Skan	      || TREE_CODE (functions) == OVERLOAD);
1162169689Skan  gcc_assert (!optype || TYPE_P (optype));
1163169689Skan  gcc_assert (TREE_TYPE (functions));
1164117395Skan
1165132718Skan  baselink = make_node (BASELINK);
1166132718Skan  TREE_TYPE (baselink) = TREE_TYPE (functions);
1167117395Skan  BASELINK_BINFO (baselink) = binfo;
1168117395Skan  BASELINK_ACCESS_BINFO (baselink) = access_binfo;
1169117395Skan  BASELINK_FUNCTIONS (baselink) = functions;
1170117395Skan  BASELINK_OPTYPE (baselink) = optype;
1171117395Skan
1172117395Skan  return baselink;
1173117395Skan}
1174117395Skan
117590075Sobrien/* Look for a member named NAME in an inheritance lattice dominated by
1176117395Skan   XBASETYPE.  If PROTECT is 0 or two, we do not check access.  If it
1177117395Skan   is 1, we enforce accessibility.  If PROTECT is zero, then, for an
1178117395Skan   ambiguous lookup, we return NULL.  If PROTECT is 1, we issue error
1179117395Skan   messages about inaccessible or ambiguous lookup.  If PROTECT is 2,
1180117395Skan   we return a TREE_LIST whose TREE_TYPE is error_mark_node and whose
1181117395Skan   TREE_VALUEs are the list of ambiguous candidates.
118252284Sobrien
1183117395Skan   WANT_TYPE is 1 when we should only return TYPE_DECLs.
118452284Sobrien
1185117395Skan   If nothing can be found return NULL_TREE and do not issue an error.  */
1186117395Skan
118718334Spetertree
1188132718Skanlookup_member (tree xbasetype, tree name, int protect, bool want_type)
118918334Speter{
119052284Sobrien  tree rval, rval_binfo = NULL_TREE;
119152284Sobrien  tree type = NULL_TREE, basetype_path = NULL_TREE;
119252284Sobrien  struct lookup_field_info lfi;
119318334Speter
119418334Speter  /* rval_binfo is the binfo associated with the found member, note,
119518334Speter     this can be set with useful information, even when rval is not
119618334Speter     set, because it must deal with ALL members, not just non-function
119718334Speter     members.  It is used for ambiguity checking and the hidden
119818334Speter     checks.  Whereas rval is only set if a proper (not hidden)
119918334Speter     non-function member is found.  */
120018334Speter
120152284Sobrien  const char *errstr = 0;
120218334Speter
1203169689Skan  gcc_assert (TREE_CODE (name) == IDENTIFIER_NODE);
120450397Sobrien
1205169689Skan  if (TREE_CODE (xbasetype) == TREE_BINFO)
120618334Speter    {
120718334Speter      type = BINFO_TYPE (xbasetype);
120818334Speter      basetype_path = xbasetype;
120918334Speter    }
1210132718Skan  else
121118334Speter    {
1212169689Skan      if (!IS_AGGR_TYPE_CODE (TREE_CODE (xbasetype)))
1213169689Skan	return NULL_TREE;
121418334Speter      type = xbasetype;
1215169689Skan      xbasetype = NULL_TREE;
121618334Speter    }
121718334Speter
1218169689Skan  type = complete_type (type);
1219169689Skan  if (!basetype_path)
1220169689Skan    basetype_path = TYPE_BINFO (type);
1221132718Skan
1222169689Skan  if (!basetype_path)
1223169689Skan    return NULL_TREE;
122450397Sobrien
122518334Speter#ifdef GATHER_STATISTICS
122618334Speter  n_calls_lookup_field++;
122750397Sobrien#endif /* GATHER_STATISTICS */
122818334Speter
1229132718Skan  memset (&lfi, 0, sizeof (lfi));
123052284Sobrien  lfi.type = type;
123152284Sobrien  lfi.name = name;
123252284Sobrien  lfi.want_type = want_type;
1233169689Skan  dfs_walk_all (basetype_path, &lookup_field_r, NULL, &lfi);
123452284Sobrien  rval = lfi.rval;
123552284Sobrien  rval_binfo = lfi.rval_binfo;
123652284Sobrien  if (rval_binfo)
123752284Sobrien    type = BINFO_TYPE (rval_binfo);
123852284Sobrien  errstr = lfi.errstr;
123918334Speter
124052284Sobrien  /* If we are not interested in ambiguities, don't report them;
124152284Sobrien     just return NULL_TREE.  */
124252284Sobrien  if (!protect && lfi.ambiguous)
124352284Sobrien    return NULL_TREE;
1244169689Skan
1245169689Skan  if (protect == 2)
124618334Speter    {
124752284Sobrien      if (lfi.ambiguous)
124852284Sobrien	return lfi.ambiguous;
124918334Speter      else
125052284Sobrien	protect = 0;
125118334Speter    }
125218334Speter
125352284Sobrien  /* [class.access]
125418334Speter
125552284Sobrien     In the case of overloaded function names, access control is
1256169689Skan     applied to the function selected by overloaded resolution.
125718334Speter
1258169689Skan     We cannot check here, even if RVAL is only a single non-static
1259169689Skan     member function, since we do not know what the "this" pointer
1260169689Skan     will be.  For:
1261169689Skan
1262169689Skan        class A { protected: void f(); };
1263169689Skan        class B : public A {
1264169689Skan          void g(A *p) {
1265169689Skan            f(); // OK
1266169689Skan            p->f(); // Not OK.
1267169689Skan          }
1268169689Skan        };
1269169689Skan
1270169689Skan    only the first call to "f" is valid.  However, if the function is
1271169689Skan    static, we can check.  */
1272169689Skan  if (rval && protect
1273169689Skan      && !really_overloaded_fn (rval)
1274169689Skan      && !(TREE_CODE (rval) == FUNCTION_DECL
1275169689Skan	   && DECL_NONSTATIC_MEMBER_FUNCTION_P (rval)))
1276169689Skan    perform_or_defer_access_check (basetype_path, rval, rval);
1277169689Skan
127818334Speter  if (errstr && protect)
127918334Speter    {
128090075Sobrien      error (errstr, name, type);
128152284Sobrien      if (lfi.ambiguous)
1282169689Skan	print_candidates (lfi.ambiguous);
128318334Speter      rval = error_mark_node;
128418334Speter    }
128550397Sobrien
1286169689Skan  if (rval && is_overloaded_fn (rval))
1287117395Skan    rval = build_baselink (rval_binfo, basetype_path, rval,
1288117395Skan			   (IDENTIFIER_TYPENAME_P (name)
1289117395Skan			   ? TREE_TYPE (name): NULL_TREE));
129018334Speter  return rval;
129118334Speter}
129218334Speter
129352284Sobrien/* Like lookup_member, except that if we find a function member we
129452284Sobrien   return NULL_TREE.  */
129550397Sobrien
129618334Spetertree
1297132718Skanlookup_field (tree xbasetype, tree name, int protect, bool want_type)
129818334Speter{
129952284Sobrien  tree rval = lookup_member (xbasetype, name, protect, want_type);
1300169689Skan
1301169689Skan  /* Ignore functions, but propagate the ambiguity list.  */
1302169689Skan  if (!error_operand_p (rval)
1303169689Skan      && (rval && BASELINK_P (rval)))
130452284Sobrien    return NULL_TREE;
130518334Speter
130652284Sobrien  return rval;
130752284Sobrien}
130818334Speter
130952284Sobrien/* Like lookup_member, except that if we find a non-function member we
131052284Sobrien   return NULL_TREE.  */
131118334Speter
131252284Sobrientree
1313132718Skanlookup_fnfields (tree xbasetype, tree name, int protect)
131452284Sobrien{
1315132718Skan  tree rval = lookup_member (xbasetype, name, protect, /*want_type=*/false);
131618334Speter
1317169689Skan  /* Ignore non-functions, but propagate the ambiguity list.  */
1318169689Skan  if (!error_operand_p (rval)
1319169689Skan      && (rval && !BASELINK_P (rval)))
132052284Sobrien    return NULL_TREE;
132152284Sobrien
132252284Sobrien  return rval;
132318334Speter}
132418334Speter
1325117395Skan/* Return the index in the CLASSTYPE_METHOD_VEC for CLASS_TYPE
1326117395Skan   corresponding to "operator TYPE ()", or -1 if there is no such
1327117395Skan   operator.  Only CLASS_TYPE itself is searched; this routine does
1328117395Skan   not scan the base classes of CLASS_TYPE.  */
1329117395Skan
1330117395Skanstatic int
1331117395Skanlookup_conversion_operator (tree class_type, tree type)
1332117395Skan{
1333169689Skan  int tpl_slot = -1;
1334117395Skan
1335169689Skan  if (TYPE_HAS_CONVERSION (class_type))
1336169689Skan    {
1337169689Skan      int i;
1338169689Skan      tree fn;
1339169689Skan      VEC(tree,gc) *methods = CLASSTYPE_METHOD_VEC (class_type);
1340117395Skan
1341169689Skan      for (i = CLASSTYPE_FIRST_CONVERSION_SLOT;
1342169689Skan	   VEC_iterate (tree, methods, i, fn); ++i)
1343169689Skan	{
1344169689Skan	  /* All the conversion operators come near the beginning of
1345169689Skan	     the class.  Therefore, if FN is not a conversion
1346169689Skan	     operator, there is no matching conversion operator in
1347169689Skan	     CLASS_TYPE.  */
1348169689Skan	  fn = OVL_CURRENT (fn);
1349169689Skan	  if (!DECL_CONV_FN_P (fn))
1350169689Skan	    break;
1351117395Skan
1352169689Skan	  if (TREE_CODE (fn) == TEMPLATE_DECL)
1353169689Skan	    /* All the templated conversion functions are on the same
1354169689Skan	       slot, so remember it.  */
1355169689Skan	    tpl_slot = i;
1356169689Skan	  else if (same_type_p (DECL_CONV_FN_TYPE (fn), type))
1357169689Skan	    return i;
1358169689Skan	}
1359169689Skan    }
1360117395Skan
1361169689Skan  return tpl_slot;
1362117395Skan}
1363117395Skan
136418334Speter/* TYPE is a class type. Return the index of the fields within
136518334Speter   the method vector with name NAME, or -1 is no such field exists.  */
136650397Sobrien
136752284Sobrienint
1368117395Skanlookup_fnfields_1 (tree type, tree name)
136918334Speter{
1370169689Skan  VEC(tree,gc) *method_vec;
1371169689Skan  tree fn;
1372117395Skan  tree tmp;
1373169689Skan  size_t i;
137418334Speter
1375117395Skan  if (!CLASS_TYPE_P (type))
1376117395Skan    return -1;
137718334Speter
1378169689Skan  if (COMPLETE_TYPE_P (type))
1379169689Skan    {
1380169689Skan      if ((name == ctor_identifier
1381169689Skan	   || name == base_ctor_identifier
1382169689Skan	   || name == complete_ctor_identifier))
1383169689Skan	{
1384169689Skan	  if (CLASSTYPE_LAZY_DEFAULT_CTOR (type))
1385169689Skan	    lazily_declare_fn (sfk_constructor, type);
1386169689Skan	  if (CLASSTYPE_LAZY_COPY_CTOR (type))
1387169689Skan	    lazily_declare_fn (sfk_copy_constructor, type);
1388169689Skan	}
1389169689Skan      else if (name == ansi_assopname(NOP_EXPR)
1390169689Skan	       && CLASSTYPE_LAZY_ASSIGNMENT_OP (type))
1391169689Skan	lazily_declare_fn (sfk_assignment_operator, type);
1392169689Skan      else if ((name == dtor_identifier
1393169689Skan		|| name == base_dtor_identifier
1394169689Skan		|| name == complete_dtor_identifier
1395169689Skan		|| name == deleting_dtor_identifier)
1396169689Skan	       && CLASSTYPE_LAZY_DESTRUCTOR (type))
1397169689Skan	lazily_declare_fn (sfk_destructor, type);
1398169689Skan    }
1399169689Skan
1400117395Skan  method_vec = CLASSTYPE_METHOD_VEC (type);
1401117395Skan  if (!method_vec)
1402117395Skan    return -1;
1403117395Skan
140418334Speter#ifdef GATHER_STATISTICS
1405117395Skan  n_calls_lookup_fnfields_1++;
140650397Sobrien#endif /* GATHER_STATISTICS */
140750397Sobrien
1408117395Skan  /* Constructors are first...  */
1409117395Skan  if (name == ctor_identifier)
1410169689Skan    {
1411169689Skan      fn = CLASSTYPE_CONSTRUCTORS (type);
1412169689Skan      return fn ? CLASSTYPE_CONSTRUCTOR_SLOT : -1;
1413169689Skan    }
1414117395Skan  /* and destructors are second.  */
1415117395Skan  if (name == dtor_identifier)
1416169689Skan    {
1417169689Skan      fn = CLASSTYPE_DESTRUCTORS (type);
1418169689Skan      return fn ? CLASSTYPE_DESTRUCTOR_SLOT : -1;
1419169689Skan    }
1420117395Skan  if (IDENTIFIER_TYPENAME_P (name))
1421117395Skan    return lookup_conversion_operator (type, TREE_TYPE (name));
142250397Sobrien
1423117395Skan  /* Skip the conversion operators.  */
1424169689Skan  for (i = CLASSTYPE_FIRST_CONVERSION_SLOT;
1425169689Skan       VEC_iterate (tree, method_vec, i, fn);
1426169689Skan       ++i)
1427169689Skan    if (!DECL_CONV_FN_P (OVL_CURRENT (fn)))
1428169689Skan      break;
1429117395Skan
1430117395Skan  /* If the type is complete, use binary search.  */
1431117395Skan  if (COMPLETE_TYPE_P (type))
1432117395Skan    {
1433169689Skan      int lo;
1434169689Skan      int hi;
1435117395Skan
1436169689Skan      lo = i;
1437169689Skan      hi = VEC_length (tree, method_vec);
1438117395Skan      while (lo < hi)
143918334Speter	{
1440117395Skan	  i = (lo + hi) / 2;
1441117395Skan
144218334Speter#ifdef GATHER_STATISTICS
144318334Speter	  n_outer_fields_searched++;
144450397Sobrien#endif /* GATHER_STATISTICS */
144590075Sobrien
1446169689Skan	  tmp = VEC_index (tree, method_vec, i);
1447169689Skan	  tmp = DECL_NAME (OVL_CURRENT (tmp));
1448169689Skan	  if (tmp > name)
1449117395Skan	    hi = i;
1450117395Skan	  else if (tmp < name)
1451117395Skan	    lo = i + 1;
1452117395Skan	  else
145390075Sobrien	    return i;
1454117395Skan	}
1455117395Skan    }
1456117395Skan  else
1457169689Skan    for (; VEC_iterate (tree, method_vec, i, fn); ++i)
1458117395Skan      {
1459117395Skan#ifdef GATHER_STATISTICS
1460117395Skan	n_outer_fields_searched++;
1461117395Skan#endif /* GATHER_STATISTICS */
1462169689Skan	if (DECL_NAME (OVL_CURRENT (fn)) == name)
1463117395Skan	  return i;
1464117395Skan      }
146590075Sobrien
1466117395Skan  return -1;
1467117395Skan}
146890075Sobrien
1469169689Skan/* Like lookup_fnfields_1, except that the name is extracted from
1470169689Skan   FUNCTION, which is a FUNCTION_DECL or a TEMPLATE_DECL.  */
1471169689Skan
1472169689Skanint
1473169689Skanclass_method_index_for_fn (tree class_type, tree function)
1474169689Skan{
1475169689Skan  gcc_assert (TREE_CODE (function) == FUNCTION_DECL
1476169689Skan	      || DECL_FUNCTION_TEMPLATE_P (function));
1477169689Skan
1478169689Skan  return lookup_fnfields_1 (class_type,
1479169689Skan			    DECL_CONSTRUCTOR_P (function) ? ctor_identifier :
1480169689Skan			    DECL_DESTRUCTOR_P (function) ? dtor_identifier :
1481169689Skan			    DECL_NAME (function));
1482169689Skan}
1483169689Skan
1484169689Skan
1485132718Skan/* DECL is the result of a qualified name lookup.  QUALIFYING_SCOPE is
1486132718Skan   the class or namespace used to qualify the name.  CONTEXT_CLASS is
1487132718Skan   the class corresponding to the object in which DECL will be used.
1488132718Skan   Return a possibly modified version of DECL that takes into account
1489132718Skan   the CONTEXT_CLASS.
149090075Sobrien
1491117395Skan   In particular, consider an expression like `B::m' in the context of
1492117395Skan   a derived class `D'.  If `B::m' has been resolved to a BASELINK,
1493117395Skan   then the most derived class indicated by the BASELINK_BINFO will be
1494117395Skan   `B', not `D'.  This function makes that adjustment.  */
149590075Sobrien
1496117395Skantree
1497169689Skanadjust_result_of_qualified_name_lookup (tree decl,
1498132718Skan					tree qualifying_scope,
1499117395Skan					tree context_class)
1500117395Skan{
1501169689Skan  if (context_class && context_class != error_mark_node
1502169689Skan      && CLASS_TYPE_P (context_class)
1503169689Skan      && CLASS_TYPE_P (qualifying_scope)
1504132718Skan      && DERIVED_FROM_P (qualifying_scope, context_class)
1505132718Skan      && BASELINK_P (decl))
1506117395Skan    {
1507117395Skan      tree base;
1508117395Skan
1509132718Skan      /* Look for the QUALIFYING_SCOPE as a base of the CONTEXT_CLASS.
1510117395Skan	 Because we do not yet know which function will be chosen by
1511117395Skan	 overload resolution, we cannot yet check either accessibility
1512117395Skan	 or ambiguity -- in either case, the choice of a static member
1513117395Skan	 function might make the usage valid.  */
1514132718Skan      base = lookup_base (context_class, qualifying_scope,
1515169689Skan			  ba_unique | ba_quiet, NULL);
1516117395Skan      if (base)
151750397Sobrien	{
1518117395Skan	  BASELINK_ACCESS_BINFO (decl) = base;
1519169689Skan	  BASELINK_BINFO (decl)
1520117395Skan	    = lookup_base (base, BINFO_TYPE (BASELINK_BINFO (decl)),
1521169689Skan			   ba_unique | ba_quiet,
1522117395Skan			   NULL);
152350397Sobrien	}
152418334Speter    }
152518334Speter
1526117395Skan  return decl;
152718334Speter}
1528117395Skan
152952284Sobrien
1530169689Skan/* Walk the class hierarchy within BINFO, in a depth-first traversal.
1531169689Skan   PRE_FN is called in preorder, while POST_FN is called in postorder.
1532169689Skan   If PRE_FN returns DFS_SKIP_BASES, child binfos will not be
1533169689Skan   walked.  If PRE_FN or POST_FN returns a different non-NULL value,
1534169689Skan   that value is immediately returned and the walk is terminated.  One
1535169689Skan   of PRE_FN and POST_FN can be NULL.  At each node, PRE_FN and
1536169689Skan   POST_FN are passed the binfo to examine and the caller's DATA
1537169689Skan   value.  All paths are walked, thus virtual and morally virtual
1538169689Skan   binfos can be multiply walked.  */
153918334Speter
1540169689Skantree
1541169689Skandfs_walk_all (tree binfo, tree (*pre_fn) (tree, void *),
1542169689Skan	      tree (*post_fn) (tree, void *), void *data)
1543169689Skan{
1544169689Skan  tree rval;
1545169689Skan  unsigned ix;
1546169689Skan  tree base_binfo;
1547132718Skan
1548169689Skan  /* Call the pre-order walking function.  */
1549169689Skan  if (pre_fn)
1550169689Skan    {
1551169689Skan      rval = pre_fn (binfo, data);
1552169689Skan      if (rval)
1553169689Skan	{
1554169689Skan	  if (rval == dfs_skip_bases)
1555169689Skan	    goto skip_bases;
1556169689Skan	  return rval;
1557169689Skan	}
1558169689Skan    }
1559169689Skan
1560169689Skan  /* Find the next child binfo to walk.  */
1561169689Skan  for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
1562169689Skan    {
1563169689Skan      rval = dfs_walk_all (base_binfo, pre_fn, post_fn, data);
1564169689Skan      if (rval)
1565169689Skan	return rval;
1566169689Skan    }
1567169689Skan
1568169689Skan skip_bases:
1569169689Skan  /* Call the post-order walking function.  */
1570169689Skan  if (post_fn)
1571169689Skan    {
1572169689Skan      rval = post_fn (binfo, data);
1573169689Skan      gcc_assert (rval != dfs_skip_bases);
1574169689Skan      return rval;
1575169689Skan    }
1576169689Skan
1577169689Skan  return NULL_TREE;
1578169689Skan}
1579169689Skan
1580169689Skan/* Worker for dfs_walk_once.  This behaves as dfs_walk_all, except
1581169689Skan   that binfos are walked at most once.  */
1582169689Skan
158352284Sobrienstatic tree
1584169689Skandfs_walk_once_r (tree binfo, tree (*pre_fn) (tree, void *),
1585169689Skan		 tree (*post_fn) (tree, void *), void *data)
158618334Speter{
1587169689Skan  tree rval;
1588169689Skan  unsigned ix;
1589169689Skan  tree base_binfo;
159018334Speter
1591169689Skan  /* Call the pre-order walking function.  */
1592169689Skan  if (pre_fn)
1593169689Skan    {
1594169689Skan      rval = pre_fn (binfo, data);
1595169689Skan      if (rval)
1596169689Skan	{
1597169689Skan	  if (rval == dfs_skip_bases)
1598169689Skan	    goto skip_bases;
159918334Speter
1600169689Skan	  return rval;
1601169689Skan	}
1602169689Skan    }
160318334Speter
1604169689Skan  /* Find the next child binfo to walk.  */
1605169689Skan  for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
160652284Sobrien    {
1607169689Skan      if (BINFO_VIRTUAL_P (base_binfo))
1608169689Skan	{
1609169689Skan	  if (BINFO_MARKED (base_binfo))
1610169689Skan	    continue;
1611169689Skan	  BINFO_MARKED (base_binfo) = 1;
1612169689Skan	}
161318334Speter
1614169689Skan      rval = dfs_walk_once_r (base_binfo, pre_fn, post_fn, data);
161552284Sobrien      if (rval)
1616169689Skan	return rval;
1617169689Skan    }
161818334Speter
1619169689Skan skip_bases:
1620169689Skan  /* Call the post-order walking function.  */
1621169689Skan  if (post_fn)
1622169689Skan    {
1623169689Skan      rval = post_fn (binfo, data);
1624169689Skan      gcc_assert (rval != dfs_skip_bases);
1625169689Skan      return rval;
1626169689Skan    }
1627169689Skan
1628169689Skan  return NULL_TREE;
1629169689Skan}
1630169689Skan
1631169689Skan/* Worker for dfs_walk_once. Recursively unmark the virtual base binfos of
1632169689Skan   BINFO.  */
1633169689Skan
1634169689Skanstatic void
1635169689Skandfs_unmark_r (tree binfo)
1636169689Skan{
1637169689Skan  unsigned ix;
1638169689Skan  tree base_binfo;
1639169689Skan
1640169689Skan  /* Process the basetypes.  */
1641169689Skan  for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
1642169689Skan    {
1643169689Skan      if (BINFO_VIRTUAL_P (base_binfo))
164452284Sobrien	{
1645169689Skan	  if (!BINFO_MARKED (base_binfo))
1646169689Skan	    continue;
1647169689Skan	  BINFO_MARKED (base_binfo) = 0;
1648169689Skan	}
1649169689Skan      /* Only walk, if it can contain more virtual bases.  */
1650169689Skan      if (CLASSTYPE_VBASECLASSES (BINFO_TYPE (base_binfo)))
1651169689Skan	dfs_unmark_r (base_binfo);
1652169689Skan    }
1653169689Skan}
1654169689Skan
1655169689Skan/* Like dfs_walk_all, except that binfos are not multiply walked.  For
1656169689Skan   non-diamond shaped hierarchies this is the same as dfs_walk_all.
1657169689Skan   For diamond shaped hierarchies we must mark the virtual bases, to
1658169689Skan   avoid multiple walks.  */
1659169689Skan
1660169689Skantree
1661169689Skandfs_walk_once (tree binfo, tree (*pre_fn) (tree, void *),
1662169689Skan	       tree (*post_fn) (tree, void *), void *data)
1663169689Skan{
1664169689Skan  static int active = 0;  /* We must not be called recursively. */
1665169689Skan  tree rval;
1666169689Skan
1667169689Skan  gcc_assert (pre_fn || post_fn);
1668169689Skan  gcc_assert (!active);
1669169689Skan  active++;
1670169689Skan
1671169689Skan  if (!CLASSTYPE_DIAMOND_SHAPED_P (BINFO_TYPE (binfo)))
1672169689Skan    /* We are not diamond shaped, and therefore cannot encounter the
1673169689Skan       same binfo twice.  */
1674169689Skan    rval = dfs_walk_all (binfo, pre_fn, post_fn, data);
1675169689Skan  else
1676169689Skan    {
1677169689Skan      rval = dfs_walk_once_r (binfo, pre_fn, post_fn, data);
1678169689Skan      if (!BINFO_INHERITANCE_CHAIN (binfo))
1679169689Skan	{
1680169689Skan	  /* We are at the top of the hierarchy, and can use the
1681169689Skan	     CLASSTYPE_VBASECLASSES list for unmarking the virtual
1682169689Skan	     bases.  */
1683169689Skan	  VEC(tree,gc) *vbases;
1684169689Skan	  unsigned ix;
1685132718Skan	  tree base_binfo;
1686169689Skan
1687169689Skan	  for (vbases = CLASSTYPE_VBASECLASSES (BINFO_TYPE (binfo)), ix = 0;
1688169689Skan	       VEC_iterate (tree, vbases, ix, base_binfo); ix++)
1689169689Skan	    BINFO_MARKED (base_binfo) = 0;
169018334Speter	}
1691169689Skan      else
1692169689Skan	dfs_unmark_r (binfo);
169318334Speter    }
169418334Speter
1695169689Skan  active--;
1696169689Skan
169752284Sobrien  return rval;
169852284Sobrien}
169918334Speter
1700169689Skan/* Worker function for dfs_walk_once_accessible.  Behaves like
1701169689Skan   dfs_walk_once_r, except (a) FRIENDS_P is true if special
1702169689Skan   access given by the current context should be considered, (b) ONCE
1703169689Skan   indicates whether bases should be marked during traversal.  */
170418334Speter
1705169689Skanstatic tree
1706169689Skandfs_walk_once_accessible_r (tree binfo, bool friends_p, bool once,
1707169689Skan			    tree (*pre_fn) (tree, void *),
1708169689Skan			    tree (*post_fn) (tree, void *), void *data)
170952284Sobrien{
171052284Sobrien  tree rval = NULL_TREE;
1711169689Skan  unsigned ix;
1712169689Skan  tree base_binfo;
171318334Speter
171452284Sobrien  /* Call the pre-order walking function.  */
1715169689Skan  if (pre_fn)
171650397Sobrien    {
1717169689Skan      rval = pre_fn (binfo, data);
171852284Sobrien      if (rval)
1719169689Skan	{
1720169689Skan	  if (rval == dfs_skip_bases)
1721169689Skan	    goto skip_bases;
1722169689Skan
1723169689Skan	  return rval;
1724169689Skan	}
172550397Sobrien    }
172650397Sobrien
1727169689Skan  /* Find the next child binfo to walk.  */
1728169689Skan  for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
172918334Speter    {
1730169689Skan      bool mark = once && BINFO_VIRTUAL_P (base_binfo);
1731169689Skan
1732169689Skan      if (mark && BINFO_MARKED (base_binfo))
1733169689Skan	continue;
1734169689Skan
1735169689Skan      /* If the base is inherited via private or protected
1736169689Skan	 inheritance, then we can't see it, unless we are a friend of
1737169689Skan	 the current binfo.  */
1738169689Skan      if (BINFO_BASE_ACCESS (binfo, ix) != access_public_node)
1739132718Skan	{
1740169689Skan	  tree scope;
1741169689Skan	  if (!friends_p)
1742169689Skan	    continue;
1743169689Skan	  scope = current_scope ();
1744169689Skan	  if (!scope
1745169689Skan	      || TREE_CODE (scope) == NAMESPACE_DECL
1746169689Skan	      || !is_friend (BINFO_TYPE (binfo), scope))
1747169689Skan	    continue;
174818334Speter	}
1749169689Skan
1750169689Skan      if (mark)
1751169689Skan	BINFO_MARKED (base_binfo) = 1;
1752169689Skan
1753169689Skan      rval = dfs_walk_once_accessible_r (base_binfo, friends_p, once,
1754169689Skan					 pre_fn, post_fn, data);
1755169689Skan      if (rval)
1756169689Skan	return rval;
175718334Speter    }
175818334Speter
1759169689Skan skip_bases:
176052284Sobrien  /* Call the post-order walking function.  */
1761169689Skan  if (post_fn)
1762169689Skan    {
1763169689Skan      rval = post_fn (binfo, data);
1764169689Skan      gcc_assert (rval != dfs_skip_bases);
1765169689Skan      return rval;
1766169689Skan    }
1767169689Skan
1768169689Skan  return NULL_TREE;
176918334Speter}
177050397Sobrien
1771169689Skan/* Like dfs_walk_once except that only accessible bases are walked.
1772169689Skan   FRIENDS_P indicates whether friendship of the local context
1773169689Skan   should be considered when determining accessibility.  */
177450397Sobrien
1775169689Skanstatic tree
1776169689Skandfs_walk_once_accessible (tree binfo, bool friends_p,
1777169689Skan			    tree (*pre_fn) (tree, void *),
1778169689Skan			    tree (*post_fn) (tree, void *), void *data)
177950397Sobrien{
1780169689Skan  bool diamond_shaped = CLASSTYPE_DIAMOND_SHAPED_P (BINFO_TYPE (binfo));
1781169689Skan  tree rval = dfs_walk_once_accessible_r (binfo, friends_p, diamond_shaped,
1782169689Skan					  pre_fn, post_fn, data);
1783169689Skan
1784169689Skan  if (diamond_shaped)
1785169689Skan    {
1786169689Skan      if (!BINFO_INHERITANCE_CHAIN (binfo))
1787169689Skan	{
1788169689Skan	  /* We are at the top of the hierarchy, and can use the
1789169689Skan	     CLASSTYPE_VBASECLASSES list for unmarking the virtual
1790169689Skan	     bases.  */
1791169689Skan	  VEC(tree,gc) *vbases;
1792169689Skan	  unsigned ix;
1793169689Skan	  tree base_binfo;
1794169689Skan
1795169689Skan	  for (vbases = CLASSTYPE_VBASECLASSES (BINFO_TYPE (binfo)), ix = 0;
1796169689Skan	       VEC_iterate (tree, vbases, ix, base_binfo); ix++)
1797169689Skan	    BINFO_MARKED (base_binfo) = 0;
1798169689Skan	}
1799169689Skan      else
1800169689Skan	dfs_unmark_r (binfo);
1801169689Skan    }
1802169689Skan  return rval;
180350397Sobrien}
180418334Speter
180590075Sobrien/* Check that virtual overrider OVERRIDER is acceptable for base function
180690075Sobrien   BASEFN. Issue diagnostic, and return zero, if unacceptable.  */
180790075Sobrien
1808169689Skanstatic int
1809132718Skancheck_final_overrider (tree overrider, tree basefn)
181090075Sobrien{
181190075Sobrien  tree over_type = TREE_TYPE (overrider);
181290075Sobrien  tree base_type = TREE_TYPE (basefn);
181390075Sobrien  tree over_return = TREE_TYPE (over_type);
181490075Sobrien  tree base_return = TREE_TYPE (base_type);
181590075Sobrien  tree over_throw = TYPE_RAISES_EXCEPTIONS (over_type);
181690075Sobrien  tree base_throw = TYPE_RAISES_EXCEPTIONS (base_type);
1817132718Skan  int fail = 0;
1818169689Skan
1819169689Skan  if (DECL_INVALID_OVERRIDER_P (overrider))
1820169689Skan    return 0;
1821169689Skan
182290075Sobrien  if (same_type_p (base_return, over_return))
182390075Sobrien    /* OK */;
1824132718Skan  else if ((CLASS_TYPE_P (over_return) && CLASS_TYPE_P (base_return))
1825132718Skan	   || (TREE_CODE (base_return) == TREE_CODE (over_return)
1826132718Skan	       && POINTER_TYPE_P (base_return)))
182790075Sobrien    {
1828132718Skan      /* Potentially covariant.  */
1829132718Skan      unsigned base_quals, over_quals;
1830169689Skan
1831132718Skan      fail = !POINTER_TYPE_P (base_return);
1832132718Skan      if (!fail)
1833132718Skan	{
1834132718Skan	  fail = cp_type_quals (base_return) != cp_type_quals (over_return);
1835169689Skan
1836132718Skan	  base_return = TREE_TYPE (base_return);
1837132718Skan	  over_return = TREE_TYPE (over_return);
1838132718Skan	}
1839132718Skan      base_quals = cp_type_quals (base_return);
1840132718Skan      over_quals = cp_type_quals (over_return);
184190075Sobrien
1842132718Skan      if ((base_quals & over_quals) != over_quals)
1843132718Skan	fail = 1;
1844169689Skan
1845132718Skan      if (CLASS_TYPE_P (base_return) && CLASS_TYPE_P (over_return))
184690075Sobrien	{
1847132718Skan	  tree binfo = lookup_base (over_return, base_return,
1848132718Skan				    ba_check | ba_quiet, NULL);
1849132718Skan
1850132718Skan	  if (!binfo)
1851132718Skan	    fail = 1;
185290075Sobrien	}
1853132718Skan      else if (!pedantic
1854132718Skan	       && can_convert (TREE_TYPE (base_type), TREE_TYPE (over_type)))
1855132718Skan	/* GNU extension, allow trivial pointer conversions such as
1856132718Skan	   converting to void *, or qualification conversion.  */
1857132718Skan	{
1858132718Skan	  /* can_convert will permit user defined conversion from a
1859132718Skan	     (reference to) class type. We must reject them.  */
1860132718Skan	  over_return = non_reference (TREE_TYPE (over_type));
1861132718Skan	  if (CLASS_TYPE_P (over_return))
1862132718Skan	    fail = 2;
1863169689Skan	  else
1864169689Skan	    {
1865169689Skan	      warning (0, "deprecated covariant return type for %q+#D",
1866169689Skan			     overrider);
1867169689Skan	      warning (0, "  overriding %q+#D", basefn);
1868169689Skan	    }
1869132718Skan	}
1870132718Skan      else
1871132718Skan	fail = 2;
187290075Sobrien    }
1873132718Skan  else
1874132718Skan    fail = 2;
1875132718Skan  if (!fail)
1876132718Skan    /* OK */;
1877132718Skan  else
187890075Sobrien    {
1879132718Skan      if (fail == 1)
1880132718Skan	{
1881169689Skan	  error ("invalid covariant return type for %q+#D", overrider);
1882169689Skan	  error ("  overriding %q+#D", basefn);
1883132718Skan	}
1884132718Skan      else
1885132718Skan	{
1886169689Skan	  error ("conflicting return type specified for %q+#D", overrider);
1887169689Skan	  error ("  overriding %q+#D", basefn);
1888132718Skan	}
1889169689Skan      DECL_INVALID_OVERRIDER_P (overrider) = 1;
189090075Sobrien      return 0;
189190075Sobrien    }
1892169689Skan
189396263Sobrien  /* Check throw specifier is at least as strict.  */
189490075Sobrien  if (!comp_except_specs (base_throw, over_throw, 0))
189590075Sobrien    {
1896169689Skan      error ("looser throw specifier for %q+#F", overrider);
1897169689Skan      error ("  overriding %q+#F", basefn);
1898169689Skan      DECL_INVALID_OVERRIDER_P (overrider) = 1;
189990075Sobrien      return 0;
190090075Sobrien    }
1901169689Skan
190250397Sobrien  return 1;
190350397Sobrien}
190450397Sobrien
190590075Sobrien/* Given a class TYPE, and a function decl FNDECL, look for
190690075Sobrien   virtual functions in TYPE's hierarchy which FNDECL overrides.
190790075Sobrien   We do not look in TYPE itself, only its bases.
1908169689Skan
1909117395Skan   Returns nonzero, if we find any. Set FNDECL's DECL_VIRTUAL_P, if we
191090075Sobrien   find that it overrides anything.
1911169689Skan
191290075Sobrien   We check that every function which is overridden, is correctly
191390075Sobrien   overridden.  */
191418334Speter
191590075Sobrienint
1916132718Skanlook_for_overrides (tree type, tree fndecl)
191790075Sobrien{
191890075Sobrien  tree binfo = TYPE_BINFO (type);
1919169689Skan  tree base_binfo;
192090075Sobrien  int ix;
192190075Sobrien  int found = 0;
192250397Sobrien
1923169689Skan  for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
192490075Sobrien    {
1925169689Skan      tree basetype = BINFO_TYPE (base_binfo);
1926169689Skan
192790075Sobrien      if (TYPE_POLYMORPHIC_P (basetype))
1928169689Skan	found += look_for_overrides_r (basetype, fndecl);
192990075Sobrien    }
193090075Sobrien  return found;
193190075Sobrien}
193290075Sobrien
1933117395Skan/* Look in TYPE for virtual functions with the same signature as
1934117395Skan   FNDECL.  */
193590075Sobrien
193618334Spetertree
1937132718Skanlook_for_overrides_here (tree type, tree fndecl)
193818334Speter{
193990075Sobrien  int ix;
194018334Speter
1941169689Skan  /* If there are no methods in TYPE (meaning that only implicitly
1942169689Skan     declared methods will ever be provided for TYPE), then there are
1943169689Skan     no virtual functions.  */
1944169689Skan  if (!CLASSTYPE_METHOD_VEC (type))
1945169689Skan    return NULL_TREE;
1946169689Skan
194790075Sobrien  if (DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (fndecl))
194890075Sobrien    ix = CLASSTYPE_DESTRUCTOR_SLOT;
194918334Speter  else
195090075Sobrien    ix = lookup_fnfields_1 (type, DECL_NAME (fndecl));
195190075Sobrien  if (ix >= 0)
195218334Speter    {
1953169689Skan      tree fns = VEC_index (tree, CLASSTYPE_METHOD_VEC (type), ix);
1954169689Skan
195590075Sobrien      for (; fns; fns = OVL_NEXT (fns))
1956169689Skan	{
1957169689Skan	  tree fn = OVL_CURRENT (fns);
195818334Speter
1959169689Skan	  if (!DECL_VIRTUAL_P (fn))
1960169689Skan	    /* Not a virtual.  */;
1961169689Skan	  else if (DECL_CONTEXT (fn) != type)
1962169689Skan	    /* Introduced with a using declaration.  */;
196390075Sobrien	  else if (DECL_STATIC_FUNCTION_P (fndecl))
196490075Sobrien	    {
196590075Sobrien	      tree btypes = TYPE_ARG_TYPES (TREE_TYPE (fn));
196690075Sobrien	      tree dtypes = TYPE_ARG_TYPES (TREE_TYPE (fndecl));
1967169689Skan	      if (compparms (TREE_CHAIN (btypes), dtypes))
196890075Sobrien		return fn;
1969169689Skan	    }
1970169689Skan	  else if (same_signature_p (fndecl, fn))
197190075Sobrien	    return fn;
197290075Sobrien	}
197390075Sobrien    }
197490075Sobrien  return NULL_TREE;
197590075Sobrien}
197618334Speter
197790075Sobrien/* Look in TYPE for virtual functions overridden by FNDECL. Check both
1978117395Skan   TYPE itself and its bases.  */
197990075Sobrien
198090075Sobrienstatic int
1981132718Skanlook_for_overrides_r (tree type, tree fndecl)
198290075Sobrien{
198390075Sobrien  tree fn = look_for_overrides_here (type, fndecl);
198490075Sobrien  if (fn)
198590075Sobrien    {
198618334Speter      if (DECL_STATIC_FUNCTION_P (fndecl))
198790075Sobrien	{
198890075Sobrien	  /* A static member function cannot match an inherited
198990075Sobrien	     virtual member function.  */
1990169689Skan	  error ("%q+#D cannot be declared", fndecl);
1991169689Skan	  error ("  since %q+#D declared in base class", fn);
199290075Sobrien	}
199318334Speter      else
199418334Speter	{
199590075Sobrien	  /* It's definitely virtual, even if not explicitly set.  */
199690075Sobrien	  DECL_VIRTUAL_P (fndecl) = 1;
199790075Sobrien	  check_final_overrider (fndecl, fn);
199890075Sobrien	}
199990075Sobrien      return 1;
200090075Sobrien    }
200118334Speter
200290075Sobrien  /* We failed to find one declared in this class. Look in its bases.  */
200390075Sobrien  return look_for_overrides (type, fndecl);
200490075Sobrien}
200518334Speter
200690075Sobrien/* Called via dfs_walk from dfs_get_pure_virtuals.  */
200790075Sobrien
200852284Sobrienstatic tree
2009132718Skandfs_get_pure_virtuals (tree binfo, void *data)
201018334Speter{
201190075Sobrien  tree type = (tree) data;
201290075Sobrien
201390075Sobrien  /* We're not interested in primary base classes; the derived class
201490075Sobrien     of which they are a primary base will contain the information we
201590075Sobrien     need.  */
201690075Sobrien  if (!BINFO_PRIMARY_P (binfo))
201718334Speter    {
201890075Sobrien      tree virtuals;
2019169689Skan
202090075Sobrien      for (virtuals = BINFO_VIRTUALS (binfo);
202190075Sobrien	   virtuals;
202290075Sobrien	   virtuals = TREE_CHAIN (virtuals))
202390075Sobrien	if (DECL_PURE_VIRTUAL_P (BV_FN (virtuals)))
2024169689Skan	  VEC_safe_push (tree, gc, CLASSTYPE_PURE_VIRTUALS (type),
2025169689Skan			 BV_FN (virtuals));
202618334Speter    }
202790075Sobrien
202890075Sobrien  return NULL_TREE;
202918334Speter}
203018334Speter
203190075Sobrien/* Set CLASSTYPE_PURE_VIRTUALS for TYPE.  */
203250397Sobrien
203390075Sobrienvoid
2034132718Skanget_pure_virtuals (tree type)
203518334Speter{
203690075Sobrien  /* Clear the CLASSTYPE_PURE_VIRTUALS list; whatever is already there
203790075Sobrien     is going to be overridden.  */
2038169689Skan  CLASSTYPE_PURE_VIRTUALS (type) = NULL;
203990075Sobrien  /* Now, run through all the bases which are not primary bases, and
204090075Sobrien     collect the pure virtual functions.  We look at the vtable in
204190075Sobrien     each class to determine what pure virtual functions are present.
204290075Sobrien     (A primary base is not interesting because the derived class of
204390075Sobrien     which it is a primary base will contain vtable entries for the
204490075Sobrien     pure virtuals in the base class.  */
2045169689Skan  dfs_walk_once (TYPE_BINFO (type), NULL, dfs_get_pure_virtuals, type);
204652284Sobrien}
204790075Sobrien
204890075Sobrien/* Debug info for C++ classes can get very large; try to avoid
204990075Sobrien   emitting it everywhere.
205018334Speter
205190075Sobrien   Note that this optimization wins even when the target supports
205290075Sobrien   BINCL (if only slightly), and reduces the amount of work for the
205390075Sobrien   linker.  */
205418334Speter
205590075Sobrienvoid
2056132718Skanmaybe_suppress_debug_info (tree t)
205718334Speter{
2058169689Skan  if (write_symbols == NO_DEBUG)
205918334Speter    return;
206018334Speter
206190075Sobrien  /* We might have set this earlier in cp_finish_decl.  */
206290075Sobrien  TYPE_DECL_SUPPRESS_DEBUG (TYPE_MAIN_DECL (t)) = 0;
206360967Sobrien
2064169689Skan  /* Always emit the information for each class every time. */
2065169689Skan  if (flag_emit_class_debug_always)
2066169689Skan    return;
2067169689Skan
206890075Sobrien  /* If we already know how we're handling this class, handle debug info
206990075Sobrien     the same way.  */
207090075Sobrien  if (CLASSTYPE_INTERFACE_KNOWN (t))
207160967Sobrien    {
207290075Sobrien      if (CLASSTYPE_INTERFACE_ONLY (t))
207390075Sobrien	TYPE_DECL_SUPPRESS_DEBUG (TYPE_MAIN_DECL (t)) = 1;
207490075Sobrien      /* else don't set it.  */
207560967Sobrien    }
207690075Sobrien  /* If the class has a vtable, write out the debug info along with
207790075Sobrien     the vtable.  */
207890075Sobrien  else if (TYPE_CONTAINS_VPTR_P (t))
207990075Sobrien    TYPE_DECL_SUPPRESS_DEBUG (TYPE_MAIN_DECL (t)) = 1;
208060967Sobrien
208190075Sobrien  /* Otherwise, just emit the debug info normally.  */
208260967Sobrien}
208360967Sobrien
208490075Sobrien/* Note that we want debugging information for a base class of a class
208590075Sobrien   whose vtable is being emitted.  Normally, this would happen because
208690075Sobrien   calling the constructor for a derived class implies calling the
208790075Sobrien   constructors for all bases, which involve initializing the
208890075Sobrien   appropriate vptr with the vtable for the base class; but in the
208990075Sobrien   presence of optimization, this initialization may be optimized
209090075Sobrien   away, so we tell finish_vtable_vardecl that we want the debugging
209190075Sobrien   information anyway.  */
209260967Sobrien
209390075Sobrienstatic tree
2094132718Skandfs_debug_mark (tree binfo, void *data ATTRIBUTE_UNUSED)
209560967Sobrien{
209690075Sobrien  tree t = BINFO_TYPE (binfo);
209760967Sobrien
2098169689Skan  if (CLASSTYPE_DEBUG_REQUESTED (t))
2099169689Skan    return dfs_skip_bases;
2100169689Skan
210190075Sobrien  CLASSTYPE_DEBUG_REQUESTED (t) = 1;
210260967Sobrien
210390075Sobrien  return NULL_TREE;
210460967Sobrien}
210560967Sobrien
210690075Sobrien/* Write out the debugging information for TYPE, whose vtable is being
210790075Sobrien   emitted.  Also walk through our bases and note that we want to
210890075Sobrien   write out information for them.  This avoids the problem of not
210990075Sobrien   writing any debug info for intermediate basetypes whose
211090075Sobrien   constructors, and thus the references to their vtables, and thus
211190075Sobrien   the vtables themselves, were optimized away.  */
211218334Speter
211318334Spetervoid
2114132718Skannote_debug_info_needed (tree type)
211518334Speter{
211690075Sobrien  if (TYPE_DECL_SUPPRESS_DEBUG (TYPE_NAME (type)))
211790075Sobrien    {
211890075Sobrien      TYPE_DECL_SUPPRESS_DEBUG (TYPE_NAME (type)) = 0;
211990075Sobrien      rest_of_type_compilation (type, toplevel_bindings_p ());
212090075Sobrien    }
212150397Sobrien
2122169689Skan  dfs_walk_all (TYPE_BINFO (type), dfs_debug_mark, NULL, 0);
212318334Speter}
212418334Speter
212518334Spetervoid
2126132718Skanprint_search_statistics (void)
212718334Speter{
212818334Speter#ifdef GATHER_STATISTICS
212918334Speter  fprintf (stderr, "%d fields searched in %d[%d] calls to lookup_field[_1]\n",
213018334Speter	   n_fields_searched, n_calls_lookup_field, n_calls_lookup_field_1);
213118334Speter  fprintf (stderr, "%d fnfields searched in %d calls to lookup_fnfields\n",
213218334Speter	   n_outer_fields_searched, n_calls_lookup_fnfields);
213318334Speter  fprintf (stderr, "%d calls to get_base_type\n", n_calls_get_base_type);
213450397Sobrien#else /* GATHER_STATISTICS */
213518334Speter  fprintf (stderr, "no search statistics\n");
213650397Sobrien#endif /* GATHER_STATISTICS */
213718334Speter}
213818334Speter
213918334Spetervoid
2140132718Skanreinit_search_statistics (void)
214118334Speter{
214250397Sobrien#ifdef GATHER_STATISTICS
214318334Speter  n_fields_searched = 0;
214418334Speter  n_calls_lookup_field = 0, n_calls_lookup_field_1 = 0;
214518334Speter  n_calls_lookup_fnfields = 0, n_calls_lookup_fnfields_1 = 0;
214618334Speter  n_calls_get_base_type = 0;
214718334Speter  n_outer_fields_searched = 0;
214818334Speter  n_contexts_saved = 0;
214950397Sobrien#endif /* GATHER_STATISTICS */
215018334Speter}
215118334Speter
2152169689Skan/* Helper for lookup_conversions_r.  TO_TYPE is the type converted to
2153169689Skan   by a conversion op in base BINFO.  VIRTUAL_DEPTH is nonzero if
2154169689Skan   BINFO is morally virtual, and VIRTUALNESS is nonzero if virtual
2155169689Skan   bases have been encountered already in the tree walk.  PARENT_CONVS
2156169689Skan   is the list of lists of conversion functions that could hide CONV
2157169689Skan   and OTHER_CONVS is the list of lists of conversion functions that
2158169689Skan   could hide or be hidden by CONV, should virtualness be involved in
2159169689Skan   the hierarchy.  Merely checking the conversion op's name is not
2160169689Skan   enough because two conversion operators to the same type can have
2161169689Skan   different names.  Return nonzero if we are visible.  */
2162169689Skan
2163169689Skanstatic int
2164169689Skancheck_hidden_convs (tree binfo, int virtual_depth, int virtualness,
2165169689Skan		    tree to_type, tree parent_convs, tree other_convs)
216618334Speter{
2167169689Skan  tree level, probe;
216850397Sobrien
2169169689Skan  /* See if we are hidden by a parent conversion.  */
2170169689Skan  for (level = parent_convs; level; level = TREE_CHAIN (level))
2171169689Skan    for (probe = TREE_VALUE (level); probe; probe = TREE_CHAIN (probe))
2172169689Skan      if (same_type_p (to_type, TREE_TYPE (probe)))
2173169689Skan	return 0;
217490075Sobrien
2175169689Skan  if (virtual_depth || virtualness)
217650397Sobrien    {
2177169689Skan     /* In a virtual hierarchy, we could be hidden, or could hide a
2178169689Skan	conversion function on the other_convs list.  */
2179169689Skan      for (level = other_convs; level; level = TREE_CHAIN (level))
2180169689Skan	{
2181169689Skan	  int we_hide_them;
2182169689Skan	  int they_hide_us;
2183169689Skan	  tree *prev, other;
218452284Sobrien
2185169689Skan	  if (!(virtual_depth || TREE_STATIC (level)))
2186169689Skan	    /* Neither is morally virtual, so cannot hide each other.  */
2187169689Skan	    continue;
218852284Sobrien
2189169689Skan	  if (!TREE_VALUE (level))
2190169689Skan	    /* They evaporated away already.  */
2191169689Skan	    continue;
219252284Sobrien
2193169689Skan	  they_hide_us = (virtual_depth
2194169689Skan			  && original_binfo (binfo, TREE_PURPOSE (level)));
2195169689Skan	  we_hide_them = (!they_hide_us && TREE_STATIC (level)
2196169689Skan			  && original_binfo (TREE_PURPOSE (level), binfo));
2197122180Skan
2198169689Skan	  if (!(we_hide_them || they_hide_us))
2199169689Skan	    /* Neither is within the other, so no hiding can occur.  */
2200169689Skan	    continue;
2201169689Skan
2202169689Skan	  for (prev = &TREE_VALUE (level), other = *prev; other;)
2203122180Skan	    {
2204169689Skan	      if (same_type_p (to_type, TREE_TYPE (other)))
2205169689Skan		{
2206169689Skan		  if (they_hide_us)
2207169689Skan		    /* We are hidden.  */
2208169689Skan		    return 0;
2209169689Skan
2210169689Skan		  if (we_hide_them)
2211169689Skan		    {
2212169689Skan		      /* We hide the other one.  */
2213169689Skan		      other = TREE_CHAIN (other);
2214169689Skan		      *prev = other;
2215169689Skan		      continue;
2216169689Skan		    }
2217169689Skan		}
2218169689Skan	      prev = &TREE_CHAIN (other);
2219169689Skan	      other = *prev;
2220122180Skan	    }
222152284Sobrien	}
222250397Sobrien    }
2223169689Skan  return 1;
222418334Speter}
222518334Speter
2226169689Skan/* Helper for lookup_conversions_r.  PARENT_CONVS is a list of lists
2227169689Skan   of conversion functions, the first slot will be for the current
2228169689Skan   binfo, if MY_CONVS is non-NULL.  CHILD_CONVS is the list of lists
2229169689Skan   of conversion functions from children of the current binfo,
2230169689Skan   concatenated with conversions from elsewhere in the hierarchy --
2231169689Skan   that list begins with OTHER_CONVS.  Return a single list of lists
2232169689Skan   containing only conversions from the current binfo and its
2233169689Skan   children.  */
223490075Sobrien
2235169689Skanstatic tree
2236169689Skansplit_conversions (tree my_convs, tree parent_convs,
2237169689Skan		   tree child_convs, tree other_convs)
223818334Speter{
223952284Sobrien  tree t;
2240169689Skan  tree prev;
224152284Sobrien
2242169689Skan  /* Remove the original other_convs portion from child_convs.  */
2243169689Skan  for (prev = NULL, t = child_convs;
2244169689Skan       t != other_convs; prev = t, t = TREE_CHAIN (t))
2245169689Skan    continue;
224650397Sobrien
2247169689Skan  if (prev)
2248169689Skan    TREE_CHAIN (prev) = NULL_TREE;
2249169689Skan  else
2250169689Skan    child_convs = NULL_TREE;
225150397Sobrien
2252169689Skan  /* Attach the child convs to any we had at this level.  */
2253169689Skan  if (my_convs)
2254169689Skan    {
2255169689Skan      my_convs = parent_convs;
2256169689Skan      TREE_CHAIN (my_convs) = child_convs;
2257169689Skan    }
2258169689Skan  else
2259169689Skan    my_convs = child_convs;
2260169689Skan
2261169689Skan  return my_convs;
226250397Sobrien}
226350397Sobrien
2264169689Skan/* Worker for lookup_conversions.  Lookup conversion functions in
2265169689Skan   BINFO and its children.  VIRTUAL_DEPTH is nonzero, if BINFO is in
2266169689Skan   a morally virtual base, and VIRTUALNESS is nonzero, if we've
2267169689Skan   encountered virtual bases already in the tree walk.  PARENT_CONVS &
2268169689Skan   PARENT_TPL_CONVS are lists of list of conversions within parent
2269169689Skan   binfos.  OTHER_CONVS and OTHER_TPL_CONVS are conversions found
2270169689Skan   elsewhere in the tree.  Return the conversions found within this
2271169689Skan   portion of the graph in CONVS and TPL_CONVS.  Return nonzero is we
2272169689Skan   encountered virtualness.  We keep template and non-template
2273169689Skan   conversions separate, to avoid unnecessary type comparisons.
227450397Sobrien
2275169689Skan   The located conversion functions are held in lists of lists.  The
2276169689Skan   TREE_VALUE of the outer list is the list of conversion functions
2277169689Skan   found in a particular binfo.  The TREE_PURPOSE of both the outer
2278169689Skan   and inner lists is the binfo at which those conversions were
2279169689Skan   found.  TREE_STATIC is set for those lists within of morally
2280169689Skan   virtual binfos.  The TREE_VALUE of the inner list is the conversion
2281169689Skan   function or overload itself.  The TREE_TYPE of each inner list node
2282169689Skan   is the converted-to type.  */
228350397Sobrien
2284169689Skanstatic int
2285169689Skanlookup_conversions_r (tree binfo,
2286169689Skan		      int virtual_depth, int virtualness,
2287169689Skan		      tree parent_convs, tree parent_tpl_convs,
2288169689Skan		      tree other_convs, tree other_tpl_convs,
2289169689Skan		      tree *convs, tree *tpl_convs)
229050397Sobrien{
2291169689Skan  int my_virtualness = 0;
2292169689Skan  tree my_convs = NULL_TREE;
2293169689Skan  tree my_tpl_convs = NULL_TREE;
2294169689Skan  tree child_convs = NULL_TREE;
2295169689Skan  tree child_tpl_convs = NULL_TREE;
2296169689Skan  unsigned i;
2297169689Skan  tree base_binfo;
2298169689Skan  VEC(tree,gc) *method_vec = CLASSTYPE_METHOD_VEC (BINFO_TYPE (binfo));
2299169689Skan  tree conv;
2300169689Skan
2301169689Skan  /* If we have no conversion operators, then don't look.  */
2302169689Skan  if (!TYPE_HAS_CONVERSION (BINFO_TYPE (binfo)))
230350397Sobrien    {
2304169689Skan      *convs = *tpl_convs = NULL_TREE;
2305169689Skan
2306169689Skan      return 0;
2307169689Skan    }
2308169689Skan
2309169689Skan  if (BINFO_VIRTUAL_P (binfo))
2310169689Skan    virtual_depth++;
2311169689Skan
2312169689Skan  /* First, locate the unhidden ones at this level.  */
2313169689Skan  for (i = CLASSTYPE_FIRST_CONVERSION_SLOT;
2314169689Skan       VEC_iterate (tree, method_vec, i, conv);
2315169689Skan       ++i)
2316169689Skan    {
2317169689Skan      tree cur = OVL_CURRENT (conv);
2318169689Skan
2319169689Skan      if (!DECL_CONV_FN_P (cur))
2320169689Skan	break;
2321169689Skan
2322169689Skan      if (TREE_CODE (cur) == TEMPLATE_DECL)
232350397Sobrien	{
2324169689Skan	  /* Only template conversions can be overloaded, and we must
2325169689Skan	     flatten them out and check each one individually.  */
2326169689Skan	  tree tpls;
2327169689Skan
2328169689Skan	  for (tpls = conv; tpls; tpls = OVL_NEXT (tpls))
2329169689Skan	    {
2330169689Skan	      tree tpl = OVL_CURRENT (tpls);
2331169689Skan	      tree type = DECL_CONV_FN_TYPE (tpl);
2332169689Skan
2333169689Skan	      if (check_hidden_convs (binfo, virtual_depth, virtualness,
2334169689Skan				      type, parent_tpl_convs, other_tpl_convs))
2335169689Skan		{
2336169689Skan		  my_tpl_convs = tree_cons (binfo, tpl, my_tpl_convs);
2337169689Skan		  TREE_TYPE (my_tpl_convs) = type;
2338169689Skan		  if (virtual_depth)
2339169689Skan		    {
2340169689Skan		      TREE_STATIC (my_tpl_convs) = 1;
2341169689Skan		      my_virtualness = 1;
2342169689Skan		    }
2343169689Skan		}
2344169689Skan	    }
234550397Sobrien	}
2346169689Skan      else
2347169689Skan	{
2348169689Skan	  tree name = DECL_NAME (cur);
2349169689Skan
2350169689Skan	  if (!IDENTIFIER_MARKED (name))
2351169689Skan	    {
2352169689Skan	      tree type = DECL_CONV_FN_TYPE (cur);
2353169689Skan
2354169689Skan	      if (check_hidden_convs (binfo, virtual_depth, virtualness,
2355169689Skan				      type, parent_convs, other_convs))
2356169689Skan		{
2357169689Skan		  my_convs = tree_cons (binfo, conv, my_convs);
2358169689Skan		  TREE_TYPE (my_convs) = type;
2359169689Skan		  if (virtual_depth)
2360169689Skan		    {
2361169689Skan		      TREE_STATIC (my_convs) = 1;
2362169689Skan		      my_virtualness = 1;
2363169689Skan		    }
2364169689Skan		  IDENTIFIER_MARKED (name) = 1;
2365169689Skan		}
2366169689Skan	    }
2367169689Skan	}
236850397Sobrien    }
236952284Sobrien
2370169689Skan  if (my_convs)
2371169689Skan    {
2372169689Skan      parent_convs = tree_cons (binfo, my_convs, parent_convs);
2373169689Skan      if (virtual_depth)
2374169689Skan	TREE_STATIC (parent_convs) = 1;
2375169689Skan    }
237650397Sobrien
2377169689Skan  if (my_tpl_convs)
2378169689Skan    {
2379169689Skan      parent_tpl_convs = tree_cons (binfo, my_tpl_convs, parent_tpl_convs);
2380169689Skan      if (virtual_depth)
2381169689Skan	TREE_STATIC (parent_tpl_convs) = 1;
2382169689Skan    }
238350397Sobrien
2384169689Skan  child_convs = other_convs;
2385169689Skan  child_tpl_convs = other_tpl_convs;
238650397Sobrien
2387169689Skan  /* Now iterate over each base, looking for more conversions.  */
2388169689Skan  for (i = 0; BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
2389169689Skan    {
2390169689Skan      tree base_convs, base_tpl_convs;
2391169689Skan      unsigned base_virtualness;
239250397Sobrien
2393169689Skan      base_virtualness = lookup_conversions_r (base_binfo,
2394169689Skan					       virtual_depth, virtualness,
2395169689Skan					       parent_convs, parent_tpl_convs,
2396169689Skan					       child_convs, child_tpl_convs,
2397169689Skan					       &base_convs, &base_tpl_convs);
2398169689Skan      if (base_virtualness)
2399169689Skan	my_virtualness = virtualness = 1;
2400169689Skan      child_convs = chainon (base_convs, child_convs);
2401169689Skan      child_tpl_convs = chainon (base_tpl_convs, child_tpl_convs);
2402169689Skan    }
240352284Sobrien
2404169689Skan  /* Unmark the conversions found at this level  */
2405169689Skan  for (conv = my_convs; conv; conv = TREE_CHAIN (conv))
2406169689Skan    IDENTIFIER_MARKED (DECL_NAME (OVL_CURRENT (TREE_VALUE (conv)))) = 0;
2407169689Skan
2408169689Skan  *convs = split_conversions (my_convs, parent_convs,
2409169689Skan			      child_convs, other_convs);
2410169689Skan  *tpl_convs = split_conversions (my_tpl_convs, parent_tpl_convs,
2411169689Skan				  child_tpl_convs, other_tpl_convs);
2412169689Skan
2413169689Skan  return my_virtualness;
241450397Sobrien}
241552284Sobrien
2416169689Skan/* Return a TREE_LIST containing all the non-hidden user-defined
2417169689Skan   conversion functions for TYPE (and its base-classes).  The
2418169689Skan   TREE_VALUE of each node is the FUNCTION_DECL of the conversion
2419169689Skan   function.  The TREE_PURPOSE is the BINFO from which the conversion
2420169689Skan   functions in this node were selected.  This function is effectively
2421169689Skan   performing a set of member lookups as lookup_fnfield does, but
2422169689Skan   using the type being converted to as the unique key, rather than the
2423169689Skan   field name.  */
242452284Sobrien
242590075Sobrientree
2426169689Skanlookup_conversions (tree type)
242752284Sobrien{
2428169689Skan  tree convs, tpl_convs;
2429169689Skan  tree list = NULL_TREE;
243052284Sobrien
2431169689Skan  complete_type (type);
2432169689Skan  if (!TYPE_BINFO (type))
2433169689Skan    return NULL_TREE;
2434169689Skan
2435169689Skan  lookup_conversions_r (TYPE_BINFO (type), 0, 0,
2436169689Skan			NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE,
2437169689Skan			&convs, &tpl_convs);
2438169689Skan
2439169689Skan  /* Flatten the list-of-lists */
2440169689Skan  for (; convs; convs = TREE_CHAIN (convs))
244190075Sobrien    {
2442169689Skan      tree probe, next;
2443169689Skan
2444169689Skan      for (probe = TREE_VALUE (convs); probe; probe = next)
2445169689Skan	{
2446169689Skan	  next = TREE_CHAIN (probe);
2447169689Skan
2448169689Skan	  TREE_CHAIN (probe) = list;
2449169689Skan	  list = probe;
2450169689Skan	}
245190075Sobrien    }
245290075Sobrien
2453169689Skan  for (; tpl_convs; tpl_convs = TREE_CHAIN (tpl_convs))
2454169689Skan    {
2455169689Skan      tree probe, next;
245690075Sobrien
2457169689Skan      for (probe = TREE_VALUE (tpl_convs); probe; probe = next)
2458169689Skan	{
2459169689Skan	  next = TREE_CHAIN (probe);
2460169689Skan
2461169689Skan	  TREE_CHAIN (probe) = list;
2462169689Skan	  list = probe;
2463169689Skan	}
2464169689Skan    }
2465169689Skan
2466169689Skan  return list;
246752284Sobrien}
246852284Sobrien
246990075Sobrien/* Returns the binfo of the first direct or indirect virtual base derived
247090075Sobrien   from BINFO, or NULL if binfo is not via virtual.  */
247152284Sobrien
247290075Sobrientree
2473132718Skanbinfo_from_vbase (tree binfo)
247452284Sobrien{
247590075Sobrien  for (; binfo; binfo = BINFO_INHERITANCE_CHAIN (binfo))
247690075Sobrien    {
2477169689Skan      if (BINFO_VIRTUAL_P (binfo))
247890075Sobrien	return binfo;
247990075Sobrien    }
248090075Sobrien  return NULL_TREE;
248190075Sobrien}
248252284Sobrien
248390075Sobrien/* Returns the binfo of the first direct or indirect virtual base derived
248490075Sobrien   from BINFO up to the TREE_TYPE, LIMIT, or NULL if binfo is not
248590075Sobrien   via virtual.  */
248690075Sobrien
248790075Sobrientree
2488132718Skanbinfo_via_virtual (tree binfo, tree limit)
248990075Sobrien{
2490169689Skan  if (limit && !CLASSTYPE_VBASECLASSES (limit))
2491169689Skan    /* LIMIT has no virtual bases, so BINFO cannot be via one.  */
2492169689Skan    return NULL_TREE;
2493169689Skan
2494169689Skan  for (; binfo && !SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), limit);
249590075Sobrien       binfo = BINFO_INHERITANCE_CHAIN (binfo))
249690075Sobrien    {
2497169689Skan      if (BINFO_VIRTUAL_P (binfo))
249890075Sobrien	return binfo;
249990075Sobrien    }
250052284Sobrien  return NULL_TREE;
250152284Sobrien}
250252284Sobrien
2503132718Skan/* BINFO is a base binfo in the complete type BINFO_TYPE (HERE).
2504132718Skan   Find the equivalent binfo within whatever graph HERE is located.
2505132718Skan   This is the inverse of original_binfo.  */
250652284Sobrien
250752284Sobrientree
2508132718Skancopied_binfo (tree binfo, tree here)
250952284Sobrien{
2510132718Skan  tree result = NULL_TREE;
2511169689Skan
2512169689Skan  if (BINFO_VIRTUAL_P (binfo))
2513132718Skan    {
2514132718Skan      tree t;
251552284Sobrien
2516132718Skan      for (t = here; BINFO_INHERITANCE_CHAIN (t);
2517132718Skan	   t = BINFO_INHERITANCE_CHAIN (t))
2518132718Skan	continue;
2519169689Skan
2520169689Skan      result = binfo_for_vbase (BINFO_TYPE (binfo), BINFO_TYPE (t));
2521132718Skan    }
2522132718Skan  else if (BINFO_INHERITANCE_CHAIN (binfo))
2523132718Skan    {
2524169689Skan      tree cbinfo;
2525169689Skan      tree base_binfo;
2526169689Skan      int ix;
2527169689Skan
2528169689Skan      cbinfo = copied_binfo (BINFO_INHERITANCE_CHAIN (binfo), here);
2529169689Skan      for (ix = 0; BINFO_BASE_ITERATE (cbinfo, ix, base_binfo); ix++)
2530169689Skan	if (SAME_BINFO_TYPE_P (BINFO_TYPE (base_binfo), BINFO_TYPE (binfo)))
2531169689Skan	  {
2532169689Skan	    result = base_binfo;
2533169689Skan	    break;
2534169689Skan	  }
2535132718Skan    }
2536132718Skan  else
2537132718Skan    {
2538169689Skan      gcc_assert (SAME_BINFO_TYPE_P (BINFO_TYPE (here), BINFO_TYPE (binfo)));
2539132718Skan      result = here;
2540132718Skan    }
2541132718Skan
2542169689Skan  gcc_assert (result);
2543132718Skan  return result;
254452284Sobrien}
2545132718Skan
2546169689Skantree
2547169689Skanbinfo_for_vbase (tree base, tree t)
2548169689Skan{
2549169689Skan  unsigned ix;
2550169689Skan  tree binfo;
2551169689Skan  VEC(tree,gc) *vbases;
2552169689Skan
2553169689Skan  for (vbases = CLASSTYPE_VBASECLASSES (t), ix = 0;
2554169689Skan       VEC_iterate (tree, vbases, ix, binfo); ix++)
2555169689Skan    if (SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), base))
2556169689Skan      return binfo;
2557169689Skan  return NULL;
2558169689Skan}
2559169689Skan
2560132718Skan/* BINFO is some base binfo of HERE, within some other
2561132718Skan   hierarchy. Return the equivalent binfo, but in the hierarchy
2562132718Skan   dominated by HERE.  This is the inverse of copied_binfo.  If BINFO
2563132718Skan   is not a base binfo of HERE, returns NULL_TREE.  */
2564132718Skan
2565132718Skantree
2566132718Skanoriginal_binfo (tree binfo, tree here)
2567132718Skan{
2568132718Skan  tree result = NULL;
2569169689Skan
2570169689Skan  if (SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), BINFO_TYPE (here)))
2571132718Skan    result = here;
2572169689Skan  else if (BINFO_VIRTUAL_P (binfo))
2573169689Skan    result = (CLASSTYPE_VBASECLASSES (BINFO_TYPE (here))
2574169689Skan	      ? binfo_for_vbase (BINFO_TYPE (binfo), BINFO_TYPE (here))
2575169689Skan	      : NULL_TREE);
2576132718Skan  else if (BINFO_INHERITANCE_CHAIN (binfo))
2577132718Skan    {
2578132718Skan      tree base_binfos;
2579169689Skan
2580132718Skan      base_binfos = original_binfo (BINFO_INHERITANCE_CHAIN (binfo), here);
2581132718Skan      if (base_binfos)
2582132718Skan	{
2583169689Skan	  int ix;
2584169689Skan	  tree base_binfo;
2585169689Skan
2586169689Skan	  for (ix = 0; (base_binfo = BINFO_BASE_BINFO (base_binfos, ix)); ix++)
2587169689Skan	    if (SAME_BINFO_TYPE_P (BINFO_TYPE (base_binfo),
2588169689Skan				   BINFO_TYPE (binfo)))
2589169689Skan	      {
2590169689Skan		result = base_binfo;
2591169689Skan		break;
2592169689Skan	      }
2593132718Skan	}
2594132718Skan    }
2595169689Skan
2596132718Skan  return result;
2597132718Skan}
2598132718Skan
2599