From 79b1d36cdde2ef1c586ada2b58f5b2d1441dd82f Mon Sep 17 00:00:00 2001
From: Paul Thomas <pault@gcc.gnu.org>
Date: Sat, 3 Jan 2009 17:47:20 +0000
Subject: [PATCH] re PR fortran/38594 (module function name mangled improperly
 if contained function of same name exists)

2009-01-03  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/38594
	* resolve.c (resolve_call): When searching for proper host
	association, use symtree rather than symbol.  For everything
	except generic subroutines, substitute the symtree in the call
	rather than the symbol.

2009-01-03  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/38594
	* gfortran.dg/host_assoc_call_3.f90: Make sure that the generic
	interface still works, in addition to original tests.
	* gfortran.dg/host_assoc_call_6.f90: New test.

From-SVN: r143032
---
 gcc/fortran/ChangeLog                         | 4140 +----------------
 gcc/fortran/ChangeLog-2008                    | 4135 ++++++++++++++++
 gcc/fortran/resolve.c                         |   11 +-
 gcc/testsuite/ChangeLog                       |    7 +
 .../gfortran.dg/host_assoc_call_3.f90         |   11 +
 .../gfortran.dg/host_assoc_call_6.f90         |   25 +
 6 files changed, 4192 insertions(+), 4137 deletions(-)
 create mode 100644 gcc/fortran/ChangeLog-2008
 create mode 100644 gcc/testsuite/gfortran.dg/host_assoc_call_6.f90

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index d1135b35dfc0..738209bb992b 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,4135 +1,7 @@
-2008-12-31  Daniel Franke  <franke.daniel@gmail.com>
+2009-01-03  Paul Thomas  <pault@gcc.gnu.org>
 
-	* check.c (dim_rank_check): Fixed checking of dimension argument
-	if array is of type EXPR_ARRAY.
-
-2008-12-22  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/38602
-	* trans-decl.c (init_intent_out_dt): Allow for optional args.
-
-2008-12-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/38398
-	* io.c: Add error checks for g0 formatting and provide adjustment of
-	error loci for improved error messages.
-
-2008-12-21  Arjen Markus  <arjen.markus@wldelft.nl>
-	    Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37605
-	* gfortran.texi: Fixed some typos and some minor style improvements.
-	* intrinsic.texi: Some clarifications and typo-fixes.
-	* invoke.texi: Better documenation of the behaviour of the
-	-fdefault-*-8 options and some other fixes.
-
-2008-12-18  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/31822
-	* gfortran.h (gfc_check_same_strlen): Made public.
-	* trans.h (gfc_trans_same_strlen_check): Made public.
-	* check.c (gfc_check_same_strlen): Made public and adapted error
-	message output to be useful not only for intrinsics.
-	(gfc_check_merge): Adapt to gfc_check_same_strlen change.
-	* expr.c (gfc_check_pointer_assign): Use gfc_check_same_strlen for
-	string length compile-time check.
-	* trans-expr.c (gfc_trans_pointer_assignment): Add runtime-check for
-	equal string lengths using gfc_trans_same_strlen_check.
-	* trans-intrinsic.c (gfc_trans_same_strlen_check): Renamed and made
-	public from conv_same_strlen_check.
-	(gfc_conv_intrinsic_merge): Adapted accordingly.
-
-2008-12-17  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/38137
-	* trans-intrinsic.c (conv_same_strlen_check): New method.
-	(gfc_conv_intrinsic_merge): Call it here to actually do the check.
-
-2008-12-15  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/38487
-	* dependency.c (gfc_is_data_pointer): New function.
-	(gfc_check_argument_var_dependency): Disable the warning
-	in the pointer case.
-	(gfc_check_dependency): Use gfc_is_data_pointer.
-
-2008-12-15  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/38113
-	* error.c (show_locus): Start counting columns at 0.
-	* primary.c (match_actual_arg): Eat spaces
-	before copying the current locus.
-	(match_variable): Copy the locus before matching.
-
-2008-12-14  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35937
-	* trans-expr.c (gfc_finish_interface_mapping): Fold convert the
-	character length to gfc_charlen_type_node.
-
-2008-12-12  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/36355
-	* check.c (gfc_check_matmul): Fixed error message for invalid
-	types to correctly identify the offending argument, added check
-	for mismatching types.
-
-2008-12-11  Richard Guenther  <rguenther@suse.de>
-
-	* Make-lang.in (install-finclude-dir): Use correct mode argument
-	for mkinstalldirs.
-
-2008-12-09  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/36376
-	PR fortran/37468
-	* lang-specs.h: Pass on -i* options to f951 to (probably) report
-	them as unknown. Duplicate gcc.c (cpp_options), but omit
-	-fpch-preprocess on -save-temps.
-
-2008-12-09  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/36457
-	* lang.opt: Added option idirafter.
-	* cpp.h (gfc_cpp_add_include_path_after): New prototype.
-	* cpp.c (gfc_cpp_handle_option): Recognize and handle OPT_dirafter.
-	(gfc_cpp_add_include_path_after): New, adds user-defined search path
-	after any other paths.
-	* invoke.texi (idirafter): New.
-	(no-range-check): Fixed entry in option-index.
-
-2008-12-09  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/37469
-	* expr.c (find_array_element): Simplify array bounds.
-	Assert that both bounds are constant expressions.
-
-2008-12-09  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/35983
-	* trans-expr.c (gfc_trans_subcomponent_assign):
-	Add se's pre and post blocks to current block.
-	(gfc_trans_structure_assign): Remove specific handling
-	of C_NULL_PTR and C_NULL_FUNPTR.
-
-2008-12-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/38425
-	* io.c (check_io_constraints): Check constraints on REC=, POS=, and
-	internal unit with POS=. Fix punctuation on a few error messages.
-
-2008-12-06  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/38415
-	* expr.c (gfc_check_pointer_assign): Added a check for abstract
-	interfaces in procedure pointer assignments, removed check involving
-	gfc_compare_interfaces until PR38290 is fixed completely.
-
-2008-12-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/38291
-	* io.c (match_dt_element): Use dt->pos in matcher.
-	(gfc_free_dt): Free dt->pos after use.
-	(gfc_resolve_dt): Use dt->pos in resolution of stream position tag.
-
-2008-12-05  Sebastian Pop  <sebastian.pop@amd.com>
-
-	PR bootstrap/38262
-	* Make-lang.in (f951): Add BACKENDLIBS, remove GMPLIBS.
-
-2008-12-02  Jakub Jelinek  <jakub@redhat.com>
-	    Diego Novillo  <dnovillo@google.com>
-
-	* Make-lang.in (install-finclude-dir): Use mkinstalldirs
-	and don't remove the finclude directory beforehand.
-
-2008-12-02  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36704
-	PR fortran/38290
-	* decl.c (match_result): Result may be a standard variable or a
-	procedure pointer.
-	* expr.c (gfc_check_pointer_assign): Additional checks for procedure
-	pointer assignments.
-	* primary.c (gfc_match_rvalue): Bugfix for procedure pointer
-	assignments.
-	* resolve.c (resolve_function): Check for attr.subroutine.
-	* symbol.c (check_conflict): Addtional checks for RESULT statements.
-	* trans-types.c (gfc_sym_type,gfc_get_function_type): Support procedure
-	pointers as function result.
-
-2008-12-01  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/38252
-	* parse.c (parse_spec): Skip statement order check in case
-	of a CONTAINS statement.
-
-2008-11-30  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37779
-	* gfortran.h (struct gfc_entry_list): Fixed typo in comment.
-	* resolve.c (is_illegal_recursion): New method.
-	(resolve_procedure_expression): Use new is_illegal_recursion instead of
-	direct check and handle function symbols correctly.
-	(resolve_actual_arglist): Removed useless recursion check.
-	(resolve_function): Use is_illegal_recursion instead of direct check.
-	(resolve_call): Ditto.
-
-2008-11-29  Eric Botcazou  <ebotcazou@adacore.com>
-
-	* trans-array.c (gfc_conv_array_parameter): Guard union access.
-
-2008-11-29  Janus Weil  <janus@gcc.gnu.org>
-	    Mikael Morin <mikael@gcc.gnu.org>
-
-	PR fortran/38289
-	PR fortran/38290
-	* decl.c (match_procedure_decl): Handle whitespaces.
-	* resolve.c (resolve_specific_s0): Bugfix in check for intrinsic
-	interface.
-
-2008-11-25  H.J. Lu  <hongjiu.lu@intel.com>
-
-	* module.c (gfc_dump_module): Report error on unlink only if
-	errno != ENOENT.
-
-2008-11-25  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/36463
-	* expr.c (replace_symbol): Don't replace the symtree
-	if the expresion is an intrinsic function. Don't create
-	non-existent symtrees.  Use symbol's name instead of symtree's,
-	different in case of module procedure dummy arguments.
-
-2008-11-25  Jan Kratochvil  <jan.kratochvil@redhat.com>
-
-	PR fortran/38248
-	* module.c (gfc_dump_module): Check rename/unlink syscalls errors.
-
-2008-11-25  Eric Botcazou  <ebotcazou@adacore.com>
-
-	PR fortran/37319
-	* parse.c (match_deferred_characteristics): Make sure 'name' is
-	initialized before reading it.
-
-2008-11-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/37803
-	* arith.c (gfc_check_real_range): Add mpfr_check_range.
-	* simplify.c (gfc_simplify_nearest): Add mpfr_check_range.
-
-2008-11-24  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/38184
-	* simplify.c (is_constant_array_expr): Return true instead of false
-	if the array constructor is empty.
-
-2008-11-24  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37779
-	* resolve.c (resolve_procedure_expression): New method.
-	(resolve_variable): Call it.
-	(resolve_actual_arglist): Call gfc_resolve_expr for procedure arguments.
-
-2008-11-24  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34820
-	* trans-expr.c (gfc_conv_function_call): Remove all code to
-	deallocate intent out derived types with allocatable
-	components.
-	(gfc_trans_assignment_1): An assignment from a scalar to an
-	array of derived types with allocatable components, requires
-	a deep copy to each array element and deallocation of the
-	converted rhs expression afterwards.
-	* trans-array.c : Minor whitespace.
-	* trans-decl.c (init_intent_out_dt): Add code to deallocate
-	allocatable components of derived types with intent out.
-	(generate_local_decl): If these types are unused, set them
-	referenced anyway but allow the uninitialized warning.
-
-	PR fortran/34143
-	* trans-expr.c (gfc_trans_subcomponent_assign): If a conversion
-	expression has a null data pointer argument, nullify the
-	allocatable component.
-
-	PR fortran/32795
-	* trans-expr.c (gfc_trans_subcomponent_assign): Only nullify
-	the data pointer if the source is not a variable.
-
-2008-11-23  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37735
-	* trans-array.c (structure_alloc_comps): Do not duplicate the
-	descriptor if this is a descriptorless array!
-
-2008-11-12  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/38160
-	* trans-types.c (gfc_validate_c_kind): Remove function.
-	* decl.c (gfc_match_kind_spec): Add C kind parameter check.
-	(verify_bind_c_derived_type): Remove gfc_validate_c_kind call.
-	(verify_c_interop_param): Update call.
-	* gfortran.h (verify_bind_c_derived_type): Update prototype.
-	(gfc_validate_c_kind): Remove.
-	* symbol.c (verify_bind_c_derived_type): Update verify_c_interop call.
-	* resolve.c (gfc_iso_c_func_interface): Ditto.
-
-2008-11-22  Jakub Jelinek  <jakub@redhat.com>
-
-	PR libfortran/37839
-	* trans-io.c (gfc_build_io_library_fndecls): Decrease pad size back
-	to 16 pointers plus 32 integers.  Don't use max integer kind
-	alignment, only gfc_intio_kind's alignment.
-	(gfc_trans_inquire): Only set flags2 if mask2 is non-zero.
-	* ioparm.def: Fix order, bitmasks and types of inquire round, sign
-	and pending fields.  Move u in dt before id.
-	* io.c (gfc_free_inquire): Free decimal and size exprs.
-	(match_inquire_element): Match size instead of matching blank twice.
-	(gfc_resolve_inquire): Resolve size.
-
-2008-11-20  Jakub Jelinek  <jakub@redhat.com>
-
-	PR middle-end/29215
-	* trans-array.c (trans_array_constructor_value,
-	gfc_build_constant_array_constructor): Fill in TREE_PURPOSE.
-
-	* trans-intrinsic.c (gfc_conv_intrinsic_minmaxloc): Use
-	gfc_index_one_node.
-	(gfc_conv_intrinsic_size): Use gfc_index_{zero,one}_node.
-
-	PR fortran/38181
-	* trans-intrinsic.c (gfc_conv_intrinsic_size): Inline 2 argument
-	size if the second argument is not optional and one argument size
-	for rank 1 arrays.
-
-2008-11-19  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/38171
-	* module.c (load_equiv): Regression fix; check that equivalence
-	members come from the same module only.
-
-2008-11-16  Mikael Morin <mikael.morin@tele2.fr>
-
-	PR fortran/35681
-	* dependency.c (gfc_check_argument_var_dependency): Add
-	elemental check flag. Issue a warning if we find a dependency
-	but don't generate a temporary. Add the case of an elemental
-	function call as actual argument to an elemental procedure.
-	Add the case of an operator expression as actual argument
-	to an elemental procedure.
-	(gfc_check_argument_dependency): Add elemental check flag.
-	Update calls to gfc_check_argument_var_dependency.
-	(gfc_check_fncall_dependency): Add elemental check flag.
-	Update call to gfc_check_argument_dependency.
-	* trans-stmt.c (gfc_trans_call): Make call to
-	gfc_conv_elemental_dependency unconditional, but with a flag
-	whether we should check dependencies between variables.
-	(gfc_conv_elemental_dependency): Add elemental check flag.
-	Update call to gfc_check_fncall_dependency.
-	* trans-expr.c (gfc_trans_arrayfunc_assign): Update call to
-	gfc_check_fncall_dependency.
-	* resolve.c (find_noncopying_intrinsics): Update call to
-	gfc_check_fncall_dependency.
-	* dependency.h (enum gfc_dep_check): New enum.
-	(gfc_check_fncall_dependency): Update prototype.
-
-2008-11-16  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/37992
-	* gfortran.h (gfc_namespace): Added member old_cl_list, 
-	backup of cl_list.
-	(gfc_free_charlen): Added prototype.
-	* symbol.c (gfc_free_charlen): New function.
-	(gfc_free_namespace): Use gfc_free_charlen.
-	* parse.c (next_statement): Backup gfc_current_ns->cl_list.
-	(reject_statement): Restore gfc_current_ns->cl_list.
-	Free cl_list's elements before dropping them.
-
-2008-11-16  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/38095
-	* trans-expr.c (gfc_map_intrinsic_function): Fix pointer access.
-
-2008-11-16  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/38119
-	* trans-array.c (gfc_trans_create_temp_array): Set the
-	loop->from to zero and the renormalisation of loop->to for all
-	dimensions.
-
-2008-11-16  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37926
-	* trans-expr.c (gfc_free_interface_mapping): Null sym->formal
-	(gfc_add_interface_mapping): Copy the pointer to the formal
-	arglist, rather than using copy_formal_args - fixes regression.
-
-2008-11-15  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37926
-	* trans-expr.c (gfc_add_interface_mapping): Transfer the formal
-	arglist and the always_explicit attribute if the dummy arg is a
-	procedure.
-
-2008-11-14  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/37988
-	* io.c (enum format_token): For readability replace FMT_POS with FMT_T,
-	FMT_TL, and FMT_TR.  (format_lex): Use new enumerators. (check_format):
-	Add check for missing positive integer.
-
-2008-10-14  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/38033
-	* trans-array.c (gfc_trans_create_temp_array): Stabilize the
-	'to' expression.
-	(gfc_conv_loop_setup): Use the end expression for the loop 'to'
-	if it is available.
-
-2008-11-12  Jakub Jelinek  <jakub@redhat.com>
-
-	PR target/35366
-	PR fortran/33759
-	* trans-const.c (gfc_conv_constant_to_tree): Warn when
-	converting an integer outside of LOGICAL's range to
-	LOGICAL.
-	* trans-intrinsic.c (gfc_conv_intrinsic_function,
-	gfc_conv_intrinsic_array_transfer, gfc_conv_intrinsic_transfer):
-	Use INTEGER_TYPE instead of BOOLEAN_TYPE for TRANSFER as
-	argument of another TRANSFER.
-
-2008-11-12  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/38065
-	* resolve.c (resolve_fntype): Fix private derived type checking.
-
-2008-11-09  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37836
-	* intrinsic.c (add_functions): Reference gfc_simplify._minval
-	and gfc_simplify_maxval.
-	* intrinsic.h : Add prototypes for gfc_simplify._minval and
-	gfc_simplify_maxval.
-	* simplify.c (min_max_choose): New function extracted from
-	simplify_min_max.
-	(simplify_min_max): Call it.
-	(simplify_minval_maxval, gfc_simplify_minval,
-	gfc_simplify_maxval): New functions.
-
-2008-11-04  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37597
-	* parse.c (gfc_fixup_sibling_symbols ): Fixup contained, even
-	when symbol not found.
-
-2008-11-03  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37821
-	* cpp.c (gfc_cpp_add_include_path): Use BRACKET.
-	* scanner.c (add_path_to_list): Argument to add at head.
-	(gfc_add_include_path): Add new argument.
-	(gfc_add_intrinsic_modules_path) Update call.
-	(load_file): Print filename/line in the error message.
-	* gfortran.h (gfc_add_include_path): Update prototype.
-	* options.c (gfc_post_options,gfc_handle_module_path_options,
-	gfc_handle_option): Update call.
-	* lang-spec.h (F951_OPTIONS): Don't insert include path twice.
-
-	* arith.c (arith_error): Add -fno-range-error to the message.
-
-2008-11-03  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37445
-	* resolve.c (resolve_actual_arglist ): Correct comparison of
-	FL_VARIABLE with e->expr_type.
-	(resolve_call): Check that host association is correct.
-	(resolve_actual_arglist ): Remove return is old_sym is use
-	associated.  Only reparse expression if old and new symbols
-	have different types.
-
-	PR fortran/PR35769
-	* resolve.c (gfc_resolve_assign_in_forall): Change error to a
-	warning.
-
-2008-11-01  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36426
-	* expr.c (replace_symbol): Replace all symbols which lie in the
-	formal namespace of the interface and copy their attributes.
-	* resolve.c (resolve_symbol): Add charlen to namespace.
-
-2008-11-01  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/19925
-	* trans-array.c (gfc_trans_array_constructor_value): Fix comment.
-	(gfc_conv_array_initializer): Convert internal_error() to gfc_error_now.
-	* array.c: Remove GFC_MAX_AC_EXPAND macro.
-	(gfc_expand_constructor): Use gfc_option.flag_max_array_constructor.
-	* gfortran.h (gfc_option): Add flag_max_array_constructor member.
-	* lang.opt: Add -fmax-array-constructor option.
-	* expr.c (gfc_match_init_expr): Fix error message to mention new option.
-	* invoke.texi: Document new option.
-	* options.c (gfc_init_options): Set default value for new option.
-	(gfc_handle_option): Deal with commandline.
-
-2008-11-01  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/35681
-	* gfortran.h (struct gfc_code): New field `resolved_isym'.
-	* trans.h (gfc_build_memcpy_call): Made public.
-	* trans-array.h (gfc_trans_create_temp_array): New argument `initial'.
-	* intrinsic.c (gfc_intrinsic_sub_interface): Set resolved_isym.
-	* iresolve.c (create_formal_for_intents): New helper method.
-	(gfc_resolve_mvbits): Put dummy formal arglist on resolved_sym.
-	* resolve.c (resolve_call): Initialize resolved_isym to NULL.
-	* trans-array.c (gfc_trans_allocate_array_storage): New argument
-	`initial' to allow initializing the allocated storage to some initial
-	value copied from another array.
-	(gfc_trans_create_temp_array): Allow initialization of the temporary
-	with a copy of some other array by using the new extension.
-	(gfc_trans_array_constructor): Pass NULL_TREE for initial argument.
-	(gfc_conv_loop_setup): Ditto.
-	* trans-intrinsic.c (gfc_conv_intrinsic_array_transfer): Ditto.
-	* trans-expr.c (gfc_conv_function_call): Ditto.
-	(gfc_build_memcpy_call): Made public.
-	* trans-stmt.c (gfc_conv_elemental_dependencies): Initialize created
-	temporary for INTENT(INOUT) arguments to the value of the mirrored
-	array and clean up the temporary as very last intructions in the created
-	block.
-	* trans.c (gfc_trans_code): For EXEC_CALL, see if we have a MVBITS call
-	and enable elemental dependency checking if we have.
-
-2008-11-01  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36322
-	PR fortran/36463
-	* gfortran.h: New function gfc_expr_replace_symbols.
-	* decl.c (match_procedure_decl): Increase reference count for interface.
-	* expr.c: New functions replace_symbol and gfc_expr_replace_symbols.
-	* resolve.c (resolve_symbol): Correctly copy array spec and char len
-	of PROCEDURE declarations from their interface.
-	* symbol.c (gfc_get_default_type): Enhanced error message.
-	(copy_formal_args): Call copy_formal_args recursively for arguments.
-	* trans-expr.c (gfc_conv_function_call): Bugfix.
-
-2008-11-01  Dennis Wassel  <dennis.wassel@gmail.com>
-
-	PR fortran/37159
-	* fortran/check.c (gfc_check_random_seed): Check PUT size
-	at compile time.
-
-2008-10-31  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/35840
-	* expr.c (gfc_reduce_init_expr): New function, containing checking code
-	from gfc_match_init_expr, so that checking can be deferred. 
-	(gfc_match_init_expr): Use gfc_reduce_init_expr.
-	* io.c (check_io_constraints): Use gfc_reduce_init_expr instead of 
-	checking that the expression is a constant. 
-	* match.h (gfc_reduce_init_expr): Prototype added. 
-
-2008-10-31  Mikael Morin  <mikael.morin@tele2.fr>
-
-	PR fortran/35820
-	* resolve.c (gfc_count_forall_iterators): New function.
-	(gfc_resolve_forall): Use gfc_count_forall_iterators to evaluate 
-	the needed memory amount to allocate. Don't forget to free allocated 
-	memory.  Add an assertion to check for memory leaks. 
-
-2008-10-30  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/37930
-	* fortran/arith.c (gfc_mpfr_to_mpz):  Test for NaN and Inf values.
-	Remove stale comment and kludge code for MPFR 2.0.1 and older.
-	(gfc_real2int): Error on conversion of NaN or Inf.
-	(gfc_complex2int): Ditto.
-	* fortran/arith.h: Update mpfr_to_mpz prototype.
-	* fortran/simplify.c (gfc_simplify_ceiling, gfc_simplify_floor,
-	gfc_simplify_ifix, gfc_simplify_idint, simplify_nint): Update function
-	calls to include locus.
-
-2008-10-30  Mikael Morin  <mikael.morin@tele2.fr>
-
-        PR fortran/37903
-        * trans-array.c (gfc_trans_create_temp_array): If n is less
-	than the temporary dimension, assert that loop->from is
-	zero (reverts to earlier versions). If there is at least one
-	null loop->to[n], it is a callee allocated array so set the
-	size to NULL and break.
-	(gfc_trans_constant_array_constructor): Set the offset to zero.
-	(gfc_trans_array_constructor): Remove loop shifting around the
-	temporary creation.
-	(gfc_conv_loop_setup): Prefer zero-based descriptors if
-	possible.  Calculate the translation from loop variables to
-	array indices if an array constructor.
-
-2008-10-30  Mikael Morin  <mikael.morin@tele2.fr>
-
-        PR fortran/37749
-        * trans-array.c (gfc_trans_create_temp_array): If size is NULL
-	use the array bounds for loop->to.
-
-2008-10-28  Tobias Burnus  <burnus@net-b.de>
-
-	* intrinsic.texi: Update OpenMP section for OMPv3.
-
-2008-10-24  Jakub Jelinek  <jakub@redhat.com>
-
-	* Make-lang.in (check-f95-subtargets, check-fortran-subtargets): New
-	aliases for check-gfortran-subtargets.
-	(lang_checks_parallelized): Add check-gfortran.
-	(check_gfortran_parallelize): New variable.
-
-2008-10-19  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37723
-	* dependency.c (gfc_dep_resolver ): If we find equal array
-	element references, go on to the next reference.
-
-2008-10-16  Daniel Kraft  <d@domob.eu>
-
-	* resolve.c (resolve_elemental_actual): Handle calls to intrinsic
-	subroutines correctly.
-
-2008-10-13  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* simplify.c: Remove MPFR_VERSION_NUM(2,3,0) conditionals.
-
-2008-10-12  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37688
-	* expr.c (gfc_expr_check_typed): Extend permission of untyped
-	expressions to both top-level variable and basic arithmetic expressions.
-
-2008-10-12  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37787
-	* dependency.c (gfc_are_equivalenced_arrays): Look in symbol
-	namespace rather than current namespace, if it is available.
-
-2008-10-12  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/37792
-	* fortran/resolve.c (resolve_fl_variable): Simplify the
-	initializer if there is one.
-
-2008-10-11  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37794
-	* module.c (check_for_ambiguous): Remove redundant code.
-
-2008-10-09  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/35723
-	* gfortran.h (gfc_suppress_error): Removed from header.
-	(gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
-	* array.c (gfc_array_size): Use new gfc_push/pop_suppress_errors
-	instead of directly changing gfc_suppress_error.
-	* intrinsic.c (gfc_intrinsic_func_interface): Ditto.
-	(gfc_intrinsic_sub_interface): Ditto.
-	* error.c (suppress_errors): Made static from `gfc_suppress_error'.
-	(gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
-	(gfc_notify_std), (gfc_error): Use new static name of global.
-	* expr.c (check_arglist), (check_references): New methods.
-	(check_restricted): Check arglists and references of EXPR_FUNCTIONs
-	and EXPR_VARAIBALEs, respectively.  Allow PARAMETER symbols.
-
-2008-10-07  Jakub Jelinek  <jakub@redhat.com>
-
-	* f95-lang.c (poplevel): Don't clear BLOCK_VARS if functionbody.
-	* trans-decl.c (gfc_build_qualified_array): Build accurate debug type
-	even if nest.
-	(build_entry_thunks, gfc_generate_function_code,
-	gfc_generate_constructors): Ensure DECL_SAVED_TREE is a BIND_EXPR
-	with DECL_INITIAL as its BLOCK.
-
-2008-10-05  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35680
-	* gfortran.h : Add 'error' bit field to gfc_expr structure.
-	* expr.c (check_inquiry): When checking a restricted expression
-	check that arguments are either variables or restricted.
-	(check_restricted): Do not emit error if the expression has
-	'error' set.  Clean up detection of host-associated variable.
-
-2008-10-05  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37638
-	* gfortran.h (struct gfc_typebound_proc): New flag `error'.
-	* resolve.c (update_arglist_pass): Added assertion.
-	(update_compcall_arglist): Fail early for erraneous procedures to avoid
-	confusion later.
-	(resolve_typebound_generic_call): Ignore erraneous specific targets
-	and added assertions.
-	(resolve_typebound_procedure): Set new `error' flag.
-
-2008-10-04  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37706
-	* module.c (load_equiv): Check the module before negating the
-	unused flag.
-
-2008-10-02  Steven Bosscher  <steven@gcc.gnu.org>
-
-	PR fortran/37635
-	* intrinsic.c (add_functions): Add LEADZ and TRAILZ as generics.
-	* intrinsic.h (gfc_simplify_leadz, gfc_simplify_trailz): New protos.
-	* gfortran.h <enum gfc_isym_id>: (GFC_ISYM_LEADZ, GFC_ISYM_TRAILZ): New.
-	* f95-lang (gfc_init_builtin_functions): Add BUILT_IN_CLZ,
-	BUILT_IN_CLZL, BUILT_IN_CLZLL, BUILT_IN_CTZ, BUILT_IN_CTZL, and
-	BUILT_IN_CTZLL.
-	* trans-intrinsic.c (gfc_conv_intrinsic_leadz,
-	gfc_conv_intrinsic_trails): New code-generation functions for LEADZ
-	and TRAILZ intrinsics.
-	(gfc_conv_intrinsic_function): Use them
-	* intrinsic.texi: Add documentation for LEADZ and TRAILZ.
-	* simplify.c (gfc_simplify_leadz, gfc_simplify_trailz): New functions.
-
-2008-09-30  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36592
-	* symbol.c (check_conflict): If a symbol in a COMMON block is a
-	procedure, it must be a procedure pointer.
-	(gfc_add_in_common): Symbols in COMMON blocks may be variables or
-	procedure pointers.
-	* trans-types.c (gfc_sym_type): Make procedure pointers in COMMON
-	blocks work.
-
-2008-09-25  Jerry DeLisle  <jvdelisle@gcc.gnu.org
-
-	PR fortran/37498
-	* trans-io.c (build_dt): Revert previous patch..
-	* ioparm.def: Delete IOPARM_dt_f2003.
-
-2008-09-25  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37504
-	* expr.c (gfc_check_pointer_assign): Allow assignment of
-	protected pointers.
-	* match.c (gfc_match_assignment,gfc_match_pointer_assignment):
-	Remove unreachable code.
-
-2008-09-24  Tobias Burnus  <burnus@net-b.de>
-
-	* options.c (set_default_std_flags,gfc_init_options):
-	Add comment: keep in sync with libgfortran.
-
-2008-09-24  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37626
-	* trans-array.c (gfc_trans_deferred_array): Don't auto-deallocate
-	result variables.
-
-2008-09-23  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37588
-	* gfortran.h (gfc_compare_actual_formal): Removed, made private.
-	(gfc_arglist_matches_symbol): New method.
-	* interface.c (compare_actual_formal): Made static.
-	(gfc_procedure_use): Use new name of compare_actual_formal.
-	(gfc_arglist_matches_symbol): New method.
-	(gfc_search_interface): Moved code partially to new
-	gfc_arglist_matches_symbol.
-	* resolve.c (resolve_typebound_generic_call): Resolve actual arglist
-	before checking against formal and use new gfc_arglist_matches_symbol
-	for checking.
-	(resolve_compcall): Set type-spec of generated expression.
-
-2008-09-23  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37580
-	* expr.c (gfc_check_pointer_assign): Add checks for pointer
-	remapping.
-
-2008-09-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org
-
-	PR fortran/37498
-	* trans-io.c (gfc_build_io_library_fndecls): Bump pad size.
-	(build_dt): Set mask bit for IOPARM_dt_f2003.
-	* ioparm.def: Add IOPARM_dt_f2003.
-
-2008-09-22  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/37486
-	* gfortran.h (gfc_option_t): New members flag_align_commons and
-	warn_align_commons. 
-	* lang.opt: New options falign-commons and Walign-commons.
-	* invoke.texi: Documentation for new options.
-	* options.c (gfc_init_options): Initialize new options.
-	(gfc_handle_options): Handle new options.
-	* trans-common.c (translate_common): Implement new options.
-	(gfc_trans_common): Set correct locus.
-
-2008-09-21  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37583
-	* decl.c (scalarize_intrinsic_call): Both subroutines and
-	functions can give a true for get_proc_mame's last argument so
-	remove the &&gfc_current_ns->proc_name->attr.function.
-	resolve.c (resolve_actual_arglist): Add check for recursion by
-	reference to procedure as actual argument.
-
-2008-09-21  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/35846
-	* trans.h (gfc_conv_string_length): New argument `expr'.
-	* trans-expr.c (flatten_array_ctors_without_strlen): New method.
-	(gfc_conv_string_length): New argument `expr' that is used in a new
-	special case handling if cl->length is NULL.
-	(gfc_conv_subref_array_arg): Pass expr to gfc_conv_string_length.
-	* trans-array.c (gfc_conv_expr_descriptor): Ditto.
-	(gfc_trans_auto_array_allocation): Pass NULL as new expr.
-	(gfc_trans_g77_array), (gfc_trans_dummy_array_bias): Ditto.
-	(gfc_trans_deferred_array): Ditto.
-	(gfc_trans_array_constructor): Save and restore old values of globals
-	used for bounds checking.
-	* trans-decl.c (gfc_trans_dummy_character): Ditto.
-	(gfc_trans_auto_character_variable): Ditto.
-
-2008-09-21  Daniel Kraft  <d@domob.eu>
-
-	* decl.c (match_procedure_in_type): Changed misleading error message
-	for not yet implemented PROCEDURE(interface) syntax.
-
-2008-09-18  Paul Thomas  <pault@gcc.gnu.org>
-
-       PR fortran/35945
-       * resolve.c (resolve_fl_variable_derived):  Remove derived type
-       comparison for use associated derived types.  Host association
-       of a derived type will not arise if there is a local derived type
-       whose use name is the same.
-
-       PR fortran/36700
-       * match.c (gfc_match_call):  Use the existing symbol even if
-       it is a function.
-
-2008-09-18  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37507
-	* trans.h (gfc_trans_runtime_error): New method.
-	(gfc_trans_runtime_error_vararg): New method.
-	(gfc_allocate_array_with_status): New argument `expr' for locus/varname.
-	(gfc_deallocate_array_with_status): Ditto.
-	* trans-array.h (gfc_array_deallocate): Ditto.
-	* trans.c (gfc_trans_runtime_error): New method.
-	(gfc_trans_runtime_error_vararg): New method, moved parts of the code
-	from gfc_trans_runtime_check here.
-	(gfc_trans_runtime_error_check): Moved code partly to new method.
-	(gfc_call_malloc): Fix tab-indentation.
-	(gfc_allocate_array_with_status): New argument `expr' and call
-	gfc_trans_runtime_error for error reporting to include locus.
-	(gfc_deallocate_with_status): Ditto.
-	* trans-stmt.c (gfc_trans_deallocate): Pass expr as new argument.
-	* trans-array.c (gfc_array_allocate): Ditto.
-	(gfc_array_deallocate): New argument `expr', passed on.
-	(gfc_trans_dealloc_allocated): Pass NULL for expr.
-	* trans-openmp.c (gfc_omp_clause_default): Ditto.
-
-2008-09-18  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37274
-	PR fortran/36374
-	* module.c (check_for_ambiguous): New function to test loaded
-	symbol for ambiguity with fixup symbol.
-	(read_module): Call check_for_ambiguous.
-	(write_symtree): Do not write the symtree for symbols coming
-	from an interface body.
-
-	PR fortran/36374
-	* resolve.c (count_specific_procs ): New function to count the
-	number of specific procedures with the same name as the generic
-	and emit appropriate errors for and actual argument reference.
-	(resolve_assumed_size_actual): Add new argument no_formal_args.
-	Correct logic around passing generic procedures as arguments.
-	Call count_specific_procs from two locations.
-	(resolve_function): Evaluate and pass no_formal_args.
-	(resolve call): The same and clean up a bit by using csym more
-	widely.
-
-	PR fortran/36454
-	* symbol.c (gfc_add_access): Access can be updated if use
-	associated and not private.
-
-2008-09-17  Jakub Jelinek  <jakub@redhat.com>
-
-	PR fortran/37536
-	* trans-stmt.c (gfc_trans_do): Optimize integer type non-simple
-	do loop initialization.
-
-2008-09-14  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-	    Tobias Burnus  <burnus@net.b.de>
-
-	PR fortran/35840
-	* io.c (match_vtag): Add tag name to error message.
-	(match_out_tag): Cleanup whitespace.
-	(gfc_resolve_dt): Resolve id and async tags. 
-
-2008-09-13  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/35770
-	* primary.c (gfc_match_varspec): Added missing type-spec clearing
-	after wrong implicit character typing.
-
-2008-09-12  Richard Guenther  <rguenther@suse.de>
-
-	* trans-intrinsic.c (gfc_conv_intrinsic_transfer): Use
-	build_fold_addr_expr to properly mark the argument
-	addressable.
-
-2008-09-11  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/36214
-	* simplify.c (simplify_cmplx): Added linebreak to long line.
-	* target-memory.c (gfc_convert_boz): Fix indentation.
-	(gfc_interpret_float): Set mpfr precision to right value before
-	calling mpfr_init.
-
-2008-09-10  H.J. Lu  <hongjiu.lu@intel.com>
-
-	* expr.c (find_array_element): Reformat comment.
-
-2008-09-10  H.J. Lu  <hongjiu.lu@intel.com>
-
-	* expr.c (find_array_element): Reformat.
-
-2008-09-10  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37420
-	* trans-decl.c (get_proc_pointer_decl): Fix -Wunused-variable.
-
-2008-09-09  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37429
-	* resolve.c (expression_rank): Added assertion to guard against
-	EXPR_COMPCALL expressions.
-	(resolve_compcall): Set expression's rank from the target procedure's.
-
-2008-09-09  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37411
-	* trans-array.c (gfc_conv_array_parameter): Added assertion that the
-	symbol has an array spec.
-
-2008-09-08  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37199
-	* trans-expr.c (gfc_add_interface_mapping): Set new_sym->as.
-	(gfc_map_intrinsic_function): Added checks against NULL bounds in
-	array specs.
-
-2008-09-08  Tobias Burnus  <burnus@net.b.de>
-
-	PR fortran/37400
-	* symbol.c (gfc_set_default_type): Copy char len.
-
-2008-09-06  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/36153
-	* fortran/resolve.c (resolve_function): Shortcircuit for SIZE and
-	UBOUND if 2nd argument is KIND.
-
-2008-09-06  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/33229
-	* resolve.c (resolve_function): An intrinsic subroutine should not be
-	called as a function.
-
-2008-09-05  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/35837
-	* resolve.c (resolve_types): Restore gfc_current_ns on exit.
-	* symbol.c (gfc_save_all): Removed blank line.
-
-2008-09-05  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/36746
-	* primary.c (gfc_match_rvalue): Removed logic to handle implicit
-	typing to a derived-type if a component reference is found.
-	(gfc_match_varspec): Moved it here.
-
-2008-09-04  Richard Guenther  <rguenther@suse.de>
-
-	* trans-array.c (gfc_conv_array_parameter): Use correct types
-	in building COND_EXPRs.
-	* trans-expr.c (gfc_conv_missing_dummy): Likewise.
-	* trans-intrinsics.c (gfc_conv_intrinsic_merge): Likewise.
-
-2008-09-04  Daniel Kraft  <d@domob.eu>
-
-	* PR fortran/37099
-	* expr.c (simplify_const_ref): Update expression's character length
-	when pulling out a substring reference.
-
-2008-09-04  Ian Lance Taylor  <iant@google.com>
-
-	* symbol.c (generate_isocbinding_symbol): Compare
-	gfc_notification_std with ERROR rather than FAILURE.
-	* resolve.c (check_assumed_size_reference): Compare array type
-	with AR_FULL rather than DIMEN_ELEMENT.
-	(resolve_actual_arglist): Compare with EXPR_VARIABLE rather than
-	FL_VARIABLE.
-
-2008-09-01  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/37228
-	* io.c (check_format): Allow specifying precision with g0 format.
-
-2008-09-02  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (struct gfc_namespace): New member `implicit_loc'.
-	(gfc_add_abstract): New method.
-	* decl.c (gfc_get_type_attr_spec): Match ABSTRACT attribute.
-	(gfc_match_derived_decl): Copy abstract attribute in derived symbol.
-	* dump-parse-tree.c (show_attr): Show ABSTRACT attribute as `ABSTRACT'
-	only to allow for ABSTRACT types.
-	* parse.c (parse_interface): Use new gfc_add_abstract.
-	* primary.c (gfc_match_structure_constructor): Check that no ABSTRACT
-	type is constructed.
-	* resolve.c (resolve_typespec_used): New method.
-	(resolve_fl_derived): Check type in respect to ABSTRACT attribute and
-	check that no component is of an ABSTRACT type.
-	(resolve_symbol): Check that no symbol is of an ABSTRACT type.
-	(resolve_types): Check IMPLICIT declarations for ABSTRACT types.
-	* symbol.c (gfc_merge_new_implicit): Remember loci of IMPLICIT's.
-	(gfc_add_abstract): New method.
-
-2008-09-01  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/37193
-	* module.c (read_module): Initialize use_only flag on used symbols.
-
-2008-09-01  Daniel Kraft  <d@domob.eu>
-
-	* gfc-internals.texi (F2003 OOP), (Type-bound Procedures): New chapter
-	and section to document the internals of type-bound procedures.
-	(gfc_expr): Document EXPR_COMPCALL.
-	* gfortran.h (struct gfc_expr): Remove unused `derived' from compcall.
-	* dump-parse-tree.c (show_compcall): New method.
-	(show_expr): Call it for EXPR_COMPCALL.
-	(show_typebound), (show_f2k_derived): New methods.
-	(show_symbol): Call show_f2k_derived.
-	(show_code_node): Handle EXEC_COMPCALL.
-	* primary.c (gfc_match_varspec): Don't initialize removed `derived' in
-	primary->value.compcall.
-
-2008-08-31  Richard Guenther  <rguenther@suse.de>
-
-	* trans-expr.c (gfc_trans_string_copy): Use the correct types
-	to compute slen and dlen.
-
-2008-08-31  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (enum gfc_statement): New entry `ST_GENERIC'.
-	(struct gfc_tbp_generic): New type.
-	(struct gfc_typebound_proc): Removed `target' and added union with
-	`specific' and `generic' members; new members `overridden',
-	`subroutine', `function' and `is_generic'.
-	(struct gfc_expr): New members `derived' and `name' in compcall union
-	member and changed type of `tbp' to gfc_typebound_proc.
-	(gfc_compare_interfaces), (gfc_compare_actual_formal): Made public.
-	* match.h (gfc_typebound_default_access): New global.
-	(gfc_match_generic): New method.
-	* decl.c (gfc_match_generic): New method.
-	(match_binding_attributes): New argument `generic' and handle it.
-	(match_procedure_in_type): Mark matched binding as non-generic.
-	* interface.c (gfc_compare_interfaces): Made public.
-	(gfc_compare_actual_formal): Ditto.
-	(check_interface_1), (compare_parameter): Use new public names.
-	(gfc_procedure_use), (gfc_search_interface): Ditto.
-	* match.c (match_typebound_call): Set base-symbol referenced.
-	* module.c (binding_generic): New global array.
-	(current_f2k_derived): New global.
-	(mio_typebound_proc): Handle IO of GENERIC bindings.
-	(mio_f2k_derived): Record current f2k-namespace in current_f2k_derived.
-	* parse.c (decode_statement): Handle GENERIC statement.
-	(gfc_ascii_statement): Ditto.
-	(typebound_default_access), (set_typebound_default_access): Removed.
-	(gfc_typebound_default_access): New global.
-	(parse_derived_contains): New default-access implementation and handle
-	GENERIC statements encountered.
-	* primary.c (gfc_match_varspec): Adapted to new gfc_typebound_proc
-	structure and removed check for SUBROUTINE/FUNCTION from here.
-	* resolve.c (extract_compcall_passed_object): New method.
-	(update_compcall_arglist): Use it.
-	(resolve_typebound_static): Adapted to new gfc_typebound_proc structure.
-	(resolve_typebound_generic_call): New method.
-	(resolve_typebound_call): Check target is a SUBROUTINE and handle calls
-	to GENERIC bindings.
-	(resolve_compcall): Ditto (check for target being FUNCTION).
-	(check_typebound_override): Handle GENERIC bindings.
-	(check_generic_tbp_ambiguity), (resolve_typebound_generic): New methods.
-	(resolve_typebound_procedure): Handle GENERIC bindings and set new
-	attributes subroutine, function and overridden in gfc_typebound_proc.
-	(resolve_fl_derived): Ensure extended type is resolved before the
-	extending one is.
-	* st.c (gfc_free_statement): Fix bug with free'ing EXEC_COMPCALL's.
-	* symbol.c (gfc_find_typebound_proc): Adapt for GENERIC changes.
-
-2008-08-29  Jan Hubicka  <jh@suse.cz>
-	
-	* parse.c (parse_interface): Silence uninitialized var warning.
-
-2008-08-29  Jakub Jelinek  <jakub@redhat.com>
-
-	* trans.h (struct lang_type): Add span.
-	(GFC_TYPE_ARRAY_SPAN): Define.
-	* trans-decl.c (gfc_get_symbol_decl): For subref array pointers,
-	copy TREE_STATIC from decl to span instead of setting it
-	unconditionally, set DECL_ARTIFICIAL, fix type of initializer
-	and set GFC_TYPE_ARRAY_SPAN on decl's type.
-	* trans-types.c (gfc_get_array_descr_info): If
-	GFC_TYPE_ARRAY_SPAN is non-NULL, use it as element size.
-
-	* trans-decl.c (check_constant_initializer,
-	gfc_emit_parameter_debug_info): New functions.
-	(gfc_generate_module_vars, gfc_generate_function_code): Emit
-	PARAMETERs and unreferenced variables with initializers into
-	debug info.
-
-	* gfortran.h (gfc_use_list): Add where field.
-	* module.c (use_locus): New static variable.
-	(gfc_match_use): Set it.
-	(gfc_use_module): Copy it to gfc_use_list's where field.
-	* trans-decl.c (gfc_generate_module_vars): Call gfc_trans_use_stmts.
-	(gfc_trans_use_stmts): Set backend locus before calling the debug
-	hook.  Allow non-VAR_DECLs to be created even for non-external
-	module.  Don't emit anything so far for renames from different
-	modules.
-
-	PR fortran/24790
-	* trans-decl.c (create_function_arglist): Set DECL_BY_REFERENCE on
-	PARM_DECLs with pointer or reference type.
-
-	* trans-decl.c (gfc_build_qualified_array): Build non-flat
-	array type for debug info purposes.
-
-	PR fortran/29635
-	PR fortran/23057
-	* f95-lang.c (gfc_init_ts): New function.
-	(LANG_HOOKS_INIT_TS): Define.
-	* gfortran.h (gfc_use_rename): New type, moved from module.c.
-	(gfc_get_use_rename): New macro, moved from module.c.
-	(gfc_use_list): New type.
-	(gfc_get_use_list): New macro.
-	(gfc_namespace): Add use_stmts field.
-	(gfc_free_use_stmts): New prototype.
-	* Make-lang.in (fortran/trans-decl.o): Depend on debug.h.
-	* module.c (gfc_use_rename, gfc_get_use_rename): Moved to
-	gfortran.h.
-	(gfc_use_module): Chain the USE statement info to
-	ns->use_stmts.
-	(gfc_free_use_stmts): New function.
-	* symbol.c (gfc_free_namespace): Call gfc_free_use_stmts.
-	* trans.h (struct module_htab_entry): New type.
-	(gfc_find_module, gfc_module_add_decl): New functions.
-	* trans.c (gfc_generate_module_code): Create NAMESPACE_DECL for
-	the module, adjust DECL_CONTEXTs of module procedures and
-	call gfc_module_add_decl for them.
-	* trans-common.c (build_common_decl): Set DECL_IGNORED_P
-	on the common variable.
-	(create_common): Set DECL_IGNORED_P for use associated vars.
-	* trans-decl.c: Include debug.h.
-	(gfc_get_symbol_decl): Set DECL_IGNORED_P on use_assoc vars from
-	modules.
-	(build_function_decl): Allow current_function_decl's context
-	to be a NAMESPACE_DECL.
-	(module_htab, cur_module): New variables.
-	(module_htab_do_hash, module_htab_eq, module_htab_decls_hash,
-	module_htab_decls_eq, gfc_find_module, gfc_module_add_decl): New
-	functions.
-	(gfc_create_module_variable): Adjust DECL_CONTEXTs of module
-	variables and types and call gfc_module_add_decl for them.
-	(gfc_generate_module_vars): Temporarily set cur_module.
-	(gfc_trans_use_stmts): New function.
-	(gfc_generate_function_code): Call it.
-	(gfc_generate_block_data): Set DECL_IGNORED_P on decl.
-	* trans-types.c (gfc_get_derived_type): Adjust DECL_CONTEXT
-	and TYPE_CONTEXT of module derived types.
-
-2008-08-28  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (enum expr_t): New value `EXPR_COMPCALL'.
-	(gfc_get_typebound_proc): New macro.
-	(struct gfc_expr): New union-member `compcall' for EXPR_COMPCALL.
-	(enum gfc_exec_op): New value `EXEC_COMPCALL'.
-	(gfc_find_typebound_proc): New argument.
-	(gfc_copy_ref), (gfc_match_varspec): Made public.
-	* decl.c (match_procedure_in_type): Use gfc_get_typebound_proc.
-	* expr.c (free_expr0), (gfc_copy_expr): Handle EXPR_COMPCALL.
-	(gfc_copy_ref): Made public and use new name.
-	(simplify_const_ref): Use new name of gfc_copy_ref.
-	(simplify_parameter_variable): Ditto.
-	(gfc_simplify_expr): gcc_unreachable for EXPR_COMPCALL.
-	* match.c (match_typebound_call): New method.
-	(gfc_match_call): Allow for CALL's to typebound procedures.
-	* module.c (binding_passing), (binding_overriding): New variables.
-	(expr_types): Add EXPR_COMPCALL.
-	(mio_expr): gcc_unreachable for EXPR_COMPCALL.
-	(mio_typebound_proc), (mio_typebound_symtree): New methods.
-	(mio_f2k_derived): Handle type-bound procedures.
-	* primary.c (gfc_match_varspec): Made public and parse trailing
-	references to type-bound procedures; new argument `sub_flag'.
-	(gfc_match_rvalue): New name and argument of gfc_match_varspec.
-	(match_variable): Ditto.
-	* resolve.c (update_arglist_pass): New method.
-	(update_compcall_arglist), (resolve_typebound_static): New methods.
-	(resolve_typebound_call), (resolve_compcall): New methods.
-	(gfc_resolve_expr): Handle EXPR_COMPCALL.
-	(resolve_code): Handle EXEC_COMPCALL.
-	(resolve_fl_derived): New argument to gfc_find_typebound_proc.
-	(resolve_typebound_procedure): Ditto and removed not-implemented error.
-	* st.c (gfc_free_statement): Handle EXEC_COMPCALL.
-	* symbol.c (gfc_find_typebound_proc): New argument `noaccess' and
-	implement access-checking.
-	* trans-expr.c (gfc_apply_interface_mapping_to_expr): gcc_unreachable
-	on EXPR_COMPCALL.
-	* trans-intrinsic.c (gfc_conv_intrinsic_bound): Add missing break.
-	* trans-openmp.c (gfc_trans_omp_array_reduction): Add missing
-	intialization of ref->type.
-
-2008-08-28  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/37253
-	* module.c (ab_attribute,attr_bits,mio_symbol_attribute): Take care of
-	saving attr.procedure and attr.proc_ptr to the module file.
-
-2008-08-25  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (gfc_find_component): Add new arguments.
-	* parse.c (parse_derived_contains): Check if the derived-type containing
-	the CONTAINS section is SEQUENCE/BIND(C).
-	* resolve.c (resolve_typebound_procedure): Check for name collision with
-	components.
-	(resolve_fl_derived): Check for name collision with inherited
-	type-bound procedures.
-	* symbol.c (gfc_find_component): New arguments `noaccess' and `silent'.
-	(gfc_add_component): Adapt for new arguments.
-	* primary.c (match_varspec), (gfc_match_structure_constructor): Ditto.
-
-2008-08-24  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37201
-	* decl.c (verify_bind_c_sym): Reject array/string returning
-	functions.
-
-2008-08-24  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37201
-	* trans-expr.c (gfc_conv_function_call): Add string_length
-	for character-returning bind(C) functions.
-
-2008-08-24  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (gfc_typebound_proc):  New struct.
-	(gfc_symtree):  New member typebound.
-	(gfc_find_typebound_proc):  Prototype for new method.
-	(gfc_get_derived_super_type):  Prototype for new method.
-	* parse.h (gfc_compile_state):  New state COMP_DERIVED_CONTAINS.
-	* decl.c (gfc_match_procedure):  Handle PROCEDURE inside derived-type
-	CONTAINS section.
-	(gfc_match_end):  Handle new context COMP_DERIVED_CONTAINS.
-	(gfc_match_private):  Ditto.
-	(match_binding_attributes), (match_procedure_in_type):  New methods.
-	(gfc_match_final_decl):  Rewrote to make use of new
-	COMP_DERIVED_CONTAINS parser state.
-	* parse.c (typebound_default_access):  New global helper variable.
-	(set_typebound_default_access):  New callback method.
-	(parse_derived_contains):  New method.
-	(parse_derived):  Extracted handling of CONTAINS to new parser state
-	and parse_derived_contains.
-	* resolve.c (resolve_bindings_derived), (resolve_bindings_result):  New.
-	(check_typebound_override), (resolve_typebound_procedure):  New methods.
-	(resolve_typebound_procedures):  New method.
-	(resolve_fl_derived):  Call new resolving method for typebound procs.
-	* symbol.c (gfc_new_symtree):  Initialize new member typebound to NULL.
-	(gfc_find_typebound_proc):  New method.
-	(gfc_get_derived_super_type):  New method.
-
-2008-08-23  Janus Weil  <janus@gcc.gnu.org>
-
-	* gfortran.h (gfc_component): Add field "symbol_attribute attr", remove
-	fields "pointer", "allocatable", "dimension", "access".
-	Remove functions "gfc_set_component_attr" and "gfc_get_component_attr".
-	* interface.c (gfc_compare_derived_types): Ditto.
-	* trans-array.c (gfc_array_allocate,structure_alloc_comps): Ditto.
-	* trans-expr.c (gfc_conv_component_ref,gfc_trans_subcomponent_assign,
-	gfc_conv_structure): Ditto.
-	* symbol.c (gfc_find_component,free_components,gfc_set_component_attr,
-	gfc_get_component_attr,verify_bind_c_derived_type,
-	generate_isocbinding_symbol): Ditto.
-	* decl.c (build_struct): Ditto.
-	* dump-parse-tree.c (show_components): Ditto.
-	* trans-stmt.c (gfc_trans_deallocate): Ditto.
-	* expr.c (gfc_check_assign,gfc_check_pointer_assign,
-	gfc_default_initializer): Ditto.
-	* module.c (mio_component): Ditto.
-	* trans-types.c (copy_dt_decls_ifequal,gfc_get_derived_type): Ditto.
-	* resolve.c (has_default_initializer,resolve_structure_cons,
-	gfc_iso_c_func_interface,find_array_spec,resolve_ref,
-	resolve_deallocate_expr,resolve_allocate_expr,resolve_fl_derived,
-	resolve_equivalence_derived): Ditto.
-	* trans-io.c (transfer_expr): Ditto.
-	* parse.c (parse_derived): Ditto.
-	* dependency.c (gfc_check_dependency): Ditto.
-	* primary.c (gfc_variable_attr): Ditto.
-
-2008-08-23  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37076
-	* arith.c (gfc_arith_concat): Fix concat of kind=4 strings.
-
-2008-08-23  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/37025
-	* target-memory.c (gfc_interpret_character): Support
-	kind=4 characters.
-
-2008-08-22  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/30239
-	* symbol.c (gfc_add_type): Warn on -Wsurprising if a function-result
-	type is re-declared but neither -pedantic nor -std=f* is given and so
-	this is no error.
-	* invoke.texi (-Wsurprising): Document this new behaviour.
-
-2008-08-22  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (in_prefix): Removed from this header.
-	* match.h (gfc_matching_prefix): Moved and renamed from `in_prefix'.
-	* decl.c (in_prefix): Removed from here.
-	(gfc_match_prefix): Use new name of `gfc_matching_prefix'.
-	* symbol.c (gfc_check_symbol_typed): Ditto.
-	* expr.c (check_typed_ns): New helper variable.
-	(expr_check_typed_help): New helper method.
-	(gfc_expr_check_typed): Rewrote to use gfc_traverse_expr to do the
-	work, fixing a minor problem.
-	* match.c (gfc_matching_prefix): New variable.
-
-2008-08-22  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/32095
-	PR fortran/34228
-	* gfortran.h (in_prefix): New global.
-	(gfc_check_symbol_typed), (gfc_check_expr_typed): New methods.
-	* array.c (match_array_element_spec): Check that bounds-expressions
-	don't have symbols not-yet-typed in them.
-	* decl.c (var_element): Check that variable used is already typed.
-	(char_len_param_value): Check that expression does not contain
-	not-yet-typed symbols.
-	(in_prefix): New global.
-	(gfc_match_prefix): Record using `in_prefix' if we're at the moment
-	parsing a prefix or not.
-	* expr.c (gfc_expr_check_typed): New method.
-	* parse.c (verify_st_order): New argument to disable error output.
-	(check_function_result_typed): New helper method.
-	(parse_spec): Check that the function-result declaration, if given in
-	a prefix, contains no not-yet-typed symbols when the IMPLICIT rules are
-	parsed.
-	* symbol.c (gfc_check_symbol_typed): Check that a symbol already has
-	a type associated to it, otherwise use the IMPLICIT rules or signal
-	an error.
-
-2008-08-21  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
-
-	* f95-lang.c: Update all calls to pedwarn.
-
-2008-08-18  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/37032
-	* gfortran.texi: Document decision on include file handling in
-	preprocessed files.
-
-2008-08-16  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36825
-	* libgfortran.h: Reduce GFC_MAX_DIMENSIONS to 7.
-
-2008-08-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35863
-	* io.c (gfc_match_open): Enable UTF-8 in checks.
-	* simplify.c (gfc_simplify_selected_char_kind): Enable iso_10646.
-
-2008-08-14  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36705
-	* symbol.c (check_conflict): Move conflict checks for (procedure,save)
-	and (procedure,intent) to resolve_fl_procedure.
-	* resolve.c (resolve_fl_procedure): Ditto.
-
-2008-08-09  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
-
-	PR 36901
-	* f95-lang.c (gfc_mark_addressable): Use "pedwarn (0," instead of
-	'pedwarn0'.
-
-2008-08-09  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/37011
-	* symbol.c (gfc_add_extension): New function.
-	* decl.c (gfc_get_type_attr_spec): Call it.
-	(gfc_match_derived_decl): Set symbol extension attribute from
-	attr.extension.
-	* gfortran.h : Add prototype for gfc_add_extension.
-
-2008-08-08  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
-
-	PR 28875
-	* options.c (set_Wall): Replace set_Wunused by warn_unused.
-
-2008-08-08  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h (gfc_finalizer):  Replaced member `procedure' by two
-	new members `proc_sym' and `proc_tree' to store the symtree after
-	resolution.
-	(gfc_find_sym_in_symtree):  Made public.
-	* decl.c (gfc_match_final_decl):  Adapted for new member name.
-	* interface.c (gfc_find_sym_in_symtree):  Made public.
-	(gfc_extend_expr), (gfc_extend_assign):  Changed call accordingly.
-	* module.c (mio_finalizer), (mio_f2k_derived), (mio_full_f2k_derived):
-	New methods for module-file IO of f2k_derived.
-	(mio_symbol):  Do IO of f2k_derived namespace.
-	* resolve.c (gfc_resolve_finalizers):  Adapted for new member name and
-	finding the symtree for the symbol here.
-	* symbol.c (gfc_free_finalizer):  Adapted for new members.
-
-2008-07-30  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* gfc-internals.texi: Update to GFDL 1.2.  Do not list GPL as
-	Invariant Section.
-	* gfortran.texi: Likewise.
-	* intrinsic.texi: Do not list GPL as Invariant Section.
-	* invoke.texi: Likewise.  Update copyright years.
-
-2008-07-29  Paul Thomas  <pault@gcc.gnu.org>
-
-	* trans-expr.c (conv_parent_component_references): New function
-	to build missing parent references.
-	(gfc_conv_variable): Call it
-	* symbol.c (gfc_add_component): Check that component name in a
-	derived type extension does not appear in parent.
-	(gfc_find_component): For a derived type extension, check if
-	the component appears in the parent derived type by calling
-	self. Separate errors for private components and private types.
-	* decl.c (match_data_constant): Add extra arg to call to
-	gfc_match_structure_constructor.
-	(check_extended_derived_type): New function to check that a
-	parent derived type exists and that it is OK for exension.
-	(gfc_get_type_attr_spec): Add extra argument 'name' and return
-	it if extends is specified.
-	(gfc_match_derived_decl): Match derived type extension and
-	build a first component of the parent derived type if OK. Add
-	the f2k namespace if not present.
-	* gfortran.h : Add the extension attribute.
-	* module.c : Handle attribute 'extension'.
-	* match.h : Modify prototypes for gfc_get_type_attr_spec and
-	gfc_match_structure_constructor.
-	* primary.c (build_actual_constructor): New function extracted
-	from gfc_match_structure_constructor and modified to call self
-	iteratively to build derived type extensions, when f2k named
-	components are used.
-	(gfc_match_structure_constructor): Do not throw error for too
-	many components if a parent type is being handled. Use
-	gfc_find_component to generate errors for non-existent or
-	private components.  Iteratively call self for derived type
-	extensions so that parent constructor is built.  If extension
-	and components left over, throw error.
-	(gfc_match_rvalue): Add extra arg to call to
-	gfc_match_structure_constructor.
-
-	* trans-array.c (gfc_conv_resolve_dependencies): If lhs and rhs
-	are the same symbol, aliassing does not matter.
-
-2008-07-29  Jan Hubicka  <jh@suse.cz>
-
-	* options.c (gfc_post_options): Do not set flag_no_inline.
-
-2008-07-29  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/36403
-	* trans-intrinsic.c (conv_generic_with_optional_char_arg):  New method
-	to append a string-length even if the string argument is missing, e.g.
-	for EOSHIFT.
-	(gfc_conv_intrinsic_function):  Call the new method for EOSHIFT, PACK
-	and RESHAPE.
-
-2008-07-28  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* gfortran.h (try): Remove macro.  Replace try with gfc_try
-	throughout.
-	* array.c: Likewise.
-	* check.c: Likewise.
-	* cpp.c: Likewise.
-	* cpp.h: Likewise.
-	* data.c: Likewise.
-	* data.h: Likewise.
-	* decl.c: Likewise.
-	* error.c: Likewise.
-	* expr.c: Likewise.
-	* interface.c: Likewise.
-	* intrinsic.c: Likewise.
-	* intrinsic.h: Likewise.
-	* io.c: Likewise.
-	* match.h: Likewise.
-	* parse.c: Likewise.
-	* parse.h: Likewise.
-	* resolve.c: Likewise.
-	* scanner.c: Likewise.
-	* simplify.c: Likewise.
-	* symbol.c: Likewise.
-	* trans-openmp.c: Likewise.
-	* trans-types.c: Likewise.
-
-2008-07-28  Tobias Burnus  <burnus@net-b.de>
-
-	* Make-lang.in: Remove -Wno-* from fortran-warn.
-
-2008-07-28  Richard Guenther  <rguenther@suse.de>
-
-	Merge from gimple-tuples-branch.
-
-	2008-07-18  Aldy Hernandez  <aldyh@redhat.com>
-
-	* trans-expr.c: Include gimple.h instead of tree-gimple.h.
-	* trans-array.c: Same.
-	* trans-openmp.c: Same.
-	* trans-stmt.c: Same.
-	* f95-lang.c: Same.
-	* trans-io.c: Same.
-	* trans-decl.c: Same.
-	* trans-intrinsic.c: Same.
-	* trans.c: Same.  Include tree-iterator.h.
-	* Make-lang.in (trans.o): Depend on tree-iterator.h
-
-	2008-07-14  Aldy Hernandez  <aldyh@redhat.com>
-
-	* trans-array.h (gfc_conv_descriptor_data_set_internal):
-	Rename to gfc_conv_descriptor_data_set.
-	(gfc_conv_descriptor_data_set_tuples): Remove.
-	* trans-array.c (gfc_conv_descriptor_data_get): Rename
-	from gfc_conv_descriptor_data_set_internal.
-	Remove last argument to gfc_add_modify.
-	(gfc_trans_allocate_array_storage): Rename gfc_add_modify_expr to
-	gfc_add_modify.
-	(gfc_trans_create_temp_array): Same.
-	(gfc_conv_array_transpose): Same.
-	(gfc_grow_array): Same.
-	(gfc_put_offset_into_var): Same.
-	(gfc_trans_array_ctor_element): Same.
-	(gfc_trans_array_constructor_subarray): Same.
-	(gfc_trans_array_constructor_value): Same.
-	(gfc_trans_scalarized_loop_end): Same.
-	(gfc_array_init_size): Same.
-	(gfc_array_allocate): Same.
-	(gfc_trans_array_bounds): Same.
-	(gfc_trans_auto_array_allocation): Same.
-	(gfc_trans_g77_array): Same.
-	(gfc_trans_dummy_array_bias): Same.
-	(gfc_conv_expr_descriptor): Same.
-	(structure_alloc_comps): Same.
-	* trans-expr.c: Same.
-	* trans-openmp.c (gfc_omp_clause_default_ctor): Same.
-	Rename gfc_conv_descriptor_data_set_tuples to
-	gfc_conv_descriptor_data_set.
-	(gfc_omp_clause_copy_ctor): Change build_gimple_modify_stmt to
-	build2_v.
-	(gfc_omp_clause_assign_op): Same.
-	(gfc_trans_omp_array_reduction): Rename gfc_add_modify_expr to
-	gfc_add_modify.
-	(gfc_trans_omp_atomic): Same.
-	(gfc_trans_omp_do): Same.  Change GIMPLE_MODIFY_STMT to MODIFY_EXPR.
-	Rename gfc_add_modify_stmt to gfc_add_modify.
-	* trans-stmt.c: Rename gfc_add_modify_expr to
-	gfc_add_modify.
-	* trans.c: Rename gfc_add_modify_expr to
-	gfc_add_modify.
-	(gfc_add_modify): Remove last argument.
-	Rename GIMPLE_MODIFY_STMT to MODIFY_EXPR.
-	* trans.h: Remove gfc_add_modify_expr, gfc_add_modify_stmt.
-	Add prototype for gfc_add_modify.
-	* f95-lang.c (union lang_tree_node): Rename GENERIC_NEXT to TREE_CHAIN.
-	* trans-decl.c: Rename gfc_add_modify_stmt to gfc_add_modify.
-	* trans-io.c: Same.
-	* trans-intrinsic.c: Same.
-
-	2008-02-25  Aldy Hernandez  <aldyh@redhat.com>
-
-	* Make-lang.in (fortran-warn): Add -Wno-format.
-
-	2008-02-19  Diego Novillo  <dnovillo@google.com>
-
-	http://gcc.gnu.org/ml/gcc-patches/2008-02/msg00804.html
-
-	* fortran/Make-lang.in (fortran-warn): Remove.
-
-	2007-11-22  Aldy Hernandez  <aldyh@redhat.com>
-
-	* trans-expr.c (gfc_trans_string_copy): Use "void *" when building a
-	memset.
-
-	2007-11-10  Aldy Hernandez  <aldyh@redhat.com>
-
-	* Make-lang.in (fortran-warn): Set to -Wno-format.
-	* trans.c (gfc_trans_code): Update comment to say GENERIC.
-	Call tree_annotate_all_with_locus instead of annotate_all_with_locus.
-
-2008-07-27  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36132
-	PR fortran/29952
-	PR fortran/36909
-	* trans.c (gfc_trans_runtime_check): Allow run-time warning besides
-	run-time error.
-	* trans.h (gfc_trans_runtime_check): Update declaration.
-	* trans-array.c (gfc_trans_array_ctor_element,gfc_trans_array_bound_check,
-	gfc_conv_array_ref,gfc_conv_ss_startstride,gfc_trans_dummy_array_bias):
-	Updated gfc_trans_runtime_check calls.
-	(gfc_conv_array_parameter): Implement flag_check_array_temporaries,
-	fix packing/unpacking for nonpresent optional actuals to optional
-	formals.
-	* trans-array.h (gfc_conv_array_parameter): Update declaration.
-	* trans-expr.c (gfc_conv_substring,gfc_trans_arrayfunc_assign,
-	gfc_conv_function_call): Updated gfc_trans_runtime_check calls.
-	(gfc_conv_function_call): Update gfc_conv_array_parameter calls.
-	* trans-expr.c (gfc_trans_goto): Updated gfc_trans_runtime_check
-	calls.
-	* trans-io.c (set_string,gfc_conv_intrinsic_repeat): Ditto.
-	(gfc_conv_intrinsic_transfer,gfc_conv_intrinsic_loc): Same for
-	gfc_conv_array_parameter.
-	* trans-intrinsics.c (gfc_conv_intrinsic_bound): Ditto.
-	* trans-decl.c (gfc_build_builtin_function_decls): Add
-	gfor_fndecl_runtime_warning_at.
-	* lang.opt: New option fcheck-array-temporaries.
-	* gfortran.h (gfc_options): New flag_check_array_temporaries.
-	* options.c (gfc_init_options, gfc_handle_option): Handle flag.
-	* invoke.texi: New option fcheck-array-temporaries.
-
-2008-07-24  Jan Hubicka  <jh@suse.cz>
-
-	* fortran/options.c (gfc_post_options): Remove flag_unline_trees code.
-
-2008-07-24  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/33141
-	* lang.opt (Wnonstd-intrinsics):  Removed option.
-	(Wintrinsics-std), (Wintrinsic-shadow):  New options.
-	* invoke.texi (Option Summary):  Removed -Wnonstd-intrinsics
-	from the list and added -Wintrinsics-std and -Wintrinsic-shadow.
-	(Error and Warning Options):  Documented the new options and removed
-	the documentation for -Wnonstd-intrinsics.
-	* gfortran.h (gfc_option_t):  New members warn_intrinsic_shadow and
-	warn_intrinsics_std, removed warn_nonstd_intrinsics.
-	(gfc_is_intrinsic):  Renamed from gfc_intrinsic_name.
-	(gfc_warn_intrinsic_shadow), (gfc_check_intrinsic_standard):  New.
-	* decl.c (match_procedure_decl):  Replaced gfc_intrinsic_name by
-	the new name gfc_is_intrinsic.
-	(warn_intrinsic_shadow):  New helper method.
-	(gfc_match_function_decl), (gfc_match_subroutine):  Call the new method
-	warn_intrinsic_shadow to check the just-parsed procedure.
-	* expr.c (check_init_expr):  Call new gfc_is_intrinsic to check whether
-	the function called is really an intrinsic in the selected standard.
-	* intrinsic.c (gfc_is_intrinsic):  Renamed from gfc_intrinsic_name and
-	extended to take into account the selected standard settings when trying
-	to find out whether a symbol is an intrinsic or not.
-	(gfc_check_intrinsic_standard):  Made public and extended.
-	(gfc_intrinsic_func_interface), (gfc_intrinsic_sub_interface):  Removed
-	the calls to check_intrinsic_standard, this check now happens inside
-	gfc_is_intrinsic.
-	(gfc_warn_intrinsic_shadow):  New method defined.
-	* options.c (gfc_init_options):  Initialize new warning flags to false
-	and removed intialization of Wnonstd-intrinsics flag.
-	(gfc_post_options):  Removed logic for Wnonstd-intrinsics flag.
-	(set_Wall):  Set new warning flags and removed Wnonstd-intrinsics flag.
-	(gfc_handle_option):  Handle the new flags and removed handling of the
-	old Wnonstd-intrinsics flag.
-	* primary.c (gfc_match_rvalue):  Replaced call to gfc_intrinsic_name by
-	the new name gfc_is_intrinsic.
-	* resolve.c (resolve_actual_arglist):  Ditto.
-	(resolve_generic_f), (resolve_unknown_f):  Ditto.
-	(is_external_proc):  Ditto.
-	(resolve_generic_s), (resolve_unknown_s):  Ditto.
-	(resolve_symbol):  Ditto and ensure for symbols declared INTRINSIC that
-	they are really available in the selected standard setting.
-
-2008-07-24  Daniel Kraft  <d@domob.eu>
-
-	* match.c (gfc_match):  Add assertion to catch wrong calls trying to
-	match upper-case characters.
-
-2008-07-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/29952
-	* gfortran.h:  Add "warn_array_temp" to gfc_option_t.
-	* lang.opt:  Add -Warray-temporaries.
-	* invoke.texi:  Document -Warray-temporaries
-	* trans-array.h (gfc_trans_create_temp_array):  Add argument of
-	type *locus.
-	(gfc_conv_loop_setup):  Likewise.
-	* trans-array.c (gfc_trans_create_temp_array):  If
-	-Warray-temporaries is given and locus is present, warn about
-	creation of array temporaries.
-	(gfc_trans_array_constructor_subarray):  Add locus to call
-	of gfc_conv_loop_setup.
-	(gfc_trans_array_constructor):  Add where argument.  Pass where
-	argument to call of gfc_trans_create_temp_array.
-	(gfc_add_loop_ss_code):  Add where argument.  Pass where argument
-	to recursive call of gfc_add_loop_ss_code and to call of
-	gfc_trans_array_constructor.
-	(gfc_conv_loop_setup):  Add where argument.  Pass where argument
-	to calls to gfc_add_loop_ss_code and to gfc_trans_create_temp_array.
-	(gfc_conv_expr_descriptor):  Pass location to call of
-	gfc_conv_loop_setup.
-	(gfc_conv_array_parameter):  If -Warray-temporaries is given,
-	warn about creation of temporary arrays.
-	* trans-expr.c (gfc_conv_subref_array_arg):  Add where argument
-	to call to gfc_conv_loop_setup.
-	(gfc_conv_function_call):  Add where argument to call to
-	gfc_trans_creat_temp_array.
-	(gfc_trans_subarray_assign):  Likewise.
-	(gfc_trans_assignment_1):  Add where argument to call to
-	gfc_conv_loop_setup.
-	* trans-stmt.c (gfc_conv_elemental_dependencies):  Add where
-	argument to call to gfc_trans_create_temp_array.
-	(gfc_trans_call):  Add where argument to call to gfc_conv_loop_setup.
-	(generate_loop_for_temp_to_lhs):  Likewise.
-	(generate_loop_for_rhs_to_temp):  Likewise.
-	(compute_inner_temp_size):  Likewise.
-	(gfc_trans-pointer_assign_need_temp):  Likewise.
-	(gfc_evaluate_where_mask):  Likewise.
-	(gfc_trans_where_assign):  Likewise.
-	(gfc_trans_where_3):  Likewise.
-	* trans-io.c (transfer_srray_component):  Add where argument
-	to function. Add where argument to call to gfc_conv_loop_setup.
-	(transfer_expr):  Add where argument to call to
-	transfer_array_component.
-	(gfc_trans_transfer):  Add where expression to call to
-	gfc_conv_loop_setup.
-	* trans-intrinsic.c (gfc_conv_intrinsic_anyall):  Add
-	where argument to call to gfc_conv_loop_setup.
-	(gfc_conv_intrinsic_count):  Likewise.
-	(gfc_conv_intrinsic_arith):  Likewise.
-	(gfc_conv_intrinsic_dot_product):  Likewise.
-	(gfc_conv_intrinsic_minmaxloc):  Likewise.
-	(gfc_conv_intrinsic_minmaxval):  Likewise.
-	(gfc_conv_intrinsic_array_transfer):  Warn about
-	creation of temporary array.
-	Add where argument to call to gfc_trans_create_temp_array.
-	* options.c (gfc_init_options):  Initialize gfc_option.warn_array_temp.
-	(gfc_handle_option):  Set gfc_option.warn_array_temp.
-
-2008-07-23  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
-
-	PR 35058
-	* f95-lang.c (gfc_mark_addressable): All calls to pedwarn changed.
-
-2008-07-22  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/29835
-	* io.c (error_element), (format_locus):  New static globals.
-	(unexpected_element):  Spelled out this message fully.
-	(next_char):  Keep track of locus when not MODE_STRING.
-	(next_char_not_space):  Remember last parsed element in error_element.
-	(format_lex):  Fix two indentation errors.
-	(check_format):  Use format_locus and possibly error_element for a
-	slightly better error message on invalid format.
-	(check_format_string):  Set format_locus to start of the string
-	expression used as format.
-
-2008-07-21  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* expr.c (gfc_check_pointer_assign): Fix typo in string.
-	* io.c (check_format): Fix typo in string.  Fix comment typos.
-	* parse.c (gfc_global_used): Likewise.
-	* resolve.c (resolve_allocate_expr): Likewise.
-	* symbol.c (gfc_set_default_type): Likewise.
-	* arith.c: Fix typos in comments.
-	* array.c: Likewise.
-	* data.c: Likewise.
-	* decl.c: Likewise.
-	* dependency.c: Likewise.
-	* f95-lang.c: Likewise.
-	* gfortran.h: Likewise.
-	* matchexp.c: Likewise.
-	* module.c: Likewise.
-	* primary.c: Likewise.
-	* scanner.c: Likewise.
-	* trans-array.c: Likewise.
-	* trans-common.c: Likewise.
-	* trans-decl.c: Likewise.
-	* trans-expr.c: Likewise.
-	* trans-intrinsic.c: Likewise.
-	* trans-types.c: Likewise.
-	* trans.c: Likewise.
-	* trans.h: Likewise.
-
-2008-07-19  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36795
-	* matchexp.c (gfc_get_parentheses): Remove obsolete workaround,
-	which caused the generation of wrong code.
-
-2008-07-19  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36342
-	* scanner.c (load_file): Add argument to destinguish between
-	true filename and displayed filename.
-	(include_line,gfc_new_file): Adapt accordingly.
-
-2008-07-19  Tobias Burnus  <burnus@net-b.de>
-
-	* check.c (gfc_check_cshift,gfc_check_eoshift,gfc_check_unpack): Add rank
-	checks for cshift's shift and eoshift's shift and boundary args.
-	(gfc_check_unpack): Add rank and shape tests for unpack.
-
-2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* gfortran.h (new): Remove macro.
-	* array.c (gfc_append_constructor, match_array_list,
-	gfc_match_array_constructor): Likewise.
-	* bbt.c (insert, gfc_insert_bbt): Likewise.
-	* decl.c (var_element, top_var_list, top_val_list, gfc_match_data,
-	get_proc_name): Likewise.
-	* expr.c (gfc_copy_actual_arglist): Likewise.
-	* interface.c (compare_actual_formal, check_new_interface,
-	gfc_add_interface): Likewise.
-	* intrinsic.c gfc_convert_type_warn, gfc_convert_chartype):
-	Likewise.
-	* io.c (match_io_iterator, match_io_list): Likewise.
-	* match.c (match_forall_header): Likewise.
-	* matchexp.c (build_node): Likewise.
-	* module.c (gfc_match_use): Likewise.
-	* scanner.c (load_file): Likewise.
-	* st.c (gfc_append_code): Likewise.
-	* symbol.c (save_symbol_data, gfc_get_sym_tree, gfc_undo_symbols,
-	gfc_commit_symbols): Likewise.
-	* trans-common.c (build_field): Likewise.
-	* trans-decl.c (gfc_finish_var_decl): Likewise.
-	* trans-expr.c (gfc_free_interface_mapping,
-	gfc_get_interface_mapping_charlen, gfc_add_interface_mapping,
-	gfc_finish_interface_mapping,
-	gfc_apply_interface_mapping_to_expr): Likewise.
-	* trans.h (gfc_interface_sym_mapping): Likewise.
-
-2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* gfortran.h (operator): Remove macro.
-	(gfc_namespace, gfc_expr): Avoid C++ keywords.
-	* arith.c (eval_intrinsic, eval_intrinsic_f2, eval_intrinsic_f3):
-	Likewise.
-	* decl.c (access_attr_decl): Likewise.
-	* dependency.c (gfc_dep_compare_expr): Likewise.
-	* dump-parse-tree.c (show_expr, show_uop, show_namespace):
-	Likewise.
-	* expr.c (gfc_copy_expr, gfc_type_convert_binary,
-	simplify_intrinsic_op, check_intrinsic_op): Likewise.
-	* interface.c (fold_unary, gfc_match_generic_spec,
-	gfc_match_interface, gfc_match_end_interface,
-	check_operator_interface, check_uop_interfaces,
-	gfc_check_interfaces, gfc_extend_expr, gfc_extend_assign,
-	gfc_add_interface, gfc_current_interface_head,
-	gfc_set_current_interface_head): Likewise.
-	* iresolve.c (gfc_resolve_dot_product, gfc_resolve_matmul):
-	Likewise.
-	* matchexp.c (gfc_get_parentheses, build_node): Likewise.
-	* module.c (gfc_use_rename, gfc_match_use, find_use_name_n,
-	number_use_names, mio_expr, load_operator_interfaces, read_module,
-	write_operator, write_module): Likewise.
-	* openmp.c (resolve_omp_atomic): Likewise.
-	* resolve.c (resolve_operator, gfc_resolve_character_operator,
-	gfc_resolve_uops): Likewise.
-	* symbol.c (free_uop_tree, gfc_free_namespace): Likewise.
-	* trans-expr.c (gfc_conv_expr_op): Likewise.
-	* trans-openmp.c (gfc_trans_omp_atomic): Likewise.
-
-2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* gfortran.h (protected): Remove macro.
-	* dump-parse-tree.c (show_attr): Avoid C++ keywords.
-	* expr.c (gfc_check_pointer_assign): Likewise.
-	* interface.c (compare_parameter_protected): Likewise.
-	* intrinsic.c (enum class, add_sym, add_sym_0, add_sym_1,
-	add_sym_1s, add_sym_1m, add_sym_2, add_sym_2s, add_sym_3,
-	add_sym_3ml, add_sym_3red, add_sym_3s, add_sym_4, add_sym_4s,
-	add_sym_5s): Likewise.
-	* match.c (gfc_match_assignment, gfc_match_pointer_assignment):
-	Likewise.
-	* module.c (mio_symbol_attribute): Likewise.
-	* primary.c (match_variable): Likewise.
-	* resolve.c (resolve_equivalence): Likewise.
-	* symbol.c (check_conflict, gfc_add_protected, gfc_copy_attr):
-	Likewise.
-	* trans-types.c (gfc_get_array_type_bounds): Likewise.
-
-2008-07-18  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* arith.c (eval_type_intrinsic0): Avoid C++ keywords.
-	* gfortran.h (try, protected, operator, new): Likewise.
-
-2008-07-17  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36825
-	PR fortran/36824
-	* array.c (gfc_match_array_spec): Fix array-rank check.
-	* resolve.c (resolve_fl_derived): Fix constentness check
-	for the array dimensions.
-
-2008-07-14  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* Make-lang.in (gfortranspec.o): Fix dependencies.
-
-2008-07-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/36725
-	* io.c: Add error check for g0 edit descriptor followed by '.'.
-
-2008-07-12  Daniel Kraft  <d@domob.eu>
-
-	* resolve.c (resolve_fl_derived):  Allow pointer components to empty
-	derived types fixing a missing part of PR fortran/33221.
-
-2008-07-10  Daniel Kraft  <d@domob.eu>
-
-	* gfc-internals.texi (section gfc_expr):  Created documentation about
-	the gfc_expr internal data structure.
-
-2008-07-07  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/36670
-	* iresolve.c (gfc_resolve_product):  Set shape of return
-	value from array.
-	(gfc_resolve_sum):  Likewise.
-
-2008-07-07  Jakub Jelinek  <jakub@redhat.com>
-
-	PR middle-end/36726
-	* f95-lang.c (poplevel): Don't ever add subblocks to
-	global_binding_level.
-
-2008-07-02  Janus Weil  <janus@gcc.gnu.org>
-	    Tobias Burnus  <burnus@net-b.de>
-	    Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/32580
-	* gfortran.h (struct gfc_symbol): New member "proc_pointer".
-	* check.c (gfc_check_associated,gfc_check_null): Implement
-	procedure pointers.
-	* decl.c (match_procedure_decl): Ditto.
-	* expr.c (gfc_check_pointer_assign,gfc_check_assign_symbol): Ditto.
-	* interface.c (compare_actual_formal): Ditto.
-	* match.h: Ditto.
-	* match.c (gfc_match_pointer_assignment): Ditto.
-	* parse.c (parse_interface): Ditto.
-	* primary.c (gfc_match_rvalue,match_variable): Ditto.
-	* resolve.c (resolve_fl_procedure): Ditto.
-	* symbol.c (check_conflict,gfc_add_external,gfc_add_pointer,
-	gfc_copy_attr,gen_fptr_param,build_formal_args): Ditto.
-	* trans-decl.c (get_proc_pointer_decl,gfc_get_extern_function_decl,
-	create_function_arglist): Ditto.
-	* trans-expr.c (gfc_conv_variable,gfc_conv_function_val,
-	gfc_conv_function_call,gfc_trans_pointer_assignment): Ditto.
-
-2008-07-02  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/36590
-	PR fortran/36681
-	* iresolve.c (resolve_mask_arg):  Don't convert mask to
-	kind=1 logical if it is of that type already.
-
-2008-06-29  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/36341
-	* iresolve.c (gfc_resolve_matmul): Copy shapes
-	from arguments.
-
-2008-06-29  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	* invoke.texi: Add documentation for runtime behavior of
-	-fno-range-check.
-
-2008-06-28  Daniel Kraft  <d@domob.eu>
-
-	* gfc-internals.texi (section gfc_code):  Extended documentation about
-	gfc_code in the internal datastructures chapter including details about
-	how IF, DO and SELECT blocks look like and an example for how the
-	block-chaining works.
-
-2008-06-25  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/36526
-	* interface.c (check_intents):  Correct error where the actual
-	arg was checked for a pointer argument, rather than the formal.
-
-2008-06-24  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34371
-	* expr.c (gfc_check_assign):  Change message and locus for
-	error when conform == 0.
-
-2008-06-23  Jakub Jelinek  <jakub@redhat.com>
-
-	PR fortran/36597
-	* cpp.c (cpp_define_builtins): Change _OPENMP value to 200805.
-
-2008-06-20  Laurynas Biveinis  <laurynas.biveinis@gmail.com>
-	    Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34908
-	PR fortran/36276
-	* scanner.c (preprocessor_line): do not call gfc_free for
-	current_file->filename if it differs from filename.
-
-2008-06-20  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	* arith.c (hollerith2representation): Fix for -Wc++-compat.
-	* array.c (gfc_get_constructor): Likewise.
-	* decl.c (gfc_get_data_variable, gfc_get_data_value, gfc_get_data,
-	create_enum_history, gfc_match_final_decl): Likewise.
-	* error.c (error_char): Likewise.
-	* expr.c (gfc_get_expr, gfc_copy_expr): Likewise.
-	* gfortran.h (gfc_get_charlen, gfc_get_array_spec,
-	gfc_get_component, gfc_get_formal_arglist, gfc_get_actual_arglist,
-	gfc_get_namelist, gfc_get_omp_clauses, gfc_get_interface,
-	gfc_get_common_head, gfc_get_dt_list, gfc_get_array_ref,
-	gfc_get_ref, gfc_get_equiv, gfc_get_case, gfc_get_iterator,
-	gfc_get_alloc, gfc_get_wide_string): Likewise.
-	* interface.c (count_types_test): Likewise.
-	* intrinsic.c (add_char_conversions, gfc_intrinsic_init_1):
-	Likewise.
-	* io.c (gfc_match_open, gfc_match_close, match_filepos, match_io,
-	gfc_match_inquire, gfc_match_wait): Likewise.
-	* match.c (gfc_match, match_forall_iterator): Likewise.
-	* module.c (gfc_get_pointer_info, gfc_get_use_rename, add_fixup,
-	add_true_name, parse_string, write_atom, quote_string,
-	mio_symtree_ref, mio_gmp_real, write_common_0): Likewise.
-	* options.c (gfc_post_options): Likewise.
-	* primary.c (match_integer_constant, match_hollerith_constant,
-	match_boz_constant, match_real_constant,
-	gfc_get_structure_ctor_component, gfc_match_structure_constructor): Likewise.
-	* scanner.c (gfc_widechar_to_char, add_path_to_list,
-	add_file_change, load_line, get_file, preprocessor_line,
-	load_file, unescape_filename, gfc_read_orig_filename): Likewise.
-	* simplify.c (gfc_simplify_ibits, gfc_simplify_ishft,
-	gfc_simplify_ishftc): Likewise.
-	* symbol.c (gfc_get_st_label, gfc_get_namespace, gfc_new_symtree,
-	gfc_get_uop, gfc_new_symbol, save_symbol_data, gfc_get_gsymbol):
-	Likewise.
-	* target-memory.c (gfc_target_interpret_expr): Likewise.
-	* trans-const.c (gfc_build_wide_string_const): Likewise.
-	* trans-expr.c (gfc_add_interface_mapping): Likewise.
-	* trans-intrinsic.c (gfc_conv_intrinsic_conversion,
-	gfc_conv_intrinsic_int, gfc_conv_intrinsic_lib_function,
-	gfc_conv_intrinsic_cmplx, gfc_conv_intrinsic_ctime,
-	gfc_conv_intrinsic_fdate, gfc_conv_intrinsic_ttynam,
-	gfc_conv_intrinsic_minmax, gfc_conv_intrinsic_minmax_char,
-	gfc_conv_intrinsic_ishftc, gfc_conv_intrinsic_index_scan_verify,
-	gfc_conv_intrinsic_merge, gfc_conv_intrinsic_trim): Likewise.
-	* trans.c (gfc_get_backend_locus): Likewise.
-	* trans.h (gfc_get_ss): Likewise.
-
-2008-06-18  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/36517, fortran/36492
-	* array.c (gfc_resolve_character_array_constructor):  Call
-	gfc_set_constant_character_len with changed length-chec argument.
-	* decl.c (gfc_set_constant_character_len):  Changed array argument to
-	be a generic length-checking argument that can be used for correct
-	checking with typespec and in special cases where the should-be length
-	is different from the target length.
-	(build_struct):  Call gfc_set_constant_character_len with changed length
-	checking argument and introduced additional checks for exceptional
-	conditions on invalid code.
-	(add_init_expr_to_sym), (do_parm):  Call gfc_set_constant_character_len
-	with changed argument.
-	* match.h (gfc_set_constant_character_len):  Changed third argument to
-	int for the should-be length rather than bool.
-
-2008-06-17  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/36112
-	* array.c (gfc_resolve_character_array_constructor):  Check that all
-	elements with constant character length have the same one rather than
-	fixing it if no typespec is given, emit an error if they don't.  Changed
-	return type to "try" and return FAILURE for the case above.
-	(gfc_resolve_array_constructor):  Removed unneeded call to
-	gfc_resolve_character_array_constructor in this function.
-	* gfortran.h (gfc_resolve_character_array_constructor):  Returns try.
-	* trans-array.c (get_array_ctor_strlen):  Return length of first element
-	rather than last element.
-	* resolve.c (gfc_resolve_expr):  Handle FAILURE return from
-	gfc_resolve_character_array_constructor.
-
-2008-06-17  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34396
-	* resolve.c (add_dt_to_dt_list):  New function.
-	(resolve_fl_derived): Call new function for pointer components
-	and when derived type resolved.
-
-2008-06-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/36515
-	* trans-decl.c (gfc_generate_function_code): Add range_check to options
-	array.
-
-2008-06-15  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* gfc-internals.texi: Expand TABs, drop indentation outside examples.
-	* gfortran.texi: Likewise.
-	* intrinsic.texi: Likewise.
-	* invoke.texi: Likewise.
-
-2008-06-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35863
-	* trans-io.c (gfc_build_io_library_fndecls): Build declaration for
-	transfer_character_wide which includes passing in the character kind to
-	support wide character IO. (transfer_expr): If the kind == 4, create the
-	argument and build the call.
-	* gfortran.texi: Fix typo.
-
-2008-06-13  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36476
-	* decl.c (do_parm): Handle init expression for len=*.
-
-2008-06-12  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36462
-	* trans-intrinsic.c (gfc_conv_intrinsic_index_scan_verify):
-	Fix passing of the BACK= argument.
-
-2008-06-10  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	* cpp.c: Add copyright notice.
-	* cpp.h: Add copyright notice.
-
-2008-06-08  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36459
-	* decl.c (match_procedure_decl): Correctly recognize if the interface
-	is an intrinsic procedure.
-
-2008-06-08  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/35830
-	* resolve.c (resolve_symbol): Copy more attributes for
-	PROCEDUREs with interfaces.
-
-2008-06-07  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/36420
-	PR fortran/36422
-	* io.c (check_format): Add new error message for zero width.
-	Use new	error message for FMT_A and with READ, FMT_G.  Allow
-	FMT_G with WRITE except when -std=F95 and -std=F2003.
-
-2008-06-07  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36437
-	* intrinsic.c (add_functions): Implement c_sizeof.
-	* trans-intrinsic.c (gfc_conv_intrinsic_sizeof): Do not
-	create unneeded variable in the scalar case.
-	* intrinsic.texi: Add C_SIZEOF documentation.
-
-2008-06-06  Tobias Burnus  <burnus@net-b.de>
-
-	* intrinsic.texi (BESSEL_J1): Fix BES(S)EL_J1 typo.
-
-2008-06-06  Jakub Jelinek  <jakub@redhat.com>
-
-	* scanner.c (skip_free_comments, skip_fixed_comments): Handle tabs.
-	* parse.c (next_free): Allow tab after !$omp.
-	(decode_omp_directive): Handle !$omp task, !$omp taskwait
-	and !$omp end task.
-	(case_executable): Add ST_OMP_TASKWAIT.
-	(case_exec_markers): Add ST_OMP_TASK.
-	(gfc_ascii_statement): Handle ST_OMP_TASK, ST_OMP_END_TASK and
-	ST_OMP_TASKWAIT.
-	(parse_omp_structured_block, parse_executable): Handle ST_OMP_TASK.
-	* gfortran.h (gfc_find_sym_in_expr): New prototype.
-	(gfc_statement): Add ST_OMP_TASK, ST_OMP_END_TASK and ST_OMP_TASKWAIT.
-	(gfc_omp_clauses): Add OMP_SCHED_AUTO to sched_kind,
-	OMP_DEFAULT_FIRSTPRIVATE to default_sharing.  Add collapse and
-	untied fields.
-	(gfc_exec_op): Add EXEC_OMP_TASK and EXEC_OMP_TASKWAIT.
-	* f95-lang.c (LANG_HOOKS_OMP_CLAUSE_COPY_CTOR,
-	LANG_HOOKS_OMP_CLAUSE_ASSIGN_OP, LANG_HOOKS_OMP_CLAUSE_DTOR,
-	LANG_HOOKS_OMP_PRIVATE_OUTER_REF): Define.
-	* trans.h (gfc_omp_clause_default_ctor): Add another argument.
-	(gfc_omp_clause_copy_ctor, gfc_omp_clause_assign_op,
-	gfc_omp_clause_dtor, gfc_omp_private_outer_ref): New prototypes.
-	* types.def (BT_ULONGLONG, BT_PTR_ULONGLONG,
-	BT_FN_BOOL_ULONGLONGPTR_ULONGLONGPTR,
-	BT_FN_BOOL_BOOL_ULL_ULL_ULL_ULLPTR_ULLPTR,
-	BT_FN_BOOL_BOOL_ULL_ULL_ULL_ULL_ULLPTR_ULLPTR,
-	BT_FN_VOID_PTR_PTR, BT_PTR_FN_VOID_PTR_PTR,
-	BT_FN_VOID_OMPFN_PTR_OMPCPYFN_LONG_LONG_BOOL_UINT): New.
-	(BT_BOOL): Use integer type with BOOL_TYPE_SIZE rather
-	than boolean_type_node.
-	* dump-parse-tree.c (gfc_show_omp_node): Handle EXEC_OMP_TASK,
-	EXEC_OMP_TASKWAIT, OMP_SCHED_AUTO, OMP_DEFAULT_FIRSTPRIVATE,
-	untied and collapse clauses.
-	(gfc_show_code_node): Handle EXEC_OMP_TASK and EXEC_OMP_TASKWAIT.
-	* trans.c (gfc_trans_code): Handle EXEC_OMP_TASK and
-	EXEC_OMP_TASKWAIT.
-	* st.c (gfc_free_statement): Likewise.
-	* resolve.c (gfc_resolve_blocks, resolve_code): Likewise.
-	(find_sym_in_expr): Rename to...
-	(gfc_find_sym_in_expr): ... this.  No longer static.
-	(resolve_allocate_expr, resolve_ordinary_assign): Adjust caller.
-	* match.h (gfc_match_omp_task, gfc_match_omp_taskwait): New
-	prototypes.
-	* openmp.c (resolve_omp_clauses): Allow allocatable arrays in
-	firstprivate, lastprivate, reduction, copyprivate and copyin
-	clauses.
-	(omp_current_do_code): Made static.
-	(omp_current_do_collapse): New variable.
-	(gfc_resolve_omp_do_blocks): Compute omp_current_do_collapse,
-	clear omp_current_do_code and omp_current_do_collapse on return.
-	(gfc_resolve_do_iterator): Handle collapsed do loops.
-	(resolve_omp_do): Likewise, diagnose errorneous collapsed do loops.
-	(OMP_CLAUSE_COLLAPSE, OMP_CLAUSE_UNTIED): Define.
-	(gfc_match_omp_clauses): Handle default (firstprivate),
-	schedule (auto), untied and collapse (n) clauses.
-	(OMP_DO_CLAUSES): Add OMP_CLAUSE_COLLAPSE.
-	(OMP_TASK_CLAUSES): Define.
-	(gfc_match_omp_task, gfc_match_omp_taskwait): New functions.
-	* trans-openmp.c (gfc_omp_private_outer_ref): New function.
-	(gfc_omp_clause_default_ctor): Add outer argument.  For allocatable
-	arrays allocate them with the bounds of the outer var if outer
-	var is allocated.
-	(gfc_omp_clause_copy_ctor, gfc_omp_clause_assign_op,
-	gfc_omp_clause_dtor): New functions.
-	(gfc_trans_omp_array_reduction): If decl is allocatable array,
-	allocate it with outer var's bounds in OMP_CLAUSE_REDUCTION_INIT
-	and deallocate it in OMP_CLAUSE_REDUCTION_MERGE.
-	(gfc_omp_predetermined_sharing): Return OMP_CLAUSE_DEFAULT_SHARED
-	for assumed-size arrays.
-	(gfc_trans_omp_do): Add par_clauses argument.  If dovar is
-	present in lastprivate clause and do loop isn't simple,
-	set OMP_CLAUSE_LASTPRIVATE_STMT.  If dovar is present in
-	parallel's lastprivate clause, change it to shared and add
-	lastprivate clause to OMP_FOR_CLAUSES.  Handle collapsed do loops.
-	(gfc_trans_omp_directive): Adjust gfc_trans_omp_do callers.
-	(gfc_trans_omp_parallel_do): Likewise.  Move collapse clause to
-	OMP_FOR from OMP_PARALLEL.
-	(gfc_trans_omp_clauses): Handle OMP_SCHED_AUTO,
-	OMP_DEFAULT_FIRSTPRIVATE, untied and collapse clauses.
-	(gfc_trans_omp_task, gfc_trans_omp_taskwait): New functions.
-	(gfc_trans_omp_directive): Handle EXEC_OMP_TASK and
-	EXEC_OMP_TASKWAIT.
-
-2008-06-04  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36322
-	PR fortran/36275
-	* resolve.c (resolve_symbol): Correctly copy the interface for a
-	PROCEDURE declaration.
-
-2008-06-02  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36361
-	* symbol.c (gfc_add_allocatable,gfc_add_dimension,
-	gfc_add_explicit_interface): Added checks.
-	* decl.c (attr_decl1): Added missing "var_locus".
-	* parse.c (parse_interface): Checking for errors.
-
-2008-06-02  Daniel Kraft  <d@domob.eu>
-
-	* gfortran.h:  New statement-type ST_FINAL for FINAL declarations.
-	(struct gfc_symbol):  New member f2k_derived.
-	(struct gfc_namespace):  New member finalizers, for use in the above
-	mentioned f2k_derived namespace.
-	(struct gfc_finalizer):  New type defined for finalizers linked list.
-	* match.h (gfc_match_final_decl):  New function header.
-	* decl.c (gfc_match_derived_decl):  Create f2k_derived namespace on
-	constructed symbol node.
-	(gfc_match_final_decl):  New function to match a FINAL declaration line.
-	* parse.c (decode_statement):  match-call for keyword FINAL.
-	(parse_derived):  Parse CONTAINS section and accept FINAL statements.
-	* resolve.c (gfc_resolve_finalizers):  New function to resolve (that is
-	in this case, check) a list of finalizer procedures.
-	(resolve_fl_derived):  Call gfc_resolve_finalizers here.
-	* symbol.c (gfc_get_namespace):  Initialize new finalizers to NULL.
-	(gfc_free_namespace):  Free finalizers list.
-	(gfc_new_symbol):  Initialize new f2k_derived to NULL.
-	(gfc_free_symbol):  Free f2k_derived namespace.
-	(gfc_free_finalizer):  New function to free a single gfc_finalizer node.
-	(gfc_free_finalizer_list):  New function to free a linked list of
-	gfc_finalizer nodes.
-
-2008-06-02  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/36375
-	PR fortran/36377
-	* cpp.c (gfc_cpp_init): Do not initialize builtins if
-	processing already preprocessed input.
-	(gfc_cpp_preprocess): Finalize output with newline.
-
-2008-05-31  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	* intrinsic.texi: Revert wrong commit.
-
-2008-05-31  Steven G. Kargl  <kargls@comcast.net>
-
-	* arith.c (gfc_arith_init_1): Remove now unused r and c variables.
-	Cleanup numerical inquiry function initialization.
-	(gfc_arith_done_1): Replace multiple mpfr_clear() invocations with
-	a single mpfr_clears().
-	(gfc_check_real_range): Re-arrange logic to eliminate multiple
-	unnecessary branching and assignments.
-	(gfc_arith_times): Use mpfr_clears() in preference to multiple
-	mpfr_clear().
-	(gfc_arith_divide): Ditto.
-	(complex_reciprocal): Eliminate now unused variables a, re, im.
-	Cleanup the mpfr abuse.  Use mpfr_clears() in preference to
-	multiple mpfr_clear().
-	(complex_pow): Fix comment whitespace.  Use mpfr_clears() in
-	preference to multiple mpfr_clear().
-	* simplify.c (gfc_simplify_and): Remove blank line.
-	(gfc_simplify_atan2): Move error checking earlier to eliminate
-	a now unnecessay gfc_free_expr().
-	(gfc_simplify_bessel_j0): Remove unnecessary gfc_set_model_kind().
-	(gfc_simplify_bessel_j1): Ditto.
-	(gfc_simplify_bessel_jn): Ditto.
- 	(gfc_simplify_bessel_y0): Ditto.
-	(gfc_simplify_bessel_y1): Ditto.
-	(gfc_simplify_bessel_yn): Ditto. 
-	(only_convert_cmplx_boz): Eliminate unnecessary duplicate code, and
-	combine nested if statement rational expressions.
-	(gfc_simplify_cos): Use mpfr_clears() in preference to multiple
-	mpfr_clear().
-	(gfc_simplify_exp): Ditto.
-	(gfc_simplify_fraction): Move gfc_set_model_kind() to after the
-	special case of 0.  Use mpfr_clears() in preference to multiple
-	mpfr_clear().
-	(gfc_simplify_gamma): Eliminate unnecessary gfc_set_model_kind().
- 	(gfc_simplify_lgamma): Ditto.
-	(gfc_simplify_log10): Ditto.
-	(gfc_simplify_log): Move gfc_set_model_kind () inside switch
-	statement. Use mpfr_clears() in preference to multiple mpfr_clear().
-	(gfc_simplify_mod):  Eliminate now unused variables quot, iquot,
-	and term.  Simplify the mpfr magic.
-	(gfc_simplify_modulo): Ditto.
-	(gfc_simplify_nearest): Eliminate unnecessary gfc_set_model_kind().
-	(gfc_simplify_scale): Use mpfr_clears() in preference to multiple
-	mpfr_clear().
-	(gfc_simplify_sin): Ditto
-	(gfc_simplify_sqrt): Ditto
-	(gfc_simplify_set_exponent):  Move gfc_set_model_kind() to after the
-	special case of 0.  Use mpfr_clears() in preference to multiple
-	mpfr_clear().
-
-2008-05-29  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR target/36348
-	* Make-lang.in (F95_OBJS): Added dependency on FORTRAN_TARGET_OBJS.
-
-2008-05-29  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* scanner.c (load_line): Add first_char argument. Don't call ungetc.
-	(gfc_read_orig_filename): Adjust call to load_line. Don't call
-	ungetc.
-	(load_file): Adjust call to load_line.
-
-2008-05-28  Janus Weil  <janus@gcc.gnu.org>
-
-	PR fortran/36325
-	PR fortran/35830
-	* interface.c (gfc_procedure_use): Enable argument checking for
-	external procedures with explicit interface.
-	* symbol.c (check_conflict): Fix conflict checking for externals.
-	(copy_formal_args): Fix handling of arrays.
-	* resolve.c (resolve_specific_f0, resolve_specific_s0): Fix handling
-	of intrinsics.
-	* parse.c (parse_interface): Non-abstract INTERFACE statement implies
-	EXTERNAL attribute.
-
-2008-05-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36319
-	* intrinsic.c (gfc_convert_chartype): Don't mark conversion
-	function as pure.
-	* trans-array.c (gfc_trans_array_ctor_element): Divide element
-	size by the size of one character to obtain length.
-	* iresolve.c (gfc_resolve_cshift): Call the _char4 variant when
-	appropriate.
-	(gfc_resolve_eoshift): Likewise.
-	* trans-intrinsic.c (gfc_conv_intrinsic_ctime): Minor beautification.
-	(gfc_conv_intrinsic_fdate): Minor beautification.
-	(gfc_conv_intrinsic_ttynam): Minor beautification.
-	(gfc_conv_intrinsic_minmax_char): Allow all character kinds.
-	(size_of_string_in_bytes): New function.
-	(gfc_conv_intrinsic_size): Call size_of_string_in_bytes for
-	character expressions.
-	(gfc_conv_intrinsic_sizeof): Likewise.
-	(gfc_conv_intrinsic_array_transfer): Likewise.
-	(gfc_conv_intrinsic_trim): Allow all character kinds. Minor
-	beautification.
-	(gfc_conv_intrinsic_repeat): Fix comment typo.
-	* simplify.c (gfc_convert_char_constant): Take care of conversion
-	of array constructors.
-
-2008-05-27  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36316
-	* trans-array.c (gfc_set_loop_bounds_from_array_spec):
-	Add missing fold_convert.
-
-2008-05-26  Daniel Franke  <franke.daniel@gmail.com>
-
-	* fortran/cpp.c (cpp_define_builtins): Remove usage of TARGET_* macros,
-	added FIXME instead.
-
-2008-05-26  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/18428
-	* lang.opt (A, C, CC, D, E, H, P, U, cpp, d, fworking-directory,
-	imultilib, iprefix, iquote, isysroot, isystem, nocpp, nostdinc,
-	o, undef, v): New options.
-	* options.c (gfc_init_options): Also initialize preprocessor
-	options.
-	(gfc_post_options): Also handle post-initialization of preprocessor
-	options.
-	(gfc_handle_option): Check if option is a preprocessor option.
-	If yes, let gfc_cpp_handle_option() handle the option.
-	* lang-specs.h: Reorganized to handle new options.
-	* scanner.c (gfc_new_file): Read temporary file instead of
-	input source if preprocessing is enabled.
-	* f95-lang.c (gfc_init): Initialize preprocessor.
-	(gfc_finish): Clean up preprocessor.
-	* cpp.c: New.
-	* cpp.h: New.
-	* Make-lang.in: Added new objects and dependencies.
-	* gfortran.texi: Updated section "Preprocessing and
-	conditional compilation".
-	* invoke.texi: Added new section "Preprocessing Options",
-	listed and documented the preprocessing options handled
-	by gfortran.
-
-2008-05-25  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/32600
-	* trans-expr.c (gfc_conv_function_call): Remove library
-	call for c_f_pointer with scalar Fortran pointers and for
-	c_f_procpointer.
-
-2008-05-21  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36257
-	* iresolve.c (check_charlen_present): Don't force the rank to 1.
-
-2008-05-19  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36265
-	* trans-expr.c (gfc_conv_string_tmp): Pick the correct type for
-	the temporary variable.
-
-2008-05-19  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* simplify.c (gfc_simplify_dble, gfc_simplify_real): Initialize
-	result variable to avoid warnings.
-
-2008-05-18  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* intrinsic.c (char_conversions, ncharconv): New static variables.
-	(find_char_conv): New function.
-	(add_functions): Add simplification functions for ADJUSTL and
-	ADJUSTR. Don't check the kind of their argument. Add checking for
-	LGE, LLE, LGT and LLT.
-	(add_subroutines): Fix argument type for SLEEP. Fix argument name
-	for SYSTEM.
-	(add_char_conversions): New function.
-	(gfc_intrinsic_init_1): Call add_char_conversions.
-	(gfc_intrinsic_done_1): Free char_conversions.
-	(check_arglist): Use kind == 0 as a signal that we don't want
-	the kind value to be checked.
-	(do_simplify): Also simplify character functions.
-	(gfc_convert_chartype): New function
-	* trans-array.c (gfc_trans_array_ctor_element): Don't force the
-	use of default character type.
-	(gfc_trans_array_constructor_value): Likewise.
-	(get_array_ctor_var_strlen): Use integer kind to build an integer
-	instead of a character kind!
-	(gfc_build_constant_array_constructor): Don't force the use of
-	default character type.
-	(gfc_conv_loop_setup): Likewise.
-	* trans-expr.c (gfc_conv_string_tmp): Don't force the use of
-	default character type. Allocate enough memory for wide strings.
-	(gfc_conv_concat_op): Make sure operand kind are the same.
-	(string_to_single_character): Remove gfc_ prefix. Reindent.
-	Don't force the use of default character type.
-	(gfc_conv_scalar_char_value): Likewise.
-	(gfc_build_compare_string): Call string_to_single_character.
-	(fill_with_spaces): New function
-	(gfc_trans_string_copy): Add kind arguments. Use them to deal
-	with wide character kinds.
-	(gfc_conv_statement_function): Whitespace fix. Call
-	gfc_trans_string_copy with new kind arguments.
-	(gfc_conv_substring_expr): Call gfc_build_wide_string_const
-	instead of using gfc_widechar_to_char.
-	(gfc_conv_string_parameter): Don't force the use of default
-	character type.
-	(gfc_trans_scalar_assign): Pass kind args to gfc_trans_string_copy.
-	* intrinsic.h (gfc_check_lge_lgt_lle_llt, gfc_convert_char_constant,
-	gfc_resolve_adjustl, gfc_resolve_adjustr): New prototypes.
-	* decl.c (gfc_set_constant_character_len): Don't assert the
-	existence of a single character kind.
-	* trans-array.h (gfc_trans_string_copy): New prototype.
-	* gfortran.h (gfc_check_character_range, gfc_convert_chartype):
-	New prototypes.
-	* error.c (print_wide_char_into_buffer): New function lifting
-	code from gfc_print_wide_char. Fix order to output '\x??' instead
-	of 'x\??'.
-	(gfc_print_wide_char): Call print_wide_char_into_buffer.
-	(show_locus): Call print_wide_char_into_buffer with buffer local
-	to this function.
-	* trans-const.c (gfc_build_wide_string_const): New function.
-	(gfc_conv_string_init): Deal with wide characters strings
-	constructors.
-	(gfc_conv_constant_to_tree): Call gfc_build_wide_string_const.
-	* trans-stmt.c (gfc_trans_label_assign): Likewise.
-	(gfc_trans_character_select): Deal with wide strings.
-	* expr.c (gfc_check_assign): Allow conversion between character
-	kinds on assignment.
-	* trans-const.h (gfc_build_wide_string_const): New prototype.
-	* trans-types.c (gfc_get_character_type_len_for_eltype,
-	gfc_get_character_type_len): Create too variants of the old
-	gfc_get_character_type_len, one getting kind argument and the
-	other one directly taking a type tree.
-	* trans.h (gfor_fndecl_select_string_char4,
-	gfor_fndecl_convert_char1_to_char4,
-	gfor_fndecl_convert_char4_to_char1): New prototypes.
-	* trans-types.h (gfc_get_character_type_len_for_eltype): New
-	prototype.
-	* resolve.c (resolve_operator): Exit early when kind mismatches
-	are detected, because that makes us issue an error message later.
-	(validate_case_label_expr): Fix wording of error message.
-	* iresolve.c (gfc_resolve_adjustl, gfc_resolve_adjustr): New
-	functions.
-	(gfc_resolve_pack): Call _char4 variants of library function
-	when dealing with wide characters.
-	(gfc_resolve_reshape): Likewise.
-	(gfc_resolve_spread): Likewise.
-	(gfc_resolve_transpose): Likewise.
-	(gfc_resolve_unpack): Likewise.
-	* target-memory.c (size_character): Take character kind bit size
-	correctly into account (not that it changes anything for now, but
-	it's more generic).
-	(gfc_encode_character): Added gfc_ prefix. Encoding each
-	character of a string by calling native_encode_expr for the
-	corresponding unsigned integer.
-	(gfc_target_encode_expr): Add gfc_ prefix to encode_character.
-	* trans-decl.c (gfc_build_intrinsic_function_decls): Build
-	gfor_fndecl_select_string_char4, gfor_fndecl_convert_char1_to_char4
-	and gfor_fndecl_convert_char4_to_char1.
-	* target-memory.h (gfc_encode_character): New prototype.
-	* arith.c (gfc_check_character_range): New function.
-	(eval_intrinsic): Allow non-default character kinds.
-	* check.c (gfc_check_access_func): Only allow default
-	character kind arguments.
-	(gfc_check_chdir): Likewise.
-	(gfc_check_chdir_sub): Likewise.
-	(gfc_check_chmod): Likewise.
-	(gfc_check_chmod_sub): Likewise.
-	(gfc_check_lge_lgt_lle_llt): New function.
-	(gfc_check_link): Likewise.
-	(gfc_check_link_sub): Likewise.
-	(gfc_check_symlnk): Likewise.
-	(gfc_check_symlnk_sub): Likewise.
-	(gfc_check_rename): Likewise.
-	(gfc_check_rename_sub): Likewise.
-	(gfc_check_fgetputc_sub): Likewise.
-	(gfc_check_fgetput_sub): Likewise.
-	(gfc_check_stat): Likewise.
-	(gfc_check_stat_sub): Likewise.
-	(gfc_check_date_and_time): Likewise.
-	(gfc_check_ctime_sub): Likewise.
-	(gfc_check_fdate_sub): Likewise.
-	(gfc_check_gerror): Likewise.
-	(gfc_check_getcwd_sub): Likewise.
-	(gfc_check_getarg): Likewise.
-	(gfc_check_getlog): Likewise.
-	(gfc_check_hostnm): Likewise.
-	(gfc_check_hostnm_sub): Likewise.
-	(gfc_check_ttynam_sub): Likewise.
-	(gfc_check_perror): Likewise.
-	(gfc_check_unlink): Likewise.
-	(gfc_check_unlink_sub): Likewise.
-	(gfc_check_system_sub): Likewise.
-	* primary.c (got_delim): Perform correct character range checking
-	for all kinds.
-	* trans-intrinsic.c (gfc_conv_intrinsic_conversion): Generate
-	calls to library functions convert_char4_to_char1 and
-	convert_char1_to_char4 for character conversions.
-	(gfc_conv_intrinsic_char): Allow all character kings.
-	(gfc_conv_intrinsic_strcmp): Fix whitespace.
-	(gfc_conv_intrinsic_repeat): Take care of all character kinds.
-	* intrinsic.texi: For all GNU intrinsics accepting character
-	arguments, mention that they're restricted to the default kind.
-	* simplify.c (simplify_achar_char): New function.
-	(gfc_simplify_achar, gfc_simplify_char): Call simplify_achar_char.
-	gfc_simplify_ichar): Don't error out for wide characters.
-	(gfc_convert_char_constant): New function.
-
-2008-05-18  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/36251
-	* symbol.c (check_conflict): Issue errors for abuse of PUBLIC, PRIVATE,
-	and BIND(C).
-	* resolve.c (gfc_verify_binding_labels): Fix NULL pointer dereference.
-
-2008-05-17  Tobias Burnus  <burnus@net-b.de>
-
-	* intrinsic.texi: Correct description of GET_COMMAND_ARGUMENT
-	and GET_ENVIRONMENT_VARIABLE; fix keyword= name for GETENV,
-	GETLOG, GMTIME, HOSTNM, IRAND, ITIME, KILL.
-	Move LOG_GAMMA after LOG10.
-
-2008-05-17  Tobias Burnus  <burnus@net-b.de>
-
-	* intrinsic.c (add_functions): Change FLUSH(C) to FLUSH(UNIT).
-	* intrinsic.texi: Change INTEGER(*) to INTEGER; fix keyword= name for
-	ABS, ADJUSTL, AINT, ALLOCATED, ANINT, ASSOCIATED, C_ASSOCIATED,
-	CEILING, DBLE, DFLOAT, DOT_PRODUCT, DREAL, FLOAT, FLOOR, GET_COMMAND.
-
-2008-05-16  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35756
-	PR fortran/35759
-	* trans-stmt.c (gfc_trans_where): Tighten up the dependency
-	check for calling gfc_trans_where_3.
-
-	PR fortran/35743
-	* trans-stmt.c (gfc_trans_where_2): Set the mask size to zero
-	if it is calculated to be negative.
-
-	PR fortran/35745
-	* trans-stmt.c (gfc_trans_where_3, gfc_trans_where_assign): Set
-	ss->where for scalar right hand sides.
-	* trans-array.c (gfc_add_loop_ss_code): If ss->where is set do
-	not evaluate scalars outside the loop.  Clean up whitespace.
-	* trans.h : Add a bitfield 'where' to gfc_ss.
-
-2008-05-16  Tobias Burnus  <burnus@net-b.de>
-
-	* libgfortran.h: Increase GFC_MAX_DIMENSIONS to 15.
-	* array.c (gfc_match_array_spec): Error with -std=f2003 if rank > 7.
-
-2008-04-16  Daniel Kraft  <d@domob.eu>
-
-	PR fortran/27997
-	* gfortran.h:  Added field "length_from_typespec" to gfc_charlength.
-	* aray.c (gfc_match_array_constructor):  Added code to parse typespec.
-	(check_element_type, check_constructor_type, gfc_check_constructor_type):
-	Extended to support explicit typespec on constructor.
-	(gfc_resolve_character_array_constructor):  Pad strings correctly for
-	explicit, constant character length.
-	* trans-array.c:  New static global variable "typespec_chararray_ctor"
-	(gfc_trans_array_constructor):  New code to support explicit but dynamic
-	character lengths.
-
-2008-05-16  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34325
-	* decl.c (match_attr_spec): Check for matching pairs of parenthesis.
-	* expr.c (gfc_specification_expr): Supplement the error message with the
-	type that was found.
-	* resolve.c (gfc_resolve_index): Likewise.
-	* match.c (gfc_match_parens): Clarify error message with "at or before".
-	(gfc_match_do): Check for matching pairs of parenthesis.
-
-2008-05-16  Tobias Burnus  <burnus@net-b.de
-
-	* intrinsic.texi: Write Fortran 77/90/95 instead of F77/90/95;
-	add missing KIND argument to ACHAR and NINT; and state that
-	the KIND argument is a F2003 extension for ACHAR, COUNT, IACHAR,
-	ICHAR, INDEX, LBOUND, LEN, LEN_TRIM, SCAN, SIZE, UBOUND, VERIFY.
-
-2008-05-16  Daniel Kraft  <d@domob.eu>
-
-	* primary.c:  New private structure "gfc_structure_ctor_component".
-	(gfc_free_structure_ctor_component):  New helper function.
-	(gfc_match_structure_constructor):  Extended largely to support named
-	arguments and default initialization for structure constructors.
-
-2008-05-15  Steven G. Kargl  <kargls@comcast.net>
-
-	* simplify.c (gfc_simplify_dble, gfc_simplify_float,
-	simplify_bound, gfc_simplify_nearest, gfc_simplify_real): Plug
-	possible memory leaks.
-	(gfc_simplify_reshape): Plug possible memory leaks and dereferencing
-	of NULL pointers.
-
-2008-05-15  Steven G. Kargl  <kargls@comcast.net>
-
-	PR fortran/36239
-	* simplify.c (gfc_simplify_int, gfc_simplify_intconv): Replaced hand
-	rolled integer conversion with gfc_int2int, gfc_real2int, and
-	gfc_complex2int.
-	(gfc_simplify_intconv): Renamed to simplify_intconv.
-	
-2008-05-15  Steven G. Kargl,   <kargl@comcast.net>
-	* gfortran.dg/and_or_xor.f90: New test
-
-	* fortran/simplify.c (gfc_simplify_and, gfc_simplify_or,
-	gfc_simplify_xor): Don't range check logical results.
-
-2008-05-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* trans-expr.c (gfc_conv_concat_op): Take care of nondefault
-	character kinds.
-	(gfc_build_compare_string): Add kind argument and use it.
-	(gfc_conv_statement_function): Fix indentation.
-	* gfortran.h (gfc_character_info): New structure.
-	(gfc_character_kinds): New array.
-	* trans-types.c (gfc_character_kinds, gfc_character_types,
-	gfc_pcharacter_types): New array.
-	(gfc_init_kinds): Fill character kinds array.
-	(validate_character): Take care of nondefault character kinds.
-	(gfc_build_uint_type): New function.
-	(gfc_init_types): Take care of nondefault character kinds.
-	(gfc_get_char_type, gfc_get_pchar_type): New functions.
-	(gfc_get_character_type_len): Use gfc_get_char_type.
-	* trans.h (gfc_build_compare_string): Adjust prototype.
-	(gfor_fndecl_compare_string_char4, gfor_fndecl_concat_string_char4,
-	gfor_fndecl_string_len_trim_char4, gfor_fndecl_string_index_char4,
-	gfor_fndecl_string_scan_char4, gfor_fndecl_string_verify_char4,
-	gfor_fndecl_string_trim_char4, gfor_fndecl_string_minmax_char4,
-	gfor_fndecl_adjustl_char4, gfor_fndecl_adjustr_char4): New
-	prototypes.
-	* trans-types.h (gfc_get_char_type, gfc_get_pchar_type): New
-	prototypes.
-	* trans-decl.c (gfor_fndecl_compare_string_char4,
-	gfor_fndecl_string_len_trim_char4, gfor_fndecl_string_index_char4,
-	gfor_fndecl_string_scan_char4, gfor_fndecl_string_verify_char4,
-	gfor_fndecl_string_trim_char4, gfor_fndecl_string_minmax_char4,
-	gfor_fndecl_adjustl_char4, gfor_fndecl_adjustr_char4,
-	gfor_fndecl_concat_string_char4): New function decls.
-	(gfc_build_intrinsic_function_decls): Define new *_char4 function
-	decls.
-	* trans-intrinsic.c (gfc_conv_intrinsic_minmax_char,
-	gfc_conv_intrinsic_len_trim, gfc_conv_intrinsic_ichar,
-	gfc_conv_intrinsic_strcmp, gfc_conv_intrinsic_trim,
-	gfc_conv_intrinsic_function): Deal with nondefault character kinds.
-
-2008-05-15  Sa Liu  <saliu@de.ibm.com>
-
-	* iso-c-binding.def: Add standard parameter to macro NAMED_INTCST.
-	All existing NAMED_INTCST definitions has standard GFC_STD_F2003,
-	c_int128_t, c_int_least128_t and c_int_fast128_t are added as
-	GNU extensions.
-	* iso-fortran-evn.def: Add standard parameter GFC_STD_F2003
-	to macro NAMED_INTCST.
-	* symbol.c (std_for_isocbinding_symbol): New helper function to 
-	return the standard that supports this isocbinding symbol.
-	(generate_isocbinding_symbol): Do not generate GNU extension symbols
-	if std=f2003. Add new parameter to NAMED_INTCST.
-	* module.c (use_iso_fortran_env_module): Add new parameter to
-	NAMED_INTCST and new field standard to struct intmod_sym.
-	* gfortran.h: Add new parameter to NAMED_INTCST.
-	* trans-types.c (init_c_interop_kinds): Add new parameter to 
-	NAMED_INTCST.
-	* intrinsic.texi: Documented new types C_INT128_T, C_INT_LEASE128_T
-	and C_INT_FAST128_T.
-
-2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36059
-	* trans-decl.c (gfc_build_dummy_array_decl): Don't repack
-	arrays that have the TARGET attribute.
-
-2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36186
-	* simplify.c (only_convert_cmplx_boz): New function.
-	(gfc_simplify_cmplx, gfc_simplify_complex, gfc_simplify_dcmplx):
-	Call only_convert_cmplx_boz.
-
-2008-05-14  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/36233
-	* interface.c (compare_actual_formal): Do not check sizes if the
-	actual is BT_PROCEDURE.
-
-2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/35682
-	* trans-array.c (gfc_conv_ss_startstride): Any negative size is
-	the same as zero size.
-	(gfc_conv_loop_setup): Fix size calculation.
-
-2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/35685
-	* trans-intrinsic.c (gfc_conv_intrinsic_bound): Correctly
-	handle zero-size sections.
-
-2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36215
-	* scanner.c (preprocessor_line): Allocate enough memory for a
-	wide string.
-
-2008-05-12  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36176
-	* target-memory.c (gfc_target_expr_size): Correctly treat
-	substrings.
-	(gfc_target_encode_expr): Likewise.
-	(gfc_interpret_complex): Whitespace change.
-
-2008-05-11  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/35719
-	* trans.c (gfc_call_malloc): If size equals zero, allocate one
-	byte; don't return a null pointer.
-
-2008-05-10  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36197
-	* module.c (quote_string): Fix sprintf format.
-
-2008-05-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/36162
-	* module.c (quote_string, unquote_string,
-	mio_allocated_wide_string): New functions.
-	(mio_expr): Call mio_allocated_wide_string where needed.
-
-2008-05-07 Kenneth Zadeck <zadeck@naturalbridge.com>
-
-	 * trans-decl.c (gfc_get_extern_function_decl, build_function_decl):
-	 Rename DECL_IS_PURE to DECL_PURE_P.
-
-2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* arith.c: (gfc_arith_concat, gfc_compare_string,
-	gfc_compare_with_Cstring, hollerith2representation,
-	gfc_hollerith2int, gfc_hollerith2real, gfc_hollerith2complex,
-	gfc_hollerith2character, gfc_hollerith2logical): Use wide
-	characters for character constants.
-	* data.c (create_character_intializer): Likewise.
-	* decl.c (gfc_set_constant_character_len): Likewise.
-	* dump-parse-tree.c (show_char_const): Correctly dump wide
-	character strings.
-	error.c (print_wide_char): Rename into gfc_print_wide_char.
-	(show_locus): Adapt to new prototype of gfc_print_wide_char.
-	expr.c (free_expr0): Representation is now disjunct from
-	character string value, so we always free it.
-	(gfc_copy_expr, find_substring_ref, gfc_simplify_expr): Adapt
-	to wide character strings.
-	* gfortran.h (gfc_expr): Make value.character.string a wide string.
-	(gfc_wide_toupper, gfc_wide_strncasecmp, gfc_wide_memset,
-	gfc_widechar_to_char, gfc_char_to_widechar): New prototypes.
-	(gfc_get_wide_string): New macro.
-	(gfc_print_wide_char): New prototype.
-	* io.c (format_string): Make a wide string.
-	(next_char, gfc_match_format, compare_to_allowed_values, 
-	gfc_match_open): Deal with wide strings.
-	* module.c (mio_expr): Convert between wide strings and ASCII ones.
-	* primary.c (match_hollerith_constant, match_charkind_name): 
-	Handle wide strings.
-	* resolve.c (build_default_init_expr): Likewise.
-	* scanner.c (gfc_wide_toupper, gfc_wide_memset,
-	gfc_char_to_widechar): New functions.
-	(wide_strchr, gfc_widechar_to_char, gfc_wide_strncasecmp):
-	Changes in prototypes.
-	(gfc_define_undef_line, load_line, preprocessor_line,
-	include_line, load_file, gfc_read_orig_filename): Handle wide
-	strings.
-	* simplify.c (gfc_simplify_achar, gfc_simplify_adjustl,
-	gfc_simplify_adjustr, gfc_simplify_char, gfc_simplify_iachar,
-	gfc_simplify_ichar, simplify_min_max, gfc_simplify_new_line,
-	gfc_simplify_repeat): Handle wide strings.
-	(wide_strspn, wide_strcspn): New helper functions.
-	(gfc_simplify_scan, gfc_simplify_trim, gfc_simplify_verify):
-	Handle wide strings.
-	* symbol.c (generate_isocbinding_symbol): Likewise.
-	* target-memory.c (size_character, gfc_target_expr_size,
-	encode_character, gfc_target_encode_expr, gfc_interpret_character,
-	gfc_target_interpret_expr): Handle wide strings.
-	* trans-const.c (gfc_conv_string_init): Lower wide strings to
-	narrow ones.
-	(gfc_conv_constant_to_tree): Likewise.
-	* trans-expr.c (gfc_conv_substring_expr): Handle wide strings.
-	* trans-io.c (gfc_new_nml_name_expr): Likewise.
-	* trans-stmt.c (gfc_trans_label_assign): Likewise.
-
-2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* simplify.c (gfc_simplify_bessel_j0,gfc_simplify_bessel_j1,
-	gfc_simplify_bessel_jn,gfc_simplify_bessel_y0,
-	gfc_simplify_bessel_y1,gfc_simplify_bessel_yn): Mark arguments
-	with ATTRIBUTE_UNUSED.
-
-2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* check.c (gfc_check_sizeof): Switch to ATTRIBUTE_UNUSED.
-	* simplify.c (gfc_simplify_lgamma): Likewise.
-
-2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* openmp.c (gfc_match_omp_eos): Use gfc_next_ascii_char and
-	gfc_peek_ascii_char.
-	* decl.c (gfc_match_kind_spec, gfc_match_type_spec,
-	gfc_match_implicit_none, match_implicit_range, gfc_match_implicit,
-	match_string_p, match_attr_spec, gfc_match_suffix,
-	match_procedure_decl, gfc_match_entry, gfc_match_subroutine):
-	Likewise.
-	* gfortran.h (gfc_char_t): New type.
-	(gfc_linebuf): Make line member a gfc_char_t.
-	(locus): Make nextc member a gfc_char_t.
-	(gfc_wide_is_printable, gfc_wide_is_digit, gfc_wide_fits_in_byte,
-	gfc_wide_tolower, gfc_wide_strlen, gfc_next_ascii_char,
-	gfc_peek_ascii_char, gfc_check_digit): New prototypes.
-	* error.c (print_wide_char): New function.
-	(show_locus): Use print_wide_char and gfc_wide_strlen.
-	* io.c (next_char): Use gfc_char_t type.
-	(match_io): Use gfc_peek_ascii_char and gfc_next_ascii_char.
-	* match.c (gfc_match_parens, gfc_match_eos,
-	gfc_match_small_literal_int, gfc_match_name, gfc_match_name_C,
-	gfc_match_intrinsic_op, gfc_match_char,  gfc_match_return,
-	gfc_match_common): Likewise.
-	* match.h (gfc_match_special_char): Change prototype.
-	* parse.c (decode_specification_statement, decode_statement,
-	decode_omp_directive, next_free, next_fixed): Use
-	gfc_peek_ascii_char and gfc_next_ascii_char.
-	* primary.c (gfc_check_digit): Change name.
-	(match_digits, match_hollerith_constant, match_boz_constant,
-	match_real_constant, next_string_char, match_charkind_name,
-	match_string_constant, match_logical_constant_string,
-	match_complex_constant, match_actual_arg, match_varspec,
-	gfc_match_rvalue, match_variable): Use gfc_peek_ascii_char and
-	gfc_next_ascii_char.
-	* scanner.c (gfc_wide_fits_in_byte, wide_is_ascii,
-	gfc_wide_is_printable, gfc_wide_tolower, gfc_wide_is_digit,
-	gfc_wide_is_digit, wide_atoi, gfc_wide_strlen, wide_strcpy,
-	wide_strchr, widechar_to_char, wide_strncmp, wide_strncasecmp,
-	gfc_next_ascii_char, gfc_peek_ascii_char):
-	New functions.
-	(next_char, gfc_define_undef_line, skip_free_comments,
-	gfc_next_char_literal, gfc_next_char, gfc_peek_char,
-	gfc_error_recovery, load_line, preprocessor_line, include_line,
-	load_file, gfc_read_orig_filename): Use gfc_char_t for source
-	characters and the {gfc_,}wide_* functions to manipulate wide
-	strings.
-
-2008-05-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/36117
-	* intrinsic.c (add_functions): Call gfc_simplify_bessel_*.
-	* intrinsic.h: Add prototypes for gfc_simplify_bessel_*.
-	* simplify.c (gfc_simplify_bessel_j0,gfc_simplify_bessel_j1,
-	gfc_simplify_bessel_jn,gfc_simplify_bessel_y0,
-	gfc_simplify_bessel_y1,gfc_simplify_bessel_yn): New.
-
-2008-05-03  Janus Weil  <jaydub66@gmail.com>
-
-	* misc.c (gfc_clear_ts): Set interface to NULL.
-
-2008-05-03  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/33268
-	* gfortran.h: Add extra_comma pointer to gfc_dt structure. Add iokind to
-	gfc_expr value union. Add io_kind enum to here from io.c.
-	* io.c (gfc_free_dt): Free extra_comma.
-	(gfc_resolve_dt): If an extra comma was encountered and io_unit is type
-	BT_CHARACTER, resolve to format_expr and set default unit.  Error if
-	io_kind is M_WRITE. (match_io):  Match the extra comma and set new
-	pointer, extra_comma.
-
-2008-05-01  Bud Davis  <bdavis9659@sbcglobal.net>
-
-	PR35940/Fortran
-	* simplify.c (gfc_simplify_index): Check for direction argument 
-	being a constant.
-
-2008-05-01  Janus Weil  <jaydub66@gmail.com>
-
-	* gfortran.h (struct gfc_symbol): Moving "interface" member to
-	gfc_typespec (plus fixing a small docu error).
-	* interface.c (gfc_procedure_use): Ditto.
-	* decl.c (match_procedure_decl): Ditto.
-	* resolve.c (resolve_specific_f0,
-	resolve_specific_f0, resolve_symbol): Ditto.
-
-2008-04-30  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* intrinsic.c (add_functions): Add SELECTED_CHAR_KIND intrinsic.
-	* intrinsic.h (gfc_check_selected_char_kind,
-	gfc_simplify_selected_char_kind): New prototypes.
-	* gfortran.h (gfc_isym_id): Add GFC_ISYM_SC_KIND.
-	* trans.h (gfor_fndecl_sc_kind): New function decl.
-	* trans-decl.c (gfor_fndecl_sc_kind): Build new decl.
-	* arith.c (gfc_compare_with_Cstring): New function.
-	* arith.h (gfc_compare_with_Cstring): New prototype.
-	* check.c (gfc_check_selected_char_kind): New function.
-	* primary.c (match_string_constant, match_kind_param): Mark
-	symbols used as literal constant kind param as referenced.
-	* trans-intrinsic.c (gfc_conv_intrinsic_sc_kind): New function.
-	(gfc_conv_intrinsic_function): Call gfc_conv_intrinsic_sc_kind.
-	* intrinsic.texi (SELECTED_CHAR_KIND): Document new intrinsic.
-	* simplify.c (gfc_simplify_selected_char_kind): New function.
-
-2008-04-28  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35997
-	* module.c (find_symbol): Do not return a result for a symbol
-	that has been renamed in another module.
-
-2008-04-26  George Helffrich <george@gcc.gnu.org>
-
-	PR fortran/35892
-	PR fortran/35154
-	* trans-common.c (create_common):  Add decl to function
-	chain (if inside one) to preserve identifier scope in debug output.
-
-2008-04-25  Jan Hubicka  <jh@suse.cz>
-
-	* trans-decl.c (trans_function_start): Update.
-
-2008-04-25  Tobias Burnus  <burnus@net-b.de>
-	    Daniel Franke <franke.daniel@gmail.com>
-
-	PR fortran/35156
-	* gfortranspec.c (lang_specific_driver): Deprecate
-	-M option; fix ICE when "-M" is last argument and
-	make "-M<dir>" work.
-	* options.c (gfc_handle_module_path_options): 
-	Use -J instead of -M in error messages.
-	* invoke.texi: Mark -M as depecated.
-
-2008-04-23  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-	    Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/35994
-	* trans-instrinsic.c (gfc_conv_intrinsic_minmaxloc): Correctly adjust
-	loop counter offset.
-
-2008-04-23  Paolo Bonzini  <bonzini@gnu.org>
-
-	* trans-expr.c (gfc_conv_structure): Don't set TREE_INVARIANT.
-	* trans-array.c (gfc_build_null_descriptor): Don't set TREE_INVARIANT.
-	(gfc_trans_array_constructor_value): Don't set TREE_INVARIANT.
-	(gfc_build_constant_array_constructor): Don't set TREE_INVARIANT.
-	(gfc_conv_array_initializer): Don't set TREE_INVARIANT.
-	* trans-common.c (get_init_field): Don't set TREE_INVARIANT.
-	(create_common): Don't set TREE_INVARIANT.
-	* trans-stmt.c (gfc_trans_character_select): Don't set TREE_INVARIANT.
-	* trans-decl.c (gfc_generate_function_code): Don't set TREE_INVARIANT.
-
-2008-04-21  Steve Ellcey  <sje@cup.hp.com>
-
-	* f95-lang.c (gfc_init_decl_processing): use ptr_mode instead of Pmode.
-
-2008-04-21  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/35019
-	* gfortranspec.c (lookup_option): Properly handle separated arguments
-	in -J option, print missing argument message when necessary.
-
-2008-04-20  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35882
-	* scanner.c (skip_fixed_comments): Update continue_line when comment is
-	detected. (gfc_next_char_literal): Likewise.
-
-2008-04-19  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35944
-	PR fortran/35946
-	PR fortran/35947
-	* trans_array.c (gfc_trans_array_constructor): Temporarily
-	realign loop, if loop->from is not zero, before creating
-	the temporary array and provide an offset.
-
-	PR fortran/35959
-	* trans-decl.c (gfc_init_default_dt): Add gfc_ prefix to name
-	and allow for NULL body.  Change all references from
-	init_default_dt to gfc_init_default_dt.
-	* trans.h : Add prototype for gfc_init_default_dt.
-	* trans-array.c (gfc_trans_deferred_vars): After nullification
-	call gfc_init_default_dt for derived types with allocatable
-	components.
-
-2008-04-18  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35892
-	* trans-common.c (create_common): Revert patch causing regression.
-
-2008-04-16  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35724
-	* iresolve.c (gfc_resolve_eoshift): Check for NULL symtree in test for
-	optional argument attribute.
-	
-2008-04-16  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35932
-	* trans-intrinsic.c (gfc_conv_intrinsic_char): Even though KIND
-	is not used, the argument must be converted.
-
-2008-04-16  Jakub Jelinek  <jakub@redhat.com>
-
-	PR target/35662
-	* f95-lang.c (gfc_init_builtin_functions): Make sure
-	BUILT_IN_SINCOS{,F,L} types aren't varargs.
-
-2008-04-15  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35864
-	* expr.c (scalarize_intrinsic_call): Reorder identification of
-	array argument so that if one is not found a segfault does not
-	occur.  Return FAILURE if all scalar arguments.
-
-2008-04-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-	    Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/35882
-	* options.c (gfc_init_options): Set the default maximum continuation
-	lines to 255 for both free and fixed form source for warnings.
-	(gfc_handle_option): Set -std=f95 fixed form max continuations to 19 and
-	the -std=f95 free form max continuations to 39 for warnings.
-	* scanner.c (gfc_next_char_literal): Adjust the current_line number only
-	if it is less than the current locus.
-
-2008-04-07  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/25829 28655
-	* io.c (io_tag): Add new tags for decimal, encoding, asynchronous,
-	round, sign, and id. (match_open_element): Match new tags.
-	(gfc_resolve_open): Resolve new tags. (gfc_match_open): Enable encoding
-	for DEFAULT only. Update error messages. (match_dt_element): Fix match
-	tag for asynchronous. Update error messages. (gfc_free_inquire): Free
-	new expressions. (match_inquire_element): Match new tags.
-	(gfc_match_inquire): Add constraint for ID and PENDING.
-	(gfc_resolve_inquire): Resolve new tags.
-	* trans-io.c (gfc_trans_inquire): Clean up whitespace and fix setting of
-	mask for ID parameter.
-	* ioparm.def: Fix order of parameters for pending, round, and sign.
-	NOTE: These must line up with the definitions in libgfortran/io/io.h. or
-	things don't work.
-
-2008-04-06  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35780
-	* expr.c (scalarize_intrinsic_call): Identify which argument is
-	an array and use that as the template.
-	(check_init_expr): Remove tests that first argument is an array
-	in the call to scalarize_intrinsic_call.
-
-2008-04-06  Tobias Schlüter  <tobi@gcc.gnu.org>
-
-	PR fortran/35832
-	* io.c (io_tag): Add field 'value'.  Split 'spec' field in
-	existing io_tags.
-	(match_etag, match_vtag, match_ltag): Split parsing in two steps
-	to give better error messages.
-
-2008-04-06  Tobias Burnus  <burnus@net-b.de>
-
-	* io.c (check_io_constraints): Add constrains. ID= requires
-	asynchronous= and asynchronous= must be init expression.
-
-2008-04-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* f95-lang.c: Set LANG_HOOKS_NAME to "GNU Fortran".
-
-2008-04-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* dump-parse-tree.c: Use fprintf, fputs and fputc instead of
-	gfc_status and gfc_status_char. Remove gfc_ prefix of the gfc_show_*
-	functions and make them static. Add new gfc_dump_parse_tree
-	function.
-	* gfortran.h (gfc_option_t): Rename verbose into dump_parse_tree.
-	(gfc_status, gfc_status_char): Delete prototypes.
-	* error.c (gfc_status, gfc_status_char): Remove functions.
-	* scanner.c (gfc_new_file): Use printf instead of gfc_status.
-	* options.c (gfc_init_options): Rename verbose into dump_parse_tree.
-	(gfc_handle_module_path_options): Use gfc_fatal_error instead of
-	gfc_status and exit.
-	(gfc_handle_option): Rename verbose into dump_parse_tree.
-	* parse.c (gfc_parse_file): Use gfc_dump_parse_tree.
-
-2008-04-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-	    Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/25829 28655
-	* dump-parse-tree.c (gfc_show_code_node): Show new I/O parameters.
-	* gfortran.h (gfc_statement): Add ST_WAIT enumerator.
-	(gfc_open): Add pointers for decimal, encoding, round, sign,
-	asynchronous. (gfc_inquire): Add pointers for asynchronous, decimal,
-	encoding, pending, round, sign, size, id.
-	(gfc_wait): New typedef struct. (gfc_dt): Add pointers for id, pos,
-	asynchronous, blank, decimal, delim, pad, round, sign.
-	(gfc_exec_op): Add EXEC_WAIT enumerator. (gfc_code): Add pointer for
-	wait. (gfc_free_wait), (gfc_resolve_wait): New function prototypes.
-	* trans-stmt.h (gfc_trans_wait): New function prototype.
-	* trans.c (gfc_trans_code): Add case for EXEC_WAIT.
-	* io.c (io_tag): Add new tags for DECIMAL, ENCODING, ROUND, SIGN,
-	ASYCHRONOUS, ID. (match_open_element): Add matchers for new tags.
-	(gfc_free_open): Free new pointers. (gfc_resolve_open): Resolve new
-	tags. (gfc_resolve_open): Remove comment around check for allowed
-	values and ASYNCHRONOUS, update it.  Likewise for DECIMAL, ENCODING,
-	ROUND, and SIGN. (match_dt_element): Add matching for new tags.
-	(gfc_free_wait): New function. (gfc_resolve_wait): New function.
-	(match_wait_element): New function. (gfc_match_wait): New function.
-	* resolve.c (gfc_resolve_blocks): Add case for EXEC_WAIT.
-	(resolve_code): Add case for EXEC_WAIT. 
-	* st.c (gfc_free_statement): Add case for EXEC_WAIT.
-	* trans-io.c (ioparam_type): Add IOPARM_ptype_wait. (gfc_st_parameter):
-	Add "wait" entry. (iocall): Add IOCALL_WAIT enumerator.
-	(gfc_build_io_library_fndecls): Add function declaration for st_wait.
-	(gfc_trans_open): Add mask bits for new I/O tags.
-	(gfc_trans_inquire): Add mask bits for new I/O tags.
-	(gfc_trans_wait): New translation function.
-	(build_dt): Add mask bits for new I/O tags.
-	* match.c (gfc_match_if) Add matcher for "wait".
-	* match.h (gfc_match_wait): Prototype for new function.
-	* ioparm.def: Add new I/O parameter definitions.
-	* parse.c (decode_statement): Add match for "wait" statement.
-	(next_statement): Add case for ST_WAIT. (gfc_ascii_statement): Same.
-
-2008-04-03  Jakub Jelinek  <jakub@redhat.com>
-
-	PR fortran/35786
-	* openmp.c (resolve_omp_clauses): Diagnose if a clause symbol
-	isn't a variable.
-
-2008-04-03  Tom Tromey  <tromey@redhat.com>
-
-	* Make-lang.in (fortran_OBJS): New variable.
-
-2008-04-03  Paolo Bonzini  <bonzini@gnu.org>
-
-	* f95-lang.c (insert_block): Kill.
-
-2008-04-01  George Helffrich <george@gcc.gnu.org>
-
-	PR fortran/35154, fortran/23057
-	* trans-common.c (create_common):  Add decl to function
-	chain to preserve identifier scope in debug output.
-
-2008-04-01  Joseph Myers  <joseph@codesourcery.com>
-
-	* gfortran.texi: Include gpl_v3.texi instead of gpl.texi
-	* Make-lang.in (GFORTRAN_TEXI): Include gpl_v3.texi instead of
-	gpl.texi.
-
-2008-03-30  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35740
-	* resolve.c (resolve_function, resolve_call): If the procedure
-	is elemental do not look for noncopying intrinsics.
-
-2008-03-29  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35698
-	* trans-array.c (gfc_array_init_size): Set 'size' zero if
-	negative in one dimension.
-
-	PR fortran/35702
-	* trans-expr.c (gfc_trans_string_copy): Only assign a char
-	directly if the lhs and rhs types are the same.
-
-2008-03-28  Daniel Franke  <franke.daniel@gmail.com>
-	    Paul Richard Thomas <paul.richard.thomas@gmail.com>
-
-	PR fortran/34714
-	* primary.c (match_variable): Improved matching of function 
-	result variables.
-	* resolve.c (resolve_allocate_deallocate): Removed checks if
-	the actual argument for STAT is a variable.
-
-2008-03-28  Tobias Burnus  <burnus@net-b.de>
-
-	* symbol.c (gfc_get_default_type): Fix error message; option
-	-fallow_leading_underscore should be -fallow-leading-underscore
-
-2008-03-27  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35724
-	* iresolve.c (gfc_resolve_cshift): Check for NULL symtree in test for
-	optional argument attribute.
-
-2008-03-27  Tom Tromey  <tromey@redhat.com>
-
-	* Make-lang.in: Revert automatic dependency patch.
-
-2008-03-25  Tom Tromey  <tromey@redhat.com>
-
-	* Make-lang.in: Remove .o targets.
-	(fortran_OBJS): New variable.
-	(fortran/gfortranspec.o): Move to fortran/.  Reduce to variable
-	setting.
-	(GFORTRAN_D_OBJS): Update.
-	(GFORTRAN_TRANS_DEPS): Remove.
-
-2008-03-24  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34813
-	* resolve.c (resolve_structure_cons): It is an error to assign
-	NULL to anything other than a pointer or allocatable component.
-
-	PR fortran/33295
-	* resolve.c (resolve_symbol): If the symbol is a derived type,
-	resolve the derived type.  If the symbol is a derived type
-	function, ensure that the derived type is visible in the same
-	namespace as the function.
-
-2008-03-23  Tobias Schlüter  <tobi@gcc.gnu.org>
-
-	* trans.h: Use fold_build in build1_v, build2_v and build3_v
-	macros.
-	* trans-openmp.c (gfc_trans_omp_critical, gfc_trans_omp_single):
-	Don't use build2_v macro.
-
-2008-03-19  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/35152
-	* interface.c (gfc_procedure_use): Check for keyworded arguments in
-	procedures without explicit interfaces.
-
-2008-03-16  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35470
-	* resolve.c (check_assumed_size_reference):  Only visit the
-	first reference and look directly at the highest dimension.
-
-2008-03-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35184
-	* trans-array.c (gfc_conv_array_index_offset): Remove unnecessary
-	assert.
-
-2008-03-15  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/35584
-	* resolve.c (resolve_branch): Less strict and pessimistic warning
-	message.
-
-2008-03-11  Paolo Bonzini  <bonzini@gnu.org>
-
-	* f95-lang.c (LANG_HOOKS_CLEAR_BINDING_STACK): Delete.
-	(gfc_be_parse_file): Call clear_binding_stack from here.
-	(gfc_clear_binding_stack): Rename to clear_binding_stack.
-		
-2008-03-09  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/35474
-	* module.c (mio_symtree_ref): After providing a symbol for a
-	missing equivalence member, resolve and NULL the fixups.
-
-2008-03-09  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* invoke.texi (Error and Warning Options): Document
-	-Wline-truncation.
-
-2008-03-08  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/34956
-	* trans-array.c (gfc_conv_ss_startstride): Fix the logic to avoid
-	checking bounds of absent optional arguments.
-
-2008-03-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/33197
-	* intrinsic.c (add_functions): Add simplification routines for
-	ERF, DERF, ERFC and DERFC.
-	* decl.c (gfc_match_suffix, gfc_match_subroutine): Change GNU
-	extensions into Fortran 2008 features.
-	* intrinsic.h (gfc_simplify_erf, gfc_simplify_erfc): New
-	prototypes.
-	* simplify.c (gfc_simplify_erf, gfc_simplify_erfc): New functions.
-
-2008-03-03  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/33197
-	* intrinsic.c (add_functions): Modify intrinsics ACOSH, ASINH,
-	ATANH, ERF, ERFC and GAMMA. Add intrinsics BESSEL_{J,Y}{0,1,N},
-	ERFC_SCALED, LOG_GAMMA and HYPOT.
-	* intrinsic.h (gfc_check_hypot, gfc_simplify_hypot,
-	gfc_resolve_hypot): New prototypes.
-	* mathbuiltins.def: Add HYPOT builtin. Make complex versions of
-	ACOSH, ASINH and ATANH available.
-	* gfortran.h (GFC_ISYM_ERFC_SCALED, GFC_ISYM_HYPOT): New values.
-	* lang.opt: Add -std=f2008 option.
-	* libgfortran.h: Define GFC_STD_F2008.
-	* lang-specs.h: Add .f08 and .F08 file suffixes.
-	* iresolve.c (gfc_resolve_hypot): New function.
-	* parse.c (parse_contained): Allow empty CONTAINS for Fortran 2008.
-	* check.c (gfc_check_hypot): New function.
-	* trans-intrinsic.c (gfc_intrinsic_map): Define ERFC_SCALE builtin.
-	* options.c (set_default_std_flags): Allow Fortran 2008 by default.
-	(form_from_filename): Add .f08 suffix.
-	(gfc_handle_option): Handle -std=f2008 option.
-	* simplify.c (gfc_simplify_hypot): New function.
-	* gfortran.texi: Document Fortran 2008 status and file extensions.
-	* intrinsic.texi: Document new BESSEL_{J,Y}{0,1,N} intrinsics,
-	as well as HYPOT and ERFC_SCALED. Update documentation of ERF,
-	ERFC, GAMMA, LGAMMA, ASINH, ACOSH and ATANH.
-	* invoke.texi: Document the new -std=f2008 option.
-
-2008-03-02  Jakub Jelinek  <jakub@redhat.com>
-
-	* gfortranspec.c (lang_specific_driver): Update copyright notice
-	dates.
-
-2008-02-29  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35059
-	* expr.c (find_array_element): Modify traversing the constructor to
-	avoid trying to access NULL memory pointed to by next for the
-	last element. (find_array_section): Exit while loop if cons->next is
-	NULL.
-	* trans-expr.c (gfc_conv_scalar_char_value): Initialize gfc_typespec.
-	(gfc_conv_function_call): Same.
-	* decl.c (gfc_match_implicit): Same.
-	* trans-intrinsic.c (gfc_conv_intrinsic_sr_kind): Same.
-
-2008-02-28  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/31463
-	PR fortran/33950
-	PR fortran/34296
-	* lang.opt: Added -Wreturn-type.
-	* options.c (gfc_handle_option): Recognize -Wreturn-type.
-	* trans-decl.c (gfc_trans_deferred_vars): Emit warnings for funtions
-	where the result value is not set.
-	(gfc_generate_function_code): Likewise.
-	(generate_local_decl): Emit warnings for funtions whose RESULT
-	variable is not set.
-
-2008-02-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/34868
-	* trans-expr.c (gfc_conv_variable): Don't build indirect
-	references when explicit interface is mandated.
-	* resolve.c (resolve_formal_arglist): Set attr.always_explicit
-	on the result symbol as well as the procedure symbol.
-
-2008-02-27  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/33387
-	* trans.h: Remove prototypes for gfor_fndecl_math_exponent4,
-	gfor_fndecl_math_exponent8, gfor_fndecl_math_exponent10 and
-	gfor_fndecl_math_exponent16.
-	* f95-lang.c (build_builtin_fntypes): Add new function types.
-	(gfc_init_builtin_functions): Add new builtins for nextafter,
-	frexp, ldexp, fabs, scalbn and inf.
-	* iresolve.c (gfc_resolve_rrspacing): Don't add hidden arguments.
-	(gfc_resolve_scale): Don't convert type of second argument.
-	(gfc_resolve_set_exponent): Likewise.
-	(gfc_resolve_size): Don't add hidden arguments.
-	* trans-decl.c: Remove gfor_fndecl_math_exponent4,
-	gfor_fndecl_math_exponent8, gfor_fndecl_math_exponent10 and
-	gfor_fndecl_math_exponent16.
-	* trans-intrinsic.c (gfc_intrinsic_map): Remove intrinsics
-	for scalbn, fraction, nearest, rrspacing, set_exponent and
-	spacing.
-	(gfc_conv_intrinsic_exponent): Directly call frexp.
-	(gfc_conv_intrinsic_fraction, gfc_conv_intrinsic_nearest,
-	gfc_conv_intrinsic_spacing, gfc_conv_intrinsic_rrspacing,
-	gfc_conv_intrinsic_scale, gfc_conv_intrinsic_set_exponent): New
-	functions.
-	(gfc_conv_intrinsic_function): Use the new functions above.
-
-2008-02-26  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/35033
-	* interface.c (check_operator_interface): Show better line for error
-	messages; fix constrains for user-defined assignment operators.
-	(gfc_extend_assign): Fix constrains for user-defined assignment
-	operators.
-
-2008-02-26  Tom Tromey  <tromey@redhat.com>
-
-	* trans-io.c (set_error_locus): Remove old location code.
-	* trans-decl.c (gfc_set_decl_location): Remove old location code.
-	* f95-lang.c (gfc_init): Remove test of USE_MAPPED_LOCATION.
-	* scanner.c (gfc_gobble_whitespace): Remove old location code.
-	(get_file): Likewise.
-	(preprocessor_line): Likewise.
-	(load_file): Likewise.
-	(gfc_new_file): Likewise.
-	* trans.c (gfc_trans_runtime_check): Remove old location code.
-	(gfc_get_backend_locus): Likewise.
-	(gfc_set_backend_locus): Likewise.
-	* data.c (gfc_assign_data_value): Remove old location code.
-	* error.c (show_locus): Remove old location code.
-	* gfortran.h (gfc_linebuf): Remove old location code.
-	(gfc_linebuf_linenum): Remove old-location variant.
-
-2008-02-25  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/34729
-	* trans-const.c (gfc_build_string_const): Don't call gettext.
-	(gfc_build_localized_string_const): New function.
-	* trans-const.h (gfc_build_localized_string_const): New prototype.
-	* trans.c (gfc_trans_runtime_check): Use
-	gfc_build_localized_string_const instead of gfc_build_string_const.
-	(gfc_call_malloc): Likewise.
-	(gfc_allocate_with_status): Likewise.
-	(gfc_allocate_array_with_status): Likewise.
-	(gfc_deallocate_with_status): Likewise.
-	(gfc_call_realloc): Likewise.
-	* trans-io.c (gfc_trans_io_runtime_check): Likewise.
-
-2008-02-24  Tobias Schlüter  <tobi@gcc.gnu.org>
-
-	* arith.c: Update copyright years.
-	* arith.h: Likewise.
-	* array.c: Likewise.
-	* bbt.c: Likewise.
-	* check.c: Likewise.
-	* data.c: Likewise.
-	* data.h: Likewise.
-	* decl.c: Likewise.
-	* dependency.c: Likewise.
-	* dependency.h: Likewise.
-	* dump-parse-tree.c: Likewise.
-	* error.c: Likewise.
-	* expr.c: Likewise.
-	* gfc-internals.texi: Likewise.
-	* gfortran.h: Likewise.
-	* gfortran.texi: Likewise.
-	* gfortranspec.c: Likewise.
-	* interface.c: Likewise.
-	* intrinsic.c: Likewise.
-	* intrinsic.h: Likewise.
-	* intrinsic.texi: Likewise.
-	* invoke.texi: Likewise.
-	* io.c: Likewise.
-	* iresolve.c: Likewise.
-	* iso-c-binding.def: Likewise.
-	* iso-fortran-env.def: Likewise.
-	* lang-specs.h: Likewise.
-	* lang.opt: Likewise.
-	* libgfortran.h: Likewise.
-	* match.c: Likewise.
-	* match.h: Likewise.
-	* matchexp.c: Likewise.
-	* misc.c: Likewise.
-	* module.c: Likewise.
-	* openmp.c: Likewise.
-	* options.c: Likewise.
-	* parse.c: Likewise.
-	* parse.h: Likewise.
-	* primary.c: Likewise.
-	* resolve.c: Likewise.
-	* scanner.c: Likewise.
-	* simplify.c: Likewise.
-	* st.c: Likewise.
-	* symbol.c: Likewise.
-	* target-memory.c: Likewise.
-	* target-memory.h: Likewise.
-	* trans-array.h: Likewise.
-	* trans-const.h: Likewise.
-	* trans-stmt.h: Likewise.
-	* trans-types.c: Likewise.
-	* trans-types.h: Likewise.
-	* types.def: Likewise.
-
-2008-02-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35223
-	* simplify.c (gfc_simplify_ibclr), (gfc_simplify_ibits),
-	(gfc_simplify_ibset): Remove call to range_check.
-	(simplify_cmplx), (gfc_simplify_dble), (gfc_simplify_float)
-	(gfc_simplify_real): Add call gfc_clear_ts to initialize the
-	temporary gfc_typspec variable.
-
-2008-02-24  Tobias Schlüter  <tobi@gcc.gnu.org>
-
-	* trans-array.c (gfc_conv_descriptor_data_get,
-	gfc_conv_descriptor_data_set_internal,
-	gfc_conv_descriptor_data_addr, gfc_conv_descriptor_offset,
-	gfc_conv_descriptor_dtype, gfc_conv_descriptor_dimension,
-	gfc_conv_descriptor_stride, gfc_conv_descriptor_lbound,
-	gfc_conv_descriptor_ubound, gfc_trans_create_temp_array,
-	gfc_conv_array_transpose, gfc_grow_array,
-	gfc_trans_array_constructor_subarray,
-	gfc_trans_array_constructor_value, gfc_trans_scalarized_loop_end,
-	gfc_array_init_size, gfc_array_allocate, gfc_array_deallocate,
-	gfc_conv_array_initializer, gfc_trans_array_bounds,
-	gfc_trans_auto_array_allocation, gfc_trans_dummy_array_bias,
-	gfc_get_dataptr_offset, gfc_conv_array_parameter,
-	gfc_trans_dealloc_allocated, get_full_array_size,
-	gfc_duplicate_allocatable, structure_alloc_comps): Use fold_buildN
-	instead of buildN.
-	* trans-expr.c (gfc_conv_expr_present, gfc_conv_missing_dummy,
-	gfc_conv_component_ref, gfc_conv_cst_int_power,
-	gfc_conv_function_call, gfc_trans_structur_assign): Likewise.
-	* trans-common.c (create_common): Likewise.
-	* trans-openmp.c (gfc_trans_omp_atomic, gfc_trans_omp_do):
-	Likewise.
-	* trans-const.c (gfc_conv_constant_to_tree): Likewise.
-	* trans-stmt.c (gfc_trans_goto, gfc_trans_return, gfc_trans_do,
-	gfc_trans_integer_select, gfc_trans_character_select,
-	gfc_trans_forall_loop, compute_overall_iter_number,
-	gfc_trans_forall_1, gfc_evaluate_where_mask, gfc_trans_allocate,
-	gfc_trans_deallocate): Likewise.
-	* trans.c (gfc_build_addr_expr, gfc_trans_runtime_check,
-	gfc_allocate_with_status, gfc_allocate_array_with_status,
-	gfc_deallocate_with_status): Likewise.
-	* f95-lang.c (gfc_truthvalue_conversion): Likewise.
-	* trans-io.c (set_parameter_const, set_parameter_value,
-	set_parameter_ref, set_string, set_internal_unit, io_result,
-	set_error_locus, nml_get_addr_expr, transfer_expr): Likewise.
-	* trans-decl.c (gfc_build_qualified_array, build_entry_thunks,
-	gfc_get_fake_result_decl, gfc_trans_auto_character_variable,
-	gfc_generate_function_code): Likewise.
-	* convert.c (convert): Likewise.
-	* trans-intrinsic.c (gfc_conv_intrinsic_conversion,
-	build_fixbound_expr, build_fix_expr, gfc_conv_intrinsic_aint,
-	gfc_conv_intrinsic_int, gfc_conv_intrinsic_imagpart,
-	gfc_conv_intrinsic_conjg, gfc_conv_intrinsic_abs,
-	gfc_conv_intrinsic_cmplx, gfc_conv_intrinsic_mod,
-	gfc_conv_intrinsic_dim, gfc_conv_intrinsic_dprod,
-	gfc_conv_intrinsic_ctime, gfc_conv_intrinsic_fdate,
-	gfc_conv_intrinsic_ttynam, gfc_conv_intrinsic_minmax,
-	gfc_conv_intrinsic_minmax_char, gfc_conv_intrinsic_count,
-	gfc_conv_intrinsic_arith, gfc_conv_intrinsic_dot_product,
-	gfc_conv_intrinsic_minmaxloc, gfc_conv_intrinsic_minmaxval,
-	gfc_conv_intrinsic_btest, gfc_conv_intrinsic_not,
-	gfc_conv_intrinsic_ibits, gfc_conv_intrinsic_ishft,
-	gfc_conv_intrinsic_ichar, gfc_conv_intrinsic_size,
-	gfc_conv_intrinsic_array_transfer, gfc_conv_intrinsic_transfer,
-	gfc_conv_allocated, gfc_conv_associated, gfc_conv_intrinsic_trim,
-	gfc_conv_intrinsic_repeat): Likewise.
-
-2008-02-23  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR target/25477
-	* trans-expr.c (gfc_conv_power_op): Use BUILT_IN_CPOW{F,,L}.
-	* f95-lang.c (gfc_init_builtin_functions): Define BUILT_IN_CPOW{F,,L}.
-	* trans.h (gfor_fndecl_math_cpow, gfor_fndecl_math_cpowf,
-	gfor_fndecl_math_cpowl10, gfor_fndecl_math_cpowl16): Remove.
-	* trans-decl.c: Likewise.
-
-2008-02-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/35059
-	* expr.c (find_array_element): Modify traversing the constructor to
-	avoid trying to access NULL memory pointed to by next for the
-	last element. (find_array_section): Exit while loop if cons->next is
-	NULL.
-
-2008-02-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34907
-	* iresolve.c (resolve_mask_arg): Add gfc_clear_ts to initialize
-	structure.
-	(gfc_resolve_aint): Likewise.
-	(gfc_resolve_anint): Likewise.
-	(gfc_resolve_besn): Likewise.
-	(gfc_resolve_cshift): Likewise.
-	(gfc_resolve_ctime): Likewise.
-	(gfc_resolve_eoshift): Likewise.
-	(gfc_resolve_index_func): Likewise.
-	(gfc_resolve_isatty): Likewise.
-	(gfc_resolve_malloc): Likewise.
-	(gfc_resolve_rrspacing): Likewise.
-	(gfc_resolve_scale): Likewise.
-	(gfc_resolve_set_exponent): Likewise.
-	(gfc_resolve_spacing): Likewise.
-	(gfc_resolve_spacing): Likewise.
-	(gfc_resolve_fgetc): Likewise.
-	(gfc_resolve_fputc): Likewise.
-	(gfc_resolve_ftell): Likewise.
-	(gfc_resolve_ttynam): Likewise.
-	(gfc_resolve_alarm_sub): Likewise.
-	(gfc_resolve_mvbits): Likewise.
-	(gfc_resolve_getarg): Likewise.
-	(gfc_resolve_signal_sub): Likewise.
-	(gfc_resolve_exit): Likewise.
-	(gfc_resolve_flush): Likewise.
-	(gfc_resolve_free): Likewise.
-	(gfc_resolve_ctime_sub): Likewise.
-	(gfc_resolve_fgetc_sub): Likewise.
-	(gfc_resolve_fputc_sub): Likewise.
-	(gfc_resolve_fseek_sub): Likewise.
-	(gfc_resolve_ftell_sub): Likewise.
-	(gfc_resolve_ttynam_sub): Likewise.
-
-2008-02-22  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
-
-	* gfc-internals.texi: Fix typos and markup nits.
-	* gfortran.texi: Likewise.
-	* intrinsic.texi: Likewise.
-
-2008-02-21  Richard Guenther  <rguenther@suse.de>
-
-	* trans-expr.c (gfc_conv_expr_op): Expand INTRINSIC_PARENTHESES
-	as unary PAREN_EXPR for real and complex typed expressions.
-	(gfc_conv_unary_op): Fold the built tree.
-
-2008-02-20  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34997
-	* match.c (gfc_match_name): Improve error message for '$'.
-
-2008-02-19  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/35030
-	* expr.c (gfc_check_pointer_assign): Add type and kind information
-	to type-mismatch message.
-	(gfc_check_assign): Unify error messages.
-
-2008-02-16  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/34952
-	* gfortran.texi: Create new section for unimplemented extensions.
-	Add "STRUCTURE and RECORD" and "ENCODE and DECODE statements".
-	Remove "smaller projects" list. Fix a few typos.
-
-2008-02-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* intrinsic.texi: Rename INDEX node to avoid clashing with
-	index.html on case-insensitive systems.
-
-2008-02-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/35150
-	* trans-expr.c (gfc_conv_function_call): Force evaluation of
-	se->expr.
-
-2008-02-10  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/35019
-	* lang.opt: Allow '-J<dir>' next to '-J <dir>', 
-	likewise '-I <dir>' and '-I<dir>'.
-
-2008-02-06  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
-
-	PR other/35107
-	* Make-lang.in (f951): Add $(GMPLIBS).
-
-2008-02-05  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/35037
-	* trans-common.c (build_field): Mark fields as volatile when needed.
-
-2008-02-05  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/35093
-	* data.c (gfc_assign_data_value): Only free "size" if
-	it has not already been freed.
-
-2008-02-05  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34945
-	* array.c (match_array_element_spec): Remove check for negative
-	array size.
-	(gfc_resolve_array_spec): Add check for negative size.
-
-2008-02-05  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/32315
-	* data.c (gfc_assign_data_value): Add bounds check for array
-	references.
-
-2008-02-04  Daniel Franke  <franke.daniel@gmail.com>
-
-	* resolve.c (resolve_where): Fix typo.
-	(gfc_resolve_where_code_in_forall): Likewise.
-
-2008-02-03  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/32760
-	* resolve.c (resolve_allocate_deallocate): New function.
-	(resolve_code): Call it for allocate and deallocate.
-	* match.c (gfc_match_allocate, gfc_match_deallocate) : Remove
-	the checking of the STAT tag and put in above new function.
-	* primary,c (match_variable): Do not fix flavor of host
-	associated symbols yet if the type is not known.
-
-2008-01-31  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34910
-	* expr.c (gfc_check_assign): It is an error to assign
-	to a sibling procedure.
-
-2008-01-30  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34975
-	* symbol.c (gfc_delete_symtree, gfc_undo_symbols): Rename
-	delete_symtree to gfc_delete_symtree.
-	* gfortran.h : Add prototype for gfc_delete_symtree.
-	* module.c (load_generic_interfaces): Transfer symbol to a
-	unique symtree and delete old symtree, instead of renaming.
-	(read_module): The rsym and the found symbol are the same, so
-	the found symtree can be deleted.
-
-	PR fortran/34429
-	* decl.c (match_char_spec): Remove the constraint on deferred
-	matching of functions and free the length expression.
-	delete_symtree to gfc_delete_symtree.
-	(gfc_match_type_spec): Whitespace.
-	(gfc_match_function_decl): Defer characteristic association for
-	all types except BT_UNKNOWN.
-	* parse.c (decode_specification_statement): Only derived type
-	function matching is delayed to the end of specification.
-
-2008-01-28  Tobias Burnus  <burnus@net-b.de>
-
-	PR libfortran/34980
-	* simplify.c (gfc_simplify_shape): Simplify rank zero arrays.
-
-2008-01-27  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34990
-	* array.c (gfc_check_constructor_type): Revert clearing the expression.
-
-2008-01-26  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34848
-	* trans-expr.c (gfc_conv_function_call): Don't call
-	gfc_add_interface_mapping if the expression is NULL.
-
-2008-01-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/31610
-	* trans-array.c (gfc_trans_create_temp_array): Remove call to
-	gcc_assert (integer_zerop (loop->from[n])).
-
-2008-01-25  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/34661
-	* resolve.c (resolve_where): Added check if user-defined assignment 
-	operator is an elemental subroutine.
-	(gfc_resolve_where_code_in_forall): Likewise.
-
-2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/33375
-	PR fortran/34858
-	* gfortran.h: Revert changes from 2008-01-17.
-	* match.c: Likewise.
-	* symbol.c: Likewise.
-	(gfc_undo_symbols): Undo namespace changes related to common blocks.
-
-2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/34202
-	* data.c (formalize_structure_cons): Skip formalization on
-	empty structures.
-
-2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
-
-	* gfortran.texi (OpenMP): Extended existing documentation.
-	(contributors): Added major contributors of 2008 that were
-	not listed yet.
-	(proposed extensions): Removed implemented items.
-
-2008-01-24  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34872
-	* parse.c (next_statement) : If ST_GET_FCN_CHARACTERISTICS  is
-	seen, check for a statement label and, if present, delete it
-	and set the locus to the start of the statement.
-
-2008-01-22  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34875
-	* trans-io.c (gfc_trans_transfer): If the array reference in a
-	read has a vector subscript, use gfc_conv_subref_array_arg to
-	copy back the temporary.
-
-2008-01-22  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34848
-	* interface.c (compare_actual_formal): Fix adding type
-	to missing_arg_type for absent optional arguments.
-
-2008-01-22  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34907
-	* parse.c (parse_spec): Change = into ==.
-
-2008-01-22  Daniel Franke  <franke.daniel@gmail.com>
-
-	PR fortran/34915
-	* expr.c (check_elemental): Fix check for valid data types.
-
-2008-01-22  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34899
-	* scanner.c (load_line): Support <tab><digit> continuation lines.
-	* invoke.texi (-Wtabs): Document this.
-
-2008-01-22  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34896
-	* module.c (read_module): Set use_rename attribute.
-
-2007-01-21  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34901
-	* interface.c (compare_parameter): Improved error message
-	for arguments of same type and mismatched kinds.
-
-2008-01-20  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34861
-	* resolve.c (resolve_entries): Do not do an array bounds check
-	if the result symbols are the same.
-
-	PR fortran/34854
-	* module.c (read_module) : Hide the symtree of the previous
-	version of the symbol if this symbol is renamed.
-
-2008-01-20  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34784
-	* array.c (gfc_check_constructor_type): Clear the expression ts
-	so that the checking starts from the deepest level of array
-	constructor.
-	* primary.c (match_varspec): If an unknown type is changed to
-	default character and the attempt to match a substring fails,
-	change it back to unknown.
-
-	PR fortran/34785
-	* trans-array.c (gfc_add_loop_ss_code) : If ss->string_length is
-	NULL for an array constructor, use the cl.length expression to
-	build it.
-	(gfc_conv_array_parameter): Change call to gfc_evaluate_now to
-	a tree assignment.
-
-2008-01-19  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR fortran/34817
-	PR fortran/34838
-	* iresolve.c (gfc_resolve_all):  Remove conversion of mask
-	argument to kind=1 by removing call to resolve_mask_arg().
-	(gfc_resolve_any):  Likewise.
-
-2008-01-19  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34760
-	* primary.c (match_variable): Handle FL_UNKNOWN without
-	uneducated guessing.
-	(match_variable): Improve error message.
-
-2008-01-18  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/32616
-	* interface.c (get_expr_storage_size): Return storage size
-	for array element designators.
-	(compare_actual_formal): Reject unequal string sizes for
-	assumed-shape dummy arguments. And fix error message for
-	array-sections with vector subscripts.
-
-2008-01-17  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34556
-	* simplify.c (is_constant_array_expr): New static function that returns
-	true if the given expression is an array and is constant.
-	(gfc_simplify_reshape): Use new function.
-
-2008-01-17  H.J. Lu  <hongjiu.lu@intel.com>
-
-	PR fortran/33375
-	* symbol.c (free_common_tree): Renamed to ...
-	(gfc_free_common_tree): This.  Remove static.
-	(gfc_free_namespace): Updated.
-
-	* gfortran.h (gfc_free_common_tree): New.
-
-	* match.c (gfc_match_common): Call gfc_free_common_tree () with
-	gfc_current_ns->common_root and set gfc_current_ns->common_root
-	to NULL on syntax error.
-
-2008-01-18  Richard Sandiford  <rsandifo@nildram.co.uk>
-
-	PR fortran/34686
-	* trans-expr.c (gfc_conv_function_call): Use proper
-	type for returned character pointers.
-
-2008-01-17  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34429
-	PR fortran/34431
-	PR fortran/34471
-	* decl.c : Remove gfc_function_kind_locus and
-	gfc_function_type_locus. Add gfc_matching_function.
-	(match_char_length): If matching a function and the length
-	does not match, return MATCH_YES and try again later.
-	(gfc_match_kind_spec): The same.
-	(match_char_kind): The same.
-	(gfc_match_type_spec): The same for numeric and derived types.
-	(match_prefix): Rename as gfc_match_prefix.
-	(gfc_match_function_decl): Except for function valued character
-	lengths, defer applying kind, type and charlen info until the
-	end of specification block.
-	gfortran.h (gfc_statement): Add ST_GET_FCN_CHARACTERISTICS.
-	parse.c (decode_specification_statement): New function.
-	(decode_statement): Call it when a function has kind = -1. Set
-	and reset gfc_matching function, as function statement is being
-	matched.
-	(match_deferred_characteristics): Simplify with a single call
-	to gfc_match_prefix. Do appropriate error handling. In any
-	case, make sure that kind = -1 is reset or corrected.
-	(parse_spec): Call above on seeing ST_GET_FCN_CHARACTERISTICS.
-	Throw an error if kind = -1 after last specification statement.
-	parse.h : Prototype for gfc_match_prefix.
-
-2008-01-16  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34796
-	* interface.c (compare_parameter): Allow AS_DEFERRED array
-	elements and reject attr.pointer array elemenents.
-	(get_expr_storage_size): Return storage size of elements of
-	assumed-shape and pointer arrays.
-
-2008-01-15  Sebastian Pop  <sebastian.pop@amd.com>
-
-	* f95-lang.c (gfc_init_builtin_functions): Initialize GOMP builtins
-	for flag_tree_parallelize_loops.
-
-2008-01-15  Thomas Koenig  <tkoenig@gcc.gnu.org>
-
-	PR libfortran/34671
-	* iresolve.c (gfc_resolve_all):  Call resolve_mask_arg.
-	(gfc_resolve_any):  Likewise.
-	(gfc_resolve_count):  Likewise.  Don't append kind of
-	argument to function name.
-
-2008-01-13  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34665
-	* resolve.c (resolve_actual_arglist): For expressions,
-	also check for assume-sized arrays.
-	* interface.c (compare_parameter): Move F2003 character checks
-	here, print error messages here, reject elements of
-	assumed-shape array as argument to dummy arrays.
-	(compare_actual_formal): Update for the changes above.
-
-2008-01-13  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34763
-	* decl.c (contained_procedure): Only check directly preceeding state.
-
-2008-01-13  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34759
-	* check.c (gfc_check_shape): Accept array ranges of
-	assumed-size arrays.
-
-2008-01-12  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34432
-	* match.c (gfc_match_name): Don't error if leading character is a '(',
-	just return MATCH_NO.
-
-2008-01-11  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34722
-	* trans-io.c (create_dummy_iostat): Commit the symbol.
-
-2008-01-11  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34537
-	* simplify.c (gfc_simplify_transfer): Return NULL if the size
-	of the element is unavailable and only assign character length
-	to the result, if 'mold' is constant.
-
-2008-01-10  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34396
-	* trans-array.c (gfc_trans_array_ctor_element):  Use gfc_trans_string_copy
-	to assign strings and perform bounds checks on the string length.
-	(get_array_ctor_strlen): Remove bounds checking.
-	(gfc_trans_array_constructor): Initialize string length checking.
-	* trans-array.h : Add prototype for gfc_trans_string_copy.
-
-2008-01-08  Richard Guenther  <rguenther@suse.de>
-
-	PR fortran/34706
-	PR tree-optimization/34683
-	* trans-types.c (gfc_get_array_type_bounds): Use an array type
-	with known size for accesses if that is known.
-
-2008-01-08  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34476
-	* expr.c (find_array_element): Check that the array bounds are
-	constant before using them.  Use lower, as well as upper bound.
-	(check_restricted): Allow implied index variable.
-
-2008-01-08  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34681
-	* trans_array.c (gfc_trans_deferred_array): Do not null the
-	data pointer on entering scope, nor deallocate it on leaving
-	scope, if the symbol has the 'save' attribute.
-
-	PR fortran/34704
-	* trans_decl.c (gfc_finish_var_decl): Derived types with
-	allocatable components and an initializer must be TREE_STATIC.
-
-2008-01-07  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34672
-	* module.c (write_generic): Rewrite completely.
-	(write_module): Change call to write_generic.
-
-2008-01-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34659
-	* scanner.c (load_line): Do not count ' ' as printable when checking for
-	continuations.
-
-2008-01-06  Paul Thomas  <pault@gcc.gnu.org>
-
-	PR fortran/34545
-	* module.c (load_needed): If the namespace has no proc_name
-	give it the module symbol.
-
-2008-01-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR fortran/34387
-	* trans-expr.c (gfc_conv_missing_dummy): Use a temporary to type convert
-	the dummy variable expression, test for NULL, and pass the variable
-	address to the called function.
-
-2007-01-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34658
-	* match.c (gfc_match_common): Remove blank common in
-	DATA BLOCK warning.
-	* resolve.c (resolve_common_vars): New function.
-	(resolve_common_blocks): Move checks to resolve_common_vars
-	and invoke that function.
-	(resolve_types): Call resolve_common_vars for blank commons.
-
-2008-01-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34655
-	* resolve.c (resolve_equivalence_derived): Reject derived types with
-	default initialization if equivalenced with COMMON variable.
-
-2008-01-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34654
-	* io.c (check_io_constraints): Disallow unformatted I/O for
-	internal units.
-
-2008-01-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34660
-	* resolve.c (resolve_formal_arglist): Reject dummy procedure in
-	ELEMENTAL functions.
-
-2008-01-06  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34662
-	* interface.c (compare_actual_formal): Reject parameter
-	actual to intent(out) dummy.
-
-2008-01-04  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/34557
-	* primary.c (match_varspec): Gobble whitespace before
-	checking for '('.
+	PR fortran/38594
+	* resolve.c (resolve_call): When searching for proper host
+	association, use symtree rather than symbol.  For everything
+	except generic subroutines, substitute the symtree in the call
+	rather than the symbol.
diff --git a/gcc/fortran/ChangeLog-2008 b/gcc/fortran/ChangeLog-2008
new file mode 100644
index 000000000000..d1135b35dfc0
--- /dev/null
+++ b/gcc/fortran/ChangeLog-2008
@@ -0,0 +1,4135 @@
+2008-12-31  Daniel Franke  <franke.daniel@gmail.com>
+
+	* check.c (dim_rank_check): Fixed checking of dimension argument
+	if array is of type EXPR_ARRAY.
+
+2008-12-22  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/38602
+	* trans-decl.c (init_intent_out_dt): Allow for optional args.
+
+2008-12-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/38398
+	* io.c: Add error checks for g0 formatting and provide adjustment of
+	error loci for improved error messages.
+
+2008-12-21  Arjen Markus  <arjen.markus@wldelft.nl>
+	    Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37605
+	* gfortran.texi: Fixed some typos and some minor style improvements.
+	* intrinsic.texi: Some clarifications and typo-fixes.
+	* invoke.texi: Better documenation of the behaviour of the
+	-fdefault-*-8 options and some other fixes.
+
+2008-12-18  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/31822
+	* gfortran.h (gfc_check_same_strlen): Made public.
+	* trans.h (gfc_trans_same_strlen_check): Made public.
+	* check.c (gfc_check_same_strlen): Made public and adapted error
+	message output to be useful not only for intrinsics.
+	(gfc_check_merge): Adapt to gfc_check_same_strlen change.
+	* expr.c (gfc_check_pointer_assign): Use gfc_check_same_strlen for
+	string length compile-time check.
+	* trans-expr.c (gfc_trans_pointer_assignment): Add runtime-check for
+	equal string lengths using gfc_trans_same_strlen_check.
+	* trans-intrinsic.c (gfc_trans_same_strlen_check): Renamed and made
+	public from conv_same_strlen_check.
+	(gfc_conv_intrinsic_merge): Adapted accordingly.
+
+2008-12-17  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/38137
+	* trans-intrinsic.c (conv_same_strlen_check): New method.
+	(gfc_conv_intrinsic_merge): Call it here to actually do the check.
+
+2008-12-15  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/38487
+	* dependency.c (gfc_is_data_pointer): New function.
+	(gfc_check_argument_var_dependency): Disable the warning
+	in the pointer case.
+	(gfc_check_dependency): Use gfc_is_data_pointer.
+
+2008-12-15  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/38113
+	* error.c (show_locus): Start counting columns at 0.
+	* primary.c (match_actual_arg): Eat spaces
+	before copying the current locus.
+	(match_variable): Copy the locus before matching.
+
+2008-12-14  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35937
+	* trans-expr.c (gfc_finish_interface_mapping): Fold convert the
+	character length to gfc_charlen_type_node.
+
+2008-12-12  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/36355
+	* check.c (gfc_check_matmul): Fixed error message for invalid
+	types to correctly identify the offending argument, added check
+	for mismatching types.
+
+2008-12-11  Richard Guenther  <rguenther@suse.de>
+
+	* Make-lang.in (install-finclude-dir): Use correct mode argument
+	for mkinstalldirs.
+
+2008-12-09  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/36376
+	PR fortran/37468
+	* lang-specs.h: Pass on -i* options to f951 to (probably) report
+	them as unknown. Duplicate gcc.c (cpp_options), but omit
+	-fpch-preprocess on -save-temps.
+
+2008-12-09  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/36457
+	* lang.opt: Added option idirafter.
+	* cpp.h (gfc_cpp_add_include_path_after): New prototype.
+	* cpp.c (gfc_cpp_handle_option): Recognize and handle OPT_dirafter.
+	(gfc_cpp_add_include_path_after): New, adds user-defined search path
+	after any other paths.
+	* invoke.texi (idirafter): New.
+	(no-range-check): Fixed entry in option-index.
+
+2008-12-09  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/37469
+	* expr.c (find_array_element): Simplify array bounds.
+	Assert that both bounds are constant expressions.
+
+2008-12-09  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/35983
+	* trans-expr.c (gfc_trans_subcomponent_assign):
+	Add se's pre and post blocks to current block.
+	(gfc_trans_structure_assign): Remove specific handling
+	of C_NULL_PTR and C_NULL_FUNPTR.
+
+2008-12-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/38425
+	* io.c (check_io_constraints): Check constraints on REC=, POS=, and
+	internal unit with POS=. Fix punctuation on a few error messages.
+
+2008-12-06  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/38415
+	* expr.c (gfc_check_pointer_assign): Added a check for abstract
+	interfaces in procedure pointer assignments, removed check involving
+	gfc_compare_interfaces until PR38290 is fixed completely.
+
+2008-12-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/38291
+	* io.c (match_dt_element): Use dt->pos in matcher.
+	(gfc_free_dt): Free dt->pos after use.
+	(gfc_resolve_dt): Use dt->pos in resolution of stream position tag.
+
+2008-12-05  Sebastian Pop  <sebastian.pop@amd.com>
+
+	PR bootstrap/38262
+	* Make-lang.in (f951): Add BACKENDLIBS, remove GMPLIBS.
+
+2008-12-02  Jakub Jelinek  <jakub@redhat.com>
+	    Diego Novillo  <dnovillo@google.com>
+
+	* Make-lang.in (install-finclude-dir): Use mkinstalldirs
+	and don't remove the finclude directory beforehand.
+
+2008-12-02  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36704
+	PR fortran/38290
+	* decl.c (match_result): Result may be a standard variable or a
+	procedure pointer.
+	* expr.c (gfc_check_pointer_assign): Additional checks for procedure
+	pointer assignments.
+	* primary.c (gfc_match_rvalue): Bugfix for procedure pointer
+	assignments.
+	* resolve.c (resolve_function): Check for attr.subroutine.
+	* symbol.c (check_conflict): Addtional checks for RESULT statements.
+	* trans-types.c (gfc_sym_type,gfc_get_function_type): Support procedure
+	pointers as function result.
+
+2008-12-01  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/38252
+	* parse.c (parse_spec): Skip statement order check in case
+	of a CONTAINS statement.
+
+2008-11-30  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37779
+	* gfortran.h (struct gfc_entry_list): Fixed typo in comment.
+	* resolve.c (is_illegal_recursion): New method.
+	(resolve_procedure_expression): Use new is_illegal_recursion instead of
+	direct check and handle function symbols correctly.
+	(resolve_actual_arglist): Removed useless recursion check.
+	(resolve_function): Use is_illegal_recursion instead of direct check.
+	(resolve_call): Ditto.
+
+2008-11-29  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* trans-array.c (gfc_conv_array_parameter): Guard union access.
+
+2008-11-29  Janus Weil  <janus@gcc.gnu.org>
+	    Mikael Morin <mikael@gcc.gnu.org>
+
+	PR fortran/38289
+	PR fortran/38290
+	* decl.c (match_procedure_decl): Handle whitespaces.
+	* resolve.c (resolve_specific_s0): Bugfix in check for intrinsic
+	interface.
+
+2008-11-25  H.J. Lu  <hongjiu.lu@intel.com>
+
+	* module.c (gfc_dump_module): Report error on unlink only if
+	errno != ENOENT.
+
+2008-11-25  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/36463
+	* expr.c (replace_symbol): Don't replace the symtree
+	if the expresion is an intrinsic function. Don't create
+	non-existent symtrees.  Use symbol's name instead of symtree's,
+	different in case of module procedure dummy arguments.
+
+2008-11-25  Jan Kratochvil  <jan.kratochvil@redhat.com>
+
+	PR fortran/38248
+	* module.c (gfc_dump_module): Check rename/unlink syscalls errors.
+
+2008-11-25  Eric Botcazou  <ebotcazou@adacore.com>
+
+	PR fortran/37319
+	* parse.c (match_deferred_characteristics): Make sure 'name' is
+	initialized before reading it.
+
+2008-11-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/37803
+	* arith.c (gfc_check_real_range): Add mpfr_check_range.
+	* simplify.c (gfc_simplify_nearest): Add mpfr_check_range.
+
+2008-11-24  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/38184
+	* simplify.c (is_constant_array_expr): Return true instead of false
+	if the array constructor is empty.
+
+2008-11-24  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37779
+	* resolve.c (resolve_procedure_expression): New method.
+	(resolve_variable): Call it.
+	(resolve_actual_arglist): Call gfc_resolve_expr for procedure arguments.
+
+2008-11-24  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34820
+	* trans-expr.c (gfc_conv_function_call): Remove all code to
+	deallocate intent out derived types with allocatable
+	components.
+	(gfc_trans_assignment_1): An assignment from a scalar to an
+	array of derived types with allocatable components, requires
+	a deep copy to each array element and deallocation of the
+	converted rhs expression afterwards.
+	* trans-array.c : Minor whitespace.
+	* trans-decl.c (init_intent_out_dt): Add code to deallocate
+	allocatable components of derived types with intent out.
+	(generate_local_decl): If these types are unused, set them
+	referenced anyway but allow the uninitialized warning.
+
+	PR fortran/34143
+	* trans-expr.c (gfc_trans_subcomponent_assign): If a conversion
+	expression has a null data pointer argument, nullify the
+	allocatable component.
+
+	PR fortran/32795
+	* trans-expr.c (gfc_trans_subcomponent_assign): Only nullify
+	the data pointer if the source is not a variable.
+
+2008-11-23  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37735
+	* trans-array.c (structure_alloc_comps): Do not duplicate the
+	descriptor if this is a descriptorless array!
+
+2008-11-12  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/38160
+	* trans-types.c (gfc_validate_c_kind): Remove function.
+	* decl.c (gfc_match_kind_spec): Add C kind parameter check.
+	(verify_bind_c_derived_type): Remove gfc_validate_c_kind call.
+	(verify_c_interop_param): Update call.
+	* gfortran.h (verify_bind_c_derived_type): Update prototype.
+	(gfc_validate_c_kind): Remove.
+	* symbol.c (verify_bind_c_derived_type): Update verify_c_interop call.
+	* resolve.c (gfc_iso_c_func_interface): Ditto.
+
+2008-11-22  Jakub Jelinek  <jakub@redhat.com>
+
+	PR libfortran/37839
+	* trans-io.c (gfc_build_io_library_fndecls): Decrease pad size back
+	to 16 pointers plus 32 integers.  Don't use max integer kind
+	alignment, only gfc_intio_kind's alignment.
+	(gfc_trans_inquire): Only set flags2 if mask2 is non-zero.
+	* ioparm.def: Fix order, bitmasks and types of inquire round, sign
+	and pending fields.  Move u in dt before id.
+	* io.c (gfc_free_inquire): Free decimal and size exprs.
+	(match_inquire_element): Match size instead of matching blank twice.
+	(gfc_resolve_inquire): Resolve size.
+
+2008-11-20  Jakub Jelinek  <jakub@redhat.com>
+
+	PR middle-end/29215
+	* trans-array.c (trans_array_constructor_value,
+	gfc_build_constant_array_constructor): Fill in TREE_PURPOSE.
+
+	* trans-intrinsic.c (gfc_conv_intrinsic_minmaxloc): Use
+	gfc_index_one_node.
+	(gfc_conv_intrinsic_size): Use gfc_index_{zero,one}_node.
+
+	PR fortran/38181
+	* trans-intrinsic.c (gfc_conv_intrinsic_size): Inline 2 argument
+	size if the second argument is not optional and one argument size
+	for rank 1 arrays.
+
+2008-11-19  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/38171
+	* module.c (load_equiv): Regression fix; check that equivalence
+	members come from the same module only.
+
+2008-11-16  Mikael Morin <mikael.morin@tele2.fr>
+
+	PR fortran/35681
+	* dependency.c (gfc_check_argument_var_dependency): Add
+	elemental check flag. Issue a warning if we find a dependency
+	but don't generate a temporary. Add the case of an elemental
+	function call as actual argument to an elemental procedure.
+	Add the case of an operator expression as actual argument
+	to an elemental procedure.
+	(gfc_check_argument_dependency): Add elemental check flag.
+	Update calls to gfc_check_argument_var_dependency.
+	(gfc_check_fncall_dependency): Add elemental check flag.
+	Update call to gfc_check_argument_dependency.
+	* trans-stmt.c (gfc_trans_call): Make call to
+	gfc_conv_elemental_dependency unconditional, but with a flag
+	whether we should check dependencies between variables.
+	(gfc_conv_elemental_dependency): Add elemental check flag.
+	Update call to gfc_check_fncall_dependency.
+	* trans-expr.c (gfc_trans_arrayfunc_assign): Update call to
+	gfc_check_fncall_dependency.
+	* resolve.c (find_noncopying_intrinsics): Update call to
+	gfc_check_fncall_dependency.
+	* dependency.h (enum gfc_dep_check): New enum.
+	(gfc_check_fncall_dependency): Update prototype.
+
+2008-11-16  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/37992
+	* gfortran.h (gfc_namespace): Added member old_cl_list, 
+	backup of cl_list.
+	(gfc_free_charlen): Added prototype.
+	* symbol.c (gfc_free_charlen): New function.
+	(gfc_free_namespace): Use gfc_free_charlen.
+	* parse.c (next_statement): Backup gfc_current_ns->cl_list.
+	(reject_statement): Restore gfc_current_ns->cl_list.
+	Free cl_list's elements before dropping them.
+
+2008-11-16  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/38095
+	* trans-expr.c (gfc_map_intrinsic_function): Fix pointer access.
+
+2008-11-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/38119
+	* trans-array.c (gfc_trans_create_temp_array): Set the
+	loop->from to zero and the renormalisation of loop->to for all
+	dimensions.
+
+2008-11-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37926
+	* trans-expr.c (gfc_free_interface_mapping): Null sym->formal
+	(gfc_add_interface_mapping): Copy the pointer to the formal
+	arglist, rather than using copy_formal_args - fixes regression.
+
+2008-11-15  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37926
+	* trans-expr.c (gfc_add_interface_mapping): Transfer the formal
+	arglist and the always_explicit attribute if the dummy arg is a
+	procedure.
+
+2008-11-14  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/37988
+	* io.c (enum format_token): For readability replace FMT_POS with FMT_T,
+	FMT_TL, and FMT_TR.  (format_lex): Use new enumerators. (check_format):
+	Add check for missing positive integer.
+
+2008-10-14  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/38033
+	* trans-array.c (gfc_trans_create_temp_array): Stabilize the
+	'to' expression.
+	(gfc_conv_loop_setup): Use the end expression for the loop 'to'
+	if it is available.
+
+2008-11-12  Jakub Jelinek  <jakub@redhat.com>
+
+	PR target/35366
+	PR fortran/33759
+	* trans-const.c (gfc_conv_constant_to_tree): Warn when
+	converting an integer outside of LOGICAL's range to
+	LOGICAL.
+	* trans-intrinsic.c (gfc_conv_intrinsic_function,
+	gfc_conv_intrinsic_array_transfer, gfc_conv_intrinsic_transfer):
+	Use INTEGER_TYPE instead of BOOLEAN_TYPE for TRANSFER as
+	argument of another TRANSFER.
+
+2008-11-12  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/38065
+	* resolve.c (resolve_fntype): Fix private derived type checking.
+
+2008-11-09  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37836
+	* intrinsic.c (add_functions): Reference gfc_simplify._minval
+	and gfc_simplify_maxval.
+	* intrinsic.h : Add prototypes for gfc_simplify._minval and
+	gfc_simplify_maxval.
+	* simplify.c (min_max_choose): New function extracted from
+	simplify_min_max.
+	(simplify_min_max): Call it.
+	(simplify_minval_maxval, gfc_simplify_minval,
+	gfc_simplify_maxval): New functions.
+
+2008-11-04  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37597
+	* parse.c (gfc_fixup_sibling_symbols ): Fixup contained, even
+	when symbol not found.
+
+2008-11-03  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37821
+	* cpp.c (gfc_cpp_add_include_path): Use BRACKET.
+	* scanner.c (add_path_to_list): Argument to add at head.
+	(gfc_add_include_path): Add new argument.
+	(gfc_add_intrinsic_modules_path) Update call.
+	(load_file): Print filename/line in the error message.
+	* gfortran.h (gfc_add_include_path): Update prototype.
+	* options.c (gfc_post_options,gfc_handle_module_path_options,
+	gfc_handle_option): Update call.
+	* lang-spec.h (F951_OPTIONS): Don't insert include path twice.
+
+	* arith.c (arith_error): Add -fno-range-error to the message.
+
+2008-11-03  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37445
+	* resolve.c (resolve_actual_arglist ): Correct comparison of
+	FL_VARIABLE with e->expr_type.
+	(resolve_call): Check that host association is correct.
+	(resolve_actual_arglist ): Remove return is old_sym is use
+	associated.  Only reparse expression if old and new symbols
+	have different types.
+
+	PR fortran/PR35769
+	* resolve.c (gfc_resolve_assign_in_forall): Change error to a
+	warning.
+
+2008-11-01  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36426
+	* expr.c (replace_symbol): Replace all symbols which lie in the
+	formal namespace of the interface and copy their attributes.
+	* resolve.c (resolve_symbol): Add charlen to namespace.
+
+2008-11-01  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/19925
+	* trans-array.c (gfc_trans_array_constructor_value): Fix comment.
+	(gfc_conv_array_initializer): Convert internal_error() to gfc_error_now.
+	* array.c: Remove GFC_MAX_AC_EXPAND macro.
+	(gfc_expand_constructor): Use gfc_option.flag_max_array_constructor.
+	* gfortran.h (gfc_option): Add flag_max_array_constructor member.
+	* lang.opt: Add -fmax-array-constructor option.
+	* expr.c (gfc_match_init_expr): Fix error message to mention new option.
+	* invoke.texi: Document new option.
+	* options.c (gfc_init_options): Set default value for new option.
+	(gfc_handle_option): Deal with commandline.
+
+2008-11-01  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/35681
+	* gfortran.h (struct gfc_code): New field `resolved_isym'.
+	* trans.h (gfc_build_memcpy_call): Made public.
+	* trans-array.h (gfc_trans_create_temp_array): New argument `initial'.
+	* intrinsic.c (gfc_intrinsic_sub_interface): Set resolved_isym.
+	* iresolve.c (create_formal_for_intents): New helper method.
+	(gfc_resolve_mvbits): Put dummy formal arglist on resolved_sym.
+	* resolve.c (resolve_call): Initialize resolved_isym to NULL.
+	* trans-array.c (gfc_trans_allocate_array_storage): New argument
+	`initial' to allow initializing the allocated storage to some initial
+	value copied from another array.
+	(gfc_trans_create_temp_array): Allow initialization of the temporary
+	with a copy of some other array by using the new extension.
+	(gfc_trans_array_constructor): Pass NULL_TREE for initial argument.
+	(gfc_conv_loop_setup): Ditto.
+	* trans-intrinsic.c (gfc_conv_intrinsic_array_transfer): Ditto.
+	* trans-expr.c (gfc_conv_function_call): Ditto.
+	(gfc_build_memcpy_call): Made public.
+	* trans-stmt.c (gfc_conv_elemental_dependencies): Initialize created
+	temporary for INTENT(INOUT) arguments to the value of the mirrored
+	array and clean up the temporary as very last intructions in the created
+	block.
+	* trans.c (gfc_trans_code): For EXEC_CALL, see if we have a MVBITS call
+	and enable elemental dependency checking if we have.
+
+2008-11-01  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36322
+	PR fortran/36463
+	* gfortran.h: New function gfc_expr_replace_symbols.
+	* decl.c (match_procedure_decl): Increase reference count for interface.
+	* expr.c: New functions replace_symbol and gfc_expr_replace_symbols.
+	* resolve.c (resolve_symbol): Correctly copy array spec and char len
+	of PROCEDURE declarations from their interface.
+	* symbol.c (gfc_get_default_type): Enhanced error message.
+	(copy_formal_args): Call copy_formal_args recursively for arguments.
+	* trans-expr.c (gfc_conv_function_call): Bugfix.
+
+2008-11-01  Dennis Wassel  <dennis.wassel@gmail.com>
+
+	PR fortran/37159
+	* fortran/check.c (gfc_check_random_seed): Check PUT size
+	at compile time.
+
+2008-10-31  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/35840
+	* expr.c (gfc_reduce_init_expr): New function, containing checking code
+	from gfc_match_init_expr, so that checking can be deferred. 
+	(gfc_match_init_expr): Use gfc_reduce_init_expr.
+	* io.c (check_io_constraints): Use gfc_reduce_init_expr instead of 
+	checking that the expression is a constant. 
+	* match.h (gfc_reduce_init_expr): Prototype added. 
+
+2008-10-31  Mikael Morin  <mikael.morin@tele2.fr>
+
+	PR fortran/35820
+	* resolve.c (gfc_count_forall_iterators): New function.
+	(gfc_resolve_forall): Use gfc_count_forall_iterators to evaluate 
+	the needed memory amount to allocate. Don't forget to free allocated 
+	memory.  Add an assertion to check for memory leaks. 
+
+2008-10-30  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/37930
+	* fortran/arith.c (gfc_mpfr_to_mpz):  Test for NaN and Inf values.
+	Remove stale comment and kludge code for MPFR 2.0.1 and older.
+	(gfc_real2int): Error on conversion of NaN or Inf.
+	(gfc_complex2int): Ditto.
+	* fortran/arith.h: Update mpfr_to_mpz prototype.
+	* fortran/simplify.c (gfc_simplify_ceiling, gfc_simplify_floor,
+	gfc_simplify_ifix, gfc_simplify_idint, simplify_nint): Update function
+	calls to include locus.
+
+2008-10-30  Mikael Morin  <mikael.morin@tele2.fr>
+
+        PR fortran/37903
+        * trans-array.c (gfc_trans_create_temp_array): If n is less
+	than the temporary dimension, assert that loop->from is
+	zero (reverts to earlier versions). If there is at least one
+	null loop->to[n], it is a callee allocated array so set the
+	size to NULL and break.
+	(gfc_trans_constant_array_constructor): Set the offset to zero.
+	(gfc_trans_array_constructor): Remove loop shifting around the
+	temporary creation.
+	(gfc_conv_loop_setup): Prefer zero-based descriptors if
+	possible.  Calculate the translation from loop variables to
+	array indices if an array constructor.
+
+2008-10-30  Mikael Morin  <mikael.morin@tele2.fr>
+
+        PR fortran/37749
+        * trans-array.c (gfc_trans_create_temp_array): If size is NULL
+	use the array bounds for loop->to.
+
+2008-10-28  Tobias Burnus  <burnus@net-b.de>
+
+	* intrinsic.texi: Update OpenMP section for OMPv3.
+
+2008-10-24  Jakub Jelinek  <jakub@redhat.com>
+
+	* Make-lang.in (check-f95-subtargets, check-fortran-subtargets): New
+	aliases for check-gfortran-subtargets.
+	(lang_checks_parallelized): Add check-gfortran.
+	(check_gfortran_parallelize): New variable.
+
+2008-10-19  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37723
+	* dependency.c (gfc_dep_resolver ): If we find equal array
+	element references, go on to the next reference.
+
+2008-10-16  Daniel Kraft  <d@domob.eu>
+
+	* resolve.c (resolve_elemental_actual): Handle calls to intrinsic
+	subroutines correctly.
+
+2008-10-13  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* simplify.c: Remove MPFR_VERSION_NUM(2,3,0) conditionals.
+
+2008-10-12  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37688
+	* expr.c (gfc_expr_check_typed): Extend permission of untyped
+	expressions to both top-level variable and basic arithmetic expressions.
+
+2008-10-12  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37787
+	* dependency.c (gfc_are_equivalenced_arrays): Look in symbol
+	namespace rather than current namespace, if it is available.
+
+2008-10-12  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/37792
+	* fortran/resolve.c (resolve_fl_variable): Simplify the
+	initializer if there is one.
+
+2008-10-11  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37794
+	* module.c (check_for_ambiguous): Remove redundant code.
+
+2008-10-09  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/35723
+	* gfortran.h (gfc_suppress_error): Removed from header.
+	(gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
+	* array.c (gfc_array_size): Use new gfc_push/pop_suppress_errors
+	instead of directly changing gfc_suppress_error.
+	* intrinsic.c (gfc_intrinsic_func_interface): Ditto.
+	(gfc_intrinsic_sub_interface): Ditto.
+	* error.c (suppress_errors): Made static from `gfc_suppress_error'.
+	(gfc_push_suppress_errors), (gfc_pop_suppress_errors): New methods.
+	(gfc_notify_std), (gfc_error): Use new static name of global.
+	* expr.c (check_arglist), (check_references): New methods.
+	(check_restricted): Check arglists and references of EXPR_FUNCTIONs
+	and EXPR_VARAIBALEs, respectively.  Allow PARAMETER symbols.
+
+2008-10-07  Jakub Jelinek  <jakub@redhat.com>
+
+	* f95-lang.c (poplevel): Don't clear BLOCK_VARS if functionbody.
+	* trans-decl.c (gfc_build_qualified_array): Build accurate debug type
+	even if nest.
+	(build_entry_thunks, gfc_generate_function_code,
+	gfc_generate_constructors): Ensure DECL_SAVED_TREE is a BIND_EXPR
+	with DECL_INITIAL as its BLOCK.
+
+2008-10-05  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35680
+	* gfortran.h : Add 'error' bit field to gfc_expr structure.
+	* expr.c (check_inquiry): When checking a restricted expression
+	check that arguments are either variables or restricted.
+	(check_restricted): Do not emit error if the expression has
+	'error' set.  Clean up detection of host-associated variable.
+
+2008-10-05  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37638
+	* gfortran.h (struct gfc_typebound_proc): New flag `error'.
+	* resolve.c (update_arglist_pass): Added assertion.
+	(update_compcall_arglist): Fail early for erraneous procedures to avoid
+	confusion later.
+	(resolve_typebound_generic_call): Ignore erraneous specific targets
+	and added assertions.
+	(resolve_typebound_procedure): Set new `error' flag.
+
+2008-10-04  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37706
+	* module.c (load_equiv): Check the module before negating the
+	unused flag.
+
+2008-10-02  Steven Bosscher  <steven@gcc.gnu.org>
+
+	PR fortran/37635
+	* intrinsic.c (add_functions): Add LEADZ and TRAILZ as generics.
+	* intrinsic.h (gfc_simplify_leadz, gfc_simplify_trailz): New protos.
+	* gfortran.h <enum gfc_isym_id>: (GFC_ISYM_LEADZ, GFC_ISYM_TRAILZ): New.
+	* f95-lang (gfc_init_builtin_functions): Add BUILT_IN_CLZ,
+	BUILT_IN_CLZL, BUILT_IN_CLZLL, BUILT_IN_CTZ, BUILT_IN_CTZL, and
+	BUILT_IN_CTZLL.
+	* trans-intrinsic.c (gfc_conv_intrinsic_leadz,
+	gfc_conv_intrinsic_trails): New code-generation functions for LEADZ
+	and TRAILZ intrinsics.
+	(gfc_conv_intrinsic_function): Use them
+	* intrinsic.texi: Add documentation for LEADZ and TRAILZ.
+	* simplify.c (gfc_simplify_leadz, gfc_simplify_trailz): New functions.
+
+2008-09-30  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36592
+	* symbol.c (check_conflict): If a symbol in a COMMON block is a
+	procedure, it must be a procedure pointer.
+	(gfc_add_in_common): Symbols in COMMON blocks may be variables or
+	procedure pointers.
+	* trans-types.c (gfc_sym_type): Make procedure pointers in COMMON
+	blocks work.
+
+2008-09-25  Jerry DeLisle  <jvdelisle@gcc.gnu.org
+
+	PR fortran/37498
+	* trans-io.c (build_dt): Revert previous patch..
+	* ioparm.def: Delete IOPARM_dt_f2003.
+
+2008-09-25  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37504
+	* expr.c (gfc_check_pointer_assign): Allow assignment of
+	protected pointers.
+	* match.c (gfc_match_assignment,gfc_match_pointer_assignment):
+	Remove unreachable code.
+
+2008-09-24  Tobias Burnus  <burnus@net-b.de>
+
+	* options.c (set_default_std_flags,gfc_init_options):
+	Add comment: keep in sync with libgfortran.
+
+2008-09-24  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37626
+	* trans-array.c (gfc_trans_deferred_array): Don't auto-deallocate
+	result variables.
+
+2008-09-23  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37588
+	* gfortran.h (gfc_compare_actual_formal): Removed, made private.
+	(gfc_arglist_matches_symbol): New method.
+	* interface.c (compare_actual_formal): Made static.
+	(gfc_procedure_use): Use new name of compare_actual_formal.
+	(gfc_arglist_matches_symbol): New method.
+	(gfc_search_interface): Moved code partially to new
+	gfc_arglist_matches_symbol.
+	* resolve.c (resolve_typebound_generic_call): Resolve actual arglist
+	before checking against formal and use new gfc_arglist_matches_symbol
+	for checking.
+	(resolve_compcall): Set type-spec of generated expression.
+
+2008-09-23  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37580
+	* expr.c (gfc_check_pointer_assign): Add checks for pointer
+	remapping.
+
+2008-09-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org
+
+	PR fortran/37498
+	* trans-io.c (gfc_build_io_library_fndecls): Bump pad size.
+	(build_dt): Set mask bit for IOPARM_dt_f2003.
+	* ioparm.def: Add IOPARM_dt_f2003.
+
+2008-09-22  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/37486
+	* gfortran.h (gfc_option_t): New members flag_align_commons and
+	warn_align_commons. 
+	* lang.opt: New options falign-commons and Walign-commons.
+	* invoke.texi: Documentation for new options.
+	* options.c (gfc_init_options): Initialize new options.
+	(gfc_handle_options): Handle new options.
+	* trans-common.c (translate_common): Implement new options.
+	(gfc_trans_common): Set correct locus.
+
+2008-09-21  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37583
+	* decl.c (scalarize_intrinsic_call): Both subroutines and
+	functions can give a true for get_proc_mame's last argument so
+	remove the &&gfc_current_ns->proc_name->attr.function.
+	resolve.c (resolve_actual_arglist): Add check for recursion by
+	reference to procedure as actual argument.
+
+2008-09-21  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/35846
+	* trans.h (gfc_conv_string_length): New argument `expr'.
+	* trans-expr.c (flatten_array_ctors_without_strlen): New method.
+	(gfc_conv_string_length): New argument `expr' that is used in a new
+	special case handling if cl->length is NULL.
+	(gfc_conv_subref_array_arg): Pass expr to gfc_conv_string_length.
+	* trans-array.c (gfc_conv_expr_descriptor): Ditto.
+	(gfc_trans_auto_array_allocation): Pass NULL as new expr.
+	(gfc_trans_g77_array), (gfc_trans_dummy_array_bias): Ditto.
+	(gfc_trans_deferred_array): Ditto.
+	(gfc_trans_array_constructor): Save and restore old values of globals
+	used for bounds checking.
+	* trans-decl.c (gfc_trans_dummy_character): Ditto.
+	(gfc_trans_auto_character_variable): Ditto.
+
+2008-09-21  Daniel Kraft  <d@domob.eu>
+
+	* decl.c (match_procedure_in_type): Changed misleading error message
+	for not yet implemented PROCEDURE(interface) syntax.
+
+2008-09-18  Paul Thomas  <pault@gcc.gnu.org>
+
+       PR fortran/35945
+       * resolve.c (resolve_fl_variable_derived):  Remove derived type
+       comparison for use associated derived types.  Host association
+       of a derived type will not arise if there is a local derived type
+       whose use name is the same.
+
+       PR fortran/36700
+       * match.c (gfc_match_call):  Use the existing symbol even if
+       it is a function.
+
+2008-09-18  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37507
+	* trans.h (gfc_trans_runtime_error): New method.
+	(gfc_trans_runtime_error_vararg): New method.
+	(gfc_allocate_array_with_status): New argument `expr' for locus/varname.
+	(gfc_deallocate_array_with_status): Ditto.
+	* trans-array.h (gfc_array_deallocate): Ditto.
+	* trans.c (gfc_trans_runtime_error): New method.
+	(gfc_trans_runtime_error_vararg): New method, moved parts of the code
+	from gfc_trans_runtime_check here.
+	(gfc_trans_runtime_error_check): Moved code partly to new method.
+	(gfc_call_malloc): Fix tab-indentation.
+	(gfc_allocate_array_with_status): New argument `expr' and call
+	gfc_trans_runtime_error for error reporting to include locus.
+	(gfc_deallocate_with_status): Ditto.
+	* trans-stmt.c (gfc_trans_deallocate): Pass expr as new argument.
+	* trans-array.c (gfc_array_allocate): Ditto.
+	(gfc_array_deallocate): New argument `expr', passed on.
+	(gfc_trans_dealloc_allocated): Pass NULL for expr.
+	* trans-openmp.c (gfc_omp_clause_default): Ditto.
+
+2008-09-18  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37274
+	PR fortran/36374
+	* module.c (check_for_ambiguous): New function to test loaded
+	symbol for ambiguity with fixup symbol.
+	(read_module): Call check_for_ambiguous.
+	(write_symtree): Do not write the symtree for symbols coming
+	from an interface body.
+
+	PR fortran/36374
+	* resolve.c (count_specific_procs ): New function to count the
+	number of specific procedures with the same name as the generic
+	and emit appropriate errors for and actual argument reference.
+	(resolve_assumed_size_actual): Add new argument no_formal_args.
+	Correct logic around passing generic procedures as arguments.
+	Call count_specific_procs from two locations.
+	(resolve_function): Evaluate and pass no_formal_args.
+	(resolve call): The same and clean up a bit by using csym more
+	widely.
+
+	PR fortran/36454
+	* symbol.c (gfc_add_access): Access can be updated if use
+	associated and not private.
+
+2008-09-17  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/37536
+	* trans-stmt.c (gfc_trans_do): Optimize integer type non-simple
+	do loop initialization.
+
+2008-09-14  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+	    Tobias Burnus  <burnus@net.b.de>
+
+	PR fortran/35840
+	* io.c (match_vtag): Add tag name to error message.
+	(match_out_tag): Cleanup whitespace.
+	(gfc_resolve_dt): Resolve id and async tags. 
+
+2008-09-13  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/35770
+	* primary.c (gfc_match_varspec): Added missing type-spec clearing
+	after wrong implicit character typing.
+
+2008-09-12  Richard Guenther  <rguenther@suse.de>
+
+	* trans-intrinsic.c (gfc_conv_intrinsic_transfer): Use
+	build_fold_addr_expr to properly mark the argument
+	addressable.
+
+2008-09-11  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/36214
+	* simplify.c (simplify_cmplx): Added linebreak to long line.
+	* target-memory.c (gfc_convert_boz): Fix indentation.
+	(gfc_interpret_float): Set mpfr precision to right value before
+	calling mpfr_init.
+
+2008-09-10  H.J. Lu  <hongjiu.lu@intel.com>
+
+	* expr.c (find_array_element): Reformat comment.
+
+2008-09-10  H.J. Lu  <hongjiu.lu@intel.com>
+
+	* expr.c (find_array_element): Reformat.
+
+2008-09-10  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37420
+	* trans-decl.c (get_proc_pointer_decl): Fix -Wunused-variable.
+
+2008-09-09  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37429
+	* resolve.c (expression_rank): Added assertion to guard against
+	EXPR_COMPCALL expressions.
+	(resolve_compcall): Set expression's rank from the target procedure's.
+
+2008-09-09  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37411
+	* trans-array.c (gfc_conv_array_parameter): Added assertion that the
+	symbol has an array spec.
+
+2008-09-08  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37199
+	* trans-expr.c (gfc_add_interface_mapping): Set new_sym->as.
+	(gfc_map_intrinsic_function): Added checks against NULL bounds in
+	array specs.
+
+2008-09-08  Tobias Burnus  <burnus@net.b.de>
+
+	PR fortran/37400
+	* symbol.c (gfc_set_default_type): Copy char len.
+
+2008-09-06  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/36153
+	* fortran/resolve.c (resolve_function): Shortcircuit for SIZE and
+	UBOUND if 2nd argument is KIND.
+
+2008-09-06  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/33229
+	* resolve.c (resolve_function): An intrinsic subroutine should not be
+	called as a function.
+
+2008-09-05  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/35837
+	* resolve.c (resolve_types): Restore gfc_current_ns on exit.
+	* symbol.c (gfc_save_all): Removed blank line.
+
+2008-09-05  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/36746
+	* primary.c (gfc_match_rvalue): Removed logic to handle implicit
+	typing to a derived-type if a component reference is found.
+	(gfc_match_varspec): Moved it here.
+
+2008-09-04  Richard Guenther  <rguenther@suse.de>
+
+	* trans-array.c (gfc_conv_array_parameter): Use correct types
+	in building COND_EXPRs.
+	* trans-expr.c (gfc_conv_missing_dummy): Likewise.
+	* trans-intrinsics.c (gfc_conv_intrinsic_merge): Likewise.
+
+2008-09-04  Daniel Kraft  <d@domob.eu>
+
+	* PR fortran/37099
+	* expr.c (simplify_const_ref): Update expression's character length
+	when pulling out a substring reference.
+
+2008-09-04  Ian Lance Taylor  <iant@google.com>
+
+	* symbol.c (generate_isocbinding_symbol): Compare
+	gfc_notification_std with ERROR rather than FAILURE.
+	* resolve.c (check_assumed_size_reference): Compare array type
+	with AR_FULL rather than DIMEN_ELEMENT.
+	(resolve_actual_arglist): Compare with EXPR_VARIABLE rather than
+	FL_VARIABLE.
+
+2008-09-01  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/37228
+	* io.c (check_format): Allow specifying precision with g0 format.
+
+2008-09-02  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (struct gfc_namespace): New member `implicit_loc'.
+	(gfc_add_abstract): New method.
+	* decl.c (gfc_get_type_attr_spec): Match ABSTRACT attribute.
+	(gfc_match_derived_decl): Copy abstract attribute in derived symbol.
+	* dump-parse-tree.c (show_attr): Show ABSTRACT attribute as `ABSTRACT'
+	only to allow for ABSTRACT types.
+	* parse.c (parse_interface): Use new gfc_add_abstract.
+	* primary.c (gfc_match_structure_constructor): Check that no ABSTRACT
+	type is constructed.
+	* resolve.c (resolve_typespec_used): New method.
+	(resolve_fl_derived): Check type in respect to ABSTRACT attribute and
+	check that no component is of an ABSTRACT type.
+	(resolve_symbol): Check that no symbol is of an ABSTRACT type.
+	(resolve_types): Check IMPLICIT declarations for ABSTRACT types.
+	* symbol.c (gfc_merge_new_implicit): Remember loci of IMPLICIT's.
+	(gfc_add_abstract): New method.
+
+2008-09-01  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/37193
+	* module.c (read_module): Initialize use_only flag on used symbols.
+
+2008-09-01  Daniel Kraft  <d@domob.eu>
+
+	* gfc-internals.texi (F2003 OOP), (Type-bound Procedures): New chapter
+	and section to document the internals of type-bound procedures.
+	(gfc_expr): Document EXPR_COMPCALL.
+	* gfortran.h (struct gfc_expr): Remove unused `derived' from compcall.
+	* dump-parse-tree.c (show_compcall): New method.
+	(show_expr): Call it for EXPR_COMPCALL.
+	(show_typebound), (show_f2k_derived): New methods.
+	(show_symbol): Call show_f2k_derived.
+	(show_code_node): Handle EXEC_COMPCALL.
+	* primary.c (gfc_match_varspec): Don't initialize removed `derived' in
+	primary->value.compcall.
+
+2008-08-31  Richard Guenther  <rguenther@suse.de>
+
+	* trans-expr.c (gfc_trans_string_copy): Use the correct types
+	to compute slen and dlen.
+
+2008-08-31  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (enum gfc_statement): New entry `ST_GENERIC'.
+	(struct gfc_tbp_generic): New type.
+	(struct gfc_typebound_proc): Removed `target' and added union with
+	`specific' and `generic' members; new members `overridden',
+	`subroutine', `function' and `is_generic'.
+	(struct gfc_expr): New members `derived' and `name' in compcall union
+	member and changed type of `tbp' to gfc_typebound_proc.
+	(gfc_compare_interfaces), (gfc_compare_actual_formal): Made public.
+	* match.h (gfc_typebound_default_access): New global.
+	(gfc_match_generic): New method.
+	* decl.c (gfc_match_generic): New method.
+	(match_binding_attributes): New argument `generic' and handle it.
+	(match_procedure_in_type): Mark matched binding as non-generic.
+	* interface.c (gfc_compare_interfaces): Made public.
+	(gfc_compare_actual_formal): Ditto.
+	(check_interface_1), (compare_parameter): Use new public names.
+	(gfc_procedure_use), (gfc_search_interface): Ditto.
+	* match.c (match_typebound_call): Set base-symbol referenced.
+	* module.c (binding_generic): New global array.
+	(current_f2k_derived): New global.
+	(mio_typebound_proc): Handle IO of GENERIC bindings.
+	(mio_f2k_derived): Record current f2k-namespace in current_f2k_derived.
+	* parse.c (decode_statement): Handle GENERIC statement.
+	(gfc_ascii_statement): Ditto.
+	(typebound_default_access), (set_typebound_default_access): Removed.
+	(gfc_typebound_default_access): New global.
+	(parse_derived_contains): New default-access implementation and handle
+	GENERIC statements encountered.
+	* primary.c (gfc_match_varspec): Adapted to new gfc_typebound_proc
+	structure and removed check for SUBROUTINE/FUNCTION from here.
+	* resolve.c (extract_compcall_passed_object): New method.
+	(update_compcall_arglist): Use it.
+	(resolve_typebound_static): Adapted to new gfc_typebound_proc structure.
+	(resolve_typebound_generic_call): New method.
+	(resolve_typebound_call): Check target is a SUBROUTINE and handle calls
+	to GENERIC bindings.
+	(resolve_compcall): Ditto (check for target being FUNCTION).
+	(check_typebound_override): Handle GENERIC bindings.
+	(check_generic_tbp_ambiguity), (resolve_typebound_generic): New methods.
+	(resolve_typebound_procedure): Handle GENERIC bindings and set new
+	attributes subroutine, function and overridden in gfc_typebound_proc.
+	(resolve_fl_derived): Ensure extended type is resolved before the
+	extending one is.
+	* st.c (gfc_free_statement): Fix bug with free'ing EXEC_COMPCALL's.
+	* symbol.c (gfc_find_typebound_proc): Adapt for GENERIC changes.
+
+2008-08-29  Jan Hubicka  <jh@suse.cz>
+	
+	* parse.c (parse_interface): Silence uninitialized var warning.
+
+2008-08-29  Jakub Jelinek  <jakub@redhat.com>
+
+	* trans.h (struct lang_type): Add span.
+	(GFC_TYPE_ARRAY_SPAN): Define.
+	* trans-decl.c (gfc_get_symbol_decl): For subref array pointers,
+	copy TREE_STATIC from decl to span instead of setting it
+	unconditionally, set DECL_ARTIFICIAL, fix type of initializer
+	and set GFC_TYPE_ARRAY_SPAN on decl's type.
+	* trans-types.c (gfc_get_array_descr_info): If
+	GFC_TYPE_ARRAY_SPAN is non-NULL, use it as element size.
+
+	* trans-decl.c (check_constant_initializer,
+	gfc_emit_parameter_debug_info): New functions.
+	(gfc_generate_module_vars, gfc_generate_function_code): Emit
+	PARAMETERs and unreferenced variables with initializers into
+	debug info.
+
+	* gfortran.h (gfc_use_list): Add where field.
+	* module.c (use_locus): New static variable.
+	(gfc_match_use): Set it.
+	(gfc_use_module): Copy it to gfc_use_list's where field.
+	* trans-decl.c (gfc_generate_module_vars): Call gfc_trans_use_stmts.
+	(gfc_trans_use_stmts): Set backend locus before calling the debug
+	hook.  Allow non-VAR_DECLs to be created even for non-external
+	module.  Don't emit anything so far for renames from different
+	modules.
+
+	PR fortran/24790
+	* trans-decl.c (create_function_arglist): Set DECL_BY_REFERENCE on
+	PARM_DECLs with pointer or reference type.
+
+	* trans-decl.c (gfc_build_qualified_array): Build non-flat
+	array type for debug info purposes.
+
+	PR fortran/29635
+	PR fortran/23057
+	* f95-lang.c (gfc_init_ts): New function.
+	(LANG_HOOKS_INIT_TS): Define.
+	* gfortran.h (gfc_use_rename): New type, moved from module.c.
+	(gfc_get_use_rename): New macro, moved from module.c.
+	(gfc_use_list): New type.
+	(gfc_get_use_list): New macro.
+	(gfc_namespace): Add use_stmts field.
+	(gfc_free_use_stmts): New prototype.
+	* Make-lang.in (fortran/trans-decl.o): Depend on debug.h.
+	* module.c (gfc_use_rename, gfc_get_use_rename): Moved to
+	gfortran.h.
+	(gfc_use_module): Chain the USE statement info to
+	ns->use_stmts.
+	(gfc_free_use_stmts): New function.
+	* symbol.c (gfc_free_namespace): Call gfc_free_use_stmts.
+	* trans.h (struct module_htab_entry): New type.
+	(gfc_find_module, gfc_module_add_decl): New functions.
+	* trans.c (gfc_generate_module_code): Create NAMESPACE_DECL for
+	the module, adjust DECL_CONTEXTs of module procedures and
+	call gfc_module_add_decl for them.
+	* trans-common.c (build_common_decl): Set DECL_IGNORED_P
+	on the common variable.
+	(create_common): Set DECL_IGNORED_P for use associated vars.
+	* trans-decl.c: Include debug.h.
+	(gfc_get_symbol_decl): Set DECL_IGNORED_P on use_assoc vars from
+	modules.
+	(build_function_decl): Allow current_function_decl's context
+	to be a NAMESPACE_DECL.
+	(module_htab, cur_module): New variables.
+	(module_htab_do_hash, module_htab_eq, module_htab_decls_hash,
+	module_htab_decls_eq, gfc_find_module, gfc_module_add_decl): New
+	functions.
+	(gfc_create_module_variable): Adjust DECL_CONTEXTs of module
+	variables and types and call gfc_module_add_decl for them.
+	(gfc_generate_module_vars): Temporarily set cur_module.
+	(gfc_trans_use_stmts): New function.
+	(gfc_generate_function_code): Call it.
+	(gfc_generate_block_data): Set DECL_IGNORED_P on decl.
+	* trans-types.c (gfc_get_derived_type): Adjust DECL_CONTEXT
+	and TYPE_CONTEXT of module derived types.
+
+2008-08-28  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (enum expr_t): New value `EXPR_COMPCALL'.
+	(gfc_get_typebound_proc): New macro.
+	(struct gfc_expr): New union-member `compcall' for EXPR_COMPCALL.
+	(enum gfc_exec_op): New value `EXEC_COMPCALL'.
+	(gfc_find_typebound_proc): New argument.
+	(gfc_copy_ref), (gfc_match_varspec): Made public.
+	* decl.c (match_procedure_in_type): Use gfc_get_typebound_proc.
+	* expr.c (free_expr0), (gfc_copy_expr): Handle EXPR_COMPCALL.
+	(gfc_copy_ref): Made public and use new name.
+	(simplify_const_ref): Use new name of gfc_copy_ref.
+	(simplify_parameter_variable): Ditto.
+	(gfc_simplify_expr): gcc_unreachable for EXPR_COMPCALL.
+	* match.c (match_typebound_call): New method.
+	(gfc_match_call): Allow for CALL's to typebound procedures.
+	* module.c (binding_passing), (binding_overriding): New variables.
+	(expr_types): Add EXPR_COMPCALL.
+	(mio_expr): gcc_unreachable for EXPR_COMPCALL.
+	(mio_typebound_proc), (mio_typebound_symtree): New methods.
+	(mio_f2k_derived): Handle type-bound procedures.
+	* primary.c (gfc_match_varspec): Made public and parse trailing
+	references to type-bound procedures; new argument `sub_flag'.
+	(gfc_match_rvalue): New name and argument of gfc_match_varspec.
+	(match_variable): Ditto.
+	* resolve.c (update_arglist_pass): New method.
+	(update_compcall_arglist), (resolve_typebound_static): New methods.
+	(resolve_typebound_call), (resolve_compcall): New methods.
+	(gfc_resolve_expr): Handle EXPR_COMPCALL.
+	(resolve_code): Handle EXEC_COMPCALL.
+	(resolve_fl_derived): New argument to gfc_find_typebound_proc.
+	(resolve_typebound_procedure): Ditto and removed not-implemented error.
+	* st.c (gfc_free_statement): Handle EXEC_COMPCALL.
+	* symbol.c (gfc_find_typebound_proc): New argument `noaccess' and
+	implement access-checking.
+	* trans-expr.c (gfc_apply_interface_mapping_to_expr): gcc_unreachable
+	on EXPR_COMPCALL.
+	* trans-intrinsic.c (gfc_conv_intrinsic_bound): Add missing break.
+	* trans-openmp.c (gfc_trans_omp_array_reduction): Add missing
+	intialization of ref->type.
+
+2008-08-28  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/37253
+	* module.c (ab_attribute,attr_bits,mio_symbol_attribute): Take care of
+	saving attr.procedure and attr.proc_ptr to the module file.
+
+2008-08-25  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (gfc_find_component): Add new arguments.
+	* parse.c (parse_derived_contains): Check if the derived-type containing
+	the CONTAINS section is SEQUENCE/BIND(C).
+	* resolve.c (resolve_typebound_procedure): Check for name collision with
+	components.
+	(resolve_fl_derived): Check for name collision with inherited
+	type-bound procedures.
+	* symbol.c (gfc_find_component): New arguments `noaccess' and `silent'.
+	(gfc_add_component): Adapt for new arguments.
+	* primary.c (match_varspec), (gfc_match_structure_constructor): Ditto.
+
+2008-08-24  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37201
+	* decl.c (verify_bind_c_sym): Reject array/string returning
+	functions.
+
+2008-08-24  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37201
+	* trans-expr.c (gfc_conv_function_call): Add string_length
+	for character-returning bind(C) functions.
+
+2008-08-24  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (gfc_typebound_proc):  New struct.
+	(gfc_symtree):  New member typebound.
+	(gfc_find_typebound_proc):  Prototype for new method.
+	(gfc_get_derived_super_type):  Prototype for new method.
+	* parse.h (gfc_compile_state):  New state COMP_DERIVED_CONTAINS.
+	* decl.c (gfc_match_procedure):  Handle PROCEDURE inside derived-type
+	CONTAINS section.
+	(gfc_match_end):  Handle new context COMP_DERIVED_CONTAINS.
+	(gfc_match_private):  Ditto.
+	(match_binding_attributes), (match_procedure_in_type):  New methods.
+	(gfc_match_final_decl):  Rewrote to make use of new
+	COMP_DERIVED_CONTAINS parser state.
+	* parse.c (typebound_default_access):  New global helper variable.
+	(set_typebound_default_access):  New callback method.
+	(parse_derived_contains):  New method.
+	(parse_derived):  Extracted handling of CONTAINS to new parser state
+	and parse_derived_contains.
+	* resolve.c (resolve_bindings_derived), (resolve_bindings_result):  New.
+	(check_typebound_override), (resolve_typebound_procedure):  New methods.
+	(resolve_typebound_procedures):  New method.
+	(resolve_fl_derived):  Call new resolving method for typebound procs.
+	* symbol.c (gfc_new_symtree):  Initialize new member typebound to NULL.
+	(gfc_find_typebound_proc):  New method.
+	(gfc_get_derived_super_type):  New method.
+
+2008-08-23  Janus Weil  <janus@gcc.gnu.org>
+
+	* gfortran.h (gfc_component): Add field "symbol_attribute attr", remove
+	fields "pointer", "allocatable", "dimension", "access".
+	Remove functions "gfc_set_component_attr" and "gfc_get_component_attr".
+	* interface.c (gfc_compare_derived_types): Ditto.
+	* trans-array.c (gfc_array_allocate,structure_alloc_comps): Ditto.
+	* trans-expr.c (gfc_conv_component_ref,gfc_trans_subcomponent_assign,
+	gfc_conv_structure): Ditto.
+	* symbol.c (gfc_find_component,free_components,gfc_set_component_attr,
+	gfc_get_component_attr,verify_bind_c_derived_type,
+	generate_isocbinding_symbol): Ditto.
+	* decl.c (build_struct): Ditto.
+	* dump-parse-tree.c (show_components): Ditto.
+	* trans-stmt.c (gfc_trans_deallocate): Ditto.
+	* expr.c (gfc_check_assign,gfc_check_pointer_assign,
+	gfc_default_initializer): Ditto.
+	* module.c (mio_component): Ditto.
+	* trans-types.c (copy_dt_decls_ifequal,gfc_get_derived_type): Ditto.
+	* resolve.c (has_default_initializer,resolve_structure_cons,
+	gfc_iso_c_func_interface,find_array_spec,resolve_ref,
+	resolve_deallocate_expr,resolve_allocate_expr,resolve_fl_derived,
+	resolve_equivalence_derived): Ditto.
+	* trans-io.c (transfer_expr): Ditto.
+	* parse.c (parse_derived): Ditto.
+	* dependency.c (gfc_check_dependency): Ditto.
+	* primary.c (gfc_variable_attr): Ditto.
+
+2008-08-23  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37076
+	* arith.c (gfc_arith_concat): Fix concat of kind=4 strings.
+
+2008-08-23  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/37025
+	* target-memory.c (gfc_interpret_character): Support
+	kind=4 characters.
+
+2008-08-22  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/30239
+	* symbol.c (gfc_add_type): Warn on -Wsurprising if a function-result
+	type is re-declared but neither -pedantic nor -std=f* is given and so
+	this is no error.
+	* invoke.texi (-Wsurprising): Document this new behaviour.
+
+2008-08-22  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (in_prefix): Removed from this header.
+	* match.h (gfc_matching_prefix): Moved and renamed from `in_prefix'.
+	* decl.c (in_prefix): Removed from here.
+	(gfc_match_prefix): Use new name of `gfc_matching_prefix'.
+	* symbol.c (gfc_check_symbol_typed): Ditto.
+	* expr.c (check_typed_ns): New helper variable.
+	(expr_check_typed_help): New helper method.
+	(gfc_expr_check_typed): Rewrote to use gfc_traverse_expr to do the
+	work, fixing a minor problem.
+	* match.c (gfc_matching_prefix): New variable.
+
+2008-08-22  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/32095
+	PR fortran/34228
+	* gfortran.h (in_prefix): New global.
+	(gfc_check_symbol_typed), (gfc_check_expr_typed): New methods.
+	* array.c (match_array_element_spec): Check that bounds-expressions
+	don't have symbols not-yet-typed in them.
+	* decl.c (var_element): Check that variable used is already typed.
+	(char_len_param_value): Check that expression does not contain
+	not-yet-typed symbols.
+	(in_prefix): New global.
+	(gfc_match_prefix): Record using `in_prefix' if we're at the moment
+	parsing a prefix or not.
+	* expr.c (gfc_expr_check_typed): New method.
+	* parse.c (verify_st_order): New argument to disable error output.
+	(check_function_result_typed): New helper method.
+	(parse_spec): Check that the function-result declaration, if given in
+	a prefix, contains no not-yet-typed symbols when the IMPLICIT rules are
+	parsed.
+	* symbol.c (gfc_check_symbol_typed): Check that a symbol already has
+	a type associated to it, otherwise use the IMPLICIT rules or signal
+	an error.
+
+2008-08-21  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
+
+	* f95-lang.c: Update all calls to pedwarn.
+
+2008-08-18  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/37032
+	* gfortran.texi: Document decision on include file handling in
+	preprocessed files.
+
+2008-08-16  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36825
+	* libgfortran.h: Reduce GFC_MAX_DIMENSIONS to 7.
+
+2008-08-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35863
+	* io.c (gfc_match_open): Enable UTF-8 in checks.
+	* simplify.c (gfc_simplify_selected_char_kind): Enable iso_10646.
+
+2008-08-14  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36705
+	* symbol.c (check_conflict): Move conflict checks for (procedure,save)
+	and (procedure,intent) to resolve_fl_procedure.
+	* resolve.c (resolve_fl_procedure): Ditto.
+
+2008-08-09  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
+
+	PR 36901
+	* f95-lang.c (gfc_mark_addressable): Use "pedwarn (0," instead of
+	'pedwarn0'.
+
+2008-08-09  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/37011
+	* symbol.c (gfc_add_extension): New function.
+	* decl.c (gfc_get_type_attr_spec): Call it.
+	(gfc_match_derived_decl): Set symbol extension attribute from
+	attr.extension.
+	* gfortran.h : Add prototype for gfc_add_extension.
+
+2008-08-08  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
+
+	PR 28875
+	* options.c (set_Wall): Replace set_Wunused by warn_unused.
+
+2008-08-08  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h (gfc_finalizer):  Replaced member `procedure' by two
+	new members `proc_sym' and `proc_tree' to store the symtree after
+	resolution.
+	(gfc_find_sym_in_symtree):  Made public.
+	* decl.c (gfc_match_final_decl):  Adapted for new member name.
+	* interface.c (gfc_find_sym_in_symtree):  Made public.
+	(gfc_extend_expr), (gfc_extend_assign):  Changed call accordingly.
+	* module.c (mio_finalizer), (mio_f2k_derived), (mio_full_f2k_derived):
+	New methods for module-file IO of f2k_derived.
+	(mio_symbol):  Do IO of f2k_derived namespace.
+	* resolve.c (gfc_resolve_finalizers):  Adapted for new member name and
+	finding the symtree for the symbol here.
+	* symbol.c (gfc_free_finalizer):  Adapted for new members.
+
+2008-07-30  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* gfc-internals.texi: Update to GFDL 1.2.  Do not list GPL as
+	Invariant Section.
+	* gfortran.texi: Likewise.
+	* intrinsic.texi: Do not list GPL as Invariant Section.
+	* invoke.texi: Likewise.  Update copyright years.
+
+2008-07-29  Paul Thomas  <pault@gcc.gnu.org>
+
+	* trans-expr.c (conv_parent_component_references): New function
+	to build missing parent references.
+	(gfc_conv_variable): Call it
+	* symbol.c (gfc_add_component): Check that component name in a
+	derived type extension does not appear in parent.
+	(gfc_find_component): For a derived type extension, check if
+	the component appears in the parent derived type by calling
+	self. Separate errors for private components and private types.
+	* decl.c (match_data_constant): Add extra arg to call to
+	gfc_match_structure_constructor.
+	(check_extended_derived_type): New function to check that a
+	parent derived type exists and that it is OK for exension.
+	(gfc_get_type_attr_spec): Add extra argument 'name' and return
+	it if extends is specified.
+	(gfc_match_derived_decl): Match derived type extension and
+	build a first component of the parent derived type if OK. Add
+	the f2k namespace if not present.
+	* gfortran.h : Add the extension attribute.
+	* module.c : Handle attribute 'extension'.
+	* match.h : Modify prototypes for gfc_get_type_attr_spec and
+	gfc_match_structure_constructor.
+	* primary.c (build_actual_constructor): New function extracted
+	from gfc_match_structure_constructor and modified to call self
+	iteratively to build derived type extensions, when f2k named
+	components are used.
+	(gfc_match_structure_constructor): Do not throw error for too
+	many components if a parent type is being handled. Use
+	gfc_find_component to generate errors for non-existent or
+	private components.  Iteratively call self for derived type
+	extensions so that parent constructor is built.  If extension
+	and components left over, throw error.
+	(gfc_match_rvalue): Add extra arg to call to
+	gfc_match_structure_constructor.
+
+	* trans-array.c (gfc_conv_resolve_dependencies): If lhs and rhs
+	are the same symbol, aliassing does not matter.
+
+2008-07-29  Jan Hubicka  <jh@suse.cz>
+
+	* options.c (gfc_post_options): Do not set flag_no_inline.
+
+2008-07-29  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/36403
+	* trans-intrinsic.c (conv_generic_with_optional_char_arg):  New method
+	to append a string-length even if the string argument is missing, e.g.
+	for EOSHIFT.
+	(gfc_conv_intrinsic_function):  Call the new method for EOSHIFT, PACK
+	and RESHAPE.
+
+2008-07-28  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* gfortran.h (try): Remove macro.  Replace try with gfc_try
+	throughout.
+	* array.c: Likewise.
+	* check.c: Likewise.
+	* cpp.c: Likewise.
+	* cpp.h: Likewise.
+	* data.c: Likewise.
+	* data.h: Likewise.
+	* decl.c: Likewise.
+	* error.c: Likewise.
+	* expr.c: Likewise.
+	* interface.c: Likewise.
+	* intrinsic.c: Likewise.
+	* intrinsic.h: Likewise.
+	* io.c: Likewise.
+	* match.h: Likewise.
+	* parse.c: Likewise.
+	* parse.h: Likewise.
+	* resolve.c: Likewise.
+	* scanner.c: Likewise.
+	* simplify.c: Likewise.
+	* symbol.c: Likewise.
+	* trans-openmp.c: Likewise.
+	* trans-types.c: Likewise.
+
+2008-07-28  Tobias Burnus  <burnus@net-b.de>
+
+	* Make-lang.in: Remove -Wno-* from fortran-warn.
+
+2008-07-28  Richard Guenther  <rguenther@suse.de>
+
+	Merge from gimple-tuples-branch.
+
+	2008-07-18  Aldy Hernandez  <aldyh@redhat.com>
+
+	* trans-expr.c: Include gimple.h instead of tree-gimple.h.
+	* trans-array.c: Same.
+	* trans-openmp.c: Same.
+	* trans-stmt.c: Same.
+	* f95-lang.c: Same.
+	* trans-io.c: Same.
+	* trans-decl.c: Same.
+	* trans-intrinsic.c: Same.
+	* trans.c: Same.  Include tree-iterator.h.
+	* Make-lang.in (trans.o): Depend on tree-iterator.h
+
+	2008-07-14  Aldy Hernandez  <aldyh@redhat.com>
+
+	* trans-array.h (gfc_conv_descriptor_data_set_internal):
+	Rename to gfc_conv_descriptor_data_set.
+	(gfc_conv_descriptor_data_set_tuples): Remove.
+	* trans-array.c (gfc_conv_descriptor_data_get): Rename
+	from gfc_conv_descriptor_data_set_internal.
+	Remove last argument to gfc_add_modify.
+	(gfc_trans_allocate_array_storage): Rename gfc_add_modify_expr to
+	gfc_add_modify.
+	(gfc_trans_create_temp_array): Same.
+	(gfc_conv_array_transpose): Same.
+	(gfc_grow_array): Same.
+	(gfc_put_offset_into_var): Same.
+	(gfc_trans_array_ctor_element): Same.
+	(gfc_trans_array_constructor_subarray): Same.
+	(gfc_trans_array_constructor_value): Same.
+	(gfc_trans_scalarized_loop_end): Same.
+	(gfc_array_init_size): Same.
+	(gfc_array_allocate): Same.
+	(gfc_trans_array_bounds): Same.
+	(gfc_trans_auto_array_allocation): Same.
+	(gfc_trans_g77_array): Same.
+	(gfc_trans_dummy_array_bias): Same.
+	(gfc_conv_expr_descriptor): Same.
+	(structure_alloc_comps): Same.
+	* trans-expr.c: Same.
+	* trans-openmp.c (gfc_omp_clause_default_ctor): Same.
+	Rename gfc_conv_descriptor_data_set_tuples to
+	gfc_conv_descriptor_data_set.
+	(gfc_omp_clause_copy_ctor): Change build_gimple_modify_stmt to
+	build2_v.
+	(gfc_omp_clause_assign_op): Same.
+	(gfc_trans_omp_array_reduction): Rename gfc_add_modify_expr to
+	gfc_add_modify.
+	(gfc_trans_omp_atomic): Same.
+	(gfc_trans_omp_do): Same.  Change GIMPLE_MODIFY_STMT to MODIFY_EXPR.
+	Rename gfc_add_modify_stmt to gfc_add_modify.
+	* trans-stmt.c: Rename gfc_add_modify_expr to
+	gfc_add_modify.
+	* trans.c: Rename gfc_add_modify_expr to
+	gfc_add_modify.
+	(gfc_add_modify): Remove last argument.
+	Rename GIMPLE_MODIFY_STMT to MODIFY_EXPR.
+	* trans.h: Remove gfc_add_modify_expr, gfc_add_modify_stmt.
+	Add prototype for gfc_add_modify.
+	* f95-lang.c (union lang_tree_node): Rename GENERIC_NEXT to TREE_CHAIN.
+	* trans-decl.c: Rename gfc_add_modify_stmt to gfc_add_modify.
+	* trans-io.c: Same.
+	* trans-intrinsic.c: Same.
+
+	2008-02-25  Aldy Hernandez  <aldyh@redhat.com>
+
+	* Make-lang.in (fortran-warn): Add -Wno-format.
+
+	2008-02-19  Diego Novillo  <dnovillo@google.com>
+
+	http://gcc.gnu.org/ml/gcc-patches/2008-02/msg00804.html
+
+	* fortran/Make-lang.in (fortran-warn): Remove.
+
+	2007-11-22  Aldy Hernandez  <aldyh@redhat.com>
+
+	* trans-expr.c (gfc_trans_string_copy): Use "void *" when building a
+	memset.
+
+	2007-11-10  Aldy Hernandez  <aldyh@redhat.com>
+
+	* Make-lang.in (fortran-warn): Set to -Wno-format.
+	* trans.c (gfc_trans_code): Update comment to say GENERIC.
+	Call tree_annotate_all_with_locus instead of annotate_all_with_locus.
+
+2008-07-27  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36132
+	PR fortran/29952
+	PR fortran/36909
+	* trans.c (gfc_trans_runtime_check): Allow run-time warning besides
+	run-time error.
+	* trans.h (gfc_trans_runtime_check): Update declaration.
+	* trans-array.c (gfc_trans_array_ctor_element,gfc_trans_array_bound_check,
+	gfc_conv_array_ref,gfc_conv_ss_startstride,gfc_trans_dummy_array_bias):
+	Updated gfc_trans_runtime_check calls.
+	(gfc_conv_array_parameter): Implement flag_check_array_temporaries,
+	fix packing/unpacking for nonpresent optional actuals to optional
+	formals.
+	* trans-array.h (gfc_conv_array_parameter): Update declaration.
+	* trans-expr.c (gfc_conv_substring,gfc_trans_arrayfunc_assign,
+	gfc_conv_function_call): Updated gfc_trans_runtime_check calls.
+	(gfc_conv_function_call): Update gfc_conv_array_parameter calls.
+	* trans-expr.c (gfc_trans_goto): Updated gfc_trans_runtime_check
+	calls.
+	* trans-io.c (set_string,gfc_conv_intrinsic_repeat): Ditto.
+	(gfc_conv_intrinsic_transfer,gfc_conv_intrinsic_loc): Same for
+	gfc_conv_array_parameter.
+	* trans-intrinsics.c (gfc_conv_intrinsic_bound): Ditto.
+	* trans-decl.c (gfc_build_builtin_function_decls): Add
+	gfor_fndecl_runtime_warning_at.
+	* lang.opt: New option fcheck-array-temporaries.
+	* gfortran.h (gfc_options): New flag_check_array_temporaries.
+	* options.c (gfc_init_options, gfc_handle_option): Handle flag.
+	* invoke.texi: New option fcheck-array-temporaries.
+
+2008-07-24  Jan Hubicka  <jh@suse.cz>
+
+	* fortran/options.c (gfc_post_options): Remove flag_unline_trees code.
+
+2008-07-24  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/33141
+	* lang.opt (Wnonstd-intrinsics):  Removed option.
+	(Wintrinsics-std), (Wintrinsic-shadow):  New options.
+	* invoke.texi (Option Summary):  Removed -Wnonstd-intrinsics
+	from the list and added -Wintrinsics-std and -Wintrinsic-shadow.
+	(Error and Warning Options):  Documented the new options and removed
+	the documentation for -Wnonstd-intrinsics.
+	* gfortran.h (gfc_option_t):  New members warn_intrinsic_shadow and
+	warn_intrinsics_std, removed warn_nonstd_intrinsics.
+	(gfc_is_intrinsic):  Renamed from gfc_intrinsic_name.
+	(gfc_warn_intrinsic_shadow), (gfc_check_intrinsic_standard):  New.
+	* decl.c (match_procedure_decl):  Replaced gfc_intrinsic_name by
+	the new name gfc_is_intrinsic.
+	(warn_intrinsic_shadow):  New helper method.
+	(gfc_match_function_decl), (gfc_match_subroutine):  Call the new method
+	warn_intrinsic_shadow to check the just-parsed procedure.
+	* expr.c (check_init_expr):  Call new gfc_is_intrinsic to check whether
+	the function called is really an intrinsic in the selected standard.
+	* intrinsic.c (gfc_is_intrinsic):  Renamed from gfc_intrinsic_name and
+	extended to take into account the selected standard settings when trying
+	to find out whether a symbol is an intrinsic or not.
+	(gfc_check_intrinsic_standard):  Made public and extended.
+	(gfc_intrinsic_func_interface), (gfc_intrinsic_sub_interface):  Removed
+	the calls to check_intrinsic_standard, this check now happens inside
+	gfc_is_intrinsic.
+	(gfc_warn_intrinsic_shadow):  New method defined.
+	* options.c (gfc_init_options):  Initialize new warning flags to false
+	and removed intialization of Wnonstd-intrinsics flag.
+	(gfc_post_options):  Removed logic for Wnonstd-intrinsics flag.
+	(set_Wall):  Set new warning flags and removed Wnonstd-intrinsics flag.
+	(gfc_handle_option):  Handle the new flags and removed handling of the
+	old Wnonstd-intrinsics flag.
+	* primary.c (gfc_match_rvalue):  Replaced call to gfc_intrinsic_name by
+	the new name gfc_is_intrinsic.
+	* resolve.c (resolve_actual_arglist):  Ditto.
+	(resolve_generic_f), (resolve_unknown_f):  Ditto.
+	(is_external_proc):  Ditto.
+	(resolve_generic_s), (resolve_unknown_s):  Ditto.
+	(resolve_symbol):  Ditto and ensure for symbols declared INTRINSIC that
+	they are really available in the selected standard setting.
+
+2008-07-24  Daniel Kraft  <d@domob.eu>
+
+	* match.c (gfc_match):  Add assertion to catch wrong calls trying to
+	match upper-case characters.
+
+2008-07-24  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/29952
+	* gfortran.h:  Add "warn_array_temp" to gfc_option_t.
+	* lang.opt:  Add -Warray-temporaries.
+	* invoke.texi:  Document -Warray-temporaries
+	* trans-array.h (gfc_trans_create_temp_array):  Add argument of
+	type *locus.
+	(gfc_conv_loop_setup):  Likewise.
+	* trans-array.c (gfc_trans_create_temp_array):  If
+	-Warray-temporaries is given and locus is present, warn about
+	creation of array temporaries.
+	(gfc_trans_array_constructor_subarray):  Add locus to call
+	of gfc_conv_loop_setup.
+	(gfc_trans_array_constructor):  Add where argument.  Pass where
+	argument to call of gfc_trans_create_temp_array.
+	(gfc_add_loop_ss_code):  Add where argument.  Pass where argument
+	to recursive call of gfc_add_loop_ss_code and to call of
+	gfc_trans_array_constructor.
+	(gfc_conv_loop_setup):  Add where argument.  Pass where argument
+	to calls to gfc_add_loop_ss_code and to gfc_trans_create_temp_array.
+	(gfc_conv_expr_descriptor):  Pass location to call of
+	gfc_conv_loop_setup.
+	(gfc_conv_array_parameter):  If -Warray-temporaries is given,
+	warn about creation of temporary arrays.
+	* trans-expr.c (gfc_conv_subref_array_arg):  Add where argument
+	to call to gfc_conv_loop_setup.
+	(gfc_conv_function_call):  Add where argument to call to
+	gfc_trans_creat_temp_array.
+	(gfc_trans_subarray_assign):  Likewise.
+	(gfc_trans_assignment_1):  Add where argument to call to
+	gfc_conv_loop_setup.
+	* trans-stmt.c (gfc_conv_elemental_dependencies):  Add where
+	argument to call to gfc_trans_create_temp_array.
+	(gfc_trans_call):  Add where argument to call to gfc_conv_loop_setup.
+	(generate_loop_for_temp_to_lhs):  Likewise.
+	(generate_loop_for_rhs_to_temp):  Likewise.
+	(compute_inner_temp_size):  Likewise.
+	(gfc_trans-pointer_assign_need_temp):  Likewise.
+	(gfc_evaluate_where_mask):  Likewise.
+	(gfc_trans_where_assign):  Likewise.
+	(gfc_trans_where_3):  Likewise.
+	* trans-io.c (transfer_srray_component):  Add where argument
+	to function. Add where argument to call to gfc_conv_loop_setup.
+	(transfer_expr):  Add where argument to call to
+	transfer_array_component.
+	(gfc_trans_transfer):  Add where expression to call to
+	gfc_conv_loop_setup.
+	* trans-intrinsic.c (gfc_conv_intrinsic_anyall):  Add
+	where argument to call to gfc_conv_loop_setup.
+	(gfc_conv_intrinsic_count):  Likewise.
+	(gfc_conv_intrinsic_arith):  Likewise.
+	(gfc_conv_intrinsic_dot_product):  Likewise.
+	(gfc_conv_intrinsic_minmaxloc):  Likewise.
+	(gfc_conv_intrinsic_minmaxval):  Likewise.
+	(gfc_conv_intrinsic_array_transfer):  Warn about
+	creation of temporary array.
+	Add where argument to call to gfc_trans_create_temp_array.
+	* options.c (gfc_init_options):  Initialize gfc_option.warn_array_temp.
+	(gfc_handle_option):  Set gfc_option.warn_array_temp.
+
+2008-07-23  Manuel Lopez-Ibanez  <manu@gcc.gnu.org>
+
+	PR 35058
+	* f95-lang.c (gfc_mark_addressable): All calls to pedwarn changed.
+
+2008-07-22  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/29835
+	* io.c (error_element), (format_locus):  New static globals.
+	(unexpected_element):  Spelled out this message fully.
+	(next_char):  Keep track of locus when not MODE_STRING.
+	(next_char_not_space):  Remember last parsed element in error_element.
+	(format_lex):  Fix two indentation errors.
+	(check_format):  Use format_locus and possibly error_element for a
+	slightly better error message on invalid format.
+	(check_format_string):  Set format_locus to start of the string
+	expression used as format.
+
+2008-07-21  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* expr.c (gfc_check_pointer_assign): Fix typo in string.
+	* io.c (check_format): Fix typo in string.  Fix comment typos.
+	* parse.c (gfc_global_used): Likewise.
+	* resolve.c (resolve_allocate_expr): Likewise.
+	* symbol.c (gfc_set_default_type): Likewise.
+	* arith.c: Fix typos in comments.
+	* array.c: Likewise.
+	* data.c: Likewise.
+	* decl.c: Likewise.
+	* dependency.c: Likewise.
+	* f95-lang.c: Likewise.
+	* gfortran.h: Likewise.
+	* matchexp.c: Likewise.
+	* module.c: Likewise.
+	* primary.c: Likewise.
+	* scanner.c: Likewise.
+	* trans-array.c: Likewise.
+	* trans-common.c: Likewise.
+	* trans-decl.c: Likewise.
+	* trans-expr.c: Likewise.
+	* trans-intrinsic.c: Likewise.
+	* trans-types.c: Likewise.
+	* trans.c: Likewise.
+	* trans.h: Likewise.
+
+2008-07-19  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36795
+	* matchexp.c (gfc_get_parentheses): Remove obsolete workaround,
+	which caused the generation of wrong code.
+
+2008-07-19  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36342
+	* scanner.c (load_file): Add argument to destinguish between
+	true filename and displayed filename.
+	(include_line,gfc_new_file): Adapt accordingly.
+
+2008-07-19  Tobias Burnus  <burnus@net-b.de>
+
+	* check.c (gfc_check_cshift,gfc_check_eoshift,gfc_check_unpack): Add rank
+	checks for cshift's shift and eoshift's shift and boundary args.
+	(gfc_check_unpack): Add rank and shape tests for unpack.
+
+2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* gfortran.h (new): Remove macro.
+	* array.c (gfc_append_constructor, match_array_list,
+	gfc_match_array_constructor): Likewise.
+	* bbt.c (insert, gfc_insert_bbt): Likewise.
+	* decl.c (var_element, top_var_list, top_val_list, gfc_match_data,
+	get_proc_name): Likewise.
+	* expr.c (gfc_copy_actual_arglist): Likewise.
+	* interface.c (compare_actual_formal, check_new_interface,
+	gfc_add_interface): Likewise.
+	* intrinsic.c gfc_convert_type_warn, gfc_convert_chartype):
+	Likewise.
+	* io.c (match_io_iterator, match_io_list): Likewise.
+	* match.c (match_forall_header): Likewise.
+	* matchexp.c (build_node): Likewise.
+	* module.c (gfc_match_use): Likewise.
+	* scanner.c (load_file): Likewise.
+	* st.c (gfc_append_code): Likewise.
+	* symbol.c (save_symbol_data, gfc_get_sym_tree, gfc_undo_symbols,
+	gfc_commit_symbols): Likewise.
+	* trans-common.c (build_field): Likewise.
+	* trans-decl.c (gfc_finish_var_decl): Likewise.
+	* trans-expr.c (gfc_free_interface_mapping,
+	gfc_get_interface_mapping_charlen, gfc_add_interface_mapping,
+	gfc_finish_interface_mapping,
+	gfc_apply_interface_mapping_to_expr): Likewise.
+	* trans.h (gfc_interface_sym_mapping): Likewise.
+
+2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* gfortran.h (operator): Remove macro.
+	(gfc_namespace, gfc_expr): Avoid C++ keywords.
+	* arith.c (eval_intrinsic, eval_intrinsic_f2, eval_intrinsic_f3):
+	Likewise.
+	* decl.c (access_attr_decl): Likewise.
+	* dependency.c (gfc_dep_compare_expr): Likewise.
+	* dump-parse-tree.c (show_expr, show_uop, show_namespace):
+	Likewise.
+	* expr.c (gfc_copy_expr, gfc_type_convert_binary,
+	simplify_intrinsic_op, check_intrinsic_op): Likewise.
+	* interface.c (fold_unary, gfc_match_generic_spec,
+	gfc_match_interface, gfc_match_end_interface,
+	check_operator_interface, check_uop_interfaces,
+	gfc_check_interfaces, gfc_extend_expr, gfc_extend_assign,
+	gfc_add_interface, gfc_current_interface_head,
+	gfc_set_current_interface_head): Likewise.
+	* iresolve.c (gfc_resolve_dot_product, gfc_resolve_matmul):
+	Likewise.
+	* matchexp.c (gfc_get_parentheses, build_node): Likewise.
+	* module.c (gfc_use_rename, gfc_match_use, find_use_name_n,
+	number_use_names, mio_expr, load_operator_interfaces, read_module,
+	write_operator, write_module): Likewise.
+	* openmp.c (resolve_omp_atomic): Likewise.
+	* resolve.c (resolve_operator, gfc_resolve_character_operator,
+	gfc_resolve_uops): Likewise.
+	* symbol.c (free_uop_tree, gfc_free_namespace): Likewise.
+	* trans-expr.c (gfc_conv_expr_op): Likewise.
+	* trans-openmp.c (gfc_trans_omp_atomic): Likewise.
+
+2008-07-19  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* gfortran.h (protected): Remove macro.
+	* dump-parse-tree.c (show_attr): Avoid C++ keywords.
+	* expr.c (gfc_check_pointer_assign): Likewise.
+	* interface.c (compare_parameter_protected): Likewise.
+	* intrinsic.c (enum class, add_sym, add_sym_0, add_sym_1,
+	add_sym_1s, add_sym_1m, add_sym_2, add_sym_2s, add_sym_3,
+	add_sym_3ml, add_sym_3red, add_sym_3s, add_sym_4, add_sym_4s,
+	add_sym_5s): Likewise.
+	* match.c (gfc_match_assignment, gfc_match_pointer_assignment):
+	Likewise.
+	* module.c (mio_symbol_attribute): Likewise.
+	* primary.c (match_variable): Likewise.
+	* resolve.c (resolve_equivalence): Likewise.
+	* symbol.c (check_conflict, gfc_add_protected, gfc_copy_attr):
+	Likewise.
+	* trans-types.c (gfc_get_array_type_bounds): Likewise.
+
+2008-07-18  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* arith.c (eval_type_intrinsic0): Avoid C++ keywords.
+	* gfortran.h (try, protected, operator, new): Likewise.
+
+2008-07-17  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36825
+	PR fortran/36824
+	* array.c (gfc_match_array_spec): Fix array-rank check.
+	* resolve.c (resolve_fl_derived): Fix constentness check
+	for the array dimensions.
+
+2008-07-14  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* Make-lang.in (gfortranspec.o): Fix dependencies.
+
+2008-07-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/36725
+	* io.c: Add error check for g0 edit descriptor followed by '.'.
+
+2008-07-12  Daniel Kraft  <d@domob.eu>
+
+	* resolve.c (resolve_fl_derived):  Allow pointer components to empty
+	derived types fixing a missing part of PR fortran/33221.
+
+2008-07-10  Daniel Kraft  <d@domob.eu>
+
+	* gfc-internals.texi (section gfc_expr):  Created documentation about
+	the gfc_expr internal data structure.
+
+2008-07-07  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/36670
+	* iresolve.c (gfc_resolve_product):  Set shape of return
+	value from array.
+	(gfc_resolve_sum):  Likewise.
+
+2008-07-07  Jakub Jelinek  <jakub@redhat.com>
+
+	PR middle-end/36726
+	* f95-lang.c (poplevel): Don't ever add subblocks to
+	global_binding_level.
+
+2008-07-02  Janus Weil  <janus@gcc.gnu.org>
+	    Tobias Burnus  <burnus@net-b.de>
+	    Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/32580
+	* gfortran.h (struct gfc_symbol): New member "proc_pointer".
+	* check.c (gfc_check_associated,gfc_check_null): Implement
+	procedure pointers.
+	* decl.c (match_procedure_decl): Ditto.
+	* expr.c (gfc_check_pointer_assign,gfc_check_assign_symbol): Ditto.
+	* interface.c (compare_actual_formal): Ditto.
+	* match.h: Ditto.
+	* match.c (gfc_match_pointer_assignment): Ditto.
+	* parse.c (parse_interface): Ditto.
+	* primary.c (gfc_match_rvalue,match_variable): Ditto.
+	* resolve.c (resolve_fl_procedure): Ditto.
+	* symbol.c (check_conflict,gfc_add_external,gfc_add_pointer,
+	gfc_copy_attr,gen_fptr_param,build_formal_args): Ditto.
+	* trans-decl.c (get_proc_pointer_decl,gfc_get_extern_function_decl,
+	create_function_arglist): Ditto.
+	* trans-expr.c (gfc_conv_variable,gfc_conv_function_val,
+	gfc_conv_function_call,gfc_trans_pointer_assignment): Ditto.
+
+2008-07-02  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/36590
+	PR fortran/36681
+	* iresolve.c (resolve_mask_arg):  Don't convert mask to
+	kind=1 logical if it is of that type already.
+
+2008-06-29  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/36341
+	* iresolve.c (gfc_resolve_matmul): Copy shapes
+	from arguments.
+
+2008-06-29  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	* invoke.texi: Add documentation for runtime behavior of
+	-fno-range-check.
+
+2008-06-28  Daniel Kraft  <d@domob.eu>
+
+	* gfc-internals.texi (section gfc_code):  Extended documentation about
+	gfc_code in the internal datastructures chapter including details about
+	how IF, DO and SELECT blocks look like and an example for how the
+	block-chaining works.
+
+2008-06-25  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/36526
+	* interface.c (check_intents):  Correct error where the actual
+	arg was checked for a pointer argument, rather than the formal.
+
+2008-06-24  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34371
+	* expr.c (gfc_check_assign):  Change message and locus for
+	error when conform == 0.
+
+2008-06-23  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/36597
+	* cpp.c (cpp_define_builtins): Change _OPENMP value to 200805.
+
+2008-06-20  Laurynas Biveinis  <laurynas.biveinis@gmail.com>
+	    Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34908
+	PR fortran/36276
+	* scanner.c (preprocessor_line): do not call gfc_free for
+	current_file->filename if it differs from filename.
+
+2008-06-20  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	* arith.c (hollerith2representation): Fix for -Wc++-compat.
+	* array.c (gfc_get_constructor): Likewise.
+	* decl.c (gfc_get_data_variable, gfc_get_data_value, gfc_get_data,
+	create_enum_history, gfc_match_final_decl): Likewise.
+	* error.c (error_char): Likewise.
+	* expr.c (gfc_get_expr, gfc_copy_expr): Likewise.
+	* gfortran.h (gfc_get_charlen, gfc_get_array_spec,
+	gfc_get_component, gfc_get_formal_arglist, gfc_get_actual_arglist,
+	gfc_get_namelist, gfc_get_omp_clauses, gfc_get_interface,
+	gfc_get_common_head, gfc_get_dt_list, gfc_get_array_ref,
+	gfc_get_ref, gfc_get_equiv, gfc_get_case, gfc_get_iterator,
+	gfc_get_alloc, gfc_get_wide_string): Likewise.
+	* interface.c (count_types_test): Likewise.
+	* intrinsic.c (add_char_conversions, gfc_intrinsic_init_1):
+	Likewise.
+	* io.c (gfc_match_open, gfc_match_close, match_filepos, match_io,
+	gfc_match_inquire, gfc_match_wait): Likewise.
+	* match.c (gfc_match, match_forall_iterator): Likewise.
+	* module.c (gfc_get_pointer_info, gfc_get_use_rename, add_fixup,
+	add_true_name, parse_string, write_atom, quote_string,
+	mio_symtree_ref, mio_gmp_real, write_common_0): Likewise.
+	* options.c (gfc_post_options): Likewise.
+	* primary.c (match_integer_constant, match_hollerith_constant,
+	match_boz_constant, match_real_constant,
+	gfc_get_structure_ctor_component, gfc_match_structure_constructor): Likewise.
+	* scanner.c (gfc_widechar_to_char, add_path_to_list,
+	add_file_change, load_line, get_file, preprocessor_line,
+	load_file, unescape_filename, gfc_read_orig_filename): Likewise.
+	* simplify.c (gfc_simplify_ibits, gfc_simplify_ishft,
+	gfc_simplify_ishftc): Likewise.
+	* symbol.c (gfc_get_st_label, gfc_get_namespace, gfc_new_symtree,
+	gfc_get_uop, gfc_new_symbol, save_symbol_data, gfc_get_gsymbol):
+	Likewise.
+	* target-memory.c (gfc_target_interpret_expr): Likewise.
+	* trans-const.c (gfc_build_wide_string_const): Likewise.
+	* trans-expr.c (gfc_add_interface_mapping): Likewise.
+	* trans-intrinsic.c (gfc_conv_intrinsic_conversion,
+	gfc_conv_intrinsic_int, gfc_conv_intrinsic_lib_function,
+	gfc_conv_intrinsic_cmplx, gfc_conv_intrinsic_ctime,
+	gfc_conv_intrinsic_fdate, gfc_conv_intrinsic_ttynam,
+	gfc_conv_intrinsic_minmax, gfc_conv_intrinsic_minmax_char,
+	gfc_conv_intrinsic_ishftc, gfc_conv_intrinsic_index_scan_verify,
+	gfc_conv_intrinsic_merge, gfc_conv_intrinsic_trim): Likewise.
+	* trans.c (gfc_get_backend_locus): Likewise.
+	* trans.h (gfc_get_ss): Likewise.
+
+2008-06-18  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/36517, fortran/36492
+	* array.c (gfc_resolve_character_array_constructor):  Call
+	gfc_set_constant_character_len with changed length-chec argument.
+	* decl.c (gfc_set_constant_character_len):  Changed array argument to
+	be a generic length-checking argument that can be used for correct
+	checking with typespec and in special cases where the should-be length
+	is different from the target length.
+	(build_struct):  Call gfc_set_constant_character_len with changed length
+	checking argument and introduced additional checks for exceptional
+	conditions on invalid code.
+	(add_init_expr_to_sym), (do_parm):  Call gfc_set_constant_character_len
+	with changed argument.
+	* match.h (gfc_set_constant_character_len):  Changed third argument to
+	int for the should-be length rather than bool.
+
+2008-06-17  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/36112
+	* array.c (gfc_resolve_character_array_constructor):  Check that all
+	elements with constant character length have the same one rather than
+	fixing it if no typespec is given, emit an error if they don't.  Changed
+	return type to "try" and return FAILURE for the case above.
+	(gfc_resolve_array_constructor):  Removed unneeded call to
+	gfc_resolve_character_array_constructor in this function.
+	* gfortran.h (gfc_resolve_character_array_constructor):  Returns try.
+	* trans-array.c (get_array_ctor_strlen):  Return length of first element
+	rather than last element.
+	* resolve.c (gfc_resolve_expr):  Handle FAILURE return from
+	gfc_resolve_character_array_constructor.
+
+2008-06-17  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34396
+	* resolve.c (add_dt_to_dt_list):  New function.
+	(resolve_fl_derived): Call new function for pointer components
+	and when derived type resolved.
+
+2008-06-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/36515
+	* trans-decl.c (gfc_generate_function_code): Add range_check to options
+	array.
+
+2008-06-15  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* gfc-internals.texi: Expand TABs, drop indentation outside examples.
+	* gfortran.texi: Likewise.
+	* intrinsic.texi: Likewise.
+	* invoke.texi: Likewise.
+
+2008-06-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35863
+	* trans-io.c (gfc_build_io_library_fndecls): Build declaration for
+	transfer_character_wide which includes passing in the character kind to
+	support wide character IO. (transfer_expr): If the kind == 4, create the
+	argument and build the call.
+	* gfortran.texi: Fix typo.
+
+2008-06-13  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36476
+	* decl.c (do_parm): Handle init expression for len=*.
+
+2008-06-12  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36462
+	* trans-intrinsic.c (gfc_conv_intrinsic_index_scan_verify):
+	Fix passing of the BACK= argument.
+
+2008-06-10  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	* cpp.c: Add copyright notice.
+	* cpp.h: Add copyright notice.
+
+2008-06-08  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36459
+	* decl.c (match_procedure_decl): Correctly recognize if the interface
+	is an intrinsic procedure.
+
+2008-06-08  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/35830
+	* resolve.c (resolve_symbol): Copy more attributes for
+	PROCEDUREs with interfaces.
+
+2008-06-07  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/36420
+	PR fortran/36422
+	* io.c (check_format): Add new error message for zero width.
+	Use new	error message for FMT_A and with READ, FMT_G.  Allow
+	FMT_G with WRITE except when -std=F95 and -std=F2003.
+
+2008-06-07  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36437
+	* intrinsic.c (add_functions): Implement c_sizeof.
+	* trans-intrinsic.c (gfc_conv_intrinsic_sizeof): Do not
+	create unneeded variable in the scalar case.
+	* intrinsic.texi: Add C_SIZEOF documentation.
+
+2008-06-06  Tobias Burnus  <burnus@net-b.de>
+
+	* intrinsic.texi (BESSEL_J1): Fix BES(S)EL_J1 typo.
+
+2008-06-06  Jakub Jelinek  <jakub@redhat.com>
+
+	* scanner.c (skip_free_comments, skip_fixed_comments): Handle tabs.
+	* parse.c (next_free): Allow tab after !$omp.
+	(decode_omp_directive): Handle !$omp task, !$omp taskwait
+	and !$omp end task.
+	(case_executable): Add ST_OMP_TASKWAIT.
+	(case_exec_markers): Add ST_OMP_TASK.
+	(gfc_ascii_statement): Handle ST_OMP_TASK, ST_OMP_END_TASK and
+	ST_OMP_TASKWAIT.
+	(parse_omp_structured_block, parse_executable): Handle ST_OMP_TASK.
+	* gfortran.h (gfc_find_sym_in_expr): New prototype.
+	(gfc_statement): Add ST_OMP_TASK, ST_OMP_END_TASK and ST_OMP_TASKWAIT.
+	(gfc_omp_clauses): Add OMP_SCHED_AUTO to sched_kind,
+	OMP_DEFAULT_FIRSTPRIVATE to default_sharing.  Add collapse and
+	untied fields.
+	(gfc_exec_op): Add EXEC_OMP_TASK and EXEC_OMP_TASKWAIT.
+	* f95-lang.c (LANG_HOOKS_OMP_CLAUSE_COPY_CTOR,
+	LANG_HOOKS_OMP_CLAUSE_ASSIGN_OP, LANG_HOOKS_OMP_CLAUSE_DTOR,
+	LANG_HOOKS_OMP_PRIVATE_OUTER_REF): Define.
+	* trans.h (gfc_omp_clause_default_ctor): Add another argument.
+	(gfc_omp_clause_copy_ctor, gfc_omp_clause_assign_op,
+	gfc_omp_clause_dtor, gfc_omp_private_outer_ref): New prototypes.
+	* types.def (BT_ULONGLONG, BT_PTR_ULONGLONG,
+	BT_FN_BOOL_ULONGLONGPTR_ULONGLONGPTR,
+	BT_FN_BOOL_BOOL_ULL_ULL_ULL_ULLPTR_ULLPTR,
+	BT_FN_BOOL_BOOL_ULL_ULL_ULL_ULL_ULLPTR_ULLPTR,
+	BT_FN_VOID_PTR_PTR, BT_PTR_FN_VOID_PTR_PTR,
+	BT_FN_VOID_OMPFN_PTR_OMPCPYFN_LONG_LONG_BOOL_UINT): New.
+	(BT_BOOL): Use integer type with BOOL_TYPE_SIZE rather
+	than boolean_type_node.
+	* dump-parse-tree.c (gfc_show_omp_node): Handle EXEC_OMP_TASK,
+	EXEC_OMP_TASKWAIT, OMP_SCHED_AUTO, OMP_DEFAULT_FIRSTPRIVATE,
+	untied and collapse clauses.
+	(gfc_show_code_node): Handle EXEC_OMP_TASK and EXEC_OMP_TASKWAIT.
+	* trans.c (gfc_trans_code): Handle EXEC_OMP_TASK and
+	EXEC_OMP_TASKWAIT.
+	* st.c (gfc_free_statement): Likewise.
+	* resolve.c (gfc_resolve_blocks, resolve_code): Likewise.
+	(find_sym_in_expr): Rename to...
+	(gfc_find_sym_in_expr): ... this.  No longer static.
+	(resolve_allocate_expr, resolve_ordinary_assign): Adjust caller.
+	* match.h (gfc_match_omp_task, gfc_match_omp_taskwait): New
+	prototypes.
+	* openmp.c (resolve_omp_clauses): Allow allocatable arrays in
+	firstprivate, lastprivate, reduction, copyprivate and copyin
+	clauses.
+	(omp_current_do_code): Made static.
+	(omp_current_do_collapse): New variable.
+	(gfc_resolve_omp_do_blocks): Compute omp_current_do_collapse,
+	clear omp_current_do_code and omp_current_do_collapse on return.
+	(gfc_resolve_do_iterator): Handle collapsed do loops.
+	(resolve_omp_do): Likewise, diagnose errorneous collapsed do loops.
+	(OMP_CLAUSE_COLLAPSE, OMP_CLAUSE_UNTIED): Define.
+	(gfc_match_omp_clauses): Handle default (firstprivate),
+	schedule (auto), untied and collapse (n) clauses.
+	(OMP_DO_CLAUSES): Add OMP_CLAUSE_COLLAPSE.
+	(OMP_TASK_CLAUSES): Define.
+	(gfc_match_omp_task, gfc_match_omp_taskwait): New functions.
+	* trans-openmp.c (gfc_omp_private_outer_ref): New function.
+	(gfc_omp_clause_default_ctor): Add outer argument.  For allocatable
+	arrays allocate them with the bounds of the outer var if outer
+	var is allocated.
+	(gfc_omp_clause_copy_ctor, gfc_omp_clause_assign_op,
+	gfc_omp_clause_dtor): New functions.
+	(gfc_trans_omp_array_reduction): If decl is allocatable array,
+	allocate it with outer var's bounds in OMP_CLAUSE_REDUCTION_INIT
+	and deallocate it in OMP_CLAUSE_REDUCTION_MERGE.
+	(gfc_omp_predetermined_sharing): Return OMP_CLAUSE_DEFAULT_SHARED
+	for assumed-size arrays.
+	(gfc_trans_omp_do): Add par_clauses argument.  If dovar is
+	present in lastprivate clause and do loop isn't simple,
+	set OMP_CLAUSE_LASTPRIVATE_STMT.  If dovar is present in
+	parallel's lastprivate clause, change it to shared and add
+	lastprivate clause to OMP_FOR_CLAUSES.  Handle collapsed do loops.
+	(gfc_trans_omp_directive): Adjust gfc_trans_omp_do callers.
+	(gfc_trans_omp_parallel_do): Likewise.  Move collapse clause to
+	OMP_FOR from OMP_PARALLEL.
+	(gfc_trans_omp_clauses): Handle OMP_SCHED_AUTO,
+	OMP_DEFAULT_FIRSTPRIVATE, untied and collapse clauses.
+	(gfc_trans_omp_task, gfc_trans_omp_taskwait): New functions.
+	(gfc_trans_omp_directive): Handle EXEC_OMP_TASK and
+	EXEC_OMP_TASKWAIT.
+
+2008-06-04  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36322
+	PR fortran/36275
+	* resolve.c (resolve_symbol): Correctly copy the interface for a
+	PROCEDURE declaration.
+
+2008-06-02  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36361
+	* symbol.c (gfc_add_allocatable,gfc_add_dimension,
+	gfc_add_explicit_interface): Added checks.
+	* decl.c (attr_decl1): Added missing "var_locus".
+	* parse.c (parse_interface): Checking for errors.
+
+2008-06-02  Daniel Kraft  <d@domob.eu>
+
+	* gfortran.h:  New statement-type ST_FINAL for FINAL declarations.
+	(struct gfc_symbol):  New member f2k_derived.
+	(struct gfc_namespace):  New member finalizers, for use in the above
+	mentioned f2k_derived namespace.
+	(struct gfc_finalizer):  New type defined for finalizers linked list.
+	* match.h (gfc_match_final_decl):  New function header.
+	* decl.c (gfc_match_derived_decl):  Create f2k_derived namespace on
+	constructed symbol node.
+	(gfc_match_final_decl):  New function to match a FINAL declaration line.
+	* parse.c (decode_statement):  match-call for keyword FINAL.
+	(parse_derived):  Parse CONTAINS section and accept FINAL statements.
+	* resolve.c (gfc_resolve_finalizers):  New function to resolve (that is
+	in this case, check) a list of finalizer procedures.
+	(resolve_fl_derived):  Call gfc_resolve_finalizers here.
+	* symbol.c (gfc_get_namespace):  Initialize new finalizers to NULL.
+	(gfc_free_namespace):  Free finalizers list.
+	(gfc_new_symbol):  Initialize new f2k_derived to NULL.
+	(gfc_free_symbol):  Free f2k_derived namespace.
+	(gfc_free_finalizer):  New function to free a single gfc_finalizer node.
+	(gfc_free_finalizer_list):  New function to free a linked list of
+	gfc_finalizer nodes.
+
+2008-06-02  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/36375
+	PR fortran/36377
+	* cpp.c (gfc_cpp_init): Do not initialize builtins if
+	processing already preprocessed input.
+	(gfc_cpp_preprocess): Finalize output with newline.
+
+2008-05-31  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	* intrinsic.texi: Revert wrong commit.
+
+2008-05-31  Steven G. Kargl  <kargls@comcast.net>
+
+	* arith.c (gfc_arith_init_1): Remove now unused r and c variables.
+	Cleanup numerical inquiry function initialization.
+	(gfc_arith_done_1): Replace multiple mpfr_clear() invocations with
+	a single mpfr_clears().
+	(gfc_check_real_range): Re-arrange logic to eliminate multiple
+	unnecessary branching and assignments.
+	(gfc_arith_times): Use mpfr_clears() in preference to multiple
+	mpfr_clear().
+	(gfc_arith_divide): Ditto.
+	(complex_reciprocal): Eliminate now unused variables a, re, im.
+	Cleanup the mpfr abuse.  Use mpfr_clears() in preference to
+	multiple mpfr_clear().
+	(complex_pow): Fix comment whitespace.  Use mpfr_clears() in
+	preference to multiple mpfr_clear().
+	* simplify.c (gfc_simplify_and): Remove blank line.
+	(gfc_simplify_atan2): Move error checking earlier to eliminate
+	a now unnecessay gfc_free_expr().
+	(gfc_simplify_bessel_j0): Remove unnecessary gfc_set_model_kind().
+	(gfc_simplify_bessel_j1): Ditto.
+	(gfc_simplify_bessel_jn): Ditto.
+ 	(gfc_simplify_bessel_y0): Ditto.
+	(gfc_simplify_bessel_y1): Ditto.
+	(gfc_simplify_bessel_yn): Ditto. 
+	(only_convert_cmplx_boz): Eliminate unnecessary duplicate code, and
+	combine nested if statement rational expressions.
+	(gfc_simplify_cos): Use mpfr_clears() in preference to multiple
+	mpfr_clear().
+	(gfc_simplify_exp): Ditto.
+	(gfc_simplify_fraction): Move gfc_set_model_kind() to after the
+	special case of 0.  Use mpfr_clears() in preference to multiple
+	mpfr_clear().
+	(gfc_simplify_gamma): Eliminate unnecessary gfc_set_model_kind().
+ 	(gfc_simplify_lgamma): Ditto.
+	(gfc_simplify_log10): Ditto.
+	(gfc_simplify_log): Move gfc_set_model_kind () inside switch
+	statement. Use mpfr_clears() in preference to multiple mpfr_clear().
+	(gfc_simplify_mod):  Eliminate now unused variables quot, iquot,
+	and term.  Simplify the mpfr magic.
+	(gfc_simplify_modulo): Ditto.
+	(gfc_simplify_nearest): Eliminate unnecessary gfc_set_model_kind().
+	(gfc_simplify_scale): Use mpfr_clears() in preference to multiple
+	mpfr_clear().
+	(gfc_simplify_sin): Ditto
+	(gfc_simplify_sqrt): Ditto
+	(gfc_simplify_set_exponent):  Move gfc_set_model_kind() to after the
+	special case of 0.  Use mpfr_clears() in preference to multiple
+	mpfr_clear().
+
+2008-05-29  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR target/36348
+	* Make-lang.in (F95_OBJS): Added dependency on FORTRAN_TARGET_OBJS.
+
+2008-05-29  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* scanner.c (load_line): Add first_char argument. Don't call ungetc.
+	(gfc_read_orig_filename): Adjust call to load_line. Don't call
+	ungetc.
+	(load_file): Adjust call to load_line.
+
+2008-05-28  Janus Weil  <janus@gcc.gnu.org>
+
+	PR fortran/36325
+	PR fortran/35830
+	* interface.c (gfc_procedure_use): Enable argument checking for
+	external procedures with explicit interface.
+	* symbol.c (check_conflict): Fix conflict checking for externals.
+	(copy_formal_args): Fix handling of arrays.
+	* resolve.c (resolve_specific_f0, resolve_specific_s0): Fix handling
+	of intrinsics.
+	* parse.c (parse_interface): Non-abstract INTERFACE statement implies
+	EXTERNAL attribute.
+
+2008-05-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36319
+	* intrinsic.c (gfc_convert_chartype): Don't mark conversion
+	function as pure.
+	* trans-array.c (gfc_trans_array_ctor_element): Divide element
+	size by the size of one character to obtain length.
+	* iresolve.c (gfc_resolve_cshift): Call the _char4 variant when
+	appropriate.
+	(gfc_resolve_eoshift): Likewise.
+	* trans-intrinsic.c (gfc_conv_intrinsic_ctime): Minor beautification.
+	(gfc_conv_intrinsic_fdate): Minor beautification.
+	(gfc_conv_intrinsic_ttynam): Minor beautification.
+	(gfc_conv_intrinsic_minmax_char): Allow all character kinds.
+	(size_of_string_in_bytes): New function.
+	(gfc_conv_intrinsic_size): Call size_of_string_in_bytes for
+	character expressions.
+	(gfc_conv_intrinsic_sizeof): Likewise.
+	(gfc_conv_intrinsic_array_transfer): Likewise.
+	(gfc_conv_intrinsic_trim): Allow all character kinds. Minor
+	beautification.
+	(gfc_conv_intrinsic_repeat): Fix comment typo.
+	* simplify.c (gfc_convert_char_constant): Take care of conversion
+	of array constructors.
+
+2008-05-27  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36316
+	* trans-array.c (gfc_set_loop_bounds_from_array_spec):
+	Add missing fold_convert.
+
+2008-05-26  Daniel Franke  <franke.daniel@gmail.com>
+
+	* fortran/cpp.c (cpp_define_builtins): Remove usage of TARGET_* macros,
+	added FIXME instead.
+
+2008-05-26  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/18428
+	* lang.opt (A, C, CC, D, E, H, P, U, cpp, d, fworking-directory,
+	imultilib, iprefix, iquote, isysroot, isystem, nocpp, nostdinc,
+	o, undef, v): New options.
+	* options.c (gfc_init_options): Also initialize preprocessor
+	options.
+	(gfc_post_options): Also handle post-initialization of preprocessor
+	options.
+	(gfc_handle_option): Check if option is a preprocessor option.
+	If yes, let gfc_cpp_handle_option() handle the option.
+	* lang-specs.h: Reorganized to handle new options.
+	* scanner.c (gfc_new_file): Read temporary file instead of
+	input source if preprocessing is enabled.
+	* f95-lang.c (gfc_init): Initialize preprocessor.
+	(gfc_finish): Clean up preprocessor.
+	* cpp.c: New.
+	* cpp.h: New.
+	* Make-lang.in: Added new objects and dependencies.
+	* gfortran.texi: Updated section "Preprocessing and
+	conditional compilation".
+	* invoke.texi: Added new section "Preprocessing Options",
+	listed and documented the preprocessing options handled
+	by gfortran.
+
+2008-05-25  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/32600
+	* trans-expr.c (gfc_conv_function_call): Remove library
+	call for c_f_pointer with scalar Fortran pointers and for
+	c_f_procpointer.
+
+2008-05-21  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36257
+	* iresolve.c (check_charlen_present): Don't force the rank to 1.
+
+2008-05-19  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36265
+	* trans-expr.c (gfc_conv_string_tmp): Pick the correct type for
+	the temporary variable.
+
+2008-05-19  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* simplify.c (gfc_simplify_dble, gfc_simplify_real): Initialize
+	result variable to avoid warnings.
+
+2008-05-18  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* intrinsic.c (char_conversions, ncharconv): New static variables.
+	(find_char_conv): New function.
+	(add_functions): Add simplification functions for ADJUSTL and
+	ADJUSTR. Don't check the kind of their argument. Add checking for
+	LGE, LLE, LGT and LLT.
+	(add_subroutines): Fix argument type for SLEEP. Fix argument name
+	for SYSTEM.
+	(add_char_conversions): New function.
+	(gfc_intrinsic_init_1): Call add_char_conversions.
+	(gfc_intrinsic_done_1): Free char_conversions.
+	(check_arglist): Use kind == 0 as a signal that we don't want
+	the kind value to be checked.
+	(do_simplify): Also simplify character functions.
+	(gfc_convert_chartype): New function
+	* trans-array.c (gfc_trans_array_ctor_element): Don't force the
+	use of default character type.
+	(gfc_trans_array_constructor_value): Likewise.
+	(get_array_ctor_var_strlen): Use integer kind to build an integer
+	instead of a character kind!
+	(gfc_build_constant_array_constructor): Don't force the use of
+	default character type.
+	(gfc_conv_loop_setup): Likewise.
+	* trans-expr.c (gfc_conv_string_tmp): Don't force the use of
+	default character type. Allocate enough memory for wide strings.
+	(gfc_conv_concat_op): Make sure operand kind are the same.
+	(string_to_single_character): Remove gfc_ prefix. Reindent.
+	Don't force the use of default character type.
+	(gfc_conv_scalar_char_value): Likewise.
+	(gfc_build_compare_string): Call string_to_single_character.
+	(fill_with_spaces): New function
+	(gfc_trans_string_copy): Add kind arguments. Use them to deal
+	with wide character kinds.
+	(gfc_conv_statement_function): Whitespace fix. Call
+	gfc_trans_string_copy with new kind arguments.
+	(gfc_conv_substring_expr): Call gfc_build_wide_string_const
+	instead of using gfc_widechar_to_char.
+	(gfc_conv_string_parameter): Don't force the use of default
+	character type.
+	(gfc_trans_scalar_assign): Pass kind args to gfc_trans_string_copy.
+	* intrinsic.h (gfc_check_lge_lgt_lle_llt, gfc_convert_char_constant,
+	gfc_resolve_adjustl, gfc_resolve_adjustr): New prototypes.
+	* decl.c (gfc_set_constant_character_len): Don't assert the
+	existence of a single character kind.
+	* trans-array.h (gfc_trans_string_copy): New prototype.
+	* gfortran.h (gfc_check_character_range, gfc_convert_chartype):
+	New prototypes.
+	* error.c (print_wide_char_into_buffer): New function lifting
+	code from gfc_print_wide_char. Fix order to output '\x??' instead
+	of 'x\??'.
+	(gfc_print_wide_char): Call print_wide_char_into_buffer.
+	(show_locus): Call print_wide_char_into_buffer with buffer local
+	to this function.
+	* trans-const.c (gfc_build_wide_string_const): New function.
+	(gfc_conv_string_init): Deal with wide characters strings
+	constructors.
+	(gfc_conv_constant_to_tree): Call gfc_build_wide_string_const.
+	* trans-stmt.c (gfc_trans_label_assign): Likewise.
+	(gfc_trans_character_select): Deal with wide strings.
+	* expr.c (gfc_check_assign): Allow conversion between character
+	kinds on assignment.
+	* trans-const.h (gfc_build_wide_string_const): New prototype.
+	* trans-types.c (gfc_get_character_type_len_for_eltype,
+	gfc_get_character_type_len): Create too variants of the old
+	gfc_get_character_type_len, one getting kind argument and the
+	other one directly taking a type tree.
+	* trans.h (gfor_fndecl_select_string_char4,
+	gfor_fndecl_convert_char1_to_char4,
+	gfor_fndecl_convert_char4_to_char1): New prototypes.
+	* trans-types.h (gfc_get_character_type_len_for_eltype): New
+	prototype.
+	* resolve.c (resolve_operator): Exit early when kind mismatches
+	are detected, because that makes us issue an error message later.
+	(validate_case_label_expr): Fix wording of error message.
+	* iresolve.c (gfc_resolve_adjustl, gfc_resolve_adjustr): New
+	functions.
+	(gfc_resolve_pack): Call _char4 variants of library function
+	when dealing with wide characters.
+	(gfc_resolve_reshape): Likewise.
+	(gfc_resolve_spread): Likewise.
+	(gfc_resolve_transpose): Likewise.
+	(gfc_resolve_unpack): Likewise.
+	* target-memory.c (size_character): Take character kind bit size
+	correctly into account (not that it changes anything for now, but
+	it's more generic).
+	(gfc_encode_character): Added gfc_ prefix. Encoding each
+	character of a string by calling native_encode_expr for the
+	corresponding unsigned integer.
+	(gfc_target_encode_expr): Add gfc_ prefix to encode_character.
+	* trans-decl.c (gfc_build_intrinsic_function_decls): Build
+	gfor_fndecl_select_string_char4, gfor_fndecl_convert_char1_to_char4
+	and gfor_fndecl_convert_char4_to_char1.
+	* target-memory.h (gfc_encode_character): New prototype.
+	* arith.c (gfc_check_character_range): New function.
+	(eval_intrinsic): Allow non-default character kinds.
+	* check.c (gfc_check_access_func): Only allow default
+	character kind arguments.
+	(gfc_check_chdir): Likewise.
+	(gfc_check_chdir_sub): Likewise.
+	(gfc_check_chmod): Likewise.
+	(gfc_check_chmod_sub): Likewise.
+	(gfc_check_lge_lgt_lle_llt): New function.
+	(gfc_check_link): Likewise.
+	(gfc_check_link_sub): Likewise.
+	(gfc_check_symlnk): Likewise.
+	(gfc_check_symlnk_sub): Likewise.
+	(gfc_check_rename): Likewise.
+	(gfc_check_rename_sub): Likewise.
+	(gfc_check_fgetputc_sub): Likewise.
+	(gfc_check_fgetput_sub): Likewise.
+	(gfc_check_stat): Likewise.
+	(gfc_check_stat_sub): Likewise.
+	(gfc_check_date_and_time): Likewise.
+	(gfc_check_ctime_sub): Likewise.
+	(gfc_check_fdate_sub): Likewise.
+	(gfc_check_gerror): Likewise.
+	(gfc_check_getcwd_sub): Likewise.
+	(gfc_check_getarg): Likewise.
+	(gfc_check_getlog): Likewise.
+	(gfc_check_hostnm): Likewise.
+	(gfc_check_hostnm_sub): Likewise.
+	(gfc_check_ttynam_sub): Likewise.
+	(gfc_check_perror): Likewise.
+	(gfc_check_unlink): Likewise.
+	(gfc_check_unlink_sub): Likewise.
+	(gfc_check_system_sub): Likewise.
+	* primary.c (got_delim): Perform correct character range checking
+	for all kinds.
+	* trans-intrinsic.c (gfc_conv_intrinsic_conversion): Generate
+	calls to library functions convert_char4_to_char1 and
+	convert_char1_to_char4 for character conversions.
+	(gfc_conv_intrinsic_char): Allow all character kings.
+	(gfc_conv_intrinsic_strcmp): Fix whitespace.
+	(gfc_conv_intrinsic_repeat): Take care of all character kinds.
+	* intrinsic.texi: For all GNU intrinsics accepting character
+	arguments, mention that they're restricted to the default kind.
+	* simplify.c (simplify_achar_char): New function.
+	(gfc_simplify_achar, gfc_simplify_char): Call simplify_achar_char.
+	gfc_simplify_ichar): Don't error out for wide characters.
+	(gfc_convert_char_constant): New function.
+
+2008-05-18  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/36251
+	* symbol.c (check_conflict): Issue errors for abuse of PUBLIC, PRIVATE,
+	and BIND(C).
+	* resolve.c (gfc_verify_binding_labels): Fix NULL pointer dereference.
+
+2008-05-17  Tobias Burnus  <burnus@net-b.de>
+
+	* intrinsic.texi: Correct description of GET_COMMAND_ARGUMENT
+	and GET_ENVIRONMENT_VARIABLE; fix keyword= name for GETENV,
+	GETLOG, GMTIME, HOSTNM, IRAND, ITIME, KILL.
+	Move LOG_GAMMA after LOG10.
+
+2008-05-17  Tobias Burnus  <burnus@net-b.de>
+
+	* intrinsic.c (add_functions): Change FLUSH(C) to FLUSH(UNIT).
+	* intrinsic.texi: Change INTEGER(*) to INTEGER; fix keyword= name for
+	ABS, ADJUSTL, AINT, ALLOCATED, ANINT, ASSOCIATED, C_ASSOCIATED,
+	CEILING, DBLE, DFLOAT, DOT_PRODUCT, DREAL, FLOAT, FLOOR, GET_COMMAND.
+
+2008-05-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35756
+	PR fortran/35759
+	* trans-stmt.c (gfc_trans_where): Tighten up the dependency
+	check for calling gfc_trans_where_3.
+
+	PR fortran/35743
+	* trans-stmt.c (gfc_trans_where_2): Set the mask size to zero
+	if it is calculated to be negative.
+
+	PR fortran/35745
+	* trans-stmt.c (gfc_trans_where_3, gfc_trans_where_assign): Set
+	ss->where for scalar right hand sides.
+	* trans-array.c (gfc_add_loop_ss_code): If ss->where is set do
+	not evaluate scalars outside the loop.  Clean up whitespace.
+	* trans.h : Add a bitfield 'where' to gfc_ss.
+
+2008-05-16  Tobias Burnus  <burnus@net-b.de>
+
+	* libgfortran.h: Increase GFC_MAX_DIMENSIONS to 15.
+	* array.c (gfc_match_array_spec): Error with -std=f2003 if rank > 7.
+
+2008-04-16  Daniel Kraft  <d@domob.eu>
+
+	PR fortran/27997
+	* gfortran.h:  Added field "length_from_typespec" to gfc_charlength.
+	* aray.c (gfc_match_array_constructor):  Added code to parse typespec.
+	(check_element_type, check_constructor_type, gfc_check_constructor_type):
+	Extended to support explicit typespec on constructor.
+	(gfc_resolve_character_array_constructor):  Pad strings correctly for
+	explicit, constant character length.
+	* trans-array.c:  New static global variable "typespec_chararray_ctor"
+	(gfc_trans_array_constructor):  New code to support explicit but dynamic
+	character lengths.
+
+2008-05-16  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34325
+	* decl.c (match_attr_spec): Check for matching pairs of parenthesis.
+	* expr.c (gfc_specification_expr): Supplement the error message with the
+	type that was found.
+	* resolve.c (gfc_resolve_index): Likewise.
+	* match.c (gfc_match_parens): Clarify error message with "at or before".
+	(gfc_match_do): Check for matching pairs of parenthesis.
+
+2008-05-16  Tobias Burnus  <burnus@net-b.de
+
+	* intrinsic.texi: Write Fortran 77/90/95 instead of F77/90/95;
+	add missing KIND argument to ACHAR and NINT; and state that
+	the KIND argument is a F2003 extension for ACHAR, COUNT, IACHAR,
+	ICHAR, INDEX, LBOUND, LEN, LEN_TRIM, SCAN, SIZE, UBOUND, VERIFY.
+
+2008-05-16  Daniel Kraft  <d@domob.eu>
+
+	* primary.c:  New private structure "gfc_structure_ctor_component".
+	(gfc_free_structure_ctor_component):  New helper function.
+	(gfc_match_structure_constructor):  Extended largely to support named
+	arguments and default initialization for structure constructors.
+
+2008-05-15  Steven G. Kargl  <kargls@comcast.net>
+
+	* simplify.c (gfc_simplify_dble, gfc_simplify_float,
+	simplify_bound, gfc_simplify_nearest, gfc_simplify_real): Plug
+	possible memory leaks.
+	(gfc_simplify_reshape): Plug possible memory leaks and dereferencing
+	of NULL pointers.
+
+2008-05-15  Steven G. Kargl  <kargls@comcast.net>
+
+	PR fortran/36239
+	* simplify.c (gfc_simplify_int, gfc_simplify_intconv): Replaced hand
+	rolled integer conversion with gfc_int2int, gfc_real2int, and
+	gfc_complex2int.
+	(gfc_simplify_intconv): Renamed to simplify_intconv.
+	
+2008-05-15  Steven G. Kargl,   <kargl@comcast.net>
+	* gfortran.dg/and_or_xor.f90: New test
+
+	* fortran/simplify.c (gfc_simplify_and, gfc_simplify_or,
+	gfc_simplify_xor): Don't range check logical results.
+
+2008-05-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* trans-expr.c (gfc_conv_concat_op): Take care of nondefault
+	character kinds.
+	(gfc_build_compare_string): Add kind argument and use it.
+	(gfc_conv_statement_function): Fix indentation.
+	* gfortran.h (gfc_character_info): New structure.
+	(gfc_character_kinds): New array.
+	* trans-types.c (gfc_character_kinds, gfc_character_types,
+	gfc_pcharacter_types): New array.
+	(gfc_init_kinds): Fill character kinds array.
+	(validate_character): Take care of nondefault character kinds.
+	(gfc_build_uint_type): New function.
+	(gfc_init_types): Take care of nondefault character kinds.
+	(gfc_get_char_type, gfc_get_pchar_type): New functions.
+	(gfc_get_character_type_len): Use gfc_get_char_type.
+	* trans.h (gfc_build_compare_string): Adjust prototype.
+	(gfor_fndecl_compare_string_char4, gfor_fndecl_concat_string_char4,
+	gfor_fndecl_string_len_trim_char4, gfor_fndecl_string_index_char4,
+	gfor_fndecl_string_scan_char4, gfor_fndecl_string_verify_char4,
+	gfor_fndecl_string_trim_char4, gfor_fndecl_string_minmax_char4,
+	gfor_fndecl_adjustl_char4, gfor_fndecl_adjustr_char4): New
+	prototypes.
+	* trans-types.h (gfc_get_char_type, gfc_get_pchar_type): New
+	prototypes.
+	* trans-decl.c (gfor_fndecl_compare_string_char4,
+	gfor_fndecl_string_len_trim_char4, gfor_fndecl_string_index_char4,
+	gfor_fndecl_string_scan_char4, gfor_fndecl_string_verify_char4,
+	gfor_fndecl_string_trim_char4, gfor_fndecl_string_minmax_char4,
+	gfor_fndecl_adjustl_char4, gfor_fndecl_adjustr_char4,
+	gfor_fndecl_concat_string_char4): New function decls.
+	(gfc_build_intrinsic_function_decls): Define new *_char4 function
+	decls.
+	* trans-intrinsic.c (gfc_conv_intrinsic_minmax_char,
+	gfc_conv_intrinsic_len_trim, gfc_conv_intrinsic_ichar,
+	gfc_conv_intrinsic_strcmp, gfc_conv_intrinsic_trim,
+	gfc_conv_intrinsic_function): Deal with nondefault character kinds.
+
+2008-05-15  Sa Liu  <saliu@de.ibm.com>
+
+	* iso-c-binding.def: Add standard parameter to macro NAMED_INTCST.
+	All existing NAMED_INTCST definitions has standard GFC_STD_F2003,
+	c_int128_t, c_int_least128_t and c_int_fast128_t are added as
+	GNU extensions.
+	* iso-fortran-evn.def: Add standard parameter GFC_STD_F2003
+	to macro NAMED_INTCST.
+	* symbol.c (std_for_isocbinding_symbol): New helper function to 
+	return the standard that supports this isocbinding symbol.
+	(generate_isocbinding_symbol): Do not generate GNU extension symbols
+	if std=f2003. Add new parameter to NAMED_INTCST.
+	* module.c (use_iso_fortran_env_module): Add new parameter to
+	NAMED_INTCST and new field standard to struct intmod_sym.
+	* gfortran.h: Add new parameter to NAMED_INTCST.
+	* trans-types.c (init_c_interop_kinds): Add new parameter to 
+	NAMED_INTCST.
+	* intrinsic.texi: Documented new types C_INT128_T, C_INT_LEASE128_T
+	and C_INT_FAST128_T.
+
+2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36059
+	* trans-decl.c (gfc_build_dummy_array_decl): Don't repack
+	arrays that have the TARGET attribute.
+
+2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36186
+	* simplify.c (only_convert_cmplx_boz): New function.
+	(gfc_simplify_cmplx, gfc_simplify_complex, gfc_simplify_dcmplx):
+	Call only_convert_cmplx_boz.
+
+2008-05-14  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/36233
+	* interface.c (compare_actual_formal): Do not check sizes if the
+	actual is BT_PROCEDURE.
+
+2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/35682
+	* trans-array.c (gfc_conv_ss_startstride): Any negative size is
+	the same as zero size.
+	(gfc_conv_loop_setup): Fix size calculation.
+
+2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/35685
+	* trans-intrinsic.c (gfc_conv_intrinsic_bound): Correctly
+	handle zero-size sections.
+
+2008-05-14  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36215
+	* scanner.c (preprocessor_line): Allocate enough memory for a
+	wide string.
+
+2008-05-12  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36176
+	* target-memory.c (gfc_target_expr_size): Correctly treat
+	substrings.
+	(gfc_target_encode_expr): Likewise.
+	(gfc_interpret_complex): Whitespace change.
+
+2008-05-11  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/35719
+	* trans.c (gfc_call_malloc): If size equals zero, allocate one
+	byte; don't return a null pointer.
+
+2008-05-10  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36197
+	* module.c (quote_string): Fix sprintf format.
+
+2008-05-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/36162
+	* module.c (quote_string, unquote_string,
+	mio_allocated_wide_string): New functions.
+	(mio_expr): Call mio_allocated_wide_string where needed.
+
+2008-05-07 Kenneth Zadeck <zadeck@naturalbridge.com>
+
+	 * trans-decl.c (gfc_get_extern_function_decl, build_function_decl):
+	 Rename DECL_IS_PURE to DECL_PURE_P.
+
+2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* arith.c: (gfc_arith_concat, gfc_compare_string,
+	gfc_compare_with_Cstring, hollerith2representation,
+	gfc_hollerith2int, gfc_hollerith2real, gfc_hollerith2complex,
+	gfc_hollerith2character, gfc_hollerith2logical): Use wide
+	characters for character constants.
+	* data.c (create_character_intializer): Likewise.
+	* decl.c (gfc_set_constant_character_len): Likewise.
+	* dump-parse-tree.c (show_char_const): Correctly dump wide
+	character strings.
+	error.c (print_wide_char): Rename into gfc_print_wide_char.
+	(show_locus): Adapt to new prototype of gfc_print_wide_char.
+	expr.c (free_expr0): Representation is now disjunct from
+	character string value, so we always free it.
+	(gfc_copy_expr, find_substring_ref, gfc_simplify_expr): Adapt
+	to wide character strings.
+	* gfortran.h (gfc_expr): Make value.character.string a wide string.
+	(gfc_wide_toupper, gfc_wide_strncasecmp, gfc_wide_memset,
+	gfc_widechar_to_char, gfc_char_to_widechar): New prototypes.
+	(gfc_get_wide_string): New macro.
+	(gfc_print_wide_char): New prototype.
+	* io.c (format_string): Make a wide string.
+	(next_char, gfc_match_format, compare_to_allowed_values, 
+	gfc_match_open): Deal with wide strings.
+	* module.c (mio_expr): Convert between wide strings and ASCII ones.
+	* primary.c (match_hollerith_constant, match_charkind_name): 
+	Handle wide strings.
+	* resolve.c (build_default_init_expr): Likewise.
+	* scanner.c (gfc_wide_toupper, gfc_wide_memset,
+	gfc_char_to_widechar): New functions.
+	(wide_strchr, gfc_widechar_to_char, gfc_wide_strncasecmp):
+	Changes in prototypes.
+	(gfc_define_undef_line, load_line, preprocessor_line,
+	include_line, load_file, gfc_read_orig_filename): Handle wide
+	strings.
+	* simplify.c (gfc_simplify_achar, gfc_simplify_adjustl,
+	gfc_simplify_adjustr, gfc_simplify_char, gfc_simplify_iachar,
+	gfc_simplify_ichar, simplify_min_max, gfc_simplify_new_line,
+	gfc_simplify_repeat): Handle wide strings.
+	(wide_strspn, wide_strcspn): New helper functions.
+	(gfc_simplify_scan, gfc_simplify_trim, gfc_simplify_verify):
+	Handle wide strings.
+	* symbol.c (generate_isocbinding_symbol): Likewise.
+	* target-memory.c (size_character, gfc_target_expr_size,
+	encode_character, gfc_target_encode_expr, gfc_interpret_character,
+	gfc_target_interpret_expr): Handle wide strings.
+	* trans-const.c (gfc_conv_string_init): Lower wide strings to
+	narrow ones.
+	(gfc_conv_constant_to_tree): Likewise.
+	* trans-expr.c (gfc_conv_substring_expr): Handle wide strings.
+	* trans-io.c (gfc_new_nml_name_expr): Likewise.
+	* trans-stmt.c (gfc_trans_label_assign): Likewise.
+
+2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* simplify.c (gfc_simplify_bessel_j0,gfc_simplify_bessel_j1,
+	gfc_simplify_bessel_jn,gfc_simplify_bessel_y0,
+	gfc_simplify_bessel_y1,gfc_simplify_bessel_yn): Mark arguments
+	with ATTRIBUTE_UNUSED.
+
+2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* check.c (gfc_check_sizeof): Switch to ATTRIBUTE_UNUSED.
+	* simplify.c (gfc_simplify_lgamma): Likewise.
+
+2008-05-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* openmp.c (gfc_match_omp_eos): Use gfc_next_ascii_char and
+	gfc_peek_ascii_char.
+	* decl.c (gfc_match_kind_spec, gfc_match_type_spec,
+	gfc_match_implicit_none, match_implicit_range, gfc_match_implicit,
+	match_string_p, match_attr_spec, gfc_match_suffix,
+	match_procedure_decl, gfc_match_entry, gfc_match_subroutine):
+	Likewise.
+	* gfortran.h (gfc_char_t): New type.
+	(gfc_linebuf): Make line member a gfc_char_t.
+	(locus): Make nextc member a gfc_char_t.
+	(gfc_wide_is_printable, gfc_wide_is_digit, gfc_wide_fits_in_byte,
+	gfc_wide_tolower, gfc_wide_strlen, gfc_next_ascii_char,
+	gfc_peek_ascii_char, gfc_check_digit): New prototypes.
+	* error.c (print_wide_char): New function.
+	(show_locus): Use print_wide_char and gfc_wide_strlen.
+	* io.c (next_char): Use gfc_char_t type.
+	(match_io): Use gfc_peek_ascii_char and gfc_next_ascii_char.
+	* match.c (gfc_match_parens, gfc_match_eos,
+	gfc_match_small_literal_int, gfc_match_name, gfc_match_name_C,
+	gfc_match_intrinsic_op, gfc_match_char,  gfc_match_return,
+	gfc_match_common): Likewise.
+	* match.h (gfc_match_special_char): Change prototype.
+	* parse.c (decode_specification_statement, decode_statement,
+	decode_omp_directive, next_free, next_fixed): Use
+	gfc_peek_ascii_char and gfc_next_ascii_char.
+	* primary.c (gfc_check_digit): Change name.
+	(match_digits, match_hollerith_constant, match_boz_constant,
+	match_real_constant, next_string_char, match_charkind_name,
+	match_string_constant, match_logical_constant_string,
+	match_complex_constant, match_actual_arg, match_varspec,
+	gfc_match_rvalue, match_variable): Use gfc_peek_ascii_char and
+	gfc_next_ascii_char.
+	* scanner.c (gfc_wide_fits_in_byte, wide_is_ascii,
+	gfc_wide_is_printable, gfc_wide_tolower, gfc_wide_is_digit,
+	gfc_wide_is_digit, wide_atoi, gfc_wide_strlen, wide_strcpy,
+	wide_strchr, widechar_to_char, wide_strncmp, wide_strncasecmp,
+	gfc_next_ascii_char, gfc_peek_ascii_char):
+	New functions.
+	(next_char, gfc_define_undef_line, skip_free_comments,
+	gfc_next_char_literal, gfc_next_char, gfc_peek_char,
+	gfc_error_recovery, load_line, preprocessor_line, include_line,
+	load_file, gfc_read_orig_filename): Use gfc_char_t for source
+	characters and the {gfc_,}wide_* functions to manipulate wide
+	strings.
+
+2008-05-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/36117
+	* intrinsic.c (add_functions): Call gfc_simplify_bessel_*.
+	* intrinsic.h: Add prototypes for gfc_simplify_bessel_*.
+	* simplify.c (gfc_simplify_bessel_j0,gfc_simplify_bessel_j1,
+	gfc_simplify_bessel_jn,gfc_simplify_bessel_y0,
+	gfc_simplify_bessel_y1,gfc_simplify_bessel_yn): New.
+
+2008-05-03  Janus Weil  <jaydub66@gmail.com>
+
+	* misc.c (gfc_clear_ts): Set interface to NULL.
+
+2008-05-03  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/33268
+	* gfortran.h: Add extra_comma pointer to gfc_dt structure. Add iokind to
+	gfc_expr value union. Add io_kind enum to here from io.c.
+	* io.c (gfc_free_dt): Free extra_comma.
+	(gfc_resolve_dt): If an extra comma was encountered and io_unit is type
+	BT_CHARACTER, resolve to format_expr and set default unit.  Error if
+	io_kind is M_WRITE. (match_io):  Match the extra comma and set new
+	pointer, extra_comma.
+
+2008-05-01  Bud Davis  <bdavis9659@sbcglobal.net>
+
+	PR35940/Fortran
+	* simplify.c (gfc_simplify_index): Check for direction argument 
+	being a constant.
+
+2008-05-01  Janus Weil  <jaydub66@gmail.com>
+
+	* gfortran.h (struct gfc_symbol): Moving "interface" member to
+	gfc_typespec (plus fixing a small docu error).
+	* interface.c (gfc_procedure_use): Ditto.
+	* decl.c (match_procedure_decl): Ditto.
+	* resolve.c (resolve_specific_f0,
+	resolve_specific_f0, resolve_symbol): Ditto.
+
+2008-04-30  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* intrinsic.c (add_functions): Add SELECTED_CHAR_KIND intrinsic.
+	* intrinsic.h (gfc_check_selected_char_kind,
+	gfc_simplify_selected_char_kind): New prototypes.
+	* gfortran.h (gfc_isym_id): Add GFC_ISYM_SC_KIND.
+	* trans.h (gfor_fndecl_sc_kind): New function decl.
+	* trans-decl.c (gfor_fndecl_sc_kind): Build new decl.
+	* arith.c (gfc_compare_with_Cstring): New function.
+	* arith.h (gfc_compare_with_Cstring): New prototype.
+	* check.c (gfc_check_selected_char_kind): New function.
+	* primary.c (match_string_constant, match_kind_param): Mark
+	symbols used as literal constant kind param as referenced.
+	* trans-intrinsic.c (gfc_conv_intrinsic_sc_kind): New function.
+	(gfc_conv_intrinsic_function): Call gfc_conv_intrinsic_sc_kind.
+	* intrinsic.texi (SELECTED_CHAR_KIND): Document new intrinsic.
+	* simplify.c (gfc_simplify_selected_char_kind): New function.
+
+2008-04-28  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35997
+	* module.c (find_symbol): Do not return a result for a symbol
+	that has been renamed in another module.
+
+2008-04-26  George Helffrich <george@gcc.gnu.org>
+
+	PR fortran/35892
+	PR fortran/35154
+	* trans-common.c (create_common):  Add decl to function
+	chain (if inside one) to preserve identifier scope in debug output.
+
+2008-04-25  Jan Hubicka  <jh@suse.cz>
+
+	* trans-decl.c (trans_function_start): Update.
+
+2008-04-25  Tobias Burnus  <burnus@net-b.de>
+	    Daniel Franke <franke.daniel@gmail.com>
+
+	PR fortran/35156
+	* gfortranspec.c (lang_specific_driver): Deprecate
+	-M option; fix ICE when "-M" is last argument and
+	make "-M<dir>" work.
+	* options.c (gfc_handle_module_path_options): 
+	Use -J instead of -M in error messages.
+	* invoke.texi: Mark -M as depecated.
+
+2008-04-23  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+	    Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/35994
+	* trans-instrinsic.c (gfc_conv_intrinsic_minmaxloc): Correctly adjust
+	loop counter offset.
+
+2008-04-23  Paolo Bonzini  <bonzini@gnu.org>
+
+	* trans-expr.c (gfc_conv_structure): Don't set TREE_INVARIANT.
+	* trans-array.c (gfc_build_null_descriptor): Don't set TREE_INVARIANT.
+	(gfc_trans_array_constructor_value): Don't set TREE_INVARIANT.
+	(gfc_build_constant_array_constructor): Don't set TREE_INVARIANT.
+	(gfc_conv_array_initializer): Don't set TREE_INVARIANT.
+	* trans-common.c (get_init_field): Don't set TREE_INVARIANT.
+	(create_common): Don't set TREE_INVARIANT.
+	* trans-stmt.c (gfc_trans_character_select): Don't set TREE_INVARIANT.
+	* trans-decl.c (gfc_generate_function_code): Don't set TREE_INVARIANT.
+
+2008-04-21  Steve Ellcey  <sje@cup.hp.com>
+
+	* f95-lang.c (gfc_init_decl_processing): use ptr_mode instead of Pmode.
+
+2008-04-21  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/35019
+	* gfortranspec.c (lookup_option): Properly handle separated arguments
+	in -J option, print missing argument message when necessary.
+
+2008-04-20  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35882
+	* scanner.c (skip_fixed_comments): Update continue_line when comment is
+	detected. (gfc_next_char_literal): Likewise.
+
+2008-04-19  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35944
+	PR fortran/35946
+	PR fortran/35947
+	* trans_array.c (gfc_trans_array_constructor): Temporarily
+	realign loop, if loop->from is not zero, before creating
+	the temporary array and provide an offset.
+
+	PR fortran/35959
+	* trans-decl.c (gfc_init_default_dt): Add gfc_ prefix to name
+	and allow for NULL body.  Change all references from
+	init_default_dt to gfc_init_default_dt.
+	* trans.h : Add prototype for gfc_init_default_dt.
+	* trans-array.c (gfc_trans_deferred_vars): After nullification
+	call gfc_init_default_dt for derived types with allocatable
+	components.
+
+2008-04-18  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35892
+	* trans-common.c (create_common): Revert patch causing regression.
+
+2008-04-16  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35724
+	* iresolve.c (gfc_resolve_eoshift): Check for NULL symtree in test for
+	optional argument attribute.
+	
+2008-04-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35932
+	* trans-intrinsic.c (gfc_conv_intrinsic_char): Even though KIND
+	is not used, the argument must be converted.
+
+2008-04-16  Jakub Jelinek  <jakub@redhat.com>
+
+	PR target/35662
+	* f95-lang.c (gfc_init_builtin_functions): Make sure
+	BUILT_IN_SINCOS{,F,L} types aren't varargs.
+
+2008-04-15  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35864
+	* expr.c (scalarize_intrinsic_call): Reorder identification of
+	array argument so that if one is not found a segfault does not
+	occur.  Return FAILURE if all scalar arguments.
+
+2008-04-13  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+	    Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/35882
+	* options.c (gfc_init_options): Set the default maximum continuation
+	lines to 255 for both free and fixed form source for warnings.
+	(gfc_handle_option): Set -std=f95 fixed form max continuations to 19 and
+	the -std=f95 free form max continuations to 39 for warnings.
+	* scanner.c (gfc_next_char_literal): Adjust the current_line number only
+	if it is less than the current locus.
+
+2008-04-07  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/25829 28655
+	* io.c (io_tag): Add new tags for decimal, encoding, asynchronous,
+	round, sign, and id. (match_open_element): Match new tags.
+	(gfc_resolve_open): Resolve new tags. (gfc_match_open): Enable encoding
+	for DEFAULT only. Update error messages. (match_dt_element): Fix match
+	tag for asynchronous. Update error messages. (gfc_free_inquire): Free
+	new expressions. (match_inquire_element): Match new tags.
+	(gfc_match_inquire): Add constraint for ID and PENDING.
+	(gfc_resolve_inquire): Resolve new tags.
+	* trans-io.c (gfc_trans_inquire): Clean up whitespace and fix setting of
+	mask for ID parameter.
+	* ioparm.def: Fix order of parameters for pending, round, and sign.
+	NOTE: These must line up with the definitions in libgfortran/io/io.h. or
+	things don't work.
+
+2008-04-06  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35780
+	* expr.c (scalarize_intrinsic_call): Identify which argument is
+	an array and use that as the template.
+	(check_init_expr): Remove tests that first argument is an array
+	in the call to scalarize_intrinsic_call.
+
+2008-04-06  Tobias Schlüter  <tobi@gcc.gnu.org>
+
+	PR fortran/35832
+	* io.c (io_tag): Add field 'value'.  Split 'spec' field in
+	existing io_tags.
+	(match_etag, match_vtag, match_ltag): Split parsing in two steps
+	to give better error messages.
+
+2008-04-06  Tobias Burnus  <burnus@net-b.de>
+
+	* io.c (check_io_constraints): Add constrains. ID= requires
+	asynchronous= and asynchronous= must be init expression.
+
+2008-04-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* f95-lang.c: Set LANG_HOOKS_NAME to "GNU Fortran".
+
+2008-04-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* dump-parse-tree.c: Use fprintf, fputs and fputc instead of
+	gfc_status and gfc_status_char. Remove gfc_ prefix of the gfc_show_*
+	functions and make them static. Add new gfc_dump_parse_tree
+	function.
+	* gfortran.h (gfc_option_t): Rename verbose into dump_parse_tree.
+	(gfc_status, gfc_status_char): Delete prototypes.
+	* error.c (gfc_status, gfc_status_char): Remove functions.
+	* scanner.c (gfc_new_file): Use printf instead of gfc_status.
+	* options.c (gfc_init_options): Rename verbose into dump_parse_tree.
+	(gfc_handle_module_path_options): Use gfc_fatal_error instead of
+	gfc_status and exit.
+	(gfc_handle_option): Rename verbose into dump_parse_tree.
+	* parse.c (gfc_parse_file): Use gfc_dump_parse_tree.
+
+2008-04-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+	    Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/25829 28655
+	* dump-parse-tree.c (gfc_show_code_node): Show new I/O parameters.
+	* gfortran.h (gfc_statement): Add ST_WAIT enumerator.
+	(gfc_open): Add pointers for decimal, encoding, round, sign,
+	asynchronous. (gfc_inquire): Add pointers for asynchronous, decimal,
+	encoding, pending, round, sign, size, id.
+	(gfc_wait): New typedef struct. (gfc_dt): Add pointers for id, pos,
+	asynchronous, blank, decimal, delim, pad, round, sign.
+	(gfc_exec_op): Add EXEC_WAIT enumerator. (gfc_code): Add pointer for
+	wait. (gfc_free_wait), (gfc_resolve_wait): New function prototypes.
+	* trans-stmt.h (gfc_trans_wait): New function prototype.
+	* trans.c (gfc_trans_code): Add case for EXEC_WAIT.
+	* io.c (io_tag): Add new tags for DECIMAL, ENCODING, ROUND, SIGN,
+	ASYCHRONOUS, ID. (match_open_element): Add matchers for new tags.
+	(gfc_free_open): Free new pointers. (gfc_resolve_open): Resolve new
+	tags. (gfc_resolve_open): Remove comment around check for allowed
+	values and ASYNCHRONOUS, update it.  Likewise for DECIMAL, ENCODING,
+	ROUND, and SIGN. (match_dt_element): Add matching for new tags.
+	(gfc_free_wait): New function. (gfc_resolve_wait): New function.
+	(match_wait_element): New function. (gfc_match_wait): New function.
+	* resolve.c (gfc_resolve_blocks): Add case for EXEC_WAIT.
+	(resolve_code): Add case for EXEC_WAIT. 
+	* st.c (gfc_free_statement): Add case for EXEC_WAIT.
+	* trans-io.c (ioparam_type): Add IOPARM_ptype_wait. (gfc_st_parameter):
+	Add "wait" entry. (iocall): Add IOCALL_WAIT enumerator.
+	(gfc_build_io_library_fndecls): Add function declaration for st_wait.
+	(gfc_trans_open): Add mask bits for new I/O tags.
+	(gfc_trans_inquire): Add mask bits for new I/O tags.
+	(gfc_trans_wait): New translation function.
+	(build_dt): Add mask bits for new I/O tags.
+	* match.c (gfc_match_if) Add matcher for "wait".
+	* match.h (gfc_match_wait): Prototype for new function.
+	* ioparm.def: Add new I/O parameter definitions.
+	* parse.c (decode_statement): Add match for "wait" statement.
+	(next_statement): Add case for ST_WAIT. (gfc_ascii_statement): Same.
+
+2008-04-03  Jakub Jelinek  <jakub@redhat.com>
+
+	PR fortran/35786
+	* openmp.c (resolve_omp_clauses): Diagnose if a clause symbol
+	isn't a variable.
+
+2008-04-03  Tom Tromey  <tromey@redhat.com>
+
+	* Make-lang.in (fortran_OBJS): New variable.
+
+2008-04-03  Paolo Bonzini  <bonzini@gnu.org>
+
+	* f95-lang.c (insert_block): Kill.
+
+2008-04-01  George Helffrich <george@gcc.gnu.org>
+
+	PR fortran/35154, fortran/23057
+	* trans-common.c (create_common):  Add decl to function
+	chain to preserve identifier scope in debug output.
+
+2008-04-01  Joseph Myers  <joseph@codesourcery.com>
+
+	* gfortran.texi: Include gpl_v3.texi instead of gpl.texi
+	* Make-lang.in (GFORTRAN_TEXI): Include gpl_v3.texi instead of
+	gpl.texi.
+
+2008-03-30  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35740
+	* resolve.c (resolve_function, resolve_call): If the procedure
+	is elemental do not look for noncopying intrinsics.
+
+2008-03-29  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35698
+	* trans-array.c (gfc_array_init_size): Set 'size' zero if
+	negative in one dimension.
+
+	PR fortran/35702
+	* trans-expr.c (gfc_trans_string_copy): Only assign a char
+	directly if the lhs and rhs types are the same.
+
+2008-03-28  Daniel Franke  <franke.daniel@gmail.com>
+	    Paul Richard Thomas <paul.richard.thomas@gmail.com>
+
+	PR fortran/34714
+	* primary.c (match_variable): Improved matching of function 
+	result variables.
+	* resolve.c (resolve_allocate_deallocate): Removed checks if
+	the actual argument for STAT is a variable.
+
+2008-03-28  Tobias Burnus  <burnus@net-b.de>
+
+	* symbol.c (gfc_get_default_type): Fix error message; option
+	-fallow_leading_underscore should be -fallow-leading-underscore
+
+2008-03-27  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35724
+	* iresolve.c (gfc_resolve_cshift): Check for NULL symtree in test for
+	optional argument attribute.
+
+2008-03-27  Tom Tromey  <tromey@redhat.com>
+
+	* Make-lang.in: Revert automatic dependency patch.
+
+2008-03-25  Tom Tromey  <tromey@redhat.com>
+
+	* Make-lang.in: Remove .o targets.
+	(fortran_OBJS): New variable.
+	(fortran/gfortranspec.o): Move to fortran/.  Reduce to variable
+	setting.
+	(GFORTRAN_D_OBJS): Update.
+	(GFORTRAN_TRANS_DEPS): Remove.
+
+2008-03-24  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34813
+	* resolve.c (resolve_structure_cons): It is an error to assign
+	NULL to anything other than a pointer or allocatable component.
+
+	PR fortran/33295
+	* resolve.c (resolve_symbol): If the symbol is a derived type,
+	resolve the derived type.  If the symbol is a derived type
+	function, ensure that the derived type is visible in the same
+	namespace as the function.
+
+2008-03-23  Tobias Schlüter  <tobi@gcc.gnu.org>
+
+	* trans.h: Use fold_build in build1_v, build2_v and build3_v
+	macros.
+	* trans-openmp.c (gfc_trans_omp_critical, gfc_trans_omp_single):
+	Don't use build2_v macro.
+
+2008-03-19  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/35152
+	* interface.c (gfc_procedure_use): Check for keyworded arguments in
+	procedures without explicit interfaces.
+
+2008-03-16  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35470
+	* resolve.c (check_assumed_size_reference):  Only visit the
+	first reference and look directly at the highest dimension.
+
+2008-03-15  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35184
+	* trans-array.c (gfc_conv_array_index_offset): Remove unnecessary
+	assert.
+
+2008-03-15  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/35584
+	* resolve.c (resolve_branch): Less strict and pessimistic warning
+	message.
+
+2008-03-11  Paolo Bonzini  <bonzini@gnu.org>
+
+	* f95-lang.c (LANG_HOOKS_CLEAR_BINDING_STACK): Delete.
+	(gfc_be_parse_file): Call clear_binding_stack from here.
+	(gfc_clear_binding_stack): Rename to clear_binding_stack.
+		
+2008-03-09  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/35474
+	* module.c (mio_symtree_ref): After providing a symbol for a
+	missing equivalence member, resolve and NULL the fixups.
+
+2008-03-09  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* invoke.texi (Error and Warning Options): Document
+	-Wline-truncation.
+
+2008-03-08  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/34956
+	* trans-array.c (gfc_conv_ss_startstride): Fix the logic to avoid
+	checking bounds of absent optional arguments.
+
+2008-03-06  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/33197
+	* intrinsic.c (add_functions): Add simplification routines for
+	ERF, DERF, ERFC and DERFC.
+	* decl.c (gfc_match_suffix, gfc_match_subroutine): Change GNU
+	extensions into Fortran 2008 features.
+	* intrinsic.h (gfc_simplify_erf, gfc_simplify_erfc): New
+	prototypes.
+	* simplify.c (gfc_simplify_erf, gfc_simplify_erfc): New functions.
+
+2008-03-03  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/33197
+	* intrinsic.c (add_functions): Modify intrinsics ACOSH, ASINH,
+	ATANH, ERF, ERFC and GAMMA. Add intrinsics BESSEL_{J,Y}{0,1,N},
+	ERFC_SCALED, LOG_GAMMA and HYPOT.
+	* intrinsic.h (gfc_check_hypot, gfc_simplify_hypot,
+	gfc_resolve_hypot): New prototypes.
+	* mathbuiltins.def: Add HYPOT builtin. Make complex versions of
+	ACOSH, ASINH and ATANH available.
+	* gfortran.h (GFC_ISYM_ERFC_SCALED, GFC_ISYM_HYPOT): New values.
+	* lang.opt: Add -std=f2008 option.
+	* libgfortran.h: Define GFC_STD_F2008.
+	* lang-specs.h: Add .f08 and .F08 file suffixes.
+	* iresolve.c (gfc_resolve_hypot): New function.
+	* parse.c (parse_contained): Allow empty CONTAINS for Fortran 2008.
+	* check.c (gfc_check_hypot): New function.
+	* trans-intrinsic.c (gfc_intrinsic_map): Define ERFC_SCALE builtin.
+	* options.c (set_default_std_flags): Allow Fortran 2008 by default.
+	(form_from_filename): Add .f08 suffix.
+	(gfc_handle_option): Handle -std=f2008 option.
+	* simplify.c (gfc_simplify_hypot): New function.
+	* gfortran.texi: Document Fortran 2008 status and file extensions.
+	* intrinsic.texi: Document new BESSEL_{J,Y}{0,1,N} intrinsics,
+	as well as HYPOT and ERFC_SCALED. Update documentation of ERF,
+	ERFC, GAMMA, LGAMMA, ASINH, ACOSH and ATANH.
+	* invoke.texi: Document the new -std=f2008 option.
+
+2008-03-02  Jakub Jelinek  <jakub@redhat.com>
+
+	* gfortranspec.c (lang_specific_driver): Update copyright notice
+	dates.
+
+2008-02-29  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35059
+	* expr.c (find_array_element): Modify traversing the constructor to
+	avoid trying to access NULL memory pointed to by next for the
+	last element. (find_array_section): Exit while loop if cons->next is
+	NULL.
+	* trans-expr.c (gfc_conv_scalar_char_value): Initialize gfc_typespec.
+	(gfc_conv_function_call): Same.
+	* decl.c (gfc_match_implicit): Same.
+	* trans-intrinsic.c (gfc_conv_intrinsic_sr_kind): Same.
+
+2008-02-28  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/31463
+	PR fortran/33950
+	PR fortran/34296
+	* lang.opt: Added -Wreturn-type.
+	* options.c (gfc_handle_option): Recognize -Wreturn-type.
+	* trans-decl.c (gfc_trans_deferred_vars): Emit warnings for funtions
+	where the result value is not set.
+	(gfc_generate_function_code): Likewise.
+	(generate_local_decl): Emit warnings for funtions whose RESULT
+	variable is not set.
+
+2008-02-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/34868
+	* trans-expr.c (gfc_conv_variable): Don't build indirect
+	references when explicit interface is mandated.
+	* resolve.c (resolve_formal_arglist): Set attr.always_explicit
+	on the result symbol as well as the procedure symbol.
+
+2008-02-27  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/33387
+	* trans.h: Remove prototypes for gfor_fndecl_math_exponent4,
+	gfor_fndecl_math_exponent8, gfor_fndecl_math_exponent10 and
+	gfor_fndecl_math_exponent16.
+	* f95-lang.c (build_builtin_fntypes): Add new function types.
+	(gfc_init_builtin_functions): Add new builtins for nextafter,
+	frexp, ldexp, fabs, scalbn and inf.
+	* iresolve.c (gfc_resolve_rrspacing): Don't add hidden arguments.
+	(gfc_resolve_scale): Don't convert type of second argument.
+	(gfc_resolve_set_exponent): Likewise.
+	(gfc_resolve_size): Don't add hidden arguments.
+	* trans-decl.c: Remove gfor_fndecl_math_exponent4,
+	gfor_fndecl_math_exponent8, gfor_fndecl_math_exponent10 and
+	gfor_fndecl_math_exponent16.
+	* trans-intrinsic.c (gfc_intrinsic_map): Remove intrinsics
+	for scalbn, fraction, nearest, rrspacing, set_exponent and
+	spacing.
+	(gfc_conv_intrinsic_exponent): Directly call frexp.
+	(gfc_conv_intrinsic_fraction, gfc_conv_intrinsic_nearest,
+	gfc_conv_intrinsic_spacing, gfc_conv_intrinsic_rrspacing,
+	gfc_conv_intrinsic_scale, gfc_conv_intrinsic_set_exponent): New
+	functions.
+	(gfc_conv_intrinsic_function): Use the new functions above.
+
+2008-02-26  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/35033
+	* interface.c (check_operator_interface): Show better line for error
+	messages; fix constrains for user-defined assignment operators.
+	(gfc_extend_assign): Fix constrains for user-defined assignment
+	operators.
+
+2008-02-26  Tom Tromey  <tromey@redhat.com>
+
+	* trans-io.c (set_error_locus): Remove old location code.
+	* trans-decl.c (gfc_set_decl_location): Remove old location code.
+	* f95-lang.c (gfc_init): Remove test of USE_MAPPED_LOCATION.
+	* scanner.c (gfc_gobble_whitespace): Remove old location code.
+	(get_file): Likewise.
+	(preprocessor_line): Likewise.
+	(load_file): Likewise.
+	(gfc_new_file): Likewise.
+	* trans.c (gfc_trans_runtime_check): Remove old location code.
+	(gfc_get_backend_locus): Likewise.
+	(gfc_set_backend_locus): Likewise.
+	* data.c (gfc_assign_data_value): Remove old location code.
+	* error.c (show_locus): Remove old location code.
+	* gfortran.h (gfc_linebuf): Remove old location code.
+	(gfc_linebuf_linenum): Remove old-location variant.
+
+2008-02-25  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/34729
+	* trans-const.c (gfc_build_string_const): Don't call gettext.
+	(gfc_build_localized_string_const): New function.
+	* trans-const.h (gfc_build_localized_string_const): New prototype.
+	* trans.c (gfc_trans_runtime_check): Use
+	gfc_build_localized_string_const instead of gfc_build_string_const.
+	(gfc_call_malloc): Likewise.
+	(gfc_allocate_with_status): Likewise.
+	(gfc_allocate_array_with_status): Likewise.
+	(gfc_deallocate_with_status): Likewise.
+	(gfc_call_realloc): Likewise.
+	* trans-io.c (gfc_trans_io_runtime_check): Likewise.
+
+2008-02-24  Tobias Schlüter  <tobi@gcc.gnu.org>
+
+	* arith.c: Update copyright years.
+	* arith.h: Likewise.
+	* array.c: Likewise.
+	* bbt.c: Likewise.
+	* check.c: Likewise.
+	* data.c: Likewise.
+	* data.h: Likewise.
+	* decl.c: Likewise.
+	* dependency.c: Likewise.
+	* dependency.h: Likewise.
+	* dump-parse-tree.c: Likewise.
+	* error.c: Likewise.
+	* expr.c: Likewise.
+	* gfc-internals.texi: Likewise.
+	* gfortran.h: Likewise.
+	* gfortran.texi: Likewise.
+	* gfortranspec.c: Likewise.
+	* interface.c: Likewise.
+	* intrinsic.c: Likewise.
+	* intrinsic.h: Likewise.
+	* intrinsic.texi: Likewise.
+	* invoke.texi: Likewise.
+	* io.c: Likewise.
+	* iresolve.c: Likewise.
+	* iso-c-binding.def: Likewise.
+	* iso-fortran-env.def: Likewise.
+	* lang-specs.h: Likewise.
+	* lang.opt: Likewise.
+	* libgfortran.h: Likewise.
+	* match.c: Likewise.
+	* match.h: Likewise.
+	* matchexp.c: Likewise.
+	* misc.c: Likewise.
+	* module.c: Likewise.
+	* openmp.c: Likewise.
+	* options.c: Likewise.
+	* parse.c: Likewise.
+	* parse.h: Likewise.
+	* primary.c: Likewise.
+	* resolve.c: Likewise.
+	* scanner.c: Likewise.
+	* simplify.c: Likewise.
+	* st.c: Likewise.
+	* symbol.c: Likewise.
+	* target-memory.c: Likewise.
+	* target-memory.h: Likewise.
+	* trans-array.h: Likewise.
+	* trans-const.h: Likewise.
+	* trans-stmt.h: Likewise.
+	* trans-types.c: Likewise.
+	* trans-types.h: Likewise.
+	* types.def: Likewise.
+
+2008-02-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35223
+	* simplify.c (gfc_simplify_ibclr), (gfc_simplify_ibits),
+	(gfc_simplify_ibset): Remove call to range_check.
+	(simplify_cmplx), (gfc_simplify_dble), (gfc_simplify_float)
+	(gfc_simplify_real): Add call gfc_clear_ts to initialize the
+	temporary gfc_typspec variable.
+
+2008-02-24  Tobias Schlüter  <tobi@gcc.gnu.org>
+
+	* trans-array.c (gfc_conv_descriptor_data_get,
+	gfc_conv_descriptor_data_set_internal,
+	gfc_conv_descriptor_data_addr, gfc_conv_descriptor_offset,
+	gfc_conv_descriptor_dtype, gfc_conv_descriptor_dimension,
+	gfc_conv_descriptor_stride, gfc_conv_descriptor_lbound,
+	gfc_conv_descriptor_ubound, gfc_trans_create_temp_array,
+	gfc_conv_array_transpose, gfc_grow_array,
+	gfc_trans_array_constructor_subarray,
+	gfc_trans_array_constructor_value, gfc_trans_scalarized_loop_end,
+	gfc_array_init_size, gfc_array_allocate, gfc_array_deallocate,
+	gfc_conv_array_initializer, gfc_trans_array_bounds,
+	gfc_trans_auto_array_allocation, gfc_trans_dummy_array_bias,
+	gfc_get_dataptr_offset, gfc_conv_array_parameter,
+	gfc_trans_dealloc_allocated, get_full_array_size,
+	gfc_duplicate_allocatable, structure_alloc_comps): Use fold_buildN
+	instead of buildN.
+	* trans-expr.c (gfc_conv_expr_present, gfc_conv_missing_dummy,
+	gfc_conv_component_ref, gfc_conv_cst_int_power,
+	gfc_conv_function_call, gfc_trans_structur_assign): Likewise.
+	* trans-common.c (create_common): Likewise.
+	* trans-openmp.c (gfc_trans_omp_atomic, gfc_trans_omp_do):
+	Likewise.
+	* trans-const.c (gfc_conv_constant_to_tree): Likewise.
+	* trans-stmt.c (gfc_trans_goto, gfc_trans_return, gfc_trans_do,
+	gfc_trans_integer_select, gfc_trans_character_select,
+	gfc_trans_forall_loop, compute_overall_iter_number,
+	gfc_trans_forall_1, gfc_evaluate_where_mask, gfc_trans_allocate,
+	gfc_trans_deallocate): Likewise.
+	* trans.c (gfc_build_addr_expr, gfc_trans_runtime_check,
+	gfc_allocate_with_status, gfc_allocate_array_with_status,
+	gfc_deallocate_with_status): Likewise.
+	* f95-lang.c (gfc_truthvalue_conversion): Likewise.
+	* trans-io.c (set_parameter_const, set_parameter_value,
+	set_parameter_ref, set_string, set_internal_unit, io_result,
+	set_error_locus, nml_get_addr_expr, transfer_expr): Likewise.
+	* trans-decl.c (gfc_build_qualified_array, build_entry_thunks,
+	gfc_get_fake_result_decl, gfc_trans_auto_character_variable,
+	gfc_generate_function_code): Likewise.
+	* convert.c (convert): Likewise.
+	* trans-intrinsic.c (gfc_conv_intrinsic_conversion,
+	build_fixbound_expr, build_fix_expr, gfc_conv_intrinsic_aint,
+	gfc_conv_intrinsic_int, gfc_conv_intrinsic_imagpart,
+	gfc_conv_intrinsic_conjg, gfc_conv_intrinsic_abs,
+	gfc_conv_intrinsic_cmplx, gfc_conv_intrinsic_mod,
+	gfc_conv_intrinsic_dim, gfc_conv_intrinsic_dprod,
+	gfc_conv_intrinsic_ctime, gfc_conv_intrinsic_fdate,
+	gfc_conv_intrinsic_ttynam, gfc_conv_intrinsic_minmax,
+	gfc_conv_intrinsic_minmax_char, gfc_conv_intrinsic_count,
+	gfc_conv_intrinsic_arith, gfc_conv_intrinsic_dot_product,
+	gfc_conv_intrinsic_minmaxloc, gfc_conv_intrinsic_minmaxval,
+	gfc_conv_intrinsic_btest, gfc_conv_intrinsic_not,
+	gfc_conv_intrinsic_ibits, gfc_conv_intrinsic_ishft,
+	gfc_conv_intrinsic_ichar, gfc_conv_intrinsic_size,
+	gfc_conv_intrinsic_array_transfer, gfc_conv_intrinsic_transfer,
+	gfc_conv_allocated, gfc_conv_associated, gfc_conv_intrinsic_trim,
+	gfc_conv_intrinsic_repeat): Likewise.
+
+2008-02-23  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR target/25477
+	* trans-expr.c (gfc_conv_power_op): Use BUILT_IN_CPOW{F,,L}.
+	* f95-lang.c (gfc_init_builtin_functions): Define BUILT_IN_CPOW{F,,L}.
+	* trans.h (gfor_fndecl_math_cpow, gfor_fndecl_math_cpowf,
+	gfor_fndecl_math_cpowl10, gfor_fndecl_math_cpowl16): Remove.
+	* trans-decl.c: Likewise.
+
+2008-02-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/35059
+	* expr.c (find_array_element): Modify traversing the constructor to
+	avoid trying to access NULL memory pointed to by next for the
+	last element. (find_array_section): Exit while loop if cons->next is
+	NULL.
+
+2008-02-22  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34907
+	* iresolve.c (resolve_mask_arg): Add gfc_clear_ts to initialize
+	structure.
+	(gfc_resolve_aint): Likewise.
+	(gfc_resolve_anint): Likewise.
+	(gfc_resolve_besn): Likewise.
+	(gfc_resolve_cshift): Likewise.
+	(gfc_resolve_ctime): Likewise.
+	(gfc_resolve_eoshift): Likewise.
+	(gfc_resolve_index_func): Likewise.
+	(gfc_resolve_isatty): Likewise.
+	(gfc_resolve_malloc): Likewise.
+	(gfc_resolve_rrspacing): Likewise.
+	(gfc_resolve_scale): Likewise.
+	(gfc_resolve_set_exponent): Likewise.
+	(gfc_resolve_spacing): Likewise.
+	(gfc_resolve_spacing): Likewise.
+	(gfc_resolve_fgetc): Likewise.
+	(gfc_resolve_fputc): Likewise.
+	(gfc_resolve_ftell): Likewise.
+	(gfc_resolve_ttynam): Likewise.
+	(gfc_resolve_alarm_sub): Likewise.
+	(gfc_resolve_mvbits): Likewise.
+	(gfc_resolve_getarg): Likewise.
+	(gfc_resolve_signal_sub): Likewise.
+	(gfc_resolve_exit): Likewise.
+	(gfc_resolve_flush): Likewise.
+	(gfc_resolve_free): Likewise.
+	(gfc_resolve_ctime_sub): Likewise.
+	(gfc_resolve_fgetc_sub): Likewise.
+	(gfc_resolve_fputc_sub): Likewise.
+	(gfc_resolve_fseek_sub): Likewise.
+	(gfc_resolve_ftell_sub): Likewise.
+	(gfc_resolve_ttynam_sub): Likewise.
+
+2008-02-22  Ralf Wildenhues  <Ralf.Wildenhues@gmx.de>
+
+	* gfc-internals.texi: Fix typos and markup nits.
+	* gfortran.texi: Likewise.
+	* intrinsic.texi: Likewise.
+
+2008-02-21  Richard Guenther  <rguenther@suse.de>
+
+	* trans-expr.c (gfc_conv_expr_op): Expand INTRINSIC_PARENTHESES
+	as unary PAREN_EXPR for real and complex typed expressions.
+	(gfc_conv_unary_op): Fold the built tree.
+
+2008-02-20  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34997
+	* match.c (gfc_match_name): Improve error message for '$'.
+
+2008-02-19  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/35030
+	* expr.c (gfc_check_pointer_assign): Add type and kind information
+	to type-mismatch message.
+	(gfc_check_assign): Unify error messages.
+
+2008-02-16  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/34952
+	* gfortran.texi: Create new section for unimplemented extensions.
+	Add "STRUCTURE and RECORD" and "ENCODE and DECODE statements".
+	Remove "smaller projects" list. Fix a few typos.
+
+2008-02-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* intrinsic.texi: Rename INDEX node to avoid clashing with
+	index.html on case-insensitive systems.
+
+2008-02-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/35150
+	* trans-expr.c (gfc_conv_function_call): Force evaluation of
+	se->expr.
+
+2008-02-10  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/35019
+	* lang.opt: Allow '-J<dir>' next to '-J <dir>', 
+	likewise '-I <dir>' and '-I<dir>'.
+
+2008-02-06  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
+
+	PR other/35107
+	* Make-lang.in (f951): Add $(GMPLIBS).
+
+2008-02-05  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/35037
+	* trans-common.c (build_field): Mark fields as volatile when needed.
+
+2008-02-05  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/35093
+	* data.c (gfc_assign_data_value): Only free "size" if
+	it has not already been freed.
+
+2008-02-05  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34945
+	* array.c (match_array_element_spec): Remove check for negative
+	array size.
+	(gfc_resolve_array_spec): Add check for negative size.
+
+2008-02-05  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/32315
+	* data.c (gfc_assign_data_value): Add bounds check for array
+	references.
+
+2008-02-04  Daniel Franke  <franke.daniel@gmail.com>
+
+	* resolve.c (resolve_where): Fix typo.
+	(gfc_resolve_where_code_in_forall): Likewise.
+
+2008-02-03  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/32760
+	* resolve.c (resolve_allocate_deallocate): New function.
+	(resolve_code): Call it for allocate and deallocate.
+	* match.c (gfc_match_allocate, gfc_match_deallocate) : Remove
+	the checking of the STAT tag and put in above new function.
+	* primary,c (match_variable): Do not fix flavor of host
+	associated symbols yet if the type is not known.
+
+2008-01-31  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34910
+	* expr.c (gfc_check_assign): It is an error to assign
+	to a sibling procedure.
+
+2008-01-30  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34975
+	* symbol.c (gfc_delete_symtree, gfc_undo_symbols): Rename
+	delete_symtree to gfc_delete_symtree.
+	* gfortran.h : Add prototype for gfc_delete_symtree.
+	* module.c (load_generic_interfaces): Transfer symbol to a
+	unique symtree and delete old symtree, instead of renaming.
+	(read_module): The rsym and the found symbol are the same, so
+	the found symtree can be deleted.
+
+	PR fortran/34429
+	* decl.c (match_char_spec): Remove the constraint on deferred
+	matching of functions and free the length expression.
+	delete_symtree to gfc_delete_symtree.
+	(gfc_match_type_spec): Whitespace.
+	(gfc_match_function_decl): Defer characteristic association for
+	all types except BT_UNKNOWN.
+	* parse.c (decode_specification_statement): Only derived type
+	function matching is delayed to the end of specification.
+
+2008-01-28  Tobias Burnus  <burnus@net-b.de>
+
+	PR libfortran/34980
+	* simplify.c (gfc_simplify_shape): Simplify rank zero arrays.
+
+2008-01-27  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34990
+	* array.c (gfc_check_constructor_type): Revert clearing the expression.
+
+2008-01-26  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34848
+	* trans-expr.c (gfc_conv_function_call): Don't call
+	gfc_add_interface_mapping if the expression is NULL.
+
+2008-01-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/31610
+	* trans-array.c (gfc_trans_create_temp_array): Remove call to
+	gcc_assert (integer_zerop (loop->from[n])).
+
+2008-01-25  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/34661
+	* resolve.c (resolve_where): Added check if user-defined assignment 
+	operator is an elemental subroutine.
+	(gfc_resolve_where_code_in_forall): Likewise.
+
+2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/33375
+	PR fortran/34858
+	* gfortran.h: Revert changes from 2008-01-17.
+	* match.c: Likewise.
+	* symbol.c: Likewise.
+	(gfc_undo_symbols): Undo namespace changes related to common blocks.
+
+2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/34202
+	* data.c (formalize_structure_cons): Skip formalization on
+	empty structures.
+
+2008-01-24  Daniel Franke  <franke.daniel@gmail.com>
+
+	* gfortran.texi (OpenMP): Extended existing documentation.
+	(contributors): Added major contributors of 2008 that were
+	not listed yet.
+	(proposed extensions): Removed implemented items.
+
+2008-01-24  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34872
+	* parse.c (next_statement) : If ST_GET_FCN_CHARACTERISTICS  is
+	seen, check for a statement label and, if present, delete it
+	and set the locus to the start of the statement.
+
+2008-01-22  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34875
+	* trans-io.c (gfc_trans_transfer): If the array reference in a
+	read has a vector subscript, use gfc_conv_subref_array_arg to
+	copy back the temporary.
+
+2008-01-22  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34848
+	* interface.c (compare_actual_formal): Fix adding type
+	to missing_arg_type for absent optional arguments.
+
+2008-01-22  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34907
+	* parse.c (parse_spec): Change = into ==.
+
+2008-01-22  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/34915
+	* expr.c (check_elemental): Fix check for valid data types.
+
+2008-01-22  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34899
+	* scanner.c (load_line): Support <tab><digit> continuation lines.
+	* invoke.texi (-Wtabs): Document this.
+
+2008-01-22  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34896
+	* module.c (read_module): Set use_rename attribute.
+
+2007-01-21  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34901
+	* interface.c (compare_parameter): Improved error message
+	for arguments of same type and mismatched kinds.
+
+2008-01-20  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34861
+	* resolve.c (resolve_entries): Do not do an array bounds check
+	if the result symbols are the same.
+
+	PR fortran/34854
+	* module.c (read_module) : Hide the symtree of the previous
+	version of the symbol if this symbol is renamed.
+
+2008-01-20  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34784
+	* array.c (gfc_check_constructor_type): Clear the expression ts
+	so that the checking starts from the deepest level of array
+	constructor.
+	* primary.c (match_varspec): If an unknown type is changed to
+	default character and the attempt to match a substring fails,
+	change it back to unknown.
+
+	PR fortran/34785
+	* trans-array.c (gfc_add_loop_ss_code) : If ss->string_length is
+	NULL for an array constructor, use the cl.length expression to
+	build it.
+	(gfc_conv_array_parameter): Change call to gfc_evaluate_now to
+	a tree assignment.
+
+2008-01-19  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/34817
+	PR fortran/34838
+	* iresolve.c (gfc_resolve_all):  Remove conversion of mask
+	argument to kind=1 by removing call to resolve_mask_arg().
+	(gfc_resolve_any):  Likewise.
+
+2008-01-19  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34760
+	* primary.c (match_variable): Handle FL_UNKNOWN without
+	uneducated guessing.
+	(match_variable): Improve error message.
+
+2008-01-18  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/32616
+	* interface.c (get_expr_storage_size): Return storage size
+	for array element designators.
+	(compare_actual_formal): Reject unequal string sizes for
+	assumed-shape dummy arguments. And fix error message for
+	array-sections with vector subscripts.
+
+2008-01-17  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34556
+	* simplify.c (is_constant_array_expr): New static function that returns
+	true if the given expression is an array and is constant.
+	(gfc_simplify_reshape): Use new function.
+
+2008-01-17  H.J. Lu  <hongjiu.lu@intel.com>
+
+	PR fortran/33375
+	* symbol.c (free_common_tree): Renamed to ...
+	(gfc_free_common_tree): This.  Remove static.
+	(gfc_free_namespace): Updated.
+
+	* gfortran.h (gfc_free_common_tree): New.
+
+	* match.c (gfc_match_common): Call gfc_free_common_tree () with
+	gfc_current_ns->common_root and set gfc_current_ns->common_root
+	to NULL on syntax error.
+
+2008-01-18  Richard Sandiford  <rsandifo@nildram.co.uk>
+
+	PR fortran/34686
+	* trans-expr.c (gfc_conv_function_call): Use proper
+	type for returned character pointers.
+
+2008-01-17  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34429
+	PR fortran/34431
+	PR fortran/34471
+	* decl.c : Remove gfc_function_kind_locus and
+	gfc_function_type_locus. Add gfc_matching_function.
+	(match_char_length): If matching a function and the length
+	does not match, return MATCH_YES and try again later.
+	(gfc_match_kind_spec): The same.
+	(match_char_kind): The same.
+	(gfc_match_type_spec): The same for numeric and derived types.
+	(match_prefix): Rename as gfc_match_prefix.
+	(gfc_match_function_decl): Except for function valued character
+	lengths, defer applying kind, type and charlen info until the
+	end of specification block.
+	gfortran.h (gfc_statement): Add ST_GET_FCN_CHARACTERISTICS.
+	parse.c (decode_specification_statement): New function.
+	(decode_statement): Call it when a function has kind = -1. Set
+	and reset gfc_matching function, as function statement is being
+	matched.
+	(match_deferred_characteristics): Simplify with a single call
+	to gfc_match_prefix. Do appropriate error handling. In any
+	case, make sure that kind = -1 is reset or corrected.
+	(parse_spec): Call above on seeing ST_GET_FCN_CHARACTERISTICS.
+	Throw an error if kind = -1 after last specification statement.
+	parse.h : Prototype for gfc_match_prefix.
+
+2008-01-16  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34796
+	* interface.c (compare_parameter): Allow AS_DEFERRED array
+	elements and reject attr.pointer array elemenents.
+	(get_expr_storage_size): Return storage size of elements of
+	assumed-shape and pointer arrays.
+
+2008-01-15  Sebastian Pop  <sebastian.pop@amd.com>
+
+	* f95-lang.c (gfc_init_builtin_functions): Initialize GOMP builtins
+	for flag_tree_parallelize_loops.
+
+2008-01-15  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR libfortran/34671
+	* iresolve.c (gfc_resolve_all):  Call resolve_mask_arg.
+	(gfc_resolve_any):  Likewise.
+	(gfc_resolve_count):  Likewise.  Don't append kind of
+	argument to function name.
+
+2008-01-13  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34665
+	* resolve.c (resolve_actual_arglist): For expressions,
+	also check for assume-sized arrays.
+	* interface.c (compare_parameter): Move F2003 character checks
+	here, print error messages here, reject elements of
+	assumed-shape array as argument to dummy arrays.
+	(compare_actual_formal): Update for the changes above.
+
+2008-01-13  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34763
+	* decl.c (contained_procedure): Only check directly preceeding state.
+
+2008-01-13  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34759
+	* check.c (gfc_check_shape): Accept array ranges of
+	assumed-size arrays.
+
+2008-01-12  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34432
+	* match.c (gfc_match_name): Don't error if leading character is a '(',
+	just return MATCH_NO.
+
+2008-01-11  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34722
+	* trans-io.c (create_dummy_iostat): Commit the symbol.
+
+2008-01-11  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34537
+	* simplify.c (gfc_simplify_transfer): Return NULL if the size
+	of the element is unavailable and only assign character length
+	to the result, if 'mold' is constant.
+
+2008-01-10  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34396
+	* trans-array.c (gfc_trans_array_ctor_element):  Use gfc_trans_string_copy
+	to assign strings and perform bounds checks on the string length.
+	(get_array_ctor_strlen): Remove bounds checking.
+	(gfc_trans_array_constructor): Initialize string length checking.
+	* trans-array.h : Add prototype for gfc_trans_string_copy.
+
+2008-01-08  Richard Guenther  <rguenther@suse.de>
+
+	PR fortran/34706
+	PR tree-optimization/34683
+	* trans-types.c (gfc_get_array_type_bounds): Use an array type
+	with known size for accesses if that is known.
+
+2008-01-08  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34476
+	* expr.c (find_array_element): Check that the array bounds are
+	constant before using them.  Use lower, as well as upper bound.
+	(check_restricted): Allow implied index variable.
+
+2008-01-08  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34681
+	* trans_array.c (gfc_trans_deferred_array): Do not null the
+	data pointer on entering scope, nor deallocate it on leaving
+	scope, if the symbol has the 'save' attribute.
+
+	PR fortran/34704
+	* trans_decl.c (gfc_finish_var_decl): Derived types with
+	allocatable components and an initializer must be TREE_STATIC.
+
+2008-01-07  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34672
+	* module.c (write_generic): Rewrite completely.
+	(write_module): Change call to write_generic.
+
+2008-01-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34659
+	* scanner.c (load_line): Do not count ' ' as printable when checking for
+	continuations.
+
+2008-01-06  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/34545
+	* module.c (load_needed): If the namespace has no proc_name
+	give it the module symbol.
+
+2008-01-06  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR fortran/34387
+	* trans-expr.c (gfc_conv_missing_dummy): Use a temporary to type convert
+	the dummy variable expression, test for NULL, and pass the variable
+	address to the called function.
+
+2007-01-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34658
+	* match.c (gfc_match_common): Remove blank common in
+	DATA BLOCK warning.
+	* resolve.c (resolve_common_vars): New function.
+	(resolve_common_blocks): Move checks to resolve_common_vars
+	and invoke that function.
+	(resolve_types): Call resolve_common_vars for blank commons.
+
+2008-01-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34655
+	* resolve.c (resolve_equivalence_derived): Reject derived types with
+	default initialization if equivalenced with COMMON variable.
+
+2008-01-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34654
+	* io.c (check_io_constraints): Disallow unformatted I/O for
+	internal units.
+
+2008-01-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34660
+	* resolve.c (resolve_formal_arglist): Reject dummy procedure in
+	ELEMENTAL functions.
+
+2008-01-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34662
+	* interface.c (compare_actual_formal): Reject parameter
+	actual to intent(out) dummy.
+
+2008-01-04  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/34557
+	* primary.c (match_varspec): Gobble whitespace before
+	checking for '('.
diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index 0b6fe4c13a98..18a81e951cb5 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -2944,15 +2944,20 @@ resolve_call (gfc_code *c)
 
   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
     {
-      gfc_find_symbol (csym->name, gfc_current_ns, 1, &sym);
+      gfc_symtree *st;
+      gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
+      sym = st ? st->n.sym : NULL;
       if (sym && csym != sym
 	      && sym->ns == gfc_current_ns
 	      && sym->attr.flavor == FL_PROCEDURE
 	      && sym->attr.contained)
 	{
 	  sym->refs++;
-	  csym = sym;
-	  c->symtree->n.sym = sym;
+	  if (csym->attr.generic)
+	    c->symtree->n.sym = sym;
+	  else
+	    c->symtree = st;
+	  csym = c->symtree->n.sym;
 	}
     }
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 5f1c4228f26b..fe53d67cfe8b 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2009-01-03  Paul Thomas  <pault@gcc.gnu.org>
+
+	PR fortran/38594
+	* gfortran.dg/host_assoc_call_3.f90: Make sure that the generic
+	interface still works, in addition to original tests.
+	* gfortran.dg/host_assoc_call_6.f90: New test.
+
 2009-01-03  Jakub Jelinek  <jakub@redhat.com>
 
 	PR c++/38705
diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90
index 6646270e5ac5..379b228e4cf1 100644
--- a/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90
+++ b/gcc/testsuite/gfortran.dg/host_assoc_call_3.f90
@@ -11,8 +11,10 @@ MODULE M1
   END INTERFACE
 CONTAINS
   SUBROUTINE S1(I)
+      i = 3
   END SUBROUTINE
   SUBROUTINE S2(F)
+      f = 4.0
   END SUBROUTINE
 END MODULE
 
@@ -36,9 +38,18 @@ CONTAINS
       end if
     END SUBROUTINE
   END SUBROUTINE
+  subroutine S4
+    integer :: check = 0
+    REAL :: rcheck = 0.0
+    call putaline(check)
+    if (check .ne. 3) call abort
+    call putaline(rcheck)
+    if (rcheck .ne. 4.0) call abort
+  end subroutine s4
 END MODULE
 
   USE M2
   CALL S3
+  call S4
 END
 ! { dg-final { cleanup-modules "M1 M2" } }
diff --git a/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90 b/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90
new file mode 100644
index 000000000000..60a5edc53c1d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/host_assoc_call_6.f90
@@ -0,0 +1,25 @@
+! { dg-do compile }
+!
+! PR fortran/38594, in which the symtree for the first
+! 'g' was being attached to the second. This is necessary
+! for generic interfaces(eg. hosts_call_3.f90) but makes
+! a mess otherwise.
+!
+! Contributed by Daniel Franke <dfranke@gcc.gnu.org>
+!
+MODULE m
+CONTAINS
+  SUBROUTINE g()
+  END SUBROUTINE
+  SUBROUTINE f()
+    CALL g()
+  CONTAINS
+    SUBROUTINE g()
+    END SUBROUTINE
+  END SUBROUTINE
+END MODULE
+
+  USE m
+  CALL g()
+END
+! { dg-final { cleanup-modules "m" } }
-- 
GitLab