Cleanup; newd_gpu renamed newd_acc

This commit is contained in:
Paolo Giannozzi 2025-04-28 19:18:34 +02:00
parent d4231da399
commit f84b29c3b6
10 changed files with 16 additions and 20 deletions

View File

@ -129,8 +129,6 @@ SUBROUTINE readxmlfile_vasp(iexch,icorr,igcx,igcc,inlc,ierr)
USE fft_rho, ONLY : rho_g2r
USE uspp, ONLY : becsum
USE uspp_param, ONLY : upf
USE paw_variables, ONLY : okpaw, ddd_PAW
USE paw_init, ONLY : paw_init_onecenter, allocate_paw_internals
USE control_flags, ONLY : gamma_only
USE funct, ONLY : get_inlc, get_dft_name
USE vdW_DF, ONLY : generate_kernel

View File

@ -142,7 +142,7 @@ SUBROUTINE electrons()
CALL v_of_rho( rho, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v)
IF (lrism) CALL rism_calc3d(rho%of_g(:, 1), esol, vsol, v%of_r, tr2)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_PAW, epaw,etot_cmp_paw)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_paw, epaw,etot_cmp_paw)
CALL set_vrs( vrs, vltot, v%of_r, kedtau, v%kin_r, dfftp%nnr, &
nspin, doublegrid )
!
@ -238,7 +238,7 @@ SUBROUTINE electrons()
!
IF (lrism) CALL rism_calc3d(rho%of_g(:, 1), esol, vsol, v%of_r, tr2)
!
IF (okpaw) CALL PAW_potential(rho%bec, ddd_PAW, epaw,etot_cmp_paw)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_paw, epaw,etot_cmp_paw)
CALL set_vrs( vrs, vltot, v%of_r, kedtau, v%kin_r, dfftp%nnr, &
nspin, doublegrid )
!
@ -446,7 +446,7 @@ SUBROUTINE electrons_scf ( printout, exxen )
USE paw_onecenter, ONLY : PAW_potential
USE paw_symmetry, ONLY : PAW_symmetrize_ddd
USE dfunct, ONLY : newd
USE dfunct_gpum, ONLY : newd_gpu
USE dfunct_gpum, ONLY : newd_acc
USE esm, ONLY : do_comp_esm, esm_printpot, esm_ewald
USE gcscf_module, ONLY : lgcscf, gcscf_mu, gcscf_ignore_mun, gcscf_set_nelec
USE clib_wrappers, ONLY : memstat
@ -990,7 +990,7 @@ SUBROUTINE electrons_scf ( printout, exxen )
! ... PAW: newd contains PAW updates of NL coefficients
!
IF (.not. use_gpu) CALL newd()
IF ( use_gpu) CALL newd_gpu()
IF ( use_gpu) CALL newd_acc()
!
IF ( lelfield ) en_el = calc_pol ( )
!

View File

@ -32,7 +32,7 @@ SUBROUTINE hinit1()
USE paw_onecenter, ONLY : paw_potential
USE paw_symmetry, ONLY : paw_symmetrize_ddd
USE dfunct, ONLY : newd
USE dfunct_gpum, ONLY : newd_gpu
USE dfunct_gpum, ONLY : newd_acc
USE exx_base, ONLY : coulomb_fac, coulomb_done
!
USE ener, ONLY : esol, vsol
@ -124,7 +124,7 @@ SUBROUTINE hinit1()
ENDIF
!
IF (.not. use_gpu) CALL newd()
IF ( use_gpu) CALL newd_gpu()
IF ( use_gpu) CALL newd_acc()
!
! ... and recalculate the products of the S with the atomic wfcs used
! ... in DFT+Hubbard calculations

View File

@ -45,7 +45,7 @@ SUBROUTINE init_run()
xclib_dft_is, xclib_set_finite_size_volume, &
dft_has_finite_size_correction
!
USE dfunct_gpum, ONLY : newd_gpu
USE dfunct_gpum, ONLY : newd_acc
USE rism_module, ONLY : lrism, rism_alloc3d
USE extffield, ONLY : init_extffield
USE control_flags, ONLY : scissor
@ -175,7 +175,7 @@ SUBROUTINE init_run()
!
IF ( use_gpu ) THEN
!
CALL newd_gpu()
CALL newd_acc()
!
ELSE
!

View File

@ -189,7 +189,7 @@ SUBROUTINE newq_acc(vr,deeq,skip_vltot)
END SUBROUTINE newq_acc
!
!----------------------------------------------------------------------------
SUBROUTINE newd_gpu( )
SUBROUTINE newd_acc( )
!----------------------------------------------------------------------------
!! This routine computes the integral of the effective potential with
!! the Q function and adds it to the bare ionic D term which is used
@ -509,6 +509,6 @@ SUBROUTINE newd_gpu( )
RETURN
END SUBROUTINE newd_nc_acc
!
END SUBROUTINE newd_gpu
END SUBROUTINE newd_acc
END MODULE dfunct_gpum

View File

@ -148,7 +148,7 @@ SUBROUTINE non_scf( )
IF (use_ace) CALL aceinit ( .false. )
CALL v_of_rho( rho, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_PAW, epaw,etot_cmp_paw)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_paw, epaw,etot_cmp_paw)
CALL set_vrs( vrs, vltot, v%of_r, kedtau, v%kin_r, dfftp%nnr, &
nspin, doublegrid )
!

View File

@ -51,7 +51,7 @@ SUBROUTINE potinit()
USE fft_rho, ONLY : rho_g2r, rho_r2g
!
USE uspp, ONLY : becsum
USE paw_variables, ONLY : okpaw, ddd_PAW
USE paw_variables, ONLY : okpaw, ddd_paw
USE paw_init, ONLY : PAW_atomic_becsum
USE paw_onecenter, ONLY : PAW_potential
!
@ -269,7 +269,7 @@ SUBROUTINE potinit()
!
CALL v_of_rho( rho, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v )
IF (okpaw) CALL PAW_potential(rho%bec, ddd_PAW, epaw)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_paw, epaw)
!
! ... calculate 3D-RISM to get the solvation potential
!

View File

@ -227,7 +227,7 @@ SUBROUTINE post_xml_init ( )
USE uspp_param, ONLY : upf, nhm, nsp
USE read_pseudo_mod, ONLY : readpp
USE uspp, ONLY : becsum, allocate_uspp
USE paw_variables, ONLY : okpaw, ddd_PAW
USE paw_variables, ONLY : okpaw, ddd_paw
USE paw_init, ONLY : paw_init_onecenter, allocate_paw_internals
USE paw_onecenter, ONLY : paw_potential
USE dfunct, ONLY : newd
@ -412,7 +412,7 @@ SUBROUTINE post_xml_init ( )
!
IF (okpaw) THEN
becsum = rho%bec
CALL PAW_potential(rho%bec, ddd_PAW)
CALL PAW_potential(rho%bec, ddd_paw)
ENDIF
CALL newd()
!

View File

@ -592,7 +592,7 @@ SUBROUTINE extrapolate_charge( dirname, rho_extr )
!
CALL v_of_rho( rho, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v )
IF (okpaw) CALL PAW_potential(rho%bec, ddd_PAW, epaw)
IF (okpaw) CALL PAW_potential(rho%bec, ddd_paw, epaw)
!
IF ( ABS( charge - nelec ) / charge > 1.D-7 ) THEN
!

View File

@ -34,8 +34,6 @@ SUBROUTINE do_cond(done)
USE mp_global, ONLY : mp_startup
USE mp_pools, ONLY : npool
USE mp_images, ONLY : intra_image_comm, nproc_image
USE paw_onecenter, ONLY : PAW_potential
USE paw_variables, ONLY : okpaw, ddd_PAW
USE mp
USE environment, ONLY : environment_start