diff --git a/CPV/src/cplib.f90 b/CPV/src/cplib.f90 index 3acff99f0..ef5625e01 100644 --- a/CPV/src/cplib.f90 +++ b/CPV/src/cplib.f90 @@ -1091,7 +1091,7 @@ subroutine nlinit use ions_base, ONLY : na, nsp use uspp, ONLY : aainit, beta, qq_nt, dvan, nhtol, nhtolm, indv,& dbeta - use uspp_param, ONLY : upf, lmaxq, nbetam, lmaxkb, nhm, nh, ish + use uspp_param, ONLY : upf, lmaxq, nbetam, lmaxkb, nhm, nh use atom, ONLY : rgrid use qgb_mod, ONLY : qgb, dqgb use smallbox_gvec, ONLY : ngb @@ -1511,7 +1511,7 @@ end subroutine dylmr2_ USE io_global, ONLY: stdout USE gvect, ONLY: gstart USE uspp, ONLY: nkb, qq_nt, indv_ijkb0 - USE uspp_param, ONLY: nh, ish, upf + USE uspp_param, ONLY: nh, upf USE mp, ONLY: mp_sum USE mp_global, ONLY: intra_bgrp_comm, nbgrp, inter_bgrp_comm USE cp_interfaces, ONLY: calbec diff --git a/CPV/src/cpr.f90 b/CPV/src/cpr.f90 index 9f8605563..47dae458f 100644 --- a/CPV/src/cpr.f90 +++ b/CPV/src/cpr.f90 @@ -22,7 +22,7 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out ) tfirst, tlast !moved here to make !autopilot work USE core, ONLY : rhoc - USE uspp_param, ONLY : nhm, nh, ish + USE uspp_param, ONLY : nhm, nh USE uspp, ONLY : nkb, vkb, vkb_d, becsum, deeq, okvan, nlcc_any USE energies, ONLY : eht, epseu, exc, etot, eself, enl, & ekin, atot, entropy, egrand, enthal, & diff --git a/CPV/src/pseudopot_sub.f90 b/CPV/src/pseudopot_sub.f90 index f42f4c634..aa1178d98 100644 --- a/CPV/src/pseudopot_sub.f90 +++ b/CPV/src/pseudopot_sub.f90 @@ -59,8 +59,7 @@ ityp ! the atomi specie for each atom use uspp, only: nkb, & ! nkbus ! - use uspp_param, only: ish, &! - upf, &! + use uspp_param, only: upf, &! lmaxkb, &! nhm, &! nbetam, &! @@ -91,7 +90,8 @@ ind = ind + 2 * upf(is)%lll( iv ) + 1 end do nh(is) = ind - ish(is)=nkb + ! next variable no longer used or existing + ! ish(is)=nkb nkb = nkb + na(is) * nh(is) if( upf(is)%tvanp ) nkbus = nkbus + na(is) * nh(is) end do @@ -476,7 +476,7 @@ USE kinds, ONLY : DP use io_global, only : stdout USE ions_base, ONLY : nsp - USE uspp_param, ONLY : upf, nh, nhm, nbetam, lmaxq, ish + USE uspp_param, ONLY : upf, nh, nhm, nbetam, lmaxq USE atom, ONLY : rgrid USE uspp, ONLY : indv USE betax, only : refg, qradx, mmx, dqradx @@ -611,7 +611,7 @@ use io_global, only: stdout USE ions_base, ONLY: nsp USE uspp_param, ONLY: upf, nh, nhm, nbetam, lmaxq - use uspp_param, only: lmaxkb, ish + use uspp_param, only: lmaxkb USE atom, ONLY: rgrid USE uspp, ONLY: indv use uspp, only: qq_nt, qq_nt_d, beta diff --git a/Modules/read_pseudo.f90 b/Modules/read_pseudo.f90 index 2dae6ced5..b01f491a0 100644 --- a/Modules/read_pseudo.f90 +++ b/Modules/read_pseudo.f90 @@ -18,7 +18,7 @@ MODULE read_pseudo_mod ! USE atom, ONLY: msh, rgrid USE ions_base, ONLY: zv - USE uspp_param, ONLY: upf, nvb + USE uspp_param, ONLY: upf USE uspp, ONLY: okvan, nlcc_any !! global variables modified on output ! @@ -36,8 +36,7 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp ) ! !! Reads PP files and puts the result into the "upf" structure of module uspp_param !! Sets DFT to input_dft if present, to the value read in PP files otherwise - !! Sets number of valence electrons Zv, control variables okvan and nlcc_any, - !! compatibility variable nvb + !! Sets number of valence electrons Zv, control variables okvan and nlcc_any !! Optionally returns cutoffs read from PP files into ecutwfc_pp, ecutrho_pp ! USE kinds, ONLY: DP @@ -232,7 +231,6 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp ) END IF ALLOCATE( rgrid( ntyp ), msh( ntyp ) ) ! - nvb = 0 DO nt = 1, ntyp ! CALL nullify_radial_grid( rgrid( nt ) ) @@ -259,10 +257,6 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp ) ! zv(nt) = upf(nt)%zp ! - ! ... count US species (obsolete?) - ! - IF (upf(nt)%tvanp) nvb=nvb+1 - ! ! check for zero atomic wfc, ! check that (occupied) atomic wfc are properly normalized ! @@ -302,7 +296,7 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp ) ! ! more initializations ! - okvan = ( nvb > 0 ) + okvan = ANY ( upf(1:ntyp)%tvanp ) nlcc_any = ANY ( upf(1:ntyp)%nlcc ) ! ! return cutoff read from PP file, if required diff --git a/upflib/make.depend b/upflib/make.depend index 91b289766..dd0202084 100644 --- a/upflib/make.depend +++ b/upflib/make.depend @@ -112,8 +112,6 @@ upf_auxtools.o : upf_kinds.o upf_const.o : upf_kinds.o upf_error.o : upf_parallel_include.o upf_invmat.o : upf_kinds.o -upf_ions.o : pseudo_types.o -upf_ions.o : upf_params.o upf_ions.o : uspp.o upf_spinorb.o : upf_kinds.o upf_spinorb.o : upf_params.o diff --git a/upflib/uspp.f90 b/upflib/uspp.f90 index 770de1f44..2a646de19 100644 --- a/upflib/uspp.f90 +++ b/upflib/uspp.f90 @@ -25,10 +25,11 @@ MODULE uspp_param INTEGER :: & lmaxkb, &! max angular momentum lmaxq ! max angular momentum + 1 for Q functions - INTEGER :: & - nvb, &! number of species with Vanderbilt PPs (CPV) - ish(npsx) ! for each specie the index of the first beta - ! function: ish(1)=1, ish(i)=1+SUM(nh(1:i-1)) +! INTEGER :: & +! nvb, &! number of species with Vanderbilt PPs (CPV) +! ish(npsx) ! for each specie the index of the first beta +! ! function: ish(1)=1, ish(i)=1+SUM(nh(1:i-1)) +! the two variables above are no longer used in CP END MODULE uspp_param !