aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/gomp/pr35786-1.f90
blob: ab72f066c49685cf299025d4dbdf06490aea22cb (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
! PR fortran/35786
! { dg-do compile }
! { dg-options "-fopenmp" }

module pr35768
  real, parameter :: one = 1.0
contains
  subroutine fn1
    !$omp parallel firstprivate (one)	! { dg-error "is not a variable" }
    !$omp end parallel
  end subroutine fn1
  subroutine fn2 (doit)
    external doit
    !$omp parallel firstprivate (doit)	! { dg-error "is not a variable" }
      call doit ()
    !$omp end parallel
  end subroutine fn2
  subroutine fn3
    interface fn4
      subroutine fn4 ()
      end subroutine fn4
    end interface
    !$omp parallel private (fn4)	! { dg-error "is not a variable" }
      call fn4 ()
    !$omp end parallel
  end subroutine fn3
  subroutine fn5
    interface fn6
      function fn6 ()
        integer :: fn6
      end function fn6
    end interface
    integer :: x
    !$omp parallel private (fn6, x)	! { dg-error "is not a variable" }
      x = fn6 ()
    !$omp end parallel
  end subroutine fn5
  function fn7 () result (re7)
    integer :: re7
    !$omp parallel private (fn7)	! { dg-error "is not a variable" }
    !$omp end parallel
  end function fn7
  function fn8 () result (re8)
    integer :: re8
    call fn9
  contains
    subroutine fn9
      !$omp parallel private (fn8)	! { dg-error "is not a variable" }
      !$omp end parallel
    end subroutine fn9
  end function fn8
  function fn10 () result (re10)
    integer :: re10, re11
    entry fn11 () result (re11)
    !$omp parallel private (fn10)	! { dg-error "is not a variable" }
    !$omp end parallel
    !$omp parallel private (fn11)	! { dg-error "is not a variable" }
    !$omp end parallel
  end function fn10
  function fn12 () result (re12)
    integer :: re12, re13
    entry fn13 () result (re13)
    call fn14
  contains
    subroutine fn14
      !$omp parallel private (fn12)	! { dg-error "is not a variable" }
      !$omp end parallel
      !$omp parallel private (fn13)	! { dg-error "is not a variable" }
      !$omp end parallel
    end subroutine fn14
  end function fn12
end module