File: default-none.f90

package info (click to toggle)
llvm-toolchain-20 1%3A20.1.8-1~exp1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 2,111,388 kB
  • sloc: cpp: 7,438,767; ansic: 1,393,871; asm: 1,012,926; python: 241,728; f90: 86,635; objc: 75,411; lisp: 42,144; pascal: 17,286; sh: 10,027; ml: 5,082; perl: 4,730; awk: 3,523; makefile: 3,349; javascript: 2,251; xml: 892; fortran: 672
file content (60 lines) | stat: -rw-r--r-- 1,301 bytes parent folder | download
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
!RUN: %python %S/../test_errors.py %s %flang -fopenmp
! Positive tests for default(none)
subroutine sb2(x)
  real :: x
end subroutine

subroutine sb1
  integer :: i
  real :: a(10), b(10), k
  inc(x) = x + 1.0
  abstract interface
    function iface(a, b)
      real, intent(in) :: a, b
      real :: iface
    end function
  end interface
  procedure(iface) :: compute
  procedure(iface), pointer :: ptr => NULL()
  ptr => fn2
  !$omp parallel default(none) shared(a,b,k) private(i)
  do i = 1, 10
    b(i) = k + sin(a(i)) + inc(a(i)) + fn1(a(i)) + compute(a(i),k) + add(k, k)
    call sb3(b(i))
    call sb2(a(i))
  end do
  !$omp end parallel
contains
 function fn1(x)
   real :: x, fn1
   fn1 = x
 end function
 function fn2(x, y)
   real, intent(in) :: x, y
   real :: fn2
   fn2 = x + y
 end function
 subroutine sb3(x)
   real :: x
   print *, x
 end subroutine
end subroutine

!construct-name inside default(none)
subroutine sb4
  !$omp parallel default(none)
    loop: do i = 1, 10
    end do loop
  !$omp end parallel
end subroutine

! Test that default(none) does not error for assumed-size array
subroutine sub( aaa)
  real,dimension(*),intent(in)::aaa
  integer::ip
  real::ccc
!$omp parallel do private(ip,ccc) default(none)
  do ip = 1, 10
     ccc= aaa(ip)
  end do
end subroutine sub