This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Patch to remove warn_for_assignment


This patch completes the change from warn_for_assignment building up
sentences from pieces with sprintf to having whole sentences in the
source passed to pedwarn.  Thus %qE can now be used in the
diagnostics, leading to better diagnostics when pointers to functions
are used, and i18n for these diagnostics no longer suffers from the
problems of translating sentence fragments.

The next stage will be arranging for warning rather than pedwarn to be
used when convert_for_assignment is called when inlining an
unprototyped function.  Although warnings for bad calls to
unprototyped functions ought to be handled by a separate pass, not
depending on optimization, we can at least readily ensure that

void f(x)signed char *x; {}
void g(unsigned char *x) { f(x); }

isn't wrongly rejected at -O3 -pedantic-errors.  In fact this mismatch
is explicitly permitted by ISO C so perhaps we shouldn't warn at all
for it by default, whereas

void f(x)int *x; {}
void g(unsigned *x) { f(x); }

does have undefined behavior on execution (although it would be
expected to work in practice) so the warning is clearly appropriate
even though dependence of such a warning on -O3 isn't ideal.

(Much the same applies to errors from convert_for_assignment, as well
as pedwarns, e.g. a call to an unprototyped function expecting a
struct but passed an int, though these are of more difficulty and
little utility, and the sensible result probably involves generating
an abort for the argument computation; in the case of pedwarns the
implicit conversion can at least be done and meaningful code
generated.)

Bootstrapped with no regressions on i686-pc-linux-gnu.  Applied to
mainline.  gcc.pot regenerated.

-- 
Joseph S. Myers               http://www.srcf.ucam.org/~jsm28/gcc/
    jsm@polyomino.org.uk (personal mail)
    joseph@codesourcery.com (CodeSourcery mail)
    jsm28@gcc.gnu.org (Bugzilla assignments and CCs)

2004-10-08  Joseph S. Myers  <jsm@polyomino.org.uk>

	* c-typeck.c (enum impl_conv): New.
	(convert_for_assignment): Use it.  Take tree for function called
	instead of its name.  Handle ObjC selectors for diagnostics at
	start of function.  Select diagnostic text within the function
	using full sentences for diagnsotics.  Use %qE to name functions
	in diagnostics.
	(convert_arguments, build_modify_expr,
	c_convert_parm_for_inlining, digest_init, c_finish_return): Update
	callers to convert_for_assignment.
	(warn_for_assignment): Remove.

testsuite:
2004-10-08  Joseph S. Myers  <jsm@polyomino.org.uk>

	* gcc.dg/assign-warn-1.c, gcc.dg/assign-warn-2.c: New tests.
	* gcc.dg/warn-1.c, gcc.dg/noncompile/20020213-1.c,
	objc.dg/method-9.m: Update expected diagnostics.

diff -rupN GCC.orig/gcc/c-typeck.c GCC/gcc/c-typeck.c
--- GCC.orig/gcc/c-typeck.c	2004-10-06 16:49:54.000000000 +0000
+++ GCC/gcc/c-typeck.c	2004-10-07 18:38:46.000000000 +0000
@@ -55,6 +55,15 @@ enum lvalue_use {
   lv_asm
 };
 
+/* Possible cases of implicit bad conversions.  Used to select
+   diagnostic messages in convert_for_assignment.  */
+enum impl_conv {
+  ic_argpass,
+  ic_assign,
+  ic_init,
+  ic_return
+};
+
 /* The level of nesting inside "__alignof__".  */
 int in_alignof;
 
@@ -81,9 +90,8 @@ static tree default_function_array_conve
 static tree lookup_field (tree, tree);
 static tree convert_arguments (tree, tree, tree, tree);
 static tree pointer_diff (tree, tree);
-static tree convert_for_assignment (tree, tree, const char *, tree, tree,
+static tree convert_for_assignment (tree, tree, enum impl_conv, tree, tree,
 				    int);
-static void warn_for_assignment (const char *, const char *, tree, int);
 static tree valid_compound_expr_initializer (tree, tree);
 static void push_string (const char *);
 static void push_member_name (tree);
@@ -2029,16 +2037,12 @@ convert_arguments (tree typelist, tree v
   tree result = NULL;
   int parmnum;
   tree selector;
-  tree name = NULL_TREE;
 
-  /* Determine the function name for the use of convert_for_assignment
-     and warn_for_assignment called from there.  */
+  /* Change pointer to function to the function itself for
+     diagnostics.  */
   if (TREE_CODE (function) == ADDR_EXPR
       && TREE_CODE (TREE_OPERAND (function, 0)) == FUNCTION_DECL)
-    {
-      function = TREE_OPERAND (function, 0);
-      name = DECL_NAME (function);
-    }
+    function = TREE_OPERAND (function, 0);
 
   /* Handle an ObjC selector specially for diagnostics.  */
   selector = objc_message_selector ();
@@ -2189,9 +2193,9 @@ convert_arguments (tree typelist, tree v
 		    }
 		}
 
-	      parmval = convert_for_assignment (type, val,
-					        (char *) 0, /* arg passing  */
-						fundecl, name, parmnum + 1);
+	      parmval = convert_for_assignment (type, val, ic_argpass,
+						fundecl, function,
+						parmnum + 1);
 
 	      if (targetm.calls.promote_prototypes (fundecl ? TREE_TYPE (fundecl) : 0)
 		  && INTEGRAL_TYPE_P (type)
@@ -3390,7 +3394,7 @@ build_modify_expr (tree lhs, enum tree_c
 
   /* Convert new value to destination type.  */
 
-  newrhs = convert_for_assignment (lhstype, newrhs, _("assignment"),
+  newrhs = convert_for_assignment (lhstype, newrhs, ic_assign,
 				   NULL_TREE, NULL_TREE, 0);
   if (TREE_CODE (newrhs) == ERROR_MARK)
     return error_mark_node;
@@ -3407,7 +3411,7 @@ build_modify_expr (tree lhs, enum tree_c
 
   if (olhstype == TREE_TYPE (result))
     return result;
-  return convert_for_assignment (olhstype, result, _("assignment"),
+  return convert_for_assignment (olhstype, result, ic_assign,
 				 NULL_TREE, NULL_TREE, 0);
 }
 
@@ -3416,21 +3420,63 @@ build_modify_expr (tree lhs, enum tree_c
    The real work of conversion is done by `convert'.
    The purpose of this function is to generate error messages
    for assignments that are not allowed in C.
-   ERRTYPE is a string to use in error messages:
-   "assignment", "return", etc.  If it is null, this is parameter passing
-   for a function call (and different error messages are output).
+   ERRTYPE says whether it is argument passing, assignment,
+   initialization or return.
 
-   FUNNAME is the name of the function being called,
-   as an IDENTIFIER_NODE, or null.
+   FUNCTION is a tree for the function being called.
    PARMNUM is the number of the argument, for printing in error messages.  */
 
 static tree
-convert_for_assignment (tree type, tree rhs, const char *errtype,
-			tree fundecl, tree funname, int parmnum)
+convert_for_assignment (tree type, tree rhs, enum impl_conv errtype,
+			tree fundecl, tree function, int parmnum)
 {
   enum tree_code codel = TREE_CODE (type);
   tree rhstype;
   enum tree_code coder;
+  tree rname = NULL_TREE;
+
+  if (errtype == ic_argpass)
+    {
+      tree selector;
+      /* Change pointer to function to the function itself for
+	 diagnostics.  */
+      if (TREE_CODE (function) == ADDR_EXPR
+	  && TREE_CODE (TREE_OPERAND (function, 0)) == FUNCTION_DECL)
+	function = TREE_OPERAND (function, 0);
+
+      /* Handle an ObjC selector specially for diagnostics.  */
+      selector = objc_message_selector ();
+      rname = function;
+      if (selector && parmnum > 2)
+	{
+	  rname = selector;
+	  parmnum -= 2;
+	}
+    }
+
+  /* This macro is used to emit diagnostics to ensure that all format
+     strings are complete sentences, visible to gettext and checked at
+     compile time.  */
+#define WARN_FOR_ASSIGNMENT(AR, AS, IN, RE)	\
+  do {						\
+    switch (errtype)				\
+      {						\
+      case ic_argpass:				\
+	pedwarn (AR, parmnum, rname);		\
+	break;					\
+      case ic_assign:				\
+	pedwarn (AS);				\
+	break;					\
+      case ic_init:				\
+	pedwarn (IN);				\
+	break;					\
+      case ic_return:				\
+	pedwarn (RE);				\
+	break;					\
+      default:					\
+	gcc_unreachable ();			\
+      }						\
+  } while (0)
 
   /* Strip NON_LVALUE_EXPRs since we aren't using as an lvalue.  */
   /* Do not use STRIP_NOPS here.  We do not want an enumerator
@@ -3507,7 +3553,8 @@ convert_for_assignment (tree type, tree 
 
   /* Conversion to a transparent union from its member types.
      This applies only to function arguments.  */
-  else if (codel == UNION_TYPE && TYPE_TRANSPARENT_UNION (type) && !errtype)
+  else if (codel == UNION_TYPE && TYPE_TRANSPARENT_UNION (type)
+	   && errtype == ic_argpass)
     {
       tree memb_types;
       tree marginal_memb_type = 0;
@@ -3582,13 +3629,27 @@ convert_for_assignment (tree type, tree 
 		     function where an ordinary one is wanted, but not
 		     vice-versa.  */
 		  if (TYPE_QUALS (ttl) & ~TYPE_QUALS (ttr))
-		    warn_for_assignment ("%s makes qualified function pointer from unqualified",
-					 errtype, funname, parmnum);
+		    WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE "
+					    "makes qualified function "
+					    "pointer from unqualified"),
+					 N_("assignment makes qualified "
+					    "function pointer from "
+					    "unqualified"),
+					 N_("initialization makes qualified "
+					    "function pointer from "
+					    "unqualified"),
+					 N_("return makes qualified function "
+					    "pointer from unqualified"));
 		}
 	      else if (TYPE_QUALS (ttr) & ~TYPE_QUALS (ttl))
-		warn_for_assignment ("%s discards qualifiers from pointer target type",
-				     errtype, funname,
-				     parmnum);
+		WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE discards "
+					"qualifiers from pointer target type"),
+				     N_("assignment discards qualifiers "
+					"from pointer target type"),
+				     N_("initialization discards qualifiers "
+					"from pointer target type"),
+				     N_("return discards qualifiers from "
+					"pointer target type"));
 	    }
 
 	  if (pedantic && !DECL_IN_SYSTEM_HEADER (fundecl))
@@ -3630,17 +3691,29 @@ convert_for_assignment (tree type, tree 
 		      which are not ANSI null ptr constants.  */
 		   && (!integer_zerop (rhs) || TREE_CODE (rhs) == NOP_EXPR)
 		   && TREE_CODE (ttl) == FUNCTION_TYPE)))
-	    warn_for_assignment ("ISO C forbids %s between function "
-				 "pointer and %<void *%>",
-				 errtype, funname, parmnum);
+	    WARN_FOR_ASSIGNMENT (N_("ISO C forbids passing argument %d of "
+				    "%qE between function pointer "
+				    "and %<void *%>"),
+				 N_("ISO C forbids assignment between "
+				    "function pointer and %<void *%>"),
+				 N_("ISO C forbids initialization between "
+				    "function pointer and %<void *%>"),
+				 N_("ISO C forbids return between function "
+				    "pointer and %<void *%>"));
 	  /* Const and volatile mean something different for function types,
 	     so the usual warnings are not appropriate.  */
 	  else if (TREE_CODE (ttr) != FUNCTION_TYPE
 		   && TREE_CODE (ttl) != FUNCTION_TYPE)
 	    {
 	      if (TYPE_QUALS (ttr) & ~TYPE_QUALS (ttl))
-		warn_for_assignment ("%s discards qualifiers from pointer target type",
-				     errtype, funname, parmnum);
+		WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE discards "
+					"qualifiers from pointer target type"),
+				     N_("assignment discards qualifiers "
+					"from pointer target type"),
+				     N_("initialization discards qualifiers "
+					"from pointer target type"),
+				     N_("return discards qualifiers from "
+					"pointer target type"));
 	      /* If this is not a case of ignoring a mismatch in signedness,
 		 no warning.  */
 	      else if (VOID_TYPE_P (ttl) || VOID_TYPE_P (ttr)
@@ -3648,8 +3721,14 @@ convert_for_assignment (tree type, tree 
 		;
 	      /* If there is a mismatch, do warn.  */
 	      else
-		warn_for_assignment ("pointer targets in %s differ in signedness",
-				     errtype, funname, parmnum);
+		WARN_FOR_ASSIGNMENT (N_("pointer targets in passing argument "
+					"%d of %qE differ in signedness"),
+				     N_("pointer targets in assignment "
+					"differ in signedness"),
+				     N_("pointer targets in initialization "
+					"differ in signedness"),
+				     N_("pointer targets in return differ "
+					"in signedness"));
 	    }
 	  else if (TREE_CODE (ttl) == FUNCTION_TYPE
 		   && TREE_CODE (ttr) == FUNCTION_TYPE)
@@ -3659,13 +3738,24 @@ convert_for_assignment (tree type, tree 
 		 it is okay to use a const or volatile function
 		 where an ordinary one is wanted, but not vice-versa.  */
 	      if (TYPE_QUALS (ttl) & ~TYPE_QUALS (ttr))
-		warn_for_assignment ("%s makes qualified function pointer from unqualified",
-				     errtype, funname, parmnum);
+		WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE makes "
+					"qualified function pointer "
+					"from unqualified"),
+				     N_("assignment makes qualified function "
+					"pointer from unqualified"),
+				     N_("initialization makes qualified "
+					"function pointer from unqualified"),
+				     N_("return makes qualified function "
+					"pointer from unqualified"));
 	    }
 	}
       else
-	warn_for_assignment ("%s from incompatible pointer type",
-			     errtype, funname, parmnum);
+	WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE from "
+				"incompatible pointer type"),
+			     N_("assignment from incompatible pointer type"),
+			     N_("initialization from incompatible "
+				"pointer type"),
+			     N_("return from incompatible pointer type"));
       return convert (type, rhs);
     }
   else if (codel == POINTER_TYPE && coder == ARRAY_TYPE)
@@ -3684,39 +3774,49 @@ convert_for_assignment (tree type, tree 
 	    && TREE_CODE (TREE_TYPE (rhs)) == INTEGER_TYPE
 	    && TREE_CODE (TREE_OPERAND (rhs, 0)) == INTEGER_CST
 	    && integer_zerop (TREE_OPERAND (rhs, 0))))
-	  warn_for_assignment ("%s makes pointer from integer without a cast",
-			       errtype, funname, parmnum);
+	WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE makes "
+				"pointer from integer without a cast"),
+			     N_("assignment makes pointer from integer "
+				"without a cast"),
+			     N_("initialization makes pointer from "
+				"integer without a cast"),
+			     N_("return makes pointer from integer "
+				"without a cast"));
 
       return convert (type, rhs);
     }
   else if (codel == INTEGER_TYPE && coder == POINTER_TYPE)
     {
-      warn_for_assignment ("%s makes integer from pointer without a cast",
-			   errtype, funname, parmnum);
+      WARN_FOR_ASSIGNMENT (N_("passing argument %d of %qE makes integer "
+			      "from pointer without a cast"),
+			   N_("assignment makes integer from pointer "
+			      "without a cast"),
+			   N_("initialization makes integer from pointer "
+			      "without a cast"),
+			   N_("return makes integer from pointer "
+			      "without a cast"));
       return convert (type, rhs);
     }
   else if (codel == BOOLEAN_TYPE && coder == POINTER_TYPE)
     return convert (type, rhs);
 
-  if (!errtype)
+  switch (errtype)
     {
-      if (funname)
-	{
-	  tree selector = objc_message_selector ();
-
-	  if (selector && parmnum > 2)
-	    error ("incompatible type for argument %d of %qs",
-		   parmnum - 2, IDENTIFIER_POINTER (selector));
-	  else
-	    error ("incompatible type for argument %d of %qs",
-		   parmnum, IDENTIFIER_POINTER (funname));
-	}
-      else
-	error ("incompatible type for argument %d of indirect function call",
-	       parmnum);
+    case ic_argpass:
+      error ("incompatible type for argument %d of %qE", parmnum, rname);
+      break;
+    case ic_assign:
+      error ("incompatible types in assignment");
+      break;
+    case ic_init:
+      error ("incompatible types in initialization");
+      break;
+    case ic_return:
+      error ("incompatible types in return");
+      break;
+    default:
+      gcc_unreachable ();
     }
-  else
-    error ("incompatible types in %s", errtype);
 
   return error_mark_node;
 }
@@ -3737,56 +3837,14 @@ c_convert_parm_for_inlining (tree parm, 
 
   type = TREE_TYPE (parm);
   ret = convert_for_assignment (type, value,
-				(char *) 0 /* arg passing  */, fn,
-				DECL_NAME (fn), argnum);
+				ic_argpass, fn,
+				fn, argnum);
   if (targetm.calls.promote_prototypes (TREE_TYPE (fn))
       && INTEGRAL_TYPE_P (type)
       && (TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node)))
     ret = default_conversion (ret);
   return ret;
 }
-
-/* Print a warning using MSGID.
-   It gets OPNAME as its one parameter.
-   If OPNAME is null, it is replaced by "passing arg ARGNUM of 'FUNCTION'".
-   FUNCTION and ARGNUM are handled specially if we are building an
-   Objective-C selector.  */
-
-static void
-warn_for_assignment (const char *msgid, const char *opname, tree function,
-		     int argnum)
-{
-  if (opname == 0)
-    {
-      tree selector = objc_message_selector ();
-      char * new_opname;
-
-      if (selector && argnum > 2)
-	{
-	  function = selector;
-	  argnum -= 2;
-	}
-      gcc_assert (argnum > 0);
-      if (function)
-	{
-	  /* Function name is known; supply it.  */
-	  const char *const argstring = _("passing arg %d of '%s'");
-	  new_opname = (char *) alloca (IDENTIFIER_LENGTH (function)
-			       + strlen (argstring) + 1 + 25 /*%d*/ + 1);
-	  sprintf (new_opname, argstring, argnum,
-		   IDENTIFIER_POINTER (function));
-	}
-      else
-	{
-	  /* Function name unknown (call through ptr); just give arg number.  */
-	  const char *const argnofun = _("passing arg %d of pointer to function");
-	  new_opname = (char *) alloca (strlen (argnofun) + 1 + 25 /*%d*/ + 1);
-	  sprintf (new_opname, argnofun, argnum);
-	}
-      opname = new_opname;
-    }
-  pedwarn (msgid, opname);
-}
 
 /* If VALUE is a compound expr all of whose expressions are constant, then
    return its value.  Otherwise, return error_mark_node.
@@ -4254,7 +4312,7 @@ digest_init (tree type, tree init, bool 
 	 for arrays and functions.  We must not call it in the
 	 case where inside_init is a null pointer constant.  */
       inside_init
-	= convert_for_assignment (type, init, _("initialization"),
+	= convert_for_assignment (type, init, ic_init,
 				  NULL_TREE, NULL_TREE, 0);
 
       /* Check to see if we have already given an error message.  */
@@ -6394,7 +6452,7 @@ c_finish_return (tree retval)
     }
   else
     {
-      tree t = convert_for_assignment (valtype, retval, _("return"),
+      tree t = convert_for_assignment (valtype, retval, ic_return,
 				       NULL_TREE, NULL_TREE, 0);
       tree res = DECL_RESULT (current_function_decl);
       tree inner;
diff -rupN GCC.orig/gcc/testsuite/gcc.dg/assign-warn-1.c GCC/gcc/testsuite/gcc.dg/assign-warn-1.c
--- GCC.orig/gcc/testsuite/gcc.dg/assign-warn-1.c	1970-01-01 00:00:00.000000000 +0000
+++ GCC/gcc/testsuite/gcc.dg/assign-warn-1.c	2004-10-07 19:11:19.000000000 +0000
@@ -0,0 +1,123 @@
+/* Test diagnostics for bad implicit type conversions.  */
+/* Origin: Joseph Myers <jsm@polyomino.org.uk> */
+/* { dg-do compile } */
+/* { dg-options "-pedantic" } */
+
+#define TESTARG(ID, TL, TR) void ID##F(TL); void ID##F2(TR x) { ID##F(x); } extern int dummy
+#define TESTARP(ID, TL, TR) struct { void (*x)(TL); } ID##Fp; void ID##F2(TR x) { ID##Fp.x(x); } extern int dummy
+#define TESTASS(ID, TL, TR) void ID##F(TR x) { TL y; y = x; } extern int dummy
+#define TESTINI(ID, TL, TR) void ID##F(TR x) { TL y = x; } extern int dummy
+#define TESTRET(ID, TL, TR) TR ID##V; TL ID##F(void) { return ID##V; } extern int dummy
+
+typedef void (*fp)(void);
+typedef void (*nrfp)(void) __attribute__((noreturn));
+
+TESTARG(fqa, nrfp, fp); /* { dg-warning "warning: passing argument 1 of 'fqaF' makes qualified function pointer from unqualified" } */
+TESTARP(fqb, nrfp, fp); /* { dg-warning "warning: passing argument 1 of 'fqbFp.x' makes qualified function pointer from unqualified" } */
+TESTASS(fqc, nrfp, fp); /* { dg-warning "warning: assignment makes qualified function pointer from unqualified" } */
+TESTINI(fqd, nrfp, fp); /* { dg-warning "warning: initialization makes qualified function pointer from unqualified" } */
+TESTRET(fqe, nrfp, fp); /* { dg-warning "warning: return makes qualified function pointer from unqualified" } */
+
+TESTARG(ofqa, fp, nrfp);
+TESTARP(ofqb, fp, nrfp);
+TESTASS(ofqc, fp, nrfp);
+TESTINI(ofqd, fp, nrfp);
+TESTRET(ofqe, fp, nrfp);
+
+TESTARG(qa, char *, const char *); /* { dg-warning "warning: passing argument 1 of 'qaF' discards qualifiers from pointer target type" } */
+TESTARP(qb, char *, const char *); /* { dg-warning "warning: passing argument 1 of 'qbFp.x' discards qualifiers from pointer target type" } */
+TESTASS(qc, char *, const char *); /* { dg-warning "warning: assignment discards qualifiers from pointer target type" } */
+TESTINI(qd, char *, const char *); /* { dg-warning "warning: initialization discards qualifiers from pointer target type" } */
+TESTRET(qe, char *, const char *); /* { dg-warning "warning: return discards qualifiers from pointer target type" } */
+
+TESTARG(oqa, const char *, char *);
+TESTARP(oqb, const char *, char *);
+TESTASS(oqc, const char *, char *);
+TESTINI(oqd, const char *, char *);
+TESTRET(oqe, const char *, char *);
+
+TESTARG(fda, fp, void *); /* { dg-warning "warning: ISO C forbids passing argument 1 of 'fdaF' between function pointer and 'void \\*'" } */
+TESTARP(fdb, fp, void *); /* { dg-warning "warning: ISO C forbids passing argument 1 of 'fdbFp.x' between function pointer and 'void \\*'" } */
+TESTASS(fdc, fp, void *); /* { dg-warning "warning: ISO C forbids assignment between function pointer and 'void \\*'" } */
+TESTINI(fdd, fp, void *); /* { dg-warning "warning: ISO C forbids initialization between function pointer and 'void \\*'" } */
+TESTRET(fde, fp, void *); /* { dg-warning "warning: ISO C forbids return between function pointer and 'void \\*'" } */
+
+TESTARG(dfa, void *, fp); /* { dg-warning "warning: ISO C forbids passing argument 1 of 'dfaF' between function pointer and 'void \\*'" } */
+TESTARP(dfb, void *, fp); /* { dg-warning "warning: ISO C forbids passing argument 1 of 'dfbFp.x' between function pointer and 'void \\*'" } */
+TESTASS(dfc, void *, fp); /* { dg-warning "warning: ISO C forbids assignment between function pointer and 'void \\*'" } */
+TESTINI(dfd, void *, fp); /* { dg-warning "warning: ISO C forbids initialization between function pointer and 'void \\*'" } */
+TESTRET(dfe, void *, fp); /* { dg-warning "warning: ISO C forbids return between function pointer and 'void \\*'" } */
+
+TESTARG(sua, int *, unsigned int *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'suaF' differ in signedness" } */
+TESTARP(sub, int *, unsigned int *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'subFp.x' differ in signedness" } */
+TESTASS(suc, int *, unsigned int *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(sud, int *, unsigned int *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(sue, int *, unsigned int *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(usa, unsigned int *, int *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'usaF' differ in signedness" } */
+TESTARP(usb, unsigned int *, int *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'usbFp.x' differ in signedness" } */
+TESTASS(usc, unsigned int *, int *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(usd, unsigned int *, int *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(use, unsigned int *, int *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(cua, char *, unsigned char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'cuaF' differ in signedness" } */
+TESTARP(cub, char *, unsigned char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'cubFp.x' differ in signedness" } */
+TESTASS(cuc, char *, unsigned char *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(cud, char *, unsigned char *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(cue, char *, unsigned char *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(uca, unsigned char *, char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'ucaF' differ in signedness" } */
+TESTARP(ucb, unsigned char *, char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'ucbFp.x' differ in signedness" } */
+TESTASS(ucc, unsigned char *, char *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(ucd, unsigned char *, char *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(uce, unsigned char *, char *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(csa, char *, signed char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'csaF' differ in signedness" } */
+TESTARP(csb, char *, signed char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'csbFp.x' differ in signedness" } */
+TESTASS(csc, char *, signed char *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(csd, char *, signed char *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(cse, char *, signed char *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(sca, signed char *, char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'scaF' differ in signedness" } */
+TESTARP(scb, signed char *, char *); /* { dg-warning "warning: pointer targets in passing argument 1 of 'scbFp.x' differ in signedness" } */
+TESTASS(scc, signed char *, char *); /* { dg-warning "warning: pointer targets in assignment differ in signedness" } */
+TESTINI(scd, signed char *, char *); /* { dg-warning "warning: pointer targets in initialization differ in signedness" } */
+TESTRET(sce, signed char *, char *); /* { dg-warning "warning: pointer targets in return differ in signedness" } */
+
+TESTARG(cia, char *, int *); /* { dg-warning "warning: passing argument 1 of 'ciaF' from incompatible pointer type" } */
+TESTARP(cib, char *, int *); /* { dg-warning "warning: passing argument 1 of 'cibFp.x' from incompatible pointer type" } */
+TESTASS(cic, char *, int *); /* { dg-warning "warning: assignment from incompatible pointer type" } */
+TESTINI(cid, char *, int *); /* { dg-warning "warning: initialization from incompatible pointer type" } */
+TESTRET(cie, char *, int *); /* { dg-warning "warning: return from incompatible pointer type" } */
+
+TESTARG(ica, int *, char *); /* { dg-warning "warning: passing argument 1 of 'icaF' from incompatible pointer type" } */
+TESTARP(icb, int *, char *); /* { dg-warning "warning: passing argument 1 of 'icbFp.x' from incompatible pointer type" } */
+TESTASS(icc, int *, char *); /* { dg-warning "warning: assignment from incompatible pointer type" } */
+TESTINI(icd, int *, char *); /* { dg-warning "warning: initialization from incompatible pointer type" } */
+TESTRET(ice, int *, char *); /* { dg-warning "warning: return from incompatible pointer type" } */
+
+TESTARG(ciia, char *, int); /* { dg-warning "warning: passing argument 1 of 'ciiaF' makes pointer from integer without a cast" } */
+TESTARP(ciib, char *, int); /* { dg-warning "warning: passing argument 1 of 'ciibFp.x' makes pointer from integer without a cast" } */
+TESTASS(ciic, char *, int); /* { dg-warning "warning: assignment makes pointer from integer without a cast" } */
+TESTINI(ciid, char *, int); /* { dg-warning "warning: initialization makes pointer from integer without a cast" } */
+TESTRET(ciie, char *, int); /* { dg-warning "warning: return makes pointer from integer without a cast" } */
+
+TESTARG(iica, int, char *); /* { dg-warning "warning: passing argument 1 of 'iicaF' makes integer from pointer without a cast" } */
+TESTARP(iicb, int, char *); /* { dg-warning "warning: passing argument 1 of 'iicbFp.x' makes integer from pointer without a cast" } */
+TESTASS(iicc, int, char *); /* { dg-warning "warning: assignment makes integer from pointer without a cast" } */
+TESTINI(iicd, int, char *); /* { dg-warning "warning: initialization makes integer from pointer without a cast" } */
+TESTRET(iice, int, char *); /* { dg-warning "warning: return makes integer from pointer without a cast" } */
+
+struct s { int a; };
+
+TESTARG(stria, struct s, int); /* { dg-error "error: incompatible type for argument 1 of 'striaF'" } */
+TESTARP(strib, struct s, int); /* { dg-error "error: incompatible type for argument 1 of 'stribFp.x'" } */
+TESTASS(stric, struct s, int); /* { dg-error "error: incompatible types in assignment" } */
+TESTINI(strid, struct s, int); /* { dg-error "error: invalid initializer" } */
+TESTRET(strie, struct s, int); /* { dg-error "error: incompatible types in return" } */
+
+TESTARG(istra, int, struct s); /* { dg-error "error: incompatible type for argument 1 of 'istraF'" } */
+TESTARP(istrb, int, struct s); /* { dg-error "error: incompatible type for argument 1 of 'istrbFp.x'" } */
+TESTASS(istrc, int, struct s); /* { dg-error "error: incompatible types in assignment" } */
+TESTINI(istrd, int, struct s); /* { dg-error "error: incompatible types in initialization" } */
+TESTRET(istre, int, struct s); /* { dg-error "error: incompatible types in return" } */
diff -rupN GCC.orig/gcc/testsuite/gcc.dg/assign-warn-2.c GCC/gcc/testsuite/gcc.dg/assign-warn-2.c
--- GCC.orig/gcc/testsuite/gcc.dg/assign-warn-2.c	1970-01-01 00:00:00.000000000 +0000
+++ GCC/gcc/testsuite/gcc.dg/assign-warn-2.c	2004-10-07 22:01:27.000000000 +0000
@@ -0,0 +1,124 @@
+/* Test diagnostics for bad implicit type conversions.
+   -pedantic-errors test.  */
+/* Origin: Joseph Myers <jsm@polyomino.org.uk> */
+/* { dg-do compile } */
+/* { dg-options "-pedantic-errors" } */
+
+#define TESTARG(ID, TL, TR) void ID##F(TL); void ID##F2(TR x) { ID##F(x); } extern int dummy
+#define TESTARP(ID, TL, TR) struct { void (*x)(TL); } ID##Fp; void ID##F2(TR x) { ID##Fp.x(x); } extern int dummy
+#define TESTASS(ID, TL, TR) void ID##F(TR x) { TL y; y = x; } extern int dummy
+#define TESTINI(ID, TL, TR) void ID##F(TR x) { TL y = x; } extern int dummy
+#define TESTRET(ID, TL, TR) TR ID##V; TL ID##F(void) { return ID##V; } extern int dummy
+
+typedef void (*fp)(void);
+typedef void (*nrfp)(void) __attribute__((noreturn));
+
+TESTARG(fqa, nrfp, fp); /* { dg-error "error: passing argument 1 of 'fqaF' makes qualified function pointer from unqualified" } */
+TESTARP(fqb, nrfp, fp); /* { dg-error "error: passing argument 1 of 'fqbFp.x' makes qualified function pointer from unqualified" } */
+TESTASS(fqc, nrfp, fp); /* { dg-error "error: assignment makes qualified function pointer from unqualified" } */
+TESTINI(fqd, nrfp, fp); /* { dg-error "error: initialization makes qualified function pointer from unqualified" } */
+TESTRET(fqe, nrfp, fp); /* { dg-error "error: return makes qualified function pointer from unqualified" } */
+
+TESTARG(ofqa, fp, nrfp);
+TESTARP(ofqb, fp, nrfp);
+TESTASS(ofqc, fp, nrfp);
+TESTINI(ofqd, fp, nrfp);
+TESTRET(ofqe, fp, nrfp);
+
+TESTARG(qa, char *, const char *); /* { dg-error "error: passing argument 1 of 'qaF' discards qualifiers from pointer target type" } */
+TESTARP(qb, char *, const char *); /* { dg-error "error: passing argument 1 of 'qbFp.x' discards qualifiers from pointer target type" } */
+TESTASS(qc, char *, const char *); /* { dg-error "error: assignment discards qualifiers from pointer target type" } */
+TESTINI(qd, char *, const char *); /* { dg-error "error: initialization discards qualifiers from pointer target type" } */
+TESTRET(qe, char *, const char *); /* { dg-error "error: return discards qualifiers from pointer target type" } */
+
+TESTARG(oqa, const char *, char *);
+TESTARP(oqb, const char *, char *);
+TESTASS(oqc, const char *, char *);
+TESTINI(oqd, const char *, char *);
+TESTRET(oqe, const char *, char *);
+
+TESTARG(fda, fp, void *); /* { dg-error "error: ISO C forbids passing argument 1 of 'fdaF' between function pointer and 'void \\*'" } */
+TESTARP(fdb, fp, void *); /* { dg-error "error: ISO C forbids passing argument 1 of 'fdbFp.x' between function pointer and 'void \\*'" } */
+TESTASS(fdc, fp, void *); /* { dg-error "error: ISO C forbids assignment between function pointer and 'void \\*'" } */
+TESTINI(fdd, fp, void *); /* { dg-error "error: ISO C forbids initialization between function pointer and 'void \\*'" } */
+TESTRET(fde, fp, void *); /* { dg-error "error: ISO C forbids return between function pointer and 'void \\*'" } */
+
+TESTARG(dfa, void *, fp); /* { dg-error "error: ISO C forbids passing argument 1 of 'dfaF' between function pointer and 'void \\*'" } */
+TESTARP(dfb, void *, fp); /* { dg-error "error: ISO C forbids passing argument 1 of 'dfbFp.x' between function pointer and 'void \\*'" } */
+TESTASS(dfc, void *, fp); /* { dg-error "error: ISO C forbids assignment between function pointer and 'void \\*'" } */
+TESTINI(dfd, void *, fp); /* { dg-error "error: ISO C forbids initialization between function pointer and 'void \\*'" } */
+TESTRET(dfe, void *, fp); /* { dg-error "error: ISO C forbids return between function pointer and 'void \\*'" } */
+
+TESTARG(sua, int *, unsigned int *); /* { dg-error "error: pointer targets in passing argument 1 of 'suaF' differ in signedness" } */
+TESTARP(sub, int *, unsigned int *); /* { dg-error "error: pointer targets in passing argument 1 of 'subFp.x' differ in signedness" } */
+TESTASS(suc, int *, unsigned int *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(sud, int *, unsigned int *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(sue, int *, unsigned int *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(usa, unsigned int *, int *); /* { dg-error "error: pointer targets in passing argument 1 of 'usaF' differ in signedness" } */
+TESTARP(usb, unsigned int *, int *); /* { dg-error "error: pointer targets in passing argument 1 of 'usbFp.x' differ in signedness" } */
+TESTASS(usc, unsigned int *, int *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(usd, unsigned int *, int *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(use, unsigned int *, int *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(cua, char *, unsigned char *); /* { dg-error "error: pointer targets in passing argument 1 of 'cuaF' differ in signedness" } */
+TESTARP(cub, char *, unsigned char *); /* { dg-error "error: pointer targets in passing argument 1 of 'cubFp.x' differ in signedness" } */
+TESTASS(cuc, char *, unsigned char *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(cud, char *, unsigned char *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(cue, char *, unsigned char *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(uca, unsigned char *, char *); /* { dg-error "error: pointer targets in passing argument 1 of 'ucaF' differ in signedness" } */
+TESTARP(ucb, unsigned char *, char *); /* { dg-error "error: pointer targets in passing argument 1 of 'ucbFp.x' differ in signedness" } */
+TESTASS(ucc, unsigned char *, char *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(ucd, unsigned char *, char *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(uce, unsigned char *, char *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(csa, char *, signed char *); /* { dg-error "error: pointer targets in passing argument 1 of 'csaF' differ in signedness" } */
+TESTARP(csb, char *, signed char *); /* { dg-error "error: pointer targets in passing argument 1 of 'csbFp.x' differ in signedness" } */
+TESTASS(csc, char *, signed char *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(csd, char *, signed char *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(cse, char *, signed char *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(sca, signed char *, char *); /* { dg-error "error: pointer targets in passing argument 1 of 'scaF' differ in signedness" } */
+TESTARP(scb, signed char *, char *); /* { dg-error "error: pointer targets in passing argument 1 of 'scbFp.x' differ in signedness" } */
+TESTASS(scc, signed char *, char *); /* { dg-error "error: pointer targets in assignment differ in signedness" } */
+TESTINI(scd, signed char *, char *); /* { dg-error "error: pointer targets in initialization differ in signedness" } */
+TESTRET(sce, signed char *, char *); /* { dg-error "error: pointer targets in return differ in signedness" } */
+
+TESTARG(cia, char *, int *); /* { dg-error "error: passing argument 1 of 'ciaF' from incompatible pointer type" } */
+TESTARP(cib, char *, int *); /* { dg-error "error: passing argument 1 of 'cibFp.x' from incompatible pointer type" } */
+TESTASS(cic, char *, int *); /* { dg-error "error: assignment from incompatible pointer type" } */
+TESTINI(cid, char *, int *); /* { dg-error "error: initialization from incompatible pointer type" } */
+TESTRET(cie, char *, int *); /* { dg-error "error: return from incompatible pointer type" } */
+
+TESTARG(ica, int *, char *); /* { dg-error "error: passing argument 1 of 'icaF' from incompatible pointer type" } */
+TESTARP(icb, int *, char *); /* { dg-error "error: passing argument 1 of 'icbFp.x' from incompatible pointer type" } */
+TESTASS(icc, int *, char *); /* { dg-error "error: assignment from incompatible pointer type" } */
+TESTINI(icd, int *, char *); /* { dg-error "error: initialization from incompatible pointer type" } */
+TESTRET(ice, int *, char *); /* { dg-error "error: return from incompatible pointer type" } */
+
+TESTARG(ciia, char *, int); /* { dg-error "error: passing argument 1 of 'ciiaF' makes pointer from integer without a cast" } */
+TESTARP(ciib, char *, int); /* { dg-error "error: passing argument 1 of 'ciibFp.x' makes pointer from integer without a cast" } */
+TESTASS(ciic, char *, int); /* { dg-error "error: assignment makes pointer from integer without a cast" } */
+TESTINI(ciid, char *, int); /* { dg-error "error: initialization makes pointer from integer without a cast" } */
+TESTRET(ciie, char *, int); /* { dg-error "error: return makes pointer from integer without a cast" } */
+
+TESTARG(iica, int, char *); /* { dg-error "error: passing argument 1 of 'iicaF' makes integer from pointer without a cast" } */
+TESTARP(iicb, int, char *); /* { dg-error "error: passing argument 1 of 'iicbFp.x' makes integer from pointer without a cast" } */
+TESTASS(iicc, int, char *); /* { dg-error "error: assignment makes integer from pointer without a cast" } */
+TESTINI(iicd, int, char *); /* { dg-error "error: initialization makes integer from pointer without a cast" } */
+TESTRET(iice, int, char *); /* { dg-error "error: return makes integer from pointer without a cast" } */
+
+struct s { int a; };
+
+TESTARG(stria, struct s, int); /* { dg-error "error: incompatible type for argument 1 of 'striaF'" } */
+TESTARP(strib, struct s, int); /* { dg-error "error: incompatible type for argument 1 of 'stribFp.x'" } */
+TESTASS(stric, struct s, int); /* { dg-error "error: incompatible types in assignment" } */
+TESTINI(strid, struct s, int); /* { dg-error "error: invalid initializer" } */
+TESTRET(strie, struct s, int); /* { dg-error "error: incompatible types in return" } */
+
+TESTARG(istra, int, struct s); /* { dg-error "error: incompatible type for argument 1 of 'istraF'" } */
+TESTARP(istrb, int, struct s); /* { dg-error "error: incompatible type for argument 1 of 'istrbFp.x'" } */
+TESTASS(istrc, int, struct s); /* { dg-error "error: incompatible types in assignment" } */
+TESTINI(istrd, int, struct s); /* { dg-error "error: incompatible types in initialization" } */
+TESTRET(istre, int, struct s); /* { dg-error "error: incompatible types in return" } */
diff -rupN GCC.orig/gcc/testsuite/gcc.dg/noncompile/20020213-1.c GCC/gcc/testsuite/gcc.dg/noncompile/20020213-1.c
--- GCC.orig/gcc/testsuite/gcc.dg/noncompile/20020213-1.c	2004-01-21 13:00:22.000000000 +0000
+++ GCC/gcc/testsuite/gcc.dg/noncompile/20020213-1.c	2004-10-07 22:02:56.000000000 +0000
@@ -24,8 +24,8 @@ int main ()
   return 0;
 }
 
-/* { dg-warning "passing arg 2 of" "2nd incompatible" { target *-*-* } 15 } */
-/* { dg-warning "passing arg 1 of" "1st incompatible" { target *-*-* } 16 } */
-/* { dg-warning "passing arg 2 of" "2nd incompatible" { target *-*-* } 16 } */
-/* { dg-warning "passing arg 1 of" "1st incompatible" { target *-*-* } 18 } */
-/* { dg-warning "passing arg 1 of" "1st incompatible" { target *-*-* } 20 } */
+/* { dg-warning "passing argument 2 of" "2nd incompatible" { target *-*-* } 15 } */
+/* { dg-warning "passing argument 1 of" "1st incompatible" { target *-*-* } 16 } */
+/* { dg-warning "passing argument 2 of" "2nd incompatible" { target *-*-* } 16 } */
+/* { dg-warning "passing argument 1 of" "1st incompatible" { target *-*-* } 18 } */
+/* { dg-warning "passing argument 1 of" "1st incompatible" { target *-*-* } 20 } */
diff -rupN GCC.orig/gcc/testsuite/gcc.dg/warn-1.c GCC/gcc/testsuite/gcc.dg/warn-1.c
--- GCC.orig/gcc/testsuite/gcc.dg/warn-1.c	2004-05-13 08:47:53.000000000 +0000
+++ GCC/gcc/testsuite/gcc.dg/warn-1.c	2004-10-07 22:02:32.000000000 +0000
@@ -12,5 +12,5 @@ void bar (void)
 {
   void *vp;
 
-  foo (vp);	/* { dg-warning "passing arg 1 of" } */
+  foo (vp);	/* { dg-warning "passing argument 1 of" } */
 }
diff -rupN GCC.orig/gcc/testsuite/objc.dg/method-9.m GCC/gcc/testsuite/objc.dg/method-9.m
--- GCC.orig/gcc/testsuite/objc.dg/method-9.m	2003-09-25 01:26:01.000000000 +0000
+++ GCC/gcc/testsuite/objc.dg/method-9.m	2004-10-07 23:53:33.000000000 +0000
@@ -37,7 +37,7 @@
      /* { dg-warning "also found .\\-\\(id\\)initWithData:\\(int\\)data." "" { target *-*-* } 13 } */
 
      /* The following warning is a consequence of picking the "wrong" method signature.  */
-     /* { dg-warning "passing arg 1 of .initWithData:. from incompatible pointer type" "" { target *-*-* } 33 } */
+     /* { dg-warning "passing argument 1 of .initWithData:. from incompatible pointer type" "" { target *-*-* } 33 } */
     return result;
 }
 @end


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]