File: thread_util.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (143 lines) | stat: -rw-r--r-- 2,897 bytes parent folder | download | duplicates (3)
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
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
!
! Copyright (C) 2002-2018 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
! Utility functions to perform threaded memcpy and memset
! threaded_memXXX contains a parallel do region
! threaded_barrier_memXXX contains a do region without parallel
! threaded_nowait_memXXX contains a do region without parallel and a nowait at the end do
!
SUBROUTINE threaded_memcpy(array, array_in, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: array_in(length)
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp parallel do
  DO i=1, length
     array(i) = array_in(i)
  ENDDO
  !$omp end parallel do
  !
END SUBROUTINE threaded_memcpy

SUBROUTINE threaded_barrier_memcpy(array, array_in, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: array_in(length)
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp do
  DO i=1, length
     array(i) = array_in(i)
  ENDDO
  !$omp end do
  !
END SUBROUTINE threaded_barrier_memcpy

SUBROUTINE threaded_nowait_memcpy(array, array_in, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: array_in(length)
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp do
  DO i=1, length
     array(i) = array_in(i)
  ENDDO
  !$omp end do nowait
  !
END SUBROUTINE threaded_nowait_memcpy

SUBROUTINE threaded_memset(array, val, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: val
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp parallel do
  DO i=1, length
     array(i) = val
  ENDDO
  !$omp end parallel do
  !
END SUBROUTINE threaded_memset

SUBROUTINE threaded_barrier_memset(array, val, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: val
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp do
  DO i=1, length
     array(i) = val
  ENDDO
  !$omp end do
  !
END SUBROUTINE threaded_barrier_memset

SUBROUTINE threaded_nowait_memset(array, val, length)
  !
  USE util_param,   ONLY : DP
  !
  IMPLICIT NONE
  !
  INTEGER, INTENT(IN) :: length
  REAL(DP), INTENT(OUT) :: array(length)
  REAL(DP), INTENT(IN) :: val
  !
  INTEGER :: i
  !
  IF (length<=0) RETURN
  !
  !$omp do
  DO i=1, length
     array(i) = val
  ENDDO
  !$omp end do nowait
  !
END SUBROUTINE threaded_nowait_memset