URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [coarray_lock_4.f90] - Rev 801
Go to most recent revision | Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-fcoarray=single" }!!! LOCK/LOCK_TYPE checks!subroutine valid()use iso_fortran_envimplicit nonetype ttype(lock_type) :: lockend type ttype t2type(lock_type), allocatable :: lock(:)[:]end type t2type(t), save :: a[*]type(t2), save :: b ! OKallocate(b%lock(1)[*])LOCK(a%lock) ! OKLOCK(a[1]%lock) ! OKLOCK(b%lock(1)) ! OKLOCK(b%lock(1)[1]) ! OKend subroutine validsubroutine invalid()use iso_fortran_envimplicit nonetype ttype(lock_type) :: lockend type ttype(t), save :: a ! { dg-error "type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }end subroutine invalidsubroutine more_testsuse iso_fortran_envimplicit nonetype ttype(lock_type) :: a ! OKend type ttype t1type(lock_type), allocatable :: c2(:)[:] ! OKend type t1type(t1) :: x1 ! OKtype t2type(lock_type), allocatable :: c1(:) ! { dg-error "Allocatable component c1 at .1. of type LOCK_TYPE must have a codimension" }end type t2type t3type(t) :: bend type t3type(t3) :: x3 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }type t4type(lock_type) :: c0(2)end type t4type(t4) :: x4 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }end subroutine more_tests
Go to most recent revision | Compare with Previous | Blame | View Log
