xref: /llvm-project/flang/test/Semantics/critical02.f90 (revision 2625510ef8094457413661ef0ce2651844f584d2)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2!C1118
3
4subroutine test1
5  critical
6    !ERROR: RETURN statement is not allowed in a CRITICAL construct
7    return
8  end critical
9end subroutine test1
10
11subroutine test2()
12  implicit none
13  critical
14    !ERROR: An image control statement is not allowed in a CRITICAL construct
15    SYNC ALL
16  end critical
17end subroutine test2
18
19subroutine test3()
20  use iso_fortran_env, only: team_type
21  implicit none
22  type(team_type) :: j
23  critical
24    !ERROR: An image control statement is not allowed in a CRITICAL construct
25    sync team (j)
26  end critical
27end subroutine test3
28
29subroutine test4()
30  integer, allocatable, codimension[:] :: ca
31
32  critical
33    !ERROR: An image control statement is not allowed in a CRITICAL construct
34    allocate(ca[*])
35  end critical
36
37  critical
38    !ERROR: An image control statement is not allowed in a CRITICAL construct
39    deallocate(ca)
40  end critical
41end subroutine test4
42
43subroutine test5()
44  use iso_fortran_env, only: team_type
45  implicit none
46  type(team_type) :: j
47  critical
48    change team (j)
49    !ERROR: An image control statement is not allowed in a CRITICAL construct
50    end team
51  end critical
52end subroutine test5
53
54subroutine test6
55  critical
56    critical
57    !ERROR: An image control statement is not allowed in a CRITICAL construct
58    end critical
59  end critical
60end subroutine test6
61
62subroutine test7()
63  use iso_fortran_env
64  type(event_type) :: x[*], y[*]
65  critical
66    !ERROR: An image control statement is not allowed in a CRITICAL construct
67    event post (x)
68    !ERROR: An image control statement is not allowed in a CRITICAL construct
69    event wait (y)
70  end critical
71end subroutine test7
72
73subroutine test8()
74  use iso_fortran_env
75  type(team_type) :: t
76
77  critical
78    !ERROR: An image control statement is not allowed in a CRITICAL construct
79    form team(1, t)
80  end critical
81end subroutine test8
82
83subroutine test9()
84  use iso_fortran_env
85  type(lock_type), save :: l[*]
86
87  critical
88    !ERROR: An image control statement is not allowed in a CRITICAL construct
89    lock(l)
90    !ERROR: An image control statement is not allowed in a CRITICAL construct
91    unlock(l)
92  end critical
93end subroutine test9
94
95subroutine test10()
96  use iso_fortran_env
97  integer, allocatable, codimension[:] :: ca
98  allocate(ca[*])
99
100  critical
101    block
102      integer, allocatable, codimension[:] :: cb
103      cb = ca
104    !TODO: Deallocation of this coarray is not currently caught
105    end block
106  end critical
107end subroutine test10
108
109subroutine test11()
110  integer, allocatable, codimension[:] :: ca, cb
111  critical
112    !ERROR: An image control statement is not allowed in a CRITICAL construct
113    call move_alloc(cb, ca)
114  end critical
115end subroutine test11
116
117subroutine test12()
118  critical
119    !ERROR: An image control statement is not allowed in a CRITICAL construct
120    stop
121  end critical
122end subroutine test12
123