2017-11-09 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / fortran / ChangeLog
blob7d016278b262150a6f893e54af7b6dc2fdd9eb2e
1 2017-11-09  Paul Thomas  <pault@gcc.gnu.org>
3         PR fortran/78619
4         * check.c (same_type_check): Introduce a new argument 'assoc'
5         with default value false. If this is true, use the symbol type
6         spec of BT_PROCEDURE expressions.
7         (gfc_check_associated): Set 'assoc' true in the call to
8         'same_type_check'.
10 2017-11-09  Steven G. Kargl  <kargl@gcc.gnu.org>
12         PR fortran/78814
13         * interface.c (symbol_rank): Check for NULL pointer.
15 2017-11-08  Steven G. Kargl  <kargl@kgcc.gnu.org>
17         PR Fortran/82841
18         * simplify.c(gfc_simplify_transfer): Do not dereference a NULL pointer.
19         Unwrap a short line.
21 2017-11-08  Steven G. Kargl  <kargl@gcc.gnu.org>
23         PR fortran/82884
24         * arith.c (gfc_hollerith2character): Clear pad.
26 2017-11-08  Janne Blomqvist  <jb@gcc.gnu.org>
28         PR 82869
29         * convert.c (truthvalue_conversion): Use logical_type_node.
30         * trans-array.c (gfc_trans_allocate_array_storage): Likewise.
31         (gfc_trans_create_temp_array): Likewise.
32         (gfc_trans_array_ctor_element): Likewise.
33         (gfc_trans_array_constructor_value): Likewise.
34         (trans_array_constructor): Likewise.
35         (trans_array_bound_check): Likewise.
36         (gfc_conv_array_ref): Likewise.
37         (gfc_trans_scalarized_loop_end): Likewise.
38         (gfc_conv_array_extent_dim): Likewise.
39         (gfc_array_init_size): Likewise.
40         (gfc_array_allocate): Likewise.
41         (gfc_trans_array_bounds): Likewise.
42         (gfc_trans_dummy_array_bias): Likewise.
43         (gfc_conv_array_parameter): Likewise.
44         (duplicate_allocatable): Likewise.
45         (duplicate_allocatable_coarray): Likewise.
46         (structure_alloc_comps): Likewise
47         (get_std_lbound): Likewise
48         (gfc_alloc_allocatable_for_assignment): Likewise
49         * trans-decl.c (add_argument_checking): Likewise
50         (gfc_generate_function_code): Likewise
51         * trans-expr.c (gfc_copy_class_to_class): Likewise
52         (gfc_trans_class_array_init_assign): Likewise
53         (gfc_trans_class_init_assign): Likewise
54         (gfc_conv_expr_present): Likewise
55         (gfc_conv_substring): Likewise
56         (gfc_conv_cst_int_power): Likewise
57         (gfc_conv_expr_op): Likewise
58         (gfc_conv_procedure_call): Likewise
59         (fill_with_spaces): Likewise
60         (gfc_trans_string_copy): Likewise
61         (gfc_trans_alloc_subarray_assign): Likewise
62         (gfc_trans_pointer_assignment): Likewise
63         (gfc_trans_scalar_assign): Likewise
64         (fcncall_realloc_result): Likewise
65         (alloc_scalar_allocatable_for_assignment): Likewise
66         (trans_class_assignment): Likewise
67         (gfc_trans_assignment_1): Likewise
68         * trans-intrinsic.c (build_fixbound_expr): Likewise
69         (gfc_conv_intrinsic_aint): Likewise
70         (gfc_trans_same_strlen_check): Likewise
71         (conv_caf_send): Likewise
72         (trans_this_image): Likewise
73         (conv_intrinsic_image_status): Likewise
74         (trans_image_index): Likewise
75         (gfc_conv_intrinsic_bound): Likewise
76         (conv_intrinsic_cobound): Likewise
77         (gfc_conv_intrinsic_mod): Likewise
78         (gfc_conv_intrinsic_dshift): Likewise
79         (gfc_conv_intrinsic_dim): Likewise
80         (gfc_conv_intrinsic_sign): Likewise
81         (gfc_conv_intrinsic_ctime): Likewise
82         (gfc_conv_intrinsic_fdate): Likewise
83         (gfc_conv_intrinsic_ttynam): Likewise
84         (gfc_conv_intrinsic_minmax): Likewise
85         (gfc_conv_intrinsic_minmax_char): Likewise
86         (gfc_conv_intrinsic_anyall): Likewise
87         (gfc_conv_intrinsic_arith): Likewise
88         (gfc_conv_intrinsic_minmaxloc): Likewise
89         (gfc_conv_intrinsic_minmaxval): Likewise
90         (gfc_conv_intrinsic_btest): Likewise
91         (gfc_conv_intrinsic_bitcomp): Likewise
92         (gfc_conv_intrinsic_shift): Likewise
93         (gfc_conv_intrinsic_ishft): Likewise
94         (gfc_conv_intrinsic_ishftc): Likewise
95         (gfc_conv_intrinsic_leadz): Likewise
96         (gfc_conv_intrinsic_trailz): Likewise
97         (gfc_conv_intrinsic_mask): Likewise
98         (gfc_conv_intrinsic_spacing): Likewise
99         (gfc_conv_intrinsic_rrspacing): Likewise
100         (gfc_conv_intrinsic_size): Likewise
101         (gfc_conv_intrinsic_sizeof): Likewise
102         (gfc_conv_intrinsic_transfer): Likewise
103         (gfc_conv_allocated): Likewise
104         (gfc_conv_associated): Likewise
105         (gfc_conv_same_type_as): Likewise
106         (gfc_conv_intrinsic_trim): Likewise
107         (gfc_conv_intrinsic_repeat): Likewise
108         (conv_isocbinding_function): Likewise
109         (conv_intrinsic_ieee_is_normal): Likewise
110         (conv_intrinsic_ieee_is_negative): Likewise
111         (conv_intrinsic_ieee_copy_sign): Likewise
112         (conv_intrinsic_move_alloc): Likewise
113         * trans-io.c (set_parameter_value_chk): Likewise
114         (set_parameter_value_inquire): Likewise
115         (set_string): Likewise
116         * trans-openmp.c (gfc_walk_alloc_comps): Likewise
117         (gfc_omp_clause_default_ctor): Likewise
118         (gfc_omp_clause_copy_ctor): Likewise
119         (gfc_omp_clause_assign_op): Likewise
120         (gfc_omp_clause_dtor): Likewise
121         (gfc_omp_finish_clause): Likewise
122         (gfc_trans_omp_clauses): Likewise
123         (gfc_trans_omp_do): Likewise
124         * trans-stmt.c (gfc_trans_goto): Likewise
125         (gfc_trans_sync): Likewise
126         (gfc_trans_arithmetic_if): Likewise
127         (gfc_trans_simple_do): Likewise
128         (gfc_trans_do): Likewise
129         (gfc_trans_forall_loop): Likewise
130         (gfc_trans_where_2): Likewise
131         (gfc_trans_allocate): Likewise
132         (gfc_trans_deallocate): Likewise
133         * trans-types.c (gfc_init_types): Initialize logical_type_node and
134         their true/false trees.
135         (gfc_get_array_descr_info): Use logical_type_node.
136         * trans-types.h (logical_type_node): New tree.
137         (logical_true_node): Likewise.
138         (logical_false_node): Likewise.
139         * trans.c (gfc_trans_runtime_check): Use logical_type_node.
140         (gfc_call_malloc): Likewise
141         (gfc_allocate_using_malloc): Likewise
142         (gfc_allocate_allocatable): Likewise
143         (gfc_add_comp_finalizer_call): Likewise
144         (gfc_add_finalizer_call): Likewise
145         (gfc_deallocate_with_status): Likewise
146         (gfc_deallocate_scalar_with_status): Likewise
147         (gfc_call_realloc): Likewise
149 2017-11-06  Paul Thomas  <pault@gcc.gnu.org>
151         PR fortran/69739
152         * trans-expr.c (gfc_map_intrinsic_function): Return false for
153         bounds without the DIM argument instead of ICEing.
155 2017-11-06  Martin Liska  <mliska@suse.cz>
157         PR middle-end/82404
158         * options.c (gfc_post_options): Set default value of
159         -Wreturn-type to false.
161 2017-11-05  Thomas Koenig  <tkoenig@gcc.gnu.org>
163         PR fortran/82471
164         * lang.opt (ffrontend-loop-interchange): New option.
165         (Wfrontend-loop-interchange): New option.
166         * options.c (gfc_post_options): Handle ffrontend-loop-interchange.
167         * frontend-passes.c (gfc_run_passes): Run
168         optimize_namespace if flag_frontend_optimize or
169         flag_frontend_loop_interchange are set.
170         (optimize_namespace): Run functions according to flags set;
171         also call index_interchange.
172         (ind_type): New function.
173         (has_var): New function.
174         (index_cost): New function.
175         (loop_comp): New function.
177 2017-11-05  Paul Thomas  <pault@gcc.gnu.org>
179         PR fortran/78641
180         * resolve.c (resolve_ordinary_assign): Do not add the _data
181         component for class valued array constructors being assigned
182         to derived type arrays.
183         * trans-array.c (gfc_trans_array_ctor_element): Take the _data
184         of class valued elements for assignment to derived type arrays.
186 2017-11-05  Paul Thomas  <pault@gcc.gnu.org>
188         PR fortran/81447
189         PR fortran/82783
190         * resolve.c (resolve_component): There is no need to resolve
191         the components of a use associated vtype.
192         (resolve_fl_derived): Unconditionally generate a vtable for any
193         module derived type, as long as the standard is F2003 or later
194         and it is not a vtype or a PDT template.
196 2017-11-05  Tom de Vries  <tom@codesourcery.com>
198         PR other/82784
199         * parse.c (match, matcha, matchs, matcho, matchds, matchdo): Remove
200         semicolon after "do {} while (0)".
202 2017-11-04  Andre Vehreschild  <vehre@gcc.gnu.org>
204         * trans-expr.c (gfc_trans_assignment_1): Character kind conversion may
205         create a loop variant temporary, too.
206         * trans-intrinsic.c (conv_caf_send): Treat char arrays as arrays and
207         not as scalars.
208         * trans.c (get_array_span): Take the character kind into account when
209         doing pointer arithmetic.
211 2017-11-04  Thomas Koenig  <tkoenig@gcc.gnu.org>
213         PR fortran/29600
214         * gfortran.h (gfc_check_f): Replace fm3l with fm4l.
215         * intrinsic.h (gfc_resolve_maxloc): Add gfc_expr * to argument
216         list in protoytpe.
217         (gfc_resolve_minloc): Likewise.
218         * check.c (gfc_check_minloc_maxloc): Handle kind argument.
219         * intrinsic.c (add_sym_3_ml): Rename to
220         (add_sym_4_ml): and handle kind argument.
221         (add_function): Replace add_sym_3ml with add_sym_4ml and add
222         extra arguments for maxloc and minloc.
223         (check_specific): Change use of check.f3ml with check.f4ml.
224         * iresolve.c (gfc_resolve_maxloc): Handle kind argument. If
225         the kind is smaller than the smallest library version available,
226         use gfc_default_integer_kind and convert afterwards.
227         (gfc_resolve_minloc): Likewise.
229 2017-11-04  Paul Thomas  <pault@gcc.gnu.org>
231         PR fortran/81735
232         * trans-decl.c (gfc_trans_deferred_vars): Do a better job of a
233         case where 'tmp' was used unititialized and remove TODO.
235 2017-11-03  Steven G. Kargl  <kargl@gcc.gnu.org>
237         PR fortran/82796
238         * resolve.c (resolve_equivalence): An entity in a common block within
239         a module cannot appear in an equivalence statement if the entity is
240         with a pure procedure.
242 2017-10-31  Jim Wilson  <wilson@tuliptree.org>
244         * parse.c (unexpected_eof): Call gcc_unreachable before return.
246 2017-10-30  Paul Thomas  <pault@gcc.gnu.org>
248         PR fortran/80850
249         * trans_expr.c (gfc_conv_procedure_call): When passing a class
250         argument to an unlimited polymorphic dummy, it is wrong to cast
251         the passed expression as unlimited, unless it is unlimited. The
252         correct way is to assign to each of the fields and set the _len
253         field to zero.
255 2017-10-30  Steven G. Kargl   <kargl@gcc.gnu.org>
257         * resolve.c (resolve_transfer): Set derived to correct symbol for
258         BT_CLASS.
260 2017-10-29  Jim Wilson  <wilson@tuliptree.org>
262         * invoke.texi: Delete adb and sdb references.
264 2017-10-28  Andre Vehreschild  <vehre@gcc.gnu.org>
266         * check.c (gfc_check_co_reduce): Clarify error message.
268 2017-10-28  Paul Thomas  <pault@gcc.gnu.org>
270         PR fortran/81758
271         * trans-expr.c (trans_class_vptr_len_assignment): 'vptr_expr'
272         must only be set if the right hand side expression is of type
273         class.
275 2017-10-27  Steven G. Kargl  <kargl@gcc.gnu.org>
277         PR fortran/82620
278         * match.c (gfc_match_allocate): Exit early on syntax error.
280 2017-10-27  Thomas Koenig  <tkoenig@gcc.gnu.org>
282         PR fortran/56342
283         * simplify.c (is_constant_array_expr): If the expression is
284         a parameter array, call gfc_simplify_expr.
286 2017-10-25  Bernhard Reutner-Fischer  <aldot@gcc.gnu.org>
288         * match.c (gfc_match_type_is): Fix typo in error message.
290 2017-10-21  Paul Thomas  <pault@gcc.gnu.org>
292         PR fortran/82586
293         * decl.c (gfc_get_pdt_instance): Remove the error message that
294         the parameter does not have a corresponding component since
295         this is now taken care of when the derived type is resolved. Go
296         straight to error return instead.
297         (gfc_match_formal_arglist): Make the PDT relevant errors
298         immediate so that parsing of the derived type can continue.
299         (gfc_match_derived_decl): Do not check the match status on
300         return from gfc_match_formal_arglist for the same reason.
301         * resolve.c (resolve_fl_derived0): Check that each type
302         parameter has a corresponding component.
304         PR fortran/82587
305         * resolve.c (resolve_generic_f): Check that the derived type
306         can be used before resolving the struture constructor.
308         PR fortran/82589
309         * symbol.c (check_conflict): Add the conflicts involving PDT
310         KIND and LEN attributes.
312 2017-10-19  Bernhard Reutner-Fischer  <aldot@gcc.gnu.org>
314         * interface.c (check_sym_interfaces, check_uop_interfaces,
315         gfc_check_interfaces): Base interface_name buffer off
316         GFC_MAX_SYMBOL_LEN.
318 2017-10-19  Jakub Jelinek  <jakub@redhat.com>
320         PR fortran/82568
321         * gfortran.h (gfc_resolve_do_iterator): Add a bool arg.
322         (gfc_resolve_omp_local_vars): New declaration.
323         * openmp.c (omp_current_ctx): Make static.
324         (gfc_resolve_omp_parallel_blocks): Handle EXEC_OMP_TASKLOOP
325         and EXEC_OMP_TASKLOOP_SIMD.
326         (gfc_resolve_do_iterator): Add ADD_CLAUSE argument, if false,
327         don't actually add any clause.  Move omp_current_ctx test
328         earlier.
329         (handle_local_var, gfc_resolve_omp_local_vars): New functions.
330         * resolve.c (gfc_resolve_code): Call gfc_resolve_omp_parallel_blocks
331         instead of just gfc_resolve_omp_do_blocks for EXEC_OMP_TASKLOOP
332         and EXEC_OMP_TASKLOOP_SIMD.
333         (gfc_resolve_code): Adjust gfc_resolve_do_iterator caller.
334         (resolve_codes): Call gfc_resolve_omp_local_vars.
336 2017-10-19  Bernhard Reutner-Fischer  <aldot@gcc.gnu.org>
338         * gfortran.h (gfc_lookup_function_fuzzy): New declaration.
339         (gfc_closest_fuzzy_match): New declaration.
340         (vec_push): New definition.
341         * misc.c (gfc_closest_fuzzy_match): New definition.
342         * resolve.c: Include spellcheck.h.
343         (lookup_function_fuzzy_find_candidates): New static function.
344         (lookup_uop_fuzzy_find_candidates): Likewise.
345         (lookup_uop_fuzzy): Likewise.
346         (resolve_operator) <INTRINSIC_USER>: Call lookup_uop_fuzzy.
347         (gfc_lookup_function_fuzzy): New definition.
348         (resolve_unknown_f): Call gfc_lookup_function_fuzzy.
349         * interface.c (check_interface0): Likewise.
350         (lookup_arg_fuzzy_find_candidates): New static function.
351         (lookup_arg_fuzzy ): Likewise.
352         (compare_actual_formal): Call lookup_arg_fuzzy.
353         * symbol.c: Include spellcheck.h.
354         (lookup_symbol_fuzzy_find_candidates): New static function.
355         (lookup_symbol_fuzzy): Likewise.
356         (gfc_set_default_type): Call lookup_symbol_fuzzy.
357         (lookup_component_fuzzy_find_candidates): New static function.
358         (lookup_component_fuzzy): Likewise.
359         (gfc_find_component): Call lookup_component_fuzzy.
361 2017-10-18  Thomas Koenig  <tkoenig@gcc.gnu.org>
363         PR fortran/82567
364         * frontend-passes.c (combine_array_constructor): If an array
365         constructor is all constants and has more elements than a small
366         constant, don't convert a*[b,c] to [a*b,a*c] to reduce compilation
367         times.
369 2017-10-18  Thomas Koenig  <tkoenig@gcc.gnu.org>
371         PR fortran/79795
372         * resolve.c (resovle_symbol): Change gcc_assert to
373         sensible error message.
375 2017-10-18  Paul Thomas  <pault@gcc.gnu.org>
377         PR fortran/82550
378         * trans_decl.c (gfc_get_symbol_decl): Procedure symbols that
379         have the 'used_in_submodule' attribute should be processed by
380         'gfc_get_extern_function_decl'.
382 2017-10-16  Fritz Reese <fritzoreese@gmail.com>
384         PR fortran/82511
385         * trans-io.c (transfer_expr): Treat BT_UNION as BT_DERIVED.
387 2017-10-15  Thomas Koenig  <tkoenig@gcc.gnu.org>
389         PR fortran/82372
390         * fortran/scanner.c (last_error_char):  New global variable.
391         (gfc_scanner_init_1): Set last_error_char to NULL.
392         (gfc_gobble_whitespace): If a character not printable or
393         not newline, issue an error.
395 2017-10-13  Paul Thomas  <pault@gcc.gnu.org>
397         PR fortran/81048
398         * resolve.c (resolve_symbol): Ensure that derived type array
399         results get default initialization.
401 2017-10-11  Nathan Sidwell  <nathan@acm.org>
403         * cpp.c (gfc_cpp_add_include_path): Update incpath_e names.
404         (gfc_cpp_add_include_path_after): Likewise.
406 2017-10-10  Richard Sandiford  <richard.sandiford@linaro.org>
408         * target-memory.c (gfc_interpret_logical): Use wi::to_wide when
409         operating on trees as wide_ints.
410         * trans-const.c (gfc_conv_tree_to_mpz): Likewise.
411         * trans-expr.c (gfc_conv_cst_int_power): Likewise.
412         * trans-intrinsic.c (trans_this_image): Likewise.
413         (gfc_conv_intrinsic_bound): Likewise.
414         (conv_intrinsic_cobound): Likewise.
416 2017-10-08  Steven G. Kargl  <kargl@gcc.gnu.org>
418         * check.c (gfc_check_x): Remove function.
419         * intrinsic.c (add_functions): Use gfc_check_fn_r.
421 2017-10-08  Paul Thomas  <pault@gcc.gnu.org>
423         PR fortran/82375
424         * module.c : Bump up MOD_VERSION to 15.
425         (mio_component): Edit comment about PDT specification list.
426         (mio_expr, mio_symbol): Include the expression and symbol PDT
427         specification lists in the same way as in mio_component.
429 2017-10-08  Thomas Koenig  <tkoenig@gcc.gnu.org>
431         * dump_prase_tree (show_symbol): Output list of variables in
432         NAMELIST.
433         (show_code_node): Add new line for ELSE and END DO for DO
434         CONCURRENT.
435         * invoke.texi: Document that the output of
436         -fdump-fortran-original, -fdump-fortran-optimized and
437         -fdump-parse-tree is unsable and may lead to ICEs.
439 2017-10-07  Paul Thomas  <pault@gcc.gnu.org>
441         PR fortran/82375
442         * class.c (gfc_find_derived_vtab): Return NULL for a passed
443         pdt template to prevent bad procedures from being written.
444         * decl.c (gfc_get_pdt_instance): Do not use the default
445         initializer for pointer and allocatable pdt type components. If
446         the component is allocatbale, set the 'alloc_comp' attribute of
447         'instance'.
448         * module.c : Add a prototype for 'mio_actual_arglist'. Add a
449         boolean argument 'pdt'.
450         (mio_component): Call it for the parameter list of pdt type
451         components with 'pdt' set to true.
452         (mio_actual_arg): Add the boolean 'pdt' and, if it is set, call
453         mio_integer for the 'spec_type'.
454         (mio_actual_arglist): Add the boolean 'pdt' and use it in the
455         call to mio_actual_arg.
456         (mio_expr, mio_omp_udr_expr): Call mio_actual_arglist with
457         'pdt' set false.
458         * resolve.c (get_pdt_spec_expr): Add the parameter name to the
459         KIND parameter error.
460         (get_pdt_constructor): Check that cons->expr is non-null.
461         * trans-array.c (structure_alloc_comps): For deallocation of
462         allocatable components, ensure that parameterized components
463         are deallocated first. Likewise, when parameterized components
464         are allocated, nullify allocatable components first. Do not
465         recurse into pointer or allocatable pdt components while
466         allocating or deallocating parameterized components. Test that
467         parameterized arrays or strings are allocated before freeing
468         them.
469         (gfc_trans_pointer_assignment): Call the new function. Tidy up
470         a minor whitespace issue.
471         trans-decl.c (gfc_trans_deferred_vars): Set 'tmp' to NULL_TREE
472         to prevent the expression from being used a second time.
474 2017-10-07  Thomas Koenig  <tkoenig@gcc.gnu.org>
476         PR fortran/49232
477         * expr.c (gfc_check_pointer_assign): Error
478         for non-contiguous rhs.
480 2017-10-07  Thomas Koenig  <tkoenig@gcc.gnu.org>
482         * gfortran.h (async_io_dt): Add external reference.
483         * io.c (async_io_dt): Add variable.
484         (compare_to_allowed_values): Add prototyte. Add optional argument
485         num. If present, set it to the number of the entry that was
486         matched.
487         (check_io_constraints): If this is for an asynchronous I/O
488         statement, set async_io_dt and set the asynchronous flag for
489         a SIZE tag.
490         * resolve.c (resolve_transfer): If async_io_dt is set, set
491         the asynchronous flag on the variable.
492         (resolve_fl_namelist): If async_io_dt is set, set the asynchronous
493         flag on all elements of the namelist.
495 2017-10-04  Paul Thomas  <pault@gcc.gnu.org>
497         PR fortran/60458
498         PR fortran/77296
499         * resolve.c (resolve_assoc_var): Deferred character type
500         associate names must not receive an integer conatant length.
501         * symbol.c (gfc_is_associate_pointer): Deferred character
502         length functions also require an associate pointer.
503         * trans-decl.c (gfc_get_symbol_decl): Deferred character
504         length functions or derived type components require the assoc
505         name to have variable string length.
506         * trans-stmt.c (trans_associate_var): Set the string length of
507         deferred string length associate names. The address expression
508         is not needed for allocatable, pointer or dummy targets. Change
509         the comment about defered string length targets.
511 2017-10-03  Thomas Koenig  <tkoenig@gcc.gnu.org>
513         * io.c (match_wait_element): Correctly match END and EOR tags.
514         * dump-parse-tree.c (show_code_node): Handle EXEC_WAIT.
516 2017-10-02  Paul Thomas  <pault@gcc.gnu.org>
518         PR fortran/82312
519         * resolve.c (gfc_resolve_code): Simplify condition for class
520         pointer assignments becoming regular assignments by asserting
521         that only class valued targets are permitted.
522         * trans-expr.c (trans_class_pointer_fcn): New function using a
523         block of code from gfc_trans_pointer_assignment.
524         (gfc_trans_pointer_assignment): Call the new function. Tidy up
525         a minor whitespace issue.
527 2017-10-01  Dominique d'Humieres  <dominiq@lps.ens.fr>
529         PR fortran/61450
530         * parse.c (gfc_global_used): Replace the gfc_internal_error
531         with an error.
533 2017-09-29  Dominique d'Humieres  <dominiq@lps.ens.fr>
535         PR fortran/25071
536         * interface.c (compare_actual_formal): Change warnings to errors
537         when "Actual argument contains too few elements for dummy
538         argument", unless -std=legacy is used.
540 2017-09-27  Thomas Schwinge  <thomas@codesourcery.com>
542         * lang.opt <Wdo-subscript>: End help text with a period.
544 2017-09-26  Thomas Koenig  <tkoenig@gcc.gnu.org>
546         * frontend-passes.c (do_subscript): Don't do anything
547         if inside an associate list.
549 2017-09-25  Thomas Koenig  <tkoenig@gcc.gnu.org>
551         * lang.opt:  Add -Wdo-subscript.
552         * frontend-passes.c (do_t): New type.
553         (doloop_list): Use variable of do_type.
554         (if_level): Variable to track if levels.
555         (select_level): Variable to track select levels.
556         (gfc_run_passes): Initialize i_level and select_level.
557         (doloop_code): Record current level of if + select
558         level in doloop_list.  Add seen_goto if there could
559         be a branch outside the loop. Use different type for
560         doloop_list.
561         (doloop_function): Call do_intent and do_subscript; move
562         functionality of checking INTENT to do_intent.
563         (insert_index_t): New type, for callback_insert_index.
564         (callback_insert_index): New function.
565         (insert_index): New function.
566         (do_subscript): New function.
567         (do_intent): New function.
568         (gfc_code_walker): Keep track of if_level and select_level.
569         * invoke.texi: Document -Wdo-subscript.
571 2017-09-25  Janne Blomqvist  <jb@gcc.gnu.org>
573         * trans.c (gfc_unlikely): Remove unnecessary fold_convert.
574         (gfc_likely): Likewise.
576 2017-09-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
577             Steven G. Kargl  <kargl@gcc.gnu.org>
579         PR fortran/80118
580         * expr.c (gfc_get_full_arrayspec_from_expr): If there is
581         no symtree, set array spec to NULL.
583 2017-09-23  Janus Weil  <janus@gcc.gnu.org>
585         PR fortran/82143
586         * lang.opt: Add the options -fdefault-real-10 and -fdefault-real-16.
587         Rename flag_default_real to flag_default_real_8.
588         * invoke.texi: Add documentation.
589         * module.c (use_iso_fortran_env_module): flag_default_real is renamed.
590         * trans-types.c (gfc_init_kinds): Implement the flags
591         -fdefault-real-10 and -fdefault-real-16. Make -fdefault-double-8 work
592         without -fdefault-real-8.
594 2017-09-21  Paul Thomas  <pault@gcc.gnu.org>
596         PR fortran/52832
597         * match.c (gfc_match_associate): Before failing the association
598         try again, allowing a proc pointer selector.
600         PR fortran/80120
601         PR fortran/81903
602         PR fortran/82121
603         * primary.c (gfc_match_varspec): Introduce 'tgt_expr', which
604         points to the associate selector, if any. Go through selector
605         references, after resolution for variables, to catch any full
606         or section array references. If a class associate name does
607         not have the same declared type as the selector, resolve the
608         selector and copy the declared type to the associate name.
609         Before throwing a no implicit type error, resolve all allowed
610         selector expressions, and copy the resulting typespec.
612         PR fortran/67543
613         * resolve.c (resolve_assoc_var): Selector must cannot be the
614         NULL expression and it must have a type.
616         PR fortran/78152
617         * resolve.c (resolve_symbol): Allow associate names to be
618         coarrays.
620 2017-09-21  Cesar Philippidis  <cesar@codesourcery.com>
622         * openmp.c (gfc_match_oacc_wait): Don't restrict wait directive
623         arguments to constant integers.
625 2017-09-17  Paul Thomas  <pault@gcc.gnu.org>
627         PR fortran/82173
628         * decl.c (gfc_get_pdt_instance): Use the component initializer
629         expression for the default, rather than the parameter value.
630         * resolve.c (resolve_pdt): New function.
631         (resolve_symbol): Call it. Remove false error, prohibiting
632         deferred type parameters for dummy arguments.
634         PR fortran/60483
635         * primary.c (gfc_match_varspec): If the type of an associate
636         name is unknown and yet there is a match, try resolving the
637         target expression and using its type.
639 2017-09-15  Paul Thomas  <pault@gcc.gnu.org>
641         PR fortran/82184
642         trans-decl.c (gfc_trans_deferred_vars): Do not null the 'span'
643         field if the symbol is either implicitly or explicitly saved.
645 2017-09-13  Paul Thomas  <pault@gcc.gnu.org>
647         PR fortran/82173
648         * decl.c (match_char_kind): If the kind expression is
649         parameterized, save it in saved_kind_expr and set kind = 0.
650         (gfc_get_pdt_instance): Resolve and simplify before emitting
651         error on expression kind. Insert a missing simplification after
652         insertion of kind expressions.
654 2017-09-12  Paul Thomas  <pault@gcc.gnu.org>
656         PR fortran/82173
657         PR fortran/82168
658         * decl.c (variable_decl): Check pdt template components for
659         appearance of KIND/LEN components in the type parameter name
660         list, that components corresponding to type parameters have
661         either KIND or LEN attributes and that KIND or LEN components
662         are scalar. Copy the initializer to the parameter value.
663         (gfc_get_pdt_instance): Add a label 'error_return' and follow
664         it with repeated code, while replacing this code with a jump.
665         Check if a parameter appears as a component in the template.
666         Make sure that the parameter expressions are integer. Validate
667         KIND expressions.
668         (gfc_match_decl_type_spec): Search for pdt_types in the parent
669         namespace since they are instantiated in the template ns.
670         * expr.c (gfc_extract_int): Use a KIND parameter if it
671         appears as a component expression.
672         (gfc_check_init_expr): Allow expressions with the pdt_kind
673         attribute.
674         *primary.c (gfc_match_actual_arglist): Make sure that the first
675         keyword argument is recognised when 'pdt' is set.
677 2017-09-10  Paul Thomas  <pault@gcc.gnu.org>
679         PR fortran/34640
680         PR fortran/40737
681         PR fortran/55763
682         PR fortran/57019
683         PR fortran/57116
685         * expr.c (is_subref_array): Add class pointer array dummies
686         to the list of expressions that return true.
687         * trans-array.c: Add SPAN_FIELD and update indices for
688         subsequent fields.
689         (gfc_conv_descriptor_span, gfc_conv_descriptor_span_get,
690         gfc_conv_descriptor_span_set, is_pointer_array,
691         get_array_span): New functions.
692         (gfc_get_descriptor_offsets_for_info): New function to preserve
693         API for access to descriptor fields for trans-types.c.
694         (gfc_conv_scalarized_array_ref): If the expression is a subref
695         array, make sure that info->descriptor is a descriptor type.
696         Otherwise, if info->descriptor is a pointer array, set 'decl'
697         and fix it if it is a component reference.
698         (build_array_ref): Simplify handling of class array refs by
699         passing the vptr to gfc_build_array_ref rather than generating
700         the pointer arithmetic in this function.
701         (gfc_conv_array_ref): As in gfc_conv_scalarized_array_ref, set
702         'decl'.
703         (gfc_array_allocate): Set the span field if this is a pointer
704         array. Use the expr3 element size if it is available, so that
705         the dynamic type element size is used.
706         (gfc_conv_expr_descriptor): Set the span field for pointer
707         assignments.
708         * trans-array.h: Prototypes for gfc_conv_descriptor_span_get
709         gfc_conv_descriptor_span_set and
710         gfc_get_descriptor_offsets_for_info added.
711         trans-decl.c (gfc_get_symbol_decl): If a non-class pointer
712         array, mark the declaration as a GFC_DECL_PTR_ARRAY_P. Remove
713         the setting of GFC_DECL_SPAN.
714         (gfc_trans_deferred_vars): Set the span field to zero in thge
715         originating scope.
716         * trans-expr.c (gfc_conv_procedure_call): Do not use copy-in/
717         copy-out to pass subref expressions to a pointer dummy.
718         (gfc_trans_pointer_assignment): Remove code for setting of
719         GFC_DECL_SPAN. Set the 'span' field for non-class pointers to
720         class function results. Likewise for rank remap. In the case
721         that the target is not a whole array, use the target array ref
722         for remap and, since the 'start' indices are missing, set the
723         lbounds to one, as required by the standard.
724         * trans-intrinsic.c (conv_expr_ref_to_caf_ref): Pick up the
725         'token' offset from the field decl in the descriptor.
726         (conv_isocbinding_subroutine): Set the 'span' field.
727         * trans-io.c (gfc_trans_transfer): Always scalarize pointer
728         array io.
729         * trans-stmt.c (trans_associate_var): Set the 'span' field.
730         * trans-types.c (gfc_get_array_descriptor_base): Add the 'span'
731         field to the array descriptor.
732         (gfc_get_derived_type): Pointer array components are marked as
733         GFC_DECL_PTR_ARRAY_P.
734         (gfc_get_array_descr_info): Replaced API breaking code for
735         descriptor offset calling gfc_get_descriptor_offsets_for_info.
736         * trans.c (get_array_span): New function.
737         (gfc_build_array_ref): Simplify by calling get_array_span and
738         obtain 'span' if 'decl' or 'vptr' present.
739         * trans.h : Rename DECL_LANG_FLAG_6, GFC_DECL_SUBREF_ARRAY_P,
740         as GFC_DECL_PTR_ARRAY_P.
742 2017-09-09  Paul Thomas  <pault@gcc.gnu.org>
744         * decl.c : Add decl_type_param_list, type_param_spec_list as
745         static variables to hold PDT spec lists.
746         (build_sym): Copy 'type_param_spec_list' to symbol spec_list.
747         (build_struct): Copy the 'saved_kind_expr' to the component
748         'kind_expr'. Check that KIND or LEN components appear in the
749         decl_type_param_list. These should appear as symbols in the
750         f2k_derived namespace. If the component is itself a PDT type,
751         copy the decl_type_param_list to the component param_list.
752         (gfc_match_kind_spec): If the KIND expression is parameterized
753         set KIND to zero and store the expression in 'saved_kind_expr'.
754         (insert_parameter_exprs): New function.
755         (gfc_insert_kind_parameter_exprs): New function.
756         (gfc_insert_parameter_exprs): New function.
757         (gfc_get_pdt_instance): New function.
758         (gfc_match_decl_type_spec): Match the decl_type_spec_list if it
759         is present. If it is, call 'gfc_get_pdt_instance' to obtain the
760         specific instance of the PDT.
761         (match_attr_spec): Match KIND and LEN attributes. Check for the
762         standard and for type/kind of the parameter. They are also not
763         allowed outside a derived type definition.
764         (gfc_match_data_decl): Null the decl_type_param_list and the
765         type_param_spec_list on entry and free them on exit.
766         (gfc_match_formal_arglist): If 'typeparam' is true, add the
767         formal symbol to the f2k_derived namespace.
768         (gfc_match_derived_decl): Register the decl_type_param_list
769         if this is a PDT. If this is a type extension, gather up all
770         the type parameters and put them in the right order.
771         *dump-parse-tree.c (show_attr): Signal PDT templates and the
772         parameter attributes.
773         (show_components): Output parameter atrributes and component
774         parameter list.
775         (show_symbol): Show variable parameter lists.
776         * expr.c (expr.c): Copy the expression parameter list.
777         (gfc_is_constant_expr): Pass on symbols representing PDT
778         parameters.
779         (gfc_check_init_expr): Break on PDT KIND parameters and
780         PDT parameter expressions.
781         (gfc_check_assign): Assigning to KIND or LEN components is an
782         error.
783         (derived_parameter_expr): New function.
784         (gfc_derived_parameter_expr): New function.
785         (gfc_spec_list_type): New function.
786         * gfortran.h : Add enum gfc_param_spec_type. Add the PDT attrs
787         to the structure symbol_attr. Add the 'kind_expr' and
788         'param_list' field to the gfc_component structure. Comment on
789         the reuse of the gfc_actual_arglist structure as storage for
790         type parameter spec lists. Add the new field 'spec_type' to
791         this structure. Add 'param_list' fields to gfc_symbol and
792         gfc_expr. Add prototypes for gfc_insert_kind_parameter_exprs,
793         gfc_insert_parameter_exprs, gfc_add_kind, gfc_add_len,
794         gfc_derived_parameter_expr and gfc_spec_list_type.
795         * interface.c (gfc_compare_derived_types): Treat PDTs in the
796         same way as sequence types.
797         * match.c : Add variable 'type_param_spec_list'.
798         (gfc_op2string, gfc_match_member_sep, gfc_match_label): Remove
799         trailing whitespace.
800         (match_derived_type_spec): Match PDTs and find specific
801         instance.
802         (gfc_match_type_spec): Remove more trailing whitespace.
803         (gfc_match_allocate): Assumed or deferred parameters cannot
804         appear here. Copy the type parameter spec list to the expr for
805         the allocatable entity. Free 'type_param_spec_list'.
806         (gfc_match_common, gfc_match_namelist, gfc_match_module): Still
807         more trailing whitespace to remove.
808         (gfc_match_type_is): Allow PDT typespecs.
809         * match.h : Modify prototypes for gfc_match_formal_arglist and
810         gfc_match_actual_arglist.
811         * module.c (ab_attribute, mstring attr_bits): PDT attributes
812         added.
813         (mio_symbol_attribute): PDT attributes handled.
814         (mio_component): Deal with 'kind_expr' field.
815         (mio_full_f2k_derived): For PDT templates, transfer the formal
816         namespace symroot to the f2k_derived namespace.
817         *primary.c (match_keyword_arg, gfc_match_actual_arglist): Add
818         modifications to handle PDT spec lists. These are flagged in
819         both cases by new boolean arguments, whose prototype defaults
820         are false.
821         (gfc_match_structure_constructor, match_variable): Remove yet
822         more trailing whitespace.
823         * resolve.c (get_pdt_spec_expr, get_pdt_constructor): New
824         functions.
825         (resolve_structure_cons): If the constructor is a PDT template,
826         call get_pdt_constructor to build it using the parameter lists
827         and then get the specific instance of the PDT.
828         (resolve_component): PDT strings need a hidden string length
829         component like deferred characters.
830         (resolve_symbol): Dummy PDTs cannot have deferred parameters.
831         * symbol.c (gfc_add_kind, gfc_add_len): New functions.
832         (free_components): Free 'kind_expr' and 'param_list' fields.
833         (gfc_free_symbol): Free the 'param_list' field.
834         (gfc_find_sym_tree): If the current state is a PDT template,
835         look for the symtree in the f2k_derived namspaces.
836         trans-array.c (structure_alloc_comps): Allocate and deallocate
837         PDTs. Check dummy arguments for compliance of LEN parameters.
838         Add the new functions to the preceeding enum.
839         (gfc_allocate_pdt_comp, gfc_deallocate_pdt_comp and
840         gfc_check_pdt_dummy): New functions calling above.
841         * trans-array.h : Add prototypes for these functions.
842         trans-decl.c (gfc_get_symbol_decl): Call gfc_defer_symbol_init
843         as appropriate for PDT symbols.
844         (gfc_trans_deferred_vars): Allocate/deallocate PDT entities as
845         they come into and out of scope. Exclude pdt_types from being
846         'gcc_unreachable'.
847         (gfc_trans_subcomponent_assign): PDT array components must be
848         handles as if they are allocatable.
849         * trans-stmt.c (gfc_trans_allocate): Handle initialization of
850         PDT entities.
851         (gfc_trans_deallocate): Likewise.
852         * trans-types.c (gfc_get_derived_type): PDT templates must not
853         arrive here. PDT string components are handles as if deferred.
854         Similarly, PDT arrays are treated as if allocatable. PDT
855         strings are pointer types.
856         * trans.c (gfc_deferred_strlen): Handle PDT strings in the same
857         way as deferred characters.
859 2017-09-01  Jakub Jelinek  <jakub@redhat.com>
861         PR c/81887
862         * parse.c (decode_omp_directive): Use matchs instead of matcho for
863         end ordered and ordered directives, except for ordered depend.  For
864         -fopenmp-simd and ordered depend, reject the stmt.
865         * trans-openmp.c (gfc_trans_omp_ordered): For -fopenmp-simd ignore
866         threads clause and if simd clause isn't present, just translate the
867         body.
869 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
870             Alan Hayward  <alan.hayward@arm.com>
871             David Sherwood  <david.sherwood@arm.com>
873         * trans-types.c (gfc_init_kinds): Use opt_scalar_int_mode for
874         the mode iterator.
876 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
877             Alan Hayward  <alan.hayward@arm.com>
878             David Sherwood  <david.sherwood@arm.com>
880         * target-memory.c (size_integer): Use SCALAR_INT_TYPE_MODE.
881         (size_logical): Likewise.
883 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
884             Alan Hayward  <alan.hayward@arm.com>
885             David Sherwood  <david.sherwood@arm.com>
887         * trans-types.c (gfc_type_for_mode): Use is_a <scalar_int_mode>.
889 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
890             Alan Hayward  <alan.hayward@arm.com>
891             David Sherwood  <david.sherwood@arm.com>
893         * trans-types.c (gfc_init_kinds): Use opt_scalar_float_mode
894         and FOR_EACH_MODE_IN_CLASS.
896 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
897             Alan Hayward  <alan.hayward@arm.com>
898             David Sherwood  <david.sherwood@arm.com>
900         * target-memory.c (size_float): Use SCALAR_FLOAT_TYPE_MODE
901         instead of TYPE_MODE.
903 2017-08-30  Richard Sandiford  <richard.sandiford@linaro.org>
904             Alan Hayward  <alan.hayward@arm.com>
905             David Sherwood  <david.sherwood@arm.com>
907         * trans-types.c (gfc_init_kinds): Use machine_mode instead of int
908         for "mode".
910 2017-08-28  Janus Weil  <janus@gcc.gnu.org>
912         PR fortran/81770
913         * expr.c (gfc_check_pointer_assign): Improve the check whether pointer
914         may outlive pointer target.
916 2017-08-27  Thomas Koenig  <tkoenig@gcc.gnu.org>
918         PR fortran/81974
919         * frontend-passes (inline_matumul_assign):  Explicity
920         set typespec for call to CONJG.
922 2017-08-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
924         PR fortran/81296
925         * trans-io.c (get_dtio_proc): Add check for format label and set
926         formatted flag accordingly. Reorganize the code a little.
928 2017-08-16  Thomas Koenig  <tkoenig@gcc.gnu.org>
930         PR fortran/81116
931         * frontend-passes.c (realloc_string_callback): If expression is a
932         concatenation, also check for dependency.
933         (constant_string_length): Check for presence of symtree.
935 2017-08-13  Thomas Koenig  <tkoenig@gcc.gnu.org>
937         * gfortran.texi: Document format of unformatted sequential files.
939 2017-08-11  Thomas Koenig  <tkoenig@gcc.gnu.org>
941         * invoke.texi:  Actually commit change about -Ofast.
943 2017-08-11  Thomas Koenig  <tkoenig@gcc.gnu.org>
945         PR fortran/60355
946         * resolve.c (resolve_symbol): Adjust (and reformat)
947         comment.  Perform check if a BIND(C) is declared
948         at module level regardless of whether it is typed
949         implicitly or not.
951 2017-08-10  Fritz Reese <fritzoreese@gmail.com>
953         * options.c (set_dec_flags): Only set legacy standards when value
954         is not zero.
956 2017-08-10  Fritz Reese <fritzoreese@gmail.com>
958         * options.c (set_dec_flags, gfc_post_options): Only set flag_d_lines
959         with -fdec when not set by user.
961 2017-08-10  Fritz Reese <fritzoreese@gmail.com>
963         * decl.c (attr_seen): New static variable.
964         * decl.c (variable_decl): Match %FILL in STRUCTURE body.
965         * gfortran.texi: Update documentation.
967 2017-08-08  Martin Liska  <mliska@suse.cz>
969         * trans-types.c: Include header files.
971 2017-08-07  Thomas Koenig  <tkoenig@gcc.gnu.org>
973         PR fortran/68829
974         PR fortran/81701
975         * options.c: Make -Ofast honor -fmax-stack-var-size.
976         * invoke.texi: Document change.
978 2017-08-01  Thomas König  <tkoenig@gcc.gnu.org>
980         PR fortran/79312
981         * intrisic.c (gfc_convert_type_warn):  Only set typespec for
982         empty array constructors which don't have it already.
984 2017-08-01  Thomas Koenig  <tkoenig@gcc.gnu.org>
986         PR fortran/45435
987         * lang.opt (fc-prototypes): Add option.
988         * gfortran.h (gfc_typespec): Add interop_kind to struct.
989         (gfc_dump_c_prototypes): Add prototype.
990         * decl.c (gfc_match_kind_spec): Copy symbol used for kind to typespec.
991         * parse.c (gfc_parse_file): Call gfc_dump_prototypes.
992         * dump-parse-tree.c (gfc_dump_c_prototypes): New function.
993         (type_return): New enum.
994         (get_c_type_name): New function.
995         (write_decl): New function.
996         (write_type): New function.
997         (write_variable): New function.
998         (write_proc): New function.
999         (write_interop_decl): New function.
1000         * invoke.texi: Document -fc-prototypes.
1002 2017-08-01  Dominique d'Humieres  <dominiq@lps.ens.fr>
1004         PR fortran/53542
1005         * expr.c (gfc_check_init_expr): Use the renamed name.
1007 2017-07-31  Jakub Jelinek  <jakub@redhat.com>
1009         * check.c (gfc_check_num_images): Fix a pasto.
1011 2017-07-29  Jakub Jelinek  <jakub@redhat.com>
1013         * trans-decl.c (gfc_trans_use_stmts): Pass false as new argument to
1014         the imported_module_or_decl debug hook.
1016 2017-07-28  Trevor Saunders  <tbsaunde+gcc@tbsaunde.org>
1018         * resolve.c (find_reachable_labels): Adjust.
1020 2017-07-25  Jakub Jelinek  <jakub@redhat.com>
1022         * ioparm.def: Use 1U << 31 instead of 1 << 31 as flags2 mask.
1024 2017-07-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
1026         * dump-parse-tree.c (show_symbol):  Show binding label if present.
1028 2017-07-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
1029             Mikael Morin  <mikael@gcc.gnu.org>
1031         PR fortran/66102
1032         * fortran/trans-array.c (gfc_conv_resolve_dependencies):
1033         Break if dependency has been found.
1035 2017-07-23  Alexander Monakov  <amonakov@ispras.ru>
1037         * interface.c (pair_cmp): Fix gfc_symbol comparison.  Adjust comment.
1039 2017-07-18  Nathan Sidwell  <nathan@acm.org>
1041         * trans.c (gfc_build_array_ref): Use TYPE_MAX_VALUE.
1043 2017-07-09  Dominique d'Humieres  <dominiq@lps.ens.fr>
1045         PR fortran/81341
1046         * class.c (class_array_ref_detected): Remove a redundant
1047         condition.
1049 2017-07-06  Harald Anlauf  <anlauf@gmx.de>
1051         PR fortran/70071
1052         * array.c (gfc_ref_dimen_size): Handle bad subscript triplets.
1054 2017-07-03  Dominique d'Humieres  <dominiq@lps.ens.fr>
1056         PR fortran/79866
1057         * resolve.c (resolve_symbol): Fix typo.
1059 2017-07-03  Dominique d'Humieres  <dominiq@lps.ens.fr>
1061         PR fortran/79843
1062         * symbol.c (check_conflict): Add missing "conflicts".
1064 2017-06-29  Cesar Philippidis  <cesar@codesourcery.com>
1066         PR fortran/77765
1067         * openmp.c (gfc_match_oacc_routine): Check if proc_name exist before
1068         comparing the routine name against it.
1070 2017-06-27  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1072         PR fortran/80164
1073         * trans-stmt.c (gfc_trans_call): If no code expr, use code->loc
1074         as warning/error locus.
1076 2017-06-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1078         PR fortran/81160
1079         * arith.c (wprecision_int_real): Set return value before
1080         mpz_clear and then return after it.
1082 2017-06-15  Janus Weil  <janus@gcc.gnu.org>
1084         PR fortran/80983
1085         * trans-expr.c (gfc_conv_procedure_call): Deallocate the result of
1086         scalar allocatable procedure-pointer components.
1088 2017-06-10  Thomas Koenig  <tkoenig@gcc.gnu.org>
1090         PR fortran/80988
1091         * frontend-passes.c (traverse_io_block):  Also
1092         check for variables occurring as indices multiple
1093         time in a single implied DO loop.
1095 2017-06-05  Janus Weil  <janus@gcc.gnu.org>
1097         PR fortran/70601
1098         * trans-expr.c (gfc_conv_procedure_call): Fix detection of allocatable
1099         function results.
1101 2017-06-05  Nicolas Koenig  <koenigni@student.ethz.ch>
1103         PR fortran/35339
1104         * frontend-passes.c (traverse_io_block): New function.
1105         (simplify_io_impl_do): New function.
1106         (optimize_namespace): Invoke gfc_code_walker with
1107         simplify_io_impl_do.
1109 2017-06-02  Jakub Jelinek  <jakub@redhat.com>
1111         PR fortran/80918
1112         * openmp.c (resolve_omp_clauses): Fix a typo.
1114 2017-05-30  David Malcolm  <dmalcolm@redhat.com>
1116         * error.c (gfc_format_decoder): Update for new bool and
1117         const char ** params.
1119 2017-05-29  Thomas Koenig  <tkoenig@gcc.gnu.org>
1121         PR fortran/37131
1122         * frontend-passes.c (check_conjg_transpose_variable):
1123         Add prototype.
1124         (has_dimen_vector_ref):  Likewise
1125         (matmul_temp_args):  New function. Add prototype.
1126         (optimize_namespace):  Call matmul_temp_args.
1128 2017-05-28  Thomas Koenig  <tkoenig@gcc.gnu.org>
1130         * frontend-passes.c (matmul_lhs_realloc):  Correct
1131         allocation size for case A1B2.
1133 2017-05-25  Thomas Koenig  <tkoenig@gcc.gnu.org>
1135         * dump-parse-tree.c (show_expr):  Also replace
1136         with dumpfile for showing values for forgotten
1137         case.
1139 2017-05-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
1141         * dump-parse-tree.c (show_expr):  Replace stdout
1142         with dumpfile for showing values.
1144 2017-05-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
1146         PR fortran/66094
1147         * frontend-passes.c (matrix_case):  Add A2TB2.
1148         (inline_limit_check):  Handle MATMUL(TRANSPOSE(A),B)
1149         (inline_matmul_assign):  Likewise.
1151 2017-05-23  Thomas Schwinge  <thomas@codesourcery.com>
1153         * openmp.c (OACC_KERNELS_CLAUSES): Add "OMP_CLAUSE_NUM_GANGS",
1154         "OMP_CLAUSE_NUM_WORKERS", "OMP_CLAUSE_VECTOR_LENGTH".
1156 2017-05-22  Janus Weil  <janus@gcc.gnu.org>
1158         PR fortran/80766
1159         * resolve.c (resolve_fl_derived): Make sure that vtype symbols are
1160         properly resolved.
1162 2017-05-19  Paul Thomas  <pault@gcc.gnu.org>
1164         PR fortran/80333
1165         * trans-io.c (nml_get_addr_expr): If we are dealing with class
1166         type data set tmp tree to get that address.
1167         (transfer_namelist_element): Set the array spec to point to the
1168         the class data.
1170 2017-05-19  David Malcolm  <dmalcolm@redhat.com>
1172         PR fortran/79852
1173         * bbt.c (insert): Remove trailing exclamation mark from message.
1174         * decl.c (gfc_match_final_decl): Likewise.
1175         * dump-parse-tree.c (show_expr): Likewise.
1176         * module.c (gfc_use_module): Likewise.
1177         * primary.c (build_actual_constructor): Likewise.
1178         (gfc_convert_to_structure_constructor): Likewise.
1180 2017-05-19  Thomas Schwinge  <thomas@codesourcery.com>
1182         * gfortran.h (enum gfc_omp_default_sharing): Add
1183         "OMP_DEFAULT_PRESENT".
1184         * dump-parse-tree.c (show_omp_clauses): Handle it.
1185         * openmp.c (gfc_match_omp_clauses): Likewise.
1186         * trans-openmp.c (gfc_trans_omp_clauses): Likewise.
1188 2017-05-18  Fritz Reese <fritzoreese@gmail.com>
1190         PR fortran/79968
1191         * decl.c (match_attr_spec, gfc_match_automatic,
1192         gfc_match_static, gfc_match_structure_decl): Unify diagnostic
1193         errors regarding -fdec options.
1194         * io.c (match_dec_etag, match_dec_vtag, match_dec_ftag): Ditto.
1196 2017-05-17  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1198         PR fortran/80741
1199         * trans-io.c (transfer_namelist_element): Change check from
1200         NULL_TREE to null_pointer_node.
1202 2017-05-17  Fritz Reese <fritzoreese@gmail.com>
1204         PR fortran/80668
1205         * expr.c (component_initializer): Don't generate initializers for
1206         pointer components.
1207         * invoke.texi (-finit-derived): Document.
1209 2017-05-16  Paul Thomas  <pault@gcc.gnu.org>
1211         PR fortran/80554
1212         * decl.c (build_sym): In a submodule allow overriding of host
1213         associated symbols from the ancestor module with a new
1214         declaration.
1216 2017-05-15  Steven G. Kargl  <kargl@gcc.gnu.org>
1218         PR fortran/80674
1219         * trans-stmt.c (gfc_trans_integer_select): Remove redundant condition.
1221 2017-05-15  Steven G. Kargl  <kargl@gcc.gnu.org>
1223         PR fortran/80752
1224         * expr.c (gfc_generate_initializer):  If type conversion fails,
1225         check for error and return NULL.
1227 2017-05-14  Nicolas Koenig  <koenigni@student.ethz.ch>
1229         PR fortran/80442
1230         * array.c (gfc_ref_dimen_size): Simplify stride
1231         expression
1232         * data.c (gfc_advance_section): Simplify start,
1233         end and stride expressions
1234         (gfc_advance_section): Simplify start and end
1235         expressions
1236         (gfc_get_section_index): Simplify start expression
1238 2017-05-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1240         * io.c (gfc_resolve_dt): Fix returns to bool type.
1242 2017-05-11  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1244         PR fortran/78659
1245         * io.c (dtio_procs_present): Add new function to check for DTIO
1246         procedures relative to I/O statement READ or WRITE.
1247         (gfc_resolve_dt): Add namelist checks using the new function.
1248         * resolve.c (dtio_procs_present): Remove function and related
1249         namelist checks. (resolve_fl_namelist): Add check specific to
1250         Fortran 95 restriction on namelist objects.
1252 2017-05-11  Nathan Sidwell  <nathan@acm.org>
1254         * trans-decl.c: Include dumpfile.h not tree-dump.h,
1256 2017-05-09  Janus Weil  <janus@gcc.gnu.org>
1258         PR fortran/79311
1259         * resolve.c (gfc_resolve_finalizers): Ensure that derived-type
1260         components have a their finalizers resolved, also if the superordinate
1261         type itself has a finalizer.
1263 2017-05-08  Thomas Koenig  <tkoenig@gcc.gnu.org>
1265         PR fortran/79930
1266         * frontend-passes.c (matmul_to_var_expr): New function,
1267         add prototype.
1268         (matmul_to_var_code):  Likewise.
1269         (optimize_namespace):  Use them from gfc_code_walker.
1271 2017-05-05  David Malcolm  <dmalcolm@redhat.com>
1273         * cpp.c (cb_cpp_error): Replace report_diagnostic
1274         with diagnostic_report_diagnostic.
1275         * error.c (gfc_warning): Likewise.
1276         (gfc_warning_now_at): Likewise.
1277         (gfc_warning_now): Likewise.
1278         (gfc_warning_internal): Likewise.
1279         (gfc_error_now): Likewise.
1280         (gfc_fatal_error): Likewise.
1281         (gfc_error_opt): Likewise.
1282         (gfc_internal_error): Likewise.
1284 2017-05-01  Thomas Koenig  <tkoenig@gcc.gnu.org>
1286         PR fortran/37131
1287         * frontend-passes.c (inline_matmul_assign): Also check bounds
1288         for allocatable lhs and matrix-vector-multiplication.
1290 2017-04-23  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1292         PR fortran/80484
1293         * io.c (format_lex): Check for '/' and set token to FMT_SLASH.
1294         (check_format): Move FMT_DT checking code to data_desc section.
1295         * module.c (gfc_match_use): Include the case of INTERFACE_DTIO.
1297 2017-04-22  Janus Weil  <janus@gcc.gnu.org>
1299         PR fortran/80121
1300         * trans-types.c (gfc_conv_procedure_call): Deallocate the components
1301         of allocatable intent(out) arguments.
1303 2017-04-21  Janus Weil  <janus@gcc.gnu.org>
1305         PR fortran/80392
1306         * trans-types.c (gfc_get_derived_type): Prevent an infinite loop when
1307         building a derived type that includes a procedure pointer component
1308         with a polymorphic result.
1310 2017-04-17  Paul Thomas  <pault@gcc.gnu.org>
1312         PR fortran/80440
1313         * module.c (find_symtree_for_symbol): Delete.
1314         (read_module): Remove the call to the above.
1316 2017-04-14  Janus Weil  <janus@gcc.gnu.org>
1318         PR fortran/80361
1319         * class.c (generate_finalization_wrapper): Give the finalization wrapper
1320         the recursive attribute.
1322 2017-04-10  Nicolas Koenig  <koenigni@student.ethz.ch>
1323             Paul Thomas  <pault@gcc.gnu.org>
1325         PR fortran/69498
1326         * module.c (gfc_match_submodule): Add error
1327         if function is called in the wrong state.
1329 2017-04-10  Janus Weil  <janus@gcc.gnu.org>
1331         PR fortran/80046
1332         * expr.c (gfc_check_pointer_assign): Check if procedure pointer
1333         components in a pointer assignment need an explicit interface.
1335 2017-03-18  Nicolas Koenig  <koenigni@student.ethz.ch>
1337         PR fortran/69498
1338         * symbol.c (gfc_delete_symtree): If there is a period in the name, ignore
1339         everything before it.
1341 2017-03-28  Janus Weil  <janus@gcc.gnu.org>
1343         PR fortran/78661
1344         * trans-io.c (transfer_namelist_element): Perform a polymorphic call
1345         to a DTIO procedure if necessary.
1347 2017-03-25  Paul Thomas  <pault@gcc.gnu.org>
1349         PR fortran/80156
1350         PR fortran/79382
1351         * decl.c (access_attr_decl): Remove the error for an absent
1352         generic DTIO interface and ensure that symbol has the flavor
1353         FL_PROCEDURE.
1355 2017-03-22  Dominique d'Humieres  <dominiq@lps.ens.fr>
1357         PR fortran/79838
1358         * module.c: Remove trailing period.
1360 2017-03-22  Dominique d'Humieres  <dominiq@lps.ens.fr>
1362         PR fortran/79602
1363         * decl.c: Replace '%s' with %qs.
1364         * expr.c: Likewise.
1365         * interface.c: Likewise.
1366         * match.c: Likewise.
1367         * primary.c: Likewise.
1368         * resolve.c: Likewise.
1370         PR fortran/79844
1371         PR fortran/80011
1372         * io.c: Remove trailing spaces.
1373         * match.c: Likewise.
1374         * openmp.c: Likewise.
1375         * resolve.c: Likewise.
1376         * trans-intrinsic.c: Likewise.
1378         PR fortran/79853
1379         * expr.c: Remove a double spaces.
1381         PR fortran/79859
1382         * primary.c: Remove spurious quotes around %qs.
1384 2017-03-22  Thomas Koenig  <tkoenig@gcc.gnu.org>
1386         PR fortran/80142
1387         * frontend-passes.c (combine_array_constructor): Take
1388         location of new expression from constructor expression instead
1389         of constructor.
1391 2017-03-20  Nicolas Koenig  <koenigni@student.ethz.ch>
1393         PR fortran/39239
1394         * symbol.c (check_conflict): Report an error if an EQUIVALENCE
1395         object is BIND(C)
1397 2017-03-18  Nicolas Koenig  <koenigni@student.ethz.ch>
1399         PR fortran/69498
1400         * decl.c (add_hidden_procptr_result): Fixed Refs count of the
1401         created "ppr@" symbol.
1403 2017-03-18  Paul Thomas  <pault@gcc.gnu.org>
1405         PR fortran/79676
1406         * module.c (mio_symbol_attribute): Remove reset of the flag
1407         'no_module_procedures'.
1408         (check_for_module_procedures): New function. Move declaration
1409         of 'no_module_procedures' to above it.
1410         (gfc_dump_module): Traverse namespace calling new function.
1412 2017-03-18  Paul Thomas  <pault@gcc.gnu.org>
1414         PR fortran/71838
1415         * symbol.c (check_conflict): A dummy procedure in a submodule,
1416         module procedure is not an error.
1417         (gfc_add_flavor): Ditto.
1419 2017-03-17  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1421         PR fortran/79841
1422         * openmp.c (check_symbol_not_pointer): Adjust diagnostics.
1424 2017-03-16  Jakub Jelinek  <jakub@redhat.com>
1426         PR fortran/80010
1427         * parse.c (gfc_ascii_statement): Use !$ACC for ST_OACC_ATOMIC
1428         and ST_OACC_END_ATOMIC, instead of !ACC.
1429         * trans-decl.c (finish_oacc_declare): Use !$ACC instead of $!ACC.
1430         * openmp.c (gfc_match_oacc_declare, gfc_match_oacc_wait,
1431         gfc_resolve_oacc_declare): Likewise.
1433         PR fortran/79886
1434         * error.c (gfc_format_decoder): Rename plus argument to set_locus,
1435         remove ATTRIBUTE_UNUSED from all arguments, call default_tree_printer
1436         if not a Fortran specific spec.
1437         * trans-io.c: Include options.h.
1438         (gfc_build_st_parameter): Temporarily disable -Wpadded around layout
1439         of artificial IO data structures.
1441 2017-03-15  David Malcolm  <dmalcolm@redhat.com>
1443         PR fortran/79860
1444         * resolve.c (resolve_contained_fntype): Make error messages more
1445         amenable to translation.
1447 2017-03-06  Richard Biener  <rguenther@suse.de>
1449         PR fortran/79894
1450         * trans.c (gfc_add_modify_loc): Weaken assert.
1452 2017-03-05  Andre Vehreschild  <vehre@gcc.gnu.org>,
1453             Alessandro Fanfarillo  <fanfarillo.gcc@gmail.com>
1455         * check.c (positive_check): Add new function checking constant for
1456         being greater then zero.
1457         (gfc_check_image_status): Add checking of image_status arguments.
1458         (gfc_check_failed_or_stopped_images): Same but for failed_- and
1459         stopped_images function.
1460         * dump-parse-tree.c (show_code_node): Added output of FAIL IMAGE.
1461         * gfortran.h (enum gfc_statement): Added FAIL_IMAGE_ST.
1462         (enum gfc_isym_id): Added new intrinsic symbols.
1463         (enum gfc_exec_op): Added EXEC_FAIL_IMAGE.
1464         * gfortran.texi: Added description for the new API functions. Updated
1465         coverage of gfortran of TS18508.
1466         * intrinsic.c (add_functions): Added symbols to resolve new intrinsic
1467         functions.
1468         * intrinsic.h: Added prototypes.
1469         * iresolve.c (gfc_resolve_failed_images): Resolve the failed_images
1470         intrinsic.
1471         (gfc_resolve_image_status): Same for image_status.
1472         (gfc_resolve_stopped_images): Same for stopped_images.
1473         * libgfortran.h: Added prototypes.
1474         * match.c (gfc_match_if): Added matching of FAIL IMAGE statement.
1475         (gfc_match_fail_image): Match a FAIL IMAGE statement.
1476         * match.h: Added prototype.
1477         * parse.c (decode_statement): Added matching for FAIL IMAGE.
1478         (next_statement): Same.
1479         (gfc_ascii_statement): Same.
1480         * resolve.c: Same.
1481         * simplify.c (gfc_simplify_failed_or_stopped_images): For COARRAY=
1482         single a constant result can be returne.d
1483         (gfc_simplify_image_status): For COARRAY=single the result is constant.
1484         * st.c (gfc_free_statement): Added FAIL_IMAGE handling.
1485         * trans-decl.c (gfc_build_builtin_function_decls): Added decls of the
1486         new intrinsics.
1487         * trans-expr.c (gfc_conv_procedure_call): This is first time all
1488         arguments of a function are optional, which is now handled here
1489         correctly.
1490         * trans-intrinsic.c (conv_intrinsic_image_status): Translate
1491         image_status.
1492         (gfc_conv_intrinsic_function): Add support for image_status.
1493         (gfc_is_intrinsic_libcall): Add support for the remaining new
1494         intrinsics.
1495         * trans-stmt.c (gfc_trans_fail_image): Trans a fail image.
1496         * trans-stmt.h: Add the prototype for the above.
1497         * trans.c (trans_code): Dispatch for fail_image.
1498         * trans.h: Add the trees for the new intrinsics.
1500 2017-03-03  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1502         PR fortran/79841
1503         * openmp.c (check_symbol_not_pointer): Adjust diagnostic.
1505 2017-02-28  Paul Thomas  <pault@gcc.gnu.org>
1507         PR fortran/79739
1508         * resolve.c (resolve_fl_procedure): Deal with the case where
1509         'submodule_name' is NULL so that gfc_error does not ICE.
1510         Reformat the error message to make it more consistent.
1512 2017-02-28  Jakub Jelinek  <jakub@redhat.com>
1514         * parse.c (parse_critical_block): Use cond ? G_("...") : G_("...")
1515         instead of just cond ? "..." : "...".
1516         * scanner.c (gfc_next_char_literal): Likewise.
1517         * match.c (match_exit_cycle): Likewise.
1519 2017-02-26  Thomas Koenig  <tkoenig@gcc.gnu.org>
1521         PR fortran/51119
1522         * options.c (gfc_post_options): Set default limit for matmul
1523         inlining to 30.
1524         * invoke.texi: Document change.
1526 2017-02-25  Dominique d'Humieres  <dominiq@lps.ens.fr>
1528         PR fortran/79601
1529         * interface.c (check_dtio_arg_TKR_intent): Change 'intent'
1530         to 'INTENT'.
1532 2017-02-25  Dominique d'Humieres  <dominiq@lps.ens.fr>
1534         PR fortran/79597
1535         * interface.c (gfc_match_end_interface): Remove spurious comma
1536         and space, replace 'got %s' with 'got %qs'.
1538 2017-02-20  Paul Thomas  <pault@gcc.gnu.org>
1540         PR fortran/79599
1541         * interface.c (check_dtio_arg_TKR_intent): Supply 'must'
1542         missing from error message.
1544 2017-02-20  Paul Thomas  <pault@gcc.gnu.org>
1546         PR fortran/79523
1547         * interface.c (gfc_find_typebound_dtio_proc): Guard test for
1548         flavor attribute by checking that symbol is resolved.
1550 2017-02-16  Paul Thomas  <pault@gcc.gnu.org>
1552         PR fortran/79382
1553         * decl.c (access_attr_decl): Test for presence of generic DTIO
1554         interface and emit error if not present.
1556 2017-02-20  Paul Thomas  <pault@gcc.gnu.org>
1558         PR fortran/79434
1559         * parse.c (check_component, parse_union): Whitespace.
1560         (set_syms_host_assoc): For a derived type, check if the module
1561         in which it was declared is one of the submodule ancestors. If
1562         it is, make the components public. Otherwise, reset attribute
1563         'host_assoc' and set 'use-assoc' so that encapsulation is
1564         preserved.
1566 2017-02-19  Paul Thomas  <pault@gcc.gnu.org>
1568         PR fortran/79447
1569         * decl.c (gfc_set_constant_character_len): Whitespace.
1570         (gfc_match_end): Catch case where a procedure is contained in
1571         a module procedure and ensure that 'end procedure' is the
1572         correct termination.
1574 2017-02-19  Paul Thomas  <pault@gcc.gnu.org>
1576         PR fortran/79402
1577         * resolve.c (fixup_unique_dummy): New function.
1578         (gfc_resolve_expr): Call it for dummy variables with a unique
1579         symtree name.
1581 2017-02-19  Andre Vehreschild  <vehre@gcc.gnu.org>
1583         PR fortran/79229
1584         * trans-expr.c (gfc_trans_assignment_1): Deref indirect refs when
1585         compiling with -fcheck=mem to check the pointer and not the data.
1587 2017-02-19  Andre Vehreschild  <vehre@gcc.gnu.org>
1589         PR fortran/79335
1590         * trans-array.c (duplicate_allocatable_coarray): Ensure attributes
1591         passed are properly initialized.
1592         (structure_alloc_comps): Same.
1593         * trans-expr.c (gfc_trans_structure_assign): Same.
1595 2017-02-13  Jakub Jelinek  <jakub@redhat.com>
1597         * trans-expr.c (gfc_conv_substring): Add missing space in diagnostics.
1599 2017-02-12  Thomas Koenig  <tkoenig@gcc.gnu.org>
1601         PR fortran/65542
1602         * intrinsic.c (gfc_intrinsic_func_interface):  Return an error
1603         for -std=f95 for disallowed transformational functions in
1604         initialization expressions.
1606 2017-02-09  Cesar Philippidis  <cesar@codesourcery.com>
1607             Joseph Myers  <joseph@codesourcery.com>
1609         * openmp.c (resolve_omp_clauses): Error on directives
1610         containing both tile and collapse clauses.
1611         (resolve_oacc_loop_blocks): Represent '*' tile arguments as zero.
1612         * trans-openmp.c (gfc_trans_omp_do): Lower tiled loops like
1613         collapsed loops.
1615 2017-02-07  Steven G. Kargl  <kargl@gcc.gnu.org>
1617         * trans-types.c (gfc_get_int_kind_from_width_isofortranen):  Choose
1618         REAL type with the widest precision if two (or more) have the same
1619         storage size.
1621 2017-02-05  Andre Vehreschild  <vehre@gcc.gnu.org>
1623         PR fortran/79344
1624         * trans-stmt.c (gfc_trans_allocate): Only deallocate the components of
1625         the temporary, when a new object was created for the temporary.  Not
1626         when it is just an alias to an existing object.
1628 2017-02-05  Andre Vehreschild  <vehre@gcc.gnu.org>
1630         PR fortran/79335
1631         * trans-decl.c (generate_coarray_sym_init): Retrieve the symbol's
1632         attributes before using them.
1634 2017-02-05  Andre Vehreschild  <vehre@gcc.gnu.org>
1636         PR fortran/78958
1637         * trans-stmt.c (gfc_trans_allocate): Add the multiplying the _len
1638         component of unlimited polymorphic objects when source-allocating.
1640 2017-02-05  Andre Vehreschild  <vehre@gcc.gnu.org>
1642         PR fortran/79230
1643         * trans-array.c (structure_alloc_comps): Ignore pointer components when
1644         freeing structures.
1646 2017-01-25  Maxim Ostapenko  <m.ostapenko@samsung.com>
1648         PR lto/79061
1649         * f95-lang.c (gfc_create_decls): Include stringpool.h.
1650         Pass main_input_filename to build_translation_unit_decl.
1652 2017-01-23  Thomas Koenig  <tkoenig@netcologne.de>
1654         * arith.c (arith_power):  If simplifying integer power expression
1655         to zero, warn if -Winteger-division is given.
1657 2017-01-22  Jakub Jelinek  <jakub@redhat.com>
1659         PR fortran/79154
1660         * parse.c (matchs, matcho, matchds, matchdo): Replace return st;
1661         with { ret = st; goto finish; }.
1662         (decode_omp_directive): Allow declare simd, declare target and
1663         simd directives in PURE/ELEMENTAL procedures.  Only call
1664         gfc_unset_implicit_pure on successful match of other procedures.
1666 2017-01-21  Gerald Pfeifer  <gerald@pfeifer.com>
1668         * gfc-internals.texi (Symbol Versioning): Change references
1669         to www.akkadia.org to https.
1671 2017-01-21  Jakub Jelinek  <jakub@redhat.com>
1673         * gfortran.h (gfc_extract_int): Change return type to bool.  Add
1674         int argument with = 0.
1675         * decl.c (gfc_match_kind_spec): Adjust gfc_extract_int caller, pass
1676         1 as new last argument to it, don't emit gfc_error.
1677         (match_char_kind): Likewise.
1678         (gfc_match_decl_type_spec): Use gfc_get_string ("%s", x) instead of
1679         gfc_get_string (x).
1680         (gfc_match_derived_decl, match_binding_attributes): Likewise.
1681         (gfc_match_structure_decl): Don't sprintf back to name, call
1682         get_struct_decl directly with gfc_dt_upper_string (name) result.
1683         * trans-stmt.c (gfc_trans_allocate): Use gfc_get_string ("%s", x)
1684         instead of gfc_get_string (x).
1685         * module.c (gfc_dt_lower_string, gfc_dt_upper_string,
1686         gfc_match_use, gfc_match_submodule, find_true_name, mio_pool_string,
1687         mio_symtree_ref, mio_expr, mio_omp_udr_expr, load_generic_interfaces,
1688         load_omp_udrs, load_needed, read_module, dump_module,
1689         create_intrinsic_function, import_iso_c_binding_module,
1690         create_int_parameter, create_int_parameter_array, create_derived_type,
1691         use_iso_fortran_env_module): Likewise.
1692         * error.c (gfc_diagnostic_starter, gfc_diagnostic_start_span): Use
1693         pp_verbatim (context->printer, "%s", x) instead of
1694         pp_verbatim (context->printer, x).
1695         * match.c (gfc_match_small_int): Adjust gfc_extract_int caller, pass
1696         1 as new last argument to it, don't emit gfc_error.
1697         (gfc_match_small_int_expr): Likewise.
1698         * iresolve.c (gfc_get_string): Optimize format "%s" case.
1699         (resolve_bound): Use gfc_get_string ("%s", x) instead of
1700         gfc_get_string (x).
1701         (resolve_transformational): Formatting fix.
1702         (gfc_resolve_char_achar): Change name argument to bool is_achar,
1703         use a single format string and if is_achar add "a" before "char".
1704         (gfc_resolve_achar, gfc_resolve_char): Adjust callers.
1705         * expr.c (gfc_extract_int): Change return type to bool, return true
1706         if some error occurred.  Add REPORT_ERROR argument, if non-zero
1707         call either gfc_error or gfc_error_now depending on its sign.
1708         * arith.c (arith_power): Adjust gfc_extract_int caller.
1709         * symbol.c (gfc_add_component): Use gfc_get_string ("%s", x) instead
1710         of gfc_get_string (x).
1711         (gfc_new_symtree, gfc_delete_symtree, gfc_get_uop, gfc_new_symbol,
1712         gfc_get_gsymbol, generate_isocbinding_symbol): Likewise.
1713         * openmp.c (gfc_match_omp_clauses): Adjust gfc_extract_int caller, pass
1714         -1 as new last argument to it, don't emit gfc_error_now.
1715         (gfc_match_omp_declare_reduction): Use gfc_get_string ("%s", x)
1716         instead of gfc_get_string (x).
1717         * check.c (kind_check): Adjust gfc_extract_int caller.
1718         * intrinsic.c (add_sym, find_sym, make_alias): Use
1719         gfc_get_string ("%s", x) instead of gfc_get_string (x).
1720         * simplify.c (get_kind, gfc_simplify_btest, gfc_simplify_maskr,
1721         gfc_simplify_maskl, gfc_simplify_poppar, gfc_simplify_repeat,
1722         gfc_simplify_selected_int_kind, gfc_simplify_selected_real_kind):
1723         Adjust gfc_extract_int callers.
1724         * trans-decl.c (gfc_find_module): Use gfc_get_string ("%s", x)
1725         instead of gfc_get_string (x).
1726         * matchexp.c (expression_syntax): Add const.
1727         * primary.c (match_kind_param, match_hollerith_constant,
1728         match_string_constant): Adjust gfc_extract_int callers.
1729         (match_keyword_arg): Use gfc_get_string ("%s", x) instead of
1730         gfc_get_string (x).
1731         * frontend-passes.c (optimize_minmaxloc): Likewise.
1733 2017-01-19  Andre Vehreschild  <vehre@gcc.gnu.org>
1735         PR fortran/70696
1736         * trans-decl.c (gfc_build_qualified_array): Add static decl to parent
1737         function only, when the decl-context is not the translation unit.
1739 2017-01-18  Louis Krupp  <louis.krupp@zoho.com>
1741         PR fortran/50069
1742         PR fortran/55086
1743         * trans-expr.c (gfc_conv_variable): Don't treat temporary variables
1744         as function arguments.
1745         * trans-stmt.c (forall_make_variable_temp,
1746         generate_loop_for_temp_to_lhs, gfc_trans_assign_need_temp,
1747         gfc_trans_forall_1): Don't adjust offset of forall temporary
1748         for array sections, make forall temporaries work for substring
1749         expressions, improve test coverage by adding -ftest-forall-temp
1750         option to request usage of temporary array in forall code.
1751         * lang.opt: Add -ftest-forall-temp option.
1752         * invoke.texi: Add -ftest-forall-temp option.
1754 2017-01-18  Andre Vehreschild  <vehre@gcc.gnu.org>
1756         * primary.c (caf_variable_attr): Improve figuring whether the current
1757         component is the last one refed.
1758         * trans-stmt.c (gfc_trans_allocate): Do not generate sync_all calls
1759         when allocating pointer or allocatable components.
1761 2017-01-18  Andre Vehreschild  <vehre@gcc.gnu.org>
1763         * gfortran.texi: Add missing parameters to caf-API functions.  Correct
1764         typos and clarify some descriptions.
1766 2017-01-18  Andre Vehreschild  <vehre@gcc.gnu.org>
1768         PR fortran/70696
1769         Missed some cases, here they are:
1770         * trans-decl.c (gfc_build_qualified_array): Add static tokens to the
1771         parent function's scope.
1772         * trans-expr.c (gfc_get_tree_for_caf_expr): Shorten code.  Remove
1773         unnecessary assert.
1775 2017-01-13  Andre Vehreschild  <vehre@gcc.gnu.org>
1777         PR fortran/70697
1778         * resolve.c (resolve_lock_unlock_event): Resolve the expression for
1779         event's until_count.
1781 2017-01-13  Andre Vehreschild  <vehre@gcc.gnu.org>
1783         PR fortran/70696
1784         * trans-expr.c (gfc_get_tree_for_caf_expr): Ensure the backend_decl
1785         is valid before accessing it.
1787 2017-01-09  Jakub Jelinek  <jakub@redhat.com>
1789         PR translation/79019
1790         PR translation/79020
1791         * decl.c (attr_decl1): Fix spelling in translatable string.
1792         * intrinsic.texi: Fix spelling - invokation -> invocation.
1793         * lang.opt (faggressive-function-elimination, gfc_convert): Fix
1794         typos in descriptions.
1795         * openmp.c (resolve_omp_clauses): Add missing whitespace to
1796         translatable strings.
1798 2017-01-08  Martin Sebor  <msebor@redhat.com>
1800         PR tree-optimization/78913
1801         PR middle-end/77708
1802         * trans-common.c (build_equiv_decl): Increase buffer size to avoid
1803         truncation for any argument.
1804         * trans-types.c (gfc_build_logical_type): Same.
1806 2017-01-07  Andre Vehreschild  <vehre@gcc.gnu.org>
1808         PR fortran/78781
1809         PR fortran/78935
1810         * expr.c (gfc_check_pointer_assign): Return the same error message for
1811         rewritten coarray pointer assignments like for plain ones.
1812         * gfortran.h: Change prototype.
1813         * primary.c (caf_variable_attr): Set attributes used ones only only
1814         ones.  Add setting of pointer_comp attribute.
1815         (gfc_caf_attr): Add setting of pointer_comp attribute.
1816         * trans-array.c (gfc_array_allocate): Add flag that the component to
1817         allocate is not an ultimate coarray component.  Add allocation of
1818         pointer arrays.
1819         (structure_alloc_comps): Extend nullify to treat pointer components in
1820         coarrays correctly.  Restructure nullify to remove redundant code.
1821         (gfc_nullify_alloc_comp): Allow setting caf_mode flags.
1822         * trans-array.h: Change prototype of gfc_nullify_alloc_comp ().
1823         * trans-decl.c (generate_coarray_sym_init): Call nullify_alloc_comp for
1824         derived type coarrays with pointer components.
1825         * trans-expr.c (gfc_trans_structure_assign): Also treat pointer
1826         components.
1827         (trans_caf_token_assign): Handle assignment of token of scalar pointer
1828         components.
1829         (gfc_trans_pointer_assignment): Call above routine.
1830         * trans-intrinsic.c (conv_expr_ref_to_caf_ref): Add treating pointer
1831         components.
1832         (gfc_conv_intrinsic_caf_get): Likewise.
1833         (conv_caf_send): Likewise.
1834         * trans-stmt.c (gfc_trans_allocate): After allocating a derived type in
1835         a coarray pre-register the tokens.
1836         (gfc_trans_deallocate): Simply determining the coarray type (scalar or
1837         array) and deregistering it correctly.
1838         * trans-types.c (gfc_typenode_for_spec): Replace in_coarray flag by the
1839         actual codim to allow lookup of array types in the cache.
1840         (gfc_build_array_type): Likewise.
1841         (gfc_get_array_descriptor_base): Likewise.
1842         (gfc_get_array_type_bounds): Likewise.
1843         (gfc_get_derived_type): Likewise.
1844         * trans-types.h: Likewise.
1845         * trans.c (gfc_deallocate_with_status): Enable deregistering of all kind
1846         of coarray components.
1847         (gfc_deallocate_scalar_with_status): Use free() in fcoarray_single mode
1848         instead of caf_deregister.
1850 2017-01-06  Jakub Jelinek  <jakub@redhat.com>
1852         * simplify.c (simplify_transformation_to_array): Use
1853         GCC_DIAGNOSTIC_PUSH_IGNORED and GCC_DIAGNOSTIC_POP instead of
1854         #pragma GCC diagnostic {push,ignored,pop}.
1856 2017-01-06  Alexandre Oliva <aoliva@redhat.com>
1858         * simplify.c (simplify_transformation_to_array): Silence
1859         array bounds warning.  Fix whitespace.
1861 2017-01-04  Alexandre Oliva <aoliva@redhat.com>
1863         * module.c (load_omp_udrs): Initialize name.
1865 2017-01-02  Janne Blomqvist  <jb@gcc.gnu.org>
1867         PR fortran/78534
1868         * trans-expr.c (gfc_trans_string_copy): Rework string copy
1869         algorithm to avoid -Wstringop-overflow warning.
1871 2017-01-01  Jakub Jelinek  <jakub@redhat.com>
1873         Update copyright years.
1875         * gfortranspec.c (lang_specific_driver): Update copyright notice
1876         dates.
1877         * gfc-internals.texi: Bump @copying's copyright year.
1878         * gfortran.texi: Ditto.
1879         * intrinsic.texi: Ditto.
1880         * invoke.texi: Ditto.
1882 Copyright (C) 2017 Free Software Foundation, Inc.
1884 Copying and distribution of this file, with or without modification,
1885 are permitted in any medium without royalty provided the copyright
1886 notice and this notice are preserved.