ieee_9.f90: XFAIL on arm*-*-gnueabi[hf].
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_14.f90
blobd7eb6b6be02dd063534c865a589958ec984056fa
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! PR fortran/46370
6 ! Coarray checks
9 ! Check for C1229: "A data-ref shall not be a polymorphic subobject of a
10 ! coindexed object." which applies to function and subroutine calls.
11 module m
12 implicit none
13 type t
14 contains
15 procedure, nopass :: sub=>sub
16 procedure, nopass :: func=>func
17 end type t
18 type t3
19 type(t) :: nopoly
20 end type t3
21 type t2
22 class(t), allocatable :: poly
23 class(t3), allocatable :: poly2
24 end type t2
25 contains
26 subroutine sub()
27 end subroutine sub
28 function func()
29 integer :: func
30 end function func
31 end module m
33 subroutine test(x)
34 use m
35 type(t2) :: x[*]
36 integer :: i
37 call x[1]%poly2%nopoly%sub() ! OK
38 i = x[1]%poly2%nopoly%func() ! OK
39 call x[1]%poly%sub() ! { dg-error "Polymorphic subobject of coindexed object" }
40 i = x[1]%poly%func() ! { dg-error "Polymorphic subobject of coindexed object" }
41 end subroutine test
44 ! Check for C617: "... a data-ref shall not be a polymorphic subobject of a
45 ! coindexed object or ..."
46 ! Before, the second allocate statment was failing - though it is no subobject.
47 program myTest
48 type t
49 end type t
50 class(t), allocatable :: a[:]
51 allocate (t :: a) ! { dg-error "Coarray specification required in ALLOCATE statement" }
52 allocate (t :: a[*]) ! OK
53 end program myTest