Skip to content
Snippets Groups Projects
Commit bbc7900c authored by David Malcolm's avatar David Malcolm
Browse files

c: improve UX for -Wincompatible-pointer-types (v3) [PR116871]


PR c/116871 notes that our diagnostics about incompatible function types
could be improved.

In particular, for the case of migrating to C23 I'm seeing a lot of
build failures with signal handlers similar to this (simplified from
alsa-tools-1.2.11, envy24control/profiles.c; see rhbz#2336278):

typedef void (*__sighandler_t) (int);

extern __sighandler_t signal (int __sig, __sighandler_t __handler)
     __attribute__ ((__nothrow__ , __leaf__));

void new_process(void)
{
  void (*int_stat)();

  int_stat = signal(2,  ((__sighandler_t) 1));

  signal(2, int_stat);
}

Before this patch, cc1 fails with this message:

t.c: In function 'new_process':
t.c:18:12: error: assignment to 'void (*)(void)' from incompatible pointer type '__sighandler_t' {aka 'void (*)(int)'} [-Wincompatible-pointer-types]
   18 |   int_stat = signal(2,  ((__sighandler_t) 1));
      |            ^
t.c:20:13: error: passing argument 2 of 'signal' from incompatible pointer type [-Wincompatible-pointer-types]
   20 |   signal(2, int_stat);
      |             ^~~~~~~~
      |             |
      |             void (*)(void)
t.c:11:57: note: expected '__sighandler_t' {aka 'void (*)(int)'} but argument is of type 'void (*)(void)'
   11 | extern __sighandler_t signal (int __sig, __sighandler_t __handler)
      |                                          ~~~~~~~~~~~~~~~^~~~~~~~~

With this patch, cc1 emits:

t.c: In function 'new_process':
t.c:18:12: error: assignment to 'void (*)(void)' from incompatible pointer type '__sighandler_t' {aka 'void (*)(int)'} [-Wincompatible-pointer-types]
   18 |   int_stat = signal(2,  ((__sighandler_t) 1));
      |            ^
t.c:9:16: note: '__sighandler_t' declared here
    9 | typedef void (*__sighandler_t) (int);
      |                ^~~~~~~~~~~~~~
t.c:20:13: error: passing argument 2 of 'signal' from incompatible pointer type [-Wincompatible-pointer-types]
   20 |   signal(2, int_stat);
      |             ^~~~~~~~
      |             |
      |             void (*)(void)
t.c:11:57: note: expected '__sighandler_t' {aka 'void (*)(int)'} but argument is of type 'void (*)(void)'
   11 | extern __sighandler_t signal (int __sig, __sighandler_t __handler)
      |                                          ~~~~~~~~~~~~~~~^~~~~~~~~
t.c:9:16: note: '__sighandler_t' declared here
    9 | typedef void (*__sighandler_t) (int);
      |                ^~~~~~~~~~~~~~

showing the location of the pertinent typedef ("__sighandler_t")

Another example, simplfied from a52dec-0.7.4: src/a52dec.c
(rhbz#2336013):

typedef void (*__sighandler_t) (int);

extern __sighandler_t signal (int __sig, __sighandler_t __handler)
     __attribute__ ((__nothrow__ , __leaf__));

/* Mismatching return type.  */
static RETSIGTYPE signal_handler (int sig)
{
}

static void print_fps (int final)
{
  signal (42, signal_handler);
}

Before this patch, cc1 emits:

t2.c: In function 'print_fps':
t2.c:22:15: error: passing argument 2 of 'signal' from incompatible pointer type [-Wincompatible-pointer-types]
   22 |   signal (42, signal_handler);
      |               ^~~~~~~~~~~~~~
      |               |
      |               int (*)(int)
t2.c:11:57: note: expected '__sighandler_t' {aka 'void (*)(int)'} but argument is of type 'int (*)(int)'
   11 | extern __sighandler_t signal (int __sig, __sighandler_t __handler)
      |                                          ~~~~~~~~~~~~~~~^~~~~~~~~

With this patch cc1 emits:

t2.c: In function 'print_fps':
t2.c:22:15: error: passing argument 2 of 'signal' from incompatible pointer type [-Wincompatible-pointer-types]
   22 |   signal (42, signal_handler);
      |               ^~~~~~~~~~~~~~
      |               |
      |               int (*)(int)
t2.c:11:57: note: expected '__sighandler_t' {aka 'void (*)(int)'} but argument is of type 'int (*)(int)'
   11 | extern __sighandler_t signal (int __sig, __sighandler_t __handler)
      |                                          ~~~~~~~~~~~~~~~^~~~~~~~~
t2.c:16:19: note: 'signal_handler' declared here
   16 | static RETSIGTYPE signal_handler (int sig)
      |                   ^~~~~~~~~~~~~~
t2.c:9:16: note: '__sighandler_t' declared here
    9 | typedef void (*__sighandler_t) (int);
      |                ^~~~~~~~~~~~~~

showing the location of the pertinent fndecl ("signal_handler"), and,
as before, the pertinent typedef.

The patch also updates the colorization in the messages to visually
link and contrast the different types and typedefs.

My hope is that this make it easier for users to decipher build failures
seen with the new C23 default.

Further improvements could be made to colorization in
convert_for_assignment, and similar improvements to C++, but I'm punting
those to GCC 16.

gcc/c/ChangeLog:
	PR c/116871
	* c-typeck.cc (pedwarn_permerror_init): Return bool for whether a
	warning was emitted.  Only call print_spelling if we warned.
	(pedwarn_init): Return bool for whether a warning was emitted.
	(permerror_init): Likewise.
	(warning_init): Return bool for whether a
	warning was emitted.  Only call print_spelling if we warned.
	(class pp_element_quoted_decl): New.
	(maybe_inform_typedef_location): New.
	(convert_for_assignment): For OPT_Wincompatible_pointer_types,
	move auto_diagnostic_group to cover all cases.  Use %e and
	pp_element rather than %qT and tree to colorize the types.
	Capture whether a warning was emitted, and, if it was,
	show various notes: for a pointer to a function, show the
	function decl, for typedef types, and show the decls.

gcc/testsuite/ChangeLog:
	PR c/116871
	* gcc.dg/c23-mismatching-fn-ptr-a52dec.c: New test.
	* gcc.dg/c23-mismatching-fn-ptr-alsatools.c: New test.
	* gcc.dg/c23-mismatching-fn-ptr.c: New test.

Signed-off-by: default avatarDavid Malcolm <dmalcolm@redhat.com>
parent f7b7fe16
No related branches found
No related tags found
No related merge requests found
...@@ -7477,7 +7477,7 @@ error_init (location_t loc, const char *gmsgid, ...) ...@@ -7477,7 +7477,7 @@ error_init (location_t loc, const char *gmsgid, ...)
   
/* Used to implement pedwarn_init and permerror_init. */ /* Used to implement pedwarn_init and permerror_init. */
   
static void ATTRIBUTE_GCC_DIAG (3,0) static bool ATTRIBUTE_GCC_DIAG (3,0)
pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid, pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid,
va_list *ap, diagnostic_t kind) va_list *ap, diagnostic_t kind)
{ {
...@@ -7487,9 +7487,13 @@ pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid, ...@@ -7487,9 +7487,13 @@ pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid,
location_t exploc = expansion_point_location_if_in_system_header (loc); location_t exploc = expansion_point_location_if_in_system_header (loc);
auto_diagnostic_group d; auto_diagnostic_group d;
bool warned = emit_diagnostic_valist (kind, exploc, opt, gmsgid, ap); bool warned = emit_diagnostic_valist (kind, exploc, opt, gmsgid, ap);
char *ofwhat = print_spelling ((char *) alloca (spelling_length () + 1)); if (warned)
if (*ofwhat && warned) {
inform (exploc, "(near initialization for %qs)", ofwhat); char *ofwhat = print_spelling ((char *) alloca (spelling_length () + 1));
if (*ofwhat)
inform (exploc, "(near initialization for %qs)", ofwhat);
}
return warned;
} }
   
/* Issue a pedantic warning for a bad initializer component. OPT is /* Issue a pedantic warning for a bad initializer component. OPT is
...@@ -7497,24 +7501,26 @@ pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid, ...@@ -7497,24 +7501,26 @@ pedwarn_permerror_init (location_t loc, int opt, const char *gmsgid,
it is unconditionally given. GMSGID identifies the message. The it is unconditionally given. GMSGID identifies the message. The
component name is taken from the spelling stack. */ component name is taken from the spelling stack. */
   
static void ATTRIBUTE_GCC_DIAG (3,0) static bool ATTRIBUTE_GCC_DIAG (3,0)
pedwarn_init (location_t loc, int opt, const char *gmsgid, ...) pedwarn_init (location_t loc, int opt, const char *gmsgid, ...)
{ {
va_list ap; va_list ap;
va_start (ap, gmsgid); va_start (ap, gmsgid);
pedwarn_permerror_init (loc, opt, gmsgid, &ap, DK_PEDWARN); bool warned = pedwarn_permerror_init (loc, opt, gmsgid, &ap, DK_PEDWARN);
va_end (ap); va_end (ap);
return warned;
} }
   
/* Like pedwarn_init, but issue a permerror. */ /* Like pedwarn_init, but issue a permerror. */
   
static void ATTRIBUTE_GCC_DIAG (3,0) static bool ATTRIBUTE_GCC_DIAG (3,0)
permerror_init (location_t loc, int opt, const char *gmsgid, ...) permerror_init (location_t loc, int opt, const char *gmsgid, ...)
{ {
va_list ap; va_list ap;
va_start (ap, gmsgid); va_start (ap, gmsgid);
pedwarn_permerror_init (loc, opt, gmsgid, &ap, DK_PERMERROR); bool warned = pedwarn_permerror_init (loc, opt, gmsgid, &ap, DK_PERMERROR);
va_end (ap); va_end (ap);
return warned;
} }
   
/* Issue a warning for a bad initializer component. /* Issue a warning for a bad initializer component.
...@@ -7538,9 +7544,12 @@ warning_init (location_t loc, int opt, const char *gmsgid) ...@@ -7538,9 +7544,12 @@ warning_init (location_t loc, int opt, const char *gmsgid)
   
/* The gmsgid may be a format string with %< and %>. */ /* The gmsgid may be a format string with %< and %>. */
warned = warning_at (exploc, opt, gmsgid); warned = warning_at (exploc, opt, gmsgid);
ofwhat = print_spelling ((char *) alloca (spelling_length () + 1)); if (warned)
if (*ofwhat && warned) {
inform (exploc, "(near initialization for %qs)", ofwhat); ofwhat = print_spelling ((char *) alloca (spelling_length () + 1));
if (*ofwhat)
inform (exploc, "(near initialization for %qs)", ofwhat);
}
} }
/* If TYPE is an array type and EXPR is a parenthesized string /* If TYPE is an array type and EXPR is a parenthesized string
...@@ -7651,6 +7660,62 @@ maybe_warn_builtin_no_proto_arg (location_t loc, tree fundecl, int parmnum, ...@@ -7651,6 +7660,62 @@ maybe_warn_builtin_no_proto_arg (location_t loc, tree fundecl, int parmnum,
fundecl); fundecl);
} }
   
/* Print a declaration in quotes, with the given highlight_color.
Analogous to handler for %qD, but with a specific highlight color. */
class pp_element_quoted_decl : public pp_element
{
public:
pp_element_quoted_decl (tree decl, const char *highlight_color)
: m_decl (decl),
m_highlight_color (highlight_color)
{
}
void add_to_phase_2 (pp_markup::context &ctxt) override
{
ctxt.begin_quote ();
ctxt.begin_highlight_color (m_highlight_color);
print_decl (ctxt);
ctxt.end_highlight_color ();
ctxt.end_quote ();
}
void print_decl (pp_markup::context &ctxt)
{
pretty_printer *const pp = &ctxt.m_pp;
pp->set_padding (pp_none);
if (DECL_NAME (m_decl))
pp_identifier (pp, lang_hooks.decl_printable_name (m_decl, 2));
else
pp_string (pp, _("({anonymous})"));
}
private:
tree m_decl;
const char *m_highlight_color;
};
/* If TYPE is from a typedef, issue a note showing the location
to the user.
Use HIGHLIGHT_COLOR as the highlight color. */
static void
maybe_inform_typedef_location (tree type, const char *highlight_color)
{
if (!typedef_variant_p (type))
return;
tree typedef_decl = TYPE_NAME (type);
gcc_assert (TREE_CODE (typedef_decl) == TYPE_DECL);
gcc_rich_location richloc (DECL_SOURCE_LOCATION (typedef_decl),
nullptr, highlight_color);
pp_element_quoted_decl e_typedef_decl (typedef_decl, highlight_color);
inform (&richloc, "%e declared here", &e_typedef_decl);
}
/* Convert value RHS to type TYPE as preparation for an assignment to /* 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 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 original type of RHS; this differs from TREE_TYPE (RHS) for enum
...@@ -8474,59 +8539,97 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type, ...@@ -8474,59 +8539,97 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
/* Avoid warning about the volatile ObjC EH puts on decls. */ /* Avoid warning about the volatile ObjC EH puts on decls. */
else if (!objc_ok) else if (!objc_ok)
{ {
auto_diagnostic_group d;
bool warned = false;
pp_markup::element_expected_type e_type (type);
pp_markup::element_actual_type e_rhstype (rhstype);
switch (errtype) switch (errtype)
{ {
case ic_argpass: case ic_argpass:
{ {
auto_diagnostic_group d;
range_label_for_type_mismatch rhs_label (rhstype, type); range_label_for_type_mismatch rhs_label (rhstype, type);
gcc_rich_location richloc (expr_loc, &rhs_label, gcc_rich_location richloc (expr_loc, &rhs_label,
highlight_colors::actual); highlight_colors::actual);
if (permerror_opt (&richloc, OPT_Wincompatible_pointer_types, warned
= permerror_opt (&richloc, OPT_Wincompatible_pointer_types,
"passing argument %d of %qE from " "passing argument %d of %qE from "
"incompatible pointer type", "incompatible pointer type",
parmnum, rname)) parmnum, rname);
if (warned)
inform_for_arg (fundecl, expr_loc, parmnum, type, rhstype); inform_for_arg (fundecl, expr_loc, parmnum, type, rhstype);
} }
break; break;
case ic_assign: case ic_assign:
if (bltin) if (bltin)
permerror_opt (location, OPT_Wincompatible_pointer_types, warned
"assignment to %qT from pointer to " = permerror_opt (location, OPT_Wincompatible_pointer_types,
"%qD with incompatible type %qT", "assignment to %e from pointer to "
type, bltin, rhstype); "%qD with incompatible type %e",
&e_type, bltin, &e_rhstype);
else else
permerror_opt (location, OPT_Wincompatible_pointer_types, warned
"assignment to %qT from incompatible pointer " = permerror_opt (location, OPT_Wincompatible_pointer_types,
"type %qT", type, rhstype); "assignment to %e from incompatible "
"pointer type %e",
&e_type, &e_rhstype);
break; break;
case ic_init: case ic_init:
case ic_init_const: case ic_init_const:
if (bltin) if (bltin)
permerror_init (location, OPT_Wincompatible_pointer_types, warned
"initialization of %qT from pointer to " = permerror_init (location, OPT_Wincompatible_pointer_types,
"%qD with incompatible type %qT", "initialization of %e from pointer to "
type, bltin, rhstype); "%qD with incompatible type %e",
&e_type, bltin, &e_rhstype);
else else
permerror_init (location, OPT_Wincompatible_pointer_types, warned
"initialization of %qT from incompatible " = permerror_init (location, OPT_Wincompatible_pointer_types,
"pointer type %qT", "initialization of %e from incompatible "
type, rhstype); "pointer type %e",
&e_type, &e_rhstype);
break; break;
case ic_return: case ic_return:
if (bltin) if (bltin)
permerror_opt (location, OPT_Wincompatible_pointer_types, warned
"returning pointer to %qD of type %qT from " = permerror_opt (location, OPT_Wincompatible_pointer_types,
"a function with incompatible type %qT", "returning pointer to %qD of type %e from "
bltin, rhstype, type); "a function with incompatible type %e",
bltin, &e_rhstype, &e_type);
else else
permerror_opt (location, OPT_Wincompatible_pointer_types, warned
"returning %qT from a function with " = permerror_opt (location, OPT_Wincompatible_pointer_types,
"incompatible return type %qT", rhstype, type); "returning %e from a function with "
"incompatible return type %e",
&e_rhstype, &e_type);
break; break;
default: default:
gcc_unreachable (); gcc_unreachable ();
} }
if (warned)
{
/* If the mismatching function type is a pointer to a function,
try to show the decl of the function. */
if (TREE_CODE (rhs) == ADDR_EXPR
&& TREE_CODE (TREE_OPERAND (rhs, 0)) == FUNCTION_DECL)
{
tree rhs_fndecl = TREE_OPERAND (rhs, 0);
if (!DECL_IS_UNDECLARED_BUILTIN (rhs_fndecl))
{
gcc_rich_location richloc
(DECL_SOURCE_LOCATION (rhs_fndecl), nullptr,
highlight_colors::actual);
pp_element_quoted_decl e_rhs_fndecl
(rhs_fndecl, highlight_colors::actual);
inform (&richloc,
"%e declared here", &e_rhs_fndecl);
}
}
/* If either/both of the types are typedefs, show the decl. */
maybe_inform_typedef_location (type,
highlight_colors::expected);
maybe_inform_typedef_location (rhstype,
highlight_colors::actual);
}
} }
   
/* If RHS isn't an address, check pointer or array of packed /* If RHS isn't an address, check pointer or array of packed
......
/* Examples of a mismatching function pointer type in
legacy code that got the wrong return type for the signal handler.
Adapted from a52dec-0.7.4: src/a52dec.c which is GPLv2+. */
/* { dg-do compile } */
/* { dg-options "-std=c23 -pedantic-errors" } */
typedef void (*__sighandler_t) (int); /* { dg-message "'__sighandler_t' declared here" } */
extern __sighandler_t signal (int __sig, __sighandler_t __handler) /* { dg-message "expected '__sighandler_t' \\{aka '\[^\n\r\]*'\\} but argument is of type '\[^\n\r\]*'" } */
__attribute__ ((__nothrow__ , __leaf__));
/* Mismatching return type. */
#define RETSIGTYPE int
static RETSIGTYPE signal_handler (int sig) /* { dg-message "'signal_handler' declared here" } */
{
}
static void print_fps (int final)
{
signal (42, signal_handler); /* { dg-error "passing argument 2 of 'signal' from incompatible pointer type" } */
}
/* Examples of a mismatching function pointer type in
legacy code that failed to compile with C23.
Adapted from alsa-tools-1.2.11:envy24control/profiles.c which is GPLv2+. */
/* { dg-do compile } */
/* { dg-options "-std=c23 -pedantic-errors" } */
typedef void (*__sighandler_t) (int); /* { dg-message "'__sighandler_t' declared here" } */
extern __sighandler_t signal (int __sig, __sighandler_t __handler)
__attribute__ ((__nothrow__ , __leaf__));
void new_process(void)
{
void (*int_stat)();
int_stat = signal(2, ((__sighandler_t) 1)); /* { dg-error "assignment to '\[^\n\r\]*' from incompatible pointer type '__sighandler_t' \\{aka '\[^\n\r\]*'\\}" } */
signal(2, int_stat); /* { dg-error "passing argument 2 of 'signal' from incompatible pointer type" } */
}
/* Verify that when we complain about incompatible pointer types
involving function pointers, we show the declaration of the
function. */
/* { dg-do compile } */
/* { dg-options "-std=c23 -pedantic-errors" } */
/* We're pretending that this is legacy code that was written before C23,
hence it uses NULL rather than nullptr. */
#define NULL ((void*)0)
typedef void (*void_int_fnptr_t) (int);
extern void takes_void_int_fnptr (void_int_fnptr_t fn); /* { dg-message "expected 'void_int_fnptr_t' \\{aka '\[^\n\r\]*'\\} but argument is of type '\[^\n\r\]*'" } */
extern void fn_argpass(); /* { dg-message "declared here" } */
void test_argpass ()
{
takes_void_int_fnptr (&fn_argpass); /* { dg-error "passing argument 1 of 'takes_void_int_fnptr' from incompatible pointer type" } */
}
extern void fn_assign(); /* { dg-message "declared here" } */
void test_assign ()
{
void (*assigned_to) (int);
assigned_to = &fn_assign; /* { dg-error "assignment to '\[^\n\r\]*' from incompatible pointer type '\[^\n\r\]*'" } */
}
extern void fn_init(); /* { dg-message "declared here" } */
void test_init ()
{
void (*initialized) (int) = &fn_init; /* { dg-error "initialization of '\[^\n\r\]*' from incompatible pointer type '\[^\n\r\]*'" } */
}
extern void fn_return(); /* { dg-message "declared here" } */
void_int_fnptr_t
test_return ()
{
return &fn_return; /* { dg-error "returning '\[^\n\r\]*' from a function with incompatible return type '\[^\n\r\]*'" } */
}
/* Test of storing a sighandler_t with a function signature mismatch.
In particular, verify that we show the locations of typedefs. */
typedef void (*sighandler_t)(int); /* { dg-message "'sighandler_t' declared here" } */
sighandler_t signal(int signum, sighandler_t handler);
typedef void (*wrong_sighandler_t)(void); /* { dg-message "'wrong_sighandler_t' declared here" } */
extern void takes_wrong_sighandler_type (wrong_sighandler_t fn); /* { dg-message "expected 'wrong_sighandler_t' \\{aka '\[^\n\r\]*'\\} but argument is of type 'sighandler_t' \\{aka '\[^\n\r\]*'\\}" } */
void test_argpass_from_signal_result ()
{
takes_wrong_sighandler_type (signal (42, NULL)); /* { dg-error "passing argument 1 of 'takes_wrong_sighandler_type' from incompatible pointer type" } */
}
void test_assign_from_signal_result ()
{
wrong_sighandler_t assigned_to;
assigned_to = signal (42, NULL); /* { dg-error "assignment to 'wrong_sighandler_t' \\{aka '\[^\n\r\]*'\\} from incompatible pointer type 'sighandler_t' \\{aka '\[^\n\r\]*'\\}" } */
}
void test_init_from_signal_result ()
{
wrong_sighandler_t initialized = signal (42, NULL); /* { dg-error "initialization of 'wrong_sighandler_t' \\{aka '\[^\n\r\]*'\\} from incompatible pointer type 'sighandler_t' \\{aka '\[^\n\r\]*'\\}" } */
}
wrong_sighandler_t
test_return_signal_result ()
{
return signal (42, NULL); /* { dg-error "returning 'sighandler_t' \\{aka '\[^\n\r\]*'\\} from a function with incompatible return type 'wrong_sighandler_t' \\{aka '\[^\n\r\]*'\\}" } */
}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment