18 USE iso_c_binding,
ONLY: c_char,&
26#include "../base/base_uses.f90"
42 FUNCTION pw_fpga_initialize()
RESULT(stat) &
43 BIND(C, name="pw_fpga_initialize_")
45 INTEGER(KIND=C_INT) :: stat
46 END FUNCTION pw_fpga_initialize
51 SUBROUTINE pw_fpga_final() &
52 BIND(C, name="pw_fpga_final_")
53 END SUBROUTINE pw_fpga_final
64 FUNCTION pw_fpga_check_bitstream(data_path, n)
RESULT(res) &
65 BIND(C, name="pw_fpga_check_bitstream_")
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
81 SUBROUTINE pw_fpga_fft3d_sp(dir, n, c_in_sp) &
82 BIND(C, name="pw_fpga_fft3d_sp_")
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
97 SUBROUTINE pw_fpga_fft3d_dp(dir, n, c_in_dp) &
98 BIND(C, name="pw_fpga_fft3d_dp_")
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
112#if defined (__PW_FPGA)
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.")
119 stat = pw_fpga_initialize()
121 cpabort(
"pw_fpga_init: failed")
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")
135#if defined (__PW_FPGA)
146 INTEGER,
DIMENSION(:),
INTENT(IN) :: n
147 COMPLEX(KIND=dp),
INTENT(INOUT) :: c_out(n(1), n(2), n(3))
149#if ! defined (__PW_FPGA)
155 CHARACTER(len=*),
PARAMETER :: routinex =
'fw_fft_fpga_r3dc1d_dp'
157 CALL timeset(routinex, handle3)
158 CALL pw_fpga_fft3d_dp(+1, n, c_out)
159 CALL timestop(handle3)
170 INTEGER,
DIMENSION(:),
INTENT(IN) :: n
171 COMPLEX(KIND=dp),
INTENT(INOUT) :: c_out(n(1), n(2), n(3))
173#if ! defined (__PW_FPGA)
179 CHARACTER(len=*),
PARAMETER :: routinex =
'bw_fft_fpga_c1dr3d_dp'
181 CALL timeset(routinex, handle3)
182 CALL pw_fpga_fft3d_dp(-1, n, c_out)
183 CALL timestop(handle3)
194 INTEGER,
DIMENSION(:),
INTENT(IN) :: n
195 COMPLEX(KIND=dp),
INTENT(INOUT) :: c_out(n(1), n(2), n(3))
197#if ! defined (__PW_FPGA)
201 COMPLEX,
DIMENSION(:, :, :),
POINTER :: c_in_sp
204 CHARACTER(len=*),
PARAMETER :: routinex =
'fw_fft_fpga_r3dc1d_sp'
206 ALLOCATE (c_in_sp(n(1), n(2), n(3)))
208 c_in_sp = cmplx(c_out, kind=
sp)
210 CALL timeset(routinex, handle3)
211 CALL pw_fpga_fft3d_sp(+1, n, c_in_sp)
212 CALL timestop(handle3)
216 c_out = cmplx(c_in_sp, kind=
dp)
228 INTEGER,
DIMENSION(:),
INTENT(IN) :: n
229 COMPLEX(KIND=dp),
INTENT(INOUT) :: c_out(n(1), n(2), n(3))
231#if ! defined (__PW_FPGA)
236 COMPLEX,
DIMENSION(:, :, :),
POINTER :: c_in_sp
239 CHARACTER(len=*),
PARAMETER :: routinex =
'bw_fft_fpga_c1dr3d_sp'
241 ALLOCATE (c_in_sp(n(1), n(2), n(3)))
243 c_in_sp = cmplx(c_out, kind=
sp)
245 CALL timeset(routinex, handle3)
246 CALL pw_fpga_fft3d_sp(-1, n, c_in_sp)
247 CALL timestop(handle3)
250 c_out = cmplx(c_in_sp, kind=
dp)
263 INTEGER,
DIMENSION(:),
INTENT(IN) :: n
266#if ! defined (__PW_FPGA)
271 CHARACTER(len=100) :: data_path
272 INTEGER :: data_path_len
275 data_path_len = len_trim(data_path)
277 res = pw_fpga_check_bitstream(data_path, n)
const char * get_data_dir()
Returns path of data directory if set, otherwise an empty string.
Utility routines to open and close files. Tracking of preconnections.
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public sp
subroutine, public pw_fpga_finalize()
Releases resources on the fpga device.
integer function, public pw_fpga_init_bitstream(n)
Invoke the pw_fpga_check_bitstream C function passing the path to the data dir.
subroutine, public pw_fpga_r3dc1d_3d_dp(n, c_out)
perform an in-place double precision fft3d on the FPGA
subroutine, public pw_fpga_r3dc1d_3d_sp(n, c_out)
perform an in-place single precision fft3d on the FPGA
subroutine, public pw_fpga_c1dr3d_3d_dp(n, c_out)
perform an in-place double precision inverse fft3d on the FPGA
subroutine, public pw_fpga_c1dr3d_3d_sp(n, c_out)
perform an in-place single precision inverse fft3d on the FPGA
subroutine, public pw_fpga_init()
Allocates resources on the fpga device.