OSDN Git Service

PR fortran/26816
[pf3gnuchains/gcc-fork.git] / gcc / fortran / ChangeLog
1 2006-03-25  Steven G. Kargl  <kargls@comcast.net>
2
3         PR fortran/26816
4         * intrinsic.c (add_functions): Allow FLOAT to accept all integer kinds.
5         * intrinsic.texi: Document FLOAT.
6
7 2006-03-25  Thomas Koenig  <Thomas.Koenig@online.de>
8
9         PR fortran/26769
10         * iresolve.c (gfc_resolve_reshape):  Remove doubling of
11         kind for complex. For real(kind=10), call reshape_r10.
12         (gfc_resolve_transpose):  For real(kind=10), call
13         transpose_r10.
14
15 2006-03-25  Roger Sayle  <roger@eyesopen.com>
16
17         * dependency.c (gfc_check_dependency): Improve handling of pointers;
18         Two variables of different types can't have a dependency, and two
19         variables with the same symbol are equal, even if pointers.
20
21 2006-03-24  Roger Sayle  <roger@eyesopen.com>
22
23         * gfortran.h (gfc_symbol): Add a new "forall_index" bit field.
24         * match.c (match_forall_iterator): Set forall_index field on
25         the iteration variable's symbol.
26         * dependency.c (contains_forall_index_p): New function to
27         traverse a gfc_expr to check whether it contains a variable
28         with forall_index set in it's symbol.
29         (gfc_check_element_vs_element): Return GFC_DEP_EQUAL for scalar
30         constant expressions that don't variables used as FORALL indices.
31
32 2006-03-22  Volker Reichelt  <reichelt@igpm.rwth-aachen.de>
33
34         PR driver/22600
35         * error.c (gfc_fatal_error): Return ICE_EXIT_CODE instead of 4.
36
37 2006-03-22  Thomas Koenig  <Thomas.Koenig@online.de>
38
39         PR fortran/19303
40         * gfortran.h (gfc_option_t):  Add record_marker.
41         * lang.opt:  Add -frecord-marker=4 and -frecord-marker=8.
42         * trans-decl.c:  Add gfor_fndecl_set_record_marker.
43         (gfc_build_builtin_function_decls): Set
44         gfor_fndecl_set_record_marker.
45         (gfc_generate_function_code):  If we are in the main program
46         and -frecord-marker was provided, call set_record_marker.
47         * options.c (gfc_handle_option):  Add handling for
48         -frecord-marker=4 and -frecord-marker=8.
49         * invoke.texi:  Document -frecord-marker.
50
51 2006-03-22  Paul Thomas  <pault@gcc.gnu.org>
52
53         PR fortran/17298
54         * trans-intrinsic.c (gfc_conv_intrinsic_array_transfer): New
55         function to implement array valued TRANSFER intrinsic.
56         (gfc_conv_intrinsic_function): Call the new function if TRANSFER
57         and non-null se->ss.
58         (gfc_walk_intrinsic_function): Treat TRANSFER as one of the
59         special cases by calling gfc_walk_intrinsic_libfunc directly.
60
61 2006-03-21  Toon Moene  <toon@moene.indiv.nluug.nl>
62
63         * options.c (gfc_init_options): Initialize
64         flag_argument_noalias to 3.
65
66 2006-03-20  Thomas Koenig  <Thomas.Koenig@online.de>
67
68         PR fortran/20935
69         * iresolve.c (gfc_resolve_maxloc):   If mask is scalar,
70         prefix the function name with an "s".  If the mask is scalar
71         or if its kind is smaller than gfc_default_logical_kind,
72         coerce it to default kind.
73         (gfc_resolve_maxval):  Likewise.
74         (gfc_resolve_minloc):  Likewise.
75         (gfc_resolve_minval):  Likewise.
76         (gfc_resolve_product):  Likewise.
77         (gfc_resolve_sum):  Likewise.
78
79 2006-03-19  Paul Thomas  <pault@gcc.gnu.org>
80
81         PR fortran/26741
82         *expr.c (external_spec_function): Permit elemental functions.
83
84         PR fortran/26716
85         *interface.c (compare_actual_formal): Detect call for procedure
86         usage and require rank checking, in this case, for assumed shape
87         and deferred shape arrays.
88         (gfc_procedure_use): Revert to pre-PR25070 call to
89         compare_actual_formal that does not require rank checking..
90
91 2006-03-16  Roger Sayle  <roger@eyesopen.com>
92
93         * gfortran.h (gfc_equiv_info): Add length field.
94         * trans-common.c (copy_equiv_list_to_ns): Set the length field.
95         * dependency.c (gfc_are_equivalenced_arrays): Use both the offset
96         and length fields to determine whether the two equivalenced symbols
97         overlap in memory.
98
99 2006-03-14  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
100
101         PR fortran/19101
102         * gfortran.h: Add warn_ampersand.
103         * invoke.texi: Add documentation for new option.
104         * lang.opt: Add Wampersand.
105         * options.c (gfc_init_options): Initialize warn_ampersand.
106         (gfc_post_options): Set the warn if pedantic.
107         (set_Wall): Set warn_ampersand.
108         (gfc_handle_option: Add Wampersand for itself, -std=f95, and -std=f2003.
109         * scanner.c (gfc_next_char_literal): Add test for missing '&' in
110         continued character constant and give warning if missing.
111
112 2006-03-14  Steven G. Kargl  <kargls@comcast.net>
113
114         PR 18537
115         * gfortran.h: Wrap Copyright line.
116         (gfc_option_t): add warn_tabs member.
117         * lang.opt: Update Coyright year.  Add the Wtabs.
118         * invoke.texi: Document -Wtabs.
119         * scanner.c (gfc_gobble_whitespace): Use warn_tabs.  Add linenum to
120         suppress multiple warnings.
121         (load_line): Use warn_tabs.  Add linenum, current_line, seen_comment
122         to suppress multiple warnings.
123         * options.c (gfc_init_options): Initialize warn_tabs.
124         (set_Wall): set warn_tabs for -Wall.
125         (gfc_post_options): Adjust flag_tabs depending on -pedantic.
126         (gfc_handle_option):  Process command-line option -W[no-]tabs
127
128 2006-03-13  Paul Thomas  <pault@gcc.gnu.org>
129
130         PR fortran/25378
131         * trans-intrinsic.c (gfc_conv_intrinsic_minmaxloc): Set the initial position to zero and
132         modify the condition for updating it, to implement the F2003 requirement for all(mask)
133         is false.
134
135 2006-03-13  Jakub Jelinek  <jakub@redhat.com>
136
137         * trans-openmp.c (gfc_trans_omp_variable): Handle references
138         to parent result.
139         * trans-expr.c (gfc_conv_variable): Remove useless setting
140         of parent_flag, formatting.
141
142         * trans-decl.c (gfc_get_fake_result_decl): Re-add setting of
143         GFC_DECL_RESULT flag.
144
145 2003-03-11  Roger Sayle  <roger@eyesopen.com>
146
147         * dependency.c (gfc_dep_compare_expr) <EXPR_OP>: Allow unary and
148         binary operators to compare equal if their operands are equal.
149         <EXPR_FUNCTION>: Allow "constant" intrinsic conversion functions
150         to compare equal, if their operands are equal.
151
152 2006-03-11  Erik Edelmann  <eedelman@gcc.gnu.org>
153
154         * symbol.c (check_conflict): Allow allocatable function results,
155         except for elemental functions.
156         * trans-array.c (gfc_trans_allocate_temp_array): Rename to ...
157         (gfc_trans_create_temp_array): ... this, and add new argument
158         callee_alloc.
159         (gfc_trans_array_constructor, gfc_conv_loop_setup): Update call
160         to gfc_trans_allocate_temp_array.
161         * trans-array.h (gfc_trans_allocate_temp_array): Update prototype.
162         * trans-expr.c (gfc_conv_function_call): Use new arg of
163         gfc_trans_create_temp_array avoid pre-allocation of temporary
164         result variables of pointer AND allocatable functions.
165         (gfc_trans_arrayfunc_assign): Return NULL for allocatable
166         functions.
167         * resolve.c (resolve_symbol): Copy value of 'allocatable' attribute
168         from sym->result to sym.
169
170 2006-03-09  Erik Edelmann  <eedelman@gcc.gnu.org>
171
172         * trans-expr.c (gfc_add_interface_mapping): Copy 'allocatable'
173         attribute from sym to new_sym.  Call build_fold_indirect_ref()
174         for allocatable arguments.
175
176 2006-03-09 Paul Thomas <pault@gcc.gnu.org>
177
178         PR fortran/26257
179         * trans-array.c (gfc_conv_expr_descriptor): Exclude calculation of
180         the offset and data when se->data_not_needed is set.
181         * trans.h: Include the data_not_need bit in gfc_se.
182         * trans-intrinsic.c (gfc_conv_intrinsic_size): Set it for SIZE.
183
184 2006-03-06  Paul Thomas  <pault@gcc.gnu.org>
185             Erik Edelmann  <eedelman@gcc.gnu.org>
186
187         * trans-array.c (gfc_trans_dealloc_allocated): New function.
188         (gfc_trans_deferred_array): Use it, instead of inline code.
189         * trans-array.h: Prototype for gfc_trans_dealloc_allocated().
190         * trans-expr.c (gfc_conv_function_call): Deallocate allocated
191         ALLOCATABLE, INTENT(OUT) arguments upon procedure entry.
192
193 2006-03-06  Paul Thomas  <pault@gcc.gnu.org>
194
195         PR fortran/26107
196         * resolve.c (resolve_function): Add name after test for pureness.
197
198         PR fortran/19546
199         * trans-expr.c (gfc_conv_variable): Detect reference to parent result,
200         store current_function_decl, replace with parent, whilst calls are
201         made to gfc_get_fake_result_decl, and restore afterwards. Signal this
202         to gfc_get_fake_result_decl with a new argument, parent_flag.
203         * trans-stmt.c (gfc_trans_return): gfc_get_fake_result_decl 2nd arg
204         is set to zero.
205         * trans.h: Add parent_flag to gfc_get_fake_result_decl prototype.
206         * trans-decl.c (gfc_get_fake_result_decl): On parent_flag, being set,
207         add decl to parent function. Replace refs to current_fake_result_decl
208         with refs to this_result_decl.
209         (gfc_generate_function_code): Null parent_fake_result_decl before the
210         translation of code for contained procedures. Set parent_flag to zero
211         in call to gfc_get_fake_result_decl.
212         * trans-intrinsic.c (gfc_conv_intrinsic_len): The same.
213
214 2006-03-05  Steven G. Kargl  <kargls@comcast.net>
215
216         * simplify.c (gfc_simplify_verify):  Fix return when SET=''.
217
218 2006-03-05  Erik Edelmann  <eedelman@gcc.gnu.org>
219
220         PR fortran/16136
221         * symbol.c (conf_std): New macro.
222         (check_conflict): Use it to allow ALLOCATABLE dummy
223         arguments for F2003.
224         * trans-expr.c (gfc_conv_function_call): Pass the
225         address of the array descriptor when dummy argument is
226         ALLOCATABLE.
227         * interface.c (compare_allocatable): New function.
228         (compare_actual_formal): Use it.
229         * resolve.c (resolve_deallocate_expr,
230         resolve_allocate_expr): Check that INTENT(IN) variables
231         aren't (de)allocated.
232         * gfortran.texi (Fortran 2003 status): List ALLOCATABLE
233         dummy arguments as supported.
234
235 2006-03-03  Roger Sayle  <roger@eyesopen.com>
236
237         * dependency.c (gfc_check_element_vs_element): Revert last change.
238
239 2006-03-03  Roger Sayle  <roger@eyesopen.com>
240
241         * dependency.c (gfc_check_element_vs_element): Consider two
242         unordered scalar subscripts as (potentially) equal.
243
244 2006-03-03  Roger Sayle  <roger@eyesopen.com>
245
246         * dependency.c (gfc_check_dependency): Call gfc_dep_resolver to
247         check whether two array references have a dependency.
248         (gfc_check_element_vs_element): Assume lref and rref must be
249         REF_ARRAYs.  If gfc_dep_compare_expr returns -2, assume these
250         references could potentially overlap.
251         (gfc_dep_resolver): Whitespace and comment tweaks.  Assume a
252         dependency if the references have different depths.  Rewrite
253         final term to clarrify we only have a dependency for overlaps.
254
255 2006-03-03  Thomas Koenig  <Thomas.Koenig@online.de>
256
257         PR fortran/25031
258         * trans-array.h:  Adjust gfc_array_allocate prototype.
259         * trans-array.c (gfc_array_allocate):  Change type of
260         gfc_array_allocatate to bool.  Function returns true if
261         it operates on an array.  Change second argument to gfc_expr.
262         Find last reference in chain.
263         If the function operates on an allocatable array, emit call to
264         allocate_array() or allocate64_array().
265         * trans-stmt.c (gfc_trans_allocate):  Code to follow to last
266         reference has been moved to gfc_array_allocate.
267         * trans.h:  Add declaration for gfor_fndecl_allocate_array and
268         gfor_fndecl_allocate64_array.
269         (gfc_build_builtin_function_decls):  Add gfor_fndecl_allocate_array
270         and gfor_fndecl_allocate64_array.
271
272 2006-03-01  Roger Sayle  <roger@eyesopen.com>
273
274         * trans-stmt.c (generate_loop_for_temp_to_lhs): Add an additional
275         INVERT argument to invert the sense of the WHEREMASK argument.
276         Remove unneeded code to AND together a list of masks.
277         (generate_loop_for_rhs_to_temp): Likewise.
278         (gfc_trans_assign_need_temp): Likewise.
279         (gfc_trans_forall_1): Likewise.
280         (gfc_evaluate_where_mask): Likewise, add a new INVERT argument
281         to specify the sense of the MASK argument.
282         (gfc_trans_where_assign): Likewise.
283         (gfc_trans_where_2): Likewise.  Restructure code that decides
284         whether we need to allocate zero, one or two temporary masks.
285         If this is a top-level WHERE (i.e. the incoming MASK is NULL),
286         we only need to allocate at most one temporary mask, and can
287         invert it's sense to provide the complementary pending execution
288         mask.  Only calculate the size of the required temporary arrays
289         if we need any.
290         (gfc_trans_where): Update call to gfc_trans_where_2.
291
292 2006-03-01  Paul Thomas  <pault@gcc.gnu.org>
293
294         * iresolve.c (gfc_resolve_dot_product):  Remove any difference in
295         treatment of logical types.
296         * trans-intrinsic.c (gfc_conv_intrinsic_dot_product):  New function. 
297
298         PR fortran/26393
299         * trans-decl.c (gfc_get_symbol_decl): Extend condition that symbols
300         must be referenced to include unreferenced symbols in an interface
301         body. 
302
303         PR fortran/20938
304         * trans-array.c (gfc_conv_resolve_dependencies): Add call to
305         gfc_are_equivalenced_arrays.
306         * symbol.c (gfc_free_equiv_infos, gfc_free_equiv_lists): New
307         functions. (gfc_free_namespace): Call them.
308         * trans-common.c (copy_equiv_list_to_ns): New function.
309         (add_equivalences): Call it.
310         * gfortran.h: Add equiv_lists to gfc_namespace and define
311         gfc_equiv_list and gfc_equiv_info.
312         * dependency.c (gfc_are_equivalenced_arrays): New function.
313         (gfc_check_dependency): Call it.
314         * dependency.h: Prototype for gfc_are_equivalenced_arrays.
315
316 2006-03-01  Roger Sayle  <roger@eyesopen.com>
317
318         * dependency.c (gfc_is_same_range): Compare the stride, lower and
319         upper bounds when testing array reference ranges for equality.
320         (gfc_check_dependency): Fix indentation whitespace.
321         (gfc_check_element_vs_element): Likewise.
322         (gfc_dep_resolver): Likewise.
323
324 2006-02-28  Thomas Koenig  <Thomas.Koenig@online.de>
325
326         * trans-intrinsic.c (gfc_conv_intrinsic_minmaxloc):
327         If the mask expression exists and has rank 0, enclose the
328         generated loop in an "if (mask)".  Put the default
329         initialization into the else branch.
330
331 2006-02-25  Thomas Koenig  <Thomas.Koenig@online.de>
332
333         PR fortran/23092
334         * trans-intrinsic.c (gfc_conv_intrinsic_arith):  If the
335         mask expression exists and has rank 0, enclose the generated
336         loop in an "if (mask)".
337         * (gfc_conv_intrinsic_minmaxloc):  Likewise.
338
339 2006-02-24  Paul Thomas  <pault@gcc.gnu.org>
340
341         PR fortran/26409
342         * resolve.c (resolve_contained_functions, resolve_types,
343         gfc_resolve): Revert patch of 2006-02-19.
344
345 2006-02-24  Paul Thomas  <pault@gcc.gnu.org>
346
347         PR fortran/24519
348         * dependency.c (gfc_is_same_range): Correct typo.
349         (gfc_check_section_vs_section): Call gfc_is_same_range.
350
351         PR fortran/25395
352         * trans-common.c (add_equivalences): Add a new flag that is set when
353         an equivalence is seen that prevents more from being reset until the
354         start of a new traversal of the list, thus ensuring completion of
355         all the equivalences.
356
357 2006-02-23  Erik Edelmann  <eedelman@gcc.gnu.org>
358
359         * module.c (read_module): Remove redundant code lines.
360
361 2006-02-20 Rafael \81Ávila de Esp\81índola <rafael.espindola@gmail.com>
362         * Make-lang.in (FORTRAN): Remove
363         (.PHONY): Remove F95 and f95. Add fortran
364
365 2006-02-20  Roger Sayle  <roger@eyesopen.com>
366
367         * trans-stmt.c (gfc_trans_where_2): Avoid updating unused current
368         execution mask for empty WHERE/ELSEWHERE clauses.  Don't allocate
369         temporary mask arrays if they won't be used.
370
371 2006-02-20  Roger Sayle  <roger@eyesopen.com>
372
373         * trans-stmt.c (gfc_trans_where_assign): Remove code to handle
374         traversing a linked list of MASKs.  The MASK is now always a
375         single element requiring no ANDing during the assignment.
376
377 2006-02-19  Thomas Koenig  <Thomas.Koenig@online.de>
378
379         * gfortran.texi:  Document environment variables which
380         influence runtime behavior.
381
382 2006-02-19  H.J. Lu  <hongjiu.lu@intel.com>
383
384         * resolve.c (resolve_contained_functions): Call resolve_entries
385         first.
386         (resolve_types): Remove calls to resolve_entries and
387         resolve_contained_functions.
388         (gfc_resolve): Call resolve_contained_functions.
389
390 2006-02-19  Erik Edelmann  <eedelman@gcc.gnu.org>
391
392         PR fortran/26201
393         * intrinsic.c (gfc_convert_type_warn): Call
394         gfc_intrinsic_symbol() on the newly created symbol.
395
396 2006-02-19  Paul Thomas  <pault@gcc.gnu.org>
397
398         PR fortran/25054
399         * resolve.c (is_non_constant_shape_array): New function.
400         (resolve_fl_variable): Remove code for the new function and call it.
401         (resolve_fl_namelist): New function.  Add test for namelist array
402         with non-constant shape, using is_non_constant_shape_array.
403         (resolve_symbol): Remove code for resolve_fl_namelist and call it.
404
405         PR fortran/25089
406         * match.c (match_namelist): Increment the refs field of an accepted
407         namelist object symbol.
408         * resolve.c (resolve_fl_namelist): Test namelist objects for a conflict
409         with contained or module procedures.
410
411 2006-02-18  Roger Sayle  <roger@eyesopen.com>
412
413         * trans-stmt.c (struct temporary_list): Delete.
414         (gfc_trans_where_2): Major reorganization.  Remove no longer needed
415         TEMP argument.  Allocate and deallocate the control mask and
416         pending control mask locally.
417         (gfc_trans_forall_1): Delete TEMP local variable, and update
418         call to gfc_trans_where_2.  No need to deallocate arrays after.
419         (gfc_evaluate_where_mask): Major reorganization.  Change return
420         type to void.  Pass in parent execution mask, MASK, and two
421         already allocated mask arrays CMASK and PMASK.  On return
422         CMASK := MASK & COND, PMASK := MASK & !COND.  MASK, CMASK and
423         CMASK may all be NULL, or refer to the same temporary arrays.
424         (gfc_trans_where): Update call to gfc_trans_where_2.  We no
425         longer need a TEMP variable or to deallocate temporary arrays
426         allocated by gfc_trans_where_2.
427
428 2006-02-18   Danny Smith  <dannysmith@users.sourceforeg.net>
429
430         * gfortran.h (gfc_add_attribute): Change uint to unsigned int.
431         * symbol.c (gfc_add_attribute): Likewise for definition.
432         * resolve.c (resolve_global_procedure): Likewise for variable 'type'.
433
434 2006-02-17  Richard Sandiford  <richard@codesourcery.com>
435
436         * trans-common.c: Include rtl.h earlier.
437         * trans-decl.c: Likewise.
438
439 2006-02-16  Jakub Jelinek  <jakub@redhat.com>
440
441         PR fortran/26224
442         * parse.c (parse_omp_do, parse_omp_structured_block): Call
443         gfc_commit_symbols and gfc_warning_check.
444
445         * openmp.c (resolve_omp_clauses): Add a dummy case label to workaround
446         PR middle-end/26316.
447
448 2006-02-16  Paul Thomas  <pault@gcc.gnu.org>
449
450         PR fortran/24557
451         * trans-expr.c (gfc_add_interface_mapping): Use the actual argument
452         for character(*) arrays, rather than casting to the type and kind
453         parameters of the formal argument.
454
455 2006-02-15  Toon Moene  <toon@moene.indiv.nluug.nl>
456
457         PR fortran/26054
458         * options.c: Do not warn for Fortran 2003 features by default.
459
460 2006-02-15  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
461
462         * check.c: Update copyright years.
463         
464         * check.c (gfc_check_minloc_maxloc, check_reduction): Don't call
465         dim_range_check on not-present optional dim argument.
466
467 2006-02-15  Jakub Jelinek  <jakub@redhat.com>
468
469         PR libgomp/25938
470         PR libgomp/25984
471         * Make-lang.in (install-finclude-dir): New goal.
472         (fortran.install-common): Depend on install-finclude-dir.
473         * lang-specs.h: If not -nostdinc, add -I finclude.
474
475 2006-02-14  Thomas Koenig  <Thomas.Koenig@online.de>
476
477         PR fortran/25045
478         * check.c (dim_check):  Perform all checks if dim is optional.
479         (gfc_check_minloc_maxloc):  Use dim_check and dim_rank_check
480         to check dim argument.
481         (check_reduction):  Likewise.
482
483 2006-02-14  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
484
485         PR fortran/26277
486         * io.c (match_ltag): Mark label as referenced.
487
488 2006-02-14  Jakub Jelinek  <jakub@redhat.com>
489             Richard Henderson  <rth@redhat.com>
490             Diego Novillo  <dnovillo@redhat.com>
491
492         * invoke.texi: Document -fopenmp.
493         * gfortran.texi (Extensions): Document OpenMP.
494
495         Backport from gomp-20050608-branch
496         * trans-openmp.c: Call build_omp_clause instead of
497         make_node when creating OMP_CLAUSE_* trees.
498         (gfc_trans_omp_reduction_list): Remove argument 'code'.
499         Adjust all callers.
500
501         * trans.h (build4_v): Define.
502         * trans-openmp.c: Call build4_v to create OMP_PARALLEL nodes.
503         Call build3_v to create OMP_SECTIONS nodes.
504
505         PR fortran/25162
506         * openmp.c (gfc_match_omp_variable_list): Call gfc_set_sym_referenced
507         on all symbols added to the variable list.
508
509         * openmp.c (gfc_match_omp_clauses): Fix check for non-INTRINSIC
510         procedure symbol in REDUCTION.
511
512         * trans-openmp.c (gfc_trans_omp_array_reduction): Use gfc_add
513         for MINUS_EXPR OMP_CLAUSE_REDUCTION_CODE.
514
515         * trans-openmp.c (gfc_trans_omp_do): Add PBLOCK argument.  If PBLOCK
516         is non-NULL, evaluate INIT/COND/INCR and chunk size expressions in
517         that statement block.
518         (gfc_trans_omp_parallel_do): Pass non-NULL PBLOCK to gfc_trans_omp_do
519         for non-ordered non-static combined loops.
520         (gfc_trans_omp_directive): Pass NULL PBLOCK to gfc_trans_omp_do.
521
522         * openmp.c: Include target.h and toplev.h.
523         (gfc_match_omp_threadprivate): Emit diagnostic if target does
524         not support TLS.
525         * Make-lang.in (fortran/openmp.o): Add dependencies on
526         target.h and toplev.h.
527
528         * trans-decl.c (gfc_get_fake_result_decl): Set GFC_DECL_RESULT.
529         * trans-openmp.c (gfc_omp_privatize_by_reference): Make
530         DECL_ARTIFICIAL vars predetermined shared except GFC_DECL_RESULT.
531         (gfc_omp_disregard_value_expr): Handle GFC_DECL_RESULT.
532         (gfc_trans_omp_variable): New function.
533         (gfc_trans_omp_variable_list, gfc_trans_omp_reduction_list): Use it.
534         * trans.h (GFC_DECL_RESULT): Define.
535
536         * trans-openmp.c (gfc_omp_firstprivatize_type_sizes): New function.
537         * f95-lang.c (LANG_HOOKS_OMP_FIRSTPRIVATIZE_TYPE_SIZES): Define.
538         * trans.h (gfc_omp_firstprivatize_type_sizes): New prototype.
539
540         * trans-openmp.c (gfc_omp_privatize_by_reference): Return
541         true if a pointer has GFC_DECL_SAVED_DESCRIPTOR set.
542         (gfc_trans_omp_array_reduction, gfc_trans_omp_reduction_list): New
543         functions.
544         (gfc_trans_omp_clauses): Add WHERE argument.  Call
545         gfc_trans_omp_reduction_list rather than gfc_trans_omp_variable_list
546         for reductions.
547         (gfc_trans_omp_do, gfc_trans_omp_parallel, gfc_trans_omp_parallel_do,
548         gfc_trans_omp_parallel_sections, gfc_trans_omp_parallel_workshare,
549         gfc_trans_omp_sections, gfc_trans_omp_single): Adjust
550         gfc_trans_omp_clauses callers.
551
552         * openmp.c (omp_current_do_code): New var.
553         (gfc_resolve_omp_do_blocks): New function.
554         (gfc_resolve_omp_parallel_blocks): Call it.
555         (gfc_resolve_do_iterator): Add CODE argument.  Don't propagate
556         predetermination if argument is !$omp do or !$omp parallel do
557         iteration variable.
558         * resolve.c (resolve_code): Call gfc_resolve_omp_do_blocks
559         for EXEC_OMP_DO.  Adjust gfc_resolve_do_iterator caller.
560         * fortran.h (gfc_resolve_omp_do_blocks): New prototype.
561         (gfc_resolve_do_iterator): Add CODE argument.
562
563         * trans.h (gfc_omp_predetermined_sharing,
564         gfc_omp_disregard_value_expr, gfc_omp_private_debug_clause): New
565         prototypes.
566         (GFC_DECL_COMMON_OR_EQUIV, GFC_DECL_CRAY_POINTEE): Define.
567         * trans-openmp.c (gfc_omp_predetermined_sharing,
568         gfc_omp_disregard_value_expr, gfc_omp_private_debug_clause): New
569         functions.
570         * trans-common.c (build_equiv_decl, build_common_decl,
571         create_common): Set GFC_DECL_COMMON_OR_EQUIV flag on the decls.
572         * trans-decl.c (gfc_finish_cray_pointee): Set GFC_DECL_CRAY_POINTEE
573         on the decl.
574         * f95-lang.c (LANG_HOOKS_OMP_PREDETERMINED_SHARING,
575         LANG_HOOKS_OMP_DISREGARD_VALUE_EXPR,
576         LANG_HOOKS_OMP_PRIVATE_DEBUG_CLAUSE): Define.
577
578         * openmp.c (resolve_omp_clauses): Remove extraneous comma.
579
580         * symbol.c (check_conflict): Add conflict between cray_pointee and
581         threadprivate.
582         * openmp.c (gfc_match_omp_threadprivate): Fail if
583         gfc_add_threadprivate returned FAILURE.
584         (resolve_omp_clauses): Diagnose Cray pointees in SHARED,
585         {,FIRST,LAST}PRIVATE and REDUCTION clauses and Cray pointers in
586         {FIRST,LAST}PRIVATE and REDUCTION clauses.
587
588         * resolve.c (omp_workshare_flag): New variable.
589         (resolve_function): Diagnose use of non-ELEMENTAL user defined
590         function in WORKSHARE construct.
591         (resolve_code): Cleanup forall_save use.  Make sure omp_workshare_flag
592         is set to correct value in different contexts.
593
594         * openmp.c (resolve_omp_clauses): Replace %s with '%s' when printing
595         variable name.
596         (resolve_omp_atomic): Likewise.
597
598         PR fortran/24493
599         * scanner.c (skip_free_comments): Set at_bol at the beginning of the
600         loop, not before it.
601         (skip_fixed_comments): Handle ! comments in the middle of line here
602         as well.
603         (gfc_skip_comments): Use skip_fixed_comments for FIXED_FORM even if
604         not at BOL.
605         (gfc_next_char_literal): Fix expected canonicalized *$omp string.
606
607         * trans-openmp.c (gfc_trans_omp_do): Use make_node and explicit
608         initialization to build OMP_FOR instead of build.
609
610         * trans-decl.c (gfc_gimplify_function): Invoke
611         diagnose_omp_structured_block_errors.
612
613         * trans-openmp.c (gfc_trans_omp_master): Use OMP_MASTER.
614         (gfc_trans_omp_ordered): Use OMP_ORDERED.
615
616         * gfortran.h (gfc_resolve_do_iterator, gfc_resolve_blocks,
617         gfc_resolve_omp_parallel_blocks): New prototypes.
618         * resolve.c (resolve_blocks): Renamed to...
619         (gfc_resolve_blocks): ... this.  Remove static.
620         (gfc_resolve_forall): Adjust caller.
621         (resolve_code): Only call gfc_resolve_blocks if code->block != 0
622         and not for EXEC_OMP_PARALLEL* directives.  Call
623         gfc_resolve_omp_parallel_blocks for EXEC_OMP_PARALLEL* directives.
624         Call gfc_resolve_do_iterator if resolved successfully EXEC_DO
625         iterator.
626         * openmp.c: Include pointer-set.h.
627         (omp_current_ctx): New variable.
628         (gfc_resolve_omp_parallel_blocks, gfc_resolve_do_iterator): New
629         functions.
630         * Make-lang.in (fortran/openmp.o): Depend on pointer-set.h.
631
632         * openmp.c (gfc_match_omp_clauses): For max/min/iand/ior/ieor,
633         look up symbol if it exists, use its name instead and, if it is not
634         INTRINSIC, issue diagnostics.
635
636         * parse.c (parse_omp_do): Handle implied end do properly.
637         (parse_executable): If parse_omp_do returned ST_IMPLIED_ENDDO,
638         return it instead of continuing.
639
640         * trans-openmp.c (gfc_trans_omp_critical): Update for changed
641         operand numbering.
642         (gfc_trans_omp_do, gfc_trans_omp_parallel, gfc_trans_omp_parallel_do,
643         gfc_trans_omp_parallel_sections, gfc_trans_omp_parallel_workshare,
644         gfc_trans_omp_sections, gfc_trans_omp_single): Likewise.
645
646         * trans.h (gfc_omp_privatize_by_reference): New prototype.
647         * f95-lang.c (LANG_HOOKS_OMP_PRIVATIZE_BY_REFERENCE): Redefine
648         to gfc_omp_privatize_by_reference.
649         * trans-openmp.c (gfc_omp_privatize_by_reference): New function.
650
651         * trans-stmt.h (gfc_trans_omp_directive): Add comment.
652
653         * openmp.c (gfc_match_omp_variable_list): Add ALLOW_COMMON argument.
654         Disallow COMMON matching if it is set.
655         (gfc_match_omp_clauses, gfc_match_omp_flush): Adjust all callers.
656         (resolve_omp_clauses): Show locus in error messages.  Check that
657         variable types in reduction clauses are appropriate for reduction
658         operators.
659
660         * resolve.c (resolve_symbol): Don't error if a threadprivate module
661         variable isn't SAVEd.
662
663         * trans-openmp.c (gfc_trans_omp_do): Put count into BLOCK, not BODY.
664         Fix typo in condition.  Fix DOVAR initialization.
665
666         * openmp.c (gfc_match_omp_clauses): Match min/iand/ior/ieor
667         rather than .min. etc.
668
669         * trans-openmpc.c (omp_not_yet): Remove.
670         (gfc_trans_omp_parallel_do): Keep listprivate clause on parallel.
671         Force creation of BIND_EXPR around the workshare construct.
672         (gfc_trans_omp_parallel_sections): Likewise.
673         (gfc_trans_omp_parallel_workshare): Likewise.
674
675         * types.def (BT_I16, BT_FN_I16_VPTR_I16,
676         BT_FN_BOOL_VPTR_I16_I16, BT_FN_I16_VPTR_I16_I16): Add.
677
678         * trans-openmp.c (gfc_trans_omp_clauses): Create OMP_CLAUSE_DEFAULT.
679         (gfc_trans_omp_code): New function.
680         (gfc_trans_omp_do): Use it, remove omp_not_yet uses.
681         (gfc_trans_omp_parallel, gfc_trans_omp_single): Likewise.
682         (gfc_trans_omp_sections): Likewise.  Only treat empty last section
683         specially if lastprivate clause is present.
684         * f95-lang.c (gfc_init_builtin_functions): Create BUILT_IN_TRAP
685         builtin.
686
687         * trans-openmp.c (gfc_trans_omp_variable_list): Update for
688         OMP_CLAUSE_DECL name change.
689         (gfc_trans_omp_do): Likewise.
690
691         * trans-openmp.c (gfc_trans_omp_clauses): Create OMP_CLAUSE_REDUCTION
692         clauses.
693         (gfc_trans_omp_atomic): Build OMP_ATOMIC instead of expanding
694         sync builtins directly.
695         (gfc_trans_omp_single): Build OMP_SINGLE statement.
696
697         * trans-openmp.c (gfc_trans_add_clause): New.
698         (gfc_trans_omp_variable_list): Take a tree code and build the clause
699         node here.  Link it to the head of a list.
700         (gfc_trans_omp_clauses): Update to match.
701         (gfc_trans_omp_do): Use gfc_trans_add_clause.
702
703         * trans-openmp.c (gfc_trans_omp_clauses): Change second argument to
704         gfc_omp_clauses *.  Use gfc_evaluate_now instead of creating
705         temporaries by hand.
706         (gfc_trans_omp_atomic, gfc_trans_omp_critical): Use buildN_v macros.
707         (gfc_trans_omp_do): New function.
708         (gfc_trans_omp_master): Dont' check for gfc_trans_code returning NULL.
709         (gfc_trans_omp_parallel): Adjust gfc_trans_omp_clauses caller.
710         Use buildN_v macros.
711         (gfc_trans_omp_parallel_do, gfc_trans_omp_parallel_sections,
712         gfc_trans_omp_parallel_workshare, gfc_trans_omp_sections,
713         gfc_trans_omp_single, gfc_trans_omp_workshare): New functions.
714         (gfc_trans_omp_directive): Use them.
715         * parse.c (parse_omp_do): Allow new_st.op == EXEC_NOP.
716         * openmp.c (resolve_omp_clauses): Check for list items present
717         in multiple clauses.
718         (resolve_omp_do): Check that iteration variable is not THREADPRIVATE
719         and is not present in any clause variable lists other than PRIVATE
720         or LASTPRIVATE.
721
722         * gfortran.h (symbol_attribute): Add threadprivate bit.
723         (gfc_common_head): Add threadprivate member, change use_assoc
724         and saved into char to save space.
725         (gfc_add_threadprivate): New prototype.
726         * symbol.c (check_conflict): Handle threadprivate.
727         (gfc_add_threadprivate): New function.
728         (gfc_copy_attr): Copy threadprivate.
729         * trans-openmp.c (gfc_trans_omp_clauses): Avoid creating a temporary
730         if IF or NUM_THREADS is constant.  Create OMP_CLAUSE_SCHEDULE and
731         OMP_CLAUSE_ORDERED.
732         * resolve.c (resolve_symbol): Complain if a THREADPRIVATE symbol
733         outside a module and not in COMMON has is not SAVEd.
734         (resolve_equivalence): Ensure THREADPRIVATE objects don't get
735         EQUIVALENCEd.
736         * trans-common.c: Include target.h and rtl.h.
737         (build_common_decl): Set DECL_TLS_MODEL if THREADPRIVATE.
738         * trans-decl.c: Include rtl.h.
739         (gfc_finish_var_decl): Set DECL_TLS_MODEL if THREADPRIVATE.
740         * dump-parse-tree.c (gfc_show_attr): Handle THREADPRIVATE.
741         * Make-lang.in (fortran/trans-decl.o): Depend on $(RTL_H).
742         (fortran/trans-common.o): Depend on $(RTL_H) and $(TARGET_H).
743         * openmp.c (gfc_match_omp_variable_list): Ensure COMMON block
744         is from current namespace.
745         (gfc_match_omp_threadprivate): Rewrite.
746         (resolve_omp_clauses): Check some clause restrictions.
747         * module.c (ab_attribute): Add AB_THREADPRIVATE.
748         (attr_bits): Add THREADPRIVATE.
749         (mio_symbol_attribute, mio_symbol_attribute): Handle threadprivate.
750         (load_commons, write_common, write_blank_common): Adjust for type
751         change of saved, store/load threadprivate bit from the integer
752         as well.
753
754         * types.def (BT_FN_UINT_UINT): New.
755         (BT_FN_VOID_UINT_UINT): Remove.
756
757         * trans-openmp.c (gfc_trans_omp_clauses, gfc_trans_omp_barrier,
758         gfc_trans_omp_critical, gfc_trans_omp_flush, gfc_trans_omp_master,
759         gfc_trans_omp_ordered, gfc_trans_omp_parallel): New functions.
760         (gfc_trans_omp_directive): Use them.
761
762         * openmp.c (expr_references_sym): Add SE argument, don't look
763         into SE tree.
764         (is_conversion): New function.
765         (resolve_omp_atomic): Adjust expr_references_sym callers.  Handle
766         promoted expressions.
767         * trans-openmp.c (gfc_trans_omp_atomic): New function.
768         (gfc_trans_omp_directive): Call it.
769
770         * f95-lang.c (builtin_type_for_size): New function.
771         (gfc_init_builtin_functions): Initialize synchronization and
772         OpenMP builtins.
773         * types.def: New file.
774         * Make-lang.in (f95-lang.o): Depend on $(BUILTINS_DEF) and
775         fortran/types.def.
776
777         * trans-openmp.c: Rename GOMP_* tree codes into OMP_*.
778
779         * dump-parse-tree.c (show_symtree): Don't crash if ns->proc_name
780         is NULL.
781
782         * dump-parse-tree.c (gfc_show_namelist, gfc_show_omp_node): New
783         functions.
784         (gfc_show_code_node): Call gfc_show_omp_node for EXEC_OMP_* nodes.
785
786         * parse.c (parse_omp_do): Call pop_state before next_statement.
787         * openmp.c (expr_references_sym, resolve_omp_atomic, resolve_omp_do):
788         New functions.
789         (gfc_resolve_omp_directive): Call them.
790         * match.c (match_exit_cycle): Issue error if EXIT or CYCLE statement
791         leaves an OpenMP structured block or if EXIT terminates !$omp do
792         loop.
793
794         * Make-lang.in (F95_PARSER_OBJS): Add fortran/openmp.o.
795         (F95_OBJS): Add fortran/trans-openmp.o.
796         (fortran/trans-openmp.o): Depend on $(GFORTRAN_TRANS_DEPS).
797         * lang.opt: Add -fopenmp option.
798         * options.c (gfc_init_options): Initialize it.
799         (gfc_handle_option): Handle it.
800         * gfortran.h (ST_OMP_ATOMIC, ST_OMP_BARRIER, ST_OMP_CRITICAL,
801         ST_OMP_END_CRITICAL, ST_OMP_END_DO, ST_OMP_END_MASTER,
802         ST_OMP_END_ORDERED, ST_OMP_END_PARALLEL, ST_OMP_END_PARALLEL_DO,
803         ST_OMP_END_PARALLEL_SECTIONS, ST_OMP_END_PARALLEL_WORKSHARE,
804         ST_OMP_END_SECTIONS, ST_OMP_END_SINGLE, ST_OMP_END_WORKSHARE,
805         ST_OMP_DO, ST_OMP_FLUSH, ST_OMP_MASTER, ST_OMP_ORDERED,
806         ST_OMP_PARALLEL, ST_OMP_PARALLEL_DO, ST_OMP_PARALLEL_SECTIONS,
807         ST_OMP_PARALLEL_WORKSHARE, ST_OMP_SECTIONS, ST_OMP_SECTION,
808         ST_OMP_SINGLE, ST_OMP_THREADPRIVATE, ST_OMP_WORKSHARE): New
809         statement codes.
810         (OMP_LIST_PRIVATE, OMP_LIST_FIRSTPRIVATE, OMP_LIST_LASTPRIVATE,
811         OMP_LIST_COPYPRIVATE, OMP_LIST_SHARED, OMP_LIST_COPYIN,
812         OMP_LIST_PLUS, OMP_LIST_REDUCTION_FIRST, OMP_LIST_MULT,
813         OMP_LIST_SUB, OMP_LIST_AND, OMP_LIST_OR, OMP_LIST_EQV,
814         OMP_LIST_NEQV, OMP_LIST_MAX, OMP_LIST_MIN, OMP_LIST_IAND,
815         OMP_LIST_IOR, OMP_LIST_IEOR, OMP_LIST_REDUCTION_LAST, OMP_LIST_NUM):
816         New OpenMP variable list types.
817         (gfc_omp_clauses): New typedef.
818         (gfc_get_omp_clauses): Define.
819         (EXEC_OMP_CRITICAL, EXEC_OMP_DO, EXEC_OMP_FLUSH, EXEC_OMP_MASTER,
820         EXEC_OMP_ORDERED, EXEC_OMP_PARALLEL, EXEC_OMP_PARALLEL_DO,
821         EXEC_OMP_PARALLEL_SECTIONS, EXEC_OMP_PARALLEL_WORKSHARE,
822         EXEC_OMP_SECTIONS, EXEC_OMP_SINGLE, EXEC_OMP_WORKSHARE,
823         EXEC_OMP_ATOMIC, EXEC_OMP_BARRIER, EXEC_OMP_END_NOWAIT,
824         EXEC_OMP_END_SINGLE): New OpenMP gfc_exec_op codes.
825         (struct gfc_code): Add omp_clauses, omp_name, omp_namelist
826         and omp_bool fields to ext union.
827         (flag_openmp): Declare.
828         (gfc_free_omp_clauses, gfc_resolve_omp_directive): New prototypes.
829         * scanner.c (openmp_flag, openmp_locus): New variables.
830         (skip_free_comments, skip_fixed_comments, gfc_next_char_literal):
831         Handle OpenMP directive lines and conditional compilation magic
832         comments.
833         * parse.h (COMP_OMP_STRUCTURED_BLOCK): New compile state.
834         * parse.c (decode_omp_directive, parse_omp_do, parse_omp_atomic,
835         parse_omp_structured_block): New functions.
836         (next_free, next_fixed): Parse OpenMP directives.
837         (case_executable, case_exec_markers, case_decl): Add ST_OMP_*
838         codes.
839         (gfc_ascii_statement): Handle ST_OMP_* codes.
840         (parse_executable): Rearrange the loop slightly, so that
841         parse_omp_do can return next_statement.
842         * match.h (gfc_match_omp_eos, gfc_match_omp_atomic,
843         gfc_match_omp_barrier, gfc_match_omp_critical, gfc_match_omp_do,
844         gfc_match_omp_flush, gfc_match_omp_master, gfc_match_omp_ordered,
845         gfc_match_omp_parallel, gfc_match_omp_parallel_do,
846         gfc_match_omp_parallel_sections, gfc_match_omp_parallel_workshare,
847         gfc_match_omp_sections, gfc_match_omp_single,
848         gfc_match_omp_threadprivate, gfc_match_omp_workshare,
849         gfc_match_omp_end_nowait, gfc_match_omp_end_single): New prototypes.
850         * resolve.c (resolve_blocks): Ignore EXEC_OMP_* block directives.
851         (resolve_code): Call gfc_resolve_omp_directive on EXEC_OMP_*
852         directives.
853         * trans.c (gfc_trans_code): Call gfc_trans_omp_directive for
854         EXEC_OMP_* directives.
855         * st.c (gfc_free_statement): Handle EXEC_OMP_* statement freeing.
856         * trans-stmt.h (gfc_trans_omp_directive): New prototype.
857         * openmp.c: New file.
858         * trans-openmp.c: New file.
859
860 2006-02-13  Andrew Pinski  <pinskia@physics.uc.edu>
861             Jakub Jelinek  <jakub@redhat.com>
862
863         PR fortran/26246
864         * trans-decl.c (gfc_get_symbol_decl, gfc_get_fake_result_decl): Use
865         gfc_add_decl_to_function rather than gfc_finish_var_decl on length.
866
867 2006-02-13  Paul Thomas  <pault@gcc.gnu.org>
868
869         PR fortran/26074
870         PR fortran/25103
871         * resolve.c (resolve_symbol): Extend the requirement that module
872         arrays have constant bounds to those in the main program.  At the
873         same time simplify the array bounds, to avoiding trapping parameter
874         array references, and exclude automatic character length from main
875         and modules. Rearrange resolve_symbol and resolve_derived to put as
876         each flavor together, as much as is possible and move all specific
877         code for flavors FL_VARIABLE, FL_PROCEDURE and FL_PARAMETER into new
878         functions.
879         (resolve_fl_var_and_proc, resolve_fl_variable, resolve_fl_procedure):
880         New functions to do work of resolve_symbol.
881         (resolve_index_expr): New function that is called from resolved_symbol
882         and is extracted from resolve_charlen.
883         (resolve_charlen): Call this new function.
884         (resolve_fl_derived): Renamed resolve_derived to be consistent with
885         the naming of the new functions for the other flavours.  Change the
886         charlen checking so that the style is consistent with other similar
887         checks. Add the generation of the gfc_dt_list, removed from resolve_
888         symbol.
889
890         PR fortran/20861
891         * resolve.c (resolve_actual_arglist): Prevent internal procedures
892         from being dummy arguments.
893
894         PR fortran/20871
895         * resolve.c (resolve_actual_arglist): Prevent pure but non-intrinsic
896         procedures from being dummy arguments.
897
898         PR fortran/25083
899         * resolve.c (check_data_variable): Add test that data variable is in
900         COMMON.
901
902         PR fortran/25088
903         * resolve.c (resolve_call): Add test that the subroutine does not
904         have a type.
905
906 2006-02-12  Erik Edelmann  <eedelman@gcc.gnu.org>
907
908         PR fortran/25806
909         * trans-array.c (gfc_trans_allocate_array_storage): New argument
910         dealloc; free the temporary only if dealloc is true.
911         (gfc_trans_allocate_temp_array): New argument bool dealloc, to be
912         passed onwards to gfc_trans_allocate_array_storage.
913         (gfc_trans_array_constructor, gfc_conv_loop_setup): Update call to
914         gfc_trans_allocate_temp_array.
915         * trans-array.h (gfc_trans_allocate_temp_array): Update function
916         prototype.
917         * trans-expr.c (gfc_conv_function_call): Set new argument 'dealloc'
918         to gfc_trans_allocate_temp_array to false in case of functions
919         returning pointers.
920         (gfc_trans_arrayfunc_assign): Return NULL for functions returning
921         pointers.
922
923 2006-02-10  Steven G. Kargl  <kargls@comcast.net>
924
925         PR fortran/20858
926         *decl.c (variable_decl): Improve error message.  Remove initialization
927         typespec.  Wrap long line.
928         *expr.c (gfc_check_pointer_assign): Permit checking of type, kind type,
929         and rank.
930         *simplify.c (gfc_simplify_null): Ensure type, kind type, and rank
931         are set.
932
933
934 2006-02-10  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
935
936         PR fortran/14771
937         * arith.c (eval_intrinsic): Accept INTRINSIC_PARENTHESES.
938         * expr.c (check_intrinsic_op): Likewise.
939         * module.c (mio_expr): Likewise.
940
941 2006-02-09  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
942
943         * dump-parse-tree.c: Update copyright years.
944         * matchexp.c: Likewise.
945         * module.c: Likewise.
946
947         PR fortran/14771
948         * gfortran.h (gfc_intrinsic_op): Add INTRINSIC_PARENTHESES.
949         * dump-parse-tree (gfc_show_expr): Handle INTRINSIC_PARENTHESES.
950         * expr.c (simplify_intrinsic_op): Treat INTRINSIC_PARENTHESES as
951         if it were INTRINSIC_UPLUS.
952         * resolve.c (resolve_operator): Handle INTRINSIC_PARENTHESES.
953         * match.c (intrinsic_operators): Add INTRINSIC_PARENTHESES.
954         * matchexp.c (match_primary): Record parentheses surrounding
955         numeric expressions.
956         * module.c (intrinsics): Add INTRINSIC_PARENTHESES for module
957         dumping.
958         * trans-expr.c (gfc_conv_expr_op): Handle INTRINSIC_PARENTHESES.
959
960 2006-02-09  Paul Thomas  <pault@gcc.gnu.org>
961
962         PR fortran/26038
963         * trans-stmt.c (gfc_trans_allocate): Provide assumed character length
964         scalar with missing backend_decl for the hidden dummy charlen.
965
966         PR fortran/25059
967         * interface.c (gfc_extend_assign): Remove detection of non-PURE
968         subroutine in assignment interface, with gfc_error, and put it in
969         * resolve.c (resolve_code).
970
971         PR fortran/25070
972         * interface.c (gfc_procedure_use): Flag rank checking for non-
973         elemental, contained or interface procedures in call to
974         (compare_actual_formal), where ranks are checked for assumed
975         shape arrays..
976
977 2006-02-08  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
978
979         PR libfortran/25425
980         * trans-decl.c (gfc_generate_function_code): Add new argument,
981         pedantic, to set_std call.
982
983 2006-02-06  Thomas Koenig  <Thomas.Koenig@online.de>
984
985         PR libfortran/23815
986         * gfortran.texi: Document the GFORTRAN_CONVERT_UNIT environment
987         variable.
988         * invoke.texi:  Mention the "Runtime" chapter.
989         Document the -fconvert= option.
990         * gfortran.h:  Add options_convert.
991         * lang.opt:  Add fconvert=little-endian, fconvert=big-endian,
992         fconvert=native and fconvert=swap.
993         * trans-decl.c (top level):  Add gfor_fndecl_set_convert.
994         (gfc_build_builtin_function_decls):  Set gfor_fndecl_set_convert.
995         (gfc_generate_function_code):  If -fconvert was specified,
996         and this is the main program, add a call to set_convert().
997         * options.c:  Handle the -fconvert options.
998
999 2006-02-06  Roger Sayle  <roger@eyesopen.com>
1000
1001         * trans-stmt.c (gfc_evaluate_where_mask): Allow the NMASK argument
1002         to be NULL to indicate that the not mask isn't required.
1003         (gfc_trans_where_2): Remove PMASK argument.  Avoid calculating the
1004         pending mask for the last clause of a WHERE chain.  Update recursive
1005         call.
1006         (gfc_trans_forall_1): Update call to gfc_trans_where_2.
1007         (gfc_trans_where): Likewise.
1008
1009 2006-02-06  Jakub Jelinek  <jakub@redhat.com>
1010
1011         Backport from gomp-20050608-branch
1012         * trans-decl.c (create_function_arglist): Handle dummy functions.
1013
1014         * trans-decl.c (gfc_get_symbol_decl): Revert explicit setting of
1015         TYPE_SIZE_UNIT.
1016         (gfc_trans_vla_type_sizes): Also "gimplify"
1017         GFC_TYPE_ARRAY_DATAPTR_TYPE for GFC_DESCRIPTOR_TYPE_P types.
1018         * trans-array.c (gfc_trans_deferred_array): Call
1019         gfc_trans_vla_type_sizes.
1020
1021         * trans-decl.c (saved_function_decls, saved_parent_function_decls):
1022         Remove unnecessary initialization.
1023         (create_function_arglist): Make sure __result has complete type.
1024         (gfc_get_fake_result_decl): Change current_fake_result_decl into
1025         a tree chain.  For entry master, create a separate variable
1026         for each result name.  For BT_CHARACTER results, call
1027         gfc_finish_var_decl on length even if it has been already created,
1028         but not pushdecl'ed.
1029         (gfc_trans_vla_type_sizes): For function/entry result, adjust
1030         result value type, not the FUNCTION_TYPE.
1031         (gfc_generate_function_code): Adjust for current_fake_result_decl
1032         changes.
1033         (gfc_trans_deferred_vars): Likewise.  Call gfc_trans_vla_type_sizes
1034         even on result if it is assumed-length character.
1035
1036         * trans-decl.c (gfc_trans_dummy_character): Add SYM argument.
1037         Call gfc_trans_vla_type_sizes.
1038         (gfc_trans_auto_character_variable): Call gfc_trans_vla_type_sizes.
1039         (gfc_trans_vla_one_sizepos, gfc_trans_vla_type_sizes_1,
1040         gfc_trans_vla_type_sizes): New functions.
1041         (gfc_trans_deferred_vars): Adjust gfc_trans_dummy_character
1042         callers.  Call gfc_trans_vla_type_sizes on assumed-length
1043         character parameters.
1044         * trans-array.c (gfc_trans_array_bounds,
1045         gfc_trans_auto_array_allocation, gfc_trans_dummy_array_bias): Call
1046         gfc_trans_vla_type_sizes.
1047         * trans.h (gfc_trans_vla_type_sizes): New prototype.
1048
1049         * trans-decl.c (gfc_build_qualified_array): For non-assumed-size
1050         arrays without constant size, create also an index var for
1051         GFC_TYPE_ARRAY_SIZE (type).  If the type is incomplete, complete
1052         it as 0..size-1.
1053         (gfc_create_string_length): Don't call gfc_defer_symbol_init
1054         if just creating DECL_ARGUMENTS.
1055         (gfc_get_symbol_decl): Call gfc_finish_var_decl and
1056         gfc_defer_symbol_init even if ts.cl->backend_decl is already
1057         set to a VAR_DECL that doesn't have DECL_CONTEXT yet.
1058         (create_function_arglist): Rework, so that hidden length
1059         arguments for CHARACTER parameters are created together with
1060         the parameters.  Resolve ts.cl->backend_decl for CHARACTER
1061         parameters.  If the argument is a non-constant length array
1062         or CHARACTER, ensure PARM_DECL has different type than
1063         its DECL_ARG_TYPE.
1064         (generate_local_decl): Call gfc_get_symbol_decl even
1065         for non-referenced non-constant length CHARACTER parameters
1066         after optionally issuing warnings.
1067         * trans-array.c (gfc_trans_array_bounds): Set last stride
1068         to GFC_TYPE_ARRAY_SIZE (type) to initialize it as well.
1069         (gfc_trans_dummy_array_bias): Initialize GFC_TYPE_ARRAY_SIZE (type)
1070         variable as well.
1071
1072         * trans-expr.c (gfc_conv_expr_val): Fix comment typo.
1073
1074         * trans-stmt.c (gfc_trans_simple_do): Fix comment.
1075
1076 2006-02-04  Roger Sayle  <roger@eyesopen.com>
1077
1078         * dependency.c (gfc_check_dependency): Remove unused vars and nvars
1079         arguments.  Replace with an "identical" argument.  A full array
1080         reference to the same symbol is a dependency if identical is true.
1081         * dependency.h (gfc_check_dependency): Update prototype.
1082         * trans-array.h (gfc_check_dependency): Delete duplicate prototype.
1083         * trans-stmt.c: #include dependency.h for gfc_check_dependency.
1084         (gfc_trans_forall_1): Update calls to gfc_check_dependency.
1085         (gfc_trans_where_2): Likewise.  Remove unneeded variables.
1086         (gfc_trans_where_3): New function for simple non-dependent WHEREs.
1087         (gfc_trans_where): Call gfc_trans_where_3 to translate simple
1088         F90-style WHERE statements without internal dependencies.
1089         * Make-lang.in (trans-stmt.o): Depend upon dependency.h.
1090
1091 2006-02-05  H.J. Lu  <hongjiu.lu@intel.com>
1092
1093         PR fortran/26041
1094         PR fortran/26064
1095         * resolve.c (resolve_types): New function.
1096         (resolve_codes): Likewise.
1097         (gfc_resolve): Use them.
1098
1099 2006-02-05  Roger Sayle  <roger@eyesopen.com>
1100
1101         * trans-stmt.c (gfc_evaluate_where_mask): Use LOGICAL*1 for WHERE
1102         masks instead of LOGICAL*4.
1103
1104 2006-02-05  Jakub Jelinek  <jakub@redhat.com>
1105
1106         * resolve.c (resolve_symbol): Initialize constructor_expr to NULL.
1107
1108 2006-02-04  Thomas Koenig  <Thomas.Koenig@online.de>
1109
1110         PR fortran/25075
1111         check.c (identical_dimen_shape):  New function.
1112         (check_dot_product):  Use identical_dimen_shape() to check sizes
1113         for dot_product.
1114         (gfc_check_matmul):  Likewise.
1115         (gfc_check_merge):  Check conformance between tsource and fsource
1116         and between tsource and mask.
1117         (gfc_check_pack):  Check conformance between array and mask.
1118
1119 2006-02-03  Steven G. Kargl  <kargls@comcast>
1120             Paul Thomas  <pault@gcc.gnu.org>
1121
1122         PR fortran/20845
1123         * resolve.c (resolve_symbol): Default initialization of derived type
1124         component reguires the SAVE attribute.
1125
1126 2006-02-02  Steven G. Kargl  <kargls@comcast>
1127
1128         PR fortran/24958
1129         match.c (gfc_match_nullify):  Free the list from head not tail.
1130
1131         PR fortran/25072
1132         * match.c (match_forall_header): Fix internal error caused by bogus
1133         gfc_epxr pointers.
1134
1135
1136 2006-01-31  Thomas Koenig  <Thomas.Koenig@online.de>
1137
1138         PR fortran/26039
1139         expr.c (gfc_check_conformance):  Reorder error message
1140         to avoid plural.
1141         check.c(gfc_check_minloc_maxloc):  Call gfc_check_conformance
1142         for checking arguments array and mask.
1143         (check_reduction):  Likewise.
1144
1145 2006-01-30  Erik Edelmann  <eedelman@gcc.gnu.org>
1146
1147         PR fortran/24266
1148         * trans-io.c (set_internal_unit): Check the rank of the
1149         expression node itself instead of its symbol.
1150
1151 2006-01-29  Paul Thomas  <pault@gcc.gnu.org>
1152
1153         PR fortran/18578
1154         PR fortran/18579
1155         PR fortran/20857
1156         PR fortran/20885
1157         * interface.c (compare_actual_formal): Error for INTENT(OUT or INOUT)
1158         if actual argument is not a variable.
1159
1160 2006-01-28  Paul Thomas  <pault@gcc.gnu.org>
1161
1162         PR fortran/17911
1163         * expr.c (gfc_check_assign, gfc_check_pointer_assign): Emit error if
1164         the lvalue is a use associated procedure.
1165
1166         PR fortran/20895
1167         PR fortran/25030
1168         * expr.c (gfc_check_pointer_assign): Emit error if lvalue and rvalue
1169         character lengths are not the same.  Use gfc_dep_compare_expr for the
1170         comparison.
1171         * gfortran.h: Add prototype for gfc_dep_compare_expr.
1172         * dependency.h: Remove prototype for gfc_dep_compare_expr.
1173
1174 2006-01-27  Paul Thomas  <pault@gcc.gnu.org>
1175
1176         PR fortran/25964
1177         * resolve.c (resolve_function): Add GFC_ISYM_LOC to the list of
1178         generic_ids exempted from assumed size checking.
1179
1180 2006-01-27  Jakub Jelinek  <jakub@redhat.com>
1181
1182         PR fortran/25324
1183         * Make-lang.in (fortran/scanner.o): Depend on toplev.h.
1184         * lang.opt (fpreprocessed): New option.
1185         * scanner.c: Include toplev.h.
1186         (gfc_src_file, gfc_src_preprocessor_lines): New variables.
1187         (preprocessor_line): Unescape filename if there were any
1188         backslashes.
1189         (load_file): If initial and gfc_src_file is not NULL,
1190         use it rather than opening the file.  If gfc_src_preprocessor_lines
1191         has non-NULL elements, pass it to preprocessor_line.
1192         (unescape_filename, gfc_read_orig_filename): New functions.
1193         * gfortran.h (gfc_option_t): Add flag_preprocessed.
1194         (gfc_read_orig_filename): New prototype.
1195         * options.c (gfc_init_options): Clear flag_preprocessed.
1196         (gfc_post_options): If flag_preprocessed, call
1197         gfc_read_orig_filename.
1198         (gfc_handle_option): Handle OPT_fpreprocessed.
1199         * lang-specs.h: Pass -fpreprocessed to f951 if preprocessing
1200         sources.
1201
1202 2006-01-27  Erik Edelmann  <eedelman@gcc.gnu.org>
1203
1204         * symbol.c (free_old_symbol): Fix confusing comment, and add code
1205           to free old_symbol->formal.
1206
1207 2006-01-26  Paul Thomas  <pault@gcc.gnu.org>
1208
1209         PR fortran/25964
1210         * resolve.c (resolve_function): Exclude statement functions from
1211         global reference checking.
1212
1213         PR fortran/25084
1214         PR fortran/20852
1215         PR fortran/25085
1216         PR fortran/25086
1217         * resolve.c (resolve_function): Declare a gfc_symbol to replace the
1218         references through the symtree to the symbol associated with the
1219         function expresion. Give error on reference to an assumed character
1220         length function is defined in an interface or an external function
1221         that is not a dummy argument.
1222         (resolve_symbol): Give error if an assumed character length function
1223         is array-valued, pointer-valued, pure or recursive. Emit warning
1224         that character(*) value functions are obsolescent in F95.
1225
1226         PR fortran/25416
1227         * trans-expr.c (gfc_conv_function_call): The above patch to resolve.c
1228         prevents any assumed character length function call from getting here
1229         except intrinsics such as SPREAD. In this case, ensure that no
1230         segfault occurs from referencing non-existent charlen->length->
1231         expr_type and provide a backend_decl for the charlen from the charlen
1232         of the first actual argument.
1233
1234         Cure temp name confusion.
1235         * trans-expr.c (gfc_get_interface_mapping_array): Change name of
1236         temporary from "parm" to "ifm" to avoid clash with temp coming from
1237         trans-array.c.
1238
1239 2006-01-25  Erik Edelmann  <eedelman@gcc.gnu.org>
1240
1241         PR fortran/25716
1242         * symbol.c (free_old_symbol): New function.
1243         (gfc_commit_symbols): Use it.
1244         (gfc_commit_symbol): New function.
1245         (gfc_use_derived): Use it.
1246         * gfortran.h: Add prototype for gfc_commit_symbol.
1247         * intrinsic.c (gfc_find_function): Search in 'conversion'
1248         if not found in 'functions'.
1249         (gfc_convert_type_warn): Add a symtree to the new
1250         expression node, and commit the new symtree->n.sym.
1251         * resolve.c (gfc_resolve_index): Make sure typespec is
1252         properly initialized.
1253
1254 2006-01-23  Paul Thomas  <pault@gcc.gnu.org>
1255
1256         PR fortran/25901
1257         * decl.c (get_proc_name): Replace subroutine and function attributes
1258         in "already defined" test by the formal arglist pointer being non-NULL.
1259
1260         Fix regression in testing of admissability of attributes.
1261         * symbol.c (gfc_add_attribute): If the current_attr has non-zero
1262         intent, do not do the check for a dummy being used.
1263         * decl.c (attr_decl1): Add current_attr.intent as the third argument
1264         in the call to gfc_add_attribute.
1265         * gfortran.h: Add the third argument to the prototype for
1266         gfc_add_attribute.
1267
1268 2006-01-21  Joseph S. Myers  <joseph@codesourcery.com>
1269
1270         * gfortranspec.c (lang_specific_driver): Update copyright notice
1271         date.
1272
1273 2006-01-21  Paul Thomas  <pault@gcc.gnu.org>
1274
1275         PR fortran/25124
1276         PR fortran/25625
1277         * decl.c (get_proc_name): If there is an existing
1278         symbol in the encompassing namespace, call errors
1279         if it is a procedure of the same name or the kind
1280         field is set, indicating a type declaration.
1281
1282         PR fortran/20881
1283         PR fortran/23308
1284         PR fortran/25538
1285         PR fortran/25710
1286         * decl.c (add_global_entry): New function to check
1287         for existing global symbol with this name and to
1288         create new one if none exists.
1289         (gfc_match_entry): Call add_global_entry before
1290         matching argument lists for subroutine and function
1291         entries.
1292         * gfortran.h: Prototype for existing function,
1293         global_used.
1294         * resolve.c (resolve_global_procedure): New function
1295         to check global symbols for procedures.
1296         (resolve_call, resolve_function): Calls to this
1297         new function for non-contained and non-module
1298         procedures.
1299         * match.c (match_common): Add check for existing
1300         global symbol, creat one if none exists and emit
1301         error if there is a clash.
1302         * parse.c (global_used): Remove static and use the
1303         gsymbol name rather than the new_block name, so that
1304         the function can be called from resolve.c.
1305         (parse_block_data, parse_module, add_global_procedure):
1306         Improve checks for existing gsymbols.  Emit error if
1307         already defined or if references were to another type.
1308         Set defined flag.
1309
1310         PR fortran/PR24276
1311         * trans-expr.c (gfc_conv_aliased_arg): New function called by 
1312         gfc_conv_function_call that coverts an expression for an aliased
1313         component reference to a derived type array into a temporary array
1314         of the same type as the component.  The temporary is passed as an
1315         actual argument for the procedure call and is copied back to the
1316         derived type after the call.
1317         (is_aliased_array): New function that detects an array reference
1318         that is followed by a component reference.
1319         (gfc_conv_function_call): Detect an aliased actual argument with
1320         is_aliased_array and convert it to a temporary and back again
1321         using gfc_conv_aliased_arg.
1322
1323 2006-01-19  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
1324
1325         * gfortranspec.c: Update copyright years.
1326         * trans.c: Likewise.
1327         * trans-array.c: Likewise.
1328         * trans-array.h: Likewise.
1329         * trans-decl.c: Likewise.
1330         * trans-stmt.c: Likewise.
1331         * trans-stmt.h: Likewise.
1332         * trans-types.c: Likewise.
1333
1334 2006-01-18  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
1335
1336         PR fortran/18540
1337         PR fortran/18937
1338         * gfortran.h (BBT_HEADER): Move definition up.
1339         (gfc_st_label): Add BBT_HEADER, remove 'prev' and 'next'.
1340         * io.c (format_asterisk): Adapt initializer.
1341         * resolve.c (resolve_branch): Allow FORTRAN 66 cross-block GOTOs
1342         as extension.
1343         (warn_unused_label): Take gfc_st_label label as argument, adapt to
1344         new data structure.
1345         (gfc_resolve): Adapt call to warn_unused_label.
1346         * symbol.c (compare_st_labels): New function.
1347         (gfc_free_st_label, free_st_labels, gfc_get_st_label): Convert to
1348         using balanced binary tree.
1349         * decl.c (match_char_length, gfc_match_old_kind_spec): Do away
1350         with 'cnt'.
1351         (warn_unused_label): Adapt to binary tree.
1352         * match.c (gfc_match_small_literal_int): Only set cnt if non-NULL.
1353         * primary.c (match_kind_param): Do away with cnt.
1354
1355 2006-01-18  Paul Thomas  <pault@gcc.gnu.org>
1356
1357         PR fortran/20869
1358         PR fortran/20875
1359         PR fortran/25024
1360         * symbol.c (check_conflict): Add pointer valued elemental
1361         functions and internal procedures with the external attribute
1362         to the list of conflicts.
1363         (gfc_add_attribute): New catch-all function to perform the
1364         checking of symbol attributes for attribute declaration
1365         statements.
1366         * decl.c (attr_decl1): Call gfc_add_attribute for each of -
1367         (gfc_match_external, gfc_match_intent, gfc_match_intrinsic,
1368         gfc_match_pointer, gfc_match_dimension, gfc_match_target):
1369         Remove spurious calls to checks in symbol.c.  Set the
1370         attribute directly and use the call to attr_decl() for
1371         checking.
1372         * gfortran.h:  Add prototype for gfc_add_attribute.
1373
1374         PR fortran/25785
1375         * resolve.c (resolve_function): Exclude PRESENT from assumed size
1376         argument checking. Replace strcmp's with comparisons with generic
1377         codes.
1378
1379 2006-01-16  Rafael \81Ávila de Esp\81índola  <rafael.espindola@gmail.com>
1380
1381         * gfortranspec.c (lang_specific_spec_functions): Remove.
1382
1383 2006-01-16  Richard Guenther  <rguenther@suse.de>
1384
1385         * trans-stmt.c (gfc_trans_if_1): Use fold_buildN and build_int_cst.
1386         (gfc_trans_arithmetic_if): Likewise.
1387         (gfc_trans_simple_do): Likewise.
1388         (gfc_trans_do): Likewise.
1389         (gfc_trans_do_while): Likewise.
1390         (gfc_trans_logical_select): Likewise.
1391         (gfc_trans_forall_loop): Likewise.
1392         (generate_loop_for_temp_to_lhs): Likewise.
1393         (generate_loop_for_rhs_to_temp): Likewise.
1394         (gfc_trans_allocate): Likewise.
1395         * trans.c (gfc_add_expr_to_block): Do not fold expr again.
1396
1397 2006-01-16  Richard Guenther  <rguenther@suse.de>
1398
1399         * trans-expr.c (gfc_conv_function_call): Use fold_build2.
1400         * trans-stmt.c (gfc_trans_goto): Likewise.  Use build_int_cst.
1401         * trans.c (gfc_trans_runtime_check): Don't fold the condition
1402         again.
1403
1404 2006-01-13  Steven G. Kargl  <kargls@comcast.net>
1405
1406         PR fortran/25756
1407         * symbol.c (gfc_free_st_label): Give variable meaningful name. Remove
1408         unneeded parenthesis. Fix-up the head of the list (2 lines gleaned
1409         from g95).
1410
1411 2006-01-13  Diego Novillo  <dnovillo@redhat.com>
1412
1413         * trans.c (gfc_add_expr_to_block): Do not fold tcc_statement
1414         nodes.
1415
1416 2006-01-11  Tobias Schl\81üter  <tobias.schlueter@physik.uni-muenchen.de>
1417
1418         * parse.c (next_fixed): Remove superfluous string concatenation.
1419
1420 2006-01-11  Bernhard Fischer  <rep.nop@aon.at>
1421
1422         PR fortran/25486
1423         * scanner.c (load_line): use maxlen to determine the line-length used
1424         for padding lines in fixed form.
1425
1426 2006-01-11  Paul Thomas  <pault@gcc.gnu.org>
1427
1428         PR fortran/25730
1429         * trans-types.c (copy_dt_decls_ifequal): Copy backend decl for
1430         character lengths.
1431
1432 2006-01-09  Andrew Pinski  <pinskia@physics.uc.edu>
1433
1434         fortran/24936
1435         * trans-stmt.c (gfc_trans_pointer_assign_need_temp): Use fold_convert
1436         to avoid type mismatch.
1437
1438 2006-01-09  Andrew Pinski  <pinskia@physics.uc.edu>
1439
1440         PR fortran/21977
1441         * trans-decl.c (gfc_generate_function_code): Move the NULLing of
1442         current_fake_result_decl down to below generate_local_vars.
1443
1444 2006-01-09  Feng Wang  <fengwang@nudt.edu.cn>
1445
1446         PR fortran/12456
1447         * trans-expr.c (gfc_to_single_character): New function that converts
1448         string to single character if its length is 1.
1449         (gfc_build_compare_string):New function that compare string and handle
1450         single character specially.
1451         (gfc_conv_expr_op): Use gfc_build_compare_string.
1452         (gfc_trans_string_copy): Use gfc_to_single_character.
1453         * trans-intrinsic.c (gfc_conv_intrinsic_strcmp): Use
1454         gfc_build_compare_string.
1455         * trans.h (gfc_build_compare_string): Add prototype.
1456
1457 2006-01-09  Feng Wang  <fengwang@nudt.edu.cn>
1458
1459         * simplify.c (gfc_simplify_char): Use UCHAR_MAX instead of literal
1460         constant.
1461         (gfc_simplify_ichar): Get the result from unsinged char and in the
1462         range 0 to UCHAR_MAX instead of CHAR_MIN to CHAR_MAX.
1463
1464 2006-01-08  Erik Edelmann  <eedelman@gcc.gnu.org>
1465
1466         PR fortran/25093
1467         * resolve.c (resolve_fntype): Check that PUBLIC functions
1468         aren't of PRIVATE type.
1469
1470 2006-01-07  Tobias Schl"uter  <tobias.schlueter@physik.uni-muenchen.de>
1471
1472         * decl.c (gfc_match_function_decl): Correctly error out in case of
1473         omitted function argument list.
1474
1475 2006-01-07  Paul Thomas  <pault@gcc.gnu.org>
1476
1477         PR fortran/22146
1478         * trans-array.c (gfc_reverse_ss): Remove static attribute.
1479         (gfc_walk_elemental_function_args): Replace gfc_expr * argument for
1480         the function call with the corresponding gfc_actual_arglist*.  Change
1481         code accordingly.
1482         (gfc_walk_function_expr): Call to gfc_walk_elemental_function_args
1483         now requires the actual argument list instead of the expression for
1484         the function call.
1485         * trans-array.h: Modify the prototype for gfc_walk_elemental_function_args
1486         and provide a prototype for gfc_reverse_ss.
1487         * trans-stmt.h (gfc_trans_call): Add the scalarization code for the case
1488         where an elemental subroutine has array valued actual arguments.
1489
1490         PR fortran/25029
1491         PR fortran/21256
1492         PR fortran/20868
1493         PR fortran/20870
1494         * resolve.c (check_assumed_size_reference): New function to check for upper
1495         bound in assumed size array references.
1496         (resolve_assumed_size_actual): New function to do a very restricted scan
1497         of actual argument expressions of those procedures for which incomplete
1498         assumed size array references are not allowed.
1499         (resolve_function, resolve_call): Switch off assumed size checking of
1500         actual arguments, except for elemental procedures and intrinsic
1501         inquiry functions, in some circumstances.
1502         (resolve_variable): Call check_assumed_size_reference.
1503
1504 2006-01-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
1505
1506         PR fortran/24268
1507         * io.c (next_char_not_space): New function that returns the next
1508         character that is not white space.
1509         (format_lex): Use the new function to skip whitespace within
1510         a format string.
1511
1512 2006-01-05  Erik Edelmann  <eedelman@gcc.gnu.org>
1513
1514         PR fortran/23675
1515         * expr.c (gfc_expr_set_symbols_referenced): New function.
1516         * gfortran.h: Add a function prototype for it.
1517         * resolve.c (resolve_function): Use it for
1518         use associated character functions lengths.
1519         * expr.c, gfortran.h, resolve.c: Updated copyright years.
1520
1521 2006-01-03  Steven G. Kargl  <kargls@comcast.net>
1522
1523         PR fortran/25101
1524         * resolve.c (resolve_forall_iterators):  Check for scalar variables;
1525         Check stride is nonzero.
1526
1527 2006-01-02  Steven G. Kargl  <kargls@comcast.net>
1528
1529         PR fortran/24640
1530         * parse.c (next_free): Check for whitespace after the label.
1531         * match.c (gfc_match_small_literal_int): Initialize cnt variable.
1532
1533 2006-01-01  Steven G. Kargl  <kargls@comcast.net>
1534
1535         * ChangeLog: Split previous years into ...
1536         * ChangeLog-2002: here.
1537         * ChangeLog-2003: here.
1538         * ChangeLog-2004: here.
1539         * ChangeLog-2005: here.