annotate gcc/testsuite/gfortran.dg/coarray_lock_4.f90 @ 158:494b0b89df80 default tip

...
author Shinji KONO <kono@ie.u-ryukyu.ac.jp>
date Mon, 25 May 2020 18:13:55 +0900
parents 04ced10e8804
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do compile }
kono
parents:
diff changeset
2 ! { dg-options "-fcoarray=single" }
kono
parents:
diff changeset
3 !
kono
parents:
diff changeset
4 !
kono
parents:
diff changeset
5 ! LOCK/LOCK_TYPE checks
kono
parents:
diff changeset
6 !
kono
parents:
diff changeset
7
kono
parents:
diff changeset
8 subroutine valid()
kono
parents:
diff changeset
9 use iso_fortran_env
kono
parents:
diff changeset
10 implicit none
kono
parents:
diff changeset
11 type t
kono
parents:
diff changeset
12 type(lock_type) :: lock
kono
parents:
diff changeset
13 end type t
kono
parents:
diff changeset
14
kono
parents:
diff changeset
15 type t2
kono
parents:
diff changeset
16 type(lock_type), allocatable :: lock(:)[:]
kono
parents:
diff changeset
17 end type t2
kono
parents:
diff changeset
18
kono
parents:
diff changeset
19 type(t), save :: a[*]
kono
parents:
diff changeset
20 type(t2), save :: b ! OK
kono
parents:
diff changeset
21
kono
parents:
diff changeset
22 allocate(b%lock(1)[*])
kono
parents:
diff changeset
23 LOCK(a%lock) ! OK
kono
parents:
diff changeset
24 LOCK(a[1]%lock) ! OK
kono
parents:
diff changeset
25
kono
parents:
diff changeset
26 LOCK(b%lock(1)) ! OK
kono
parents:
diff changeset
27 LOCK(b%lock(1)[1]) ! OK
kono
parents:
diff changeset
28 end subroutine valid
kono
parents:
diff changeset
29
kono
parents:
diff changeset
30 subroutine invalid()
kono
parents:
diff changeset
31 use iso_fortran_env
kono
parents:
diff changeset
32 implicit none
kono
parents:
diff changeset
33 type t
kono
parents:
diff changeset
34 type(lock_type) :: lock
kono
parents:
diff changeset
35 end type t
kono
parents:
diff changeset
36 type(t), save :: a ! { dg-error "type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
kono
parents:
diff changeset
37 end subroutine invalid
kono
parents:
diff changeset
38
kono
parents:
diff changeset
39 subroutine more_tests
kono
parents:
diff changeset
40 use iso_fortran_env
kono
parents:
diff changeset
41 implicit none
kono
parents:
diff changeset
42 type t
kono
parents:
diff changeset
43 type(lock_type) :: a ! OK
kono
parents:
diff changeset
44 end type t
kono
parents:
diff changeset
45
kono
parents:
diff changeset
46 type t1
kono
parents:
diff changeset
47 type(lock_type), allocatable :: c2(:)[:] ! OK
kono
parents:
diff changeset
48 end type t1
kono
parents:
diff changeset
49 type(t1) :: x1 ! OK
kono
parents:
diff changeset
50
kono
parents:
diff changeset
51 type t2
kono
parents:
diff changeset
52 type(lock_type), allocatable :: c1(:) ! { dg-error "Allocatable component c1 at .1. of type LOCK_TYPE must have a codimension" }
kono
parents:
diff changeset
53 end type t2
kono
parents:
diff changeset
54
kono
parents:
diff changeset
55 type t3
kono
parents:
diff changeset
56 type(t) :: b
kono
parents:
diff changeset
57 end type t3
kono
parents:
diff changeset
58 type(t3) :: x3 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
kono
parents:
diff changeset
59
kono
parents:
diff changeset
60 type t4
kono
parents:
diff changeset
61 type(lock_type) :: c0(2)
kono
parents:
diff changeset
62 end type t4
kono
parents:
diff changeset
63 type(t4) :: x4 ! { dg-error "of type LOCK_TYPE or with subcomponent of type LOCK_TYPE must be a coarray" }
kono
parents:
diff changeset
64 end subroutine more_tests