summaryrefslogtreecommitdiff
path: root/flang/test/Semantics/expr-errors04.f90
blob: be794c7c78f6d1efcdb84f915759cfc2dc1c44cc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
! RUN: %python %S/test_errors.py %s %flang_fc1
! Regression test for more than one part-ref with nonzero rank

program m
  interface
    function real_info1(i)
    end
    subroutine real_info2()
    end
    subroutine real_generic()
    end
  end interface
  type mt
    complex :: c, c2(2)
    integer :: x, x2(2)
    character(10) :: s, s2(2)
    real, pointer :: p
    real, allocatable :: a
   contains
    procedure, nopass :: info1 => real_info1
    procedure, nopass :: info2 => real_info2
    procedure, nopass :: real_generic
    generic :: g1 => real_generic
  end type
  type mt2
    type(mt) :: t1(2,2)
  end type
  type mt3
    type(mt2) :: t2(2)
  end type
  type mt4
    type(mt3) :: t3(2)
  end type
  type(mt4) :: t(2)

  print *, t(1)%t3(1)%t2(1)%t1%x ! no error
  print *, t(1)%t3(1)%t2(1)%t1%x2(1) ! no error
  print *, t(1)%t3(1)%t2(1)%t1%s(1:2) ! no error
  print *, t(1)%t3(1)%t2(1)%t1%s2(1)(1:2) ! no error
  print *, t(1)%t3(1)%t2(1)%t1%c%RE ! no error
  print *, t(1)%t3(1)%t2(1)%t1%c%IM ! no error
  print *, t(1)%t3(1)%t2(1)%t1%c2(1)%RE ! no error
  print *, t(1)%t3(1)%t2(1)%t1%c2(1)%IM ! no error

  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%x
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2%t1%x
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3(1)%t2%t1%x
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2(1)%t1%x
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%x2(1)
  !ERROR: Reference to whole rank-1 component 'x2' of rank-2 array of derived type is not allowed
  print *, t(1)%t3%t2%t1%x2
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3(1)%t2%t1%x2(1)
  !ERROR: Subscripts of component 'x2' of rank-2 derived type array have rank 1 but must all be scalar
  print *, t(1)%t3(1)%t2(1)%t1%x2(1:)
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%s(1:2)
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2(1)%t1%s(1:2)
  !ERROR: Subscripts of component 't1' of rank-1 derived type array have rank 1 but must all be scalar
  print *, t%t3%t2%t1(1,:)%s(1:2)
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%s2(1)(1:2)
  !ERROR: Subscripts of component 's2' of rank-2 derived type array have rank 1 but must all be scalar
  print *, t(1)%t3%t2%t1%s2(1:)(1:2)
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%c%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2%t1%c%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3(1)%t2%t1%c%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2(1)%t1%c%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%c%IM
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%c2(1)%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2%t1%c2(1)%RE
  !ERROR: Subscripts of component 'c2' of rank-2 derived type array have rank 1 but must all be scalar
  print *, t(1)%t3(1)%t2%t1%c2(1:)%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t(1)%t3%t2(1)%t1%c2(1)%RE
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  print *, t%t3%t2%t1%c2(1)%IM

  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  call sub0(t%t3%t2%t1%info1(i))
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  call sub0(t%t3%t2%t1%info1)
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  call t%t3%t2%t1%info2
  !ERROR: Reference to whole rank-2 component 't1' of rank-1 array of derived type is not allowed
  call t%t3%t2%t1%g1

  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call sub0(t%t3%t2%t1(1)%info1(i))
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call sub0(t%t3%t2%t1(1)%info1)
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call t%t3%t2%t1(1)%info2
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call t%t3%t2%t1(1)%g1

  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call sub0(t%t3%t2%t1(1:)%info1(i))
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call sub0(t%t3%t2%t1(1:)%info1)
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call t%t3%t2%t1(1:)%info2
  !ERROR: Reference to rank-2 object 't1' has 1 subscripts
  call t%t3%t2%t1(1:)%g1

  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  print *, t(1)%t3(1)%t2(1)%t1%p
  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  print *, t%t3(1)%t2(1)%t1(1,1)%p
  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  print *, t(1)%t3(1)%t2(1)%t1%a
  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  print *, t%t3(1)%t2(1)%t1(1,1)%a
  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  t(1)%t3(1)%t2(1)%t1%p => null()
  !ERROR: An allocatable or pointer component reference must be applied to a scalar base
  t%t3(1)%t2(1)%t1(1,1)%p => null()

end