Skip to content

Commit

Permalink
v_of_rho (in particular configuration) and and some more ffts ported …
Browse files Browse the repository at this point in the history
…to GPU. Also added some missing deallocations to PW cleanup.
  • Loading branch information
romerojosh committed Jun 26, 2017
1 parent dcd8d0e commit 9d25bf6
Show file tree
Hide file tree
Showing 7 changed files with 836 additions and 444 deletions.
8 changes: 7 additions & 1 deletion PW/src/clean_pw.f90
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ SUBROUTINE clean_pw( lflag )
eigts1_d, eigts2_d, eigts3_d
USE gvecs, ONLY : nls_d
USE wvfct, ONLY : g2kin_d, et_d, wg_d
USE us, ONLY : qrad_d
USE us, ONLY : qrad_d, tab_d, tab_d2y_d
#endif
IMPLICIT NONE
!
Expand Down Expand Up @@ -150,6 +150,9 @@ SUBROUTINE clean_pw( lflag )
IF ( ALLOCATED( vrs ) ) DEALLOCATE( vrs )
if (spline_ps) then
IF ( ALLOCATED( tab_d2y) ) DEALLOCATE( tab_d2y )
#ifdef USE_CUDA
IF ( ALLOCATED( tab_d2y_d) ) DEALLOCATE( tab_d2y_d )
#endif
endif
IF ( ALLOCATED( nls ) ) DEALLOCATE( nls )
IF ( ALLOCATED( nlsm ) ) DEALLOCATE( nlsm )
Expand Down Expand Up @@ -178,6 +181,9 @@ SUBROUTINE clean_pw( lflag )
IF ( ALLOCATED( qrad ) ) DEALLOCATE( qrad )
IF ( ALLOCATED( tab ) ) DEALLOCATE( tab )
IF ( ALLOCATED( tab_at ) ) DEALLOCATE( tab_at )
#ifdef USE_CUDA
IF ( ALLOCATED( tab_d ) ) DEALLOCATE( tab_d )
#endif
IF ( lspinorb ) THEN
IF ( ALLOCATED( fcoef ) ) DEALLOCATE( fcoef )
END IF
Expand Down
43 changes: 38 additions & 5 deletions PW/src/electrons.f90
Original file line number Diff line number Diff line change
Expand Up @@ -372,9 +372,10 @@ SUBROUTINE electrons_scf ( printout, exxen )
USE plugin_variables, ONLY : plugin_etot
!
#ifdef USE_CUDA
USE funct, ONLY : get_iexch, get_icorr, get_igcx, get_igcc
USE dfunct, ONLY : newd_gpu
USE cudafor
USE scf, ONLY : rho_core_d, rhog_core_d, vltot_d, vrs_d
USE scf, ONLY : rho_core_d, rhog_core_d, vltot_d, vrs_d
#endif
IMPLICIT NONE
!
Expand Down Expand Up @@ -402,7 +403,7 @@ SUBROUTINE electrons_scf ( printout, exxen )
LOGICAL :: &
first, exst
#ifdef USE_CUDA
INTEGER :: istat
INTEGER :: istat, iexch, icorr, igcx, igcc
#endif
!
! ... auxiliary variables for calculating and storing temporary copies of
Expand Down Expand Up @@ -649,9 +650,32 @@ SUBROUTINE electrons_scf ( printout, exxen )
ehart, etxc, vtxc, eth, etotefield, charge, v)
!CALL v_of_rho( rhoin, rho_core, rhog_core, &
! ehart, etxc, vtxc, eth, etotefield, charge, v)
#else
#ifdef USE_CUDA
iexch = get_iexch
icorr = get_icorr
igcx = get_igcx
igcc = get_igcc

! If calling PBE functional configuration, use GPU path
if (iexch .eq. 1 .and. icorr .eq. 4 .and. igcx .eq. 3 .and. igcc .eq. 4) then
rho_core_d = rho_core
rhog_core_d = rhog_core
v%of_r_d = v%of_r
rhoin%of_r_d = rhoin%of_r
rhoin%of_g_d = rhoin%of_g
CALL v_of_rho_gpu( rhoin, rho_core, rho_core_d, rhog_core, rhog_core_d,&
ehart, etxc, vtxc, eth, etotefield, charge, v)

! Otherwise, fallback to CPU path
else
CALL v_of_rho( rhoin, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v)
endif
#else
CALL v_of_rho( rhoin, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v)
#endif
#endif
IF (okpaw) THEN
CALL PAW_potential(rhoin%bec, ddd_paw, epaw,etot_cmp_paw)
Expand Down Expand Up @@ -708,15 +732,24 @@ SUBROUTINE electrons_scf ( printout, exxen )
!
! ... define the total local potential (external + scf)
!
#ifdef USE_CUDA
v%of_r_d = v%of_r
vltot_d = vltot
CALL sum_vrs_gpu( dfftp%nnr, nspin, vltot_d, v%of_r_d, vrs_d )
#else
CALL sum_vrs( dfftp%nnr, nspin, vltot, v%of_r, vrs )
#endif
!
! ... interpolate the total local potential
!
CALL interpolate_vrs( dfftp%nnr, nspin, doublegrid, kedtau, v%kin_r, vrs )
!
#ifdef USE_CUDA
vrs_d = vrs
CALL interpolate_vrs_gpu( dfftp%nnr, nspin, doublegrid, kedtau, v%kin_r, vrs_d)
vrs = vrs_d
#else
CALL interpolate_vrs( dfftp%nnr, nspin, doublegrid, kedtau, v%kin_r, vrs )
#endif
!vrs_d = vrs
!
! ... in the US case we have to recompute the self-consistent
! ... term in the nonlocal potential
! ... PAW: newd contains PAW updates of NL coefficients
Expand Down
Loading

0 comments on commit 9d25bf6

Please sign in to comment.