2 ! { dg-options "-fcoarray=single" }
9 character(len
=30) :: str(2)
11 critical fkl
! { dg-error "Syntax error in CRITICAL" }
12 end critical fkl
! { dg-error "Expecting END PROGRAM" }
14 sync
all (stat
=1) ! { dg-error "Syntax error in SYNC ALL" }
15 sync
all ( stat
= n
,stat
=k
) ! { dg-error "Redundant STAT" }
16 sync
memory (errmsg
=str
)
17 sync
memory (errmsg
=n
) ! { dg-error "must be a scalar CHARACTER variable" }
18 sync
images (*, stat
=1.0) ! { dg-error "Syntax error in SYNC IMAGES" }
19 sync
images (-1) ! { dg-error "must between 1 and num_images" }
22 sync
images ( m(1:0) )
23 sync
images ( reshape([1],[1,1])) ! { dg-error "must be a scalar or rank-1" }
28 stop 'error' ! { dg-error "Image control statement STOP" }
29 sync all
! { dg-error "Image control statement SYNC" }
30 return 1 ! { dg-error "Image control statement RETURN" }
31 critical
! { dg-error "Nested CRITICAL block" }
33 end critical
! { dg-error "Expecting END SUBROUTINE" }
39 cycle
! { dg-error "leaves CRITICAL construct" }
47 exit outer
! { dg-error "leaves CRITICAL construct" }
55 333 continue ! { dg-error "leaves CRITICAL construct" }
59 goto 333 ! { dg-error "leaves CRITICAL construct" }
70 goto 555 ! { dg-error "leaves CRITICAL construct" }
75 555 end if ! { dg-error "leaves CRITICAL construct" }
78 pure
subroutine pureSub()
79 critical
! { dg-error "Image control statement CRITICAL" }
80 end critical
! { dg-error "Expecting END SUBROUTINE statement" }
81 sync all
! { dg-error "Image control statement SYNC" }
83 end subroutine pureSub
87 goto 10 ! { dg-warning "is not in the same block" }
90 5 continue ! { dg-warning "is not in the same block" }
92 goto 20 ! { dg-error "leaves CRITICAL construct" }
93 goto 30 ! { dg-error "leaves CRITICAL construct" }
94 10 END CRITICAL
! { dg-warning "is not in the same block" }
95 goto 5 ! { dg-warning "is not in the same block" }
96 20 continue ! { dg-error "leaves CRITICAL construct" }
98 30 continue ! { dg-error "leaves CRITICAL construct" }