OSDN Git Service

2007-02-14 Steven G. Kargl <kargl@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / ChangeLog
1 2007-02-14  Steven G. Kargl  <kargl@gcc.gnu.org>
2
3         PR fortran/30799
4         * primary.c (match_logical_constant): Return MATCH_ERROR on invalid
5         kind.
6
7 2007-02-14  Steven G. Kargl  <kargl@gcc.gnu.org>
8
9         * misc.c (gfc_typename): Fix potential buffer overflow.
10
11 2007-02-13  Paul Thomas  <pault@gcc.gnu.org>
12
13         PR fortran/30554
14         * module.c (read_module): Set pointer_info to referenced if the
15         symbol has no namespace.
16
17 2007-02-12  Nick Clifton  <nickc@redhat.com>
18
19         * lang.opt:  Add Warning attribute to warning options.
20
21 2007-02-11  Daniel Franke  <franke.daniel@gmail.com>
22
23         * intrinsic.texi (HOSTNM): Fix typographical error in syntax.
24         (SLEEP): Added section and documentation.
25
26 2007-02-11  Tobias Schlüter  <tobi@gcc.gnu.org>
27
28         PR fortran/30478
29         * decl.c (add_init_expr_to_sym): Remove ENUM specific code.
30         (variable_decl): Likewise.  Rewrap comment.
31         (match_attr_spec): Remove ENUM specific code.
32         (gfc_match_enum): Fix typo in error message.
33         (enumerator_decl): New function.
34         (gfc_match_enumerator_def): Use enumerator_decl instead of
35         variable_decl.  Adapt code accordingly.
36
37 2007-02-11  Paul Thomas  <pault@gcc.gnu.org>
38
39         PR fortran/30554
40         * module.c (find_symtree_for_symbol): New function to return
41         a symtree that is not a "unique symtree" given a symbol.
42         (read_module): Do not automatically set pointer_info to
43         referenced because this inhibits the generation of a unique
44         symtree.  Recycle the existing symtree if possible by calling
45         find_symtree_for_symbol.
46
47         PR fortran/30319
48         * decl.c (add_init_expr_to_sym): Make new charlen for an array
49         constructor initializer.
50
51 2007-02-10  Richard Henderson  <rth@redhat.com>, Jakub Jelinek  <jakub@redhat.com>
52
53         * f95-lang.c (gfc_init_builtin_functions): Add __emutls_get_address
54         and __emutls_register_common.
55         * openmp.c (gfc_match_omp_threadprivate): Don't error if !have_tls.
56         * trans-common.c (build_common_decl): Don't check have_tls.
57         * trans-decl.c (gfc_finish_var_decl): Likewise.
58         * types.def (BT_WORD, BT_FN_PTR_PTR): New.
59         (BT_FN_VOID_PTR_WORD_WORD_PTR): New.
60
61 2007-02-09  Tobias Burnus  <burnus@net-b.de>
62
63         PR fortran/30512
64         * trans-intrinsic.c (gfc_conv_intrinsic_minmaxloc,
65           gfc_conv_intrinsic_minmaxval): Use HUGE-1 for most negative integer.
66
67 2007-02-09  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
68
69         PR fortran/30720
70         * trans-array.c (gfc_trans_create_temp_array): Remove use of the
71         function argument. Always generate code for negative extent.
72         Simplify said code.
73         * trans-array.h (gfc_trans_create_temp_array): Change prototype.
74         * trans-expr.c (gfc_conv_function_call): Remove use of last argument
75         of gfc_trans_create_temp_array.
76         * trans-intrinsic.c (gfc_conv_intrinsic_array_transfer): Likewise.
77         * trans-stmt.c (gfc_conv_elemental_dependencies): Likewise.
78
79 2007-02-08  Roger Sayle  <roger@eyesopen.com>
80
81         * trans-stmt.c (gfc_trans_forall_1): Optimize the cases where the
82         mask expression is a compile-time constant (".true." or ".false.").
83
84 2007-02-04  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
85
86         PR fortran/30611
87         * trans-intrinsic.c (gfc_conv_intrinsic_repeat): Evaluate
88         arguments only once. Generate check that NCOPIES argument is not
89         negative.
90
91 2007-02-04  Steven G. Kargl <kargl@gcc.gnu.org>
92
93         PR fortran/30605
94         * fortran/invoke.texi: Update documentation.
95         * fortran/options.c (gfc_post_options): Deal with tabs with -std=f2003
96         and -pedantic.
97
98 2007-02-03  Kazu Hirata  <kazu@codesourcery.com>
99
100         * trans-array.c: Fix a comment typo.
101
102 2007-02-03  Paul Thomas  <pault@gcc.gnu.org>
103
104         PR fortran/30514
105         * array.c (match_array_element_spec): If the length of an array is
106         negative, adjust the upper limit to make it zero length.
107
108         PR fortran/30660
109         * resolve.c (pure_function, resolve_function): Initialize name to
110         null to clear up build warnings.
111         (resolve_fl_variable): Look at components explicitly to check for
112         default initializer, rather than using gfc_default_initializer.
113
114 2007-02-02  Steven G. Kargl <kargl@gcc.gnu.org>
115
116         PR fortran/30683
117         * resolve.c (resolve_generic_f): Check for non-NULL sym.
118
119 2007-02-02  Roger Sayle  <roger@eyesopen.com>
120
121         * trans.c (gfc_build_array_ref): Use STRIP_TYPE_NOPS to eliminate
122         NON_LVALUE_EXPR nodes and useless type conversions.
123
124 2007-02-02  Paul Thomas  <pault@gcc.gnu.org>
125
126         PR fortran/30284
127         PR fortran/30626
128         * trans-expr.c (gfc_conv_aliased_arg): Remove static attribute
129         from function and make sure that substring lengths are
130         translated.
131         (is_aliased_array): Remove static attribute.
132         * trans.c : Add prototypes for gfc_conv_aliased_arg and
133         is_aliased_array.
134         * trans-io.c (set_internal_unit): Add the post block to the
135         arguments of the function.  Use is_aliased_array to check if
136         temporary is needed; if so call gfc_conv_aliased_arg.
137         (build_dt): Pass the post block to set_internal_unit and
138         add to the block after all io activiy is done.
139
140 2007-02-01  Roger Sayle  <roger@eyesopen.com>
141
142         * trans-array.c (gfc_conv_expr_descriptor): We don't need to use
143         a temporary array to pass a constant non-character array constructor.
144         Generalize the descriptor generation code to handle scalarizer
145         "info" without an array reference.
146
147 2007-02-01  Roger Sayle  <roger@eyesopen.com>
148
149         * dependency.c (gfc_check_dependency) <EXPR_ARRAY>: Implement
150         dependency checking for array constructors.
151
152 2007-02-01  Roger Sayle  <roger@eyesopen.com>
153
154         * trans-stmt.c (compute_overall_iter_number): Document function
155         arguments.  Generalize "unconditional forall nest with constant
156         bounds" optimization to eliminate unconditional inner loops with
157         constant bounds.
158
159 2007-01-31  Tobias Burnus  <burnus@net-b.de>
160
161         PR fortran/30520
162         * interface.c (compare_actual_formal): Check conformance between
163           actual and VOLATILE dummy arguments.
164         * symbol.c (gfc_add_volatile): Allow setting of VOLATILE
165           multiple times in different scopes.
166         * decl.c (gfc_match_volatile): Search symbol in host association.
167
168 2007-01-31  Kazu Hirata  <kazu@codesourcery.com>
169
170         * simplify.c, trans-array.c: Fix comment typos.
171
172 2007-01-30  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
173
174         * invoke.texi (Code Gen Options): Fix abbreviation typo.
175         * intrinsic.texi (ACCESS, LSHIFT, RSHIFT): Fix typos.
176
177 2007-01-30  Steve Ellcey  <sje@cup.hp.com>
178
179         PR fortran/30432
180         * trans-types.c (gfc_get_function_type):  Do not add void_type_node
181         to empty arg list.
182         * trans-decl.c (create_function_arglist): Change assert.
183
184 2007-01-29  Paul Thomas  <pault@gcc.gnu.org>
185
186         PR fortran/30554
187         * module.c (read_module): If a symbol is excluded by an ONLY
188         clause, check to see if there is a symtree already loaded. If
189         so, attach the symtree to the pointer_info.
190
191 2007-01-28  Thomas Koenig  <Thomas.Koenig@online.de>
192
193         PR libfortran/30389
194         * gfortran.h:  Remove gfc_simplify_init_1.
195         * arith.h:  Remove third argument from gfc_compare_string.
196         * arith.c(gfc_compare_expression):  Remove third argument
197         from call to gfc_compare_string.
198         (gfc_compare_string):  Remove third argument xcoll_table.
199         Remove use of xcoll_table.
200         * misc.c(gfc_init_1):  Remove call to gfc_simplify_init_1.
201         * simplify.c(ascii_table):  Remove.
202         (xascii_table): Likewise.
203         (gfc_simplify_achar):  ICE if extract_int fails.  Remove use of
204         ascii_table.  Warn if -Wsurprising and value < 0 or > 127.
205         (gfc_simplify_char):  ICE if extract_int fails. Error if
206         value < 0 or value > 255.
207         (gfc_simplify_iachar):  Remove use of xascii_table.
208         Char values outside of 0..255 are an ICE.
209         (gfc_simplify_lge):  Remove use of xascii_table.
210         (gfc_simplify_lgt):  Likewise.
211         (gfc_simplify_lle):  Likewise.
212         (gfc_simplify_llt):  Likewise.
213         (invert_table):  Remove.
214         (gfc_simplify_init_1):  Remove.
215
216 2007-01-27  Roger Sayle  <roger@eyesopen.com>
217
218         * trans-stmt.c (forall_info): Replace the next_nest and outer
219         fields that previously implemented a doubly-linked list with a
220         single prev_nest field (singly-linked list).
221         (gfc_trans_nested_forall_loop): The nested_forall_info argument
222         now denotes the innermost FORALL in the loop nest.
223         (compute_overall_iter_number): Use prev_nest instead of next_nest.
224         (gfc_trans_forall_1): Link/cons the new "info" to the head of the
225         nested_forall_info linked list.  Free the current "info" when done.
226
227 2007-01-27  Paul Thomas  <pault@gcc.gnu.org>
228
229         PR fortran/30407
230         * trans-expr.c (gfc_conv_operator_assign): New function.
231         * trans.h : Add prototype for gfc_conv_operator_assign.
232         * trans-stmt.c (gfc_trans_where_assign): Add a gfc_symbol for
233         a potential operator assignment subroutine.  If it is non-NULL
234         call gfc_conv_operator_assign instead of the first assignment.
235         ( gfc_trans_where_2): In the case of an operator assignment,
236         extract the argument expressions from the code for the
237         subroutine call and pass the symbol to gfc_trans_where_assign.
238         resolve.c (resolve_where, gfc_resolve_where_code_in_forall,
239         gfc_resolve_forall_body): Resolve the subroutine call for
240         operator assignments.
241
242 2007-01-26  Steven Bosscher  <stevenb.gcc@gmail.com>
243             Steven G. Kargl <kargl@gcc.gnu.org>
244
245         PR fortran/30278
246         * fortran/io.c (next_char): Deal with backslash escaped characters.
247         Issue warnings in non -std=gnu cases.
248         * fortran/primary.c (next_string_char): Issue warnings in non
249
250 2007-01-26  Tobias Burnus  <burnus@net-b.de>
251
252         * lang-specs.h: Add support for .f03 and .F03 extensions.
253         * gfortran.texi: Document .f03 extension.
254         * options.c (form_from_filename): Recognize .f03.
255
256 2007-01-25  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
257
258         PR fortran/30437
259         * lang.opt (Wall): Remove RejectNegative.
260         * options.c (gfc_handle_option): Wall can be disabled.
261         (set_Wall): Add a parameter for disabling Wall.
262         
263 2007-01-23  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
264
265         PR fortran/30532
266         * scanner.c (load_line): Remove check fot ctrl-z and don't gobble.
267         
268 2007-01-23  Paul Thomas  <pault@gcc.gnu.org>
269
270         PR fortran/30481
271         * match.c (gfc_match_namelist): Add check for assumed size character
272         in namelist and provide error if found.
273
274 2007-01-21  Brooks Moses  <brooks.moses@codesourcery.com>
275
276         * intrinsic.texi (ACHAR): Added cross-references.
277         (CHAR): Put cross-references in alphabetical order.
278         (IACHAR): Added cross-references.
279         (ICHAR): Added cross-references.
280
281 2007-01-20  Brooks Moses  <brooks.moses@codesourcery.com>
282
283         * intrinsic.texi: Edited all "Syntax" examples to a consistent form.
284         (MAXVAL): Corrected description of result characteristics.
285         (MINVAL): Same.
286         (UMASK): Added documentation.
287
288 2007-01-20  Steven G. Kargl  <kargl@gcc.gnu.org>
289
290         * openmp.c, matchexp.c, module.c, scanner.c, resolve.c, st.c,
291         parse.c, primary.c, options.c, misc.c, simplify.c:  Next installment
292         in the massive whitespace patch.
293
294 2007-01-20  Roger Sayle  <roger@eyesopen.com>
295
296         * module.c (mio_array_ref): The dimen_type fields of an array ref
297         are an enumerated type and can't be read/written directly with a
298         call to mio_integer.  Instead loop over and cast each element.
299
300 2007-01-20  Roger Sayle  <roger@eyesopen.com>
301
302         * dependency.c (gfc_full_array_ref_p): Check that ref->next is NULL,
303         i.e. that the ARRAY_REF doesn't mention components.
304         * trans-array.c (gfc_constant_array_constructor_p): Export external
305         function renamed from constant_array_constructor_p.
306         (gfc_build_constant_array_constructor): Export.
307         (gfc_trans_array_constructor): Update call to the renamed function
308         constant_array_constructor_p.
309         * trans-array.h (gfc_constant_array_constructor_p): Prototype here.
310         (gfc_build_constant_array_constructor): Likewise.
311         * trans-expr.c (gfc_build_memcpy_call): New helper function split
312         out from gfc_trans_array_copy.
313         (gfc_trans_array_copy): Use gfc_build_memcpy_call.
314         (gfc_trans_array_constructor_copy): New function to optimize
315         assigning an entire array from a constant array constructor.
316         (gfc_trans_assignment): Call gfc_trans_array_constructor_copy
317         when appropriate.
318
319 2007-01-20  Roger Sayle  <roger@eyesopen.com>
320
321         * trans-intrinsic.c (gfc_conv_intrinsic_sign): New branchless
322         implementation for the SIGN intrinsic with integral operands.
323         (gfc_conv_intrinsic_minmax): Fix whitespace.
324
325 2007-01-20  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
326
327         * gfortran.h (gfc_options_t): Add flag_allow_leading_underscore.
328         * lang.opt: Add -fallow-leading-underscore.
329         * match.c (gfc_match_name): Allow leading underscore in symbol
330         name if -fallow-leading-underscore is used.
331         * symbol.c (gfc_get_default_type): Add special case for symbol
332         names beginning with an underscore.
333         * trans-decl.c (gfc_get_extern_function_decl,
334         gfc_build_intrinsic_function_decls): Add _gfortran prefix to
335         library symbols selected_int_kind, selected_real_kind and 
336         all specifics.
337         * options.c (gfc_init_options, gfc_handle_option): Handle the
338         new -fallow-leading-underscore option.
339
340 2007-01-20  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
341
342         PR fortran/30446
343         * options.c (gfc_handle_module_path_options): Path used in -J
344         option is now added to the module search path.
345
346 2007-01-20  Richard Guenther  <rguenther@suse.de>
347
348         PR fortran/30223
349         * f95-lang.c (gfc_init_builtin_functions): Provide cbrt and
350         cexpi builtins if we have TARGET_C99_FUNCTIONS.  Provide
351         sincos builtins if the target has sincos.
352
353 2007-01-19  Brooks Moses  <brooks.moses@codesourcery.com>
354
355         * intrinsic.texi (MATMUL): Corrected a typo.
356         (MAX): Separated @var arguments.
357         (MIN): Separated @var arguments.
358
359 2007-01-19  Brooks Moses  <brooks.moses@codesourcery.com>
360
361         * intrinsic.texi: general whitespace cleanup.
362         (menu): Added TIME8, removed UNMASK.
363         (AINT): Clarified argument requirement.
364         (ANINT): Clarified argument requirement.
365         (CEILING): Clarified argument requirement.
366         (CHAR): Clarified argument requirement.
367         (CMPLX): Clarified argument requirement.
368         (DCMPLX): Clarified argument requirement.
369         (FGET): Line rewrapping.
370         (FLOOR): Clarified argument requirement.
371         (GMTIME): Added documentation.
372         (IAND): Added cross-reference.
373         (IBCLR): Added cross-reference.
374         (IBSET): Added cross-reference.
375         (IEOR): Added cross-reference.
376         (INT): Collapsed examples, clarified argument requirement.
377         (IOR): Added cross-references.
378         (LEN_TRIM): Corrected result kind.
379         (LINK): Added cross-reference.
380         (LLT): Removed "documentation pending".
381         (LOGICAL): Added documentation.
382         (LSHIFT): Added documentation.
383         (LTIME): Added documentation.
384         (MATMUL): Added documentation.
385         (MAX): Added documentation.
386         (MAXLOC): Added documentation.
387         (MAXVAL): Added documentation.
388         (MERGE): Added documentation.
389         (MIN): Added documentation.
390         (MINLOC): Added documentation.
391         (MINVAL): Added documentation.
392         (MVBITS): Moved to correct place, added documentation.
393         (NOT): Added documentation.
394         (PERROR): Added documentation.
395         (RAN): Moved to correct place, added documentation.
396         (REAL): Clarified argument requirement.
397         (RENAME): Added documentation.
398         (RSHIFT): Clarified argument requirement.
399         (SIGN): Corrected table specification.
400         (SYMLNK): Added documentation.
401         (SYSTEM): Added documentation.
402         (TIME): Added documentation.
403         (TIME8): Added section and documentation.
404         (UNMASK): Removed erroneous section.
405
406 2007-01-18  H.J. Lu  <hongjiu.lu@intel.com>
407
408         * trans-stmt.c (compute_overall_iter_number): Fix a typo.
409
410 2007-01-18  Roger Sayle  <roger@eyesopen.com>
411
412         * trans-expr.c (copyable_array_p): Consider user derived types without
413         allocatable components to be copyable.
414
415 2007-01-18  Roger Sayle  <roger@eyesopen.com>
416
417         * trans-stmt.c (compute_overall_iter_number): Enhance to precompute
418         the number of interations in unconditional FORALL nests with constant
419         bounds.
420
421 2007-01-18  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
422             Tobias Burnus  <burnus@net-b.de>
423
424         PR libfortran/29649
425         * gfortran.h (gfc_option_t): Add flag_dump_core.
426         * lang.opt: Add -fdump-core option.
427         * invoke.texi: Document the new options.
428         * trans-decl.c (gfc_build_builtin_function_decls): Add new
429           options to the call to set_std.
430         * options.c (gfc_init_options, gfc_handle_option): Set the
431           new options.
432
433 2007-01-17  Paul Thomas  <pault@gcc.gnu.org>
434
435         PR fortran/30476
436         * module.c (load_generic_interfaces): Make the marking of the
437         symbol as ambiguous conditional on the module names being
438         different.
439         (write_generic): Ensure that the generic interface has a
440         non-NULL module field.
441
442 2007-01-16  Roger Sayle  <roger@eyesopen.com>
443
444         PR fortran/30404
445         * trans-stmt.c (forall_info): Remove pmask field.
446         (gfc_trans_forall_loop): Remove NVAR argument, instead assume that
447         NVAR covers all the interation variables in the current forall_info.
448         Add an extra OUTER parameter, which specified the loop header in
449         which to place mask index initializations.
450         (gfc_trans_nested_forall_loop): Remove NEST_FLAG argument.
451         Change the semantics of MASK_FLAG to only control the mask in the
452         innermost loop.
453         (compute_overall_iter_number): Optimize the trivial case of a
454         top-level loop having a constant number of iterations.  Update
455         call to gfc_trans_nested_forall_loop.  Calculate the number of
456         times the inner loop will be executed, not to size of the 
457         iteration space.
458         (allocate_temp_for_forall_nest_1): Reuse SIZE as BYTESIZE when
459         sizeof(type) == 1.  Tidy up.
460         (gfc_trans_assign_need_temp): Remove NEST_FLAG argument from calls
461         to gfc_trans_nested_forall_loop.
462         (gfc_trans_pointer_assign_need_temp): Likewise.
463         (gfc_trans_forall_1): Remove unused BYTESIZE, TMPVAR, SIZEVAR and
464         LENVAR local variables.  Split mask allocation into a separate
465         hunk/pass from mask population.  Use allocate_temp_for_forall_nest
466         to allocate the FORALL mask with the correct size.  Update calls
467         to gfc_trans_nested_forall_loop.
468         (gfc_evaluate_where_mask): Update call to
469         gfc_trans_nested_forall_loop.
470         (gfc_trans_where_2): Likewise.
471
472 2007-01-15  Paul Thomas  <pault@gcc.gnu.org>
473
474         PR fortran/28172
475         * trans-stmt.c (gfc_trans_call): If it does not have one, get
476         a backend_decl for an alternate return.
477
478         PR fortran/29389
479         * resolve.c (pure_function): Statement functions are pure. Note
480         that this will have to recurse to comply fully with F95.
481
482         PR fortran/29712
483         * resolve.c (resolve_function): Only a reference to the final
484         dimension of an assumed size array is an error in an inquiry
485         function.
486
487         PR fortran/30283
488         * resolve.c (resolve_function): Make sure that the function
489         expression has a type.
490
491 2007-01-14  Paul Thomas  <pault@gcc.gnu.org>
492
493         PR fortran/30410
494         * trans-decl.c (gfc_sym_mangled_function_id): Module, external
495         symbols must not have the module name prepended.
496
497 2007-01-11  Thomas Koenig  <Thomas.Koenig@online.de>
498
499         PR libfortran/30415
500         * iresolve.c (gfc_resolve_maxloc):  If the rank
501         of the return array is nonzero and we process an
502         integer array smaller than default kind, coerce
503         the array to default integer.
504         * iresolve.c (gfc_resolve_minloc):  Likewise.
505
506 2007-01-11  Brooks Moses  <brooks.moses@codesourcery.com>
507
508         * simplify.c: Update copyright to 2007.
509         * scanner.c: Same.
510
511 2007-01-11  Francois-Xavier Coudert  <coudert@clipper.ens.fr>
512
513         PR fortran/30430
514         * scanner.c (gfc_release_include_path): Free gfc_option.module_dir
515         only once!
516
517 2007-01-09  Brooks Moses  <brooks.moses@codesourcery.com>
518
519         * simplify.c (gfc_simplify_ibclr): Fix POS comparison.
520         (gfc_simplify_ibset): Same.
521
522 2007-01-09  Brooks Moses  <brooks.moses@codesourcery.com>
523
524         PR 30381
525         PR 30420
526         * simplify.c (convert_mpz_to_unsigned): New function.
527         (convert_mpz_to_signed): New function, largely based on
528         twos_complement().
529         (twos_complement): Removed.
530         (gfc_simplify_ibclr): Add conversions to and from an
531         unsigned representation before bit-twiddling.
532         (gfc_simplify_ibset): Same.
533         (gfc_simplify_ishftc): Add checks for overly large
534         constant arguments, only check the third argument if
535         it's present, carry over high bits into the result as
536         appropriate, and perform the final conversion back to
537         a signed representation using the correct sign bit.
538         (gfc_simplify_not): Removed unnecessary masking.
539
540 2007-01-09  Paul Thomas  <pault@gcc.gnu.org>
541
542         PR fortran/30408
543         * resolve.c (resolve_code): Use the code->expr character length
544         directly to set length of llen.
545
546 2007-01-09  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
547
548         PR fortran/30408
549         * lang.opt: Add Wcharacter_truncation option.
550         * options.c (gfc_init_options): Initialize
551         gfc_option.warn_character_truncation to zero.
552         (gfc_handle_option): Add case for OPT_Wcharacter_truncation.
553
554 2007-01-08  Steven G. Kargl  <kargl@gcc.gnu.org>
555
556         * interface.c, intrinsic.c, gfortranspec.c, io.c, f95-lang.c,
557         iresolve.c, match.c:  Update Copyright years.  Whitespace.
558
559 2007-01-08  Richard Guenther  <rguenther@suse.de>
560
561         * trans-io.c (transfer_array_desc): Use build_int_cst instead
562         of build_int_cstu.
563
564 2007-01-08  Roger Sayle  <roger@eyesopen.com>
565
566         * trans-array.c (constant_array_constructor_p): New function to
567         determine whether an array constructor consists only of constant
568         elements, and if so return it's size.
569         (gfc_build_constant_array_constructor): Construct a statically
570         initialized gfortran array for a given EXPR_ARRAY.
571         (gfc_trans_constant_array_constructor): Efficiently scalarize
572         a constant array constructor.
573         (gfc_trans_array_constructor):  Tidy up use of CONST_STRING.
574         Special case scalarization of constant array constructors, all of
575         whose elements are specified, using constant_array_constructor_p 
576         and gfc_trans_constant_array_constructor.
577         (gfc_conv_scalarized_array_ref): Check whetger info->offset is zero
578         before adding it to index, to avoid creating a NON_LVALUE_EXPR.
579
580 2007-01-08  Kazu Hirata  <kazu@codesourcery.com>
581
582         gfortran.texi: Fix typos.
583
584 2007-01-07  Steven G. Kargl  <kargl@gcc.gnu.org>
585
586         * decl.c, dump-parse-tree.c, error.c, data.c, expr.c, dependency.c,
587         convert.c:  Update Copyright dates.  Fix whitespace.
588
589 2007-01-07  Bernhard Fischer  <aldot@gcc.gnu.org>
590
591         * data.c (gfc_assign_data_value): Fix whitespace.
592
593 2007-01-07  Bernhard Fischer  <aldot@gcc.gnu.org>
594
595         * trans-array.c (gfc_trans_create_temp_array, gfc_array_init_size):
596         Commentary typo fix.
597
598 2007-01-07  Bernhard Fischer  <aldot@gcc.gnu.org>
599
600         PR fortran/27698
601         * match.c (gfc_match_name): Print diagnostics for invalid
602         character in names.
603
604 2007-01-06  Steven G. Kargl  <kargl@gcc.gnu.org>
605
606         * array.c: Fix whitespace in comment table.
607
608 2007-01-06  Steven G. Kargl  <kargl@gcc.gnu.org>
609
610         * array.c, bbt.c, check.c:  Update copyright years.  Whitespace.
611
612 2007-01-06  Steven G. Kargl  <kargl@gcc.gnu.org>
613
614         * arith.c: Update copyright years.  Whitespace.
615
616 2007-01-05  Roger Sayle  <roger@eyesopen.com>
617
618         * trans-expr.c (gfc_trans_assignment_1): New subroutine to scalarize
619         array assignments split out from gfc_trans_assignment.
620         (gfc_trans_array_copy): New function to implement array to array
621         copies via calls to __builtin_memcpy.
622         (copyable_array_p): New helper function to identify an array of
623         simple/POD types, that may be copied/assigned using memcpy.
624         (gfc_trans_assignment): Use gfc_trans_array_copy to handle simple
625         whole array assignments considered suitable by copyable_array_p.
626         Invoke gfc_trans_assignment_1 to perform the fallback scalarization.
627
628 2007-01-05  Roger Sayle  <roger@eyesopen.com>
629
630         * trans-array.c (gfc_trans_array_constructor_value): Make the
631         static const "data" array as TREE_READONLY.
632         * trans-stmt.c (gfc_trans_character_select): Likewise.
633
634 2007-01-05  Roger Sayle  <roger@eyesopen.com>
635
636         * trans-array.c (gfc_conv_loop_setup):  Test whether the loop
637         stride is one, to avoid fold_build2 introducing a useless
638         NON_LVALUE_EXPR node.
639
640 2007-01-05  Tobias Burnus  <burnus@net-b.de>
641
642         * symbol.c (check_conflict): Fix error message.
643
644 2007-01-05  Paul Thomas  <pault@gcc.gnu.org>
645
646         PR fortran/23232
647         * decl.c (gfc_in_match_data, gfc_set_in_match_data): New
648         functions to signal that a DATA statement is being matched.
649         (gfc_match_data): Call gfc_set_in_match_data on entry and on
650         exit.
651         * gfortran.h : Add prototypes for above.
652         * expr.c (check_init_expr): Avoid check on parameter or
653         variable if gfc_in_match_data is true.
654         (gfc_match_init_expr): Do not call error on non-reduction of
655         expression if gfc_in_match_data is true.
656
657         PR fortran/27996
658         PR fortran/27998
659         * decl.c (gfc_set_constant_character_len): Add boolean arg to
660         flag array constructor resolution.  Warn if string is being
661         truncated.  Standard dependent error if string is padded. Set
662         new arg to false for all three calls to
663         gfc_set_constant_character_len.
664         * match.h : Add boolean arg to prototype for
665         gfc_set_constant_character_len.
666         * gfortran.h : Add warn_character_truncation to gfc_options.
667         * options.c (set_Wall): Set warn_character_truncation if -Wall
668         is set.
669         * resolve.c (resolve_code): Warn if rhs string in character
670         assignment has to be truncated.
671         * array.c (gfc_resolve_character_array_constructor): Set new
672         argument to true for call to gfc_set_constant_character_len.
673
674 2007-01-05  Tobias Burnus  <burnus@net-b.de>
675
676         PR fortran/29624
677         * interface.c (compare_parameter_intent): New function.
678           (check_intents): Support pointer intents.
679         * symbol.c (check_conflict): Support pointer intents,
680           better conflict_std message.
681         * expr.c (gfc_check_assign,gfc_check_pointer_assign):
682           Support pointer intents.
683         * resolve.c (resolve_deallocate_expr,resolve_allocate_expr):
684           Support pointer intents.
685
686 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
687
688         PR 30371
689         * check.c (gfc_check_kill_sub): Add checks for non-scalar
690         arguments.
691
692 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
693
694         * intrinsic.texi: Minor cleanup, reflowing overlong
695         paragraphs, and correcting whitespace.
696
697 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
698
699         * intrinsic.texi (LBOUND): Add documentation.
700         (LGE): Add documentation.
701         (LGT): Add documentation.
702         (LINK): Add documentation.
703         (LLE): Add documentation.
704         (LLT): Add documentation.
705         (LNBLNK): Add documentation.
706         (UBOUND): Add documentation.
707         (UNLINK): Add documentation.
708
709 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
710
711         * intrinsic.texi (IAND): Clarify argument specifications.
712         (IBCLR): Add documentation.
713         (IBITS): Add documentation.
714         (IBSET): Add documentation.
715         (IEOR): Add documentation.
716         (IERRNO): Add documentation.
717         (INDEX): Add documentation.
718         (IOR): Add documentation.
719         (ISHFT): Add documentation.
720         (ISHFTC): Add documentation.
721         (KILL): Add documentation.
722         (LEN_TRIM): Add documentation.
723
724 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
725
726         PR 30235
727         * interface.c (compare_actual_formal): check for
728         alternate returns when iterating over non-present
729         arguments.
730
731 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
732
733         * invoke.texi: Update manpage copyright to include 2007.
734
735 2007-01-04  Brooks Moses  <brooks.moses@codesourcery.com>
736
737         * gfortran.texi: Update copyright to include 2007.
738         * intrinsic.texi: Update copyright to include 2007.
739         * invoke.texi: Update copyright to include 2007.
740
741 2007-01-02  Tobias Burnus  <burnus@net-b.de>
742             Jakub Jelinek  <jakub@redhat.com>
743
744         PR fortran/30276
745         * scanner.c (open_included_file): Revert patch.
746           (gfc_open_included_file): Support absolute pathnames.
747           (gfc_open_intrinsic_module): Support absolute pathnames.
748
749 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
750
751         * gfortran.texi (GNU Fortran and GCC): Rewrite
752
753 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
754
755         * gfortran.texi (Introduction): Lower "Part I:
756         Introduction" to a chapter, renumber Parts II and III to
757         Parts I and II.
758         * intrinsic.texi (Introduction): Rename to "Introduction
759         to Intrinsics" to avoid conflict with the new chapter.
760
761 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
762
763         * intrinsic.texi (Introduction): Rewrite first paragraph.
764
765 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
766
767         * invoke.texi (OpenMP): Added index entry.
768         * gfortran.texi (title page): Removed erroneous '*'.
769
770 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
771
772         * gfortran.texi (GFORTRAN_DEFAULT_RECL): Added units
773         to description.
774         (Extensions): Miscellaneous minor rewriting and copyediting.
775         (BOZ-literal constants): Renamed from Hexadecimal constants.
776         (Hollerith constants support): Added explanation and 
777         suggestions for standard-conforming modern equivalents.
778
779 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
780
781         * intrinsic.texi: Improvements to index entries; change
782         @findex entries to @cindex entries.
783         * invoke.texi: Standardize and improve index entries.
784         * gfortran.texi: Fix @code in one index entry.
785
786 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
787
788         * invoke.texi: Change @code-type macros to appropriate
789         variants (@command, @option, etc.)
790         * gfortran.texi: Same.
791
792 2007-01-03  Brooks Moses  <brooks.moses@codesourcery.com>
793
794         * intrinsic.texi: Various minor cleanups.
795
796 2007-01-02  Steven G. Kargl  <kargls@comcast.net>
797
798         * trans-intrinsic.c (gfc_conv_intrinsic_ibits): Fix call to
799         build_int_cst.
800
801 2007-01-02  Tobias Burnus  <burnus@net-b.de>
802
803         PR fortran/30276
804         * scanner.c (open_included_file): Support full-path filenames.
805
806 2007-01-02  Paul Thomas  <pault@gcc.gnu.org>
807
808         PR fortran/20896
809         * interface.c (check_sym_interfaces): Remove call to
810         resolve_global_procedure.
811         gfortran.h : Remove prototype for resolve_global_procedure.
812         resolve.c (resolve_global_procedure): Add static attribute
813         to function declaration.
814
815 2007-01-01  Steven G. Kargl  <kargls@comcast.net>
816
817         * ChangeLog: Copy to ...
818         * ChangeLog-2006: here.