Move innermost_block_tracker global to parse_state
[deliverable/binutils-gdb.git] / gdb / ada-lang.c
index 7ff00a01475c786ecb76d2d5c3e74f28f2a4127d..51615dcd36132b9a1fdc71ebb46113d079f86920 100644 (file)
@@ -1,6 +1,6 @@
 /* Ada language support routines for GDB, the GNU debugger.
 
-   Copyright (C) 1992-2018 Free Software Foundation, Inc.
+   Copyright (C) 1992-2019 Free Software Foundation, Inc.
 
    This file is part of GDB.
 
@@ -49,9 +49,9 @@
 #include "valprint.h"
 #include "source.h"
 #include "observable.h"
-#include "vec.h"
+#include "common/vec.h"
 #include "stack.h"
-#include "gdb_vecs.h"
+#include "common/gdb_vecs.h"
 #include "typeprint.h"
 #include "namespace.h"
 
@@ -125,7 +125,8 @@ static int num_defns_collected (struct obstack *);
 static struct block_symbol *defns_collected (struct obstack *, int);
 
 static struct value *resolve_subexp (expression_up *, int *, int,
-                                     struct type *);
+                                     struct type *, int,
+                                    innermost_block_tracker *);
 
 static void replace_operator_with_call (expression_up *, int, int, int,
                                         struct symbol *, const struct block *);
@@ -190,8 +191,6 @@ static int ada_is_unconstrained_packed_array_type (struct type *);
 static struct value *value_subscript_packed (struct value *, int,
                                              struct value **);
 
-static void move_bits (gdb_byte *, int, const gdb_byte *, int, int, int);
-
 static struct value *coerce_unspec_val_to_type (struct value *,
                                                 struct type *);
 
@@ -227,7 +226,7 @@ static int find_struct_field (const char *, struct type *, int,
 
 static int ada_resolve_function (struct block_symbol *, int,
                                  struct value **, int, const char *,
-                                 struct type *);
+                                 struct type *, int);
 
 static int ada_is_direct_array_type (struct type *);
 
@@ -2669,72 +2668,6 @@ ada_value_primitive_packed_val (struct value *obj, const gdb_byte *valaddr,
   return v;
 }
 
-/* Move N bits from SOURCE, starting at bit offset SRC_OFFSET to
-   TARGET, starting at bit offset TARG_OFFSET.  SOURCE and TARGET must
-   not overlap.  */
-static void
-move_bits (gdb_byte *target, int targ_offset, const gdb_byte *source,
-          int src_offset, int n, int bits_big_endian_p)
-{
-  unsigned int accum, mask;
-  int accum_bits, chunk_size;
-
-  target += targ_offset / HOST_CHAR_BIT;
-  targ_offset %= HOST_CHAR_BIT;
-  source += src_offset / HOST_CHAR_BIT;
-  src_offset %= HOST_CHAR_BIT;
-  if (bits_big_endian_p)
-    {
-      accum = (unsigned char) *source;
-      source += 1;
-      accum_bits = HOST_CHAR_BIT - src_offset;
-
-      while (n > 0)
-        {
-          int unused_right;
-
-          accum = (accum << HOST_CHAR_BIT) + (unsigned char) *source;
-          accum_bits += HOST_CHAR_BIT;
-          source += 1;
-          chunk_size = HOST_CHAR_BIT - targ_offset;
-          if (chunk_size > n)
-            chunk_size = n;
-          unused_right = HOST_CHAR_BIT - (chunk_size + targ_offset);
-          mask = ((1 << chunk_size) - 1) << unused_right;
-          *target =
-            (*target & ~mask)
-            | ((accum >> (accum_bits - chunk_size - unused_right)) & mask);
-          n -= chunk_size;
-          accum_bits -= chunk_size;
-          target += 1;
-          targ_offset = 0;
-        }
-    }
-  else
-    {
-      accum = (unsigned char) *source >> src_offset;
-      source += 1;
-      accum_bits = HOST_CHAR_BIT - src_offset;
-
-      while (n > 0)
-        {
-          accum = accum + ((unsigned char) *source << accum_bits);
-          accum_bits += HOST_CHAR_BIT;
-          source += 1;
-          chunk_size = HOST_CHAR_BIT - targ_offset;
-          if (chunk_size > n)
-            chunk_size = n;
-          mask = ((1 << chunk_size) - 1) << targ_offset;
-          *target = (*target & ~mask) | ((accum << targ_offset) & mask);
-          n -= chunk_size;
-          accum_bits -= chunk_size;
-          accum >>= chunk_size;
-          target += 1;
-          targ_offset = 0;
-        }
-    }
-}
-
 /* Store the contents of FROMVAL into the location of TOVAL.
    Return a new value with the location of TOVAL and contents of
    FROMVAL.   Handles assignment into packed fields that have
@@ -2777,11 +2710,11 @@ ada_value_assign (struct value *toval, struct value *fromval)
       if (from_size == 0)
        from_size = TYPE_LENGTH (value_type (fromval)) * TARGET_CHAR_BIT;
       if (gdbarch_bits_big_endian (get_type_arch (type)))
-        move_bits (buffer, value_bitpos (toval),
-                  value_contents (fromval), from_size - bits, bits, 1);
+        copy_bitwise (buffer, value_bitpos (toval),
+                     value_contents (fromval), from_size - bits, bits, 1);
       else
-        move_bits (buffer, value_bitpos (toval),
-                  value_contents (fromval), 0, bits, 0);
+        copy_bitwise (buffer, value_bitpos (toval),
+                     value_contents (fromval), 0, bits, 0);
       write_memory_with_notification (to_addr, buffer, len);
 
       val = value_copy (toval);
@@ -2833,14 +2766,14 @@ value_assign_to_component (struct value *container, struct value *component,
          = TYPE_LENGTH (value_type (component)) * TARGET_CHAR_BIT - bits;
       else
        src_offset = 0;
-      move_bits (value_contents_writeable (container) + offset_in_container,
-                value_bitpos (container) + bit_offset_in_container,
-                value_contents (val), src_offset, bits, 1);
+      copy_bitwise (value_contents_writeable (container) + offset_in_container,
+                   value_bitpos (container) + bit_offset_in_container,
+                   value_contents (val), src_offset, bits, 1);
     }
   else
-    move_bits (value_contents_writeable (container) + offset_in_container,
-              value_bitpos (container) + bit_offset_in_container,
-              value_contents (val), 0, bits, 0);
+    copy_bitwise (value_contents_writeable (container) + offset_in_container,
+                 value_bitpos (container) + bit_offset_in_container,
+                 value_contents (val), 0, bits, 0);
 }
 
 /* Determine if TYPE is an access to an unconstrained array.  */
@@ -3241,16 +3174,18 @@ ada_array_length (struct value *arr, int n)
   return high - low + 1;
 }
 
-/* An empty array whose type is that of ARR_TYPE (an array type),
-   with bounds LOW to LOW-1.  */
+/* An array whose type is that of ARR_TYPE (an array type), with
+   bounds LOW to HIGH, but whose contents are unimportant.  If HIGH is
+   less than LOW, then LOW-1 is used.  */
 
 static struct value *
-empty_array (struct type *arr_type, int low)
+empty_array (struct type *arr_type, int low, int high)
 {
   struct type *arr_type0 = ada_check_typedef (arr_type);
   struct type *index_type
     = create_static_range_type
-        (NULL, TYPE_TARGET_TYPE (TYPE_INDEX_TYPE (arr_type0)),  low, low - 1);
+        (NULL, TYPE_TARGET_TYPE (TYPE_INDEX_TYPE (arr_type0)), low,
+        high < low ? low - 1 : high);
   struct type *elt_type = ada_array_element_type (arr_type0, 1);
 
   return allocate_value (create_array_type (NULL, elt_type, index_type));
@@ -3286,7 +3221,8 @@ ada_decoded_op_name (enum exp_opcode op)
    return type is preferred.  May change (expand) *EXP.  */
 
 static void
-resolve (expression_up *expp, int void_context_p)
+resolve (expression_up *expp, int void_context_p, int parse_completion,
+        innermost_block_tracker *tracker)
 {
   struct type *context_type = NULL;
   int pc = 0;
@@ -3294,7 +3230,7 @@ resolve (expression_up *expp, int void_context_p)
   if (void_context_p)
     context_type = builtin_type ((*expp)->gdbarch)->builtin_void;
 
-  resolve_subexp (expp, &pc, 1, context_type);
+  resolve_subexp (expp, &pc, 1, context_type, parse_completion, tracker);
 }
 
 /* Resolve the operator of the subexpression beginning at
@@ -3308,7 +3244,8 @@ resolve (expression_up *expp, int void_context_p)
 
 static struct value *
 resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
-                struct type *context_type)
+                struct type *context_type, int parse_completion,
+               innermost_block_tracker *tracker)
 {
   int pc = *pos;
   int i;
@@ -3333,19 +3270,20 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
       else
         {
           *pos += 3;
-          resolve_subexp (expp, pos, 0, NULL);
+          resolve_subexp (expp, pos, 0, NULL, parse_completion, tracker);
         }
       nargs = longest_to_int (exp->elts[pc + 1].longconst);
       break;
 
     case UNOP_ADDR:
       *pos += 1;
-      resolve_subexp (expp, pos, 0, NULL);
+      resolve_subexp (expp, pos, 0, NULL, parse_completion, tracker);
       break;
 
     case UNOP_QUAL:
       *pos += 3;
-      resolve_subexp (expp, pos, 1, check_typedef (exp->elts[pc + 1].type));
+      resolve_subexp (expp, pos, 1, check_typedef (exp->elts[pc + 1].type),
+                     parse_completion, tracker);
       break;
 
     case OP_ATR_MODULUS:
@@ -3376,11 +3314,12 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
         struct value *arg1;
 
         *pos += 1;
-        arg1 = resolve_subexp (expp, pos, 0, NULL);
+        arg1 = resolve_subexp (expp, pos, 0, NULL, parse_completion, tracker);
         if (arg1 == NULL)
-          resolve_subexp (expp, pos, 1, NULL);
+          resolve_subexp (expp, pos, 1, NULL, parse_completion, tracker);
         else
-          resolve_subexp (expp, pos, 1, value_type (arg1));
+          resolve_subexp (expp, pos, 1, value_type (arg1), parse_completion,
+                         tracker);
         break;
       }
 
@@ -3468,7 +3407,8 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
 
   argvec = XALLOCAVEC (struct value *, nargs + 1);
   for (i = 0; i < nargs; i += 1)
-    argvec[i] = resolve_subexp (expp, pos, 1, NULL);
+    argvec[i] = resolve_subexp (expp, pos, 1, NULL, parse_completion,
+                               tracker);
   argvec[i] = NULL;
   exp = expp->get ();
 
@@ -3537,7 +3477,7 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
               i = ada_resolve_function
                 (candidates.data (), n_candidates, NULL, 0,
                  SYMBOL_LINKAGE_NAME (exp->elts[pc + 2].symbol),
-                 context_type);
+                 context_type, parse_completion);
               if (i < 0)
                 error (_("Could not find a match for %s"),
                        SYMBOL_PRINT_NAME (exp->elts[pc + 2].symbol));
@@ -3552,7 +3492,7 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
 
           exp->elts[pc + 1].block = candidates[i].block;
           exp->elts[pc + 2].symbol = candidates[i].symbol;
-         innermost_block.update (candidates[i]);
+         tracker->update (candidates[i]);
         }
 
       if (deprocedure_p
@@ -3588,7 +3528,7 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
                   (candidates.data (), n_candidates,
                    argvec, nargs,
                    SYMBOL_LINKAGE_NAME (exp->elts[pc + 5].symbol),
-                   context_type);
+                   context_type, parse_completion);
                 if (i < 0)
                   error (_("Could not find a match for %s"),
                          SYMBOL_PRINT_NAME (exp->elts[pc + 5].symbol));
@@ -3596,7 +3536,7 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
 
             exp->elts[pc + 4].block = candidates[i].block;
             exp->elts[pc + 5].symbol = candidates[i].symbol;
-           innermost_block.update (candidates[i]);
+           tracker->update (candidates[i]);
           }
       }
       break;
@@ -3628,11 +3568,12 @@ resolve_subexp (expression_up *expp, int *pos, int deprocedure_p,
 
           n_candidates =
             ada_lookup_symbol_list (ada_decoded_op_name (op),
-                                    (struct block *) NULL, VAR_DOMAIN,
+                                   NULL, VAR_DOMAIN,
                                     &candidates);
 
           i = ada_resolve_function (candidates.data (), n_candidates, argvec,
-                                   nargs, ada_decoded_op_name (op), NULL);
+                                   nargs, ada_decoded_op_name (op), NULL,
+                                   parse_completion);
           if (i < 0)
             break;
 
@@ -3799,7 +3740,8 @@ return_match (struct type *func_type, struct type *context_type)
 static int
 ada_resolve_function (struct block_symbol syms[],
                       int nsyms, struct value **args, int nargs,
-                      const char *name, struct type *context_type)
+                      const char *name, struct type *context_type,
+                     int parse_completion)
 {
   int fallback;
   int k;
@@ -3971,16 +3913,16 @@ user_select_syms (struct block_symbol *syms, int nsyms, int max_results)
     error (_("\
 canceled because the command is ambiguous\n\
 See set/show multiple-symbol."));
-  
+
   /* If select_mode is "all", then return all possible symbols.
      Only do that if more than one symbol can be selected, of course.
      Otherwise, display the menu as usual.  */
   if (select_mode == multiple_symbols_all && max_results > 1)
     return nsyms;
 
-  printf_unfiltered (_("[0] cancel\n"));
+  printf_filtered (_("[0] cancel\n"));
   if (max_results > 1)
-    printf_unfiltered (_("[1] all\n"));
+    printf_filtered (_("[1] all\n"));
 
   sort_choices (syms, nsyms);
 
@@ -3994,16 +3936,16 @@ See set/show multiple-symbol."));
           struct symtab_and_line sal =
             find_function_start_sal (syms[i].symbol, 1);
 
-         printf_unfiltered ("[%d] ", i + first_choice);
+         printf_filtered ("[%d] ", i + first_choice);
          ada_print_symbol_signature (gdb_stdout, syms[i].symbol,
                                      &type_print_raw_options);
          if (sal.symtab == NULL)
-           printf_unfiltered (_(" at <no source file available>:%d\n"),
-                              sal.line);
+           printf_filtered (_(" at <no source file available>:%d\n"),
+                            sal.line);
          else
-           printf_unfiltered (_(" at %s:%d\n"),
-                              symtab_to_filename_for_display (sal.symtab),
-                              sal.line);
+           printf_filtered (_(" at %s:%d\n"),
+                            symtab_to_filename_for_display (sal.symtab),
+                            sal.line);
           continue;
         }
       else
@@ -4019,37 +3961,37 @@ See set/show multiple-symbol."));
 
           if (SYMBOL_LINE (syms[i].symbol) != 0 && symtab != NULL)
            {
-             printf_unfiltered ("[%d] ", i + first_choice);
+             printf_filtered ("[%d] ", i + first_choice);
              ada_print_symbol_signature (gdb_stdout, syms[i].symbol,
                                          &type_print_raw_options);
-             printf_unfiltered (_(" at %s:%d\n"),
-                                symtab_to_filename_for_display (symtab),
-                                SYMBOL_LINE (syms[i].symbol));
+             printf_filtered (_(" at %s:%d\n"),
+                              symtab_to_filename_for_display (symtab),
+                              SYMBOL_LINE (syms[i].symbol));
            }
           else if (is_enumeral
                    && TYPE_NAME (SYMBOL_TYPE (syms[i].symbol)) != NULL)
             {
-              printf_unfiltered (("[%d] "), i + first_choice);
+              printf_filtered (("[%d] "), i + first_choice);
               ada_print_type (SYMBOL_TYPE (syms[i].symbol), NULL,
                               gdb_stdout, -1, 0, &type_print_raw_options);
-              printf_unfiltered (_("'(%s) (enumeral)\n"),
-                                 SYMBOL_PRINT_NAME (syms[i].symbol));
+              printf_filtered (_("'(%s) (enumeral)\n"),
+                              SYMBOL_PRINT_NAME (syms[i].symbol));
             }
          else
            {
-             printf_unfiltered ("[%d] ", i + first_choice);
+             printf_filtered ("[%d] ", i + first_choice);
              ada_print_symbol_signature (gdb_stdout, syms[i].symbol,
                                          &type_print_raw_options);
 
              if (symtab != NULL)
-               printf_unfiltered (is_enumeral
-                                  ? _(" in %s (enumeral)\n")
-                                  : _(" at %s:?\n"),
-                                  symtab_to_filename_for_display (symtab));
+               printf_filtered (is_enumeral
+                                ? _(" in %s (enumeral)\n")
+                                : _(" at %s:?\n"),
+                                symtab_to_filename_for_display (symtab));
              else
-               printf_unfiltered (is_enumeral
-                                  ? _(" (enumeral)\n")
-                                  : _(" at ?\n"));
+               printf_filtered (is_enumeral
+                                ? _(" (enumeral)\n")
+                                : _(" at ?\n"));
            }
         }
     }
@@ -4824,11 +4766,11 @@ standard_lookup (const char *name, const struct block *block,
                  domain_enum domain)
 {
   /* Initialize it just to avoid a GCC false warning.  */
-  struct block_symbol sym = {NULL, NULL};
+  struct block_symbol sym = {};
 
   if (lookup_cached_symbol (name, domain, &sym.symbol, NULL))
     return sym.symbol;
-  sym = lookup_symbol_in_language (name, block, domain, language_c, 0);
+  ada_lookup_encoded_symbol (name, block, domain, &sym);
   cache_symbol (name, domain, sym.symbol, sym.block);
   return sym.symbol;
 }
@@ -4981,8 +4923,6 @@ struct bound_minimal_symbol
 ada_lookup_simple_minsym (const char *name)
 {
   struct bound_minimal_symbol result;
-  struct objfile *objfile;
-  struct minimal_symbol *msymbol;
 
   memset (&result, 0, sizeof (result));
 
@@ -4992,16 +4932,19 @@ ada_lookup_simple_minsym (const char *name)
   symbol_name_matcher_ftype *match_name
     = ada_get_symbol_name_matcher (lookup_name);
 
-  ALL_MSYMBOLS (objfile, msymbol)
-  {
-    if (match_name (MSYMBOL_LINKAGE_NAME (msymbol), lookup_name, NULL)
-        && MSYMBOL_TYPE (msymbol) != mst_solib_trampoline)
-      {
-       result.minsym = msymbol;
-       result.objfile = objfile;
-       break;
-      }
-  }
+  for (objfile *objfile : current_program_space->objfiles ())
+    {
+      for (minimal_symbol *msymbol : objfile->msymbols ())
+       {
+         if (match_name (MSYMBOL_LINKAGE_NAME (msymbol), lookup_name, NULL)
+             && MSYMBOL_TYPE (msymbol) != mst_solib_trampoline)
+           {
+             result.minsym = msymbol;
+             result.objfile = objfile;
+             break;
+           }
+       }
+    }
 
   return result;
 }
@@ -5481,7 +5424,8 @@ struct match_data
    other has been found.  */
 
 static int
-aux_add_nonlocal_symbols (struct block *block, struct symbol *sym, void *data0)
+aux_add_nonlocal_symbols (const struct block *block, struct symbol *sym,
+                         void *data0)
 {
   struct match_data *data = (struct match_data *) data0;
   
@@ -5672,8 +5616,6 @@ add_nonlocal_symbols (struct obstack *obstackp,
                      const lookup_name_info &lookup_name,
                      domain_enum domain, int global)
 {
-  struct objfile *objfile;
-  struct compunit_symtab *cu;
   struct match_data data;
 
   memset (&data, 0, sizeof data);
@@ -5681,7 +5623,7 @@ add_nonlocal_symbols (struct obstack *obstackp,
 
   bool is_wild_match = lookup_name.ada ().wild_match_p ();
 
-  ALL_OBJFILES (objfile)
+  for (objfile *objfile : current_program_space->objfiles ())
     {
       data.objfile = objfile;
 
@@ -5698,7 +5640,7 @@ add_nonlocal_symbols (struct obstack *obstackp,
                                               symbol_name_match_type::FULL,
                                               compare_names);
 
-      ALL_OBJFILE_COMPUNITS (objfile, cu)
+      for (compunit_symtab *cu : objfile->compunits ())
        {
          const struct block *global_block
            = BLOCKVECTOR_BLOCK (COMPUNIT_BLOCKVECTOR (cu), GLOBAL_BLOCK);
@@ -5714,7 +5656,7 @@ add_nonlocal_symbols (struct obstack *obstackp,
       const char *name = ada_lookup_name (lookup_name);
       std::string name1 = std::string ("<_ada_") + name + '>';
 
-      ALL_OBJFILES (objfile)
+      for (objfile *objfile : current_program_space->objfiles ())
         {
          data.objfile = objfile;
          objfile->sf->qf->map_matching_symbols (objfile, name1.c_str (),
@@ -5984,7 +5926,7 @@ ada_lookup_symbol_nonlocal (const struct language_defn *langdef,
        return sym;
     }
 
-  return (struct block_symbol) {NULL, NULL};
+  return {};
 }
 
 
@@ -6459,9 +6401,6 @@ ada_collect_symbol_completion_matches (completion_tracker &tracker,
                                       enum type_code code)
 {
   struct symbol *sym;
-  struct compunit_symtab *s;
-  struct minimal_symbol *msymbol;
-  struct objfile *objfile;
   const struct block *b, *surrounding_static_block = 0;
   struct block_iterator iter;
 
@@ -6481,35 +6420,38 @@ ada_collect_symbol_completion_matches (completion_tracker &tracker,
      anything that isn't a text symbol (everything else will be
      handled by the psymtab code above).  */
 
-  ALL_MSYMBOLS (objfile, msymbol)
-  {
-    QUIT;
-
-    if (completion_skip_symbol (mode, msymbol))
-      continue;
-
-    language symbol_language = MSYMBOL_LANGUAGE (msymbol);
-
-    /* Ada minimal symbols won't have their language set to Ada.  If
-       we let completion_list_add_name compare using the
-       default/C-like matcher, then when completing e.g., symbols in a
-       package named "pck", we'd match internal Ada symbols like
-       "pckS", which are invalid in an Ada expression, unless you wrap
-       them in '<' '>' to request a verbatim match.
-
-       Unfortunately, some Ada encoded names successfully demangle as
-       C++ symbols (using an old mangling scheme), such as "name__2Xn"
-       -> "Xn::name(void)" and thus some Ada minimal symbols end up
-       with the wrong language set.  Paper over that issue here.  */
-    if (symbol_language == language_auto
-       || symbol_language == language_cplus)
-      symbol_language = language_ada;
-
-    completion_list_add_name (tracker,
-                             symbol_language,
-                             MSYMBOL_LINKAGE_NAME (msymbol),
-                             lookup_name, text, word);
-  }
+  for (objfile *objfile : current_program_space->objfiles ())
+    {
+      for (minimal_symbol *msymbol : objfile->msymbols ())
+       {
+         QUIT;
+
+         if (completion_skip_symbol (mode, msymbol))
+           continue;
+
+         language symbol_language = MSYMBOL_LANGUAGE (msymbol);
+
+         /* Ada minimal symbols won't have their language set to Ada.  If
+            we let completion_list_add_name compare using the
+            default/C-like matcher, then when completing e.g., symbols in a
+            package named "pck", we'd match internal Ada symbols like
+            "pckS", which are invalid in an Ada expression, unless you wrap
+            them in '<' '>' to request a verbatim match.
+
+            Unfortunately, some Ada encoded names successfully demangle as
+            C++ symbols (using an old mangling scheme), such as "name__2Xn"
+            -> "Xn::name(void)" and thus some Ada minimal symbols end up
+            with the wrong language set.  Paper over that issue here.  */
+         if (symbol_language == language_auto
+             || symbol_language == language_cplus)
+           symbol_language = language_ada;
+
+         completion_list_add_name (tracker,
+                                   symbol_language,
+                                   MSYMBOL_LINKAGE_NAME (msymbol),
+                                   lookup_name, text, word);
+       }
+    }
 
   /* Search upwards from currently selected frame (so that we can
      complete on local vars.  */
@@ -6534,40 +6476,46 @@ ada_collect_symbol_completion_matches (completion_tracker &tracker,
   /* Go through the symtabs and check the externs and statics for
      symbols which match.  */
 
-  ALL_COMPUNITS (objfile, s)
-  {
-    QUIT;
-    b = BLOCKVECTOR_BLOCK (COMPUNIT_BLOCKVECTOR (s), GLOBAL_BLOCK);
-    ALL_BLOCK_SYMBOLS (b, iter, sym)
+  for (objfile *objfile : current_program_space->objfiles ())
     {
-      if (completion_skip_symbol (mode, sym))
-       continue;
+      for (compunit_symtab *s : objfile->compunits ())
+       {
+         QUIT;
+         b = BLOCKVECTOR_BLOCK (COMPUNIT_BLOCKVECTOR (s), GLOBAL_BLOCK);
+         ALL_BLOCK_SYMBOLS (b, iter, sym)
+           {
+             if (completion_skip_symbol (mode, sym))
+               continue;
 
-      completion_list_add_name (tracker,
-                               SYMBOL_LANGUAGE (sym),
-                               SYMBOL_LINKAGE_NAME (sym),
-                               lookup_name, text, word);
+             completion_list_add_name (tracker,
+                                       SYMBOL_LANGUAGE (sym),
+                                       SYMBOL_LINKAGE_NAME (sym),
+                                       lookup_name, text, word);
+           }
+       }
     }
-  }
 
-  ALL_COMPUNITS (objfile, s)
-  {
-    QUIT;
-    b = BLOCKVECTOR_BLOCK (COMPUNIT_BLOCKVECTOR (s), STATIC_BLOCK);
-    /* Don't do this block twice.  */
-    if (b == surrounding_static_block)
-      continue;
-    ALL_BLOCK_SYMBOLS (b, iter, sym)
-    {
-      if (completion_skip_symbol (mode, sym))
-       continue;
+  for (objfile *objfile : current_program_space->objfiles ())
+    {
+      for (compunit_symtab *s : objfile->compunits ())
+       {
+         QUIT;
+         b = BLOCKVECTOR_BLOCK (COMPUNIT_BLOCKVECTOR (s), STATIC_BLOCK);
+         /* Don't do this block twice.  */
+         if (b == surrounding_static_block)
+           continue;
+         ALL_BLOCK_SYMBOLS (b, iter, sym)
+           {
+             if (completion_skip_symbol (mode, sym))
+               continue;
 
-      completion_list_add_name (tracker,
-                               SYMBOL_LANGUAGE (sym),
-                               SYMBOL_LINKAGE_NAME (sym),
-                               lookup_name, text, word);
+             completion_list_add_name (tracker,
+                                       SYMBOL_LANGUAGE (sym),
+                                       SYMBOL_LINKAGE_NAME (sym),
+                                       lookup_name, text, word);
+           }
+       }
     }
-  }
 }
 
                                 /* Field Access */
@@ -8560,11 +8508,11 @@ ada_template_to_fixed_record_type_1 (struct type *type,
   if (TYPE_LENGTH (type) <= 0)
     {
       if (TYPE_NAME (rtype))
-       warning (_("Invalid type size for `%s' detected: %d."),
-                TYPE_NAME (rtype), TYPE_LENGTH (type));
+       warning (_("Invalid type size for `%s' detected: %s."),
+                TYPE_NAME (rtype), pulongest (TYPE_LENGTH (type)));
       else
-       warning (_("Invalid type size for <unnamed> detected: %d."),
-                TYPE_LENGTH (type));
+       warning (_("Invalid type size for <unnamed> detected: %s."),
+                pulongest (TYPE_LENGTH (type)));
     }
   else
     {
@@ -10996,7 +10944,9 @@ ada_evaluate_subexp (struct type *expect_type, struct expression *exp,
                error_call_unknown_return_type (NULL);
              return allocate_value (TYPE_TARGET_TYPE (type));
            }
-         return call_function_by_hand (argvec[0], NULL, nargs, argvec + 1);
+         return call_function_by_hand (argvec[0], NULL,
+                                       gdb::make_array_view (argvec + 1,
+                                                             nargs));
        case TYPE_CODE_INTERNAL_FUNCTION:
          if (noside == EVAL_AVOID_SIDE_EFFECTS)
            /* We don't know anything about what the internal
@@ -11094,7 +11044,8 @@ ada_evaluate_subexp (struct type *expect_type, struct expression *exp,
         if (noside == EVAL_AVOID_SIDE_EFFECTS
             && ada_is_array_descriptor_type (ada_check_typedef
                                              (value_type (array))))
-          return empty_array (ada_type_of_array (array, 0), low_bound);
+          return empty_array (ada_type_of_array (array, 0), low_bound,
+                             high_bound);
 
         array = ada_coerce_to_simple_array_ptr (array);
 
@@ -11118,7 +11069,7 @@ ada_evaluate_subexp (struct type *expect_type, struct expression *exp,
             struct type *type0 = ada_check_typedef (value_type (array));
 
             if (high_bound < low_bound || noside == EVAL_AVOID_SIDE_EFFECTS)
-              return empty_array (TYPE_TARGET_TYPE (type0), low_bound);
+              return empty_array (TYPE_TARGET_TYPE (type0), low_bound, high_bound);
             else
               {
                 struct type *arr_type0 =
@@ -11132,7 +11083,7 @@ ada_evaluate_subexp (struct type *expect_type, struct expression *exp,
         else if (noside == EVAL_AVOID_SIDE_EFFECTS)
           return array;
         else if (high_bound < low_bound)
-          return empty_array (value_type (array), low_bound);
+          return empty_array (value_type (array), low_bound, high_bound);
         else
           return ada_value_slice (array, longest_to_int (low_bound),
                                  longest_to_int (high_bound));
@@ -12457,8 +12408,8 @@ static std::string ada_exception_catchpoint_cond_string
 class ada_catchpoint_location : public bp_location
 {
 public:
-  ada_catchpoint_location (const bp_location_ops *ops, breakpoint *owner)
-    : bp_location (ops, owner)
+  ada_catchpoint_location (breakpoint *owner)
+    : bp_location (owner)
   {}
 
   /* The condition that checks whether the exception that was raised
@@ -12467,24 +12418,6 @@ public:
   expression_up excep_cond_expr;
 };
 
-/* Implement the DTOR method in the bp_location_ops structure for all
-   Ada exception catchpoint kinds.  */
-
-static void
-ada_catchpoint_location_dtor (struct bp_location *bl)
-{
-  struct ada_catchpoint_location *al = (struct ada_catchpoint_location *) bl;
-
-  al->excep_cond_expr.reset ();
-}
-
-/* The vtable to be used in Ada catchpoint locations.  */
-
-static const struct bp_location_ops ada_catchpoint_location_ops =
-{
-  ada_catchpoint_location_dtor
-};
-
 /* An instance of this type is used to represent an Ada catchpoint.  */
 
 struct ada_catchpoint : public breakpoint
@@ -12554,7 +12487,7 @@ static struct bp_location *
 allocate_location_exception (enum ada_exception_catchpoint_kind ex,
                             struct breakpoint *self)
 {
-  return new ada_catchpoint_location (&ada_catchpoint_location_ops, self);
+  return new ada_catchpoint_location (self);
 }
 
 /* Implement the RE_SET method in the breakpoint_ops structure for all
@@ -13255,7 +13188,7 @@ ada_exception_catchpoint_cond_string (const char *excep_string,
 
 static struct symtab_and_line
 ada_exception_sal (enum ada_exception_catchpoint_kind ex,
-                  const char **addr_string, const struct breakpoint_ops **ops)
+                  std::string *addr_string, const struct breakpoint_ops **ops)
 {
   const char *sym_name;
   struct symbol *sym;
@@ -13275,7 +13208,7 @@ ada_exception_sal (enum ada_exception_catchpoint_kind ex,
     error (_("Unable to insert catchpoint. %s is not a function."), sym_name);
 
   /* Set ADDR_STRING.  */
-  *addr_string = xstrdup (sym_name);
+  *addr_string = sym_name;
 
   /* Set OPS.  */
   *ops = ada_exception_breakpoint_ops (ex);
@@ -13307,12 +13240,12 @@ create_ada_exception_catchpoint (struct gdbarch *gdbarch,
                                 int disabled,
                                 int from_tty)
 {
-  const char *addr_string = NULL;
+  std::string addr_string;
   const struct breakpoint_ops *ops = NULL;
   struct symtab_and_line sal = ada_exception_sal (ex_kind, &addr_string, &ops);
 
   std::unique_ptr<ada_catchpoint> c (new ada_catchpoint ());
-  init_ada_exception_breakpoint (c.get (), gdbarch, sal, addr_string,
+  init_ada_exception_breakpoint (c.get (), gdbarch, sal, addr_string.c_str (),
                                 ops, tempflag, disabled, from_tty);
   c->excep_string = excep_string;
   create_excep_cond_exprs (c.get (), ex_kind);
@@ -13614,9 +13547,6 @@ static void
 ada_add_global_exceptions (compiled_regex *preg,
                           std::vector<ada_exc_info> *exceptions)
 {
-  struct objfile *objfile;
-  struct compunit_symtab *s;
-
   /* In Ada, the symbol "search name" is a linkage name, whereas the
      regular expression used to do the matching refers to the natural
      name.  So match against the decoded name.  */
@@ -13630,26 +13560,29 @@ ada_add_global_exceptions (compiled_regex *preg,
                           NULL,
                           VARIABLES_DOMAIN);
 
-  ALL_COMPUNITS (objfile, s)
+  for (objfile *objfile : current_program_space->objfiles ())
     {
-      const struct blockvector *bv = COMPUNIT_BLOCKVECTOR (s);
-      int i;
-
-      for (i = GLOBAL_BLOCK; i <= STATIC_BLOCK; i++)
+      for (compunit_symtab *s : objfile->compunits ())
        {
-         struct block *b = BLOCKVECTOR_BLOCK (bv, i);
-         struct block_iterator iter;
-         struct symbol *sym;
+         const struct blockvector *bv = COMPUNIT_BLOCKVECTOR (s);
+         int i;
 
-         ALL_BLOCK_SYMBOLS (b, iter, sym)
-           if (ada_is_non_standard_exception_sym (sym)
-               && name_matches_regex (SYMBOL_NATURAL_NAME (sym), preg))
-             {
-               struct ada_exc_info info
-                 = {SYMBOL_PRINT_NAME (sym), SYMBOL_VALUE_ADDRESS (sym)};
+         for (i = GLOBAL_BLOCK; i <= STATIC_BLOCK; i++)
+           {
+             const struct block *b = BLOCKVECTOR_BLOCK (bv, i);
+             struct block_iterator iter;
+             struct symbol *sym;
 
-               exceptions->push_back (info);
-             }
+             ALL_BLOCK_SYMBOLS (b, iter, sym)
+               if (ada_is_non_standard_exception_sym (sym)
+                   && name_matches_regex (SYMBOL_NATURAL_NAME (sym), preg))
+                 {
+                   struct ada_exc_info info
+                     = {SYMBOL_PRINT_NAME (sym), SYMBOL_VALUE_ADDRESS (sym)};
+
+                   exceptions->push_back (info);
+                 }
+           }
        }
     }
 }
@@ -14254,6 +14187,16 @@ do_full_match (const char *symbol_search_name,
   return full_match (symbol_search_name, ada_lookup_name (lookup_name));
 }
 
+/* symbol_name_matcher_ftype for exact (verbatim) matches.  */
+
+static bool
+do_exact_match (const char *symbol_search_name,
+               const lookup_name_info &lookup_name,
+               completion_match_result *comp_match_res)
+{
+  return strcmp (symbol_search_name, ada_lookup_name (lookup_name)) == 0;
+}
+
 /* Build the Ada lookup name for LOOKUP_NAME.  */
 
 ada_lookup_name_info::ada_lookup_name_info (const lookup_name_info &lookup_name)
@@ -14364,6 +14307,8 @@ ada_get_symbol_name_matcher (const lookup_name_info &lookup_name)
     {
       if (lookup_name.ada ().wild_match_p ())
        return do_wild_match;
+      else if (lookup_name.ada ().verbatim_p ())
+       return do_exact_match;
       else
        return do_full_match;
     }
@@ -14538,7 +14483,7 @@ _initialize_ada_language (void)
   initialize_ada_catchpoint_ops ();
 
   add_prefix_cmd ("ada", no_class, set_ada_command,
-                  _("Prefix command for changing Ada-specfic settings"),
+                  _("Prefix command for changing Ada-specific settings"),
                   &set_ada_list, "set ada ", 0, &setlist);
 
   add_prefix_cmd ("ada", no_class, show_ada_command,
@@ -14569,7 +14514,14 @@ overloads selection menu is activated"),
 
   add_catch_command ("exception", _("\
 Catch Ada exceptions, when raised.\n\
-With an argument, catch only exceptions with the given name."),
+Usage: catch exception [ ARG ]\n\
+\n\
+Without any argument, stop when any Ada exception is raised.\n\
+If ARG is \"unhandled\" (without the quotes), only stop when the exception\n\
+being raised does not have a handler (and will therefore lead to the task's\n\
+termination).\n\
+Otherwise, the catchpoint only stops when the name of the exception being\n\
+raised is the same as ARG."),
                     catch_ada_exception_command,
                      NULL,
                     CATCH_PERMANENT,
This page took 0.03981 seconds and 4 git commands to generate.