2 ! { dg-options "-fcoarray=single" }
4 ! Coarray support -- corank declarations
9 integer(c_int
), bind(C
) :: a
[*] ! { dg-error "BIND.C. attribute conflicts with CODIMENSION" }
11 type, bind(C
) :: t
! { dg-error "cannot have the ALLOCATABLE" }
12 integer(c_int
), allocatable
:: a
[:] ! { dg-error "cannot have the ALLOCATABLE" }
13 integer(c_int
) :: b
[*] ! { dg-error "must be allocatable" }
17 subroutine bind(a
) bind(C
) ! { dg-error "Coarray dummy variable" }
19 integer(c_int
) :: a
[*]
22 subroutine allo(x
) ! { dg-error "can thus not be an allocatable coarray" }
23 integer, allocatable
, intent(out
) :: x
[:]
27 integer :: modvar
[*] ! OK, implicit save
29 complex, allocatable
:: b(:,:,:,:)[:,:,:]
34 integer, parameter :: a
[*] = 4 ! { dg-error "PARAMETER attribute conflicts with CODIMENSION" }
35 integer, pointer :: b
[:] ! { dg-error "is not ALLOCATABLE, SAVE nor a dummy" }
41 volatile :: a
! { dg-error "Specifying VOLATILE for coarray" }
45 volatile :: a
! { dg-error "Specifying VOLATILE for coarray" }
50 function func() result(func2
) ! { dg-error "shall not be a coarray or have a coarray component" }
57 integer, allocatable
:: a
[:]
60 type(t
), allocatable
:: b
! { dg-error "nonpointer, nonallocatable scalar" }
63 type(t
), pointer :: c
! { dg-error "nonpointer, nonallocatable scalar" }
66 type(t
) :: d(4) ! { dg-error "nonpointer, nonallocatable scalar" }
68 end subroutine invalid
71 integer :: a(:)[4,-1:6,4:*]
73 integer, allocatable
:: a
[:]
78 type(t2
), save :: xt2
[*]
82 integer :: A
[*] ! Valid, implicit SAVE attribute
85 ! { dg-final { cleanup-modules "m" } }