xref: /llvm-project/flang/test/Semantics/OpenMP/nested-simd.f90 (revision e67e09a77ea1e4802c0f6bc0409c9f5e9d1fae9a)
13323a4bdSKiran Chandramohan! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp
23323a4bdSKiran Chandramohan! OpenMP Version 4.5
33323a4bdSKiran Chandramohan! Various checks with the nesting of SIMD construct
43323a4bdSKiran Chandramohan
53323a4bdSKiran ChandramohanSUBROUTINE NESTED_GOOD(N)
63323a4bdSKiran Chandramohan  INTEGER N, I, J, K, A(10), B(10)
73323a4bdSKiran Chandramohan  !$OMP SIMD
83323a4bdSKiran Chandramohan  DO I = 1,N
93323a4bdSKiran Chandramohan    !$OMP ATOMIC
103323a4bdSKiran Chandramohan    K =  K + 1
113323a4bdSKiran Chandramohan    IF (I <= 10) THEN
123323a4bdSKiran Chandramohan      !$OMP ORDERED SIMD
133323a4bdSKiran Chandramohan      DO J = 1,N
143323a4bdSKiran Chandramohan        A(J) = J
153323a4bdSKiran Chandramohan      END DO
163323a4bdSKiran Chandramohan      !$OMP END ORDERED
173323a4bdSKiran Chandramohan    ENDIF
183323a4bdSKiran Chandramohan  END DO
193323a4bdSKiran Chandramohan  !$OMP END SIMD
203323a4bdSKiran Chandramohan
213323a4bdSKiran Chandramohan  !$OMP SIMD
223323a4bdSKiran Chandramohan  DO I = 1,N
233323a4bdSKiran Chandramohan    IF (I <= 10) THEN
243323a4bdSKiran Chandramohan      !$OMP SIMD
253323a4bdSKiran Chandramohan      DO J = 1,N
263323a4bdSKiran Chandramohan        A(J) = J
273323a4bdSKiran Chandramohan      END DO
283323a4bdSKiran Chandramohan      !$OMP END SIMD
293323a4bdSKiran Chandramohan    ENDIF
303323a4bdSKiran Chandramohan  END DO
313323a4bdSKiran Chandramohan  !$OMP END SIMD
323323a4bdSKiran ChandramohanEND SUBROUTINE NESTED_GOOD
333323a4bdSKiran Chandramohan
343323a4bdSKiran ChandramohanSUBROUTINE NESTED_BAD(N)
353323a4bdSKiran Chandramohan  INTEGER N, I, J, K, A(10), B(10)
363323a4bdSKiran Chandramohan
373323a4bdSKiran Chandramohan  !$OMP SIMD
383323a4bdSKiran Chandramohan  DO I = 1,N
393323a4bdSKiran Chandramohan    IF (I <= 10) THEN
403323a4bdSKiran Chandramohan      !$OMP ORDERED SIMD
413323a4bdSKiran Chandramohan      DO J = 1,N
423323a4bdSKiran Chandramohan        print *, "Hi"
43*e67e09a7SAnchu Rajendran S        !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
443323a4bdSKiran Chandramohan        !ERROR: TEAMS region can only be strictly nested within the implicit parallel region or TARGET region
453323a4bdSKiran Chandramohan        !$omp teams
463323a4bdSKiran Chandramohan         DO K = 1,N
473323a4bdSKiran Chandramohan        print *, 'Hello'
483323a4bdSKiran Chandramohan        END DO
493323a4bdSKiran Chandramohan        !$omp end teams
503323a4bdSKiran Chandramohan      END DO
513323a4bdSKiran Chandramohan      !$OMP END ORDERED
523323a4bdSKiran Chandramohan    ENDIF
533323a4bdSKiran Chandramohan  END DO
543323a4bdSKiran Chandramohan  !$OMP END SIMD
553323a4bdSKiran Chandramohan
563323a4bdSKiran Chandramohan  !$OMP SIMD
573323a4bdSKiran Chandramohan  DO I = 1,N
583323a4bdSKiran Chandramohan    !$OMP ATOMIC
593323a4bdSKiran Chandramohan    K =  K + 1
603323a4bdSKiran Chandramohan    IF (I <= 10) THEN
61*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
623323a4bdSKiran Chandramohan      !$omp task
633323a4bdSKiran Chandramohan      do J = 1, N
643323a4bdSKiran Chandramohan        K = 2
653323a4bdSKiran Chandramohan      end do
663323a4bdSKiran Chandramohan      !$omp end task
67*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
683323a4bdSKiran Chandramohan      !$omp target
693323a4bdSKiran Chandramohan      do J = 1, N
703323a4bdSKiran Chandramohan        K = 2
713323a4bdSKiran Chandramohan      end do
723323a4bdSKiran Chandramohan      !$omp end target
73*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
743323a4bdSKiran Chandramohan      !$OMP DO
753323a4bdSKiran Chandramohan      DO J = 1,N
763323a4bdSKiran Chandramohan        A(J) = J
773323a4bdSKiran Chandramohan      END DO
783323a4bdSKiran Chandramohan      !$OMP END DO
79*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
803323a4bdSKiran Chandramohan      !$OMP PARALLEL DO
813323a4bdSKiran Chandramohan      DO J = 1,N
823323a4bdSKiran Chandramohan        A(J) = J
833323a4bdSKiran Chandramohan      END DO
843323a4bdSKiran Chandramohan      !$OMP END PARALLEL DO
853323a4bdSKiran Chandramohan    ENDIF
863323a4bdSKiran Chandramohan  END DO
873323a4bdSKiran Chandramohan  !$OMP END SIMD
883323a4bdSKiran Chandramohan
893323a4bdSKiran Chandramohan  !$OMP DO SIMD
903323a4bdSKiran Chandramohan  DO I = 1,N
913323a4bdSKiran Chandramohan    !$OMP ATOMIC
923323a4bdSKiran Chandramohan    K =  K + 1
933323a4bdSKiran Chandramohan    IF (I <= 10) THEN
94*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
953323a4bdSKiran Chandramohan      !$omp task
963323a4bdSKiran Chandramohan      do J = 1, N
973323a4bdSKiran Chandramohan        K = 2
983323a4bdSKiran Chandramohan      end do
993323a4bdSKiran Chandramohan      !$omp end task
100*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1013323a4bdSKiran Chandramohan      !$omp target
1023323a4bdSKiran Chandramohan      do J = 1, N
1033323a4bdSKiran Chandramohan        K = 2
1043323a4bdSKiran Chandramohan      end do
1053323a4bdSKiran Chandramohan      !$omp end target
106*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1073323a4bdSKiran Chandramohan      !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
1083323a4bdSKiran Chandramohan      !$OMP DO
1093323a4bdSKiran Chandramohan      DO J = 1,N
1103323a4bdSKiran Chandramohan        A(J) = J
1113323a4bdSKiran Chandramohan      END DO
1123323a4bdSKiran Chandramohan      !$OMP END DO
113*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1143323a4bdSKiran Chandramohan      !$OMP PARALLEL DO
1153323a4bdSKiran Chandramohan      DO J = 1,N
1163323a4bdSKiran Chandramohan        A(J) = J
1173323a4bdSKiran Chandramohan      END DO
1183323a4bdSKiran Chandramohan      !$OMP END PARALLEL DO
1193323a4bdSKiran Chandramohan    ENDIF
1203323a4bdSKiran Chandramohan  END DO
1213323a4bdSKiran Chandramohan  !$OMP END DO SIMD
1223323a4bdSKiran Chandramohan
1233323a4bdSKiran Chandramohan  !$OMP PARALLEL DO SIMD
1243323a4bdSKiran Chandramohan  DO I = 1,N
1253323a4bdSKiran Chandramohan    !$OMP ATOMIC
1263323a4bdSKiran Chandramohan    K =  K + 1
1273323a4bdSKiran Chandramohan    IF (I <= 10) THEN
128*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1293323a4bdSKiran Chandramohan      !$omp task
1303323a4bdSKiran Chandramohan      do J = 1, N
1313323a4bdSKiran Chandramohan        K = 2
1323323a4bdSKiran Chandramohan      end do
1333323a4bdSKiran Chandramohan      !$omp end task
134*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1353323a4bdSKiran Chandramohan      !$omp target
1363323a4bdSKiran Chandramohan      do J = 1, N
1373323a4bdSKiran Chandramohan        K = 2
1383323a4bdSKiran Chandramohan      end do
1393323a4bdSKiran Chandramohan      !$omp end target
140*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1413323a4bdSKiran Chandramohan      !ERROR: A worksharing region may not be closely nested inside a worksharing, explicit task, taskloop, critical, ordered, atomic, or master region
1423323a4bdSKiran Chandramohan      !$OMP DO
1433323a4bdSKiran Chandramohan      DO J = 1,N
1443323a4bdSKiran Chandramohan        A(J) = J
1453323a4bdSKiran Chandramohan      END DO
1463323a4bdSKiran Chandramohan      !$OMP END DO
147*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1483323a4bdSKiran Chandramohan      !$OMP PARALLEL DO
1493323a4bdSKiran Chandramohan      DO J = 1,N
1503323a4bdSKiran Chandramohan        A(J) = J
1513323a4bdSKiran Chandramohan      END DO
1523323a4bdSKiran Chandramohan      !$OMP END PARALLEL DO
1533323a4bdSKiran Chandramohan    ENDIF
1543323a4bdSKiran Chandramohan  END DO
1553323a4bdSKiran Chandramohan  !$OMP END PARALLEL DO SIMD
1563323a4bdSKiran Chandramohan
1573323a4bdSKiran Chandramohan  !$OMP TARGET SIMD
1583323a4bdSKiran Chandramohan  DO I = 1,N
1593323a4bdSKiran Chandramohan    !$OMP ATOMIC
1603323a4bdSKiran Chandramohan    K =  K + 1
1613323a4bdSKiran Chandramohan    IF (I <= 10) THEN
162*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1633323a4bdSKiran Chandramohan      !$omp task
1643323a4bdSKiran Chandramohan      do J = 1, N
1653323a4bdSKiran Chandramohan        K = 2
1663323a4bdSKiran Chandramohan      end do
1673323a4bdSKiran Chandramohan      !$omp end task
168*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1693323a4bdSKiran Chandramohan      !$omp target
1703323a4bdSKiran Chandramohan      do J = 1, N
1713323a4bdSKiran Chandramohan        K = 2
1723323a4bdSKiran Chandramohan      end do
1733323a4bdSKiran Chandramohan      !$omp end target
174*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1753323a4bdSKiran Chandramohan      !$OMP DO
1763323a4bdSKiran Chandramohan      DO J = 1,N
1773323a4bdSKiran Chandramohan        A(J) = J
1783323a4bdSKiran Chandramohan      END DO
1793323a4bdSKiran Chandramohan      !$OMP END DO
180*e67e09a7SAnchu Rajendran S      !ERROR: The only OpenMP constructs that can be encountered during execution of a 'SIMD' region are the `ATOMIC` construct, the `LOOP` construct, the `SIMD` construct, the `SCAN` construct and the `ORDERED` construct with the `SIMD` clause.
1813323a4bdSKiran Chandramohan      !$OMP PARALLEL DO
1823323a4bdSKiran Chandramohan      DO J = 1,N
1833323a4bdSKiran Chandramohan        A(J) = J
1843323a4bdSKiran Chandramohan      END DO
1853323a4bdSKiran Chandramohan      !$OMP END PARALLEL DO
1863323a4bdSKiran Chandramohan    ENDIF
1873323a4bdSKiran Chandramohan  END DO
1883323a4bdSKiran Chandramohan  !$OMP END TARGET SIMD
1893323a4bdSKiran Chandramohan
1903323a4bdSKiran Chandramohan
1913323a4bdSKiran ChandramohanEND SUBROUTINE NESTED_BAD
192