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