view libgomp/testsuite/libgomp.fortran/stack.f90 @ 63:b7f97abdc517 gcc-4.6-20100522

update gcc from gcc-4.5.0 to gcc-4.6
author ryoma <e075725@ie.u-ryukyu.ac.jp>
date Mon, 24 May 2010 12:47:05 +0900
parents a06113de4d67
children 84e7813d76e9
line wrap: on
line source

! { dg-do run }
program stack
  implicit none
  integer id
  integer ilocs(2)
  integer omp_get_thread_num, foo
  call omp_set_num_threads (2)
!$omp parallel private (id)
  id = omp_get_thread_num() + 1
  ilocs(id) = foo()
!$omp end parallel
  ! Check that the two threads are not sharing a location for
  ! the array x in foo()
  if (ilocs(1) .eq. ilocs(2)) call abort
end program stack

integer function foo ()
  implicit none
  real x(100,100)
  foo = loc(x)
end function foo