variable tot_charge added to the input of pw.x [silviu]

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@2673 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
silviu 2006-01-01 09:17:24 +00:00
parent 8d7ea2691d
commit a09a59d8f6
3 changed files with 29 additions and 17 deletions

View File

@ -100,7 +100,10 @@ SUBROUTINE iosys()
nelup_ => nelup, & nelup_ => nelup, &
neldw_ => neldw, & neldw_ => neldw, &
b_length_ => b_length, & b_length_ => b_length, &
lcart_ => lcart lcart_ => lcart, &
tot_charge_ => tot_charge, &
tot_magnetization_ => tot_magnetization, &
multiplicity_ => multiplicity
! !
USE ktetra, ONLY : nk1, nk2, nk3, k1, k2, k3, ltetra USE ktetra, ONLY : nk1, nk2, nk3, k1, k2, k3, ltetra
! !
@ -191,6 +194,7 @@ SUBROUTINE iosys()
! !
USE input_parameters, ONLY : ibrav, celldm, a, b, c, cosab, cosac, cosbc, & USE input_parameters, ONLY : ibrav, celldm, a, b, c, cosab, cosac, cosbc, &
nat, ntyp, nbnd, nelec, nelup, neldw, & nat, ntyp, nbnd, nelec, nelup, neldw, &
tot_charge, tot_magnetization, multiplicity, &
ecutwfc, ecutrho, & ecutwfc, ecutrho, &
nr1, nr2, nr3, nr1s, nr2s, nr3s, & nr1, nr2, nr3, nr1s, nr2s, nr3s, &
nosym, starting_magnetization, & nosym, starting_magnetization, &
@ -374,7 +378,8 @@ SUBROUTINE iosys()
! !
END SELECT END SELECT
! !
IF ( nelup == 0.D0 .AND. neldw == 0.D0 ) THEN IF ( nelup == 0.D0 .AND. neldw == 0.D0 .AND. &
tot_magnetization < 0 .AND. multiplicity == 0) THEN
! !
two_fermi_energies = .FALSE. two_fermi_energies = .FALSE.
! !
@ -1121,6 +1126,9 @@ SUBROUTINE iosys()
nelec_ = nelec nelec_ = nelec
nelup_ = nelup nelup_ = nelup
neldw_ = neldw neldw_ = neldw
tot_charge_ = tot_charge
tot_magnetization_ = tot_magnetization
multiplicity_ = multiplicity
! !
lspinorb_ = lspinorb lspinorb_ = lspinorb
noncolin_ = noncolin noncolin_ = noncolin

View File

@ -150,12 +150,15 @@ MODULE klist
nelec, &! number of electrons nelec, &! number of electrons
nelup, &! number of spin-up electrons (if two_fermi_energies=t) nelup, &! number of spin-up electrons (if two_fermi_energies=t)
neldw, &! number of spin-dw electrons (if two_fermi_energies=t) neldw, &! number of spin-dw electrons (if two_fermi_energies=t)
tot_charge, &! total charge
b_length ! length of the b vectors b_length ! length of the b vectors
INTEGER :: & INTEGER :: &
ngk(npk), &! number of plane waves for each k point ngk(npk), &! number of plane waves for each k point
nks, &! number of k points in this pool nks, &! number of k points in this pool
nkstot, &! total number of k points nkstot, &! total number of k points
ngauss ! type of smearing technique ngauss, &! type of smearing technique
tot_magnetization, &! nelup-neldw >= 0 (negative value means unspecified)
multiplicity ! spin multiplicity
LOGICAL :: & LOGICAL :: &
lgauss, &! if .TRUE.: use gaussian broadening lgauss, &! if .TRUE.: use gaussian broadening
lxkcry, &! if .TRUE.:k-pnts in cryst. basis accepted in input lxkcry, &! if .TRUE.:k-pnts in cryst. basis accepted in input

View File

@ -51,7 +51,8 @@ SUBROUTINE setup()
USE gsmooth, ONLY : doublegrid, gcutms USE gsmooth, ONLY : doublegrid, gcutms
USE klist, ONLY : xk, wk, xqq, nks, nelec, degauss, lgauss, & USE klist, ONLY : xk, wk, xqq, nks, nelec, degauss, lgauss, &
lxkcry, nkstot, b_length, lcart, & lxkcry, nkstot, b_length, lcart, &
nelup, neldw, two_fermi_energies nelup, neldw, two_fermi_energies, &
tot_charge, tot_magnetization, multiplicity
USE lsda_mod, ONLY : lsda, nspin, current_spin, isk, & USE lsda_mod, ONLY : lsda, nspin, current_spin, isk, &
starting_magnetization starting_magnetization
USE ktetra, ONLY : nk1, nk2, nk3, k1, k2, k3, & USE ktetra, ONLY : nk1, nk2, nk3, k1, k2, k3, &
@ -157,10 +158,10 @@ SUBROUTINE setup()
! !
#if defined (__PGI) #if defined (__PGI)
DO na = 1, nat DO na = 1, nat
nelec = nelec + zv( ityp(na) ) nelec = nelec + zv( ityp(na) ) - tot_charge
END DO END DO
#else #else
nelec = SUM( zv(ityp(1:nat)) ) nelec = SUM( zv(ityp(1:nat)) ) - tot_charge
#endif #endif
! !
END IF END IF