diff --git a/gcc/ChangeLog b/gcc/ChangeLog index 737ab285be38d3434a1cc2911e3203c98ff0a831..0905e540d5f29f07354a4aa07d820938648a7d88 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,3 +1,46 @@ +2003-07-19 Zack Weinberg <zack@codesourcery.com> + + * c-decl.c (named_labels, shadowed_labels, label_level_chain) + (push_label_level, pop_label_level): Kill. + (struct binding_level): Rename level_chain to outer. + Add outer_function field. Change parm_flag, function_body, + keep, keep_if_subblocks to 1-bit bitfields of type bool. + (current_function_level): New variable. + (keep_next_level_flag, keep_next_if_subblocks): Change type to bool. + (keep_next_level, declare_parm_level, warn_if_shadowing): + Update to match. + (struct language_function): Kill named_labels, shadowed_labels fields. + (c_init_decl_processing, start_function, c_push__function_context) + (c_pop_function_context): No need to muck with named_labels nor + shadowed_labels. + + (make_binding_level): No need to clear the structure here. + (pop_binding_level): Always operate on current_binding_level. + Update current_function_level if necessary. + (pushlevel): Don't clear named_labels. Update current_function_level + if necessary. Use "true" and "false" where appropriate. + (poplevel): Diagnose labels defined but not used, or vice + versa, and clear out label-meanings leaving scope, while + walking down the decls list, for all binding levels. + Handle LABEL_DECLs appearing in the shadowed list. + pop_binding_level takes no arguments. + (pushdecl_function_level): Use current_function_level. + + (make_label, bind_label): New static functions. + (declare_label): New exported function. + (lookup_label, define_label): Rewritten for new data structure. + (shadow_label): Kill. + + * c-tree.h: Prototype declare_label; don't prototype + push_label_level, pop_label_level, nor shadow_label. + * c-parse.in: Remove all calls to push_label_level and + pop_label_level. Use declare_label for __label__ decls. + + * doc/extend.texi: Clarify that __label__ can be used to + declare labels with local scope in any nested block, not + just statement expressions. Cross-reference nested functions + section from local labels section. + 2003-07-19 Zdenek Dvorak <rakdver@atrey.karlin.mff.cuni.cz> * sched-rgn.c (find_rgns): Initialize current_edge correctly. @@ -13,7 +56,7 @@ 2003-07-19 Ulrich Weigand <uweigand@de.ibm.com> - * config/s390/s390.c (legitimize_pic_address): Access local symbols + * config/s390/s390.c (legitimize_pic_address): Access local symbols relative to the GOT instead of relative to the literal pool base. (s390_output_symbolic_const): Handle new GOT-relative accesses. * config/s390/s390.md ("call"): Access local functions and PLT stubs @@ -21,7 +64,7 @@ ("call_value"): Likewise. ("call_value_tls"): Likewise. - * config/s390/s390.c (s390_chunkify_start): Remove pool anchor + * config/s390/s390.c (s390_chunkify_start): Remove pool anchor reloading. Support LTREL_BASE / LTREL_OFFSET construct. (s390_chunkify_finish): Likewise. (s390_chunkify_cancel): Likewise. @@ -40,12 +83,12 @@ * config/s390/s390.c (s390_split_branches): Use LTREL_BASE/OFFSET. (s390_load_got): New function. Use LTREL_BASE/OFFSET. (s390_emit_prologue): Use it. - * config/s390/s390.md ("builtin_longjmp", "builtin_setjmp_setup", - "builtin_setjmp_receiver"): Cleanup. Use s390_load_got. Do not + * config/s390/s390.md ("builtin_longjmp", "builtin_setjmp_setup", + "builtin_setjmp_receiver"): Cleanup. Use s390_load_got. Do not hard-code register 14. * config/s390/s390-protos.h (s390_load_got): Declare. - * config/s390/s390.c (NR_C_MODES, constant_modes, gen_consttable): + * config/s390/s390.c (NR_C_MODES, constant_modes, gen_consttable): Support TImode constants. * config/s390/s390.md ("consttable_ti"): New. ("consttable_si", "consttable_di"): Handle TLS symbols correctly. @@ -61,7 +104,7 @@ "pool_start_64", "pool_end_64", "reload_base_31", "reload_base_64", "pool", "literal_pool_31", "literal_pool_64"): Cleanup. Use symbolic UNSPEC values. - * config/s390/s390.c (larl_operand, s390_short_displacement, + * config/s390/s390.c (larl_operand, s390_short_displacement, bras_sym_operand, s390_cannot_force_const_mem, s390_delegitimize_address, s390_decompose_address, legitimize_pic_address, s390_output_symbolic_const, @@ -163,7 +206,7 @@ 2003-07-18 Kazu Hirata <kazu@cs.umass.edu> - * combine.c (simplify_comparison): Don't share rtx when converting + * combine.c (simplify_comparison): Don't share rtx when converting (ne (and (not X) 1) 0) to (eq (and X 1) 0). 2003-07-18 David Edelsohn <edelsohn@gnu.org> diff --git a/gcc/c-decl.c b/gcc/c-decl.c index bd3b76140cbcbca72c5539c0ec33cd141ebb4818..990b4efbf389ec6c68dafe78c0f2b578b154ee56 100644 --- a/gcc/c-decl.c +++ b/gcc/c-decl.c @@ -115,16 +115,6 @@ static GTY(()) struct stmt_tree_s c_stmt_tree; static GTY(()) tree c_scope_stmt_stack; -/* A list (chain of TREE_LIST nodes) of all LABEL_DECLs in the function - that have names. Here so we can clear out their names' definitions - at the end of the function. */ - -static GTY(()) tree named_labels; - -/* A list of LABEL_DECLs from outer contexts that are currently shadowed. */ - -static GTY(()) tree shadowed_labels; - /* A list of external DECLs that appeared at block scope when there was some other global meaning for that identifier. */ static GTY(()) tree truly_local_externals; @@ -206,23 +196,26 @@ struct binding_level GTY(()) that were entered and exited one level down. */ tree blocks; - /* The binding level which this one is contained in (inherits from). */ - struct binding_level *level_chain; + /* The scope containing this one. */ + struct binding_level *outer; - /* Nonzero if we are currently filling this level with parameter + /* The next outermost function scope. */ + struct binding_level *outer_function; + + /* True if we are currently filling this level with parameter declarations. */ - char parm_flag; + bool parm_flag : 1; - /* Nonzero if this is the outermost block scope of a function body. + /* True if this is the outermost block scope of a function body. This scope contains both the parameters and the local variables declared in the outermost block. */ - char function_body; + bool function_body : 1; - /* Nonzero means make a BLOCK for this level regardless of all else. */ - char keep; + /* True means make a BLOCK for this level regardless of all else. */ + bool keep : 1; - /* Nonzero means make a BLOCK if this level has any subblocks. */ - char keep_if_subblocks; + /* True means make a BLOCK if this level has any subblocks. */ + bool keep_if_subblocks : 1; /* List of decls in `names' that have incomplete structure or union types. */ @@ -244,28 +237,24 @@ static GTY(()) struct binding_level *current_binding_level; static GTY((deletable (""))) struct binding_level *free_binding_level; +/* The innermost function scope. Ordinary (not explicitly declared) + labels, bindings to error_mark_node, and the lazily-created + bindings of __func__ and its friends get this scope. */ +static GTY(()) struct binding_level *current_function_level; + /* The outermost binding level, for names of file scope. This is created when the compiler is started and exists through the entire run. */ static GTY(()) struct binding_level *global_binding_level; -/* Nonzero means unconditionally make a BLOCK for the next level pushed. */ - -static int keep_next_level_flag; - -/* Nonzero means make a BLOCK for the next level pushed - if it has subblocks. */ +/* True means unconditionally make a BLOCK for the next level pushed. */ -static int keep_next_if_subblocks; +static bool keep_next_level_flag; -/* The chain of outer levels of label scopes. - This uses the same data structure used for binding levels, - but it works differently: each link in the chain records - saved values of named_labels and shadowed_labels for - a label binding level outside the current one. */ +/* True means make a BLOCK for the next level pushed if it has subblocks. */ -static GTY(()) struct binding_level *label_level_chain; +static bool keep_next_if_subblocks; /* Functions called automatically at the beginning and end of execution. */ @@ -274,9 +263,11 @@ tree static_ctors, static_dtors; /* Forward declarations. */ static struct binding_level *make_binding_level (void); -static void pop_binding_level (struct binding_level **); +static void pop_binding_level (void); static int duplicate_decls (tree, tree, int, int); static int redeclaration_error_message (tree, tree); +static tree make_label (tree, location_t); +static void bind_label (tree, tree, struct binding_level *); static void implicit_decl_warning (tree); static void storedecls (tree); static void storetags (tree); @@ -356,8 +347,7 @@ make_binding_level (void) if (free_binding_level) { result = free_binding_level; - free_binding_level = result->level_chain; - memset (result, 0, sizeof(struct binding_level)); + free_binding_level = result->outer; } else result = ggc_alloc_cleared (sizeof (struct binding_level)); @@ -365,17 +355,21 @@ make_binding_level (void) return result; } -/* Remove a binding level from a list and add it to the level chain. */ +/* Remove the topmost binding level from the stack and add it to the + free list, updating current_function_level if necessary. */ static void -pop_binding_level (struct binding_level **lp) +pop_binding_level (void) { - struct binding_level *l = *lp; - *lp = l->level_chain; + struct binding_level *scope = current_binding_level; + + current_binding_level = scope->outer; + if (scope->function_body) + current_function_level = scope->outer_function; - memset (l, 0, sizeof (struct binding_level)); - l->level_chain = free_binding_level; - free_binding_level = l; + memset (scope, 0, sizeof (struct binding_level)); + scope->outer = free_binding_level; + free_binding_level = scope; } /* Nonzero if we are currently in the global binding level. */ @@ -389,7 +383,7 @@ global_bindings_p (void) void keep_next_level (void) { - keep_next_level_flag = 1; + keep_next_level_flag = true; } /* Identify this binding level as a level of parameters. */ @@ -397,7 +391,7 @@ keep_next_level (void) void declare_parm_level (void) { - current_binding_level->parm_flag = 1; + current_binding_level->parm_flag = true; } /* Nonzero if currently making parm declarations. */ @@ -413,12 +407,6 @@ in_parm_level_p (void) void pushlevel (int dummy ATTRIBUTE_UNUSED) { - /* If this is the top level of a function, make sure that - NAMED_LABELS is 0. */ - - if (current_binding_level == global_binding_level) - named_labels = 0; - if (keep_next_if_subblocks) { /* This is the transition from the parameters to the top level @@ -429,22 +417,24 @@ pushlevel (int dummy ATTRIBUTE_UNUSED) store_parm_decls, which in turn is called when and only when we are about to encounter the opening curly brace for the function body. */ - current_binding_level->parm_flag = 0; - current_binding_level->function_body = 1; - current_binding_level->keep |= keep_next_level_flag; - current_binding_level->keep_if_subblocks = 1; - - keep_next_level_flag = 0; - keep_next_if_subblocks = 0; + current_binding_level->parm_flag = false; + current_binding_level->function_body = true; + current_binding_level->keep |= keep_next_level_flag; + current_binding_level->keep_if_subblocks = true; + current_binding_level->outer_function = current_function_level; + current_function_level = current_binding_level; + + keep_next_level_flag = false; + keep_next_if_subblocks = false; } else { struct binding_level *newlevel = make_binding_level (); - newlevel->keep = keep_next_level_flag; - newlevel->level_chain = current_binding_level; + newlevel->keep = keep_next_level_flag; + newlevel->outer = current_binding_level; current_binding_level = newlevel; - keep_next_level_flag = 0; + keep_next_level_flag = false; } } @@ -496,7 +486,27 @@ poplevel (int keep, int reverse, int functionbody) containing functions. */ for (link = decls; link; link = TREE_CHAIN (link)) { - if (DECL_NAME (link) != 0) + if (TREE_CODE (link) == LABEL_DECL) + { + if (TREE_USED (link) && DECL_INITIAL (link) == 0) + { + error ("%Hlabel `%D' used but not defined", + &DECL_SOURCE_LOCATION (link), link); + /* Avoid crashing later. */ + DECL_INITIAL (link) = error_mark_node; + } + else if (!TREE_USED (link) && warn_unused_label) + { + if (DECL_INITIAL (link) != 0) + warning ("%Hlabel `%D' defined but not used", + &DECL_SOURCE_LOCATION (link), link); + else + warning ("%Hlabel `%D' declared but not defined", + &DECL_SOURCE_LOCATION (link), link); + } + IDENTIFIER_LABEL_VALUE (DECL_NAME (link)) = 0; + } + else if (DECL_NAME (link) != 0) { if (DECL_EXTERNAL (link) && current_binding_level != global_binding_level) @@ -521,11 +531,14 @@ poplevel (int keep, int reverse, int functionbody) if (TREE_PURPOSE (link)) IDENTIFIER_TAG_VALUE (TREE_PURPOSE (link)) = 0; - /* Restore all name-meanings of the outer levels + /* Restore all name- and label-meanings of the outer levels that were shadowed by this level. */ for (link = current_binding_level->shadowed; link; link = TREE_CHAIN (link)) - IDENTIFIER_SYMBOL_VALUE (TREE_PURPOSE (link)) = TREE_VALUE (link); + if (TREE_VALUE (link) && TREE_CODE (TREE_VALUE (link)) == LABEL_DECL) + IDENTIFIER_LABEL_VALUE (TREE_PURPOSE (link)) = TREE_VALUE (link); + else + IDENTIFIER_SYMBOL_VALUE (TREE_PURPOSE (link)) = TREE_VALUE (link); /* Restore all tag-meanings of the outer levels that were shadowed by this level. */ @@ -599,38 +612,8 @@ poplevel (int keep, int reverse, int functionbody) for (link = tags; link; link = TREE_CHAIN (link)) TYPE_CONTEXT (TREE_VALUE (link)) = decl; - /* If the level being exited is the top level of a function, check - over all the labels, and clear out the current (function local) - meanings of their names. Then add them to BLOCK_VARS. */ - - if (functionbody) - { - for (link = named_labels; link; link = TREE_CHAIN (link)) - { - tree label = TREE_VALUE (link); - - if (DECL_INITIAL (label) == 0) - { - error ("%Hlabel '%D' used but not defined", - &DECL_SOURCE_LOCATION (label), label); - /* Avoid crashing later. */ - define_label (input_location, DECL_NAME (label)); - } - else if (warn_unused_label && !TREE_USED (label)) - warning ("%Hlabel '%D' defined but not used", - &DECL_SOURCE_LOCATION (label), label); - IDENTIFIER_LABEL_VALUE (DECL_NAME (label)) = 0; - - /* Put the labels into the "variables" of the - top-level block, so debugger can see them. */ - TREE_CHAIN (label) = BLOCK_VARS (block); - BLOCK_VARS (block) = label; - } - } - /* Pop the current level, and free the structure for reuse. */ - - pop_binding_level (¤t_binding_level); + pop_binding_level (); /* Dispose of the block that we just made inside some higher level. */ if (functionbody) @@ -671,77 +654,6 @@ set_block (tree block ATTRIBUTE_UNUSED) { } -void -push_label_level (void) -{ - struct binding_level *newlevel; - - newlevel = make_binding_level (); - - /* Add this level to the front of the chain (stack) of label levels. */ - - newlevel->level_chain = label_level_chain; - label_level_chain = newlevel; - - newlevel->names = named_labels; - newlevel->shadowed = shadowed_labels; - named_labels = 0; - shadowed_labels = 0; -} - -void -pop_label_level (void) -{ - struct binding_level *level = label_level_chain; - tree link, prev; - - /* Clear out the definitions of the declared labels in this level. - Leave in the list any ordinary, non-declared labels. */ - for (link = named_labels, prev = 0; link;) - { - if (C_DECLARED_LABEL_FLAG (TREE_VALUE (link))) - { - if (DECL_SOURCE_LINE (TREE_VALUE (link)) == 0) - { - error ("%Hlabel '%D' used but not defined", - &DECL_SOURCE_LOCATION (TREE_VALUE (link)), - TREE_VALUE (link)); - /* Avoid crashing later. */ - define_label (input_location, DECL_NAME (TREE_VALUE (link))); - } - else if (warn_unused_label && !TREE_USED (TREE_VALUE (link))) - warning ("%Hlabel '%D' defined but not used", - &DECL_SOURCE_LOCATION (TREE_VALUE (link)), - TREE_VALUE (link)); - IDENTIFIER_LABEL_VALUE (DECL_NAME (TREE_VALUE (link))) = 0; - - /* Delete this element from the list. */ - link = TREE_CHAIN (link); - if (prev) - TREE_CHAIN (prev) = link; - else - named_labels = link; - } - else - { - prev = link; - link = TREE_CHAIN (link); - } - } - - /* Bring back all the labels that were shadowed. */ - for (link = shadowed_labels; link; link = TREE_CHAIN (link)) - if (DECL_NAME (TREE_VALUE (link)) != 0) - IDENTIFIER_LABEL_VALUE (DECL_NAME (TREE_VALUE (link))) - = TREE_VALUE (link); - - named_labels = chainon (named_labels, level->names); - shadowed_labels = level->shadowed; - - /* Pop the current level, and free the structure for reuse. */ - pop_binding_level (&label_level_chain); -} - /* Push a definition or a declaration of struct, union or enum tag "name". "type" should be the type node. We assume that the tag "name" is not already defined. @@ -1631,7 +1543,7 @@ warn_if_shadowing (tree x, tree old) declarator in a declaration, as opposed to a definition, but there is no way to tell it's not a definition. */ || (TREE_CODE (x) == PARM_DECL - && current_binding_level->level_chain->parm_flag)) + && current_binding_level->outer->parm_flag)) return; name = IDENTIFIER_POINTER (DECL_NAME (x)); @@ -1864,13 +1776,7 @@ pushdecl_top_level (tree x) static void pushdecl_function_level (tree x, tree name) { - struct binding_level *scope; - - scope = current_binding_level; - while (scope->function_body == 0) - scope = scope->level_chain; - if (!scope) - abort (); + struct binding_level *scope = current_function_level; if (x == error_mark_node) scope->shadowed = tree_cons (name, IDENTIFIER_SYMBOL_VALUE (name), @@ -2051,84 +1957,110 @@ undeclared_variable (tree id) } } -/* Get the LABEL_DECL corresponding to identifier ID as a label. +/* Subroutine of lookup_label, declare_label, define_label: construct a + LABEL_DECL with all the proper frills. */ + +static tree +make_label (tree name, location_t location) +{ + tree label = build_decl (LABEL_DECL, name, void_type_node); + + DECL_CONTEXT (label) = current_function_decl; + DECL_MODE (label) = VOIDmode; + DECL_SOURCE_LOCATION (label) = location; + + return label; +} + +/* Another subroutine of lookup_label, declare_label, define_label: + set up the binding of name to LABEL_DECL in the given SCOPE. */ + +static void +bind_label (tree name, tree label, struct binding_level *scope) +{ + if (IDENTIFIER_LABEL_VALUE (name)) + scope->shadowed = tree_cons (name, IDENTIFIER_LABEL_VALUE (name), + scope->shadowed); + IDENTIFIER_LABEL_VALUE (name) = label; + + TREE_CHAIN (label) = scope->names; + scope->names = label; +} + +/* Get the LABEL_DECL corresponding to identifier NAME as a label. Create one if none exists so far for the current function. - This function is called for both label definitions and label references. */ + This is called when a label is used in a goto expression or + has its address taken. */ tree -lookup_label (tree id) +lookup_label (tree name) { - tree decl = IDENTIFIER_LABEL_VALUE (id); + tree label; if (current_function_decl == 0) { error ("label %s referenced outside of any function", - IDENTIFIER_POINTER (id)); + IDENTIFIER_POINTER (name)); return 0; } - /* Use a label already defined or ref'd with this name. */ - if (decl != 0) - { - /* But not if it is inherited and wasn't declared to be inheritable. */ - if (DECL_CONTEXT (decl) != current_function_decl - && ! C_DECLARED_LABEL_FLAG (decl)) - return shadow_label (id); - return decl; + /* Use a label already defined or ref'd with this name, but not if + it is inherited from a containing function and wasn't declared + using __label__. */ + label = IDENTIFIER_LABEL_VALUE (name); + if (label && (DECL_CONTEXT (label) == current_function_decl + || C_DECLARED_LABEL_FLAG (label))) + { + /* If the label has only been declared, update its apparent + location to point here, for better diagnostics if it + turns out not to have been defined. */ + if (!TREE_USED (label)) + DECL_SOURCE_LOCATION (label) = input_location; + return label; } - decl = build_decl (LABEL_DECL, id, void_type_node); - - /* A label not explicitly declared must be local to where it's ref'd. */ - DECL_CONTEXT (decl) = current_function_decl; - - DECL_MODE (decl) = VOIDmode; + /* No label binding for that identifier; make one. */ + label = make_label (name, input_location); - /* Say where one reference is to the label, - for the sake of the error if it is not defined. */ - DECL_SOURCE_LOCATION (decl) = input_location; - - IDENTIFIER_LABEL_VALUE (id) = decl; - - named_labels = tree_cons (NULL_TREE, decl, named_labels); - - return decl; + /* Ordinary labels go in the current function scope, which is + not necessarily the current label scope. */ + bind_label (name, label, current_function_level); + return label; } -/* Make a label named NAME in the current function, - shadowing silently any that may be inherited from containing functions - or containing scopes. +/* Make a label named NAME in the current function, shadowing silently + any that may be inherited from containing functions or containing + scopes. This is called for __label__ declarations. */ - Note that valid use, if the label being shadowed - comes from another scope in the same function, - requires calling declare_nonlocal_label right away. */ +/* Note that valid use, if the label being shadowed comes from another + scope in the same function, requires calling declare_nonlocal_label + right away. (Is this still true? -zw 2003-07-17) */ tree -shadow_label (tree name) +declare_label (tree name) { - tree decl = IDENTIFIER_LABEL_VALUE (name); + tree label = IDENTIFIER_LABEL_VALUE (name); + tree dup; - if (decl != 0) - { - tree dup; + /* Check to make sure that the label hasn't already been declared + at this scope */ + for (dup = current_binding_level->names; dup; dup = TREE_CHAIN (dup)) + if (dup == label) + { + error ("duplicate label declaration `%s'", IDENTIFIER_POINTER (name)); + error ("%Hthis is a previous declaration", + &DECL_SOURCE_LOCATION (dup)); - /* Check to make sure that the label hasn't already been declared - at this label scope */ - for (dup = named_labels; dup; dup = TREE_CHAIN (dup)) - if (TREE_VALUE (dup) == decl) - { - error ("duplicate label declaration '%E'", name); - error ("%Hthis is a previous declaration", - &DECL_SOURCE_LOCATION (TREE_VALUE (dup))); - /* Just use the previous declaration. */ - return lookup_label (name); - } + /* Just use the previous declaration. */ + return dup; + } - shadowed_labels = tree_cons (NULL_TREE, decl, shadowed_labels); - IDENTIFIER_LABEL_VALUE (name) = decl = 0; - } + label = make_label (name, input_location); + C_DECLARED_LABEL_FLAG (label) = 1; - return lookup_label (name); + /* Declared labels go in the current scope. */ + bind_label (name, label, current_binding_level); + return label; } /* Define a label, specifying the location in the source file. @@ -2138,33 +2070,54 @@ shadow_label (tree name) tree define_label (location_t location, tree name) { - tree decl = lookup_label (name); - - /* If label with this name is known from an outer context, shadow it. */ - if (decl != 0 && DECL_CONTEXT (decl) != current_function_decl) - { - shadowed_labels = tree_cons (NULL_TREE, decl, shadowed_labels); - IDENTIFIER_LABEL_VALUE (name) = 0; - decl = lookup_label (name); + tree label; + + /* Find any preexisting label with this name. It is an error + if that label has already been defined in this function, or + if there is a containing function with a declared label with + the same name. */ + label = IDENTIFIER_LABEL_VALUE (name); + + if (label + && ((DECL_CONTEXT (label) == current_function_decl + && DECL_INITIAL (label) != 0) + || (DECL_CONTEXT (label) != current_function_decl + && C_DECLARED_LABEL_FLAG (label)))) + { + error ("%Hduplicate label `%D'", &location, label); + if (DECL_INITIAL (label)) + error ("%H`%D' previously defined here", + &DECL_SOURCE_LOCATION (label), label); + else + error ("%H`%D' previously declared here", + &DECL_SOURCE_LOCATION (label), label); + return 0; } - - if (warn_traditional && !in_system_header && lookup_name (name)) - warning ("%Htraditional C lacks a separate namespace for labels, " - "identifier `%s' conflicts", &location, IDENTIFIER_POINTER (name)); - - if (DECL_INITIAL (decl) != 0) + else if (label && DECL_CONTEXT (label) == current_function_decl) { - error ("%Hduplicate label `%s'", &location, IDENTIFIER_POINTER (name)); - return 0; + /* The label has been used or declared already in this function, + but not defined. Update its location to point to this + definition. */ + DECL_SOURCE_LOCATION (label) = location; } else { - /* Mark label as having been defined. */ - DECL_INITIAL (decl) = error_mark_node; - /* Say where in the source. */ - DECL_SOURCE_LOCATION (decl) = location; - return decl; + /* No label binding for that identifier; make one. */ + label = make_label (name, location); + + /* Ordinary labels go in the current function scope, which is + not necessarily the current label scope. */ + bind_label (name, label, current_function_level); } + + if (warn_traditional && !in_system_header && lookup_name (name)) + warning ("%Htraditional C lacks a separate namespace for labels, " + "identifier `%s' conflicts", &location, + IDENTIFIER_POINTER (name)); + + /* Mark label as having been defined. */ + DECL_INITIAL (label) = error_mark_node; + return label; } /* Return the list of declarations of the current level. @@ -2316,7 +2269,6 @@ c_init_decl_processing (void) c_parse_init (); current_function_decl = NULL; - named_labels = NULL; current_binding_level = NULL_BINDING_LEVEL; free_binding_level = NULL_BINDING_LEVEL; @@ -5571,8 +5523,6 @@ start_function (tree declspecs, tree declarator, tree attributes) current_function_returns_abnormally = 0; warn_about_return_type = 0; current_extern_inline = 0; - named_labels = 0; - shadowed_labels = 0; /* Don't expand any sizes in the return type of the function. */ immediate_size_expand = 0; @@ -6611,8 +6561,6 @@ check_for_loop_decls (void) struct language_function GTY(()) { struct c_language_function base; - tree named_labels; - tree shadowed_labels; int returns_value; int returns_null; int returns_abnormally; @@ -6633,8 +6581,6 @@ c_push_function_context (struct function *f) p->base.x_stmt_tree = c_stmt_tree; p->base.x_scope_stmt_stack = c_scope_stmt_stack; - p->named_labels = named_labels; - p->shadowed_labels = shadowed_labels; p->returns_value = current_function_returns_value; p->returns_null = current_function_returns_null; p->returns_abnormally = current_function_returns_abnormally; @@ -6649,13 +6595,6 @@ void c_pop_function_context (struct function *f) { struct language_function *p = f->language; - tree link; - - /* Bring back all the labels that were shadowed. */ - for (link = shadowed_labels; link; link = TREE_CHAIN (link)) - if (DECL_NAME (TREE_VALUE (link)) != 0) - IDENTIFIER_LABEL_VALUE (DECL_NAME (TREE_VALUE (link))) - = TREE_VALUE (link); if (DECL_SAVED_INSNS (current_function_decl) == 0 && DECL_SAVED_TREE (current_function_decl) == NULL_TREE) @@ -6669,8 +6608,6 @@ c_pop_function_context (struct function *f) c_stmt_tree = p->base.x_stmt_tree; c_scope_stmt_stack = p->base.x_scope_stmt_stack; - named_labels = p->named_labels; - shadowed_labels = p->shadowed_labels; current_function_returns_value = p->returns_value; current_function_returns_null = p->returns_null; current_function_returns_abnormally = p->returns_abnormally; diff --git a/gcc/c-parse.in b/gcc/c-parse.in index a009895951ed1c630e6f690a7e1573f189465c8f..a798ec3dc01b3d8e626aab3f6d75b50b02980635 100644 --- a/gcc/c-parse.in +++ b/gcc/c-parse.in @@ -664,8 +664,6 @@ primary: if (pedantic) pedwarn ("ISO C forbids braced-groups within expressions"); - pop_label_level (); - saved_last_tree = COMPOUND_BODY ($1); RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); last_tree = saved_last_tree; @@ -677,7 +675,6 @@ primary: } | compstmt_primary_start error ')' { - pop_label_level (); last_tree = COMPOUND_BODY ($1); TREE_CHAIN (last_tree) = NULL_TREE; $$ = error_mark_node; @@ -2113,7 +2110,7 @@ label_decl: { tree link; for (link = $2; link; link = TREE_CHAIN (link)) { - tree label = shadow_label (TREE_VALUE (link)); + tree label = declare_label (TREE_VALUE (link)); C_DECLARED_LABEL_FLAG (label) = 1; add_decl_stmt (label); } @@ -2158,7 +2155,6 @@ compstmt_primary_start: there is a way to turn off the entire subtree of blocks that are contained in it. */ keep_next_level (); - push_label_level (); compstmt_count++; $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree)); } diff --git a/gcc/c-tree.h b/gcc/c-tree.h index 876f116f60683d5f42f0ba4eb89756f1fa341949..fb12e7a8d00cd9aa04dab9e822e7b031e7b1fc34 100644 --- a/gcc/c-tree.h +++ b/gcc/c-tree.h @@ -197,6 +197,7 @@ extern void clear_parm_order (void); extern int complete_array_type (tree, tree, int); extern void declare_parm_level (void); extern void undeclared_variable (tree); +extern tree declare_label (tree); extern tree define_label (location_t, tree); extern void finish_decl (tree, tree, tree); extern tree finish_enum (tree, tree, tree); @@ -214,13 +215,10 @@ extern void parmlist_tags_warning (void); extern void pending_xref_error (void); extern void c_push_function_context (struct function *); extern void c_pop_function_context (struct function *); -extern void pop_label_level (void); -extern void push_label_level (void); extern void push_parm_decl (tree); extern tree pushdecl_top_level (tree); extern void pushtag (tree, tree); extern tree set_array_declarator_type (tree, tree, int); -extern tree shadow_label (tree); extern void shadow_tag (tree); extern void shadow_tag_warned (tree, int); extern tree start_enum (tree); diff --git a/gcc/doc/extend.texi b/gcc/doc/extend.texi index b8fefede87116e46c0e9d62e53aae96f5d099a62..6170978b1efce0d6dbb74db9e1c8c50e25b48425 100644 --- a/gcc/doc/extend.texi +++ b/gcc/doc/extend.texi @@ -424,7 +424,7 @@ extensions, accepted by GCC in C89 mode and in C++. @menu * Statement Exprs:: Putting statements and declarations inside expressions. -* Local Labels:: Labels local to a statement-expression. +* Local Labels:: Labels local to a block. * Labels as Values:: Getting pointers to labels, and computed gotos. * Nested Functions:: As in Algol and Pascal, lexical scoping of functions. * Constructing Calls:: Dispatching a call to another function. @@ -577,10 +577,10 @@ bug.) @cindex local labels @cindex macros, local labels -Each statement expression is a scope in which @dfn{local labels} can be -declared. A local label is simply an identifier; you can jump to it -with an ordinary @code{goto} statement, but only from within the -statement expression it belongs to. +GCC allows you to declare @dfn{local labels} in any nested block +scope. A local label is just like an ordinary label, but you can +only reference it (with a @code{goto} statement, or by taking its +address) within the block in which it was declared. A local label declaration looks like this: @@ -595,21 +595,38 @@ or __label__ @var{label1}, @var{label2}, /* @r{@dots{}} */; @end example -Local label declarations must come at the beginning of the statement -expression, right after the @samp{(@{}, before any ordinary -declarations. +Local label declarations must come at the beginning of the block, +before any ordinary declarations or statements. The label declaration defines the label @emph{name}, but does not define the label itself. You must do this in the usual way, with @code{@var{label}:}, within the statements of the statement expression. -The local label feature is useful because statement expressions are -often used in macros. If the macro contains nested loops, a @code{goto} -can be useful for breaking out of them. However, an ordinary label -whose scope is the whole function cannot be used: if the macro can be -expanded several times in one function, the label will be multiply -defined in that function. A local label avoids this problem. For -example: +The local label feature is useful for complex macros. If a macro +contains nested loops, a @code{goto} can be useful for breaking out of +them. However, an ordinary label whose scope is the whole function +cannot be used: if the macro can be expanded several times in one +function, the label will be multiply defined in that function. A +local label avoids this problem. For example: + +@example +#define SEARCH(value, array, target) \ +do @{ \ + __label__ found; \ + typeof (target) _SEARCH_target = (target); \ + typeof (*(array)) *_SEARCH_array = (array); \ + int i, j; \ + int value; \ + for (i = 0; i < max; i++) \ + for (j = 0; j < max; j++) \ + if (_SEARCH_array[i][j] == _SEARCH_target) \ + @{ (value) = i; goto found; @} \ + (value) = -1; \ + found:; \ +@} while (0) +@end example + +This could also be written using a statement-expression: @example #define SEARCH(array, target) \ @@ -629,6 +646,9 @@ example: @}) @end example +Local label declarations also make the labels they declare visible to +nested functions, if there are any. @xref{Nested Functions}, for details. + @node Labels as Values @section Labels as Values @cindex labels as values diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index 68387b2635f3862e052d241013124da6d3a6a6ee..8407b0d9bf24cac45be119bd1a231fd6ba14e070 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,10 +1,17 @@ +2003-07-19 Zack Weinberg <zack@codesourcery.com> + + * gcc.dg/noncompile/label-1.c: New comprehensive test case for + diagnostics of ill-formed constructs involving labels. + * gcc.dg/noncompile/label-lineno-1.c: Add error regexp for + the new 'previously defined here' message. + 2003-07-18 Nathan Sidwell <nathan@codesourcery.com> * g++.dg/parse/non-dependent2.C: New test. 2003-07-18 Andrew Pinski <pinskia@physics.uc.edu> - * g++.dg/init/init-ref4.C: xfail on targets without + * g++.dg/init/init-ref4.C: xfail on targets without weak symbols. 2003-07-17 Jakub Jelinek <jakub@redhat.com> @@ -278,7 +285,7 @@ * g++.dg/opt/emptyunion.C: New testcase. 2003-07-07 Richard Kenner <kenner@vlsi1.ultra.nyu.edu> - Eric Botcazou <ebotcazou@libertysurf.fr> + Eric Botcazou <ebotcazou@libertysurf.fr> * g++.dg/opt/stack1.C: New test. @@ -286,7 +293,7 @@ * g++.old-deja/g++.jason/typeid1.C: Make it a compile test, not a run test. - + PR c++/11431 * g++.dg/expr/static_cast3.C: New test. diff --git a/gcc/testsuite/gcc.dg/noncompile/label-1.c b/gcc/testsuite/gcc.dg/noncompile/label-1.c new file mode 100644 index 0000000000000000000000000000000000000000..c646b48fb8d4f2d0b9fef6db0ce665aad9eb0797 --- /dev/null +++ b/gcc/testsuite/gcc.dg/noncompile/label-1.c @@ -0,0 +1,175 @@ +/* Test various diagnostics of ill-formed constructs involving labels. */ +/* { dg-do compile } */ +/* { dg-options "-Wunused" } */ + +extern void dummy(void); + +/* labels must be defined */ +void a(void) +{ + goto l; /* { dg-error "used but not defined" "no label" } */ +} + +/* warnings for labels defined but not used, or declared but not defined */ +void b(void) +{ + __label__ l; + l: /* { dg-warning "defined but not used" "no goto 1" } */ + m: /* { dg-warning "defined but not used" "no goto 2" } */ + dummy(); +} + +void c(void) +{ + __label__ l; /* { dg-warning "declared but not defined" "only __label__" } */ + dummy(); +} + +/* can't have two labels with the same name in the same function */ +void d(void) +{ + l: dummy(); /* { dg-error "previously defined" "prev def same scope" } */ + l: dummy(); /* { dg-error "duplicate label" "dup label same scope" } */ + goto l; +} + +/* even at different scopes */ +void e(void) +{ + l: dummy(); /* { dg-error "previously defined" "prev def diff scope" } */ + { + l: dummy(); /* { dg-error "duplicate label" "dup label diff scope" } */ + } + goto l; +} + +/* but, with __label__, you can */ +void f(void) +{ + l: dummy(); + { + __label__ l; + l: dummy(); /* { dg-warning "defined but not used" "unused shadow 1" } */ + }; + goto l; /* this reaches the outer l */ +} + +/* a __label__ is not visible outside its scope */ +void g(void) +{ + dummy(); + { + __label__ l; + l: dummy(); + goto l; + } + goto l; /* { dg-error "used but not defined" "label ref out of scope" } */ +} + +/* __label__ can appear at top level of a function, too... + ... but doesn't provide a definition of the label */ +void h(void) +{ + __label__ l; + dummy (); + + goto l; /* { dg-error "used but not defined" "used, only __label__" } */ +} + +/* A nested function may not goto a label outside itself */ +void i(void) +{ + auto void nest(void); + + l: nest(); + + void nest(void) + { + goto l; /* { dg-error "used but not defined" "nest use outer label" } */ + } + + goto l; /* reaches the outer l */ +} + +/* which means that a nested function may have its own label with the + same name as the outer function */ +void j(void) +{ + auto void nest(void); + + l: nest(); + + void nest(void) + { + l: dummy(); /* { dg-warning "defined but not used" "nest label same name" } */ + } + + goto l; /* reaches the outer l */ +} + +/* and, turnabout, an outer function may not goto a label in a nested + function */ +void k(void) +{ + void nest(void) + { + l: dummy(); /* { dg-warning "defined but not used" "outer use nest label" } */ + } + + goto l; /* { dg-error "used but not defined" "outer use nest label" } */ + nest(); +} + +/* not even with __label__ */ +void l(void) +{ + void nest(void) + { + __label__ l; + l: dummy(); /* { dg-warning "defined but not used" "outer use nest __label__" } */ + } + + goto l; /* { dg-error "used but not defined" "outer use nest __label__" } */ + nest(); +} + + +/* but if the outer label is declared with __label__, then a nested + function can goto that label (accomplishing a longjmp) */ +void m(void) +{ + __label__ l; + void nest(void) { goto l; } + nest(); + dummy(); + l:; +} + +/* and that means the nested function cannot have its own label with + the same name as an outer label declared with __label__ */ + +void n(void) +{ + __label__ l; /* { dg-error "previously declared" "outer label decl" } */ + void nest(void) + { + l: goto l; /* { dg-error "duplicate label" "inner label defn" } */ + } + + l: + nest(); +} + +/* unless the nested function uses __label__ too! */ +void o(void) +{ + __label__ l; + void nest(void) + { + __label__ l; + l: goto l; + } + + l: goto l; + nest(); +} diff --git a/gcc/testsuite/gcc.dg/noncompile/label-lineno-1.c b/gcc/testsuite/gcc.dg/noncompile/label-lineno-1.c index 28a2aeafca45fe7df693b9de027e77af52d7a769..0c5599434f8bd51cfb7e6aada26aa69fd940431d 100644 --- a/gcc/testsuite/gcc.dg/noncompile/label-lineno-1.c +++ b/gcc/testsuite/gcc.dg/noncompile/label-lineno-1.c @@ -4,7 +4,7 @@ void foo(int i) { - my_label: + my_label: /* { dg-error "previously defined" "prev label" } */ i++;