118334Speter/* Generate information regarding function declarations and definitions based
218334Speter   on information stored in GCC's tree structure.  This code implements the
318334Speter   -aux-info option.
490075Sobrien   Copyright (C) 1989, 1991, 1994, 1995, 1997, 1998,
5169689Skan   1999, 2000, 2003, 2004 Free Software Foundation, Inc.
618334Speter   Contributed by Ron Guilmette (rfg@segfault.us.com).
718334Speter
890075SobrienThis file is part of GCC.
918334Speter
1090075SobrienGCC is free software; you can redistribute it and/or modify it under
1190075Sobrienthe terms of the GNU General Public License as published by the Free
1290075SobrienSoftware Foundation; either version 2, or (at your option) any later
1390075Sobrienversion.
1418334Speter
1590075SobrienGCC is distributed in the hope that it will be useful, but WITHOUT ANY
1690075SobrienWARRANTY; without even the implied warranty of MERCHANTABILITY or
1790075SobrienFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
1890075Sobrienfor more details.
1918334Speter
2018334SpeterYou should have received a copy of the GNU General Public License
2190075Sobrienalong with GCC; see the file COPYING.  If not, write to the Free
22169689SkanSoftware Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
23169689Skan02110-1301, USA.  */
2418334Speter
2518334Speter#include "config.h"
2650397Sobrien#include "system.h"
27132718Skan#include "coretypes.h"
28132718Skan#include "tm.h"
2918334Speter#include "flags.h"
3018334Speter#include "tree.h"
3118334Speter#include "c-tree.h"
32132718Skan#include "toplev.h"
3318334Speter
3418334Speterenum formals_style_enum {
3518334Speter  ansi,
3618334Speter  k_and_r_names,
3718334Speter  k_and_r_decls
3818334Speter};
3918334Spetertypedef enum formals_style_enum formals_style;
4018334Speter
4118334Speter
4252284Sobrienstatic const char *data_type;
4318334Speter
44132718Skanstatic char *affix_data_type (const char *) ATTRIBUTE_MALLOC;
45132718Skanstatic const char *gen_formal_list_for_type (tree, formals_style);
46132718Skanstatic int   deserves_ellipsis (tree);
47132718Skanstatic const char *gen_formal_list_for_func_def (tree, formals_style);
48132718Skanstatic const char *gen_type (const char *, tree, formals_style);
49132718Skanstatic const char *gen_decl (tree, int, formals_style);
5018334Speter
5118334Speter/* Given a string representing an entire type or an entire declaration
5218334Speter   which only lacks the actual "data-type" specifier (at its left end),
5318334Speter   affix the data-type specifier to the left end of the given type
5418334Speter   specification or object declaration.
5518334Speter
5618334Speter   Because of C language weirdness, the data-type specifier (which normally
5718334Speter   goes in at the very left end) may have to be slipped in just to the
5818334Speter   right of any leading "const" or "volatile" qualifiers (there may be more
5918334Speter   than one).  Actually this may not be strictly necessary because it seems
6018334Speter   that GCC (at least) accepts `<data-type> const foo;' and treats it the
6118334Speter   same as `const <data-type> foo;' but people are accustomed to seeing
6218334Speter   `const char *foo;' and *not* `char const *foo;' so we try to create types
6318334Speter   that look as expected.  */
6418334Speter
6550397Sobrienstatic char *
66132718Skanaffix_data_type (const char *param)
6718334Speter{
6890075Sobrien  char *const type_or_decl = ASTRDUP (param);
6918334Speter  char *p = type_or_decl;
7018334Speter  char *qualifiers_then_data_type;
7118334Speter  char saved;
7218334Speter
7318334Speter  /* Skip as many leading const's or volatile's as there are.  */
7418334Speter
7518334Speter  for (;;)
7618334Speter    {
7718334Speter      if (!strncmp (p, "volatile ", 9))
78169689Skan	{
79169689Skan	  p += 9;
80169689Skan	  continue;
81169689Skan	}
8218334Speter      if (!strncmp (p, "const ", 6))
83169689Skan	{
84169689Skan	  p += 6;
85169689Skan	  continue;
86169689Skan	}
8718334Speter      break;
8818334Speter    }
8918334Speter
9018334Speter  /* p now points to the place where we can insert the data type.  We have to
9118334Speter     add a blank after the data-type of course.  */
9218334Speter
9318334Speter  if (p == type_or_decl)
9490075Sobrien    return concat (data_type, " ", type_or_decl, NULL);
9518334Speter
9618334Speter  saved = *p;
9718334Speter  *p = '\0';
9890075Sobrien  qualifiers_then_data_type = concat (type_or_decl, data_type, NULL);
9918334Speter  *p = saved;
10090075Sobrien  return reconcat (qualifiers_then_data_type,
10190075Sobrien		   qualifiers_then_data_type, " ", p, NULL);
10218334Speter}
10318334Speter
10418334Speter/* Given a tree node which represents some "function type", generate the
10518334Speter   source code version of a formal parameter list (of some given style) for
10618334Speter   this function type.  Return the whole formal parameter list (including
10718334Speter   a pair of surrounding parens) as a string.   Note that if the style
10818334Speter   we are currently aiming for is non-ansi, then we just return a pair
10950397Sobrien   of empty parens here.  */
11018334Speter
11152284Sobrienstatic const char *
112132718Skangen_formal_list_for_type (tree fntype, formals_style style)
11318334Speter{
11452284Sobrien  const char *formal_list = "";
11518334Speter  tree formal_type;
11618334Speter
11718334Speter  if (style != ansi)
11818334Speter    return "()";
11918334Speter
12018334Speter  formal_type = TYPE_ARG_TYPES (fntype);
12118334Speter  while (formal_type && TREE_VALUE (formal_type) != void_type_node)
12218334Speter    {
12352284Sobrien      const char *this_type;
12418334Speter
12518334Speter      if (*formal_list)
126169689Skan	formal_list = concat (formal_list, ", ", NULL);
12718334Speter
12818334Speter      this_type = gen_type ("", TREE_VALUE (formal_type), ansi);
12950397Sobrien      formal_list
13050397Sobrien	= ((strlen (this_type))
13190075Sobrien	   ? concat (formal_list, affix_data_type (this_type), NULL)
13290075Sobrien	   : concat (formal_list, data_type, NULL));
13318334Speter
13418334Speter      formal_type = TREE_CHAIN (formal_type);
13518334Speter    }
13618334Speter
13718334Speter  /* If we got to here, then we are trying to generate an ANSI style formal
13818334Speter     parameters list.
13918334Speter
14018334Speter     New style prototyped ANSI formal parameter lists should in theory always
14118334Speter     contain some stuff between the opening and closing parens, even if it is
14218334Speter     only "void".
14318334Speter
14418334Speter     The brutal truth though is that there is lots of old K&R code out there
14518334Speter     which contains declarations of "pointer-to-function" parameters and
14618334Speter     these almost never have fully specified formal parameter lists associated
14718334Speter     with them.  That is, the pointer-to-function parameters are declared
14818334Speter     with just empty parameter lists.
14918334Speter
15018334Speter     In cases such as these, protoize should really insert *something* into
15118334Speter     the vacant parameter lists, but what?  It has no basis on which to insert
15218334Speter     anything in particular.
15318334Speter
15418334Speter     Here, we make life easy for protoize by trying to distinguish between
15518334Speter     K&R empty parameter lists and new-style prototyped parameter lists
15618334Speter     that actually contain "void".  In the latter case we (obviously) want
15718334Speter     to output the "void" verbatim, and that what we do.  In the former case,
15818334Speter     we do our best to give protoize something nice to insert.
15918334Speter
16018334Speter     This "something nice" should be something that is still valid (when
16118334Speter     re-compiled) but something that can clearly indicate to the user that
16218334Speter     more typing information (for the parameter list) should be added (by
16318334Speter     hand) at some convenient moment.
16418334Speter
16518334Speter     The string chosen here is a comment with question marks in it.  */
16618334Speter
16718334Speter  if (!*formal_list)
16818334Speter    {
16918334Speter      if (TYPE_ARG_TYPES (fntype))
170169689Skan	/* assert (TREE_VALUE (TYPE_ARG_TYPES (fntype)) == void_type_node);  */
171169689Skan	formal_list = "void";
17218334Speter      else
173169689Skan	formal_list = "/* ??? */";
17418334Speter    }
17518334Speter  else
17618334Speter    {
17718334Speter      /* If there were at least some parameters, and if the formals-types-list
178169689Skan	 petered out to a NULL (i.e. without being terminated by a
179169689Skan	 void_type_node) then we need to tack on an ellipsis.  */
18018334Speter      if (!formal_type)
181169689Skan	formal_list = concat (formal_list, ", ...", NULL);
18218334Speter    }
18318334Speter
18490075Sobrien  return concat (" (", formal_list, ")", NULL);
18518334Speter}
18618334Speter
18718334Speter/* For the generation of an ANSI prototype for a function definition, we have
18818334Speter   to look at the formal parameter list of the function's own "type" to
18918334Speter   determine if the function's formal parameter list should end with an
190117395Skan   ellipsis.  Given a tree node, the following function will return nonzero
19118334Speter   if the "function type" parameter list should end with an ellipsis.  */
19218334Speter
19318334Speterstatic int
194132718Skandeserves_ellipsis (tree fntype)
19518334Speter{
19618334Speter  tree formal_type;
19718334Speter
19818334Speter  formal_type = TYPE_ARG_TYPES (fntype);
19918334Speter  while (formal_type && TREE_VALUE (formal_type) != void_type_node)
20018334Speter    formal_type = TREE_CHAIN (formal_type);
20118334Speter
20218334Speter  /* If there were at least some parameters, and if the formals-types-list
20318334Speter     petered out to a NULL (i.e. without being terminated by a void_type_node)
20418334Speter     then we need to tack on an ellipsis.  */
20518334Speter
20618334Speter  return (!formal_type && TYPE_ARG_TYPES (fntype));
20718334Speter}
20818334Speter
20918334Speter/* Generate a parameter list for a function definition (in some given style).
21018334Speter
21118334Speter   Note that this routine has to be separate (and different) from the code that
21218334Speter   generates the prototype parameter lists for function declarations, because
21318334Speter   in the case of a function declaration, all we have to go on is a tree node
21418334Speter   representing the function's own "function type".  This can tell us the types
21518334Speter   of all of the formal parameters for the function, but it cannot tell us the
21618334Speter   actual *names* of each of the formal parameters.  We need to output those
21718334Speter   parameter names for each function definition.
21818334Speter
21918334Speter   This routine gets a pointer to a tree node which represents the actual
22018334Speter   declaration of the given function, and this DECL node has a list of formal
22118334Speter   parameter (variable) declarations attached to it.  These formal parameter
22218334Speter   (variable) declaration nodes give us the actual names of the formal
22318334Speter   parameters for the given function definition.
22418334Speter
22518334Speter   This routine returns a string which is the source form for the entire
22618334Speter   function formal parameter list.  */
22718334Speter
22852284Sobrienstatic const char *
229132718Skangen_formal_list_for_func_def (tree fndecl, formals_style style)
23018334Speter{
23152284Sobrien  const char *formal_list = "";
23218334Speter  tree formal_decl;
23318334Speter
23418334Speter  formal_decl = DECL_ARGUMENTS (fndecl);
23518334Speter  while (formal_decl)
23618334Speter    {
23752284Sobrien      const char *this_formal;
23818334Speter
23918334Speter      if (*formal_list && ((style == ansi) || (style == k_and_r_names)))
240169689Skan	formal_list = concat (formal_list, ", ", NULL);
24118334Speter      this_formal = gen_decl (formal_decl, 0, style);
24218334Speter      if (style == k_and_r_decls)
243169689Skan	formal_list = concat (formal_list, this_formal, "; ", NULL);
24418334Speter      else
245169689Skan	formal_list = concat (formal_list, this_formal, NULL);
24618334Speter      formal_decl = TREE_CHAIN (formal_decl);
24718334Speter    }
24818334Speter  if (style == ansi)
24918334Speter    {
25018334Speter      if (!DECL_ARGUMENTS (fndecl))
251169689Skan	formal_list = concat (formal_list, "void", NULL);
25218334Speter      if (deserves_ellipsis (TREE_TYPE (fndecl)))
253169689Skan	formal_list = concat (formal_list, ", ...", NULL);
25418334Speter    }
25518334Speter  if ((style == ansi) || (style == k_and_r_names))
25690075Sobrien    formal_list = concat (" (", formal_list, ")", NULL);
25718334Speter  return formal_list;
25818334Speter}
25918334Speter
26018334Speter/* Generate a string which is the source code form for a given type (t).  This
26118334Speter   routine is ugly and complex because the C syntax for declarations is ugly
26218334Speter   and complex.  This routine is straightforward so long as *no* pointer types,
26318334Speter   array types, or function types are involved.
26418334Speter
26518334Speter   In the simple cases, this routine will return the (string) value which was
26618334Speter   passed in as the "ret_val" argument.  Usually, this starts out either as an
26718334Speter   empty string, or as the name of the declared item (i.e. the formal function
26818334Speter   parameter variable).
26918334Speter
27018334Speter   This routine will also return with the global variable "data_type" set to
27118334Speter   some string value which is the "basic" data-type of the given complete type.
27218334Speter   This "data_type" string can be concatenated onto the front of the returned
27318334Speter   string after this routine returns to its caller.
27418334Speter
27518334Speter   In complicated cases involving pointer types, array types, or function
27618334Speter   types, the C declaration syntax requires an "inside out" approach, i.e. if
27718334Speter   you have a type which is a "pointer-to-function" type, you need to handle
27818334Speter   the "pointer" part first, but it also has to be "innermost" (relative to
27918334Speter   the declaration stuff for the "function" type).  Thus, is this case, you
28018334Speter   must prepend a "(*" and append a ")" to the name of the item (i.e. formal
28118334Speter   variable).  Then you must append and prepend the other info for the
28218334Speter   "function type" part of the overall type.
28318334Speter
28418334Speter   To handle the "innermost precedence" rules of complicated C declarators, we
28518334Speter   do the following (in this routine).  The input parameter called "ret_val"
28618334Speter   is treated as a "seed".  Each time gen_type is called (perhaps recursively)
28718334Speter   some additional strings may be appended or prepended (or both) to the "seed"
28818334Speter   string.  If yet another (lower) level of the GCC tree exists for the given
28918334Speter   type (as in the case of a pointer type, an array type, or a function type)
29018334Speter   then the (wrapped) seed is passed to a (recursive) invocation of gen_type()
29118334Speter   this recursive invocation may again "wrap" the (new) seed with yet more
29218334Speter   declarator stuff, by appending, prepending (or both).  By the time the
29318334Speter   recursion bottoms out, the "seed value" at that point will have a value
29418334Speter   which is (almost) the complete source version of the declarator (except
29518334Speter   for the data_type info).  Thus, this deepest "seed" value is simply passed
29618334Speter   back up through all of the recursive calls until it is given (as the return
29718334Speter   value) to the initial caller of the gen_type() routine.  All that remains
29818334Speter   to do at this point is for the initial caller to prepend the "data_type"
29918334Speter   string onto the returned "seed".  */
30018334Speter
30152284Sobrienstatic const char *
302132718Skangen_type (const char *ret_val, tree t, formals_style style)
30318334Speter{
30418334Speter  tree chain_p;
30518334Speter
30650397Sobrien  /* If there is a typedef name for this type, use it.  */
30750397Sobrien  if (TYPE_NAME (t) && TREE_CODE (TYPE_NAME (t)) == TYPE_DECL)
30818334Speter    data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
30918334Speter  else
31018334Speter    {
31118334Speter      switch (TREE_CODE (t))
312169689Skan	{
313169689Skan	case POINTER_TYPE:
314169689Skan	  if (TYPE_READONLY (t))
315169689Skan	    ret_val = concat ("const ", ret_val, NULL);
316169689Skan	  if (TYPE_VOLATILE (t))
317169689Skan	    ret_val = concat ("volatile ", ret_val, NULL);
31818334Speter
319169689Skan	  ret_val = concat ("*", ret_val, NULL);
32018334Speter
32118334Speter	  if (TREE_CODE (TREE_TYPE (t)) == ARRAY_TYPE || TREE_CODE (TREE_TYPE (t)) == FUNCTION_TYPE)
32290075Sobrien	    ret_val = concat ("(", ret_val, ")", NULL);
32318334Speter
324169689Skan	  ret_val = gen_type (ret_val, TREE_TYPE (t), style);
32518334Speter
326169689Skan	  return ret_val;
32718334Speter
328169689Skan	case ARRAY_TYPE:
32990075Sobrien	  if (!COMPLETE_TYPE_P (t) || TREE_CODE (TYPE_SIZE (t)) != INTEGER_CST)
33090075Sobrien	    ret_val = gen_type (concat (ret_val, "[]", NULL),
33152284Sobrien				TREE_TYPE (t), style);
33218334Speter	  else if (int_size_in_bytes (t) == 0)
33390075Sobrien	    ret_val = gen_type (concat (ret_val, "[0]", NULL),
33452284Sobrien				TREE_TYPE (t), style);
33518334Speter	  else
33618334Speter	    {
33718334Speter	      int size = (int_size_in_bytes (t) / int_size_in_bytes (TREE_TYPE (t)));
33818334Speter	      char buff[10];
33918334Speter	      sprintf (buff, "[%d]", size);
34090075Sobrien	      ret_val = gen_type (concat (ret_val, buff, NULL),
34118334Speter				  TREE_TYPE (t), style);
34218334Speter	    }
343169689Skan	  break;
34418334Speter
345169689Skan	case FUNCTION_TYPE:
346169689Skan	  ret_val = gen_type (concat (ret_val,
34752284Sobrien				      gen_formal_list_for_type (t, style),
34890075Sobrien				      NULL),
34952284Sobrien			      TREE_TYPE (t), style);
350169689Skan	  break;
35118334Speter
352169689Skan	case IDENTIFIER_NODE:
353169689Skan	  data_type = IDENTIFIER_POINTER (t);
354169689Skan	  break;
35518334Speter
35618334Speter	/* The following three cases are complicated by the fact that a
357169689Skan	   user may do something really stupid, like creating a brand new
358169689Skan	   "anonymous" type specification in a formal argument list (or as
359169689Skan	   part of a function return type specification).  For example:
36018334Speter
36118334Speter		int f (enum { red, green, blue } color);
36218334Speter
36318334Speter	   In such cases, we have no name that we can put into the prototype
36418334Speter	   to represent the (anonymous) type.  Thus, we have to generate the
36518334Speter	   whole darn type specification.  Yuck!  */
36618334Speter
367169689Skan	case RECORD_TYPE:
36818334Speter	  if (TYPE_NAME (t))
36918334Speter	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
37018334Speter	  else
37118334Speter	    {
37218334Speter	      data_type = "";
37318334Speter	      chain_p = TYPE_FIELDS (t);
37418334Speter	      while (chain_p)
37518334Speter		{
37652284Sobrien		  data_type = concat (data_type, gen_decl (chain_p, 0, ansi),
37790075Sobrien				      NULL);
37818334Speter		  chain_p = TREE_CHAIN (chain_p);
37990075Sobrien		  data_type = concat (data_type, "; ", NULL);
38018334Speter		}
38190075Sobrien	      data_type = concat ("{ ", data_type, "}", NULL);
38218334Speter	    }
38390075Sobrien	  data_type = concat ("struct ", data_type, NULL);
38418334Speter	  break;
38518334Speter
386169689Skan	case UNION_TYPE:
38718334Speter	  if (TYPE_NAME (t))
38818334Speter	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
38918334Speter	  else
39018334Speter	    {
39118334Speter	      data_type = "";
39218334Speter	      chain_p = TYPE_FIELDS (t);
39318334Speter	      while (chain_p)
39418334Speter		{
39552284Sobrien		  data_type = concat (data_type, gen_decl (chain_p, 0, ansi),
39690075Sobrien				      NULL);
39718334Speter		  chain_p = TREE_CHAIN (chain_p);
39890075Sobrien		  data_type = concat (data_type, "; ", NULL);
39918334Speter		}
40090075Sobrien	      data_type = concat ("{ ", data_type, "}", NULL);
40118334Speter	    }
40290075Sobrien	  data_type = concat ("union ", data_type, NULL);
40318334Speter	  break;
40418334Speter
405169689Skan	case ENUMERAL_TYPE:
40618334Speter	  if (TYPE_NAME (t))
40718334Speter	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
40818334Speter	  else
40918334Speter	    {
41018334Speter	      data_type = "";
41118334Speter	      chain_p = TYPE_VALUES (t);
41218334Speter	      while (chain_p)
41318334Speter		{
41418334Speter		  data_type = concat (data_type,
41590075Sobrien			IDENTIFIER_POINTER (TREE_PURPOSE (chain_p)), NULL);
41618334Speter		  chain_p = TREE_CHAIN (chain_p);
41718334Speter		  if (chain_p)
41890075Sobrien		    data_type = concat (data_type, ", ", NULL);
41918334Speter		}
42090075Sobrien	      data_type = concat ("{ ", data_type, " }", NULL);
42118334Speter	    }
42290075Sobrien	  data_type = concat ("enum ", data_type, NULL);
42318334Speter	  break;
42418334Speter
425169689Skan	case TYPE_DECL:
426169689Skan	  data_type = IDENTIFIER_POINTER (DECL_NAME (t));
427169689Skan	  break;
428132718Skan
429169689Skan	case INTEGER_TYPE:
430169689Skan	  data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
431169689Skan	  /* Normally, `unsigned' is part of the deal.  Not so if it comes
432132718Skan	     with a type qualifier.  */
433169689Skan	  if (TYPE_UNSIGNED (t) && TYPE_QUALS (t))
434132718Skan	    data_type = concat ("unsigned ", data_type, NULL);
43518334Speter	  break;
43618334Speter
437169689Skan	case REAL_TYPE:
438169689Skan	  data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
439169689Skan	  break;
44018334Speter
441169689Skan	case VOID_TYPE:
442169689Skan	  data_type = "void";
443169689Skan	  break;
44418334Speter
44518334Speter	case ERROR_MARK:
44618334Speter	  data_type = "[ERROR]";
44718334Speter	  break;
44818334Speter
449169689Skan	default:
450169689Skan	  gcc_unreachable ();
451169689Skan	}
45218334Speter    }
45318334Speter  if (TYPE_READONLY (t))
45490075Sobrien    ret_val = concat ("const ", ret_val, NULL);
45518334Speter  if (TYPE_VOLATILE (t))
45690075Sobrien    ret_val = concat ("volatile ", ret_val, NULL);
45752284Sobrien  if (TYPE_RESTRICT (t))
45890075Sobrien    ret_val = concat ("restrict ", ret_val, NULL);
45918334Speter  return ret_val;
46018334Speter}
46118334Speter
46218334Speter/* Generate a string (source) representation of an entire entity declaration
46318334Speter   (using some particular style for function types).
46418334Speter
46518334Speter   The given entity may be either a variable or a function.
46618334Speter
467117395Skan   If the "is_func_definition" parameter is nonzero, assume that the thing
46818334Speter   we are generating a declaration for is a FUNCTION_DECL node which is
46918334Speter   associated with a function definition.  In this case, we can assume that
47018334Speter   an attached list of DECL nodes for function formal arguments is present.  */
47118334Speter
47252284Sobrienstatic const char *
473132718Skangen_decl (tree decl, int is_func_definition, formals_style style)
47418334Speter{
47552284Sobrien  const char *ret_val;
47618334Speter
47718334Speter  if (DECL_NAME (decl))
47818334Speter    ret_val = IDENTIFIER_POINTER (DECL_NAME (decl));
47918334Speter  else
48018334Speter    ret_val = "";
48118334Speter
48218334Speter  /* If we are just generating a list of names of formal parameters, we can
48318334Speter     simply return the formal parameter name (with no typing information
48418334Speter     attached to it) now.  */
48518334Speter
48618334Speter  if (style == k_and_r_names)
48718334Speter    return ret_val;
48818334Speter
48918334Speter  /* Note that for the declaration of some entity (either a function or a
49018334Speter     data object, like for instance a parameter) if the entity itself was
49118334Speter     declared as either const or volatile, then const and volatile properties
49218334Speter     are associated with just the declaration of the entity, and *not* with
49318334Speter     the `type' of the entity.  Thus, for such declared entities, we have to
49418334Speter     generate the qualifiers here.  */
49518334Speter
49618334Speter  if (TREE_THIS_VOLATILE (decl))
49790075Sobrien    ret_val = concat ("volatile ", ret_val, NULL);
49818334Speter  if (TREE_READONLY (decl))
49990075Sobrien    ret_val = concat ("const ", ret_val, NULL);
50018334Speter
50118334Speter  data_type = "";
50218334Speter
50318334Speter  /* For FUNCTION_DECL nodes, there are two possible cases here.  First, if
50418334Speter     this FUNCTION_DECL node was generated from a function "definition", then
50518334Speter     we will have a list of DECL_NODE's, one for each of the function's formal
50618334Speter     parameters.  In this case, we can print out not only the types of each
50718334Speter     formal, but also each formal's name.  In the second case, this
50818334Speter     FUNCTION_DECL node came from an actual function declaration (and *not*
50918334Speter     a definition).  In this case, we do nothing here because the formal
51018334Speter     argument type-list will be output later, when the "type" of the function
51118334Speter     is added to the string we are building.  Note that the ANSI-style formal
51218334Speter     parameter list is considered to be a (suffix) part of the "type" of the
51318334Speter     function.  */
51418334Speter
51518334Speter  if (TREE_CODE (decl) == FUNCTION_DECL && is_func_definition)
51618334Speter    {
51752284Sobrien      ret_val = concat (ret_val, gen_formal_list_for_func_def (decl, ansi),
51890075Sobrien			NULL);
51918334Speter
52018334Speter      /* Since we have already added in the formals list stuff, here we don't
521169689Skan	 add the whole "type" of the function we are considering (which
522169689Skan	 would include its parameter-list info), rather, we only add in
523169689Skan	 the "type" of the "type" of the function, which is really just
524169689Skan	 the return-type of the function (and does not include the parameter
525169689Skan	 list info).  */
52618334Speter
52718334Speter      ret_val = gen_type (ret_val, TREE_TYPE (TREE_TYPE (decl)), style);
52818334Speter    }
52918334Speter  else
53018334Speter    ret_val = gen_type (ret_val, TREE_TYPE (decl), style);
53118334Speter
53218334Speter  ret_val = affix_data_type (ret_val);
53318334Speter
534169689Skan  if (TREE_CODE (decl) != FUNCTION_DECL && C_DECL_REGISTER (decl))
53590075Sobrien    ret_val = concat ("register ", ret_val, NULL);
53618334Speter  if (TREE_PUBLIC (decl))
53790075Sobrien    ret_val = concat ("extern ", ret_val, NULL);
53818334Speter  if (TREE_CODE (decl) == FUNCTION_DECL && !TREE_PUBLIC (decl))
53990075Sobrien    ret_val = concat ("static ", ret_val, NULL);
54018334Speter
54118334Speter  return ret_val;
54218334Speter}
54318334Speter
54450397Sobrienextern FILE *aux_info_file;
54518334Speter
54618334Speter/* Generate and write a new line of info to the aux-info (.X) file.  This
54718334Speter   routine is called once for each function declaration, and once for each
54818334Speter   function definition (even the implicit ones).  */
54918334Speter
55018334Spetervoid
551132718Skangen_aux_info_record (tree fndecl, int is_definition, int is_implicit,
552132718Skan		     int is_prototyped)
55318334Speter{
55418334Speter  if (flag_gen_aux_info)
55518334Speter    {
55618334Speter      static int compiled_from_record = 0;
557169689Skan      expanded_location xloc = expand_location (DECL_SOURCE_LOCATION (fndecl));
55818334Speter
55918334Speter      /* Each output .X file must have a header line.  Write one now if we
56018334Speter	 have not yet done so.  */
56118334Speter
562169689Skan      if (!compiled_from_record++)
56318334Speter	{
56418334Speter	  /* The first line tells which directory file names are relative to.
56518334Speter	     Currently, -aux-info works only for files in the working
56618334Speter	     directory, so just use a `.' as a placeholder for now.  */
56718334Speter	  fprintf (aux_info_file, "/* compiled from: . */\n");
56818334Speter	}
56918334Speter
57018334Speter      /* Write the actual line of auxiliary info.  */
57118334Speter
57218334Speter      fprintf (aux_info_file, "/* %s:%d:%c%c */ %s;",
573169689Skan	       xloc.file, xloc.line,
57418334Speter	       (is_implicit) ? 'I' : (is_prototyped) ? 'N' : 'O',
57518334Speter	       (is_definition) ? 'F' : 'C',
57618334Speter	       gen_decl (fndecl, is_definition, ansi));
57718334Speter
57818334Speter      /* If this is an explicit function declaration, we need to also write
57918334Speter	 out an old-style (i.e. K&R) function header, just in case the user
58018334Speter	 wants to run unprotoize.  */
58118334Speter
58218334Speter      if (is_definition)
58318334Speter	{
58418334Speter	  fprintf (aux_info_file, " /*%s %s*/",
58518334Speter		   gen_formal_list_for_func_def (fndecl, k_and_r_names),
58618334Speter		   gen_formal_list_for_func_def (fndecl, k_and_r_decls));
58718334Speter	}
58818334Speter
58918334Speter      fprintf (aux_info_file, "\n");
59018334Speter    }
59118334Speter}
592