mirror of
https://gitlab.com/scemama/qp_plugins_scemama.git
synced 2024-11-07 14:43:41 +01:00
53 lines
2.2 KiB
Fortran
53 lines
2.2 KiB
Fortran
|
|
||
|
module gpu_module
|
||
|
use iso_c_binding
|
||
|
implicit none
|
||
|
|
||
|
interface
|
||
|
subroutine compute_r2_space_chol_gpu(nO,nV,cholesky_mo_num, &
|
||
|
t1,tau,cc_space_v_vo_chol,cc_space_v_vv_chol, r2) bind(C)
|
||
|
import c_int, c_double
|
||
|
integer(c_int), value :: nO, nV, cholesky_mo_num
|
||
|
real(c_double), intent(in) :: t1(nO,nV)
|
||
|
real(c_double), intent(in) :: tau(nO,nO,nV,nV)
|
||
|
real(c_double), intent(in) :: cc_space_v_vo_chol(cholesky_mo_num,nV,nO)
|
||
|
real(c_double), intent(in) :: cc_space_v_vv_chol(cholesky_mo_num,nV,nV)
|
||
|
real(c_double), intent(out) :: r2(nO,nO,nV,nV)
|
||
|
end subroutine
|
||
|
|
||
|
subroutine gemm0(nO, nV, cholesky_mo_num, cc_space_v_vo_chol, t1, tmp_cc) bind(C, name="gemm0")
|
||
|
import c_int, c_double
|
||
|
integer(c_int), value :: nO, nV, cholesky_mo_num
|
||
|
real(c_double) :: cc_space_v_vo_chol(cholesky_mo_num,nV,nO)
|
||
|
real(c_double) :: t1(nO,nV)
|
||
|
real(c_double) :: tmp_cc(cholesky_mo_num,nV,nV)
|
||
|
end subroutine gemm0
|
||
|
|
||
|
subroutine gemm1(iblock, nV, cholesky_mo_num, tmp_cc, cc_space_v_vv_chol_, tmpB1) bind(C, name="gemm1")
|
||
|
import c_int, c_double
|
||
|
integer(c_int), value :: iblock, nV, cholesky_mo_num
|
||
|
real(c_double) :: tmp_cc(cholesky_mo_num,nV,nV)
|
||
|
real(c_double) :: cc_space_v_vv_chol_(cholesky_mo_num,nV)
|
||
|
real(c_double) :: tmpB1(nV,16,nV)
|
||
|
end subroutine gemm1
|
||
|
|
||
|
subroutine gemm2(iblock, nV, cholesky_mo_num, tmp_cc2, cc_space_v_vv_chol, tmpB1) bind(C, name="gemm2")
|
||
|
import c_int, c_double
|
||
|
integer(c_int), value :: iblock, nV, cholesky_mo_num
|
||
|
real(c_double) :: tmp_cc2(cholesky_mo_num,nV)
|
||
|
real(c_double) :: cc_space_v_vv_chol(cholesky_mo_num,nV,nV)
|
||
|
real(c_double) :: tmpB1(nV,16,nV)
|
||
|
end subroutine gemm2
|
||
|
|
||
|
subroutine gemm3(iblock, nO, nV, gam, tau, B1, r2) bind(C, name="gemm3")
|
||
|
import c_int, c_double
|
||
|
integer(c_int), value :: iblock, nO, nV, gam
|
||
|
real(c_double) :: tau(nO,nO,nV,nV)
|
||
|
real(c_double) :: B1(nV,nV,*)
|
||
|
real(c_double) :: r2(nO,nO,nV,nV)
|
||
|
end subroutine gemm3
|
||
|
|
||
|
end interface
|
||
|
|
||
|
end module
|