re PR middle-end/43796 (ICE in is_overflow_infinity (tree-vrp.c:184) with gfortran -fcheck=bounds -O2)

2010-04-19  Richard Guenther  <rguenther@suse.de>

	PR tree-optimization/43796
	* tree-vrp.c (adjust_range_with_scev): Lookup init and step
	from SCEV in the lattice.
	(vrp_visit_phi_node): Dump change.

	* gfortran.dg/pr43796.f90: New testcase.

From-SVN: r158520
This commit is contained in:
Richard Guenther 2010-04-19 15:17:26 +00:00 committed by Richard Biener
parent 479881c395
commit 1936a7d49c
4 changed files with 82 additions and 2 deletions

View File

@ -1,3 +1,10 @@
2010-04-19 Richard Guenther <rguenther@suse.de>
PR tree-optimization/43796
* tree-vrp.c (adjust_range_with_scev): Lookup init and step
from SCEV in the lattice.
(vrp_visit_phi_node): Dump change.
2010-04-19 Richard Guenther <rguenther@suse.de>
* configure.ac: Fix quoting around elf_getshstrndx ABI check.

View File

@ -1,3 +1,8 @@
2010-04-19 Richard Guenther <rguenther@suse.de>
PR tree-optimization/43796
* gfortran.dg/pr43796.f90: New testcase.
2010-04-19 Richard Guenther <rguenther@suse.de>
PR tree-optimization/43783

View File

@ -0,0 +1,51 @@
! { dg-do compile }
! { dg-options "-O2 -fcheck=bounds" }
FUNCTION F06FKFN(N,W,INCW,X,INCX)
IMPLICIT NONE
INTEGER, PARAMETER :: WP = KIND(0.0D0)
REAL (KIND=WP) :: F06FKFN
REAL (KIND=WP), PARAMETER :: ONE = 1.0E+0_WP
REAL (KIND=WP), PARAMETER :: ZERO = 0.0E+0_WP
INTEGER, INTENT (IN) :: INCW, INCX, N
REAL (KIND=WP), INTENT (IN) :: W(*), X(*)
REAL (KIND=WP) :: ABSYI, NORM, SCALE, SSQ
INTEGER :: I, IW, IX
REAL (KIND=WP), EXTERNAL :: F06BMFN
INTRINSIC ABS, SQRT
IF (N<1) THEN
NORM = ZERO
ELSE IF (N==1) THEN
NORM = SQRT(W(1))*ABS(X(1))
ELSE
IF (INCW>0) THEN
IW = 1
ELSE
IW = 1 - (N-1)*INCW
END IF
IF (INCX>0) THEN
IX = 1
ELSE
IX = 1 - (N-1)*INCX
END IF
SCALE = ZERO
SSQ = ONE
DO I = 1, N
IF ((W(IW)/=ZERO) .AND. (X(IX)/=ZERO)) THEN
ABSYI = SQRT(W(IW))*ABS(X(IX))
IF (SCALE<ABSYI) THEN
SSQ = 1 + SSQ*(SCALE/ABSYI)**2
SCALE = ABSYI
ELSE
SSQ = SSQ + (ABSYI/SCALE)**2
END IF
END IF
IW = IW + INCW
IX = IX + INCX
END DO
NORM = F06BMFN(SCALE,SSQ)
END IF
F06FKFN = NORM
RETURN
END FUNCTION F06FKFN

View File

@ -3153,7 +3153,7 @@ static void
adjust_range_with_scev (value_range_t *vr, struct loop *loop,
gimple stmt, tree var)
{
tree init, step, chrec, tmin, tmax, min, max, type;
tree init, step, chrec, tmin, tmax, min, max, type, tem;
enum ev_direction dir;
/* TODO. Don't adjust anti-ranges. An anti-range may provide
@ -3174,7 +3174,13 @@ adjust_range_with_scev (value_range_t *vr, struct loop *loop,
return;
init = initial_condition_in_loop_num (chrec, loop->num);
tem = op_with_constant_singleton_value_range (init);
if (tem)
init = tem;
step = evolution_part_in_loop_num (chrec, loop->num);
tem = op_with_constant_singleton_value_range (step);
if (tem)
step = tem;
/* If STEP is symbolic, we can't know whether INIT will be the
minimum or maximum value in the range. Also, unless INIT is
@ -6432,7 +6438,18 @@ vrp_visit_phi_node (gimple phi)
/* If the new range is different than the previous value, keep
iterating. */
if (update_value_range (lhs, &vr_result))
return SSA_PROP_INTERESTING;
{
if (dump_file && (dump_flags & TDF_DETAILS))
{
fprintf (dump_file, "Found new range for ");
print_generic_expr (dump_file, lhs, 0);
fprintf (dump_file, ": ");
dump_value_range (dump_file, &vr_result);
fprintf (dump_file, "\n\n");
}
return SSA_PROP_INTERESTING;
}
/* Nothing changed, don't add outgoing edges. */
return SSA_PROP_NOT_INTERESTING;