re PR tree-optimization/32663 (revision 126369 went into an infinite loop)

2007-07-11  Daniel Berlin  <dberlin@dberlin.org>

	PR tree-optimization/32663
	
	* tree.h (VALUE_HANDLE_VUSES): Remove.
	(struct tree_value_handle): Remove vuses.

	* tree-vn.c (create_value_handle_for_expr): Don't set
	VALUE_HANDLE_VUSES. 

	* tree-ssa-pre.c (expression_vuses): New.
	(alloc_expression_id): Set up expression_vuses.
	(get_expression_vuses): New.
	(set_expression_vuses): Ditto.
	(clear_expression_ids): Modify for expression_vuses.
	(phi_translate_1): Ditto.
	(phi_translate_set): Ditto.
	(value_dies_in_block_x): Ditto
	(valid_in_sets): Ditto.
	(add_to_sets): Ditto.
	(find_existing_value_expr): Ditto.
	(create_value_handle_for_expr): Ditto.
	(make_values_for_stmt): Ditto.
	(vuse_equiv): Remove.

From-SVN: r126568
This commit is contained in:
Daniel Berlin 2007-07-12 02:20:04 +00:00 committed by Daniel Berlin
parent 433e6a8cf2
commit c5830edf85
8 changed files with 250 additions and 70 deletions

View file

@ -1,3 +1,28 @@
2007-07-11 Daniel Berlin <dberlin@dberlin.org>
PR tree-optimization/32663
* tree.h (VALUE_HANDLE_VUSES): Remove.
(struct tree_value_handle): Remove vuses.
* tree-vn.c (create_value_handle_for_expr): Don't set
VALUE_HANDLE_VUSES.
* tree-ssa-pre.c (expression_vuses): New.
(alloc_expression_id): Set up expression_vuses.
(get_expression_vuses): New.
(set_expression_vuses): Ditto.
(clear_expression_ids): Modify for expression_vuses.
(phi_translate_1): Ditto.
(phi_translate_set): Ditto.
(value_dies_in_block_x): Ditto
(valid_in_sets): Ditto.
(add_to_sets): Ditto.
(find_existing_value_expr): Ditto.
(create_value_handle_for_expr): Ditto.
(make_values_for_stmt): Ditto.
(vuse_equiv): Remove.
2007-07-11 Alexandre Oliva <aoliva@redhat.com>
* Makefile.in (mostlyclean): Remove object files.

View file

@ -1,3 +1,7 @@
2007-07-11 Daniel Berlin <dberlin@dberlin.org>
* gfortran.fortran-torture/compile/pr32663.f90: New test.
2007-07-11 Paolo Carlini <pcarlini@suse.de>
PR c++/31027

View file

@ -37,7 +37,7 @@ void foo (void)
/* Second, we should thread the edge out of the loop via the break
statement. We also realize that the final bytes == 0 test is useless,
and thread over it. */
/* { dg-final { scan-tree-dump-times "Threaded jump" 2 "vrp1" } } */
/* { dg-final { scan-tree-dump-times "Threaded jump" 3 "vrp1" } } */
/* { dg-final { cleanup-tree-dump "vrp1" } } */

View file

@ -0,0 +1,147 @@
SUBROUTINE DIMOID(DEN,RLMO,SSQU,STRI,ATMU,IATM,IWHI,MAPT,INAT,
* IATB,L1,L2,M1,M2,NATS,NOSI,NCAT,NSWE)
C
IMPLICIT DOUBLE PRECISION(A-H,O-Z)
C
DIMENSION RLMO(L1,L1),SSQU(L1,L1),STRI(L2),ATMU(NATS),DEN(M2)
DIMENSION IATM(NATS,M1),IWHI(M1+NATS),MAPT(M1),INAT(M1+NATS)
DIMENSION IATB(NATS,M1)
C
PARAMETER (MXATM=500, MXSH=1000, MXGTOT=5000, MXAO=2047)
C
LOGICAL GOPARR,DSKWRK,MASWRK
C
COMMON /INFOA / NAT,ICH,MUL,NUM,NQMT,NE,NA,NB,
* ZAN(MXATM),C(3,MXATM)
COMMON /IOFILE/ IR,IW,IP,IJKO,IJKT,IDAF,NAV,IODA(400)
COMMON /NSHEL / EX(MXGTOT),CS(MXGTOT),CP(MXGTOT),CD(MXGTOT),
* CF(MXGTOT),CG(MXGTOT),
* KSTART(MXSH),KATOM(MXSH),KTYPE(MXSH),
* KNG(MXSH),KLOC(MXSH),KMIN(MXSH),
* KMAX(MXSH),NSHELL
COMMON /OPTLOC/ CVGLOC,MAXLOC,IPRTLO,ISYMLO,IFCORE,NOUTA,NOUTB,
* MOOUTA(MXAO),MOOUTB(MXAO)
COMMON /PAR / ME,MASTER,NPROC,IBTYP,IPTIM,GOPARR,DSKWRK,MASWRK
COMMON /RUNLAB/ TITLE(10),A(MXATM),B(MXATM),BFLAB(MXAO)
C
C
DO 920 II=1,M1
INAT(II) = 0
920 CONTINUE
C
DO 900 IO = NOUTA+1,NUMLOC
IZ = IO - NOUTA
DO 895 II=NST,NEND
ATMU(II) = 0.0D+00
IATM(II,IZ) = 0
895 CONTINUE
IFUNC = 0
DO 890 ISHELL = 1,NSHELL
IAT = KATOM(ISHELL)
IST = KMIN(ISHELL)
IEN = KMAX(ISHELL)
DO 880 INO = IST,IEN
IFUNC = IFUNC + 1
IF (IAT.LT.NST.OR.IAT.GT.NEND) GOTO 880
ZINT = 0.0D+00
DO 870 II = 1,L1
ZINT = ZINT + RLMO(II,IO)*SSQU(II,IFUNC)
870 CONTINUE
ATMU(IAT) = ATMU(IAT) + RLMO(IFUNC,IO)*ZINT
880 CONTINUE
890 CONTINUE
IF (MASWRK) WRITE(IW,9010) IZ,(ATMU(II),II=NST,NEND)
900 CONTINUE
C
NOSI = 0
DO 700 II=1,M1
NO=0
DO 720 JJ=1,NAT
NO = NO + 1
720 CONTINUE
740 CONTINUE
IF (NO.GT.1.OR.NO.EQ.0) THEN
NOSI = NOSI + 1
IWHI(NOSI) = II
ENDIF
IF (MASWRK)
* WRITE(IW,9030) II,(IATM(J,II),A(IATM(J,II)),J=1,NO)
700 CONTINUE
C
IF (MASWRK) THEN
WRITE(IW,9035) NOSI
IF (NOSI.GT.0) THEN
WRITE(IW,9040) (IWHI(I),I=1,NOSI)
WRITE(IW,9040)
ELSE
WRITE(IW,9040)
ENDIF
ENDIF
C
CALL DCOPY(L1*L1,RLMO,1,SSQU,1)
CALL DCOPY(M2,DEN,1,STRI,1)
C
IP2 = NOUTA
IS2 = M1+NOUTA-NOSI
DO 695 II=1,NAT
INAT(II) = 0
695 CONTINUE
C
DO 690 IAT=1,NAT
DO 680 IORB=1,M1
IP1 = IORB + NOUTA
IF (IATM(1,IORB).NE.IAT) GOTO 680
IF (IATM(2,IORB).NE.0) GOTO 680
INAT(IAT) = INAT(IAT) + 1
IP2 = IP2 + 1
CALL DCOPY(L1,SSQU(1,IP1),1,RLMO(1,IP2),1)
CALL ICOPY(NAT,IATM(1,IORB),1,IATB(1,IP2-NOUTA),1)
MAPT(IORB) = IP2-NOUTA
680 CONTINUE
DO 670 IORB=1,NOSI
IS1 = IWHI(IORB) + NOUTA
IF (IAT.EQ.NAT.AND.IATM(1,IWHI(IORB)).EQ.0) GOTO 675
IF (IATM(1,IWHI(IORB)).NE.IAT) GOTO 670
675 CONTINUE
IS2 = IS2 + 1
MAPT(IWHI(IORB)) = IS2-NOUTA
670 CONTINUE
690 CONTINUE
C
NSWE = 0
NCAT = 0
LASP = 1
NLAST = 0
DO 620 II=1,NAT
NSWE = NSWE + (IWHI(II)*(IWHI(II)-1))/2
NCAT = NCAT + 1
INAT(NCAT) = LASP + NLAST
LASP = INAT(NCAT)
NLAST = IWHI(II)
IWHI(NCAT) = II
620 CONTINUE
C
DO 610 II=1,NOSI
NCAT = NCAT + 1
INAT(NCAT) = LASP + NLAST
LASP = INAT(NCAT)
NLAST = 1
IWHI(NCAT) = 0
610 CONTINUE
C
RETURN
C
8000 FORMAT(/1X,'** MULLIKEN ATOMIC POPULATIONS FOR EACH NON-FROZEN ',
* 'LOCALIZED ORBITAL **')
9000 FORMAT(/3X,'ATOM',2X,100(I2,1X,A4))
9005 FORMAT(1X,'LMO')
9010 FORMAT(1X,I3,3X,100F7.3)
9015 FORMAT(/1X,'** ATOMIC POPULATIONS GREATER THAN ',F4.2,
* ' ARE CONSIDERED MAJOR **')
9020 FORMAT(/2X,'LMO',3X,'MAJOR CONTRIBUTIONS FROM ATOM(S)')
9030 FORMAT(2X,I3,2X,100(I2,1X,A2,2X))
9035 FORMAT(/1X,'NO OF LMOS INVOLVING MORE THAN ONE ATOM =',I3)
9040 FORMAT(1X,'THESE ARE LMOS :',100I3)
C
END

View file

@ -185,6 +185,12 @@ Boston, MA 02110-1301, USA. */
/* Next global expression id number. */
static unsigned int next_expression_id;
typedef VEC(tree, gc) *vuse_vec;
DEF_VEC_P (vuse_vec);
DEF_VEC_ALLOC_P (vuse_vec, heap);
static VEC(vuse_vec, heap) *expression_vuses;
/* Mapping from expression to id number we can use in bitmap sets. */
static VEC(tree, heap) *expressions;
@ -203,6 +209,7 @@ alloc_expression_id (tree expr)
ann->aux = XNEW (unsigned int);
* ((unsigned int *)ann->aux) = next_expression_id++;
VEC_safe_push (tree, heap, expressions, expr);
VEC_safe_push (vuse_vec, heap, expression_vuses, NULL);
return next_expression_id - 1;
}
@ -240,6 +247,25 @@ expression_for_id (unsigned int id)
return VEC_index (tree, expressions, id);
}
/* Return the expression vuses for EXPR, if there are any. */
static inline vuse_vec
get_expression_vuses (tree expr)
{
return VEC_index (vuse_vec, expression_vuses,
get_or_alloc_expression_id (expr));
}
/* Set the expression vuses for EXPR to VUSES. */
static inline void
set_expression_vuses (tree expr, vuse_vec vuses)
{
VEC_replace (vuse_vec, expression_vuses,
get_or_alloc_expression_id (expr), vuses);
}
/* Free the expression id field in all of our expressions,
and then destroy the expressions array. */
@ -255,6 +281,7 @@ clear_expression_ids (void)
tree_common_ann (expr)->aux = NULL;
}
VEC_free (tree, heap, expressions);
VEC_free (vuse_vec, heap, expression_vuses);
}
static bool in_fre = false;
@ -956,13 +983,7 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
/* Phi translations of a given expression don't change. */
if (EXPR_P (expr) || GIMPLE_STMT_P (expr))
{
tree vh;
vh = get_value_handle (expr);
if (vh && TREE_CODE (vh) == VALUE_HANDLE)
phitrans = phi_trans_lookup (expr, pred, VALUE_HANDLE_VUSES (vh));
else
phitrans = phi_trans_lookup (expr, pred, NULL);
phitrans = phi_trans_lookup (expr, pred, get_expression_vuses (expr));
}
else
phitrans = phi_trans_lookup (expr, pred, NULL);
@ -995,10 +1016,9 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
tree oldsc = CALL_EXPR_STATIC_CHAIN (expr);
tree newfn, newsc = NULL;
tree newexpr = NULL_TREE;
tree vh = get_value_handle (expr);
bool invariantarg = false;
int i, nargs;
VEC (tree, gc) *vuses = VALUE_HANDLE_VUSES (vh);
VEC (tree, gc) *vuses = get_expression_vuses (expr);
VEC (tree, gc) *tvuses;
newfn = phi_translate_1 (find_leader_in_sets (oldfn, set1, set2),
@ -1084,6 +1104,7 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
newexpr->base.ann = NULL;
vn_lookup_or_add_with_vuses (newexpr, tvuses);
expr = newexpr;
set_expression_vuses (newexpr, tvuses);
}
phi_trans_add (oldexpr, expr, pred, tvuses);
}
@ -1095,14 +1116,16 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
VEC (tree, gc) * oldvuses = NULL;
VEC (tree, gc) * newvuses = NULL;
oldvuses = VALUE_HANDLE_VUSES (get_value_handle (expr));
oldvuses = get_expression_vuses (expr);
if (oldvuses)
newvuses = translate_vuses_through_block (oldvuses, phiblock,
pred);
if (oldvuses != newvuses)
vn_lookup_or_add_with_vuses (expr, newvuses);
{
vn_lookup_or_add_with_vuses (expr, newvuses);
set_expression_vuses (expr, newvuses);
}
phi_trans_add (oldexpr, expr, pred, newvuses);
}
return expr;
@ -1160,7 +1183,7 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
}
}
oldvuses = VALUE_HANDLE_VUSES (get_value_handle (expr));
oldvuses = get_expression_vuses (expr);
if (oldvuses)
newvuses = translate_vuses_through_block (oldvuses, phiblock,
pred);
@ -1195,6 +1218,7 @@ phi_translate_1 (tree expr, bitmap_set_t set1, bitmap_set_t set2,
{
newexpr->base.ann = NULL;
vn_lookup_or_add_with_vuses (newexpr, newvuses);
set_expression_vuses (newexpr, newvuses);
}
expr = newexpr;
}
@ -1360,14 +1384,8 @@ phi_translate_set (bitmap_set_t dest, bitmap_set_t set, basic_block pred,
we won't look them up that way, or use the result, anyway. */
if (translated && !is_gimple_min_invariant (translated))
{
tree vh = get_value_handle (translated);
VEC (tree, gc) *vuses;
/* The value handle itself may also be an invariant, in
which case, it has no vuses. */
vuses = !is_gimple_min_invariant (vh)
? VALUE_HANDLE_VUSES (vh) : NULL;
phi_trans_add (expr, translated, pred, vuses);
phi_trans_add (expr, translated, pred,
get_expression_vuses (translated));
}
if (translated != NULL)
@ -1413,7 +1431,7 @@ bitmap_find_leader (bitmap_set_t set, tree val)
return NULL;
}
/* Determine if VALUE, a memory operation, is ANTIC_IN at the top of
/* Determine if EXPR, a memory expressionn, is ANTIC_IN at the top of
BLOCK by seeing if it is not killed in the block. Note that we are
only determining whether there is a store that kills it. Because
of the order in which clean iterates over values, we are guaranteed
@ -1421,11 +1439,11 @@ bitmap_find_leader (bitmap_set_t set, tree val)
ANTIC_IN set already. */
static bool
value_dies_in_block_x (tree vh, basic_block block)
value_dies_in_block_x (tree expr, basic_block block)
{
int i;
tree vuse;
VEC (tree, gc) *vuses = VALUE_HANDLE_VUSES (vh);
VEC (tree, gc) *vuses = get_expression_vuses (expr);
/* Conservatively, a value dies if it's vuses are defined in this
block, unless they come from phi nodes (which are merge operations,
@ -1462,7 +1480,6 @@ static bool
valid_in_sets (bitmap_set_t set1, bitmap_set_t set2, tree expr,
basic_block block)
{
tree vh = get_value_handle (expr);
switch (TREE_CODE_CLASS (TREE_CODE (expr)))
{
case tcc_binary:
@ -1504,7 +1521,7 @@ valid_in_sets (bitmap_set_t set1, bitmap_set_t set2, tree expr,
if (!union_contains_value (set1, set2, arg))
return false;
}
return !value_dies_in_block_x (vh, block);
return !value_dies_in_block_x (expr, block);
}
return false;
}
@ -1540,7 +1557,7 @@ valid_in_sets (bitmap_set_t set1, bitmap_set_t set2, tree expr,
&& !union_contains_value (set1, set2, op3))
return false;
}
return !value_dies_in_block_x (vh, block);
return !value_dies_in_block_x (expr, block);
}
}
return false;
@ -1552,7 +1569,7 @@ valid_in_sets (bitmap_set_t set1, bitmap_set_t set2, tree expr,
}
case tcc_declaration:
return !value_dies_in_block_x (vh, block);
return !value_dies_in_block_x (expr, block);
default:
/* No other cases should be encountered. */
@ -2905,11 +2922,11 @@ add_to_exp_gen (basic_block block, tree op)
any). */
static inline void
add_to_sets (tree var, tree expr, tree stmt, bitmap_set_t s1,
add_to_sets (tree var, tree expr, VEC(tree, gc) *vuses, bitmap_set_t s1,
bitmap_set_t s2)
{
tree val;
val = vn_lookup_or_add_with_stmt (expr, stmt);
val = vn_lookup_or_add_with_vuses (expr, vuses);
/* VAR and EXPR may be the same when processing statements for which
we are not computing value numbers (e.g., non-assignments, or
@ -2928,7 +2945,7 @@ add_to_sets (tree var, tree expr, tree stmt, bitmap_set_t s1,
and return it if it exists. */
static inline tree
find_existing_value_expr (tree t, tree stmt)
find_existing_value_expr (tree t, VEC (tree, gc) *vuses)
{
bitmap_iterator bi;
unsigned int bii;
@ -2936,7 +2953,7 @@ find_existing_value_expr (tree t, tree stmt)
bitmap_set_t exprset;
if (REFERENCE_CLASS_P (t) || TREE_CODE (t) == CALL_EXPR || DECL_P (t))
vh = vn_lookup_with_stmt (t, stmt);
vh = vn_lookup_with_vuses (t, vuses);
else
vh = vn_lookup (t);
@ -2960,7 +2977,7 @@ find_existing_value_expr (tree t, tree stmt)
any). Insert EXPR's operands into the EXP_GEN set for BLOCK. */
static inline tree
create_value_expr_from (tree expr, basic_block block, tree stmt)
create_value_expr_from (tree expr, basic_block block, VEC (tree, gc) *vuses)
{
int i;
enum tree_code code = TREE_CODE (expr);
@ -3008,9 +3025,10 @@ create_value_expr_from (tree expr, basic_block block, tree stmt)
/* Recursively value-numberize reference ops and tree lists. */
if (REFERENCE_CLASS_P (op))
{
tree tempop = create_value_expr_from (op, block, stmt);
tree tempop = create_value_expr_from (op, block, vuses);
op = tempop ? tempop : op;
val = vn_lookup_or_add_with_stmt (op, stmt);
val = vn_lookup_or_add_with_vuses (op, vuses);
set_expression_vuses (op, vuses);
}
else
{
@ -3024,7 +3042,7 @@ create_value_expr_from (tree expr, basic_block block, tree stmt)
TREE_OPERAND (vexpr, i) = val;
}
efi = find_existing_value_expr (vexpr, stmt);
efi = find_existing_value_expr (vexpr, vuses);
if (efi)
return efi;
get_or_alloc_expression_id (vexpr);
@ -3289,22 +3307,6 @@ make_values_for_phi (tree phi, basic_block block)
}
}
/* Return true if both the statement and the value handles have no
vuses, or both the statement and the value handle do have vuses.
Unlike SCCVN, PRE needs not only to know equivalence, but what the
actual vuses are so it can translate them through blocks. Thus,
we have to make a new value handle if the existing one has no
vuses but needs them. */
static bool
vuse_equiv (tree vh1, tree stmt)
{
bool stmt_has_vuses = !ZERO_SSA_OPERANDS (stmt, SSA_OP_VIRTUAL_USES);
return (VALUE_HANDLE_VUSES (vh1) && stmt_has_vuses)
|| (!VALUE_HANDLE_VUSES (vh1) && !stmt_has_vuses);
}
/* Create value handles for STMT in BLOCK. Return true if we handled
the statement. */
@ -3316,8 +3318,10 @@ make_values_for_stmt (tree stmt, basic_block block)
tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
tree valvh = NULL_TREE;
tree lhsval;
VEC (tree, gc) *vuses = NULL;
valvh = get_sccvn_value (lhs);
if (valvh)
{
vn_add (lhs, valvh);
@ -3340,7 +3344,7 @@ make_values_for_stmt (tree stmt, basic_block block)
}
lhsval = valvh ? valvh : get_value_handle (lhs);
vuses = copy_vuses_from_stmt (stmt);
STRIP_USELESS_TYPE_CONVERSION (rhs);
if (can_value_number_operation (rhs)
&& (!lhsval || !is_gimple_min_invariant (lhsval)))
@ -3348,12 +3352,13 @@ make_values_for_stmt (tree stmt, basic_block block)
/* For value numberable operation, create a
duplicate expression with the operands replaced
with the value handles of the original RHS. */
tree newt = create_value_expr_from (rhs, block, stmt);
tree newt = create_value_expr_from (rhs, block, vuses);
if (newt)
{
set_expression_vuses (newt, vuses);
/* If we already have a value number for the LHS, reuse
it rather than creating a new one. */
if (lhsval && vuse_equiv (lhsval, stmt))
if (lhsval)
{
set_value_handle (newt, lhsval);
if (!is_gimple_min_invariant (lhsval))
@ -3361,7 +3366,7 @@ make_values_for_stmt (tree stmt, basic_block block)
}
else
{
tree val = vn_lookup_or_add_with_stmt (newt, stmt);
tree val = vn_lookup_or_add_with_vuses (newt, vuses);
vn_add (lhs, val);
}
@ -3382,6 +3387,7 @@ make_values_for_stmt (tree stmt, basic_block block)
if (lhsval)
{
set_expression_vuses (rhs, vuses);
set_value_handle (rhs, lhsval);
if (!is_gimple_min_invariant (lhsval))
add_to_value (lhsval, rhs);
@ -3393,7 +3399,8 @@ make_values_for_stmt (tree stmt, basic_block block)
/* Compute a value number for the RHS of the statement
and add its value to the AVAIL_OUT set for the block.
Add the LHS to TMP_GEN. */
add_to_sets (lhs, rhs, stmt, TMP_GEN (block),
set_expression_vuses (rhs, vuses);
add_to_sets (lhs, rhs, vuses, TMP_GEN (block),
AVAIL_OUT (block));
}
/* None of the rest of these can be PRE'd. */

View file

@ -1431,6 +1431,14 @@ try_to_simplify (tree stmt, tree rhs)
/* For references, see if we find a result for the lookup,
and use it if we do. */
case tcc_declaration:
/* Pull out any truly constant values. */
if (TREE_READONLY (rhs)
&& TREE_STATIC (rhs)
&& DECL_INITIAL (rhs)
&& is_gimple_min_invariant (DECL_INITIAL (rhs)))
return DECL_INITIAL (rhs);
/* Fallthrough. */
case tcc_reference:
{
tree result = vn_reference_lookup (rhs,

View file

@ -108,9 +108,6 @@ set_value_handle (tree e, tree v)
gcc_assert (is_gimple_min_invariant (e));
}
/* A comparison function for use in qsort to compare vuses. Simply
subtracts version numbers. */
@ -329,7 +326,7 @@ vn_lookup_with_vuses (tree expr, VEC (tree, gc) *vuses)
}
static tree
create_value_handle_for_expr (tree expr, VEC (tree, gc) *vuses)
create_value_handle_for_expr (tree expr, VEC(tree, gc) *vuses)
{
tree v;
@ -337,8 +334,6 @@ create_value_handle_for_expr (tree expr, VEC (tree, gc) *vuses)
if (dump_file && (dump_flags & TDF_DETAILS))
print_creation_to_file (v, expr, vuses);
if (vuses)
VALUE_HANDLE_VUSES (v) = vuses;
return v;
}

View file

@ -3340,9 +3340,6 @@ struct tree_statement_list
#define VALUE_HANDLE_EXPR_SET(NODE) \
(VALUE_HANDLE_CHECK (NODE)->value_handle.expr_set)
#define VALUE_HANDLE_VUSES(NODE) \
(VALUE_HANDLE_CHECK (NODE)->value_handle.vuses)
/* Defined and used in tree-ssa-pre.c. */
struct tree_value_handle GTY(())
@ -3356,9 +3353,6 @@ struct tree_value_handle GTY(())
conveniently dense form starting at 0, so that we can make
bitmaps of value handles. */
unsigned int id;
/* Set of virtual uses represented by this handle. */
VEC (tree, gc) *vuses;
};
/* Define the overall contents of a tree node.