455114c4c17991115a530285bbe56d9e0dfece63
[external/binutils.git] / gdb / compile / compile-c-symbols.c
1 /* Convert symbols from GDB to GCC
2
3    Copyright (C) 2014-2015 Free Software Foundation, Inc.
4
5    This file is part of GDB.
6
7    This program is free software; you can redistribute it and/or modify
8    it under the terms of the GNU General Public License as published by
9    the Free Software Foundation; either version 3 of the License, or
10    (at your option) any later version.
11
12    This program is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
19
20
21 #include "defs.h"
22 #include "compile-internal.h"
23 #include "gdb_assert.h"
24 #include "symtab.h"
25 #include "parser-defs.h"
26 #include "block.h"
27 #include "objfiles.h"
28 #include "compile.h"
29 #include "value.h"
30 #include "exceptions.h"
31 #include "gdbtypes.h"
32 #include "dwarf2loc.h"
33
34 \f
35
36 /* Object of this type are stored in the compiler's symbol_err_map.  */
37
38 struct symbol_error
39 {
40   /* The symbol.  */
41
42   const struct symbol *sym;
43
44   /* The error message to emit.  This is malloc'd and owned by the
45      hash table.  */
46
47   char *message;
48 };
49
50 /* Hash function for struct symbol_error.  */
51
52 static hashval_t
53 hash_symbol_error (const void *a)
54 {
55   const struct symbol_error *se = a;
56
57   return htab_hash_pointer (se->sym);
58 }
59
60 /* Equality function for struct symbol_error.  */
61
62 static int
63 eq_symbol_error (const void *a, const void *b)
64 {
65   const struct symbol_error *sea = a;
66   const struct symbol_error *seb = b;
67
68   return sea->sym == seb->sym;
69 }
70
71 /* Deletion function for struct symbol_error.  */
72
73 static void
74 del_symbol_error (void *a)
75 {
76   struct symbol_error *se = a;
77
78   xfree (se->message);
79   xfree (se);
80 }
81
82 /* Associate SYMBOL with some error text.  */
83
84 static void
85 insert_symbol_error (htab_t hash, const struct symbol *sym, const char *text)
86 {
87   struct symbol_error e;
88   void **slot;
89
90   e.sym = sym;
91   slot = htab_find_slot (hash, &e, INSERT);
92   if (*slot == NULL)
93     {
94       struct symbol_error *e = XNEW (struct symbol_error);
95
96       e->sym = sym;
97       e->message = xstrdup (text);
98       *slot = e;
99     }
100 }
101
102 /* Emit the error message corresponding to SYM, if one exists, and
103    arrange for it not to be emitted again.  */
104
105 static void
106 error_symbol_once (struct compile_c_instance *context,
107                    const struct symbol *sym)
108 {
109   struct symbol_error search;
110   struct symbol_error *err;
111   char *message;
112
113   if (context->symbol_err_map == NULL)
114     return;
115
116   search.sym = sym;
117   err = htab_find (context->symbol_err_map, &search);
118   if (err == NULL || err->message == NULL)
119     return;
120
121   message = err->message;
122   err->message = NULL;
123   make_cleanup (xfree, message);
124   error (_("%s"), message);
125 }
126
127 \f
128
129 /* Compute the name of the pointer representing a local symbol's
130    address.  */
131
132 static char *
133 symbol_substitution_name (struct symbol *sym)
134 {
135   return concat ("__", SYMBOL_NATURAL_NAME (sym), "_ptr", (char *) NULL);
136 }
137
138 /* Convert a given symbol, SYM, to the compiler's representation.
139    CONTEXT is the compiler instance.  IS_GLOBAL is true if the
140    symbol came from the global scope.  IS_LOCAL is true if the symbol
141    came from a local scope.  (Note that the two are not strictly
142    inverses because the symbol might have come from the static
143    scope.)  */
144
145 static void
146 convert_one_symbol (struct compile_c_instance *context,
147                     struct symbol *sym,
148                     int is_global,
149                     int is_local)
150 {
151   gcc_type sym_type;
152   const char *filename = symbol_symtab (sym)->filename;
153   unsigned short line = SYMBOL_LINE (sym);
154
155   error_symbol_once (context, sym);
156
157   if (SYMBOL_CLASS (sym) == LOC_LABEL)
158     sym_type = 0;
159   else
160     sym_type = convert_type (context, SYMBOL_TYPE (sym));
161
162   if (SYMBOL_DOMAIN (sym) == STRUCT_DOMAIN)
163     {
164       /* Binding a tag, so we don't need to build a decl.  */
165       C_CTX (context)->c_ops->tagbind (C_CTX (context),
166                                        SYMBOL_NATURAL_NAME (sym),
167                                        sym_type, filename, line);
168     }
169   else
170     {
171       gcc_decl decl;
172       enum gcc_c_symbol_kind kind;
173       CORE_ADDR addr = 0;
174       char *symbol_name = NULL;
175
176       switch (SYMBOL_CLASS (sym))
177         {
178         case LOC_TYPEDEF:
179           kind = GCC_C_SYMBOL_TYPEDEF;
180           break;
181
182         case LOC_LABEL:
183           kind = GCC_C_SYMBOL_LABEL;
184           addr = SYMBOL_VALUE_ADDRESS (sym);
185           break;
186
187         case LOC_BLOCK:
188           kind = GCC_C_SYMBOL_FUNCTION;
189           addr = BLOCK_START (SYMBOL_BLOCK_VALUE (sym));
190           if (is_global && TYPE_GNU_IFUNC (SYMBOL_TYPE (sym)))
191             addr = gnu_ifunc_resolve_addr (target_gdbarch (), addr);
192           break;
193
194         case LOC_CONST:
195           if (TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_ENUM)
196             {
197               /* Already handled by convert_enum.  */
198               return;
199             }
200           C_CTX (context)->c_ops->build_constant (C_CTX (context), sym_type,
201                                                   SYMBOL_NATURAL_NAME (sym),
202                                                   SYMBOL_VALUE (sym),
203                                                   filename, line);
204           return;
205
206         case LOC_CONST_BYTES:
207           error (_("Unsupported LOC_CONST_BYTES for symbol \"%s\"."),
208                  SYMBOL_PRINT_NAME (sym));
209
210         case LOC_UNDEF:
211           internal_error (__FILE__, __LINE__, _("LOC_UNDEF found for \"%s\"."),
212                           SYMBOL_PRINT_NAME (sym));
213
214         case LOC_COMMON_BLOCK:
215           error (_("Fortran common block is unsupported for compilation "
216                    "evaluaton of symbol \"%s\"."),
217                  SYMBOL_PRINT_NAME (sym));
218
219         case LOC_OPTIMIZED_OUT:
220           error (_("Symbol \"%s\" cannot be used for compilation evaluation "
221                    "as it is optimized out."),
222                  SYMBOL_PRINT_NAME (sym));
223
224         case LOC_COMPUTED:
225           if (is_local)
226             goto substitution;
227           /* Probably TLS here.  */
228           warning (_("Symbol \"%s\" is thread-local and currently can only "
229                      "be referenced from the current thread in "
230                      "compiled code."),
231                    SYMBOL_PRINT_NAME (sym));
232           /* FALLTHROUGH */
233         case LOC_UNRESOLVED:
234           /* 'symbol_name' cannot be used here as that one is used only for
235              local variables from compile_dwarf_expr_to_c.
236              Global variables can be accessed by GCC only by their address, not
237              by their name.  */
238           {
239             struct value *val;
240             struct frame_info *frame = NULL;
241
242             if (symbol_read_needs_frame (sym))
243               {
244                 frame = get_selected_frame (NULL);
245                 if (frame == NULL)
246                   error (_("Symbol \"%s\" cannot be used because "
247                            "there is no selected frame"),
248                          SYMBOL_PRINT_NAME (sym));
249               }
250
251             val = read_var_value (sym, frame);
252             if (VALUE_LVAL (val) != lval_memory)
253               error (_("Symbol \"%s\" cannot be used for compilation "
254                        "evaluation as its address has not been found."),
255                      SYMBOL_PRINT_NAME (sym));
256
257             kind = GCC_C_SYMBOL_VARIABLE;
258             addr = value_address (val);
259           }
260           break;
261
262
263         case LOC_REGISTER:
264         case LOC_ARG:
265         case LOC_REF_ARG:
266         case LOC_REGPARM_ADDR:
267         case LOC_LOCAL:
268         substitution:
269           kind = GCC_C_SYMBOL_VARIABLE;
270           symbol_name = symbol_substitution_name (sym);
271           break;
272
273         case LOC_STATIC:
274           kind = GCC_C_SYMBOL_VARIABLE;
275           addr = SYMBOL_VALUE_ADDRESS (sym);
276           break;
277
278         case LOC_FINAL_VALUE:
279         default:
280           gdb_assert_not_reached ("Unreachable case in convert_one_symbol.");
281
282         }
283
284       /* Don't emit local variable decls for a raw expression.  */
285       if (context->base.scope != COMPILE_I_RAW_SCOPE
286           || symbol_name == NULL)
287         {
288           decl = C_CTX (context)->c_ops->build_decl (C_CTX (context),
289                                                      SYMBOL_NATURAL_NAME (sym),
290                                                      kind,
291                                                      sym_type,
292                                                      symbol_name, addr,
293                                                      filename, line);
294
295           C_CTX (context)->c_ops->bind (C_CTX (context), decl, is_global);
296         }
297
298       xfree (symbol_name);
299     }
300 }
301
302 /* Convert a full symbol to its gcc form.  CONTEXT is the compiler to
303    use, IDENTIFIER is the name of the symbol, SYM is the symbol
304    itself, and DOMAIN is the domain which was searched.  */
305
306 static void
307 convert_symbol_sym (struct compile_c_instance *context, const char *identifier,
308                     struct symbol *sym, domain_enum domain)
309 {
310   const struct block *static_block, *found_block;
311   int is_local_symbol;
312
313   found_block = block_found;
314
315   /* If we found a symbol and it is not in the  static or global
316      scope, then we should first convert any static or global scope
317      symbol of the same name.  This lets this unusual case work:
318
319      int x; // Global.
320      int func(void)
321      {
322      int x;
323      // At this spot, evaluate "extern int x; x"
324      }
325   */
326
327   static_block = block_static_block (found_block);
328   /* STATIC_BLOCK is NULL if FOUND_BLOCK is the global block.  */
329   is_local_symbol = (found_block != static_block && static_block != NULL);
330   if (is_local_symbol)
331     {
332       struct symbol *global_sym;
333
334       global_sym = lookup_symbol (identifier, NULL, domain, NULL);
335       /* If the outer symbol is in the static block, we ignore it, as
336          it cannot be referenced.  */
337       if (global_sym != NULL
338           && block_found != block_static_block (block_found))
339         {
340           if (compile_debug)
341             fprintf_unfiltered (gdb_stdlog,
342                                 "gcc_convert_symbol \"%s\": global symbol\n",
343                                 identifier);
344           convert_one_symbol (context, global_sym, 1, 0);
345         }
346     }
347
348   if (compile_debug)
349     fprintf_unfiltered (gdb_stdlog,
350                         "gcc_convert_symbol \"%s\": local symbol\n",
351                         identifier);
352   convert_one_symbol (context, sym, 0, is_local_symbol);
353 }
354
355 /* Convert a minimal symbol to its gcc form.  CONTEXT is the compiler
356    to use and BMSYM is the minimal symbol to convert.  */
357
358 static void
359 convert_symbol_bmsym (struct compile_c_instance *context,
360                       struct bound_minimal_symbol bmsym)
361 {
362   struct minimal_symbol *msym = bmsym.minsym;
363   struct objfile *objfile = bmsym.objfile;
364   struct type *type;
365   enum gcc_c_symbol_kind kind;
366   gcc_type sym_type;
367   gcc_decl decl;
368   CORE_ADDR addr;
369
370   addr = MSYMBOL_VALUE_ADDRESS (objfile, msym);
371
372   /* Conversion copied from write_exp_msymbol.  */
373   switch (MSYMBOL_TYPE (msym))
374     {
375     case mst_text:
376     case mst_file_text:
377     case mst_solib_trampoline:
378       type = objfile_type (objfile)->nodebug_text_symbol;
379       kind = GCC_C_SYMBOL_FUNCTION;
380       break;
381
382     case mst_text_gnu_ifunc:
383       /* nodebug_text_gnu_ifunc_symbol would cause:
384          function return type cannot be function  */
385       type = objfile_type (objfile)->nodebug_text_symbol;
386       kind = GCC_C_SYMBOL_FUNCTION;
387       addr = gnu_ifunc_resolve_addr (target_gdbarch (), addr);
388       break;
389
390     case mst_data:
391     case mst_file_data:
392     case mst_bss:
393     case mst_file_bss:
394       type = objfile_type (objfile)->nodebug_data_symbol;
395       kind = GCC_C_SYMBOL_VARIABLE;
396       break;
397
398     case mst_slot_got_plt:
399       type = objfile_type (objfile)->nodebug_got_plt_symbol;
400       kind = GCC_C_SYMBOL_FUNCTION;
401       break;
402
403     default:
404       type = objfile_type (objfile)->nodebug_unknown_symbol;
405       kind = GCC_C_SYMBOL_VARIABLE;
406       break;
407     }
408
409   sym_type = convert_type (context, type);
410   decl = C_CTX (context)->c_ops->build_decl (C_CTX (context),
411                                              MSYMBOL_NATURAL_NAME (msym),
412                                              kind, sym_type, NULL, addr,
413                                              NULL, 0);
414   C_CTX (context)->c_ops->bind (C_CTX (context), decl, 1 /* is_global */);
415 }
416
417 /* See compile-internal.h.  */
418
419 void
420 gcc_convert_symbol (void *datum,
421                     struct gcc_c_context *gcc_context,
422                     enum gcc_c_oracle_request request,
423                     const char *identifier)
424 {
425   struct compile_c_instance *context = datum;
426   domain_enum domain;
427   int found = 0;
428
429   switch (request)
430     {
431     case GCC_C_ORACLE_SYMBOL:
432       domain = VAR_DOMAIN;
433       break;
434     case GCC_C_ORACLE_TAG:
435       domain = STRUCT_DOMAIN;
436       break;
437     case GCC_C_ORACLE_LABEL:
438       domain = LABEL_DOMAIN;
439       break;
440     default:
441       gdb_assert_not_reached ("Unrecognized oracle request.");
442     }
443
444   /* We can't allow exceptions to escape out of this callback.  Safest
445      is to simply emit a gcc error.  */
446   TRY
447     {
448       struct symbol *sym;
449
450       sym = lookup_symbol (identifier, context->base.block, domain, NULL);
451       if (sym != NULL)
452         {
453           convert_symbol_sym (context, identifier, sym, domain);
454           found = 1;
455         }
456       else if (domain == VAR_DOMAIN)
457         {
458           struct bound_minimal_symbol bmsym;
459
460           bmsym = lookup_minimal_symbol (identifier, NULL, NULL);
461           if (bmsym.minsym != NULL)
462             {
463               convert_symbol_bmsym (context, bmsym);
464               found = 1;
465             }
466         }
467     }
468
469   CATCH (e, RETURN_MASK_ALL)
470     {
471       C_CTX (context)->c_ops->error (C_CTX (context), e.message);
472     }
473   END_CATCH
474
475   if (compile_debug && !found)
476     fprintf_unfiltered (gdb_stdlog,
477                         "gcc_convert_symbol \"%s\": lookup_symbol failed\n",
478                         identifier);
479   return;
480 }
481
482 /* See compile-internal.h.  */
483
484 gcc_address
485 gcc_symbol_address (void *datum, struct gcc_c_context *gcc_context,
486                     const char *identifier)
487 {
488   struct compile_c_instance *context = datum;
489   gcc_address result = 0;
490   int found = 0;
491
492   /* We can't allow exceptions to escape out of this callback.  Safest
493      is to simply emit a gcc error.  */
494   TRY
495     {
496       struct symbol *sym;
497
498       /* We only need global functions here.  */
499       sym = lookup_symbol (identifier, NULL, VAR_DOMAIN, NULL);
500       if (sym != NULL && SYMBOL_CLASS (sym) == LOC_BLOCK)
501         {
502           if (compile_debug)
503             fprintf_unfiltered (gdb_stdlog,
504                                 "gcc_symbol_address \"%s\": full symbol\n",
505                                 identifier);
506           result = BLOCK_START (SYMBOL_BLOCK_VALUE (sym));
507           if (TYPE_GNU_IFUNC (SYMBOL_TYPE (sym)))
508             result = gnu_ifunc_resolve_addr (target_gdbarch (), result);
509           found = 1;
510         }
511       else
512         {
513           struct bound_minimal_symbol msym;
514
515           msym = lookup_bound_minimal_symbol (identifier);
516           if (msym.minsym != NULL)
517             {
518               if (compile_debug)
519                 fprintf_unfiltered (gdb_stdlog,
520                                     "gcc_symbol_address \"%s\": minimal "
521                                     "symbol\n",
522                                     identifier);
523               result = BMSYMBOL_VALUE_ADDRESS (msym);
524               if (MSYMBOL_TYPE (msym.minsym) == mst_text_gnu_ifunc)
525                 result = gnu_ifunc_resolve_addr (target_gdbarch (), result);
526               found = 1;
527             }
528         }
529     }
530
531   CATCH (e, RETURN_MASK_ERROR)
532     {
533       C_CTX (context)->c_ops->error (C_CTX (context), e.message);
534     }
535   END_CATCH
536
537   if (compile_debug && !found)
538     fprintf_unfiltered (gdb_stdlog,
539                         "gcc_symbol_address \"%s\": failed\n",
540                         identifier);
541   return result;
542 }
543
544 \f
545
546 /* A hash function for symbol names.  */
547
548 static hashval_t
549 hash_symname (const void *a)
550 {
551   const struct symbol *sym = a;
552
553   return htab_hash_string (SYMBOL_NATURAL_NAME (sym));
554 }
555
556 /* A comparison function for hash tables that just looks at symbol
557    names.  */
558
559 static int
560 eq_symname (const void *a, const void *b)
561 {
562   const struct symbol *syma = a;
563   const struct symbol *symb = b;
564
565   return strcmp (SYMBOL_NATURAL_NAME (syma), SYMBOL_NATURAL_NAME (symb)) == 0;
566 }
567
568 /* If a symbol with the same name as SYM is already in HASHTAB, return
569    1.  Otherwise, add SYM to HASHTAB and return 0.  */
570
571 static int
572 symbol_seen (htab_t hashtab, struct symbol *sym)
573 {
574   void **slot;
575
576   slot = htab_find_slot (hashtab, sym, INSERT);
577   if (*slot != NULL)
578     return 1;
579
580   *slot = sym;
581   return 0;
582 }
583
584 /* Generate C code to compute the length of a VLA.  */
585
586 static void
587 generate_vla_size (struct compile_c_instance *compiler,
588                    struct ui_file *stream,
589                    struct gdbarch *gdbarch,
590                    unsigned char *registers_used,
591                    CORE_ADDR pc,
592                    struct type *type,
593                    struct symbol *sym)
594 {
595   type = check_typedef (type);
596
597   if (TYPE_CODE (type) == TYPE_CODE_REF)
598     type = check_typedef (TYPE_TARGET_TYPE (type));
599
600   switch (TYPE_CODE (type))
601     {
602     case TYPE_CODE_RANGE:
603       {
604         if (TYPE_HIGH_BOUND_KIND (type) == PROP_LOCEXPR
605             || TYPE_HIGH_BOUND_KIND (type) == PROP_LOCLIST)
606           {
607             const struct dynamic_prop *prop = &TYPE_RANGE_DATA (type)->high;
608             char *name = c_get_range_decl_name (prop);
609             struct cleanup *cleanup = make_cleanup (xfree, name);
610
611             dwarf2_compile_property_to_c (stream, name,
612                                           gdbarch, registers_used,
613                                           prop, pc, sym);
614             do_cleanups (cleanup);
615           }
616       }
617       break;
618
619     case TYPE_CODE_ARRAY:
620       generate_vla_size (compiler, stream, gdbarch, registers_used, pc,
621                          TYPE_INDEX_TYPE (type), sym);
622       generate_vla_size (compiler, stream, gdbarch, registers_used, pc,
623                          TYPE_TARGET_TYPE (type), sym);
624       break;
625
626     case TYPE_CODE_UNION:
627     case TYPE_CODE_STRUCT:
628       {
629         int i;
630
631         for (i = 0; i < TYPE_NFIELDS (type); ++i)
632           if (!field_is_static (&TYPE_FIELD (type, i)))
633             generate_vla_size (compiler, stream, gdbarch, registers_used, pc,
634                                TYPE_FIELD_TYPE (type, i), sym);
635       }
636       break;
637     }
638 }
639
640 /* Generate C code to compute the address of SYM.  */
641
642 static void
643 generate_c_for_for_one_variable (struct compile_c_instance *compiler,
644                                  struct ui_file *stream,
645                                  struct gdbarch *gdbarch,
646                                  unsigned char *registers_used,
647                                  CORE_ADDR pc,
648                                  struct symbol *sym)
649 {
650
651   TRY
652     {
653       if (is_dynamic_type (SYMBOL_TYPE (sym)))
654         {
655           struct ui_file *size_file = mem_fileopen ();
656           struct cleanup *cleanup = make_cleanup_ui_file_delete (size_file);
657
658           generate_vla_size (compiler, size_file, gdbarch, registers_used, pc,
659                              SYMBOL_TYPE (sym), sym);
660           ui_file_put (size_file, ui_file_write_for_put, stream);
661
662           do_cleanups (cleanup);
663         }
664
665       if (SYMBOL_COMPUTED_OPS (sym) != NULL)
666         {
667           char *generated_name = symbol_substitution_name (sym);
668           struct cleanup *cleanup = make_cleanup (xfree, generated_name);
669           /* We need to emit to a temporary buffer in case an error
670              occurs in the middle.  */
671           struct ui_file *local_file = mem_fileopen ();
672
673           make_cleanup_ui_file_delete (local_file);
674           SYMBOL_COMPUTED_OPS (sym)->generate_c_location (sym, local_file,
675                                                           gdbarch,
676                                                           registers_used,
677                                                           pc, generated_name);
678           ui_file_put (local_file, ui_file_write_for_put, stream);
679
680           do_cleanups (cleanup);
681         }
682       else
683         {
684           switch (SYMBOL_CLASS (sym))
685             {
686             case LOC_REGISTER:
687             case LOC_ARG:
688             case LOC_REF_ARG:
689             case LOC_REGPARM_ADDR:
690             case LOC_LOCAL:
691               error (_("Local symbol unhandled when generating C code."));
692
693             case LOC_COMPUTED:
694               gdb_assert_not_reached (_("LOC_COMPUTED variable "
695                                         "missing a method."));
696
697             default:
698               /* Nothing to do for all other cases, as they don't represent
699                  local variables.  */
700               break;
701             }
702         }
703     }
704
705   CATCH (e, RETURN_MASK_ERROR)
706     {
707       if (compiler->symbol_err_map == NULL)
708         compiler->symbol_err_map = htab_create_alloc (10,
709                                                       hash_symbol_error,
710                                                       eq_symbol_error,
711                                                       del_symbol_error,
712                                                       xcalloc,
713                                                       xfree);
714       insert_symbol_error (compiler->symbol_err_map, sym, e.message);
715     }
716   END_CATCH
717 }
718
719 /* See compile-internal.h.  */
720
721 unsigned char *
722 generate_c_for_variable_locations (struct compile_c_instance *compiler,
723                                    struct ui_file *stream,
724                                    struct gdbarch *gdbarch,
725                                    const struct block *block,
726                                    CORE_ADDR pc)
727 {
728   struct cleanup *cleanup, *outer;
729   htab_t symhash;
730   const struct block *static_block = block_static_block (block);
731   unsigned char *registers_used;
732
733   /* If we're already in the static or global block, there is nothing
734      to write.  */
735   if (static_block == NULL || block == static_block)
736     return NULL;
737
738   registers_used = XCNEWVEC (unsigned char, gdbarch_num_regs (gdbarch));
739   outer = make_cleanup (xfree, registers_used);
740
741   /* Ensure that a given name is only entered once.  This reflects the
742      reality of shadowing.  */
743   symhash = htab_create_alloc (1, hash_symname, eq_symname, NULL,
744                                xcalloc, xfree);
745   cleanup = make_cleanup_htab_delete (symhash);
746
747   while (1)
748     {
749       struct symbol *sym;
750       struct block_iterator iter;
751
752       /* Iterate over symbols in this block, generating code to
753          compute the location of each local variable.  */
754       for (sym = block_iterator_first (block, &iter);
755            sym != NULL;
756            sym = block_iterator_next (&iter))
757         {
758           if (!symbol_seen (symhash, sym))
759             generate_c_for_for_one_variable (compiler, stream, gdbarch,
760                                              registers_used, pc, sym);
761         }
762
763       /* If we just finished the outermost block of a function, we're
764          done.  */
765       if (BLOCK_FUNCTION (block) != NULL)
766         break;
767       block = BLOCK_SUPERBLOCK (block);
768     }
769
770   do_cleanups (cleanup);
771   discard_cleanups (outer);
772   return registers_used;
773 }