Fixed a bug in turboTDDFT which was appearing if empty states were also computed.

This bug is related to the variable nwordwfc, which depends on the number of bands.
In turboTDDFT if empty states are computed (which is not needed for turbo_lanczos.x, but allowed,
and in fact the code will simply skip empty states), the global variable nbnd is set equal to 
nbnd_occ, i.e. only occupied bands (this is not my idea), which is bad, because global 
variables should not change their values. Due to such a confusion, I introduced this bug
some time ago. Now this is fixed.  


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@12603 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
timrov 2016-07-22 13:36:45 +00:00
parent e95fad1b10
commit 4627f7e55b
10 changed files with 45 additions and 27 deletions

View File

@ -23,6 +23,7 @@ Fixed in 6.0 version:
(courtesy Marton Voros) (commit 12426)
* PHonon: support for Goedecker-Hutter-Teter pseudopotentials was missing
(courtesy of Sebastiano Caravati)
* turboTDDFPT: Problem if empty states were also computed.
Incompatible changes in 6.0 version:

View File

@ -141,7 +141,7 @@ PROGRAM lr_dav_main
CONTAINS
SUBROUTINE lr_print_preamble()
USE lr_variables, ONLY : no_hxc, itermax
USE lr_variables, ONLY : no_hxc, d0psi_rs
USE uspp, ONLY : okvan
USE funct, only : dft_is_hybrid
USE martyna_tuckerman, ONLY : do_comp_mt
@ -182,9 +182,10 @@ CONTAINS
IF (no_hxc) THEN
WRITE(stdout,'(5x,"No Hartree/Exchange/Correlation")')
ELSEIF (dft_is_hybrid()) THEN
ELSEIF (dft_is_hybrid() .AND. .NOT.d0psi_rs) THEN
WRITE(stdout, '(/5x,"Use of exact-exchange enabled. Note the EXX correction to the [H,X]", &
&/5x,"commutator is NOT included hence the f-sum rule will be violated.")')
& /5x,"commutator is NOT included hence the f-sum rule will be violated.", &
& /5x,"You can try to use the variable d0psi_rs=.true. (see the documentation).")' )
ENDIF
END SUBROUTINE lr_print_preamble

View File

@ -21,8 +21,8 @@ SUBROUTINE lr_init_nfo()
USE klist, ONLY : nks,xk,ngk,igk_k
USE wvfct, ONLY : nbnd
USE realus, ONLY : real_space
USE lr_variables, ONLY : lr_verbosity, eels, nwordd0psi, &
nwordrestart, restart, size_evc, tmp_dir_lr
USE lr_variables, ONLY : lr_verbosity, eels, restart, &
size_evc, tmp_dir_lr
USE io_global, ONLY : stdout
USE constants, ONLY : tpi, eps8
USE noncollin_module, ONLY : npol
@ -91,15 +91,12 @@ SUBROUTINE lr_init_nfo()
!
ENDIF
!
! The length of the arrays d0psi, evc1 etc.
!
nwordd0psi = 2 * nbnd * npwx * npol * nksq
nwordrestart = 2 * nbnd * npwx * npol * nksq
nwordwfc = nbnd * npwx * npol
!
! 2) EELS-specific operations
!
IF (eels) THEN
!
size_evc = nbnd * npwx * npol * nksq
nwordwfc = nbnd * npwx * npol
!
! Open file to read the wavefunctions at k and k+q points
! after the nscf calculation.
@ -112,8 +109,6 @@ SUBROUTINE lr_init_nfo()
CALL errore ('lr_init_nfo', 'file '//trim(prefix)//'.wfc not found', 1)
ENDIF
!
size_evc = nksq * nbnd * npwx * npol
!
! If restart=.true. recalculate the small group of q.
!
IF (restart) CALL lr_smallgq (xq)

View File

@ -307,7 +307,7 @@ CONTAINS
SUBROUTINE lr_print_preamble()
USE lr_variables, ONLY : no_hxc
USE lr_variables, ONLY : no_hxc, d0psi_rs
USE uspp, ONLY : okvan
USE funct, ONLY : dft_is_hybrid
USE martyna_tuckerman, ONLY : do_comp_mt
@ -338,7 +338,7 @@ SUBROUTINE lr_print_preamble()
!
IF (no_hxc) THEN
WRITE(stdout,'(5x,"No Hartree/Exchange/Correlation")')
ELSEIF (dft_is_hybrid()) THEN
ELSEIF (dft_is_hybrid() .AND. .NOT.d0psi_rs) THEN
WRITE(stdout, '(/5x,"Use of exact-exchange enabled. Note the EXX correction to the [H,X]", &
& /5x,"commutator is NOT included hence the f-sum rule will be violated.", &
& /5x,"You can try to use the variable d0psi_rs=.true. (see the documentation).")' )

View File

@ -1,5 +1,5 @@
!
! Copyright (C) 2001-2015 Quantum ESPRESSO group
! Copyright (C) 2001-2016 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,
@ -17,10 +17,12 @@ SUBROUTINE lr_read_d0psi()
!
USE klist, ONLY : nks,degauss
USE io_files, ONLY : prefix, diropn, tmp_dir, wfc_dir
USE lr_variables, ONLY : d0psi, d0psi2, n_ipol, LR_polarization, lr_verbosity, &
& nwordd0psi, iund0psi, eels
USE lr_variables, ONLY : d0psi, d0psi2, n_ipol, LR_polarization, &
& lr_verbosity, nwordd0psi, iund0psi, eels
USE wvfct, ONLY : nbnd, npwx, et
USE io_global, ONLY : stdout
USE qpoint, ONLY : nksq
USE noncollin_module, ONLY : npol
!
IMPLICIT NONE
!
@ -35,6 +37,8 @@ SUBROUTINE lr_read_d0psi()
WRITE(stdout,'("<lr_read_d0psi>")')
endif
!
nwordd0psi = 2 * nbnd * npwx * npol * nksq
!
! This is a parallel read, done in wfc_dir
!
tmp_dir_saved = tmp_dir
@ -101,5 +105,7 @@ SUBROUTINE lr_read_d0psi()
!
tmp_dir = tmp_dir_saved
!
RETURN
!
END SUBROUTINE lr_read_d0psi
!-----------------------------------------------------------------------

View File

@ -66,8 +66,6 @@ SUBROUTINE lr_read_wf()
CALL normal_read()
ENDIF
!
!WRITE(stdout,'(5x,"Finished reading wfc.")')
!
IF (.NOT.eels) evc(:,:) = evc0(:,:,1)
!
IF ( dft_is_hybrid() ) THEN
@ -116,9 +114,11 @@ SUBROUTINE normal_read()
WRITE( stdout, '(/5x,"Normal read")' )
!
use_tg = dffts%have_task_groups
size_evc = nksq * nbnd * npwx * npol
incr = 2
!
size_evc = nbnd * npwx * npol * nksq
nwordwfc = nbnd * npwx * npol
!
! Read in the ground state wavefunctions.
! This is a parallel read, done in wfc_dir.
!
@ -334,7 +334,8 @@ SUBROUTINE virt_read()
!
ENDIF
!
size_evc = nksq * nbnd_occ(1) * npwx * npol
size_evc = nbnd_occ(1) * npwx * npol * nksq
nwordwfc = nbnd * npwx * npol ! nbnd > nbnd_occ(1)
!
! Read in the ground state wavefunctions
! This is a parallel read, done in wfc_dir
@ -435,6 +436,8 @@ SUBROUTINE virt_read()
!
nbnd = nbnd_occ(1)
!
nwordwfc = nbnd * npwx * npol ! needed for EXX
!
CALL deallocate_bec_type(becp)
CALL allocate_bec_type ( nkb, nbnd, becp )
!

View File

@ -25,14 +25,15 @@ SUBROUTINE lr_restart(iter_restart,rflag)
lr_verbosity, charge_response, LR_polarization, n_ipol, &
eels, sum_rule
USE charg_resp, ONLY : resonance_condition, rho_1_tot,rho_1_tot_im
USE wvfct, ONLY : nbnd
USE wvfct, ONLY : nbnd, npwx
USE becmod, ONLY : bec_type, becp, calbec
USE uspp, ONLY : vkb
USE io_global, ONLY : ionode
USE mp, ONLY : mp_bcast
USE mp_world, ONLY : world_comm
USE fft_base, ONLY : dfftp
USE noncollin_module, ONLY : nspin_mag
USE noncollin_module, ONLY : nspin_mag, npol
USE qpoint, ONLY : nksq
IMPLICIT NONE
!
@ -180,6 +181,8 @@ SUBROUTINE lr_restart(iter_restart,rflag)
! Note: Restart files are always in outdir
! Reading Lanczos vectors
!
nwordrestart = 2 * nbnd * npwx * npol * nksq
!
CALL diropn ( iunrestart, 'restart_lanczos.'//trim(int_to_char(LR_polarization)), nwordrestart, exst)
!
CALL davcio(evc1(:,:,:,1),nwordrestart,iunrestart,1,-1)

View File

@ -38,6 +38,7 @@ SUBROUTINE lr_solve_e
USE realus, ONLY : real_space, real_space_debug
USE control_lr, ONLY : alpha_pv
USE qpoint, ONLY : nksq
USE noncollin_module, ONLY : npol
!
IMPLICIT NONE
INTEGER :: ibnd, ik, is, ip
@ -129,6 +130,8 @@ SUBROUTINE lr_solve_e
! Writing of d0psi to the file.
! This is a parallel writing, done in wfc_dir
!
nwordd0psi = 2 * nbnd * npwx * npol * nksq
!
tmp_dir_saved = tmp_dir
!
IF ( wfc_dir /= 'undefined' ) tmp_dir = wfc_dir

View File

@ -27,9 +27,10 @@ SUBROUTINE lr_write_restart()
USE fft_base, ONLY : dfftp
USE io_global, ONLY : ionode, stdout
USE klist, ONLY : nks, nelec
USE noncollin_module, ONLY : nspin_mag, noncolin
use lsda_mod, only : nspin
USE noncollin_module, ONLY : nspin_mag, noncolin, npol
use lsda_mod, ONLY : nspin
USE cell_base, ONLY : alat, omega
USE qpoint, ONLY : nksq
!
IMPLICIT NONE
CHARACTER(len=6), EXTERNAL :: int_to_char
@ -165,7 +166,7 @@ SUBROUTINE lr_write_restart()
!
! Writing wavefuncion files for restart
!
!nwordrestart = 2 * nbnd * npwx * nks
nwordrestart = 2 * nbnd * npwx * npol * nksq
!
CALL diropn ( iunrestart, 'restart_lanczos.'//trim(int_to_char(LR_polarization)), nwordrestart, exst)
!

View File

@ -373,8 +373,10 @@ lr_psym_eels.o : ../../Modules/fft_base.o
lr_psym_eels.o : ../../Modules/kind.o
lr_psym_eels.o : ../../Modules/mp_global.o
lr_psym_eels.o : ../../Modules/noncol.o
lr_read_d0psi.o : ../../LR_Modules/lrcom.o
lr_read_d0psi.o : ../../Modules/io_files.o
lr_read_d0psi.o : ../../Modules/io_global.o
lr_read_d0psi.o : ../../Modules/noncol.o
lr_read_d0psi.o : ../../PW/src/pwcom.o
lr_read_d0psi.o : lr_variables.o
lr_read_wf.o : ../../FFTXlib/fft_interfaces.o
@ -432,6 +434,7 @@ lr_readin.o : ../../iotk/src/iotk_module.o
lr_readin.o : lr_charg_resp.o
lr_readin.o : lr_dav_variables.o
lr_readin.o : lr_variables.o
lr_restart.o : ../../LR_Modules/lrcom.o
lr_restart.o : ../../Modules/becmod.o
lr_restart.o : ../../Modules/control_flags.o
lr_restart.o : ../../Modules/fft_base.o
@ -489,6 +492,7 @@ lr_solve_e.o : ../../Modules/ions_base.o
lr_solve_e.o : ../../Modules/kind.o
lr_solve_e.o : ../../Modules/mp.o
lr_solve_e.o : ../../Modules/mp_global.o
lr_solve_e.o : ../../Modules/noncol.o
lr_solve_e.o : ../../Modules/recvec.o
lr_solve_e.o : ../../Modules/uspp.o
lr_solve_e.o : ../../Modules/wavefunctions.o
@ -533,6 +537,7 @@ lr_us.o : ../../PW/src/realus.o
lr_us.o : lr_variables.o
lr_variables.o : ../../Modules/control_flags.o
lr_variables.o : ../../Modules/kind.o
lr_write_restart.o : ../../LR_Modules/lrcom.o
lr_write_restart.o : ../../Modules/cell_base.o
lr_write_restart.o : ../../Modules/fft_base.o
lr_write_restart.o : ../../Modules/io_files.o