Removal of unused variables

This commit is contained in:
Paolo Giannozzi 2021-02-26 13:09:35 +00:00
parent 28fe128488
commit 8cec26b2d9
6 changed files with 16 additions and 23 deletions

View File

@ -1091,7 +1091,7 @@ subroutine nlinit
use ions_base, ONLY : na, nsp use ions_base, ONLY : na, nsp
use uspp, ONLY : aainit, beta, qq_nt, dvan, nhtol, nhtolm, indv,& use uspp, ONLY : aainit, beta, qq_nt, dvan, nhtol, nhtolm, indv,&
dbeta 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 atom, ONLY : rgrid
use qgb_mod, ONLY : qgb, dqgb use qgb_mod, ONLY : qgb, dqgb
use smallbox_gvec, ONLY : ngb use smallbox_gvec, ONLY : ngb
@ -1511,7 +1511,7 @@ end subroutine dylmr2_
USE io_global, ONLY: stdout USE io_global, ONLY: stdout
USE gvect, ONLY: gstart USE gvect, ONLY: gstart
USE uspp, ONLY: nkb, qq_nt, indv_ijkb0 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, ONLY: mp_sum
USE mp_global, ONLY: intra_bgrp_comm, nbgrp, inter_bgrp_comm USE mp_global, ONLY: intra_bgrp_comm, nbgrp, inter_bgrp_comm
USE cp_interfaces, ONLY: calbec USE cp_interfaces, ONLY: calbec

View File

@ -22,7 +22,7 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
tfirst, tlast !moved here to make tfirst, tlast !moved here to make
!autopilot work !autopilot work
USE core, ONLY : rhoc 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 uspp, ONLY : nkb, vkb, vkb_d, becsum, deeq, okvan, nlcc_any
USE energies, ONLY : eht, epseu, exc, etot, eself, enl, & USE energies, ONLY : eht, epseu, exc, etot, eself, enl, &
ekin, atot, entropy, egrand, enthal, & ekin, atot, entropy, egrand, enthal, &

View File

@ -59,8 +59,7 @@
ityp ! the atomi specie for each atom ityp ! the atomi specie for each atom
use uspp, only: nkb, & ! use uspp, only: nkb, & !
nkbus ! nkbus !
use uspp_param, only: ish, &! use uspp_param, only: upf, &!
upf, &!
lmaxkb, &! lmaxkb, &!
nhm, &! nhm, &!
nbetam, &! nbetam, &!
@ -91,7 +90,8 @@
ind = ind + 2 * upf(is)%lll( iv ) + 1 ind = ind + 2 * upf(is)%lll( iv ) + 1
end do end do
nh(is) = ind nh(is) = ind
ish(is)=nkb ! next variable no longer used or existing
! ish(is)=nkb
nkb = nkb + na(is) * nh(is) nkb = nkb + na(is) * nh(is)
if( upf(is)%tvanp ) nkbus = nkbus + na(is) * nh(is) if( upf(is)%tvanp ) nkbus = nkbus + na(is) * nh(is)
end do end do
@ -476,7 +476,7 @@
USE kinds, ONLY : DP USE kinds, ONLY : DP
use io_global, only : stdout use io_global, only : stdout
USE ions_base, ONLY : nsp 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 atom, ONLY : rgrid
USE uspp, ONLY : indv USE uspp, ONLY : indv
USE betax, only : refg, qradx, mmx, dqradx USE betax, only : refg, qradx, mmx, dqradx
@ -611,7 +611,7 @@
use io_global, only: stdout use io_global, only: stdout
USE ions_base, ONLY: nsp USE ions_base, ONLY: nsp
USE uspp_param, ONLY: upf, nh, nhm, nbetam, lmaxq 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 atom, ONLY: rgrid
USE uspp, ONLY: indv USE uspp, ONLY: indv
use uspp, only: qq_nt, qq_nt_d, beta use uspp, only: qq_nt, qq_nt_d, beta

View File

@ -18,7 +18,7 @@ MODULE read_pseudo_mod
! !
USE atom, ONLY: msh, rgrid USE atom, ONLY: msh, rgrid
USE ions_base, ONLY: zv USE ions_base, ONLY: zv
USE uspp_param, ONLY: upf, nvb USE uspp_param, ONLY: upf
USE uspp, ONLY: okvan, nlcc_any USE uspp, ONLY: okvan, nlcc_any
!! global variables modified on output !! 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 !! 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 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, !! Sets number of valence electrons Zv, control variables okvan and nlcc_any
!! compatibility variable nvb
!! Optionally returns cutoffs read from PP files into ecutwfc_pp, ecutrho_pp !! Optionally returns cutoffs read from PP files into ecutwfc_pp, ecutrho_pp
! !
USE kinds, ONLY: DP USE kinds, ONLY: DP
@ -232,7 +231,6 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp )
END IF END IF
ALLOCATE( rgrid( ntyp ), msh( ntyp ) ) ALLOCATE( rgrid( ntyp ), msh( ntyp ) )
! !
nvb = 0
DO nt = 1, ntyp DO nt = 1, ntyp
! !
CALL nullify_radial_grid( rgrid( nt ) ) CALL nullify_radial_grid( rgrid( nt ) )
@ -259,10 +257,6 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp )
! !
zv(nt) = upf(nt)%zp zv(nt) = upf(nt)%zp
! !
! ... count US species (obsolete?)
!
IF (upf(nt)%tvanp) nvb=nvb+1
!
! check for zero atomic wfc, ! check for zero atomic wfc,
! check that (occupied) atomic wfc are properly normalized ! check that (occupied) atomic wfc are properly normalized
! !
@ -302,7 +296,7 @@ SUBROUTINE readpp ( input_dft, printout, ecutwfc_pp, ecutrho_pp )
! !
! more initializations ! more initializations
! !
okvan = ( nvb > 0 ) okvan = ANY ( upf(1:ntyp)%tvanp )
nlcc_any = ANY ( upf(1:ntyp)%nlcc ) nlcc_any = ANY ( upf(1:ntyp)%nlcc )
! !
! return cutoff read from PP file, if required ! return cutoff read from PP file, if required

View File

@ -112,8 +112,6 @@ upf_auxtools.o : upf_kinds.o
upf_const.o : upf_kinds.o upf_const.o : upf_kinds.o
upf_error.o : upf_parallel_include.o upf_error.o : upf_parallel_include.o
upf_invmat.o : upf_kinds.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_ions.o : uspp.o
upf_spinorb.o : upf_kinds.o upf_spinorb.o : upf_kinds.o
upf_spinorb.o : upf_params.o upf_spinorb.o : upf_params.o

View File

@ -25,10 +25,11 @@ MODULE uspp_param
INTEGER :: & INTEGER :: &
lmaxkb, &! max angular momentum lmaxkb, &! max angular momentum
lmaxq ! max angular momentum + 1 for Q functions lmaxq ! max angular momentum + 1 for Q functions
INTEGER :: & ! INTEGER :: &
nvb, &! number of species with Vanderbilt PPs (CPV) ! nvb, &! number of species with Vanderbilt PPs (CPV)
ish(npsx) ! for each specie the index of the first beta ! ish(npsx) ! for each specie the index of the first beta
! function: ish(1)=1, ish(i)=1+SUM(nh(1:i-1)) ! ! 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 END MODULE uspp_param
! !