OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /openrisc/trunk/gnu-old/gcc-4.2.2/gcc/testsuite/gfortran.dg/vect
    from Rev 154 to Rev 816
    Reverse comparison

Rev 154 → Rev 816

/vect-4.f90
0,0 → 1,16
! { dg-do compile }
! { dg-require-effective-target vect_float }
 
! Peeling to align the store to Y will also align the load from Y.
! The load from X may still be misaligned.
 
SUBROUTINE SAXPY(X, Y, A)
DIMENSION X(64), Y(64)
Y = Y + A * X
END
 
! { dg-final { scan-tree-dump-times "vectorized 1 loops" 1 "vect" } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using peeling" 1 "vect" } }
! { dg-final { scan-tree-dump-times "Vectorizing an unaligned access" 1 "vect" } }
! { dg-final { scan-tree-dump-times "accesses have the same alignment." 1 "vect" } }
! { dg-final { cleanup-tree-dump "vect" } }
/vect-5.f90
0,0 → 1,51
! { dg-require-effective-target vect_int }
 
Subroutine foo (N, M)
Integer N
Integer M
integer A(8,16)
integer B(8)
 
B = (/ 2, 3, 5, 7, 11, 13, 17, 23 /)
 
! Unknown loop bound. J depends on I.
 
do I = 1, N
do J = I, M
A(J,2) = B(J)
end do
end do
 
do I = 1, N
do J = I, M
if (A(J,2) /= B(J)) then
call abort ()
endif
end do
end do
 
Return
end
 
 
program main
 
Call foo (16, 8)
 
stop
end
 
! { dg-final { scan-tree-dump-times "vectorized 2 loops" 1 "vect" } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using peeling" 1 "vect" { xfail { vect_no_align } } } }
! { dg-final { scan-tree-dump-times "Vectorizing an unaligned access" 2 "vect" { xfail { vect_no_align } } } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using versioning." 3 "vect" { target { ilp32 && vect_no_align } } } }
 
! We also expect to vectorize one loop for lp64 targets that support
! misaligned access:
! scan-tree-dump-times "vectorized 1 loops" 1 "vect" { target { lp64 && !vect_no_align } }
! scan-tree-dump-times "Alignment of access forced using peeling" 1 "vect" { target { lp64 && !vect_no_align } }
! scan-tree-dump-times "Vectorizing an unaligned access" 1 "vect" { target { lp64 && !vect_no_align } }
! but we currently can't combine logical operators. (Could define
! a keyword for "not_vect_no_align" if desired).
 
! { dg-final { cleanup-tree-dump "vect" } }
/pr19049.f90
0,0 → 1,24
! { dg-do compile }
! { dg-require-effective-target vect_float }
 
subroutine s111 (ntimes,ld,n,ctime,dtime,a,b,c,d,e,aa,bb,cc)
! linear dependence testing
! no dependence - vectorizable
! but not consecutive access
 
integer ntimes, ld, n, i, nl
real a(n), b(n), c(n), d(n), e(n), aa(ld,n), bb(ld,n), cc(ld,n)
real t1, t2, second, chksum, ctime, dtime, cs1d
do 1 nl = 1,2*ntimes
do 10 i = 2,n,2
a(i) = a(i-1) + b(i)
10 continue
call dummy(ld,n,a,b,c,d,e,aa,bb,cc,1.)
1 continue
return
end
 
! { dg-final { scan-tree-dump-times "vectorized 1 loops" 0 "vect" } }
! { dg-final { scan-tree-dump-times "complicated access pattern" 1 "vect" } }
! { dg-final { cleanup-tree-dump "vect" } }
 
/vect-1.f90
0,0 → 1,11
! { dg-do compile }
! { dg-require-effective-target vect_float }
 
DIMENSION A(1000000), B(1000000), C(1000000)
READ*, X, Y
A = LOG(X); B = LOG(Y); C = A + B
PRINT*, C(500000)
END
 
! { dg-final { scan-tree-dump-times "vectorized 3 loops" 1 "vect" } }
! { dg-final { cleanup-tree-dump "vect" } }
/vect.exp
0,0 → 1,99
# Copyright (C) 1997, 2004, 2007 Free Software Foundation, Inc.
 
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 3 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# You should have received a copy of the GNU General Public License
# along with GCC; see the file COPYING3. If not see
# <http://www.gnu.org/licenses/>.
 
# GCC testsuite that uses the `dg.exp' driver.
 
# Load support procs.
load_lib gfortran-dg.exp
load_lib target-supports.exp
 
# Set up flags used for tests that don't specify options.
set DEFAULT_VECTCFLAGS ""
 
# These flags are used for all targets.
lappend DEFAULT_VECTCFLAGS "-O2" "-ftree-vectorize" \
"-ftree-vectorizer-verbose=4" "-fdump-tree-vect-stats"
 
# If the target system supports vector instructions, the default action
# for a test is 'run', otherwise it's 'compile'. Save current default.
# Executing vector instructions on a system without hardware vector support
# is also disabled by a call to check_vect, but disabling execution here is
# more efficient.
global dg-do-what-default
set save-dg-do-what-default ${dg-do-what-default}
 
# Skip these tests for targets that do not support generating vector
# code. Set additional target-dependent vector flags, which can be
# overridden by using dg-options in individual tests.
if [istarget "powerpc*-*-*"] {
# If there are powerpc targets to skip, do it here.
 
lappend DEFAULT_VECTCFLAGS "-maltivec"
if [check_vmx_hw_available] {
set dg-do-what-default run
} else {
if [is-effective-target ilp32] {
# Specify a cpu that supports VMX for compile-only tests.
lappend DEFAULT_VECTCFLAGS "-mcpu=7400"
}
set dg-do-what-default compile
}
} elseif { [istarget "i?86-*-*"] || [istarget "x86_64-*-*"] } {
lappend DEFAULT_VECTCFLAGS "-msse2"
set dg-do-what-default run
} elseif [istarget "mipsisa64*-*-*"] {
lappend DEFAULT_VECTCFLAGS "-mpaired-single"
set dg-do-what-default run
} elseif [istarget "sparc*-*-*"] {
lappend DEFAULT_VECTCFLAGS "-mcpu=ultrasparc" "-mvis"
set dg-do-what-default run
} elseif [istarget "alpha*-*-*"] {
lappend DEFAULT_VECTCFLAGS "-mmax"
if [check_alpha_max_hw_available] {
set dg-do-what-default run
} else {
set dg-do-what-default compile
}
} elseif [istarget "ia64-*-*"] {
set dg-do-what-default run
} else {
return
}
 
# Return 1 if the effective target is LP64 or if the effective target
# does not support a vector alignment mechanism.
 
proc check_effective_target_lp64_or_vect_no_align { } {
if { [is-effective-target lp64]
|| [is-effective-target vect_no_align] } {
set answer 1
} else {
set answer 0
}
return $answer
}
 
# Initialize `dg'.
dg-init
 
# Main loop.
gfortran-dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/*.\[fF\]{,90,95,03} ]] $DEFAULT_VECTCFLAGS
 
# Clean up.
set dg-do-what-default ${save-dg-do-what-default}
 
# All done.
dg-finish
/vect-2.f90
0,0 → 1,22
! { dg-do compile }
! { dg-require-effective-target vect_float }
 
SUBROUTINE FOO(A, B, C)
DIMENSION A(1000000), B(1000000), C(1000000)
READ*, X, Y
A = LOG(X); B = LOG(Y); C = A + B
PRINT*, C(500000)
END
 
! First loop (A=LOG(X)) is vectorized using peeling to align the store.
! Same for the second loop (B=LOG(Y)).
! Third loop (C = A + B) is vectorized using versioning (for targets that don't
! support unaligned loads) or using peeling to align the store (on targets that
! support unaligned loads).
 
! { dg-final { scan-tree-dump-times "vectorized 3 loops" 1 "vect" } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using peeling" 3 "vect" { xfail vect_no_align } } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using peeling" 2 "vect" { target vect_no_align } } }
! { dg-final { scan-tree-dump-times "Vectorizing an unaligned access" 2 "vect" { xfail vect_no_align } } }
! { dg-final { scan-tree-dump-times "Alignment of access forced using versioning." 3 "vect" {target vect_no_align } } }
! { dg-final { cleanup-tree-dump "vect" } }
/vect-3.f90
0,0 → 1,11
! { dg-do compile }
! { dg-require-effective-target vect_float }
 
SUBROUTINE SAXPY(X, Y, A, N)
DIMENSION X(N), Y(N)
Y = Y + A * X
END
 
! fail to vectorize due to failure to compute number of iterations (PR tree-optimization/18527)
! { dg-final { scan-tree-dump-times "Vectorizing an unaligned access" 2 "vect" { xfail *-*-* } } }
! { dg-final { cleanup-tree-dump "vect" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.