diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 8af36683afa30ba2163ce7d4b0ce92fe4f99bff5..f68a6cafdd91f322e83f40212889b890f524b531 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,15 @@
+2010-04-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/18918
+	* iso-fortran-env.def: Add the integer parameters atomic_int_kind,
+	atomic_logical_kind, iostat_inquire_internal_unit, stat_locked,
+	stat_locked_other_image, stat_stopped_image and stat_unlocked of
+	Fortran 2008.
+	* intrinsic.texi (iso_fortran_env): Ditto.
+	* libgfortran.h (libgfortran_stat_codes): New enum.
+	* module.c (use_iso_fortran_env_module): Honour -std= when loading
+	constants from the intrinsic module.
+
 2010-04-06  Tobias Burnus  <burnus@net-b.de>
 
 	PR fortran/39997
diff --git a/gcc/fortran/intrinsic.texi b/gcc/fortran/intrinsic.texi
index 52992ba0c41f264247b7e33b50843debd054bf6d..4439464c40107d8bffcd172151bcfd6c3106d553 100644
--- a/gcc/fortran/intrinsic.texi
+++ b/gcc/fortran/intrinsic.texi
@@ -11281,14 +11281,21 @@ Fortran 95 elemental function: @ref{IEOR}
 @section @code{ISO_FORTRAN_ENV}
 @table @asis
 @item @emph{Standard}:
-Fortran 2003 and later; @code{INT8}, @code{INT16}, @code{INT32}, @code{INT64},
-@code{REAL32}, @code{REAL64}, @code{REAL128} are Fortran 2008 or later
+Fortran 2003 and later, except when otherwise noted
 @end table
 
 The @code{ISO_FORTRAN_ENV} module provides the following scalar default-integer
 named constants:
 
 @table @asis
+@item @code{ATOMIC_INT_KIND}:
+Default-kind integer constant to be used as kind parameter when defining
+integer variables used in atomic operations. (Fortran 2008 or later.)
+
+@item @code{ATOMIC_LOGICAL_KIND}:
+Default-kind integer constant to be used as kind parameter when defining
+logical variables used in atomic operations. (Fortran 2008 or later.)
+
 @item @code{CHARACTER_STORAGE_SIZE}:
 Size in bits of the character storage unit.
 
@@ -11302,10 +11309,10 @@ Size in bits of the file-storage unit.
 Identifies the preconnected unit identified by the asterisk
 (@code{*}) in @code{READ} statement.
 
-@item @code{INT8}, @code{INT16}, @code{INT32}, @code{INT64}
+@item @code{INT8}, @code{INT16}, @code{INT32}, @code{INT64}:
 Kind type parameters to specify an INTEGER type with a storage
 size of 16, 32, and 64 bits. It is negative if a target platform
-does not support the particular kind.
+does not support the particular kind. (Fortran 2008 or later.)
 
 @item @code{IOSTAT_END}:
 The value assigned to the variable passed to the IOSTAT= specifier of
@@ -11315,6 +11322,11 @@ an input/output statement if an end-of-file condition occurred.
 The value assigned to the variable passed to the IOSTAT= specifier of
 an input/output statement if an end-of-record condition occurred.
 
+@item @code{IOSTAT_INQUIRE_INTERNAL_UNIT}:
+Scalar default-integer constant, used by @code{INQUIRE} for the
+IOSTAT= specifier to denote an that a unit number identifies an
+internal unit. (Fortran 2008 or later.)
+
 @item @code{NUMERIC_STORAGE_SIZE}:
 The size in bits of the numeric storage unit.
 
@@ -11322,10 +11334,29 @@ The size in bits of the numeric storage unit.
 Identifies the preconnected unit identified by the asterisk
 (@code{*}) in @code{WRITE} statement.
 
-@item @code{REAL32}, @code{REAL64}, @code{REAL128}
+@item @code{REAL32}, @code{REAL64}, @code{REAL128}:
 Kind type parameters to specify a REAL type with a storage
 size of 32, 64, and 128 bits. It is negative if a target platform
-does not support the particular kind.
+does not support the particular kind. (Fortran 2008 or later.)
+
+@item @code{STAT_LOCKED}:
+Scalar default-integer constant used as STAT= return value by @code{LOCK} to
+denote that the lock variable is locked by the executing image. (Fortran 2008
+or later.)
+
+@item @code{STAT_LOCKED_OTHER_IMAGE}:
+Scalar default-integer constant used as STAT= return value by @code{UNLOCK} to
+denote that the lock variable is locked by another image. (Fortran 2008 or
+later.)
+
+@item @code{STAT_STOPPED_IMAGE}:
+Positive, scalar default-integer constant used as STAT= return value if the
+argument in the statement requires synchronisation with an image, which has
+initiated the termination of the execution. (Fortran 2008 or later.)
+
+@item @code{STAT_UNLOCKED}:
+Scalar default-integer constant used as STAT= return value by @code{UNLOCK} to
+denote that the lock variable is unlocked. (Fortran 2008 or later.)
 @end table
 
 
diff --git a/gcc/fortran/iso-fortran-env.def b/gcc/fortran/iso-fortran-env.def
index fa6071f45b2f01e7e8e13552f4bccca5e16b86d3..6c009f1c8fd0d9d87ec318c2b2e231cdf451f61a 100644
--- a/gcc/fortran/iso-fortran-env.def
+++ b/gcc/fortran/iso-fortran-env.def
@@ -1,4 +1,4 @@
-/* Copyright (C) 2006, 2007, 2008 Free Software Foundation, Inc.
+/* Copyright (C) 2006, 2007, 2008, 2009, 2010 Free Software Foundation, Inc.
 
 This file is part of GCC.
 
@@ -25,6 +25,10 @@ along with GCC; see the file COPYING3.  If not see
      -- the value it has
      -- the standard that supports this type  */ 
 
+NAMED_INTCST (ISOFORTRANENV_FILE_ATOMIC_INT_KIND, "atomic_int_kind", \
+              gfc_default_integer_kind, GFC_STD_F2008)
+NAMED_INTCST (ISOFORTRANENV_FILE_ATOMIC_LOGICAL_KIND, "atomic_logical_kind", \
+              gfc_default_logical_kind, GFC_STD_F2008)
 NAMED_INTCST (ISOFORTRANENV_CHARACTER_STORAGE_SIZE, "character_storage_size", \
               gfc_character_storage_size, GFC_STD_F2003)
 NAMED_INTCST (ISOFORTRANENV_ERROR_UNIT, "error_unit", GFC_STDERR_UNIT_NUMBER, \
@@ -45,6 +49,9 @@ NAMED_INTCST (ISOFORTRANENV_IOSTAT_END, "iostat_end", LIBERROR_END, \
               GFC_STD_F2003)
 NAMED_INTCST (ISOFORTRANENV_IOSTAT_EOR, "iostat_eor", LIBERROR_EOR, \
               GFC_STD_F2003)
+NAMED_INTCST (ISOFORTRANENV_IOSTAT_INQUIRE_INTERNAL_UNIT, \
+              "iostat_inquire_internal_unit", GFC_INQUIRE_INTERNAL_UNIT, \
+              GFC_STD_F2008)
 NAMED_INTCST (ISOFORTRANENV_NUMERIC_STORAGE_SIZE, "numeric_storage_size", \
               gfc_numeric_storage_size, GFC_STD_F2003)
 NAMED_INTCST (ISOFORTRANENV_OUTPUT_UNIT, "output_unit", GFC_STDOUT_UNIT_NUMBER, \
@@ -55,3 +62,13 @@ NAMED_INTCST (ISOFORTRANENV_REAL64, "real64", \
               gfc_get_real_kind_from_width_isofortranenv (64), GFC_STD_F2008)
 NAMED_INTCST (ISOFORTRANENV_REAL128, "real128", \
               gfc_get_real_kind_from_width_isofortranenv (128), GFC_STD_F2008)
+NAMED_INTCST (ISOFORTRANENV_FILE_STAT_LOCKED, "stat_locked", \
+              GFC_STAT_LOCKED, GFC_STD_F2008)
+NAMED_INTCST (ISOFORTRANENV_FILE_STAT_LOCKED_OTHER_IMAGE, \
+              "stat_locked_other_image", \
+	      GFC_STAT_LOCKED_OTHER_IMAGE, GFC_STD_F2008)
+NAMED_INTCST (ISOFORTRANENV_FILE_STAT_STOPPED_IMAGE, "stat_stopped_image", \
+              GFC_STAT_STOPPED_IMAGE, GFC_STD_F2008)
+NAMED_INTCST (ISOFORTRANENV_FILE_STAT_UNLOCKED, "stat_unlocked", \
+              GFC_STAT_UNLOCKED, GFC_STD_F2008)
+
diff --git a/gcc/fortran/libgfortran.h b/gcc/fortran/libgfortran.h
index ca0da5176110974bb543d90e0727f4ad071e1470..85bd43df98c047a2a0a6c967baab9b517a044101 100644
--- a/gcc/fortran/libgfortran.h
+++ b/gcc/fortran/libgfortran.h
@@ -96,6 +96,15 @@ typedef enum
 }
 libgfortran_error_codes;
 
+typedef enum
+{
+  GFC_STAT_UNLOCKED = 0,
+  GFC_STAT_LOCKED,
+  GFC_STAT_LOCKED_OTHER_IMAGE,
+  GFC_STAT_STOPPED_IMAGE,
+  GFC_INQUIRE_INTERNAL_UNIT  /* Must be different from STAT_STOPPED_IMAGE.  */
+}
+libgfortran_stat_codes;
 
 /* Default unit number for preconnected standard input and output.  */
 #define GFC_STDIN_UNIT_NUMBER 5
diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index 0fc1921417280c9ae7a5ad76d87fce48cb91609e..666fd84240ba849f8f2a1c21b559b77bc88e4b4f 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -5401,6 +5401,11 @@ use_iso_fortran_env_module (void)
 			   gfc_option.flag_default_integer
 			     ? "-fdefault-integer-8" : "-fdefault-real-8");
 
+        if (gfc_notify_std (symbol[i].standard, "The symbol '%s', referrenced "
+			    "at %C, is not in the selected standard",
+			    symbol[i].name) == FAILURE)
+	  continue;
+
 	create_int_parameter (u->local_name[0] ? u->local_name
 					       : symbol[i].name,
 			      symbol[i].value, mod, INTMOD_ISO_FORTRAN_ENV,
@@ -5411,6 +5416,10 @@ use_iso_fortran_env_module (void)
       for (i = 0; symbol[i].name; i++)
 	{
 	  local_name = NULL;
+
+	  if ((gfc_option.allow_std & symbol[i].standard) == 0)
+	    break;
+
 	  for (u = gfc_rename_list; u; u = u->next)
 	    {
 	      if (strcmp (symbol[i].name, u->use_name) == 0)
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index a65ba45835b79851dc17ceeb9c33e1043806c597..4053293bb45a8f2940531c37db32cd7014d4cedc 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,9 @@
+2010-04-06  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/18918
+	* gfortran.dg/iso_fortran_env_5.f90: New test.
+	* gfortran.dg/iso_fortran_env_6.f90: New test.
+
 2010-04-06  Tobias Burnus  <burnus@net-b.de>
 
 	PR fortran/39997
diff --git a/gcc/testsuite/gfortran.dg/iso_fortran_env_5.f90 b/gcc/testsuite/gfortran.dg/iso_fortran_env_5.f90
new file mode 100644
index 0000000000000000000000000000000000000000..92c2e40dea5a6439246071a919abea3a6e18a778
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/iso_fortran_env_5.f90
@@ -0,0 +1,27 @@
+! { dg-do compile }
+! { dg-options "-O2 -fdump-tree-original" }
+!
+! Check for new F2008 integer constants, needed for
+! coarray support (cf. PR fortran/18918)
+!
+
+USE iso_fortran_env
+implicit none
+integer :: i
+integer(kind=ATOMIC_INT_KIND) :: atomic_int
+logical(kind=ATOMIC_LOGICAL_KIND) :: atomic_bool
+
+i = 0
+if (IOSTAT_INQUIRE_INTERNAL_UNIT <= 0) call abort()
+if (IOSTAT_INQUIRE_INTERNAL_UNIT == STAT_STOPPED_IMAGE) call abort()
+if (STAT_STOPPED_IMAGE <= 0) call abort()
+
+if ((STAT_LOCKED_OTHER_IMAGE == STAT_LOCKED) &
+    .or.(STAT_LOCKED_OTHER_IMAGE == STAT_UNLOCKED)) call abort()
+if (STAT_LOCKED == STAT_UNLOCKED) call abort()
+
+end
+
+! { dg-final { scan-tree-dump-times "abort" 0 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }
+
diff --git a/gcc/testsuite/gfortran.dg/iso_fortran_env_6.f90 b/gcc/testsuite/gfortran.dg/iso_fortran_env_6.f90
new file mode 100644
index 0000000000000000000000000000000000000000..951e1384f94e6021b0dfb6d1ecb6441226ac1020
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/iso_fortran_env_6.f90
@@ -0,0 +1,33 @@
+! { dg-do compile }
+! { dg-options "-std=f2003" }
+!
+! Check for new F2008 integer constants, needed for
+! coarray support (cf. PR fortran/18918)
+!
+
+USE iso_fortran_env
+implicit none
+integer(kind=ATOMIC_INT_KIND) :: atomic_int ! { dg-error "has no IMPLICIT type" }
+logical(kind=ATOMIC_LOGICAL_KIND) :: atomic_bool ! { dg-error "has no IMPLICIT type" }
+
+if (IOSTAT_INQUIRE_INTERNAL_UNIT <= 0) call abort() ! { dg-error "has no IMPLICIT type" }
+print *,STAT_STOPPED_IMAGE ! { dg-error "has no IMPLICIT type" }
+print *, STAT_LOCKED_OTHER_IMAGE ! { dg-error "has no IMPLICIT type" }
+print *, STAT_LOCKED ! { dg-error "has no IMPLICIT type" }
+print *, STAT_UNLOCKED ! { dg-error "has no IMPLICIT type" }
+end
+
+module m
+USE iso_fortran_env, only: ATOMIC_INT_KIND ! { dg-error "is not in the selected standard" }
+implicit none
+end module m
+
+module m2
+USE iso_fortran_env, only: foo => STAT_UNLOCKED ! { dg-error "is not in the selected standard" }
+implicit none
+end module m2
+
+module m3
+USE iso_fortran_env, foo => IOSTAT_INQUIRE_INTERNAL_UNIT ! { dg-error "not found" }
+implicit none
+end module m3