URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [stack.f90] - Rev 735
Compare with Previous | Blame | View Log
! { 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