diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 9c88eb8ead69effddfe849764578ac7dafdfa5d9..9e54b6f2bd05ff4f23406200caf6b4880de247e1 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -14,7 +14,7 @@
 	* interface.c (is_procptr_result): New function to check if an
 	expression is a procedure-pointer result.
 	(compare_actual_formal): Use it.
-
+^L
 Copyright (C) 2015 Free Software Foundation, Inc.
 
 Copying and distribution of this file, with or without modification,
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 5fc092e9acf3ec67e1507fd4855d22a16849bd11..a47a1a18ede4046c8726af3295814d6882820bbb 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,7 @@
+2015-01-02  Tobias Burnus  <burnus@net-b.de>
+
+	* gfortran.dg/coarray/collectives_4.f90: New.
+
 2015-01-02  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/57562
@@ -18,7 +22,7 @@
 
 	PR fortran/60507
 	* gfortran.dg/dummy_procedure_11.f90: New.
-
+^L
 Copyright (C) 2015 Free Software Foundation, Inc.
 
 Copying and distribution of this file, with or without modification,
diff --git a/gcc/testsuite/gfortran.dg/coarray/collectives_4.f90 b/gcc/testsuite/gfortran.dg/coarray/collectives_4.f90
new file mode 100644
index 0000000000000000000000000000000000000000..6e7be46eb3c48ef7f03e8f0d08a59c9b207d242d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray/collectives_4.f90
@@ -0,0 +1,24 @@
+! { dg-do run }
+!
+! CO_REDUCE
+!
+implicit none (type, external)
+intrinsic :: co_reduce
+integer :: stat
+integer :: i4, i4_2, i
+
+i4 = 21 * this_image()
+i4_2 = 21
+do i = 2, num_images()
+  i4_2 = i4_2 * 21 * i
+end do
+call co_reduce(i4, op_i4, stat=stat)
+if (stat /= 0) call abort()
+if (i4_2 /= i4) call abort()
+
+contains
+  pure integer function op_i4(a,b)
+    integer, value :: a, b
+    op_i4 = a * b
+  end function op_i4
+end
diff --git a/libgfortran/ChangeLog b/libgfortran/ChangeLog
index 24ad58ecb57d803a7d1691e38b2c04f7f6018d74..4a4ea96c86dba1e0c4213d0ec42a6ff169ade132 100644
--- a/libgfortran/ChangeLog
+++ b/libgfortran/ChangeLog
@@ -1,779 +1,9 @@
-2014-11-28  Bernd Schmidt  <bernds@codesourcery.com>
+2015-01-02  Tobias Burnus  <burnus@net-b.de>
 
-        * Makefile.am (AM_CFLAGS): Add -DLIBGFOR_MINIMAL if LIBGFOR_MINIMAL.
-        (gfor_io_src, gfor_heper_src, gfor_src): Split into minimal and
-        always included sources.
-        * Makefile.in: Regenerate.
-        * configure.ac (LIBGFOR_MINIMAL): New AM_CONDITIONAL.
-        * configure: Regenerate.
-        * caf/single.c (caf_runtime_error): Don't print messages if
-        LIBGFOR_MINIMAL.
-        * runtime/compile_options.c (fatal_error_in_progress,
-        show_signal, backtrace_handler, maybe_find_addr2line): Guard with
-        !defined LIBGFOR_MINIMAL.
-        (set_options): Likewise for the backtrace code.
-        * runtime/minimal.c: New file.
-
-2014-11-25  Uros Bizjak  <ubizjak@gmail.com>
-
-	* intrinsics/env.c (getenv): Remove unused variable res_len.
-
-2014-11-24  John David Anglin  <danglin@gcc.gnu.org>
-
-	* configure.ac: Guard include of <ieeefp.h>.
-	* configure: Rebuilt.
-
-2014-11-21  H.J. Lu  <hongjiu.lu@intel.com>
-
-	PR bootstrap/63784
-	* configure: Regenerated.
-
-2014-11-16  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/60324
-	* intrinsics/random.c (kiss_size): Rename to KISS_SIZE, make it a
-	macro instead of a variable.
-	(random_seed_i4): Make seed correct size, remove assert, KISS_SIZE
-	related changes.
-	(random_seed_i8): KISS_SIZE related changes.
-
-2014-11-13  Marek Polacek  <polacek@redhat.com>
-
-	* intrinsics/access.c: Include <stdlib.h>.
-	* intrinsics/chdir.c: Likewise.
-	* intrinsics/chmod.c: Likewise.
-	* intrinsics/link.c: Likewise.
-	* intrinsics/perror.c: Likewise.
-	* intrinsics/rename.c: Likewise.
-	* intrinsics/symlnk.c: Likewise.
-	* intrinsics/unlink.c: Likewise.
-
-2014-11-13  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/60324
-	* configure: Regenerated.
-	* configure.ac (AM_CFLAGS): Add Werror=vla.
-	* libgfortran.h (gfc_alloca): Remove macro.
-	(fc_strdup_notrim): New prototype.
-	* intrinsics/access.c (access_func): Use fc_strdup rather than
-	stack allocation.
-	* intrinsics/chdir.c (chdir_i4_sub): Likewise.
-	(chdir_i8_sub): Likewise.
-	* intrinsics/chmod.c (chmod_internal): New function, move logic
-	here.
-	(chmod_func): Call chmod_internal.
-	* intrinsics/env.c (getenv): Use fc_strdup rather than stack
-	allocation.
-	(get_environment_variable_i4): Likewise.
-	* intrinsics/execute_command_line.c (execute_command_line):
-	Likewise.
-	* intrinsics/hostnm.c (hostnm_0): New function, use static buffer
-	rather than VLA.
-	(hostnm_i4_sub): Call hostnm_0.
-	(hostnm_i8_sub): Likewise.
-	(hostnm): Likewise.
-	* intrinsics/link.c (link_internal): New function, use fc_strdup
-	rather than stack allocation.
-	(link_i4_sub): Call link_internal.
-	(link_i8_sub): Likewise.
-	(link_i4): Likewise.
-	(link_i8): Likewise.
-	* intrinsics/perror.c (perror_sub): Use fc_strdup rather than
-	stack allocation.
-	* intrinsics/random.c (random_seed_i4): Use static buffer rather
-	than VLA, use _Static_assert to make sure it's big enough.
-	* intrinsics/rename.c (rename_internal): New function, use
-	fc_strdup rather than stack allocation.
-	(rename_i4_sub): Call rename_internal.
-	(rename_i8_sub): Likewise.
-	(rename_i4): Likewise.
-	(rename_i8): Likewise.
-	* intrinsics/stat.c (stat_i4_sub_0): Use fc_strdup rather than
-	stack allocation.
-	(stat_i8_sub_0): Likewise.
-	* intrinsics/symlink.c (symlnk_internal): New function, use
-	fc_strdup rather than stack allocation.
-	(symlnk_i4_sub): Call symlnk_internal.
-	(symlnk_i8_sub): Likewise.
-	(symlnk_i4): Likewise.
-	(symlnk_i8): Likewise.
-	* intrinsics/system.c (system_sub): Use fc_strdup rather than
-	stack allocation.
-	* intrinsics/unlink.c (unlink_i4_sub): Likewise.
-	* io/file_pos.c (READ_CHUNK): Make it a macro rather than variable.
-	* io/list_read.c (nml_get_obj_data): Use fixed stack buffer, fall
-	back to xmalloc/free for large sizes.
-	* io/read.c (read_f): Likewise.
-	* io/transfer.c (MAX_READ): Make it a macro rather than variable.
-	(WRITE_CHUNK): Likewise.
-	* io/write_float.def (write_float): Use fixed stack buffer, fall
-	back to xmalloc/free for large sizes.
-	* runtime/string.c (fc_strdup_notrim): New function.
-
-2014-11-11  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR target/63610
-	* configure: Regenerate.
-
-2014-11-10  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/47007
-	PR libfortran/61847
-	* config.h.in: Regenerated.
-	* configure: Regenerated.
-	* configure.ac (AC_CHECK_HEADERS_ONCE): Check for xlocale.h.
-	(AC_CHECK_FUNCS_ONCE): Check for newlocale, freelocale, uselocale,
-	strerror_l.
-	* io/io.h (locale.h): Include.
-	(xlocale.h): Include if present.
-	(c_locale): New variable.
-	(old_locale): New variable.
-	(old_locale_ctr): New variable.
-	(old_locale_lock): New variable.
-	(st_parameter_dt): Add old_locale member.
-	* io/transfer.c (data_transfer_init): Set locale to "C" if doing
-	formatted transfer.
-	(finalize_transfer): Reset locale to previous.
-	* io/unit.c (c_locale): New variable.
-	(old_locale): New variable.
-	(old_locale_ctr): New variable.
-	(old_locale_lock): New variable.
-	(init_units): Init c_locale, init old_locale_lock.
-	(close_units): Free c_locale.
-	* runtime/error.c (locale.h): Include.
-	(xlocale.h): Include if present.
-	(gf_strerror): Use strerror_l if available. Reset locale to
-	LC_GLOBAL_LOCALE for strerror_r branch.
-
-2014-10-20  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/63589
-	* configure.ac: Check for strtok_r.
-	* runtime/main.c (gfstrtok_r): Fallback implementation of
-	strtok_r.
-	(find_addr2line): Use strtok_r to split PATH.
-	* config.h.in: Regenerated.
-	* configure: Regenerated.
-
-2014-10-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* ieee/ieee_helper.c (ieee_is_finite_*, ieee_is_nan_*,
-	ieee_is_negative_*, ieee_is_normal_*, ieee_copy_sign_*,
-	ieee_unordered_*, ieee_logb_*, ieee_rint_*, ieee_scalb_*,
-	ieee_rem_*, ieee_next_after_*): Remove functions.
-	* gfortran.map (GFORTRAN_1.5): Remove corresponding symbols.
-
-2014-10-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR libgfortran/63460
-	* io/unit.c (init_units): Initialize the DELIM flag to
-	UNSPECIFIED for the STDIN unit so that the flag is
-	correctly set later.
-
-2014-10-01  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* intrinsics/pack_generic.c (pack_s_internal): Fix
-	-Wmaybe-uninitialized warning.
-	* m4/unpack.m4 (unpack0_'rtype_code`): Likewise.
-	(unpack1_'rtype_code`): Likewise.
-	* generated/unpack_*.m4: Regenerated.
-
-2014-09-30  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* configure.ac (AM_CFLAGS): Add
-	-Werror=implicit-function-declaration.
-	* Makefile.in: Regenerated.
-	* aclocal.m4: Regenerated.
-	* configure: Regenerated.
-
-2014-09-25  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (_gfortran_caf_co_broadcast): New prototype.
-	* caf/single.c (_gfortran_caf_co_broadcast): New.
-
-2014-09-18  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/62768
-	* io/inquire.c (inquire_via_unit): Use gfc_unit.filename also when
-	HAVE_TTYNAME{_R} is not defined.
-
-2014-09-17  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/62768
-	* io/io.h (gfc_unit): Store C string for the filename.
-	* io/close.c (st_close): Use gfc_unit.filename.
-	* io/inquire.c (inquire_via_unit): Likewise.
-	* io/open.c (new_unit): Likewise.
-	(already_open): Likewise, unlink file before freeing filename.
-	* io/unit.c (init_units): Likewise.
-	(close_unit_1): Likewise.
-	(filename_from_unit): Likewise.
-	* io/unix.c (compare_file_filename): Likewise.
-	(find_file0): Likewise.
-	(delete_file): Likewise.
-
-2014-09-10  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* io/transfer.c (read_block_form): Fix pad status check (found by
-	Thomas Schwinge with -Wlogical-not-parentheses).
-
-2014-08-31  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (_gfortran_caf_send, _gfortran_caf_get,
-	_gfortran_caf_sendget): Update prototype.
-	* caf/single.c (_gfortran_caf_send, _gfortran_caf_get,
-	_gfortran_caf_sendget): Handle may_require_tmp.
-
-2014-08-20  Steven G. Kargl  <kargl@gcc.gnu.org>
-
-	PR libgfortran/62188
-	* m4/bessel.m4: Avoid indexing off the end of an array.
-	* generated/bessel_r10.c: Regenerated.
-	* generated/bessel_r16.c: Ditto.
-	* generated/bessel_r4.c: Ditto.
-	* generated/bessel_r8.c: Ditto.
-
-2014-08-14  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (caf_register_t): Update for critical.
-	(_gfortran_caf_critical, _gfortran_caf_end_critical): Remove.
-	(_gfortran_caf_lock, _gfortran_caf_unlock): Add.
-	* caf/single.c (_gfortran_caf_register): Handle locking
-	variables.
-	(_gfortran_caf_sendget): Re-name args for consistency.
-	(_gfortran_caf_lock, _gfortran_caf_unlock): Add.
-
-2014-08-04  Jakub Jelinek  <jakub@redhat.com>
-
-	* runtime/memory.c (xmallocarray): Avoid division for the common case.
-
-2014-07-20  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR libgfortran/61632
-	* io/format.c (format_error): Avoid invalid string pointer by
-	using the fortran string length values to generate error string.
-	(parse_format): Allocate the null terminator for the format
-	string.
-
-2014-07-12  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (_gfortran_caf_atomic_define,
-	_gfortran_caf_atomic_ref, _gfortran_caf_atomic_op,
-	_gfortran_caf_atomic_cas): New prototypes.
-	* caf/single.c (_gfortran_caf_atomic_define,
-	_gfortran_caf_atomic_ref, _gfortran_caf_atomic_op,
-	_gfortran_caf_atomic_cas): New functions.
-
-2014-07-10  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* config/fpu-*.h (get_fpu_rounding_mode, set_fpu_rounding_mode,
-	support_fpu_rounding_mode): Clean up, mark unreachable code as such.
-
-2014-07-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* libgfortran.h (support_fpu_underflow_control,
-	get_fpu_underflow_mode, set_fpu_underflow_mode): New prototypes.
-	* config/fpu-*.h (support_fpu_underflow_control,
-	get_fpu_underflow_mode, set_fpu_underflow_mode):
-	New functions.
-	* ieee/ieee_arithmetic.F90: Support underflow control.
-
-2014-07-08  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
-
-	* config/fpu-sysv.h (get_fpu_rounding_mode): Use FP_RN, FP_RP,
-	FP_RM, FP_RZ unconditionally.
-	(set_fpu_rounding_mode): Likewise.
-
-2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* libgfortran.h: Assume __GNUC__.
-
-2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* runtime/stop.c: Use C11 _Noreturn.
-	* libgfortran.h: Use C11 _Noreturn in prototypes.
-	Move REALPART, IMAGPART and COMPLEX_ASSIGN macros...
-	* intrinsics/c99_functions.c: ... here.
-
-2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* config/fpu-387.h, config/fpu-aix.h, config/fpu-sysv.h,
-	config/fpu-glibc.h: Use static assertions.
-
-2014-07-05  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
-
-	* configure, config.h.in: Regenerate.
-	* config/fpu-sysv.h: Include <assert.h>.
-
-2014-07-02  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* config/fpu-glibc.h: Fix comment about FE_DENORMAL.
-
-2014-07-02  Uros Bizjak  <ubizjak@gmail.com>
-
-	* configure.host (ieee_flags): Add -mieee for alpha*.
-
-	* config/fpu-glibc.h (support_fpu_rounding_mode): Correctly handle
-	GFC_FPE_UPWARD, GFC_FPE_DOWNWARD and GFC_FPE_TOWARDZERO.
-	* config/fpu-aix.h (support_fpu_rounding_mode): Ditto.
-
-2014-06-29  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	* config/fpu-387.h (my_fenv_t): Amend structure so it also works
-	on mingw32.
-
-2014-06-28  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR libgfortran/61640
-	* io/list_read.c (next_char_internal): Adjust the read length to
-	a single wide character. (eat_spaces): Add missing paren.
-	* io/unix.c (mem_read4): Use the correct mem_alloc function for
-	wide character internal reads.
-
-2014-06-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR fortran/29383
-	* configure.host: Add checks for IEEE support, rework priorities.
-	* configure.ac: Define IEEE_SUPPORT, check for fpsetsticky and
-	fpresetsticky.
-	* configure: Regenerate.
-	* Makefile.am: Build new ieee files, install IEEE_* modules.
-	* Makefile.in: Regenerate.
-	* gfortran.map (GFORTRAN_1.6): Add new symbols.
-	* libgfortran.h (get_fpu_trap_exceptions, set_fpu_trap_exceptions,
-	support_fpu_trap, set_fpu_except_flags, support_fpu_flag,
-	support_fpu_rounding_mode, get_fpu_state, set_fpu_state): New
-	prototypes.
-	* config/fpu-*.h (get_fpu_trap_exceptions,
-	set_fpu_trap_exceptions, support_fpu_trap, set_fpu_except_flags,
-	support_fpu_flag, support_fpu_rounding_mode, get_fpu_state,
-	set_fpu_state): New functions.
-	* ieee/ieee_features.F90: New file.
-	* ieee/ieee_exceptions.F90: New file.
-	* ieee/ieee_arithmetic.F90: New file.
-	* ieee/ieee_helper.c: New file.
-
-2014-06-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR libgfortran/61499
-	* io/list_read.c (eat_spaces): Use a 'for' loop instead of
-	'while' loop to skip the loop if there are no bytes left in the
-	string. Only seek if actual spaces can be skipped.
-
-2014-06-25  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/single.c (assign_char4_from_char1, assign_char1_from_char4,
-	convert_type): New static functions.
-	(_gfortran_caf_get, _gfortran_caf_send): Use them.
-
-2014-06-19  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/single.c (_gfortran_caf_co_sum, _gfortran_caf_co_max,
-	_gfortran_caf_co_min): Fix stat setting.
-
-2014-06-17  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (gfc_descriptor_t): New typedef.
-	(caf_vector_t): Update.
-	(_gfortran_caf_co_sum, _gfortran_caf_co_max, _gfortran_caf_co_min):
-	Remove vector-subscript argument.
-	(_gfortran_caf_co_send, _gfortran_caf_co_get,
-	_gfortran_caf_co_sendget): New.
-	* caf/single.c (_gfortran_caf_co_sum, _gfortran_caf_co_max,
-	_gfortran_caf_co_min): Remove vector-subscript argument.
-	(_gfortran_caf_co_send, _gfortran_caf_co_get,
-	_gfortran_caf_co_sendget): New.
-
-2014-06-17  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* libgfortran.h (xmallocarray): New prototype.
-	* runtime/memory.c (xmallocarray): New function.
-	(xcalloc): Check for nonzero separately instead of multiplying.
-	* generated/*.c: Regenerated.
-	* intrinsics/cshift0.c (cshift0): Call xmallocarray instead of
-	xmalloc.
-	* intrinsics/eoshift0.c (eoshift0): Likewise.
-	* intrinsics/eoshift2.c (eoshift2): Likewise.
-	* intrinsics/pack_generic.c (pack_internal): Likewise.
-	(pack_s_internal): Likewise.
-	* intrinsics/reshape_generic.c (reshape_internal): Likewise.
-	* intrinsics/spread_generic.c (spread_internal): Likewise.
-	(spread_internal_scalar): Likewise.
-	* intrinsics/string_intrinsics_inc.c (string_trim): Likewise.
-	(string_minmax): Likewise.
-	* intrinsics/transpose_generic.c (transpose_internal): Likewise.
-	* intrinsics/unpack_generic.c (unpack_internal): Likewise.
-	* io/list_read.c (nml_touch_nodes): Don't cast xmalloc return value.
-	* io/transfer.c (st_set_nml_var): Call xmallocarray instead of
-	xmalloc.
-	* io/unit.c (get_internal_unit): Likewise.
-	(filename_from_unit): Don't cast xmalloc return value.
-	* io/write.c (nml_write_obj): Likewise, formatting.
-	* m4/bessel.m4 (bessel_jn_r'rtype_kind`): Call xmallocarray
-	instead of xmalloc.
-	(besse_yn_r'rtype_kind`): Likewise.
-	* m4/cshift1.m4 (cshift1): Likewise.
-	* m4/eoshift1.m4 (eoshift1): Likewise.
-	* m4/eoshift3.m4 (eoshift3): Likewise.
-	* m4/iforeach.m4: Likewise.
-	* m4/ifunction.m4: Likewise.
-	* m4/ifunction_logical.m4 (name`'rtype_qual`_'atype_code):
-	Likewise.
-	* m4/in_pack.m4 (internal_pack_'rtype_ccode`): Likewise.
-	* m4/matmul.m4 (matmul_'rtype_code`): Likewise.
-	* m4/matmull.m4 (matmul_'rtype_code`): Likewise.
-	* m4/pack.m4 (pack_'rtype_code`): Likewise.
-	* m4/reshape.m4 (reshape_'rtype_ccode`): Likewise.
-	* m4/shape.m4 (shape_'rtype_kind`): Likewise.
-	* m4/spread.m4 (spread_'rtype_code`): Likewise.
-	(spread_scalar_'rtype_code`): Likewise.
-	* m4/transpose.m4 (transpose_'rtype_code`): Likewise.
-	* m4/unpack.m4 (unpack0_'rtype_code`): Likewise.
-	(unpack1_'rtype_code`): Likewise.
-	* runtime/convert_char.c (convert_char1_to_char4): Likewise.
-	(convert_char4_to_char1): Simplify.
-	* runtime/environ.c (init_unformatted): Call xmallocarray instead
-	of xmalloc.
-	* runtime/in_pack_generic.c (internal_pack): Likewise.
-
-2014-06-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
-
-	PR libfortran/60468
-	* configure.ac: Include <math.h> when checking for fp_except_t
-	and fp_rnd_t types.
-	* configure: Regenerate.
-
-2014-06-08  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/56981
-	* io/unix.h (struct stream_vtable): Add new member function,
-	markeor.
-	(smarkeor): New inline function.
-	(flush_if_unbuffered): Remove prototype.
-	* io/unix.c (raw_markeor): New function.
-	(raw_vtable): Initialize markeor member.
-	(buf_markeor): New function.
-	(buf_vtable): Initialize markeor member.
-	(mem_vtable): Likewise.
-	(mem4_vtable): Likewise.
-	(flush_if_unbuffered): Remove function.
-	* io/transfer.c (next_record): Call smarkeor instead of
-	flush_if_unbuffered.
-
-2014-05-27  Uros Bizjak  <ubizjak@gmail.com>
-
-	* intrinsics/getcwd.c: Include stdlib.h.
-
-2014-05-26  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* libgfortran.h (xrealloc): New prototype.
-	* runtime/memory.c (xrealloc): New function.
-	* io/fbuf.c (fbuf_alloc): Use xrealloc.
-	* io/list_read.c (push_char_default): Likewise.
-	(push_char4): Likewise.
-
-2014-05-26  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/61310
-	* intrinsics/ctime.c (strctime): Rename to gf_ctime, use snprintf
-	instead of strftime.
-	(fdate): Use gf_ctime.
-	(fdate_sub): Likewise.
-	(ctime): Likewise.
-	(ctime_sub): Likewise.
-
-2014-05-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
-
-	PR libgfortran/55117
-	* io/list_read.c (extended_look_ahead): New helper function to
-	scan the namelist name and look for matches with the new '+'
-	extended type parent indicator.  (str_comp_extended): New
-	helper function to compare the namelist name with the varname
-	namelist. (find_nml_name): Use the new helper functions to match
-	the extended type varnames.
-
-2014-05-23  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/61173
-	* io/list_read.c (eat_spaces): If the next character pointed to
-	is a space, don't seek, must be at the end.
-
-2014-05-23  Hans-Peter Nilsson  <hp@axis.com>
-
-	* configure.ac [with_newlib] (HAVE_STRNLEN, HAVE_STRNDUP): Define.
-	* configure: Regenerate.
-
-2014-05-23  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/60324
-	* runtime/string.c: Include stdlib.h.
-
-2014-05-22  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/60324
-	* config.h.in: Regenerated.
-	* configure: Regenerated.
-	* configure.ac (AC_CHECK_FUNCS_ONCE): Check for strnlen and
-	strndup.
-	* libgfortran.h (fc_strdup): New prototype.
-	* runtime/string.c (strnlen): New fallback function.
-	(strndup): New fallback function.
-	(fc_strdup): New function.
-	* io/close.c (st_close): Use fc_strdup.
-	* io/open.c (new_unit): Likewise.
-	(already_open): Likewise.
-	* io/unit.c (filename_from_unit): Likewise.
-	* io/unix.c (unpack_filename): Remove function.
-	(regular_file): Rename to regular_file2, add path argument.
-	(regular_file): New function calling regular_file2.
-	(compare_file_filename): Use fc_strdup.
-	(find_file): Likewise.
-	(delete_file): Likewise.
-	(file_exists): Likewise.
-	(file_size): Likewise.
-	(inquire_sequential): Likewise.
-	(inquire_direct): Likewise.
-	(inquire_formatted): Likewise.
-	(inquire_access): Likewise.
-	* io/unix.h (unpack_filename): Remove prototype.
-	* runtime/main.c (please_free_exe_path_when_done): Change type to
-	bool.
-	(store_exe_path): Use malloced buffer, grow as needed.
-
-2014-05-17  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/52539
-	* io/io.h (gfc_unit): New function pointers *next_char_fn_ptr
-	and *push_char_fn_ptr.
-	*io/list_read.c (next_char): Create macro with this name to call
-	the new function pointer. Split the original next_char function
-	into three new functions. (next_char_default, next_char_internal,
-	next_char_utf8): New functions. (push_char): Create macro with
-	this name to call new function pointer. Split the original
-	push_char into three new functions. (push_char_default,
-	push_char_internal, push_char4): New functions. (set_workers):
-	New function to initilize the function pointers depending on the
-	type of IO to be performed. (list_formatted_read_scalar): Use
-	set_workers function. (finish_list_read): Likewise.
-	(namelist_read): Likewise.
-	(nml_get_obj_data): Use push_char_default.
-
-2014-05-16  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/61187
-	* io/unix.c (raw_close): Check if s->fd is -1.
-	(fd_to_stream): Check return value of fstat(), handle error.
-
-2014-05-12  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	PR libfortran/61035
-	* intrinsics/getcwd.c (getcwd_i4_sub): Avoid potentially large
-	stack allocation, avoid extra copying in the common case.
-
-2014-05-12  Janne Blomqvist  <jb@gcc.gnu.org>
-
-	* configure.ac (AM_CFLAGS): Use -std=gnu11.
-	(CFLAGS): Likewise.
-	* configure: Regenerated.
-
-2014-05-11  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (_gfortran_caf_num_images): Change type of
-	second argument to int.
-	* caf/mpi.c (_gfortran_caf_num_images): Ditto.
-	* caf/single.c (_gfortran_caf_num_images): Ditto.
-
-2014-05-08  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (caf_vector_t, _gfortran_caf_co_sum,
-	_gfortran_caf_co_min, _gfortran_caf_co_max): Declare
-	* caf/single.c
-
-2014-05-06  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/61049
-	* io/list_read.c (list_formatted_read_scalar): Use eat_separator
-	and delete extraneous code.
-
-2014-04-30  Tobias Burnus  <burnus@net-b.de>
-
-	* caf/libcaf.h (_gfortran_caf_this_image, _gfortran_caf_num_images):
-	New prototypes.
-	(_gfortran_caf_init): Change prototype.
-	(mpi_token_t): New typedef.
-	(TOKEN): New define.
-	* caf/mpi.c (_gfortran_caf_this_image, _gfortran_caf_num_images):
-	New functions.
-	(_gfortran_caf_init): Update.
-	(_gfortran_caf_finalize, _gfortran_caf_register,
-	_gfortran_caf_deregister): Use mpi_token_t.
-	* caf/single.c (_gfortran_caf_this_image, _gfortran_caf_num_images):
-	New functions.
-	(_gfortran_caf_init): Update.
-	(_gfortran_caf_finalize, _gfortran_caf_register,
-	_gfortran_caf_deregister): Use mpi_token_t, simplify.
-
-2014-04-26  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/52539
-	* io/list_read.c: Add uchar typedef. (push_char4): New function
-	to save kind=4 character. (next_char_utf8): New function to read
-	a single UTF-8 encoded character value. (read_chracter): Update
-	to use the new functions for reading UTF-8 strings.
-	(list_formatted_read_scalar): Update to handle list directed
-	reads of UTF-8 strings. (nml_read_obj): Likewise update for
-	UTF-8 strings in namelists.
-	* io/write.c (nml_write_obj): Add kind=4 character support for
-	namelist writes.
-
-2014-04-24  Kyrylo Tkachov  <kyrylo.tkachov@arm.com>
-
-	* configure.ac: Quote usage of ac_cv_func_clock_gettime in if test.
-	* configure: Regenerate.
-
-2014-04-22  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
-
-	* config/fpu-387.h [__sun__ && __svr4__]: Remove SSE execution
-	check.
-
-2014-04-11  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/60810
-	io/unit.c (is_trim_ok): If internal unit is array, do not trim.
-
-2014-03-21  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/60148
-	* io/transfer.c (data_transfer_init): If std= was specified, set
-	delim status to DELIM_NONE of no other was specified.
-
-2014-03-18  Ulrich Weigand  <Ulrich.Weigand@de.ibm.com>
-
-	* configure.ac: Check for presence of fcntl.
-	* configure: Regenerate.
-	* config.h.in: Regenerate.
-	* io/unix.c (set_close_on_exec): Check for HAVE_FCNTL.
-
-2014-03-17  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/48600
-	* io/list_read.c (list_formatted_read_scalar): Do not use
-	eat_separator. Explicitly set the comma and end-of-line flags.
-	Check for END condition from finish_separator.
-
-2014-03-15  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/58324
-	* io/list_read.c (finish_list_read): Read one character to check
-	for the end of the file.  If it is the end, then issue the file
-	end error message.  If not, use eat_line to reach the end
-	without giving error.  The next attempt to read will then
-	issue the error as described above.
-
-2014-03-12  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/38199
-	* io/read.c (read_decimal): Quickly skip spaces to avoid calls
-	to next_char.
-	* io/unit.c (is_trim_ok): New helper function to check various
-	conditions to see if its OK to trim the internal unit string.
-	(get_internal_unit): Use LEN_TRIM to shorten selected internal
-	unit strings for optimizing READ. Enable this optimization for
-	formatted READ.
-	* io/list_read.c (finish_list_read): Don't call eat_line for
-	internal units.
-
-2014-03-08  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/38199
-	* io/list_read.c (next_char): Mark unlikely error checks.
-	(eat_spaces): For character array reading, skip ahead over
-	spaces rather than call next_char multiple times.
-
-2014-03-08  Tobias Burnus  <burnus@net-b.de>
-
-	* libgfortran.h (unlikely, likely): Add usage comment.
-
-2014-03-08  Dominique d'Humieres  <dominiq@lps.ens.fr>
-
-	PR libgfortran/60128
-	* io/write_float.def (output_float): Remove unused variable
-	nzero_real. Replace a double space with a single one.
-	(determine_en_precision): Fix wrong handling of the EN format.
-
-2014-03-03  Jerry DeLisle  <jvdelisle@gcc.gnu>
-
-	PR libfortran/60148
-	* io/inquire.c (inquire_via_unit): In the case of
-	DELIM_UNSPECIFIED set inquire return string to "NONE".
-	* io/list_read.c (read_character): In the case of DELIM_NONE and
-	namelists, complete the character read using the namelist
-	variable length.
-	* io/open.c (new_unit): Don't set delim status to none if not
-	specified so that DELIM_UNSPECIFIED can be used later.
-	* io/transfer.c (data_transfer_init): For namelist I/O, if the
-	unit delim status is unspecified set the current status to quote.
-	Otherwise, set current status to the unit status.
-	* io/unit.c (get_internel_unit, init_unit): Remember to set
-	flags_delim initially to DELIM_UNSPECIFIED so defaults come out
-	correctly.
-	* io/write.c (write_character): Add a new function argument
-	"mode" to signify that raw output is to be used vs output with
-	delimiters. If the mode is set to DELIM (1) proceed with
-	delimiters. (list_formatted_write_scalar): Write the separator
-	only if a delimiter was previously specified. Update the call to
-	write_character with the mode argument given.
-	(namelist_write_newline): Use the mode argument. (nml_write_obj):
-	Use the mode argument. Remove use of tmp_delim. Write the
-	semi-colon or comma correctly only when needed with using
-	delimiters. Cleanup whitespace.
-	(namelist_write): If delim is not specified in namelist I/O,
-	default	to using quotes. Get rid of the tmp_delim variable and
-	use the new mode argument in write_character.
-
-2014-02-21  Tobias Burnus  <burnus@net-b.de>
-
-	PR fortran/60286
-	* libgfortran/io/inquire.c (yes, no): New static const char vars.
-	(inquire_via_unit): Use them. Use OPEN mode instead of using
-	POSIX's access to query about write=, read= and readwrite=.
-
-2014-01-20  Jerry DeLisle  <jvdelisle@gcc.gnu>
-	    Dominique d'Humieres  <dominiq@lps.ens.fr>
-
-	* io/write_float.def (output_float): Remove inadvertent test
-	code from previous patch.
-
-2014-01-19  Jerry DeLisle  <jvdelisle@gcc.gnu>
-	    Dominique d'Humieres  <dominiq@lps.ens.fr>
-
-	PR libfortran/59771
-	PR libfortran/59774
-	PR libfortran/59836
-	* io/write_float.def (output_float): Fix wrong handling of the
-	Fw.0 format.
-	(output_float_FMT_G_): Fixes rounding issues with -m32.
-
-2014-01-11  Jerry DeLisle  <jvdelisle@gcc.gnu>
-	    Dominique d'Humieres  <dominiq@lps.ens.fr>
-	    Steven G. Kargl  <kargl@gcc.gnu.org>
-
-	PR libfortran/59700
-	PR libfortran/59764
-	* io/io.h (struct st_parameter_dt): Assign expanded_read flag to
-	unused bit. Define new variable line_buffer_pos.
-	* io/list_read.c (free_saved, next_char, l_push_char,
-	read_logical, read_real): Replace use of item_count with
-	line_buffer_pos for line_buffer look ahead.
-	(read_logical, read_integer, parse_real, read_real, check_type):
-	Adjust location of free_line to after generating error messages
-	to retain the correct item count for the message.
-
-2014-01-02  Richard Sandiford  <rdsandiford@googlemail.com>
-
-	Update copyright years
+	* caf/single.c (_gfortran_caf_co_reduce): New function.
+	* caf/libcaf.h (_gfortran_caf_co_reduce): New prototype.
 ^L
-Copyright (C) 2013-2014 Free Software Foundation, Inc.
+Copyright (C) 2015 Free Software Foundation, Inc.
 
 Copying and distribution of this file, with or without modification,
 are permitted in any medium without royalty provided the copyright
diff --git a/libgfortran/ChangeLog-2014 b/libgfortran/ChangeLog-2014
new file mode 100644
index 0000000000000000000000000000000000000000..42b00c77fc84bdd418f1d7106586bcfbaed04dfc
--- /dev/null
+++ b/libgfortran/ChangeLog-2014
@@ -0,0 +1,780 @@
+2014-11-28  Bernd Schmidt  <bernds@codesourcery.com>
+
+	* Makefile.am (AM_CFLAGS): Add -DLIBGFOR_MINIMAL if LIBGFOR_MINIMAL.
+	(gfor_io_src, gfor_heper_src, gfor_src): Split into minimal and
+	always included sources.
+	* Makefile.in: Regenerate.
+	* configure.ac (LIBGFOR_MINIMAL): New AM_CONDITIONAL.
+	* configure: Regenerate.
+	* caf/single.c (caf_runtime_error): Don't print messages if
+	LIBGFOR_MINIMAL.
+	* runtime/compile_options.c (fatal_error_in_progress,
+	show_signal, backtrace_handler, maybe_find_addr2line): Guard with
+	!defined LIBGFOR_MINIMAL.
+	(set_options): Likewise for the backtrace code.
+	* runtime/minimal.c: New file.
+
+2014-11-25  Uros Bizjak  <ubizjak@gmail.com>
+
+	* intrinsics/env.c (getenv): Remove unused variable res_len.
+
+2014-11-24  John David Anglin  <danglin@gcc.gnu.org>
+
+	* configure.ac: Guard include of <ieeefp.h>.
+	* configure: Rebuilt.
+
+2014-11-21  H.J. Lu  <hongjiu.lu@intel.com>
+
+	PR bootstrap/63784
+	* configure: Regenerated.
+
+2014-11-16  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/60324
+	* intrinsics/random.c (kiss_size): Rename to KISS_SIZE, make it a
+	macro instead of a variable.
+	(random_seed_i4): Make seed correct size, remove assert, KISS_SIZE
+	related changes.
+	(random_seed_i8): KISS_SIZE related changes.
+
+2014-11-13  Marek Polacek  <polacek@redhat.com>
+
+	* intrinsics/access.c: Include <stdlib.h>.
+	* intrinsics/chdir.c: Likewise.
+	* intrinsics/chmod.c: Likewise.
+	* intrinsics/link.c: Likewise.
+	* intrinsics/perror.c: Likewise.
+	* intrinsics/rename.c: Likewise.
+	* intrinsics/symlnk.c: Likewise.
+	* intrinsics/unlink.c: Likewise.
+
+2014-11-13  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/60324
+	* configure: Regenerated.
+	* configure.ac (AM_CFLAGS): Add Werror=vla.
+	* libgfortran.h (gfc_alloca): Remove macro.
+	(fc_strdup_notrim): New prototype.
+	* intrinsics/access.c (access_func): Use fc_strdup rather than
+	stack allocation.
+	* intrinsics/chdir.c (chdir_i4_sub): Likewise.
+	(chdir_i8_sub): Likewise.
+	* intrinsics/chmod.c (chmod_internal): New function, move logic
+	here.
+	(chmod_func): Call chmod_internal.
+	* intrinsics/env.c (getenv): Use fc_strdup rather than stack
+	allocation.
+	(get_environment_variable_i4): Likewise.
+	* intrinsics/execute_command_line.c (execute_command_line):
+	Likewise.
+	* intrinsics/hostnm.c (hostnm_0): New function, use static buffer
+	rather than VLA.
+	(hostnm_i4_sub): Call hostnm_0.
+	(hostnm_i8_sub): Likewise.
+	(hostnm): Likewise.
+	* intrinsics/link.c (link_internal): New function, use fc_strdup
+	rather than stack allocation.
+	(link_i4_sub): Call link_internal.
+	(link_i8_sub): Likewise.
+	(link_i4): Likewise.
+	(link_i8): Likewise.
+	* intrinsics/perror.c (perror_sub): Use fc_strdup rather than
+	stack allocation.
+	* intrinsics/random.c (random_seed_i4): Use static buffer rather
+	than VLA, use _Static_assert to make sure it's big enough.
+	* intrinsics/rename.c (rename_internal): New function, use
+	fc_strdup rather than stack allocation.
+	(rename_i4_sub): Call rename_internal.
+	(rename_i8_sub): Likewise.
+	(rename_i4): Likewise.
+	(rename_i8): Likewise.
+	* intrinsics/stat.c (stat_i4_sub_0): Use fc_strdup rather than
+	stack allocation.
+	(stat_i8_sub_0): Likewise.
+	* intrinsics/symlink.c (symlnk_internal): New function, use
+	fc_strdup rather than stack allocation.
+	(symlnk_i4_sub): Call symlnk_internal.
+	(symlnk_i8_sub): Likewise.
+	(symlnk_i4): Likewise.
+	(symlnk_i8): Likewise.
+	* intrinsics/system.c (system_sub): Use fc_strdup rather than
+	stack allocation.
+	* intrinsics/unlink.c (unlink_i4_sub): Likewise.
+	* io/file_pos.c (READ_CHUNK): Make it a macro rather than variable.
+	* io/list_read.c (nml_get_obj_data): Use fixed stack buffer, fall
+	back to xmalloc/free for large sizes.
+	* io/read.c (read_f): Likewise.
+	* io/transfer.c (MAX_READ): Make it a macro rather than variable.
+	(WRITE_CHUNK): Likewise.
+	* io/write_float.def (write_float): Use fixed stack buffer, fall
+	back to xmalloc/free for large sizes.
+	* runtime/string.c (fc_strdup_notrim): New function.
+
+2014-11-11  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR target/63610
+	* configure: Regenerate.
+
+2014-11-10  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/47007
+	PR libfortran/61847
+	* config.h.in: Regenerated.
+	* configure: Regenerated.
+	* configure.ac (AC_CHECK_HEADERS_ONCE): Check for xlocale.h.
+	(AC_CHECK_FUNCS_ONCE): Check for newlocale, freelocale, uselocale,
+	strerror_l.
+	* io/io.h (locale.h): Include.
+	(xlocale.h): Include if present.
+	(c_locale): New variable.
+	(old_locale): New variable.
+	(old_locale_ctr): New variable.
+	(old_locale_lock): New variable.
+	(st_parameter_dt): Add old_locale member.
+	* io/transfer.c (data_transfer_init): Set locale to "C" if doing
+	formatted transfer.
+	(finalize_transfer): Reset locale to previous.
+	* io/unit.c (c_locale): New variable.
+	(old_locale): New variable.
+	(old_locale_ctr): New variable.
+	(old_locale_lock): New variable.
+	(init_units): Init c_locale, init old_locale_lock.
+	(close_units): Free c_locale.
+	* runtime/error.c (locale.h): Include.
+	(xlocale.h): Include if present.
+	(gf_strerror): Use strerror_l if available. Reset locale to
+	LC_GLOBAL_LOCALE for strerror_r branch.
+
+2014-10-20  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/63589
+	* configure.ac: Check for strtok_r.
+	* runtime/main.c (gfstrtok_r): Fallback implementation of
+	strtok_r.
+	(find_addr2line): Use strtok_r to split PATH.
+	* config.h.in: Regenerated.
+	* configure: Regenerated.
+
+2014-10-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* ieee/ieee_helper.c (ieee_is_finite_*, ieee_is_nan_*,
+	ieee_is_negative_*, ieee_is_normal_*, ieee_copy_sign_*,
+	ieee_unordered_*, ieee_logb_*, ieee_rint_*, ieee_scalb_*,
+	ieee_rem_*, ieee_next_after_*): Remove functions.
+	* gfortran.map (GFORTRAN_1.5): Remove corresponding symbols.
+
+2014-10-05  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR libgfortran/63460
+	* io/unit.c (init_units): Initialize the DELIM flag to
+	UNSPECIFIED for the STDIN unit so that the flag is
+	correctly set later.
+
+2014-10-01  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* intrinsics/pack_generic.c (pack_s_internal): Fix
+	-Wmaybe-uninitialized warning.
+	* m4/unpack.m4 (unpack0_'rtype_code`): Likewise.
+	(unpack1_'rtype_code`): Likewise.
+	* generated/unpack_*.m4: Regenerated.
+
+2014-09-30  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* configure.ac (AM_CFLAGS): Add
+	-Werror=implicit-function-declaration.
+	* Makefile.in: Regenerated.
+	* aclocal.m4: Regenerated.
+	* configure: Regenerated.
+
+2014-09-25  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (_gfortran_caf_co_broadcast): New prototype.
+	* caf/single.c (_gfortran_caf_co_broadcast): New.
+
+2014-09-18  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/62768
+	* io/inquire.c (inquire_via_unit): Use gfc_unit.filename also when
+	HAVE_TTYNAME{_R} is not defined.
+
+2014-09-17  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/62768
+	* io/io.h (gfc_unit): Store C string for the filename.
+	* io/close.c (st_close): Use gfc_unit.filename.
+	* io/inquire.c (inquire_via_unit): Likewise.
+	* io/open.c (new_unit): Likewise.
+	(already_open): Likewise, unlink file before freeing filename.
+	* io/unit.c (init_units): Likewise.
+	(close_unit_1): Likewise.
+	(filename_from_unit): Likewise.
+	* io/unix.c (compare_file_filename): Likewise.
+	(find_file0): Likewise.
+	(delete_file): Likewise.
+
+2014-09-10  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* io/transfer.c (read_block_form): Fix pad status check (found by
+	Thomas Schwinge with -Wlogical-not-parentheses).
+
+2014-08-31  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (_gfortran_caf_send, _gfortran_caf_get,
+	_gfortran_caf_sendget): Update prototype.
+	* caf/single.c (_gfortran_caf_send, _gfortran_caf_get,
+	_gfortran_caf_sendget): Handle may_require_tmp.
+
+2014-08-20  Steven G. Kargl  <kargl@gcc.gnu.org>
+
+	PR libgfortran/62188
+	* m4/bessel.m4: Avoid indexing off the end of an array.
+	* generated/bessel_r10.c: Regenerated.
+	* generated/bessel_r16.c: Ditto.
+	* generated/bessel_r4.c: Ditto.
+	* generated/bessel_r8.c: Ditto.
+
+2014-08-14  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (caf_register_t): Update for critical.
+	(_gfortran_caf_critical, _gfortran_caf_end_critical): Remove.
+	(_gfortran_caf_lock, _gfortran_caf_unlock): Add.
+	* caf/single.c (_gfortran_caf_register): Handle locking
+	variables.
+	(_gfortran_caf_sendget): Re-name args for consistency.
+	(_gfortran_caf_lock, _gfortran_caf_unlock): Add.
+
+2014-08-04  Jakub Jelinek  <jakub@redhat.com>
+
+	* runtime/memory.c (xmallocarray): Avoid division for the common case.
+
+2014-07-20  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR libgfortran/61632
+	* io/format.c (format_error): Avoid invalid string pointer by
+	using the fortran string length values to generate error string.
+	(parse_format): Allocate the null terminator for the format
+	string.
+
+2014-07-12  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (_gfortran_caf_atomic_define,
+	_gfortran_caf_atomic_ref, _gfortran_caf_atomic_op,
+	_gfortran_caf_atomic_cas): New prototypes.
+	* caf/single.c (_gfortran_caf_atomic_define,
+	_gfortran_caf_atomic_ref, _gfortran_caf_atomic_op,
+	_gfortran_caf_atomic_cas): New functions.
+
+2014-07-10  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* config/fpu-*.h (get_fpu_rounding_mode, set_fpu_rounding_mode,
+	support_fpu_rounding_mode): Clean up, mark unreachable code as such.
+
+2014-07-09  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* libgfortran.h (support_fpu_underflow_control,
+	get_fpu_underflow_mode, set_fpu_underflow_mode): New prototypes.
+	* config/fpu-*.h (support_fpu_underflow_control,
+	get_fpu_underflow_mode, set_fpu_underflow_mode):
+	New functions.
+	* ieee/ieee_arithmetic.F90: Support underflow control.
+
+2014-07-08  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* config/fpu-sysv.h (get_fpu_rounding_mode): Use FP_RN, FP_RP,
+	FP_RM, FP_RZ unconditionally.
+	(set_fpu_rounding_mode): Likewise.
+
+2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* libgfortran.h: Assume __GNUC__.
+
+2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* runtime/stop.c: Use C11 _Noreturn.
+	* libgfortran.h: Use C11 _Noreturn in prototypes.
+	Move REALPART, IMAGPART and COMPLEX_ASSIGN macros...
+	* intrinsics/c99_functions.c: ... here.
+
+2014-07-07  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* config/fpu-387.h, config/fpu-aix.h, config/fpu-sysv.h,
+	config/fpu-glibc.h: Use static assertions.
+
+2014-07-05  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* configure, config.h.in: Regenerate.
+	* config/fpu-sysv.h: Include <assert.h>.
+
+2014-07-02  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* config/fpu-glibc.h: Fix comment about FE_DENORMAL.
+
+2014-07-02  Uros Bizjak  <ubizjak@gmail.com>
+
+	* configure.host (ieee_flags): Add -mieee for alpha*.
+
+	* config/fpu-glibc.h (support_fpu_rounding_mode): Correctly handle
+	GFC_FPE_UPWARD, GFC_FPE_DOWNWARD and GFC_FPE_TOWARDZERO.
+	* config/fpu-aix.h (support_fpu_rounding_mode): Ditto.
+
+2014-06-29  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	* config/fpu-387.h (my_fenv_t): Amend structure so it also works
+	on mingw32.
+
+2014-06-28  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR libgfortran/61640
+	* io/list_read.c (next_char_internal): Adjust the read length to
+	a single wide character. (eat_spaces): Add missing paren.
+	* io/unix.c (mem_read4): Use the correct mem_alloc function for
+	wide character internal reads.
+
+2014-06-28  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR fortran/29383
+	* configure.host: Add checks for IEEE support, rework priorities.
+	* configure.ac: Define IEEE_SUPPORT, check for fpsetsticky and
+	fpresetsticky.
+	* configure: Regenerate.
+	* Makefile.am: Build new ieee files, install IEEE_* modules.
+	* Makefile.in: Regenerate.
+	* gfortran.map (GFORTRAN_1.6): Add new symbols.
+	* libgfortran.h (get_fpu_trap_exceptions, set_fpu_trap_exceptions,
+	support_fpu_trap, set_fpu_except_flags, support_fpu_flag,
+	support_fpu_rounding_mode, get_fpu_state, set_fpu_state): New
+	prototypes.
+	* config/fpu-*.h (get_fpu_trap_exceptions,
+	set_fpu_trap_exceptions, support_fpu_trap, set_fpu_except_flags,
+	support_fpu_flag, support_fpu_rounding_mode, get_fpu_state,
+	set_fpu_state): New functions.
+	* ieee/ieee_features.F90: New file.
+	* ieee/ieee_exceptions.F90: New file.
+	* ieee/ieee_arithmetic.F90: New file.
+	* ieee/ieee_helper.c: New file.
+
+2014-06-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR libgfortran/61499
+	* io/list_read.c (eat_spaces): Use a 'for' loop instead of
+	'while' loop to skip the loop if there are no bytes left in the
+	string. Only seek if actual spaces can be skipped.
+
+2014-06-25  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/single.c (assign_char4_from_char1, assign_char1_from_char4,
+	convert_type): New static functions.
+	(_gfortran_caf_get, _gfortran_caf_send): Use them.
+
+2014-06-19  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/single.c (_gfortran_caf_co_sum, _gfortran_caf_co_max,
+	_gfortran_caf_co_min): Fix stat setting.
+
+2014-06-17  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (gfc_descriptor_t): New typedef.
+	(caf_vector_t): Update.
+	(_gfortran_caf_co_sum, _gfortran_caf_co_max, _gfortran_caf_co_min):
+	Remove vector-subscript argument.
+	(_gfortran_caf_co_send, _gfortran_caf_co_get,
+	_gfortran_caf_co_sendget): New.
+	* caf/single.c (_gfortran_caf_co_sum, _gfortran_caf_co_max,
+	_gfortran_caf_co_min): Remove vector-subscript argument.
+	(_gfortran_caf_co_send, _gfortran_caf_co_get,
+	_gfortran_caf_co_sendget): New.
+
+2014-06-17  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* libgfortran.h (xmallocarray): New prototype.
+	* runtime/memory.c (xmallocarray): New function.
+	(xcalloc): Check for nonzero separately instead of multiplying.
+	* generated/*.c: Regenerated.
+	* intrinsics/cshift0.c (cshift0): Call xmallocarray instead of
+	xmalloc.
+	* intrinsics/eoshift0.c (eoshift0): Likewise.
+	* intrinsics/eoshift2.c (eoshift2): Likewise.
+	* intrinsics/pack_generic.c (pack_internal): Likewise.
+	(pack_s_internal): Likewise.
+	* intrinsics/reshape_generic.c (reshape_internal): Likewise.
+	* intrinsics/spread_generic.c (spread_internal): Likewise.
+	(spread_internal_scalar): Likewise.
+	* intrinsics/string_intrinsics_inc.c (string_trim): Likewise.
+	(string_minmax): Likewise.
+	* intrinsics/transpose_generic.c (transpose_internal): Likewise.
+	* intrinsics/unpack_generic.c (unpack_internal): Likewise.
+	* io/list_read.c (nml_touch_nodes): Don't cast xmalloc return value.
+	* io/transfer.c (st_set_nml_var): Call xmallocarray instead of
+	xmalloc.
+	* io/unit.c (get_internal_unit): Likewise.
+	(filename_from_unit): Don't cast xmalloc return value.
+	* io/write.c (nml_write_obj): Likewise, formatting.
+	* m4/bessel.m4 (bessel_jn_r'rtype_kind`): Call xmallocarray
+	instead of xmalloc.
+	(besse_yn_r'rtype_kind`): Likewise.
+	* m4/cshift1.m4 (cshift1): Likewise.
+	* m4/eoshift1.m4 (eoshift1): Likewise.
+	* m4/eoshift3.m4 (eoshift3): Likewise.
+	* m4/iforeach.m4: Likewise.
+	* m4/ifunction.m4: Likewise.
+	* m4/ifunction_logical.m4 (name`'rtype_qual`_'atype_code):
+	Likewise.
+	* m4/in_pack.m4 (internal_pack_'rtype_ccode`): Likewise.
+	* m4/matmul.m4 (matmul_'rtype_code`): Likewise.
+	* m4/matmull.m4 (matmul_'rtype_code`): Likewise.
+	* m4/pack.m4 (pack_'rtype_code`): Likewise.
+	* m4/reshape.m4 (reshape_'rtype_ccode`): Likewise.
+	* m4/shape.m4 (shape_'rtype_kind`): Likewise.
+	* m4/spread.m4 (spread_'rtype_code`): Likewise.
+	(spread_scalar_'rtype_code`): Likewise.
+	* m4/transpose.m4 (transpose_'rtype_code`): Likewise.
+	* m4/unpack.m4 (unpack0_'rtype_code`): Likewise.
+	(unpack1_'rtype_code`): Likewise.
+	* runtime/convert_char.c (convert_char1_to_char4): Likewise.
+	(convert_char4_to_char1): Simplify.
+	* runtime/environ.c (init_unformatted): Call xmallocarray instead
+	of xmalloc.
+	* runtime/in_pack_generic.c (internal_pack): Likewise.
+
+2014-06-15  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
+
+	PR libfortran/60468
+	* configure.ac: Include <math.h> when checking for fp_except_t
+	and fp_rnd_t types.
+	* configure: Regenerate.
+
+2014-06-08  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/56981
+	* io/unix.h (struct stream_vtable): Add new member function,
+	markeor.
+	(smarkeor): New inline function.
+	(flush_if_unbuffered): Remove prototype.
+	* io/unix.c (raw_markeor): New function.
+	(raw_vtable): Initialize markeor member.
+	(buf_markeor): New function.
+	(buf_vtable): Initialize markeor member.
+	(mem_vtable): Likewise.
+	(mem4_vtable): Likewise.
+	(flush_if_unbuffered): Remove function.
+	* io/transfer.c (next_record): Call smarkeor instead of
+	flush_if_unbuffered.
+
+2014-05-27  Uros Bizjak  <ubizjak@gmail.com>
+
+	* intrinsics/getcwd.c: Include stdlib.h.
+
+2014-05-26  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* libgfortran.h (xrealloc): New prototype.
+	* runtime/memory.c (xrealloc): New function.
+	* io/fbuf.c (fbuf_alloc): Use xrealloc.
+	* io/list_read.c (push_char_default): Likewise.
+	(push_char4): Likewise.
+
+2014-05-26  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/61310
+	* intrinsics/ctime.c (strctime): Rename to gf_ctime, use snprintf
+	instead of strftime.
+	(fdate): Use gf_ctime.
+	(fdate_sub): Likewise.
+	(ctime): Likewise.
+	(ctime_sub): Likewise.
+
+2014-05-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
+
+	PR libgfortran/55117
+	* io/list_read.c (extended_look_ahead): New helper function to
+	scan the namelist name and look for matches with the new '+'
+	extended type parent indicator.  (str_comp_extended): New
+	helper function to compare the namelist name with the varname
+	namelist. (find_nml_name): Use the new helper functions to match
+	the extended type varnames.
+
+2014-05-23  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/61173
+	* io/list_read.c (eat_spaces): If the next character pointed to
+	is a space, don't seek, must be at the end.
+
+2014-05-23  Hans-Peter Nilsson  <hp@axis.com>
+
+	* configure.ac [with_newlib] (HAVE_STRNLEN, HAVE_STRNDUP): Define.
+	* configure: Regenerate.
+
+2014-05-23  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/60324
+	* runtime/string.c: Include stdlib.h.
+
+2014-05-22  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/60324
+	* config.h.in: Regenerated.
+	* configure: Regenerated.
+	* configure.ac (AC_CHECK_FUNCS_ONCE): Check for strnlen and
+	strndup.
+	* libgfortran.h (fc_strdup): New prototype.
+	* runtime/string.c (strnlen): New fallback function.
+	(strndup): New fallback function.
+	(fc_strdup): New function.
+	* io/close.c (st_close): Use fc_strdup.
+	* io/open.c (new_unit): Likewise.
+	(already_open): Likewise.
+	* io/unit.c (filename_from_unit): Likewise.
+	* io/unix.c (unpack_filename): Remove function.
+	(regular_file): Rename to regular_file2, add path argument.
+	(regular_file): New function calling regular_file2.
+	(compare_file_filename): Use fc_strdup.
+	(find_file): Likewise.
+	(delete_file): Likewise.
+	(file_exists): Likewise.
+	(file_size): Likewise.
+	(inquire_sequential): Likewise.
+	(inquire_direct): Likewise.
+	(inquire_formatted): Likewise.
+	(inquire_access): Likewise.
+	* io/unix.h (unpack_filename): Remove prototype.
+	* runtime/main.c (please_free_exe_path_when_done): Change type to
+	bool.
+	(store_exe_path): Use malloced buffer, grow as needed.
+
+2014-05-17  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/52539
+	* io/io.h (gfc_unit): New function pointers *next_char_fn_ptr
+	and *push_char_fn_ptr.
+	*io/list_read.c (next_char): Create macro with this name to call
+	the new function pointer. Split the original next_char function
+	into three new functions. (next_char_default, next_char_internal,
+	next_char_utf8): New functions. (push_char): Create macro with
+	this name to call new function pointer. Split the original
+	push_char into three new functions. (push_char_default,
+	push_char_internal, push_char4): New functions. (set_workers):
+	New function to initilize the function pointers depending on the
+	type of IO to be performed. (list_formatted_read_scalar): Use
+	set_workers function. (finish_list_read): Likewise.
+	(namelist_read): Likewise.
+	(nml_get_obj_data): Use push_char_default.
+
+2014-05-16  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/61187
+	* io/unix.c (raw_close): Check if s->fd is -1.
+	(fd_to_stream): Check return value of fstat(), handle error.
+
+2014-05-12  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	PR libfortran/61035
+	* intrinsics/getcwd.c (getcwd_i4_sub): Avoid potentially large
+	stack allocation, avoid extra copying in the common case.
+
+2014-05-12  Janne Blomqvist  <jb@gcc.gnu.org>
+
+	* configure.ac (AM_CFLAGS): Use -std=gnu11.
+	(CFLAGS): Likewise.
+	* configure: Regenerated.
+
+2014-05-11  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (_gfortran_caf_num_images): Change type of
+	second argument to int.
+	* caf/mpi.c (_gfortran_caf_num_images): Ditto.
+	* caf/single.c (_gfortran_caf_num_images): Ditto.
+
+2014-05-08  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (caf_vector_t, _gfortran_caf_co_sum,
+	_gfortran_caf_co_min, _gfortran_caf_co_max): Declare
+	* caf/single.c
+
+2014-05-06  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/61049
+	* io/list_read.c (list_formatted_read_scalar): Use eat_separator
+	and delete extraneous code.
+
+2014-04-30  Tobias Burnus  <burnus@net-b.de>
+
+	* caf/libcaf.h (_gfortran_caf_this_image, _gfortran_caf_num_images):
+	New prototypes.
+	(_gfortran_caf_init): Change prototype.
+	(mpi_token_t): New typedef.
+	(TOKEN): New define.
+	* caf/mpi.c (_gfortran_caf_this_image, _gfortran_caf_num_images):
+	New functions.
+	(_gfortran_caf_init): Update.
+	(_gfortran_caf_finalize, _gfortran_caf_register,
+	_gfortran_caf_deregister): Use mpi_token_t.
+	* caf/single.c (_gfortran_caf_this_image, _gfortran_caf_num_images):
+	New functions.
+	(_gfortran_caf_init): Update.
+	(_gfortran_caf_finalize, _gfortran_caf_register,
+	_gfortran_caf_deregister): Use mpi_token_t, simplify.
+
+2014-04-26  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/52539
+	* io/list_read.c: Add uchar typedef. (push_char4): New function
+	to save kind=4 character. (next_char_utf8): New function to read
+	a single UTF-8 encoded character value. (read_chracter): Update
+	to use the new functions for reading UTF-8 strings.
+	(list_formatted_read_scalar): Update to handle list directed
+	reads of UTF-8 strings. (nml_read_obj): Likewise update for
+	UTF-8 strings in namelists.
+	* io/write.c (nml_write_obj): Add kind=4 character support for
+	namelist writes.
+
+2014-04-24  Kyrylo Tkachov  <kyrylo.tkachov@arm.com>
+
+	* configure.ac: Quote usage of ac_cv_func_clock_gettime in if test.
+	* configure: Regenerate.
+
+2014-04-22  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
+
+	* config/fpu-387.h [__sun__ && __svr4__]: Remove SSE execution
+	check.
+
+2014-04-11  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/60810
+	io/unit.c (is_trim_ok): If internal unit is array, do not trim.
+
+2014-03-21  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/60148
+	* io/transfer.c (data_transfer_init): If std= was specified, set
+	delim status to DELIM_NONE of no other was specified.
+
+2014-03-18  Ulrich Weigand  <Ulrich.Weigand@de.ibm.com>
+
+	* configure.ac: Check for presence of fcntl.
+	* configure: Regenerate.
+	* config.h.in: Regenerate.
+	* io/unix.c (set_close_on_exec): Check for HAVE_FCNTL.
+
+2014-03-17  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/48600
+	* io/list_read.c (list_formatted_read_scalar): Do not use
+	eat_separator. Explicitly set the comma and end-of-line flags.
+	Check for END condition from finish_separator.
+
+2014-03-15  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/58324
+	* io/list_read.c (finish_list_read): Read one character to check
+	for the end of the file.  If it is the end, then issue the file
+	end error message.  If not, use eat_line to reach the end
+	without giving error.  The next attempt to read will then
+	issue the error as described above.
+
+2014-03-12  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/38199
+	* io/read.c (read_decimal): Quickly skip spaces to avoid calls
+	to next_char.
+	* io/unit.c (is_trim_ok): New helper function to check various
+	conditions to see if its OK to trim the internal unit string.
+	(get_internal_unit): Use LEN_TRIM to shorten selected internal
+	unit strings for optimizing READ. Enable this optimization for
+	formatted READ.
+	* io/list_read.c (finish_list_read): Don't call eat_line for
+	internal units.
+
+2014-03-08  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/38199
+	* io/list_read.c (next_char): Mark unlikely error checks.
+	(eat_spaces): For character array reading, skip ahead over
+	spaces rather than call next_char multiple times.
+
+2014-03-08  Tobias Burnus  <burnus@net-b.de>
+
+	* libgfortran.h (unlikely, likely): Add usage comment.
+
+2014-03-08  Dominique d'Humieres  <dominiq@lps.ens.fr>
+
+	PR libgfortran/60128
+	* io/write_float.def (output_float): Remove unused variable
+	nzero_real. Replace a double space with a single one.
+	(determine_en_precision): Fix wrong handling of the EN format.
+
+2014-03-03  Jerry DeLisle  <jvdelisle@gcc.gnu>
+
+	PR libfortran/60148
+	* io/inquire.c (inquire_via_unit): In the case of
+	DELIM_UNSPECIFIED set inquire return string to "NONE".
+	* io/list_read.c (read_character): In the case of DELIM_NONE and
+	namelists, complete the character read using the namelist
+	variable length.
+	* io/open.c (new_unit): Don't set delim status to none if not
+	specified so that DELIM_UNSPECIFIED can be used later.
+	* io/transfer.c (data_transfer_init): For namelist I/O, if the
+	unit delim status is unspecified set the current status to quote.
+	Otherwise, set current status to the unit status.
+	* io/unit.c (get_internel_unit, init_unit): Remember to set
+	flags_delim initially to DELIM_UNSPECIFIED so defaults come out
+	correctly.
+	* io/write.c (write_character): Add a new function argument
+	"mode" to signify that raw output is to be used vs output with
+	delimiters. If the mode is set to DELIM (1) proceed with
+	delimiters. (list_formatted_write_scalar): Write the separator
+	only if a delimiter was previously specified. Update the call to
+	write_character with the mode argument given.
+	(namelist_write_newline): Use the mode argument. (nml_write_obj):
+	Use the mode argument. Remove use of tmp_delim. Write the
+	semi-colon or comma correctly only when needed with using
+	delimiters. Cleanup whitespace.
+	(namelist_write): If delim is not specified in namelist I/O,
+	default	to using quotes. Get rid of the tmp_delim variable and
+	use the new mode argument in write_character.
+
+2014-02-21  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/60286
+	* libgfortran/io/inquire.c (yes, no): New static const char vars.
+	(inquire_via_unit): Use them. Use OPEN mode instead of using
+	POSIX's access to query about write=, read= and readwrite=.
+
+2014-01-20  Jerry DeLisle  <jvdelisle@gcc.gnu>
+	    Dominique d'Humieres  <dominiq@lps.ens.fr>
+
+	* io/write_float.def (output_float): Remove inadvertent test
+	code from previous patch.
+
+2014-01-19  Jerry DeLisle  <jvdelisle@gcc.gnu>
+	    Dominique d'Humieres  <dominiq@lps.ens.fr>
+
+	PR libfortran/59771
+	PR libfortran/59774
+	PR libfortran/59836
+	* io/write_float.def (output_float): Fix wrong handling of the
+	Fw.0 format.
+	(output_float_FMT_G_): Fixes rounding issues with -m32.
+
+2014-01-11  Jerry DeLisle  <jvdelisle@gcc.gnu>
+	    Dominique d'Humieres  <dominiq@lps.ens.fr>
+	    Steven G. Kargl  <kargl@gcc.gnu.org>
+
+	PR libfortran/59700
+	PR libfortran/59764
+	* io/io.h (struct st_parameter_dt): Assign expanded_read flag to
+	unused bit. Define new variable line_buffer_pos.
+	* io/list_read.c (free_saved, next_char, l_push_char,
+	read_logical, read_real): Replace use of item_count with
+	line_buffer_pos for line_buffer look ahead.
+	(read_logical, read_integer, parse_real, read_real, check_type):
+	Adjust location of free_line to after generating error messages
+	to retain the correct item count for the message.
+
+2014-01-02  Richard Sandiford  <rdsandiford@googlemail.com>
+
+	Update copyright years
+^L
+Copyright (C) 2014 Free Software Foundation, Inc.
+
+Copying and distribution of this file, with or without modification,
+are permitted in any medium without royalty provided the copyright
+notice and this notice are preserved.
diff --git a/libgfortran/caf/libcaf.h b/libgfortran/caf/libcaf.h
index ffd0980bf6742cd57f5bf1b7424be93acef18048..625078cdcbbd2d5c30afd4fc394a6e23fe5f1945 100644
--- a/libgfortran/caf/libcaf.h
+++ b/libgfortran/caf/libcaf.h
@@ -110,6 +110,8 @@ void _gfortran_caf_co_broadcast (gfc_descriptor_t *, int, int *, char *, int);
 void _gfortran_caf_co_sum (gfc_descriptor_t *, int, int *, char *, int);
 void _gfortran_caf_co_min (gfc_descriptor_t *, int, int *, char *, int, int);
 void _gfortran_caf_co_max (gfc_descriptor_t *, int, int *, char *, int, int);
+void _gfortran_caf_co_reduce (gfc_descriptor_t *, void* (*) (void *, void*),
+			      int, int, int *, char *, int, int);
 
 void _gfortran_caf_get (caf_token_t, size_t, int, gfc_descriptor_t *,
                         caf_vector_t *, gfc_descriptor_t *, int, int, bool);
diff --git a/libgfortran/caf/single.c b/libgfortran/caf/single.c
index 632d172cf9ebe8a8ced014757733ca6a0801f87d..2a553723465a6d74d78bb7c8803ac3043f4063b9 100644
--- a/libgfortran/caf/single.c
+++ b/libgfortran/caf/single.c
@@ -254,6 +254,21 @@ _gfortran_caf_co_max (gfc_descriptor_t *a __attribute__ ((unused)),
 }
 
 
+void
+_gfortran_caf_co_reduce (gfc_descriptor_t *a __attribute__ ((unused)),
+                        void * (*opr) (void *, void *)
+                               __attribute__ ((unused)),
+                        int opr_flags __attribute__ ((unused)),
+                        int result_image __attribute__ ((unused)),
+                        int *stat, char *errmsg __attribute__ ((unused)),
+                        int a_len __attribute__ ((unused)),
+                        int errmsg_len __attribute__ ((unused)))
+ {
+   if (stat)
+     *stat = 0;
+ }
+
+
 static void
 assign_char4_from_char1 (size_t dst_size, size_t src_size, uint32_t *dst,
 			 unsigned char *src)