(git:ccc2433)
pw_fpga.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \note
10 !> This module contains routines necessary to operate on plane waves on INTEL
11 !> FPGAs using OpenCL. It depends at execution time on the board support
12 !> packages of the specific FPGA
13 !> \author Arjun Ramaswami
14 !> \author Robert Schade
15 ! **************************************************************************************************
16 
17 MODULE pw_fpga
18  USE iso_c_binding, ONLY: c_char,&
19  c_double_complex,&
20  c_float_complex,&
21  c_int,&
22  c_null_char
23  USE cp_files, ONLY: get_data_dir
24  USE kinds, ONLY: dp,&
25  sp
26 #include "../base/base_uses.f90"
27 
28  IMPLICIT NONE
29 
30  PRIVATE
31 
33  PUBLIC :: pw_fpga_init_bitstream
36 
37  INTERFACE
38 ! **************************************************************************************************
39 !> \brief Initialize FPGA
40 !> \retval status if the routine failed or not
41 ! **************************************************************************************************
42  FUNCTION pw_fpga_initialize() RESULT(stat) &
43  BIND(C, name="pw_fpga_initialize_")
44  IMPORT
45  INTEGER(KIND=C_INT) :: stat
46  END FUNCTION pw_fpga_initialize
47 
48 ! **************************************************************************************************
49 !> \brief Destroy FPGA
50 ! **************************************************************************************************
51  SUBROUTINE pw_fpga_final() &
52  BIND(C, name="pw_fpga_final_")
53  END SUBROUTINE pw_fpga_final
54 
55  END INTERFACE
56 
57  INTERFACE
58 ! **************************************************************************************************
59 !> \brief Check whether an fpga bitstream for the given FFT3d size is present & load binary if needed
60 !> \param data_path - path to the data directory
61 !> \param npts - fft3d size
62 !> \return res - true if fft3d size supported
63 ! **************************************************************************************************
64  FUNCTION pw_fpga_check_bitstream(data_path, n) RESULT(res) &
65  BIND(C, name="pw_fpga_check_bitstream_")
66  IMPORT
67  CHARACTER(KIND=C_CHAR) :: data_path(*)
68  INTEGER(KIND=C_INT) :: n(3)
69  INTEGER(KIND=C_INT) :: res
70  END FUNCTION pw_fpga_check_bitstream
71 
72  END INTERFACE
73 
74  INTERFACE
75 ! **************************************************************************************************
76 !> \brief single precision FFT3d using FPGA
77 !> \param dir - direction of FFT3d
78 !> \param npts - dimensions of FFT3d
79 !> \param single precision c_in...
80 ! **************************************************************************************************
81  SUBROUTINE pw_fpga_fft3d_sp(dir, n, c_in_sp) &
82  BIND(C, name="pw_fpga_fft3d_sp_")
83  IMPORT
84  INTEGER(KIND=C_INT), VALUE :: dir
85  INTEGER(KIND=C_INT) :: n(3)
86  COMPLEX(KIND=C_FLOAT_COMPLEX) :: c_in_sp(n(1), n(2), n(3))
87  END SUBROUTINE pw_fpga_fft3d_sp
88  END INTERFACE
89 
90  INTERFACE
91 ! **************************************************************************************************
92 !> \brief double precision FFT3d using FPGA
93 !> \param dir - direction of FFT3d
94 !> \param npts - dimensions of FFT3d
95 !> \param double precision c_in...
96 ! **************************************************************************************************
97  SUBROUTINE pw_fpga_fft3d_dp(dir, n, c_in_dp) &
98  BIND(C, name="pw_fpga_fft3d_dp_")
99  IMPORT
100  INTEGER(KIND=C_INT), VALUE :: dir
101  INTEGER(KIND=C_INT) :: n(3)
102  COMPLEX(KIND=C_DOUBLE_COMPLEX) :: c_in_dp(n(1), n(2), n(3))
103  END SUBROUTINE pw_fpga_fft3d_dp
104  END INTERFACE
105 
106 CONTAINS
107 
108 ! **************************************************************************************************
109 !> \brief Allocates resources on the fpga device
110 ! **************************************************************************************************
111  SUBROUTINE pw_fpga_init()
112 #if defined (__PW_FPGA)
113  INTEGER :: stat
114 
115 #if defined(__OFFLOAD) && !defined(__NO_OFFLOAD_PW)
116 #error "OFFLOAD and FPGA cannot be configured concurrently! Recompile with -D__NO_OFFLOAD_PW."
117  cpabort("OFFLOAD and FPGA cannot be configured concurrently! Recompile with -D__NO_OFFLOAD_PW.")
118 #endif
119  stat = pw_fpga_initialize()
120  IF (stat /= 0) &
121  cpabort("pw_fpga_init: failed")
122 #endif
123 
124 #if (__PW_FPGA_SP && !(__PW_FPGA))
125 #error "Define both __PW_FPGA_SP and __PW_FPGA"
126  cpabort("Define both __PW_FPGA_SP and __PW_FPGA")
127 #endif
128 
129  END SUBROUTINE pw_fpga_init
130 
131 ! **************************************************************************************************
132 !> \brief Releases resources on the fpga device
133 ! **************************************************************************************************
134  SUBROUTINE pw_fpga_finalize()
135 #if defined (__PW_FPGA)
136  CALL pw_fpga_final()
137 #endif
138  END SUBROUTINE pw_fpga_finalize
139 
140 ! **************************************************************************************************
141 !> \brief perform an in-place double precision fft3d on the FPGA
142 !> \param n ...
143 !> \param c_out ...
144 ! **************************************************************************************************
145  SUBROUTINE pw_fpga_r3dc1d_3d_dp(n, c_out)
146  INTEGER, DIMENSION(:), INTENT(IN) :: n
147  COMPLEX(KIND=dp), INTENT(INOUT) :: c_out(n(1), n(2), n(3))
148 
149 #if ! defined (__PW_FPGA)
150  mark_used(c_out)
151  mark_used(n)
152 #else
153  INTEGER :: handle3
154 
155  CHARACTER(len=*), PARAMETER :: routinex = 'fw_fft_fpga_r3dc1d_dp'
156 
157  CALL timeset(routinex, handle3)
158  CALL pw_fpga_fft3d_dp(+1, n, c_out)
159  CALL timestop(handle3)
160 
161 #endif
162  END SUBROUTINE
163 
164 ! **************************************************************************************************
165 !> \brief perform an in-place double precision inverse fft3d on the FPGA
166 !> \param n ...
167 !> \param c_out ...
168 ! **************************************************************************************************
169  SUBROUTINE pw_fpga_c1dr3d_3d_dp(n, c_out)
170  INTEGER, DIMENSION(:), INTENT(IN) :: n
171  COMPLEX(KIND=dp), INTENT(INOUT) :: c_out(n(1), n(2), n(3))
172 
173 #if ! defined (__PW_FPGA)
174  mark_used(c_out)
175  mark_used(n)
176 #else
177  INTEGER :: handle3
178 
179  CHARACTER(len=*), PARAMETER :: routinex = 'bw_fft_fpga_c1dr3d_dp'
180 
181  CALL timeset(routinex, handle3)
182  CALL pw_fpga_fft3d_dp(-1, n, c_out)
183  CALL timestop(handle3)
184 
185 #endif
186  END SUBROUTINE
187 
188 ! **************************************************************************************************
189 !> \brief perform an in-place single precision fft3d on the FPGA
190 !> \param n ...
191 !> \param c_out ...
192 ! **************************************************************************************************
193  SUBROUTINE pw_fpga_r3dc1d_3d_sp(n, c_out)
194  INTEGER, DIMENSION(:), INTENT(IN) :: n
195  COMPLEX(KIND=dp), INTENT(INOUT) :: c_out(n(1), n(2), n(3))
196 
197 #if ! defined (__PW_FPGA)
198  mark_used(c_out)
199  mark_used(n)
200 #else
201  COMPLEX, DIMENSION(:, :, :), POINTER :: c_in_sp
202  INTEGER :: handle3
203 
204  CHARACTER(len=*), PARAMETER :: routinex = 'fw_fft_fpga_r3dc1d_sp'
205 
206  ALLOCATE (c_in_sp(n(1), n(2), n(3)))
207  ! pointer to single precision complex array
208  c_in_sp = cmplx(c_out, kind=sp)
209 
210  CALL timeset(routinex, handle3)
211  CALL pw_fpga_fft3d_sp(+1, n, c_in_sp)
212  CALL timestop(handle3)
213 
214  ! typecast sp back to dp
215  !c_out = CMPLX(real(c_in_sp), 0.0_dp, KIND=dp)
216  c_out = cmplx(c_in_sp, kind=dp)
217 
218  DEALLOCATE (c_in_sp)
219 #endif
220  END SUBROUTINE
221 
222 ! **************************************************************************************************
223 !> \brief perform an in-place single precision inverse fft3d on the FPGA
224 !> \param n ...
225 !> \param c_out ...
226 ! **************************************************************************************************
227  SUBROUTINE pw_fpga_c1dr3d_3d_sp(n, c_out)
228  INTEGER, DIMENSION(:), INTENT(IN) :: n
229  COMPLEX(KIND=dp), INTENT(INOUT) :: c_out(n(1), n(2), n(3))
230 
231 #if ! defined (__PW_FPGA)
232  mark_used(c_out)
233  mark_used(n)
234 
235 #else
236  COMPLEX, DIMENSION(:, :, :), POINTER :: c_in_sp
237  INTEGER :: handle3
238 
239  CHARACTER(len=*), PARAMETER :: routinex = 'bw_fft_fpga_c1dr3d_sp'
240 
241  ALLOCATE (c_in_sp(n(1), n(2), n(3)))
242  ! pointer to single precision complex array
243  c_in_sp = cmplx(c_out, kind=sp)
244 
245  CALL timeset(routinex, handle3)
246  CALL pw_fpga_fft3d_sp(-1, n, c_in_sp)
247  CALL timestop(handle3)
248 
249  ! typecast sp back to dp
250  c_out = cmplx(c_in_sp, kind=dp)
251 
252  DEALLOCATE (c_in_sp)
253 #endif
254  END SUBROUTINE
255 
256 ! **************************************************************************************************
257 !> \brief Invoke the pw_fpga_check_bitstream C function passing the path to the data dir
258 !> \param n - fft3d size
259 !> \return ...
260 !> \retval res - true if fft size found and initialized else false
261 ! **************************************************************************************************
262  FUNCTION pw_fpga_init_bitstream(n) RESULT(res)
263  INTEGER, DIMENSION(:), INTENT(IN) :: n
264  INTEGER :: res
265 
266 #if ! defined (__PW_FPGA)
267  res = 0
268  mark_used(n)
269  mark_used(res)
270 #else
271  CHARACTER(len=100) :: data_path
272  INTEGER :: data_path_len
273 
274  data_path = trim(get_data_dir())//c_null_char
275  data_path_len = len_trim(data_path)
276 
277  res = pw_fpga_check_bitstream(data_path, n)
278 #endif
279  END FUNCTION
280 
281 END MODULE pw_fpga
282 
Utility routines to open and close files. Tracking of preconnections.
Definition: cp_files.F:16
character(len=default_path_length) function, public get_data_dir()
Returns path of data directory if set, otherwise an empty string.
Definition: cp_files.F:542
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public sp
Definition: kinds.F:33
subroutine, public pw_fpga_finalize()
Releases resources on the fpga device.
Definition: pw_fpga.F:135
integer function, public pw_fpga_init_bitstream(n)
Invoke the pw_fpga_check_bitstream C function passing the path to the data dir.
Definition: pw_fpga.F:263
subroutine, public pw_fpga_r3dc1d_3d_dp(n, c_out)
perform an in-place double precision fft3d on the FPGA
Definition: pw_fpga.F:146
subroutine, public pw_fpga_r3dc1d_3d_sp(n, c_out)
perform an in-place single precision fft3d on the FPGA
Definition: pw_fpga.F:194
subroutine, public pw_fpga_c1dr3d_3d_dp(n, c_out)
perform an in-place double precision inverse fft3d on the FPGA
Definition: pw_fpga.F:170
subroutine, public pw_fpga_c1dr3d_3d_sp(n, c_out)
perform an in-place single precision inverse fft3d on the FPGA
Definition: pw_fpga.F:228
subroutine, public pw_fpga_init()
Allocates resources on the fpga device.
Definition: pw_fpga.F:112