1
0
mirror of https://gitlab.com/scemama/qp_plugins_scemama.git synced 2024-11-07 14:43:41 +01:00
qp_plugins_scemama/devel/ccsd_gpu/gpu_module.f90
2023-07-16 15:39:37 +02:00

29 lines
1013 B
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 gpu_dgemm(transa, transb, m, n, k, alpha, A, lda, B, ldb, beta, C, ldc) bind(C)
import c_int, c_double, c_char
character(c_char), value :: transa, transb
integer(c_int), value :: m,n,k,lda,ldb,ldc
real(c_double), value :: alpha, beta
real(c_double) :: A(lda,*), B(ldb,*), C(ldc,*)
end subroutine
end interface
end module