xref: /llvm-project/flang/test/Semantics/ucobound.f90 (revision 94963919011d77c2f3f9d867cb73067a4f50e87c)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Check for semantic errors in ucobound() function references
3
4program ucobound_tests
5  use iso_c_binding, only : c_int32_t, c_int64_t
6  implicit none
7
8  integer n, i, array(1), non_coarray(1), scalar_coarray[*], array_coarray(1)[*], non_constant, scalar
9  integer, parameter :: const_out_of_range_dim = 5, const_in_range_dim = 1
10  real, allocatable :: coarray_corank3[:,:,:]
11  logical non_integer, logical_coarray[3,*]
12  logical, parameter :: const_non_integer = .true.
13  integer, allocatable :: ucobounds(:)
14  real bounded[2:3,4:5,*]
15
16  integer(kind=merge(kind(1),-1,ucobound(bounded,1)==3.and.ucobound(bounded,2)==5)) test_ucobound
17
18  !___ standard-conforming statement with no optional arguments present ___
19  ucobounds = ucobound(scalar_coarray)
20  ucobounds = ucobound(array_coarray)
21  ucobounds = ucobound(coarray_corank3)
22  ucobounds = ucobound(logical_coarray)
23  ucobounds = ucobound(coarray=scalar_coarray)
24
25  !___ standard-conforming statements with optional dim argument present ___
26  n = ucobound(scalar_coarray, 1)
27  n = ucobound(coarray_corank3, 1)
28  n = ucobound(coarray_corank3, 3)
29  n = ucobound(scalar_coarray, const_in_range_dim)
30  n = ucobound(logical_coarray, const_in_range_dim)
31  n = ucobound(scalar_coarray, dim=1)
32  n = ucobound(coarray=scalar_coarray, dim=1)
33  n = ucobound( dim=1, coarray=scalar_coarray)
34
35  !___ standard-conforming statements with optional kind argument present ___
36  n = ucobound(scalar_coarray, 1, c_int32_t)
37
38  n = ucobound(scalar_coarray, 1, kind=c_int32_t)
39
40  n = ucobound(scalar_coarray, dim=1, kind=c_int32_t)
41  n = ucobound(scalar_coarray, kind=c_int32_t, dim=1)
42
43  ucobounds = ucobound(scalar_coarray, kind=c_int32_t)
44
45  ucobounds = ucobound(coarray=scalar_coarray, kind=c_int32_t)
46  ucobounds = ucobound(kind=c_int32_t, coarray=scalar_coarray)
47
48  n = ucobound(coarray=scalar_coarray, dim=1, kind=c_int32_t)
49  n = ucobound(dim=1, coarray=scalar_coarray, kind=c_int32_t)
50  n = ucobound(kind=c_int32_t, coarray=scalar_coarray, dim=1)
51  n = ucobound(dim=1, kind=c_int32_t, coarray=scalar_coarray)
52  n = ucobound(kind=c_int32_t, dim=1, coarray=scalar_coarray)
53
54  !___ non-conforming statements ___
55
56  !ERROR: DIM=0 dimension must be positive
57  n = ucobound(scalar_coarray, dim=0)
58
59  !ERROR: DIM=0 dimension must be positive
60  n = ucobound(coarray_corank3, dim=0)
61
62  !ERROR: DIM=-1 dimension must be positive
63  n = ucobound(scalar_coarray, dim=-1)
64
65  !ERROR: DIM=2 dimension is out of range for corank-1 coarray
66  n = ucobound(array_coarray, dim=2)
67
68  !ERROR: DIM=2 dimension is out of range for corank-1 coarray
69  n = ucobound(array_coarray, 2)
70
71  !ERROR: DIM=4 dimension is out of range for corank-3 coarray
72  n = ucobound(coarray_corank3, dim=4)
73
74  !ERROR: DIM=4 dimension is out of range for corank-3 coarray
75  n = ucobound(dim=4, coarray=coarray_corank3)
76
77  !ERROR: DIM=5 dimension is out of range for corank-3 coarray
78  n = ucobound(coarray_corank3, const_out_of_range_dim)
79
80  !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches scalar INTEGER(4) and rank 1 array of INTEGER(4)
81  scalar = ucobound(scalar_coarray)
82
83  !ERROR: missing mandatory 'coarray=' argument
84  n = ucobound(dim=i)
85
86  !ERROR: Actual argument for 'dim=' has bad type 'LOGICAL(4)'
87  n = ucobound(scalar_coarray, non_integer)
88
89  !ERROR: Actual argument for 'dim=' has bad type 'LOGICAL(4)'
90  n = ucobound(scalar_coarray, dim=non_integer)
91
92  !ERROR: Actual argument for 'kind=' has bad type 'LOGICAL(4)'
93  ucobounds = ucobound(scalar_coarray, kind=const_non_integer)
94
95  !ERROR: Actual argument for 'kind=' has bad type 'LOGICAL(4)'
96  n = ucobound(scalar_coarray, 1, const_non_integer)
97
98  !ERROR: 'kind=' argument must be a constant scalar integer whose value is a supported kind for the intrinsic result type
99  ucobounds = ucobound(scalar_coarray, kind=non_constant)
100
101  !ERROR: 'kind=' argument must be a constant scalar integer whose value is a supported kind for the intrinsic result type
102  n = ucobound(scalar_coarray, dim=1, kind=non_constant)
103
104  !ERROR: 'kind=' argument must be a constant scalar integer whose value is a supported kind for the intrinsic result type
105  n = ucobound(scalar_coarray, 1, non_constant)
106
107  !ERROR: missing mandatory 'coarray=' argument
108  n = ucobound(dim=i, kind=c_int32_t)
109
110  !ERROR: actual argument #2 without a keyword may not follow an actual argument with a keyword
111  n = ucobound(coarray=scalar_coarray, i)
112
113  n = ucobound(coarray=scalar_coarray, dim=i)
114
115  !ERROR: missing mandatory 'coarray=' argument
116  ucobounds = ucobound()
117
118  !ERROR: 'coarray=' argument must have corank > 0 for intrinsic 'ucobound'
119  ucobounds = ucobound(3.4)
120
121  !ERROR: keyword argument to intrinsic 'ucobound' was supplied positionally by an earlier actual argument
122  n = ucobound(scalar_coarray, 1, coarray=scalar_coarray)
123
124  !ERROR: too many actual arguments for intrinsic 'ucobound'
125  n = ucobound(scalar_coarray, i, c_int32_t, 0)
126
127  !ERROR: 'coarray=' argument must have corank > 0 for intrinsic 'ucobound'
128  ucobounds = ucobound(coarray=non_coarray)
129
130  !ERROR: 'coarray=' argument must have corank > 0 for intrinsic 'ucobound'
131  n = ucobound(coarray=non_coarray, dim=1)
132
133  !ERROR: 'dim=' argument has unacceptable rank 1
134  n = ucobound(scalar_coarray, array )
135
136  !ERROR: unknown keyword argument to intrinsic 'ucobound'
137  ucobounds = ucobound(c=scalar_coarray)
138
139  !ERROR: unknown keyword argument to intrinsic 'ucobound'
140  n = ucobound(scalar_coarray, dims=i)
141
142  !ERROR: unknown keyword argument to intrinsic 'ucobound'
143  n = ucobound(scalar_coarray, i, kinds=c_int32_t)
144
145  !ERROR: repeated keyword argument to intrinsic 'ucobound'
146  n = ucobound(scalar_coarray, dim=1, dim=2)
147
148  !ERROR: repeated keyword argument to intrinsic 'ucobound'
149  ucobounds = ucobound(coarray=scalar_coarray, coarray=array_coarray)
150
151  !ERROR: repeated keyword argument to intrinsic 'ucobound'
152  ucobounds = ucobound(scalar_coarray, kind=c_int32_t, kind=c_int64_t)
153
154end program ucobound_tests
155