URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [libgomp/] [testsuite/] [libgomp.fortran/] [omp_parse4.f90] - Rev 735
Compare with Previous | Blame | View Log
! { dg-do run }!$ use omp_libcall test_worksharecontainssubroutine test_workshareinteger :: i, j, k, l, mdouble precision, dimension (64) :: d, einteger, dimension (10) :: f, ginteger, dimension (16, 16) :: a, b, cinteger, dimension (16) :: nd(:) = 1e = 7f = 10l = 256m = 512g(1:3) = -1g(4:6) = 0g(7:8) = 5g(9:10) = 10forall (i = 1:16, j = 1:16) a (i, j) = i * 16 + jforall (j = 1:16) n (j) = j!$omp parallel num_threads (4) private (j, k)!$omp barrier!$omp worksharei = 6e(:) = d(:)where (g .lt. 0)f = 100elsewhere (g .eq. 0)f = 200 + felsewherewhere (g .gt. 6) f = f + sum (g)f = 300 + fend wherewhere (f .gt. 210) g = 0!$omp end workshare nowait!$omp workshareforall (j = 1:16, k = 1:16) b (k, j) = a (j, k)forall (k = 1:16) c (k, 1:16) = a (1:16, k)forall (j = 2:16, n (17 - j) / 4 * 4 .ne. n (17 - j))n (j) = n (j - 1) * n (j)end forall!$omp endworkshare!$omp workshare!$omp atomici = i + 8 + 6!$omp critical!$omp critical (critical_foox)l = 128!$omp end critical (critical_foox)!$omp endcritical!$omp parallel num_threads (2)!$ if (omp_get_thread_num () .eq. 0) m = omp_get_num_threads ()!$omp atomicl = 1 + l!$omp end parallel!$omp end workshare!$omp end parallelif (any (f .ne. (/100, 100, 100, 210, 210, 210, 310, 310, 337, 337/))) && call abortif (any (g .ne. (/-1, -1, -1, 0, 0, 0, 0, 0, 0, 0/))) call abortif (i .ne. 20) call abort!$ if (l .ne. 128 + m) call abortif (any (d .ne. 1 .or. e .ne. 1)) call abortif (any (b .ne. transpose (a))) call abortif (any (c .ne. b)) call abortif (any (n .ne. (/1, 2, 6, 12, 5, 30, 42, 56, 9, 90, && 110, 132, 13, 182, 210, 240/))) call abortend subroutine test_workshareend
