From 8715c4f8920fa99bbe0f46578f3d45a14c1d0d21 Mon Sep 17 00:00:00 2001 From: Jules Villard Date: Thu, 17 May 2018 06:13:39 -0700 Subject: [PATCH] [clang] make switch statement translation more robust Summary: Labels inside switch statements were causing havoc (see test), and the translation of switch statements in general could be improved to handle more cases. It turns out that `case` (and `default`) statements are more or less fancy labels into the code. In other words, if you erase all the `case XXX:` and `default:` strings in the `switch` statement you get the real structure of the program, and `switch` just jumps straight to the first `case` directives (and to the second if the first one is not satisfied, etc. until all `case`/`default` have been considered). This suggests an alternative implementation: translate the body of the `switch` and simply record the list of switch cases inside that body, along with where they point to. Then post-process this list to construct the control flow of the `switch`, which points into the control-flow of the `body`. In order not to modify every function in `CTrans` to propagate the current list of cases, I created an ugly `ref` inside `SwitchCase` instead (but it cannot be directly accessed and it's guaranteed to be well-parenthesised wrt nested switches by the `SwitchCase` API so it's not too bad). [unrelated] Also make translation failures output more information about what exactly in the source code is causing the crash, and the ancestors in the AST that lead to the crash site. Reviewed By: martinoluca Differential Revision: D8011046 fbshipit-source-id: 8455090 --- infer/src/base/Location.ml | 21 +- infer/src/base/Location.mli | 2 + infer/src/clang/SwitchCase.ml | 39 + infer/src/clang/SwitchCase.mli | 23 + infer/src/clang/cTrans.ml | 310 +++---- infer/src/clang/cTrans_utils.mli | 2 +- .../c/frontend/switchstmt/switch.c | 35 +- .../c/frontend/switchstmt/switch.c.dot | 818 +++++++++--------- .../c/frontend/switchstmt/switch_unroll.c | 27 + .../c/frontend/switchstmt/switch_unroll.c.dot | 108 +++ .../frontend/switchstmt/switch_with_labels.c | 39 + .../switchstmt/switch_with_labels.c.dot | 114 +++ .../attributes/clang_fallthrough.cpp.dot | 4 +- .../frontend/destructors/break_scope.cpp.dot | 46 +- .../var_decl_inside_switch.cpp.dot | 36 +- 15 files changed, 937 insertions(+), 687 deletions(-) create mode 100644 infer/src/clang/SwitchCase.ml create mode 100644 infer/src/clang/SwitchCase.mli create mode 100644 infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c create mode 100644 infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c.dot create mode 100644 infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c create mode 100644 infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c.dot diff --git a/infer/src/base/Location.ml b/infer/src/base/Location.ml index cccd445a4..d87ca8ec2 100644 --- a/infer/src/base/Location.ml +++ b/infer/src/base/Location.ml @@ -28,13 +28,20 @@ let pp f (loc: t) = if loc.col <> -1 then F.fprintf f ", column %d" loc.col -let to_string loc = - let s = string_of_int loc.line in - if loc.col <> -1 then Printf.sprintf "%s:%d" s loc.col else s +let pp_short f loc = + F.pp_print_int f loc.line ; + if loc.col <> -1 then F.fprintf f ":%d" loc.col +let to_string loc = F.asprintf "%a" pp_short loc + (** Pretty print a file-position of a location *) -let pp_file_pos f (loc: t) = - let fname = SourceFile.to_string loc.file in - let pos = to_string loc in - F.fprintf f "%s:%s" fname pos +let pp_file_pos f (loc: t) = F.fprintf f "%a:%a" SourceFile.pp loc.file pp_short loc + +let pp_range f (loc_start, loc_end) = + let pp_end loc_start f loc_end = + if Int.equal loc_end.line loc_start.line then + if Int.equal loc_end.col loc_start.col then () else F.fprintf f "-%d" loc_end.col + else F.fprintf f "-%a" pp_short loc_end + in + F.fprintf f "%a%a" pp_file_pos loc_start (pp_end loc_start) loc_end diff --git a/infer/src/base/Location.mli b/infer/src/base/Location.mli index 002245cce..8d050f6f3 100644 --- a/infer/src/base/Location.mli +++ b/infer/src/base/Location.mli @@ -32,3 +32,5 @@ val to_string : t -> string val pp_file_pos : Format.formatter -> t -> unit (** Pretty print a file-position of a location *) + +val pp_range : Format.formatter -> t * t -> unit diff --git a/infer/src/clang/SwitchCase.ml b/infer/src/clang/SwitchCase.ml new file mode 100644 index 000000000..8384fb910 --- /dev/null +++ b/infer/src/clang/SwitchCase.ml @@ -0,0 +1,39 @@ +(* + * Copyright (c) 2018 - present Facebook, Inc. + * All rights reserved. + * + * This source code is licensed under the BSD style license found in the + * LICENSE file in the root directory of this source tree. An additional grant + * of patent rights can be found in the PATENTS file in the same directory. + *) +open! IStd +module F = Format + +type condition = Case of Clang_ast_t.stmt | Default + +type t = {condition: condition; stmt_info: Clang_ast_t.stmt_info; root_nodes: Procdesc.Node.t list} + +let current_cases : t list ref = ref [] + +let in_switch_body ~f x = + let outer_switch_cases = !current_cases in + current_cases := [] ; + let res = f x in + let rev_switch_cases = !current_cases in + current_cases := outer_switch_cases ; + (List.rev rev_switch_cases, res) + + +let add switch_case = current_cases := switch_case :: !current_cases + +let pp_condition fmt = function + | Case stmt -> + F.fprintf fmt "case %a:" (Pp.to_string ~f:Clang_ast_j.string_of_stmt) stmt + | Default -> + F.pp_print_string fmt "default:" + + +let pp fmt {condition; root_nodes} = + F.fprintf fmt "%a -> @[[%a]@]" pp_condition condition + (Pp.semicolon_seq Procdesc.Node.pp) + root_nodes diff --git a/infer/src/clang/SwitchCase.mli b/infer/src/clang/SwitchCase.mli new file mode 100644 index 000000000..b242bfaf2 --- /dev/null +++ b/infer/src/clang/SwitchCase.mli @@ -0,0 +1,23 @@ +(* + * Copyright (c) 2018 - present Facebook, Inc. + * All rights reserved. + * + * This source code is licensed under the BSD style license found in the + * LICENSE file in the root directory of this source tree. An additional grant + * of patent rights can be found in the PATENTS file in the same directory. + *) + +open! IStd +module F = Format + +type condition = Case of Clang_ast_t.stmt | Default + +type t = {condition: condition; stmt_info: Clang_ast_t.stmt_info; root_nodes: Procdesc.Node.t list} + +val in_switch_body : f:('a -> 'b) -> 'a -> t list * 'b + +val add : t -> unit + +val pp_condition : F.formatter -> condition -> unit [@@warning "-32"] + +val pp : F.formatter -> t -> unit [@@warning "-32"] diff --git a/infer/src/clang/cTrans.ml b/infer/src/clang/cTrans.ml index 2f4560aaf..1c1892eeb 100644 --- a/infer/src/clang/cTrans.ml +++ b/infer/src/clang/cTrans.ml @@ -747,14 +747,8 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s let rec labelStmt_trans trans_state stmt_info stmt_list label_name = let context = trans_state.context in - (* go ahead with the translation *) - let res_trans = - match stmt_list with - | [stmt] -> - instruction trans_state stmt - | _ -> - (* expected a stmt or at most a compoundstmt *) assert false - in + let[@warning "-8"] [stmt] = stmt_list in + let res_trans = instruction trans_state stmt in (* create the label root node into the hashtbl *) let sil_loc = CLocation.location_of_stmt_info context.translation_unit_context.source_file stmt_info @@ -1523,7 +1517,8 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s let prune_nodes' = if branch then prune_nodes_t else prune_nodes_f in List.iter ~f:(fun n -> Procdesc.node_set_succs_exn context.procdesc n res_trans.control.root_nodes []) - prune_nodes' + prune_nodes' ; + res_trans in match stmt_list with | [cond; exp1; exp2] -> @@ -1546,8 +1541,12 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s (cond_trans ~if_kind:Sil.Ik_bexp ~negate_cond:false) in (* Note: by contruction prune nodes are leafs_nodes_cond *) - do_branch true exp1 var_typ res_trans_cond.control.leaf_nodes join_node pvar ; - do_branch false exp2 var_typ res_trans_cond.control.leaf_nodes join_node pvar ; + let _ : trans_result = + do_branch true exp1 var_typ res_trans_cond.control.leaf_nodes join_node pvar + in + let _ : trans_result = + do_branch false exp2 var_typ res_trans_cond.control.leaf_nodes join_node pvar + in let id = Ident.create_fresh Ident.knormal in let instrs = [Sil.Load (id, Exp.Lvar pvar, var_typ, sil_loc)] in mk_trans_result (Exp.Var id, typ) @@ -1764,179 +1763,104 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s assert false - (* Assumption: the CompoundStmt can be made of different stmts, not just CaseStmts *) + and caseStmt_trans trans_state stmt_info case_stmt_list = + (* ignore the [case lhs ... rhs: body] form, only support the [case condition: body] form *) + let[@warning "-8"] [condition; _rhs; body] = case_stmt_list in + let body_trans_result = instruction trans_state body in + (let open SwitchCase in + add {condition= Case condition; stmt_info; root_nodes= body_trans_result.control.root_nodes}) ; + body_trans_result + + + and defaultStmt_trans trans_state stmt_info default_stmt_list = + let[@warning "-8"] [body] = default_stmt_list in + let body_trans_result = instruction trans_state body in + (let open SwitchCase in + add {condition= Default; stmt_info; root_nodes= body_trans_result.control.root_nodes}) ; + body_trans_result + + and switchStmt_trans trans_state stmt_info switch_stmt_list = + (* overview: translate the body of the switch statement, which automatically collects the + various cases at the same time, then link up the cases together and together with the switch + condition variable *) + (* unsupported: initialization *) + let[@warning "-8"] [_initialization; variable; condition; body] = switch_stmt_list in let context = trans_state.context in - let succ_nodes = trans_state.succ_nodes in - let continuation = trans_state.continuation in let sil_loc = CLocation.location_of_stmt_info context.translation_unit_context.source_file stmt_info in - let open Clang_ast_t in - match switch_stmt_list with - | [_; decl_stmt; cond; CompoundStmt (stmt_info, stmt_list)] -> - let trans_state_pri = PriorityNode.try_claim_priority_node trans_state stmt_info in - let trans_state' = {trans_state_pri with succ_nodes= []} in - let res_trans_cond_tmp = instruction trans_state' cond in - let switch_special_cond_node = - let node_kind = Procdesc.Node.Stmt_node "Switch_stmt" in - Procdesc.create_node context.procdesc sil_loc node_kind res_trans_cond_tmp.control.instrs - in - List.iter - ~f:(fun n' -> - Procdesc.node_set_succs_exn context.procdesc n' [switch_special_cond_node] [] ) - res_trans_cond_tmp.control.leaf_nodes ; - let root_nodes = - if res_trans_cond_tmp.control.root_nodes <> [] then res_trans_cond_tmp.control.root_nodes - else [switch_special_cond_node] - in - let switch_e_cond', _ = res_trans_cond_tmp.return in - let res_trans_cond = - { res_trans_cond_tmp with - control= - {res_trans_cond_tmp.control with root_nodes; leaf_nodes= [switch_special_cond_node]} - } - in - let res_trans_decl = declStmt_in_condition_trans trans_state decl_stmt res_trans_cond in - let trans_state_no_pri = - if PriorityNode.own_priority_node trans_state_pri.priority stmt_info then - {trans_state_pri with priority= Free} - else trans_state_pri - in - let switch_exit_point = succ_nodes in - let continuation' = - match continuation with - | Some cont -> - Some {cont with break= switch_exit_point} - | None -> - Some {break= switch_exit_point; continue= []; return_temp= false} - in - let trans_state'' = {trans_state_no_pri with continuation= continuation'} in - let merge_into_cases stmt_list = - (* returns list_of_cases * before_any_case_instrs *) - let rec aux rev_stmt_list acc cases = - match rev_stmt_list with - | CaseStmt (info, a :: b :: CaseStmt x :: c) :: rest -> - (* case x: case y: ... *) - if c <> [] (* empty case with nested case, then followed by some instructions *) - then assert false ; - let rest' = CaseStmt (info, [a; b]) :: rest in - let rev_stmt_list' = CaseStmt x :: rest' in - aux rev_stmt_list' acc cases - | CaseStmt (info, a :: b :: DefaultStmt x :: c) :: rest -> - (* case x: default: ... *) - if c <> [] (* empty case with nested case, then followed by some instructions *) - then assert false ; - let rest' = CaseStmt (info, [a; b]) :: rest in - let rev_stmt_list' = DefaultStmt x :: rest' in - aux rev_stmt_list' acc cases - | DefaultStmt (info, CaseStmt x :: c) :: rest -> - (* default: case x: ... *) - if c <> [] (* empty case with nested case, then followed by some instructions *) - then assert false ; - let rest' = DefaultStmt (info, []) :: rest in - let rev_stmt_list' = CaseStmt x :: rest' in - aux rev_stmt_list' acc cases - | CaseStmt (info, a :: b :: c) :: rest -> - aux rest [] (CaseStmt (info, a :: b :: c @ acc) :: cases) - | DefaultStmt (info, c) :: rest -> - (* default is always the last in the list *) - aux rest [] (DefaultStmt (info, c @ acc) :: cases) - | x :: rest -> - aux rest (x :: acc) cases - | [] -> - (cases, acc) + let trans_state_pri = PriorityNode.try_claim_priority_node trans_state stmt_info in + let trans_state' = {trans_state_pri with succ_nodes= []} in + let res_trans_cond_tmp = instruction trans_state' condition in + let switch_node = + let node_kind = Procdesc.Node.Stmt_node "SwitchStmt" in + Procdesc.create_node context.procdesc sil_loc node_kind res_trans_cond_tmp.control.instrs + in + List.iter + ~f:(fun n' -> Procdesc.node_set_succs_exn context.procdesc n' [switch_node] []) + res_trans_cond_tmp.control.leaf_nodes ; + let root_nodes = + if res_trans_cond_tmp.control.root_nodes <> [] then res_trans_cond_tmp.control.root_nodes + else [switch_node] + in + let condition_exp, _ = res_trans_cond_tmp.return in + let condition_result = + { res_trans_cond_tmp with + control= {res_trans_cond_tmp.control with root_nodes; leaf_nodes= [switch_node]} } + in + let variable_result = declStmt_in_condition_trans trans_state variable condition_result in + let trans_state_no_pri = + if PriorityNode.own_priority_node trans_state_pri.priority stmt_info then + {trans_state_pri with priority= Free} + else trans_state_pri + in + let continuation' = + let switch_exit_point = trans_state.succ_nodes in + match trans_state.continuation with + | Some cont -> + Some {cont with break= switch_exit_point} + | None -> + Some {break= switch_exit_point; continue= []; return_temp= false} + in + let inner_trans_state = {trans_state_no_pri with continuation= continuation'} in + let switch_cases, (_: trans_result) = + SwitchCase.in_switch_body ~f:(instruction inner_trans_state) body + in + let link_up_switch_cases curr_succ_nodes = function + | {SwitchCase.condition= Case case_condition; stmt_info; root_nodes} -> + (* create case prune nodes, link the then branch to [root_nodes], the else branch to + [curr_succ_nodes] *) + let trans_state_pri = PriorityNode.try_claim_priority_node inner_trans_state stmt_info in + let res_trans_case_const = instruction trans_state_pri case_condition in + let e_const, _ = res_trans_case_const.return in + let sil_eq_cond = Exp.BinOp (Binop.Eq, condition_exp, e_const) in + let sil_loc = + CLocation.location_of_stmt_info context.translation_unit_context.source_file stmt_info in - aux (List.rev stmt_list) [] [] - in - let list_of_cases, pre_case_stmts = merge_into_cases stmt_list in - let rec connected_instruction rev_instr_list successor_nodes = - (* returns the entry point of the translated set of instr *) - match rev_instr_list with - | [] -> - successor_nodes - | instr :: rest -> - let trans_state''' = {trans_state'' with succ_nodes= successor_nodes} in - let res_trans_instr = instruction trans_state''' instr in - let instr_entry_points = res_trans_instr.control.root_nodes in - connected_instruction rest instr_entry_points - in - let rec translate_and_connect_cases cases next_nodes next_prune_nodes = - let create_prune_nodes_for_case case = - match case with - | CaseStmt (stmt_info, case_const :: _ :: _) -> - let trans_state_pri = - PriorityNode.try_claim_priority_node trans_state'' stmt_info - in - let res_trans_case_const = instruction trans_state_pri case_const in - let e_const, _ = res_trans_case_const.return in - let sil_eq_cond = Exp.BinOp (Binop.Eq, switch_e_cond', e_const) in - let sil_loc = - CLocation.location_of_stmt_info context.translation_unit_context.source_file - stmt_info - in - let true_prune_node = - create_prune_node context.procdesc ~branch:true ~negate_cond:false sil_eq_cond - res_trans_case_const.control.instrs sil_loc Sil.Ik_switch - in - let false_prune_node = - create_prune_node context.procdesc ~branch:false ~negate_cond:true sil_eq_cond - res_trans_case_const.control.instrs sil_loc Sil.Ik_switch - in - (true_prune_node, false_prune_node) - | _ -> - assert false + let true_prune_node = + create_prune_node context.procdesc ~branch:true ~negate_cond:false sil_eq_cond + res_trans_case_const.control.instrs sil_loc Sil.Ik_switch in - match cases with - (* top-down to handle default cases *) - | [] -> - (next_nodes, next_prune_nodes) - | (CaseStmt (_, _ :: _ :: case_content) as case) :: rest -> - let last_nodes, last_prune_nodes = - translate_and_connect_cases rest next_nodes next_prune_nodes - in - let case_entry_point = connected_instruction (List.rev case_content) last_nodes in - (* connects between cases, then continuation has priority about breaks *) - let prune_node_t, prune_node_f = create_prune_nodes_for_case case in - Procdesc.node_set_succs_exn context.procdesc prune_node_t case_entry_point [] ; - Procdesc.node_set_succs_exn context.procdesc prune_node_f last_prune_nodes [] ; - (case_entry_point, [prune_node_t; prune_node_f]) - | DefaultStmt (stmt_info, default_content) :: rest -> - let sil_loc = - CLocation.location_of_stmt_info context.translation_unit_context.source_file - stmt_info - in - let placeholder_entry_point = - Procdesc.create_node context.procdesc sil_loc - (Procdesc.Node.Stmt_node "DefaultStmt_placeholder") [] - in - let last_nodes, last_prune_nodes = - translate_and_connect_cases rest next_nodes [placeholder_entry_point] - in - let default_entry_point = - connected_instruction (List.rev default_content) last_nodes - in - Procdesc.node_set_succs_exn context.procdesc placeholder_entry_point - default_entry_point [] ; - (default_entry_point, last_prune_nodes) - | _ -> - assert false - in - let top_entry_point, top_prune_nodes = - translate_and_connect_cases list_of_cases succ_nodes succ_nodes - in - let _ = connected_instruction (List.rev pre_case_stmts) top_entry_point in - Procdesc.node_set_succs_exn context.procdesc switch_special_cond_node top_prune_nodes [] ; - let top_nodes = res_trans_decl.control.root_nodes in - (* succ_nodes will remove the temps *) - mk_trans_result (mk_fresh_void_exp_typ ()) - {empty_control with root_nodes= top_nodes; leaf_nodes= succ_nodes} - | _ -> - (* TODO(t21762295) this raises sometimes *) - CFrontend_config.incorrect_assumption __POS__ stmt_info.Clang_ast_t.si_source_range - "Unexpected Switch Statement sub-expression list: [%a]" - (Pp.semicolon_seq (Pp.to_string ~f:Clang_ast_j.string_of_stmt)) - switch_stmt_list + let false_prune_node = + create_prune_node context.procdesc ~branch:false ~negate_cond:true sil_eq_cond + res_trans_case_const.control.instrs sil_loc Sil.Ik_switch + in + Procdesc.node_set_succs_exn context.procdesc true_prune_node root_nodes [] ; + Procdesc.node_set_succs_exn context.procdesc false_prune_node curr_succ_nodes [] ; + (* return prune nodes as next roots *) + [true_prune_node; false_prune_node] + | {SwitchCase.condition= Default; root_nodes} -> + (* just return the [root_nodes] to be linked to the previous case's fallthrough *) + root_nodes + in + let cases_root_nodes = + List.fold switch_cases ~init:trans_state.succ_nodes ~f:link_up_switch_cases + in + Procdesc.node_set_succs_exn context.procdesc switch_node cases_root_nodes [] ; + let top_nodes = variable_result.control.root_nodes in + mk_trans_result (mk_fresh_void_exp_typ ()) + {empty_control with root_nodes= top_nodes; leaf_nodes= trans_state.succ_nodes} and stmtExpr_trans trans_state source_range stmt_list = @@ -3213,7 +3137,24 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s "Translating statement '%a' (pointer= '%a')@\n@[" (Pp.to_string ~f:Clang_ast_proj.get_stmt_kind_string) instr pp_pointer instr ; - let trans_result = instruction_aux trans_state instr in + let trans_result = + try instruction_aux trans_state instr with e -> + IExn.reraise_after e ~f:(fun () -> + let {Clang_ast_t.si_source_range}, _ = Clang_ast_proj.get_stmt_tuple instr in + let source_file = + trans_state.context.CContext.translation_unit_context.CFrontend_config.source_file + in + let loc_start = + CLocation.location_of_source_range ~pick_location:`Start source_file si_source_range + in + let loc_end = + CLocation.location_of_source_range ~pick_location:`End source_file si_source_range + in + L.internal_error "%a: ERROR translating statement '%a'@\n" Location.pp_range + (loc_start, loc_end) + (Pp.to_string ~f:Clang_ast_proj.get_stmt_kind_string) + instr ) + in L.(debug Capture Verbose) "@]" ; trans_result @@ -3253,12 +3194,10 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s ifStmt_trans trans_state stmt_info stmt_list | SwitchStmt (stmt_info, switch_stmt_list) -> switchStmt_trans trans_state stmt_info switch_stmt_list - | CaseStmt ({Clang_ast_t.si_source_range}, _) -> - (* where do we even get case stmts outside of the switch stmt? (t21762295) *) - CFrontend_config.incorrect_assumption __POS__ si_source_range - "Case statement outside of switch statement: %a" - (Pp.to_string ~f:Clang_ast_j.string_of_stmt) - instr + | CaseStmt (stmt_info, stmt_list) -> + caseStmt_trans trans_state stmt_info stmt_list + | DefaultStmt (stmt_info, stmt_list) -> + defaultStmt_trans trans_state stmt_info stmt_list | StmtExpr ({Clang_ast_t.si_source_range}, stmt_list, _) -> stmtExpr_trans trans_state si_source_range stmt_list | ForStmt (stmt_info, [init; decl_stmt; condition; increment; body]) -> @@ -3543,8 +3482,7 @@ module CTrans_funct (F : CModule_type.CFrontend) : CModule_type.CTranslation = s | SEHFinallyStmt _ | SEHLeaveStmt _ | SEHTryStmt _ - | ShuffleVectorExpr _ - | DefaultStmt _ -> + | ShuffleVectorExpr _ -> let (stmt_info, stmts), ret_typ = match Clang_ast_proj.get_expr_tuple instr with | Some (stmt_info, stmts, expr_info) -> diff --git a/infer/src/clang/cTrans_utils.mli b/infer/src/clang/cTrans_utils.mli index b111a4243..bb397bba5 100644 --- a/infer/src/clang/cTrans_utils.mli +++ b/infer/src/clang/cTrans_utils.mli @@ -15,7 +15,7 @@ type continuation = { break: Procdesc.Node.t list ; continue: Procdesc.Node.t list ; return_temp: bool - (* true if temps should not be removed in the node but returned to ancestors *) } + (** true if temps should not be removed in the node but returned to ancestors *) } type priority_node = Free | Busy of Clang_ast_t.pointer diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c index 218abbf09..4d24a7dcd 100644 --- a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c @@ -9,10 +9,13 @@ #import -int m1() { +int test_switch1() { int value = 0; + // infinite loop while (value < 10) { switch (value) { + // code before the first case statement gets skipped but can be used to + // declare variables int x = 1; printf("(out)HELLO WORLD!"); x = value + 1; @@ -32,12 +35,10 @@ int m1() { return 0; } -int m2() { +int test_switch2() { int value = 0; switch (value) { - int x = 1; - printf("(out)HELLO WORLD!"); - x = value + 1; + int x; case 0: printf("(0)HELLO WORLD!"); break; @@ -57,7 +58,7 @@ int m2() { return 0; } -int m3() { +int test_switch3() { int value = 0; switch (value) { case 0: @@ -75,12 +76,10 @@ int m3() { return 0; } -int m4() { +int test_switch4() { int value = 0; switch (value) { - int x = 1; - printf("(out)HELLO WORLD!"); - x = value + 1; + int x; case 0: printf("(0)HELLO WORLD!"); break; @@ -100,11 +99,11 @@ int m4() { return 0; } -int m5() { +int test_switch5() { int value = 0; while (value < 10) { switch (value) { - int x = 1; + int x; printf("(out)HELLO WORLD!"); x = value + 1; continue; @@ -116,7 +115,7 @@ int m5() { return 0; } -int m6() { +int test_switch6() { int value = 0; switch (value > 0 ? 1 : 0) { case 0: @@ -136,7 +135,7 @@ int m6() { int getValue() { return 1; } -int m7() { +int test_switch7() { int value = 0; switch (getValue()) { case 0: @@ -154,7 +153,7 @@ int m7() { return 0; } -int m8() { +int test_switch8() { int value = 0; while (value < 10) { switch (getValue() == 0 ? 1 : 2) { @@ -176,19 +175,19 @@ int m8() { return 0; } -int m9() { +int test_switch9() { int value = 0; switch (value) {} return 0; } -int m10() { +int test_switch10() { int value = 0; switch (value = 7) {} return 0; } -int m11() { +int test_switch11() { int value = 0; switch (value = (value == 0 ? 7 : 9)) { case 0: diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c.dot b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c.dot index 973fc6417..485786e3e 100644 --- a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c.dot +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch.c.dot @@ -1,806 +1,764 @@ /* @generated */ digraph cfg { -"getValue.faa0c7b1433b0c97fcdc15fa47c8180f_1" [label="1: Start getValue\nFormals: \nLocals: \n DECLARE_LOCALS(&return); [line 137, column 1]\n " color=yellow style=filled] +"getValue.faa0c7b1433b0c97fcdc15fa47c8180f_1" [label="1: Start getValue\nFormals: \nLocals: \n DECLARE_LOCALS(&return); [line 136, column 1]\n " color=yellow style=filled] "getValue.faa0c7b1433b0c97fcdc15fa47c8180f_1" -> "getValue.faa0c7b1433b0c97fcdc15fa47c8180f_3" ; "getValue.faa0c7b1433b0c97fcdc15fa47c8180f_2" [label="2: Exit getValue \n " color=yellow style=filled] -"getValue.faa0c7b1433b0c97fcdc15fa47c8180f_3" [label="3: Return Stmt \n *&return:int=1 [line 137, column 18]\n " shape="box"] +"getValue.faa0c7b1433b0c97fcdc15fa47c8180f_3" [label="3: Return Stmt \n *&return:int=1 [line 136, column 18]\n " shape="box"] "getValue.faa0c7b1433b0c97fcdc15fa47c8180f_3" -> "getValue.faa0c7b1433b0c97fcdc15fa47c8180f_2" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_1" [label="1: Start m1\nFormals: \nLocals: x:int value:int \n DECLARE_LOCALS(&return,&x,&value); [line 12, column 1]\n " color=yellow style=filled] +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_1" [label="1: Start test_switch1\nFormals: \nLocals: x:int value:int \n DECLARE_LOCALS(&return,&x,&value); [line 12, column 1]\n " color=yellow style=filled] - "m1.ae7be26cdaa742ca148068d5ac90eaca_1" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_23" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_2" [label="2: Exit m1 \n " color=yellow style=filled] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_1" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_22" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_2" [label="2: Exit test_switch1 \n " color=yellow style=filled] -"m1.ae7be26cdaa742ca148068d5ac90eaca_3" [label="3: Return Stmt \n *&return:int=0 [line 32, column 3]\n " shape="box"] +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_3" [label="3: Return Stmt \n *&return:int=0 [line 35, column 3]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_3" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_2" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_4" [label="4: + \n " ] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_3" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_2" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" [label="4: + \n " ] - "m1.ae7be26cdaa742ca148068d5ac90eaca_4" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_5" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 14, column 10]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_5" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 15, column 10]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_5" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_6" ; - "m1.ae7be26cdaa742ca148068d5ac90eaca_5" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_7" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 14, column 10]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_5" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_6" ; + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_5" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_7" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 15, column 10]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_6" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_9" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 14, column 10]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_6" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_9" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 15, column 10]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_7" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_3" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_8" [label="8: Call _fun_printf \n n$1=_fun_printf(\"(after_switch)HELLO WORLD!\":char const *) [line 30, column 5]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_7" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_3" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_8" [label="8: Call _fun_printf \n n$1=_fun_printf(\"(after_switch)HELLO WORLD!\":char const *) [line 33, column 5]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_8" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_4" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_9" [label="9: Switch_stmt \n n$2=*&value:int [line 15, column 13]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_8" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_9" [label="9: SwitchStmt \n n$2=*&value:int [line 16, column 13]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_9" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_18" ; - "m1.ae7be26cdaa742ca148068d5ac90eaca_9" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_19" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_10" [label="10: DefaultStmt_placeholder \n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_9" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_20" ; + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_9" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_21" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_10" [label="10: Call _fun_printf \n n$4=_fun_printf(\"(2/def)HELLO WORLD!\":char const *) [line 30, column 9]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_10" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_11" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_11" [label="11: Call _fun_printf \n n$4=_fun_printf(\"(2/def)HELLO WORLD!\":char const *) [line 27, column 9]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_10" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_11" [label="11: Call _fun_printf \n n$6=_fun_printf(\"(1)HELLO WORLD!\":char const *) [line 26, column 9]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_11" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_4" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_12" [label="12: Prune (true branch, switch) \n PRUNE((n$2 == 2), true); [line 25, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_11" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_12" [label="12: Call _fun_printf \n n$8=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 23, column 9]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_12" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_11" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$2 == 2), false); [line 25, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_12" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_8" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_13" [label="13: BinaryOperatorStmt: Assign \n n$9=*&value:int [line 21, column 11]\n *&x:int=(n$9 + 1) [line 21, column 7]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_13" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_10" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_14" [label="14: Call _fun_printf \n n$6=_fun_printf(\"(1)HELLO WORLD!\":char const *) [line 23, column 9]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_13" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_12" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_14" [label="14: Call _fun_printf \n n$10=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 20, column 7]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_14" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_4" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_15" [label="15: Prune (true branch, switch) \n PRUNE((n$2 == 1), true); [line 22, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_14" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_13" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_15" [label="15: DeclStmt \n *&x:int=1 [line 19, column 7]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_15" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_14" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$2 == 1), false); [line 22, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_15" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_14" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_16" [label="16: Prune (true branch, switch) \n PRUNE((n$2 == 2), true); [line 28, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_16" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_12" ; - "m1.ae7be26cdaa742ca148068d5ac90eaca_16" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_13" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_17" [label="17: Call _fun_printf \n n$8=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 20, column 9]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_16" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_10" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_17" [label="17: Prune (false branch, switch) \n PRUNE(!(n$2 == 2), false); [line 28, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_17" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_8" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_18" [label="18: Prune (true branch, switch) \n PRUNE((n$2 == 0), true); [line 19, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_17" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_10" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_18" [label="18: Prune (true branch, switch) \n PRUNE((n$2 == 1), true); [line 25, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_18" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_17" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_19" [label="19: Prune (false branch, switch) \n PRUNE(!(n$2 == 0), false); [line 19, column 7]\n " shape="invhouse"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_18" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_11" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_19" [label="19: Prune (false branch, switch) \n PRUNE(!(n$2 == 1), false); [line 25, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_19" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_15" ; - "m1.ae7be26cdaa742ca148068d5ac90eaca_19" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_16" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_20" [label="20: BinaryOperatorStmt: Assign \n n$9=*&value:int [line 18, column 11]\n *&x:int=(n$9 + 1) [line 18, column 7]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_19" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_16" ; + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_19" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_17" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_20" [label="20: Prune (true branch, switch) \n PRUNE((n$2 == 0), true); [line 22, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_20" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_17" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_21" [label="21: Call _fun_printf \n n$10=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 17, column 7]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_20" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_12" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_21" [label="21: Prune (false branch, switch) \n PRUNE(!(n$2 == 0), false); [line 22, column 7]\n " shape="invhouse"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_21" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_20" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_22" [label="22: DeclStmt \n *&x:int=1 [line 16, column 7]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_21" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_18" ; + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_21" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_19" ; +"test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_22" [label="22: DeclStmt \n *&value:int=0 [line 13, column 3]\n " shape="box"] - "m1.ae7be26cdaa742ca148068d5ac90eaca_22" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_21" ; -"m1.ae7be26cdaa742ca148068d5ac90eaca_23" [label="23: DeclStmt \n *&value:int=0 [line 13, column 3]\n " shape="box"] + "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_22" -> "test_switch1.7c92c7e14d1a0ee28a9ab29b22df5d3f_4" ; +"test_switch10.8a4170d3888102a2491712a5ad55ad8d_1" [label="1: Start test_switch10\nFormals: \nLocals: value:int \n DECLARE_LOCALS(&return,&value); [line 184, column 1]\n " color=yellow style=filled] - "m1.ae7be26cdaa742ca148068d5ac90eaca_23" -> "m1.ae7be26cdaa742ca148068d5ac90eaca_4" ; -"m10.e66050aa5d0a7e0ecb49429ea4b0a32b_1" [label="1: Start m10\nFormals: \nLocals: value:int \n DECLARE_LOCALS(&return,&value); [line 185, column 1]\n " color=yellow style=filled] + "test_switch10.8a4170d3888102a2491712a5ad55ad8d_1" -> "test_switch10.8a4170d3888102a2491712a5ad55ad8d_5" ; +"test_switch10.8a4170d3888102a2491712a5ad55ad8d_2" [label="2: Exit test_switch10 \n " color=yellow style=filled] - "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_1" -> "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_5" ; -"m10.e66050aa5d0a7e0ecb49429ea4b0a32b_2" [label="2: Exit m10 \n " color=yellow style=filled] +"test_switch10.8a4170d3888102a2491712a5ad55ad8d_3" [label="3: Return Stmt \n *&return:int=0 [line 187, column 3]\n " shape="box"] -"m10.e66050aa5d0a7e0ecb49429ea4b0a32b_3" [label="3: Return Stmt \n *&return:int=0 [line 188, column 3]\n " shape="box"] + "test_switch10.8a4170d3888102a2491712a5ad55ad8d_3" -> "test_switch10.8a4170d3888102a2491712a5ad55ad8d_2" ; +"test_switch10.8a4170d3888102a2491712a5ad55ad8d_4" [label="4: SwitchStmt \n *&value:int=7 [line 186, column 11]\n n$0=*&value:int [line 186, column 11]\n " shape="box"] - "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_3" -> "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_2" ; -"m10.e66050aa5d0a7e0ecb49429ea4b0a32b_4" [label="4: Switch_stmt \n *&value:int=7 [line 187, column 11]\n n$0=*&value:int [line 187, column 11]\n " shape="box"] + "test_switch10.8a4170d3888102a2491712a5ad55ad8d_4" -> "test_switch10.8a4170d3888102a2491712a5ad55ad8d_3" ; +"test_switch10.8a4170d3888102a2491712a5ad55ad8d_5" [label="5: DeclStmt \n *&value:int=0 [line 185, column 3]\n " shape="box"] - "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_4" -> "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_3" ; -"m10.e66050aa5d0a7e0ecb49429ea4b0a32b_5" [label="5: DeclStmt \n *&value:int=0 [line 186, column 3]\n " shape="box"] + "test_switch10.8a4170d3888102a2491712a5ad55ad8d_5" -> "test_switch10.8a4170d3888102a2491712a5ad55ad8d_4" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_1" [label="1: Start test_switch11\nFormals: \nLocals: 0$?%__sil_tmpSIL_temp_conditional___n$0:int value:int \n DECLARE_LOCALS(&return,&0$?%__sil_tmpSIL_temp_conditional___n$0,&value); [line 190, column 1]\n " color=yellow style=filled] - "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_5" -> "m10.e66050aa5d0a7e0ecb49429ea4b0a32b_4" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_1" [label="1: Start m11\nFormals: \nLocals: 0$?%__sil_tmpSIL_temp_conditional___n$0:int value:int \n DECLARE_LOCALS(&return,&0$?%__sil_tmpSIL_temp_conditional___n$0,&value); [line 191, column 1]\n " color=yellow style=filled] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_1" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_14" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_2" [label="2: Exit test_switch11 \n " color=yellow style=filled] - "m11.c4534fe0ca256b331e9a3f14fe17229d_1" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_14" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_2" [label="2: Exit m11 \n " color=yellow style=filled] +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_3" [label="3: Return Stmt \n *&return:int=0 [line 196, column 3]\n " shape="box"] -"m11.c4534fe0ca256b331e9a3f14fe17229d_3" [label="3: Return Stmt \n *&return:int=0 [line 197, column 3]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_3" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_2" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_4" [label="4: + \n " ] - "m11.c4534fe0ca256b331e9a3f14fe17229d_3" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_2" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_4" [label="4: + \n " ] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_4" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_10" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_5" [label="5: BinaryOperatorStmt: EQ \n n$1=*&value:int [line 192, column 20]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_4" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_10" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_5" [label="5: BinaryOperatorStmt: EQ \n n$1=*&value:int [line 193, column 20]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_5" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_6" ; + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_5" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_7" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_6" [label="6: Prune (true branch, boolean exp) \n PRUNE((n$1 == 0), true); [line 192, column 20]\n " shape="invhouse"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_5" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_6" ; - "m11.c4534fe0ca256b331e9a3f14fe17229d_5" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_7" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_6" [label="6: Prune (true branch, boolean exp) \n PRUNE((n$1 == 0), true); [line 193, column 20]\n " shape="invhouse"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_6" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_8" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_7" [label="7: Prune (false branch, boolean exp) \n PRUNE(!(n$1 == 0), false); [line 192, column 20]\n " shape="invhouse"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_6" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_8" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_7" [label="7: Prune (false branch, boolean exp) \n PRUNE(!(n$1 == 0), false); [line 193, column 20]\n " shape="invhouse"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_7" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_9" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_8" [label="8: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=7 [line 192, column 20]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_7" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_9" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_8" [label="8: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=7 [line 193, column 20]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_8" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_4" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_9" [label="9: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=9 [line 192, column 20]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_8" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_4" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_9" [label="9: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=9 [line 193, column 20]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_9" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_4" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_10" [label="10: SwitchStmt \n n$2=*&0$?%__sil_tmpSIL_temp_conditional___n$0:int [line 192, column 20]\n *&value:int=n$2 [line 192, column 11]\n n$3=*&value:int [line 192, column 11]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_9" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_4" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_10" [label="10: Switch_stmt \n n$2=*&0$?%__sil_tmpSIL_temp_conditional___n$0:int [line 193, column 20]\n *&value:int=n$2 [line 193, column 11]\n n$3=*&value:int [line 193, column 11]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_10" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_12" ; + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_10" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_13" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_11" [label="11: Call _fun_printf \n n$4=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 194, column 7]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_10" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_12" ; - "m11.c4534fe0ca256b331e9a3f14fe17229d_10" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_13" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_11" [label="11: Call _fun_printf \n n$4=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 195, column 7]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_11" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_3" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_12" [label="12: Prune (true branch, switch) \n PRUNE((n$3 == 0), true); [line 193, column 5]\n " shape="invhouse"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_11" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_3" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_12" [label="12: Prune (true branch, switch) \n PRUNE((n$3 == 0), true); [line 194, column 5]\n " shape="invhouse"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_12" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_11" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$3 == 0), false); [line 193, column 5]\n " shape="invhouse"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_12" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_11" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$3 == 0), false); [line 194, column 5]\n " shape="invhouse"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_13" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_3" ; +"test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_14" [label="14: DeclStmt \n *&value:int=0 [line 191, column 3]\n " shape="box"] - "m11.c4534fe0ca256b331e9a3f14fe17229d_13" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_3" ; -"m11.c4534fe0ca256b331e9a3f14fe17229d_14" [label="14: DeclStmt \n *&value:int=0 [line 192, column 3]\n " shape="box"] + "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_14" -> "test_switch11.a1a6d859e414d268a57ed2a2bb6f8a8e_5" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_1" [label="1: Start test_switch2\nFormals: \nLocals: something:int z:int x:int value:int \n DECLARE_LOCALS(&return,&something,&z,&x,&value); [line 38, column 1]\n " color=yellow style=filled] - "m11.c4534fe0ca256b331e9a3f14fe17229d_14" -> "m11.c4534fe0ca256b331e9a3f14fe17229d_5" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_1" [label="1: Start m2\nFormals: \nLocals: something:int z:int x:int value:int \n DECLARE_LOCALS(&return,&something,&z,&x,&value); [line 35, column 1]\n " color=yellow style=filled] + "test_switch2.0717c55583f10f472ddb2d73d867e556_1" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_18" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_2" [label="2: Exit test_switch2 \n " color=yellow style=filled] - "m2.aaf2f89992379705dac844c0a2a1d45f_1" -> "m2.aaf2f89992379705dac844c0a2a1d45f_22" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_2" [label="2: Exit m2 \n " color=yellow style=filled] +"test_switch2.0717c55583f10f472ddb2d73d867e556_3" [label="3: Return Stmt \n *&return:int=0 [line 58, column 3]\n " shape="box"] -"m2.aaf2f89992379705dac844c0a2a1d45f_3" [label="3: Return Stmt \n *&return:int=0 [line 57, column 3]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_3" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_2" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_4" [label="4: SwitchStmt \n n$0=*&value:int [line 40, column 11]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_3" -> "m2.aaf2f89992379705dac844c0a2a1d45f_2" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_4" [label="4: Switch_stmt \n n$0=*&value:int [line 37, column 11]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_4" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_16" ; + "test_switch2.0717c55583f10f472ddb2d73d867e556_4" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_17" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_5" [label="5: BinaryOperatorStmt: Assign \n *&z:int=42 [line 52, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_4" -> "m2.aaf2f89992379705dac844c0a2a1d45f_17" ; - "m2.aaf2f89992379705dac844c0a2a1d45f_4" -> "m2.aaf2f89992379705dac844c0a2a1d45f_18" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_5" [label="5: DefaultStmt_placeholder \n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_5" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_3" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_6" [label="6: UnaryOperator \n n$3=*&something:int [line 50, column 7]\n *&something:int=(n$3 + 1) [line 50, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_5" -> "m2.aaf2f89992379705dac844c0a2a1d45f_12" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_6" [label="6: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 54, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_6" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_5" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_7" [label="7: DeclStmt \n *&something:int=1 [line 49, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_6" -> "m2.aaf2f89992379705dac844c0a2a1d45f_3" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_7" [label="7: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 54, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_7" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_6" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_8" [label="8: DeclStmt \n *&z:int=9 [line 45, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_7" -> "m2.aaf2f89992379705dac844c0a2a1d45f_5" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_8" [label="8: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 53, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_8" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_7" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_9" [label="9: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 43, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_8" -> "m2.aaf2f89992379705dac844c0a2a1d45f_3" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_9" [label="9: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 53, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_9" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_3" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_10" [label="10: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 55, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_9" -> "m2.aaf2f89992379705dac844c0a2a1d45f_6" ; - "m2.aaf2f89992379705dac844c0a2a1d45f_9" -> "m2.aaf2f89992379705dac844c0a2a1d45f_7" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_10" [label="10: BinaryOperatorStmt: Assign \n *&z:int=42 [line 51, column 7]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_10" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_3" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_11" [label="11: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 55, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_10" -> "m2.aaf2f89992379705dac844c0a2a1d45f_3" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_11" [label="11: UnaryOperator \n n$3=*&something:int [line 49, column 7]\n *&something:int=(n$3 + 1) [line 49, column 7]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_11" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_3" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_12" [label="12: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 54, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_11" -> "m2.aaf2f89992379705dac844c0a2a1d45f_10" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_12" [label="12: DeclStmt \n *&something:int=1 [line 48, column 7]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_12" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_3" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 54, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_12" -> "m2.aaf2f89992379705dac844c0a2a1d45f_11" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_13" [label="13: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 47, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_13" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_10" ; + "test_switch2.0717c55583f10f472ddb2d73d867e556_13" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_11" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_14" [label="14: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 48, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_13" -> "m2.aaf2f89992379705dac844c0a2a1d45f_12" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 47, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_14" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_7" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_15" [label="15: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 48, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_14" -> "m2.aaf2f89992379705dac844c0a2a1d45f_8" ; - "m2.aaf2f89992379705dac844c0a2a1d45f_14" -> "m2.aaf2f89992379705dac844c0a2a1d45f_9" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_15" [label="15: DeclStmt \n *&z:int=9 [line 44, column 7]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_15" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_12" ; + "test_switch2.0717c55583f10f472ddb2d73d867e556_15" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_13" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_16" [label="16: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 42, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_15" -> "m2.aaf2f89992379705dac844c0a2a1d45f_12" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_16" [label="16: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 42, column 7]\n " shape="box"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_16" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_9" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_17" [label="17: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 42, column 5]\n " shape="invhouse"] - "m2.aaf2f89992379705dac844c0a2a1d45f_16" -> "m2.aaf2f89992379705dac844c0a2a1d45f_3" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_17" [label="17: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 41, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_17" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_7" ; +"test_switch2.0717c55583f10f472ddb2d73d867e556_18" [label="18: DeclStmt \n *&value:int=0 [line 39, column 3]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_17" -> "m2.aaf2f89992379705dac844c0a2a1d45f_16" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_18" [label="18: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 41, column 5]\n " shape="invhouse"] + "test_switch2.0717c55583f10f472ddb2d73d867e556_18" -> "test_switch2.0717c55583f10f472ddb2d73d867e556_4" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_1" [label="1: Start test_switch3\nFormals: \nLocals: z:int something:int value:int \n DECLARE_LOCALS(&return,&z,&something,&value); [line 61, column 1]\n " color=yellow style=filled] - "m2.aaf2f89992379705dac844c0a2a1d45f_18" -> "m2.aaf2f89992379705dac844c0a2a1d45f_13" ; - "m2.aaf2f89992379705dac844c0a2a1d45f_18" -> "m2.aaf2f89992379705dac844c0a2a1d45f_14" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_19" [label="19: BinaryOperatorStmt: Assign \n n$6=*&value:int [line 40, column 9]\n *&x:int=(n$6 + 1) [line 40, column 5]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_1" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_17" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_2" [label="2: Exit test_switch3 \n " color=yellow style=filled] - "m2.aaf2f89992379705dac844c0a2a1d45f_19" -> "m2.aaf2f89992379705dac844c0a2a1d45f_16" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_20" [label="20: Call _fun_printf \n n$7=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 39, column 5]\n " shape="box"] +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" [label="3: Return Stmt \n *&return:int=0 [line 76, column 3]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_20" -> "m2.aaf2f89992379705dac844c0a2a1d45f_19" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_21" [label="21: DeclStmt \n *&x:int=1 [line 38, column 5]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_2" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_4" [label="4: SwitchStmt \n n$0=*&value:int [line 63, column 11]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_21" -> "m2.aaf2f89992379705dac844c0a2a1d45f_20" ; -"m2.aaf2f89992379705dac844c0a2a1d45f_22" [label="22: DeclStmt \n *&value:int=0 [line 36, column 3]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_4" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_15" ; + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_4" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_16" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_5" [label="5: DeclStmt \n *&z:int=9 [line 71, column 7]\n " shape="box"] - "m2.aaf2f89992379705dac844c0a2a1d45f_22" -> "m2.aaf2f89992379705dac844c0a2a1d45f_4" ; -"m3.9678f7a7939f457fa0d9353761e189c7_1" [label="1: Start m3\nFormals: \nLocals: z:int something:int value:int \n DECLARE_LOCALS(&return,&z,&something,&value); [line 60, column 1]\n " color=yellow style=filled] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_5" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_6" [label="6: UnaryOperator \n n$3=*&something:int [line 69, column 7]\n *&something:int=(n$3 + 1) [line 69, column 7]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_1" -> "m3.9678f7a7939f457fa0d9353761e189c7_17" ; -"m3.9678f7a7939f457fa0d9353761e189c7_2" [label="2: Exit m3 \n " color=yellow style=filled] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_6" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_7" [label="7: DeclStmt \n *&something:int=1 [line 68, column 7]\n " shape="box"] -"m3.9678f7a7939f457fa0d9353761e189c7_3" [label="3: Return Stmt \n *&return:int=0 [line 75, column 3]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_7" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_6" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_8" [label="8: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 65, column 7]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_3" -> "m3.9678f7a7939f457fa0d9353761e189c7_2" ; -"m3.9678f7a7939f457fa0d9353761e189c7_4" [label="4: Switch_stmt \n n$0=*&value:int [line 62, column 11]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_8" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_9" [label="9: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 73, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_4" -> "m3.9678f7a7939f457fa0d9353761e189c7_15" ; - "m3.9678f7a7939f457fa0d9353761e189c7_4" -> "m3.9678f7a7939f457fa0d9353761e189c7_16" ; -"m3.9678f7a7939f457fa0d9353761e189c7_5" [label="5: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 72, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_9" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_10" [label="10: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 73, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_5" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_6" [label="6: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 72, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_10" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_11" [label="11: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 72, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_6" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_7" [label="7: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 71, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_11" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_3" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_12" [label="12: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 72, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_7" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_8" [label="8: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 71, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_12" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_9" ; + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_12" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_10" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_13" [label="13: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 67, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_8" -> "m3.9678f7a7939f457fa0d9353761e189c7_5" ; - "m3.9678f7a7939f457fa0d9353761e189c7_8" -> "m3.9678f7a7939f457fa0d9353761e189c7_6" ; -"m3.9678f7a7939f457fa0d9353761e189c7_9" [label="9: DeclStmt \n *&z:int=9 [line 70, column 7]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_13" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_7" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 67, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_9" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_10" [label="10: UnaryOperator \n n$3=*&something:int [line 68, column 7]\n *&something:int=(n$3 + 1) [line 68, column 7]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_14" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_11" ; + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_14" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_12" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_15" [label="15: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 64, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_10" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_11" [label="11: DeclStmt \n *&something:int=1 [line 67, column 7]\n " shape="box"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_15" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_8" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 64, column 5]\n " shape="invhouse"] - "m3.9678f7a7939f457fa0d9353761e189c7_11" -> "m3.9678f7a7939f457fa0d9353761e189c7_10" ; -"m3.9678f7a7939f457fa0d9353761e189c7_12" [label="12: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 66, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_16" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_13" ; + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_16" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_14" ; +"test_switch3.d602e3f7cc0068667fd33a3e54ff193c_17" [label="17: DeclStmt \n *&value:int=0 [line 62, column 3]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_12" -> "m3.9678f7a7939f457fa0d9353761e189c7_11" ; -"m3.9678f7a7939f457fa0d9353761e189c7_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 66, column 5]\n " shape="invhouse"] + "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_17" -> "test_switch3.d602e3f7cc0068667fd33a3e54ff193c_4" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_1" [label="1: Start test_switch4\nFormals: \nLocals: something:int z:int x:int value:int \n DECLARE_LOCALS(&return,&something,&z,&x,&value); [line 79, column 1]\n " color=yellow style=filled] - "m3.9678f7a7939f457fa0d9353761e189c7_13" -> "m3.9678f7a7939f457fa0d9353761e189c7_7" ; - "m3.9678f7a7939f457fa0d9353761e189c7_13" -> "m3.9678f7a7939f457fa0d9353761e189c7_8" ; -"m3.9678f7a7939f457fa0d9353761e189c7_14" [label="14: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 64, column 7]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_1" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_18" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_2" [label="2: Exit test_switch4 \n " color=yellow style=filled] - "m3.9678f7a7939f457fa0d9353761e189c7_14" -> "m3.9678f7a7939f457fa0d9353761e189c7_3" ; -"m3.9678f7a7939f457fa0d9353761e189c7_15" [label="15: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 63, column 5]\n " shape="invhouse"] +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" [label="3: Return Stmt \n *&return:int=0 [line 99, column 3]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_15" -> "m3.9678f7a7939f457fa0d9353761e189c7_14" ; -"m3.9678f7a7939f457fa0d9353761e189c7_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 63, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_2" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_4" [label="4: SwitchStmt \n n$0=*&value:int [line 81, column 11]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_16" -> "m3.9678f7a7939f457fa0d9353761e189c7_12" ; - "m3.9678f7a7939f457fa0d9353761e189c7_16" -> "m3.9678f7a7939f457fa0d9353761e189c7_13" ; -"m3.9678f7a7939f457fa0d9353761e189c7_17" [label="17: DeclStmt \n *&value:int=0 [line 61, column 3]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_4" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_16" ; + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_4" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_17" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_5" [label="5: BinaryOperatorStmt: Assign \n *&z:int=42 [line 93, column 7]\n " shape="box"] - "m3.9678f7a7939f457fa0d9353761e189c7_17" -> "m3.9678f7a7939f457fa0d9353761e189c7_4" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_1" [label="1: Start m4\nFormals: \nLocals: something:int z:int x:int value:int \n DECLARE_LOCALS(&return,&something,&z,&x,&value); [line 78, column 1]\n " color=yellow style=filled] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_5" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_6" [label="6: UnaryOperator \n n$3=*&something:int [line 91, column 7]\n *&something:int=(n$3 + 1) [line 91, column 7]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_1" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_22" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_2" [label="2: Exit m4 \n " color=yellow style=filled] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_6" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_5" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_7" [label="7: DeclStmt \n *&something:int=1 [line 90, column 7]\n " shape="box"] -"m4.fd6b6fc9220b72d21683ae8e4f50a210_3" [label="3: Return Stmt \n *&return:int=0 [line 100, column 3]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_7" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_6" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_8" [label="8: DeclStmt \n *&z:int=9 [line 86, column 7]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_3" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_2" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_4" [label="4: Switch_stmt \n n$0=*&value:int [line 80, column 11]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_8" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_7" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_9" [label="9: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 84, column 7]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_4" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_17" ; - "m4.fd6b6fc9220b72d21683ae8e4f50a210_4" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_18" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_5" [label="5: DefaultStmt_placeholder \n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_9" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_10" [label="10: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 96, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_5" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_12" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_6" [label="6: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 97, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_10" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_11" [label="11: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 96, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_6" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_3" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_7" [label="7: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 97, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_11" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_12" [label="12: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 95, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_7" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_5" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_8" [label="8: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 96, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_12" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_3" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 95, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_8" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_3" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_9" [label="9: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 96, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_13" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_10" ; + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_13" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_11" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_14" [label="14: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 89, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_9" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_6" ; - "m4.fd6b6fc9220b72d21683ae8e4f50a210_9" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_7" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_10" [label="10: BinaryOperatorStmt: Assign \n *&z:int=42 [line 94, column 7]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_14" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_7" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_15" [label="15: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 89, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_10" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_3" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_11" [label="11: UnaryOperator \n n$3=*&something:int [line 92, column 7]\n *&something:int=(n$3 + 1) [line 92, column 7]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_15" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_12" ; + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_15" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_13" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_16" [label="16: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 83, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_11" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_10" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_12" [label="12: DeclStmt \n *&something:int=1 [line 91, column 7]\n " shape="box"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_16" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_9" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_17" [label="17: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 83, column 5]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_12" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_11" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_13" [label="13: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 90, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_17" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_7" ; +"test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_18" [label="18: DeclStmt \n *&value:int=0 [line 80, column 3]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_13" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_12" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 90, column 5]\n " shape="invhouse"] + "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_18" -> "test_switch4.70d4e6e8539e8d1ee3505d4562bc236d_4" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_1" [label="1: Start test_switch5\nFormals: \nLocals: x:int value:int \n DECLARE_LOCALS(&return,&x,&value); [line 102, column 1]\n " color=yellow style=filled] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_14" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_8" ; - "m4.fd6b6fc9220b72d21683ae8e4f50a210_14" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_9" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_15" [label="15: DeclStmt \n *&z:int=9 [line 87, column 7]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_1" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_14" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_2" [label="2: Exit test_switch5 \n " color=yellow style=filled] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_15" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_12" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_16" [label="16: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 85, column 7]\n " shape="box"] +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_3" [label="3: Return Stmt \n *&return:int=0 [line 115, column 3]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_16" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_3" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_17" [label="17: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 84, column 5]\n " shape="invhouse"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_3" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_2" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" [label="4: + \n " ] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_17" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_16" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_18" [label="18: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 84, column 5]\n " shape="invhouse"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_5" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 104, column 10]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_18" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_13" ; - "m4.fd6b6fc9220b72d21683ae8e4f50a210_18" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_14" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_19" [label="19: BinaryOperatorStmt: Assign \n n$6=*&value:int [line 83, column 9]\n *&x:int=(n$6 + 1) [line 83, column 5]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_5" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_6" ; + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_5" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_7" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 104, column 10]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_19" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_16" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_20" [label="20: Call _fun_printf \n n$7=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 82, column 5]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_6" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_8" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 104, column 10]\n " shape="invhouse"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_20" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_19" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_21" [label="21: DeclStmt \n *&x:int=1 [line 81, column 5]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_7" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_3" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_8" [label="8: SwitchStmt \n n$1=*&value:int [line 105, column 13]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_21" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_20" ; -"m4.fd6b6fc9220b72d21683ae8e4f50a210_22" [label="22: DeclStmt \n *&value:int=0 [line 79, column 3]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_8" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_12" ; + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_8" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_13" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_9" [label="9: Call _fun_printf \n n$3=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 111, column 9]\n " shape="box"] - "m4.fd6b6fc9220b72d21683ae8e4f50a210_22" -> "m4.fd6b6fc9220b72d21683ae8e4f50a210_4" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_1" [label="1: Start m5\nFormals: \nLocals: x:int value:int \n DECLARE_LOCALS(&return,&x,&value); [line 103, column 1]\n " color=yellow style=filled] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_9" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_10" [label="10: BinaryOperatorStmt: Assign \n n$5=*&value:int [line 108, column 11]\n *&x:int=(n$5 + 1) [line 108, column 7]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_1" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_15" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_2" [label="2: Exit m5 \n " color=yellow style=filled] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_10" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_11" [label="11: Call _fun_printf \n n$6=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 107, column 7]\n " shape="box"] -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_3" [label="3: Return Stmt \n *&return:int=0 [line 116, column 3]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_11" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_10" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_12" [label="12: Prune (true branch, switch) \n PRUNE((n$1 == 0), true); [line 110, column 7]\n " shape="invhouse"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_3" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_2" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" [label="4: + \n " ] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_12" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_9" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$1 == 0), false); [line 110, column 7]\n " shape="invhouse"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_5" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 105, column 10]\n " shape="box"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_13" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" ; +"test_switch5.1d93fcc376cd01517eabe22cb325bcfd_14" [label="14: DeclStmt \n *&value:int=0 [line 103, column 3]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_5" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_6" ; - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_5" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_7" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 105, column 10]\n " shape="invhouse"] + "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_14" -> "test_switch5.1d93fcc376cd01517eabe22cb325bcfd_4" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_1" [label="1: Start test_switch6\nFormals: \nLocals: 0$?%__sil_tmpSIL_temp_conditional___n$0:int z:int something:int value:int \n DECLARE_LOCALS(&return,&0$?%__sil_tmpSIL_temp_conditional___n$0,&z,&something,&value); [line 118, column 1]\n " color=yellow style=filled] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_6" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_8" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 105, column 10]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_1" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_23" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_2" [label="2: Exit test_switch6 \n " color=yellow style=filled] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_7" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_3" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_8" [label="8: Switch_stmt \n n$1=*&value:int [line 106, column 13]\n " shape="box"] +"test_switch6.a23e54b3840073f4ece330ef3c560915_3" [label="3: Return Stmt \n *&return:int=0 [line 133, column 3]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_8" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_10" ; - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_8" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_11" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_9" [label="9: Call _fun_printf \n n$3=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 112, column 9]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_3" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_2" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_4" [label="4: + \n " ] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_9" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_10" [label="10: Prune (true branch, switch) \n PRUNE((n$1 == 0), true); [line 111, column 7]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_4" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_10" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_5" [label="5: BinaryOperatorStmt: GT \n n$1=*&value:int [line 120, column 11]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_10" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_9" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_11" [label="11: Prune (false branch, switch) \n PRUNE(!(n$1 == 0), false); [line 111, column 7]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_5" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_6" ; + "test_switch6.a23e54b3840073f4ece330ef3c560915_5" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_7" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_6" [label="6: Prune (true branch, boolean exp) \n PRUNE((n$1 > 0), true); [line 120, column 11]\n " shape="invhouse"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_11" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_12" [label="12: BinaryOperatorStmt: Assign \n n$5=*&value:int [line 109, column 11]\n *&x:int=(n$5 + 1) [line 109, column 7]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_6" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_8" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_7" [label="7: Prune (false branch, boolean exp) \n PRUNE(!(n$1 > 0), false); [line 120, column 11]\n " shape="invhouse"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_12" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_13" [label="13: Call _fun_printf \n n$6=_fun_printf(\"(out)HELLO WORLD!\":char const *) [line 108, column 7]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_7" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_9" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_8" [label="8: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=1 [line 120, column 11]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_13" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_12" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_14" [label="14: DeclStmt \n *&x:int=1 [line 107, column 7]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_8" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_4" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_9" [label="9: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=0 [line 120, column 11]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_14" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_13" ; -"m5.7b1f6dff14d8c2dfeb7da9487be0612d_15" [label="15: DeclStmt \n *&value:int=0 [line 104, column 3]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_9" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_4" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_10" [label="10: SwitchStmt \n n$2=*&0$?%__sil_tmpSIL_temp_conditional___n$0:int [line 120, column 11]\n " shape="box"] - "m5.7b1f6dff14d8c2dfeb7da9487be0612d_15" -> "m5.7b1f6dff14d8c2dfeb7da9487be0612d_4" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_1" [label="1: Start m6\nFormals: \nLocals: 0$?%__sil_tmpSIL_temp_conditional___n$0:int z:int something:int value:int \n DECLARE_LOCALS(&return,&0$?%__sil_tmpSIL_temp_conditional___n$0,&z,&something,&value); [line 119, column 1]\n " color=yellow style=filled] + "test_switch6.a23e54b3840073f4ece330ef3c560915_10" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_21" ; + "test_switch6.a23e54b3840073f4ece330ef3c560915_10" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_22" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_11" [label="11: DeclStmt \n *&z:int=9 [line 128, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_1" -> "m6.36604411a85db2bd9e97e22bfb5b692d_23" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_2" [label="2: Exit m6 \n " color=yellow style=filled] + "test_switch6.a23e54b3840073f4ece330ef3c560915_11" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_12" [label="12: UnaryOperator \n n$5=*&something:int [line 126, column 7]\n *&something:int=(n$5 + 1) [line 126, column 7]\n " shape="box"] -"m6.36604411a85db2bd9e97e22bfb5b692d_3" [label="3: Return Stmt \n *&return:int=0 [line 134, column 3]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_12" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_13" [label="13: DeclStmt \n *&something:int=1 [line 125, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_3" -> "m6.36604411a85db2bd9e97e22bfb5b692d_2" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_4" [label="4: + \n " ] + "test_switch6.a23e54b3840073f4ece330ef3c560915_13" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_12" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_14" [label="14: Call _fun_printf \n n$7=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 122, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_4" -> "m6.36604411a85db2bd9e97e22bfb5b692d_10" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_5" [label="5: BinaryOperatorStmt: GT \n n$1=*&value:int [line 121, column 11]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_14" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_15" [label="15: Prune (true branch, switch) \n PRUNE((n$2 == 3), true); [line 130, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_5" -> "m6.36604411a85db2bd9e97e22bfb5b692d_6" ; - "m6.36604411a85db2bd9e97e22bfb5b692d_5" -> "m6.36604411a85db2bd9e97e22bfb5b692d_7" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_6" [label="6: Prune (true branch, boolean exp) \n PRUNE((n$1 > 0), true); [line 121, column 11]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_15" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$2 == 3), false); [line 130, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_6" -> "m6.36604411a85db2bd9e97e22bfb5b692d_8" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_7" [label="7: Prune (false branch, boolean exp) \n PRUNE(!(n$1 > 0), false); [line 121, column 11]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_16" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_17" [label="17: Prune (true branch, switch) \n PRUNE((n$2 == 2), true); [line 129, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_7" -> "m6.36604411a85db2bd9e97e22bfb5b692d_9" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_8" [label="8: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=1 [line 121, column 11]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_17" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_3" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_18" [label="18: Prune (false branch, switch) \n PRUNE(!(n$2 == 2), false); [line 129, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_8" -> "m6.36604411a85db2bd9e97e22bfb5b692d_4" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_9" [label="9: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$0:int=0 [line 121, column 11]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_18" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_15" ; + "test_switch6.a23e54b3840073f4ece330ef3c560915_18" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_16" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_19" [label="19: Prune (true branch, switch) \n PRUNE((n$2 == 1), true); [line 124, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_9" -> "m6.36604411a85db2bd9e97e22bfb5b692d_4" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_10" [label="10: Switch_stmt \n n$2=*&0$?%__sil_tmpSIL_temp_conditional___n$0:int [line 121, column 11]\n " shape="box"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_19" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_13" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_20" [label="20: Prune (false branch, switch) \n PRUNE(!(n$2 == 1), false); [line 124, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_10" -> "m6.36604411a85db2bd9e97e22bfb5b692d_21" ; - "m6.36604411a85db2bd9e97e22bfb5b692d_10" -> "m6.36604411a85db2bd9e97e22bfb5b692d_22" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_11" [label="11: Prune (true branch, switch) \n PRUNE((n$2 == 3), true); [line 131, column 5]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_20" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_17" ; + "test_switch6.a23e54b3840073f4ece330ef3c560915_20" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_18" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_21" [label="21: Prune (true branch, switch) \n PRUNE((n$2 == 0), true); [line 121, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_11" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_12" [label="12: Prune (false branch, switch) \n PRUNE(!(n$2 == 3), false); [line 131, column 5]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_21" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_14" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_22" [label="22: Prune (false branch, switch) \n PRUNE(!(n$2 == 0), false); [line 121, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_12" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_13" [label="13: Prune (true branch, switch) \n PRUNE((n$2 == 2), true); [line 130, column 5]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_22" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_19" ; + "test_switch6.a23e54b3840073f4ece330ef3c560915_22" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_20" ; +"test_switch6.a23e54b3840073f4ece330ef3c560915_23" [label="23: DeclStmt \n *&value:int=0 [line 119, column 3]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_13" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$2 == 2), false); [line 130, column 5]\n " shape="invhouse"] + "test_switch6.a23e54b3840073f4ece330ef3c560915_23" -> "test_switch6.a23e54b3840073f4ece330ef3c560915_5" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_1" [label="1: Start test_switch7\nFormals: \nLocals: z:int something:int value:int \n DECLARE_LOCALS(&return,&z,&something,&value); [line 138, column 1]\n " color=yellow style=filled] - "m6.36604411a85db2bd9e97e22bfb5b692d_14" -> "m6.36604411a85db2bd9e97e22bfb5b692d_11" ; - "m6.36604411a85db2bd9e97e22bfb5b692d_14" -> "m6.36604411a85db2bd9e97e22bfb5b692d_12" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_15" [label="15: DeclStmt \n *&z:int=9 [line 129, column 7]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_1" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_17" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_2" [label="2: Exit test_switch7 \n " color=yellow style=filled] - "m6.36604411a85db2bd9e97e22bfb5b692d_15" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_16" [label="16: UnaryOperator \n n$5=*&something:int [line 127, column 7]\n *&something:int=(n$5 + 1) [line 127, column 7]\n " shape="box"] +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" [label="3: Return Stmt \n *&return:int=0 [line 153, column 3]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_16" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_17" [label="17: DeclStmt \n *&something:int=1 [line 126, column 7]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_2" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_4" [label="4: SwitchStmt \n n$0=_fun_getValue() [line 140, column 11]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_17" -> "m6.36604411a85db2bd9e97e22bfb5b692d_16" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_18" [label="18: Prune (true branch, switch) \n PRUNE((n$2 == 1), true); [line 125, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_4" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_15" ; + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_4" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_16" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_5" [label="5: DeclStmt \n *&z:int=9 [line 148, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_18" -> "m6.36604411a85db2bd9e97e22bfb5b692d_17" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_19" [label="19: Prune (false branch, switch) \n PRUNE(!(n$2 == 1), false); [line 125, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_5" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_6" [label="6: UnaryOperator \n n$3=*&something:int [line 146, column 7]\n *&something:int=(n$3 + 1) [line 146, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_19" -> "m6.36604411a85db2bd9e97e22bfb5b692d_13" ; - "m6.36604411a85db2bd9e97e22bfb5b692d_19" -> "m6.36604411a85db2bd9e97e22bfb5b692d_14" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_20" [label="20: Call _fun_printf \n n$7=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 123, column 7]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_6" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_7" [label="7: DeclStmt \n *&something:int=1 [line 145, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_20" -> "m6.36604411a85db2bd9e97e22bfb5b692d_3" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_21" [label="21: Prune (true branch, switch) \n PRUNE((n$2 == 0), true); [line 122, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_7" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_6" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_8" [label="8: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 142, column 7]\n " shape="box"] - "m6.36604411a85db2bd9e97e22bfb5b692d_21" -> "m6.36604411a85db2bd9e97e22bfb5b692d_20" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_22" [label="22: Prune (false branch, switch) \n PRUNE(!(n$2 == 0), false); [line 122, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_8" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_9" [label="9: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 150, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_22" -> "m6.36604411a85db2bd9e97e22bfb5b692d_18" ; - "m6.36604411a85db2bd9e97e22bfb5b692d_22" -> "m6.36604411a85db2bd9e97e22bfb5b692d_19" ; -"m6.36604411a85db2bd9e97e22bfb5b692d_23" [label="23: DeclStmt \n *&value:int=0 [line 120, column 3]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_9" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_10" [label="10: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 150, column 5]\n " shape="invhouse"] - "m6.36604411a85db2bd9e97e22bfb5b692d_23" -> "m6.36604411a85db2bd9e97e22bfb5b692d_5" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_1" [label="1: Start m7\nFormals: \nLocals: z:int something:int value:int \n DECLARE_LOCALS(&return,&z,&something,&value); [line 139, column 1]\n " color=yellow style=filled] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_10" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_11" [label="11: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 149, column 5]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_1" -> "m7.0449904fbf32607bf8ce5c26823dbc29_17" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_2" [label="2: Exit m7 \n " color=yellow style=filled] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_11" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_3" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_12" [label="12: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 149, column 5]\n " shape="invhouse"] -"m7.0449904fbf32607bf8ce5c26823dbc29_3" [label="3: Return Stmt \n *&return:int=0 [line 154, column 3]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_12" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_9" ; + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_12" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_10" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_13" [label="13: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 144, column 5]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_3" -> "m7.0449904fbf32607bf8ce5c26823dbc29_2" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_4" [label="4: Switch_stmt \n n$0=_fun_getValue() [line 141, column 11]\n " shape="box"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_13" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_7" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 144, column 5]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_4" -> "m7.0449904fbf32607bf8ce5c26823dbc29_15" ; - "m7.0449904fbf32607bf8ce5c26823dbc29_4" -> "m7.0449904fbf32607bf8ce5c26823dbc29_16" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_5" [label="5: Prune (true branch, switch) \n PRUNE((n$0 == 3), true); [line 151, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_14" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_11" ; + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_14" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_12" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_15" [label="15: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 141, column 5]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_5" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_6" [label="6: Prune (false branch, switch) \n PRUNE(!(n$0 == 3), false); [line 151, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_15" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_8" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 141, column 5]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_6" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_7" [label="7: Prune (true branch, switch) \n PRUNE((n$0 == 2), true); [line 150, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_16" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_13" ; + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_16" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_14" ; +"test_switch7.8298274f5578f21bdddf71ffa79afcb8_17" [label="17: DeclStmt \n *&value:int=0 [line 139, column 3]\n " shape="box"] - "m7.0449904fbf32607bf8ce5c26823dbc29_7" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_8" [label="8: Prune (false branch, switch) \n PRUNE(!(n$0 == 2), false); [line 150, column 5]\n " shape="invhouse"] + "test_switch7.8298274f5578f21bdddf71ffa79afcb8_17" -> "test_switch7.8298274f5578f21bdddf71ffa79afcb8_4" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_1" [label="1: Start test_switch8\nFormals: \nLocals: a:int 0$?%__sil_tmpSIL_temp_conditional___n$1:int z:int something:int value:int \n DECLARE_LOCALS(&return,&a,&0$?%__sil_tmpSIL_temp_conditional___n$1,&z,&something,&value); [line 156, column 1]\n " color=yellow style=filled] - "m7.0449904fbf32607bf8ce5c26823dbc29_8" -> "m7.0449904fbf32607bf8ce5c26823dbc29_5" ; - "m7.0449904fbf32607bf8ce5c26823dbc29_8" -> "m7.0449904fbf32607bf8ce5c26823dbc29_6" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_9" [label="9: DeclStmt \n *&z:int=9 [line 149, column 7]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_1" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_29" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_2" [label="2: Exit test_switch8 \n " color=yellow style=filled] - "m7.0449904fbf32607bf8ce5c26823dbc29_9" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_10" [label="10: UnaryOperator \n n$3=*&something:int [line 147, column 7]\n *&something:int=(n$3 + 1) [line 147, column 7]\n " shape="box"] +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_3" [label="3: Return Stmt \n *&return:int=0 [line 175, column 3]\n " shape="box"] - "m7.0449904fbf32607bf8ce5c26823dbc29_10" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_11" [label="11: DeclStmt \n *&something:int=1 [line 146, column 7]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_3" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_2" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_4" [label="4: + \n " ] - "m7.0449904fbf32607bf8ce5c26823dbc29_11" -> "m7.0449904fbf32607bf8ce5c26823dbc29_10" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_12" [label="12: Prune (true branch, switch) \n PRUNE((n$0 == 1), true); [line 145, column 5]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_4" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_5" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 158, column 10]\n " shape="box"] - "m7.0449904fbf32607bf8ce5c26823dbc29_12" -> "m7.0449904fbf32607bf8ce5c26823dbc29_11" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$0 == 1), false); [line 145, column 5]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_5" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_6" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_5" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_7" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 158, column 10]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_13" -> "m7.0449904fbf32607bf8ce5c26823dbc29_7" ; - "m7.0449904fbf32607bf8ce5c26823dbc29_13" -> "m7.0449904fbf32607bf8ce5c26823dbc29_8" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_14" [label="14: Call _fun_printf \n n$5=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 143, column 7]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_6" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_10" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 158, column 10]\n " shape="invhouse"] - "m7.0449904fbf32607bf8ce5c26823dbc29_14" -> "m7.0449904fbf32607bf8ce5c26823dbc29_3" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_15" [label="15: Prune (true branch, switch) \n PRUNE((n$0 == 0), true); [line 142, column 5]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_7" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_3" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" [label="8: DeclStmt \n *&a:int=0 [line 173, column 5]\n " shape="box"] - "m7.0449904fbf32607bf8ce5c26823dbc29_15" -> "m7.0449904fbf32607bf8ce5c26823dbc29_14" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$0 == 0), false); [line 142, column 5]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_4" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_9" [label="9: + \n " ] - "m7.0449904fbf32607bf8ce5c26823dbc29_16" -> "m7.0449904fbf32607bf8ce5c26823dbc29_12" ; - "m7.0449904fbf32607bf8ce5c26823dbc29_16" -> "m7.0449904fbf32607bf8ce5c26823dbc29_13" ; -"m7.0449904fbf32607bf8ce5c26823dbc29_17" [label="17: DeclStmt \n *&value:int=0 [line 140, column 3]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_9" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_15" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_10" [label="10: BinaryOperatorStmt: EQ \n n$2=_fun_getValue() [line 159, column 13]\n " shape="box"] - "m7.0449904fbf32607bf8ce5c26823dbc29_17" -> "m7.0449904fbf32607bf8ce5c26823dbc29_4" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_1" [label="1: Start m8\nFormals: \nLocals: a:int 0$?%__sil_tmpSIL_temp_conditional___n$1:int z:int something:int value:int \n DECLARE_LOCALS(&return,&a,&0$?%__sil_tmpSIL_temp_conditional___n$1,&z,&something,&value); [line 157, column 1]\n " color=yellow style=filled] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_10" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_11" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_10" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_12" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_11" [label="11: Prune (true branch, boolean exp) \n PRUNE((n$2 == 0), true); [line 159, column 13]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_1" -> "m8.980b79c2a71b9bcc117e08a990b5b332_29" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_2" [label="2: Exit m8 \n " color=yellow style=filled] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_11" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_13" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_12" [label="12: Prune (false branch, boolean exp) \n PRUNE(!(n$2 == 0), false); [line 159, column 13]\n " shape="invhouse"] -"m8.980b79c2a71b9bcc117e08a990b5b332_3" [label="3: Return Stmt \n *&return:int=0 [line 176, column 3]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_12" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_14" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_13" [label="13: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$1:int=1 [line 159, column 13]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_3" -> "m8.980b79c2a71b9bcc117e08a990b5b332_2" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_4" [label="4: + \n " ] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_13" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_9" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_14" [label="14: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$1:int=2 [line 159, column 13]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_4" -> "m8.980b79c2a71b9bcc117e08a990b5b332_5" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_5" [label="5: BinaryOperatorStmt: LT \n n$0=*&value:int [line 159, column 10]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_14" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_9" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_15" [label="15: SwitchStmt \n n$3=*&0$?%__sil_tmpSIL_temp_conditional___n$1:int [line 159, column 13]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_5" -> "m8.980b79c2a71b9bcc117e08a990b5b332_6" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_5" -> "m8.980b79c2a71b9bcc117e08a990b5b332_7" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_6" [label="6: Prune (true branch, while) \n PRUNE((n$0 < 10), true); [line 159, column 10]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_15" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_27" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_15" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_28" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_16" [label="16: DeclStmt \n *&z:int=9 [line 168, column 9]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_6" -> "m8.980b79c2a71b9bcc117e08a990b5b332_10" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_7" [label="7: Prune (false branch, while) \n PRUNE(!(n$0 < 10), false); [line 159, column 10]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_16" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_17" [label="17: UnaryOperator \n n$7=*&something:int [line 165, column 9]\n *&something:int=(n$7 + 1) [line 165, column 9]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_7" -> "m8.980b79c2a71b9bcc117e08a990b5b332_3" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_8" [label="8: DeclStmt \n *&a:int=0 [line 174, column 5]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_17" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_4" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_18" [label="18: DeclStmt \n *&something:int=1 [line 164, column 9]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_8" -> "m8.980b79c2a71b9bcc117e08a990b5b332_4" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_9" [label="9: + \n " ] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_18" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_17" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_19" [label="19: Return Stmt \n *&return:int=0 [line 162, column 9]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_9" -> "m8.980b79c2a71b9bcc117e08a990b5b332_15" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_10" [label="10: BinaryOperatorStmt: EQ \n n$2=_fun_getValue() [line 160, column 13]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_19" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_2" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_20" [label="20: Call _fun_printf \n n$8=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 161, column 9]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_10" -> "m8.980b79c2a71b9bcc117e08a990b5b332_11" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_10" -> "m8.980b79c2a71b9bcc117e08a990b5b332_12" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_11" [label="11: Prune (true branch, boolean exp) \n PRUNE((n$2 == 0), true); [line 160, column 13]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_20" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_19" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_21" [label="21: Prune (true branch, switch) \n PRUNE((n$3 == 3), true); [line 170, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_11" -> "m8.980b79c2a71b9bcc117e08a990b5b332_13" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_12" [label="12: Prune (false branch, boolean exp) \n PRUNE(!(n$2 == 0), false); [line 160, column 13]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_21" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_22" [label="22: Prune (false branch, switch) \n PRUNE(!(n$3 == 3), false); [line 170, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_12" -> "m8.980b79c2a71b9bcc117e08a990b5b332_14" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_13" [label="13: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$1:int=1 [line 160, column 13]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_22" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_23" [label="23: Prune (true branch, switch) \n PRUNE((n$3 == 2), true); [line 169, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_13" -> "m8.980b79c2a71b9bcc117e08a990b5b332_9" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_14" [label="14: ConditionalStmt Branch \n *&0$?%__sil_tmpSIL_temp_conditional___n$1:int=2 [line 160, column 13]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_23" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_8" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_24" [label="24: Prune (false branch, switch) \n PRUNE(!(n$3 == 2), false); [line 169, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_14" -> "m8.980b79c2a71b9bcc117e08a990b5b332_9" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_15" [label="15: Switch_stmt \n n$3=*&0$?%__sil_tmpSIL_temp_conditional___n$1:int [line 160, column 13]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_24" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_21" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_24" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_22" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_25" [label="25: Prune (true branch, switch) \n PRUNE((n$3 == 1), true); [line 163, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_15" -> "m8.980b79c2a71b9bcc117e08a990b5b332_27" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_15" -> "m8.980b79c2a71b9bcc117e08a990b5b332_28" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_16" [label="16: Prune (true branch, switch) \n PRUNE((n$3 == 3), true); [line 171, column 7]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_25" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_18" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_26" [label="26: Prune (false branch, switch) \n PRUNE(!(n$3 == 1), false); [line 163, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_16" -> "m8.980b79c2a71b9bcc117e08a990b5b332_8" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_17" [label="17: Prune (false branch, switch) \n PRUNE(!(n$3 == 3), false); [line 171, column 7]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_26" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_23" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_26" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_24" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_27" [label="27: Prune (true branch, switch) \n PRUNE((n$3 == 0), true); [line 160, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_17" -> "m8.980b79c2a71b9bcc117e08a990b5b332_8" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_18" [label="18: Prune (true branch, switch) \n PRUNE((n$3 == 2), true); [line 170, column 7]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_27" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_20" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_28" [label="28: Prune (false branch, switch) \n PRUNE(!(n$3 == 0), false); [line 160, column 7]\n " shape="invhouse"] - "m8.980b79c2a71b9bcc117e08a990b5b332_18" -> "m8.980b79c2a71b9bcc117e08a990b5b332_8" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_19" [label="19: Prune (false branch, switch) \n PRUNE(!(n$3 == 2), false); [line 170, column 7]\n " shape="invhouse"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_28" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_25" ; + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_28" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_26" ; +"test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_29" [label="29: DeclStmt \n *&value:int=0 [line 157, column 3]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_19" -> "m8.980b79c2a71b9bcc117e08a990b5b332_16" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_19" -> "m8.980b79c2a71b9bcc117e08a990b5b332_17" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_20" [label="20: DeclStmt \n *&z:int=9 [line 169, column 9]\n " shape="box"] + "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_29" -> "test_switch8.6a6653773b94c1bb3f3c90dc1790d1ed_4" ; +"test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_1" [label="1: Start test_switch9\nFormals: \nLocals: value:int \n DECLARE_LOCALS(&return,&value); [line 178, column 1]\n " color=yellow style=filled] - "m8.980b79c2a71b9bcc117e08a990b5b332_20" -> "m8.980b79c2a71b9bcc117e08a990b5b332_8" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_21" [label="21: UnaryOperator \n n$7=*&something:int [line 166, column 9]\n *&something:int=(n$7 + 1) [line 166, column 9]\n " shape="box"] + "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_1" -> "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_5" ; +"test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_2" [label="2: Exit test_switch9 \n " color=yellow style=filled] - "m8.980b79c2a71b9bcc117e08a990b5b332_21" -> "m8.980b79c2a71b9bcc117e08a990b5b332_4" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_22" [label="22: DeclStmt \n *&something:int=1 [line 165, column 9]\n " shape="box"] +"test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_3" [label="3: Return Stmt \n *&return:int=0 [line 181, column 3]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_22" -> "m8.980b79c2a71b9bcc117e08a990b5b332_21" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_23" [label="23: Prune (true branch, switch) \n PRUNE((n$3 == 1), true); [line 164, column 7]\n " shape="invhouse"] + "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_3" -> "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_2" ; +"test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_4" [label="4: SwitchStmt \n n$0=*&value:int [line 180, column 11]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_23" -> "m8.980b79c2a71b9bcc117e08a990b5b332_22" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_24" [label="24: Prune (false branch, switch) \n PRUNE(!(n$3 == 1), false); [line 164, column 7]\n " shape="invhouse"] + "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_4" -> "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_3" ; +"test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_5" [label="5: DeclStmt \n *&value:int=0 [line 179, column 3]\n " shape="box"] - "m8.980b79c2a71b9bcc117e08a990b5b332_24" -> "m8.980b79c2a71b9bcc117e08a990b5b332_18" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_24" -> "m8.980b79c2a71b9bcc117e08a990b5b332_19" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_25" [label="25: Return Stmt \n *&return:int=0 [line 163, column 9]\n " shape="box"] - - - "m8.980b79c2a71b9bcc117e08a990b5b332_25" -> "m8.980b79c2a71b9bcc117e08a990b5b332_2" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_26" [label="26: Call _fun_printf \n n$8=_fun_printf(\"(0)HELLO WORLD!\":char const *) [line 162, column 9]\n " shape="box"] - - - "m8.980b79c2a71b9bcc117e08a990b5b332_26" -> "m8.980b79c2a71b9bcc117e08a990b5b332_25" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_27" [label="27: Prune (true branch, switch) \n PRUNE((n$3 == 0), true); [line 161, column 7]\n " shape="invhouse"] - - - "m8.980b79c2a71b9bcc117e08a990b5b332_27" -> "m8.980b79c2a71b9bcc117e08a990b5b332_26" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_28" [label="28: Prune (false branch, switch) \n PRUNE(!(n$3 == 0), false); [line 161, column 7]\n " shape="invhouse"] - - - "m8.980b79c2a71b9bcc117e08a990b5b332_28" -> "m8.980b79c2a71b9bcc117e08a990b5b332_23" ; - "m8.980b79c2a71b9bcc117e08a990b5b332_28" -> "m8.980b79c2a71b9bcc117e08a990b5b332_24" ; -"m8.980b79c2a71b9bcc117e08a990b5b332_29" [label="29: DeclStmt \n *&value:int=0 [line 158, column 3]\n " shape="box"] - - - "m8.980b79c2a71b9bcc117e08a990b5b332_29" -> "m8.980b79c2a71b9bcc117e08a990b5b332_4" ; -"m9.5bbb291cc1e38a051365ee9edb7cbd14_1" [label="1: Start m9\nFormals: \nLocals: value:int \n DECLARE_LOCALS(&return,&value); [line 179, column 1]\n " color=yellow style=filled] - - - "m9.5bbb291cc1e38a051365ee9edb7cbd14_1" -> "m9.5bbb291cc1e38a051365ee9edb7cbd14_5" ; -"m9.5bbb291cc1e38a051365ee9edb7cbd14_2" [label="2: Exit m9 \n " color=yellow style=filled] - - -"m9.5bbb291cc1e38a051365ee9edb7cbd14_3" [label="3: Return Stmt \n *&return:int=0 [line 182, column 3]\n " shape="box"] - - - "m9.5bbb291cc1e38a051365ee9edb7cbd14_3" -> "m9.5bbb291cc1e38a051365ee9edb7cbd14_2" ; -"m9.5bbb291cc1e38a051365ee9edb7cbd14_4" [label="4: Switch_stmt \n n$0=*&value:int [line 181, column 11]\n " shape="box"] - - - "m9.5bbb291cc1e38a051365ee9edb7cbd14_4" -> "m9.5bbb291cc1e38a051365ee9edb7cbd14_3" ; -"m9.5bbb291cc1e38a051365ee9edb7cbd14_5" [label="5: DeclStmt \n *&value:int=0 [line 180, column 3]\n " shape="box"] - - - "m9.5bbb291cc1e38a051365ee9edb7cbd14_5" -> "m9.5bbb291cc1e38a051365ee9edb7cbd14_4" ; + "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_5" -> "test_switch9.f4a96f02ca05cf92a483f69cdfe717b1_4" ; } diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c new file mode 100644 index 000000000..1ac8c7199 --- /dev/null +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c @@ -0,0 +1,27 @@ +/* + * Copyright (c) 2018 - present Facebook, Inc. + * All rights reserved. + * + * This source code is licensed under the BSD style license found in the + * LICENSE file in the root directory of this source tree. An additional grant + * of patent rights can be found in the PATENTS file in the same directory. + */ +int unroll_loop(int n) { + int ret = 0; + int loop = n + 3 / 4; + switch (n % 8) { + case 0: + do { + ret++; + case 3: + ret++; + if (1) { + case 2: + ret++; + } + case 1: + ret++; + } while (--loop > 0); + } + return ret; +} diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c.dot b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c.dot new file mode 100644 index 000000000..a5d8f681a --- /dev/null +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_unroll.c.dot @@ -0,0 +1,108 @@ +/* @generated */ +digraph cfg { +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_1" [label="1: Start unroll_loop\nFormals: n:int\nLocals: loop:int ret:int \n DECLARE_LOCALS(&return,&loop,&ret); [line 9, column 1]\n " color=yellow style=filled] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_1" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_25" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_2" [label="2: Exit unroll_loop \n " color=yellow style=filled] + + +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_3" [label="3: Return Stmt \n n$0=*&ret:int [line 26, column 10]\n *&return:int=n$0 [line 26, column 3]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_3" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_2" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_4" [label="4: SwitchStmt \n n$1=*&n:int [line 12, column 11]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_4" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_22" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_4" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_23" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_5" [label="5: + \n " ] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_5" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_15" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_6" [label="6: BinaryOperatorStmt: GT \n n$2=*&loop:int [line 24, column 16]\n *&loop:int=(n$2 - 1) [line 24, column 16]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_6" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_7" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_6" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_8" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_7" [label="7: Prune (true branch, do while) \n PRUNE(((n$2 - 1) > 0), true); [line 24, column 16]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_7" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_5" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_8" [label="8: Prune (false branch, do while) \n PRUNE(!((n$2 - 1) > 0), false); [line 24, column 16]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_8" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_3" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_9" [label="9: UnaryOperator \n n$3=*&ret:int [line 23, column 11]\n *&ret:int=(n$3 + 1) [line 23, column 11]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_9" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_6" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_10" [label="10: + \n " ] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_10" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_9" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_11" [label="11: Prune (true branch, if) \n PRUNE(1, true); [line 18, column 15]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_11" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_13" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_12" [label="12: Prune (false branch, if) \n PRUNE(!1, false); [line 18, column 15]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_12" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_10" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_13" [label="13: UnaryOperator \n n$4=*&ret:int [line 20, column 15]\n *&ret:int=(n$4 + 1) [line 20, column 15]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_13" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_10" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_14" [label="14: UnaryOperator \n n$7=*&ret:int [line 17, column 11]\n *&ret:int=(n$7 + 1) [line 17, column 11]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_14" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_11" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_14" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_12" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_15" [label="15: UnaryOperator \n n$8=*&ret:int [line 15, column 9]\n *&ret:int=(n$8 + 1) [line 15, column 9]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_15" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_14" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_16" [label="16: Prune (true branch, switch) \n PRUNE(((n$1 % 8) == 1), true); [line 22, column 9]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_16" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_9" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_17" [label="17: Prune (false branch, switch) \n PRUNE(!((n$1 % 8) == 1), false); [line 22, column 9]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_17" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_3" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_18" [label="18: Prune (true branch, switch) \n PRUNE(((n$1 % 8) == 2), true); [line 19, column 13]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_18" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_13" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_19" [label="19: Prune (false branch, switch) \n PRUNE(!((n$1 % 8) == 2), false); [line 19, column 13]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_19" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_16" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_19" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_17" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_20" [label="20: Prune (true branch, switch) \n PRUNE(((n$1 % 8) == 3), true); [line 16, column 9]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_20" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_14" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_21" [label="21: Prune (false branch, switch) \n PRUNE(!((n$1 % 8) == 3), false); [line 16, column 9]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_21" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_18" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_21" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_19" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_22" [label="22: Prune (true branch, switch) \n PRUNE(((n$1 % 8) == 0), true); [line 13, column 5]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_22" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_5" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_23" [label="23: Prune (false branch, switch) \n PRUNE(!((n$1 % 8) == 0), false); [line 13, column 5]\n " shape="invhouse"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_23" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_20" ; + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_23" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_21" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_24" [label="24: DeclStmt \n n$11=*&n:int [line 11, column 14]\n *&loop:int=(n$11 + (3 / 4)) [line 11, column 3]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_24" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_4" ; +"unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_25" [label="25: DeclStmt \n *&ret:int=0 [line 10, column 3]\n " shape="box"] + + + "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_25" -> "unroll_loop.7d9e50ecf5e5106a8dd5deee005639d6_24" ; +} diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c new file mode 100644 index 000000000..97540761c --- /dev/null +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c @@ -0,0 +1,39 @@ +/* + * Copyright (c) 2018 - present Facebook, Inc. + * All rights reserved. + * + * This source code is licensed under the BSD style license found in the + * LICENSE file in the root directory of this source tree. An additional grant + * of patent rights can be found in the PATENTS file in the same directory. + */ + +int label_default(char x) { + int ret = 0; + switch (x) { + case 1: + ret++; + goto l; + case 2: + ret = 2; + break; + l: + default: + ret--; + } + return ret; +} + +int label_case(char x) { + int ret = 0; + switch (x) { + case 1: + ret++; + goto l; + l: + case 2: + case 3: + ret++; + break; + } + return ret; +} diff --git a/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c.dot b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c.dot new file mode 100644 index 000000000..d9728177e --- /dev/null +++ b/infer/tests/codetoanalyze/c/frontend/switchstmt/switch_with_labels.c.dot @@ -0,0 +1,114 @@ +/* @generated */ +digraph cfg { +"label_case.83d07a314df100648248d9156212096b_1" [label="1: Start label_case\nFormals: x:char\nLocals: ret:int \n DECLARE_LOCALS(&return,&ret); [line 26, column 1]\n " color=yellow style=filled] + + + "label_case.83d07a314df100648248d9156212096b_1" -> "label_case.83d07a314df100648248d9156212096b_14" ; +"label_case.83d07a314df100648248d9156212096b_2" [label="2: Exit label_case \n " color=yellow style=filled] + + +"label_case.83d07a314df100648248d9156212096b_3" [label="3: Return Stmt \n n$0=*&ret:int [line 38, column 10]\n *&return:int=n$0 [line 38, column 3]\n " shape="box"] + + + "label_case.83d07a314df100648248d9156212096b_3" -> "label_case.83d07a314df100648248d9156212096b_2" ; +"label_case.83d07a314df100648248d9156212096b_4" [label="4: SwitchStmt \n n$1=*&x:char [line 28, column 11]\n " shape="box"] + + + "label_case.83d07a314df100648248d9156212096b_4" -> "label_case.83d07a314df100648248d9156212096b_12" ; + "label_case.83d07a314df100648248d9156212096b_4" -> "label_case.83d07a314df100648248d9156212096b_13" ; +"label_case.83d07a314df100648248d9156212096b_5" [label="5: UnaryOperator \n n$3=*&ret:int [line 35, column 7]\n *&ret:int=(n$3 + 1) [line 35, column 7]\n " shape="box"] + + + "label_case.83d07a314df100648248d9156212096b_5" -> "label_case.83d07a314df100648248d9156212096b_3" ; +"label_case.83d07a314df100648248d9156212096b_6" [label="6: Skip GotoLabel_l \n " color="gray"] + + + "label_case.83d07a314df100648248d9156212096b_6" -> "label_case.83d07a314df100648248d9156212096b_5" ; +"label_case.83d07a314df100648248d9156212096b_7" [label="7: UnaryOperator \n n$6=*&ret:int [line 30, column 7]\n *&ret:int=(n$6 + 1) [line 30, column 7]\n " shape="box"] + + + "label_case.83d07a314df100648248d9156212096b_7" -> "label_case.83d07a314df100648248d9156212096b_6" ; +"label_case.83d07a314df100648248d9156212096b_8" [label="8: Prune (true branch, switch) \n PRUNE((n$1 == 3), true); [line 34, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_8" -> "label_case.83d07a314df100648248d9156212096b_5" ; +"label_case.83d07a314df100648248d9156212096b_9" [label="9: Prune (false branch, switch) \n PRUNE(!(n$1 == 3), false); [line 34, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_9" -> "label_case.83d07a314df100648248d9156212096b_3" ; +"label_case.83d07a314df100648248d9156212096b_10" [label="10: Prune (true branch, switch) \n PRUNE((n$1 == 2), true); [line 33, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_10" -> "label_case.83d07a314df100648248d9156212096b_5" ; +"label_case.83d07a314df100648248d9156212096b_11" [label="11: Prune (false branch, switch) \n PRUNE(!(n$1 == 2), false); [line 33, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_11" -> "label_case.83d07a314df100648248d9156212096b_8" ; + "label_case.83d07a314df100648248d9156212096b_11" -> "label_case.83d07a314df100648248d9156212096b_9" ; +"label_case.83d07a314df100648248d9156212096b_12" [label="12: Prune (true branch, switch) \n PRUNE((n$1 == 1), true); [line 29, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_12" -> "label_case.83d07a314df100648248d9156212096b_7" ; +"label_case.83d07a314df100648248d9156212096b_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$1 == 1), false); [line 29, column 5]\n " shape="invhouse"] + + + "label_case.83d07a314df100648248d9156212096b_13" -> "label_case.83d07a314df100648248d9156212096b_10" ; + "label_case.83d07a314df100648248d9156212096b_13" -> "label_case.83d07a314df100648248d9156212096b_11" ; +"label_case.83d07a314df100648248d9156212096b_14" [label="14: DeclStmt \n *&ret:int=0 [line 27, column 3]\n " shape="box"] + + + "label_case.83d07a314df100648248d9156212096b_14" -> "label_case.83d07a314df100648248d9156212096b_4" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_1" [label="1: Start label_default\nFormals: x:char\nLocals: ret:int \n DECLARE_LOCALS(&return,&ret); [line 10, column 1]\n " color=yellow style=filled] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_1" -> "label_default.f30729864b0243c0a794ef0254fe7d23_13" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_2" [label="2: Exit label_default \n " color=yellow style=filled] + + +"label_default.f30729864b0243c0a794ef0254fe7d23_3" [label="3: Return Stmt \n n$0=*&ret:int [line 23, column 10]\n *&return:int=n$0 [line 23, column 3]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_3" -> "label_default.f30729864b0243c0a794ef0254fe7d23_2" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_4" [label="4: SwitchStmt \n n$1=*&x:char [line 12, column 11]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_4" -> "label_default.f30729864b0243c0a794ef0254fe7d23_11" ; + "label_default.f30729864b0243c0a794ef0254fe7d23_4" -> "label_default.f30729864b0243c0a794ef0254fe7d23_12" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_5" [label="5: UnaryOperator \n n$2=*&ret:int [line 21, column 7]\n *&ret:int=(n$2 - 1) [line 21, column 7]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_5" -> "label_default.f30729864b0243c0a794ef0254fe7d23_3" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_6" [label="6: Skip GotoLabel_l \n " color="gray"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_6" -> "label_default.f30729864b0243c0a794ef0254fe7d23_5" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_7" [label="7: BinaryOperatorStmt: Assign \n *&ret:int=2 [line 17, column 7]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_7" -> "label_default.f30729864b0243c0a794ef0254fe7d23_3" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_8" [label="8: UnaryOperator \n n$6=*&ret:int [line 14, column 7]\n *&ret:int=(n$6 + 1) [line 14, column 7]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_8" -> "label_default.f30729864b0243c0a794ef0254fe7d23_6" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_9" [label="9: Prune (true branch, switch) \n PRUNE((n$1 == 2), true); [line 16, column 5]\n " shape="invhouse"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_9" -> "label_default.f30729864b0243c0a794ef0254fe7d23_7" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_10" [label="10: Prune (false branch, switch) \n PRUNE(!(n$1 == 2), false); [line 16, column 5]\n " shape="invhouse"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_10" -> "label_default.f30729864b0243c0a794ef0254fe7d23_5" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_11" [label="11: Prune (true branch, switch) \n PRUNE((n$1 == 1), true); [line 13, column 5]\n " shape="invhouse"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_11" -> "label_default.f30729864b0243c0a794ef0254fe7d23_8" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_12" [label="12: Prune (false branch, switch) \n PRUNE(!(n$1 == 1), false); [line 13, column 5]\n " shape="invhouse"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_12" -> "label_default.f30729864b0243c0a794ef0254fe7d23_9" ; + "label_default.f30729864b0243c0a794ef0254fe7d23_12" -> "label_default.f30729864b0243c0a794ef0254fe7d23_10" ; +"label_default.f30729864b0243c0a794ef0254fe7d23_13" [label="13: DeclStmt \n *&ret:int=0 [line 11, column 3]\n " shape="box"] + + + "label_default.f30729864b0243c0a794ef0254fe7d23_13" -> "label_default.f30729864b0243c0a794ef0254fe7d23_4" ; +} diff --git a/infer/tests/codetoanalyze/cpp/frontend/attributes/clang_fallthrough.cpp.dot b/infer/tests/codetoanalyze/cpp/frontend/attributes/clang_fallthrough.cpp.dot index 03738c54a..cb09e51fb 100644 --- a/infer/tests/codetoanalyze/cpp/frontend/attributes/clang_fallthrough.cpp.dot +++ b/infer/tests/codetoanalyze/cpp/frontend/attributes/clang_fallthrough.cpp.dot @@ -22,12 +22,12 @@ digraph cfg { "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_3" -> "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_2" ; -"switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_4" [label="4: Switch_stmt \n n$2=*&n:int [line 14, column 11]\n " shape="box"] +"switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_4" [label="4: SwitchStmt \n n$2=*&n:int [line 14, column 11]\n " shape="box"] "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_4" -> "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_12" ; "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_4" -> "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_13" ; -"switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_5" [label="5: BinaryOperatorStmt: Assign \n n$5=_fun_h() [line 21, column 13]\n *&res:int=n$5 [line 21, column 7]\n " shape="box"] +"switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_5" [label="5: BinaryOperatorStmt: Assign \n n$6=_fun_h() [line 21, column 13]\n *&res:int=n$6 [line 21, column 7]\n " shape="box"] "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_5" -> "switch_with_fallthrough#6355028676793350740.9380c19327ea36a0a69b7e115d031492_3" ; diff --git a/infer/tests/codetoanalyze/cpp/frontend/destructors/break_scope.cpp.dot b/infer/tests/codetoanalyze/cpp/frontend/destructors/break_scope.cpp.dot index 0cd0b2fa6..e51c6d3dd 100644 --- a/infer/tests/codetoanalyze/cpp/frontend/destructors/break_scope.cpp.dot +++ b/infer/tests/codetoanalyze/cpp/frontend/destructors/break_scope.cpp.dot @@ -234,66 +234,66 @@ digraph cfg { "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_4" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_3" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_5" [label="5: Switch_stmt \n n$6=*&n:int [line 117, column 11]\n " shape="box"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_5" [label="5: SwitchStmt \n n$6=*&n:int [line 117, column 11]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_5" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_17" ; "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_5" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_6" [label="6: Destruction \n _=*&x4:break_scope::X [line 127, column 5]\n n$8=_fun_break_scope::X_~X(&x4:break_scope::X*) [line 127, column 5]\n " shape="box"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_6" [label="6: Destruction \n _=*&x4:break_scope::X [line 127, column 5]\n n$9=_fun_break_scope::X_~X(&x4:break_scope::X*) [line 127, column 5]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_6" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_4" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" [label="7: DeclStmt \n n$10=_fun_break_scope::X_X(&x4:break_scope::X*) [line 126, column 9]\n " shape="box"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" [label="7: DeclStmt \n n$11=_fun_break_scope::X_X(&x4:break_scope::X*) [line 126, column 9]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_6" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_8" [label="8: Prune (true branch, switch) \n PRUNE((n$6 == 3), true); [line 125, column 5]\n " shape="invhouse"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_8" [label="8: Destruction \n _=*&x3:break_scope::X [line 124, column 5]\n n$13=_fun_break_scope::X_~X(&x3:break_scope::X*) [line 124, column 5]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_8" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_9" [label="9: Prune (false branch, switch) \n PRUNE(!(n$6 == 3), false); [line 125, column 5]\n " shape="invhouse"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_9" [label="9: Destruction \n _=*&x3:break_scope::X [line 123, column 7]\n n$16=_fun_break_scope::X_~X(&x3:break_scope::X*) [line 123, column 7]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_9" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_4" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" [label="10: Destruction \n _=*&x3:break_scope::X [line 124, column 5]\n n$12=_fun_break_scope::X_~X(&x3:break_scope::X*) [line 124, column 5]\n " shape="box"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" [label="10: DeclStmt \n n$18=_fun_break_scope::X_X(&x3:break_scope::X*) [line 122, column 9]\n " shape="box"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_11" [label="11: Destruction \n _=*&x3:break_scope::X [line 123, column 7]\n n$15=_fun_break_scope::X_~X(&x3:break_scope::X*) [line 123, column 7]\n " shape="box"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_9" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_11" [label="11: Destruction \n _=*&x2:break_scope::X [line 120, column 5]\n n$20=_fun_break_scope::X_~X(&x2:break_scope::X*) [line 120, column 5]\n " shape="box"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_11" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_4" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" [label="12: DeclStmt \n n$17=_fun_break_scope::X_X(&x3:break_scope::X*) [line 122, column 9]\n " shape="box"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_11" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" [label="12: DeclStmt \n n$22=_fun_break_scope::X_X(&x2:break_scope::X*) [line 119, column 9]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_11" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" [label="13: Prune (true branch, switch) \n PRUNE((n$6 == 2), true); [line 121, column 5]\n " shape="invhouse"] +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" [label="13: Prune (true branch, switch) \n PRUNE((n$6 == 3), true); [line 125, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$6 == 2), false); [line 121, column 5]\n " shape="invhouse"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_7" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$6 == 3), false); [line 125, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_8" ; - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_9" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" [label="15: Destruction \n _=*&x2:break_scope::X [line 120, column 5]\n n$19=_fun_break_scope::X_~X(&x2:break_scope::X*) [line 120, column 5]\n " shape="box"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_4" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" [label="15: Prune (true branch, switch) \n PRUNE((n$6 == 2), true); [line 121, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" [label="16: DeclStmt \n n$21=_fun_break_scope::X_X(&x2:break_scope::X*) [line 119, column 9]\n " shape="box"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_10" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" [label="16: Prune (false branch, switch) \n PRUNE(!(n$6 == 2), false); [line 121, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" ; + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" ; + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" ; "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_17" [label="17: Prune (true branch, switch) \n PRUNE((n$6 == 1), true); [line 118, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_17" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" ; + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_17" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_12" ; "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" [label="18: Prune (false branch, switch) \n PRUNE(!(n$6 == 1), false); [line 118, column 5]\n " shape="invhouse"] - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_13" ; - "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_14" ; -"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_19" [label="19: DeclStmt \n n$23=_fun_break_scope::X_X(&x1:break_scope::X*) [line 116, column 5]\n " shape="box"] + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_15" ; + "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_18" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_16" ; +"test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_19" [label="19: DeclStmt \n n$24=_fun_break_scope::X_X(&x1:break_scope::X*) [line 116, column 5]\n " shape="box"] "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_19" -> "test_switch#break_scope#5012999682930893305.43ca855443a5fa68fa701447a90f7a1f_5" ; diff --git a/infer/tests/codetoanalyze/cpp/shared/nestedoperators/var_decl_inside_switch.cpp.dot b/infer/tests/codetoanalyze/cpp/shared/nestedoperators/var_decl_inside_switch.cpp.dot index a56f8b528..0d40121dc 100644 --- a/infer/tests/codetoanalyze/cpp/shared/nestedoperators/var_decl_inside_switch.cpp.dot +++ b/infer/tests/codetoanalyze/cpp/shared/nestedoperators/var_decl_inside_switch.cpp.dot @@ -7,55 +7,51 @@ digraph cfg { "get#10177141129833125794.403aae26476e3a02c544075e122228e0_2" [label="2: Exit get \n " color=yellow style=filled] -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" [label="3: Switch_stmt \n n$1=*&x:int [line 11, column 15]\n " shape="box"] +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" [label="3: SwitchStmt \n n$1=*&x:int [line 11, column 15]\n " shape="box"] + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" ; "get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_13" ; - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_14" ; "get#10177141129833125794.403aae26476e3a02c544075e122228e0_4" [label="4: DeclStmt \n n$2=*&a:int [line 11, column 19]\n *&x:int=n$2 [line 11, column 11]\n " shape="box"] "get#10177141129833125794.403aae26476e3a02c544075e122228e0_4" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_3" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_5" [label="5: DefaultStmt_placeholder \n " shape="box"] +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_5" [label="5: Return Stmt \n n$4=*&x:int [line 18, column 14]\n *&return:int=n$4 [line 18, column 7]\n " shape="box"] - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_5" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_6" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_6" [label="6: Return Stmt \n n$3=*&x:int [line 18, column 14]\n *&return:int=n$3 [line 18, column 7]\n " shape="box"] + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_5" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_2" ; +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_6" [label="6: Return Stmt \n *&return:int=1 [line 16, column 7]\n " shape="box"] "get#10177141129833125794.403aae26476e3a02c544075e122228e0_6" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_2" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" [label="7: Return Stmt \n *&return:int=1 [line 16, column 7]\n " shape="box"] +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" [label="7: Return Stmt \n *&return:int=0 [line 14, column 7]\n " shape="box"] "get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_2" ; "get#10177141129833125794.403aae26476e3a02c544075e122228e0_8" [label="8: Prune (true branch, switch) \n PRUNE((n$1 == 2), true); [line 15, column 5]\n " shape="invhouse"] - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_8" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" ; + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_8" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_6" ; "get#10177141129833125794.403aae26476e3a02c544075e122228e0_9" [label="9: Prune (false branch, switch) \n PRUNE(!(n$1 == 2), false); [line 15, column 5]\n " shape="invhouse"] "get#10177141129833125794.403aae26476e3a02c544075e122228e0_9" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_5" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" [label="10: Return Stmt \n *&return:int=0 [line 14, column 7]\n " shape="box"] +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" [label="10: Prune (true branch, switch) \n PRUNE((n$1 == 1), true); [line 13, column 5]\n " shape="invhouse"] - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_2" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" [label="11: Prune (true branch, switch) \n PRUNE((n$1 == 1), true); [line 13, column 5]\n " shape="invhouse"] + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" ; +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" [label="11: Prune (false branch, switch) \n PRUNE(!(n$1 == 1), false); [line 13, column 5]\n " shape="invhouse"] - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" [label="12: Prune (false branch, switch) \n PRUNE(!(n$1 == 1), false); [line 13, column 5]\n " shape="invhouse"] + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_8" ; + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_9" ; +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" [label="12: Prune (true branch, switch) \n PRUNE((n$1 == 0), true); [line 12, column 5]\n " shape="invhouse"] - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_8" ; - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_9" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_13" [label="13: Prune (true branch, switch) \n PRUNE((n$1 == 0), true); [line 12, column 5]\n " shape="invhouse"] + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_7" ; +"get#10177141129833125794.403aae26476e3a02c544075e122228e0_13" [label="13: Prune (false branch, switch) \n PRUNE(!(n$1 == 0), false); [line 12, column 5]\n " shape="invhouse"] "get#10177141129833125794.403aae26476e3a02c544075e122228e0_13" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_10" ; -"get#10177141129833125794.403aae26476e3a02c544075e122228e0_14" [label="14: Prune (false branch, switch) \n PRUNE(!(n$1 == 0), false); [line 12, column 5]\n " shape="invhouse"] - - - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_14" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" ; - "get#10177141129833125794.403aae26476e3a02c544075e122228e0_14" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_12" ; + "get#10177141129833125794.403aae26476e3a02c544075e122228e0_13" -> "get#10177141129833125794.403aae26476e3a02c544075e122228e0_11" ; }