re PR fortran/62142 (internal compiler error: Segmentation fault (X = X - L*floor...
[platform/upstream/gcc.git] / gcc / fortran / ChangeLog
1 2014-08-15  Thomas Koenig  <tkoenig@gcc.gnu.org>
2
3         PR fortran/62142
4         * trans-expr.c (is_runtime_conformable):  Add NULL pointer checks.
5
6 2014-08-15  Tobias Burnus  <burnus@net-b.de>
7
8         * resolve.c (resolve_critical): Fix name mangling.
9         * trans-stmt.c (gfc_trans_critical): Fix lock call.
10
11 2014-08-15  Manuel López-Ibáñez  <manu@gcc.gnu.org>
12
13         PR fortran/44054
14         * gfortran.h: Define GCC_DIAG_STYLE.
15         (gfc_diagnostics_init,gfc_warning_cmdline): Declare.
16         * trans-array.c: Include gfortran.h before diagnostic-core.h.
17         * trans-expr.c: Likewise.
18         * trans-openmp.c: Likewise.
19         * trans-const.c: Likewise.
20         * trans.c: Likewise.
21         * trans-types.c: Likewise.
22         * f95-lang.c: Likewise.
23         * trans-decl.c: Likewise.
24         * trans-io.c: Likewise.
25         * trans-intrinsic.c: Likewise.
26         * error.c: Include diagnostic.h and diagnostic-color.h.
27         (gfc_diagnostic_build_prefix): New.
28         (gfc_diagnostic_starter): New.
29         (gfc_diagnostic_finalizer): New.
30         (gfc_warning_cmdline): New.
31         (gfc_diagnostics_init): New.
32         * gfc-diagnostic.def: New.
33         * options.c (gfc_init_options): Call gfc_diagnostics_init.
34         (gfc_post_options): Use gfc_warning_cmdline.
35
36 2014-08-15  Jakub Jelinek  <jakub@redhat.com>
37             Tobias Burnus  <burnus@net-b.de>
38
39         PR fortran/62131
40         * openmp.c (resolve_omp_atomic): Only complain if code->expr1's attr
41         is allocatable, rather than whenever var->attr.allocatable.
42
43 2014-08-15  Jakub Jelinek  <jakub@redhat.com>
44
45         PR fortran/62107
46         * trans-openmp.c (gfc_omp_finish_clause): Handle scalar pointer
47         or allocatable passed by reference.
48         (gfc_trans_omp_clauses) <case OMP_LIST_MAP>: Likewise.
49
50 2014-08-14  Thomas Koenig  <tkoenig@gcc.gnu.org>
51
52         PR fortran/62106
53         * gfortran.h (symbol_attribute):  Add fe_temp flag.
54         * frontend-passes.c (is_fe_temp):  New function.
55         (create_var):  Don't add a temporary for an already
56         created variable or for a constant.
57         (combine_ARRAY_constructor):  Remove special handling
58         for constants.
59
60 2014-08-14  Tobias Burnus  <burnus@net-b.de>
61
62         * gfortran.texi (caf_register_t): Add CAF_REGTYPE_CRITICAL.
63         (_gfortran_caf_register): Update for locking/critical.
64         (_gfortran_caf_lock, _gfortran_caf_unlock): Add.
65         * resolve.c (resolve_critical): New.
66         (gfc_resolve_code): Call it.
67         * trans-decl.c (gfor_fndecl_caf_critical,
68         gfor_fndecl_caf_end_critical): Remove.
69         (gfor_fndecl_caf_lock, gfor_fndecl_caf_unlock): Add.
70         (gfc_build_builtin_function_decls): Remove critical,
71         assign locking declarations.
72         (generate_coarray_sym_init): Handle locking and
73         critical variables.
74         * trans-stmt.c (gfc_trans_critical): Add calls to
75         lock/unlock libcaf functions.
76         * trans.h (gfc_coarray_type): Update locking, add
77         critical enum values.
78         (gfor_fndecl_caf_critical, gfor_fndecl_caf_end_critical): Remove.
79         (gfor_fndecl_caf_lock, gfor_fndecl_caf_unlock): Add.
80
81 2014-08-14  Tobias Burnus  <burnus@net-b.de>
82
83         * gfortran.texi (Coarray Programming): Add first ABI
84         documentation.
85
86 2014-08-14  Jakub Jelinek  <jakub@redhat.com>
87
88         PR fortran/62076
89         * openmp.c (gfc_match_omp_clauses): When failed to match
90         operator name, defined op name or name, set buffer to
91         empty string.  Don't call gfc_find_omp_udr if buffer is empty
92         string.
93         (gfc_match_omp_declare_reduction): Call gfc_undo_symbols ()
94         before calling gfc_free_omp_udr.
95
96 2014-08-11  Richard Biener  <rguenther@suse.de>
97
98         PR fortran/61950
99         * trans-expr.c (gfc_conv_structure): Initialize _size with
100         a value of proper type.
101
102 2014-08-10  Thomas Koenig  <tkoenig@gcc.gnu.org>
103
104         PR fortran/61999
105         * simplify.c (gfc_simplify_dot_product): Convert types of
106         vectors before calculating the result.
107
108 2014-08-02  Trevor Saunders  <tsaunders@mozilla.com>
109
110         * openmp.c, trans-decl.c: Use hash_set instead of pointer_set.
111
112 2014-07-26  Tobias Burnus  <burnus@net-b.de>
113
114         PR fortran/61881
115         PR fortran/61888
116         PR fortran/57305
117         * intrinsic.texi (SIZEOF): Document changed behavior
118         for polymorphic arrays.
119
120 2014-07-26  Tobias Burnus  <burnus@net-b.de>
121
122         PR fortran/61881
123         PR fortran/61888
124         PR fortran/57305
125         * check.c (gfc_check_sizeof): Permit for assumed type if and
126         only if it has an array descriptor.
127         * intrinsic.c (do_ts29113_check): Permit SIZEOF.
128         (add_functions): SIZEOF is an Inquiry function.
129         * intrinsic.texi (SIZEOF): Add note that only contiguous
130         arrays are permitted.
131         * trans-expr.c (gfc_conv_intrinsic_to_class): Handle assumed
132         rank.
133         * trans-intrinsic.c (gfc_conv_intrinsic_sizeof): Handle
134         assumed type + array descriptor, CLASS and assumed rank.
135         (gfc_conv_intrinsic_storage_size): Handle class arrays.
136
137 2014-07-25  Tobias Burnus  <burnus@net-b.de>
138
139         * simplify.c (gfc_simplify_storage_size): Use proper
140         integer kind for the returned value.
141
142 2014-07-24  Uros Bizjak  <ubizjak@gmail.com>
143
144         * intrinsic.texi (Intrinsic Procedures) <ATOMIC_DEFINE>: Move to
145         correct menu position to match sectioning.
146
147 2014-06-15  Tobias Burnus  <burnus@net-b.de>
148
149         * symbol.c (check_conflict): Add codimension conflict with
150         pointer; fix cray-pointee check.
151
152 2014-06-14  Tobias Burnus  <burnus@net-b.de>
153
154         * trans-intrinsic.c (conv_intrinsic_atomic_ref): Fix handling
155         for kind mismatch with -fcoarray=lib.
156
157 2014-07-12  Paul Thomas  <pault@gcc.gnu.org>
158
159         PR fortran/61780
160         * dependency.c (gfc_dep_resolver): Index the 'reverse' array so
161         that elements are skipped. This then correctly aligns 'reverse'
162         with the scalarizer loops.
163
164 2014-07-12  Tobias Burnus  <burnus@net-b.de>
165
166         PR fortran/61628
167         * trans-types.c (gfc_init_types): Fix data-type bug
168         with gfc_max_array_element_size.
169
170 2014-07-12  Tobias Burnus  <burnus@net-b.de>
171
172         * libgfortran.h (libcaf_atomic_codes): Add.
173         * trans-decl.c (gfor_fndecl_caf_atomic_def,
174         gfor_fndecl_caf_atomic_ref, gfor_fndecl_caf_atomic_cas,
175         gfor_fndecl_caf_atomic_op): New variables.
176         (gfc_build_builtin_function_decls): Initialize them.
177         * trans.h (gfor_fndecl_caf_atomic_def,
178         gfor_fndecl_caf_atomic_ref, gfor_fndecl_caf_atomic_cas,
179         gfor_fndecl_caf_atomic_op): New variables.
180         * trans-intrinsic.c (conv_intrinsic_atomic_op,
181         conv_intrinsic_atomic_ref, conv_intrinsic_atomic_cas):
182         Add library calls with -fcoarray=lib.
183
184 2014-07-12  Tobias Burnus  <burnus@net-b.de>
185
186         * check.c (gfc_check_atomic): Update for STAT=.
187         (gfc_check_atomic_def, gfc_check_atomic_ref): Update call.
188         (gfc_check_atomic_op, gfc_check_atomic_cas,
189         gfc_check_atomic_fetch_op): New.
190         * gfortran.h (gfc_isym_id): GFC_ISYM_ATOMIC_CAS, GFC_ISYM_ATOMIC_ADD,
191         GFC_ISYM_ATOMIC_AND, GFC_ISYM_ATOMIC_OR, GFC_ISYM_ATOMIC_XOR,
192         GFC_ISYM_ATOMIC_FETCH_ADD, GFC_ISYM_ATOMIC_FETCH_AND,
193         GFC_ISYM_ATOMIC_FETCH_OR and GFC_ISYM_ATOMIC_FETCH_XOR.
194         * intrinsic.c (add_subroutines): Handle them.
195         * intrinsic.texi: Add documentation for them.
196         (ATOMIC_REF, ATOMIC_DEFINE): Add STAT=.
197         (ISO_FORTRAN_ENV): Add STAT_FAILED_IMAGE.
198         * intrinsic.h (gfc_check_atomic_op, gfc_check_atomic_cas,
199         gfc_check_atomic_fetch_op): New
200         prototypes.
201         * libgfortran.h (libgfortran_stat_codes): Add GFC_STAT_FAILED_IMAGE.
202         * iso-fortran-env.def: Add it.
203         * trans-intrinsic.c (conv_intrinsic_atomic_op): Renamed from
204         conv_intrinsic_atomic_ref; handle more atomics.
205         (conv_intrinsic_atomic_def): Handle STAT=.
206         (conv_intrinsic_atomic_cas): New.
207         (gfc_conv_intrinsic_subroutine): Handle new atomics.
208
209 2014-07-09  Bernd Schmidt  <bernds@codesourcery.com>
210
211         * trans-array.c (gfc_build_constant_array_constructor): Build a
212         static decl manually.
213         * trans-decl.c (create_main_function): Likewise.
214
215 2014-07-07  Paul Thomas  <pault@gcc.gnu.org>
216
217         PR fortran/61459
218         PR fortran/58883
219         * trans-expr.c (fcncall_realloc_result): Use the natural type
220         for the address expression of 'res_desc'.
221
222 2014-07-07  Gerald Pfeifer  <gerald@pfeifer.com>
223
224         * gfortran.texi (Fortran 2003 status): Fix grammar.
225
226 2014-07-04  Tobias Burnus  <burnus@net-b.de>
227
228         * resolve.c (resolve_assoc_var): Fix corank setting.
229         * trans-array.c (gfc_conv_descriptor_token): Change assert.
230         for select-type temporaries.
231         * trans-decl.c (generate_coarray_sym_init): Skip for
232         attr.select_type_temporary.
233         * trans-expr.c (gfc_conv_procedure_call): Fix for
234         select-type temporaries.
235         * trans-intrinsic.c (get_caf_token_offset): Ditto.
236         (gfc_conv_intrinsic_caf_get, gfc_conv_intrinsic_caf_send): Set
237         the correct dtype.
238         * trans-types.h (gfc_get_dtype_rank_type): New.
239         * trans-types.c (gfc_get_dtype_rank_type): Ditto.
240
241 2014-07-03  Tobias Burnus  <burnus@net-b.de>
242
243         * scanner.c (skip_free_comments): Fix indentation.
244
245 2014-07-02  Jakub Jelinek  <jakub@redhat.com>
246             Fritz Reese  <Reese-Fritz@zai.com>
247
248         * decl.c (variable_decl): Reject old style initialization
249         for derived type components.
250
251 2014-06-29  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
252
253         PR fortran/36275
254         PR fortran/38839
255         * decl.c (check_bind_name_identifier): New function.
256         (gfc_match_bind_c): Match any constant expression as binding
257         label.
258         * match.c (gfc_match_name_C): Remove.
259
260 2014-06-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
261
262         PR fortran/29383
263         * gfortran.h (gfc_simplify_ieee_selected_real_kind): New prototype.
264         * libgfortran.h (GFC_FPE_*): Use simple integer values, valid in
265         both C and Fortran.
266         * expr.c (gfc_check_init_expr): Simplify IEEE_SELECTED_REAL_KIND.
267         * simplify.c (gfc_simplify_ieee_selected_real_kind): New function.
268         * module.c (mio_symbol): Keep track of symbols which came from
269         intrinsic modules.
270         (gfc_use_module): Keep track of the IEEE modules.
271         * trans-decl.c (gfc_get_symbol_decl): Adjust code since
272         we have new intrinsic modules.
273         (gfc_build_builtin_function_decls): Build decls for
274         ieee_procedure_entry and ieee_procedure_exit.
275         (is_from_ieee_module, is_ieee_module_used, save_fp_state,
276         restore_fp_state): New functions.
277         (gfc_generate_function_code): Save and restore floating-point
278         state on procedure entry/exit, when IEEE modules are used.
279         * intrinsic.texi: Document the IEEE modules.
280
281 2014-06-25  Tobias Burnus  <burnus@net-b.de>
282
283         * interface.c (check_intents): Fix diagnostic with
284         coindexed coarrays.
285
286 2014-06-25  Tobias Burnus  <burnus@net-b.de>
287
288         * resolve.c (resolve_ordinary_assign): Don't invoke caf_send
289         when assigning a coindexed RHS scalar to a noncoindexed LHS
290         array.
291         * trans-intrinsic.c (conv_caf_send): Do numeric type conversion
292         for a noncoindexed scalar RHS.
293
294 2014-06-25  Tobias Burnus  <burnus@net-b.de>
295
296         * check.c (check_co_minmaxsum): Add definable check.
297         * expr.c (gfc_check_vardef_context): Fix context == NULL case.
298         * trans-expr.c (get_scalar_to_descriptor_type): Handle pointer
299         arguments.
300         * trans-intrinsic.c (gfc_conv_intrinsic_caf_get): Fix generation of
301         temporary strings.
302
303 2014-06-25  Jakub Jelinek  <jakub@redhat.com>
304
305         * trans.h (gfc_omp_clause_linear_ctor): New prototype.
306         * trans-openmp.c (gfc_omp_linear_clause_add_loop,
307         gfc_omp_clause_linear_ctor): New functions.
308         (gfc_trans_omp_clauses): Make sure OMP_CLAUSE_LINEAR_STEP has
309         correct type.  Set OMP_CLAUSE_LINEAR_ARRAY flag if needed.
310         * f95-lang.c (LANG_HOOKS_OMP_CLAUSE_LINEAR_CTOR): Redefine.
311
312 2014-06-24  Jakub Jelinek  <jakub@redhat.com>
313
314         * dump-parse-tree.c (show_omp_namelist): Use n->udr->udr instead
315         of n->udr.
316         * f95-lang.c (gfc_init_builtin_functions): Initialize
317         BUILT_IN_ASSUME_ALIGNED.
318         * gfortran.h (gfc_omp_namelist): Change udr field type to
319         struct gfc_omp_namelist_udr.
320         (gfc_omp_namelist_udr): New type.
321         (gfc_get_omp_namelist_udr): Define.
322         (gfc_resolve_code): New prototype.
323         * match.c (gfc_free_omp_namelist): Free name->udr.
324         * module.c (intrinsics): Add INTRINSIC_USER.
325         (fix_mio_expr): Likewise.
326         (mio_expr): Handle INSTRINSIC_USER and non-resolved EXPR_FUNCTION.
327         * openmp.c (gfc_match_omp_clauses): Adjust initialization of n->udr.
328         (gfc_match_omp_declare_reduction): Treat len=: the same as len=*.
329         Set attr.flavor on omp_{out,in,priv,orig} artificial variables.
330         (struct resolve_omp_udr_callback_data): New type.
331         (resolve_omp_udr_callback, resolve_omp_udr_callback2,
332         resolve_omp_udr_clause): New functions.
333         (resolve_omp_clauses): Adjust for n->udr changes, resolve UDR clauses
334         here.
335         (omp_udr_callback): Don't check for implicitly declared functions
336         here.
337         (gfc_resolve_omp_udr): Don't call gfc_resolve.  Don't check for
338         implicitly declared subroutines here.
339         * resolve.c (resolve_function): If value.function.isym is non-NULL,
340         consider it already resolved.
341         (resolve_code): Renamed to ...
342         (gfc_resolve_code): ... this.  No longer static.
343         (gfc_resolve_blocks, generate_component_assignments, resolve_codes):
344         Adjust callers.
345         * trans-openmp.c (gfc_omp_privatize_by_reference): Don't privatize
346         by reference type (C_PTR) variables.
347         (gfc_omp_finish_clause): Make sure OMP_CLAUSE_SIZE is non-NULL.
348         (gfc_trans_omp_udr_expr): Remove.
349         (gfc_trans_omp_array_reduction_or_udr): Adjust for n->udr changes.
350         Don't call gfc_trans_omp_udr_expr, even for sym->attr.dimension
351         expand it as assignment or subroutine call.  Don't initialize
352         value.function.isym.
353
354 2014-06-23  Tobias Burnus  <burnus@net-b.de>
355
356         * trans-decl.c (gfc_trans_deferred_vars): Fix handling of
357         explicit-size arrays with -fcoarray=lib.
358
359 2014-06-20  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
360
361         PR fortran/33363
362         * invoke.texi: Don't mention nonexisting -fcase-lower option.
363
364 2014-06-19  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
365
366         PR fortran/61454
367         * expr.c (scalarize_intrinsic_call): Take care of optional
368         arguments.
369
370 2014-06-19  Tobias Burnus  <burnus@net-b.de>
371
372         * trans-intrinsic.c (conv_co_minmaxsum): Fix argument
373         passing.
374
375 2014-06-18  Tobias Burnus  <burnus@net-b.de>
376
377         * gfortran.texi (OpenMP): Update refs to OpenMP 4.0.
378         * intrinsic.texi (OpenMP Modules): Ditto.
379
380 2014-06-18  Jakub Jelinek  <jakub@redhat.com>
381
382         * cpp.c (cpp_define_builtins): Change _OPENMP macro to
383         201307.
384         * dump-parse-tree.c (show_omp_namelist): Add list_type
385         argument.  Adjust for rop being u.reduction_op now,
386         handle depend_op or map_op.
387         (show_omp_node): Adjust callers.  Print some new
388         OpenMP 4.0 clauses, adjust for OMP_LIST_DEPEND_{IN,OUT}
389         becoming a single OMP_LIST_DEPEND.
390         * f95-lang.c (gfc_handle_omp_declare_target_attribute): New
391         function.
392         (gfc_attribute_table): New variable.
393         (LANG_HOOKS_OMP_FINISH_CLAUSE, LANG_HOOKS_ATTRIBUTE_TABLE): Redefine.
394         * frontend-passes.c (gfc_code_walker): Handle new OpenMP target
395         EXEC_OMP_* codes and new clauses.
396         * gfortran.h (gfc_statement): Add ST_OMP_TARGET, ST_OMP_END_TARGET,
397         ST_OMP_TARGET_DATA, ST_OMP_END_TARGET_DATA, ST_OMP_TARGET_UPDATE,
398         ST_OMP_DECLARE_TARGET, ST_OMP_TEAMS, ST_OMP_END_TEAMS,
399         ST_OMP_DISTRIBUTE, ST_OMP_END_DISTRIBUTE, ST_OMP_DISTRIBUTE_SIMD,
400         ST_OMP_END_DISTRIBUTE_SIMD, ST_OMP_DISTRIBUTE_PARALLEL_DO,
401         ST_OMP_END_DISTRIBUTE_PARALLEL_DO, ST_OMP_DISTRIBUTE_PARALLEL_DO_SIMD,
402         ST_OMP_END_DISTRIBUTE_PARALLEL_DO_SIMD, ST_OMP_TARGET_TEAMS,
403         ST_OMP_END_TARGET_TEAMS, ST_OMP_TEAMS_DISTRIBUTE,
404         ST_OMP_END_TEAMS_DISTRIBUTE, ST_OMP_TEAMS_DISTRIBUTE_SIMD,
405         ST_OMP_END_TEAMS_DISTRIBUTE_SIMD, ST_OMP_TARGET_TEAMS_DISTRIBUTE,
406         ST_OMP_END_TARGET_TEAMS_DISTRIBUTE,
407         ST_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD,
408         ST_OMP_END_TARGET_TEAMS_DISTRIBUTE_SIMD,
409         ST_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO,
410         ST_OMP_END_TEAMS_DISTRIBUTE_PARALLEL_DO,
411         ST_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO,
412         ST_OMP_END_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO,
413         ST_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD,
414         ST_OMP_END_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD,
415         ST_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD and
416         ST_OMP_END_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD.
417         (symbol_attribute): Add omp_declare_target field.
418         (gfc_omp_depend_op, gfc_omp_map_op): New enums.
419         (gfc_omp_namelist): Replace rop field with union
420         containing reduction_op, depend_op and map_op.
421         (OMP_LIST_DEPEND_IN, OMP_LIST_DEPEND_OUT): Remove.
422         (OMP_LIST_DEPEND, OMP_LIST_MAP, OMP_LIST_TO, OMP_LIST_FROM): New.
423         (gfc_omp_clauses): Add num_teams, device, thread_limit,
424         dist_sched_kind, dist_chunk_size fields.
425         (gfc_common_head): Add omp_declare_target field.
426         (gfc_exec_op): Add EXEC_OMP_TARGET, EXEC_OMP_TARGET_DATA,
427         EXEC_OMP_TEAMS, EXEC_OMP_DISTRIBUTE, EXEC_OMP_DISTRIBUTE_SIMD,
428         EXEC_OMP_DISTRIBUTE_PARALLEL_DO, EXEC_OMP_DISTRIBUTE_PARALLEL_DO_SIMD,
429         EXEC_OMP_TARGET_TEAMS, EXEC_OMP_TEAMS_DISTRIBUTE,
430         EXEC_OMP_TEAMS_DISTRIBUTE_SIMD, EXEC_OMP_TARGET_TEAMS_DISTRIBUTE,
431         EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_SIMD,
432         EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO,
433         EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO,
434         EXEC_OMP_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD,
435         EXEC_OMP_TARGET_TEAMS_DISTRIBUTE_PARALLEL_DO_SIMD and
436         EXEC_OMP_TARGET_UPDATE.
437         (gfc_add_omp_declare_target): New prototype.
438         * match.h (gfc_match_omp_declare_target, gfc_match_omp_distribute,
439         gfc_match_omp_distribute_parallel_do,
440         gfc_match_omp_distribute_parallel_do_simd,
441         gfc_match_omp_distribute_simd, gfc_match_omp_target,
442         gfc_match_omp_target_data, gfc_match_omp_target_teams,
443         gfc_match_omp_target_teams_distribute,
444         gfc_match_omp_target_teams_distribute_parallel_do,
445         gfc_match_omp_target_teams_distribute_parallel_do_simd,
446         gfc_match_omp_target_teams_distribute_simd,
447         gfc_match_omp_target_update, gfc_match_omp_teams,
448         gfc_match_omp_teams_distribute,
449         gfc_match_omp_teams_distribute_parallel_do,
450         gfc_match_omp_teams_distribute_parallel_do_simd,
451         gfc_match_omp_teams_distribute_simd): New prototypes.
452         * module.c (ab_attribute): Add AB_OMP_DECLARE_TARGET.
453         (attr_bits): Likewise.
454         (mio_symbol_attribute): Handle omp_declare_target attribute.
455         (gfc_free_omp_clauses): Free num_teams, device, thread_limit
456         and dist_chunk_size expressions.
457         (OMP_CLAUSE_PRIVATE, OMP_CLAUSE_FIRSTPRIVATE, OMP_CLAUSE_LASTPRIVATE,
458         OMP_CLAUSE_COPYPRIVATE, OMP_CLAUSE_SHARED, OMP_CLAUSE_COPYIN,
459         OMP_CLAUSE_REDUCTION, OMP_CLAUSE_IF, OMP_CLAUSE_NUM_THREADS,
460         OMP_CLAUSE_SCHEDULE, OMP_CLAUSE_DEFAULT, OMP_CLAUSE_ORDERED,
461         OMP_CLAUSE_COLLAPSE, OMP_CLAUSE_UNTIED, OMP_CLAUSE_FINAL,
462         OMP_CLAUSE_MERGEABLE, OMP_CLAUSE_ALIGNED, OMP_CLAUSE_DEPEND,
463         OMP_CLAUSE_INBRANCH, OMP_CLAUSE_LINEAR, OMP_CLAUSE_NOTINBRANCH,
464         OMP_CLAUSE_PROC_BIND, OMP_CLAUSE_SAFELEN, OMP_CLAUSE_SIMDLEN,
465         OMP_CLAUSE_UNIFORM): Use 1U instead of 1.
466         (OMP_CLAUSE_DEVICE, OMP_CLAUSE_MAP, OMP_CLAUSE_TO, OMP_CLAUSE_FROM,
467         OMP_CLAUSE_NUM_TEAMS, OMP_CLAUSE_THREAD_LIMIT,
468         OMP_CLAUSE_DIST_SCHEDULE): Define.
469         (gfc_match_omp_clauses): Change mask parameter to unsigned int.
470         Adjust for rop becoming u.reduction_op.  Disallow inbranch with
471         notinbranch.  For depend clause, always create OMP_LIST_DEPEND
472         and fill in u.depend_op.  Handle num_teams, device, map,
473         to, from, thread_limit and dist_schedule clauses.
474         (OMP_DECLARE_SIMD_CLAUSES): Or in OMP_CLAUSE_INBRANCH and
475         OMP_CLAUSE_NOTINBRANCH.
476         (OMP_TARGET_CLAUSES, OMP_TARGET_DATA_CLAUSES,
477         OMP_TARGET_UPDATE_CLAUSES, OMP_TEAMS_CLAUSES,
478         OMP_DISTRIBUTE_CLAUSES): Define.
479         (match_omp): New function.
480         (gfc_match_omp_do, gfc_match_omp_do_simd, gfc_match_omp_parallel,
481         gfc_match_omp_parallel_do, gfc_match_omp_parallel_do_simd,
482         gfc_match_omp_parallel_sections, gfc_match_omp_parallel_workshare,
483         gfc_match_omp_sections, gfc_match_omp_simd, gfc_match_omp_single,
484         gfc_match_omp_task): Rewritten using match_omp.
485         (gfc_match_omp_threadprivate, gfc_match_omp_declare_reduction):
486         Diagnose if the directives are followed by unexpected junk.
487         (gfc_match_omp_distribute, gfc_match_omp_distribute_parallel_do,
488         gfc_match_omp_distribute_parallel_do_simd,
489         gfc_match_omp_distrbute_simd, gfc_match_omp_declare_target,
490         gfc_match_omp_target, gfc_match_omp_target_data,
491         gfc_match_omp_target_teams, gfc_match_omp_target_teams_distribute,
492         gfc_match_omp_target_teams_distribute_parallel_do,
493         gfc_match_omp_target_teams_distribute_parallel_do_simd,
494         gfc_match_omp_target_teams_distrbute_simd, gfc_match_omp_target_update,
495         gfc_match_omp_teams, gfc_match_omp_teams_distribute,
496         gfc_match_omp_teams_distribute_parallel_do,
497         gfc_match_omp_teams_distribute_parallel_do_simd,
498         gfc_match_omp_teams_distrbute_simd): New functions.
499         * openmp.c (resolve_omp_clauses): Adjust for
500         OMP_LIST_DEPEND_{IN,OUT} being changed to OMP_LIST_DEPEND.  Handle
501         OMP_LIST_MAP, OMP_LIST_FROM, OMP_LIST_TO, num_teams, device,
502         dist_chunk_size and thread_limit.
503         (gfc_resolve_omp_parallel_blocks): Only put sharing clauses into
504         ctx.sharing_clauses.  Call gfc_resolve_omp_do_blocks for various
505         new EXEC_OMP_* codes.
506         (resolve_omp_do): Handle various new EXEC_OMP_* codes.
507         (gfc_resolve_omp_directive): Likewise.
508         (gfc_resolve_omp_declare_simd): Add missing space to diagnostics.
509         * parse.c (decode_omp_directive): Handle parsing of OpenMP 4.0
510         offloading related directives.
511         (case_executable): Add ST_OMP_TARGET_UPDATE.
512         (case_exec_markers): Add ST_OMP_TARGET*, ST_OMP_TEAMS*,
513         ST_OMP_DISTRIBUTE*.
514         (case_decl): Add ST_OMP_DECLARE_TARGET.
515         (gfc_ascii_statement): Handle new ST_OMP_* codes.
516         (parse_omp_do): Handle various new ST_OMP_* codes.
517         (parse_executable): Likewise.
518         * resolve.c (gfc_resolve_blocks): Handle various new EXEC_OMP_*
519         codes.
520         (resolve_code): Likewise.
521         (resolve_symbol): Change that !$OMP DECLARE TARGET variables
522         are saved.
523         * st.c (gfc_free_statement): Handle various new EXEC_OMP_* codes.
524         * symbol.c (check_conflict): Check omp_declare_target conflicts.
525         (gfc_add_omp_declare_target): New function.
526         (gfc_copy_attr): Copy omp_declare_target.
527         * trans.c (trans_code): Handle various new EXEC_OMP_* codes.
528         * trans-common.c (build_common_decl): Add "omp declare target"
529         attribute if needed.
530         * trans-decl.c (add_attributes_to_decl): Likewise.
531         * trans.h (gfc_omp_finish_clause): New prototype.
532         * trans-openmp.c (gfc_omp_finish_clause): New function.
533         (gfc_trans_omp_reduction_list): Adjust for rop being renamed
534         to u.reduction_op.
535         (gfc_trans_omp_clauses): Adjust for OMP_LIST_DEPEND_{IN,OUT}
536         change to OMP_LIST_DEPEND and fix up depend handling.
537         Handle OMP_LIST_MAP, OMP_LIST_TO, OMP_LIST_FROM, num_teams,
538         thread_limit, device, dist_chunk_size and dist_sched_kind.
539         (gfc_trans_omp_do): Handle EXEC_OMP_DISTRIBUTE.
540         (GFC_OMP_SPLIT_DISTRIBUTE, GFC_OMP_SPLIT_TEAMS,
541         GFC_OMP_SPLIT_TARGET, GFC_OMP_SPLIT_NUM, GFC_OMP_MASK_DISTRIBUTE,
542         GFC_OMP_MASK_TEAMS, GFC_OMP_MASK_TARGET, GFC_OMP_MASK_NUM): New.
543         (gfc_split_omp_clauses): Handle splitting of clauses for new
544         EXEC_OMP_* codes.
545         (gfc_trans_omp_do_simd): Add pblock argument, adjust for being
546         callable for combined constructs.
547         (gfc_trans_omp_parallel_do, gfc_trans_omp_parallel_do_simd): Likewise.
548         (gfc_trans_omp_distribute, gfc_trans_omp_teams,
549         gfc_trans_omp_target, gfc_trans_omp_target_data,
550         gfc_trans_omp_target_update): New functions.
551         (gfc_trans_omp_directive): Adjust gfc_trans_omp_* callers, handle
552         new EXEC_OMP_* codes.
553
554 2014-06-18  Tobias Burnus  <burnus@net-b.de>
555
556         PR fortran/61126
557         * invoke.texi (-Wunused-parameter): Make clearer when
558         -Wextra implies this option.
559
560 2014-06-18  Manuel López-Ibáñez  <manu@gcc.gnu.org>
561
562         PR fortran/61126
563         * options.c (gfc_handle_option): Remove call to
564         handle_generated_option.
565
566 2014-06-17  Tobias Burnus  <burnus@net-b.de>
567
568         * check.c (gfc_check_atomic, gfc_check_atomic_def):
569         Use argument for GFC_ISYM_CAF_GET.
570         * resolve.c (resolve_variable): Enable CAF_GET insertion.
571         (resolve_lock_unlock): Remove GFC_ISYM_CAF_GET.
572         (resolve_ordinary_assign): Enable CAF_SEND insertion.
573         * trans-const.c (gfc_build_string_const,
574         gfc_build_wide_string_const): Set TYPE_STRING_FLAG.
575         * trans-decl.c (gfor_fndecl_caf_get, gfor_fndecl_caf_send,
576         gfor_fndecl_caf_sendget): New global variables.
577         (gfc_build_builtin_function_decls): Initialize them;
578         update co_min/max/sum initialization.
579         * trans-expr.c (gfc_get_tree_for_caf_expr): Renamed from
580         get_tree_for_caf_expr and removed static.
581         (gfc_conv_procedure_call): Update call.
582         * trans-intrinsic.c (caf_get_image_index,
583         conv_caf_vector_subscript_elem, conv_caf_vector_subscript,
584         get_caf_token_offset, gfc_conv_intrinsic_caf_get,
585         conv_caf_send): New.
586         (gfc_conv_intrinsic_function, gfc_conv_intrinsic_subroutine,
587         gfc_walk_intrinsic_function): Handle CAF_GET and CAF_SEND.
588         (conv_co_minmaxsum): Update call for remove unused vector
589         subscript.
590         (conv_intrinsic_atomic_def, conv_intrinsic_atomic_ref):
591         Skip a CAF_GET of the argument.
592         * trans-types.c (gfc_get_caf_vector_type): New.
593         * trans-types.h (gfc_get_caf_vector_type): New.
594         * trans.h (gfor_fndecl_caf_get, gfor_fndecl_caf_send,
595         gfor_fndecl_caf_sendget): New global variables.
596         (gfc_get_tree_for_caf_expr): New prototypes.
597
598 2014-06-15  Jan Hubicka  <hubicka@ucw.cz>
599
600         * trans-common.c (build_common_decl): Use
601         set_decl_tls_model.
602         * trans-decl.c (gfc_finish_var_decl): Likewise.
603         (get_proc_pointer_decl): Likewise.
604
605 2014-06-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
606
607         PR fortran/28484
608         PR fortran/61429
609         * check.c (gfc_check_system_clock): Improve checking of arguments.
610         * intrinsic.texi: Update doc of SYSTEM_CLOCK.
611         * iresolve.c (gfc_resolve_system_clock): Choose library function
612         used depending on argument kinds.
613         * trans-decl.c (gfc_build_intrinsic_function_decls): Build
614         decls for system_clock_4 and system_clock_8.
615         * trans-intrinsic.c (conv_intrinsic_system_clock): New function.
616         (gfc_conv_intrinsic_subroutine): Call conv_intrinsic_system_clock.
617         * trans.h (gfor_fndecl_system_clock4, gfor_fndecl_system_clock8):
618         New variables.
619
620 2014-06-12  Tobias Burnus  <burnus@net-b.de>
621
622         * gfortran.h (gfc_copy_formal_args_intr): Update prototype.
623         * symbol.c (gfc_copy_formal_args_intr): Handle the case
624         that absent optional arguments should be ignored.
625         * trans-intrinsic.c (gfc_get_symbol_for_expr): Ditto.
626         (gfc_conv_intrinsic_funcall,
627         conv_generic_with_optional_char_arg): Update call.
628         * resolve.c (gfc_resolve_intrinsic): Ditto.
629
630 2014-06-10  Dominique d'Humieres <dominiq@lps.ens.fr>
631             Mikael Morin <mikael@gcc.gnu.org>
632
633         PR fortran/41936
634         * trans-expr.c (gfc_conv_expr_reference): Deallocate array
635         components.
636
637 2014-06-10  Jakub Jelinek  <jakub@redhat.com>
638
639         PR fortran/60928
640         * f95-lang.c (gfc_init_builtin_functions): Handle -fopenmp-simd
641         like -fopenmp.
642         * openmp.c (resolve_omp_clauses): Remove allocatable components
643         diagnostics.  Add associate-name and intent(in) pointer
644         diagnostics for various clauses, diagnose procedure pointers in
645         reduction clause.
646         * parse.c (match_word_omp_simd): New function.
647         (matchs, matcho): New macros.
648         (decode_omp_directive): Change match macros to either matchs
649         or matcho.  Handle -fopenmp-simd.
650         (next_free, next_fixed): Handle -fopenmp-simd like -fopenmp.
651         * scanner.c (skip_free_comments, skip_fixed_comments, include_line):
652         Likewise.
653         * trans-array.c (get_full_array_size): Rename to...
654         (gfc_full_array_size): ... this.  No longer static.
655         (duplicate_allocatable): Adjust caller.  Add NO_MEMCPY argument
656         and handle it.
657         (gfc_duplicate_allocatable, gfc_copy_allocatable_data): Adjust
658         duplicate_allocatable callers.
659         (gfc_duplicate_allocatable_nocopy): New function.
660         (structure_alloc_comps): Adjust g*_full_array_size and
661         duplicate_allocatable caller.
662         * trans-array.h (gfc_full_array_size,
663         gfc_duplicate_allocatable_nocopy): New prototypes.
664         * trans-common.c (create_common): Call gfc_finish_decl_attrs.
665         * trans-decl.c (gfc_finish_decl_attrs): New function.
666         (gfc_finish_var_decl, create_function_arglist,
667         gfc_get_fake_result_decl): Call it.
668         (gfc_allocate_lang_decl): If DECL_LANG_SPECIFIC is already allocated,
669         don't allocate it again.
670         (gfc_get_symbol_decl): Set GFC_DECL_ASSOCIATE_VAR_P on
671         associate-names.
672         * trans.h (gfc_finish_decl_attrs): New prototype.
673         (struct lang_decl): Add scalar_allocatable and scalar_pointer
674         bitfields.
675         (GFC_DECL_SCALAR_ALLOCATABLE, GFC_DECL_SCALAR_POINTER,
676         GFC_DECL_GET_SCALAR_ALLOCATABLE, GFC_DECL_GET_SCALAR_POINTER,
677         GFC_DECL_ASSOCIATE_VAR_P): Define.
678         (GFC_POINTER_TYPE_P): Remove.
679         * trans-openmp.c (gfc_omp_privatize_by_reference): Don't check
680         GFC_POINTER_TYPE_P, instead test GFC_DECL_GET_SCALAR_ALLOCATABLE,
681         GFC_DECL_GET_SCALAR_POINTER or GFC_DECL_CRAY_POINTEE on decl.
682         (gfc_omp_predetermined_sharing): Associate-names are predetermined.
683         (enum walk_alloc_comps): New.
684         (gfc_has_alloc_comps, gfc_omp_unshare_expr_r, gfc_omp_unshare_expr,
685         gfc_walk_alloc_comps): New functions.
686         (gfc_omp_private_outer_ref): Return true for scalar allocatables or
687         decls with allocatable components.
688         (gfc_omp_clause_default_ctor, gfc_omp_clause_copy_ctor,
689         gfc_omp_clause_assign_op, gfc_omp_clause_dtor): Fix up handling of
690         allocatables, handle also OMP_CLAUSE_REDUCTION, handle scalar
691         allocatables and decls with allocatable components.
692         (gfc_trans_omp_array_reduction_or_udr): Don't handle allocatable
693         arrays here.
694         (gfc_trans_omp_reduction_list): Call
695         gfc_trans_omp_array_reduction_or_udr even for allocatable scalars.
696         (gfc_trans_omp_do_simd): If -fno-openmp, just expand it as OMP_SIMD.
697         (gfc_trans_omp_parallel_do_simd): Likewise.
698         * trans-types.c (gfc_sym_type): Don't set GFC_POINTER_TYPE_P.
699         (gfc_get_derived_type): Call gfc_finish_decl_attrs.
700
701 2014-06-09  Paul Thomas  <pault@gcc.gnu.org>
702
703         PR fortran/61406
704         * trans-stmt.c (trans_associate_var): Check that array
705         constructors are constant for direct reference.
706
707 2014-06-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
708
709         PR fortran/36096
710         * intrinsic.texi: Fix documentation of BESSEL_J0, BESSEL_J1,
711         BESSEL_Y0, and BESSEL_Y1.
712
713 2014-06-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
714
715         PR fortran/45187
716         * trans-decl.c (gfc_create_module_variable): Don't create
717         Cray-pointee decls twice.
718
719 2014-06-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
720
721         * io.c (resolve_tag): Warn on non-default kind for NUMBER,
722         NEXTREC, RECL, NAMED, OPENED and PENDING I/O specifiers.
723
724 2014-06-06  Jakub Jelinek  <jakub@redhat.com>
725
726         * dump-parse-tree.c (show_omp_namelist): Dump reduction
727         id in each list item.
728         (show_omp_node): Only handle OMP_LIST_REDUCTION, not
729         OMP_LIST_REDUCTION_FIRST .. OMP_LIST_REDUCTION_LAST.  Don't
730         dump reduction id here.
731         * frontend-passes.c (dummy_code_callback): Renamed to...
732         (gfc_dummy_code_callback): ... this.  No longer static.
733         (optimize_reduction): Use gfc_dummy_code_callback instead of
734         dummy_code_callback.
735         * gfortran.h (gfc_statement): Add ST_OMP_DECLARE_REDUCTION.
736         (symbol_attribute): Add omp_udr_artificial_var bitfield.
737         (gfc_omp_reduction_op): New enum.
738         (gfc_omp_namelist): Add rop and udr fields.
739         (OMP_LIST_PLUS, OMP_LIST_REDUCTION_FIRST, OMP_LIST_MULT,
740         OMP_LIST_SUB, OMP_LIST_AND, OMP_LIST_OR, OMP_LIST_EQV,
741         OMP_LIST_NEQV, OMP_LIST_MAX, OMP_LIST_MIN, OMP_LIST_IAND,
742         OMP_LIST_IOR, OMP_LIST_IEOR, OMP_LIST_REDUCTION_LAST): Removed.
743         (OMP_LIST_REDUCTION): New.
744         (gfc_omp_udr): New type.
745         (gfc_get_omp_udr): Define.
746         (gfc_symtree): Add n.omp_udr field.
747         (gfc_namespace): Add omp_udr_root field, add omp_udr_ns bitfield.
748         (gfc_free_omp_udr, gfc_omp_udr_find, gfc_resolve_omp_udrs,
749         gfc_dummy_code_callback): New prototypes.
750         * match.h (gfc_match_omp_declare_reduction): New prototype.
751         * module.c (MOD_VERSION): Increase to 13.
752         (omp_declare_reduction_stmt): New array.
753         (mio_omp_udr_expr, write_omp_udr, write_omp_udrs, load_omp_udrs):
754         New functions.
755         (read_module): Read OpenMP user defined reductions.
756         (write_module): Write OpenMP user defined reductions.
757         * openmp.c: Include arith.h.
758         (gfc_free_omp_udr, gfc_find_omp_udr): New functions.
759         (gfc_match_omp_clauses): Handle user defined reductions.
760         Store reduction kind into gfc_omp_namelist instead of using
761         several OMP_LIST_* entries.
762         (match_udr_expr, gfc_omp_udr_predef, gfc_omp_udr_find,
763         gfc_match_omp_declare_reduction): New functions.
764         (resolve_omp_clauses): Adjust for reduction clauses being only
765         in OMP_LIST_REDUCTION list.  Diagnose missing UDRs.
766         (struct omp_udr_callback_data): New type.
767         (omp_udr_callback, gfc_resolve_omp_udr, gfc_resolve_omp_udrs): New
768         functions.
769         * parse.c (decode_omp_directive): Handle !$omp declare reduction.
770         (case_decl): Add ST_OMP_DECLARE_REDUCTION.
771         (gfc_ascii_statement): Print ST_OMP_DECLARE_REDUCTION.
772         * resolve.c (resolve_fl_variable): Allow len=: or len=* on
773         sym->attr.omp_udr_artificial_var symbols.
774         (resolve_types): Call gfc_resolve_omp_udrs.
775         * symbol.c (gfc_get_uop): If gfc_current_ns->omp_udr_ns,
776         use parent ns instead of gfc_current_ns.
777         (gfc_get_sym_tree): Don't insert symbols into
778         namespaces with omp_udr_ns set.
779         (free_omp_udr_tree): New function.
780         (gfc_free_namespace): Call it.
781         * trans-openmp.c (struct omp_udr_find_orig_data): New type.
782         (omp_udr_find_orig, gfc_trans_omp_udr_expr): New functions.
783         (gfc_trans_omp_array_reduction): Renamed to...
784         (gfc_trans_omp_array_reduction_or_udr): ... this.  Remove SYM
785         argument, instead pass gfc_omp_namelist pointer N.  Handle
786         user defined reductions.
787         (gfc_trans_omp_reduction_list): Remove REDUCTION_CODE argument.
788         Handle user defined reductions and reduction ops in gfc_omp_namelist.
789         (gfc_trans_omp_clauses): Adjust for just a single OMP_LIST_REDUCTION
790         list.
791         (gfc_split_omp_clauses): Likewise.
792
793 2014-06-05  Richard Biener  <rguenther@suse.de>
794
795         PR fortran/61418
796         * gfortranspec.c (spec_file): Remove.
797         (find_spec_file): Likewise.
798         (lang_specific_driver): Do not look for specs file in -L
799         or append -specs command line argument.
800         (lang_specific_pre_link): Always %:include libgfortran.spec.
801
802 2014-06-02  Andrew MacLeod  <amacleod@redhat.com>
803
804         * fortran/trans.c (trans_runtime_error_vararg): Call
805         fold_build_call_array_loc instead of fold_builtin_call_array.
806
807 2014-06-02  Bernd Schmidt  <bernds@codesourcery.com>
808
809         * trans-decl.c (gfc_build_builtin_function_decls): Correct number of
810         arguments to caf_init.
811
812 2014-05-26  Tobias Burnus  <burnus@net-b.de>
813
814         * gfortran.texi (Project Status): Fix broken link.
815
816 2014-05-26  Janne Blomqvist  <jb@gcc.gnu.org>
817
818         PR libfortran/61310
819         * intrinsics.texi (CTIME): Remove mention of locale-dependent
820         behavior.
821
822 2014-05-26  Tobias Burnus  <burnus@net-b.de>
823
824         PR fortran/55117
825         * trans-io.c (nml_full_name, transfer_namelist_element): Insert
826         a '+' rather then '%' to differentiate namelist variable names
827         that are based on extended derived types.
828
829 2014-05-25  Tobias Burnus  <burnus@net-b.de>
830
831         * check.c (gfc_check_num_images): New.
832         (gfc_check_this_image): Handle distance argument.
833         * intrinsic.c (add_functions): Update this_image and num_images
834         for new distance and failed arguments.
835         * intrinsic.texi (THIS_IMAGE, NUM_IMAGES): Document the new
836         arguments.
837         * intrinsic.h (gfc_check_num_images): New.
838         (gfc_check_this_image, gfc_simplify_num_images,
839         gfc_simplify_this_image, gfc_resolve_this_image): Update prototype.
840         * iresolve.c (gfc_resolve_this_image): Handle distance argument.
841         * simplify.c (gfc_simplify_num_images, gfc_simplify_this_image):
842         Handle new arguments.
843         * trans-intrinsic.c (trans_this_image, trans_num_images): Ditto.
844         (gfc_conv_intrinsic_function): Update trans_num_images call.
845
846 2014-05-23  Tobias Burnus  <burnus@net-b.de>
847
848         * gfc-internals.texi: Change URLs to HTTPS; fix broken links.
849         * gfortran.texi: Ditto.
850
851 2014-05-22  Thomas Schwinge  <thomas@codesourcery.com>
852
853         * f95-lang.c (DEF_FUNCTION_TYPE_0, DEF_FUNCTION_TYPE_6)
854         (DEF_FUNCTION_TYPE_7, DEF_FUNCTION_TYPE_8)
855         (DEF_FUNCTION_TYPE_VAR_5): Cosmetic fixes.
856         * types.def: Simplify examples for DEF_FUNCTION_TYPE_*.
857
858 2014-05-17  Trevor Saunders  <tsaunders@mozilla.com>
859
860         * f95-lang.c (pushlevel): Adjust.
861         * trans-decl.c (gfc_allocate_lang_decl): Adjust.
862         (gfc_find_module): Likewise.
863         * trans-types.c (gfc_get_nodesc_array_type): Likewise.
864         (gfc_get_array_type_bounds): Likewise.
865         (gfc_nonrestricted_type): Likewise.
866         * trans.h: Don't use variable_size gty attribute.
867
868 2014-05-17  Dominique d'Humieres <dominiq@lps.ens.fr>
869
870         * check.c (gfc_check_fn_rc2008): move "argument" to the right
871         place.
872
873 2014-05-12  Tobias Burnus  <burnus@net-b.de>
874
875         PR fortran/60127
876         * openmp.c (resolve_omp_do): Reject do concurrent loops.
877
878 2014-05-12  Thomas Koenig  <tkoenig@gcc.gnu.org>
879
880         PR fortran/60834
881         * frontend-passes.c (in_assoc_list):  New variable.
882         (optimize_namespace):  Initialize in_assoc_list
883         (combine_array_constructor): Don't try to combine
884         assoc lists.
885         (gfc_code_walker):  Keep track of in_assoc_list.
886
887 2014-05-11  Jakub Jelinek  <jakub@redhat.com>
888
889         * gfortran.h (gfc_statement): Add ST_OMP_CANCEL,
890         ST_OMP_CANCELLATION_POINT, ST_OMP_TASKGROUP, ST_OMP_END_TASKGROUP,
891         ST_OMP_SIMD, ST_OMP_END_SIMD, ST_OMP_DO_SIMD, ST_OMP_END_DO_SIMD,
892         ST_OMP_PARALLEL_DO_SIMD, ST_OMP_END_PARALLEL_DO_SIMD and
893         ST_OMP_DECLARE_SIMD.
894         (gfc_omp_namelist): New typedef.
895         (gfc_get_omp_namelist): Define.
896         (OMP_LIST_UNIFORM, OMP_LIST_ALIGNED, OMP_LIST_LINEAR,
897         OMP_LIST_DEPEND_IN, OMP_LIST_DEPEND_OUT): New clause list kinds.
898         (gfc_omp_proc_bind_kind, gfc_omp_cancel_kind): New enums.
899         (gfc_omp_clauses): Change type of lists to gfc_omp_namelist *.
900         Add inbranch, notinbranch, cancel, proc_bind, safelen_expr and
901         simdlen_expr fields.
902         (gfc_omp_declare_simd): New typedef.
903         (gfc_get_omp_declare_simd): Define.
904         (gfc_namespace): Add omp_declare_simd field.
905         (gfc_exec_op): Add EXEC_OMP_CANCEL, EXEC_OMP_CANCELLATION_POINT,
906         EXEC_OMP_TASKGROUP, EXEC_OMP_SIMD, EXEC_OMP_DO_SIMD and
907         EXEC_OMP_PARALLEL_DO_SIMD.
908         (gfc_omp_atomic_op): Add GFC_OMP_ATOMIC_MASK, GFC_OMP_ATOMIC_SEQ_CST
909         and GFC_OMP_ATOMIC_SWAP.
910         (gfc_code): Change type of omp_namelist field to gfc_omp_namelist *.
911         (gfc_free_omp_namelist, gfc_free_omp_declare_simd,
912         gfc_free_omp_declare_simd_list, gfc_resolve_omp_declare_simd): New
913         prototypes.
914         * trans-stmt.h (gfc_trans_omp_declare_simd): New prototype.
915         * symbol.c (gfc_free_namespace): Call gfc_free_omp_declare_simd.
916         * openmp.c (gfc_free_omp_clauses): Free safelen_expr and
917         simdlen_expr.  Use gfc_free_omp_namelist instead of
918         gfc_free_namelist.
919         (gfc_free_omp_declare_simd, gfc_free_omp_declare_simd_list): New
920         functions.
921         (gfc_match_omp_variable_list): Add end_colon, headp and
922         allow_sections arguments.  Handle parsing of array sections.
923         Use *omp_namelist* instead of *namelist* data structure and
924         functions/macros.  Allow termination at : character.
925         (OMP_CLAUSE_ALIGNED, OMP_CLAUSE_DEPEND, OMP_CLAUSE_INBRANCH,
926         OMP_CLAUSE_LINEAR, OMP_CLAUSE_NOTINBRANCH, OMP_CLAUSE_PROC_BIND,
927         OMP_CLAUSE_SAFELEN, OMP_CLAUSE_SIMDLEN, OMP_CLAUSE_UNIFORM): Define.
928         (gfc_match_omp_clauses): Change first and needs_space variables
929         into arguments with default values.  Parse inbranch, notinbranch,
930         proc_bind, safelen, simdlen, uniform, linear, aligned and
931         depend clauses.
932         (OMP_PARALLEL_CLAUSES): Add OMP_CLAUSE_PROC_BIND.
933         (OMP_DECLARE_SIMD_CLAUSES, OMP_SIMD_CLAUSES): Define.
934         (OMP_TASK_CLAUSES): Add OMP_CLAUSE_DEPEND.
935         (gfc_match_omp_do_simd): New function.
936         (gfc_match_omp_flush): Use *omp_namelist* instead of *namelist*
937         data structure and functions/macros.
938         (gfc_match_omp_simd, gfc_match_omp_declare_simd,
939         gfc_match_omp_parallel_do_simd): New functions.
940         (gfc_match_omp_atomic): Handle seq_cst clause.  Handle atomic swap.
941         (gfc_match_omp_taskgroup, gfc_match_omp_cancel_kind,
942         gfc_match_omp_cancel, gfc_match_omp_cancellation_point): New
943         functions.
944         (resolve_omp_clauses): Add where, omp_clauses and ns arguments.
945         Use *omp_namelist* instead of *namelist* data structure and
946         functions/macros.  Resolve uniform, aligned, linear, depend,
947         safelen and simdlen clauses.
948         (resolve_omp_atomic): Adjust for GFC_OMP_ATOMIC_{MASK,SEQ_CST,SWAP}
949         addition, recognize atomic swap.
950         (gfc_resolve_omp_parallel_blocks): Use gfc_omp_namelist instead
951         of gfc_namelist.  Handle EXEC_OMP_PARALLEL_DO_SIMD the same as
952         EXEC_OMP_PARALLEL_DO.
953         (gfc_resolve_do_iterator): Use *omp_namelist* instead of *namelist*
954         data structure and functions/macros.
955         (resolve_omp_do): Likewise.  Handle EXEC_OMP_SIMD, EXEC_OMP_DO_SIMD,
956         EXEC_OMP_PARALLEL_DO_SIMD.
957         (gfc_resolve_omp_directive): Handle EXEC_OMP_SIMD, EXEC_OMP_DO_SIMD,
958         EXEC_OMP_PARALLEL_DO_SIMD and EXEC_OMP_CANCEL.  Adjust
959         resolve_omp_clauses caller.
960         (gfc_resolve_omp_declare_simd): New function.
961         * parse.c (decode_omp_directive): Parse cancellation point, cancel,
962         declare simd, end do simd, end simd, end parallel do simd,
963         end taskgroup, parallel do simd, simd and taskgroup directives.
964         (case_executable): Add ST_OMP_CANCEL and ST_OMP_CANCELLATION_POINT.
965         (case_exec_markers): Add ST_OMP_TASKGROUP, case ST_OMP_SIMD,
966         ST_OMP_DO_SIMD and ST_OMP_PARALLEL_DO_SIMD.
967         (case_decl): Add ST_OMP_DECLARE_SIMD.
968         (gfc_ascii_statement): Handle ST_OMP_CANCEL,
969         ST_OMP_CANCELLATION_POINT, ST_OMP_TASKGROUP, ST_OMP_END_TASKGROUP,
970         ST_OMP_SIMD, ST_OMP_END_SIMD, ST_OMP_DO_SIMD, ST_OMP_END_DO_SIMD,
971         ST_OMP_PARALLEL_DO_SIMD, ST_OMP_END_PARALLEL_DO_SIMD and
972         ST_OMP_DECLARE_SIMD.
973         (parse_omp_do): Handle ST_OMP_SIMD, ST_OMP_DO_SIMD and
974         ST_OMP_PARALLEL_DO_SIMD.
975         (parse_omp_atomic): Adjust for GFC_OMP_ATOMIC_* additions.
976         (parse_omp_structured_block): Handle ST_OMP_TASKGROUP and
977         ST_OMP_PARALLEL_DO_SIMD.
978         (parse_executable): Handle ST_OMP_SIMD, ST_OMP_DO_SIMD,
979         ST_OMP_PARALLEL_DO_SIMD and ST_OMP_TASKGROUP.
980         * trans-decl.c (gfc_get_extern_function_decl,
981         gfc_create_function_decl): Call gfc_trans_omp_declare_simd if
982         needed.
983         * frontend-passes.c (gfc_code_walker): Handle EXEC_OMP_SIMD,
984         EXEC_OMP_DO_SIMD and EXEC_OMP_PARALLEL_DO_SIMD.  Walk
985         safelen_expr and simdlen_expr.  Walk expressions in gfc_omp_namelist
986         of depend, aligned and linear clauses.
987         * match.c (match_exit_cycle): Handle EXEC_OMP_SIMD, EXEC_OMP_DO_SIMD
988         and EXEC_OMP_PARALLEL_DO_SIMD.
989         (gfc_free_omp_namelist): New function.
990         * dump-parse-tree.c (show_namelist): Removed.
991         (show_omp_namelist): New function.
992         (show_omp_node): Handle OpenMP 4.0 additions.
993         (show_code_node): Handle EXEC_OMP_CANCEL, EXEC_OMP_CANCELLATION_POINT,
994         EXEC_OMP_DO_SIMD, EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and
995         EXEC_OMP_TASKGROUP.
996         * match.h (gfc_match_omp_cancel, gfc_match_omp_cancellation_point,
997         gfc_match_omp_declare_simd, gfc_match_omp_do_simd,
998         gfc_match_omp_parallel_do_simd, gfc_match_omp_simd,
999         gfc_match_omp_taskgroup): New prototypes.
1000         * trans-openmp.c (gfc_trans_omp_variable): Add declare_simd
1001         argument, handle it.  Allow current_function_decl to be NULL.
1002         (gfc_trans_omp_variable_list): Add declare_simd argument, pass
1003         it through to gfc_trans_omp_variable and disregard whether
1004         sym is referenced if declare_simd is true.  Work on gfc_omp_namelist
1005         instead of gfc_namelist.
1006         (gfc_trans_omp_reduction_list): Work on gfc_omp_namelist instead of
1007         gfc_namelist.  Adjust gfc_trans_omp_variable caller.
1008         (gfc_trans_omp_clauses): Add declare_simd argument, pass it through
1009         to gfc_trans_omp_variable{,_list} callers.  Work on gfc_omp_namelist
1010         instead of gfc_namelist.  Handle inbranch, notinbranch, safelen,
1011         simdlen, depend, uniform, linear, proc_bind and aligned clauses.
1012         Handle cancel kind.
1013         (gfc_trans_omp_atomic): Handle seq_cst clause, handle atomic swap,
1014         adjust for GFC_OMP_ATOMIC_* changes.
1015         (gfc_trans_omp_cancel, gfc_trans_omp_cancellation_point): New
1016         functions.
1017         (gfc_trans_omp_do): Add op argument, handle simd translation into
1018         generic.
1019         (GFC_OMP_SPLIT_SIMD, GFC_OMP_SPLIT_DO, GFC_OMP_SPLIT_PARALLEL,
1020         GFC_OMP_SPLIT_NUM, GFC_OMP_MASK_SIMD, GFC_OMP_MASK_DO,
1021         GFC_OMP_MASK_PARALLEL): New.
1022         (gfc_split_omp_clauses, gfc_trans_omp_do_simd): New functions.
1023         (gfc_trans_omp_parallel_do): Rework to use gfc_split_omp_clauses.
1024         (gfc_trans_omp_parallel_do_simd, gfc_trans_omp_taskgroup): New
1025         functions.
1026         (gfc_trans_omp_directive): Handle EXEC_OMP_CANCEL,
1027         EXEC_OMP_CANCELLATION_POINT, EXEC_OMP_DO_SIMD,
1028         EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and EXEC_OMP_TASKGROUP.
1029         Adjust gfc_trans_omp_do caller.
1030         (gfc_trans_omp_declare_simd): New function.
1031         * st.c (gfc_free_statement): Handle EXEC_OMP_CANCEL,
1032         EXEC_OMP_CANCELLATION_POINT, EXEC_OMP_DO_SIMD,
1033         EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and EXEC_OMP_TASKGROUP.
1034         For EXEC_OMP_FLUSH call gfc_free_omp_namelist instead of
1035         gfc_free_namelist.
1036         * module.c (omp_declare_simd_clauses): New variable.
1037         (mio_omp_declare_simd): New function.
1038         (mio_symbol): Call it.
1039         * trans.c (trans_code): Handle EXEC_OMP_CANCEL,
1040         EXEC_OMP_CANCELLATION_POINT, EXEC_OMP_DO_SIMD,
1041         EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and EXEC_OMP_TASKGROUP.
1042         * resolve.c (gfc_resolve_blocks): Handle EXEC_OMP_DO_SIMD,
1043         EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and EXEC_OMP_TASKGROUP.
1044         (resolve_code): Handle EXEC_OMP_CANCEL,
1045         EXEC_OMP_CANCELLATION_POINT, EXEC_OMP_DO_SIMD,
1046         EXEC_OMP_PARALLEL_DO_SIMD, EXEC_OMP_SIMD and EXEC_OMP_TASKGROUP.
1047         (resolve_types): Call gfc_resolve_omp_declare_simd.
1048
1049 2014-05-11  Tobias Burnus  <burnus@net-b.de>
1050
1051         * trans-intrinsic.c (gfc_build_builtin_function_decls):
1052         Change type of second argument to int.
1053
1054 2014-05-09  Mike Stump  <mikestump@comcast.net>
1055
1056         PR fortran/61109
1057         * trans-array.c (gfc_conv_array_initializer): Fix wide-int
1058         conversion bug.
1059
1060 2014-05-08  Tobias Burnus  <burnus@net-b.de>
1061
1062         * gfortran.h (gfc_isym_id): Add GFC_ISYM_CAF_GET
1063         and GFC_ISYM_CAF_SEND.
1064         * intrinsic.c (add_functions): Add only internally
1065         accessible caf_get and caf_send functions.
1066         * resolve.c (add_caf_get_intrinsic,
1067         remove_caf_get_intrinsic): New functions.
1068         (resolve_variable): Resolve expression rank and
1069         prepare for add_caf_get_intrinsic call.
1070         (gfc_resolve_expr): For variables, remove rank
1071         resolution.
1072         (resolve_ordinary_assign): Prepare call to
1073         GFC_ISYM_CAF_SEND.
1074         (resolve_code): Avoid call to GFC_ISYM_CAF_GET for
1075         the LHS of an assignment.
1076
1077 2014-05-08  Tobias Burnus  <burnus@net-b.de>
1078
1079         * trans-intrinsic.c (conv_co_minmaxsum): Change condition style.
1080
1081 2014-05-08  Tobias Burnus  <burnus@net-b.de>
1082
1083         * check.c (check_co_minmaxsum, gfc_check_co_minmax,
1084         gfc_check_co_sum): New.
1085         * error.c (gfc_notify_std): Update -std=f2008ts.
1086         * gfortran.h (gfc_isym_id): Add GFC_ISYM_CO_MAX,
1087         GFC_ISYM_CO_MIN, GFC_ISYM_CO_SUM.
1088         * intrinsic.h (gfc_check_co_minmax,
1089         gfc_check_co_sum): Declare.
1090         * intrinsic.c (add_subroutines): Add co_min, co_max
1091         and co_sum.
1092         (gfc_check_intrinsic_standard): Update text for
1093         -std=f2008ts.
1094         * intrinsic.texi (CO_MIN, CO_MAX, CO_SUM): Document
1095         them.
1096         * invoke.texi (-std=f2008ts): Update wording.
1097         * trans.h (gfor_fndecl_co_max,
1098         gfor_fndecl_co_min, gfor_fndecl_co_sum): Define.
1099         * trans-decl.c (gfor_fndecl_co_max,
1100         gfor_fndecl_co_min, gfor_fndecl_co_sum): Define.
1101         (gfc_build_builtin_function_decls): Assign to it.
1102         * trans-intrinsic.c (conv_co_minmaxsum): New.
1103         (gfc_conv_intrinsic_subroutine): Call it.
1104
1105 2014-05-06  Kenneth Zadeck  <zadeck@naturalbridge.com>
1106             Mike Stump  <mikestump@comcast.net>
1107             Richard Sandiford  <rdsandiford@googlemail.com>
1108
1109         * target-memory.c: Include wide-int.h.
1110         (gfc_interpret_logical): Use wide-int interfaces.
1111         * trans-array.c: Include wide-int.h.
1112         (gfc_conv_array_initializer): Use wide-int interfaces.
1113         * trans-const.c: Include wide-int.h.
1114         (gfc_conv_string_init): Use wide-int interfaces.
1115         (gfc_conv_mpz_to_tree): Likewise.
1116         (gfc_conv_tree_to_mpz): Likewise.
1117         * trans-decl.c (gfc_can_put_var_on_stack): Use tree_fits_uhwi_p.
1118         * trans-expr.c: Include wide-int.h.
1119         (gfc_conv_cst_int_power): Use wide-int interfaces.
1120         (gfc_string_to_single_character): Likewise.
1121         (gfc_optimize_len_trim): Likewise.
1122         * trans-intrinsic.c: Include wide-int.h.
1123         (trans_this_image): Use wide-int interfaces.
1124         (gfc_conv_intrinsic_bound): Likewise.
1125         (conv_intrinsic_cobound): Likewise.
1126         * trans-types.c (gfc_init_types): Likewise.
1127         (gfc_get_array_type_bounds): Pass an integer of the correct type
1128         instead of using integer_one_node.
1129
1130 2014-04-30  Tobias Burnus  <burnus@net-b.de>
1131
1132         * trans-decl.c (create_function_arglist): Add hidden coarray arguments
1133         also for polymorphic coarrays.
1134         * trans-expr.c (gfc_conv_procedure_call): Pass hidden coarray arguments
1135         also for polymorphic coarrays.
1136
1137 2014-04-30  Tobias Burnus  <burnus@net-b.de>
1138
1139         * resolve.c (resolve_function): Don't do
1140         assumed-size check for lcobound/ucobound.
1141         * trans-types.c (gfc_build_array_type): Only build an array
1142         descriptor with codimensions for allocatable coarrays.
1143
1144 2014-04-30  Tobias Burnus  <burnus@net-b.de>
1145
1146         * gfortran.h (gfc_init_coarray_decl): Remove.
1147         * parse.c (translate_all_program_units): Remove call to it.
1148         (gfc_parse_file): Update call.
1149         * trans.h (gfor_fndecl_caf_this_image,
1150         gfor_fndecl_caf_num_images): Add.
1151         (gfort_gvar_caf_num_images,
1152         gfort_gvar_caf_this_image): Remove.
1153         * trans-decl.c (gfor_fndecl_caf_this_image,
1154         gfor_fndecl_caf_num_images): Add.
1155         (gfort_gvar_caf_num_images,
1156         gfort_gvar_caf_this_image): Remove.
1157         (gfc_build_builtin_function_decls): Init new decl.
1158         (gfc_init_coarray_dec): Remove.
1159         (create_main_function): Change calls.
1160         * trans-intrinsic.c (trans_this_image, trans_image_index,
1161         conv_intrinsic_cobound): Generate call to new library function
1162         instead of to a static variable.
1163         * trans-stmt.c (gfc_trans_sync): Ditto.
1164
1165 2014-04-30  Tobias Burnus  <burnus@net-b.de>
1166
1167         * trans-expr.c (get_tree_for_caf_expr): Fix handling of polymorphic
1168         and derived-type coarrays.
1169
1170 2014-04-27  Thomas Koenig  <tkoenig@gcc.gnu.org>
1171
1172         PR fortran/59604
1173         PR fortran/58003
1174         * gfortran.h (gfc_convert_mpz_to_signed):  Add prototype.
1175         * arith.c (gfc_int2int):  Convert number to signed if
1176         arithmetic overflow is not checked.
1177         * simplify.c (convert_mpz_to_unsigned): Only trigger assert for
1178         size if range checking is in force.
1179         (convert_mpz_to_signed):  Make non-static, rename to
1180         (gfc_convert_mpz_to_signed).
1181         (simplify_dshift): Use gfc_convert_mpz_to_signed.
1182         (gfc_simplify_ibclr):  Likewise.
1183         (gfc_simplify_ibits):  Likewise.
1184         (gfc_simplify_ibset):  Likewise.
1185         (simplify_shift):  Likewise.
1186         (gfc_simplify_ishiftc):  Likewise.
1187         (gfc_simplify_maskr):  Likewise.
1188         (gfc_simplify_maskl):  Likewise.
1189
1190 2014-04-22  Tobias Burnus  <burnus@net-b.de>
1191
1192         PR fortran/60881
1193         * trans-expr.c (gfc_trans_subcomponent_assign): Fix handling
1194         of scalar coarrays.
1195
1196 2014-04-17  Jakub Jelinek  <jakub@redhat.com>
1197
1198         * trans-types.c (gfc_init_kinds): Make sure GET_MODE_BITSIZE
1199         argument is enum machine_mode.
1200
1201 2014-04-13  Paul Thomas  <pault@gcc.gnu.org>
1202
1203         PR fortran/58085
1204         PR fortran/60717
1205         * trans.h: Add 'use_offset' bitfield to gfc_se.
1206         * trans-array.c (gfc_conv_expr_descriptor): Use 'use_offset'
1207         as a trigger to unconditionally recalculate the offset for
1208         array slices and constant arrays.
1209         trans-expr.c (gfc_conv_intrinsic_to_class): Use it.
1210         trans-stmt.c (trans_associate_var): Ditto.
1211         (gfc_conv_procedure_call): Ditto.
1212
1213 2014-04-11  Tobias Burnus  <burnus@net-b.de>
1214
1215         PR fortran/58880
1216         PR fortran/60495
1217         * resolve.c (gfc_resolve_finalizers): Ensure that vtables
1218         and finalization wrappers are generated.
1219
1220 2014-04-11  Janne Blomqvist  <jb@gcc.gnu.org>
1221
1222         * intrinsic.texi (RANDOM_SEED): Improve example.
1223
1224 2014-04-10  Bernd Edlinger  <bernd.edlinger@hotmail.de>
1225
1226         * class.c (gfc_build_class_symbol): Append "_t" to target class
1227         names to make the generated type names unique.
1228
1229 2014-04-04  Bernd Edlinger  <bernd.edlinger@hotmail.de>
1230
1231         PR fortran/60191
1232         * trans-types.c (gfc_get_function_type): In case of recursion
1233         build a variadic function type with empty argument list instead of a
1234         stdarg-like function type with incomplete argument list.
1235
1236 2014-04-04  Tobias Burnus  <burnus@net-b.de>
1237
1238         * check.c (gfc_check_cmplx): Fix typo.
1239
1240 2014-03-28  Mikael Morin  <mikael@gcc.gnu.org>
1241             Tobias Burnus  <burnus@net-b.de>
1242
1243         PR fortran/60576
1244         * trans-expr.c (gfc_conv_derived_to_class): Avoid
1245         generation of out-of-bounds range expr.
1246
1247 2014-03-28  Mikael Morin  <mikael@gcc.gnu.org>
1248
1249         PR fortran/60677
1250         * trans-intrinsic.c (gfc_conv_intrinsic_ichar): Enlarge argument
1251         list buffer.
1252
1253 2014-03-27  Thomas Koenig  <tkoenig@gcc.gnu.org>
1254
1255         PR fortran/60522
1256         * frontend-passes.c (cfe_code):  Do not walk subtrees
1257         for WHERE.
1258
1259 2014-03-27  Tobias Burnus  <burnus@net-b.de>
1260
1261         PR fortran/58880
1262         * trans-expr.c (gfc_conv_scalar_to_descriptor): Fix handling
1263         of nonpointers.
1264
1265 2014-03-26 Dominique d'Humieres <dominiq@lps.ens.fr>
1266
1267         PR fortran/34928
1268         * fortran.texi: Document Volatile COMMON as not supported.
1269
1270 2014-03-22  Jakub Jelinek  <jakub@redhat.com>
1271
1272         PR debug/60603
1273         * cpp.c (gfc_cpp_init): Restore cb_change_file call to
1274         <built-in>.
1275
1276 2014-03-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1277
1278         PR fortran/60148
1279         * gfortran.texi: Add description of namelist DELIM= behavior.
1280
1281 2014-03-19  Tobias Burnus  <burnus@net-b.>
1282
1283         PR fortran/60543
1284         * io.c (check_io_constraints): Use gfc_unset_implicit_pure.
1285         * resolve.c (resolve_ordinary_assign): Ditto.
1286
1287 2014-03-19  Tobias Burnus  <burnus@net-b.de>
1288
1289         PR fortran/60543
1290         PR fortran/60283
1291         * gfortran.h (gfc_unset_implicit_pure): New prototype.
1292         * resolve.c (gfc_unset_implicit_pure): New.
1293         (resolve_structure_cons, resolve_function,
1294         pure_subroutine): Use it.
1295         * decl.c (match_old_style_init, gfc_match_data,
1296         match_pointer_init, variable_decl): Ditto.
1297         * expr.c (gfc_check_pointer_assign): Ditto.
1298         * intrinsic.c (gfc_intrinsic_sub_interface): Ditto.
1299         * io.c (match_vtag, gfc_match_open, gfc_match_close,
1300         match_filepos, gfc_match_inquire, gfc_match_print,
1301         gfc_match_wait): Ditto.
1302         * match.c (gfc_match_critical, gfc_match_stopcode,
1303         lock_unlock_statement, sync_statement, gfc_match_allocate,
1304         gfc_match_deallocate): Ditto.
1305         * parse.c (decode_omp_directive): Ditto.
1306         * symbol.c (gfc_add_save): Ditto.
1307
1308 2014-03-18  Janus Weil  <janus@gcc.gnu.org>
1309
1310         PR fortran/55207
1311         PR fortran/60549
1312         * decl.c (match_attr_spec): Revert r208590.
1313
1314 2014-03-18  Jakub Jelinek  <jakub@redhat.com>
1315
1316         PR ipa/58721
1317         * trans.c (gfc_unlikely, gfc_likely): Don't add __builtin_expect
1318         if !optimize.
1319
1320 2014-03-18  Tobias Burnus  <burnus@net-b.de>
1321
1322         PR ipa/58721
1323         * trans.h (gfc_unlikely, gfc_likely): Add predictor as argument.
1324         (gfc_trans_io_runtime_check): Remove.
1325         * trans-io.c (gfc_trans_io_runtime_check): Make static; add has_iostat
1326         as argument, add predictor to block.
1327         (set_parameter_value, gfc_trans_open, gfc_trans_close, build_filepos,
1328         gfc_trans_inquire, gfc_trans_wait, build_dt): Update calls.
1329         * trans.c (gfc_unlikely, gfc_likely): Add predictor as argument.
1330         (gfc_trans_runtime_check, gfc_allocate_using_malloc,
1331         gfc_allocate_allocatable, gfc_deallocate_with_status): Set explicitly
1332         branch predictor.
1333         * trans-expr.c (gfc_conv_procedure_call): Ditto.
1334         * trans-stmt.c (gfc_trans_allocate): Ditto.
1335         * trans-array.c (gfc_array_init_size, gfc_array_allocate): Ditto.
1336
1337 2014-03-15  Janus Weil  <janus@gcc.gnu.org>
1338
1339         PR fortran/55207
1340         * decl.c (match_attr_spec): Variables in the main program implicitly
1341         get the SAVE attribute in Fortran 2008.
1342
1343 2014-03-14  Mikael Morin  <mikael@gcc.gnu.org>
1344
1345         PR fortran/60392
1346         * trans-array.c (gfc_conv_array_parameter): Don't reuse the descriptor
1347         if it has transposed dimensions.
1348
1349 2014-03-08  Tobias Burnus  <burnus@net-b.de>
1350
1351         PR fortran/60447
1352         * f95-lang.c (gfc_init): Return false when only
1353         preprocessing.
1354         * options.c (gfc_post_options): Ditto.
1355
1356 2014-03-08  Tobias Burnus  <burnus@net-b.de>
1357
1358         * gfortran.texi (Fortran 2003 Status): Mention finalization,
1359         deferred-length character support and input rounding.
1360         (Fortran 2008 Status): Mention that at termination
1361         signalling exceptions are shown.
1362
1363 2014-03-06  Paul Thomas  <pault@gcc.gnu.org>
1364             Janus Weil  <janus@gcc.gnu.org>
1365
1366         PR fortran/51976
1367         * gfortran.h (symbol_attribute): Add deferred_parameter attribute.
1368         * primary.c (build_actual_constructor): It is not an error if
1369         a missing component has the deferred_parameter attribute;
1370         equally, if one is given a value, it is an error.
1371         * resolve.c (resolve_fl_derived0): Remove error for deferred
1372         character length components.  Add the hidden string length
1373         field to the structure. Give it the deferred_parameter
1374         attribute.
1375         * trans-array.c (duplicate_allocatable): Add a strlen field
1376         which is used as the element size if it is non-null.
1377         (gfc_duplicate_allocatable, gfc_copy_allocatable_data): Pass a
1378         NULL to the new argument in duplicate_allocatable.
1379         (structure_alloc_comps): Set the hidden string length as
1380         appropriate. Use it in calls to duplicate_allocatable.
1381         (gfc_alloc_allocatable_for_assignment): When a deferred length
1382         backend declaration is variable, use that; otherwise use the
1383         string length from the expression evaluation.
1384         * trans-expr.c (gfc_conv_component_ref): If this is a deferred
1385         character length component, the string length should have the
1386         value of the hidden string length field.
1387         (gfc_trans_subcomponent_assign): Set the hidden string length
1388         field for deferred character length components.  Allocate the
1389         necessary memory for the string.
1390         (alloc_scalar_allocatable_for_assignment): Same change as in
1391         gfc_alloc_allocatable_for_assignment above.
1392         * trans-stmt.c (gfc_trans_allocate): Likewise.
1393         * trans-intrinsic (size_of_string_in_bytes): Make non-static.
1394         * trans-types.c (gfc_get_derived_type): Set the tree type for
1395         a deferred character length component.
1396         * trans.c (gfc_deferred_strlen): New function.
1397         * trans.h (size_of_string_in_bytes,gfc_deferred_strlen): New prototypes.
1398
1399 2014-03-01  Mikael Morin  <mikael@gcc.gnu.org>
1400
1401         PR fortran/60341
1402         * frontend-passes.c (optimize_comparison): Guard two union accesses
1403         with the corresponding tag checks.
1404
1405 2014-02-28  Janus Weil  <janus@gcc.gnu.org>
1406
1407         PR fortran/60359
1408         * class.c (find_intrinsic_vtab): Prevent duplicate creation of copy
1409         procedure for characters.
1410
1411 2014-02-21  Janus Weil  <janus@gcc.gnu.org>
1412
1413         PR fortran/60302
1414         * check.c (gfc_check_c_f_pointer): Only clear 'size' if 'gfc_array_size'
1415         is successful.
1416
1417 2014-02-21  Janus Weil  <janus@gcc.gnu.org>
1418
1419         PR fortran/60234
1420         * gfortran.h (gfc_build_class_symbol): Removed argument.
1421         * class.c (gfc_add_component_ref): Fix up missing vtype if necessary.
1422         (gfc_build_class_symbol): Remove argument 'delayed_vtab'. vtab is always
1423         delayed now, except for unlimited polymorphics.
1424         (comp_is_finalizable): Procedure pointer components are not finalizable.
1425         * decl. (build_sym, build_struct, attr_decl1): Removed argument of
1426         'gfc_build_class_symbol'.
1427         * match.c (copy_ts_from_selector_to_associate, select_type_set_tmp):
1428         Ditto.
1429         * symbol.c (gfc_set_default_type): Ditto.
1430
1431 2014-02-19  Janus Weil  <janus@gcc.gnu.org>
1432
1433         PR fortran/60232
1434         * expr.c (gfc_get_variable_expr): Don't add REF_ARRAY for dimensionful
1435         functions, which are used as procedure pointer target.
1436
1437 2014-02-18  Tobias Burnus  <burnus@net-b.de>
1438
1439         PR fortran/49397
1440         * expr.c (gfc_check_pointer_assign): Add check for
1441         F2008Cor2, C729.
1442         * trans-decl.c (gfc_get_symbol_decl): Correctly generate external
1443         decl in a corner case.
1444
1445 2014-02-18  Janus Weil  <janus@gcc.gnu.org>
1446
1447         PR fortran/60231
1448         * resolve.c (check_generic_tbp_ambiguity): Check for presence of dummy
1449         arguments to prevent ICE.
1450
1451 2014-02-17  Janus Weil  <janus@gcc.gnu.org>
1452
1453         PR fortran/55907
1454         * resolve.c (build_default_init_expr): Don't initialize character
1455         variable if -fno-automatic is given.
1456
1457 2014-02-15  Mikael Morin  <mikael@gcc.gnu.org>
1458
1459         PR fortran/59599
1460         * trans-intrinsic.c (gfc_conv_intrinsic_ichar): Calculate the
1461         number of arguments.
1462
1463 2014-02-11  Jakub Jelinek  <jakub@redhat.com>
1464
1465         PR fortran/52370
1466         * trans-decl.c (gfc_build_dummy_array_decl): Set TREE_NO_WARNING
1467         on decl if sym->attr.optional.
1468
1469 2014-02-09  Paul Thomas  <pault@gcc.gnu.org>
1470
1471         PR fortran/57522
1472         * resolve.c (resolve_assoc_var): Set the subref_array_pointer
1473         attribute for the 'associate-name' if necessary.
1474         * trans-stmt.c (trans_associate_var): If the 'associate-name'
1475         is a subref_array_pointer, assign the element size of the
1476         associate variable to 'span'.
1477
1478 2014-02-09  Paul Thomas  <pault@gcc.gnu.org>
1479
1480         PR fortran/59026
1481         * trans-expr.c (gfc_conv_procedure_call): Pass the value of the
1482         actual argument to a formal argument with the value attribute
1483         in an elemental procedure.
1484
1485 2014-02-08  Janus Weil  <janus@gcc.gnu.org>
1486             Mikael Morin <mikael.morin@gcc.gnu.org>
1487
1488         PR fortran/58470
1489         * class.c (generate_finalization_wrapper): Assert that proc_tree has
1490         been set in gfc_resolve_finalizers.
1491         * resolve.c (resolve_fl_derived0): Remove unnecessary call to
1492         gfc_is_finalizable.
1493
1494 2014-02-07  Benno Schulenberg  <bensberg@justemail.net>
1495
1496         PR translation/52289
1497         * fortran/resolve.c (resolve_ordinary_assign): Fix typoed word
1498         in an error message.
1499
1500 2014-02-02  Mikael Morin  <mikael@gcc.gnu.org>
1501
1502         PR fortran/57033
1503         * primary.c (gfc_convert_to_structure_constructor): Avoid null pointer
1504         dereference.
1505
1506 2014-02-01  Paul Thomas  <pault@gcc.gnu.org>
1507
1508         PR fortran/59906
1509         * trans-stmt.c (gfc_add_loop_ss_code): In the case of character
1510         SS_REFERENCE, use gfc_conv_string_parameter to ensure that a
1511         pointer to the string is stored.
1512         * trans-expr.c (gfc_conv_expr_reference): Likewise, use
1513         gfc_conv_string_parameter to ensure that a pointer to is passed
1514         to the elemental function.
1515
1516 2014-01-28  Paul Thomas  <pault@gcc.gnu.org>
1517
1518         PR fortran/59414
1519         * trans-stmt.c (gfc_trans_allocate): Before the pointer
1520         assignment to transfer the source _vptr to a class allocate
1521         expression, the final class reference should be exposed. The
1522         tail that includes the _data and array references is stored.
1523         This reduced expression is transferred to 'lhs' and the _vptr
1524         added. Then the tail is restored to the allocate expression.
1525
1526 2014-01-26  Mikael Morin  <mikael@gcc.gnu.org>
1527
1528         PR fortran/58007
1529         * module.c (read_module): Assert for component name correctness.
1530
1531 2014-01-18  Mikael Morin  <mikael@gcc.gnu.org>
1532
1533         PR fortran/58007
1534         * module.c (MOD_VERSION): Bump.
1535         (fp2, find_pointer2): Remove.
1536         (mio_component_ref): Don't forcedfully set the containing derived type
1537         symbol for loading.  Remove unused argument.
1538         (mio_ref): Update caller
1539         (mio_symbol): Dump component list earlier.
1540         (skip_list): New argument nest_level.  Initialize level with the new
1541         argument.
1542         (read_module): Add forced pointer components association for derived
1543         type symbols.
1544
1545 2014-01-12  Janus Weil  <janus@gcc.gnu.org>
1546
1547         PR fortran/58026
1548         * decl.c (gfc_match_data_decl): Improve error recovery.
1549
1550 2014-01-09  Tobias Burnus  <burnus@net-b.de>
1551
1552         * cpp.c (gfc_cpp_handle_option): Add missing break.
1553         * trans-io.c (transfer_expr): Silence unused value warning.
1554
1555 2014-01-08  Janus Weil  <janus@gcc.gnu.org>
1556
1557         PR fortran/58182
1558         * resolve.c (gfc_verify_binding_labels): Modify order of checks.
1559
1560 2014-01-06  Janus Weil  <janus@gcc.gnu.org>
1561
1562         PR fortran/59589
1563         * class.c (comp_is_finalizable): New function to dermine if a given
1564         component is finalizable.
1565         (finalize_component, generate_finalization_wrapper): Use it.
1566
1567 2014-01-06  Janus Weil  <janus@gcc.gnu.org>
1568
1569         PR fortran/59023
1570         PR fortran/59662
1571         * resolve.c (resolve_global_procedure): Don't apply to c-binding
1572         procedures.
1573         (gfc_verify_binding_labels): Remove duplicate line.
1574
1575 2014-01-04  Janus Weil  <janus@gcc.gnu.org>
1576
1577         PR fortran/59547
1578         * class.c (add_proc_comp): Copy pure attribute.
1579
1580 2014-01-02  Richard Sandiford  <rdsandiford@googlemail.com>
1581
1582         Update copyright years
1583
1584 2014-01-02  Tobias Burnus  <burnus@net-b.de>
1585
1586         * gfortranspec.c (lang_specific_driver): Update copyright notice
1587         dates.
1588         * gfc-internals.texi: Bump @copying's copyright year.
1589         * gfortran.texi: Ditto.
1590         * intrinsic.texi: Ditto.
1591         * invoke.texi: Ditto.
1592
1593 2014-01-02  Janus Weil  <janus@gcc.gnu.org>
1594
1595         PR fortran/59654
1596         * resolve.c (resolve_typebound_procedures): No need to create the vtab
1597         here.
1598 \f
1599 Copyright (C) 2014 Free Software Foundation, Inc.
1600
1601 Copying and distribution of this file, with or without modification,
1602 are permitted in any medium without royalty provided the copyright
1603 notice and this notice are preserved.