OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / coarray_4.f90
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
3 !
4 ! Coarray support -- corank declarations
5 ! PR fortran/18918
6 !
7
8 subroutine valid(n, c, f)
9   implicit none
10   integer :: n
11   integer, save :: a[*], b(4)[-1:4,*]
12   real :: c(*)[1,0:3,3:*]
13   real :: f(n)[0:n,-100:*]
14   integer, allocatable :: d[:], e(:)[:,:]
15   integer, save, codimension[1,*] :: g, h(7), i(6)[*], j[*]
16   integer :: k
17   codimension :: k[*]
18   save :: k
19   integer :: ii = 7
20   block
21     integer :: j = 5
22     integer, save :: kk[j, *] ! { dg-error "Variable .j. cannot appear in the expression" }
23   end block
24 end subroutine valid
25
26 subroutine valid2()
27   type t
28     integer, allocatable :: a[:]
29   end type t
30   type, extends(t) :: tt
31     integer, allocatable :: b[:]
32   end type tt
33   type(tt), save :: foo
34   type(tt) :: bar
35 end subroutine valid2
36
37 subroutine invalid(n)
38   implicit none
39   integer :: n
40   integer :: k[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
41   integer :: h(3)[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
42   integer, save :: a[*]
43   codimension :: a[1,*] ! { dg-error "Duplicate CODIMENSION attribute" }
44   complex, save :: hh(n)[*] ! { dg-error "cannot have the SAVE attribute" }
45   integer :: j = 6
46
47   integer, save :: hf1[j,*] ! { dg-error "cannot appear in the expression" }
48   integer, save :: hf2[n,*] ! OK
49   integer, save :: hf3(4)[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }
50   integer, save :: hf4(5)[n,*] ! OK
51
52   integer, allocatable :: a2[*] ! { dg-error "must have deferred shape" }
53   integer, allocatable :: a3(:)[*] ! { dg-error "must have deferred shape" }
54   integer, allocatable :: a4[*] ! { dg-error "must have deferred shape" }
55 end subroutine invalid
56
57 subroutine invalid2
58   use iso_c_binding
59   implicit none
60   type t0
61     integer, allocatable :: a[:,:,:]
62   end type t0
63   type t
64   end type t
65   type, extends(t) :: tt ! { dg-error "has a coarray component, parent type" }
66     integer, allocatable :: a[:]
67   end type tt
68   type ttt
69     integer, pointer :: a[:] ! { dg-error "must be allocatable" }
70   end type ttt
71   type t4
72     integer, allocatable :: b[4,*] ! { dg-error "with deferred shape" }
73   end type t4
74   type t5
75     type(c_ptr), allocatable :: p[:] ! { dg-error "shall not be a coarray" }
76   end type t5
77   type(t0), save :: t0_1[*] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
78   type(t0), allocatable :: t0_2[:] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
79   type(c_ptr), save :: pp[*] ! { dg-error "shall not be a coarray" }
80 end subroutine invalid2
81
82 elemental subroutine elem(a) ! { dg-error "Coarray dummy argument" }
83   integer, intent(in) :: a[*]
84 end subroutine
85
86 function func() result(res)
87   integer :: res[*] ! { dg-error "CODIMENSION attribute conflicts with RESULT" }
88 end function func