[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Semantics / coarrays01.f90
blob0a6f88a7e748c9005b92617598fd46cd012b4c9e
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Test selector and team-value in CHANGE TEAM statement
4 ! OK
5 subroutine s1
6 use iso_fortran_env, only: team_type
7 type(team_type) :: t
8 real :: y[10,*]
9 change team(t, x[10,*] => y)
10 end team
11 form team(1, t)
12 end
14 subroutine s2
15 use iso_fortran_env
16 type(team_type) :: t
17 real :: y[10,*], y2[*], x[*]
18 ! C1113
19 !ERROR: Selector 'y' was already used as a selector or coarray in this statement
20 change team(t, x[10,*] => y, x2[*] => y)
21 end team
22 !ERROR: Selector 'x' was already used as a selector or coarray in this statement
23 change team(t, x[10,*] => y, x2[*] => x)
24 end team
25 !ERROR: Coarray 'y' was already used as a selector or coarray in this statement
26 change team(t, x[10,*] => y, y[*] => y2)
27 end team
28 end
30 subroutine s3
31 type :: team_type
32 end type
33 type :: foo
34 real :: a
35 end type
36 type(team_type) :: t1
37 type(foo) :: t2
38 type(team_type) :: t3(3)
39 real :: y[10,*]
40 ! C1114
41 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
42 change team(t1, x[10,*] => y)
43 end team
44 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
45 change team(t2, x[10,*] => y)
46 end team
47 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
48 change team(t2%a, x[10,*] => y)
49 end team
50 !ERROR: Must be a scalar value, but is a rank-1 array
51 change team(t3, x[10,*] => y)
52 end team
53 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
54 form team(1, t1)
55 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
56 form team(2, t2)
57 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
58 form team(2, t2%a)
59 !ERROR: Team value must be of type TEAM_TYPE from module ISO_FORTRAN_ENV
60 form team(3, t3(2))
61 !ERROR: Must be a scalar value, but is a rank-1 array
62 form team(3, t3)
63 end
65 subroutine s4
66 use iso_fortran_env, only: team_type
67 complex :: z
68 integer :: i, j(10)
69 type(team_type) :: t, t2(2)
70 form team(i, t)
71 !ERROR: Must be a scalar value, but is a rank-1 array
72 form team(1, t2)
73 !ERROR: Must have INTEGER type, but is COMPLEX(4)
74 form team(z, t)
75 !ERROR: Must be a scalar value, but is a rank-1 array
76 form team(j, t)
77 end