diff --git a/gcc/c-family/c-common.def b/gcc/c-family/c-common.def index 5de96e5d4a894e5d729c9261bfc4579388062227..dc49ad09e2f34760402057d6cb3e27bec1c0b9bb 100644 --- a/gcc/c-family/c-common.def +++ b/gcc/c-family/c-common.def @@ -58,28 +58,31 @@ DEFTREECODE (SIZEOF_EXPR, "sizeof_expr", tcc_expression, 1) DEFTREECODE (PAREN_SIZEOF_EXPR, "paren_sizeof_expr", tcc_expression, 1) /* Used to represent a `for' statement. The operands are - FOR_INIT_STMT, FOR_COND, FOR_EXPR, FOR_BODY, and FOR_SCOPE, + FOR_INIT_STMT, FOR_COND, FOR_EXPR, FOR_BODY, FOR_SCOPE, and FOR_NAME respectively. */ -DEFTREECODE (FOR_STMT, "for_stmt", tcc_statement, 5) +DEFTREECODE (FOR_STMT, "for_stmt", tcc_statement, 6) -/* Used to represent a 'while' statement. The operands are WHILE_COND - and WHILE_BODY, respectively. */ -DEFTREECODE (WHILE_STMT, "while_stmt", tcc_statement, 2) +/* Used to represent a 'while' statement. The operands are WHILE_COND, + WHILE_BODY, and WHILE_NAME, respectively. */ +DEFTREECODE (WHILE_STMT, "while_stmt", tcc_statement, 3) -/* Used to represent a 'do' statement. The operands are DO_COND and - DO_BODY, respectively. */ -DEFTREECODE (DO_STMT, "do_stmt", tcc_statement, 2) +/* Used to represent a 'do' statement. The operands are DO_COND, DO_BODY, + and DO_NAME, respectively. */ +DEFTREECODE (DO_STMT, "do_stmt", tcc_statement, 3) -/* Used to represent a 'break' statement. */ -DEFTREECODE (BREAK_STMT, "break_stmt", tcc_statement, 0) +/* Used to represent a 'break' statement. The operand BREAK_NAME is + the {FOR,WHILE,DO,SWITCH}_NAME to which it applies. NULL_TREE means + innermost. */ +DEFTREECODE (BREAK_STMT, "break_stmt", tcc_statement, 1) -/* Used to represent a 'continue' statement. */ -DEFTREECODE (CONTINUE_STMT, "continue_stmt", tcc_statement, 0) +/* Used to represent a 'continue' statement. The operand CONTINUE_NAME is + the {FOR,WHILE,DO}_STMT to which it applies. NULL_TREE means innermost. */ +DEFTREECODE (CONTINUE_STMT, "continue_stmt", tcc_statement, 1) /* Used to represent a 'switch' statement. The operands are - SWITCH_STMT_COND, SWITCH_STMT_BODY, SWITCH_STMT_TYPE, and - SWITCH_STMT_SCOPE, respectively. */ -DEFTREECODE (SWITCH_STMT, "switch_stmt", tcc_statement, 4) + SWITCH_STMT_COND, SWITCH_STMT_BODY, SWITCH_STMT_TYPE, SWITCH_STMT_SCOPE, + and SWITCH_STMT_NAME, respectively. */ +DEFTREECODE (SWITCH_STMT, "switch_stmt", tcc_statement, 5) /* Extensions for C++ Concepts. */ diff --git a/gcc/c-family/c-common.h b/gcc/c-family/c-common.h index 027f077d51bc5dbea813a364d04c89d59e7b03e9..0f50866c2545a0a630d227b9d837083d207eceee 100644 --- a/gcc/c-family/c-common.h +++ b/gcc/c-family/c-common.h @@ -1216,9 +1216,13 @@ extern const char *c_get_substring_location (const substring_loc &substr_loc, location_t *out_loc); /* In c-gimplify.cc. */ +typedef hash_map<tree, tree_pair, + simple_hashmap_traits<tree_decl_hash, + tree_pair>> bc_hash_map_t; typedef struct bc_state { tree bc_label[2]; + bc_hash_map_t *bc_hash_map; } bc_state_t; extern void save_bc_state (bc_state_t *); extern void restore_bc_state (bc_state_t *); @@ -1501,29 +1505,39 @@ extern tree build_userdef_literal (tree suffix_id, tree value, tree num_string); -/* WHILE_STMT accessors. These give access to the condition of the - while statement and the body of the while statement, respectively. */ +/* WHILE_STMT accessors. These give access to the condition of the + while statement, the body and name of the while statement, respectively. */ #define WHILE_COND(NODE) TREE_OPERAND (WHILE_STMT_CHECK (NODE), 0) #define WHILE_BODY(NODE) TREE_OPERAND (WHILE_STMT_CHECK (NODE), 1) +#define WHILE_NAME(NODE) TREE_OPERAND (WHILE_STMT_CHECK (NODE), 2) -/* DO_STMT accessors. These give access to the condition of the do - statement and the body of the do statement, respectively. */ +/* DO_STMT accessors. These give access to the condition of the do + statement, the body and name of the do statement, respectively. */ #define DO_COND(NODE) TREE_OPERAND (DO_STMT_CHECK (NODE), 0) #define DO_BODY(NODE) TREE_OPERAND (DO_STMT_CHECK (NODE), 1) +#define DO_NAME(NODE) TREE_OPERAND (DO_STMT_CHECK (NODE), 2) -/* FOR_STMT accessors. These give access to the init statement, - condition, update expression, and body of the for statement, +/* FOR_STMT accessors. These give access to the init statement, + condition, update expression, body and name of the for statement, respectively. */ #define FOR_INIT_STMT(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 0) #define FOR_COND(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 1) #define FOR_EXPR(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 2) #define FOR_BODY(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 3) #define FOR_SCOPE(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 4) +#define FOR_NAME(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 5) + +/* BREAK_STMT accessors. */ +#define BREAK_NAME(NODE) TREE_OPERAND (BREAK_STMT_CHECK (NODE), 0) + +/* CONTINUE_STMT accessors. */ +#define CONTINUE_NAME(NODE) TREE_OPERAND (CONTINUE_STMT_CHECK (NODE), 0) #define SWITCH_STMT_COND(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 0) #define SWITCH_STMT_BODY(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 1) #define SWITCH_STMT_TYPE(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 2) #define SWITCH_STMT_SCOPE(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 3) +#define SWITCH_STMT_NAME(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 4) /* True if there are case labels for all possible values of switch cond, either because there is a default: case label or because the case label ranges cover all values. */ diff --git a/gcc/c-family/c-gimplify.cc b/gcc/c-family/c-gimplify.cc index 3e29766e092e30c29e16c7f23d0b1f02a704896a..09ea1b79159070e2323544c2d8482589a0447b18 100644 --- a/gcc/c-family/c-gimplify.cc +++ b/gcc/c-family/c-gimplify.cc @@ -133,6 +133,10 @@ enum bc_t { bc_break = 0, bc_continue = 1 }; linked through TREE_CHAIN. */ static tree bc_label[2]; +/* Hash map from loop/switch names (identified by LABEL_DECL) to + corresponding break and (if any) continue labels. */ +static bc_hash_map_t *bc_hash_map; + /* Begin a scope which can be exited by a break or continue statement. BC indicates which. @@ -172,6 +176,26 @@ finish_bc_block (tree *block, enum bc_t bc, tree label) DECL_CHAIN (label) = NULL_TREE; } +/* For named loop or switch with NAME, remember corresponding break + label BLAB and continue label CLAB. */ + +static void +note_named_bc (tree name, tree blab, tree clab) +{ + if (bc_hash_map == NULL) + bc_hash_map = new bc_hash_map_t (32); + bc_hash_map->put (name, std::make_pair (blab, clab)); +} + +/* Remove NAME from the map after processing body of the loop or + switch. */ + +static void +release_named_bc (tree name) +{ + bc_hash_map->remove (name); +} + /* Allow saving and restoring break/continue state. */ void @@ -179,8 +203,10 @@ save_bc_state (bc_state_t *state) { state->bc_label[bc_break] = bc_label[bc_break]; state->bc_label[bc_continue] = bc_label[bc_continue]; + state->bc_hash_map = bc_hash_map; bc_label[bc_break] = NULL_TREE; bc_label[bc_continue] = NULL_TREE; + bc_hash_map = NULL; } void @@ -188,8 +214,10 @@ restore_bc_state (bc_state_t *state) { gcc_assert (bc_label[bc_break] == NULL); gcc_assert (bc_label[bc_continue] == NULL); + gcc_assert (bc_hash_map == NULL); bc_label[bc_break] = state->bc_label[bc_break]; bc_label[bc_continue] = state->bc_label[bc_continue]; + bc_hash_map = state->bc_hash_map; } /* Get the LABEL_EXPR to represent a break or continue statement @@ -229,8 +257,9 @@ expr_loc_or_loc (const_tree expr, location_t or_loc) static void genericize_c_loop (tree *stmt_p, location_t start_locus, tree cond, tree body, - tree incr, bool cond_is_first, int *walk_subtrees, - void *data, walk_tree_fn func, walk_tree_lh lh) + tree incr, tree name, bool cond_is_first, + int *walk_subtrees, void *data, walk_tree_fn func, + walk_tree_lh lh) { tree blab, clab; tree entry = NULL, exit = NULL, t; @@ -245,10 +274,15 @@ genericize_c_loop (tree *stmt_p, location_t start_locus, tree cond, tree body, blab = begin_bc_block (bc_break, start_locus); clab = begin_bc_block (bc_continue, start_locus); + if (name) + note_named_bc (name, blab, clab); walk_tree_1 (&body, func, data, NULL, lh); *walk_subtrees = 0; + if (name) + release_named_bc (name); + /* If condition is zero don't generate a loop construct. */ if (cond && integer_zerop (cond)) { @@ -373,8 +407,8 @@ genericize_for_stmt (tree *stmt_p, int *walk_subtrees, void *data, } genericize_c_loop (&loop, EXPR_LOCATION (stmt), FOR_COND (stmt), - FOR_BODY (stmt), FOR_EXPR (stmt), 1, walk_subtrees, - data, func, lh); + FOR_BODY (stmt), FOR_EXPR (stmt), FOR_NAME (stmt), 1, + walk_subtrees, data, func, lh); append_to_statement_list (loop, &expr); if (expr == NULL_TREE) expr = loop; @@ -389,8 +423,8 @@ genericize_while_stmt (tree *stmt_p, int *walk_subtrees, void *data, { tree stmt = *stmt_p; genericize_c_loop (stmt_p, EXPR_LOCATION (stmt), WHILE_COND (stmt), - WHILE_BODY (stmt), NULL_TREE, 1, walk_subtrees, - data, func, lh); + WHILE_BODY (stmt), NULL_TREE, WHILE_NAME (stmt), 1, + walk_subtrees, data, func, lh); } /* Genericize a DO_STMT node *STMT_P. */ @@ -401,8 +435,8 @@ genericize_do_stmt (tree *stmt_p, int *walk_subtrees, void *data, { tree stmt = *stmt_p; genericize_c_loop (stmt_p, EXPR_LOCATION (stmt), DO_COND (stmt), - DO_BODY (stmt), NULL_TREE, 0, walk_subtrees, - data, func, lh); + DO_BODY (stmt), NULL_TREE, DO_NAME (stmt), 0, + walk_subtrees, data, func, lh); } /* Genericize a SWITCH_STMT node *STMT_P by turning it into a SWITCH_EXPR. */ @@ -412,7 +446,7 @@ genericize_switch_stmt (tree *stmt_p, int *walk_subtrees, void *data, walk_tree_fn func, walk_tree_lh lh) { tree stmt = *stmt_p; - tree break_block, body, cond, type; + tree blab, body, cond, type; location_t stmt_locus = EXPR_LOCATION (stmt); body = SWITCH_STMT_BODY (stmt); @@ -423,19 +457,25 @@ genericize_switch_stmt (tree *stmt_p, int *walk_subtrees, void *data, walk_tree_1 (&cond, func, data, NULL, lh); - break_block = begin_bc_block (bc_break, stmt_locus); + blab = begin_bc_block (bc_break, stmt_locus); + if (SWITCH_STMT_NAME (stmt)) + note_named_bc (SWITCH_STMT_NAME (stmt), blab, NULL_TREE); walk_tree_1 (&body, func, data, NULL, lh); + + if (SWITCH_STMT_NAME (stmt)) + release_named_bc (SWITCH_STMT_NAME (stmt)); + walk_tree_1 (&type, func, data, NULL, lh); *walk_subtrees = 0; - if (TREE_USED (break_block)) - SWITCH_BREAK_LABEL_P (break_block) = 1; - finish_bc_block (&body, bc_break, break_block); + if (TREE_USED (blab)) + SWITCH_BREAK_LABEL_P (blab) = 1; + finish_bc_block (&body, bc_break, blab); *stmt_p = build2_loc (stmt_locus, SWITCH_EXPR, type, cond, body); SWITCH_ALL_CASES_P (*stmt_p) = SWITCH_STMT_ALL_CASES_P (stmt); gcc_checking_assert (!SWITCH_STMT_NO_BREAK_P (stmt) - || !TREE_USED (break_block)); + || !TREE_USED (blab)); } /* Genericize a CONTINUE_STMT node *STMT_P. */ @@ -445,7 +485,16 @@ genericize_continue_stmt (tree *stmt_p) { tree stmt_list = NULL; tree pred = build_predict_expr (PRED_CONTINUE, NOT_TAKEN); - tree label = get_bc_label (bc_continue); + tree label; + if (CONTINUE_NAME (*stmt_p)) + { + tree_pair *slot = bc_hash_map->get (CONTINUE_NAME (*stmt_p)); + gcc_checking_assert (slot); + label = slot->second; + TREE_USED (label) = 1; + } + else + label = get_bc_label (bc_continue); location_t location = EXPR_LOCATION (*stmt_p); tree jump = build1_loc (location, GOTO_EXPR, void_type_node, label); append_to_statement_list_force (pred, &stmt_list); @@ -458,7 +507,16 @@ genericize_continue_stmt (tree *stmt_p) static void genericize_break_stmt (tree *stmt_p) { - tree label = get_bc_label (bc_break); + tree label; + if (BREAK_NAME (*stmt_p)) + { + tree_pair *slot = bc_hash_map->get (BREAK_NAME (*stmt_p)); + gcc_checking_assert (slot); + label = slot->first; + TREE_USED (label) = 1; + } + else + label = get_bc_label (bc_break); location_t location = EXPR_LOCATION (*stmt_p); *stmt_p = build1_loc (location, GOTO_EXPR, void_type_node, label); } @@ -615,6 +673,8 @@ c_genericize (tree fndecl) hash_set<tree> pset; walk_tree (&DECL_SAVED_TREE (fndecl), c_genericize_control_r, &pset, &pset); + delete bc_hash_map; + bc_hash_map = NULL; restore_bc_state (&save_state); pop_cfun (); } diff --git a/gcc/c-family/c-pretty-print.cc b/gcc/c-family/c-pretty-print.cc index 0c764aecc3dee2dded70daa69f0d74774d74dabd..13806714446ce365118e4904d3507bd13098bc18 100644 --- a/gcc/c-family/c-pretty-print.cc +++ b/gcc/c-family/c-pretty-print.cc @@ -2943,8 +2943,23 @@ c_pretty_printer::statement (tree t) continue ; return expression(opt) ; */ case BREAK_STMT: + pp_string (this, "break"); + if (BREAK_NAME (t)) + { + pp_space (this); + pp_c_tree_decl_identifier (this, BREAK_NAME (t)); + } + pp_c_semicolon (this); + pp_needs_newline (this) = true; + break; + case CONTINUE_STMT: - pp_string (this, TREE_CODE (t) == BREAK_STMT ? "break" : "continue"); + pp_string (this, "continue"); + if (CONTINUE_NAME (t)) + { + pp_space (this); + pp_c_tree_decl_identifier (this, CONTINUE_NAME (t)); + } pp_c_semicolon (this); pp_needs_newline (this) = true; break; diff --git a/gcc/c/c-decl.cc b/gcc/c/c-decl.cc index 224c015cd6df2698b70a69b1427e195743594089..eec69d42dbcf23cd05610e2f36623ae5c9b07519 100644 --- a/gcc/c/c-decl.cc +++ b/gcc/c/c-decl.cc @@ -162,6 +162,14 @@ vec<c_omp_declare_target_attr, va_gc> *current_omp_declare_target_attribute; #pragma omp begin assumes ... #pragma omp end assumes regions we are in. */ vec<c_omp_begin_assumes_data, va_gc> *current_omp_begin_assumes; + +/* Vector of loop names with C_DECL_LOOP_NAME or C_DECL_SWITCH_NAME marked + LABEL_DECL as the last and canonical for each loop or switch. */ +static vec<tree> loop_names; + +/* Hash table mapping LABEL_DECLs to the canonical LABEL_DECLs if LOOP_NAMES + vector becomes too long. */ +static decl_tree_map *loop_names_hash; /* Each c_binding structure describes one binding of an identifier to a decl. All the decls in a scope - irrespective of namespace - are @@ -694,13 +702,14 @@ add_stmt (tree t) SET_EXPR_LOCATION (t, input_location); } - if (code == LABEL_EXPR || code == CASE_LABEL_EXPR) - STATEMENT_LIST_HAS_LABEL (cur_stmt_list) = 1; - /* Add T to the statement-tree. Non-side-effect statements need to be recorded during statement expressions. */ if (!building_stmt_list_p ()) push_stmt_list (); + + if (code == LABEL_EXPR || code == CASE_LABEL_EXPR) + STATEMENT_LIST_HAS_LABEL (cur_stmt_list) = 1; + append_to_statement_list_force (t, &cur_stmt_list); return t; @@ -11683,6 +11692,10 @@ c_push_function_context (void) c_stmt_tree.x_cur_stmt_list = vec_safe_copy (c_stmt_tree.x_cur_stmt_list); p->x_in_statement = in_statement; p->x_switch_stack = c_switch_stack; + p->loop_names = loop_names; + loop_names = vNULL; + p->loop_names_hash = loop_names_hash; + loop_names_hash = NULL; p->arg_info = current_function_arg_info; p->returns_value = current_function_returns_value; p->returns_null = current_function_returns_null; @@ -11722,6 +11735,12 @@ c_pop_function_context (void) p->base.x_stmt_tree.x_cur_stmt_list = NULL; in_statement = p->x_in_statement; c_switch_stack = p->x_switch_stack; + loop_names.release (); + loop_names = p->loop_names; + p->loop_names = vNULL; + delete loop_names_hash; + loop_names_hash = p->loop_names_hash; + p->loop_names_hash = NULL; current_function_arg_info = p->arg_info; current_function_returns_value = p->returns_value; current_function_returns_null = p->returns_null; @@ -13804,4 +13823,212 @@ c_check_in_current_scope (tree decl) return b != NULL && B_IN_CURRENT_SCOPE (b); } +/* Search for loop or switch names. BEFORE_LABELS is last statement before + possible labels and SWITCH_P true for a switch, false for loops. + Searches through last statements in cur_stmt_list, stops when seeing + BEFORE_LABELs, or statement other than LABEL_EXPR or CASE_LABEL_EXPR. + Returns number of loop/switch names found and if any are found, sets + *LAST_P to the canonical loop/switch name LABEL_DECL. */ + +int +c_get_loop_names (tree before_labels, bool switch_p, tree *last_p) +{ + *last_p = NULL_TREE; + if (!building_stmt_list_p () + || !STATEMENT_LIST_HAS_LABEL (cur_stmt_list) + || before_labels == void_list_node) + return 0; + + int ret = 0; + tree last = NULL_TREE; + for (tree_stmt_iterator tsi = tsi_last (cur_stmt_list); + !tsi_end_p (tsi); tsi_prev (&tsi)) + { + tree stmt = tsi_stmt (tsi); + if (stmt == before_labels) + break; + else if (TREE_CODE (stmt) == LABEL_EXPR) + { + if (last == NULL_TREE) + last = LABEL_EXPR_LABEL (stmt); + else + { + loop_names.safe_push (LABEL_EXPR_LABEL (stmt)); + ++ret; + } + } + else if (TREE_CODE (stmt) != CASE_LABEL_EXPR) + break; + } + if (last) + { + if (switch_p) + C_DECL_SWITCH_NAME (last) = 1; + else + C_DECL_LOOP_NAME (last) = 1; + loop_names.safe_push (last); + ++ret; + if (loop_names.length () > 16) + { + unsigned int first = 0, i; + tree l, c = NULL_TREE; + if (loop_names_hash == NULL) + loop_names_hash = new decl_tree_map (ret); + else + first = loop_names.length () - ret; + FOR_EACH_VEC_ELT_REVERSE (loop_names, i, l) + { + if (C_DECL_LOOP_NAME (l) || C_DECL_SWITCH_NAME (l)) + c = l; + loop_names_hash->put (l, c); + if (i == first) + break; + } + } + *last_p = last; + } + return ret; +} + +/* Undoes what get_loop_names did when it returned NUM_NAMES. */ + +void +c_release_loop_names (int num_names) +{ + unsigned len = loop_names.length () - num_names; + if (loop_names_hash) + { + if (len <= 16) + { + delete loop_names_hash; + loop_names_hash = NULL; + } + else + { + unsigned int i; + tree l; + FOR_EACH_VEC_ELT_REVERSE (loop_names, i, l) + { + loop_names_hash->remove (l); + if (i == len) + break; + } + } + } + loop_names.truncate (len); +} + +/* Finish processing of break or continue identifier operand. + NAME is the identifier operand of break or continue and + IS_BREAK is true iff it is break stmt. Returns the operand + to use for BREAK_STMT or CONTINUE_STMT, either NULL_TREE or + canonical loop/switch name LABEL_DECL. */ + +tree +c_finish_bc_name (location_t loc, tree name, bool is_break) +{ + tree label = NULL_TREE, lab; + pedwarn_c23 (loc, OPT_Wpedantic, + "ISO C does not support %qs statement with an identifier " + "operand before C2Y", is_break ? "break" : "continue"); + + /* If I_LABEL_DECL is NULL or not from current function, don't waste time + trying to find it among loop_names, it can't be there. */ + if (!loop_names.is_empty () + && current_function_scope + && (lab = I_LABEL_DECL (name)) + && DECL_CONTEXT (lab) == current_function_decl) + { + unsigned int i; + tree l, c = NULL_TREE; + if (loop_names_hash) + { + if (tree *val = loop_names_hash->get (lab)) + label = *val; + } + else + FOR_EACH_VEC_ELT_REVERSE (loop_names, i, l) + { + if (C_DECL_LOOP_NAME (l) || C_DECL_SWITCH_NAME (l)) + c = l; + if (l == lab) + { + label = c; + break; + } + } + if (label) + TREE_USED (lab) = 1; + } + if (label == NULL_TREE) + { + auto_vec<const char *> candidates; + unsigned int i; + tree l, c = NULL_TREE; + FOR_EACH_VEC_ELT_REVERSE (loop_names, i, l) + { + if (C_DECL_LOOP_NAME (l) || C_DECL_SWITCH_NAME (l)) + c = l; + if (is_break || C_DECL_LOOP_NAME (c)) + candidates.safe_push (IDENTIFIER_POINTER (DECL_NAME (l))); + } + const char *hint = find_closest_string (IDENTIFIER_POINTER (name), + &candidates); + if (hint) + { + gcc_rich_location richloc (loc); + richloc.add_fixit_replace (hint); + if (is_break) + error_at (&richloc, "%<break%> statement operand %qE does not " + "refer to a named loop or %<switch%>; " + "did you mean %qs?", name, hint); + else + error_at (&richloc, "%<continue%> statement operand %qE does not " + "refer to a named loop; did you mean %qs?", + name, hint); + } + else if (is_break) + error_at (loc, "%<break%> statement operand %qE does not refer to a " + "named loop or %<switch%>", name); + else + error_at (loc, "%<continue%> statement operand %qE does not refer to " + "a named loop", name); + } + else if (!C_DECL_LOOP_NAME (label) && !is_break) + { + auto_diagnostic_group d; + error_at (loc, "%<continue%> statement operand %qE refers to a named " + "%<switch%>", name); + inform (DECL_SOURCE_LOCATION (label), "%<switch%> name defined here"); + label = NULL_TREE; + } + else if (!C_DECL_LOOP_SWITCH_NAME_VALID (label)) + { + auto_diagnostic_group d; + if (C_DECL_LOOP_NAME (label)) + { + error_at (loc, "%qs statement operand %qE refers to a loop outside " + "of its body", is_break ? "break" : "continue", name); + inform (DECL_SOURCE_LOCATION (label), "loop name defined here"); + } + else + { + error_at (loc, "%<break%> statement operand %qE refers to a " + "%<switch%> outside of its body", name); + inform (DECL_SOURCE_LOCATION (label), + "%<switch%> name defined here"); + } + label = NULL_TREE; + } + else if (label == loop_names.last () && (in_statement & IN_NAMED_STMT) != 0) + /* If it is just a fancy reference to the innermost construct, handle it + just like break; or continue; though tracking cheaply what is the + innermost loop for continue when nested in switches would require + another global variable and updating it. */ + label = NULL_TREE; + else + C_DECL_LOOP_SWITCH_NAME_USED (label) = 1; + return label; +} + #include "gt-c-c-decl.h" diff --git a/gcc/c/c-lang.h b/gcc/c/c-lang.h index e51264495fe39aee39547bead7b3d48ec5c43660..7888ab1548dbb568eac3c09392d9585064edccf2 100644 --- a/gcc/c/c-lang.h +++ b/gcc/c/c-lang.h @@ -54,6 +54,8 @@ struct GTY(()) language_function { unsigned char x_in_statement; struct c_switch * GTY((skip)) x_switch_stack; struct c_arg_info * GTY((skip)) arg_info; + vec<tree> GTY((skip)) loop_names; + decl_tree_map * GTY((skip)) loop_names_hash; int returns_value; int returns_null; int returns_abnormally; diff --git a/gcc/c/c-parser.cc b/gcc/c/c-parser.cc index fe01f955e215042419fbc9edb41cc587e4248ae8..0ffbdc7e01e437f4c4934490ebe81baf1e9dd6db 100644 --- a/gcc/c/c-parser.cc +++ b/gcc/c/c-parser.cc @@ -1670,18 +1670,19 @@ static tree c_parser_compound_statement (c_parser *, location_t * = NULL); static location_t c_parser_compound_statement_nostart (c_parser *); static void c_parser_label (c_parser *, tree); static void c_parser_statement (c_parser *, bool *, location_t * = NULL); -static void c_parser_statement_after_labels (c_parser *, bool *, +static void c_parser_statement_after_labels (c_parser *, bool *, tree, vec<tree> * = NULL, attr_state = {}); static tree c_parser_c99_block_statement (c_parser *, bool *, location_t * = NULL); static void c_parser_if_statement (c_parser *, bool *, vec<tree> *); -static void c_parser_switch_statement (c_parser *, bool *); +static void c_parser_switch_statement (c_parser *, bool *, tree); static void c_parser_while_statement (c_parser *, bool, unsigned short, bool, - bool *); -static void c_parser_do_statement (c_parser *, bool, unsigned short, bool); + bool *, tree); +static void c_parser_do_statement (c_parser *, bool, unsigned short, bool, + tree); static void c_parser_for_statement (c_parser *, bool, unsigned short, bool, - bool *); + bool *, tree); static tree c_parser_asm_statement (c_parser *); static tree c_parser_asm_operands (c_parser *); static tree c_parser_asm_goto_operands (c_parser *); @@ -1735,7 +1736,7 @@ static void c_parser_omp_nothing (c_parser *); enum pragma_context { pragma_external, pragma_struct, pragma_param, pragma_stmt, pragma_compound }; -static bool c_parser_pragma (c_parser *, enum pragma_context, bool *); +static bool c_parser_pragma (c_parser *, enum pragma_context, bool *, tree); static bool c_parser_omp_cancellation_point (c_parser *, enum pragma_context); static bool c_parser_omp_target (c_parser *, enum pragma_context, bool *); static void c_parser_omp_begin (c_parser *); @@ -2038,7 +2039,7 @@ c_parser_external_declaration (c_parser *parser) break; case CPP_PRAGMA: mark_valid_location_for_stdc_pragma (true); - c_parser_pragma (parser, pragma_external, NULL); + c_parser_pragma (parser, pragma_external, NULL, NULL_TREE); mark_valid_location_for_stdc_pragma (false); break; case CPP_PLUS: @@ -2377,7 +2378,7 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok, while (parser->in_omp_attribute_pragma) { gcc_assert (c_parser_next_token_is (parser, CPP_PRAGMA)); - c_parser_pragma (parser, pragma_external, NULL); + c_parser_pragma (parser, pragma_external, NULL, NULL_TREE); } c_parser_consume_token (parser); return; @@ -4071,7 +4072,7 @@ c_parser_struct_or_union_specifier (c_parser *parser) /* Accept #pragmas at struct scope. */ if (c_parser_next_token_is (parser, CPP_PRAGMA)) { - c_parser_pragma (parser, pragma_struct, NULL); + c_parser_pragma (parser, pragma_struct, NULL, NULL_TREE); continue; } /* Parse some comma-separated declarations, but not the @@ -5023,7 +5024,7 @@ c_parser_parameter_declaration (c_parser *parser, tree attrs, /* Accept #pragmas between parameter declarations. */ while (c_parser_next_token_is (parser, CPP_PRAGMA)) - c_parser_pragma (parser, pragma_param, NULL); + c_parser_pragma (parser, pragma_param, NULL, NULL_TREE); if (!c_parser_next_token_starts_declspecs (parser) && !c_parser_nth_token_starts_std_attributes (parser, 1)) @@ -7013,6 +7014,24 @@ c_parser_handle_musttail (c_parser *parser, tree std_attrs, attr_state &attr) return std_attrs; } +/* Return a statement before optional series of LABEL_EXPR/CASE_LABEL_EXPRs. + Instead of collecting vectors of labels before each stmt just in case + the statement would be iteration or switch statement for named loops, + we just remember last emitted statement and let the iteration/switch + statement search backwards in cur_stmt_list until that stmt for loop + names if any. */ + +static tree +get_before_labels () +{ + if (!building_stmt_list_p ()) + return NULL_TREE; + tree_stmt_iterator tsi = tsi_last (cur_stmt_list); + if (tsi_end_p (tsi)) + return NULL_TREE; + return tsi_stmt (tsi); +} + /* Parse a compound statement except for the opening brace. This is used for parsing both compound statements and statement expressions (which follow different paths to handling the opening). */ @@ -7089,6 +7108,7 @@ c_parser_compound_statement_nostart (c_parser *parser) c_parser_consume_token (parser); return endloc; } + tree before_labels = get_before_labels (); while (c_parser_next_token_is_not (parser, CPP_CLOSE_BRACE)) { location_t loc = c_parser_peek_token (parser)->location; @@ -7119,6 +7139,7 @@ c_parser_compound_statement_nostart (c_parser *parser) omp_for_parse_state->depth--; sl = push_stmt_list (); parser->error = false; + before_labels = get_before_labels (); continue; } else if (want_nested_loop @@ -7132,7 +7153,7 @@ c_parser_compound_statement_nostart (c_parser *parser) tree pre_sl = pop_stmt_list (sl); tree nested_sl = push_stmt_list (); mark_valid_location_for_stdc_pragma (false); - c_parser_statement_after_labels (parser, NULL); + c_parser_statement_after_labels (parser, NULL, NULL_TREE); nested_sl = pop_stmt_list (nested_sl); if (omp_for_parse_state->want_nested_loop) { @@ -7151,6 +7172,7 @@ c_parser_compound_statement_nostart (c_parser *parser) sl = push_stmt_list (); } parser->error = false; + before_labels = get_before_labels (); continue; } else if (c_parser_next_token_is (parser, CPP_SEMICOLON)) @@ -7161,6 +7183,7 @@ c_parser_compound_statement_nostart (c_parser *parser) do that, as an extension. */ /* FIXME: Maybe issue a warning or something here? */ c_parser_consume_token (parser); + before_labels = get_before_labels (); continue; } } @@ -7222,6 +7245,7 @@ c_parser_compound_statement_nostart (c_parser *parser) "ISO C90 forbids mixed declarations and code"); last_stmt = fallthru_attr_p; last_label = false; + before_labels = get_before_labels (); } else if (c_parser_next_token_is_keyword (parser, RID_EXTENSION)) { @@ -7263,6 +7287,7 @@ c_parser_compound_statement_nostart (c_parser *parser) pedwarn_c90 (loc, OPT_Wdeclaration_after_statement, "ISO C90 forbids mixed declarations and code"); last_stmt = false; + before_labels = get_before_labels (); } else goto statement; @@ -7282,7 +7307,7 @@ c_parser_compound_statement_nostart (c_parser *parser) omp_for_parse_state->want_nested_loop = false; if (c_parser_pragma (parser, last_label ? pragma_stmt : pragma_compound, - NULL)) + NULL, before_labels)) { last_label = false; last_stmt = true; @@ -7291,6 +7316,7 @@ c_parser_compound_statement_nostart (c_parser *parser) } if (omp_for_parse_state) omp_for_parse_state->want_nested_loop = want_nested_loop; + before_labels = get_before_labels (); } else if (c_parser_next_token_is (parser, CPP_EOF)) { @@ -7310,6 +7336,7 @@ c_parser_compound_statement_nostart (c_parser *parser) { error_at (loc, "%<else%> without a previous %<if%>"); c_parser_consume_token (parser); + before_labels = get_before_labels (); continue; } } @@ -7321,7 +7348,8 @@ c_parser_compound_statement_nostart (c_parser *parser) last_stmt = true; mark_valid_location_for_stdc_pragma (false); if (!omp_for_parse_state) - c_parser_statement_after_labels (parser, NULL, NULL, a); + c_parser_statement_after_labels (parser, NULL, before_labels, + NULL, a); else { /* In canonical loop nest form, nested loops can only appear @@ -7331,9 +7359,10 @@ c_parser_compound_statement_nostart (c_parser *parser) it must be intervening code. */ omp_for_parse_state->want_nested_loop = false; check_omp_intervening_code (parser); - c_parser_statement_after_labels (parser, NULL); + c_parser_statement_after_labels (parser, NULL, before_labels); omp_for_parse_state->want_nested_loop = want_nested_loop; } + before_labels = get_before_labels (); } parser->error = false; @@ -7645,11 +7674,26 @@ c_parser_label (c_parser *parser, tree std_attrs) static void c_parser_statement (c_parser *parser, bool *if_p, location_t *loc_after_labels) { + tree before_labels = get_before_labels (); attr_state a = c_parser_all_labels (parser); if (loc_after_labels) *loc_after_labels = c_parser_peek_token (parser)->location; parser->omp_attrs_forbidden_p = false; - c_parser_statement_after_labels (parser, if_p, NULL, a); + c_parser_statement_after_labels (parser, if_p, before_labels, NULL, a); +} + +/* Parse and handle optional identifier after break or continue keywords. */ + +static tree +c_parser_bc_name (c_parser *parser, bool is_break) +{ + if (!c_parser_next_token_is (parser, CPP_NAME)) + return NULL_TREE; + + c_token *tok = c_parser_peek_token (parser); + tree label = c_finish_bc_name (tok->location, tok->value, is_break); + c_parser_consume_token (parser); + return label; } /* Parse a statement, other than a labeled statement. CHAIN is a vector @@ -7658,10 +7702,14 @@ c_parser_statement (c_parser *parser, bool *if_p, location_t *loc_after_labels) IF_P is used to track whether there's a (possibly labeled) if statement which is not enclosed in braces and has an else clause. This is used to - implement -Wparentheses. ASTATE is an earlier parsed attribute state. */ + implement -Wparentheses. ASTATE is an earlier parsed attribute state. + + BEFORE_LABELS is last statement before possible labels, see + get_before_labels description for details. */ static void c_parser_statement_after_labels (c_parser *parser, bool *if_p, + tree before_labels, vec<tree> *chain, attr_state astate) { location_t loc = c_parser_peek_token (parser)->location; @@ -7687,16 +7735,16 @@ c_parser_statement_after_labels (c_parser *parser, bool *if_p, c_parser_if_statement (parser, if_p, chain); break; case RID_SWITCH: - c_parser_switch_statement (parser, if_p); + c_parser_switch_statement (parser, if_p, before_labels); break; case RID_WHILE: - c_parser_while_statement (parser, false, 0, false, if_p); + c_parser_while_statement (parser, false, 0, false, if_p, before_labels); break; case RID_DO: - c_parser_do_statement (parser, false, 0, false); + c_parser_do_statement (parser, false, 0, false, before_labels); break; case RID_FOR: - c_parser_for_statement (parser, false, 0, false, if_p); + c_parser_for_statement (parser, false, 0, false, if_p, before_labels); break; case RID_GOTO: c_parser_consume_token (parser); @@ -7720,11 +7768,13 @@ c_parser_statement_after_labels (c_parser *parser, bool *if_p, goto expect_semicolon; case RID_CONTINUE: c_parser_consume_token (parser); - stmt = c_finish_bc_stmt (loc, objc_foreach_continue_label, false); + stmt = c_finish_bc_stmt (loc, objc_foreach_continue_label, false, + c_parser_bc_name (parser, false)); goto expect_semicolon; case RID_BREAK: c_parser_consume_token (parser); - stmt = c_finish_bc_stmt (loc, objc_foreach_break_label, true); + stmt = c_finish_bc_stmt (loc, objc_foreach_break_label, true, + c_parser_bc_name (parser, true)); goto expect_semicolon; case RID_RETURN: c_parser_consume_token (parser); @@ -7840,7 +7890,7 @@ c_parser_statement_after_labels (c_parser *parser, bool *if_p, c_parser_consume_token (parser); break; case CPP_PRAGMA: - if (!c_parser_pragma (parser, pragma_stmt, if_p)) + if (!c_parser_pragma (parser, pragma_stmt, if_p, before_labels)) goto restart; break; default: @@ -7935,6 +7985,7 @@ c_parser_if_body (c_parser *parser, bool *if_p, location_t body_loc_after_labels = UNKNOWN_LOCATION; token_indent_info body_tinfo = get_token_indent_info (c_parser_peek_token (parser)); + tree before_labels = get_before_labels (); c_parser_all_labels (parser); if (c_parser_next_token_is (parser, CPP_SEMICOLON)) @@ -7951,7 +8002,7 @@ c_parser_if_body (c_parser *parser, bool *if_p, else { body_loc_after_labels = c_parser_peek_token (parser)->location; - c_parser_statement_after_labels (parser, if_p); + c_parser_statement_after_labels (parser, if_p, before_labels); } token_indent_info next_tinfo @@ -7979,6 +8030,7 @@ c_parser_else_body (c_parser *parser, const token_indent_info &else_tinfo, token_indent_info body_tinfo = get_token_indent_info (c_parser_peek_token (parser)); location_t body_loc_after_labels = UNKNOWN_LOCATION; + tree before_labels = get_before_labels (); c_parser_all_labels (parser); if (c_parser_next_token_is (parser, CPP_SEMICOLON)) @@ -7994,7 +8046,7 @@ c_parser_else_body (c_parser *parser, const token_indent_info &else_tinfo, { if (!c_parser_next_token_is (parser, CPP_OPEN_BRACE)) body_loc_after_labels = c_parser_peek_token (parser)->location; - c_parser_statement_after_labels (parser, NULL, chain); + c_parser_statement_after_labels (parser, NULL, before_labels, chain); } token_indent_info next_tinfo @@ -8134,10 +8186,12 @@ c_parser_if_statement (c_parser *parser, bool *if_p, vec<tree> *chain) switch-statement: switch (expression) statement -*/ + + BEFORE_LABELS is last statement before possible labels, see + get_before_labels description for details. */ static void -c_parser_switch_statement (c_parser *parser, bool *if_p) +c_parser_switch_statement (c_parser *parser, bool *if_p, tree before_labels) { struct c_expr ce; tree block, expr, body; @@ -8146,6 +8200,8 @@ c_parser_switch_statement (c_parser *parser, bool *if_p) location_t switch_cond_loc; gcc_assert (c_parser_next_token_is_keyword (parser, RID_SWITCH)); c_parser_consume_token (parser); + tree switch_name; + int num_names = c_get_loop_names (before_labels, true, &switch_name); block = c_begin_compound_stmt (flag_isoc99); bool explicit_cast_p = false; matching_parens parens; @@ -8167,9 +8223,18 @@ c_parser_switch_statement (c_parser *parser, bool *if_p) expr = error_mark_node; ce.original_type = error_mark_node; } - c_start_switch (switch_loc, switch_cond_loc, expr, explicit_cast_p); + tree stmt + = c_start_switch (switch_loc, switch_cond_loc, expr, explicit_cast_p, + switch_name); save_in_statement = in_statement; in_statement |= IN_SWITCH_STMT; + if (switch_name) + { + C_DECL_LOOP_SWITCH_NAME_VALID (switch_name) = 1; + in_statement |= IN_NAMED_STMT; + } + else + in_statement &= ~IN_NAMED_STMT; location_t loc_after_labels; bool open_brace_p = c_parser_peek_token (parser)->type == CPP_OPEN_BRACE; body = c_parser_c99_block_statement (parser, if_p, &loc_after_labels); @@ -8179,6 +8244,14 @@ c_parser_switch_statement (c_parser *parser, bool *if_p) RID_SWITCH); c_finish_switch (body, ce.original_type); in_statement = save_in_statement; + if (num_names) + { + if (!C_DECL_LOOP_SWITCH_NAME_USED (switch_name)) + SWITCH_STMT_NAME (stmt) = NULL_TREE; + else + SWITCH_STMT_NO_BREAK_P (stmt) = 0; + c_release_loop_names (num_names); + } add_stmt (c_end_compound_stmt (switch_loc, block, flag_isoc99)); c_parser_maybe_reclassify_token (parser); } @@ -8190,11 +8263,14 @@ c_parser_switch_statement (c_parser *parser, bool *if_p) IF_P is used to track whether there's a (possibly labeled) if statement which is not enclosed in braces and has an else clause. This is used to - implement -Wparentheses. */ + implement -Wparentheses. + + BEFORE_LABELS is last statement before possible labels, see + get_before_labels description for details. */ static void c_parser_while_statement (c_parser *parser, bool ivdep, unsigned short unroll, - bool novector, bool *if_p) + bool novector, bool *if_p, tree before_labels) { tree block, cond, body; unsigned char save_in_statement; @@ -8202,6 +8278,8 @@ c_parser_while_statement (c_parser *parser, bool ivdep, unsigned short unroll, gcc_assert (c_parser_next_token_is_keyword (parser, RID_WHILE)); token_indent_info while_tinfo = get_token_indent_info (c_parser_peek_token (parser)); + tree loop_name; + int num_names = c_get_loop_names (before_labels, false, &loop_name); if (parser->omp_for_parse_state) { @@ -8231,6 +8309,11 @@ c_parser_while_statement (c_parser *parser, bool ivdep, unsigned short unroll, integer_zero_node); save_in_statement = in_statement; in_statement = IN_ITERATION_STMT; + if (loop_name) + { + C_DECL_LOOP_SWITCH_NAME_VALID (loop_name) = 1; + in_statement |= IN_NAMED_STMT; + } token_indent_info body_tinfo = get_token_indent_info (c_parser_peek_token (parser)); @@ -8238,9 +8321,13 @@ c_parser_while_statement (c_parser *parser, bool ivdep, unsigned short unroll, location_t loc_after_labels; bool open_brace = c_parser_next_token_is (parser, CPP_OPEN_BRACE); body = c_parser_c99_block_statement (parser, if_p, &loc_after_labels); - add_stmt (build_stmt (loc, WHILE_STMT, cond, body)); + if (loop_name && !C_DECL_LOOP_SWITCH_NAME_USED (loop_name)) + loop_name = NULL_TREE; + add_stmt (build_stmt (loc, WHILE_STMT, cond, body, loop_name)); add_stmt (c_end_compound_stmt (loc, block, flag_isoc99)); c_parser_maybe_reclassify_token (parser); + if (num_names) + c_release_loop_names (num_names); token_indent_info next_tinfo = get_token_indent_info (c_parser_peek_token (parser)); @@ -8257,16 +8344,20 @@ c_parser_while_statement (c_parser *parser, bool ivdep, unsigned short unroll, do-statement: do statement while ( expression ) ; -*/ + + BEFORE_LABELS is last statement before possible labels, see + get_before_labels description for details. */ static void c_parser_do_statement (c_parser *parser, bool ivdep, unsigned short unroll, - bool novector) + bool novector, tree before_labels) { tree block, cond, body; unsigned char save_in_statement; location_t loc; gcc_assert (c_parser_next_token_is_keyword (parser, RID_DO)); + tree loop_name; + int num_names = c_get_loop_names (before_labels, false, &loop_name); if (parser->omp_for_parse_state) { @@ -8284,9 +8375,20 @@ c_parser_do_statement (c_parser *parser, bool ivdep, unsigned short unroll, loc = c_parser_peek_token (parser)->location; save_in_statement = in_statement; in_statement = IN_ITERATION_STMT; + if (loop_name) + { + C_DECL_LOOP_SWITCH_NAME_VALID (loop_name) = 1; + in_statement |= IN_NAMED_STMT; + } body = c_parser_c99_block_statement (parser, NULL); c_parser_require_keyword (parser, RID_WHILE, "expected %<while%>"); in_statement = save_in_statement; + if (num_names) + { + if (!C_DECL_LOOP_SWITCH_NAME_USED (loop_name)) + loop_name = NULL_TREE; + c_release_loop_names (num_names); + } cond = c_parser_paren_condition (parser); if (ivdep && cond != error_mark_node) cond = build3 (ANNOTATE_EXPR, TREE_TYPE (cond), cond, @@ -8306,7 +8408,7 @@ c_parser_do_statement (c_parser *parser, bool ivdep, unsigned short unroll, if (!c_parser_require (parser, CPP_SEMICOLON, "expected %<;%>")) c_parser_skip_to_end_of_block_or_statement (parser); - add_stmt (build_stmt (loc, DO_STMT, cond, body)); + add_stmt (build_stmt (loc, DO_STMT, cond, body, loop_name)); add_stmt (c_end_compound_stmt (loc, block, flag_isoc99)); } @@ -8367,11 +8469,14 @@ c_parser_do_statement (c_parser *parser, bool ivdep, unsigned short unroll, IF_P is used to track whether there's a (possibly labeled) if statement which is not enclosed in braces and has an else clause. This is used to - implement -Wparentheses. */ + implement -Wparentheses. + + BEFORE_LABELS is last statement before possible labels, see + get_before_labels description for details. */ static void c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, - bool novector, bool *if_p) + bool novector, bool *if_p, tree before_labels) { tree block, cond, incr, body; unsigned char save_in_statement; @@ -8386,6 +8491,8 @@ c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, gcc_assert (c_parser_next_token_is_keyword (parser, RID_FOR)); token_indent_info for_tinfo = get_token_indent_info (c_parser_peek_token (parser)); + tree loop_name; + int num_names = c_get_loop_names (before_labels, false, &loop_name); if (parser->omp_for_parse_state) { @@ -8578,9 +8685,22 @@ c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, save_objc_foreach_continue_label = objc_foreach_continue_label; objc_foreach_break_label = create_artificial_label (loc); objc_foreach_continue_label = create_artificial_label (loc); + if (loop_name) + { + gcc_checking_assert (!DECL_CHAIN (loop_name) + && !DECL_CHAIN (objc_foreach_break_label)); + C_DECL_SWITCH_NAME (loop_name) = 1; + DECL_CHAIN (loop_name) = objc_foreach_break_label; + DECL_CHAIN (objc_foreach_break_label) = objc_foreach_continue_label; + } } else in_statement = IN_ITERATION_STMT; + if (loop_name) + { + C_DECL_LOOP_SWITCH_NAME_VALID (loop_name) = 1; + in_statement |= IN_NAMED_STMT; + } token_indent_info body_tinfo = get_token_indent_info (c_parser_peek_token (parser)); @@ -8589,6 +8709,16 @@ c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, bool open_brace = c_parser_next_token_is (parser, CPP_OPEN_BRACE); body = c_parser_c99_block_statement (parser, if_p, &loc_after_labels); + if (loop_name && is_foreach_statement) + { + gcc_checking_assert (DECL_CHAIN (loop_name) == objc_foreach_break_label + && (DECL_CHAIN (objc_foreach_break_label) + == objc_foreach_continue_label)); + C_DECL_SWITCH_NAME (loop_name) = 0; + DECL_CHAIN (loop_name) = NULL_TREE; + DECL_CHAIN (objc_foreach_break_label) = NULL_TREE; + } + if (is_foreach_statement) objc_finish_foreach_loop (for_loc, object_expression, collection_expression, body, @@ -8596,7 +8726,9 @@ c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, objc_foreach_continue_label); else add_stmt (build_stmt (for_loc, FOR_STMT, NULL_TREE, cond, incr, - body, NULL_TREE)); + body, NULL_TREE, + loop_name && C_DECL_LOOP_SWITCH_NAME_USED (loop_name) + ? loop_name : NULL_TREE)); add_stmt (c_end_compound_stmt (for_loc, block, flag_isoc99 || c_dialect_objc ())); c_parser_maybe_reclassify_token (parser); @@ -8610,6 +8742,8 @@ c_parser_for_statement (c_parser *parser, bool ivdep, unsigned short unroll, for_tinfo.location, RID_FOR); in_statement = save_in_statement; + if (num_names) + c_release_loop_names (num_names); if (is_foreach_statement) { objc_foreach_break_label = save_objc_foreach_break_label; @@ -13245,7 +13379,7 @@ c_parser_objc_class_instance_variables (c_parser *parser) } else if (c_parser_next_token_is (parser, CPP_PRAGMA)) { - c_parser_pragma (parser, pragma_external, NULL); + c_parser_pragma (parser, pragma_external, NULL, NULL_TREE); continue; } @@ -13516,7 +13650,7 @@ c_parser_objc_methodprotolist (c_parser *parser) c_parser_objc_methodproto (parser); break; case CPP_PRAGMA: - c_parser_pragma (parser, pragma_external, NULL); + c_parser_pragma (parser, pragma_external, NULL, NULL_TREE); break; case CPP_EOF: return; @@ -14585,10 +14719,12 @@ c_parser_pragma_unroll (c_parser *parser) /* Handle pragmas. Some OpenMP pragmas are associated with, and therefore should be considered, statements. ALLOW_STMT is true if we're within the context of a function and such pragmas are to be allowed. Returns - true if we actually parsed such a pragma. */ + true if we actually parsed such a pragma. BEFORE_LABELS is last statement + before possible labels, see get_before_labels description for details. */ static bool -c_parser_pragma (c_parser *parser, enum pragma_context context, bool *if_p) +c_parser_pragma (c_parser *parser, enum pragma_context context, bool *if_p, + tree before_labels) { unsigned int id; const char *construct = NULL; @@ -14841,11 +14977,14 @@ c_parser_pragma (c_parser *parser, enum pragma_context context, bool *if_p) return false; } if (c_parser_next_token_is_keyword (parser, RID_FOR)) - c_parser_for_statement (parser, ivdep, unroll, novector, if_p); + c_parser_for_statement (parser, ivdep, unroll, novector, if_p, + before_labels); else if (c_parser_next_token_is_keyword (parser, RID_WHILE)) - c_parser_while_statement (parser, ivdep, unroll, novector, if_p); + c_parser_while_statement (parser, ivdep, unroll, novector, if_p, + before_labels); else - c_parser_do_statement (parser, ivdep, unroll, novector); + c_parser_do_statement (parser, ivdep, unroll, novector, + before_labels); } return true; @@ -22568,7 +22707,7 @@ c_parser_omp_loop_nest (c_parser *parser, bool *if_p) } break; default: - c_parser_pragma (parser, pragma_stmt, NULL); + c_parser_pragma (parser, pragma_stmt, NULL, void_list_node); break; } if (transform == NULL_TREE) @@ -25468,7 +25607,7 @@ c_maybe_parse_omp_decl (tree decl, tree d) parser->tokens = toks->address (); parser->tokens_avail = toks->length (); parser->in_omp_attribute_pragma = toks; - c_parser_pragma (parser, pragma_external, NULL); + c_parser_pragma (parser, pragma_external, NULL, NULL_TREE); parser->in_omp_decl_attribute = NULL_TREE; return true; } diff --git a/gcc/c/c-tree.h b/gcc/c/c-tree.h index b3e7bb013b6a8273eff9421acb082a51655bf9f5..c35ea36ba9160e11cad5ba8a5ec28e901275cdbc 100644 --- a/gcc/c/c-tree.h +++ b/gcc/c/c-tree.h @@ -90,6 +90,24 @@ along with GCC; see the file COPYING3. If not see #define C_DECL_BUILTIN_PROTOTYPE(EXP) \ DECL_LANG_FLAG_6 (FUNCTION_DECL_CHECK (EXP)) +/* For LABEL_DECLs marks canonical name of a loop. */ +#define C_DECL_LOOP_NAME(EXP) DECL_LANG_FLAG_3 (LABEL_DECL_CHECK (EXP)) + +/* For LABEL_DECLs marks canonical name of a switch. During parsing of + ObjC foreach named loop both C_DECL_LOOP_NAME and C_DECL_SWITCH_NAME + are temporarily set. */ +#define C_DECL_SWITCH_NAME(EXP) DECL_LANG_FLAG_5 (LABEL_DECL_CHECK (EXP)) + +/* For LABEL_DECLs marks canonical name of a loop or switch being + valid for use in break identifier or continue identifier statements. */ +#define C_DECL_LOOP_SWITCH_NAME_VALID(EXP) \ + DECL_LANG_FLAG_6 (LABEL_DECL_CHECK (EXP)) + +/* For LABEL_DECLs marks canonical loop or switch names which were actually + used in one or more break identifier or continue identifier statements. */ +#define C_DECL_LOOP_SWITCH_NAME_USED(EXP) \ + DECL_LANG_FLAG_8 (LABEL_DECL_CHECK (EXP)) + /* Record whether a decl was declared register. This is strictly a front-end flag, whereas DECL_REGISTER is used for code generation; they may differ for structures with volatile fields. */ @@ -611,12 +629,15 @@ extern struct obstack parser_obstack; to IN_OMP_BLOCK if parsing OpenMP structured block and IN_OMP_FOR if parsing OpenMP loop. If parsing a switch statement, this is bitwise ORed with IN_SWITCH_STMT, unless parsing an - iteration-statement, OpenMP block or loop within that switch. */ + iteration-statement, OpenMP block or loop within that switch. + If the innermost iteration/switch statement is named, IN_NAMED_STMT + is additionally bitwise ORed into it. */ #define IN_SWITCH_STMT 1 #define IN_ITERATION_STMT 2 #define IN_OMP_BLOCK 4 #define IN_OMP_FOR 8 #define IN_OBJC_FOREACH 16 +#define IN_NAMED_STMT 32 extern unsigned char in_statement; extern bool switch_statement_break_seen_p; @@ -723,6 +744,9 @@ extern struct c_declspecs *declspecs_add_alignas (location_t, struct c_declspecs *, tree); extern struct c_declspecs *finish_declspecs (struct c_declspecs *); extern size_t c_tree_size (enum tree_code); +extern int c_get_loop_names (tree, bool, tree *); +extern void c_release_loop_names (int); +extern tree c_finish_bc_name (location_t, tree, bool); /* in c-objc-common.cc */ extern bool c_objc_common_init (void); @@ -812,7 +836,7 @@ extern void process_init_element (location_t, struct c_expr, bool, extern tree build_compound_literal (location_t, tree, tree, bool, unsigned int, struct c_declspecs *); extern void check_compound_literal_type (location_t, struct c_type_name *); -extern tree c_start_switch (location_t, location_t, tree, bool); +extern tree c_start_switch (location_t, location_t, tree, bool, tree); extern void c_finish_switch (tree, tree); extern tree build_asm_expr (location_t, tree, tree, tree, tree, tree, bool, bool); @@ -828,7 +852,7 @@ extern tree c_finish_stmt_expr (location_t, tree); extern tree c_process_expr_stmt (location_t, tree); extern tree c_finish_expr_stmt (location_t, tree); extern tree c_finish_return (location_t, tree, tree, bool = false); -extern tree c_finish_bc_stmt (location_t, tree, bool); +extern tree c_finish_bc_stmt (location_t, tree, bool, tree); extern tree c_finish_goto_label (location_t, tree); extern tree c_finish_goto_ptr (location_t, c_expr val); extern tree c_expr_to_decl (tree, bool *, bool *); diff --git a/gcc/c/c-typeck.cc b/gcc/c/c-typeck.cc index ba6d96d26b2b166190c1bb2dac747e2386f0be0e..869b3a6d6bb47afd164d147dd28d1e34d1a74b46 100644 --- a/gcc/c/c-typeck.cc +++ b/gcc/c/c-typeck.cc @@ -11943,7 +11943,7 @@ struct c_switch *c_switch_stack; tree c_start_switch (location_t switch_loc, location_t switch_cond_loc, - tree exp, bool explicit_cast_p) + tree exp, bool explicit_cast_p, tree switch_name) { tree orig_type = error_mark_node; bool bool_cond_p = false; @@ -11996,7 +11996,7 @@ c_start_switch (location_t switch_loc, /* Add this new SWITCH_STMT to the stack. */ cs = XNEW (struct c_switch); cs->switch_stmt = build_stmt (switch_loc, SWITCH_STMT, exp, - NULL_TREE, orig_type, NULL_TREE); + NULL_TREE, orig_type, NULL_TREE, switch_name); cs->orig_type = orig_type; cs->cases = splay_tree_new (case_compare, NULL, NULL); cs->bindings = c_get_switch_bindings (); @@ -12097,7 +12097,7 @@ c_finish_if_stmt (location_t if_locus, tree cond, tree then_block, } tree -c_finish_bc_stmt (location_t loc, tree label, bool is_break) +c_finish_bc_stmt (location_t loc, tree label, bool is_break, tree name) { /* In switch statements break is sometimes stylistically used after a return statement. This can lead to spurious warnings about @@ -12109,7 +12109,7 @@ c_finish_bc_stmt (location_t loc, tree label, bool is_break) bool skip = !block_may_fallthru (cur_stmt_list); if (is_break) - switch (in_statement) + switch (in_statement & ~IN_NAMED_STMT) { case 0: error_at (loc, "break statement not within loop or switch"); @@ -12129,7 +12129,7 @@ c_finish_bc_stmt (location_t loc, tree label, bool is_break) break; } else - switch (in_statement & ~IN_SWITCH_STMT) + switch (in_statement & ~(IN_SWITCH_STMT | IN_NAMED_STMT)) { case 0: error_at (loc, "continue statement not within a loop"); @@ -12148,14 +12148,24 @@ c_finish_bc_stmt (location_t loc, tree label, bool is_break) if (skip) return NULL_TREE; else if ((in_statement & IN_OBJC_FOREACH) - && !(is_break && (in_statement & IN_SWITCH_STMT))) + && !(is_break && (in_statement & IN_SWITCH_STMT)) + && name == NULL_TREE) { /* The foreach expander produces low-level code using gotos instead of a structured loop construct. */ gcc_assert (label); return add_stmt (build_stmt (loc, GOTO_EXPR, label)); } - return add_stmt (build_stmt (loc, (is_break ? BREAK_STMT : CONTINUE_STMT))); + else if (name && C_DECL_LOOP_NAME (name) && C_DECL_SWITCH_NAME (name)) + { + label = DECL_CHAIN (name); + if (!is_break) + label = DECL_CHAIN (label); + /* Foreach expander from some outer level. */ + return add_stmt (build_stmt (loc, GOTO_EXPR, label)); + } + return add_stmt (build_stmt (loc, is_break ? BREAK_STMT : CONTINUE_STMT, + name)); } /* A helper routine for c_process_expr_stmt and c_finish_stmt_expr. */ diff --git a/gcc/cp/semantics.cc b/gcc/cp/semantics.cc index 0370d81de01fd5dcabfa12a9bdaacb0755817d23..dabfb1ff53f5682d17d22eef7af95e991d2a2643 100644 --- a/gcc/cp/semantics.cc +++ b/gcc/cp/semantics.cc @@ -1368,7 +1368,7 @@ tree begin_while_stmt (void) { tree r; - r = build_stmt (input_location, WHILE_STMT, NULL_TREE, NULL_TREE); + r = build_stmt (input_location, WHILE_STMT, NULL_TREE, NULL_TREE, NULL_TREE); add_stmt (r); WHILE_BODY (r) = do_pushlevel (sk_block); begin_cond (&WHILE_COND (r)); @@ -1425,7 +1425,8 @@ finish_while_stmt (tree while_stmt) tree begin_do_stmt (void) { - tree r = build_stmt (input_location, DO_STMT, NULL_TREE, NULL_TREE); + tree r = build_stmt (input_location, DO_STMT, NULL_TREE, NULL_TREE, + NULL_TREE); begin_maybe_infinite_loop (boolean_true_node); add_stmt (r); DO_BODY (r) = push_stmt_list (); @@ -1546,7 +1547,7 @@ begin_for_stmt (tree scope, tree init) tree r; r = build_stmt (input_location, FOR_STMT, NULL_TREE, NULL_TREE, - NULL_TREE, NULL_TREE, NULL_TREE); + NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE); if (scope == NULL_TREE) { @@ -1783,7 +1784,7 @@ finish_break_stmt (void) if (!block_may_fallthru (cur_stmt_list)) return void_node; note_break_stmt (); - return add_stmt (build_stmt (input_location, BREAK_STMT)); + return add_stmt (build_stmt (input_location, BREAK_STMT, NULL_TREE)); } /* Finish a continue-statement. */ @@ -1791,7 +1792,7 @@ finish_break_stmt (void) tree finish_continue_stmt (void) { - return add_stmt (build_stmt (input_location, CONTINUE_STMT)); + return add_stmt (build_stmt (input_location, CONTINUE_STMT, NULL_TREE)); } /* Begin a switch-statement. Returns a new SWITCH_STMT if @@ -1803,7 +1804,8 @@ begin_switch_stmt (void) tree r, scope; scope = do_pushlevel (sk_cond); - r = build_stmt (input_location, SWITCH_STMT, NULL_TREE, NULL_TREE, NULL_TREE, scope); + r = build_stmt (input_location, SWITCH_STMT, NULL_TREE, NULL_TREE, NULL_TREE, + scope, NULL_TREE); begin_cond (&SWITCH_STMT_COND (r)); diff --git a/gcc/testsuite/gcc.dg/c23-named-loops-1.c b/gcc/testsuite/gcc.dg/c23-named-loops-1.c new file mode 100644 index 0000000000000000000000000000000000000000..2be4111d518539700dcbadc9e67907cae402f76c --- /dev/null +++ b/gcc/testsuite/gcc.dg/c23-named-loops-1.c @@ -0,0 +1,144 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c23 -pedantic-errors" } */ + +void +foo (int w) +{ + d: e: f:; + a: b: c: + for (int x = 0; x < 32; ++x) + { + if (x == 0) + continue a; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 1) + continue b; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 2) + continue c; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 31) + break b; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + } + int y = 0; + g: h: + #pragma GCC unroll 2 + while (y < 16) + { + ++y; + if (y == 12) + continue g; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 13) + continue h; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 14) + break g; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + } + i: j:; + k: l: + switch (y) + { + case 6: + break; + case 7: + break k; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + case 8: + break l; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + } + m: n: o: p: + for (int x = 0; x < 2; ++x) + q: r: s: t: + switch (x) + { + case 0: + u: v: + case 3: + w: x: + for (int y = 0; y < 2; ++y) + y: z: + for (int z = 0; z < 2; ++z) + aa: ab: ac: + for (int a = 0; a < 2; ++a) + ad: ae: af: + switch (a) + { + case 0: + if (w == 0) + break ae; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 1) + break ab; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 2) + break z; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 3) + break v; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 4) + break s; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 5) + break p; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 6) + break; + else if (w == 7) + continue aa; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 8) + continue y; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 9) + continue x; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 10) + continue m; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + ag: ah: + do + { + if (w == 11) + break ag; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else + continue ah; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + while (0); + break; + default: + break; + } + break; + default: + break; + } + [[]] [[]] ai: + [[]] [[]] aj: + [[]] [[]] ak: + [[]] [[]] [[]] + for (int x = 0; x < 32; ++x) + if (x == 31) + break ak; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 30) + break aj; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 29) + continue ai; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + al: + [[]] am: + [[]] + do + { + if (w == 42) + continue am; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 41) + break al; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + } + while (1); + an: + [[]] ao: + [[]] [[]] + while (w) + { + if (w == 40) + break ao; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 39) + continue an; /* { dg-error "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + [[]] ap: + [[]] aq: + [[]] + switch (w) + { + case 42: + break ap; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + default: + break aq; /* { dg-error "ISO C does not support 'break' statement with an identifier operand before" } */ + } +} diff --git a/gcc/testsuite/gcc.dg/c23-named-loops-5.c b/gcc/testsuite/gcc.dg/c23-named-loops-5.c new file mode 100644 index 0000000000000000000000000000000000000000..cb8f897fd3e562018e3a0731574070210e7839ef --- /dev/null +++ b/gcc/testsuite/gcc.dg/c23-named-loops-5.c @@ -0,0 +1,5 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c23 -pedantic-errors -Wno-c23-c2y-compat" } */ + +#include "c23-named-loops-1.c" diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-1.c b/gcc/testsuite/gcc.dg/c2y-named-loops-1.c new file mode 100644 index 0000000000000000000000000000000000000000..686092946ada32e8bf1deb705b589108b7fdb1d7 --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-1.c @@ -0,0 +1,144 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -Wc23-c2y-compat" } */ + +void +foo (int w) +{ + d: e: f:; + a: b: c: + for (int x = 0; x < 32; ++x) + { + if (x == 0) + continue a; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 1) + continue b; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 2) + continue c; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 31) + break b; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + int y = 0; + g: h: + #pragma GCC unroll 2 + while (y < 16) + { + ++y; + if (y == 12) + continue g; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 13) + continue h; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 14) + break g; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + i: j:; + k: l: + switch (y) + { + case 6: + break; + case 7: + break k; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + case 8: + break l; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + m: n: o: p: + for (int x = 0; x < 2; ++x) + q: r: s: t: + switch (x) + { + case 0: + u: v: + case 3: + w: x: + for (int y = 0; y < 2; ++y) + y: z: + for (int z = 0; z < 2; ++z) + aa: ab: ac: + for (int a = 0; a < 2; ++a) + ad: ae: af: + switch (a) + { + case 0: + if (w == 0) + break ae; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 1) + break ab; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 2) + break z; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 3) + break v; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 4) + break s; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 5) + break p; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 6) + break; + else if (w == 7) + continue aa; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 8) + continue y; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 9) + continue x; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 10) + continue m; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + ag: ah: + do + { + if (w == 11) + break ag; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else + continue ah; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + while (0); + break; + default: + break; + } + break; + default: + break; + } + [[]] [[]] ai: + [[]] [[]] aj: + [[]] [[]] ak: + [[]] [[]] [[]] + for (int x = 0; x < 32; ++x) + if (x == 31) + break ak; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 30) + break aj; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 29) + continue ai; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + al: + [[]] am: + [[]] + do + { + if (w == 42) + continue am; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 41) + break al; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + while (1); + an: + [[]] ao: + [[]] [[]] + while (w) + { + if (w == 40) + break ao; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 39) + continue an; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + [[]] ap: + [[]] aq: + [[]] + switch (w) + { + case 42: + break ap; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + default: + break aq; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } +} diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-2.c b/gcc/testsuite/gcc.dg/c2y-named-loops-2.c new file mode 100644 index 0000000000000000000000000000000000000000..8d33b81e6a0dd3ff0ff8b15d93bcb54118504ad5 --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-2.c @@ -0,0 +1,45 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -pedantic-errors" } */ + +void +foo (int x) +{ + label1: + for (int i = 0; i < 16; ++i) + another_label1: + for (int j = 0; j < 16; ++j) + break label2; /* { dg-error "'break' statement operand 'label2' does not refer to a named loop or 'switch'; did you mean 'label1'\\\?" } */ + for (int i = 0; i < 16; ++i) + break label3; /* { dg-error "'break' statement operand 'label3' does not refer to a named loop or 'switch'" } */ + label4: /* { dg-message "'switch' name defined here" } */ + switch (x) + { + case 0: + for (int i = 0; i < 16; ++i) + continue label5; /* { dg-error "'continue' statement operand 'label5' does not refer to a named loop" } */ + break label4; + case 1: + for (int i = 0; i < 16; ++i) + continue label4; /* { dg-error "'continue' statement operand 'label4' refers to a named 'switch'" } */ + } + label6: + for (int i = 0; i < 16; ++i) + continue label7; /* { dg-error "'continue' statement operand 'label7' does not refer to a named loop; did you mean 'label6'\\\?" } */ + label2: + for (int i = 0; i < 16; ++i) + ; + label8:; + for (int i = 0; i < 16; ++i) + break label8; /* { dg-error "'break' statement operand 'label8' does not refer to a named loop or 'switch'" } */ + label9:; + for (int i = 0; i < 16; ++i) + continue label9; /* { dg-error "'continue' statement operand 'label9' does not refer to a named loop" } */ + label10: + ; + switch (x) + { + case 0: + break label10; /* { dg-error "'break' statement operand 'label10' does not refer to a named loop or 'switch'" } */ + } +} diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-4.c b/gcc/testsuite/gcc.dg/c2y-named-loops-4.c new file mode 100644 index 0000000000000000000000000000000000000000..660cda9040ad27bc3e80d79de028dc6777952581 --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-4.c @@ -0,0 +1,159 @@ +/* N3355 - Named loops. */ +/* { dg-do run } */ +/* { dg-options "-std=c2y -pedantic-errors" } */ + +extern void abort (void); + +void +foo (int x) +{ + int i, j, k, l, m; + label1: + for (i = 0; i < 2; ++i) + { + if (i == 1) + { + if (x != 11) + abort (); + return; + } + label2: + switch (i) + { + label3: + case 0: + for (j = 0; j < 2; ++j) + { + if (j == 1) + { + if (x != 8) + abort (); + return; + } + label4: + for (k = 0; k < 2; ++k) + { + if (k == 1) + { + if (x != 6) + abort (); + return; + } + l = 0; + label5: + while (l < 2) + { + if (l == 1) + { + if (x != 4) + abort (); + return; + } + ++l; + m = 0; + label6: + do + { + if (m == 1) + { + if (x != 2) + abort (); + return; + } + ++m; + label7: + switch (x) + { + case 0: + break label7; + case 1: + break label6; + case 2: + continue label6; + case 3: + break label5; + case 4: + continue label5; + case 5: + break label4; + case 6: + continue label4; + case 7: + break label3; + case 8: + continue label3; + case 9: + break label2; + case 10: + break label1; + case 11: + continue label1; + default: + abort (); + break; + } + if (x) + abort (); + return; + } + while (m < 2); + if (x != 1 || m != 1) + abort (); + return; + } + if (x != 3 || l != 1 || m != 1) + abort (); + return; + } + if (x != 5 || k != 0 || l != 1 || m != 1) + abort (); + return; + } + if (x != 7 || j != 0 || k != 0 || l != 1 || m != 1) + abort (); + return; + } + if (x != 9 || j != 0 || k != 0 || l != 1 || m != 1) + abort (); + return; + } + if (x != 10 || i != 0 || j != 0 || k != 0 || l != 1 || m != 1) + abort (); +} + +void +bar (int x) +{ + int i, j; + label1: + for (i = 0; i < 2; ++i) + { + if (i == 1) + { + if (x != 1) + abort (); + return; + } + for (j = 0; j < 2; ++j) + if (j == 1) + abort (); + else if (x == 0) + break label1; + else if (x == 1) + continue label1; + else + abort (); + abort (); + } + if (x != 0) + abort (); +} + +int +main () +{ + for (int n = 0; n <= 11; ++n) + foo (n); + bar (0); + bar (1); +} diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-5.c b/gcc/testsuite/gcc.dg/c2y-named-loops-5.c new file mode 100644 index 0000000000000000000000000000000000000000..2db1930eec576af3f59a1bf9a15d37b55e88c6f3 --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-5.c @@ -0,0 +1,5 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -pedantic-errors" } */ + +#include "c2y-named-loops-1.c" diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-6.c b/gcc/testsuite/gcc.dg/c2y-named-loops-6.c new file mode 100644 index 0000000000000000000000000000000000000000..d34103af910d64d212a02ec8cf1b14f140c9b4cc --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-6.c @@ -0,0 +1,32 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -Wall" } */ + +void +foo (int x) +{ + lab0: + switch (x) + { + case 1: + ++x; + /* FALLTHRU */ + lab1: + case 2: + /* FALLTHRU */ + case 3: + lab2: + for (int i = 0; i < 4; ++i) + if (i == 0) + continue lab2; + else if (i == 1) + continue lab1; + else if (x == 2) + break lab1; + else + break lab0; + break; + default: + break; + } +} diff --git a/gcc/testsuite/gcc.dg/c2y-named-loops-7.c b/gcc/testsuite/gcc.dg/c2y-named-loops-7.c new file mode 100644 index 0000000000000000000000000000000000000000..dda3e4e99dc6e90e73e35342c7d1f262edd702ce --- /dev/null +++ b/gcc/testsuite/gcc.dg/c2y-named-loops-7.c @@ -0,0 +1,32 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -Wall" } */ + +void +foo (int x) +{ + lab0: + switch (x) + { + case 1: + ++x; + [[fallthrough]]; + lab1: /* { dg-warning "label 'lab1' defined but not used" } */ + case 2: + [[fallthrough]]; + case 3: + lab2: + for (int i = 0; i < 4; ++i) + if (i == 0) + continue lab2; + else if (i == 1) + continue lab1; /* { dg-error "'continue' statement operand 'lab1' does not refer to a named loop; did you mean 'lab2'\\\?" } */ + else if (x == 2) + break lab1; /* { dg-error "'break' statement operand 'lab1' does not refer to a named loop or 'switch'; did you mean 'lab2'\\\?" } */ + else + break lab0; + break; + default: + break; + } +} diff --git a/gcc/testsuite/gcc.dg/gnu2y-named-loops-3.c b/gcc/testsuite/gcc.dg/gnu2y-named-loops-3.c new file mode 100644 index 0000000000000000000000000000000000000000..18ab975368e30dfb4a317bc969ba2ca193119fa5 --- /dev/null +++ b/gcc/testsuite/gcc.dg/gnu2y-named-loops-3.c @@ -0,0 +1,117 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=gnu2y" } */ + +void +foo (int x) +{ + for (int i = 0; i < 16; ++i) + { + int k; + label1: /* { dg-message "loop name defined here" } */ + for (int j = ({ if (x == 0) break label1; 0; }); j < 16; ++j) /* { dg-error "'break' statement operand 'label1' refers to a loop outside of its body" } */ + ; + label2: /* { dg-message "loop name defined here" } */ + for (int j = ({ if (x == 1) continue label2; 0; }); j < 16; ++j) /* { dg-error "'continue' statement operand 'label2' refers to a loop outside of its body" } */ + ; + label3: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < ({ if (x == 2) break label3; 16; }); ++j) /* { dg-error "'break' statement operand 'label3' refers to a loop outside of its body" } */ + ; + label4: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < ({ if (x == 3) continue label4; 16; }); ++j) /* { dg-error "'continue' statement operand 'label4' refers to a loop outside of its body" } */ + ; + label5: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < 16; j += ({ if (x == 4) break label5; 1; })) /* { dg-error "'break' statement operand 'label5' refers to a loop outside of its body" } */ + ; + label6: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < 16; j += ({ if (x == 5) continue label6; 1; })) /* { dg-error "'continue' statement operand 'label6' refers to a loop outside of its body" } */ + ; + k = 0; + label7: /* { dg-message "loop name defined here" } */ + while (k < ({ if (x == 6) break label7; 16; })) /* { dg-error "'break' statement operand 'label7' refers to a loop outside of its body" } */ + ++k; + k = 0; + label8: /* { dg-message "loop name defined here" } */ + while (k < ({ if (x == 7) continue label8; 16; })) /* { dg-error "'continue' statement operand 'label8' refers to a loop outside of its body" } */ + ++k; + k = 0; + label9: + do + ++k; + while (k <= ({ if (x == 8) break label9; 16; })); /* { dg-error "'break' statement operand 'label9' does not refer to a named loop or 'switch'" } */ + k = 0; + label10: + do + ++k; + while (k <= ({ if (x == 9) continue label10; 16; })); /* { dg-error "'continue' statement operand 'label10' does not refer to a named loop" } */ + label11: /* { dg-message "'switch' name defined here" } */ + switch (x + ({ if (x == 10) break label11; 0; })) /* { dg-error "'break' statement operand 'label11' refers to a 'switch' outside of its body" } */ + { + case 0: + break; + } + } + label12: + label13: + label14: + for (int i = 0; i < 32; ++i) + { + label15: + switch (i) + { + label16: + case 0: + label17: + label18: + label19: + label20: + label21: + label22: + label23: + label24: + label25: + label26: + label27: + label28: + label29: + label30: + for (int j = 0; j < 32; ++j) + { + if (j == 31) + continue label14; + else if (j == 30) + break label15; + void bar (void) + { + label31: + for (int k = 0; k < 32; ++k) + if (k == 31) + continue label31; + else if (k == 30) + break label31; + else if (k == 29) + continue label22; /* { dg-error "'continue' statement operand 'label22' does not refer to a named loop; did you mean 'label31'\\\?" } */ + else if (k == 28) + break label20; /* { dg-error "'break' statement operand 'label20' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + else if (k == 27) + break label15; /* { dg-error "'break' statement operand 'label15' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + else if (k == 26) + continue label13; /* { dg-error "'continue' statement operand 'label13' does not refer to a named loop; did you mean 'label31'\\\?" } */ + else if (k == 25) + break label12; /* { dg-error "'break' statement operand 'label12' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + } + bar (); + if (j == 29) + continue label22; + else if (j == 28) + break label20; + else if (j == 27) + break label15; + else if (j == 26) + continue label13; + else if (j == 25) + break label12; + } + } + } +} diff --git a/gcc/testsuite/gcc.dg/gnu99-named-loops-1.c b/gcc/testsuite/gcc.dg/gnu99-named-loops-1.c new file mode 100644 index 0000000000000000000000000000000000000000..cb1c690ac15b6f314315aacd5a037f608db8be06 --- /dev/null +++ b/gcc/testsuite/gcc.dg/gnu99-named-loops-1.c @@ -0,0 +1,144 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=gnu99 -Wpedantic" } */ + +void +foo (int w) +{ + d: e: f:; + a: b: c: + for (int x = 0; x < 32; ++x) + { + if (x == 0) + continue a; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 1) + continue b; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 2) + continue c; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (x == 31) + break b; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + int y = 0; + g: h: + #pragma GCC unroll 2 + while (y < 16) + { + ++y; + if (y == 12) + continue g; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 13) + continue h; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (y == 14) + break g; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + i: j:; + k: l: + switch (y) + { + case 6: + break; + case 7: + break k; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + case 8: + break l; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + m: n: o: p: + for (int x = 0; x < 2; ++x) + q: r: s: t: + switch (x) + { + case 0: + u: v: + case 3: + w: x: + for (int y = 0; y < 2; ++y) + y: z: + for (int z = 0; z < 2; ++z) + aa: ab: ac: + for (int a = 0; a < 2; ++a) + ad: ae: af: + switch (a) + { + case 0: + if (w == 0) + break ae; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 1) + break ab; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 2) + break z; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 3) + break v; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 4) + break s; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 5) + break p; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 6) + break; + else if (w == 7) + continue aa; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 8) + continue y; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 9) + continue x; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 10) + continue m; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + ag: ah: + do + { + if (w == 11) + break ag; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else + continue ah; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + while (0); + break; + default: + break; + } + break; + default: + break; + } + [[]] [[]] ai: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] [[]] aj: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] [[]] ak: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] [[]] [[]] /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + for (int x = 0; x < 32; ++x) + if (x == 31) + break ak; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 30) + break aj; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (x == 29) + continue ai; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + al: + [[]] am: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + do + { + if (w == 42) + continue am; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + else if (w == 41) + break al; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } + while (1); + an: + [[]] ao: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] [[]] /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + while (w) + { + if (w == 40) + break ao; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + else if (w == 39) + continue an; /* { dg-warning "ISO C does not support 'continue' statement with an identifier operand before" } */ + } + [[]] ap: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] aq: /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + [[]] /* { dg-warning "ISO C does not support '\\\[\\\[\\\]\\\]' attributes before C23" } */ + switch (w) + { + case 42: + break ap; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + default: + break aq; /* { dg-warning "ISO C does not support 'break' statement with an identifier operand before" } */ + } +} diff --git a/gcc/testsuite/gcc.dg/gnu99-named-loops-2.c b/gcc/testsuite/gcc.dg/gnu99-named-loops-2.c new file mode 100644 index 0000000000000000000000000000000000000000..46c6ba8e602d1b12d18e35adf51a035ccc8b72af --- /dev/null +++ b/gcc/testsuite/gcc.dg/gnu99-named-loops-2.c @@ -0,0 +1,45 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=gnu99" } */ + +void +foo (int x) +{ + label1: + for (int i = 0; i < 16; ++i) + another_label1: + for (int j = 0; j < 16; ++j) + break label2; /* { dg-error "'break' statement operand 'label2' does not refer to a named loop or 'switch'; did you mean 'label1'\\\?" } */ + for (int i = 0; i < 16; ++i) + break label3; /* { dg-error "'break' statement operand 'label3' does not refer to a named loop or 'switch'" } */ + label4: /* { dg-message "'switch' name defined here" } */ + switch (x) + { + case 0: + for (int i = 0; i < 16; ++i) + continue label5; /* { dg-error "'continue' statement operand 'label5' does not refer to a named loop" } */ + break label4; + case 1: + for (int i = 0; i < 16; ++i) + continue label4; /* { dg-error "'continue' statement operand 'label4' refers to a named 'switch'" } */ + } + label6: + for (int i = 0; i < 16; ++i) + continue label7; /* { dg-error "'continue' statement operand 'label7' does not refer to a named loop; did you mean 'label6'\\\?" } */ + label2: + for (int i = 0; i < 16; ++i) + ; + label8:; + for (int i = 0; i < 16; ++i) + break label8; /* { dg-error "'break' statement operand 'label8' does not refer to a named loop or 'switch'" } */ + label9:; + for (int i = 0; i < 16; ++i) + continue label9; /* { dg-error "'continue' statement operand 'label9' does not refer to a named loop" } */ + label10: + ; + switch (x) + { + case 0: + break label10; /* { dg-error "'break' statement operand 'label10' does not refer to a named loop or 'switch'" } */ + } +} diff --git a/gcc/testsuite/gcc.dg/gnu99-named-loops-3.c b/gcc/testsuite/gcc.dg/gnu99-named-loops-3.c new file mode 100644 index 0000000000000000000000000000000000000000..ee944736c7a6e3384f7b854814310ab0df525296 --- /dev/null +++ b/gcc/testsuite/gcc.dg/gnu99-named-loops-3.c @@ -0,0 +1,117 @@ +/* N3355 - Named loops. */ +/* { dg-do compile } */ +/* { dg-options "-std=gnu99" } */ + +void +foo (int x) +{ + for (int i = 0; i < 16; ++i) + { + int k; + label1: /* { dg-message "loop name defined here" } */ + for (int j = ({ if (x == 0) break label1; 0; }); j < 16; ++j) /* { dg-error "'break' statement operand 'label1' refers to a loop outside of its body" } */ + ; + label2: /* { dg-message "loop name defined here" } */ + for (int j = ({ if (x == 1) continue label2; 0; }); j < 16; ++j) /* { dg-error "'continue' statement operand 'label2' refers to a loop outside of its body" } */ + ; + label3: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < ({ if (x == 2) break label3; 16; }); ++j) /* { dg-error "'break' statement operand 'label3' refers to a loop outside of its body" } */ + ; + label4: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < ({ if (x == 3) continue label4; 16; }); ++j) /* { dg-error "'continue' statement operand 'label4' refers to a loop outside of its body" } */ + ; + label5: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < 16; j += ({ if (x == 4) break label5; 1; })) /* { dg-error "'break' statement operand 'label5' refers to a loop outside of its body" } */ + ; + label6: /* { dg-message "loop name defined here" } */ + for (int j = 0; j < 16; j += ({ if (x == 5) continue label6; 1; })) /* { dg-error "'continue' statement operand 'label6' refers to a loop outside of its body" } */ + ; + k = 0; + label7: /* { dg-message "loop name defined here" } */ + while (k < ({ if (x == 6) break label7; 16; })) /* { dg-error "'break' statement operand 'label7' refers to a loop outside of its body" } */ + ++k; + k = 0; + label8: /* { dg-message "loop name defined here" } */ + while (k < ({ if (x == 7) continue label8; 16; })) /* { dg-error "'continue' statement operand 'label8' refers to a loop outside of its body" } */ + ++k; + k = 0; + label9: + do + ++k; + while (k <= ({ if (x == 8) break label9; 16; })); /* { dg-error "'break' statement operand 'label9' does not refer to a named loop or 'switch'" } */ + k = 0; + label10: + do + ++k; + while (k <= ({ if (x == 9) continue label10; 16; })); /* { dg-error "'continue' statement operand 'label10' does not refer to a named loop" } */ + label11: /* { dg-message "'switch' name defined here" } */ + switch (x + ({ if (x == 10) break label11; 0; })) /* { dg-error "'break' statement operand 'label11' refers to a 'switch' outside of its body" } */ + { + case 0: + break; + } + } + label12: + label13: + label14: + for (int i = 0; i < 32; ++i) + { + label15: + switch (i) + { + label16: + case 0: + label17: + label18: + label19: + label20: + label21: + label22: + label23: + label24: + label25: + label26: + label27: + label28: + label29: + label30: + for (int j = 0; j < 32; ++j) + { + if (j == 31) + continue label14; + else if (j == 30) + break label15; + void bar (void) + { + label31: + for (int k = 0; k < 32; ++k) + if (k == 31) + continue label31; + else if (k == 30) + break label31; + else if (k == 29) + continue label22; /* { dg-error "'continue' statement operand 'label22' does not refer to a named loop; did you mean 'label31'\\\?" } */ + else if (k == 28) + break label20; /* { dg-error "'break' statement operand 'label20' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + else if (k == 27) + break label15; /* { dg-error "'break' statement operand 'label15' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + else if (k == 26) + continue label13; /* { dg-error "'continue' statement operand 'label13' does not refer to a named loop; did you mean 'label31'\\\?" } */ + else if (k == 25) + break label12; /* { dg-error "'break' statement operand 'label12' does not refer to a named loop or 'switch'; did you mean 'label31'\\\?" } */ + } + bar (); + if (j == 29) + continue label22; + else if (j == 28) + break label20; + else if (j == 27) + break label15; + else if (j == 26) + continue label13; + else if (j == 25) + break label12; + } + } + } +} diff --git a/gcc/testsuite/gcc.dg/gnu99-named-loops-4.c b/gcc/testsuite/gcc.dg/gnu99-named-loops-4.c new file mode 100644 index 0000000000000000000000000000000000000000..637a063c1a5fb03e76a62bc1f310e26b9a43fd5f --- /dev/null +++ b/gcc/testsuite/gcc.dg/gnu99-named-loops-4.c @@ -0,0 +1,5 @@ +/* N3355 - Named loops. */ +/* { dg-do run } */ +/* { dg-options "-std=gnu99" } */ + +#include "c2y-named-loops-4.c" diff --git a/gcc/testsuite/gcc.dg/gomp/named-loops-1.c b/gcc/testsuite/gcc.dg/gomp/named-loops-1.c new file mode 100644 index 0000000000000000000000000000000000000000..9b944d3cb9f87b9b2342cb0ab6403e4569d1eadb --- /dev/null +++ b/gcc/testsuite/gcc.dg/gomp/named-loops-1.c @@ -0,0 +1,101 @@ +/* Cases which will be IMHO always invalid in OpenMP, + just perhaps could have different diagnostic wording. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -fopenmp" } */ + +void +foo () +{ + label1: + for (int i = 0; i < 32; ++i) + #pragma omp parallel for + for (int j = 0; j < 32; ++j) + { + if (j == 31) + break label1; /* { dg-error "break statement used with OpenMP for loop" } */ + else if (j == 30) + continue label1; /* { dg-error "invalid branch to/from OpenMP structured block" } */ + label2: + for (int k = 0; k < 32; ++k) + if (k == 31) + break label2; + else if (k == 30) + continue label2; + else if (k == 29) + break label1; /* { dg-error "invalid branch to/from OpenMP structured block" } */ + else if (k == 28) + continue label1; /* { dg-error "invalid branch to/from OpenMP structured block" } */ + } +} + +void +bar () +{ + label1: + #pragma omp parallel for + for (int i = 0; i < 32; ++i) + if (i == 31) + break label1; /* { dg-error "break' statement operand 'label1' does not refer to a named loop or 'switch'" } */ + /* { dg-error "break statement used with OpenMP for loop" "" { target *-*-* } .-1 } */ + label2: + #pragma omp parallel for collapse(2) + for (int i = 0; i < 32; ++i) + for (int j = 0; j < 32; ++j) + if (i == 31 && j == 31) + break label2; /* { dg-error "'break' statement operand 'label2' does not refer to a named loop or 'switch'" } */ + /* { dg-error "break statement used with OpenMP for loop" "" { target *-*-* } .-1 } */ + else if (i == 31 && j == 30) + continue label2; /* { dg-error "'continue' statement operand 'label2' does not refer to a named loop" } */ +} + +void +baz () +{ + label1: + [[omp::directive (parallel for)]] + for (int i = 0; i < 32; ++i) + if (i == 31) + break label1; /* { dg-error "break' statement operand 'label1' does not refer to a named loop or 'switch'" } */ + /* { dg-error "break statement used with OpenMP for loop" "" { target *-*-* } .-1 } */ + label2: + [[omp::directive (parallel for, collapse(2))]] + for (int i = 0; i < 32; ++i) + for (int j = 0; j < 32; ++j) + if (i == 31 && j == 31) + break label2; /* { dg-error "'break' statement operand 'label2' does not refer to a named loop or 'switch'" } */ + /* { dg-error "break statement used with OpenMP for loop" "" { target *-*-* } .-1 } */ + else if (i == 31 && j == 30) + continue label2; /* { dg-error "'continue' statement operand 'label2' does not refer to a named loop" } */ +} + +void +qux () +{ + label1: + #pragma omp parallel for collapse(2) + for (int i = 0; i < 32; ++i) /* { dg-error "not enough nested loops" } */ + label2: + for (int j = 0; j < 32; ++j) + if (j == 31) + break label1; /* { dg-error "'break' statement operand 'label1' does not refer to a named loop or 'switch'; did you mean 'label2'\\\?" } */ + else if (j == 30) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop; did you mean 'label2'\\\?" } */ + else if (j == 29) + break label2; /* This is IMHO invalid too and currently just diagnosed by the not enough nested loops. */ +} + +void +garply () +{ + label1: + [[omp::directive (parallel for, collapse(2))]] + for (int i = 0; i < 32; ++i) /* { dg-error "not enough nested loops" } */ + label2: + for (int j = 0; j < 32; ++j) + if (j == 31) + break label1; /* { dg-error "'break' statement operand 'label1' does not refer to a named loop or 'switch'; did you mean 'label2'\\\?" } */ + else if (j == 30) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop; did you mean 'label2'\\\?" } */ + else if (j == 29) + break label2; /* This is IMHO invalid too and currently just diagnosed by the not enough nested loops. */ +} diff --git a/gcc/testsuite/gcc.dg/gomp/named-loops-2.c b/gcc/testsuite/gcc.dg/gomp/named-loops-2.c new file mode 100644 index 0000000000000000000000000000000000000000..2120923f71479960155f21164f5c7e9d8a83144e --- /dev/null +++ b/gcc/testsuite/gcc.dg/gomp/named-loops-2.c @@ -0,0 +1,82 @@ +/* Cases which perhaps could be valid in OpenMP one day, but aren't + accepted right now. */ +/* { dg-do compile } */ +/* { dg-options "-std=c2y -fopenmp" } */ + +void +foo () +{ + label1: + #pragma omp parallel for + for (int i = 0; i < 32; ++i) + if (i == 31) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop" } */ + else + { + label2: + for (int j = 0; j < 32; ++j) + if (j == 31) + continue label2; + else if (j == 30) + break label2; + else if (j == 29) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop; did you mean 'label2'\\\?" } */ + } +} + +void +bar () +{ + label1: + [[omp::directive (parallel for)]] + for (int i = 0; i < 32; ++i) + if (i == 31) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop" } */ + else + { + label2: + for (int j = 0; j < 32; ++j) + if (j == 31) + continue label2; + else if (j == 30) + break label2; + else if (j == 29) + continue label1; /* { dg-error "'continue' statement operand 'label1' does not refer to a named loop; did you mean 'label2'\\\?" } */ + } +} + +void +baz () +{ + label1: + #pragma omp parallel for collapse(2) + for (int i = 0; i < 32; ++i) /* { dg-error "not enough nested loops" } */ + label2: + for (int j = 0; j < 32; ++j) + label3: + for (int k = 0; k < 32; ++k) + if (k == 31) + continue label3; + else if (k == 30) + break label3; + else if (k == 29) + continue label2; +} + +void +qux () +{ + label1: + [[omp::directive (parallel for, collapse(2))]] + for (int i = 0; i < 32; ++i) /* { dg-error "not enough nested loops" } */ + label2: + for (int j = 0; j < 32; ++j) + label3: + for (int k = 0; k < 32; ++k) + if (k == 31) + continue label3; + else if (k == 30) + break label3; + else if (k == 29) + continue label2; +} diff --git a/gcc/testsuite/objc.dg/named-loops-1.m b/gcc/testsuite/objc.dg/named-loops-1.m new file mode 100644 index 0000000000000000000000000000000000000000..5c1b81e7daf1b04923bfbc1c6cb2b4abdd405376 --- /dev/null +++ b/gcc/testsuite/objc.dg/named-loops-1.m @@ -0,0 +1,172 @@ +/* Test basic Objective-C foreach syntax. This tests iterations, with + the basic syntax 'for (object in array) statements' +*/ +/* { dg-do run } */ +/* { dg-skip-if "No NeXT fast enum. pre-Darwin9" { *-*-darwin[5-8]* } { "-fnext-runtime" } { "" } } */ +/* { dg-xfail-run-if "Needs OBJC2 ABI" { *-*-darwin* && { lp64 && { ! objc2 } } } { "-fnext-runtime" } { "" } } */ +/* { dg-options "-mno-constant-cfstrings" { target *-*-darwin* } } */ +/* { dg-additional-sources "../objc-obj-c++-shared/nsconstantstring-class-impl.m" } */ +/* { dg-additional-options "-Wno-objc-root-class" } */ + +#include "../objc-obj-c++-shared/TestsuiteObject.m" +#ifndef __NEXT_RUNTIME__ +#include <objc/NXConstStr.h> +#else +#include "../objc-obj-c++-shared/nsconstantstring-class.h" +#endif + +extern int printf (const char *, ...); +#include <stdlib.h> + +/* +struct __objcFastEnumerationState +{ + unsigned long state; + id *itemsPtr; + unsigned long *mutationsPtr; + unsigned long extra[5]; +}; +*/ + + /* A mini-array implementation that can be used to test fast + enumeration. You create the array with some objects; you can + mutate the array, and you can fast-enumerate it. + */ +@interface MyArray : TestsuiteObject +{ + unsigned int length; + id *objects; + unsigned long mutated; +} +- (id) initWithLength: (unsigned int)l objects: (id *)o; +- (void) mutate; +- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState *)state + objects:(id *)stackbuf + count:(unsigned long)len; +@end + +@implementation MyArray : TestsuiteObject +- (id) initWithLength: (unsigned int)l + objects: (id *)o +{ + length = l; + objects = o; + mutated = 0; + return self; +} +- (void) mutate +{ + mutated = 1; +} +- (unsigned long)countByEnumeratingWithState: (struct __objcFastEnumerationState*)state + objects: (id*)stackbuf + count: (unsigned long)len +{ + unsigned long i, batch_size; + + /* We keep how many objects we served in the state->state counter. So the next batch + will contain up to length - state->state objects. */ + batch_size = length - state->state; + + /* Make obvious adjustments. */ + if (batch_size < 0) + batch_size = 0; + + if (batch_size > len) + batch_size = len; + + /* Copy the objects. */ + for (i = 0; i < batch_size; i++) + stackbuf[i] = objects[i]; + + state->state += batch_size; + state->itemsPtr = stackbuf; + state->mutationsPtr = &mutated; + + return batch_size; +} +@end + +void +foo (MyArray *array, int x) +{ + TestsuiteObject *object; + int i, j, k; + + label1: + for (i = 0; i < 2; ++i) + { + if (i == 1) + { + if (x != 5) + abort (); + return; + } + k = 0; + label2: + for (object in array) + { + if (k == 1) + { + if (x != 3) + abort (); + return; + } + ++k; + label3: + for (j = 0; j < 2; ++j) + { + if (j == 1) + { + if (x != 1) + abort (); + return; + } + label4: + switch (x) + { + case 0: + break label4; + case 1: + continue label3; + case 2: + break label3; + case 3: + continue label2; + case 4: + break label2; + case 5: + continue label1; + default: + break label1; + } + if (x != 0) + abort (); + return; + } + if (x != 2) + abort (); + return; + } + if (x != 4) + abort (); + return; + } + if (x <= 5) + abort (); +} + +int +main () +{ + MyArray *array; + id objects[2] = { @"object1", @"object2" }; + int i; + + array = [[MyArray alloc] initWithLength: 2 + objects: objects]; + for (i = 0; i < 6; ++i) + foo (array, i); + + return 0; +}