In response to Joseph's comment I've removed the interaction
with -Wpedantic from the updated patch.

In addition, to help detect bugs like the one in the test case
for pr87886, I have also enhanced the detection of incompatible
calls to include integer/real type mismatches so that calls like
the one below are diagnosed:

  extern double sqrt ();
  int f (int x)
  {
    return sqrt (x);   // passing int where double is expected
  }

With the removal of the -Wpedantic interaction declaring abort()
without a prototype is no longer diagnosed and so the test suite
changes to add the prototype are not necessary.  I decided not
to back them out because Jeff indicated a preference for making
these kinds of improvements in general in an unrelated
discussion.

On 11/02/2018 05:40 PM, Martin Sebor wrote:
On 11/02/2018 04:52 PM, Joseph Myers wrote:
On Fri, 2 Nov 2018, Martin Sebor wrote:

I have reworked the patch to resolve any lingering concerns about
warnings in configure tests.  The attached revision only warns
with -Wextra and only for incompatible declarations of built-ins
that take arguments.  For void built-ins like abort() it only
warns with -Wpedantic (this required adjustments to several
tests that are being compiled with -pedantic-errors).

I don't think this use of -Wpedantic is appropriate.  -Wpedantic is not a
catch-all for warnings we don't want to enable with some other option;
it's specifically for programs doing something that is disallowed by
ISO C
(such warnings may or may not also be enabled by other relevant options).

Since this declaration is not disallowed by ISO C, -Wpedantic should not
result in a warning for it.

(I do consider declarations with () for built-in functions without
arguments to be more dubious than for user-defined functions without
arguments, simply because good practice would be to include the standard
header to get declarations of those functions, whereas for user-defined
functions the code might simply be using C++ style for declaring
functions
without arguments.)

-Wpedantic alone doesn't cause a warning, only in conjunction
with -Wno-builtin-declaration-mismatch.

But I have no preference for what option to put it under, or
necessarily think that using -Wpedantic (or any other "group"
option) like this is a great idea (it doesn't work with #pragma
GCC diagnostic that way I think it should).  In fact, with
the latest approach of diagnosing unsafe calls to these functions
regardless of the declaration form it doesn't seem that important
that declarations of built-ins with no arguments be diagnosed at
all.  Either way, there aren't enough of them for it to matter
much.  I think there's just one: abort.  I'm fine with removing
this part of the patch.

Is there anything else?

Martin

PR c/83656 - missing -Wbuiltin-declaration-mismatch on declaration without prototype

gcc/c/ChangeLog:

	PR c/83656
	* c-decl.c (header_for_builtin_fn): Declare.
	(diagnose_mismatched_decls): Diagnose declarations of built-in
	functions without a prototype.
	* c-typeck.c (maybe_warn_builtin_no_proto_arg): New function.
	(convert_argument): Same.
	(convert_arguments): Factor code out into convert_argument.
	Detect mismatches between built-in formal arguments in calls
	to built-in without prototype.
	(build_conditional_expr): Same.
	(type_or_builtin_type): New function.
	(convert_for_assignment): Add argument.  Conditionally issue
	warnings instead of errors for mismatches.

gcc/testsuite/ChangeLog:

	PR c/83656
	* gcc.dg/20021006-1.c
	* gcc.dg/Wbuiltin-declaration-mismatch.c: New test.
	* gcc.dg/Wbuiltin-declaration-mismatch-2.c: New test.
	* gcc.dg/Wbuiltin-declaration-mismatch-3.c: New test.
	* gcc.dg/Wbuiltin-declaration-mismatch-4.c: New test.
	* gcc.dg/Walloca-16.c: Adjust.
	* gcc.dg/Wrestrict-4.c: Adjust.
	* gcc.dg/Wrestrict-5.c: Adjust.
	* gcc.dg/atomic/stdatomic-generic.c: Adjust.
	* gcc.dg/atomic/stdatomic-lockfree.c: Adjust.
	* gcc.dg/initpri1.c: Adjust.
	* gcc.dg/pr15698-1.c: Adjust.
	* gcc.dg/pr69156.c: Adjust.
	* gcc.dg/pr83463.c: Adjust.
	* gcc.dg/redecl-4.c: Adjust.
	* gcc.dg/tls/thr-init-2.c: Adjust.
	* gcc.dg/torture/pr55890-2.c: Adjust.
	* gcc.dg/torture/pr55890-3.c: Adjust.
	* gcc.dg/torture/pr67741.c: Adjust.
	* gcc.dg/torture/stackalign/sibcall-1.c: Adjust.
	* gcc.dg/torture/tls/thr-init-1.c: Adjust.
	* gcc.dg/tree-ssa/builtins-folding-gimple-ub.c: Adjust.

diff --git a/gcc/c/c-decl.c b/gcc/c/c-decl.c
index cbbf7eb..524ac83 100644
--- a/gcc/c/c-decl.c
+++ b/gcc/c/c-decl.c
@@ -604,6 +604,7 @@ static tree grokparms (struct c_arg_info *, bool);
 static void layout_array_type (tree);
 static void warn_defaults_to (location_t, int, const char *, ...)
     ATTRIBUTE_GCC_DIAG(3,4);
+static const char *header_for_builtin_fn (enum built_in_function);
 
 /* T is a statement.  Add it to the statement-tree.  This is the
    C/ObjC version--C++ has a slightly different version of this
@@ -1887,12 +1888,25 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	    *oldtypep = oldtype = trytype;
 	  else
 	    {
+	      const char *header
+		= header_for_builtin_fn (DECL_FUNCTION_CODE (olddecl));
+	      location_t loc = DECL_SOURCE_LOCATION (newdecl);
+	      if (warning_at (loc, OPT_Wbuiltin_declaration_mismatch,
+			      "conflicting types for built-in function %q+D; "
+			      "expected %qT",
+			      newdecl, oldtype)
+		  && header)
+		{
+		  /* Suggest the right header to include as the preferred
+		     solution rather than the spelling of the declaration.  */
+		  rich_location richloc (line_table, loc);
+		  maybe_add_include_fixit (&richloc, header, true);
+		  inform (&richloc,
+			  "%qD is declared in header %qs", olddecl, header);
+		}
 	      /* If types don't match for a built-in, throw away the
 		 built-in.  No point in calling locate_old_decl here, it
 		 won't print anything.  */
-	      warning (OPT_Wbuiltin_declaration_mismatch,
-		       "conflicting types for built-in function %q+D",
-		       newdecl);
 	      return false;
 	    }
 	}
@@ -2026,15 +2040,33 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	 can't validate the argument list) the built-in definition is
 	 overridden, but optionally warn this was a bad choice of name.  */
       if (fndecl_built_in_p (olddecl)
-	  && !C_DECL_DECLARED_BUILTIN (olddecl)
-	  && (!TREE_PUBLIC (newdecl)
-	      || (DECL_INITIAL (newdecl)
-		  && !prototype_p (TREE_TYPE (newdecl)))))
+	  && !C_DECL_DECLARED_BUILTIN (olddecl))
 	{
-	  warning (OPT_Wshadow, "declaration of %q+D shadows "
-		   "a built-in function", newdecl);
-	  /* Discard the old built-in function.  */
-	  return false;
+	  if (!TREE_PUBLIC (newdecl)
+	      || (DECL_INITIAL (newdecl)
+		  && !prototype_p (TREE_TYPE (newdecl))))
+	    {
+	      warning_at (DECL_SOURCE_LOCATION (newdecl),
+			  OPT_Wshadow, "declaration of %qD shadows "
+			  "a built-in function", newdecl);
+	      /* Discard the old built-in function.  */
+	      return false;
+	    }
+
+	  if (!prototype_p (TREE_TYPE (newdecl)))
+	    {
+	      /* Set for built-ins that take no arguments.  */
+	      bool func_void_args = false;
+	      if (tree at = TYPE_ARG_TYPES (oldtype))
+		func_void_args = VOID_TYPE_P (TREE_VALUE (at));
+
+	      if (extra_warnings && !func_void_args)
+		warning_at (DECL_SOURCE_LOCATION (newdecl),
+			    OPT_Wbuiltin_declaration_mismatch,
+			    "declaration of built-in function %qD without "
+			    "a prototype; expected %qT",
+			    newdecl, TREE_TYPE (olddecl));
+	    }
 	}
 
       if (DECL_INITIAL (newdecl))
diff --git a/gcc/c/c-typeck.c b/gcc/c/c-typeck.c
index 9d09b8d..45331be 100644
--- a/gcc/c/c-typeck.c
+++ b/gcc/c/c-typeck.c
@@ -97,7 +97,8 @@ static int convert_arguments (location_t, vec<location_t>, tree,
 			      tree);
 static tree pointer_diff (location_t, tree, tree, tree *);
 static tree convert_for_assignment (location_t, location_t, tree, tree, tree,
-				    enum impl_conv, bool, tree, tree, int);
+				    enum impl_conv, bool, tree, tree, int,
+				    int = 0);
 static tree valid_compound_expr_initializer (tree, tree);
 static void push_string (const char *);
 static void push_member_name (tree);
@@ -3183,6 +3184,188 @@ c_build_function_call_vec (location_t loc, vec<location_t> arg_loc,
   return build_function_call_vec (loc, arg_loc, function, params, origtypes);
 }
 
+/* Helper for convert_arguments called to convert the VALue of argument
+   number ARGNUM from ORIGTYPE to the corresponding parameter number
+   PARMNUL and TYPE.  */
+
+static tree
+convert_argument (location_t ploc, tree function, tree fundecl,
+		  tree type, tree origtype, tree val, bool npc,
+		  tree rname, int parmnum, int argnum,
+		  bool excess_precision, int warnopt)
+{
+  tree valtype = TREE_TYPE (val);
+
+  tree parmval;
+
+  /* Formal parm type is specified by a function prototype.  */
+
+  if (type == error_mark_node || !COMPLETE_TYPE_P (type))
+    {
+      error_at (ploc, "type of formal parameter %d is incomplete",
+		parmnum + 1);
+      parmval = val;
+    }
+  else
+    {
+      /* Optionally warn about conversions that differ from the default
+	 conversions.  */
+      if (warn_traditional_conversion || warn_traditional)
+	{
+	  unsigned int formal_prec = TYPE_PRECISION (type);
+
+	  if (INTEGRAL_TYPE_P (type)
+	      && TREE_CODE (valtype) == REAL_TYPE)
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as integer rather "
+			"than floating due to prototype",
+			argnum, rname);
+	  if (INTEGRAL_TYPE_P (type)
+	      && TREE_CODE (valtype) == COMPLEX_TYPE)
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as integer rather "
+			"than complex due to prototype",
+			argnum, rname);
+	  else if (TREE_CODE (type) == COMPLEX_TYPE
+		   && TREE_CODE (valtype) == REAL_TYPE)
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as complex rather "
+			"than floating due to prototype",
+			argnum, rname);
+	  else if (TREE_CODE (type) == REAL_TYPE
+		   && INTEGRAL_TYPE_P (valtype))
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as floating rather "
+			"than integer due to prototype",
+			argnum, rname);
+	  else if (TREE_CODE (type) == COMPLEX_TYPE
+		   && INTEGRAL_TYPE_P (valtype))
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as complex rather "
+			"than integer due to prototype",
+			argnum, rname);
+	  else if (TREE_CODE (type) == REAL_TYPE
+		   && TREE_CODE (valtype) == COMPLEX_TYPE)
+	    warning_at (ploc, OPT_Wtraditional_conversion,
+			"passing argument %d of %qE as floating rather "
+			"than complex due to prototype",
+			argnum, rname);
+	  /* ??? At some point, messages should be written about
+	     conversions between complex types, but that's too messy
+	     to do now.  */
+	  else if (TREE_CODE (type) == REAL_TYPE
+		   && TREE_CODE (valtype) == REAL_TYPE)
+	    {
+	      /* Warn if any argument is passed as `float',
+		 since without a prototype it would be `double'.  */
+	      if (formal_prec == TYPE_PRECISION (float_type_node)
+		  && type != dfloat32_type_node)
+		warning_at (ploc, 0,
+			    "passing argument %d of %qE as %<float%> "
+			    "rather than %<double%> due to prototype",
+			    argnum, rname);
+
+	      /* Warn if mismatch between argument and prototype
+		 for decimal float types.  Warn of conversions with
+		 binary float types and of precision narrowing due to
+		 prototype. */
+	      else if (type != valtype
+		       && (type == dfloat32_type_node
+			   || type == dfloat64_type_node
+			   || type == dfloat128_type_node
+			   || valtype == dfloat32_type_node
+			   || valtype == dfloat64_type_node
+			   || valtype == dfloat128_type_node)
+		       && (formal_prec
+			   <= TYPE_PRECISION (valtype)
+			   || (type == dfloat128_type_node
+			       && (valtype
+				   != dfloat64_type_node
+				   && (valtype
+				       != dfloat32_type_node)))
+			   || (type == dfloat64_type_node
+			       && (valtype
+				   != dfloat32_type_node))))
+		warning_at (ploc, 0,
+			    "passing argument %d of %qE as %qT "
+			    "rather than %qT due to prototype",
+			    argnum, rname, type, valtype);
+
+	    }
+	  /* Detect integer changing in width or signedness.
+	     These warnings are only activated with
+	     -Wtraditional-conversion, not with -Wtraditional.  */
+	  else if (warn_traditional_conversion
+		   && INTEGRAL_TYPE_P (type)
+		   && INTEGRAL_TYPE_P (valtype))
+	    {
+	      tree would_have_been = default_conversion (val);
+	      tree type1 = TREE_TYPE (would_have_been);
+
+	      if (val == error_mark_node)
+		/* VAL could have been of incomplete type.  */;
+	      else if (TREE_CODE (type) == ENUMERAL_TYPE
+		       && (TYPE_MAIN_VARIANT (type)
+			   == TYPE_MAIN_VARIANT (valtype)))
+		/* No warning if function asks for enum
+		   and the actual arg is that enum type.  */
+		;
+	      else if (formal_prec != TYPE_PRECISION (type1))
+		warning_at (ploc, OPT_Wtraditional_conversion,
+			    "passing argument %d of %qE "
+			    "with different width due to prototype",
+			    argnum, rname);
+	      else if (TYPE_UNSIGNED (type) == TYPE_UNSIGNED (type1))
+		;
+	      /* Don't complain if the formal parameter type
+		 is an enum, because we can't tell now whether
+		 the value was an enum--even the same enum.  */
+	      else if (TREE_CODE (type) == ENUMERAL_TYPE)
+		;
+	      else if (TREE_CODE (val) == INTEGER_CST
+		       && int_fits_type_p (val, type))
+		/* Change in signedness doesn't matter
+		   if a constant value is unaffected.  */
+		;
+	      /* If the value is extended from a narrower
+		 unsigned type, it doesn't matter whether we
+		 pass it as signed or unsigned; the value
+		 certainly is the same either way.  */
+	      else if (TYPE_PRECISION (valtype) < TYPE_PRECISION (type)
+		       && TYPE_UNSIGNED (valtype))
+		;
+	      else if (TYPE_UNSIGNED (type))
+		warning_at (ploc, OPT_Wtraditional_conversion,
+			    "passing argument %d of %qE "
+			    "as unsigned due to prototype",
+			    argnum, rname);
+	      else
+		warning_at (ploc, OPT_Wtraditional_conversion,
+			    "passing argument %d of %qE "
+			    "as signed due to prototype",
+			    argnum, rname);
+	    }
+	}
+
+      /* Possibly restore an EXCESS_PRECISION_EXPR for the
+	 sake of better warnings from convert_and_check.  */
+      if (excess_precision)
+	val = build1 (EXCESS_PRECISION_EXPR, valtype, val);
+
+      parmval = convert_for_assignment (ploc, ploc, type,
+					val, origtype, ic_argpass,
+					npc, fundecl, function,
+					parmnum + 1, warnopt);
+
+      if (targetm.calls.promote_prototypes (fundecl ? TREE_TYPE (fundecl) : 0)
+	  && INTEGRAL_TYPE_P (type)
+	  && (TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node)))
+	parmval = default_conversion (parmval);
+    }
+
+  return parmval;
+}
+
 /* Convert the argument expressions in the vector VALUES
    to the types in the list TYPELIST.
 
@@ -3209,7 +3392,6 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
 		   vec<tree, va_gc> *values, vec<tree, va_gc> *origtypes,
 		   tree function, tree fundecl)
 {
-  tree typetail, val;
   unsigned int parmnum;
   bool error_args = false;
   const bool type_generic = fundecl
@@ -3227,50 +3409,69 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
   /* Handle an ObjC selector specially for diagnostics.  */
   selector = objc_message_selector ();
 
+  /* For a call to a built-in function declared without a prototype,
+     set to the built-in function's argument list.  */
+  tree builtin_typelist = NULL_TREE;
+
   /* For type-generic built-in functions, determine whether excess
      precision should be removed (classification) or not
      (comparison).  */
-  if (type_generic
+  if (fundecl
       && fndecl_built_in_p (fundecl, BUILT_IN_NORMAL))
     {
-      switch (DECL_FUNCTION_CODE (fundecl))
+      built_in_function code = DECL_FUNCTION_CODE (fundecl);
+      if (C_DECL_BUILTIN_PROTOTYPE (fundecl))
 	{
-	case BUILT_IN_ISFINITE:
-	case BUILT_IN_ISINF:
-	case BUILT_IN_ISINF_SIGN:
-	case BUILT_IN_ISNAN:
-	case BUILT_IN_ISNORMAL:
-	case BUILT_IN_FPCLASSIFY:
-	  type_generic_remove_excess_precision = true;
-	  break;
+	  if (tree bdecl = builtin_decl_implicit (code))
+	    builtin_typelist = TYPE_ARG_TYPES (TREE_TYPE (bdecl));
+	}
 
-	case BUILT_IN_ADD_OVERFLOW_P:
-	case BUILT_IN_SUB_OVERFLOW_P:
-	case BUILT_IN_MUL_OVERFLOW_P:
-	  /* The last argument of these type-generic builtins
-	     should not be promoted.  */
-	  type_generic_overflow_p = true;
-	  break;
+      /* For type-generic built-in functions, determine whether excess
+	 precision should be removed (classification) or not
+	 (comparison).  */
+      if (type_generic)
+	switch (code)
+	  {
+	  case BUILT_IN_ISFINITE:
+	  case BUILT_IN_ISINF:
+	  case BUILT_IN_ISINF_SIGN:
+	  case BUILT_IN_ISNAN:
+	  case BUILT_IN_ISNORMAL:
+	  case BUILT_IN_FPCLASSIFY:
+	    type_generic_remove_excess_precision = true;
+	    break;
 
-	default:
-	  break;
-	}
+	  case BUILT_IN_ADD_OVERFLOW_P:
+	  case BUILT_IN_SUB_OVERFLOW_P:
+	  case BUILT_IN_MUL_OVERFLOW_P:
+	    /* The last argument of these type-generic builtins
+	       should not be promoted.  */
+	    type_generic_overflow_p = true;
+	    break;
+
+	  default:
+	    break;
+	  }
     }
 
   /* Scan the given expressions and types, producing individual
      converted arguments.  */
 
-  for (typetail = typelist, parmnum = 0;
+  tree typetail, builtin_typetail, val;
+  for (typetail = typelist,
+	 builtin_typetail = builtin_typelist,
+	 parmnum = 0;
        values && values->iterate (parmnum, &val);
        ++parmnum)
     {
-      tree type = typetail ? TREE_VALUE (typetail) : 0;
+      tree type = typetail ? TREE_VALUE (typetail) : NULL_TREE;
+      tree builtin_type = (builtin_typetail
+			   ? TREE_VALUE (builtin_typetail) : NULL_TREE);
       tree valtype = TREE_TYPE (val);
       tree rname = function;
       int argnum = parmnum + 1;
       const char *invalid_func_diag;
       bool excess_precision = false;
-      bool npc;
       tree parmval;
       /* Some __atomic_* builtins have additional hidden argument at
 	 position 0.  */
@@ -3289,13 +3490,25 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
 	  return error_args ? -1 : (int) parmnum;
 	}
 
+      if (builtin_type == void_type_node)
+	{
+	  warning_at (loc, OPT_Wbuiltin_declaration_mismatch,
+		      "too many arguments to built-in function %qE "
+		      "expecting %d",
+		      function, parmnum);
+
+	  inform_declaration (fundecl);
+	  builtin_typetail = NULL_TREE;
+	}
+
       if (selector && argnum > 2)
 	{
 	  rname = selector;
 	  argnum -= 2;
 	}
 
-      npc = null_pointer_constant_p (val);
+      /* Determine if VAL is a null pointer constant before folding it.  */
+      bool npc = null_pointer_constant_p (val);
 
       /* If there is excess precision and a prototype, convert once to
 	 the required type rather than converting via the semantic
@@ -3340,172 +3553,10 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
 
       if (type != NULL_TREE)
 	{
-	  /* Formal parm type is specified by a function prototype.  */
-
-	  if (type == error_mark_node || !COMPLETE_TYPE_P (type))
-	    {
-	      error_at (ploc, "type of formal parameter %d is incomplete",
-			parmnum + 1);
-	      parmval = val;
-	    }
-	  else
-	    {
-	      tree origtype;
-
-	      /* Optionally warn about conversions that
-		 differ from the default conversions.  */
-	      if (warn_traditional_conversion || warn_traditional)
-		{
-		  unsigned int formal_prec = TYPE_PRECISION (type);
-
-		  if (INTEGRAL_TYPE_P (type)
-		      && TREE_CODE (valtype) == REAL_TYPE)
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as integer rather "
-				"than floating due to prototype",
-				argnum, rname);
-		  if (INTEGRAL_TYPE_P (type)
-		      && TREE_CODE (valtype) == COMPLEX_TYPE)
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as integer rather "
-				"than complex due to prototype",
-				argnum, rname);
-		  else if (TREE_CODE (type) == COMPLEX_TYPE
-			   && TREE_CODE (valtype) == REAL_TYPE)
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as complex rather "
-				"than floating due to prototype",
-				argnum, rname);
-		  else if (TREE_CODE (type) == REAL_TYPE
-			   && INTEGRAL_TYPE_P (valtype))
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as floating rather "
-				"than integer due to prototype",
-				argnum, rname);
-		  else if (TREE_CODE (type) == COMPLEX_TYPE
-			   && INTEGRAL_TYPE_P (valtype))
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as complex rather "
-				"than integer due to prototype",
-				argnum, rname);
-		  else if (TREE_CODE (type) == REAL_TYPE
-			   && TREE_CODE (valtype) == COMPLEX_TYPE)
-		    warning_at (ploc, OPT_Wtraditional_conversion,
-				"passing argument %d of %qE as floating rather "
-				"than complex due to prototype",
-				argnum, rname);
-		  /* ??? At some point, messages should be written about
-		     conversions between complex types, but that's too messy
-		     to do now.  */
-		  else if (TREE_CODE (type) == REAL_TYPE
-			   && TREE_CODE (valtype) == REAL_TYPE)
-		    {
-		      /* Warn if any argument is passed as `float',
-			 since without a prototype it would be `double'.  */
-		      if (formal_prec == TYPE_PRECISION (float_type_node)
-			  && type != dfloat32_type_node)
-			warning_at (ploc, 0,
-				    "passing argument %d of %qE as %<float%> "
-				    "rather than %<double%> due to prototype",
-				    argnum, rname);
-
-		      /* Warn if mismatch between argument and prototype
-			 for decimal float types.  Warn of conversions with
-			 binary float types and of precision narrowing due to
-			 prototype. */
- 		      else if (type != valtype
-			       && (type == dfloat32_type_node
-				   || type == dfloat64_type_node
-				   || type == dfloat128_type_node
-				   || valtype == dfloat32_type_node
-				   || valtype == dfloat64_type_node
-				   || valtype == dfloat128_type_node)
-			       && (formal_prec
-				   <= TYPE_PRECISION (valtype)
-				   || (type == dfloat128_type_node
-				       && (valtype
-					   != dfloat64_type_node
-					   && (valtype
-					       != dfloat32_type_node)))
-				   || (type == dfloat64_type_node
-				       && (valtype
-					   != dfloat32_type_node))))
-			warning_at (ploc, 0,
-				    "passing argument %d of %qE as %qT "
-				    "rather than %qT due to prototype",
-				    argnum, rname, type, valtype);
-
-		    }
-		  /* Detect integer changing in width or signedness.
-		     These warnings are only activated with
-		     -Wtraditional-conversion, not with -Wtraditional.  */
-		  else if (warn_traditional_conversion
-			   && INTEGRAL_TYPE_P (type)
-			   && INTEGRAL_TYPE_P (valtype))
-		    {
-		      tree would_have_been = default_conversion (val);
-		      tree type1 = TREE_TYPE (would_have_been);
-
-		      if (val == error_mark_node)
-			/* VAL could have been of incomplete type.  */;
-		      else if (TREE_CODE (type) == ENUMERAL_TYPE
-			       && (TYPE_MAIN_VARIANT (type)
-				   == TYPE_MAIN_VARIANT (valtype)))
-			/* No warning if function asks for enum
-			   and the actual arg is that enum type.  */
-			;
-		      else if (formal_prec != TYPE_PRECISION (type1))
-			warning_at (ploc, OPT_Wtraditional_conversion,
-				    "passing argument %d of %qE "
-				    "with different width due to prototype",
-				    argnum, rname);
-		      else if (TYPE_UNSIGNED (type) == TYPE_UNSIGNED (type1))
-			;
-		      /* Don't complain if the formal parameter type
-			 is an enum, because we can't tell now whether
-			 the value was an enum--even the same enum.  */
-		      else if (TREE_CODE (type) == ENUMERAL_TYPE)
-			;
-		      else if (TREE_CODE (val) == INTEGER_CST
-			       && int_fits_type_p (val, type))
-			/* Change in signedness doesn't matter
-			   if a constant value is unaffected.  */
-			;
-		      /* If the value is extended from a narrower
-			 unsigned type, it doesn't matter whether we
-			 pass it as signed or unsigned; the value
-			 certainly is the same either way.  */
-		      else if (TYPE_PRECISION (valtype) < TYPE_PRECISION (type)
-			       && TYPE_UNSIGNED (valtype))
-			;
-		      else if (TYPE_UNSIGNED (type))
-			warning_at (ploc, OPT_Wtraditional_conversion,
-				    "passing argument %d of %qE "
-				    "as unsigned due to prototype",
-				    argnum, rname);
-		      else
-			warning_at (ploc, OPT_Wtraditional_conversion,
-				    "passing argument %d of %qE "
-				    "as signed due to prototype",
-				    argnum, rname);
-		    }
-		}
-
-	      /* Possibly restore an EXCESS_PRECISION_EXPR for the
-		 sake of better warnings from convert_and_check.  */
-	      if (excess_precision)
-		val = build1 (EXCESS_PRECISION_EXPR, valtype, val);
-	      origtype = (!origtypes) ? NULL_TREE : (*origtypes)[parmnum];
-	      parmval = convert_for_assignment (loc, ploc, type,
-						val, origtype, ic_argpass,
-						npc, fundecl, function,
-						parmnum + 1);
-
-	      if (targetm.calls.promote_prototypes (fundecl ? TREE_TYPE (fundecl) : 0)
-		  && INTEGRAL_TYPE_P (type)
-		  && (TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node)))
-		parmval = default_conversion (parmval);
-	    }
+	  tree origtype = (!origtypes) ? NULL_TREE : (*origtypes)[parmnum];
+	  parmval = convert_argument (ploc, function, fundecl, type, origtype,
+				      val, npc, rname, parmnum, argnum,
+				      excess_precision, 0);
 	}
       else if (promote_float_arg)
         {
@@ -3547,8 +3598,24 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
       if (parmval == error_mark_node)
 	error_args = true;
 
+      if (!type && builtin_type && TREE_CODE (builtin_type) != VOID_TYPE)
+	{
+	  /* For a call to a built-in function declared without a prototype,
+	     perform the coversions from the argument to the expected type
+	     but issue warnings rather than errors for any mismatches.
+	     Ignore the converted argument and use the PARMVAL obtained
+	     above by applying default coversions instead.  */
+	  tree origtype = (!origtypes) ? NULL_TREE : (*origtypes)[parmnum];
+	  convert_argument (ploc, function, fundecl, builtin_type, origtype,
+			    val, npc, rname, parmnum, argnum, excess_precision,
+			    OPT_Wbuiltin_declaration_mismatch);
+	}
+
       if (typetail)
 	typetail = TREE_CHAIN (typetail);
+
+      if (builtin_typetail)
+	builtin_typetail = TREE_CHAIN (builtin_typetail);
     }
 
   gcc_assert (parmnum == vec_safe_length (values));
@@ -3560,6 +3627,18 @@ convert_arguments (location_t loc, vec<location_t> arg_loc, tree typelist,
       return -1;
     }
 
+  if (builtin_typetail && TREE_VALUE (builtin_typetail) != void_type_node)
+    {
+      unsigned nargs = parmnum;
+      for (tree t = builtin_typetail; t; t = TREE_CHAIN (t))
+	++nargs;
+
+      warning_at (loc, OPT_Wbuiltin_declaration_mismatch,
+		  "too few arguments to built-in function %qE expecting %u",
+		  function, nargs - 1);
+      inform_declaration (fundecl);
+    }
+
   return error_args ? -1 : (int) parmnum;
 }
 
@@ -4922,6 +5001,40 @@ ep_convert_and_check (location_t loc, tree type, tree expr,
   return convert (type, expr);
 }
 
+/* If EXPR refers to a built-in declared without a prototype returns
+   the actual type of the built-in and, if non-null, set *BLTIN to
+   a pointer to the built-in.  Otherwise return the type of EXPR
+   and clear *BLTIN if non-null. */
+
+static tree
+type_or_builtin_type (tree expr, tree *bltin = NULL)
+{
+  tree dummy;
+  if (!bltin)
+    bltin = &dummy;
+
+  *bltin = NULL_TREE;
+
+  tree type = TREE_TYPE (expr);
+  if (TREE_CODE (expr) != ADDR_EXPR)
+    return type;
+
+  tree oper = TREE_OPERAND (expr, 0);
+  if (!DECL_P (oper)
+      || TREE_CODE (oper) != FUNCTION_DECL
+      || !fndecl_built_in_p (oper, BUILT_IN_NORMAL))
+    return type;
+
+  built_in_function code = DECL_FUNCTION_CODE (oper);
+  if (!C_DECL_BUILTIN_PROTOTYPE (oper))
+    return type;
+
+  if ((*bltin = builtin_decl_implicit (code)))
+    type = build_pointer_type (TREE_TYPE (*bltin));
+
+  return type;
+}
+
 /* Build and return a conditional expression IFEXP ? OP1 : OP2.  If
    IFEXP_BCP then the condition is a call to __builtin_constant_p, and
    if folded to an integer constant then the unselected half may
@@ -4966,9 +5079,11 @@ build_conditional_expr (location_t colon_loc, tree ifexp, bool ifexp_bcp,
       || TREE_CODE (TREE_TYPE (op2)) == ERROR_MARK)
     return error_mark_node;
 
-  type1 = TREE_TYPE (op1);
+  tree bltin1 = NULL_TREE;
+  tree bltin2 = NULL_TREE;
+  type1 = type_or_builtin_type (op1, &bltin1);
   code1 = TREE_CODE (type1);
-  type2 = TREE_TYPE (op2);
+  type2 = type_or_builtin_type (op2, &bltin2);
   code2 = TREE_CODE (type2);
 
   if (code1 == POINTER_TYPE && reject_gcc_builtin (op1))
@@ -5206,9 +5321,14 @@ build_conditional_expr (location_t colon_loc, tree ifexp, bool ifexp_bcp,
       else
 	{
 	  int qual = ENCODE_QUAL_ADDR_SPACE (as_common);
-
-	  pedwarn (colon_loc, 0,
-		   "pointer type mismatch in conditional expression");
+	  if (bltin1 && bltin2)	
+	    warning_at (colon_loc, OPT_Wincompatible_pointer_types,
+			"pointer type mismatch between %qT and %qT "
+			"of %qD and %qD in conditional expression",
+			type1, type2, bltin1, bltin2);
+	  else
+	    pedwarn (colon_loc, 0,
+		     "pointer type mismatch in conditional expression");
 	  result_type = build_pointer_type
 			  (build_qualified_type (void_type_node, qual));
 	}
@@ -6322,6 +6442,46 @@ inform_for_arg (tree fundecl, location_t ploc, int parmnum,
 	  expected_type, actual_type);
 }
 
+/* Issue a warning when an argument of ARGTYPE is passed to a built-in
+   function FUNDECL declared without prototype to parameter PARMNUM of
+   PARMTYPE when ARGTYPE does not promote to PARMTYPE.  */
+
+static void
+maybe_warn_builtin_no_proto_arg (location_t loc, tree fundecl, int parmnum,
+				 tree parmtype, tree argtype)
+{
+  tree_code parmcode = TREE_CODE (parmtype);
+  tree_code argcode = TREE_CODE (argtype);
+  tree promoted = c_type_promotes_to (argtype);
+
+  /* Avoid warning for enum arguments that promote to an integer type
+     of the same size/mode.  */
+  if (parmcode == INTEGER_TYPE
+      && argcode == ENUMERAL_TYPE
+      && TYPE_MODE (parmtype) == TYPE_MODE (argtype))
+    return;
+
+  if (parmcode == argcode
+      && TYPE_MAIN_VARIANT (parmtype) == TYPE_MAIN_VARIANT (promoted))
+    return;
+
+  /* This diagnoses even signed/unsigned mismatches.  Those might be
+     safe in many cases but GCC may emit suboptimal code for them so
+     warning on those cases drives efficiency improvements.  */
+  if (warning_at (loc, OPT_Wbuiltin_declaration_mismatch,
+		  TYPE_MAIN_VARIANT (promoted) == argtype
+		  ? G_("%qD argument %d type is %qT where %qT is expected "
+		       "in a call to built-in function declared without "
+		       "prototype")
+		  : G_("%qD argument %d promotes to %qT where %qT is expected "
+		       "in a call to built-in function declared without "
+		       "prototype"),
+		  fundecl, parmnum, promoted, parmtype))
+    inform (DECL_SOURCE_LOCATION (fundecl),
+	    "built-in %qD declared here",
+	    fundecl);
+}
+
 /* Convert value RHS to type TYPE as preparation for an assignment to
    an lvalue of type TYPE.  If ORIGTYPE is not NULL_TREE, it is the
    original type of RHS; this differs from TREE_TYPE (RHS) for enum
@@ -6346,13 +6506,16 @@ inform_for_arg (tree fundecl, location_t ploc, int parmnum,
 	    ^
 
    FUNCTION is a tree for the function being called.
-   PARMNUM is the number of the argument, for printing in error messages.  */
+   PARMNUM is the number of the argument, for printing in error messages.
+   WARNOPT may be set to a warning option to issue the corresponding warning
+   rather than an error for invalid conversions.  Used for calls to built-in
+   functions declared without a prototype.  */
 
 static tree
 convert_for_assignment (location_t location, location_t expr_loc, tree type,
 			tree rhs, tree origtype, enum impl_conv errtype,
 			bool null_pointer_constant, tree fundecl,
-			tree function, int parmnum)
+			tree function, int parmnum, int warnopt /* = 0 */)
 {
   enum tree_code codel = TREE_CODE (type);
   tree orig_rhs = rhs;
@@ -6550,7 +6713,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	 an unprototyped function, it is compile-time undefined;
 	 making it a constraint in that case was rejected in
 	 DR#252.  */
-      error_at (location, "void value not ignored as it ought to be");
+      const char msg[] = "void value not ignored as it ought to be";
+      if (warnopt)
+	warning_at (location, warnopt, msg);
+      else
+	error_at (location, msg);
       return error_mark_node;
     }
   rhs = require_complete_type (location, rhs);
@@ -6566,7 +6733,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     {
       if (!lvalue_p (rhs))
 	{
-	  error_at (location, "cannot pass rvalue to reference parameter");
+	  const char msg[] = "cannot pass rvalue to reference parameter";
+	  if (warnopt)
+	    warning_at (location, warnopt, msg);
+	  else
+	    error_at (location, msg);
 	  return error_mark_node;
 	}
       if (!c_mark_addressable (rhs))
@@ -6578,7 +6749,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 				    build_pointer_type (TREE_TYPE (type)),
 				    rhs, origtype, errtype,
 				    null_pointer_constant, fundecl, function,
-				    parmnum);
+				    parmnum, warnopt);
       if (rhs == error_mark_node)
 	return error_mark_node;
 
@@ -6600,15 +6771,18 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	       || coder == ENUMERAL_TYPE || coder == COMPLEX_TYPE
 	       || coder == BOOLEAN_TYPE))
     {
-      tree ret;
+      if (warnopt && errtype == ic_argpass)
+	maybe_warn_builtin_no_proto_arg (expr_loc, fundecl, parmnum, type,
+					 rhstype);
+
       bool save = in_late_binary_op;
       if (codel == BOOLEAN_TYPE || codel == COMPLEX_TYPE
 	  || (coder == REAL_TYPE
 	      && (codel == INTEGER_TYPE || codel == ENUMERAL_TYPE)
 	      && sanitize_flags_p (SANITIZE_FLOAT_CAST)))
 	in_late_binary_op = true;
-      ret = convert_and_check (expr_loc != UNKNOWN_LOCATION
-			       ? expr_loc : location, type, orig_rhs);
+      tree ret = convert_and_check (expr_loc != UNKNOWN_LOCATION
+				    ? expr_loc : location, type, orig_rhs);
       in_late_binary_op = save;
       return ret;
     }
@@ -6742,6 +6916,12 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
   else if ((codel == POINTER_TYPE || codel == REFERENCE_TYPE)
 	   && (coder == codel))
     {
+      /* If RHS refers to a built-in declared without a prototype
+	 BLTIN is the declaration of the built-in with a prototype
+	 and RHSTYPE is set to the actual type of the built-in.  */
+      tree bltin;
+      rhstype = type_or_builtin_type (rhs, &bltin);
+
       tree ttl = TREE_TYPE (type);
       tree ttr = TREE_TYPE (rhstype);
       tree mvl = ttl;
@@ -6805,21 +6985,45 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	  switch (errtype)
 	    {
 	    case ic_argpass:
-	      error_at (expr_loc, "passing argument %d of %qE from pointer to "
-			"non-enclosed address space", parmnum, rname);
+	      {
+		const char msg[] = G_("passing argument %d of %qE from "
+				      "pointer to non-enclosed address space");
+		if (warnopt)
+		  warning_at (expr_loc, warnopt, msg, parmnum, rname);
+		else
+		  error_at (expr_loc, msg, parmnum, rname);
 	      break;
+	      }
 	    case ic_assign:
-	      error_at (location, "assignment from pointer to "
-			"non-enclosed address space");
-	      break;
+	      {
+		const char msg[] = G_("assignment from pointer to "
+				      "non-enclosed address space");
+		if (warnopt)
+		  warning_at (location, warnopt, msg);
+		else
+		  error_at (location, msg);
+		break;
+	      }
 	    case ic_init:
-	      error_at (location, "initialization from pointer to "
-			"non-enclosed address space");
-	      break;
+	      {
+		const char msg[] = G_("initialization from pointer to "
+				      "non-enclosed address space");
+		if (warnopt)
+		  warning_at (location, warnopt, msg);
+		else
+		  error_at (location, msg);
+		break;
+	      }
 	    case ic_return:
-	      error_at (location, "return from pointer to "
-			"non-enclosed address space");
-	      break;
+	      {
+		const char msg[] = G_("return from pointer to "
+				      "non-enclosed address space");
+		if (warnopt)
+		  warning_at (location, warnopt, msg);
+		else
+		  error_at (location, msg);
+		break;
+	      }
 	    default:
 	      gcc_unreachable ();
 	    }
@@ -7017,19 +7221,38 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	      }
 	      break;
 	    case ic_assign:
-	      pedwarn (location, OPT_Wincompatible_pointer_types,
-		       "assignment to %qT from incompatible pointer type %qT",
-		       type, rhstype);
+	      if (bltin)
+		pedwarn (location, OPT_Wincompatible_pointer_types,
+			 "assignment to %qT from pointer to "
+			 "%qD with incompatible type %qT",
+			 type, bltin, rhstype);
+	      else
+		pedwarn (location, OPT_Wincompatible_pointer_types,
+			 "assignment to %qT from incompatible pointer type %qT",
+			 type, rhstype);
 	      break;
 	    case ic_init:
-	      pedwarn_init (location, OPT_Wincompatible_pointer_types,
-			    "initialization of %qT from incompatible pointer "
-			    "type %qT", type, rhstype);
+	      if (bltin)
+		pedwarn_init (location, OPT_Wincompatible_pointer_types,
+			      "initialization of %qT from pointer to "
+			      "%qD with incompatible type %qT",
+			      type, bltin, rhstype);
+	      else
+		pedwarn_init (location, OPT_Wincompatible_pointer_types,
+			      "initialization of %qT from incompatible "
+			      "pointer type %qT",
+			      type, rhstype);
 	      break;
 	    case ic_return:
-	      pedwarn (location, OPT_Wincompatible_pointer_types,
-		       "returning %qT from a function with incompatible "
-		       "return type %qT", rhstype, type);
+	      if (bltin)
+		pedwarn (location, OPT_Wincompatible_pointer_types,
+			 "returning pointer to %qD of type %qT from "
+			 "a function with incompatible type %qT",
+			 bltin, rhstype, type);
+	      else
+		pedwarn (location, OPT_Wincompatible_pointer_types,
+			 "returning %qT from a function with incompatible "
+			 "return type %qT", rhstype, type);
 	      break;
 	    default:
 	      gcc_unreachable ();
@@ -7042,7 +7265,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     {
       /* ??? This should not be an error when inlining calls to
 	 unprototyped functions.  */
-      error_at (location, "invalid use of non-lvalue array");
+      const char msg[] = "invalid use of non-lvalue array";
+      if (warnopt)
+	warning_at (location, warnopt, msg);
+      else
+	error_at (location, msg);
       return error_mark_node;
     }
   else if (codel == POINTER_TYPE && coder == INTEGER_TYPE)
@@ -7138,25 +7365,44 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	auto_diagnostic_group d;
 	range_label_for_type_mismatch rhs_label (rhstype, type);
 	gcc_rich_location richloc (expr_loc, &rhs_label);
-	error_at (&richloc, "incompatible type for argument %d of %qE", parmnum,
-		  rname);
+	const char msg[] = G_("incompatible type for argument %d of %qE");
+	if (warnopt)
+	  warning_at (expr_loc, warnopt, msg, parmnum, rname);
+	else
+	  error_at (&richloc, msg, parmnum, rname);
 	inform_for_arg (fundecl, expr_loc, parmnum, type, rhstype);
       }
       break;
     case ic_assign:
-      error_at (location, "incompatible types when assigning to type %qT from "
-		"type %qT", type, rhstype);
-      break;
+      {
+	const char msg[]
+	  = G_("incompatible types when assigning to type %qT from type %qT");
+	if (warnopt)
+	  warning_at (expr_loc, 0, msg, type, rhstype);
+	else
+	  error_at (expr_loc, msg, type, rhstype);
+	break;
+      }
     case ic_init:
-      error_at (location,
-		"incompatible types when initializing type %qT using type %qT",
-		type, rhstype);
-      break;
+      {
+	const char msg[]
+	  = G_("incompatible types when initializing type %qT using type %qT");
+	if (warnopt)
+	  warning_at (location, 0, msg, type, rhstype);
+	else
+	  error_at (location, msg, type, rhstype);
+	break;
+      }
     case ic_return:
-      error_at (location,
-		"incompatible types when returning type %qT but %qT was "
-		"expected", rhstype, type);
-      break;
+      {
+	const char msg[]
+	  = G_("incompatible types when returning type %qT but %qT was expected");
+	if (warnopt)
+	  warning_at (location, 0, msg, rhstype, type);
+	else
+	  error_at (location, msg, rhstype, type);
+	break;
+      }
     default:
       gcc_unreachable ();
     }
diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi
index 284594d..45cb222 100644
--- a/gcc/doc/invoke.texi
+++ b/gcc/doc/invoke.texi
@@ -6809,9 +6809,26 @@ attributes.
 @item -Wno-builtin-declaration-mismatch
 @opindex Wno-builtin-declaration-mismatch
 @opindex Wbuiltin-declaration-mismatch
-Warn if a built-in function is declared with the wrong signature or 
-as non-function.
-This warning is enabled by default.
+Warn if a built-in function is declared with an incompatible signature
+or as a non-function, or when a built-in function declared with a type
+that does not include a prototype is called with arguments whose promoted
+types do not match those expected by the function.  When @option{-Wextra}
+is specified, also warn when a built-in function that takes arguments is
+declared without a prototype.  The @option{-Wno-builtin-declaration-mismatch}
+warning is enabled by default.  To avoid the warning include the appropriate
+header to bring the prototypes of built-in functions into scope.
+
+For example, the call to @code{memset} below is diagnosed by the warning
+because the function expects a value of type @code{size_t} as its argument
+but the type of @code{32} is @code{int}.  With @option{-Wextra},
+the declaration of the function is diagnosed as well.
+@smallexample
+extern void* memset ();
+void f (void *d)
+@{
+  memset (d, '\0', 32);
+@}
+@end smallexample
 
 @item -Wno-builtin-macro-redefined
 @opindex Wno-builtin-macro-redefined
diff --git a/gcc/testsuite/gcc.dg/20021006-1.c b/gcc/testsuite/gcc.dg/20021006-1.c
index 63cc8a5..92df2c5 100644
--- a/gcc/testsuite/gcc.dg/20021006-1.c
+++ b/gcc/testsuite/gcc.dg/20021006-1.c
@@ -2,7 +2,7 @@
    This testcase was miscompiled on x86-64 due to wrong access to the struct
    members.  */
 
-extern void abort();
+extern void abort(void);
 
 struct A {
   long x;
diff --git a/gcc/testsuite/gcc.dg/Walloca-16.c b/gcc/testsuite/gcc.dg/Walloca-16.c
index 3ee96a9..866594c 100644
--- a/gcc/testsuite/gcc.dg/Walloca-16.c
+++ b/gcc/testsuite/gcc.dg/Walloca-16.c
@@ -4,3 +4,5 @@
 
 void *alloca ();
 __typeof__(alloca ()) a () { return alloca (); }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-2.c b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-2.c
new file mode 100644
index 0000000..9d75cd8
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-2.c
@@ -0,0 +1,25 @@
+/* PR c/83656 - missing -Wbuiltin-declaration-mismatch on declaration
+   without prototype
+   { dg-do compile }
+   { dg-options "-Wall -Wextra" } */
+
+typedef __SIZE_TYPE__ size_t;
+
+/* Verify that ordinary library built-ins are not diagnosed with -Wextra
+   when they take no arguments (except in cases of return type mismatches).
+   This is in anticipation that C may some day adopt the same syntax as
+   C++ for declaring functions that take no arguments.  */
+
+void abort ();
+
+/* Verify that ordinary library built-ins are diagnosed with -Wextra
+   when they take arguments.  */
+
+void* memcpy ();    /* { dg-warning "declaration of built-in function .memcpy. without a prototype; expected .void \\\*\\\(void \\\*, const void \\\*, \(long \)*unsigned int\\\)." } */
+void* memset ();    /* { dg-warning "declaration of built-in function .memset. without a prototype; expected .void \\\*\\\(void \\\*, int, *\(long \)*unsigned int\\\)." } */
+size_t strlen ();   /* { dg-warning "declaration of built-in function .strlen. without a prototype; expected .\(long \)*unsigned int\\\(const char \\\*\\\)." } */
+
+/* Variadic built-ins are diagnosed even without -Wextra (they are,
+   in fact, diagnosed by default).  */
+int printf ();      /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
+int sprintf ();     /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-3.c b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-3.c
new file mode 100644
index 0000000..f2ec325
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-3.c
@@ -0,0 +1,116 @@
+/* PR c/83656 - missing -Wbuiltin-declaration-mismatch on declaration
+   without prototype
+   { dg-do compile }
+   { dg-options "-Wbuiltin-declaration-mismatch" } */
+
+typedef __SIZE_TYPE__ size_t;
+
+/* Built-ins declared without a prototype are not diagnosed by default
+   (without -Wextra) except when their return type doesn't match.  */
+int abort ();       /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
+
+/* Built-ins declared without a prototype are not diagnosed without -Wextra.  */
+void exit ();
+void* memcpy ();
+void* memset ();
+
+
+void test_call_abort (void)
+{
+  /* Verify that a valid call to abort() is not diagnosed.  */
+  abort ();
+
+  /* Unfortunately, the incompatible declaration above makes GCC "forget"
+     that abort() is a built-in and so the invalid calls below aren't
+     diagnosed.  The only saving grace is that the invalid declaration
+     that differs in the return type is diagnosed by default. */
+  abort (1);        /* { dg-warning "too many arguments to built-in function .abort. expecting 0" "pr?????" { xfail *-*-* } } */
+
+  abort (1, 2);     /* { dg-warning "too many arguments" "pr?????" { xfail *-*-* } } */
+}
+
+
+void test_call_exit (void)
+{
+  /* Verify that valid calls to exit are not diagnosed.  */
+  exit ('\0');
+  exit (0);
+
+  /* Also verify calls to the built-in.  */
+  __builtin_exit ('\0');
+  __builtin_exit (0);
+  __builtin_exit (0.0);
+
+  exit ();          /* { dg-warning "too few arguments to built-in function 'exit' expecting 1" } */
+
+  exit (1, 2);      /* { dg-warning "too many arguments" } */
+
+  /* Verify that passing incompatible arguments triggers a warning.  */
+  exit ("");        /* { dg-warning "\\\[-Wint-conversion]" } */
+
+  struct S { int i; } s = { 0 };
+  exit (s);         /* { dg-warning "incompatible type for argument 1" } */
+}
+
+
+void test_call_memcpy (void *p, const void *q, size_t n)
+{
+  memcpy (p, q, n);
+
+  memcpy ();        /* { dg-warning "too few arguments to built-in function 'memcpy' expecting 3" } */
+
+  memcpy (p);       /* { dg-warning "too few arguments to built-in function 'memcpy' expecting 3" } */
+
+  memcpy (p, q);     /* { dg-warning "too few arguments to built-in function 'memcpy' expecting 3" } */
+
+  memcpy (q, p, n); /* { dg-warning "\\\[-Wdiscarded-qualifiers]" } */
+
+  memcpy (p, n, q); /* { dg-warning "\\\[-Wint-conversion]" } */
+
+  memcpy (p, q, n, 0); /* { dg-warning "too many arguments to built-in function 'memcpy' expecting 3" } */
+}
+
+
+typedef void* (memcpy_t)(void*, const void*, size_t);
+typedef void* (memset_t)(void*, int, size_t);
+
+void test_init (void)
+{
+  /* Verify that initialization of a pointer by the address of a built-in
+     function of a matching type declared without a prototype doesn't
+     trigger a warning...  */
+  memset_t *pmemset = memset;
+
+  /* ...but initialization by the address of an incompatible built-in
+     does even without -Wextra.  */
+  memcpy_t *pmemcpy = memset;           /* { dg-warning "\\\[-Wincompatible-pointer-types]" } */
+}
+
+
+void test_assign (void)
+{
+  /* Same as above but for assignment.  */
+  memset_t *pmemset;
+  pmemset = memset;
+
+  memcpy_t *pmemcpy;
+  pmemcpy = memset;                     /* { dg-warning "\\\[-Wincompatible-pointer-types]" } */
+}
+
+
+/* Verify that passing built-ins declared without a prototype to
+   functions that expect a pointer to a function of a specific type
+   is diagnosed.  Ditto for return statements.  */
+
+void take_memcpy (memcpy_t*);
+void take_any (int, ...);
+
+memset_t* pass_args (int i)
+{
+  take_memcpy (memcpy);
+  take_memcpy (memset);                 /* { dg-warning "\\\[-Wincompatible-pointer-types]" } */
+
+  take_any (0, i ? memcpy : memset);    /* { dg-warning "\\\[-Wincompatible-pointer-types]" } */
+
+  return memcpy;                        /* { dg-warning "\\\[-Wincompatible-pointer-types]" } */
+}
diff --git a/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-4.c b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-4.c
new file mode 100644
index 0000000..3c82e9d
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch-4.c
@@ -0,0 +1,152 @@
+/* PR c/83656 - missing -Wbuiltin-declaration-mismatch on declaration
+   without prototype
+   { dg-do compile }
+   { dg-options "-Wbuiltin-declaration-mismatch" } */
+
+typedef __PTRDIFF_TYPE__ ptrdiff_t;
+typedef __SIZE_TYPE__    size_t;
+
+char c;
+signed char sc;
+unsigned char uc;
+short si;
+unsigned short usi;
+int i;
+unsigned ui;
+long li;
+unsigned long uli;
+
+size_t szi;
+typedef size_t SizeType;
+SizeType szti;
+
+ptrdiff_t diffi;
+
+enum E { e0 } e;
+
+float f;
+double d;
+long double ld;
+
+
+/* Verify warnings for undefined calls to built-ins expecting integer
+   arguments.  */
+
+int abs ();         /* { dg-message "built-in .abs. declared here" } */
+
+void test_integer_conversion_abs (void)
+{
+  i = abs (c);
+  i = abs (sc);
+  i = abs (uc);
+
+  i = abs (si);
+  i = abs (usi);
+
+  i = abs (i);
+  i = abs (ui);     /* { dg-warning ".abs. argument 1 type is .unsigned int. where .int. is expected in a call to built-in function declared without prototype" } */
+
+  /* Verify that the same call as above but to the built-in doesn't
+     trigger a warning.  */
+  i = __builtin_abs (ui);
+
+  i = abs (li);     /* { dg-warning ".abs. argument 1 type is .long int. where .int. is expected in a call to built-in function declared without prototype" } */
+  i = abs (uli);    /* { dg-warning ".abs. argument 1 type is .long unsigned int. where .int. is expected in a call to built-in function declared without prototype" } */
+
+  i = abs (e0);
+  i = abs (e);
+
+  i = abs (-1.0);   /* { dg-warning ".abs. argument 1 type is .double. where .int. is expected in a call to built-in function declared without prototype" } */
+  i = abs (f);      /* { dg-warning ".abs. argument 1 promotes to .double. where .int. is expected in a call to built-in function declared without prototype" } */
+  i = abs (ld);     /* { dg-warning ".abs. argument 1 type is .long double. where .int. is expected in a call to built-in function declared without prototype" } */
+
+  /* Verify that the same call as above but to the built-in doesn't
+     trigger a warning.  */
+  i = __builtin_abs (ld);
+}
+
+
+extern void* memset ();
+
+void test_integer_conversion_memset (void *d)
+{
+  memset (d, 0, sizeof (int));
+  memset (d, '\0', szi);
+  memset (d, i, szti);
+
+  /* Passing a ptrdiff_t where size_t is expected may not be unsafe
+     but because GCC may emits suboptimal code for such calls warning
+     for them helps improve efficiency.  */
+  memset (d, 0, diffi);       /* { dg-warning ".memset. argument 3 promotes to .ptrdiff_t. {aka .long int.} where .long unsigned int. is expected" } */
+
+  memset (d, 0, 2.0);         /* { dg-warning ".memset. argument 3 type is .double. where 'long unsigned int' is expected" } */
+
+  /* Verify that the same call as above but to the built-in doesn't
+     trigger a warning.  */
+  __builtin_memset (d, 0.0, 4.0);
+}
+
+
+/* Verify warnings for undefined calls to built-ins expecting floating
+   arguments.  */
+
+double fabs ();           /* { dg-message "built-in .fabs. declared here" } */
+
+/* Expect a warning for fabsf below because even a float argument promotes
+   to double.  Unfortunately, invalid calls to fabsf() are not diagnosed.  */
+float fabsf ();           /* { dg-warning "conflicting types for built-in function .fabsf.; expected .float\\\(float\\\)." } */
+long double fabsl ();     /* { dg-message "built-in .fabsl. declared here" } */
+
+void test_real_conversion_fabs (void)
+{
+  d = fabs (c);     /* { dg-warning ".fabs. argument 1 promotes to .int. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  d = fabs (i);     /* { dg-warning ".fabs. argument 1 type is .int. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  d = fabs (li);    /* { dg-warning ".fabs. argument 1 type is .long int. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  /* In C, the type of an enumeration constant is int.  */
+  d = fabs (e0);    /* { dg-warning ".fabs. argument 1 type is .int. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  d = fabs (e);     /* { dg-warning ".fabs. argument 1 type is .enum E. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  /* No warning here since float is promoted to double.  */
+  d = fabs (f);
+
+  d = fabs (ld);    /* { dg-warning ".fabs. argument 1 type is .long double. where .double. is expected in a call to built-in function declared without prototype" } */
+
+  d = fabsf (c);    /* { dg-warning ".fabsf. argument 1 promotes to .int. where .float. is expected in a call to built-in function declared without prototype" "pr87890" { xfail *-*-* } } */
+
+  d = fabsl (c);    /* { dg-warning ".fabsl. argument 1 promotes to .int. where .long double. is expected in a call to built-in function declared without prototype" } */
+
+  d = fabsl (f);    /* { dg-warning ".fabsl. argument 1 promotes to .double. where .long double. is expected in a call to built-in function declared without prototype" } */
+
+  /* Verify that the same call as above but to the built-in doesn't
+     trigger a warning.  */
+  d = __builtin_fabsl (f);
+}
+
+/* Verify warnings for calls to a two-argument real function.  */
+
+double pow ();      /* { dg-message "built-in .pow. declared here" } */
+
+void test_real_conversion_pow (void)
+{
+  d = pow (2.0, 2.0);
+  d = pow (d, 3.0);
+  d = pow (d, d);
+
+  d = pow (2, 3.0); /* { dg-warning ".pow. argument 1 type is .int. where .double. is expected in a call to built-in function declared without prototype" } */
+  d = pow (3.0, 2); /* { dg-warning ".pow. argument 2 type is .int. where .double. is expected in a call to built-in function declared without prototype" } */
+}
+
+
+/* Verify warnings for calls that discard qualifiers.  */
+
+extern void* memcpy ();
+
+void test_qual_conversion_memcpy (void *d, const void *s)
+{
+  memcpy (d, s, sizeof (int));
+  memcpy (s, d, sizeof (int));    /* { dg-warning "passing argument 1 of .memcpy. discards 'const' qualifier from pointer target type" } */
+}
diff --git a/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch.c b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch.c
new file mode 100644
index 0000000..ed66fd3
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/Wbuiltin-declaration-mismatch.c
@@ -0,0 +1,23 @@
+/* PR c/83656 - missing -Wbuiltin-declaration-mismatch on declaration
+   without prototype
+   { dg-do compile }
+   { dg-options "-Wall" } */
+
+typedef __SIZE_TYPE__ size_t;
+
+/* Verify that ordinary library built-ins are not diagnosed with -Wall
+   (or by default) whether or not they take arguments (even though they
+   should be).  */
+
+void abort ();
+void* memcpy ();
+void* memset ();
+size_t strlen ();
+
+/* Verify mismatches in return types are diagnosed.  */
+int exit ();        /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
+
+/* Variadic built-ins are diagnosed with -Wall (they are, in fact,
+   diagnosed by default).  */
+int printf ();      /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
+int sprintf ();     /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/Wrestrict-4.c b/gcc/testsuite/gcc.dg/Wrestrict-4.c
index f2398ef..55ea6c0 100644
--- a/gcc/testsuite/gcc.dg/Wrestrict-4.c
+++ b/gcc/testsuite/gcc.dg/Wrestrict-4.c
@@ -108,3 +108,5 @@ void* test_strncpy_2 (char *d, const char *s)
 {
   return strncpy (d, s);
 }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/Wrestrict-5.c b/gcc/testsuite/gcc.dg/Wrestrict-5.c
index 4912ee5..7064e1e 100644
--- a/gcc/testsuite/gcc.dg/Wrestrict-5.c
+++ b/gcc/testsuite/gcc.dg/Wrestrict-5.c
@@ -41,3 +41,6 @@ void test_strncpy_nowarn (char *d)
 {
   strncpy (d + 1, d + 3, "");
 }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" }
+   { dg-prune-output "\\\[-Wint-conversion]" } */
diff --git a/gcc/testsuite/gcc.dg/atomic/stdatomic-generic.c b/gcc/testsuite/gcc.dg/atomic/stdatomic-generic.c
index 8033c53..96582b4 100644
--- a/gcc/testsuite/gcc.dg/atomic/stdatomic-generic.c
+++ b/gcc/testsuite/gcc.dg/atomic/stdatomic-generic.c
@@ -4,7 +4,7 @@
 
 #include <stdatomic.h>
 
-extern void abort ();
+extern void abort (void);
 extern int memcmp (const void *, const void *, __SIZE_TYPE__);
 
 typedef struct test {
diff --git a/gcc/testsuite/gcc.dg/atomic/stdatomic-lockfree.c b/gcc/testsuite/gcc.dg/atomic/stdatomic-lockfree.c
index 29310e9..c6d06a5 100644
--- a/gcc/testsuite/gcc.dg/atomic/stdatomic-lockfree.c
+++ b/gcc/testsuite/gcc.dg/atomic/stdatomic-lockfree.c
@@ -5,7 +5,7 @@
 #include <stdatomic.h>
 #include <stdint.h>
 
-extern void abort ();
+extern void abort (void);
 
 _Atomic _Bool aba;
 atomic_bool abt;
diff --git a/gcc/testsuite/gcc.dg/initpri1.c b/gcc/testsuite/gcc.dg/initpri1.c
index 794ea2b..b6afd76 100644
--- a/gcc/testsuite/gcc.dg/initpri1.c
+++ b/gcc/testsuite/gcc.dg/initpri1.c
@@ -1,6 +1,6 @@
 /* { dg-do run { target init_priority } } */
 
-extern void abort ();
+extern void abort (void);
 
 int i;
 int j;
diff --git a/gcc/testsuite/gcc.dg/pr15698-1.c b/gcc/testsuite/gcc.dg/pr15698-1.c
index 5a75a10..cbe613c 100644
--- a/gcc/testsuite/gcc.dg/pr15698-1.c
+++ b/gcc/testsuite/gcc.dg/pr15698-1.c
@@ -21,3 +21,5 @@ char *rindex(a, b)
 {
   return 0;
 }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/pr69156.c b/gcc/testsuite/gcc.dg/pr69156.c
index 1addfa3..522ac00 100644
--- a/gcc/testsuite/gcc.dg/pr69156.c
+++ b/gcc/testsuite/gcc.dg/pr69156.c
@@ -5,6 +5,6 @@
 _Bool
 foo ()
 {
-  _Bool (*f) () = __builtin_abs;	/* { dg-warning "initialization of '_Bool \\(\\*\\)\\(\\)' from incompatible pointer type" } */
+  _Bool (*f) () = __builtin_abs;	/* { dg-warning "initialization of '_Bool \\(\\*\\)\\(\\)' from pointer to .__builtin_abs. with incompatible type .int \\\(\\\*\\\)." } */
   return f (0);
 }
diff --git a/gcc/testsuite/gcc.dg/pr83463.c b/gcc/testsuite/gcc.dg/pr83463.c
index ddf662f..cd11f64 100644
--- a/gcc/testsuite/gcc.dg/pr83463.c
+++ b/gcc/testsuite/gcc.dg/pr83463.c
@@ -15,3 +15,5 @@ p ()
 {
   m (p + (long) a);
 }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/redecl-4.c b/gcc/testsuite/gcc.dg/redecl-4.c
index 2ba74a3..8f12488 100644
--- a/gcc/testsuite/gcc.dg/redecl-4.c
+++ b/gcc/testsuite/gcc.dg/redecl-4.c
@@ -27,3 +27,6 @@ f (void)
 
 /* Should still diagnose incompatible prototype for strcmp.  */
 int strcmp (void); /* { dg-error "conflict" } */
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" }
+   { dg-prune-output "\\\[-Wint-conversion]" } */
diff --git a/gcc/testsuite/gcc.dg/tls/thr-init-2.c b/gcc/testsuite/gcc.dg/tls/thr-init-2.c
index 22c96ea..a540389 100644
--- a/gcc/testsuite/gcc.dg/tls/thr-init-2.c
+++ b/gcc/testsuite/gcc.dg/tls/thr-init-2.c
@@ -2,7 +2,7 @@
 /* { dg-require-effective-target tls_runtime } */
 /* { dg-add-options tls } */
 
-extern void abort() ;
+extern void abort (void);
 
 static __thread int fstat ;
 static __thread int fstat = 1;
diff --git a/gcc/testsuite/gcc.dg/torture/pr55890-2.c b/gcc/testsuite/gcc.dg/torture/pr55890-2.c
index 1cf71d7..31779e0 100644
--- a/gcc/testsuite/gcc.dg/torture/pr55890-2.c
+++ b/gcc/testsuite/gcc.dg/torture/pr55890-2.c
@@ -2,3 +2,5 @@
 
 extern void *memcpy();
 int main() { memcpy(); }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/torture/pr55890-3.c b/gcc/testsuite/gcc.dg/torture/pr55890-3.c
index c7f77be..21a3d98 100644
--- a/gcc/testsuite/gcc.dg/torture/pr55890-3.c
+++ b/gcc/testsuite/gcc.dg/torture/pr55890-3.c
@@ -7,3 +7,5 @@ bar ()
 {
   return memmove ();
 }
+
+/* { dg-prune-output "\\\[-Wbuiltin-declaration-mismatch]" } */
diff --git a/gcc/testsuite/gcc.dg/torture/pr67741.c b/gcc/testsuite/gcc.dg/torture/pr67741.c
index 1ffc707..833e53e 100644
--- a/gcc/testsuite/gcc.dg/torture/pr67741.c
+++ b/gcc/testsuite/gcc.dg/torture/pr67741.c
@@ -3,11 +3,12 @@
 struct singlecomplex { float real, imag ; } ;
 struct doublecomplex { double real, imag ; } ;
 struct extendedcomplex { long double real, imag ; } ;
-extern double cabs();
+extern double cabs(); /* { dg-warning "\\\[-Wbuiltin-declaration-mismatch]" } */
 float cabsf(fc)
      struct singlecomplex fc;  /* { dg-warning "doesn't match" } */
 {
   struct doublecomplex dc ;
   dc.real=fc.real; dc.imag=fc.imag;
-  return (float) cabs(dc);
+  return (float) cabs(dc);   /* { dg-warning "incompatible type for argument 1 of .cabs." } */
 }
+
diff --git a/gcc/testsuite/gcc.dg/torture/stackalign/sibcall-1.c b/gcc/testsuite/gcc.dg/torture/stackalign/sibcall-1.c
index 8c17475..c4992df 100644
--- a/gcc/testsuite/gcc.dg/torture/stackalign/sibcall-1.c
+++ b/gcc/testsuite/gcc.dg/torture/stackalign/sibcall-1.c
@@ -1,7 +1,7 @@
 /* { dg-do run } */
 
 extern int ok (int);
-extern void exit ();
+extern void exit (int);
 static int gen_x86_64_shrd (int);
 static int
 gen_x86_64_shrd(int a __attribute__ ((__unused__)))
diff --git a/gcc/testsuite/gcc.dg/torture/tls/thr-init-1.c b/gcc/testsuite/gcc.dg/torture/tls/thr-init-1.c
index ff3338f..3ae2e29 100644
--- a/gcc/testsuite/gcc.dg/torture/tls/thr-init-1.c
+++ b/gcc/testsuite/gcc.dg/torture/tls/thr-init-1.c
@@ -3,7 +3,7 @@
 /* { dg-add-options tls } */
 
 extern int printf (char *,...);
-extern void abort() ;
+extern void abort(void) ;
 
 int test_code(int b)
 {
diff --git a/gcc/testsuite/gcc.dg/tree-ssa/builtins-folding-gimple-ub.c b/gcc/testsuite/gcc.dg/tree-ssa/builtins-folding-gimple-ub.c
index a313998..0912b68 100644
--- a/gcc/testsuite/gcc.dg/tree-ssa/builtins-folding-gimple-ub.c
+++ b/gcc/testsuite/gcc.dg/tree-ssa/builtins-folding-gimple-ub.c
@@ -31,4 +31,5 @@ main (void)
   return 0;
 }
 
-/* { dg-final { scan-tree-dump-times "__builtin_memchr" 2 "optimized" } } */
+/* { dg-prune-output "-Wbuiltin-declaration-mismatch" }
+   { dg-final { scan-tree-dump-times "__builtin_memchr" 2 "optimized" } } */

Reply via email to