summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/coarray_38.f90
blob: 04ef742faabb280edff308f356395f01c5061fc3 (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
! { dg-do compile }
! { dg-options "-fcoarray=lib" }
!
! Valid code - but currently not implemented for -fcoarray=lib; single okay 
!
subroutine one
implicit none
type t
  integer, allocatable :: a
  integer :: b
end type t
type t2
  type(t), allocatable :: caf2[:]
end type t2
type(t), save :: caf[*],x
type(t2) :: y

x = caf[4] ! OK, now
x%a = caf[4]%a ! OK, now
x%b = caf[4]%b ! OK
x = y%caf2[5]  ! OK, now
x%a = y%caf2[4]%a ! OK, now
x%b = y%caf2[4]%b ! OK
end subroutine one

subroutine two
implicit none
type t
  integer, pointer :: a
  integer :: b
end type t
type t2
  type(t), allocatable :: caf2[:]
end type t2
type(t), save :: caf[*],x
type(t2) :: y

x = caf[4]     ! OK
x%a = caf[4]%a ! OK, now
x%b = caf[4]%b ! OK
x = y%caf2[5]  ! OK
x%a = y%caf2[4]%a !  OK, now
x%b = y%caf2[4]%b ! OK
end subroutine two

subroutine three
implicit none
type t
  integer :: b
end type t
type t2
  type(t), allocatable :: caf2(:)[:]
end type t2
type(t), save :: caf(10)[*]
integer :: x(10)
type(t2) :: y

x(1) = caf(2)[4]%b ! OK
x(:) = caf(:)[4]%b ! OK now

x(1) = y%caf2(2)[4]%b ! OK
x(:) = y%caf2(:)[4]%b ! OK now
end subroutine three

subroutine four
implicit none
type t
  integer, allocatable :: a
  integer :: b
end type t
type t2
  class(t), allocatable :: caf2[:]
end type t2
class(t), allocatable :: caf[:] ! { dg-error "Sorry, allocatable/pointer components in polymorphic" }
type(t) :: x
type(t2) :: y

!x = caf[4]    ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
x%a = caf[4]%a ! OK, now
x%b = caf[4]%b ! OK
!x = y%caf2[5] ! Unsupported - and ICEs in resolve_ordinary_assign, cf. PR fortran/65397
x%a = y%caf2[4]%a ! Ok, now
x%b = y%caf2[4]%b ! OK
end subroutine four

subroutine five
implicit none
type t
  integer, pointer :: a
  integer :: b
end type t
type t2
  class(t), allocatable :: caf2[:]
end type t2
class(t), save, allocatable :: caf[:] ! { dg-error "Sorry, allocatable/pointer components in polymorphic" }
type(t) :: x
type(t2) :: y

!x = caf[4]     ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
x%a = caf[4]%a ! OK, now
x%b = caf[4]%b ! OK
!x = y%caf2[5]  ! OK - but ICEs in resolve_ordinary_assign, cf. PR fortran/65397
x%a = y%caf2[4]%a ! OK, now
x%b = y%caf2[4]%b ! OK
end subroutine five

subroutine six
implicit none
type t
  integer :: b
end type t
type t2
  class(t), allocatable :: caf2(:)[:]
end type t2
class(t), save, allocatable :: caf(:)[:]
integer :: x(10)
type(t2) :: y

x(1) = caf(2)[4]%b ! OK
x(:) = caf(:)[4]%b ! OK now

x(1) = y%caf2(2)[4]%b ! OK
x(:) = y%caf2(:)[4]%b ! OK now
end subroutine six

call one()
call two()
call three()
call four()
call five()
call six()
end