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

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-dev/] [fsf-gcc-snapshot-1-mar-12/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [lastprivate2.f90] - Diff between revs 735 and 783

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 735 Rev 783
program lastprivate
program lastprivate
  integer :: i, k
  integer :: i, k
  common /c/ i, k
  common /c/ i, k
  !$omp parallel num_threads (4)
  !$omp parallel num_threads (4)
  call test1
  call test1
  !$omp end parallel
  !$omp end parallel
  if (i .ne. 21 .or. k .ne. 20) call abort
  if (i .ne. 21 .or. k .ne. 20) call abort
  !$omp parallel num_threads (4)
  !$omp parallel num_threads (4)
  call test2
  call test2
  !$omp end parallel
  !$omp end parallel
  if (i .ne. 64 .or. k .ne. 61) call abort
  if (i .ne. 64 .or. k .ne. 61) call abort
  !$omp parallel num_threads (4)
  !$omp parallel num_threads (4)
  call test3
  call test3
  !$omp end parallel
  !$omp end parallel
  if (i .ne. 14 .or. k .ne. 11) call abort
  if (i .ne. 14 .or. k .ne. 11) call abort
  call test4
  call test4
  call test5
  call test5
  call test6
  call test6
  call test7
  call test7
  call test8
  call test8
  call test9
  call test9
  call test10
  call test10
  call test11
  call test11
  call test12
  call test12
contains
contains
  subroutine test1
  subroutine test1
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp do lastprivate (i, k)
    !$omp do lastprivate (i, k)
    do i = 1, 20
    do i = 1, 20
      k = i
      k = i
    end do
    end do
  end subroutine test1
  end subroutine test1
  subroutine test2
  subroutine test2
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp do lastprivate (i, k)
    !$omp do lastprivate (i, k)
    do i = 7, 61, 3
    do i = 7, 61, 3
      k = i
      k = i
    end do
    end do
  end subroutine test2
  end subroutine test2
  function ret3 ()
  function ret3 ()
    integer :: ret3
    integer :: ret3
    ret3 = 3
    ret3 = 3
  end function ret3
  end function ret3
  subroutine test3
  subroutine test3
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp do lastprivate (i, k)
    !$omp do lastprivate (i, k)
    do i = -10, 11, ret3 ()
    do i = -10, 11, ret3 ()
      k = i
      k = i
    end do
    end do
  end subroutine test3
  end subroutine test3
  subroutine test4
  subroutine test4
    integer :: j, l
    integer :: j, l
    !$omp parallel do lastprivate (j, l) num_threads (4)
    !$omp parallel do lastprivate (j, l) num_threads (4)
    do j = 1, 20
    do j = 1, 20
      l = j
      l = j
    end do
    end do
    if (j .ne. 21 .or. l .ne. 20) call abort
    if (j .ne. 21 .or. l .ne. 20) call abort
  end subroutine test4
  end subroutine test4
  subroutine test5
  subroutine test5
    integer :: j, l
    integer :: j, l
    l = 77
    l = 77
    !$omp parallel do lastprivate (j, l) num_threads (4) firstprivate (l)
    !$omp parallel do lastprivate (j, l) num_threads (4) firstprivate (l)
    do j = 7, 61, 3
    do j = 7, 61, 3
      l = j
      l = j
    end do
    end do
    if (j .ne. 64 .or. l .ne. 61) call abort
    if (j .ne. 64 .or. l .ne. 61) call abort
  end subroutine test5
  end subroutine test5
  subroutine test6
  subroutine test6
    integer :: j, l
    integer :: j, l
    !$omp parallel do lastprivate (j, l) num_threads (4)
    !$omp parallel do lastprivate (j, l) num_threads (4)
    do j = -10, 11, ret3 ()
    do j = -10, 11, ret3 ()
      l = j
      l = j
    end do
    end do
    if (j .ne. 14 .or. l .ne. 11) call abort
    if (j .ne. 14 .or. l .ne. 11) call abort
  end subroutine test6
  end subroutine test6
  subroutine test7
  subroutine test7
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp parallel do lastprivate (i, k) num_threads (4)
    !$omp parallel do lastprivate (i, k) num_threads (4)
    do i = 1, 20
    do i = 1, 20
      k = i
      k = i
    end do
    end do
    if (i .ne. 21 .or. k .ne. 20) call abort
    if (i .ne. 21 .or. k .ne. 20) call abort
  end subroutine test7
  end subroutine test7
  subroutine test8
  subroutine test8
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp parallel do lastprivate (i, k) num_threads (4)
    !$omp parallel do lastprivate (i, k) num_threads (4)
    do i = 7, 61, 3
    do i = 7, 61, 3
      k = i
      k = i
    end do
    end do
    if (i .ne. 64 .or. k .ne. 61) call abort
    if (i .ne. 64 .or. k .ne. 61) call abort
  end subroutine test8
  end subroutine test8
  subroutine test9
  subroutine test9
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    k = 77
    k = 77
    !$omp parallel do lastprivate (i, k) num_threads (4) firstprivate (k)
    !$omp parallel do lastprivate (i, k) num_threads (4) firstprivate (k)
    do i = -10, 11, ret3 ()
    do i = -10, 11, ret3 ()
      k = i
      k = i
    end do
    end do
    if (i .ne. 14 .or. k .ne. 11) call abort
    if (i .ne. 14 .or. k .ne. 11) call abort
  end subroutine test9
  end subroutine test9
  subroutine test10
  subroutine test10
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp parallel num_threads (4)
    !$omp parallel num_threads (4)
    !$omp do lastprivate (i, k)
    !$omp do lastprivate (i, k)
    do i = 1, 20
    do i = 1, 20
      k = i
      k = i
    end do
    end do
    !$omp end parallel
    !$omp end parallel
    if (i .ne. 21 .or. k .ne. 20) call abort
    if (i .ne. 21 .or. k .ne. 20) call abort
  end subroutine test10
  end subroutine test10
  subroutine test11
  subroutine test11
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    !$omp parallel num_threads (4)
    !$omp parallel num_threads (4)
    !$omp do lastprivate (i, k)
    !$omp do lastprivate (i, k)
    do i = 7, 61, 3
    do i = 7, 61, 3
      k = i
      k = i
    end do
    end do
    !$omp end parallel
    !$omp end parallel
    if (i .ne. 64 .or. k .ne. 61) call abort
    if (i .ne. 64 .or. k .ne. 61) call abort
  end subroutine test11
  end subroutine test11
  subroutine test12
  subroutine test12
    integer :: i, k
    integer :: i, k
    common /c/ i, k
    common /c/ i, k
    k = 77
    k = 77
    !$omp parallel num_threads (4)
    !$omp parallel num_threads (4)
    !$omp do lastprivate (i, k) firstprivate (k)
    !$omp do lastprivate (i, k) firstprivate (k)
    do i = -10, 11, ret3 ()
    do i = -10, 11, ret3 ()
      k = i
      k = i
    end do
    end do
    !$omp end parallel
    !$omp end parallel
    if (i .ne. 14 .or. k .ne. 11) call abort
    if (i .ne. 14 .or. k .ne. 11) call abort
  end subroutine test12
  end subroutine test12
end program lastprivate
end program lastprivate
 
 

powered by: WebSVN 2.1.0

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