Remove this_pert_is_on_file. hp_dvpsi_pert is called once for each ik.

This commit is contained in:
Jae-Mo Lihm 2021-08-30 18:30:15 +09:00
parent 6316753cf3
commit 2d1bb55362
4 changed files with 3 additions and 28 deletions

View File

@ -26,7 +26,6 @@ subroutine hp_allocate_q
USE eqv, ONLY : dpsi, evq, dmuxc, dvpsi
USE control_lr, ONLY : lgamma
USE ldaU, ONLY : Hubbard_lmax, nwfcU
USE ldaU_hp, ONLY : this_pert_is_on_file
USE ldaU_lr, ONLY : swfcatomk, swfcatomkpq
!
IMPLICIT NONE
@ -44,9 +43,6 @@ subroutine hp_allocate_q
ALLOCATE (dpsi(npwx*npol,nbnd))
ALLOCATE (dmuxc(dfftp%nnr,nspin_mag,nspin_mag))
!
ALLOCATE (this_pert_is_on_file(nksq))
this_pert_is_on_file(:) = .FALSE.
!
IF (okvan) THEN
ALLOCATE (eigqts(nat))
ALLOCATE (becp1(nksq))

View File

@ -22,7 +22,6 @@ SUBROUTINE hp_dealloc_q()
& dvxc_s, vsgga, segni
USE eqv, ONLY : dmuxc, dpsi, dvpsi, evq
USE control_lr, ONLY : lgamma, nbnd_occ
USE ldaU_hp, ONLY : this_pert_is_on_file
USE ldaU_lr, ONLY : swfcatomk, swfcatomkpq
!
IMPLICIT NONE
@ -42,9 +41,6 @@ SUBROUTINE hp_dealloc_q()
if (allocated(ikqs)) deallocate (ikqs)
if (allocated(m_loc)) deallocate (m_loc)
!
if (allocated(this_pert_is_on_file)) &
& deallocate (this_pert_is_on_file)
!
IF (okvan) THEN
if (allocated(eigqts)) deallocate (eigqts)
if (allocated(becp1)) then

View File

@ -20,8 +20,6 @@ subroutine hp_dvpsi_pert (ik)
!
! dvpsi is for a given "k", "q" and "J"
!
! dvpsi is READ from file if this_pert_is_on_file(ik) = .TRUE.
! otherwise dvpsi is COMPUTED and WRITTEN on file
! (evc, swfcatomk, swfcatomkpq must be set)
!
USE kinds, ONLY : DP
@ -38,8 +36,7 @@ subroutine hp_dvpsi_pert (ik)
USE units_lr, ONLY : iuatswfc
USE control_lr, ONLY : lgamma
USE ldaU, ONLY : Hubbard_lmax, Hubbard_l, offsetU, nwfcU
USE ldaU_hp, ONLY : nqsh, perturbed_atom, this_pert_is_on_file, &
iudvwfc, lrdvwfc
USE ldaU_hp, ONLY : nqsh, perturbed_atom, iudvwfc, lrdvwfc
USE ldaU_lr, ONLY : swfcatomk, swfcatomkpq
!
IMPLICIT NONE
@ -60,23 +57,11 @@ subroutine hp_dvpsi_pert (ik)
DO na = 1, nat
IF (perturbed_atom(na)) counter = counter + 1
ENDDO
IF (counter.NE.1) CALL errore( 'hp_dvpsi_pert', "One perturbed atom must be specified", 1)
IF (counter /= 1) CALL errore( 'hp_dvpsi_pert', "One perturbed atom must be specified", 1)
!
dvpsi(:,:) = (0.0d0, 0.0d0)
!
! If this is not the first iteration, hence dvpsi was already
! computed before. So read it from file and exit.
!
IF (this_pert_is_on_file(ik)) THEN
!
CALL get_buffer(dvpsi, lrdvwfc, iudvwfc, ik)
CALL stop_clock ('hp_dvpsi_pert')
RETURN
!
ENDIF
!
! If this is a first iteration, then dvpsi must be computed
! and written on file.
! Compute dvpsi for ik and write on buffer iudvwfc
!
ALLOCATE (proj(nbnd,nwfcU))
!
@ -127,7 +112,6 @@ subroutine hp_dvpsi_pert (ik)
! Write dvpsi on file.
!
CALL save_buffer(dvpsi, lrdvwfc, iudvwfc, ik)
this_pert_is_on_file(ik) = .true.
!
DEALLOCATE (proj)
!

View File

@ -49,7 +49,6 @@ MODULE ldaU_hp
LOGICAL, ALLOCATABLE :: todo_atom(:), & ! Which atoms must be perturbed
perturbed_atom(:), & ! Controls which atom is perturbed in the HP
! calculation
this_pert_is_on_file(:), & ! The perturbation is written on file or not
comp_iq(:) ! If .true. this q point has to be calculated
!
INTEGER :: nath, & ! Number of (real) atoms in the primitive cell