File: distribute.f90

package info (click to toggle)
llvm-toolchain-19 1%3A19.1.7-3
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 1,998,520 kB
  • sloc: cpp: 6,951,680; ansic: 1,486,157; asm: 913,598; python: 232,024; f90: 80,126; objc: 75,281; lisp: 37,276; pascal: 16,990; sh: 10,009; ml: 5,058; perl: 4,724; awk: 3,523; makefile: 3,167; javascript: 2,504; xml: 892; fortran: 664; cs: 573
file content (114 lines) | stat: -rw-r--r-- 2,667 bytes parent folder | download | duplicates (7)
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
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
! REQUIRES: openmp_runtime

! RUN: %flang_fc1 -emit-hlfir %openmp_flags %s -o - | FileCheck %s

! CHECK-LABEL: func @_QPdistribute_simple
subroutine distribute_simple()
  ! CHECK: omp.teams
  !$omp teams

  ! CHECK: omp.distribute {
  !$omp distribute

  ! CHECK-NEXT: omp.loop_nest
  do i = 1, 10
    call foo()
    ! CHECK: omp.yield
  end do

  !$omp end distribute

  ! CHECK: omp.terminator
  !$omp end teams
end subroutine distribute_simple

!===============================================================================
! `dist_schedule` clause
!===============================================================================

! CHECK-LABEL: func @_QPdistribute_dist_schedule
! CHECK-SAME: %[[X_ARG:.*]]: !fir.ref<i32>
subroutine distribute_dist_schedule(x)
  ! CHECK: %[[X_REF:.*]]:2 = hlfir.declare %[[X_ARG]]
  integer, intent(in) :: x

  ! CHECK: omp.teams
  !$omp teams

  ! STATIC SCHEDULE, CONSTANT CHUNK SIZE

  ! CHECK: %[[CONST_CHUNK_SIZE:.*]] = arith.constant 5 : i32
  ! CHECK: omp.distribute
  ! CHECK-SAME: dist_schedule_static
  ! CHECK-SAME: chunk_size(%[[CONST_CHUNK_SIZE]] : i32)
  !$omp distribute dist_schedule(static, 5)

  ! CHECK-NEXT: omp.loop_nest
  do i = 1, 10
    call foo()
    ! CHECK: omp.yield
  end do

  !$omp end distribute

  ! STATIC SCHEDULE, VARIABLE CHUNK SIZE

  ! CHECK: %[[X:.*]] = fir.load %[[X_REF]]#0
  ! CHECK: omp.distribute
  ! CHECK-SAME: dist_schedule_static
  ! CHECK-SAME: chunk_size(%[[X]] : i32)
  !$omp distribute dist_schedule(static, x)

  ! CHECK-NEXT: omp.loop_nest
  do i = 1, 10
    call foo()
    ! CHECK: omp.yield
  end do

  !$omp end distribute

  ! STATIC SCHEDULE, NO CHUNK SIZE

  ! CHECK: omp.distribute
  ! CHECK-SAME: dist_schedule_static
  ! CHECK-NOT: chunk_size
  !$omp distribute dist_schedule(static)

  ! CHECK-NEXT: omp.loop_nest
  do i = 1, 10
    call foo()
    ! CHECK: omp.yield
  end do

  !$omp end distribute

  ! CHECK: omp.terminator
  !$omp end teams
end subroutine distribute_dist_schedule

!===============================================================================
! `allocate` clause
!===============================================================================

! CHECK-LABEL: func @_QPdistribute_allocate
subroutine distribute_allocate()
  use omp_lib
  integer :: x
  ! CHECK: omp.teams
  !$omp teams

  ! CHECK: omp.distribute
  ! CHECK-SAME: allocate(%{{.+}} : i64 -> %{{.+}} : !fir.ref<i32>)
  !$omp distribute allocate(omp_high_bw_mem_alloc: x) private(x)

  ! CHECK-NEXT: omp.loop_nest
  do i = 1, 10
    x = i
    ! CHECK: omp.yield 
  end do

  !$omp end distribute

  ! CHECK: omp.terminator
  !$omp end teams
end subroutine distribute_allocate