diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 9137da53870850c9a836c6678e165be6a6d311e1..8d5bcfac932d19e323d53be479c773e7f144ce01 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,8 @@
+2007-09-17  Tobias Burnus  <burnus@net-b.de>
+
+	* resolve.c (resolve_fl_procedure): Allow private dummies
+	for Fortran 2003.
+
 2007-09-17  Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
 
 	* trans-types.c (gfc_get_desc_dim_type): Do not to try
diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index 55d087ff0892d921959c3f1b11519373238ed49f..a2444a348946157c945d8c73333054a637b9a9d7 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -6885,12 +6885,13 @@ resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
 	      && arg->sym->ts.type == BT_DERIVED
 	      && !arg->sym->ts.derived->attr.use_assoc
 	      && !gfc_check_access (arg->sym->ts.derived->attr.access,
-				    arg->sym->ts.derived->ns->default_access))
+				    arg->sym->ts.derived->ns->default_access)
+	      && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
+				 "PRIVATE type and cannot be a dummy argument"
+				 " of '%s', which is PUBLIC at %L",
+				 arg->sym->name, sym->name, &sym->declared_at)
+		 == FAILURE)
 	    {
-	      gfc_error_now ("'%s' is of a PRIVATE type and cannot be "
-			     "a dummy argument of '%s', which is "
-			     "PUBLIC at %L", arg->sym->name, sym->name,
-			     &sym->declared_at);
 	      /* Stop this message from recurring.  */
 	      arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
 	      return FAILURE;
@@ -6907,12 +6908,14 @@ resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
 		  && arg->sym->ts.type == BT_DERIVED
 		  && !arg->sym->ts.derived->attr.use_assoc
 		  && !gfc_check_access (arg->sym->ts.derived->attr.access,
-					arg->sym->ts.derived->ns->default_access))
+					arg->sym->ts.derived->ns->default_access)
+		  && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
+				     "'%s' in PUBLIC interface '%s' at %L "
+				     "takes dummy arguments of '%s' which is "
+				     "PRIVATE", iface->sym->name, sym->name,
+				     &iface->sym->declared_at,
+				     gfc_typename (&arg->sym->ts)) == FAILURE)
 		{
-		  gfc_error_now ("Procedure '%s' in PUBLIC interface '%s' at %L takes "
-				 "dummy arguments of '%s' which is PRIVATE",
-				 iface->sym->name, sym->name, &iface->sym->declared_at,
-				 gfc_typename(&arg->sym->ts));
 		  /* Stop this message from recurring.  */
 		  arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
 		  return FAILURE;
@@ -6930,12 +6933,14 @@ resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
 		  && arg->sym->ts.type == BT_DERIVED
 		  && !arg->sym->ts.derived->attr.use_assoc
 		  && !gfc_check_access (arg->sym->ts.derived->attr.access,
-					arg->sym->ts.derived->ns->default_access))
+					arg->sym->ts.derived->ns->default_access)
+		  && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
+				     "'%s' in PUBLIC interface '%s' at %L "
+				     "takes dummy arguments of '%s' which is "
+				     "PRIVATE", iface->sym->name, sym->name,
+				     &iface->sym->declared_at,
+				     gfc_typename (&arg->sym->ts)) == FAILURE)
 		{
-		  gfc_error_now ("Procedure '%s' in PUBLIC interface '%s' at %L takes "
-				 "dummy arguments of '%s' which is PRIVATE",
-				 iface->sym->name, sym->name, &iface->sym->declared_at,
-				 gfc_typename(&arg->sym->ts));
 		  /* Stop this message from recurring.  */
 		  arg->sym->ts.derived->attr.access = ACCESS_PUBLIC;
 		  return FAILURE;
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 1c5209a66a576f291e95108117951bcc60aa55a2..94285578b5cea11a500f4836cb3cd2a7d349a84a 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2007-09-17  Tobias Burnus  <burnus@net-b.de>
+
+	* gfortran.dg/interface_15.f90: Compile with -std=f95.
+	* gfortran.dg/private_type_1.f90: Ditto
+	* gfortran.dg/interface_18.f90: New.
+	* gfortran.dg/private_type_8.f90: New.
+
 2007-09-16  Paolo Carlini  <pcarlini@suse.de>
 
 	PR c++/33124
diff --git a/gcc/testsuite/gfortran.dg/interface_15.f90 b/gcc/testsuite/gfortran.dg/interface_15.f90
index c9a3add74aedf0dbbbcdbfa715b24bb1a942810f..15f4298390e945e1a7f508a479d6d31bc5e346cd 100644
--- a/gcc/testsuite/gfortran.dg/interface_15.f90
+++ b/gcc/testsuite/gfortran.dg/interface_15.f90
@@ -1,5 +1,5 @@
 ! { dg-do compile }
-! { dg-options "-c" }
+! { dg-options "-c -std=f95" }
 ! Testcase from PR fortran/25094
 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
 
diff --git a/gcc/testsuite/gfortran.dg/interface_18.f90 b/gcc/testsuite/gfortran.dg/interface_18.f90
new file mode 100644
index 0000000000000000000000000000000000000000..d0a54754883bdcfda0589b5ae7cee798ede6136e
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/interface_18.f90
@@ -0,0 +1,21 @@
+! { dg-do compile }
+! { dg-options "-std=f2003" }
+!
+! Public procedures with private types for the dummies
+! is valid F2003, but invalid per Fortran 95, Sect. 5.2.3
+! See interface_15.f90 for the F95 test case.
+!
+   module mytype_application
+     implicit none
+     private
+     public :: mytype_test
+     type :: mytype_type
+       integer :: i=0
+     end type mytype_type
+   contains
+     subroutine mytype_test( mytype )
+       type(mytype_type), intent(in out) :: mytype
+     end subroutine mytype_test
+   end module mytype_application 
+
+! { dg-final { cleanup-modules "mytype_application" } }
diff --git a/gcc/testsuite/gfortran.dg/private_type_1.f90 b/gcc/testsuite/gfortran.dg/private_type_1.f90
index 34bc457a52fd16a78e36cedc09230241e2f619e6..b6e915104b95a9a8a40e4c7c84bfc2e3590869ea 100644
--- a/gcc/testsuite/gfortran.dg/private_type_1.f90
+++ b/gcc/testsuite/gfortran.dg/private_type_1.f90
@@ -1,4 +1,5 @@
 ! { dg-do compile }
+! { dg-options "-std=f95" }
 ! PR21986 - test based on original example.
 ! A public subroutine must not have private-type, dummy arguments.
 ! Contributed by Paul Thomas <pault@gcc.gnu.org>
diff --git a/gcc/testsuite/gfortran.dg/private_type_8.f90 b/gcc/testsuite/gfortran.dg/private_type_8.f90
new file mode 100644
index 0000000000000000000000000000000000000000..df1609646cfa3e2788435dd3b1a6bef2ad0f1a75
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/private_type_8.f90
@@ -0,0 +1,21 @@
+! { dg-do compile }
+! A public subroutine can have private-type, dummy arguments
+! in Fortran 2003 (but not in Fortran 95).
+! See private_type_1.f90 for the F95 test.
+!
+module modboom
+  implicit none
+  private
+  public:: dummysub
+  type:: intwrapper
+    integer n
+  end type intwrapper
+contains
+  subroutine dummysub(size, arg_array)
+   type(intwrapper) :: size
+   real, dimension(size%n) :: arg_array
+   real :: local_array(4)
+  end subroutine dummysub
+end module modboom
+
+! { dg-final { cleanup-modules "modboom" } }