URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray_4.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-fcoarray=single" }!! Coarray support -- corank declarations! PR fortran/18918!subroutine valid(n, c, f)implicit noneinteger :: ninteger, save :: a[*], b(4)[-1:4,*]real :: c(*)[1,0:3,3:*]real :: f(n)[0:n,-100:*]integer, allocatable :: d[:], e(:)[:,:]integer, save, codimension[1,*] :: g, h(7), i(6)[*], j[*]integer :: kcodimension :: k[*]save :: kinteger :: ii = 7blockinteger :: j = 5integer, save :: kk[j, *] ! { dg-error "Variable .j. cannot appear in the expression" }end blockend subroutine validsubroutine valid2()type tinteger, allocatable :: a[:]end type ttype, extends(t) :: ttinteger, allocatable :: b[:]end type tttype(tt), save :: footype(tt) :: barend subroutine valid2subroutine invalid(n)implicit noneinteger :: ninteger :: k[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }integer :: h(3)[*] ! { dg-error "not ALLOCATABLE, SAVE nor a dummy" }integer, save :: a[*]codimension :: a[1,*] ! { dg-error "Duplicate CODIMENSION attribute" }complex, save :: hh(n)[*] ! { dg-error "cannot have the SAVE attribute" }integer :: j = 6integer, save :: hf1[j,*] ! { dg-error "cannot appear in the expression" }integer, save :: hf2[n,*] ! OKinteger, save :: hf3(4)[j,*] ! { dg-error "cannot appear in the expression|cannot have the SAVE attribute" }integer, save :: hf4(5)[n,*] ! OKinteger, allocatable :: a2[*] ! { dg-error "must have deferred shape" }integer, allocatable :: a3(:)[*] ! { dg-error "must have deferred shape" }integer, allocatable :: a4[*] ! { dg-error "must have deferred shape" }end subroutine invalidsubroutine invalid2use iso_c_bindingimplicit nonetype t0integer, allocatable :: a[:,:,:]end type t0type tend type ttype, extends(t) :: tt ! { dg-error "has a coarray component, parent type" }integer, allocatable :: a[:]end type tttype tttinteger, pointer :: a[:] ! { dg-error "must be allocatable" }end type ttttype t4integer, allocatable :: b[4,*] ! { dg-error "with deferred shape" }end type t4type t5type(c_ptr), allocatable :: p[:] ! { dg-error "shall not be a coarray" }end type t5type(t0), save :: t0_1[*] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }type(t0), allocatable :: t0_2[:] ! { dg-error "shall be a nonpointer, nonallocatable scalar" }type(c_ptr), save :: pp[*] ! { dg-error "shall not be a coarray" }end subroutine invalid2elemental subroutine elem(a) ! { dg-error "Coarray dummy argument" }integer, intent(in) :: a[*]end subroutinefunction func() result(res)integer :: res[*] ! { dg-error "CODIMENSION attribute conflicts with RESULT" }end function func
