URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [allocatable7.f90] - Rev 857
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do run }
integer, allocatable :: a(:)
logical :: l
l = .false.
!$omp parallel firstprivate (a) reduction (.or.:l)
l = allocated (a)
allocate (a(10))
l = l .or. .not. allocated (a)
a = 10
if (any (a .ne. 10)) l = .true.
deallocate (a)
l = l .or. allocated (a)
!$omp end parallel
if (l) call abort
end
Go to most recent revision | Compare with Previous | Blame | View Log