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