xref: /llvm-project/flang/test/Semantics/resolve124.f90 (revision 3af717d661e9fe8d562181b933a373ca58e41b27)
1*3af717d6Skhaki3! RUN: %python %S/test_errors.py %s %flang_fc1
2*3af717d6Skhaki3! Tests for F'2023 C1132:
3*3af717d6Skhaki3! A variable-name that appears in a REDUCE locality-spec shall be of intrinsic
4*3af717d6Skhaki3! type suitable for the intrinsic operation or function specified by its
5*3af717d6Skhaki3! reduce-operation.
6*3af717d6Skhaki3
7*3af717d6Skhaki3subroutine s1(n)
8*3af717d6Skhaki3! This is OK
9*3af717d6Skhaki3  integer :: i1, i2, i3, i4, i5, i6, i7, n
10*3af717d6Skhaki3  real(8) :: r1, r2, r3, r4
11*3af717d6Skhaki3  complex :: c1, c2
12*3af717d6Skhaki3  logical :: l1, l2, l3(n,n), l4(n)
13*3af717d6Skhaki3  do concurrent(i=1:5) &
14*3af717d6Skhaki3       & reduce(+:i1,r1,c1) reduce(*:i2,r2,c2) reduce(iand:i3) reduce(ieor:i4) &
15*3af717d6Skhaki3       & reduce(ior:i5) reduce(max:i6,r3) reduce(min:i7,r4) reduce(.and.:l1) &
16*3af717d6Skhaki3       & reduce(.or.:l2) reduce(.eqv.:l3) reduce(.neqv.:l4)
17*3af717d6Skhaki3  end do
18*3af717d6Skhaki3end subroutine s1
19*3af717d6Skhaki3
20*3af717d6Skhaki3subroutine s2()
21*3af717d6Skhaki3! Cannot apply logical operations to integer variables
22*3af717d6Skhaki3  integer :: i1, i2, i3, i4
23*3af717d6Skhaki3!ERROR: Reduction variable 'i1' ('INTEGER(4)') does not have a suitable type ('LOGICAL').
24*3af717d6Skhaki3!ERROR: Reduction variable 'i2' ('INTEGER(4)') does not have a suitable type ('LOGICAL').
25*3af717d6Skhaki3!ERROR: Reduction variable 'i3' ('INTEGER(4)') does not have a suitable type ('LOGICAL').
26*3af717d6Skhaki3!ERROR: Reduction variable 'i4' ('INTEGER(4)') does not have a suitable type ('LOGICAL').
27*3af717d6Skhaki3  do concurrent(i=1:5) &
28*3af717d6Skhaki3       & reduce(.and.:i1) reduce(.or.:i2) reduce(.eqv.:i3) reduce(.neqv.:i4)
29*3af717d6Skhaki3  end do
30*3af717d6Skhaki3end subroutine s2
31*3af717d6Skhaki3
32*3af717d6Skhaki3subroutine s3()
33*3af717d6Skhaki3! Cannot apply integer/logical operations to real variables
34*3af717d6Skhaki3  real :: r1, r2, r3, r4
35*3af717d6Skhaki3!ERROR: Reduction variable 'r1' ('REAL(4)') does not have a suitable type ('INTEGER').
36*3af717d6Skhaki3!ERROR: Reduction variable 'r2' ('REAL(4)') does not have a suitable type ('INTEGER').
37*3af717d6Skhaki3!ERROR: Reduction variable 'r3' ('REAL(4)') does not have a suitable type ('INTEGER').
38*3af717d6Skhaki3!ERROR: Reduction variable 'r4' ('REAL(4)') does not have a suitable type ('LOGICAL').
39*3af717d6Skhaki3!ERROR: Reduction variable 'r5' ('REAL(4)') does not have a suitable type ('LOGICAL').
40*3af717d6Skhaki3!ERROR: Reduction variable 'r6' ('REAL(4)') does not have a suitable type ('LOGICAL').
41*3af717d6Skhaki3!ERROR: Reduction variable 'r7' ('REAL(4)') does not have a suitable type ('LOGICAL').
42*3af717d6Skhaki3  do concurrent(i=1:5) &
43*3af717d6Skhaki3       & reduce(iand:r1) reduce(ieor:r2) reduce(ior:r3) reduce(.and.:r4) &
44*3af717d6Skhaki3       & reduce(.or.:r5) reduce(.eqv.:r6) reduce(.neqv.:r7)
45*3af717d6Skhaki3  end do
46*3af717d6Skhaki3end subroutine s3
47*3af717d6Skhaki3
48*3af717d6Skhaki3subroutine s4()
49*3af717d6Skhaki3! Cannot apply integer/logical operations to complex variables
50*3af717d6Skhaki3  complex :: c1, c2, c3, c4, c5, c6, c7, c8, c9
51*3af717d6Skhaki3!ERROR: Reduction variable 'c1' ('COMPLEX(4)') does not have a suitable type ('INTEGER').
52*3af717d6Skhaki3!ERROR: Reduction variable 'c2' ('COMPLEX(4)') does not have a suitable type ('INTEGER').
53*3af717d6Skhaki3!ERROR: Reduction variable 'c3' ('COMPLEX(4)') does not have a suitable type ('INTEGER').
54*3af717d6Skhaki3!ERROR: Reduction variable 'c4' ('COMPLEX(4)') does not have a suitable type ('INTEGER', or 'REAL').
55*3af717d6Skhaki3!ERROR: Reduction variable 'c5' ('COMPLEX(4)') does not have a suitable type ('INTEGER', or 'REAL').
56*3af717d6Skhaki3!ERROR: Reduction variable 'c6' ('COMPLEX(4)') does not have a suitable type ('LOGICAL').
57*3af717d6Skhaki3!ERROR: Reduction variable 'c7' ('COMPLEX(4)') does not have a suitable type ('LOGICAL').
58*3af717d6Skhaki3!ERROR: Reduction variable 'c8' ('COMPLEX(4)') does not have a suitable type ('LOGICAL').
59*3af717d6Skhaki3!ERROR: Reduction variable 'c9' ('COMPLEX(4)') does not have a suitable type ('LOGICAL').
60*3af717d6Skhaki3  do concurrent(i=1:5) &
61*3af717d6Skhaki3       & reduce(iand:c1) reduce(ieor:c2) reduce(ior:c3) reduce(max:c4) &
62*3af717d6Skhaki3       & reduce(min:c5) reduce(.and.:c6) reduce(.or.:c7) reduce(.eqv.:c8) &
63*3af717d6Skhaki3       & reduce(.neqv.:c9)
64*3af717d6Skhaki3  end do
65*3af717d6Skhaki3end subroutine s4
66*3af717d6Skhaki3
67*3af717d6Skhaki3subroutine s5()
68*3af717d6Skhaki3! Cannot apply integer operations to logical variables
69*3af717d6Skhaki3  logical :: l1, l2, l3, l4, l5, l6, l7
70*3af717d6Skhaki3!ERROR: Reduction variable 'l1' ('LOGICAL(4)') does not have a suitable type ('COMPLEX', 'INTEGER', or 'REAL').
71*3af717d6Skhaki3!ERROR: Reduction variable 'l2' ('LOGICAL(4)') does not have a suitable type ('COMPLEX', 'INTEGER', or 'REAL').
72*3af717d6Skhaki3!ERROR: Reduction variable 'l3' ('LOGICAL(4)') does not have a suitable type ('INTEGER').
73*3af717d6Skhaki3!ERROR: Reduction variable 'l4' ('LOGICAL(4)') does not have a suitable type ('INTEGER').
74*3af717d6Skhaki3!ERROR: Reduction variable 'l5' ('LOGICAL(4)') does not have a suitable type ('INTEGER').
75*3af717d6Skhaki3!ERROR: Reduction variable 'l6' ('LOGICAL(4)') does not have a suitable type ('INTEGER', or 'REAL').
76*3af717d6Skhaki3!ERROR: Reduction variable 'l7' ('LOGICAL(4)') does not have a suitable type ('INTEGER', or 'REAL').
77*3af717d6Skhaki3  do concurrent(i=1:5) &
78*3af717d6Skhaki3       & reduce(+:l1) reduce(*:l2) reduce(iand:l3) reduce(ieor:l4) &
79*3af717d6Skhaki3       & reduce(ior:l5) reduce(max:l6) reduce(min:l7)
80*3af717d6Skhaki3  end do
81*3af717d6Skhaki3end subroutine s5
82*3af717d6Skhaki3
83*3af717d6Skhaki3subroutine s6()
84*3af717d6Skhaki3! Cannot reduce a character
85*3af717d6Skhaki3  character ch
86*3af717d6Skhaki3!ERROR: Reduction variable 'ch' ('CHARACTER(1_8,1)') does not have a suitable type ('COMPLEX', 'INTEGER', or 'REAL').
87*3af717d6Skhaki3  do concurrent(i=1:5) reduce(+:ch)
88*3af717d6Skhaki3  end do
89*3af717d6Skhaki3end subroutine s6
90