Cleanup of fixed parameters - only a few remains in parameters.f90.

The others have been either removed or moved to where they belong


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@5436 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2009-02-19 09:49:49 +00:00
parent 8fa987f651
commit e68f2c9d6f
17 changed files with 33 additions and 72 deletions

View File

@ -70,7 +70,6 @@ MODULE cp_restart
epseu, enl, exc, vave
USE mp_global, ONLY : nproc, mpime
USE mp, ONLY : mp_sum
USE parameters, ONLY : nhclm
USE fft_base, ONLY : dfftp
USE constants, ONLY : pi
USE cp_interfaces, ONLY : n_atom_wfc
@ -916,7 +915,7 @@ MODULE cp_restart
USE cp_main_variables, ONLY : nprint_nfi, distribute_lambda, descla, distribute_zmat
USE mp, ONLY : mp_sum
USE mp_global, ONLY : intra_image_comm
USE parameters, ONLY : nhclm, ntypx
USE parameters, ONLY : ntypx
USE constants, ONLY : eps8, angstrom_au, pi
!
IMPLICIT NONE

View File

@ -977,7 +977,6 @@ END FUNCTION
USE uspp, ONLY: deeq
USE cvan, ONLY: nvb
USE ions_base, ONLY: nat, nsp, na
USE parameters, ONLY: nsx
USE constants, ONLY: pi, fpi
USE grid_dimensions, ONLY: nr3, nnr => nnrx
USE gvecb, ONLY: ngb, npb, nmb, gxb
@ -1002,7 +1001,7 @@ END FUNCTION
REAL(DP) fion(3,nat)
! local
INTEGER isup,isdw,iss, iv,ijv,jv, ik, nfft, isa, ia, is, ig
REAL(DP) fvan(3,nat,nsx), fac, fac1, fac2, boxdotgrid
REAL(DP) fvan(3,nat,nvb), fac, fac1, fac2, boxdotgrid
COMPLEX(DP) ci, facg1, facg2
COMPLEX(DP), ALLOCATABLE :: qv(:)
EXTERNAL boxdotgrid
@ -2476,7 +2475,6 @@ end function set_Hubbard_l
!
use control_flags, ONLY: tfor, tprnfor
use kinds, ONLY: DP
use parameters, ONLY: nsx
use ions_base, only: na, nat, nsp
use gvecw, only: ngw
use reciprocal_vectors, only: ng0 => gstart

View File

@ -1,5 +1,5 @@
!
! Copyright (C) 2002-2005 FPMD-CPV groups
! Copyright (C) 2002-2009 Quantum-ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
@ -10,14 +10,11 @@
!=----------------------------------------------------------------------------=!
#include "f_defs.h"
USE kinds
USE parameters, ONLY: nspinx
USE dspev_module, ONLY: pdspev_drv, dspev_drv
USE electrons_base, ONLY: nbnd, nbndx, nbsp, nbspx, nspin, nel, nelt, &
nupdwn, iupdwn, telectrons_base_initval, f, &
nudx
USE cp_electronic_mass, ONLY: ecutmass => emass_cutoff
USE cp_electronic_mass, ONLY: emass
USE cp_electronic_mass, ONLY: emass_precond
USE cp_electronic_mass, ONLY: ecutmass => emass_cutoff, emass, emass_precond
IMPLICIT NONE
@ -27,6 +24,7 @@
! ... declare module-scope variables
INTEGER, PARAMETER :: nspinx = 2
LOGICAL :: band_first = .TRUE.
INTEGER :: n_emp = 0 ! number of empty states

View File

@ -40,7 +40,6 @@ SUBROUTINE init_run()
USE ensemble_dft, ONLY : tens, z0t
USE cg_module, ONLY : tcg
USE electrons_base, ONLY : nudx, nbnd
USE parameters, ONLY : nspinx
USE efield_module, ONLY : tefield, tefield2
USE uspp_param, ONLY : nhm
USE ions_nose, ONLY : xnhp0, xnhpm, vnhp, nhpcl, nhpdim
@ -84,8 +83,7 @@ SUBROUTINE init_run()
!
IMPLICIT NONE
!
INTEGER :: neupdwn( nspinx )
INTEGER :: lds_wfc, i
INTEGER :: i
CHARACTER(LEN=256) :: dirname
!
!

View File

@ -97,7 +97,6 @@ MODULE input
USE input_parameters, ONLY : atom_pfile, pseudo_dir, ntyp, nat, &
prefix, outdir, xc_type
USE control_flags, ONLY : program_name
USE parameters, ONLY : nsx
USE read_pseudo_module_fpmd, ONLY : readpp
USE io_files, ONLY : psfile_ => psfile , &
pseudo_dir_ => pseudo_dir, &

View File

@ -58,7 +58,6 @@ SUBROUTINE cpmain_x( tau, fion, etot )
! ... declare modules
USE kinds
USE parameters, ONLY: nacx, nspinx
USE control_flags, ONLY: tbeg, nomore, tprnfor, tpre, &
nbeg, newnfi, tnewnfi, isave, iprint, tv0rd, nv0rd, tzeroc, tzerop, &
tfor, thdyn, tzeroe, tsde, tsdp, tsdc, taurdr, ndr, &

View File

@ -12,7 +12,6 @@ MODULE cp_main_variables
!----------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE parameters, ONLY : nsx, nacx
USE control_flags, ONLY : program_name
USE funct, ONLY : dft_is_meta
USE metagga, ONLY : kedtaur, kedtaus, kedtaug
@ -74,6 +73,8 @@ MODULE cp_main_variables
INTEGER :: nrlx = 0 ! leading dimension of the distribute (by row ) lambda matrix
LOGICAL :: la_proc = .FALSE. ! indicate if a proc own a block of lambda
!
INTEGER, PARAMETER :: nacx = 10 ! max number of averaged
! quantities saved to the restart
REAL(DP) :: acc(nacx)
REAL(DP) :: acc_this_run(nacx)
!
@ -201,7 +202,7 @@ MODULE cp_main_variables
allocate(rho_gaus(nnr))
allocate(v_vol(nnr))
if (jellium.or.t_gauss) allocate(posv(3,nr1*nr2*nr3))
if (t_gauss) allocate(f_vol(3,nax,nsx))
if (t_gauss) allocate(f_vol(3,nax,nsp))
!
end if
!

View File

@ -217,7 +217,6 @@ cplib.o : ../Modules/ions_base.o
cplib.o : ../Modules/kind.o
cplib.o : ../Modules/mp.o
cplib.o : ../Modules/mp_global.o
cplib.o : ../Modules/parameters.o
cplib.o : ../Modules/recvec.o
cplib.o : ../Modules/sic.o
cplib.o : ../Modules/smallbox.o
@ -369,7 +368,6 @@ electrons.o : ../Modules/electrons_base.o
electrons.o : ../Modules/io_global.o
electrons.o : ../Modules/kind.o
electrons.o : ../Modules/mp_global.o
electrons.o : ../Modules/parameters.o
electrons.o : cp_emass.o
emptystates.o : ../Modules/cell_base.o
emptystates.o : ../Modules/check_stop.o
@ -529,7 +527,6 @@ init_run.o : ../Modules/io_global.o
init_run.o : ../Modules/ions_base.o
init_run.o : ../Modules/ions_nose.o
init_run.o : ../Modules/kind.o
init_run.o : ../Modules/parameters.o
init_run.o : ../Modules/printout_base.o
init_run.o : ../Modules/recvec.o
init_run.o : ../Modules/timestep.o
@ -602,7 +599,6 @@ input.o : ../Modules/ions_base.o
input.o : ../Modules/ions_nose.o
input.o : ../Modules/kind.o
input.o : ../Modules/metadyn_vars.o
input.o : ../Modules/parameters.o
input.o : ../Modules/printout_base.o
input.o : ../Modules/read_cards.o
input.o : ../Modules/read_namelists.o
@ -653,7 +649,6 @@ main.o : ../Modules/io_global.o
main.o : ../Modules/ions_base.o
main.o : ../Modules/ions_nose.o
main.o : ../Modules/kind.o
main.o : ../Modules/parameters.o
main.o : ../Modules/printout_base.o
main.o : ../Modules/recvec.o
main.o : ../Modules/sic.o
@ -690,7 +685,6 @@ mainvar.o : ../Modules/functionals.o
mainvar.o : ../Modules/kind.o
mainvar.o : ../Modules/mp.o
mainvar.o : ../Modules/mp_global.o
mainvar.o : ../Modules/parameters.o
mainvar.o : modules.o
mainvar.o : pres_ai_mod.o
mainvar.o : wave_types.o
@ -742,7 +736,6 @@ nlcc.o : ../Modules/ions_base.o
nlcc.o : ../Modules/kind.o
nlcc.o : ../Modules/mp.o
nlcc.o : ../Modules/mp_global.o
nlcc.o : ../Modules/parameters.o
nlcc.o : ../Modules/recvec.o
nlcc.o : ../Modules/smallbox.o
nlcc.o : ../Modules/uspp.o
@ -1084,7 +1077,6 @@ wave.o : ../Modules/recvec.o
wave.o : ../Modules/wave_base.o
wave.o : electrons.o
wave_types.o : ../Modules/kind.o
wave_types.o : ../Modules/parameters.o
waveinit.o : ../Modules/kind.o
wf.o : ../Modules/cell_base.o
wf.o : ../Modules/constants.o

View File

@ -348,7 +348,6 @@
use grid_dimensions, only: nr1, nr2, nr3, nnr => nnrx
use cell_base, only: omega
use ions_base, only: nsp, na, nat
use parameters, only: nsx
use small_box, only: tpibab
use uspp_param, only: upf
use core, only: rhocb
@ -452,7 +451,6 @@
! Same logic as for rhov: use box grid for core charges
!
use ions_base, only: nsp, na, nat
use parameters, only: nsx
use uspp_param, only: upf
use grid_dimensions, only: nr3, nnr => nnrx
use gvecb, only: ngb, npb, nmb

View File

@ -17,7 +17,6 @@
USE kinds
USE parameters, ONLY: nspinx
IMPLICIT NONE
PRIVATE
SAVE
@ -34,8 +33,8 @@
INTEGER :: ngwl ! local number of pw
INTEGER :: ngwt ! global number of pw
INTEGER :: nbl( nspinx ) ! local number of bands
INTEGER :: nbt( nspinx ) ! global number of bands
INTEGER :: nbl( 2 ) ! local number of bands
INTEGER :: nbt( 2 ) ! global number of bands
INTEGER :: nkl ! local number of k-points
INTEGER :: nkt ! global number of k-points

View File

@ -25,7 +25,7 @@ MODULE input_parameters
!=----------------------------------------------------------------------------=!
!
USE kinds, ONLY : DP
USE parameters, ONLY : nsx, npkx, nspinx, lqmax, nhclm, max_nconstr
USE parameters, ONLY : nsx, npk, lqmax
USE wannier_new,ONLY : wannier_data
!
IMPLICIT NONE
@ -465,7 +465,7 @@ MODULE input_parameters
LOGICAL :: lda_plus_u = .FALSE.
! ONLY PWSCF
INTEGER, PARAMETER :: nspinx=2
REAL(DP) :: starting_ns_eigenvalue(lqmax,nspinx,nsx) = -1.0_DP
! ONLY PWSCF
@ -1076,10 +1076,13 @@ MODULE input_parameters
! value of the ionic temperature (in Kelvin) forced
! by the temperature control
INTEGER, PARAMETER :: nhclm = 4
REAL(DP) :: fnosep( nhclm ) = 50.0_DP
! meaningful only with "ion_temperature = 'nose' "
! oscillation frequency of the nose thermostat (in terahertz)
! nhclm is a max length for the chain
! nhclm is the max length for the chain; it can be easily increased
! since the restart file should be able to handle it
! perhaps better to align nhclm by 4
INTEGER :: nhpcl = 0
! non-zero only with "ion_temperature = 'nose' "
@ -1215,7 +1218,7 @@ MODULE input_parameters
!
! ... variable for meta-dynamics
!
INTEGER, PARAMETER :: max_nconstr = 100
INTEGER :: fe_nstep = 100
INTEGER :: sw_nstep = 10
INTEGER :: eq_nstep = 0
@ -1491,7 +1494,7 @@ MODULE input_parameters
!
! ... k-points inputs
LOGICAL :: tk_inp = .FALSE.
REAL(DP) :: xk(3,npkx) = 0.0_DP, wk(npkx) = 0.0_DP
REAL(DP) :: xk(3,npk) = 0.0_DP, wk(npk) = 0.0_DP
INTEGER :: nkstot = 0, nk1 = 0, nk2 = 0, nk3 = 0, k1 = 0, k2 = 0, k3 = 0
CHARACTER(LEN=80) :: k_points = 'gamma'
! k_points = 'automatic' | 'crystal' | 'tpiba' | 'gamma'*

View File

@ -10,7 +10,6 @@
!------------------------------------------------------------------------------!
USE kinds, ONLY: DP
USE parameters, ONLY: nhclm
!
IMPLICIT NONE
! Some comments are in order on how Nose-Hoover chains work here (K.N. Kudin)
@ -37,18 +36,16 @@
! qnp are the chain masses, qnp_ is a temporary array for now
! see subroutine ions_nose_allocate on what are the dimensions of these
! variables
! nhclm is now mostly not used, needs to be cleaned up at some point
!
INTEGER :: nhpcl=1, ndega, nhpdim=1, nhptyp=0, nhpbeg=0, nhpend=0
INTEGER, ALLOCATABLE :: atm2nhp(:)
INTEGER, ALLOCATABLE :: anum2nhp(:)
REAL(DP), ALLOCATABLE :: vnhp(:), xnhp0(:), xnhpm(:), xnhpp(:), &
ekin2nhp(:), gkbt2nhp(:), scal2nhp(:), qnp(:), qnp_(:)
ekin2nhp(:), gkbt2nhp(:), scal2nhp(:), qnp(:), qnp_(:), fnosep(:)
REAL(DP) :: gkbt = 0.0_DP
REAL(DP) :: kbt = 0.0_DP
REAL(DP) :: tempw = 0.0_DP
REAL(DP) :: fnosep( nhclm ) = 0.0_DP
!------------------------------------------------------------------------------!
CONTAINS
@ -100,8 +97,6 @@
! Add one more chain on top if needed
nhpdim = nhpdim + nhpend
IF( nhpcl > nhclm ) &
CALL errore(' ions_nose_init ', ' nhpcl out of range ', nhpcl )
endif
!
CALL ions_nose_allocate()
@ -265,6 +260,7 @@
IF ( .NOT. ALLOCATED( anum2nhp ) ) ALLOCATE( anum2nhp( nhpdim ) )
IF ( .NOT. ALLOCATED( qnp ) ) ALLOCATE( qnp( nhpcl*nhpdim ) )
IF ( .NOT. ALLOCATED( qnp_ ) ) ALLOCATE( qnp_( nhpcl ) )
IF ( .NOT. ALLOCATED( fnosep ) ) ALLOCATE( fnosep( nhpcl ) )
!
vnhp = 0.0_DP
xnhp0 = 0.0_DP
@ -291,6 +287,7 @@
IF ( ALLOCATED( anum2nhp ) ) DEALLOCATE( anum2nhp )
IF ( ALLOCATED( qnp ) ) DEALLOCATE( qnp )
IF ( ALLOCATED( qnp_ ) ) DEALLOCATE( qnp_ )
IF ( ALLOCATED( fnosep ) ) DEALLOCATE( fnosep )
!
IF( ALLOCATED( atm2nhp ) ) DEALLOCATE( atm2nhp )
!

View File

@ -89,7 +89,6 @@ ions_nose.o : control_flags.o
ions_nose.o : io_global.o
ions_nose.o : ions_base.o
ions_nose.o : kind.o
ions_nose.o : parameters.o
ions_nose.o : timestep.o
metadyn_base.o : basic_algebra_routines.o
metadyn_base.o : cell_base.o

View File

@ -1,5 +1,5 @@
!
! Copyright (C) 2001-2007 Quantum-Espresso group
! Copyright (C) 2001-2009 Quantum-Espresso group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
@ -11,32 +11,12 @@ MODULE parameters
IMPLICIT NONE
SAVE
!
! First all the parameter declaration
!
INTEGER, PARAMETER :: &
ntypx = 10, &! max number of different types of atom
npsx = ntypx, &! max number of different PPs (obsolete)
nsx = ntypx, &! max number of atomic species (CP)
npk = 40000, &! max number of k-points
lmaxx = 3 ! max non local angular momentum (l=0 to lmaxx)
!
INTEGER, PARAMETER :: &
lqmax= 2*lmaxx+1 ! max number of angular momenta of Q
!
! ... More parameter for the CP codes
!
INTEGER, PARAMETER :: nacx = 10 ! max number of averaged
! quantities saved to the restart
INTEGER, PARAMETER :: nsx = ntypx ! maximum number of species
INTEGER, PARAMETER :: npkx = npk ! maximum number of K points
INTEGER, PARAMETER :: nspinx = 2 ! maximum number of spinors
INTEGER, PARAMETER :: nhclm = 4 ! maximum number NH chain length,
! nhclm can be easily increased since the restart
! file should be able to handle it, perhaps better
! to align nhclm by 4
INTEGER, PARAMETER :: max_nconstr = 100 ! max number of constrains
lmaxx = 3, &! max non local angular momentum (l=0 to lmaxx)
lqmax= 2*lmaxx+1 ! max number of angular momenta of Q
END MODULE parameters

View File

@ -1327,7 +1327,7 @@ MODULE read_namelists_module
CALL errore( sub_name , &
& ' ntyp too large, increase NSX ', MAX( ntyp, 1) )
!
IF( nspin < 1 .OR. nspin > nspinx ) &
IF( nspin < 1 .OR. nspin > 2 ) &
CALL errore( sub_name ,' nspin out of range ', MAX(nspin, 1 ) )
!
IF( ecutwfc <= 0.0_DP ) &

View File

@ -282,7 +282,7 @@ SUBROUTINE projwave( filproj, lsym )
REAL (DP), ALLOCATABLE ::roverlap(:,:), rwork1(:),rproj0(:,:)
! ... or for gamma-point.
REAL(DP), ALLOCATABLE :: charges(:,:,:), proj1 (:)
REAL(DP) :: psum, totcharge(nspinx)
REAL(DP) :: psum, totcharge(2)
INTEGER :: nksinit, nkslast
CHARACTER(LEN=256) :: filename
CHARACTER (len=1) :: l_label(0:3)=(/'s','p','d','f'/)
@ -746,7 +746,7 @@ SUBROUTINE projwave_nc(filproj, lsym )
COMPLEX(DP), ALLOCATABLE :: overlap(:,:), work(:,:),work1(:), proj0(:,:)
! Some workspace for k-point calculation ...
REAL(DP), ALLOCATABLE :: charges(:,:,:), proj1 (:)
REAL(DP) :: psum, totcharge(nspinx), fact(2), spinor, compute_mj
REAL(DP) :: psum, totcharge(2), fact(2), spinor, compute_mj
INTEGER, ALLOCATABLE :: idx(:)
!
COMPLEX(DP) :: d12(2, 2, 48), d32(4, 4, 48), d52(6, 6, 48), &
@ -1936,7 +1936,7 @@ SUBROUTINE pprojwave( filproj, lsym )
REAL (DP), ALLOCATABLE ::roverlap_d(:,:)
! ... or for gamma-point.
REAL(DP), ALLOCATABLE :: charges(:,:,:), proj1 (:)
REAL(DP) :: psum, totcharge(nspinx)
REAL(DP) :: psum, totcharge(2)
INTEGER :: nksinit, nkslast
CHARACTER(LEN=256) :: filename
CHARACTER(LEN=256) :: auxname

View File

@ -413,10 +413,11 @@ MODULE ldaU
! ... The quantities needed in lda+U calculations
!
USE kinds, ONLY : DP
USE parameters, ONLY : lqmax, nspinx, ntypx
USE parameters, ONLY : lqmax, ntypx
!
SAVE
!
INTEGER, PARAMETER :: nspinx=2
COMPLEX(DP), ALLOCATABLE :: &
swfcatom(:,:) ! orthogonalized atomic wfcs
! REAL(DP), ALLOCATABLE :: &
@ -483,7 +484,7 @@ END MODULE fixed_occ
MODULE spin_orb
USE kinds, ONLY: DP
USE parameters, ONLY : lmaxx, npsx
USE parameters, ONLY : lmaxx
SAVE