More variable name harmonization

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@7249 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2010-11-23 17:03:37 +00:00
parent 7081f2311f
commit 60b15869c2
7 changed files with 30 additions and 31 deletions

View File

@ -1084,14 +1084,14 @@ end subroutine sort_gvec
!
!------------------------------------------------------------------------------!
SUBROUTINE ecutoffs_setup( ecutwfc, ecutrho, ecfixed, qcutz, q2sigma, &
SUBROUTINE ecutoffs_setup( ecutwfc, ecutrho_,ecfixed, qcutz, q2sigma, &
refg_ )
USE kinds, ONLY: DP
USE constants, ONLY: eps8
USE gvecw, ONLY: ecutw
USE gvecw, ONLY: ecfix, ecutz, ecsig
USE gvecp, ONLY: ecutp
USE gvecp, ONLY: ecutrho
USE gvecs, ONLY: ecuts, dual, doublegrid
use betax, only: mmx, refg
USE pseudopotential, only: tpstab
@ -1100,18 +1100,18 @@ end subroutine sort_gvec
USE uspp, only: okvan
IMPLICIT NONE
REAL(DP), INTENT(IN) :: ecutwfc, ecutrho, ecfixed, qcutz, q2sigma
REAL(DP), INTENT(IN) :: ecutwfc, ecutrho_, ecfixed, qcutz, q2sigma
REAL(DP), INTENT(IN) :: refg_
ecutw = ecutwfc
IF ( ecutrho <= 0.D0 ) THEN
IF ( ecutrho_ <= 0.D0 ) THEN
!
dual = 4.D0
!
ELSE
!
dual = ecutrho / ecutwfc
dual = ecutrho_ / ecutwfc
!
IF ( dual <= 1.D0 ) &
CALL errore( ' ecutoffs_setup ', ' invalid dual? ', 1 )
@ -1121,7 +1121,7 @@ end subroutine sort_gvec
doublegrid = ( dual > 4.D0 )
IF ( doublegrid .AND. .NOT. okvan ) &
CALL errore( 'setup', 'No USPP: set ecutrho=4*ecutwfc', 1 )
ecutp = dual * ecutwfc
ecutrho = dual * ecutwfc
!
IF ( doublegrid ) THEN
!
@ -1129,7 +1129,7 @@ end subroutine sort_gvec
!
ELSE
!
ecuts = ecutp
ecuts = ecutrho
!
END IF
@ -1148,12 +1148,12 @@ end subroutine sort_gvec
IF( thdyn ) THEN
! ... a larger table is used when cell is moving to allow
! ... large volume fluctuation
mmx = NINT( 2.0d0 * ecutp / refg )
mmx = NINT( 2.0d0 * ecutrho / refg )
ELSE
mmx = NINT( 1.2d0 * ecutp / refg )
mmx = NINT( 1.2d0 * ecutrho / refg )
END IF
mmx = NINT( 2.0d0 * ecutp / refg ) ! debug
mmx = NINT( 2.0d0 * ecutrho / refg ) ! debug
RETURN
END SUBROUTINE ecutoffs_setup
@ -1166,7 +1166,7 @@ end subroutine sort_gvec
USE kinds, ONLY: DP
USE gvecw, ONLY: ecutwfc => ecutw, gcutw
USE gvecp, ONLY: ecutrho => ecutp, gcutp
USE gvecp, ONLY: ecutrho, gcutm
USE gvecs, ONLY: ecuts, gcuts
USE gvecb, ONLY: ecutb, gcutb
USE gvecw, ONLY: ecfix, ecutz, ecsig
@ -1201,7 +1201,7 @@ end subroutine sort_gvec
! ... Constant cutoff simulation parameters
gcutw = ecutwfc / tpiba**2 ! wave function cut-off
gcutp = ecutrho / tpiba**2 ! potential cut-off
gcutm = ecutrho / tpiba**2 ! potential cut-off
gcuts = ecuts / tpiba**2 ! smooth mesh cut-off
kcut = 0.0_DP
@ -1228,7 +1228,7 @@ end subroutine sort_gvec
! Print out informations about different cut-offs
USE gvecw, ONLY: ecutwfc => ecutw, gcutw
USE gvecp, ONLY: ecutrho => ecutp, gcutp
USE gvecp, ONLY: ecutrho, gcutm
USE gvecw, ONLY: ecfix, ecutz, ecsig
USE gvecw, ONLY: ekcut, gkcut
USE gvecs, ONLY: ecuts, gcuts
@ -1236,7 +1236,7 @@ end subroutine sort_gvec
use betax, only: mmx, refg
USE io_global, ONLY: stdout
WRITE( stdout, 100 ) ecutwfc, ecutrho, ecuts, sqrt(gcutw), sqrt(gcutp), sqrt(gcuts)
WRITE( stdout, 100 ) ecutwfc, ecutrho, ecuts, sqrt(gcutw), sqrt(gcutm), sqrt(gcuts)
IF( ecutz > 0.0d0 ) THEN
WRITE( stdout, 150 ) ecutz, ecsig, ecfix
END IF
@ -1657,11 +1657,10 @@ SUBROUTINE gmeshinfo( )
USE io_global, ONLY: ionode, ionode_id, stdout
USE mp, ONLY: mp_max, mp_gather
use gvecb, only: ngb
USE reciprocal_vectors, only: ngst, ngs, ngsx, ngm, ngm_g, &
USE reciprocal_vectors, only: ngst, ngs, ngsx, ngm, ngm_g, ngmx,&
ngw_g => ngwt, &
ngw_l => ngw , &
ngw_lx => ngwx, &
ng_lx => ngmx
ngw_lx => ngwx
IMPLICIT NONE
@ -1677,7 +1676,7 @@ SUBROUTINE gmeshinfo( )
ng_snd(1) = ngm_g
ng_snd(2) = ngm
ng_snd(3) = ng_lx
ng_snd(3) = ngmx
CALL mp_gather(ng_snd, ng_rcv, ionode_id, intra_image_comm)
!
IF(ionode) THEN

View File

@ -57,7 +57,7 @@ MODULE cp_restart
USE grid_dimensions, ONLY : nr1, nr2, nr3, nr1x, nr2x, nr3l
USE smooth_grid_dimensions, ONLY : nr1s, nr2s, nr3s
USE smallbox_grid_dimensions, ONLY : nr1b, nr2b, nr3b
USE gvecp, ONLY : ngm, ngm_g, ecutp, gcutp
USE gvecp, ONLY : ngm, ngm_g
USE gvecs, ONLY : ngs, ngst, ecuts, gcuts, dual
USE gvecw, ONLY : ngw, ngwt, ecutw, gcutw
USE reciprocal_vectors, ONLY : ig_l2g, mill_l
@ -926,7 +926,7 @@ MODULE cp_restart
USE grid_dimensions, ONLY : nr1, nr2, nr3
USE smooth_grid_dimensions, ONLY : nr1s, nr2s, nr3s
USE smallbox_grid_dimensions, ONLY : nr1b, nr2b, nr3b
USE gvecp, ONLY : ngm, ecutp
USE gvecp, ONLY : ngm
USE gvecs, ONLY : ngs, ngst
USE gvecw, ONLY : ngw, ngwt, ecutw
USE electrons_base, ONLY : nspin, nbnd, nelt, nel, &

View File

@ -100,7 +100,7 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
USE cell_base, ONLY : cell_kinene, cell_gamma, &
cell_move, cell_hmove
USE gvecw, ONLY : ecutw
USE gvecp, ONLY : ecutp
USE gvecp, ONLY : ecutrho
USE time_step, ONLY : delt, tps, dt2, twodelt
USE cp_interfaces, ONLY : cp_print_rho, nlfh, print_lambda
USE cp_main_variables, ONLY : acc, bec, lambda, lambdam, lambdap, &
@ -856,7 +856,7 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
irb, ibrav, b1, b2, b3, taus, tausm, vels, &
velsm, acc, lambda, lambdam, xnhe0, xnhem, &
vnhe, xnhp0, xnhpm, vnhp, nhpcl, nhpdim, &
ekincm, xnhh0, xnhhm, vnhh, velh, ecutp, &
ekincm, xnhh0, xnhhm, vnhh, velh, ecutrho, &
ecutw, delt, celldm, fion, tps, z0t, f, rhor )
!
IF ( tstop ) EXIT main_loop

View File

@ -33,7 +33,7 @@
USE reciprocal_vectors, ONLY: mill_g, g2_g, bi1, bi2, bi3
USE recvecs_subroutines, ONLY: recvecs_init
use gvecw, only: gcutw, gkcut
use gvecp, only: ecut => ecutp, gcut => gcutp
use gvecp, only: ecutrho, gcutm
use gvecs, only: gcuts
use gvecb, only: gcutb
USE fft_base, ONLY: dfftp, dffts
@ -71,7 +71,7 @@
! ... Initialize (global) real and compute global reciprocal dimensions
!
CALL realspace_grids_init( alat, a1, a2, a3, gcut, gcuts, ng_ , ngs_ )
CALL realspace_grids_init( alat, a1, a2, a3, gcutm, gcuts, ng_ , ngs_ )
!
! ... cell dimensions and lattice vectors
@ -131,11 +131,11 @@ if( ionode ) then
!write(6,*) a1
!write(6,*) a2
!write(6,*) a3
!write(6,*) gcut, gkcut, gcut
!write(6,*)gcut, gkcut, gcut
!write(6,*) nr1, nr2, nr3, nr1x, nr2x, nr3x, nr1s, nr2s, nr3s, nr1sx, nr2sx, nr3sx, ngw_ , ngm_ , ngs_
end if
CALL pstickset( dfftp, dffts, alat, a1, a2, a3, gcut, gkcut, gcuts, &
CALL pstickset( dfftp, dffts, alat, a1, a2, a3, gcutm, gkcut, gcuts, &
nr1, nr2, nr3, nr1x, nr2x, nr3x, nr1s, nr2s, nr3s, nr1sx, nr2sx, &
nr3sx, ngw_ , ngm_ , ngs_ )
!
@ -154,7 +154,7 @@ end if
!
! ... generate g-space
!
call ggencp( b1, b2, b3, nr1, nr2, nr3, nr1s, nr2s, nr3s, gcut, gcuts, gkcut, gamma_only )
call ggencp( b1, b2, b3, nr1, nr2, nr3, nr1s, nr2s, nr3s, gcutm, gcuts, gkcut, gamma_only )
!
! Allocate index required to compute polarizability
@ -182,7 +182,7 @@ end if
! now set gcutb
gcutb = ecut / tpibab / tpibab
gcutb = ecutrho / tpibab / tpibab
!
CALL ggenb ( b1b, b2b, b3b, nr1b, nr2b, nr3b, nr1bx, nr2bx, nr3bx, gcutb )

View File

@ -54,7 +54,6 @@ SUBROUTINE init_run()
USE time_step, ONLY : dt2, delt, tps
USE electrons_nose, ONLY : xnhe0, xnhem, vnhe
USE cell_nose, ONLY : xnhh0, xnhhm, vnhh
USE gvecp, ONLY : ecutp
USE funct, ONLY : dft_is_meta
USE metagga, ONLY : crosstaus, dkedtaus, gradwfc
!

View File

@ -25,6 +25,7 @@ Fixed in CVS version:
* PW: corrected an old bug for Berry's phase finite electric field
calculations with non-orthorombic simulation cells. Also fixed
an old but minor bug on averaging of Berry phases between strings
* PW: problem with symmetrization in the noncollinear case
Fixed in version 4.2.1:

View File

@ -70,8 +70,8 @@
INTEGER :: ngl = 0 ! number of G-vector shells up to ngw
INTEGER :: ngmx = 0 ! maximum local number of G vectors
REAL(DP) :: ecutp = 0.0_DP
REAL(DP) :: gcutp = 0.0_DP
REAL(DP) :: ecutrho = 0.0_DP
REAL(DP) :: gcutm = 0.0_DP
!=----------------------------------------------------------------------------=!
END MODULE gvecp