]> Git Repo - binutils.git/blob - gdb/f-lang.c
gdb: move go_language class declaration into header file
[binutils.git] / gdb / f-lang.c
1 /* Fortran language support routines for GDB, the GNU debugger.
2
3    Copyright (C) 1993-2020 Free Software Foundation, Inc.
4
5    Contributed by Motorola.  Adapted from the C parser by Farooq Butt
6    ([email protected]).
7
8    This file is part of GDB.
9
10    This program is free software; you can redistribute it and/or modify
11    it under the terms of the GNU General Public License as published by
12    the Free Software Foundation; either version 3 of the License, or
13    (at your option) any later version.
14
15    This program is distributed in the hope that it will be useful,
16    but WITHOUT ANY WARRANTY; without even the implied warranty of
17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18    GNU General Public License for more details.
19
20    You should have received a copy of the GNU General Public License
21    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
22
23 #include "defs.h"
24 #include "symtab.h"
25 #include "gdbtypes.h"
26 #include "expression.h"
27 #include "parser-defs.h"
28 #include "language.h"
29 #include "varobj.h"
30 #include "gdbcore.h"
31 #include "f-lang.h"
32 #include "valprint.h"
33 #include "value.h"
34 #include "cp-support.h"
35 #include "charset.h"
36 #include "c-lang.h"
37 #include "target-float.h"
38 #include "gdbarch.h"
39 #include "gdbcmd.h"
40 #include "f-array-walker.h"
41
42 #include <math.h>
43
44 /* Whether GDB should repack array slices created by the user.  */
45 static bool repack_array_slices = false;
46
47 /* Implement 'show fortran repack-array-slices'.  */
48 static void
49 show_repack_array_slices (struct ui_file *file, int from_tty,
50                           struct cmd_list_element *c, const char *value)
51 {
52   fprintf_filtered (file, _("Repacking of Fortran array slices is %s.\n"),
53                     value);
54 }
55
56 /* Debugging of Fortran's array slicing.  */
57 static bool fortran_array_slicing_debug = false;
58
59 /* Implement 'show debug fortran-array-slicing'.  */
60 static void
61 show_fortran_array_slicing_debug (struct ui_file *file, int from_tty,
62                                   struct cmd_list_element *c,
63                                   const char *value)
64 {
65   fprintf_filtered (file, _("Debugging of Fortran array slicing is %s.\n"),
66                     value);
67 }
68
69 /* Local functions */
70
71 static struct value *fortran_argument_convert (struct value *value,
72                                                bool is_artificial);
73
74 /* Return the encoding that should be used for the character type
75    TYPE.  */
76
77 const char *
78 f_language::get_encoding (struct type *type)
79 {
80   const char *encoding;
81
82   switch (TYPE_LENGTH (type))
83     {
84     case 1:
85       encoding = target_charset (get_type_arch (type));
86       break;
87     case 4:
88       if (type_byte_order (type) == BFD_ENDIAN_BIG)
89         encoding = "UTF-32BE";
90       else
91         encoding = "UTF-32LE";
92       break;
93
94     default:
95       error (_("unrecognized character type"));
96     }
97
98   return encoding;
99 }
100
101 \f
102
103 /* Table of operators and their precedences for printing expressions.  */
104
105 const struct op_print f_language::op_print_tab[] =
106 {
107   {"+", BINOP_ADD, PREC_ADD, 0},
108   {"+", UNOP_PLUS, PREC_PREFIX, 0},
109   {"-", BINOP_SUB, PREC_ADD, 0},
110   {"-", UNOP_NEG, PREC_PREFIX, 0},
111   {"*", BINOP_MUL, PREC_MUL, 0},
112   {"/", BINOP_DIV, PREC_MUL, 0},
113   {"DIV", BINOP_INTDIV, PREC_MUL, 0},
114   {"MOD", BINOP_REM, PREC_MUL, 0},
115   {"=", BINOP_ASSIGN, PREC_ASSIGN, 1},
116   {".OR.", BINOP_LOGICAL_OR, PREC_LOGICAL_OR, 0},
117   {".AND.", BINOP_LOGICAL_AND, PREC_LOGICAL_AND, 0},
118   {".NOT.", UNOP_LOGICAL_NOT, PREC_PREFIX, 0},
119   {".EQ.", BINOP_EQUAL, PREC_EQUAL, 0},
120   {".NE.", BINOP_NOTEQUAL, PREC_EQUAL, 0},
121   {".LE.", BINOP_LEQ, PREC_ORDER, 0},
122   {".GE.", BINOP_GEQ, PREC_ORDER, 0},
123   {".GT.", BINOP_GTR, PREC_ORDER, 0},
124   {".LT.", BINOP_LESS, PREC_ORDER, 0},
125   {"**", UNOP_IND, PREC_PREFIX, 0},
126   {"@", BINOP_REPEAT, PREC_REPEAT, 0},
127   {NULL, OP_NULL, PREC_REPEAT, 0}
128 };
129 \f
130
131 /* Return the number of dimensions for a Fortran array or string.  */
132
133 int
134 calc_f77_array_dims (struct type *array_type)
135 {
136   int ndimen = 1;
137   struct type *tmp_type;
138
139   if ((array_type->code () == TYPE_CODE_STRING))
140     return 1;
141
142   if ((array_type->code () != TYPE_CODE_ARRAY))
143     error (_("Can't get dimensions for a non-array type"));
144
145   tmp_type = array_type;
146
147   while ((tmp_type = TYPE_TARGET_TYPE (tmp_type)))
148     {
149       if (tmp_type->code () == TYPE_CODE_ARRAY)
150         ++ndimen;
151     }
152   return ndimen;
153 }
154
155 /* A class used by FORTRAN_VALUE_SUBARRAY when repacking Fortran array
156    slices.  This is a base class for two alternative repacking mechanisms,
157    one for when repacking from a lazy value, and one for repacking from a
158    non-lazy (already loaded) value.  */
159 class fortran_array_repacker_base_impl
160   : public fortran_array_walker_base_impl
161 {
162 public:
163   /* Constructor, DEST is the value we are repacking into.  */
164   fortran_array_repacker_base_impl (struct value *dest)
165     : m_dest (dest),
166       m_dest_offset (0)
167   { /* Nothing.  */ }
168
169   /* When we start processing the inner most dimension, this is where we
170      will be creating values for each element as we load them and then copy
171      them into the M_DEST value.  Set a value mark so we can free these
172      temporary values.  */
173   void start_dimension (bool inner_p)
174   {
175     if (inner_p)
176       {
177         gdb_assert (m_mark == nullptr);
178         m_mark = value_mark ();
179       }
180   }
181
182   /* When we finish processing the inner most dimension free all temporary
183      value that were created.  */
184   void finish_dimension (bool inner_p, bool last_p)
185   {
186     if (inner_p)
187       {
188         gdb_assert (m_mark != nullptr);
189         value_free_to_mark (m_mark);
190         m_mark = nullptr;
191       }
192   }
193
194 protected:
195   /* Copy the contents of array element ELT into M_DEST at the next
196      available offset.  */
197   void copy_element_to_dest (struct value *elt)
198   {
199     value_contents_copy (m_dest, m_dest_offset, elt, 0,
200                          TYPE_LENGTH (value_type (elt)));
201     m_dest_offset += TYPE_LENGTH (value_type (elt));
202   }
203
204   /* The value being written to.  */
205   struct value *m_dest;
206
207   /* The byte offset in M_DEST at which the next element should be
208      written.  */
209   LONGEST m_dest_offset;
210
211   /* Set with a call to VALUE_MARK, and then reset after calling
212      VALUE_FREE_TO_MARK.  */
213   struct value *m_mark = nullptr;
214 };
215
216 /* A class used by FORTRAN_VALUE_SUBARRAY when repacking Fortran array
217    slices.  This class is specialised for repacking an array slice from a
218    lazy array value, as such it does not require the parent array value to
219    be loaded into GDB's memory; the parent value could be huge, while the
220    slice could be tiny.  */
221 class fortran_lazy_array_repacker_impl
222   : public fortran_array_repacker_base_impl
223 {
224 public:
225   /* Constructor.  TYPE is the type of the slice being loaded from the
226      parent value, so this type will correctly reflect the strides required
227      to find all of the elements from the parent value.  ADDRESS is the
228      address in target memory of value matching TYPE, and DEST is the value
229      we are repacking into.  */
230   explicit fortran_lazy_array_repacker_impl (struct type *type,
231                                              CORE_ADDR address,
232                                              struct value *dest)
233     : fortran_array_repacker_base_impl (dest),
234       m_addr (address)
235   { /* Nothing.  */ }
236
237   /* Create a lazy value in target memory representing a single element,
238      then load the element into GDB's memory and copy the contents into the
239      destination value.  */
240   void process_element (struct type *elt_type, LONGEST elt_off, bool last_p)
241   {
242     copy_element_to_dest (value_at_lazy (elt_type, m_addr + elt_off));
243   }
244
245 private:
246   /* The address in target memory where the parent value starts.  */
247   CORE_ADDR m_addr;
248 };
249
250 /* A class used by FORTRAN_VALUE_SUBARRAY when repacking Fortran array
251    slices.  This class is specialised for repacking an array slice from a
252    previously loaded (non-lazy) array value, as such it fetches the
253    element values from the contents of the parent value.  */
254 class fortran_array_repacker_impl
255   : public fortran_array_repacker_base_impl
256 {
257 public:
258   /* Constructor.  TYPE is the type for the array slice within the parent
259      value, as such it has stride values as required to find the elements
260      within the original parent value.  ADDRESS is the address in target
261      memory of the value matching TYPE.  BASE_OFFSET is the offset from
262      the start of VAL's content buffer to the start of the object of TYPE,
263      VAL is the parent object from which we are loading the value, and
264      DEST is the value into which we are repacking.  */
265   explicit fortran_array_repacker_impl (struct type *type, CORE_ADDR address,
266                                         LONGEST base_offset,
267                                         struct value *val, struct value *dest)
268     : fortran_array_repacker_base_impl (dest),
269       m_base_offset (base_offset),
270       m_val (val)
271   {
272     gdb_assert (!value_lazy (val));
273   }
274
275   /* Extract an element of ELT_TYPE at offset (M_BASE_OFFSET + ELT_OFF)
276      from the content buffer of M_VAL then copy this extracted value into
277      the repacked destination value.  */
278   void process_element (struct type *elt_type, LONGEST elt_off, bool last_p)
279   {
280     struct value *elt
281       = value_from_component (m_val, elt_type, (elt_off + m_base_offset));
282     copy_element_to_dest (elt);
283   }
284
285 private:
286   /* The offset into the content buffer of M_VAL to the start of the slice
287      being extracted.  */
288   LONGEST m_base_offset;
289
290   /* The parent value from which we are extracting a slice.  */
291   struct value *m_val;
292 };
293
294 /* Called from evaluate_subexp_standard to perform array indexing, and
295    sub-range extraction, for Fortran.  As well as arrays this function
296    also handles strings as they can be treated like arrays of characters.
297    ARRAY is the array or string being accessed.  EXP, POS, and NOSIDE are
298    as for evaluate_subexp_standard, and NARGS is the number of arguments
299    in this access (e.g. 'array (1,2,3)' would be NARGS 3).  */
300
301 static struct value *
302 fortran_value_subarray (struct value *array, struct expression *exp,
303                         int *pos, int nargs, enum noside noside)
304 {
305   type *original_array_type = check_typedef (value_type (array));
306   bool is_string_p = original_array_type->code () == TYPE_CODE_STRING;
307
308   /* Perform checks for ARRAY not being available.  The somewhat overly
309      complex logic here is just to keep backward compatibility with the
310      errors that we used to get before FORTRAN_VALUE_SUBARRAY was
311      rewritten.  Maybe a future task would streamline the error messages we
312      get here, and update all the expected test results.  */
313   if (exp->elts[*pos].opcode != OP_RANGE)
314     {
315       if (type_not_associated (original_array_type))
316         error (_("no such vector element (vector not associated)"));
317       else if (type_not_allocated (original_array_type))
318         error (_("no such vector element (vector not allocated)"));
319     }
320   else
321     {
322       if (type_not_associated (original_array_type))
323         error (_("array not associated"));
324       else if (type_not_allocated (original_array_type))
325         error (_("array not allocated"));
326     }
327
328   /* First check that the number of dimensions in the type we are slicing
329      matches the number of arguments we were passed.  */
330   int ndimensions = calc_f77_array_dims (original_array_type);
331   if (nargs != ndimensions)
332     error (_("Wrong number of subscripts"));
333
334   /* This will be initialised below with the type of the elements held in
335      ARRAY.  */
336   struct type *inner_element_type;
337
338   /* Extract the types of each array dimension from the original array
339      type.  We need these available so we can fill in the default upper and
340      lower bounds if the user requested slice doesn't provide that
341      information.  Additionally unpacking the dimensions like this gives us
342      the inner element type.  */
343   std::vector<struct type *> dim_types;
344   {
345     dim_types.reserve (ndimensions);
346     struct type *type = original_array_type;
347     for (int i = 0; i < ndimensions; ++i)
348       {
349         dim_types.push_back (type);
350         type = TYPE_TARGET_TYPE (type);
351       }
352     /* TYPE is now the inner element type of the array, we start the new
353        array slice off as this type, then as we process the requested slice
354        (from the user) we wrap new types around this to build up the final
355        slice type.  */
356     inner_element_type = type;
357   }
358
359   /* As we analyse the new slice type we need to understand if the data
360      being referenced is contiguous.  Do decide this we must track the size
361      of an element at each dimension of the new slice array.  Initially the
362      elements of the inner most dimension of the array are the same inner
363      most elements as the original ARRAY.  */
364   LONGEST slice_element_size = TYPE_LENGTH (inner_element_type);
365
366   /* Start off assuming all data is contiguous, this will be set to false
367      if access to any dimension results in non-contiguous data.  */
368   bool is_all_contiguous = true;
369
370   /* The TOTAL_OFFSET is the distance in bytes from the start of the
371      original ARRAY to the start of the new slice.  This is calculated as
372      we process the information from the user.  */
373   LONGEST total_offset = 0;
374
375   /* A structure representing information about each dimension of the
376      resulting slice.  */
377   struct slice_dim
378   {
379     /* Constructor.  */
380     slice_dim (LONGEST l, LONGEST h, LONGEST s, struct type *idx)
381       : low (l),
382         high (h),
383         stride (s),
384         index (idx)
385     { /* Nothing.  */ }
386
387     /* The low bound for this dimension of the slice.  */
388     LONGEST low;
389
390     /* The high bound for this dimension of the slice.  */
391     LONGEST high;
392
393     /* The byte stride for this dimension of the slice.  */
394     LONGEST stride;
395
396     struct type *index;
397   };
398
399   /* The dimensions of the resulting slice.  */
400   std::vector<slice_dim> slice_dims;
401
402   /* Process the incoming arguments.   These arguments are in the reverse
403      order to the array dimensions, that is the first argument refers to
404      the last array dimension.  */
405   if (fortran_array_slicing_debug)
406     debug_printf ("Processing array access:\n");
407   for (int i = 0; i < nargs; ++i)
408     {
409       /* For each dimension of the array the user will have either provided
410          a ranged access with optional lower bound, upper bound, and
411          stride, or the user will have supplied a single index.  */
412       struct type *dim_type = dim_types[ndimensions - (i + 1)];
413       if (exp->elts[*pos].opcode == OP_RANGE)
414         {
415           int pc = (*pos) + 1;
416           enum range_flag range_flag = (enum range_flag) exp->elts[pc].longconst;
417           *pos += 3;
418
419           LONGEST low, high, stride;
420           low = high = stride = 0;
421
422           if ((range_flag & RANGE_LOW_BOUND_DEFAULT) == 0)
423             low = value_as_long (evaluate_subexp (nullptr, exp, pos, noside));
424           else
425             low = f77_get_lowerbound (dim_type);
426           if ((range_flag & RANGE_HIGH_BOUND_DEFAULT) == 0)
427             high = value_as_long (evaluate_subexp (nullptr, exp, pos, noside));
428           else
429             high = f77_get_upperbound (dim_type);
430           if ((range_flag & RANGE_HAS_STRIDE) == RANGE_HAS_STRIDE)
431             stride = value_as_long (evaluate_subexp (nullptr, exp, pos, noside));
432           else
433             stride = 1;
434
435           if (stride == 0)
436             error (_("stride must not be 0"));
437
438           /* Get information about this dimension in the original ARRAY.  */
439           struct type *target_type = TYPE_TARGET_TYPE (dim_type);
440           struct type *index_type = dim_type->index_type ();
441           LONGEST lb = f77_get_lowerbound (dim_type);
442           LONGEST ub = f77_get_upperbound (dim_type);
443           LONGEST sd = index_type->bit_stride ();
444           if (sd == 0)
445             sd = TYPE_LENGTH (target_type) * 8;
446
447           if (fortran_array_slicing_debug)
448             {
449               debug_printf ("|-> Range access\n");
450               std::string str = type_to_string (dim_type);
451               debug_printf ("|   |-> Type: %s\n", str.c_str ());
452               debug_printf ("|   |-> Array:\n");
453               debug_printf ("|   |   |-> Low bound: %s\n", plongest (lb));
454               debug_printf ("|   |   |-> High bound: %s\n", plongest (ub));
455               debug_printf ("|   |   |-> Bit stride: %s\n", plongest (sd));
456               debug_printf ("|   |   |-> Byte stride: %s\n", plongest (sd / 8));
457               debug_printf ("|   |   |-> Type size: %s\n",
458                             pulongest (TYPE_LENGTH (dim_type)));
459               debug_printf ("|   |   '-> Target type size: %s\n",
460                             pulongest (TYPE_LENGTH (target_type)));
461               debug_printf ("|   |-> Accessing:\n");
462               debug_printf ("|   |   |-> Low bound: %s\n",
463                             plongest (low));
464               debug_printf ("|   |   |-> High bound: %s\n",
465                             plongest (high));
466               debug_printf ("|   |   '-> Element stride: %s\n",
467                             plongest (stride));
468             }
469
470           /* Check the user hasn't asked for something invalid.  */
471           if (high > ub || low < lb)
472             error (_("array subscript out of bounds"));
473
474           /* Calculate what this dimension of the new slice array will look
475              like.  OFFSET is the byte offset from the start of the
476              previous (more outer) dimension to the start of this
477              dimension.  E_COUNT is the number of elements in this
478              dimension.  REMAINDER is the number of elements remaining
479              between the last included element and the upper bound.  For
480              example an access '1:6:2' will include elements 1, 3, 5 and
481              have a remainder of 1 (element #6).  */
482           LONGEST lowest = std::min (low, high);
483           LONGEST offset = (sd / 8) * (lowest - lb);
484           LONGEST e_count = std::abs (high - low) + 1;
485           e_count = (e_count + (std::abs (stride) - 1)) / std::abs (stride);
486           LONGEST new_low = 1;
487           LONGEST new_high = new_low + e_count - 1;
488           LONGEST new_stride = (sd * stride) / 8;
489           LONGEST last_elem = low + ((e_count - 1) * stride);
490           LONGEST remainder = high - last_elem;
491           if (low > high)
492             {
493               offset += std::abs (remainder) * TYPE_LENGTH (target_type);
494               if (stride > 0)
495                 error (_("incorrect stride and boundary combination"));
496             }
497           else if (stride < 0)
498             error (_("incorrect stride and boundary combination"));
499
500           /* Is the data within this dimension contiguous?  It is if the
501              newly computed stride is the same size as a single element of
502              this dimension.  */
503           bool is_dim_contiguous = (new_stride == slice_element_size);
504           is_all_contiguous &= is_dim_contiguous;
505
506           if (fortran_array_slicing_debug)
507             {
508               debug_printf ("|   '-> Results:\n");
509               debug_printf ("|       |-> Offset = %s\n", plongest (offset));
510               debug_printf ("|       |-> Elements = %s\n", plongest (e_count));
511               debug_printf ("|       |-> Low bound = %s\n", plongest (new_low));
512               debug_printf ("|       |-> High bound = %s\n",
513                             plongest (new_high));
514               debug_printf ("|       |-> Byte stride = %s\n",
515                             plongest (new_stride));
516               debug_printf ("|       |-> Last element = %s\n",
517                             plongest (last_elem));
518               debug_printf ("|       |-> Remainder = %s\n",
519                             plongest (remainder));
520               debug_printf ("|       '-> Contiguous = %s\n",
521                             (is_dim_contiguous ? "Yes" : "No"));
522             }
523
524           /* Figure out how big (in bytes) an element of this dimension of
525              the new array slice will be.  */
526           slice_element_size = std::abs (new_stride * e_count);
527
528           slice_dims.emplace_back (new_low, new_high, new_stride,
529                                    index_type);
530
531           /* Update the total offset.  */
532           total_offset += offset;
533         }
534       else
535         {
536           /* There is a single index for this dimension.  */
537           LONGEST index
538             = value_as_long (evaluate_subexp_with_coercion (exp, pos, noside));
539
540           /* Get information about this dimension in the original ARRAY.  */
541           struct type *target_type = TYPE_TARGET_TYPE (dim_type);
542           struct type *index_type = dim_type->index_type ();
543           LONGEST lb = f77_get_lowerbound (dim_type);
544           LONGEST ub = f77_get_upperbound (dim_type);
545           LONGEST sd = index_type->bit_stride () / 8;
546           if (sd == 0)
547             sd = TYPE_LENGTH (target_type);
548
549           if (fortran_array_slicing_debug)
550             {
551               debug_printf ("|-> Index access\n");
552               std::string str = type_to_string (dim_type);
553               debug_printf ("|   |-> Type: %s\n", str.c_str ());
554               debug_printf ("|   |-> Array:\n");
555               debug_printf ("|   |   |-> Low bound: %s\n", plongest (lb));
556               debug_printf ("|   |   |-> High bound: %s\n", plongest (ub));
557               debug_printf ("|   |   |-> Byte stride: %s\n", plongest (sd));
558               debug_printf ("|   |   |-> Type size: %s\n",
559                             pulongest (TYPE_LENGTH (dim_type)));
560               debug_printf ("|   |   '-> Target type size: %s\n",
561                             pulongest (TYPE_LENGTH (target_type)));
562               debug_printf ("|   '-> Accessing:\n");
563               debug_printf ("|       '-> Index: %s\n",
564                             plongest (index));
565             }
566
567           /* If the array has actual content then check the index is in
568              bounds.  An array without content (an unbound array) doesn't
569              have a known upper bound, so don't error check in that
570              situation.  */
571           if (index < lb
572               || (dim_type->index_type ()->bounds ()->high.kind () != PROP_UNDEFINED
573                   && index > ub)
574               || (VALUE_LVAL (array) != lval_memory
575                   && dim_type->index_type ()->bounds ()->high.kind () == PROP_UNDEFINED))
576             {
577               if (type_not_associated (dim_type))
578                 error (_("no such vector element (vector not associated)"));
579               else if (type_not_allocated (dim_type))
580                 error (_("no such vector element (vector not allocated)"));
581               else
582                 error (_("no such vector element"));
583             }
584
585           /* Calculate using the type stride, not the target type size.  */
586           LONGEST offset = sd * (index - lb);
587           total_offset += offset;
588         }
589     }
590
591   if (noside == EVAL_SKIP)
592     return array;
593
594   /* Build a type that represents the new array slice in the target memory
595      of the original ARRAY, this type makes use of strides to correctly
596      find only those elements that are part of the new slice.  */
597   struct type *array_slice_type = inner_element_type;
598   for (const auto &d : slice_dims)
599     {
600       /* Create the range.  */
601       dynamic_prop p_low, p_high, p_stride;
602
603       p_low.set_const_val (d.low);
604       p_high.set_const_val (d.high);
605       p_stride.set_const_val (d.stride);
606
607       struct type *new_range
608         = create_range_type_with_stride ((struct type *) NULL,
609                                          TYPE_TARGET_TYPE (d.index),
610                                          &p_low, &p_high, 0, &p_stride,
611                                          true);
612       array_slice_type
613         = create_array_type (nullptr, array_slice_type, new_range);
614     }
615
616   if (fortran_array_slicing_debug)
617     {
618       debug_printf ("'-> Final result:\n");
619       debug_printf ("    |-> Type: %s\n",
620                     type_to_string (array_slice_type).c_str ());
621       debug_printf ("    |-> Total offset: %s\n",
622                     plongest (total_offset));
623       debug_printf ("    |-> Base address: %s\n",
624                     core_addr_to_string (value_address (array)));
625       debug_printf ("    '-> Contiguous = %s\n",
626                     (is_all_contiguous ? "Yes" : "No"));
627     }
628
629   /* Should we repack this array slice?  */
630   if (!is_all_contiguous && (repack_array_slices || is_string_p))
631     {
632       /* Build a type for the repacked slice.  */
633       struct type *repacked_array_type = inner_element_type;
634       for (const auto &d : slice_dims)
635         {
636           /* Create the range.  */
637           dynamic_prop p_low, p_high, p_stride;
638
639           p_low.set_const_val (d.low);
640           p_high.set_const_val (d.high);
641           p_stride.set_const_val (TYPE_LENGTH (repacked_array_type));
642
643           struct type *new_range
644             = create_range_type_with_stride ((struct type *) NULL,
645                                              TYPE_TARGET_TYPE (d.index),
646                                              &p_low, &p_high, 0, &p_stride,
647                                              true);
648           repacked_array_type
649             = create_array_type (nullptr, repacked_array_type, new_range);
650         }
651
652       /* Now copy the elements from the original ARRAY into the packed
653          array value DEST.  */
654       struct value *dest = allocate_value (repacked_array_type);
655       if (value_lazy (array)
656           || (total_offset + TYPE_LENGTH (array_slice_type)
657               > TYPE_LENGTH (check_typedef (value_type (array)))))
658         {
659           fortran_array_walker<fortran_lazy_array_repacker_impl> p
660             (array_slice_type, value_address (array) + total_offset, dest);
661           p.walk ();
662         }
663       else
664         {
665           fortran_array_walker<fortran_array_repacker_impl> p
666             (array_slice_type, value_address (array) + total_offset,
667              total_offset, array, dest);
668           p.walk ();
669         }
670       array = dest;
671     }
672   else
673     {
674       if (VALUE_LVAL (array) == lval_memory)
675         {
676           /* If the value we're taking a slice from is not yet loaded, or
677              the requested slice is outside the values content range then
678              just create a new lazy value pointing at the memory where the
679              contents we're looking for exist.  */
680           if (value_lazy (array)
681               || (total_offset + TYPE_LENGTH (array_slice_type)
682                   > TYPE_LENGTH (check_typedef (value_type (array)))))
683             array = value_at_lazy (array_slice_type,
684                                    value_address (array) + total_offset);
685           else
686             array = value_from_contents_and_address (array_slice_type,
687                                                      (value_contents (array)
688                                                       + total_offset),
689                                                      (value_address (array)
690                                                       + total_offset));
691         }
692       else if (!value_lazy (array))
693         {
694           const void *valaddr = value_contents (array) + total_offset;
695           array = allocate_value (array_slice_type);
696           memcpy (value_contents_raw (array), valaddr, TYPE_LENGTH (array_slice_type));
697         }
698       else
699         error (_("cannot subscript arrays that are not in memory"));
700     }
701
702   return array;
703 }
704
705 /* Special expression evaluation cases for Fortran.  */
706
707 static struct value *
708 evaluate_subexp_f (struct type *expect_type, struct expression *exp,
709                    int *pos, enum noside noside)
710 {
711   struct value *arg1 = NULL, *arg2 = NULL;
712   enum exp_opcode op;
713   int pc;
714   struct type *type;
715
716   pc = *pos;
717   *pos += 1;
718   op = exp->elts[pc].opcode;
719
720   switch (op)
721     {
722     default:
723       *pos -= 1;
724       return evaluate_subexp_standard (expect_type, exp, pos, noside);
725
726     case UNOP_ABS:
727       arg1 = evaluate_subexp (nullptr, exp, pos, noside);
728       if (noside == EVAL_SKIP)
729         return eval_skip_value (exp);
730       type = value_type (arg1);
731       switch (type->code ())
732         {
733         case TYPE_CODE_FLT:
734           {
735             double d
736               = fabs (target_float_to_host_double (value_contents (arg1),
737                                                    value_type (arg1)));
738             return value_from_host_double (type, d);
739           }
740         case TYPE_CODE_INT:
741           {
742             LONGEST l = value_as_long (arg1);
743             l = llabs (l);
744             return value_from_longest (type, l);
745           }
746         }
747       error (_("ABS of type %s not supported"), TYPE_SAFE_NAME (type));
748
749     case BINOP_MOD:
750       arg1 = evaluate_subexp (nullptr, exp, pos, noside);
751       arg2 = evaluate_subexp (value_type (arg1), exp, pos, noside);
752       if (noside == EVAL_SKIP)
753         return eval_skip_value (exp);
754       type = value_type (arg1);
755       if (type->code () != value_type (arg2)->code ())
756         error (_("non-matching types for parameters to MOD ()"));
757       switch (type->code ())
758         {
759         case TYPE_CODE_FLT:
760           {
761             double d1
762               = target_float_to_host_double (value_contents (arg1),
763                                              value_type (arg1));
764             double d2
765               = target_float_to_host_double (value_contents (arg2),
766                                              value_type (arg2));
767             double d3 = fmod (d1, d2);
768             return value_from_host_double (type, d3);
769           }
770         case TYPE_CODE_INT:
771           {
772             LONGEST v1 = value_as_long (arg1);
773             LONGEST v2 = value_as_long (arg2);
774             if (v2 == 0)
775               error (_("calling MOD (N, 0) is undefined"));
776             LONGEST v3 = v1 - (v1 / v2) * v2;
777             return value_from_longest (value_type (arg1), v3);
778           }
779         }
780       error (_("MOD of type %s not supported"), TYPE_SAFE_NAME (type));
781
782     case UNOP_FORTRAN_CEILING:
783       {
784         arg1 = evaluate_subexp (nullptr, exp, pos, noside);
785         if (noside == EVAL_SKIP)
786           return eval_skip_value (exp);
787         type = value_type (arg1);
788         if (type->code () != TYPE_CODE_FLT)
789           error (_("argument to CEILING must be of type float"));
790         double val
791           = target_float_to_host_double (value_contents (arg1),
792                                          value_type (arg1));
793         val = ceil (val);
794         return value_from_host_double (type, val);
795       }
796
797     case UNOP_FORTRAN_FLOOR:
798       {
799         arg1 = evaluate_subexp (nullptr, exp, pos, noside);
800         if (noside == EVAL_SKIP)
801           return eval_skip_value (exp);
802         type = value_type (arg1);
803         if (type->code () != TYPE_CODE_FLT)
804           error (_("argument to FLOOR must be of type float"));
805         double val
806           = target_float_to_host_double (value_contents (arg1),
807                                          value_type (arg1));
808         val = floor (val);
809         return value_from_host_double (type, val);
810       }
811
812     case BINOP_FORTRAN_MODULO:
813       {
814         arg1 = evaluate_subexp (nullptr, exp, pos, noside);
815         arg2 = evaluate_subexp (value_type (arg1), exp, pos, noside);
816         if (noside == EVAL_SKIP)
817           return eval_skip_value (exp);
818         type = value_type (arg1);
819         if (type->code () != value_type (arg2)->code ())
820           error (_("non-matching types for parameters to MODULO ()"));
821         /* MODULO(A, P) = A - FLOOR (A / P) * P */
822         switch (type->code ())
823           {
824           case TYPE_CODE_INT:
825             {
826               LONGEST a = value_as_long (arg1);
827               LONGEST p = value_as_long (arg2);
828               LONGEST result = a - (a / p) * p;
829               if (result != 0 && (a < 0) != (p < 0))
830                 result += p;
831               return value_from_longest (value_type (arg1), result);
832             }
833           case TYPE_CODE_FLT:
834             {
835               double a
836                 = target_float_to_host_double (value_contents (arg1),
837                                                value_type (arg1));
838               double p
839                 = target_float_to_host_double (value_contents (arg2),
840                                                value_type (arg2));
841               double result = fmod (a, p);
842               if (result != 0 && (a < 0.0) != (p < 0.0))
843                 result += p;
844               return value_from_host_double (type, result);
845             }
846           }
847         error (_("MODULO of type %s not supported"), TYPE_SAFE_NAME (type));
848       }
849
850     case BINOP_FORTRAN_CMPLX:
851       arg1 = evaluate_subexp (nullptr, exp, pos, noside);
852       arg2 = evaluate_subexp (value_type (arg1), exp, pos, noside);
853       if (noside == EVAL_SKIP)
854         return eval_skip_value (exp);
855       type = builtin_f_type(exp->gdbarch)->builtin_complex_s16;
856       return value_literal_complex (arg1, arg2, type);
857
858     case UNOP_FORTRAN_KIND:
859       arg1 = evaluate_subexp (NULL, exp, pos, EVAL_AVOID_SIDE_EFFECTS);
860       type = value_type (arg1);
861
862       switch (type->code ())
863         {
864           case TYPE_CODE_STRUCT:
865           case TYPE_CODE_UNION:
866           case TYPE_CODE_MODULE:
867           case TYPE_CODE_FUNC:
868             error (_("argument to kind must be an intrinsic type"));
869         }
870
871       if (!TYPE_TARGET_TYPE (type))
872         return value_from_longest (builtin_type (exp->gdbarch)->builtin_int,
873                                    TYPE_LENGTH (type));
874       return value_from_longest (builtin_type (exp->gdbarch)->builtin_int,
875                                  TYPE_LENGTH (TYPE_TARGET_TYPE (type)));
876
877
878     case OP_F77_UNDETERMINED_ARGLIST:
879       /* Remember that in F77, functions, substring ops and array subscript
880          operations cannot be disambiguated at parse time.  We have made
881          all array subscript operations, substring operations as well as
882          function calls come here and we now have to discover what the heck
883          this thing actually was.  If it is a function, we process just as
884          if we got an OP_FUNCALL.  */
885       int nargs = longest_to_int (exp->elts[pc + 1].longconst);
886       (*pos) += 2;
887
888       /* First determine the type code we are dealing with.  */
889       arg1 = evaluate_subexp (nullptr, exp, pos, noside);
890       type = check_typedef (value_type (arg1));
891       enum type_code code = type->code ();
892
893       if (code == TYPE_CODE_PTR)
894         {
895           /* Fortran always passes variable to subroutines as pointer.
896              So we need to look into its target type to see if it is
897              array, string or function.  If it is, we need to switch
898              to the target value the original one points to.  */
899           struct type *target_type = check_typedef (TYPE_TARGET_TYPE (type));
900
901           if (target_type->code () == TYPE_CODE_ARRAY
902               || target_type->code () == TYPE_CODE_STRING
903               || target_type->code () == TYPE_CODE_FUNC)
904             {
905               arg1 = value_ind (arg1);
906               type = check_typedef (value_type (arg1));
907               code = type->code ();
908             }
909         }
910
911       switch (code)
912         {
913         case TYPE_CODE_ARRAY:
914         case TYPE_CODE_STRING:
915           return fortran_value_subarray (arg1, exp, pos, nargs, noside);
916
917         case TYPE_CODE_PTR:
918         case TYPE_CODE_FUNC:
919         case TYPE_CODE_INTERNAL_FUNCTION:
920           {
921             /* It's a function call.  Allocate arg vector, including
922             space for the function to be called in argvec[0] and a
923             termination NULL.  */
924             struct value **argvec = (struct value **)
925               alloca (sizeof (struct value *) * (nargs + 2));
926             argvec[0] = arg1;
927             int tem = 1;
928             for (; tem <= nargs; tem++)
929               {
930                 argvec[tem] = evaluate_subexp_with_coercion (exp, pos, noside);
931                 /* Arguments in Fortran are passed by address.  Coerce the
932                    arguments here rather than in value_arg_coerce as
933                    otherwise the call to malloc to place the non-lvalue
934                    parameters in target memory is hit by this Fortran
935                    specific logic.  This results in malloc being called
936                    with a pointer to an integer followed by an attempt to
937                    malloc the arguments to malloc in target memory.
938                    Infinite recursion ensues.  */
939                 if (code == TYPE_CODE_PTR || code == TYPE_CODE_FUNC)
940                   {
941                     bool is_artificial
942                       = TYPE_FIELD_ARTIFICIAL (value_type (arg1), tem - 1);
943                     argvec[tem] = fortran_argument_convert (argvec[tem],
944                                                             is_artificial);
945                   }
946               }
947             argvec[tem] = 0;    /* signal end of arglist */
948             if (noside == EVAL_SKIP)
949               return eval_skip_value (exp);
950             return evaluate_subexp_do_call (exp, noside, argvec[0],
951                                             gdb::make_array_view (argvec + 1,
952                                                                   nargs),
953                                             NULL, expect_type);
954           }
955
956         default:
957           error (_("Cannot perform substring on this type"));
958         }
959     }
960
961   /* Should be unreachable.  */
962   return nullptr;
963 }
964
965 /* Special expression lengths for Fortran.  */
966
967 static void
968 operator_length_f (const struct expression *exp, int pc, int *oplenp,
969                    int *argsp)
970 {
971   int oplen = 1;
972   int args = 0;
973
974   switch (exp->elts[pc - 1].opcode)
975     {
976     default:
977       operator_length_standard (exp, pc, oplenp, argsp);
978       return;
979
980     case UNOP_FORTRAN_KIND:
981     case UNOP_FORTRAN_FLOOR:
982     case UNOP_FORTRAN_CEILING:
983       oplen = 1;
984       args = 1;
985       break;
986
987     case BINOP_FORTRAN_CMPLX:
988     case BINOP_FORTRAN_MODULO:
989       oplen = 1;
990       args = 2;
991       break;
992
993     case OP_F77_UNDETERMINED_ARGLIST:
994       oplen = 3;
995       args = 1 + longest_to_int (exp->elts[pc - 2].longconst);
996       break;
997     }
998
999   *oplenp = oplen;
1000   *argsp = args;
1001 }
1002
1003 /* Helper for PRINT_SUBEXP_F.  Arguments are as for PRINT_SUBEXP_F, except
1004    the extra argument NAME which is the text that should be printed as the
1005    name of this operation.  */
1006
1007 static void
1008 print_unop_subexp_f (struct expression *exp, int *pos,
1009                      struct ui_file *stream, enum precedence prec,
1010                      const char *name)
1011 {
1012   (*pos)++;
1013   fprintf_filtered (stream, "%s(", name);
1014   print_subexp (exp, pos, stream, PREC_SUFFIX);
1015   fputs_filtered (")", stream);
1016 }
1017
1018 /* Helper for PRINT_SUBEXP_F.  Arguments are as for PRINT_SUBEXP_F, except
1019    the extra argument NAME which is the text that should be printed as the
1020    name of this operation.  */
1021
1022 static void
1023 print_binop_subexp_f (struct expression *exp, int *pos,
1024                       struct ui_file *stream, enum precedence prec,
1025                       const char *name)
1026 {
1027   (*pos)++;
1028   fprintf_filtered (stream, "%s(", name);
1029   print_subexp (exp, pos, stream, PREC_SUFFIX);
1030   fputs_filtered (",", stream);
1031   print_subexp (exp, pos, stream, PREC_SUFFIX);
1032   fputs_filtered (")", stream);
1033 }
1034
1035 /* Special expression printing for Fortran.  */
1036
1037 static void
1038 print_subexp_f (struct expression *exp, int *pos,
1039                 struct ui_file *stream, enum precedence prec)
1040 {
1041   int pc = *pos;
1042   enum exp_opcode op = exp->elts[pc].opcode;
1043
1044   switch (op)
1045     {
1046     default:
1047       print_subexp_standard (exp, pos, stream, prec);
1048       return;
1049
1050     case UNOP_FORTRAN_KIND:
1051       print_unop_subexp_f (exp, pos, stream, prec, "KIND");
1052       return;
1053
1054     case UNOP_FORTRAN_FLOOR:
1055       print_unop_subexp_f (exp, pos, stream, prec, "FLOOR");
1056       return;
1057
1058     case UNOP_FORTRAN_CEILING:
1059       print_unop_subexp_f (exp, pos, stream, prec, "CEILING");
1060       return;
1061
1062     case BINOP_FORTRAN_CMPLX:
1063       print_binop_subexp_f (exp, pos, stream, prec, "CMPLX");
1064       return;
1065
1066     case BINOP_FORTRAN_MODULO:
1067       print_binop_subexp_f (exp, pos, stream, prec, "MODULO");
1068       return;
1069
1070     case OP_F77_UNDETERMINED_ARGLIST:
1071       (*pos)++;
1072       print_subexp_funcall (exp, pos, stream);
1073       return;
1074     }
1075 }
1076
1077 /* Special expression dumping for Fortran.  */
1078
1079 static int
1080 dump_subexp_body_f (struct expression *exp,
1081                     struct ui_file *stream, int elt)
1082 {
1083   int opcode = exp->elts[elt].opcode;
1084   int oplen, nargs, i;
1085
1086   switch (opcode)
1087     {
1088     default:
1089       return dump_subexp_body_standard (exp, stream, elt);
1090
1091     case UNOP_FORTRAN_KIND:
1092     case UNOP_FORTRAN_FLOOR:
1093     case UNOP_FORTRAN_CEILING:
1094     case BINOP_FORTRAN_CMPLX:
1095     case BINOP_FORTRAN_MODULO:
1096       operator_length_f (exp, (elt + 1), &oplen, &nargs);
1097       break;
1098
1099     case OP_F77_UNDETERMINED_ARGLIST:
1100       return dump_subexp_body_funcall (exp, stream, elt + 1);
1101     }
1102
1103   elt += oplen;
1104   for (i = 0; i < nargs; i += 1)
1105     elt = dump_subexp (exp, stream, elt);
1106
1107   return elt;
1108 }
1109
1110 /* Special expression checking for Fortran.  */
1111
1112 static int
1113 operator_check_f (struct expression *exp, int pos,
1114                   int (*objfile_func) (struct objfile *objfile,
1115                                        void *data),
1116                   void *data)
1117 {
1118   const union exp_element *const elts = exp->elts;
1119
1120   switch (elts[pos].opcode)
1121     {
1122     case UNOP_FORTRAN_KIND:
1123     case UNOP_FORTRAN_FLOOR:
1124     case UNOP_FORTRAN_CEILING:
1125     case BINOP_FORTRAN_CMPLX:
1126     case BINOP_FORTRAN_MODULO:
1127       /* Any references to objfiles are held in the arguments to this
1128          expression, not within the expression itself, so no additional
1129          checking is required here, the outer expression iteration code
1130          will take care of checking each argument.  */
1131       break;
1132
1133     default:
1134       return operator_check_standard (exp, pos, objfile_func, data);
1135     }
1136
1137   return 0;
1138 }
1139
1140 /* Expression processing for Fortran.  */
1141 const struct exp_descriptor f_language::exp_descriptor_tab =
1142 {
1143   print_subexp_f,
1144   operator_length_f,
1145   operator_check_f,
1146   dump_subexp_body_f,
1147   evaluate_subexp_f
1148 };
1149
1150 /* See language.h.  */
1151
1152 void
1153 f_language::language_arch_info (struct gdbarch *gdbarch,
1154                                 struct language_arch_info *lai) const
1155 {
1156   const struct builtin_f_type *builtin = builtin_f_type (gdbarch);
1157
1158   /* Helper function to allow shorter lines below.  */
1159   auto add  = [&] (struct type * t)
1160   {
1161     lai->add_primitive_type (t);
1162   };
1163
1164   add (builtin->builtin_character);
1165   add (builtin->builtin_logical);
1166   add (builtin->builtin_logical_s1);
1167   add (builtin->builtin_logical_s2);
1168   add (builtin->builtin_logical_s8);
1169   add (builtin->builtin_real);
1170   add (builtin->builtin_real_s8);
1171   add (builtin->builtin_real_s16);
1172   add (builtin->builtin_complex_s8);
1173   add (builtin->builtin_complex_s16);
1174   add (builtin->builtin_void);
1175
1176   lai->set_string_char_type (builtin->builtin_character);
1177   lai->set_bool_type (builtin->builtin_logical_s2, "logical");
1178 }
1179
1180 /* See language.h.  */
1181
1182 unsigned int
1183 f_language::search_name_hash (const char *name) const
1184 {
1185   return cp_search_name_hash (name);
1186 }
1187
1188 /* See language.h.  */
1189
1190 struct block_symbol
1191 f_language::lookup_symbol_nonlocal (const char *name,
1192                                     const struct block *block,
1193                                     const domain_enum domain) const
1194 {
1195   return cp_lookup_symbol_nonlocal (this, name, block, domain);
1196 }
1197
1198 /* See language.h.  */
1199
1200 symbol_name_matcher_ftype *
1201 f_language::get_symbol_name_matcher_inner
1202         (const lookup_name_info &lookup_name) const
1203 {
1204   return cp_get_symbol_name_matcher (lookup_name);
1205 }
1206
1207 /* Single instance of the Fortran language class.  */
1208
1209 static f_language f_language_defn;
1210
1211 static void *
1212 build_fortran_types (struct gdbarch *gdbarch)
1213 {
1214   struct builtin_f_type *builtin_f_type
1215     = GDBARCH_OBSTACK_ZALLOC (gdbarch, struct builtin_f_type);
1216
1217   builtin_f_type->builtin_void
1218     = arch_type (gdbarch, TYPE_CODE_VOID, TARGET_CHAR_BIT, "void");
1219
1220   builtin_f_type->builtin_character
1221     = arch_type (gdbarch, TYPE_CODE_CHAR, TARGET_CHAR_BIT, "character");
1222
1223   builtin_f_type->builtin_logical_s1
1224     = arch_boolean_type (gdbarch, TARGET_CHAR_BIT, 1, "logical*1");
1225
1226   builtin_f_type->builtin_integer_s2
1227     = arch_integer_type (gdbarch, gdbarch_short_bit (gdbarch), 0,
1228                          "integer*2");
1229
1230   builtin_f_type->builtin_integer_s8
1231     = arch_integer_type (gdbarch, gdbarch_long_long_bit (gdbarch), 0,
1232                          "integer*8");
1233
1234   builtin_f_type->builtin_logical_s2
1235     = arch_boolean_type (gdbarch, gdbarch_short_bit (gdbarch), 1,
1236                          "logical*2");
1237
1238   builtin_f_type->builtin_logical_s8
1239     = arch_boolean_type (gdbarch, gdbarch_long_long_bit (gdbarch), 1,
1240                          "logical*8");
1241
1242   builtin_f_type->builtin_integer
1243     = arch_integer_type (gdbarch, gdbarch_int_bit (gdbarch), 0,
1244                          "integer");
1245
1246   builtin_f_type->builtin_logical
1247     = arch_boolean_type (gdbarch, gdbarch_int_bit (gdbarch), 1,
1248                          "logical*4");
1249
1250   builtin_f_type->builtin_real
1251     = arch_float_type (gdbarch, gdbarch_float_bit (gdbarch),
1252                        "real", gdbarch_float_format (gdbarch));
1253   builtin_f_type->builtin_real_s8
1254     = arch_float_type (gdbarch, gdbarch_double_bit (gdbarch),
1255                        "real*8", gdbarch_double_format (gdbarch));
1256   auto fmt = gdbarch_floatformat_for_type (gdbarch, "real(kind=16)", 128);
1257   if (fmt != nullptr)
1258     builtin_f_type->builtin_real_s16
1259       = arch_float_type (gdbarch, 128, "real*16", fmt);
1260   else if (gdbarch_long_double_bit (gdbarch) == 128)
1261     builtin_f_type->builtin_real_s16
1262       = arch_float_type (gdbarch, gdbarch_long_double_bit (gdbarch),
1263                          "real*16", gdbarch_long_double_format (gdbarch));
1264   else
1265     builtin_f_type->builtin_real_s16
1266       = arch_type (gdbarch, TYPE_CODE_ERROR, 128, "real*16");
1267
1268   builtin_f_type->builtin_complex_s8
1269     = init_complex_type ("complex*8", builtin_f_type->builtin_real);
1270   builtin_f_type->builtin_complex_s16
1271     = init_complex_type ("complex*16", builtin_f_type->builtin_real_s8);
1272
1273   if (builtin_f_type->builtin_real_s16->code () == TYPE_CODE_ERROR)
1274     builtin_f_type->builtin_complex_s32
1275       = arch_type (gdbarch, TYPE_CODE_ERROR, 256, "complex*32");
1276   else
1277     builtin_f_type->builtin_complex_s32
1278       = init_complex_type ("complex*32", builtin_f_type->builtin_real_s16);
1279
1280   return builtin_f_type;
1281 }
1282
1283 static struct gdbarch_data *f_type_data;
1284
1285 const struct builtin_f_type *
1286 builtin_f_type (struct gdbarch *gdbarch)
1287 {
1288   return (const struct builtin_f_type *) gdbarch_data (gdbarch, f_type_data);
1289 }
1290
1291 /* Command-list for the "set/show fortran" prefix command.  */
1292 static struct cmd_list_element *set_fortran_list;
1293 static struct cmd_list_element *show_fortran_list;
1294
1295 void _initialize_f_language ();
1296 void
1297 _initialize_f_language ()
1298 {
1299   f_type_data = gdbarch_data_register_post_init (build_fortran_types);
1300
1301   add_basic_prefix_cmd ("fortran", no_class,
1302                         _("Prefix command for changing Fortran-specific settings."),
1303                         &set_fortran_list, "set fortran ", 0, &setlist);
1304
1305   add_show_prefix_cmd ("fortran", no_class,
1306                        _("Generic command for showing Fortran-specific settings."),
1307                        &show_fortran_list, "show fortran ", 0, &showlist);
1308
1309   add_setshow_boolean_cmd ("repack-array-slices", class_vars,
1310                            &repack_array_slices, _("\
1311 Enable or disable repacking of non-contiguous array slices."), _("\
1312 Show whether non-contiguous array slices are repacked."), _("\
1313 When the user requests a slice of a Fortran array then we can either return\n\
1314 a descriptor that describes the array in place (using the original array data\n\
1315 in its existing location) or the original data can be repacked (copied) to a\n\
1316 new location.\n\
1317 \n\
1318 When the content of the array slice is contiguous within the original array\n\
1319 then the result will never be repacked, but when the data for the new array\n\
1320 is non-contiguous within the original array repacking will only be performed\n\
1321 when this setting is on."),
1322                            NULL,
1323                            show_repack_array_slices,
1324                            &set_fortran_list, &show_fortran_list);
1325
1326   /* Debug Fortran's array slicing logic.  */
1327   add_setshow_boolean_cmd ("fortran-array-slicing", class_maintenance,
1328                            &fortran_array_slicing_debug, _("\
1329 Set debugging of Fortran array slicing."), _("\
1330 Show debugging of Fortran array slicing."), _("\
1331 When on, debugging of Fortran array slicing is enabled."),
1332                             NULL,
1333                             show_fortran_array_slicing_debug,
1334                             &setdebuglist, &showdebuglist);
1335 }
1336
1337 /* Ensures that function argument VALUE is in the appropriate form to
1338    pass to a Fortran function.  Returns a possibly new value that should
1339    be used instead of VALUE.
1340
1341    When IS_ARTIFICIAL is true this indicates an artificial argument,
1342    e.g. hidden string lengths which the GNU Fortran argument passing
1343    convention specifies as being passed by value.
1344
1345    When IS_ARTIFICIAL is false, the argument is passed by pointer.  If the
1346    value is already in target memory then return a value that is a pointer
1347    to VALUE.  If VALUE is not in memory (e.g. an integer literal), allocate
1348    space in the target, copy VALUE in, and return a pointer to the in
1349    memory copy.  */
1350
1351 static struct value *
1352 fortran_argument_convert (struct value *value, bool is_artificial)
1353 {
1354   if (!is_artificial)
1355     {
1356       /* If the value is not in the inferior e.g. registers values,
1357          convenience variables and user input.  */
1358       if (VALUE_LVAL (value) != lval_memory)
1359         {
1360           struct type *type = value_type (value);
1361           const int length = TYPE_LENGTH (type);
1362           const CORE_ADDR addr
1363             = value_as_long (value_allocate_space_in_inferior (length));
1364           write_memory (addr, value_contents (value), length);
1365           struct value *val
1366             = value_from_contents_and_address (type, value_contents (value),
1367                                                addr);
1368           return value_addr (val);
1369         }
1370       else
1371         return value_addr (value); /* Program variables, e.g. arrays.  */
1372     }
1373     return value;
1374 }
1375
1376 /* See f-lang.h.  */
1377
1378 struct type *
1379 fortran_preserve_arg_pointer (struct value *arg, struct type *type)
1380 {
1381   if (value_type (arg)->code () == TYPE_CODE_PTR)
1382     return value_type (arg);
1383   return type;
1384 }
1385
1386 /* See f-lang.h.  */
1387
1388 CORE_ADDR
1389 fortran_adjust_dynamic_array_base_address_hack (struct type *type,
1390                                                 CORE_ADDR address)
1391 {
1392   gdb_assert (type->code () == TYPE_CODE_ARRAY);
1393
1394   int ndimensions = calc_f77_array_dims (type);
1395   LONGEST total_offset = 0;
1396
1397   /* Walk through each of the dimensions of this array type and figure out
1398      if any of the dimensions are "backwards", that is the base address
1399      for this dimension points to the element at the highest memory
1400      address and the stride is negative.  */
1401   struct type *tmp_type = type;
1402   for (int i = 0 ; i < ndimensions; ++i)
1403     {
1404       /* Grab the range for this dimension and extract the lower and upper
1405          bounds.  */
1406       tmp_type = check_typedef (tmp_type);
1407       struct type *range_type = tmp_type->index_type ();
1408       LONGEST lowerbound, upperbound, stride;
1409       if (!get_discrete_bounds (range_type, &lowerbound, &upperbound))
1410         error ("failed to get range bounds");
1411
1412       /* Figure out the stride for this dimension.  */
1413       struct type *elt_type = check_typedef (TYPE_TARGET_TYPE (tmp_type));
1414       stride = tmp_type->index_type ()->bounds ()->bit_stride ();
1415       if (stride == 0)
1416         stride = type_length_units (elt_type);
1417       else
1418         {
1419           struct gdbarch *arch = get_type_arch (elt_type);
1420           int unit_size = gdbarch_addressable_memory_unit_size (arch);
1421           stride /= (unit_size * 8);
1422         }
1423
1424       /* If this dimension is "backward" then figure out the offset
1425          adjustment required to point to the element at the lowest memory
1426          address, and add this to the total offset.  */
1427       LONGEST offset = 0;
1428       if (stride < 0 && lowerbound < upperbound)
1429         offset = (upperbound - lowerbound) * stride;
1430       total_offset += offset;
1431       tmp_type = TYPE_TARGET_TYPE (tmp_type);
1432     }
1433
1434   /* Adjust the address of this object and return it.  */
1435   address += total_offset;
1436   return address;
1437 }
This page took 0.10689 seconds and 4 git commands to generate.