arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_6.f90
blobd30567ac212fac67e3298a347d0f464bbad0d256
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! Coarray support -- corank declarations
5 ! PR fortran/18918
7 module m2
8 use iso_c_binding
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" }
14 end type t
15 end module m2
17 subroutine bind(a) bind(C) ! { dg-error "Coarray dummy variable" }
18 use iso_c_binding
19 integer(c_int) :: a[*]
20 end subroutine bind
22 subroutine allo(x) ! { dg-error "can thus not be an allocatable coarray" }
23 integer, allocatable, intent(out) :: x[:]
24 end subroutine allo
26 module m
27 integer :: modvar[*] ! OK, implicit save
28 type t
29 complex, allocatable :: b(:,:,:,:)[:,:,:]
30 end type t
31 end module m
33 subroutine bar()
34 integer, parameter :: a[*] = 4 ! { dg-error "PARAMETER attribute conflicts with CODIMENSION" }
35 integer :: b[*] ! { dg-error "is not ALLOCATABLE, SAVE nor a dummy" }
36 end subroutine bar
38 subroutine vol()
39 integer,save :: a[*]
40 block
41 volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
42 end block
43 contains
44 subroutine int()
45 volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
46 end subroutine int
47 end subroutine vol
50 function func() result(func2) ! { dg-error "shall not be a coarray or have a coarray component" }
51 use m
52 type(t) :: func2
53 end function func
55 subroutine invalid()
56 type t
57 integer, allocatable :: a[:]
58 end type t
59 type t2
60 type(t), allocatable :: b ! { dg-error "nonpointer, nonallocatable scalar" }
61 end type t2
62 type t3
63 type(t), pointer :: c ! { dg-error "nonpointer, nonallocatable scalar" }
64 end type t3
65 type t4
66 type(t) :: d(4) ! { dg-error "nonpointer, nonallocatable scalar" }
67 end type t4
68 end subroutine invalid
70 subroutine valid(a)
71 integer :: a(:)[4,-1:6,4:*]
72 type t
73 integer, allocatable :: a[:]
74 end type t
75 type t2
76 type(t) :: b
77 end type t2
78 type(t2), save :: xt2[*] ! { dg-error "nonpointer, nonallocatable scalar, which is not a coarray" }
79 end subroutine valid
81 program main
82 integer :: A[*] ! Valid, implicit SAVE attribute
83 end program main