This removes the referenced vars machinery (stubbing out
add_referenced_vars and gimple_referenced_vars - a patch fixing
all callers will be 2c/2).

Bootstrap and regtest pending on x86_64-unknown-linux-gnu.

Richard.

2012-08-01  Richard Guenther  <rguent...@suse.de>

        * tree-flow.h (struct gimple_df): Remove referenced_vars member.
        (typedef referenced_var_iterator): Remove.
        (FOR_EACH_REFERENCED_VAR): Likewise.
        (num_referenced_vars): Likewise.
        (debug_referenced_vars, dump_referenced_vars): Likewise.
        (add_referenced_var_1, add_referenced_var): Likewise.
        (remove_referenced_var): Likewise.
        (find_referenced_vars_in): Likewise.
        * tree-dfa.c (find_referenced_vars): Remove.
        (pass_referenced_vars): Likewise.
        (make_rename_temp): Do not add referenced vars.
        (dump_referenced_vars): Remove.
        (debug_referenced_vars): Likewise.
        (dump_dfa_stats): Do not dump referenced var stats.
        (find_vars_r): Remove.
        (find_referenced_vars_in): Likewise.
        (referenced_var_check_and_insert): Likewise.
        (add_referenced_var_1): Likewise.
        (remove_referenced_var): Likewise.
        * tree-flow-inline.h (gimple_referenced_vars): Remove.
        (first_referenced_var): Likewise.
        (end_referenced_vars_p): Likewise.
        (next_referenced_var): Likewise.
        * tree-inline.c (copy_bb): Do not add referenced vars.
        * tree-into-ssa.c (pass_build_ssa): Do not require PROP_referenced_vars.
        * tree-pass.h (PROP_referenced_vars): Remove.
        (pass_referenced_vars): Likewise.
        * tree-profile.c (gimple_gen_edge_profiler): Do not add referenced vars.
        (gimple_gen_interval_profiler): Likewise.
        (gimple_gen_pow2_profiler): Likewise.
        (gimple_gen_one_value_profiler): Likewise.
        (gimple_gen_ic_profiler): Likewise.
        (gimple_gen_average_profiler): Likewise.
        (gimple_gen_ior_profiler): Likewise.
        * tree-ssa-live.c (remove_unused_locals): Do not touch referenced vars.
        * tree-ssa.c (init_tree_ssa): Do not allocate referenced vars.
        (delete_tree_ssa): Do not free referenced vars.
        * tree-cfg.c (move_stmt_op): Do not add referenced vars.
        * tree-ssa-operands.c (create_vop_var): Likewise.

Index: trunk/gcc/cgraphunit.c
===================================================================
*** trunk.orig/gcc/cgraphunit.c 2012-08-01 12:38:31.000000000 +0200
--- trunk/gcc/cgraphunit.c      2012-08-01 12:38:40.619962135 +0200
*************** init_lowered_empty_function (tree decl)
*** 1228,1235 ****
  
    DECL_SAVED_TREE (decl) = error_mark_node;
    cfun->curr_properties |=
!     (PROP_gimple_lcf | PROP_gimple_leh | PROP_cfg | PROP_referenced_vars |
!      PROP_ssa | PROP_gimple_any);
  
    /* Create BB for body of the function and connect it properly.  */
    bb = create_basic_block (NULL, (void *) 0, ENTRY_BLOCK_PTR);
--- 1228,1234 ----
  
    DECL_SAVED_TREE (decl) = error_mark_node;
    cfun->curr_properties |=
!     (PROP_gimple_lcf | PROP_gimple_leh | PROP_cfg | PROP_ssa | 
PROP_gimple_any);
  
    /* Create BB for body of the function and connect it properly.  */
    bb = create_basic_block (NULL, (void *) 0, ENTRY_BLOCK_PTR);
Index: trunk/gcc/gimple-fold.c
===================================================================
*** trunk.orig/gcc/gimple-fold.c        2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/gimple-fold.c     2012-08-01 12:38:40.620962135 +0200
*************** gimplify_and_update_call_from_tree (gimp
*** 653,661 ****
    for (i = gsi_start (stmts); !gsi_end_p (i); gsi_next (&i))
      {
        new_stmt = gsi_stmt (i);
-       /* The replacement can expose previously unreferenced variables.  */
-       if (gimple_in_ssa_p (cfun))
-       find_referenced_vars_in (new_stmt);
        /* If the new statement possibly has a VUSE, update it with exact SSA
         name we know will reach this one.  */
        if (gimple_has_mem_ops (new_stmt))
--- 653,658 ----
Index: trunk/gcc/gimple-streamer-in.c
===================================================================
*** trunk.orig/gcc/gimple-streamer-in.c 2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/gimple-streamer-in.c      2012-08-01 12:38:40.621962134 +0200
*************** input_bb (struct lto_input_block *ib, en
*** 310,317 ****
    while (tag)
      {
        gimple stmt = input_gimple_stmt (ib, data_in, fn, tag);
-       if (!is_gimple_debug (stmt))
-       find_referenced_vars_in (stmt);
        gsi_insert_after (&bsi, stmt, GSI_NEW_STMT);
  
        /* After the statement, expect a 0 delimiter or the EH region
--- 310,315 ----
*************** input_bb (struct lto_input_block *ib, en
*** 332,339 ****
    tag = streamer_read_record_start (ib);
    while (tag)
      {
!       gimple phi = input_phi (ib, bb, data_in, fn);
!       find_referenced_vars_in (phi);
        tag = streamer_read_record_start (ib);
      }
  }
--- 330,336 ----
    tag = streamer_read_record_start (ib);
    while (tag)
      {
!       input_phi (ib, bb, data_in, fn);
        tag = streamer_read_record_start (ib);
      }
  }
Index: trunk/gcc/passes.c
===================================================================
*** trunk.orig/gcc/passes.c     2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/passes.c  2012-08-01 12:38:40.622962134 +0200
*************** init_optimization_passes (void)
*** 1285,1291 ****
        NEXT_PASS (pass_init_datastructures);
        NEXT_PASS (pass_expand_omp);
  
-       NEXT_PASS (pass_referenced_vars);
        NEXT_PASS (pass_build_ssa);
        NEXT_PASS (pass_lower_vector);
        NEXT_PASS (pass_early_warn_uninitialized);
--- 1285,1290 ----
*************** dump_properties (FILE *dump, unsigned in
*** 2603,2610 ****
      fprintf (dump, "PROP_gimple_leh\n");
    if (props & PROP_cfg)
      fprintf (dump, "PROP_cfg\n");
-   if (props & PROP_referenced_vars)
-     fprintf (dump, "PROP_referenced_vars\n");
    if (props & PROP_ssa)
      fprintf (dump, "PROP_ssa\n");
    if (props & PROP_no_crit_edges)
--- 2602,2607 ----
Index: trunk/gcc/tree-dfa.c
===================================================================
*** trunk.orig/gcc/tree-dfa.c   2012-08-01 12:38:34.000000000 +0200
--- trunk/gcc/tree-dfa.c        2012-08-01 12:38:40.622962134 +0200
*************** static void collect_dfa_stats (struct df
*** 64,119 ****
  /*---------------------------------------------------------------------------
                        Dataflow analysis (DFA) routines
  ---------------------------------------------------------------------------*/
- /* Find all the variables referenced in the function.  This function
-    builds the global arrays REFERENCED_VARS and CALL_CLOBBERED_VARS.
- 
-    Note that this function does not look for statement operands, it simply
-    determines what variables are referenced in the program and detects
-    various attributes for each variable used by alias analysis and the
-    optimizer.  */
- 
- static unsigned int
- find_referenced_vars (void)
- {
-   basic_block bb;
-   gimple_stmt_iterator si;
- 
-   FOR_EACH_BB (bb)
-     {
-       for (si = gsi_start_bb (bb); !gsi_end_p (si); gsi_next (&si))
-       {
-         gimple stmt = gsi_stmt (si);
-         if (is_gimple_debug (stmt))
-           continue;
-         find_referenced_vars_in (gsi_stmt (si));
-       }
- 
-       for (si = gsi_start_phis (bb); !gsi_end_p (si); gsi_next (&si))
-       find_referenced_vars_in (gsi_stmt (si));
-     }
- 
-   return 0;
- }
- 
- struct gimple_opt_pass pass_referenced_vars =
- {
-  {
-   GIMPLE_PASS,
-   "*referenced_vars",                 /* name */
-   NULL,                                       /* gate */
-   find_referenced_vars,                       /* execute */
-   NULL,                                       /* sub */
-   NULL,                                       /* next */
-   0,                                  /* static_pass_number */
-   TV_FIND_REFERENCED_VARS,            /* tv_id */
-   PROP_gimple_leh | PROP_cfg,         /* properties_required */
-   PROP_referenced_vars,                       /* properties_provided */
-   0,                                  /* properties_destroyed */
-   0,                                  /* todo_flags_start */
-   0                                     /* todo_flags_finish */
-  }
- };
- 
  
  /* Renumber all of the gimple stmt uids.  */
  
--- 64,69 ----
*************** renumber_gimple_stmt_uids_in_blocks (bas
*** 170,181 ****
  tree
  make_rename_temp (tree type, const char *prefix)
  {
!   tree t = create_tmp_reg (type, prefix);
! 
!   if (gimple_referenced_vars (cfun))
!     add_referenced_var (t);
! 
!   return t;
  }
  
  
--- 120,126 ----
  tree
  make_rename_temp (tree type, const char *prefix)
  {
!   return create_tmp_reg (type, prefix);
  }
  
  
*************** make_rename_temp (tree type, const char
*** 183,218 ****
  /*---------------------------------------------------------------------------
                              Debugging functions
  ---------------------------------------------------------------------------*/
- /* Dump the list of all the referenced variables in the current function to
-    FILE.  */
- 
- void
- dump_referenced_vars (FILE *file)
- {
-   tree var;
-   referenced_var_iterator rvi;
- 
-   fprintf (file, "\nReferenced variables in %s: %u\n\n",
-          get_name (current_function_decl), (unsigned) num_referenced_vars);
- 
-   FOR_EACH_REFERENCED_VAR (cfun, var, rvi)
-     {
-       fprintf (file, "Variable: ");
-       dump_variable (file, var);
-     }
- 
-   fprintf (file, "\n");
- }
- 
- 
- /* Dump the list of all the referenced variables to stderr.  */
- 
- DEBUG_FUNCTION void
- debug_referenced_vars (void)
- {
-   dump_referenced_vars (stderr);
- }
- 
  
  /* Dump variable VAR and its may-aliases to FILE.  */
  
--- 128,133 ----
*************** dump_dfa_stats (FILE *file)
*** 298,308 ****
    fprintf (file, fmt_str, "", "  instances  ", "used ");
    fprintf (file, 
"---------------------------------------------------------\n");
  
-   size = num_referenced_vars * sizeof (tree);
-   total += size;
-   fprintf (file, fmt_str_1, "Referenced variables", (unsigned 
long)num_referenced_vars,
-          SCALE (size), LABEL (size));
- 
    size = dfa_stats.num_var_anns * sizeof (struct var_ann_d);
    total += size;
    fprintf (file, fmt_str_1, "Variables annotated", dfa_stats.num_var_anns,
--- 213,218 ----
*************** collect_dfa_stats (struct dfa_stats_d *d
*** 374,382 ****
  
    memset ((void *)dfa_stats_p, 0, sizeof (struct dfa_stats_d));
  
-   /* Count all the variable annotations.  */
-   dfa_stats_p->num_var_anns = htab_elements (gimple_referenced_vars (cfun));
- 
    /* Walk all the statements in the function counting references.  */
    FOR_EACH_BB (bb)
      {
--- 284,289 ----
*************** collect_dfa_stats (struct dfa_stats_d *d
*** 406,489 ****
  /*---------------------------------------------------------------------------
                             Miscellaneous helpers
  ---------------------------------------------------------------------------*/
- /* Callback for walk_tree.  Used to collect variables referenced in
-    the function.  */
- 
- static tree
- find_vars_r (tree *tp, int *walk_subtrees, void *data)
- {
-   struct function *fn = (struct function *) data;
- 
-   /* If we are reading the lto info back in, we need to rescan the
-      referenced vars.  */
-   if (TREE_CODE (*tp) == SSA_NAME)
-     add_referenced_var_1 (SSA_NAME_VAR (*tp), fn);
- 
-   /* If T is a regular variable that the optimizers are interested
-      in, add it to the list of variables.  */
-   else if ((TREE_CODE (*tp) == VAR_DECL
-           && !is_global_var (*tp))
-          || TREE_CODE (*tp) == PARM_DECL
-          || TREE_CODE (*tp) == RESULT_DECL)
-     add_referenced_var_1 (*tp, fn);
- 
-   /* Type, _DECL and constant nodes have no interesting children.
-      Ignore them.  */
-   else if (IS_TYPE_OR_DECL_P (*tp) || CONSTANT_CLASS_P (*tp))
-     *walk_subtrees = 0;
- 
-   return NULL_TREE;
- }
- 
- /* Find referenced variables in STMT.  */
- 
- void
- find_referenced_vars_in (gimple stmt)
- {
-   size_t i;
- 
-   if (gimple_code (stmt) != GIMPLE_PHI)
-     {
-       for (i = 0; i < gimple_num_ops (stmt); i++)
-       walk_tree (gimple_op_ptr (stmt, i), find_vars_r, cfun, NULL);
-     }
-   else
-     {
-       walk_tree (gimple_phi_result_ptr (stmt), find_vars_r, cfun, NULL);
- 
-       for (i = 0; i < gimple_phi_num_args (stmt); i++)
-       {
-         tree arg = gimple_phi_arg_def (stmt, i);
-         walk_tree (&arg, find_vars_r, cfun, NULL);
-       }
-     }
- }
- 
- 
- /* Check if TO is in the referenced_vars hash table and insert it if not.
-    Return true if it required insertion.  */
- 
- static bool
- referenced_var_check_and_insert (tree to, struct function *fn)
- {
-   tree *loc;
-   struct tree_decl_minimal in;
-   unsigned int uid = DECL_UID (to);
- 
-   in.uid = uid;
-   loc = (tree *) htab_find_slot_with_hash (gimple_referenced_vars (fn),
-                                          &in, uid, INSERT);
-   if (*loc)
-     {
-       /* DECL_UID has already been entered in the table.  Verify that it is
-        the same entry as TO.  See PR 27793.  */
-       gcc_assert (*loc == to);
-       return false;
-     }
- 
-   *loc = to;
-   return true;
- }
  
  /* Lookup VAR UID in the default_defs hashtable and return the associated
     variable.  */
--- 313,318 ----
*************** set_default_def (tree var, tree def)
*** 532,589 ****
     SSA_NAME_IS_DEFAULT_DEF (def) = true;
  }
  
- /* Add VAR to the list of referenced variables if it isn't already there.  */
- 
- bool
- add_referenced_var_1 (tree var, struct function *fn)
- {
-   gcc_checking_assert (TREE_CODE (var) == VAR_DECL
-                      || TREE_CODE (var) == PARM_DECL
-                      || TREE_CODE (var) == RESULT_DECL);
- 
-   gcc_checking_assert ((TREE_CODE (var) == VAR_DECL
-                       && VAR_DECL_IS_VIRTUAL_OPERAND (var))
-                      || !is_global_var (var));
- 
-   /* Insert VAR into the referenced_vars hash table if it isn't present
-      and allocate its var-annotation.  */
-   if (referenced_var_check_and_insert (var, fn))
-     {
-       gcc_checking_assert (!*DECL_VAR_ANN_PTR (var));
-       *DECL_VAR_ANN_PTR (var) = ggc_alloc_cleared_var_ann_d ();
-       return true;
-     }
- 
-   return false;
- }
- 
- /* Remove VAR from the list of referenced variables and clear its
-    var-annotation.  */
- 
- void
- remove_referenced_var (tree var)
- {
-   var_ann_t v_ann;
-   struct tree_decl_minimal in;
-   void **loc;
-   unsigned int uid = DECL_UID (var);
- 
-   gcc_checking_assert (TREE_CODE (var) == VAR_DECL
-                      || TREE_CODE (var) == PARM_DECL
-                      || TREE_CODE (var) == RESULT_DECL);
- 
-   gcc_checking_assert (!is_global_var (var));
- 
-   v_ann = var_ann (var);
-   ggc_free (v_ann);
-   *DECL_VAR_ANN_PTR (var) = NULL;
- 
-   in.uid = uid;
-   loc = htab_find_slot_with_hash (gimple_referenced_vars (cfun), &in, uid,
-                                 NO_INSERT);
-   htab_clear_slot (gimple_referenced_vars (cfun), loc);
- }
- 
  
  /* If EXP is a handled component reference for a structure, return the
     base variable.  The access range is delimited by bit positions *POFFSET and
--- 361,366 ----
Index: trunk/gcc/tree-flow-inline.h
===================================================================
*** trunk.orig/gcc/tree-flow-inline.h   2012-08-01 12:38:33.000000000 +0200
--- trunk/gcc/tree-flow-inline.h        2012-08-01 12:38:40.622962134 +0200
*************** gimple_in_ssa_p (const struct function *
*** 37,47 ****
  
  /* Array of all variables referenced in the function.  */
  static inline htab_t
! gimple_referenced_vars (const struct function *fun)
  {
!   if (!fun || !fun->gimple_df)
!     return NULL;
!   return fun->gimple_df->referenced_vars;
  }
  
  /* Artificial variable used for the virtual operand FUD chain.  */
--- 37,45 ----
  
  /* Array of all variables referenced in the function.  */
  static inline htab_t
! gimple_referenced_vars (const struct function *fun ATTRIBUTE_UNUSED)
  {
!   return NULL;
  }
  
  /* Artificial variable used for the virtual operand FUD chain.  */
*************** next_htab_element (htab_iterator *hti)
*** 98,131 ****
    return NULL;
  }
  
- /* Initialize ITER to point to the first referenced variable in the
-    referenced_vars hashtable, and return that variable.  */
- 
- static inline tree
- first_referenced_var (struct function *fn, referenced_var_iterator *iter)
- {
-   return (tree) first_htab_element (&iter->hti,
-                                   gimple_referenced_vars (fn));
- }
- 
- /* Return true if we have hit the end of the referenced variables ITER is
-    iterating through.  */
- 
- static inline bool
- end_referenced_vars_p (const referenced_var_iterator *iter)
- {
-   return end_htab_p (&iter->hti);
- }
- 
- /* Make ITER point to the next referenced_var in the referenced_var hashtable,
-    and return that variable.  */
- 
- static inline tree
- next_referenced_var (referenced_var_iterator *iter)
- {
-   return (tree) next_htab_element (&iter->hti);
- }
- 
  /* Return the variable annotation for T, which must be a _DECL node.
     Return NULL if the variable annotation doesn't already exist.  */
  static inline var_ann_t
--- 96,101 ----
Index: trunk/gcc/tree-flow.h
===================================================================
*** trunk.orig/gcc/tree-flow.h  2012-08-01 12:38:34.000000000 +0200
--- trunk/gcc/tree-flow.h       2012-08-01 12:38:40.623962134 +0200
*************** struct GTY(()) tm_restart_node {
*** 45,53 ****
     gimple_ accessor defined in tree-flow-inline.h, all publicly modifiable
     fields should have gimple_set accessor.  */
  struct GTY(()) gimple_df {
-   /* Array of all variables referenced in the function.  */
-   htab_t GTY((param_is (union tree_node))) referenced_vars;
- 
    /* A vector of all the noreturn calls passed to modify_stmt.
       cleanup_control_flow uses it to detect cases where a mid-block
       indirect call has been turned into a noreturn call.  When this
--- 45,50 ----
*************** extern int int_tree_map_eq (const void *
*** 308,330 ****
  extern unsigned int uid_decl_map_hash (const void *);
  extern int uid_decl_map_eq (const void *, const void *);
  
- typedef struct
- {
-   htab_iterator hti;
- } referenced_var_iterator;
- 
- /* This macro loops over all the referenced vars, one at a time, putting the
-    current var in VAR.  Note:  You are not allowed to add referenced variables
-    to the hashtable while using this macro.  Doing so may cause it to behave
-    erratically.  */
- 
- #define FOR_EACH_REFERENCED_VAR(FN, VAR, ITER)                \
-   for ((VAR) = first_referenced_var ((FN), &(ITER));  \
-        !end_referenced_vars_p (&(ITER));              \
-        (VAR) = next_referenced_var (&(ITER)))
- 
- #define num_referenced_vars htab_elements (gimple_referenced_vars (cfun))
- 
  #define num_ssa_names (VEC_length (tree, cfun->gimple_df->ssa_names))
  #define ssa_name(i) (VEC_index (tree, cfun->gimple_df->ssa_names, (i)))
  
--- 305,310 ----
*************** extern void renumber_gimple_stmt_uids (v
*** 478,497 ****
  extern void renumber_gimple_stmt_uids_in_blocks (basic_block *, int);
  extern void dump_dfa_stats (FILE *);
  extern void debug_dfa_stats (void);
- extern void debug_referenced_vars (void);
- extern void dump_referenced_vars (FILE *);
  extern void dump_variable (FILE *, tree);
  extern void debug_variable (tree);
- extern bool add_referenced_var_1 (tree, struct function *);
- #define add_referenced_var(v) add_referenced_var_1 ((v), cfun)
- extern void remove_referenced_var (tree);
  extern tree make_rename_temp (tree, const char *);
  extern void set_default_def (tree, tree);
  extern tree gimple_default_def (struct function *, tree);
  extern bool stmt_references_abnormal_ssa_name (gimple);
  extern tree get_addr_base_and_unit_offset (tree, HOST_WIDE_INT *);
- extern void find_referenced_vars_in (gimple);
  extern void dump_enumerated_decls (FILE *, int);
  
  /* In tree-phinodes.c  */
  extern void reserve_phi_args_for_new_edge (basic_block);
--- 458,472 ----
  extern void renumber_gimple_stmt_uids_in_blocks (basic_block *, int);
  extern void dump_dfa_stats (FILE *);
  extern void debug_dfa_stats (void);
  extern void dump_variable (FILE *, tree);
  extern void debug_variable (tree);
  extern tree make_rename_temp (tree, const char *);
  extern void set_default_def (tree, tree);
  extern tree gimple_default_def (struct function *, tree);
  extern bool stmt_references_abnormal_ssa_name (gimple);
  extern tree get_addr_base_and_unit_offset (tree, HOST_WIDE_INT *);
  extern void dump_enumerated_decls (FILE *, int);
+ #define add_referenced_var(i) do { } while (0)
  
  /* In tree-phinodes.c  */
  extern void reserve_phi_args_for_new_edge (basic_block);
Index: trunk/gcc/tree-inline.c
===================================================================
*** trunk.orig/gcc/tree-inline.c        2012-08-01 12:38:32.000000000 +0200
--- trunk/gcc/tree-inline.c     2012-08-01 12:38:40.624962134 +0200
*************** copy_bb (copy_body_data *id, basic_block
*** 1802,1808 ****
              ssa_op_iter i;
              tree def;
  
-             find_referenced_vars_in (gsi_stmt (copy_gsi));
              FOR_EACH_SSA_TREE_OPERAND (def, stmt, i, SSA_OP_DEF)
                if (TREE_CODE (def) == SSA_NAME)
                  SSA_NAME_DEF_STMT (def) = stmt;
--- 1802,1807 ----
Index: trunk/gcc/tree-into-ssa.c
===================================================================
*** trunk.orig/gcc/tree-into-ssa.c      2012-08-01 12:38:34.000000000 +0200
--- trunk/gcc/tree-into-ssa.c   2012-08-01 12:38:40.624962134 +0200
*************** struct gimple_opt_pass pass_build_ssa =
*** 2466,2472 ****
    NULL,                                       /* next */
    0,                                  /* static_pass_number */
    TV_TREE_SSA_OTHER,                  /* tv_id */
!   PROP_cfg | PROP_referenced_vars,    /* properties_required */
    PROP_ssa,                           /* properties_provided */
    0,                                  /* properties_destroyed */
    0,                                  /* todo_flags_start */
--- 2466,2472 ----
    NULL,                                       /* next */
    0,                                  /* static_pass_number */
    TV_TREE_SSA_OTHER,                  /* tv_id */
!   PROP_cfg,                           /* properties_required */
    PROP_ssa,                           /* properties_provided */
    0,                                  /* properties_destroyed */
    0,                                  /* todo_flags_start */
Index: trunk/gcc/tree-pass.h
===================================================================
*** trunk.orig/gcc/tree-pass.h  2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/tree-pass.h       2012-08-01 12:38:40.624962134 +0200
*************** struct simple_ipa_opt_pass
*** 142,148 ****
  #define PROP_gimple_lcf               (1 << 1)        /* lowered control flow 
*/
  #define PROP_gimple_leh               (1 << 2)        /* lowered eh */
  #define PROP_cfg              (1 << 3)
- #define PROP_referenced_vars  (1 << 4)
  #define PROP_ssa              (1 << 5)
  #define PROP_no_crit_edges      (1 << 6)
  #define PROP_rtl              (1 << 7)
--- 142,147 ----
*************** extern struct gimple_opt_pass pass_lower
*** 267,273 ****
  extern struct gimple_opt_pass pass_lower_resx;
  extern struct gimple_opt_pass pass_build_cfg;
  extern struct gimple_opt_pass pass_early_tree_profile;
- extern struct gimple_opt_pass pass_referenced_vars;
  extern struct gimple_opt_pass pass_cleanup_eh;
  extern struct gimple_opt_pass pass_sra;
  extern struct gimple_opt_pass pass_sra_early;
--- 266,271 ----
Index: trunk/gcc/tree-profile.c
===================================================================
*** trunk.orig/gcc/tree-profile.c       2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/tree-profile.c    2012-08-01 12:38:40.625962134 +0200
*************** gimple_gen_edge_profiler (int edgeno, ed
*** 220,226 ****
    one = build_int_cst (gcov_type_node, 1);
    stmt1 = gimple_build_assign (gcov_type_tmp_var, ref);
    gimple_assign_set_lhs (stmt1, make_ssa_name (gcov_type_tmp_var, stmt1));
-   find_referenced_vars_in (stmt1);
    stmt2 = gimple_build_assign_with_ops (PLUS_EXPR, gcov_type_tmp_var,
                                        gimple_assign_lhs (stmt1), one);
    gimple_assign_set_lhs (stmt2, make_ssa_name (gcov_type_tmp_var, stmt2));
--- 220,225 ----
*************** gimple_gen_interval_profiler (histogram_
*** 267,273 ****
    val = prepare_instrumented_value (&gsi, value);
    call = gimple_build_call (tree_interval_profiler_fn, 4,
                            ref_ptr, val, start, steps);
-   find_referenced_vars_in (call);
    gsi_insert_before (&gsi, call, GSI_NEW_STMT);
  }
  
--- 266,271 ----
*************** gimple_gen_pow2_profiler (histogram_valu
*** 288,294 ****
                                      true, NULL_TREE, true, GSI_SAME_STMT);
    val = prepare_instrumented_value (&gsi, value);
    call = gimple_build_call (tree_pow2_profiler_fn, 2, ref_ptr, val);
-   find_referenced_vars_in (call);
    gsi_insert_before (&gsi, call, GSI_NEW_STMT);
  }
  
--- 286,291 ----
*************** gimple_gen_one_value_profiler (histogram
*** 309,315 ****
                                      true, NULL_TREE, true, GSI_SAME_STMT);
    val = prepare_instrumented_value (&gsi, value);
    call = gimple_build_call (tree_one_value_profiler_fn, 2, ref_ptr, val);
-   find_referenced_vars_in (call);
    gsi_insert_before (&gsi, call, GSI_NEW_STMT);
  }
  
--- 306,311 ----
*************** gimple_gen_ic_profiler (histogram_value
*** 341,350 ****
  
    tmp1 = create_tmp_reg (ptr_void, "PROF");
    stmt1 = gimple_build_assign (ic_gcov_type_ptr_var, ref_ptr);
-   find_referenced_vars_in (stmt1);
    stmt2 = gimple_build_assign (tmp1, unshare_expr (value->hvalue.value));
    gimple_assign_set_lhs (stmt2, make_ssa_name (tmp1, stmt2));
-   find_referenced_vars_in (stmt2);
    stmt3 = gimple_build_assign (ic_void_ptr_var, gimple_assign_lhs (stmt2));
  
    gsi_insert_before (&gsi, stmt1, GSI_SAME_STMT);
--- 337,344 ----
*************** gimple_gen_average_profiler (histogram_v
*** 439,445 ****
                                      true, GSI_SAME_STMT);
    val = prepare_instrumented_value (&gsi, value);
    call = gimple_build_call (tree_average_profiler_fn, 2, ref_ptr, val);
-   find_referenced_vars_in (call);
    gsi_insert_before (&gsi, call, GSI_NEW_STMT);
  }
  
--- 433,438 ----
*************** gimple_gen_ior_profiler (histogram_value
*** 460,466 ****
                                      true, NULL_TREE, true, GSI_SAME_STMT);
    val = prepare_instrumented_value (&gsi, value);
    call = gimple_build_call (tree_ior_profiler_fn, 2, ref_ptr, val);
-   find_referenced_vars_in (call);
    gsi_insert_before (&gsi, call, GSI_NEW_STMT);
  }
  
--- 453,458 ----
Index: trunk/gcc/tree-ssa-live.c
===================================================================
*** trunk.orig/gcc/tree-ssa-live.c      2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/tree-ssa-live.c   2012-08-01 12:38:40.625962134 +0200
*************** void
*** 692,699 ****
  remove_unused_locals (void)
  {
    basic_block bb;
!   tree var, t;
!   referenced_var_iterator rvi;
    bitmap global_unused_vars = NULL;
    unsigned srcidx, dstidx, num, ix;
    bool have_local_clobbers = false;
--- 692,698 ----
  remove_unused_locals (void)
  {
    basic_block bb;
!   tree var;
    bitmap global_unused_vars = NULL;
    unsigned srcidx, dstidx, num, ix;
    bool have_local_clobbers = false;
*************** remove_unused_locals (void)
*** 708,717 ****
  
    mark_scope_block_unused (DECL_INITIAL (current_function_decl));
  
-   /* Assume all locals are unused.  */
-   FOR_EACH_REFERENCED_VAR (cfun, t, rvi)
-     clear_is_used (t);
- 
    /* Assume all globals in local decls are unused.  */
    global_unused_vars = BITMAP_ALLOC (NULL);
    FOR_EACH_LOCAL_DECL (cfun, ix, var)
--- 707,712 ----
*************** remove_unused_locals (void)
*** 837,852 ****
                  print_generic_expr (dump_file, var, 0);
                  fprintf (dump_file, " from local-decls\n");
                }
-             if (var_ann (var))
-               {
-               remove_referenced_var (var);
-               if (dump_file && (dump_flags & TDF_DETAILS))
-                 {
-                   fprintf (dump_file, "removing ");
-                   print_generic_expr (dump_file, var, 0);
-                   fprintf (dump_file, " from referenced vars\n");
-                 }
-               }
              if (cfun->nonlocal_goto_save_area
                  && TREE_OPERAND (cfun->nonlocal_goto_save_area, 0) == var)
                cfun->nonlocal_goto_save_area = NULL;
--- 832,837 ----
*************** remove_unused_locals (void)
*** 865,878 ****
    if (dstidx != num)
      VEC_truncate (tree, cfun->local_decls, dstidx);
  
-   /* ???  We end up with decls in referenced-vars that are not in
-      local-decls.  */
-   FOR_EACH_REFERENCED_VAR (cfun, t, rvi)
-     if (TREE_CODE (t) == VAR_DECL
-       && !VAR_DECL_IS_VIRTUAL_OPERAND (t)
-       && !is_used_p (t))
-       gcc_unreachable ();
- 
    remove_unused_scope_block_p (DECL_INITIAL (current_function_decl),
                               global_unused_vars);
  
--- 850,855 ----
Index: trunk/gcc/tree-ssa.c
===================================================================
*** trunk.orig/gcc/tree-ssa.c   2012-08-01 12:38:34.000000000 +0200
--- trunk/gcc/tree-ssa.c        2012-08-01 12:38:40.625962134 +0200
*************** void
*** 1104,1111 ****
  init_tree_ssa (struct function *fn)
  {
    fn->gimple_df = ggc_alloc_cleared_gimple_df ();
-   fn->gimple_df->referenced_vars = htab_create_ggc (20, uid_decl_map_hash,
-                                                   uid_decl_map_eq, NULL);
    fn->gimple_df->default_defs = htab_create_ggc (20, uid_ssaname_map_hash,
                                                 uid_ssaname_map_eq, NULL);
    pt_solution_reset (&fn->gimple_df->escaped);
--- 1104,1109 ----
*************** struct gimple_opt_pass pass_init_datastr
*** 1147,1164 ****
  void
  delete_tree_ssa (void)
  {
-   referenced_var_iterator rvi;
-   tree var;
- 
-   /* Remove annotations from every referenced local variable.  */
-   FOR_EACH_REFERENCED_VAR (cfun, var, rvi)
-     {
-       ggc_free (var_ann (var));
-       *DECL_VAR_ANN_PTR (var) = NULL;
-     }
-   htab_delete (gimple_referenced_vars (cfun));
-   cfun->gimple_df->referenced_vars = NULL;
- 
    fini_ssanames ();
  
    /* We no longer maintain the SSA operand cache at this point.  */
--- 1145,1150 ----
Index: trunk/gcc/tree-cfg.c
===================================================================
*** trunk.orig/gcc/tree-cfg.c   2012-08-01 12:37:57.000000000 +0200
--- trunk/gcc/tree-cfg.c        2012-08-01 12:38:40.626962134 +0200
*************** move_stmt_op (tree *tp, int *walk_subtre
*** 6124,6131 ****
            {
              struct function *to_fn = DECL_STRUCT_FUNCTION (p->to_context);
              replace_by_duplicate_decl (tp, p->vars_map, p->to_context);
-             if (gimple_referenced_vars (to_fn))
-               add_referenced_var_1 (*tp, to_fn);
            }
        }
        *walk_subtrees = 0;
--- 6124,6129 ----
Index: trunk/gcc/tree-ssa-operands.c
===================================================================
*** trunk.orig/gcc/tree-ssa-operands.c  2012-08-01 12:38:31.000000000 +0200
--- trunk/gcc/tree-ssa-operands.c       2012-08-01 12:38:40.627962134 +0200
*************** create_vop_var (struct function *fn)
*** 177,183 ****
    TREE_ADDRESSABLE (global_var) = 0;
    VAR_DECL_IS_VIRTUAL_OPERAND (global_var) = 1;
  
-   add_referenced_var_1 (global_var, fn);
    fn->gimple_df->vop = global_var;
  }
  
--- 177,182 ----

Reply via email to