OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc1/] [libgomp/] [testsuite/] [libgomp.fortran/] [threadprivate3.f90] - Diff between revs 273 and 338

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

Rev 273 Rev 338
! { dg-do run }
! { dg-do run }
! { dg-require-effective-target tls_runtime }
! { dg-require-effective-target tls_runtime }
module threadprivate3
module threadprivate3
  integer, dimension(:,:), pointer :: foo => NULL()
  integer, dimension(:,:), pointer :: foo => NULL()
!$omp threadprivate (foo)
!$omp threadprivate (foo)
end module threadprivate3
end module threadprivate3
  use omp_lib
  use omp_lib
  use threadprivate3
  use threadprivate3
  integer, dimension(:), pointer :: bar1
  integer, dimension(:), pointer :: bar1
  integer, dimension(2), target :: bar2, var
  integer, dimension(2), target :: bar2, var
  common /thrc/ bar1, bar2
  common /thrc/ bar1, bar2
!$omp threadprivate (/thrc/)
!$omp threadprivate (/thrc/)
  integer, dimension(:), pointer, save :: bar3 => NULL()
  integer, dimension(:), pointer, save :: bar3 => NULL()
!$omp threadprivate (bar3)
!$omp threadprivate (bar3)
  logical :: l
  logical :: l
  type tt
  type tt
    integer :: a
    integer :: a
    integer :: b = 32
    integer :: b = 32
  end type tt
  end type tt
  type (tt), save :: baz
  type (tt), save :: baz
!$omp threadprivate (baz)
!$omp threadprivate (baz)
  l = .false.
  l = .false.
  call omp_set_dynamic (.false.)
  call omp_set_dynamic (.false.)
  call omp_set_num_threads (4)
  call omp_set_num_threads (4)
  var = 6
  var = 6
!$omp parallel num_threads (4) reduction (.or.:l)
!$omp parallel num_threads (4) reduction (.or.:l)
  bar2 = omp_get_thread_num ()
  bar2 = omp_get_thread_num ()
  l = associated (bar3)
  l = associated (bar3)
  bar1 => bar2
  bar1 => bar2
  l = l.or..not.associated (bar1)
  l = l.or..not.associated (bar1)
  l = l.or..not.associated (bar1, bar2)
  l = l.or..not.associated (bar1, bar2)
  l = l.or.any (bar1.ne.omp_get_thread_num ())
  l = l.or.any (bar1.ne.omp_get_thread_num ())
  nullify (bar1)
  nullify (bar1)
  l = l.or.associated (bar1)
  l = l.or.associated (bar1)
  allocate (bar3 (4))
  allocate (bar3 (4))
  l = l.or..not.associated (bar3)
  l = l.or..not.associated (bar3)
  bar3 = omp_get_thread_num () - 2
  bar3 = omp_get_thread_num () - 2
  if (omp_get_thread_num () .ne. 0) then
  if (omp_get_thread_num () .ne. 0) then
    deallocate (bar3)
    deallocate (bar3)
    if (associated (bar3)) call abort
    if (associated (bar3)) call abort
  else
  else
    bar1 => var
    bar1 => var
  end if
  end if
  bar2 = omp_get_thread_num () * 6 + 130
  bar2 = omp_get_thread_num () * 6 + 130
  l = l.or.(baz%b.ne.32)
  l = l.or.(baz%b.ne.32)
  baz%a = omp_get_thread_num () * 2
  baz%a = omp_get_thread_num () * 2
  baz%b = omp_get_thread_num () * 2 + 1
  baz%b = omp_get_thread_num () * 2 + 1
!$omp end parallel
!$omp end parallel
  if (l) call abort
  if (l) call abort
  if (.not.associated (bar1)) call abort
  if (.not.associated (bar1)) call abort
  if (any (bar1.ne.6)) call abort
  if (any (bar1.ne.6)) call abort
  if (.not.associated (bar3)) call abort
  if (.not.associated (bar3)) call abort
  if (any (bar3 .ne. -2)) call abort
  if (any (bar3 .ne. -2)) call abort
  deallocate (bar3)
  deallocate (bar3)
  if (associated (bar3)) call abort
  if (associated (bar3)) call abort
  allocate (bar3 (10))
  allocate (bar3 (10))
  bar3 = 17
  bar3 = 17
!$omp parallel copyin (bar1, bar2, bar3, baz) num_threads (4) &
!$omp parallel copyin (bar1, bar2, bar3, baz) num_threads (4) &
!$omp& reduction (.or.:l)
!$omp& reduction (.or.:l)
  l = l.or..not.associated (bar1)
  l = l.or..not.associated (bar1)
  l = l.or.any (bar1.ne.6)
  l = l.or.any (bar1.ne.6)
  l = l.or.any (bar2.ne.130)
  l = l.or.any (bar2.ne.130)
  l = l.or..not.associated (bar3)
  l = l.or..not.associated (bar3)
  l = l.or.size (bar3).ne.10
  l = l.or.size (bar3).ne.10
  l = l.or.any (bar3.ne.17)
  l = l.or.any (bar3.ne.17)
  allocate (bar1 (4))
  allocate (bar1 (4))
  bar1 = omp_get_thread_num ()
  bar1 = omp_get_thread_num ()
  bar2 = omp_get_thread_num () + 8
  bar2 = omp_get_thread_num () + 8
  l = l.or.(baz%a.ne.0)
  l = l.or.(baz%a.ne.0)
  l = l.or.(baz%b.ne.1)
  l = l.or.(baz%b.ne.1)
  baz%a = omp_get_thread_num () * 3 + 4
  baz%a = omp_get_thread_num () * 3 + 4
  baz%b = omp_get_thread_num () * 3 + 5
  baz%b = omp_get_thread_num () * 3 + 5
!$omp barrier
!$omp barrier
  if (omp_get_thread_num () .eq. 0) then
  if (omp_get_thread_num () .eq. 0) then
    deallocate (bar3)
    deallocate (bar3)
  end if
  end if
  bar3 => bar2
  bar3 => bar2
!$omp barrier
!$omp barrier
  l = l.or..not.associated (bar1)
  l = l.or..not.associated (bar1)
  l = l.or..not.associated (bar3)
  l = l.or..not.associated (bar3)
  l = l.or.any (bar1.ne.omp_get_thread_num ())
  l = l.or.any (bar1.ne.omp_get_thread_num ())
  l = l.or.size (bar1).ne.4
  l = l.or.size (bar1).ne.4
  l = l.or.any (bar2.ne.omp_get_thread_num () + 8)
  l = l.or.any (bar2.ne.omp_get_thread_num () + 8)
  l = l.or.any (bar3.ne.omp_get_thread_num () + 8)
  l = l.or.any (bar3.ne.omp_get_thread_num () + 8)
  l = l.or.size (bar3).ne.2
  l = l.or.size (bar3).ne.2
  l = l.or.(baz%a .ne. omp_get_thread_num () * 3 + 4)
  l = l.or.(baz%a .ne. omp_get_thread_num () * 3 + 4)
  l = l.or.(baz%b .ne. omp_get_thread_num () * 3 + 5)
  l = l.or.(baz%b .ne. omp_get_thread_num () * 3 + 5)
!$omp end parallel
!$omp end parallel
  if (l) call abort
  if (l) call abort
end
end
! { dg-final { cleanup-modules "threadprivate3" } }
! { dg-final { cleanup-modules "threadprivate3" } }
 
 

powered by: WebSVN 2.1.0

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