This is the mail archive of the gdb-patches@sources.redhat.com mailing list for the GDB project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[RFC] environment.c


I'm more or less ready to start adding a 'struct environment' member
to struct block and making corresponding changes in the code,
following the process I outlined in
<http://sources.redhat.com/ml/gdb/2002-09/msg00042.html>.

I've written all the environment code, and I'll include that in the
bottom of this message.  I've examined all the places where the
current GDB code refers to BLOCK_HASHTABLE, BLOCK_NSYMS, BLOCK_SYM,
BLOCK_BUCKETS, BLOCK_BUCKET, ALL_BLOCK_SYMBOLS, and BLOCK_SHOULD_SORT,
and I've tried to find all places where current GDB code creates a
struct block; I'm confident that it should be straightforward to make
the transition in all of those places.  If anybody's curious, here are
the most distinctive special cases:

* jv-lang.c and mdebugread.c both create blocks on their own, rather
  than using buildsym.c.  This is what the linear_expandable and
  block_expandable implementations are for.

* Some of the ada code seems to write an ALL_BLOCK_SYMBOLS by hand,
  except that it jumps into the middle of the search.  But it only
  jumps into the middle if it tries to examine a sorted block and
  finds that it needs to look at things more closely.  Given that
  BLOCK_SHOULD_SORT is becoming irrelevant, those uses should be able
  to be currently replaced by ALL_BLOCK_SYMBOLS (and hence by the new
  ALL_ENV_SYMBOLS).

* There's a few places where GDB reports on its internal status (for
  the purpose of debugging GDB) where it does something like print out
  the number of symbols in a block.  When the time comes, I'll look at
  those more closely; I'll probably add an environment function just
  to support that.

Assuming there are no objections, I'll start submitting actual patches
for approval on Monday.

Beneath my signature, I'm including 'enviroment.c'.  Some of the
contents of this file will end up in symtab.h when I submit the actual
patches; I've marked the relevant section with a comment.  I'm not
planning to add this file all at once: instead, I'll add only those
sections of the file that are actually being used at any given point
in the transition process.  That way I won't be adding code that isn't
getting called and tested (e.g. by running it through the testsuite to
make sure I haven't caused any regressions).

Also, note that the file contains some ugly names starting with
ENV_TEMP.  I've used these to flag parts of the code that will only
exist while the transition to using environments is in progress: it
will all go away once block are completed switched over.

I don't expect this to make a significant difference in the
performance of GDB.  (In contrast, in the next step of this process,
fixing up global symbols, I'll try hard to improve GDB's performance.)

David Carlton
carlton@math.stanford.edu

/* Routines for name->symbol translation in GDB.
   
   Copyright 2002 Free Software Foundation, Inc.

   Contributed by David Carlton <carlton@bactrian.org>.

   This file is part of GDB.

   This program is free software; you can redistribute it and/or modify
   it under the terms of the GNU General Public License as published by
   the Free Software Foundation; either version 2 of the License, or (at
   your option) any later version.

   This program is distributed in the hope that it will be useful, but
   WITHOUT ANY WARRANTY; without even the implied warranty of
   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
   General Public License for more details.

   You should have received a copy of the GNU General Public License
   along with this program; if not, write to the Free Software
   Foundation, Inc., 59 Temple Place - Suite 330,
   Boston, MA 02111-1307, USA.  */

#include "defs.h"
#include "gdb_obstack.h"
#include "symtab.h"
#include "buildsym.h"
#include "gdb_assert.h"

/* Stuff starting here will be moved to probably symtab.h.  */

/* NOTE: carlton/2002-09-11: Names that start with ENV_TEMP are
   intended to be relatively ephemeral; they'll all be deleted once
   the transition to environments is completed.  */

/* An opaque type for environments; only environment.c should know
   about its innards.  */

struct environment;

/* The functions for creating various types of environments.  */

/* Create an environment implemented via a fixed-size hashtable.  All
   memory it uses is allocated on OBSTACK; the environment is
   initialized from SYMBOL_LIST.  */

extern struct environment *env_create_hashed (struct obstack *obstack,
					      const struct pending
					      *symbol_list);

/* Create an environment implemented via a fixed-size array.  All
   memory it uses is allocated on OBSTACK; the environment is
   initialized from the SYMBOL_LIST.  The symbols are ordered in the
   same order that they're found in SYMBOL_LIST.  */

extern struct environment *env_create_linear (struct obstack *obstack,
					      const struct pending
					      *symbol_list);

/* Create an environment implemented via an array that grows as
   necessary.  The environment is initially empty; to add symbols to
   it, call env_add_symbol().  Call env_free() when you're done with
   it.  */

/* FIXME: carlton/2002-09-11: This environment type exists only to
   make mdebugread.c and jv-lang.c happy.  The former should be
   converted over to the buildsym.c mechanisms (or made obsolete, I
   suggest in an excess of optimism); the latter should probably be
   rethought.  */

extern struct environment *env_create_linear_expandable (void);

/* Create an environment implemented via a struct block.  */

extern struct environment *ENV_TEMP_create_block (struct block *block);

/* Create an environment implemented via a struct block that can grow
   if necessary.  The environment is initially empty; to add symbols
   to it, call ENV_TEMP_add_block_symbol().  */

extern struct environment *ENV_TEMP_create_block_expandable (struct block
							     *block);

/* Free an environment, including all data that the environment itself
   may have allocated.  It's safe to call this on an environment
   allocated using an obstack: in that case, nothing will happen.  */

extern void env_free (struct environment *env);

/* Add a symbol to an expandable environment.  */

extern void env_add_symbol (struct environment *env, struct symbol *sym);

/* Add a symbol to an ENV_TEMP_block_expandable.  Returns the
   associated block (which may get moved during the call in
   question).  */

extern struct block *ENV_TEMP_add_block_symbol (struct environment *env,
						struct symbol *sym);

/* Lookup a name in an environment.  */

/* NOTE: carlton/2002-09-11: The "_shallow" part is a reminder that,
   eventually, there will be a version of this that descends to parent
   environments.  */

extern struct symbol *env_lookup_shallow(const struct environment *env,
					 const char *name,
					 const char *mangled_name,
					 namespace_enum namespace);

/* A type containing data that is used when iterating over all symbols
   in an environment.  */

/* NOTE: carlton/2002-09-11: I originally wanted to make this opaque,
   but that led to complications.  Fortunately, it turned out that all
   implementations of environments currently need to keep track of the
   same types of data (though how they interpret that data varies
   depending on the implementation), so it's really not so bad after
   all.  But code outside of environment.c should never examine the
   innards of an env_iterator.  */

struct env_iterator
{
  /* The environment that this iterator is associated to.  */
  const struct environment *env;
  /* The next two members are data that is used in a way that depends
     on ENV's implementation type.  */
  int index;
  struct symbol *current;
};

/* Initialize ITERATOR to point at the first symbol in ENV, and
   return that first symbol, or NULL if ENV is empty.  */

extern struct symbol *env_iterator_first (const struct environment *env,
					  struct env_iterator *iterator);

/* Advance ITERATOR, and return the next symbol, or NULL if there are
   no more symbols.  */

extern struct symbol *env_iterator_next (struct env_iterator *iterator);

/* Macro to loop through all symbols in an environment ENV, in no
   particular order.  ITER is a struct env_iterator (NOTE: _not_ a
   struct env_iterator *), and SYM points to the current symbol.

   It's implemented as a single loop, so you can terminate the loop
   early by a break if you desire.  */

#define ALL_ENV_SYMBOLS(env, iter, sym)				\
	for ((sym) = env_iterator_first ((env), &(iter));	\
	     (sym);						\
	     (sym) = env_iterator_next (&(iter)))

/* Stuff starting here really will stay in environment.c rather than
   be moved to symtab.h.  */

/* NOTE: carlton/2002-09-11: Names that start with ENV_TEMP are
   intended to be relatively ephemeral; they'll all be deleted once
   the transition to environments is completed.  */

/* There are various different implementations of environments, all
   accessible to the outside world via an opaque 'struct environment'.
   Given that goal, and the (admittedly less important) goal not to
   have unnecessary pointers within the data structure, the simplest
   way to handle this seems to be to have struct environment have a
   single member, which is a union of structs giving all of the
   different implementations; each of those structs starts off with an
   'env_type' member which tells you what member of the union to
   actually look at.  */

/* These are the different types of implementations.  */

enum env_type
  {
    /* Symbols are stored in a (fixed-size) hash table.  */
    ENV_HASHED,
    /* Symbols are stored in a (fixed-size) array.  */
    ENV_LINEAR,
    /* Symbols are stored in an expandable array.  */
    ENV_LINEAR_EXPANDABLE,
    /* Symbols are stored in a struct block.  */
    ENV_TEMP_BLOCK,
    /* Symbols are stored in a struct block that can expand.  */
    ENV_TEMP_BLOCK_EXPANDABLE,
  };

/* These are the data structures holding the implementations
   themselves.  */

/* In this implementation, symbols are stored in a fixed-size hash
   table.  */

struct environment_hashed
{
  int nbuckets;
  struct symbol **buckets;
};

/* In this implementation, symbols are stored in a fixed-size
   array.  */

struct environment_linear
{
  int nsyms;
  struct symbol **syms;
};

/* In this implementation, symbols are stored in an array that grows
   as necessary.  Note: the entries are ordered so that its initial
   segment matches environment_linear.  */

struct environment_linear_expandable
{
  /* How many symbols we currently have.  */
  int nsyms;
  struct symbol **syms;
  /* How many symbols we can store before needing to reallocate.  */
  int capacity;
};

/* In this implementation, symbols are stored in a struct block.  */

struct ENV_TEMP_environment_block
{
  struct block *block;
};

/* In this implementation, symbols are stored in a struct block that
   can expand.  */

struct ENV_TEMP_environment_block_expandable
{
  struct block *block;
  int capacity;
};

/* See comments before the definition of enum env_type for a
   discussion on the multiplicity of implementations.  */

/* NOTE: carlton/2002-09-12: At some point, I considered having struct
   environment be a struct containing one data member that was a union
   of implementation structs, each of which started with the data
   that's common to all implementations (currently just
   implementation_type).  The advantage to that is that then the
   environment creation functions could allocate just enough space to
   store the current implementation, rather than enough space to store
   the largest possible implementation.  The disavantage is that it's
   theoretically slightly nonportable and makes it a bit more
   tedious/error-prone to add new common data in the future.  Given
   the small amount of wasted space, the disadvantages of that method
   seemed to outweigh the benefits.  */

struct environment
{
  enum env_type implementation_type;
  union
  {
    struct environment_hashed hashed;
    struct environment_linear linear;
    struct environment_linear_expandable linear_expandable;
    struct ENV_TEMP_environment_block ENV_TEMP_block;
    struct ENV_TEMP_environment_block_expandable ENV_TEMP_block_expandable;
  }
  data;
};

/* Accessor macros.  */

#define ENV_TYPE(e)		(e)->implementation_type

#define ENV_HASHED_NBUCKETS(e)	(e)->data.hashed.nbuckets
#define ENV_HASHED_BUCKETS(e)	(e)->data.hashed.buckets
#define ENV_HASHED_BUCKET(e,i)	ENV_HASHED_BUCKETS (e) [i]

/* These can be used on linear_expandable environments, too.  */
#define ENV_LINEAR_NSYMS(e)	(e)->data.linear.nsyms
#define ENV_LINEAR_SYMS(e)	(e)->data.linear.syms
#define ENV_LINEAR_SYM(e,i)	ENV_LINEAR_SYMS (e) [i]

#define ENV_LINEAR_EXPANDABLE_CAPACITY(e) (e)->data.linear_expandable.capacity

/* This can be used on block_expandable environments, too.  */
#define ENV_TEMP_BLOCK_BLOCK(e)		(e)->data.ENV_TEMP_block.block

#define ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY(e)	\
	(e)->data.ENV_TEMP_block_expandable.capacity

/* This calculates the number of buckets we'll use in a hashtable,
   given the number of symbols that it will contain.  */

#define ENV_HASHTABLE_SIZE(n)	BLOCK_HASHTABLE_SIZE (n)

/* This is the initial capacity for linear_expandable environments.
   (And it's also the capacity for block_expandable enviroments once a
   single symbol has been added to them.)  */

#define ENV_LINEAR_EXPANDABLE_INITIAL_CAPACITY	10

/* Accessor macros for env_iterators; they're here rather than
   symtab.h because code elsewhere should treat env_iterators as
   opaque.  */

/* The environment that the iterator is associated to.  */
#define ENV_ITERATOR_ENV(iter)		(iter)->env
/* For linear environments, the index of the last symbol returned; for
   hashed environments, the bucket of the last symbol returned.  */
#define ENV_ITERATOR_INDEX(iter)	(iter)->index
/* For hashed environments, this points to the last symbol returned;
   otherwise, this is unused.  */
#define ENV_ITERATOR_CURRENT(iter)	(iter)->current

/* Functions to handle some of the common code in env_iterator_first
   and env_iterator_next.  */

static struct symbol *env_iterator_hashed_advance (struct env_iterator *iter);

static struct symbol *ENV_TEMP_iterator_block_hashed_advance (struct
							      env_iterator
							      *iter);


/* Next come the functions to create environments of various types.  */

/* Create an environment implemented via a fixed-size hashtable.  All
   memory it uses is allocated on the OBSTACK; the environment is
   initialized from SYMBOL_LIST.  */

struct environment *
env_create_hashed (struct obstack *obstack,
		   const struct pending *symbol_list)
{
  struct environment *retval;
  int nsyms, nbuckets, i;
  struct symbol **buckets;
  const struct pending *list_counter;

  retval = obstack_alloc (obstack, sizeof (struct environment));
  ENV_TYPE (retval) = ENV_HASHED;

  /* Calculate the number of symbols, and allocate space for them.  */
  for (nsyms = 0, list_counter = symbol_list;
       list_counter != NULL;
       nsyms += list_counter->nsyms, list_counter = list_counter->next)
    {
      /* EMPTY */ ;
    }
  nbuckets = ENV_HASHTABLE_SIZE (nsyms);
  ENV_HASHED_NBUCKETS (retval) = nbuckets;
  buckets = obstack_alloc (obstack, nbuckets * sizeof (struct symbol *));
  memset (buckets, 0, nbuckets * sizeof (struct symbol *));
  ENV_HASHED_BUCKETS (retval) = buckets;

  /* Now fill the buckets.  */
  for (list_counter = symbol_list;
       list_counter != NULL;
       list_counter = list_counter->next)
    {
      for (i = list_counter->nsyms - 1; i >= 0; --i)
	{
	  struct symbol *sym = list_counter->symbol[i];
	  unsigned int hash_index;
	  const char *name = SYMBOL_DEMANGLED_NAME (sym);
	  if (name == NULL)
	    name = SYMBOL_NAME (sym);
	  hash_index = msymbol_hash_iw (name) % nbuckets;
	  sym->hash_next = buckets[hash_index];
	  buckets[hash_index] = sym;
	}
    }

  return retval;
}

/* Create an environment implemented via a fixed-size array.  All
   memory it uses is allocated on OBSTACK; the environment is
   initialized from SYMBOL_LIST.  The symbols are ordered in the same
   order that they're found in SYMBOL_LIST.  */

struct environment *
env_create_linear (struct obstack *obstack,
		   const struct pending *symbol_list)
{
  struct environment *retval;
  int nsyms, i, j;
  struct symbol **syms;
  const struct pending *list_counter;

  retval = obstack_alloc (obstack, sizeof (struct environment));
  ENV_TYPE (retval) = ENV_LINEAR;

  /* Calculate the number of symbols, and allocate space for them.  */
  for (nsyms = 0, list_counter = symbol_list;
       list_counter != NULL;
       nsyms += list_counter->nsyms, list_counter = list_counter->next)
    {
      /* EMPTY */ ;
    }
  ENV_LINEAR_NSYMS (retval) = nsyms;
  syms = obstack_alloc (obstack, nsyms * sizeof (struct symbol *));
  ENV_LINEAR_SYMS (retval) = syms;

  /* Now fill in the symbols.  Start filling in from the back, so as
     to preserve the original order of the symbols.  */
  for (list_counter = symbol_list, j = nsyms - 1;
       list_counter != NULL;
       list_counter = list_counter->next)
    {
      for (i = list_counter->nsyms - 1;
	   i >= 0;
	   --i, --j)
	{
	  syms[j] = list_counter->symbol[i];
	}
    }

  return retval;
}

/* Create an environment implemented via an array that grows as
   necessary.  The environment is initially empty; to add symbols to
   it, call env_add_symbol().  Call env_free() when
   you're done with it.  */

struct environment *
env_create_linear_expandable (void)
{
  struct environment *retval;

  retval = xmalloc (sizeof (struct environment));
  ENV_TYPE (retval) = ENV_LINEAR_EXPANDABLE;
  ENV_LINEAR_NSYMS (retval) = 0;
  ENV_LINEAR_EXPANDABLE_CAPACITY (retval)
    = ENV_LINEAR_EXPANDABLE_INITIAL_CAPACITY;
  ENV_LINEAR_SYMS (retval)
    = xmalloc (ENV_LINEAR_EXPANDABLE_CAPACITY (retval)
	       * sizeof (struct symbol *));

  return retval;
}

/* Create an environment implemented via a struct block.
   
   This has a memory leak: the memory allocated via it never gets
   freed.  (Unless the calling code calls env_free(), which is
   unlikely.)  But given that this implementation of environments will
   go away once the transition to environments is finished and given
   that, in practice, the amount of memory leaked will be very small,
   I'm not inclined to fix that (e.g. by allocating on the same
   obstack used for the argument).  */

struct environment *
ENV_TEMP_create_block (struct block *block)
{
  struct environment *retval;

  retval = xmalloc (sizeof (struct environment));
  ENV_TYPE (retval) = ENV_TEMP_BLOCK;
  ENV_TEMP_BLOCK_BLOCK (retval) = block;

  return retval;
}

/* Create an environment implemented via a struct block that can grow
   if necessary.  The environment is initially empty; to add symbols
   to it, call ENV_TEMP_add_block_symbol().

   As with ENV_TEMP_create_block(), this has an unimportant memory
   leak.  */

struct environment *
ENV_TEMP_create_block_expandable (struct block *block)
{
  struct environment *retval;

  retval = xmalloc (sizeof (struct environment));
  ENV_TYPE (retval) = ENV_TEMP_BLOCK_EXPANDABLE;
  ENV_TEMP_BLOCK_BLOCK (retval) = block;

  /* Set capacity to 0; the first call to ENV_TEMP_add_block_symbol()
     will resize the block.  */
  ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (retval) = 0;

  return retval;
}

/* Free an environment, including all data that the environment itself
   may have allocated.  It's safe to call this on an environment
   allocated using an obstack: in that case, nothing will happen.  */

void
env_free (struct environment *env)
{
  switch (ENV_TYPE (env))
    {
    case ENV_HASHED:
    case ENV_LINEAR:
      /* Allocated on an obstack: do nothing.  */
      break;
    case ENV_LINEAR_EXPANDABLE:
      xfree (ENV_LINEAR_SYMS (env));
      xfree (env);
      break;
    case ENV_TEMP_BLOCK:
      xfree (env);
      break;
    case ENV_TEMP_BLOCK_EXPANDABLE:
      xfree (env);
      break;
    default:
      internal_error (__FILE__, __LINE__,
		      "env_free: unexpected environment type");
    }
}

/* Add a symbol to a (non-ENV_TEMP) expandable environment.  (Which
   currently means to a linear_expandable environment.)  */

void
env_add_symbol (struct environment *env, struct symbol *sym)
{
  gdb_assert (ENV_TYPE (env) == ENV_LINEAR_EXPANDABLE);
  
  int nsyms = ++ENV_LINEAR_NSYMS (env);

  /* Do we have enough room?  If not, grow it.  */
  if (nsyms > ENV_LINEAR_EXPANDABLE_CAPACITY (env)) {
    ENV_LINEAR_EXPANDABLE_CAPACITY (env) *= 2;
    ENV_LINEAR_SYMS (env)
      = xrealloc (ENV_LINEAR_SYMS (env),
		  ENV_LINEAR_EXPANDABLE_CAPACITY (env)
		  * sizeof (struct symbol *));
  }

  ENV_LINEAR_SYM (env, nsyms - 1) = sym;
}

/* Add a symbol to an ENV_TEMP_block_expandable.  Returns the
   associated block (which may get moved during the call in
   question).  */

struct block *
ENV_TEMP_add_block_symbol (struct environment *env,
			   struct symbol *sym)
{
  gdb_assert (ENV_TYPE (env) == ENV_TEMP_BLOCK_EXPANDABLE);

  int nsyms = ++BLOCK_NSYMS (ENV_TEMP_BLOCK_BLOCK (env));

  /* Do we have enough room?  If not, grow it.  */
  if (nsyms > ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (env)) {
    ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (env)
      = (ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (env)
	 ? 2 * ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (env)
	 : ENV_LINEAR_EXPANDABLE_INITIAL_CAPACITY);
    ENV_TEMP_BLOCK_BLOCK (env)
      = xrealloc (ENV_TEMP_BLOCK_BLOCK (env),
		  sizeof (struct block)
		  + ((ENV_TEMP_BLOCK_EXPANDABLE_CAPACITY (env) - 1)
		     * sizeof (struct symbol *)));
  }

  BLOCK_SYM (ENV_TEMP_BLOCK_BLOCK (env), nsyms - 1) = sym;

  return ENV_TEMP_BLOCK_BLOCK (env);
}

/* Lookup a name in an environment.  The "_shallow" part is a reminder
   that, eventually, there will be a version of this that descends to
   parent environments.  */

/* FIXME: carlton/2002-09-12: For now, the arguments are the similar
   to lookup_block_symbol().  It seems not unlikely to me that, once
   C++ support is a bit more regularized, the arguments will change
   slightly; who knows...  */

struct symbol *
env_lookup_shallow(const struct environment *env,
		   const char *name,
		   const char *mangled_name,
		   namespace_enum namespace)
{
  switch (ENV_TYPE (env))
    {
    case ENV_HASHED:
      {
	unsigned int hash_index
	  = msymbol_hash_iw (name) % ENV_HASHED_NBUCKETS (env);
	struct symbol *sym;

	for (sym = ENV_HASHED_BUCKET (env, hash_index);
	     sym;
	     sym = sym->hash_next)
	  {
	    if (SYMBOL_NAMESPACE (sym) == namespace
		&& (mangled_name
		    ? strcmp (SYMBOL_NAME (sym), mangled_name) == 0
		    : SYMBOL_MATCHES_NAME (sym, name)))
	      return sym;
	  }

	return NULL;
      }
    case ENV_LINEAR:
    case ENV_LINEAR_EXPANDABLE:
      {
	/* More or less copied from lookup_block_symbol() in symtab.c,
	   including the comments.  */

	int i, nsyms = ENV_LINEAR_NSYMS (env);
	struct symbol *sym, *sym_found = NULL;

	for (i = 0; i < nsyms; ++i)
	  {
	    sym = ENV_LINEAR_SYM (env, i);
	    if (SYMBOL_NAMESPACE (sym) == namespace
		&& (mangled_name
		    ? strcmp (SYMBOL_NAME (sym), mangled_name) == 0
		    : SYMBOL_MATCHES_NAME (sym, name)))
	      {

#if 0
		/* FIXME: carlton/2002-09-11: According to
		   <http://sources.redhat.com/ml/gdb/2002-03/msg00232.html>,
		   the SYMBOL_ALIASES stuff is unused, and it makes
		   the code messier, so I'm #if'ing it out here.  */

		/* If SYM has aliases, then use any alias that is active
		   at the current PC.  If no alias is active at the current
		   PC, then use the main symbol.
		   
		   ?!? Is checking the current pc correct?  Is this routine
		   ever called to look up a symbol from another context?
		   
		   FIXME: No, it's not correct.  If someone sets a
		   conditional breakpoint at an address, then the
		   breakpoint's `struct expression' should refer to the
		   `struct symbol' appropriate for the breakpoint's
		   address, which may not be the PC.
		   
		   Even if it were never called from another context,
		   it's totally bizarre for lookup_symbol's behavior to
		   depend on the value of the inferior's current PC.  We
		   should pass in the appropriate PC as well as the
		   block.  The interface to lookup_symbol should change
		   to require the caller to provide a PC.  */

		if (SYMBOL_ALIASES (sym))
		  sym = find_active_alias (sym, read_pc ());
#endif /* 0 */
		/* NOTE: carlton/2002-09-11: I wish I understood
		   exactly the situations where this next bit is
		   important.  Sigh.  */
		
		/* Note that parameter symbols do not always show up
		   last in the list; this loop makes sure to take
		   anything else other than parameter symbols first;
		   it only uses parameter symbols as a last resort.
		   Note that this only takes up extra computation time
		   on a match.  */

		sym_found = sym;
		if (SYMBOL_CLASS (sym) != LOC_ARG &&
		    SYMBOL_CLASS (sym) != LOC_LOCAL_ARG &&
		    SYMBOL_CLASS (sym) != LOC_REF_ARG &&
		    SYMBOL_CLASS (sym) != LOC_REGPARM &&
		    SYMBOL_CLASS (sym) != LOC_REGPARM_ADDR &&
		    SYMBOL_CLASS (sym) != LOC_BASEREG_ARG)
		  {
		    break;
		  }
	      }
	  }
	
	return (sym_found);		/* Will be NULL if not found. */
      }
    case ENV_TEMP_BLOCK:
    case ENV_TEMP_BLOCK_EXPANDABLE:
      {
	struct block *block = ENV_TEMP_BLOCK_BLOCK (env);

	/* The rest is copied verbatim from symtab.c, except that it
	   skips the sorted-list stuff and #if's out the aliases
	   stuff.  */

	register int bot, top, inc;
	register struct symbol *sym;
	register struct symbol *sym_found = NULL;

	if (BLOCK_HASHTABLE (block))
	  {
	    unsigned int hash_index;
	    hash_index = msymbol_hash_iw (name);
	    hash_index = hash_index % BLOCK_BUCKETS (block);
	    for (sym = BLOCK_BUCKET (block, hash_index); sym;
		 sym = sym->hash_next)
	      {
		if (SYMBOL_NAMESPACE (sym) == namespace 
		    && (mangled_name
			? strcmp (SYMBOL_NAME (sym), mangled_name) == 0
			: SYMBOL_MATCHES_NAME (sym, name)))
		  return sym;
	      }
	    return NULL;
	  }
	
	/* Note that parameter symbols do not always show up last in
	   the list; this loop makes sure to take anything else other
	   than parameter symbols first; it only uses parameter
	   symbols as a last resort.  Note that this only takes up
	   extra computation time on a match.  */

	top = BLOCK_NSYMS (block);
	bot = 0;
	while (bot < top)
	  {
	    sym = BLOCK_SYM (block, bot);
	    if (SYMBOL_NAMESPACE (sym) == namespace
		&& (mangled_name
		    ? strcmp (SYMBOL_NAME (sym), mangled_name) == 0
		    : SYMBOL_MATCHES_NAME (sym, name)))
	      {
#if 0
		/* FIXME: carlton/2002-09-11: According to
		   <http://sources.redhat.com/ml/gdb/2002-03/msg00232.html>,
		   the SYMBOL_ALIASES stuff is unused, and it makes
		   the code messier, so I'm commenting it out here.
		   (Of course, this version of the code is only
		   temporary, anyways.)  */

		/* If SYM has aliases, then use any alias that is
		   active at the current PC.  If no alias is active at
		   the current PC, then use the main symbol.
		   
		   ?!? Is checking the current pc correct?  Is this routine
		   ever called to look up a symbol from another context?
		   
		   FIXME: No, it's not correct.  If someone sets a
		   conditional breakpoint at an address, then the
		   breakpoint's `struct expression' should refer to the
		   `struct symbol' appropriate for the breakpoint's
		   address, which may not be the PC.
		   
		   Even if it were never called from another context,
		   it's totally bizarre for lookup_symbol's behavior to
		   depend on the value of the inferior's current PC.  We
		   should pass in the appropriate PC as well as the
		   block.  The interface to lookup_symbol should change
		   to require the caller to provide a PC.  */
		
		if (SYMBOL_ALIASES (sym))
		  sym = find_active_alias (sym, read_pc ());
#endif /* 0 */
		
		sym_found = sym;
		if (SYMBOL_CLASS (sym) != LOC_ARG &&
		    SYMBOL_CLASS (sym) != LOC_LOCAL_ARG &&
		    SYMBOL_CLASS (sym) != LOC_REF_ARG &&
		    SYMBOL_CLASS (sym) != LOC_REGPARM &&
		    SYMBOL_CLASS (sym) != LOC_REGPARM_ADDR &&
		    SYMBOL_CLASS (sym) != LOC_BASEREG_ARG)
		  {
		    break;
		  }
	      }
	    bot++;
	  }
	return (sym_found);		/* Will be NULL if not found. */
      }
    default:
      internal_error (__FILE__, __LINE__,
		      "env_lookup_shallow: unexpected environment type");
    }
}

/* Initialize ITERATOR to point at the first symbol in ENV, and
   returns that first symbol, or NULL if ENV is empty.  */

struct symbol *
env_iterator_first (const struct environment *env,
		    struct env_iterator *iterator)
{
  ENV_ITERATOR_ENV (iterator) = env;

  switch (ENV_TYPE (env))
    {
    case ENV_HASHED:
      ENV_ITERATOR_INDEX (iterator) = -1;
      return env_iterator_hashed_advance (iterator);
    case ENV_LINEAR:
    case ENV_LINEAR_EXPANDABLE:
      ENV_ITERATOR_INDEX (iterator) = 0;
      return ENV_LINEAR_NSYMS (env) ? ENV_LINEAR_SYM (env, 0) : NULL;
    case ENV_TEMP_BLOCK:
    case ENV_TEMP_BLOCK_EXPANDABLE:
      {
	struct block *block = ENV_TEMP_BLOCK_BLOCK (env);
	
	if (BLOCK_HASHTABLE (block))
	  {
	    ENV_ITERATOR_INDEX (iterator) = -1;
	    return ENV_TEMP_iterator_block_hashed_advance (iterator);
	  }
	else
	  {
	    ENV_ITERATOR_INDEX (iterator) = 0;
	    return BLOCK_NSYMS (block) ? BLOCK_SYM (block, 0) : NULL;
	  }
      }
    default:
      internal_error (__FILE__, __LINE__,
		      "env_iterator_first: unexpected environment type");
    }
}

/* Advance ITERATOR, and return the next symbol, or NULL if there are
   no more symbols.  */

struct symbol *
env_iterator_next (struct env_iterator *iterator)
{
  const struct environment *env = ENV_ITERATOR_ENV (iterator);

  switch (ENV_TYPE (env))
    {
    case ENV_HASHED:
      {
	struct symbol *next = ENV_ITERATOR_CURRENT (iterator)->hash_next;

	if (next == NULL)
	  return env_iterator_hashed_advance (iterator);
	else
	  {
	    ENV_ITERATOR_CURRENT (iterator) = next;
	    return next;
	  }
      }
    case ENV_LINEAR:
    case ENV_LINEAR_EXPANDABLE:
      {
	if (ENV_ITERATOR_INDEX (iterator) >= ENV_LINEAR_NSYMS (env))
	  return NULL;
	else
	  return ENV_LINEAR_SYM (env, ++ENV_ITERATOR_INDEX (iterator));
      }
    case ENV_TEMP_BLOCK:
    case ENV_TEMP_BLOCK_EXPANDABLE:
      {
	struct block *block = ENV_TEMP_BLOCK_BLOCK (env);
	
	if (BLOCK_HASHTABLE (block))
	  {
	    struct symbol *next
	      = ENV_ITERATOR_CURRENT (iterator)->hash_next;
	    
	    if (next == NULL)
	      return ENV_TEMP_iterator_block_hashed_advance (iterator);
	    else
	      {
		ENV_ITERATOR_CURRENT (iterator) = next;
		return next;
	      }
	  }
	else
	  {
	    if (ENV_ITERATOR_INDEX (iterator) >= BLOCK_NSYMS (block))
	      return NULL;
	    else
	      return BLOCK_SYM (block, ++ENV_ITERATOR_INDEX (iterator));
	  }
      }
    default:
      internal_error (__FILE__, __LINE__,
		      "env_iterator_next: unexpected environment type");
    }
}

/* Search for the next nonempty bucket; update iterator accordingly,
   and return it.  */

static struct symbol *
env_iterator_hashed_advance (struct env_iterator *iterator)
{
  const struct environment *env = ENV_ITERATOR_ENV (iterator);
  int nbuckets = ENV_HASHED_NBUCKETS (env);
  int i;

  for (i = ENV_ITERATOR_INDEX (iterator) + 1; i < nbuckets; ++i)
    {
      struct symbol *sym = ENV_HASHED_BUCKET (env, i);
      
      if (sym != NULL)
	{
	  ENV_ITERATOR_INDEX (iterator) = i;
	  ENV_ITERATOR_CURRENT (iterator) = sym;
	  return sym;
	}
    }

  return NULL;
}

/* Search for the next nonempty bucket; update iterator accordingly,
   and return it.  */

static struct symbol *
ENV_TEMP_iterator_block_hashed_advance (struct env_iterator *iterator)
{
  struct block *block =
    ENV_TEMP_BLOCK_BLOCK (ENV_ITERATOR_ENV (iterator));
  int nbuckets = BLOCK_BUCKETS (block);
  int i;

  for (i = ENV_ITERATOR_INDEX (iterator) + 1; i < nbuckets; ++i)
    {
      struct symbol *sym = BLOCK_BUCKET (block, i);
      
      if (sym != NULL)
	{
	  ENV_ITERATOR_INDEX (iterator) = i;
	  ENV_ITERATOR_CURRENT (iterator) = sym;
	  return sym;
	}
    }

  return NULL;
}


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]