Index: gcc/fortran/expr.c
===================================================================
--- gcc/fortran/expr.c	(revision 197551)
+++ gcc/fortran/expr.c	(working copy)
@@ -3562,6 +3562,22 @@ gfc_check_pointer_assign (gfc_expr *lvalue, gfc_ex
       if (s1 == s2 || !s1 || !s2)
 	return SUCCESS;
 
+      /* F08:7.2.2.4 (4)  */
+      if (s1->attr.if_source == IFSRC_UNKNOWN
+	  && gfc_explicit_interface_required (s2, err, sizeof(err)))
+	{
+	  gfc_error ("Explicit interface required for '%s' at %L: %s",
+		     s1->name, &lvalue->where, err);
+	  return FAILURE;
+	}
+      if (s2->attr.if_source == IFSRC_UNKNOWN
+	  && gfc_explicit_interface_required (s1, err, sizeof(err)))
+	{
+	  gfc_error ("Explicit interface required for '%s' at %L: %s",
+		     s2->name, &rvalue->where, err);
+	  return FAILURE;
+	}
+
       if (!gfc_compare_interfaces (s1, s2, name, 0, 1,
 				   err, sizeof(err), NULL, NULL))
 	{
Index: gcc/fortran/gfortran.h
===================================================================
--- gcc/fortran/gfortran.h	(revision 197551)
+++ gcc/fortran/gfortran.h	(working copy)
@@ -2851,6 +2851,7 @@ match gfc_iso_c_sub_interface(gfc_code *, gfc_symb
 gfc_expr *gfc_expr_to_initialize (gfc_expr *);
 bool gfc_type_is_extensible (gfc_symbol *);
 gfc_try gfc_resolve_intrinsic (gfc_symbol *, locus *);
+bool gfc_explicit_interface_required (gfc_symbol *, char *, int);
 
 
 /* array.c */
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 197551)
+++ gcc/fortran/resolve.c	(working copy)
@@ -2121,6 +2121,126 @@ not_entry_self_reference  (gfc_symbol *sym, gfc_na
   return true;
 }
 
+
+/* Check for the requirement of an explicit interface. F08:12.4.2.2.  */
+
+bool
+gfc_explicit_interface_required (gfc_symbol *sym, char *errmsg, int err_len)
+{
+  gfc_formal_arglist *arg = gfc_sym_get_dummy_args (sym);
+
+  for ( ; arg; arg = arg->next)
+    {
+      if (!arg->sym)
+	continue;
+
+      if (arg->sym->attr.allocatable)  /* (2a)  */
+	{
+	  snprintf (errmsg, err_len, "allocatable argument");
+	  return true;
+	}
+      else if (arg->sym->attr.asynchronous)
+	{
+	  snprintf (errmsg, err_len, "asynchronous argument");
+	  return true;
+	}
+      else if (arg->sym->attr.optional)
+	{
+	  snprintf (errmsg, err_len, "optional argument");
+	  return true;
+	}
+      else if (arg->sym->attr.pointer)
+	{
+	  snprintf (errmsg, err_len, "pointer argument");
+	  return true;
+	}
+      else if (arg->sym->attr.target)
+	{
+	  snprintf (errmsg, err_len, "target argument");
+	  return true;
+	}
+      else if (arg->sym->attr.value)
+	{
+	  snprintf (errmsg, err_len, "value argument");
+	  return true;
+	}
+      else if (arg->sym->attr.volatile_)
+	{
+	  snprintf (errmsg, err_len, "volatile argument");
+	  return true;
+	}
+      else if (arg->sym->as && arg->sym->as->type == AS_ASSUMED_SHAPE)  /* (2b)  */
+	{
+	  snprintf (errmsg, err_len, "assumed-shape argument");
+	  return true;
+	}
+      else if (arg->sym->as && arg->sym->as->type == AS_ASSUMED_RANK)  /* TS 29113, 6.2.  */
+	{
+	  snprintf (errmsg, err_len, "assumed-rank argument");
+	  return true;
+	}
+      else if (arg->sym->attr.codimension)  /* (2c)  */
+	{
+	  snprintf (errmsg, err_len, "coarray argument");
+	  return true;
+	}
+      else if (false)  /* (2d) TODO: parametrized derived type  */
+	{
+	  snprintf (errmsg, err_len, "parametrized derived type argument");
+	  return true;
+	}
+      else if (arg->sym->ts.type == BT_CLASS)  /* (2e)  */
+	{
+	  snprintf (errmsg, err_len, "polymorphic argument");
+	  return true;
+	}
+      else if (arg->sym->ts.type == BT_ASSUMED)
+	{
+	  /* As assumed-type is unlimited polymorphic (cf. above).
+	     See also TS 29113, Note 6.1.  */
+	  snprintf (errmsg, err_len, "assumed-type argument");
+	  return true;
+	}
+    }
+
+  if (sym->attr.function)
+    {
+      gfc_symbol *res = sym->result ? sym->result : sym;
+
+      if (res->attr.dimension)  /* (3a)  */
+	{
+	  snprintf (errmsg, err_len, "array result");
+	  return true;
+	}
+      else if (res->attr.pointer || res->attr.allocatable)  /* (3b)  */
+	{
+	  snprintf (errmsg, err_len, "pointer or allocatable result");
+	  return true;
+	}
+      else if (res->ts.type == BT_CHARACTER && res->ts.u.cl
+	       && res->ts.u.cl->length
+	       && res->ts.u.cl->length->expr_type != EXPR_CONSTANT)  /* (3c)  */
+	{
+	  snprintf (errmsg, err_len, "result with non-constant character length");
+	  return true;
+	}
+    }
+
+  if (sym->attr.elemental)  /* (4)  */
+    {
+      snprintf (errmsg, err_len, "elemental procedure");
+      return true;
+    }
+  else if (sym->attr.is_bind_c)  /* (5)  */
+    {
+      snprintf (errmsg, err_len, "bind(c) procedure");
+      return true;
+    }
+
+  return false;
+}
+
+
 static void
 resolve_global_procedure (gfc_symbol *sym, locus *where,
 			  gfc_actual_arglist **actual, int sub)
@@ -2128,6 +2248,7 @@ resolve_global_procedure (gfc_symbol *sym, locus *
   gfc_gsymbol * gsym;
   gfc_namespace *ns;
   enum gfc_symbol_type type;
+  char reason[200];
 
   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
 
@@ -2221,139 +2342,17 @@ resolve_global_procedure (gfc_symbol *sym, locus *
 		       &sym->declared_at, l1, l2);
 	}
 
-     /* Type mismatch of function return type and expected type.  */
-     if (sym->attr.function
-	 && !gfc_compare_types (&sym->ts, &def_sym->ts))
+      /* Type mismatch of function return type and expected type.  */
+      if (sym->attr.function && !gfc_compare_types (&sym->ts, &def_sym->ts))
 	gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
 		   sym->name, &sym->declared_at, gfc_typename (&sym->ts),
 		   gfc_typename (&def_sym->ts));
 
-      if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
-	{
-	  gfc_formal_arglist *arg = def_sym->formal;
-	  for ( ; arg; arg = arg->next)
-	    if (!arg->sym)
-	      continue;
-	    /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
-	    else if (arg->sym->attr.allocatable
-		     || arg->sym->attr.asynchronous
-		     || arg->sym->attr.optional
-		     || arg->sym->attr.pointer
-		     || arg->sym->attr.target
-		     || arg->sym->attr.value
-		     || arg->sym->attr.volatile_)
-	      {
-		gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
-			   "has an attribute that requires an explicit "
-			   "interface for this procedure", arg->sym->name,
-			   sym->name, &sym->declared_at);
-		break;
-	      }
-	    /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
-	    else if (arg->sym && arg->sym->as
-		     && arg->sym->as->type == AS_ASSUMED_SHAPE)
-	      {
-		gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
-			   "argument '%s' must have an explicit interface",
-			   sym->name, &sym->declared_at, arg->sym->name);
-		break;
-	      }
-	    /* TS 29113, 6.2.  */
-	    else if (arg->sym && arg->sym->as
-		     && arg->sym->as->type == AS_ASSUMED_RANK)
-	      {
-		gfc_error ("Procedure '%s' at %L with assumed-rank dummy "
-			   "argument '%s' must have an explicit interface",
-			   sym->name, &sym->declared_at, arg->sym->name);
-		break;
-	      }
-	    /* F2008, 12.4.2.2 (2c)  */
-	    else if (arg->sym->attr.codimension)
-	      {
-		gfc_error ("Procedure '%s' at %L with coarray dummy argument "
-			   "'%s' must have an explicit interface",
-			   sym->name, &sym->declared_at, arg->sym->name);
-		break;
-	      }
-	    /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
-	    else if (false) /* TODO: is a parametrized derived type  */
-	      {
-		gfc_error ("Procedure '%s' at %L with parametrized derived "
-			   "type argument '%s' must have an explicit "
-			   "interface", sym->name, &sym->declared_at,
-			   arg->sym->name);
-		break;
-	      }
-	    /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
-	    else if (arg->sym->ts.type == BT_CLASS)
-	      {
-		gfc_error ("Procedure '%s' at %L with polymorphic dummy "
-			   "argument '%s' must have an explicit interface",
-			   sym->name, &sym->declared_at, arg->sym->name);
-		break;
-	      }
-	    /* As assumed-type is unlimited polymorphic (cf. above).
-	       See also  TS 29113, Note 6.1.  */
-	    else if (arg->sym->ts.type == BT_ASSUMED)
-	      {
-		gfc_error ("Procedure '%s' at %L with assumed-type dummy "
-			   "argument '%s' must have an explicit interface",
-			   sym->name, &sym->declared_at, arg->sym->name);
-		break;
-	      }
-	}
+      if (sym->attr.if_source == IFSRC_UNKNOWN
+	  && gfc_explicit_interface_required (def_sym, reason, sizeof(reason)))
+	gfc_error ("Explicit interface required for '%s' at %L: %s",
+		    sym->name, &sym->declared_at, reason);
 
-      if (def_sym->attr.function)
-	{
-	  /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
-	  if (def_sym->as && def_sym->as->rank
-	      && (!sym->as || sym->as->rank != def_sym->as->rank))
-	    gfc_error ("The reference to function '%s' at %L either needs an "
-		       "explicit INTERFACE or the rank is incorrect", sym->name,
-		       where);
-
-	  /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
-	  if ((def_sym->result->attr.pointer
-	       || def_sym->result->attr.allocatable)
-	       && (sym->attr.if_source != IFSRC_IFBODY
-		   || def_sym->result->attr.pointer
-			!= sym->result->attr.pointer
-		   || def_sym->result->attr.allocatable
-			!= sym->result->attr.allocatable))
-	    gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
-		       "result must have an explicit interface", sym->name,
-		       where);
-
-	  /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
-	  if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
-	      && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
-	    {
-	      gfc_charlen *cl = sym->ts.u.cl;
-
-	      if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
-		  && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
-		{
-		  gfc_error ("Nonconstant character-length function '%s' at %L "
-			     "must have an explicit interface", sym->name,
-			     &sym->declared_at);
-		}
-	    }
-	}
-
-      /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
-      if (def_sym->attr.elemental && !sym->attr.elemental)
-	{
-	  gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
-		     "interface", sym->name, &sym->declared_at);
-	}
-
-      /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
-      if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
-	{
-	  gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
-		     "an explicit interface", sym->name, &sym->declared_at);
-	}
-
       if (!pedantic
 	  || ((gfc_option.warn_std & GFC_STD_LEGACY)
 	      && !(gfc_option.warn_std & GFC_STD_GNU)))
Index: gcc/testsuite/gfortran.dg/assumed_rank_4.f90
===================================================================
--- gcc/testsuite/gfortran.dg/assumed_rank_4.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/assumed_rank_4.f90	(working copy)
@@ -20,8 +20,8 @@ end subroutine valid2
 
 subroutine foo99(x)
   integer  x(99)
-  call valid1(x) ! { dg-error "Procedure 'valid1' at .1. with assumed-rank dummy argument 'x' must have an explicit interface" }
-  call valid2(x(1)) ! { dg-error "Procedure 'valid2' at .1. with assumed-type dummy argument 'x' must have an explicit interface" }
+  call valid1(x) ! { dg-error "Explicit interface required" }
+  call valid2(x(1)) ! { dg-error "Explicit interface required" }
 end subroutine foo99
 
 subroutine foo(x)
Index: gcc/testsuite/gfortran.dg/auto_char_len_4.f90
===================================================================
--- gcc/testsuite/gfortran.dg/auto_char_len_4.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/auto_char_len_4.f90	(working copy)
@@ -14,8 +14,8 @@ FUNCTION a()
 END FUNCTION a
 
 SUBROUTINE s(n)
-  CHARACTER(LEN=n), EXTERNAL :: a ! { dg-error "must have an explicit interface" }
-  CHARACTER(LEN=n), EXTERNAL :: d ! { dg-error "must have an explicit interface" }
+  CHARACTER(LEN=n), EXTERNAL :: a ! { dg-error "Explicit interface required" }
+  CHARACTER(LEN=n), EXTERNAL :: d ! { dg-error "Explicit interface required" }
   interface
     function b (m)                ! This is OK
       CHARACTER(LEN=m) :: b
Index: gcc/testsuite/gfortran.dg/block_11.f90
===================================================================
--- gcc/testsuite/gfortran.dg/block_11.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/block_11.f90	(working copy)
@@ -50,7 +50,7 @@ module m3
   implicit none
 contains
   subroutine my_test()
-    procedure(), pointer :: ptr
+    procedure(sub), pointer :: ptr
     ! Before the fix, one had the link error
     ! "undefined reference to `sub.1909'"
     block
Index: gcc/testsuite/gfortran.dg/whole_file_16.f90
===================================================================
--- gcc/testsuite/gfortran.dg/whole_file_16.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/whole_file_16.f90	(working copy)
@@ -5,7 +5,7 @@
 !
 program main
   real, dimension(2) :: a
-  call foo(a)                ! { dg-error "must have an explicit interface" }
+  call foo(a)                ! { dg-error "Explicit interface required" }
 end program main
 
 subroutine foo(a)
Index: gcc/testsuite/gfortran.dg/whole_file_18.f90
===================================================================
--- gcc/testsuite/gfortran.dg/whole_file_18.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/whole_file_18.f90	(working copy)
@@ -5,7 +5,7 @@
 !
       PROGRAM MAIN
       REAL A
-      CALL SUB(A)             ! { dg-error "requires an explicit interface" }
+      CALL SUB(A)             ! { dg-error "Explicit interface required" }
       END PROGRAM
 
       SUBROUTINE SUB(A,I)
Index: gcc/testsuite/gfortran.dg/whole_file_20.f03
===================================================================
--- gcc/testsuite/gfortran.dg/whole_file_20.f03	(revision 197551)
+++ gcc/testsuite/gfortran.dg/whole_file_20.f03	(working copy)
@@ -17,8 +17,8 @@ PROGRAM main
 
   INTEGER :: coarr[*]
 
-  CALL coarray(coarr)         ! { dg-error " must have an explicit interface" }
-  CALL polymorph(tt)          ! { dg-error " must have an explicit interface" }
+  CALL coarray(coarr)         ! { dg-error "Explicit interface required" }
+  CALL polymorph(tt)          ! { dg-error "Explicit interface required" }
 END PROGRAM
 
 SUBROUTINE coarray(a)
Index: gcc/testsuite/gfortran.dg/whole_file_7.f90
===================================================================
--- gcc/testsuite/gfortran.dg/whole_file_7.f90	(revision 197551)
+++ gcc/testsuite/gfortran.dg/whole_file_7.f90	(working copy)
@@ -29,6 +29,6 @@ end function test
 
 program arr     ! The error was not picked up causing an ICE
   real, dimension(2) :: res
-  res = test(2) ! { dg-error "needs an explicit INTERFACE" }
+  res = test(2) ! { dg-error "Explicit interface required" }
   print *, res
 end program
