c-aux-info.c revision 52284
1/* Generate information regarding function declarations and definitions based
2   on information stored in GCC's tree structure.  This code implements the
3   -aux-info option.
4   Copyright (C) 1989, 91, 94, 95, 97-98, 1999 Free Software Foundation, Inc.
5   Contributed by Ron Guilmette (rfg@segfault.us.com).
6
7This file is part of GNU CC.
8
9GNU CC is free software; you can redistribute it and/or modify
10it under the terms of the GNU General Public License as published by
11the Free Software Foundation; either version 2, or (at your option)
12any later version.
13
14GNU CC is distributed in the hope that it will be useful,
15but WITHOUT ANY WARRANTY; without even the implied warranty of
16MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17GNU General Public License for more details.
18
19You should have received a copy of the GNU General Public License
20along with GNU CC; see the file COPYING.  If not, write to
21the Free Software Foundation, 59 Temple Place - Suite 330,
22Boston, MA 02111-1307, USA.  */
23
24#include "config.h"
25#include "system.h"
26#include "toplev.h"
27#include "flags.h"
28#include "tree.h"
29#include "c-tree.h"
30
31enum formals_style_enum {
32  ansi,
33  k_and_r_names,
34  k_and_r_decls
35};
36typedef enum formals_style_enum formals_style;
37
38
39static const char *data_type;
40
41static char *affix_data_type		PROTO((const char *));
42static const char *gen_formal_list_for_type PROTO((tree, formals_style));
43static int   deserves_ellipsis		PROTO((tree));
44static const char *gen_formal_list_for_func_def PROTO((tree, formals_style));
45static const char *gen_type		PROTO((const char *, tree, formals_style));
46static const char *gen_decl		PROTO((tree, int, formals_style));
47
48/* Concatenate a sequence of strings, returning the result.
49
50   This function is based on the one in libiberty.  */
51
52/* This definition will conflict with the one from prefix.c in
53   libcpp.a when linking cc1 and cc1obj.  So only provide it if we are
54   not using libcpp.a */
55#ifndef USE_CPPLIB
56char *
57concat VPROTO((const char *first, ...))
58{
59  register int length;
60  register char *newstr;
61  register char *end;
62  register const char *arg;
63  va_list args;
64#ifndef ANSI_PROTOTYPES
65  const char *first;
66#endif
67
68  /* First compute the size of the result and get sufficient memory.  */
69
70  VA_START (args, first);
71#ifndef ANSI_PROTOTYPES
72  first = va_arg (args, const char *);
73#endif
74
75  arg = first;
76  length = 0;
77
78  while (arg != 0)
79    {
80      length += strlen (arg);
81      arg = va_arg (args, const char *);
82    }
83
84  newstr = (char *) malloc (length + 1);
85  va_end (args);
86
87  /* Now copy the individual pieces to the result string.  */
88
89  VA_START (args, first);
90#ifndef ANSI_PROTOTYPES
91  first = va_arg (args, char *);
92#endif
93
94  end = newstr;
95  arg = first;
96  while (arg != 0)
97    {
98      while (*arg)
99	*end++ = *arg++;
100      arg = va_arg (args, const char *);
101    }
102  *end = '\000';
103  va_end (args);
104
105  return (newstr);
106}
107#endif /* ! USE_CPPLIB */
108
109/* Given a string representing an entire type or an entire declaration
110   which only lacks the actual "data-type" specifier (at its left end),
111   affix the data-type specifier to the left end of the given type
112   specification or object declaration.
113
114   Because of C language weirdness, the data-type specifier (which normally
115   goes in at the very left end) may have to be slipped in just to the
116   right of any leading "const" or "volatile" qualifiers (there may be more
117   than one).  Actually this may not be strictly necessary because it seems
118   that GCC (at least) accepts `<data-type> const foo;' and treats it the
119   same as `const <data-type> foo;' but people are accustomed to seeing
120   `const char *foo;' and *not* `char const *foo;' so we try to create types
121   that look as expected.  */
122
123static char *
124affix_data_type (param)
125     const char *param;
126{
127  char *type_or_decl = (char *) alloca (strlen (param) + 1);
128  char *p = type_or_decl;
129  char *qualifiers_then_data_type;
130  char saved;
131
132  strcpy (type_or_decl, param);
133
134  /* Skip as many leading const's or volatile's as there are.  */
135
136  for (;;)
137    {
138      if (!strncmp (p, "volatile ", 9))
139        {
140          p += 9;
141          continue;
142        }
143      if (!strncmp (p, "const ", 6))
144        {
145          p += 6;
146          continue;
147        }
148      break;
149    }
150
151  /* p now points to the place where we can insert the data type.  We have to
152     add a blank after the data-type of course.  */
153
154  if (p == type_or_decl)
155    return concat (data_type, " ", type_or_decl, NULL_PTR);
156
157  saved = *p;
158  *p = '\0';
159  qualifiers_then_data_type = concat (type_or_decl, data_type, NULL_PTR);
160  *p = saved;
161  return concat (qualifiers_then_data_type, " ", p, NULL_PTR);
162}
163
164/* Given a tree node which represents some "function type", generate the
165   source code version of a formal parameter list (of some given style) for
166   this function type.  Return the whole formal parameter list (including
167   a pair of surrounding parens) as a string.   Note that if the style
168   we are currently aiming for is non-ansi, then we just return a pair
169   of empty parens here.  */
170
171static const char *
172gen_formal_list_for_type (fntype, style)
173     tree fntype;
174     formals_style style;
175{
176  const char *formal_list = "";
177  tree formal_type;
178
179  if (style != ansi)
180    return "()";
181
182  formal_type = TYPE_ARG_TYPES (fntype);
183  while (formal_type && TREE_VALUE (formal_type) != void_type_node)
184    {
185      const char *this_type;
186
187      if (*formal_list)
188        formal_list = concat (formal_list, ", ", NULL_PTR);
189
190      this_type = gen_type ("", TREE_VALUE (formal_type), ansi);
191      formal_list
192	= ((strlen (this_type))
193	   ? concat (formal_list, affix_data_type (this_type), NULL_PTR)
194	   : concat (formal_list, data_type, NULL_PTR));
195
196      formal_type = TREE_CHAIN (formal_type);
197    }
198
199  /* If we got to here, then we are trying to generate an ANSI style formal
200     parameters list.
201
202     New style prototyped ANSI formal parameter lists should in theory always
203     contain some stuff between the opening and closing parens, even if it is
204     only "void".
205
206     The brutal truth though is that there is lots of old K&R code out there
207     which contains declarations of "pointer-to-function" parameters and
208     these almost never have fully specified formal parameter lists associated
209     with them.  That is, the pointer-to-function parameters are declared
210     with just empty parameter lists.
211
212     In cases such as these, protoize should really insert *something* into
213     the vacant parameter lists, but what?  It has no basis on which to insert
214     anything in particular.
215
216     Here, we make life easy for protoize by trying to distinguish between
217     K&R empty parameter lists and new-style prototyped parameter lists
218     that actually contain "void".  In the latter case we (obviously) want
219     to output the "void" verbatim, and that what we do.  In the former case,
220     we do our best to give protoize something nice to insert.
221
222     This "something nice" should be something that is still valid (when
223     re-compiled) but something that can clearly indicate to the user that
224     more typing information (for the parameter list) should be added (by
225     hand) at some convenient moment.
226
227     The string chosen here is a comment with question marks in it.  */
228
229  if (!*formal_list)
230    {
231      if (TYPE_ARG_TYPES (fntype))
232        /* assert (TREE_VALUE (TYPE_ARG_TYPES (fntype)) == void_type_node);  */
233        formal_list = "void";
234      else
235        formal_list = "/* ??? */";
236    }
237  else
238    {
239      /* If there were at least some parameters, and if the formals-types-list
240         petered out to a NULL (i.e. without being terminated by a
241         void_type_node) then we need to tack on an ellipsis.  */
242      if (!formal_type)
243        formal_list = concat (formal_list, ", ...", NULL_PTR);
244    }
245
246  return concat (" (", formal_list, ")", NULL_PTR);
247}
248
249/* For the generation of an ANSI prototype for a function definition, we have
250   to look at the formal parameter list of the function's own "type" to
251   determine if the function's formal parameter list should end with an
252   ellipsis.  Given a tree node, the following function will return non-zero
253   if the "function type" parameter list should end with an ellipsis.  */
254
255static int
256deserves_ellipsis (fntype)
257     tree fntype;
258{
259  tree formal_type;
260
261  formal_type = TYPE_ARG_TYPES (fntype);
262  while (formal_type && TREE_VALUE (formal_type) != void_type_node)
263    formal_type = TREE_CHAIN (formal_type);
264
265  /* If there were at least some parameters, and if the formals-types-list
266     petered out to a NULL (i.e. without being terminated by a void_type_node)
267     then we need to tack on an ellipsis.  */
268
269  return (!formal_type && TYPE_ARG_TYPES (fntype));
270}
271
272/* Generate a parameter list for a function definition (in some given style).
273
274   Note that this routine has to be separate (and different) from the code that
275   generates the prototype parameter lists for function declarations, because
276   in the case of a function declaration, all we have to go on is a tree node
277   representing the function's own "function type".  This can tell us the types
278   of all of the formal parameters for the function, but it cannot tell us the
279   actual *names* of each of the formal parameters.  We need to output those
280   parameter names for each function definition.
281
282   This routine gets a pointer to a tree node which represents the actual
283   declaration of the given function, and this DECL node has a list of formal
284   parameter (variable) declarations attached to it.  These formal parameter
285   (variable) declaration nodes give us the actual names of the formal
286   parameters for the given function definition.
287
288   This routine returns a string which is the source form for the entire
289   function formal parameter list.  */
290
291static const char *
292gen_formal_list_for_func_def (fndecl, style)
293     tree fndecl;
294     formals_style style;
295{
296  const char *formal_list = "";
297  tree formal_decl;
298
299  formal_decl = DECL_ARGUMENTS (fndecl);
300  while (formal_decl)
301    {
302      const char *this_formal;
303
304      if (*formal_list && ((style == ansi) || (style == k_and_r_names)))
305        formal_list = concat (formal_list, ", ", NULL_PTR);
306      this_formal = gen_decl (formal_decl, 0, style);
307      if (style == k_and_r_decls)
308        formal_list = concat (formal_list, this_formal, "; ", NULL_PTR);
309      else
310        formal_list = concat (formal_list, this_formal, NULL_PTR);
311      formal_decl = TREE_CHAIN (formal_decl);
312    }
313  if (style == ansi)
314    {
315      if (!DECL_ARGUMENTS (fndecl))
316        formal_list = concat (formal_list, "void", NULL_PTR);
317      if (deserves_ellipsis (TREE_TYPE (fndecl)))
318        formal_list = concat (formal_list, ", ...", NULL_PTR);
319    }
320  if ((style == ansi) || (style == k_and_r_names))
321    formal_list = concat (" (", formal_list, ")", NULL_PTR);
322  return formal_list;
323}
324
325/* Generate a string which is the source code form for a given type (t).  This
326   routine is ugly and complex because the C syntax for declarations is ugly
327   and complex.  This routine is straightforward so long as *no* pointer types,
328   array types, or function types are involved.
329
330   In the simple cases, this routine will return the (string) value which was
331   passed in as the "ret_val" argument.  Usually, this starts out either as an
332   empty string, or as the name of the declared item (i.e. the formal function
333   parameter variable).
334
335   This routine will also return with the global variable "data_type" set to
336   some string value which is the "basic" data-type of the given complete type.
337   This "data_type" string can be concatenated onto the front of the returned
338   string after this routine returns to its caller.
339
340   In complicated cases involving pointer types, array types, or function
341   types, the C declaration syntax requires an "inside out" approach, i.e. if
342   you have a type which is a "pointer-to-function" type, you need to handle
343   the "pointer" part first, but it also has to be "innermost" (relative to
344   the declaration stuff for the "function" type).  Thus, is this case, you
345   must prepend a "(*" and append a ")" to the name of the item (i.e. formal
346   variable).  Then you must append and prepend the other info for the
347   "function type" part of the overall type.
348
349   To handle the "innermost precedence" rules of complicated C declarators, we
350   do the following (in this routine).  The input parameter called "ret_val"
351   is treated as a "seed".  Each time gen_type is called (perhaps recursively)
352   some additional strings may be appended or prepended (or both) to the "seed"
353   string.  If yet another (lower) level of the GCC tree exists for the given
354   type (as in the case of a pointer type, an array type, or a function type)
355   then the (wrapped) seed is passed to a (recursive) invocation of gen_type()
356   this recursive invocation may again "wrap" the (new) seed with yet more
357   declarator stuff, by appending, prepending (or both).  By the time the
358   recursion bottoms out, the "seed value" at that point will have a value
359   which is (almost) the complete source version of the declarator (except
360   for the data_type info).  Thus, this deepest "seed" value is simply passed
361   back up through all of the recursive calls until it is given (as the return
362   value) to the initial caller of the gen_type() routine.  All that remains
363   to do at this point is for the initial caller to prepend the "data_type"
364   string onto the returned "seed".  */
365
366static const char *
367gen_type (ret_val, t, style)
368     const char *ret_val;
369     tree t;
370     formals_style style;
371{
372  tree chain_p;
373
374  /* If there is a typedef name for this type, use it.  */
375  if (TYPE_NAME (t) && TREE_CODE (TYPE_NAME (t)) == TYPE_DECL)
376    data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
377  else
378    {
379      switch (TREE_CODE (t))
380        {
381        case POINTER_TYPE:
382          if (TYPE_READONLY (t))
383            ret_val = concat ("const ", ret_val, NULL_PTR);
384          if (TYPE_VOLATILE (t))
385            ret_val = concat ("volatile ", ret_val, NULL_PTR);
386
387          ret_val = concat ("*", ret_val, NULL_PTR);
388
389	  if (TREE_CODE (TREE_TYPE (t)) == ARRAY_TYPE || TREE_CODE (TREE_TYPE (t)) == FUNCTION_TYPE)
390	    ret_val = concat ("(", ret_val, ")", NULL_PTR);
391
392          ret_val = gen_type (ret_val, TREE_TYPE (t), style);
393
394          return ret_val;
395
396        case ARRAY_TYPE:
397	  if (TYPE_SIZE (t) == 0 || TREE_CODE (TYPE_SIZE (t)) != INTEGER_CST)
398	    ret_val = gen_type (concat (ret_val, "[]", NULL_PTR),
399				TREE_TYPE (t), style);
400	  else if (int_size_in_bytes (t) == 0)
401	    ret_val = gen_type (concat (ret_val, "[0]", NULL_PTR),
402				TREE_TYPE (t), style);
403	  else
404	    {
405	      int size = (int_size_in_bytes (t) / int_size_in_bytes (TREE_TYPE (t)));
406	      char buff[10];
407	      sprintf (buff, "[%d]", size);
408	      ret_val = gen_type (concat (ret_val, buff, NULL_PTR),
409				  TREE_TYPE (t), style);
410	    }
411          break;
412
413        case FUNCTION_TYPE:
414          ret_val = gen_type (concat (ret_val,
415				      gen_formal_list_for_type (t, style),
416				      NULL_PTR),
417			      TREE_TYPE (t), style);
418          break;
419
420        case IDENTIFIER_NODE:
421          data_type = IDENTIFIER_POINTER (t);
422          break;
423
424	/* The following three cases are complicated by the fact that a
425           user may do something really stupid, like creating a brand new
426           "anonymous" type specification in a formal argument list (or as
427           part of a function return type specification).  For example:
428
429		int f (enum { red, green, blue } color);
430
431	   In such cases, we have no name that we can put into the prototype
432	   to represent the (anonymous) type.  Thus, we have to generate the
433	   whole darn type specification.  Yuck!  */
434
435        case RECORD_TYPE:
436	  if (TYPE_NAME (t))
437	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
438	  else
439	    {
440	      data_type = "";
441	      chain_p = TYPE_FIELDS (t);
442	      while (chain_p)
443		{
444		  data_type = concat (data_type, gen_decl (chain_p, 0, ansi),
445				      NULL_PTR);
446		  chain_p = TREE_CHAIN (chain_p);
447		  data_type = concat (data_type, "; ", NULL_PTR);
448		}
449	      data_type = concat ("{ ", data_type, "}", NULL_PTR);
450	    }
451	  data_type = concat ("struct ", data_type, NULL_PTR);
452	  break;
453
454        case UNION_TYPE:
455	  if (TYPE_NAME (t))
456	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
457	  else
458	    {
459	      data_type = "";
460	      chain_p = TYPE_FIELDS (t);
461	      while (chain_p)
462		{
463		  data_type = concat (data_type, gen_decl (chain_p, 0, ansi),
464				      NULL_PTR);
465		  chain_p = TREE_CHAIN (chain_p);
466		  data_type = concat (data_type, "; ", NULL_PTR);
467		}
468	      data_type = concat ("{ ", data_type, "}", NULL_PTR);
469	    }
470	  data_type = concat ("union ", data_type, NULL_PTR);
471	  break;
472
473        case ENUMERAL_TYPE:
474	  if (TYPE_NAME (t))
475	    data_type = IDENTIFIER_POINTER (TYPE_NAME (t));
476	  else
477	    {
478	      data_type = "";
479	      chain_p = TYPE_VALUES (t);
480	      while (chain_p)
481		{
482		  data_type = concat (data_type,
483			IDENTIFIER_POINTER (TREE_PURPOSE (chain_p)), NULL_PTR);
484		  chain_p = TREE_CHAIN (chain_p);
485		  if (chain_p)
486		    data_type = concat (data_type, ", ", NULL_PTR);
487		}
488	      data_type = concat ("{ ", data_type, " }", NULL_PTR);
489	    }
490	  data_type = concat ("enum ", data_type, NULL_PTR);
491	  break;
492
493        case TYPE_DECL:
494          data_type = IDENTIFIER_POINTER (DECL_NAME (t));
495          break;
496
497        case INTEGER_TYPE:
498          data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
499          /* Normally, `unsigned' is part of the deal.  Not so if it comes
500    	     with a type qualifier.  */
501          if (TREE_UNSIGNED (t) && TYPE_QUALS (t))
502    	    data_type = concat ("unsigned ", data_type, NULL_PTR);
503	  break;
504
505        case REAL_TYPE:
506          data_type = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (t)));
507          break;
508
509        case VOID_TYPE:
510          data_type = "void";
511          break;
512
513	case ERROR_MARK:
514	  data_type = "[ERROR]";
515	  break;
516
517        default:
518          abort ();
519        }
520    }
521  if (TYPE_READONLY (t))
522    ret_val = concat ("const ", ret_val, NULL_PTR);
523  if (TYPE_VOLATILE (t))
524    ret_val = concat ("volatile ", ret_val, NULL_PTR);
525  if (TYPE_RESTRICT (t))
526    ret_val = concat ("restrict ", ret_val, NULL_PTR);
527  return ret_val;
528}
529
530/* Generate a string (source) representation of an entire entity declaration
531   (using some particular style for function types).
532
533   The given entity may be either a variable or a function.
534
535   If the "is_func_definition" parameter is non-zero, assume that the thing
536   we are generating a declaration for is a FUNCTION_DECL node which is
537   associated with a function definition.  In this case, we can assume that
538   an attached list of DECL nodes for function formal arguments is present.  */
539
540static const char *
541gen_decl (decl, is_func_definition, style)
542     tree decl;
543     int is_func_definition;
544     formals_style style;
545{
546  const char *ret_val;
547
548  if (DECL_NAME (decl))
549    ret_val = IDENTIFIER_POINTER (DECL_NAME (decl));
550  else
551    ret_val = "";
552
553  /* If we are just generating a list of names of formal parameters, we can
554     simply return the formal parameter name (with no typing information
555     attached to it) now.  */
556
557  if (style == k_and_r_names)
558    return ret_val;
559
560  /* Note that for the declaration of some entity (either a function or a
561     data object, like for instance a parameter) if the entity itself was
562     declared as either const or volatile, then const and volatile properties
563     are associated with just the declaration of the entity, and *not* with
564     the `type' of the entity.  Thus, for such declared entities, we have to
565     generate the qualifiers here.  */
566
567  if (TREE_THIS_VOLATILE (decl))
568    ret_val = concat ("volatile ", ret_val, NULL_PTR);
569  if (TREE_READONLY (decl))
570    ret_val = concat ("const ", ret_val, NULL_PTR);
571
572  data_type = "";
573
574  /* For FUNCTION_DECL nodes, there are two possible cases here.  First, if
575     this FUNCTION_DECL node was generated from a function "definition", then
576     we will have a list of DECL_NODE's, one for each of the function's formal
577     parameters.  In this case, we can print out not only the types of each
578     formal, but also each formal's name.  In the second case, this
579     FUNCTION_DECL node came from an actual function declaration (and *not*
580     a definition).  In this case, we do nothing here because the formal
581     argument type-list will be output later, when the "type" of the function
582     is added to the string we are building.  Note that the ANSI-style formal
583     parameter list is considered to be a (suffix) part of the "type" of the
584     function.  */
585
586  if (TREE_CODE (decl) == FUNCTION_DECL && is_func_definition)
587    {
588      ret_val = concat (ret_val, gen_formal_list_for_func_def (decl, ansi),
589			NULL_PTR);
590
591      /* Since we have already added in the formals list stuff, here we don't
592         add the whole "type" of the function we are considering (which
593         would include its parameter-list info), rather, we only add in
594         the "type" of the "type" of the function, which is really just
595         the return-type of the function (and does not include the parameter
596         list info).  */
597
598      ret_val = gen_type (ret_val, TREE_TYPE (TREE_TYPE (decl)), style);
599    }
600  else
601    ret_val = gen_type (ret_val, TREE_TYPE (decl), style);
602
603  ret_val = affix_data_type (ret_val);
604
605  if (TREE_CODE (decl) != FUNCTION_DECL && DECL_REGISTER (decl))
606    ret_val = concat ("register ", ret_val, NULL_PTR);
607  if (TREE_PUBLIC (decl))
608    ret_val = concat ("extern ", ret_val, NULL_PTR);
609  if (TREE_CODE (decl) == FUNCTION_DECL && !TREE_PUBLIC (decl))
610    ret_val = concat ("static ", ret_val, NULL_PTR);
611
612  return ret_val;
613}
614
615extern FILE *aux_info_file;
616
617/* Generate and write a new line of info to the aux-info (.X) file.  This
618   routine is called once for each function declaration, and once for each
619   function definition (even the implicit ones).  */
620
621void
622gen_aux_info_record (fndecl, is_definition, is_implicit, is_prototyped)
623     tree fndecl;
624     int is_definition;
625     int is_implicit;
626     int is_prototyped;
627{
628  if (flag_gen_aux_info)
629    {
630      static int compiled_from_record = 0;
631
632      /* Each output .X file must have a header line.  Write one now if we
633	 have not yet done so.  */
634
635      if (! compiled_from_record++)
636	{
637	  /* The first line tells which directory file names are relative to.
638	     Currently, -aux-info works only for files in the working
639	     directory, so just use a `.' as a placeholder for now.  */
640	  fprintf (aux_info_file, "/* compiled from: . */\n");
641	}
642
643      /* Write the actual line of auxiliary info.  */
644
645      fprintf (aux_info_file, "/* %s:%d:%c%c */ %s;",
646	       DECL_SOURCE_FILE (fndecl),
647	       DECL_SOURCE_LINE (fndecl),
648	       (is_implicit) ? 'I' : (is_prototyped) ? 'N' : 'O',
649	       (is_definition) ? 'F' : 'C',
650	       gen_decl (fndecl, is_definition, ansi));
651
652      /* If this is an explicit function declaration, we need to also write
653	 out an old-style (i.e. K&R) function header, just in case the user
654	 wants to run unprotoize.  */
655
656      if (is_definition)
657	{
658	  fprintf (aux_info_file, " /*%s %s*/",
659		   gen_formal_list_for_func_def (fndecl, k_and_r_names),
660		   gen_formal_list_for_func_def (fndecl, k_and_r_decls));
661	}
662
663      fprintf (aux_info_file, "\n");
664    }
665}
666