Merge branch 'ef_shift_merge' into 'develop'

Small changes to efermi_shift

See merge request QEF/q-e!1558
This commit is contained in:
giannozz 2021-09-10 15:33:23 +00:00
commit c5e8c505fb
3 changed files with 13 additions and 11 deletions

View File

@ -166,7 +166,6 @@ SUBROUTINE hp_solve_linear_system (na, iq)
ALLOCATE (ldoss(dffts%nnr, nspin_mag)) ALLOCATE (ldoss(dffts%nnr, nspin_mag))
ALLOCATE (becsum1 ( (nhm * (nhm + 1))/2, nat, nspin_mag)) ALLOCATE (becsum1 ( (nhm * (nhm + 1))/2, nat, nspin_mag))
CALL localdos (ldos, ldoss, becsum1, dos_ef) CALL localdos (ldos, ldoss, becsum1, dos_ef)
becsum1 = becsum1 * 2 ! because ef_shift adds 0.5 * becsum1 to dbecsum
IF (.NOT.okpaw) DEALLOCATE (becsum1) IF (.NOT.okpaw) DEALLOCATE (becsum1)
ENDIF ENDIF
! !

View File

@ -81,6 +81,7 @@ SUBROUTINE ef_shift (npert, dos_ef, ldos, drhoscf, dbecsum, becsum1, irr, sym_de
! !
call start_clock ('ef_shift') call start_clock ('ef_shift')
! !
! This routine is used only at q=Gamma where the dimension of irrep never exceeds 3
IF (npert > 3) CALL errore("ef_shift", "npert exceeds 3", 1) IF (npert > 3) CALL errore("ef_shift", "npert exceeds 3", 1)
! !
! determines Fermi energy shift (such that each pertubation is neutral) ! determines Fermi energy shift (such that each pertubation is neutral)
@ -118,7 +119,7 @@ SUBROUTINE ef_shift (npert, dos_ef, ldos, drhoscf, dbecsum, becsum1, irr, sym_de
IF (PRESENT(dbecsum) .AND. PRESENT(becsum1)) THEN IF (PRESENT(dbecsum) .AND. PRESENT(becsum1)) THEN
DO ipert = 1, npert DO ipert = 1, npert
dbecsum(:,:,:,ipert) = dbecsum(:,:,:,ipert) & dbecsum(:,:,:,ipert) = dbecsum(:,:,:,ipert) &
+ def(ipert) * CMPLX(becsum1(:,:,:)*0.5_DP, 0.0_DP, KIND=DP) + def(ipert) * CMPLX(becsum1(:,:,:), 0.0_DP, KIND=DP)
ENDDO ENDDO
ENDIF ENDIF
! !
@ -179,6 +180,7 @@ SUBROUTINE ef_shift_wfc(npert, ldoss, drhoscf)
! !
call start_clock ('ef_shift_wfc') call start_clock ('ef_shift_wfc')
! !
! This routine is used only at q=Gamma where the dimension of irrep never exceeds 3
IF (npert > 3) CALL errore("ef_shift_wfc", "npert exceeds 3", 1) IF (npert > 3) CALL errore("ef_shift_wfc", "npert exceeds 3", 1)
! !
! Update the perturbed wavefunctions according to the Fermi energy shift ! Update the perturbed wavefunctions according to the Fermi energy shift

View File

@ -398,21 +398,22 @@ SUBROUTINE solve_linter (irr, imode0, npe, drhoscf)
call mp_sum ( drhoscf, inter_pool_comm ) call mp_sum ( drhoscf, inter_pool_comm )
call mp_sum ( drhoscfh, inter_pool_comm ) call mp_sum ( drhoscfh, inter_pool_comm )
IF (okpaw) call mp_sum ( dbecsum, inter_pool_comm ) IF (okpaw) call mp_sum ( dbecsum, inter_pool_comm )
! !
! q=0 in metallic case deserve special care (e_Fermi can shift)
!
IF (okpaw) THEN IF (okpaw) THEN
IF (lmetq0) CALL ef_shift(npe, dos_ef, ldos, drhoscfh, &
dbecsum, becsum1, irr, sym_def)
DO ipert=1,npe DO ipert=1,npe
dbecsum(:,:,:,ipert)=2.0_DP *dbecsum(:,:,:,ipert) & dbecsum(:,:,:,ipert)=2.0_DP *dbecsum(:,:,:,ipert) &
+becsumort(:,:,:,imode0+ipert) +becsumort(:,:,:,imode0+ipert)
ENDDO ENDDO
ELSE ENDIF
IF (lmetq0) CALL ef_shift(npe, dos_ef, ldos, drhoscfh, & !
irr=irr, sym_def=sym_def) ! q=0 in metallic case deserve special care (e_Fermi can shift)
!
IF (lmetq0) THEN
IF (okpaw) THEN
CALL ef_shift(npe, dos_ef, ldos, drhoscfh, dbecsum, becsum1, irr, sym_def)
ELSE
CALL ef_shift(npe, dos_ef, ldos, drhoscfh, irr=irr, sym_def=sym_def)
ENDIF
ENDIF ENDIF
! !
! After the loop over the perturbations we have the linear change ! After the loop over the perturbations we have the linear change