More rho-core cleanup: interpolation routines renamed and moved to upflib/

This commit is contained in:
Paolo Giannozzi 2023-06-09 16:53:10 +02:00
parent 4a82083944
commit 14485134d2
12 changed files with 19 additions and 19 deletions

View File

@ -55,7 +55,7 @@ SUBROUTINE dvpsi_kb(ik,nu)
mu = 3*(na-1)
IF ( u(mu+1,nu)**2+u(mu+2,nu)**2+u(mu+3,nu)**2> 1.0d-12) THEN
nt=ityp(na)
IF (upf(nt)%nlcc) CALL drhoc (nt, ngl, gl, tpiba2, rhocg )
IF (upf(nt)%nlcc) CALL interp_rhc (nt, ngl, gl, tpiba2, rhocg )
has_nlcc = has_nlcc .or. upf(nt)%nlcc
DO ng = 1,ngm
gtau = tpi * ( g(1,ng)*tau(1,na) + &

View File

@ -63,7 +63,7 @@ SUBROUTINE dynmatcc(dyncc)
DO na=1,nat
nta=ityp(na)
IF ( upf(nta)%nlcc ) THEN
CALL drhoc (nta, ngl, gl, tpiba2, rhocg)
CALL interp_rhc (nta, ngl, gl, tpiba2, rhocg)
DO ig=1,ngm
exg = tpi* ( g(1,ig)*tau(1,na) + &
g(2,ig)*tau(2,na) + &
@ -89,7 +89,7 @@ SUBROUTINE dynmatcc(dyncc)
DO nb=1,nat
ntb=ityp(nb)
IF ( upf(ntb)%nlcc ) THEN
CALL drhoc (ntb, ngl, gl, tpiba2, rhocg)
CALL interp_rhc (ntb, ngl, gl, tpiba2, rhocg)
DO ig=1,ngm
exg = tpi* ( g(1,ig)*tau(1,nb) + &
g(2,ig)*tau(2,nb) + &

View File

@ -49,7 +49,7 @@ subroutine set_drhoc (q, drc)
ALLOCATE ( rhc(ngm) )
do nt = 1, ntyp
if ( upf(nt)%nlcc ) then
call drhoc( nt, ngm, qg2, tpiba2, rhc )
call interp_rhc( nt, ngm, qg2, tpiba2, rhc )
drc (:,nt) = CMPLX(rhc(:), kind=dp)
else
drc (:,nt) = (0.0_dp, 0.0_dp)

View File

@ -44,11 +44,9 @@ set(src_pw
src/Coul_cut_2D.f90
src/d_matrix.f90
src/data_structure.f90
src/deriv_drhoc.f90
src/divide_class.f90
src/divide_class_so.f90
src/divide_et_impera.f90
src/drhoc.f90
src/rotate_wfc.f90
src/run_driver.f90
src/dvloc_of_g.f90

View File

@ -55,11 +55,9 @@ coset.o \
Coul_cut_2D.o \
d_matrix.o \
data_structure.o \
deriv_drhoc.o \
divide_class.o \
divide_class_so.o \
divide_et_impera.o \
drhoc.o \
rotate_wfc.o \
run_driver.o \
dvloc_of_g.o \

View File

@ -89,7 +89,7 @@ SUBROUTINE force_cc( forcecc )
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
!
CALL drhoc( nt, ngl, gl, tpiba2, rhocg )
CALL interp_rhc( nt, ngl, gl, tpiba2, rhocg )
!
#if !defined(_OPENACC)
!$omp parallel do private( tau1,tau2,tau3,forcecc_x,forcecc_y,forcecc_z,&

View File

@ -51,9 +51,9 @@ SUBROUTINE set_rhoc
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
!
! drhoc computes the radial fourier transform for each shell of g vec
! interp_rhc computes the radial fourier transform for each shell of g vec
!
CALL drhoc (nt, ngl, gl, tpiba2, rhocg)
CALL interp_rhc (nt, ngl, gl, tpiba2, rhocg)
!
! multiply by the structure factor and sum
!

View File

@ -87,7 +87,7 @@ SUBROUTINE stres_cc( sigmaxcc )
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
!
CALL drhoc( nt, ngl, gl, tpiba2, rhocg )
CALL interp_rhc( nt, ngl, gl, tpiba2, rhocg )
!
! ... diagonal term
IF (gstart==2) THEN
@ -104,7 +104,7 @@ SUBROUTINE stres_cc( sigmaxcc )
strf(ng,nt)) * rhocg(igtongl(ng)) * fact
ENDDO
!
CALL deriv_drhoc( nt, ngl, gl, tpiba2, rhocg )
CALL interp_drhc( nt, ngl, gl, tpiba2, rhocg )
!
! ... non diagonal term (g=0 contribution missing)
!

View File

@ -13,6 +13,8 @@ set(src_upflib
init_tab_rho.f90
init_tab_rhc.f90
interp_atwfc.f90
interp_rhc.f90
interp_drhc.f90
init_us_2_base.f90
gth.f90
paw_variables.f90

View File

@ -29,6 +29,8 @@ dqvan2.o \
dylmr2.o \
gth.o \
interp_atwfc.o \
interp_rhc.o \
interp_drhc.o \
paw_variables.o \
pseudo_types.o \
qvan2.o \

View File

@ -6,11 +6,11 @@
! or http://www.gnu.org/copyleft/gpl.txt .
!
!----------------------------------------------------------------------------
SUBROUTINE deriv_drhoc( nt, ngl, gl, tpiba2, drhocg )
SUBROUTINE interp_drhc( nt, ngl, gl, tpiba2, drhocg )
!--------------------------------------------------------------------------
!! Calculates the Fourier transform of \(d\text{Rho}_c/dG\).
!
USE kinds
USE upf_kinds, ONLY : dp
USE uspp_data, ONLY : tab_rhc, dq
!
IMPLICIT NONE
@ -56,5 +56,5 @@ SUBROUTINE deriv_drhoc( nt, ngl, gl, tpiba2, drhocg )
!
RETURN
!
END SUBROUTINE deriv_drhoc
END SUBROUTINE interp_drhc

View File

@ -7,11 +7,11 @@
!
!
!-----------------------------------------------------------------------
SUBROUTINE drhoc( nt, ngl, gl, tpiba2, rhocg )
SUBROUTINE interp_rhc( nt, ngl, gl, tpiba2, rhocg )
!-----------------------------------------------------------------------
!! Calculates the radial Fourier transform of the core charge.
!
USE kinds, ONLY : dp
USE upf_kinds, ONLY : dp
USE uspp_data, ONLY : tab_rhc, dq
!
IMPLICIT NONE
@ -55,4 +55,4 @@ SUBROUTINE drhoc( nt, ngl, gl, tpiba2, rhocg )
ENDDO
!$acc end data
!
END SUBROUTINE drhoc
END SUBROUTINE interp_rhc