Diagonalization threshold for the first scf iteration performed after the first

ionic step has been reduced to 1.D-6 (previously was 1.D-5).
C.S.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3160 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
sbraccia 2006-06-06 21:00:40 +00:00
parent 279497445b
commit de62bd8851
1 changed files with 81 additions and 58 deletions

View File

@ -79,8 +79,7 @@ SUBROUTINE electrons()
dr2, &! the norm of the diffence between potential
charge, &! the total charge
mag, &! local magnetization
ehomo, elumo, &! highest occupied and lowest onuccupied levels
tcpu ! cpu time
ehomo, elumo ! highest occupied and lowest onuccupied levels
INTEGER :: &
i, &! counter on polarization
is, &! counter on spins
@ -143,8 +142,7 @@ SUBROUTINE electrons()
!
END IF
!
tcpu = get_clock( 'PWSCF' )
WRITE( stdout, 9000 ) tcpu
WRITE( stdout, 9000 ) get_clock( 'PWSCF' )
!
CALL flush_unit( stdout )
!
@ -173,14 +171,14 @@ SUBROUTINE electrons()
!
! ... Convergence threshold for iterative diagonalization
!
! ... for the first scf iteration of each ionic step after the first,
! ... the threshold is fixed to a default value of 1.D-5
! ... for the first scf iteration of each ionic step (after the first),
! ... the threshold is fixed to a default value of 1.D-6
!
#if defined (EXX)
10 continue
10 CONTINUE
#endif
IF ( istep > 1 ) ethr = 1.D-5
!
IF ( istep > 0 ) ethr = 1.D-6
!
WRITE( stdout, 9001 )
!
@ -192,26 +190,30 @@ SUBROUTINE electrons()
!
! ... bring starting rho to G-space
!
IF ( .not. ALLOCATED(rhog) ) ALLOCATE (rhog(ngm, nspin))
do is = 1, nspin
IF ( .NOT. ALLOCATED( rhog ) ) ALLOCATE( rhog( ngm, nspin ) )
!
DO is = 1, nspin
!
psic(:) = rho(:,is)
call cft3 (psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1)
!
CALL cft3( psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1 )
!
rhog(:,is) = psic(nl(:))
end do
!
END DO
!
DO idum = 1, niter
!
IF ( check_stop_now() ) RETURN
!
!
iter = iter + 1
!
WRITE( stdout, 9010 ) iter, ecutwfc, mixing_beta
!
CALL flush_unit( stdout )
!
! ... Convergence threshold for iterative diagonalization
! ... is automatically updated during self consistency
! ... Convergence threshold for iterative diagonalization is
! ... automatically updated during self consistency
!
IF ( iter > 1 .AND. ik_ == 0 ) THEN
!
@ -241,19 +243,30 @@ SUBROUTINE electrons()
!
! ... diagonalization of the KS hamiltonian
!
if ( lelfield ) then
do inberry=1,nberrycyc
IF ( lelfield ) THEN
!
DO inberry = 1, nberrycyc
!
ALLOCATE( psi( npwx, nbnd ) )
do ik=1,nks
call davcio(psi,nwordwfc,iunwfc,ik,-1)
call davcio(psi,nwordwfc,iunefield,ik,1)
end do
!
DO ik = 1, nks
!
CALL davcio( psi, nwordwfc, iunwfc, ik, -1 )
CALL davcio( psi, nwordwfc, iunefield, ik, 1 )
!
END DO
!
DEALLOCATE( psi )
!
CALL c_bands( iter, ik_, dr2 )
end do
else
!
END DO
!
ELSE
!
CALL c_bands( iter, ik_, dr2 )
end if
!
END IF
!
IF ( check_stop_now() ) RETURN
!
@ -283,11 +296,16 @@ SUBROUTINE electrons()
! ... bring newly calculated (in sum_band) rho to G-space for mixing
!
ALLOCATE( rhognew( ngm, nspin ) )
do is = 1, nspin
!
DO is = 1, nspin
!
psic(:) = rho(:,is)
call cft3 (psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, - 1)
!
CALL cft3( psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1 )
!
rhognew(:,is) = psic(nl(:))
end do
!
END DO
!
CALL mix_rho( rhognew, rhog, nsnew, ns, mixing_beta, &
dr2, tr2_min, iter, nmix, flmix, conv_elec )
@ -323,13 +341,20 @@ SUBROUTINE electrons()
! ... bring mixed rho from G- to R-space
!
ALLOCATE( rhonew( nrxx, nspin ) )
do is = 1, nspin
psic( :) = (0.d0, 0.d0)
!
DO is = 1, nspin
!
psic(:) = ( 0.D0, 0.D0 )
!
psic(nl(:)) = rhog(:,is)
if (gamma_only) psic( nlm(:) ) = CONJG (rhog (:, is))
call cft3 (psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, +1)
!
IF ( gamma_only ) psic(nlm(:)) = CONJG( rhog(:,is) )
!
CALL cft3( psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, 1 )
!
rhonew(:,is) = psic(:)
end do
!
END DO
!
! ... no convergence yet: calculate new potential from
! ... new estimate of the charge density
@ -354,8 +379,8 @@ SUBROUTINE electrons()
!
CALL write_rho( rho, nspin )
!
! ... convergence reached: store V(out)-V(in) in vnew
! ... Used to correct the forces
! ... convergence reached: store V(out)-V(in) in vnew ( used
! ... to correct the forces )
!
CALL v_of_rho( rho, rho_core, nr1, nr2, nr3, nrx1, nrx2, nrx3, &
nrxx, nl, ngm, gstart, nspin, g, gg, alat, omega, &
@ -435,8 +460,7 @@ SUBROUTINE electrons()
!
END IF
!
tcpu = get_clock( 'PWSCF' )
WRITE( stdout, 9000 ) tcpu
WRITE( stdout, 9000 ) get_clock( 'PWSCF' )
!
IF ( conv_elec ) WRITE( stdout, 9101 )
!
@ -789,8 +813,7 @@ SUBROUTINE electrons()
!
CALL poolrecover( et, nbnd, nkstot, nks )
!
tcpu = get_clock( 'PWSCF' )
WRITE( stdout, 9000 ) tcpu
WRITE( stdout, 9000 ) get_clock( 'PWSCF' )
!
WRITE( stdout, 9102 )
!