OSDN Git Service

Add NIOS2 support. Code from SourceyG++.
[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, save :: kk[ii, *] ! { dg-error "cannot have the SAVE attribute" }
22   end block
23 end subroutine valid
24
25 subroutine valid2()
26   type t
27     integer, allocatable :: a[:]
28   end type t
29   type, extends(t) :: tt
30     integer, allocatable :: b[:]
31   end type tt
32   type(tt), save :: foo
33   type(tt) :: bar ! { dg-error "is a coarray or has a coarray component" }
34 end subroutine valid2
35
36 subroutine invalid(n)
37   implicit none
38   integer :: n
39   integer :: k[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
40   integer :: h(3)[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }
41   integer, save :: a[*]
42   codimension :: a[1,*] ! { dg-error "Duplicate CODIMENSION attribute" }
43   complex, save :: hh(n)[*] ! { dg-error "cannot have the SAVE attribute" }
44   integer :: j = 6
45
46   integer, save :: hf1[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }
47   integer, save :: hf2[n,*] ! { dg-error "cannot have the SAVE attribute" }
48   integer, save :: hf3(4)[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }
49   integer, save :: hf4(5)[n,*] ! { dg-error "cannot have the SAVE attribute" }
50
51   integer, allocatable :: a2[*] ! { dg-error "must have deferred shape" }
52   integer, allocatable :: a3(:)[*] ! { dg-error "must have deferred shape" }
53   integer, allocatable :: a4[*] ! { dg-error "must have deferred shape" }
54 end subroutine invalid
55
56 subroutine invalid2
57   use iso_c_binding
58   implicit none
59   type t0
60     integer, allocatable :: a[:,:,:]
61   end type t0
62   type t
63   end type t
64   type, extends(t) :: tt ! { dg-error "has a coarray component, parent type" }
65     integer, allocatable :: a[:]
66   end type tt
67   type ttt
68     integer, pointer :: a[:] ! { dg-error "must be allocatable" }
69   end type ttt
70   type t4
71     integer, allocatable :: b[4,*] ! { dg-error "with deferred shape" }
72   end type t4
73   type t5
74     type(c_ptr), allocatable :: p[:] ! { dg-error "shall not be a coarray" }
75   end type t5
76   type(t0), save :: t0_1[*] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
77   type(t0), allocatable :: t0_2[:] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }
78   type(c_ptr), save :: pp[*] ! { dg-error "shall not be a coarray" }
79 end subroutine invalid2
80
81 elemental subroutine elem(a) ! { dg-error "Coarray dummy argument" }
82   integer, intent(in) :: a[*]
83 end subroutine
84
85 function func() result(res)
86   integer :: res[*] ! { dg-error "CODIMENSION attribute conflicts with RESULT" }
87 end function func