re PR tree-optimization/40801 (internal compiler error: in vect_get_vec_def_for_stmt_copy, at tree-vect-stmts.c:1096)
PR tree-optimization/40801 * tree-vect-stmts.c (vectorizable_call): Get previous copy of vector operand from the previous copy of vector statement. Pass the correct definition type value to vect_get_vec_def_for_stmt_copy(). From-SVN: r150096
This commit is contained in:
parent
23c35ef67a
commit
63827fb8e2
@ -1,3 +1,11 @@
|
||||
2009-07-26 Ira Rosen <irar@il.ibm.com>
|
||||
|
||||
PR tree-optimization/40801
|
||||
* tree-vect-stmts.c (vectorizable_call): Get previous copy
|
||||
of vector operand from the previous copy of vector statement.
|
||||
Pass the correct definition type value to
|
||||
vect_get_vec_def_for_stmt_copy().
|
||||
|
||||
2009-07-25 John David Anglin <dave.anglin@nrc-cnrc.gc.ca>
|
||||
|
||||
* collect2.c (scan_libraries): Use CONST_CAST2 to perform char ** to
|
||||
|
@ -1,3 +1,10 @@
|
||||
2009-07-26 Ira Rosen <irar@il.ibm.com>
|
||||
|
||||
PR tree-optimization/40801
|
||||
* gfortran.dg/vect/fast-math-real8-pr40801.f90: New test.
|
||||
* gfortran.dg/vect/vect.exp: Run tests starting with
|
||||
"fast-math-real8" with -ffast-math and -fdefault-real-8.
|
||||
|
||||
2009-07-25 David Daney <ddaney@caviumnetworks.com>
|
||||
|
||||
PR rtl-optimization/40445
|
||||
|
37
gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90
Normal file
37
gcc/testsuite/gfortran.dg/vect/fast-math-real8-pr40801.f90
Normal file
@ -0,0 +1,37 @@
|
||||
! { dg-do compile }
|
||||
|
||||
MODULE YOMPHY0
|
||||
REAL :: ECMNP
|
||||
REAL :: SCO
|
||||
REAL :: USDMLT
|
||||
END MODULE YOMPHY0
|
||||
SUBROUTINE ACCONV ( KIDIA,KFDIA,KLON,KTDIA,KLEV,&
|
||||
&CDLOCK)
|
||||
USE YOMPHY0 , ONLY : ECMNP ,SCO ,USDMLT
|
||||
REAL :: PAPHIF(KLON,KLEV),PCVGQ(KLON,KLEV)&
|
||||
&,PFPLCL(KLON,0:KLEV),PFPLCN(KLON,0:KLEV),PSTRCU(KLON,0:KLEV)&
|
||||
&,PSTRCV(KLON,0:KLEV)
|
||||
INTEGER :: KNLAB(KLON,KLEV),KNND(KLON)
|
||||
REAL :: ZCP(KLON,KLEV),ZLHE(KLON,KLEV),ZDSE(KLON,KLEV)&
|
||||
&,ZPOII(KLON),ZALF(KLON),ZLN(KLON),ZUN(KLON),ZVN(KLON)&
|
||||
&,ZPOIL(KLON)
|
||||
DO JLEV=KLEV-1,KTDIA,-1
|
||||
DO JIT=1,NBITER
|
||||
ZLN(JLON)=MAX(0.,ZLN(JLON)&
|
||||
&-(ZQW(JLON,JLEV)-ZQN(JLON)&
|
||||
&*(PQ(JLON,JLEV+1)-ZQN(JLON))))*KNLAB(JLON,JLEV)
|
||||
ENDDO
|
||||
ENDDO
|
||||
IF (ITOP < KLEV+1) THEN
|
||||
DO JLON=KIDIA,KFDIA
|
||||
ZZVAL=PFPLCL(JLON,KLEV)+PFPLCN(JLON,KLEV)-SCO
|
||||
KNND(JLON)=KNND(JLON)*MAX(0.,-SIGN(1.,0.-ZZVAL))
|
||||
ENDDO
|
||||
DO JLEV=ITOP,KLEV
|
||||
DO JLON=KIDIA,KFDIA
|
||||
ENDDO
|
||||
ENDDO
|
||||
ENDIF
|
||||
END SUBROUTINE ACCONV
|
||||
|
||||
! { dg-final { cleanup-tree-dump "vect" } }
|
@ -125,6 +125,12 @@ lappend DEFAULT_VECTCFLAGS "-ffast-math"
|
||||
dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/fast-math-*.\[fF\]{,90,95,03,08} ]] \
|
||||
"" $DEFAULT_VECTCFLAGS
|
||||
|
||||
# -ffast-math tests
|
||||
set DEFAULT_VECTCFLAGS $SAVED_DEFAULT_VECTCFLAGS
|
||||
lappend DEFAULT_VECTCFLAGS "-ffast-math" "-fdefault-real-8"
|
||||
dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/fast-math-real8*.\[fF\]{,90,95,03,08} ]] \
|
||||
"" $DEFAULT_VECTCFLAGS
|
||||
|
||||
# -fvect-cost-model tests
|
||||
set DEFAULT_VECTCFLAGS $SAVED_DEFAULT_VECTCFLAGS
|
||||
lappend DEFAULT_VECTCFLAGS "-fvect-cost-model"
|
||||
|
@ -1227,7 +1227,7 @@ vectorizable_call (gimple stmt, gimple_stmt_iterator *gsi, gimple *vec_stmt)
|
||||
tree fndecl, new_temp, def, rhs_type, lhs_type;
|
||||
gimple def_stmt;
|
||||
enum vect_def_type dt[2] = {vect_unknown_def_type, vect_unknown_def_type};
|
||||
gimple new_stmt;
|
||||
gimple new_stmt = NULL;
|
||||
int ncopies, j;
|
||||
VEC(tree, heap) *vargs = NULL;
|
||||
enum { NARROW, NONE, WIDEN } modifier;
|
||||
@ -1367,8 +1367,11 @@ vectorizable_call (gimple stmt, gimple_stmt_iterator *gsi, gimple *vec_stmt)
|
||||
vec_oprnd0
|
||||
= vect_get_vec_def_for_operand (op, stmt, NULL);
|
||||
else
|
||||
vec_oprnd0
|
||||
= vect_get_vec_def_for_stmt_copy (dt[nargs], vec_oprnd0);
|
||||
{
|
||||
vec_oprnd0 = gimple_call_arg (new_stmt, i);
|
||||
vec_oprnd0
|
||||
= vect_get_vec_def_for_stmt_copy (dt[i], vec_oprnd0);
|
||||
}
|
||||
|
||||
VEC_quick_push (tree, vargs, vec_oprnd0);
|
||||
}
|
||||
@ -1406,14 +1409,15 @@ vectorizable_call (gimple stmt, gimple_stmt_iterator *gsi, gimple *vec_stmt)
|
||||
vec_oprnd0
|
||||
= vect_get_vec_def_for_operand (op, stmt, NULL);
|
||||
vec_oprnd1
|
||||
= vect_get_vec_def_for_stmt_copy (dt[nargs], vec_oprnd0);
|
||||
= vect_get_vec_def_for_stmt_copy (dt[i], vec_oprnd0);
|
||||
}
|
||||
else
|
||||
{
|
||||
vec_oprnd1 = gimple_call_arg (new_stmt, 2*i);
|
||||
vec_oprnd0
|
||||
= vect_get_vec_def_for_stmt_copy (dt[nargs], vec_oprnd1);
|
||||
= vect_get_vec_def_for_stmt_copy (dt[i], vec_oprnd1);
|
||||
vec_oprnd1
|
||||
= vect_get_vec_def_for_stmt_copy (dt[nargs], vec_oprnd0);
|
||||
= vect_get_vec_def_for_stmt_copy (dt[i], vec_oprnd0);
|
||||
}
|
||||
|
||||
VEC_quick_push (tree, vargs, vec_oprnd0);
|
||||
|
Loading…
x
Reference in New Issue
Block a user