diff --git a/FFTXlib/make.depend b/FFTXlib/make.depend index 779d75de6..445e64f80 100644 --- a/FFTXlib/make.depend +++ b/FFTXlib/make.depend @@ -75,3 +75,10 @@ scatter_mod.o : fft_types.o stick_base.o : fft_param.o tg_gather.o : fft_param.o tg_gather.o : fft_types.o +fft_stick.o : +fft_stick.o : +fftw.o : +fftw_dp.o : +fftw_dp.o : +fftw_sp.o : +fftw_sp.o : diff --git a/Modules/ions_base.f90 b/Modules/ions_base.f90 index 540eb088b..c46b85d98 100644 --- a/Modules/ions_base.f90 +++ b/Modules/ions_base.f90 @@ -11,6 +11,7 @@ USE kinds, ONLY : DP USE parameters, ONLY : ntypx + USE uspp_param, ONLY : nsp ! IMPLICIT NONE SAVE @@ -19,8 +20,6 @@ ! na(is) = number of atoms of species is ! nax = max number of atoms of a given species ! nat = total number of atoms of all species - - INTEGER :: nsp = 0 INTEGER :: na(ntypx) = 0 INTEGER :: nax = 0 INTEGER :: nat = 0 diff --git a/Modules/make.depend b/Modules/make.depend index fd8b38546..5cbc7f95c 100644 --- a/Modules/make.depend +++ b/Modules/make.depend @@ -164,6 +164,7 @@ io_files.o : kind.o io_files.o : mp_images.o io_files.o : parameters.o io_files.o : wrappers.o +ions_base.o : ../upflib/uspp.o ions_base.o : cell_base.o ions_base.o : constants.o ions_base.o : io_global.o diff --git a/PHonon/PH/make.depend b/PHonon/PH/make.depend index 52a8aeca5..f205cce56 100644 --- a/PHonon/PH/make.depend +++ b/PHonon/PH/make.depend @@ -1214,6 +1214,7 @@ phescf.o : phcom.o phescf.o : ramanm.o phescf.o : write_hub.o phonon.o : ../../Modules/check_stop.o +phonon.o : ../../Modules/control_flags.o phonon.o : ../../Modules/environment.o phonon.o : ../../Modules/mp_global.o phonon.o : ph_restart.o diff --git a/PW/src/Makefile b/PW/src/Makefile index 3e322c183..67c09cc10 100644 --- a/PW/src/Makefile +++ b/PW/src/Makefile @@ -122,8 +122,6 @@ hinit1.o \ init_ns.o \ init_q_aeps.o \ init_run.o \ -init_us_0.o \ -init_us_b0.o \ init_us_1.o \ init_us_2.o \ init_at_1.o \ diff --git a/PW/src/hinit0.f90 b/PW/src/hinit0.f90 index 4511ce2d5..ed5baeb93 100644 --- a/PW/src/hinit0.f90 +++ b/PW/src/hinit0.f90 @@ -17,7 +17,8 @@ SUBROUTINE hinit0() USE cell_base, ONLY : alat, at, bg, omega USE cellmd, ONLY : omega_old, at_old, lmovecell USE fft_base, ONLY : dfftp - USE gvect, ONLY : ngm, g, eigts1, eigts2, eigts3 + USE gvect, ONLY : ecutrho, ngm, g, eigts1, eigts2, eigts3 + USE gvecw, ONLY : ecutwfc USE vlocal, ONLY : strf USE realus, ONLY : generate_qpointlist, betapointlist, & init_realspace_vars, real_space @@ -25,6 +26,7 @@ SUBROUTINE hinit0() USE control_flags, ONLY : tqr, tq_smoothing, tbeta_smoothing, restart USE io_global, ONLY : stdout USE noncollin_module, ONLY : report + USE mp_bands, ONLY : intra_bgrp_comm ! IMPLICIT NONE REAL (dp) :: alat_old @@ -37,8 +39,8 @@ SUBROUTINE hinit0() ! ! ... k-point independent parameters of non-local pseudopotentials ! - IF (tbeta_smoothing) CALL init_us_b0() - IF (tq_smoothing) CALL init_us_0() + IF (tbeta_smoothing) CALL init_us_b0(ecutwfc,intra_bgrp_comm) + IF (tq_smoothing) CALL init_us_0(ecutrho,intra_bgrp_comm) CALL init_us_1() IF ( lda_plus_U .AND. ( U_projection == 'pseudo' ) ) CALL init_q_aeps() CALL init_at_1() diff --git a/PW/src/make.depend b/PW/src/make.depend index f6ea50515..9c73f22b5 100644 --- a/PW/src/make.depend +++ b/PW/src/make.depend @@ -942,9 +942,11 @@ h_psi_meta.o : scf_mod.o hinit0.o : ../../Modules/cell_base.o hinit0.o : ../../Modules/control_flags.o hinit0.o : ../../Modules/fft_base.o +hinit0.o : ../../Modules/gvecw.o hinit0.o : ../../Modules/io_global.o hinit0.o : ../../Modules/ions_base.o hinit0.o : ../../Modules/kind.o +hinit0.o : ../../Modules/mp_bands.o hinit0.o : ../../Modules/noncol.o hinit0.o : ../../Modules/recvec.o hinit0.o : atomic_wfc_mod.o @@ -1022,17 +1024,6 @@ init_run.o : newd.o init_run.o : paw_init.o init_run.o : pwcom.o init_run.o : symme.o -init_us_0.o : ../../Modules/cell_base.o -init_us_0.o : ../../Modules/constants.o -init_us_0.o : ../../Modules/io_global.o -init_us_0.o : ../../Modules/ions_base.o -init_us_0.o : ../../Modules/kind.o -init_us_0.o : ../../Modules/mp_bands.o -init_us_0.o : ../../Modules/recvec.o -init_us_0.o : ../../UtilXlib/mp.o -init_us_0.o : ../../upflib/atom.o -init_us_0.o : ../../upflib/uspp.o -init_us_0.o : pwcom.o init_us_1.o : ../../Modules/cell_base.o init_us_1.o : ../../Modules/constants.o init_us_1.o : ../../Modules/ions_base.o @@ -1054,16 +1045,6 @@ init_us_2.o : ../../upflib/gth.o init_us_2.o : ../../upflib/splinelib.o init_us_2.o : ../../upflib/uspp.o init_us_2.o : pwcom.o -init_us_b0.o : ../../Modules/constants.o -init_us_b0.o : ../../Modules/gvecw.o -init_us_b0.o : ../../Modules/io_global.o -init_us_b0.o : ../../Modules/ions_base.o -init_us_b0.o : ../../Modules/kind.o -init_us_b0.o : ../../Modules/mp_bands.o -init_us_b0.o : ../../UtilXlib/mp.o -init_us_b0.o : ../../upflib/atom.o -init_us_b0.o : ../../upflib/uspp.o -init_us_b0.o : pwcom.o init_vloc.o : ../../Modules/cell_base.o init_vloc.o : ../../Modules/ions_base.o init_vloc.o : ../../Modules/kind.o @@ -1749,6 +1730,7 @@ pw_restart_new.o : xdm_dispersion.o pwcom.o : ../../Modules/kind.o pwcom.o : ../../Modules/parameters.o pwcom.o : ../../upflib/upf_params.o +pwcom.o : ../../upflib/uspp_data.o pwscf.o : ../../Modules/command_line_options.o pwscf.o : ../../Modules/environment.o pwscf.o : ../../Modules/mp_global.o @@ -1781,6 +1763,7 @@ read_file_new.o : ../../Modules/io_files.o read_file_new.o : ../../Modules/io_global.o read_file_new.o : ../../Modules/ions_base.o read_file_new.o : ../../Modules/kind.o +read_file_new.o : ../../Modules/mp_bands.o read_file_new.o : ../../Modules/noncol.o read_file_new.o : ../../Modules/paw_variables.o read_file_new.o : ../../Modules/read_pseudo.o diff --git a/PW/src/pwcom.f90 b/PW/src/pwcom.f90 index 305249d4a..c31e6bf27 100644 --- a/PW/src/pwcom.f90 +++ b/PW/src/pwcom.f90 @@ -420,29 +420,7 @@ END MODULE cellmd ! ! MODULE us - ! - !! These parameters are needed with the US pseudopotentials. - ! - USE kinds, ONLY : DP - ! - SAVE - ! - INTEGER :: nqxq - !! size of interpolation table - INTEGER :: nqx - !! number of interpolation points - REAL(DP), PARAMETER:: dq = 0.01D0 - !! space between points in the pseudopotential tab. - REAL(DP), ALLOCATABLE :: qrad(:,:,:,:) - !! radial FT of Q functions - REAL(DP), ALLOCATABLE :: tab(:,:,:) - !! interpolation table for PPs - REAL(DP), ALLOCATABLE :: tab_at(:,:,:) - !! interpolation table for atomic wfc - LOGICAL :: spline_ps = .FALSE. - REAL(DP), ALLOCATABLE :: tab_d2y(:,:,:) - !! for cubic splines - ! + use uspp_data END MODULE us ! ! diff --git a/PW/src/read_file_new.f90 b/PW/src/read_file_new.f90 index 55336c03d..2f9aab5f4 100644 --- a/PW/src/read_file_new.f90 +++ b/PW/src/read_file_new.f90 @@ -141,9 +141,10 @@ SUBROUTINE post_xml_init ( ) USE Coul_cut_2D, ONLY : do_cutoff_2D, cutoff_fact USE ions_base, ONLY : nat, nsp, tau, ityp USE recvec_subs, ONLY : ggen, ggens - USE gvect, ONLY : gg, ngm, g, gcutm, mill, ngm_g, ig_l2g, & + USE gvect, ONLY : ecutrho, gg, ngm, g, gcutm, mill, ngm_g, ig_l2g, & eigts1, eigts2, eigts3, gstart, gshells USE gvecs, ONLY : ngms, gcutms + USE gvecw, ONLY : ecutwfc USE fft_rho, ONLY : rho_g2r USE fft_base, ONLY : dfftp, dffts USE scf, ONLY : rho, rho_core, rhog_core, v @@ -158,6 +159,7 @@ SUBROUTINE post_xml_init ( ) USE spin_orb, ONLY : lspinorb USE cell_base, ONLY : at, bg, set_h_ainv USE symm_base, ONLY : d1, d2, d3 + USE mp_bands, ONLY : intra_bgrp_comm USE realus, ONLY : betapointlist, generate_qpointlist, & init_realspace_vars,real_space ! @@ -224,8 +226,8 @@ SUBROUTINE post_xml_init ( ) ! ... the core correction charge (if any) - from hinit0.f90 ! CALL init_vloc() - IF (tbeta_smoothing) CALL init_us_b0() - IF (tq_smoothing) CALL init_us_0() + IF (tbeta_smoothing) CALL init_us_b0(ecutwfc,intra_bgrp_comm) + IF (tq_smoothing) CALL init_us_0(ecutrho,intra_bgrp_comm) CALL init_us_1() IF ( lda_plus_U .AND. ( U_projection == 'pseudo' ) ) CALL init_q_aeps() CALL init_at_1() diff --git a/TDDFPT/src/make.depend b/TDDFPT/src/make.depend index a7d727326..82c3495b5 100644 --- a/TDDFPT/src/make.depend +++ b/TDDFPT/src/make.depend @@ -262,6 +262,7 @@ lr_dvpsi_eels.o : lr_variables.o lr_eels_main.o : ../../LR_Modules/lrcom.o lr_eels_main.o : ../../Modules/check_stop.o lr_eels_main.o : ../../Modules/constants.o +lr_eels_main.o : ../../Modules/control_flags.o lr_eels_main.o : ../../Modules/environment.o lr_eels_main.o : ../../Modules/fft_base.o lr_eels_main.o : ../../Modules/io_files.o diff --git a/install/makedeps.sh b/install/makedeps.sh index 7e9b3686b..9b18cbdae 100755 --- a/install/makedeps.sh +++ b/install/makedeps.sh @@ -62,6 +62,8 @@ for dir in $dirs; do DEPEND3="$LEVEL2/include $LEVEL2/FFTXlib $LEVEL2/LAXlib $LEVEL2/UtilXlib" DEPEND2="$DEPEND3 $LEVEL2/upflib $LEVEL2/Modules" case $DIR in + upflib ) + DEPENDS="$LEVEL1/include $LEVEL1/UtilXlib" ;; Modules ) DEPENDS="$DEPEND1" ;; LR_Modules ) diff --git a/upflib/CMakeLists.txt b/upflib/CMakeLists.txt index a8567db59..f9a04c599 100644 --- a/upflib/CMakeLists.txt +++ b/upflib/CMakeLists.txt @@ -1,6 +1,8 @@ set(sources atom.f90 atomic_number.f90 + init_us_0.f90 + init_us_b0.f90 upf_erf.f90 upf_utils.f90 gth.f90 @@ -26,6 +28,7 @@ set(sources upf_parallel_include.f90 upf_to_internal.f90 uspp.f90 + uspp_data.f90 write_upf_new.f90 xmltools.f90 ylmr2.f90) diff --git a/upflib/Makefile b/upflib/Makefile index 88b308418..f54bca180 100644 --- a/upflib/Makefile +++ b/upflib/Makefile @@ -3,6 +3,7 @@ include ../make.inc QEMODS = libupf.a +MODFLAGS= $(MOD_FLAG)../UtilXlib # list of modules @@ -12,6 +13,8 @@ atomic_number.o \ upf_erf.o \ upf_utils.o \ gth.o \ +init_us_0.o \ +init_us_b0.o \ pseudo_types.o \ radial_grids.o \ read_cpmd.o \ @@ -34,6 +37,7 @@ upf_params.o \ upf_parallel_include.o \ upf_to_internal.o \ uspp.o \ +uspp_data.o \ write_upf_new.o \ xmltools.o \ ylmr2.o diff --git a/PW/src/init_us_0.f90 b/upflib/init_us_0.f90 similarity index 98% rename from PW/src/init_us_0.f90 rename to upflib/init_us_0.f90 index 334dafd1b..72fd94b27 100644 --- a/PW/src/init_us_0.f90 +++ b/upflib/init_us_0.f90 @@ -7,7 +7,7 @@ ! ! !----------------------------------------------------------------------------------- -SUBROUTINE init_us_0 +SUBROUTINE init_us_0(ecutrho,intra_bgrp_comm) !--------------------------------------------------------------------------------- !! This routine performs the following task: for each uspp or paw pseudopotential !! the l-dependent aumentation charge \(\text{ q_nb_mb_l}\)(r), stored in @@ -21,20 +21,19 @@ SUBROUTINE init_us_0 !! \[ \text{filter}(x,a,\text{nn}) = e^{-\text{axx}} \sum_{k=0,\text{nn}} !! \frac{\text{axx}^k}{k!}\ . \] ! - USE kinds, ONLY: DP - USE gvect, ONLY: ecutrho - USE io_global, ONLY: stdout - USE constants, ONLY: fpi, sqrt2, eps8, eps6 + USE upf_kinds, ONLY: DP + USE upf_io, ONLY: stdout + USE upf_const, ONLY: fpi, sqrt2, eps8, eps6 USE atom, ONLY: rgrid - USE ions_base, ONLY: ntyp => nsp - USE cell_base, ONLY: omega, tpiba - USE us, ONLY: dq - USE uspp_param, ONLY: upf, lmaxq, nbetam - USE mp_bands, ONLY: intra_bgrp_comm + USE uspp_data, ONLY: dq + USE uspp_param, ONLY: ntyp => nsp, upf, lmaxq, nbetam USE mp, ONLY: mp_sum ! IMPLICIT NONE ! + REAL(DP), INTENT(IN) :: ecutrho + INTEGER, INTENT(IN) :: intra_bgrp_comm + ! ! ... local variables ! ! sdg diff --git a/PW/src/init_us_b0.f90 b/upflib/init_us_b0.f90 similarity index 97% rename from PW/src/init_us_b0.f90 rename to upflib/init_us_b0.f90 index 6b71ac927..f5b9313e9 100644 --- a/PW/src/init_us_b0.f90 +++ b/upflib/init_us_b0.f90 @@ -6,23 +6,23 @@ ! or http://www.gnu.org/copyleft/gpl.txt . ! !---------------------------------------------------------------------- -SUBROUTINE init_us_b0 +SUBROUTINE init_us_b0(ecutwfc,intra_bgrp_comm) !---------------------------------------------------------------------- !! In this routine the beta_l(r) are smoothed. ! - USE kinds, ONLY : DP - USE gvecw, ONLY : ecutwfc - USE io_global, ONLY : stdout - USE constants, ONLY : fpi + USE upf_kinds, ONLY : DP + USE upf_io, ONLY : stdout + USE upf_const, ONLY : fpi USE atom, ONLY : rgrid - USE ions_base, ONLY : ntyp => nsp - USE us, ONLY : dq - USE uspp_param, ONLY : upf, nbetam - USE mp_bands, ONLY : intra_bgrp_comm + USE uspp_data, ONLY : dq + USE uspp_param, ONLY : ntyp => nsp, upf, nbetam USE mp, ONLY : mp_sum ! IMPLICIT NONE ! + REAL(DP), INTENT(IN) :: ecutwfc + INTEGER, INTENT(IN) :: intra_bgrp_comm + ! ! FILTER PARAMETERS: see REAL(DP) FUNCTION filter( x, a, n ) below for full definition and meaning. INTEGER :: nf ! Smoothing parameter, order of the polynomial in the inverse gaussian approximant. REAL(DP):: af ! Smoothing parameter, exponent of the gaussian decaying factor, to be chosen so that diff --git a/upflib/make.depend b/upflib/make.depend index 2ce6a55a7..5674130cc 100644 --- a/upflib/make.depend +++ b/upflib/make.depend @@ -9,6 +9,20 @@ gth.o : pseudo_types.o gth.o : upf_const.o gth.o : upf_kinds.o gth.o : upf_params.o +init_us_0.o : ../UtilXlib/mp.o +init_us_0.o : atom.o +init_us_0.o : upf_const.o +init_us_0.o : upf_io.o +init_us_0.o : upf_kinds.o +init_us_0.o : uspp.o +init_us_0.o : uspp_data.o +init_us_b0.o : ../UtilXlib/mp.o +init_us_b0.o : atom.o +init_us_b0.o : upf_const.o +init_us_b0.o : upf_io.o +init_us_b0.o : upf_kinds.o +init_us_b0.o : uspp.o +init_us_b0.o : uspp_data.o pseudo_types.o : upf_kinds.o radial_grids.o : upf_const.o radial_grids.o : upf_kinds.o @@ -70,6 +84,7 @@ uspp.o : upf_const.o uspp.o : upf_invmat.o uspp.o : upf_kinds.o uspp.o : upf_params.o +uspp_data.o : upf_kinds.o virtual_v2.o : pseudo_types.o virtual_v2.o : splinelib.o virtual_v2.o : upf.o diff --git a/upflib/upf_const.f90 b/upflib/upf_const.f90 index 586fb27f0..1b8f93e6a 100644 --- a/upflib/upf_const.f90 +++ b/upflib/upf_const.f90 @@ -22,6 +22,7 @@ MODULE upf_const REAL(DP), PARAMETER :: pi = 3.14159265358979323846_DP REAL(DP), PARAMETER :: tpi = 2.0_DP * pi REAL(DP), PARAMETER :: fpi = 4.0_DP * pi + REAL(DP), PARAMETER :: sqrt2 = 1.41421356237309504880_DP ! ! ... zero up to a given accuracy ! diff --git a/upflib/uspp.f90 b/upflib/uspp.f90 index 840944cf9..8b7ee25d5 100644 --- a/upflib/uspp.f90 +++ b/upflib/uspp.f90 @@ -16,6 +16,7 @@ MODULE uspp_param SAVE PRIVATE :: randy ! + INTEGER :: nsp ! actual number of species TYPE (pseudo_upf), ALLOCATABLE, TARGET :: upf(:) INTEGER :: &