aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/coarray_6.f90
blob: f44ac01597a3dd5b167be153f481e7dbdea506e2 (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
! { dg-do compile }
! { dg-options "-fcoarray=single" }
!
! Coarray support -- corank declarations
! PR fortran/18918
!
module m2
  use iso_c_binding
  integer(c_int), bind(C) :: a[*] ! { dg-error "BIND.C. attribute conflicts with CODIMENSION" }

  type, bind(C) :: t ! { dg-error "cannot have the ALLOCATABLE" }
    integer(c_int), allocatable :: a[:] ! { dg-error "cannot have the ALLOCATABLE" }
    integer(c_int)  :: b[*] ! { dg-error "must be allocatable" }
  end type t
end module m2

subroutine bind(a) bind(C) ! { dg-error "Coarray dummy variable" }
  use iso_c_binding
  integer(c_int) :: a[*]
end subroutine bind

subroutine allo(x) ! { dg-error "can thus not be an allocatable coarray" }
  integer, allocatable, intent(out) :: x[:]
end subroutine allo

module m
  integer :: modvar[*] ! OK, implicit save
  type t
    complex, allocatable :: b(:,:,:,:)[:,:,:]
  end type t
end module m

subroutine bar()
  integer, parameter :: a[*] = 4 ! { dg-error "PARAMETER attribute conflicts with CODIMENSION" }
  integer, pointer :: b[:] ! { dg-error "is not ALLOCATABLE, SAVE nor a dummy" }
end subroutine bar

subroutine vol()
  integer,save :: a[*]
  block
    volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
  end block
contains
  subroutine int()
    volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }
  end subroutine int
end subroutine vol


function func() result(func2) ! { dg-error "shall not be a coarray or have a coarray component" }
  use m
  type(t) :: func2
end function func

subroutine invalid()
  type t
    integer, allocatable :: a[:]
  end type t
  type t2
    type(t), allocatable :: b ! { dg-error "nonpointer, nonallocatable scalar" }
  end type t2
  type t3
    type(t), pointer :: c ! { dg-error "nonpointer, nonallocatable scalar" }
  end type t3
  type t4
    type(t) :: d(4) ! { dg-error "nonpointer, nonallocatable scalar" }
  end type t4
end subroutine invalid

subroutine valid(a)
  integer :: a(:)[4,-1:6,4:*]
  type t
    integer, allocatable :: a[:]
  end type t
  type t2
    type(t) :: b
  end type t2
  type(t2), save :: xt2[*] ! { dg-error "nonpointer, nonallocatable scalar, which is not a coarray" }
end subroutine valid

program main
  integer :: A[*] ! Valid, implicit SAVE attribute
end program main