Minor cleanup

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@7476 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2011-02-04 11:12:39 +00:00
parent 2994b9e093
commit 2b7d346620
8 changed files with 12 additions and 13 deletions

View File

@ -35,8 +35,7 @@
use gvect, only: gstart
use ions_base, only: na, nat, pmass, nax, nsp, rcmax
use grid_dimensions, only: nrxx, nr1, nr2, nr3
use cell_base, only: omega, alat
use cell_base, only: h, hold, deth, wmass, tpiba2
use cell_base, only: omega, alat, tpiba2
use smooth_grid_dimensions, only: nrxxs
use local_pseudo, only: vps, rhops
use io_global, ONLY : stdout, ionode, ionode_id

View File

@ -20,7 +20,7 @@ SUBROUTINE from_scratch( )
USE ions_nose, ONLY : xnhp0, xnhpm, vnhp
USE cell_base, ONLY : ainv, h, s_to_r, ibrav, omega, press, &
hold, r_to_s, deth, wmass, iforceh, &
cell_force, boxdimensions, velh, at, alat
cell_force, velh, at, alat
USE cell_nose, ONLY : xnhh0, xnhhm, vnhh
USE electrons_nose, ONLY : xnhe0, xnhem, vnhe
use electrons_base, ONLY : nbsp, f, nspin, nupdwn, iupdwn, nbsp_bgrp, nbspx_bgrp, nbspx

View File

@ -47,7 +47,6 @@
USE grid_dimensions, &
ONLY: nrxx, nr1, nr2, nr3
USE cell_base, ONLY: omega, alat
USE cell_base, ONLY: h, hold, deth, wmass
USE smooth_grid_dimensions, &
ONLY: nrxxs, nr1s, nr2s, nr3s
USE local_pseudo, ONLY: vps, rhops
@ -356,7 +355,6 @@
USE grid_dimensions, &
ONLY: nrxx, nr1, nr2, nr3
USE cell_base, ONLY: omega, alat
USE cell_base, ONLY: h, hold, deth, wmass
USE smooth_grid_dimensions, &
ONLY: nrxxs, nr1s, nr2s, nr3s
USE local_pseudo, ONLY: vps, rhops
@ -548,7 +546,6 @@
USE grid_dimensions, &
ONLY: nrxx, nr1, nr2, nr3
USE cell_base, ONLY: omega, alat
USE cell_base, ONLY: h, hold, deth, wmass
USE smooth_grid_dimensions, &
ONLY: nrxxs, nr1s, nr2s, nr3s
USE local_pseudo, ONLY: vps, rhops

View File

@ -1071,6 +1071,7 @@ MODULE input
USE cell_base, ONLY: frich
USE efield_module, ONLY: tefield, efield_info, tefield2, efield_info2
USE io_global, ONLY: meta_ionode, stdout
USE time_step, ONLY: delt
!
!
IMPLICIT NONE
@ -1139,7 +1140,7 @@ MODULE input
!
CALL cell_print_info( )
!
IF( thdyn .AND. tnoseh ) CALL cell_nose_info()
IF( thdyn .AND. tnoseh ) CALL cell_nose_info (delt)
!
! CALL sic_info() ! maybe useful
!

View File

@ -485,6 +485,7 @@ END SUBROUTINE diagonalize_parallel
CALL mp_max( diff, desc( la_comm_ ) )
IF( diff < ortho_eps ) EXIT ITERATIVE_LOOP
!
@ -1087,7 +1088,7 @@ END SUBROUTINE diagonalize_parallel
USE uspp, ONLY: nkb, nkbus
USE uspp_param, ONLY: nh, nvb, ish
USE gvecw, ONLY: ngw
USE control_flags, ONLY: iprint, iprsta
USE control_flags, ONLY: iprsta
USE mp, ONLY: mp_sum, mp_bcast
USE mp_global, ONLY: intra_bgrp_comm, leg_ortho, me_bgrp, inter_bgrp_comm
USE electrons_base, ONLY: nbspx_bgrp, ibgrp_g2l, nbsp, nspin, nupdwn, iupdwn, nbspx
@ -1300,7 +1301,7 @@ END SUBROUTINE diagonalize_parallel
USE gvecw, ONLY: ngw
USE electrons_base, ONLY: nbsp_bgrp, nbsp
USE constants, ONLY: pi, fpi
USE control_flags, ONLY: iprint, iprsta
USE control_flags, ONLY: iprsta
USE mp, ONLY: mp_sum
!
IMPLICIT NONE

View File

@ -736,7 +736,7 @@
USE kinds, ONLY: DP
USE constants, ONLY: fpi
USE control_flags, ONLY: gamma_only
USE cell_base, ONLY: tpiba2, boxdimensions
USE cell_base, ONLY: tpiba2
USE gvect, ONLY: ngm
USE gvect, ONLY: gstart, gg
USE sic_module, ONLY: sic_epsilon, sic_alpha

View File

@ -17,7 +17,7 @@ SUBROUTINE from_restart( )
USE electrons_base, ONLY : nspin, iupdwn, nupdwn, f, nbsp, nbsp_bgrp
USE io_global, ONLY : ionode, ionode_id, stdout
USE cell_base, ONLY : ainv, h, hold, deth, r_to_s, s_to_r, &
boxdimensions, velh, at, alat
velh, at, alat
USE ions_base, ONLY : na, nsp, iforce, vel_srt, nat, randpos
USE time_step, ONLY : tps, delt
USE ions_positions, ONLY : taus, tau0, tausm, taum, vels, fion, fionm, set_velocities

View File

@ -1012,15 +1012,16 @@ CONTAINS
end subroutine cell_nose_shiftvar
SUBROUTINE cell_nose_info()
SUBROUTINE cell_nose_info ( delt )
use constants, only: au_terahertz, pi
use time_step, only: delt
USE io_global, ONLY: stdout
USE control_flags, ONLY: tnoseh
IMPLICIT NONE
REAL(DP), INTENT (IN) :: delt
INTEGER :: nsvar
REAL(DP) :: wnoseh