2 ! { dg-options "-fcoarray=single" }
5 ! LOCK/LOCK_TYPE checks
11 type, extends(t
) :: t2
! { dg-error "coarray component, parent type .t. shall also have one" }
12 type(lock_type
), allocatable
:: c(:)[:]
14 end subroutine extends
20 type(lock_type
), allocatable
:: x(:)[:]
27 type(lock_type
), allocatable
:: x
! { dg-error "Allocatable component x at .1. of type LOCK_TYPE must have a codimension" }
34 type(lock_type
) :: x
! OK
40 type(lock_type
), intent(out
) :: x
[*] ! OK
43 subroutine sub1(x
) ! { dg-error "is INTENT.OUT. and can thus not be an allocatable coarray or have coarray components" }
45 type(lock_type
), allocatable
, intent(out
) :: x(:)[:]
48 subroutine sub2(x
) ! { dg-error "is INTENT.OUT. and can thus not be an allocatable coarray or have coarray components" }
50 type(t
), intent(out
) :: x
53 subroutine sub3(x
) ! { dg-error "with coarray component shall be a nonpointer, nonallocatable scalar" }
55 type(t
), intent(inout
) :: x
[*]
60 type(t3
), intent(inout
) :: x
[*] ! OK
67 type(lock_type
) :: lock
! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
68 end subroutine lock_test
76 type(lock_type
), save :: lock
[*],lock2(2)[*]
77 lock(t
) ! { dg-error "Syntax error in LOCK statement" }
78 lock(x
) ! { dg-error "must be a scalar of type LOCK_TYPE" }
81 lock(lock2
) ! { dg-error "must be a scalar of type LOCK_TYPE" }
83 end subroutine lock_test2
88 type(lock_type
), save :: a
[*], b
[*]
89 a
= b
! { dg-error "LOCK_TYPE in variable definition context" }
90 b
= lock_type() ! { dg-error "LOCK_TYPE in variable definition context" }
91 print *, a
! { dg-error "cannot have PRIVATE components" }
92 end subroutine lock_test3
97 type(lock_type
), allocatable
:: A(:)[:]
100 lock(A(1), acquired_lock
=ob
)
103 end subroutine lock_test4
106 subroutine argument_check()
108 type(lock_type
), SAVE :: ll
[*]
109 call no_interface(ll
) ! { dg-error "Actual argument of LOCK_TYPE or with LOCK_TYPE component at .1. requires an explicit interface" }
110 call test(ll
) ! { dg-error "non-INTENT.INOUT. dummy .x. at .1., which is LOCK_TYPE or has a LOCK_TYPE component" }
113 type(lock_type
), intent(in
) :: x
[*]
115 end subroutine argument_check