re PR fortran/56845 ([OOP] _vptr not set to declared type for CLASS + SAVE)
[platform/upstream/gcc.git] / gcc / fortran / ChangeLog
1 2013-04-12  Tobias Burnus  <burnus@net-b.de>
2
3         PR fortran/56845
4         * trans-decl.c (gfc_trans_deferred_vars): Set _vptr for
5         allocatable static BT_CLASS.
6         * trans-expr.c (gfc_class_set_static_fields): New function.
7         * trans.h (gfc_class_set_static_fields): New prototype.
8
9 2013-04-11  Janne Blomqvist  <jb@gcc.gnu.org>
10
11         * gfortran.h: Remove enum gfc_try, replace gfc_try with bool type.
12         * arith.c: Replace gfc_try with bool type.
13         * array.c: Likewise.
14         * check.c: Likewise.
15         * class.c: Likewise.
16         * cpp.c: Likewise.
17         * cpp.h: Likewise.
18         * data.c: Likewise.
19         * data.h: Likewise.
20         * decl.c: Likewise.
21         * error.c: Likewise.
22         * expr.c: Likewise.
23         * f95-lang.c: Likewise.
24         * interface.c: Likewise.
25         * intrinsic.c: Likewise.
26         * intrinsic.h: Likewise.
27         * io.c: Likewise.
28         * match.c: Likewise.
29         * match.h: Likewise.
30         * module.c: Likewise.
31         * openmp.c: Likewise.
32         * parse.c: Likewise.
33         * parse.h: Likewise.
34         * primary.c: Likewise.
35         * resolve.c: Likewise.
36         * scanner.c: Likewise.
37         * simplify.c: Likewise.
38         * symbol.c: Likewise.
39         * trans-intrinsic.c: Likewise.
40         * trans-openmp.c: Likewise.
41         * trans-stmt.c: Likewise.
42         * trans-types.c: Likewise.
43
44 2013-04-09  Tobias Burnus  <burnus@net-b.de>
45
46         * gfortran.texi (KIND Type Parameters,
47         Internal representation of LOGICAL variables): Add crossrefs.
48         (Intrinsic Types): Mention issues with _Bool interop.
49         (Naming and argument-passing conventions): New section.
50
51 2013-04-08  Thomas Koenig  <tkoenig@gcc.gnu.org>
52
53         PR fortran/56782
54         * frontend-passes.c (callback_reduction):  Dont't do
55         any simplification if there is only a single element
56         which has an iterator.
57
58 2013-04-07  Tobias Burnus  <burnus@net-b.de>
59
60         PR fortran/56849
61         * iresolve.c (gfc_resolve_reshape): Set shape also
62         with order=.
63
64 2013-04-04  Janus Weil  <janus@gcc.gnu.org>
65
66         PR fortran/40881
67         * match.c (gfc_match_return): Remove standard notification.
68         * primary.c (gfc_match_actual_arglist): Add standard notification.
69
70 2013-04-04  Tobias Burnus  <burnus@net-b.de>
71
72         PR fortran/50269
73         * gcc/fortran/check.c (is_c_interoperable,
74         gfc_check_c_loc): Correct c_loc array checking
75         for Fortran 2003 and Fortran 2008.
76
77 2013-04-03  Janus Weil  <janus@gcc.gnu.org>
78
79         PR fortran/56284
80         PR fortran/40881
81         * decl.c (gfc_match_formal_arglist): Warn about alternate-return
82         arguments.
83         * interface.c (check_dummy_characteristics): Return if symbols are NULL.
84
85 2013-04-01  Janus Weil  <janus@gcc.gnu.org>
86
87         PR fortran/56500
88         * symbol.c (gfc_set_default_type): Build class container for
89         IMPLICIT CLASS.
90
91 2013-03-31  Tobias Burnus  <burnus@net-b.de>
92
93         * class.c (finalization_scalarizer, finalizer_insert_packed_call,
94         generate_finalization_wrapper): Avoid segfault with absent SIZE=
95         argment to TRANSFER and use correct result kind for SIZE.
96         * intrinsic.c (gfc_isym_id_by_intmod): Also handle ids of
97         nonmodules.
98         * trans.c (gfc_build_final_call): Handle coarrays.
99
100 2013-03-30  Thomas Koenig  <tkoenig@gcc.gnu.org>
101
102         * trans-expr.c (build_memcmp_call):  New function.
103         (gfc_build_compare_string):  If the strings
104         compared have constant and equal lengths and
105         the strings are kind=1, or, for kind=4 strings,
106         the test is for (in)equality, use memcmp().
107
108 2013-03-29  Tobias Burnus  <burnus@net-b.de>
109
110         PR fortran/35203
111         * trans-decl.c (create_function_arglist): Pass hidden argument
112         for passed-by-value optional+value dummies.
113         * trans-expr.c (gfc_conv_expr_present,
114         gfc_conv_procedure_call): Handle those.
115
116 2013-03-28  Thomas Koenig  <tkoenig@gcc.gnu.org>
117
118         PR fortran/45159
119         * gfortran.h (gfc_dep_difference):  Add prototype.
120         * dependency.c (discard_nops):  New function.
121         (gfc_dep_difference):  New function.
122         (check_section_vs_section):  Use gfc_dep_difference
123         to calculate the difference of starting indices.
124         * trans-expr.c (gfc_conv_substring):  Use
125         gfc_dep_difference to calculate the length of
126         substrings where possible.
127
128 2013-03-28  Thomas Koenig  <tkoenig@gcc.gnu.org>
129
130         PR fortran/55806
131         * frontend-passes.c (optimize_code):  Keep track of
132         current code to make code insertion possible.
133         (combine_array_constructor):  New function.
134         (optimize_op):  Call it.
135
136 2013-03-27  Tobias Burnus  <burnus@net-b.de>
137
138         PR fortran/56650
139         PR fortran/36437
140         * check.c (gfc_check_sizeof, gfc_check_c_sizeof,
141         gfc_check_storage_size): Update checks.
142         * intrinsic.texi (SIZEOF): Correct class.
143         * intrinsic.h (gfc_simplify_sizeof,
144         gfc_simplify_storage_size): New prototypes.
145         * intrinsic.c (add_functions): Use them.
146         * simplify.c (gfc_simplify_sizeof,
147         gfc_simplify_storage_size): New functions.
148
149 2013-03-27  Janne Blomqvist  <jb@gcc.gnu.org>
150
151         PR fortran/25708
152         * module.c (module_locus): Use long for position.
153         (module_content): New variable.
154         (module_pos): Likewise.
155         (prev_character): Remove.
156         (bad_module): Free data instead of closing mod file.
157         (set_module_locus): Use module_pos.
158         (get_module_locus): Likewise.
159         (module_char): use buffer rather than stdio file.
160         (module_unget_char): Likewise.
161         (read_module_to_tmpbuf): New function.
162         (gfc_use_module): Call read_module_to_tmpbuf.
163
164 2013-03-26  Tobias Burnus  <burnus@net-b.de>
165
166         PR fortran/56649
167         * simplify.c (gfc_simplify_merge): Simplify more.
168
169 2013-03-25  Tobias Burnus  <burnus@net-b.de>
170
171         PR fortran/38536
172         PR fortran/38813
173         PR fortran/38894
174         PR fortran/39288
175         PR fortran/40963
176         PR fortran/45824
177         PR fortran/47023
178         PR fortran/47034
179         PR fortran/49023
180         PR fortran/50269
181         PR fortran/50612
182         PR fortran/52426
183         PR fortran/54263
184         PR fortran/55343
185         PR fortran/55444
186         PR fortran/55574
187         PR fortran/56079
188         PR fortran/56378
189         * check.c (gfc_var_strlen): Properly handle 0-sized string.
190         (gfc_check_c_sizeof): Use is_c_interoperable, add checks.
191         (is_c_interoperable, gfc_check_c_associated, gfc_check_c_f_pointer,
192         gfc_check_c_f_procpointer, gfc_check_c_funloc, gfc_check_c_loc): New
193         functions.
194         * expr.c (check_inquiry): Add c_sizeof, compiler_version and
195         compiler_options.
196         (gfc_check_pointer_assign): Refine function result check.
197         gfortran.h (gfc_isym_id): Add GFC_ISYM_C_ASSOCIATED,
198         GFC_ISYM_C_F_POINTER, GFC_ISYM_C_F_PROCPOINTER, GFC_ISYM_C_FUNLOC,
199         GFC_ISYM_C_LOC.
200         (iso_fortran_env_symbol, iso_c_binding_symbol): Handle
201         NAMED_SUBROUTINE.
202         (generate_isocbinding_symbol): Update prototype.
203         (get_iso_c_sym): Remove.
204         (gfc_isym_id_by_intmod, gfc_isym_id_by_intmod_sym): New prototypes.
205         * intrinsic.c (gfc_intrinsic_subroutine_by_id): New function.
206         (gfc_intrinsic_sub_interface): Use it.
207         (add_functions, add_subroutines): Add missing C-binding intrinsics.
208         (gfc_intrinsic_func_interface): Add special case for c_loc.
209         gfc_isym_id_by_intmod, gfc_isym_id_by_intmod_sym): New functions.
210         (gfc_intrinsic_func_interface, gfc_intrinsic_sub_interface): Use them.
211         * intrinsic.h (gfc_check_c_associated, gfc_check_c_f_pointer,
212         gfc_check_c_f_procpointer, gfc_check_c_funloc, gfc_check_c_loc,
213         gfc_resolve_c_loc, gfc_resolve_c_funloc): New prototypes.
214         * iresolve.c (gfc_resolve_c_loc, gfc_resolve_c_funloc): New
215         functions.
216         * iso-c-binding.def: Split PROCEDURE into NAMED_SUBROUTINE and
217         NAMED_FUNCTION.
218         * iso-fortran-env.def: Add NAMED_SUBROUTINE for completeness.
219         * module.c (create_intrinsic_function): Support subroutines and
220         derived-type results.
221         (use_iso_fortran_env_module): Update calls.
222         (import_iso_c_binding_module): Ditto; update calls to
223         generate_isocbinding_symbol.
224         * resolve.c (find_arglists): Skip for intrinsic symbols.
225         (gfc_resolve_intrinsic): Find intrinsic subs via id.
226         (is_scalar_expr_ptr, gfc_iso_c_func_interface,
227         set_name_and_label, gfc_iso_c_sub_interface): Remove.
228         (resolve_function, resolve_specific_s0): Remove calls to those.
229         (resolve_structure_cons): Fix handling.
230         * symbol.c (gen_special_c_interop_ptr): Update c_ptr/c_funptr
231         generation.
232         (gen_cptr_param, gen_fptr_param, gen_shape_param,
233         build_formal_args, get_iso_c_sym): Remove.
234         (std_for_isocbinding_symbol): Handle NAMED_SUBROUTINE.
235         (generate_isocbinding_symbol): Support hidden symbols and
236         using c_ptr/c_funptr symtrees for nullptr defs.
237         * target-memory.c (gfc_target_encode_expr): Fix handling
238         of c_ptr/c_funptr.
239         * trans-expr.c (conv_isocbinding_procedure): Remove.
240         (gfc_conv_procedure_call): Remove call to it.
241         (gfc_trans_subcomponent_assign, gfc_conv_expr): Update handling
242         of c_ptr/c_funptr.
243         * trans-intrinsic.c (conv_isocbinding_function,
244         conv_isocbinding_subroutine): New.
245         (gfc_conv_intrinsic_function, gfc_conv_intrinsic_subroutine):
246         Call them.
247         * trans-io.c (transfer_expr): Fix handling of c_ptr/c_funptr.
248         * trans-types.c (gfc_typenode_for_spec,
249         gfc_get_derived_type): Ditto.
250         (gfc_init_c_interop_kinds): Handle NAMED_SUBROUTINE.
251
252 2013-03-18  Tobias Burnus  <burnus@net-b.de>
253
254         * gfortran.h (gfc_option_t): Remove flag_whole_file.
255         * invoke.texi (-fno-whole-file): Remove.
256         * lang.opt (fwhole-file): Change to Ignore.
257         * options.c (gfc_init_options, gfc_post_options,
258         gfc_handle_option): Remove !flag_whole_file handling
259         * parse.c (resolve_all_program_units, translate_all_program_units,
260         gfc_parse_file): Ditto.
261         * resolve.c (resolve_global_procedure): Ditto.
262         * trans-decl.c (gfc_get_symbol_decl, gfc_get_extern_function_decl,
263         gfc_create_module_variable): Ditto.
264         * trans-types.c (gfc_get_derived_type): Ditto.
265
266 2013-03-15  Tobias Burnus  <burnus@net-b.de>
267
268         PR fortran/56615
269         * trans-intrinsic.c (gfc_conv_intrinsic_transfer): Pack arrays
270         if they are not simply contiguous.
271
272 2013-03-11  Tobias Burnus  <burnus@net-b.de>
273
274         * gfortran.texi (STRUCTURE and RECORD): State more clearly how
275         to convert them into derived types.
276
277 2013-03-10  Paul Thomas  <pault@gcc.gnu.org>
278
279         PR fortran/56575
280         * expr.c (gfc_default_initializer): Check that a class declared
281         type has any components.
282         * resolve.c (resolve_fl_derived0): On failing the test for C437
283         set the type to BT_UNKNOWN to prevent repeat error messages.
284
285 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
286
287         PR fortran/56477
288         * expr.c (gfc_check_pointer_assign): Avoid NULL pointer dereference.
289
290 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
291
292         PR fortran/54730
293         * array.c (gfc_match_array_constructor): Set a checkpoint before
294         matching a typespec.  Drop it on success, restore it otherwise.
295
296 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
297
298         PR fortran/54730
299         * gfortran.h (struct gfc_undo_change_set): New field 'previous'.
300         (gfc_new_undo_checkpoint, gfc_drop_last_undo_checkpoint,
301         gfc_restore_last_undo_checkpoint): New prototypes.
302         * symbol.c (default_undo_chgset_var): Update initialization.
303         (single_undo_checkpoint_p, gfc_new_undo_checkpoint,
304         free_undo_change_set_data, pop_undo_change_set,
305         gfc_drop_last_undo_checkpoint, enforce_single_undo_checkpoint):
306         New functions.
307         (save_symbol_data): Handle multiple change sets.  Make sure old_symbol
308         field's previous value is not overwritten.  Clear gfc_new field.
309         (restore_old_symbol): Restore previous old_symbol field.
310         (gfc_restore_last_undo_checkpoint): New function, using body renamed
311         from gfc_undo_symbols.  Restore the previous change set as current one.
312         (gfc_undo_symbols): New body.
313         (gfc_commit_symbols, gfc_commit_symbol, gfc_enforce_clean_symbol_state):
314         Call enforce_single_undo_checkpoint.
315         (gfc_symbol_done_2): Ditto.  Free change set data.
316
317 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
318
319         * symbol.c (restore_old_symbol): Fix thinko.
320
321 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
322
323         * symbol.c (gfc_undo_symbols): Move code...
324         (restore_old_symbol): ... here as a new function.
325
326 2013-03-03  Mikael Morin  <mikael@gcc.gnu.org>
327
328         * Make-lang.in (F95_PARSER_OBJS): Add dependency to vec.h.
329         * gfortran.h: Include vec.h.
330         (gfc_undo_change_set): New struct.
331         * symbol.c (tentative_tbp): Remove struct.
332         (changed_syms, tentative_tbp_list): Remove variables.
333         (default_undo_chgset_var, latest_undo_chgset): New variables.
334         (save_symbol_data, gfc_get_sym_tree, gfc_undo_symbols,
335         gfc_commit_symbols, gfc_commit_symbol,
336         gfc_enforce_clean_symbol_state, gfc_get_typebound_proc):
337         Use latest_undo_chgset instead of changed_syms and tentative_tbp_list.
338
339 2013-03-01  Tobias Burnus  <burnus@net-b.de>
340
341         PR fortran/56491
342         * iresolve.c (resolve_bound): Use gfc_get_string instead of xstrdup.
343         * symbol.c (free_components): Free proc-pointer components.
344
345 2013-03-01  Tobias Burnus  <burnus@net-b.de>
346
347         * trans-decl.c (gfc_trans_deferred_vars): Free expr after use.
348         * trans-io.c (build_dt): Ditto.
349
350 2013-02-24  Joseph Myers  <joseph@codesourcery.com>
351
352         * resolve.c (generate_component_assignments): Don't use UTF-8
353         ligature in diagnostic.
354
355 2013-02-21  Janus Weil  <janus@gcc.gnu.org>
356
357         PR fortran/56385
358         * trans-array.c (structure_alloc_comps): Handle procedure-pointer
359         components with allocatable result.
360
361 2013-02-21  Tobias Burnus  <burnus@net-b.de>
362
363         PR fortran/56416
364         * gfortran.texi (Part II: Language Reference, Extensions,
365         Non-Fortran Main Program): Sort @menu to match actual section order.
366         * intrinsic.texi (Intrinsic Procedures): Ditto.
367         (C_F_POINTER, PRECISION): Move to the alphabetically correct place.
368
369 2013-02-15  Tobias Burnus  <burnus@net-b.de>
370             Mikael Morin  <mikael@gcc.gnu.org>
371
372         PR fortran/56318
373         * simplify.c (gfc_simplify_matmul): Fix result shape
374         and matmul result.
375
376 2013-02-15  Tobias Burnus  <burnus@net-b.de>
377
378         PR fortran/53818
379         * resolve.c (apply_default_init_local): Don't create an
380         initializer for a result variable.
381
382 2013-02-14  Thomas Koenig  <tkoenig@gcc.gnu.org>
383
384         PR fortran/56224
385         * gfortran.h (gfc_add_include_path):  Add boolean argument
386         for warn.
387         * scanner.c (gfc_add_include_path):  Pass along warn argument
388         to add_path_to_list.
389         * options.c (gfc_post_options):  Add true warn argument to
390         gfc_add_include_path.
391         (gfc_handle_module_path_options):  Likewise.
392         (gfc_handle_option): Also gfc_add_include_path for intrinsic
393         modules, without warning.
394
395 2013-02-14  Paul Thomas  <pault@gcc.gnu.org>
396             Tobias Burnus  <burnus@net-b.de>
397
398         PR testsuite/56138
399         * trans-decl.c (gfc_get_symbol_decl): Fix deferred-length
400         results for functions without extra result variable.
401
402         Revert:
403         2013-01-30  Tobias Burnus  <burnus@net-b.de>
404
405         PR fortran/56138
406         * trans-decl.c (gfc_trans_deferred_vars): Fix deferred-length
407         results for functions without extra result variable.
408
409 2013-02-12  Janus Weil  <janus@gcc.gnu.org>
410
411         PR fortran/46952
412         * resolve.c (resolve_call): Do not check deferred procedures for
413         recursiveness.
414
415 2013-02-09  Paul Thomas  <pault@gcc.gnu.org>
416
417         PR fortran/55362
418         * check.c (array_check): It is an error if a procedure is
419         passed.
420
421 2013-02-08  Mikael Morin  <mikael@gcc.gnu.org>
422
423         PR fortran/54107
424         * trans-types.c (gfc_get_function_type): Change a NULL backend_decl
425         to error_mark_node on entry.  Detect recursive types.  Build a variadic
426         procedure type if the type is recursive.  Restore the initial
427         backend_decl.
428
429 2013-02-07  Tobias Burnus  <burnus@net-b.de>
430
431         PR fortran/54339
432         * gfortran.texi (Standards): Mention TS29113.
433         (Varying Length Character): Mention deferred-length
434         strings.
435         (Fortran 2003 Status): Add unlimited polymorphic.
436         (TS 29113 Status): Add TYPE(*) and DIMENSION(..).
437         (C Interop): Update the section about TS29113.
438
439 2013-02-06 Paul Thomas  <pault@gcc.gnu.org>
440
441         PR fortran/55789
442         * trans-array.c (trans_array_constructor): Remove condition
443         'dynamic' = true if the loop ubound is a VAR_DECL.
444
445 2013-02-04  Paul Thomas  <pault@gcc.gnu.org>
446
447         PR fortran/56008
448         PR fortran/47517
449         * trans-array.c (gfc_alloc_allocatable_for_assignment): Save
450         the lhs descriptor before it is modified for reallocation. Use
451         it to deallocate allocatable components in the reallocation
452         block.  Nullify allocatable components for newly (re)allocated
453         arrays.
454
455 2013-02-04  Mikael Morin  <mikael@gcc.gnu.org>
456
457         PR fortran/54195
458         * resolve.c (resolve_typebound_procedures): Recurse through
459         resolve_symbol.
460
461 2013-02-04  Mikael Morin  <mikael@gcc.gnu.org>
462
463         PR fortran/54107
464         PR fortran/54195
465         * gfortran.h (struct gfc_symbol): New field 'resolved'.
466         * resolve.c (resolve_fl_var_and_proc): Don't skip result symbols.
467         (resolve_symbol): Skip duplicate calls.  Don't check the current
468         namespace.
469
470 2013-02-02  Thomas Koenig  <tkoenig@gcc.gnu.org>
471
472         PR fortran/50627
473         PR fortran/56054
474         * decl.c (gfc_match_end):  Remove half-ready namespace
475         from parent if the end of a block is missing.
476         * parse.c (parse_module):  Do not put namespace into
477         gsymbol on error.
478
479 2013-01-30  Tobias Burnus  <burnus@net-b.de>
480
481         PR fortran/56138
482         * trans-decl.c (gfc_trans_deferred_vars): Fix deferred-length
483         results for functions without extra result variable.
484
485 2013-01-29  Janus Weil  <janus@gcc.gnu.org>
486             Mikael Morin  <mikael@gcc.gnu.org>
487
488         PR fortran/54107
489         * gfortran.h (gfc_component): Delete members 'formal' and 'formal_ns'.
490         (gfc_copy_formal_args,gfc_copy_formal_args_ppc,gfc_expr_replace_symbols,
491         gfc_expr_replace_comp): Delete.
492         (gfc_sym_get_dummy_args): New prototype.
493         * dependency.c (gfc_check_fncall_dependency): Use
494         'gfc_sym_get_dummy_args'.
495         * expr.c (gfc_is_constant_expr): Ditto.
496         (replace_symbol,gfc_expr_replace_symbols,replace_comp,
497         gfc_expr_replace_comp): Deleted.
498         * frontend-passes.c (doloop_code,do_function): Use
499         'gfc_sym_get_dummy_args'.
500         * interface.c (gfc_check_operator_interface,gfc_compare_interfaces,
501         gfc_procedure_use,gfc_ppc_use,gfc_arglist_matches_symbol,
502         gfc_check_typebound_override): Ditto.
503         * module.c (MOD_VERSION): Bump module version.
504         (mio_component): Do not read/write 'formal' and 'formal_ns'.
505         * resolve.c (resolve_procedure_interface,resolve_fl_derived0): Do not
506         copy formal args, but just keep a pointer to the interface.
507         (resolve_function,resolve_call,resolve_typebound_generic_call,
508         resolve_ppc_call,resolve_expr_ppc,generate_component_assignments,
509         resolve_fl_procedure,gfc_resolve_finalizers,check_generic_tbp_ambiguity,
510         resolve_typebound_procedure,check_uop_procedure): Use
511         'gfc_sym_get_dummy_args'.
512         * symbol.c (free_components): Do not free 'formal' and 'formal_ns'.
513         (gfc_copy_formal_args,gfc_copy_formal_args_ppc): Deleted.
514         (gfc_sym_get_dummy_args): New function.
515         * trans-array.c (get_array_charlen,gfc_walk_elemental_function_args):
516         Use 'gfc_sym_get_dummy_args'.
517         * trans-decl.c (build_function_decl,create_function_arglist,
518         build_entry_thunks,init_intent_out_dt,gfc_trans_deferred_vars,
519         add_argument_checking): Ditto.
520         * trans-expr.c (gfc_map_fcn_formal_to_actual,gfc_conv_procedure_call,
521         gfc_conv_statement_function): Ditto.
522         * trans-stmt.c (gfc_conv_elemental_dependencies): Ditto.
523         * trans-types.c (create_fn_spec,gfc_get_function_type): Ditto.
524
525 2013-01-28  Tobias Burnus  <burnus@net-b.de>
526             Mikael Morin  <mikael@gcc.gnu.org>
527
528         PR fortran/53537
529         * symbol.c (gfc_find_sym_tree): Don't look for the symbol outside an
530         interface block.
531         (gfc_get_ha_symtree): Let gfc_find_sym_tree lookup the parent namespace.
532         * decl.c (gfc_match_data_decl): Ditto.
533         (variable_decl): Remove undeclared type error.
534         (gfc_match_import): Use renamed instead of original name.
535
536 2013-01-27 Paul Thomas  <pault@gcc.gnu.org>
537
538         PR fortran/55984
539         PR fortran/56047
540         * gfortran.h : Add associate_var to symbol_attr.
541         * resolve.c (resolve_assoc_var): Set associate_var attribute.
542         If the target class_ok is set, set it for the associate
543         variable.
544         * check.c (allocatable_check): Associate variables should not
545         have the allocatable attribute even if their symbols do.
546         * class.c (gfc_build_class_symbol): Symbols with associate_var
547         set will always have a good class container.
548
549 2013-01-23  Janus Weil  <janus@gcc.gnu.org>
550
551         PR fortran/56081
552         * resolve.c (resolve_select): Add argument 'select_type', reject
553         non-scalar expressions.
554         (resolve_select_type,resolve_code): Pass new argument to
555         'resolve_select'.
556
557 2013-01-23  Jakub Jelinek  <jakub@redhat.com>
558
559         PR fortran/56052
560         * trans-decl.c (gfc_get_symbol_decl): Set DECL_ARTIFICIAL
561         and DECL_IGNORED_P on select_type_temporary and don't set
562         DECL_BY_REFERENCE.
563
564 2013-01-21  Thomas Koenig  <tkoenig@gcc.gnu.org>
565
566         PR fortran/55919
567         * scanner.c (add_path_to_list): Copy path to temporary and strip
568         trailing directory separators before calling stat().
569
570 2013-01-17  Richard Biener  <rguenther@suse.de>
571
572         * trans-stmt.c (gfc_trans_do): Conditionally compute countm1
573         dependent on sign of step, avoids repeated evaluation of
574         step sign test.  Avoid undefined overflow issues by using unsigned
575         arithmetic.
576
577 2013-01-16  Janus Weil  <janus@gcc.gnu.org>
578
579         PR fortran/55983
580         * class.c (find_typebound_proc_uop): Check for f2k_derived instead of
581         asserting it.
582
583 2013-01-16  Jakub Jelinek  <jakub@redhat.com>
584             Tobias Burnus  <burnus@net-b.de>
585
586         PR driver/55884
587         * lang.opt (fintrinsic-modules-path): Don't accept Joined.
588         (fintrinsic-modules-path=): New.
589         * options.c (gfc_handle_option, gfc_get_option_string,
590         gfc_get_option_string): Handle the latter.
591
592 2013-01-16  Jakub Jelinek  <jakub@redhat.com>
593
594         PR fortran/52865
595         * trans-stmt.c (gfc_trans_do): Put countm1-- before conditional
596         and use value of countm1 before the decrement in the condition.
597
598 2013-01-15  Paul Thomas  <pault@gcc.gnu.org>
599
600         PR fortran/54286
601         * expr.c (gfc_check_pointer_assign): Check for presence of
602         's2' before using it.
603
604 2013-01-14  Thomas Koenig  <tkoenig@gcc.gnu.org>
605
606         PR fortran/55806
607         * frontend-passes.c (optimize_reduction):  New function,
608         including prototype.
609         (callback_reduction):  Likewise.
610         (gfc_run_passes):  Also run optimize_reduction.
611         (copy_walk_reduction_arg):  New function.
612         (dummy_code_callback):  New function.
613
614 2013-01-13  Jakub Jelinek  <jakub@redhat.com>
615
616         PR fortran/55935
617         * trans-expr.c (gfc_conv_structure): Call
618         unshare_expr_without_location on the ctor elements.
619
620 2013-01-13  Paul Thomas  <pault@gcc.gnu.org>
621
622         PR fortran/54286
623         * expr.c (gfc_check_pointer_assign): Ensure that both lvalue
624         and rvalue interfaces are presented to gfc_compare_interfaces.
625         Simplify references to interface names by using the symbols
626         themselves. Call gfc_compare_interfaces with s1 and s2 inter-
627         changed to overcome the asymmetry of this function. Do not
628         repeat the check for the presence of s1 and s2.
629
630 2013-01-12  Janus Weil  <janus@gcc.gnu.org>
631
632         PR fortran/55072
633         * trans-array.c (gfc_conv_array_parameter): No packing was done for
634         full arrays of derived type.
635
636 2013-01-08  Paul Thomas  <pault@gcc.gnu.org>
637
638         PR fortran/55868
639         * class.c (get_unique_type_string): Change $tar to STAR and
640         replace sprintf by strcpy where there is no formatting.
641         * decl.c (gfc_match_decl_type_spec): Change $tar to STAR.
642
643 2013-01-09  Mikael Morin  <mikael@gcc.gnu.org>
644
645         PR fortran/47203
646         * module.c (check_for_ambiguous): Get the current program unit using
647         gfc_current_ns.
648
649 2013-01-09  Tobias Burnus  <burnus@net-b.de>
650
651         PR fortran/55758
652         * resolve.c (resolve_symbol): Reject non-C_Bool logicals
653         in BIND(C) procedures with -std=f*.
654
655 2013-01-08  Paul Thomas  <pault@gcc.gnu.org>
656
657         PR fortran/55618
658         * trans-expr.c (gfc_conv_procedure_call): Dereference scalar
659         character function arguments to elemental procedures in
660         scalarization loops.
661
662 2013-01-07  Tobias Burnus  <burnus@net-b.de>
663
664         PR fortran/55763
665         * gfortran.h (gfc_check_assign_symbol): Update prototype.
666         * decl.c (add_init_expr_to_sym, do_parm): Update call.
667         * expr.c (gfc_check_assign_symbol): Handle BT_CLASS and
668         improve error location; support components.
669         (gfc_check_pointer_assign): Handle component assignments.
670         * resolve.c (resolve_fl_derived0): Call gfc_check_assign_symbol.
671         (resolve_values): Update call.
672         (resolve_structure_cons): Avoid double diagnostic.
673
674 2013-01-07  Tobias Burnus  <burnus@net-b.de>
675             Thomas Koenig  <tkoenig@gcc.gnu.org>
676
677         PR fortran/55852
678         * expr.c (gfc_build_intrinsic_call): Avoid clashes
679         with user's procedures.
680         * gfortran.h (gfc_build_intrinsic_call): Update prototype.
681         * simplify.c (gfc_simplify_size): Update call.
682         * class.c (finalization_scalarizer, finalization_get_offset,
683         finalizer_insert_packed_call, generate_finalization_wrapper):
684         Clean up by using gfc_build_intrinsic_call.
685
686 2013-01-07  Tobias Burnus  <burnus@net-b.de>
687
688         PR fortran/55763
689         * resolve.c (resolve_select_type): Reject intrinsic types for
690         a non-unlimited-polymorphic selector.
691
692 2013-01-06  Paul Thomas  <pault@gcc.gnu.org>
693
694         PR fortran/53876
695         PR fortran/54990
696         PR fortran/54992
697         * trans-array.c (build_array_ref): Check the TYPE_CANONICAL
698         to see if it is GFC_CLASS_TYPE_P.
699         * trans-expr.c (gfc_get_vptr_from_expr): The same.
700         (gfc_conv_class_to_class): If the types are not the same,
701         cast parmese->expr to the type of ctree.
702         * trans-types.c (gfc_get_derived_type): GFC_CLASS_TYPE_P of
703         CLASS components must be set.
704
705 2013-01-06  Mikael Morin  <mikael@gcc.gnu.org>
706
707         PR fortran/42769
708         PR fortran/45836
709         PR fortran/45900
710         * module.c (read_module): Don't reuse local symtree if the associated
711         symbol isn't exactly the one wanted.  Don't reuse local symtree if it is
712         ambiguous.
713         * resolve.c (resolve_call): Use symtree's name instead of symbol's to
714         lookup the symtree.
715
716 2013-01-05  Steven G. Kargl  <kargl@gcc.gnu.org>
717             Mikael Morin  <mikael@gcc.gnu.org>
718
719         PR fortran/55827
720         * class.c (gfc_fix_class_refs): Adapt ts initialization for the case
721         e->symtree == NULL.
722         * trans-expr.c (gfc_conv_function_expr): Init sym earlier. Use it.
723
724 2013-01-05  Tobias Burnus  <burnus@net-b.de>
725
726         * class.c (finalize_component): Used passed offset expr.
727         (finalization_get_offset): New static function.
728         (finalizer_insert_packed_call, generate_finalization_wrapper): Use it
729         to handle noncontiguous arrays.
730
731 2013-01-04  Tobias Burnus  <burnus@net-b.de>
732
733         * trans.c (gfc_build_final_call): New function.
734         * trans.h (gfc_build_final_call, gfc_conv_scalar_to_descriptor):
735         New function prototypes.
736         * trans-expr.c (gfc_conv_scalar_to_descriptor): Renamed from
737         conv_scalar_to_descriptor, removed static attribute.
738         (gfc_conv_procedure_call): Honor renaming.
739
740 2013-01-04  Tobias Burnus  <burnus@net-b.de>
741
742         * intrinsic.c (add_functions): New internal intrinsic
743         function GFC_PREFIX ("stride").
744         * gfortran.h (gfc_isym_id): Add GFC_ISYM_STRIDE.
745         * intrinsic.h (gfc_resolve_stride): New prototypes.
746         * iresolve.c (gfc_resolve_stride): New function.
747         * trans-intrinsic.c (conv_intrinsic_stride): New static
748         function.
749         (gfc_conv_intrinsic_function): Use it.
750
751 2013-01-04  Tobias Burnus  <burnus@net-b.de>
752
753         * class.c (gfc_find_intrinsic_vtab): Add _final
754         component.
755         * decl.c (gfc_match_null): Remove superfluous
756         variadic argument to gfc_match.
757
758 2013-01-04  Paul Thomas  <pault@gcc.gnu.org>
759
760         PR fortran/55172
761         * match.c (copy_ts_from_selector_to_associate): Remove call to
762         gfc_resolve_expr and replace it with explicit setting of the
763         array reference type.
764         * resolve.c (resolve_select_type): It is an error if the
765         selector is coindexed.
766
767 2013-01-04  Tobias Burnus  <burnus@net-b.de>
768
769         PR fortran/55763
770         * decl.c (gfc_match_null): Parse and reject MOLD.
771
772 2013-01-04  Tobias Burnus  <burnus@net-b.de>
773
774         PR fortran/55854
775         PR fortran/55763
776         * class.c (gfc_class_null_initializer): Fix finding the vtab.
777         (gfc_find_intrinsic_vtab): Use BT_VOID for some components.
778
779 2013-01-03  Janus Weil  <janus@gcc.gnu.org>
780
781         PR fortran/55855
782         * expr.c (gfc_check_assign): Use 'gfc_expr_attr' to evaluate attributes
783         of rvalue. Correct hyphenation in error message.
784
785 2013-01-03  Jakub Jelinek  <jakub@redhat.com>
786
787         * gfortranspec.c (lang_specific_driver): Update copyright notice
788         dates.
789 \f
790 Copyright (C) 2013 Free Software Foundation, Inc.
791
792 Copying and distribution of this file, with or without modification,
793 are permitted in any medium without royalty provided the copyright
794 notice and this notice are preserved.