1! RUN: %S/test_errors.sh %s %t %f18
2! Tests for C1128:
3! A variable-name that appears in a LOCAL or LOCAL_INIT locality-spec shall not
4! have the ALLOCATABLE; INTENT (IN); or OPTIONAL attribute; shall not be of
5! finalizable type; shall not be a nonpointer polymorphic dummy argument; and
6! shall not be a coarray or an assumed-size array.
7
8subroutine s1()
9! Cannot have ALLOCATABLE variable in a locality spec
10  integer, allocatable :: k
11!ERROR: ALLOCATABLE variable 'k' not allowed in a locality-spec
12  do concurrent(i=1:5) local(k)
13  end do
14end subroutine s1
15
16subroutine s2(arg)
17! Cannot have a dummy OPTIONAL in a locality spec
18  integer, optional :: arg
19!ERROR: OPTIONAL argument 'arg' not allowed in a locality-spec
20  do concurrent(i=1:5) local(arg)
21  end do
22end subroutine s2
23
24subroutine s3(arg)
25! This is OK
26  real :: arg
27  do concurrent(i=1:5) local(arg)
28  end do
29end subroutine s3
30
31subroutine s4(arg)
32! Cannot have a dummy INTENT(IN) in a locality spec
33  real, intent(in) :: arg
34!ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
35  do concurrent(i=1:5) local(arg)
36  end do
37end subroutine s4
38
39module m
40! Cannot have a variable of a finalizable type in a locality spec
41  type t1
42    integer :: i
43  contains
44    final :: f
45  end type t1
46 contains
47  subroutine s5()
48    type(t1) :: var
49    !ERROR: Finalizable variable 'var' not allowed in a locality-spec
50    do concurrent(i=1:5) local(var)
51    end do
52  end subroutine s5
53  subroutine f(x)
54    type(t1) :: x
55  end subroutine f
56end module m
57
58subroutine s6
59! Cannot have a nonpointer polymorphic dummy argument in a locality spec
60  type :: t
61    integer :: field
62  end type t
63contains
64  subroutine s(x, y)
65    class(t), pointer :: x
66    class(t) :: y
67
68! This is allowed
69    do concurrent(i=1:5) local(x)
70    end do
71
72! This is not allowed
73!ERROR: Nonpointer polymorphic argument 'y' not allowed in a locality-spec
74    do concurrent(i=1:5) local(y)
75    end do
76  end subroutine s
77end subroutine s6
78
79subroutine s7()
80! Cannot have a coarray
81  integer, codimension[*] :: coarray_var
82!ERROR: Coarray 'coarray_var' not allowed in a locality-spec
83  do concurrent(i=1:5) local(coarray_var)
84  end do
85end subroutine s7
86
87subroutine s8(arg)
88! Cannot have an assumed size array
89  integer, dimension(*) :: arg
90!ERROR: Assumed size array 'arg' not allowed in a locality-spec
91  do concurrent(i=1:5) local(arg)
92  end do
93end subroutine s8
94