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