xref: /llvm-project/flang/test/Semantics/expr-errors04.f90 (revision f13d6001324e9c9653d8568c1d86e182b217e272)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Regression test for more than one part-ref with nonzero rank
3
4program m
5  interface
6    function real_info1(i)
7    end
8    subroutine real_info2()
9    end
10    subroutine real_generic()
11    end
12  end interface
13  type mt
14    complex :: c, c2(2)
15    integer :: x, x2(2)
16    character(10) :: s, s2(2)
17    real, pointer :: p
18    real, allocatable :: a
19   contains
20    procedure, nopass :: info1 => real_info1
21    procedure, nopass :: info2 => real_info2
22    procedure, nopass :: real_generic
23    generic :: g1 => real_generic
24  end type
25  type mt2
26    type(mt) :: t1(2,2)
27  end type
28  type mt3
29    type(mt2) :: t2(2)
30  end type
31  type mt4
32    type(mt3) :: t3(2)
33  end type
34  type(mt4) :: t(2)
35
36  print *, t(1)%t3(1)%t2(1)%t1%x ! no error
37  print *, t(1)%t3(1)%t2(1)%t1%x2(1) ! no error
38  print *, t(1)%t3(1)%t2(1)%t1%s(1:2) ! no error
39  print *, t(1)%t3(1)%t2(1)%t1%s2(1)(1:2) ! no error
40  print *, t(1)%t3(1)%t2(1)%t1%c%RE ! no error
41  print *, t(1)%t3(1)%t2(1)%t1%c%IM ! no error
42  print *, t(1)%t3(1)%t2(1)%t1%c2(1)%RE ! no error
43  print *, t(1)%t3(1)%t2(1)%t1%c2(1)%IM ! no error
44
45  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
46  print *, t%t3%t2%t1%x
47  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
48  print *, t(1)%t3%t2%t1%x
49  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
50  print *, t(1)%t3(1)%t2%t1%x
51  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
52  print *, t(1)%t3%t2(1)%t1%x
53  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
54  print *, t%t3%t2%t1%x2(1)
55  !ERROR: Reference to whole rank-1 component 'x2' of rank-2 array of derived type is not allowed
56  print *, t(1)%t3%t2%t1%x2
57  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
58  print *, t(1)%t3(1)%t2%t1%x2(1)
59  !ERROR: Subscripts of component 'x2' of rank-2 derived type array have rank 1 but must all be scalar
60  print *, t(1)%t3(1)%t2(1)%t1%x2(1:)
61  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
62  print *, t%t3%t2%t1%s(1:2)
63  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
64  print *, t(1)%t3%t2(1)%t1%s(1:2)
65  !ERROR: Subscripts of component 't1' of rank-1 derived type array have rank 1 but must all be scalar
66  print *, t%t3%t2%t1(1,:)%s(1:2)
67  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
68  print *, t%t3%t2%t1%s2(1)(1:2)
69  !ERROR: Subscripts of component 's2' of rank-2 derived type array have rank 1 but must all be scalar
70  print *, t(1)%t3%t2%t1%s2(1:)(1:2)
71  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
72  print *, t%t3%t2%t1%c%RE
73  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
74  print *, t(1)%t3%t2%t1%c%RE
75  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
76  print *, t(1)%t3(1)%t2%t1%c%RE
77  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
78  print *, t(1)%t3%t2(1)%t1%c%RE
79  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
80  print *, t%t3%t2%t1%c%IM
81  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
82  print *, t%t3%t2%t1%c2(1)%RE
83  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
84  print *, t(1)%t3%t2%t1%c2(1)%RE
85  !ERROR: Subscripts of component 'c2' of rank-2 derived type array have rank 1 but must all be scalar
86  print *, t(1)%t3(1)%t2%t1%c2(1:)%RE
87  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
88  print *, t(1)%t3%t2(1)%t1%c2(1)%RE
89  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
90  print *, t%t3%t2%t1%c2(1)%IM
91
92  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
93  call sub0(t%t3%t2%t1%info1(i))
94  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
95  call sub0(t%t3%t2%t1%info1)
96  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
97  call t%t3%t2%t1%info2
98  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
99  call t%t3%t2%t1%g1
100
101  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
102  call sub0(t%t3%t2%t1(1)%info1(i))
103  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
104  call sub0(t%t3%t2%t1(1)%info1)
105  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
106  call t%t3%t2%t1(1)%info2
107  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
108  call t%t3%t2%t1(1)%g1
109
110  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
111  call sub0(t%t3%t2%t1(1:)%info1(i))
112  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
113  call sub0(t%t3%t2%t1(1:)%info1)
114  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
115  call t%t3%t2%t1(1:)%info2
116  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
117  call t%t3%t2%t1(1:)%g1
118
119  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
120  print *, t(1)%t3(1)%t2(1)%t1%p
121  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
122  print *, t%t3(1)%t2(1)%t1(1,1)%p
123  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
124  print *, t(1)%t3(1)%t2(1)%t1%a
125  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
126  print *, t%t3(1)%t2(1)%t1(1,1)%a
127  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
128  t(1)%t3(1)%t2(1)%t1%p => null()
129  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
130  t%t3(1)%t2(1)%t1(1,1)%p => null()
131
132end
133