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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [vect/] [vect-5.f90] - Diff between revs 154 and 816

Only display areas with differences | Details | Blame | View Log

Rev 154 Rev 816
! { dg-require-effective-target vect_int }
! { dg-require-effective-target vect_int }
        Subroutine foo (N, M)
        Subroutine foo (N, M)
        Integer N
        Integer N
        Integer M
        Integer M
        integer A(8,16)
        integer A(8,16)
        integer B(8)
        integer B(8)
        B = (/ 2, 3, 5, 7, 11, 13, 17, 23 /)
        B = (/ 2, 3, 5, 7, 11, 13, 17, 23 /)
        ! Unknown loop bound. J depends on I.
        ! Unknown loop bound. J depends on I.
        do I = 1, N
        do I = 1, N
          do J = I, M
          do J = I, M
            A(J,2) = B(J)
            A(J,2) = B(J)
          end do
          end do
        end do
        end do
        do I = 1, N
        do I = 1, N
          do J = I, M
          do J = I, M
            if (A(J,2) /= B(J)) then
            if (A(J,2) /= B(J)) then
              call abort ()
              call abort ()
              endif
              endif
          end do
          end do
        end do
        end do
        Return
        Return
        end
        end
        program main
        program main
        Call foo (16, 8)
        Call foo (16, 8)
        stop
        stop
        end
        end
! { dg-final { scan-tree-dump-times "vectorized 2 loops" 1 "vect"  } }
! { 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 "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 "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 } } } }
! { 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
! We also expect to vectorize one loop for lp64 targets that support
! misaligned access:
! misaligned access:
!   scan-tree-dump-times "vectorized 1 loops" 1 "vect" { target { lp64 && !vect_no_align } }
!   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 "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 } }
!   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
! but we currently can't combine logical operators. (Could define
! a keyword for "not_vect_no_align" if desired).
! a keyword for "not_vect_no_align" if desired).
! { dg-final { cleanup-tree-dump "vect" } }
! { 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.