2017-11-05 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_lock_5.f90
blobb419606b0de1e73198ecac5cb34a9d79da6cf50f
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! LOCK_TYPE checks
6 module m3
7 use iso_fortran_env
8 type, extends(lock_type) :: lock
9 integer :: j = 7
10 end type lock
11 end module m3
13 use m3
14 type(lock_type) :: tl[*] = lock_type ()
15 type(lock) :: t[*]
16 tl = lock_type () ! { dg-error "variable definition context" }
17 print *,t%j
18 end
20 subroutine test()
21 use iso_fortran_env
22 type t
23 type(lock_type) :: lock
24 end type t
26 type t2
27 type(t), pointer :: x ! { dg-error "Pointer component x at .1. has a noncoarray subcomponent of type LOCK_TYPE, which must have a codimension or be a subcomponent of a coarray" }
28 end type t2
29 end subroutine test
31 subroutine test2()
32 use iso_fortran_env
33 implicit none
34 type t
35 type(lock_type), allocatable :: lock ! { dg-error "Allocatable component lock at .1. of type LOCK_TYPE must have a codimension" }
36 end type t
37 type t2
38 type(lock_type) :: lock
39 end type t2
40 type t3
41 type(t2), allocatable :: lock_cmp
42 end type t3
43 type t4
44 integer, allocatable :: a[:]
45 type(t2) :: b ! { dg-error "Noncoarray component b at .1. of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must have a codimension or be a subcomponent of a coarray. .Variables of type t4 may not have a codimension as already a coarray subcomponent exists." }
46 end type t4
47 type t5
48 type(t2) :: c ! { dg-error "Noncoarray component c at .1. of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must have a codimension or be a subcomponent of a coarray. .Variables of type t5 may not have a codimension as d at .2. has a codimension or a coarray subcomponent." }
49 integer, allocatable :: d[:] ! { dg-error "Noncoarray component c at .1. of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must have a codimension or be a subcomponent of a coarray. .Variables of type t5 may not have a codimension as d at .2. has a codimension or a coarray subcomponent." }
50 end type t5
51 end subroutine test2