OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [do_concurrent_1.f90] - Blame information for rev 694

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do compile }
2
! { dg-options "-fcoarray=single" }
3
!
4
! PR fortran/44646
5
!
6
! DO CONCURRENT
7
!
8
implicit none
9
integer :: i, j
10
 
11
outer: do, concurrent ( i = 1 : 4)
12
  do j = 1, 5
13
    if (j == 1) cycle ! OK
14
    cycle outer ! OK: C821   FIXME
15
    exit outer ! { dg-error "EXIT statement at .1. leaves DO CONCURRENT construct" }
16
  end do
17
end do outer
18
 
19
do concurrent (j = 1:5)
20
  cycle ! OK
21
end do
22
 
23
outer2: do j = 1, 7
24
  do concurrent (j=1:5:2) ! cycle outer2 - bad: C821
25
    cycle outer2 ! { dg-error "leaves DO CONCURRENT construct" }
26
  end do
27
end do outer2
28
 
29
do concurrent ( i = 1 : 4)
30
  exit ! { dg-error "EXIT statement at .1. leaves DO CONCURRENT construct" }
31
end do
32
end
33
 
34
subroutine foo()
35
  do concurrent ( i = 1 : 4)
36
    return   ! { dg-error "Image control statement RETURN" }
37
    sync all ! { dg-error "Image control statement SYNC" }
38
    call test () ! { dg-error "Subroutine call to .test. in DO CONCURRENT block at .1. is not PURE" }
39
    stop ! { dg-error "Image control statement STOP" }
40
  end do
41
  do concurrent ( i = 1 : 4)
42
    critical ! { dg-error "Image control statement CRITICAL at .1. in DO CONCURRENT block" }
43
      print *, i
44
!    end critical
45
  end do
46
 
47
  critical
48
    do concurrent ( i = 1 : 4) ! OK
49
    end do
50
  end critical
51
end
52
 
53
subroutine caf()
54
  use iso_fortran_env
55
  implicit none
56
  type(lock_type), allocatable :: lock[:]
57
  integer :: i
58
  do, concurrent (i = 1:3)
59
    allocate (lock[*]) ! { dg-error "ALLOCATE of coarray at .1. in DO CONCURRENT block" }
60
    lock(lock) ! { dg-error "Image control statement LOCK" }
61
    unlock(lock) ! { dg-error "Image control statement UNLOCK" }
62
    deallocate (lock) ! { dg-error "DEALLOCATE of coarray at .1. in DO CONCURRENT block" }
63
  end do
64
 
65
  critical
66
    allocate (lock[*]) ! { dg-error "ALLOCATE of coarray at .1. in CRITICAL block" }
67
    lock(lock) ! { dg-error "Image control statement LOCK" }
68
    unlock(lock) ! { dg-error "Image control statement UNLOCK" }
69
    deallocate (lock) ! { dg-error "DEALLOCATE of coarray at .1. in CRITICAL block" }
70
  end critical
71
end subroutine caf

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.