URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray_6.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-fcoarray=single" }!! Coarray support -- corank declarations! PR fortran/18918!module m2use iso_c_bindinginteger(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 tend module m2subroutine bind(a) bind(C) ! { dg-error "Coarray dummy variable" }use iso_c_bindinginteger(c_int) :: a[*]end subroutine bindsubroutine allo(x) ! { dg-error "can thus not be an allocatable coarray" }integer, allocatable, intent(out) :: x[:]end subroutine allomodule minteger :: modvar[*] ! OK, implicit savetype tcomplex, allocatable :: b(:,:,:,:)[:,:,:]end type tend module msubroutine 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 barsubroutine vol()integer,save :: a[*]blockvolatile :: a ! { dg-error "Specifying VOLATILE for coarray" }end blockcontainssubroutine int()volatile :: a ! { dg-error "Specifying VOLATILE for coarray" }end subroutine intend subroutine volfunction func() result(func2) ! { dg-error "shall not be a coarray or have a coarray component" }use mtype(t) :: func2end function funcsubroutine invalid()type tinteger, allocatable :: a[:]end type ttype t2type(t), allocatable :: b ! { dg-error "nonpointer, nonallocatable scalar" }end type t2type t3type(t), pointer :: c ! { dg-error "nonpointer, nonallocatable scalar" }end type t3type t4type(t) :: d(4) ! { dg-error "nonpointer, nonallocatable scalar" }end type t4end subroutine invalidsubroutine valid(a)integer :: a(:)[4,-1:6,4:*]type tinteger, allocatable :: a[:]end type ttype t2type(t) :: bend type t2type(t2), save :: xt2[*]end subroutine validprogram maininteger :: A[*] ! Valid, implicit SAVE attributeend program main! { dg-final { cleanup-modules "m" } }
