Beautifications

This commit is contained in:
Samuel Ponce 2019-04-25 14:05:32 +01:00
parent 859990fdf9
commit d4caadf36b
10 changed files with 29 additions and 29 deletions

View File

@ -730,7 +730,7 @@
REAL(kind=DP) :: zero_vect(3) REAL(kind=DP) :: zero_vect(3)
!! temporary zero vector !! temporary zero vector
REAL(kind=DP) :: delta REAL(kind=DP) :: delta
!! \delta_nm = 1 if n == m and 0 if n .neq. m !! \delta_nm = 1 if n == m and 0 if n /= m
! !
COMPLEX(kind=DP) :: Apos(3,nbndsub,nbndsub,nks) COMPLEX(kind=DP) :: Apos(3,nbndsub,nbndsub,nks)
!! A^W_{mn,\alpha}(k) !! A^W_{mn,\alpha}(k)

View File

@ -921,6 +921,18 @@
iq_restart = 1 iq_restart = 1
first_cycle = .FALSE. first_cycle = .FALSE.
first_time = .TRUE. first_time = .TRUE.
IF (scattering .AND. .NOT. iterative_bte) THEN
ALLOCATE (inv_tau_all(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
ALLOCATE (zi_allvb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
inv_tau_all(:,:,:) = zero
zi_allvb(:,:,:) = zero
ENDIF
IF (int_mob .AND. carrier) THEN
ALLOCATE (inv_tau_allcb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
ALLOCATE (zi_allcb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
inv_tau_allcb(:,:,:) = zero
zi_allcb(:,:,:) = zero
ENDIF
! !
! Restart in SERTA case or self-energy case ! Restart in SERTA case or self-energy case
IF (restart) THEN IF (restart) THEN
@ -996,18 +1008,6 @@
! Fine mesh set of g-matrices. It is large for memory storage ! Fine mesh set of g-matrices. It is large for memory storage
ALLOCATE (epf17(ibndmax-ibndmin+1, ibndmax-ibndmin+1, nmodes, nkf)) ALLOCATE (epf17(ibndmax-ibndmin+1, ibndmax-ibndmin+1, nmodes, nkf))
epf17(:,:,:,:) = czero epf17(:,:,:,:) = czero
IF (scattering .AND. .NOT. iterative_bte) THEN
ALLOCATE (inv_tau_all(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
ALLOCATE (zi_allvb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
inv_tau_all(:,:,:) = zero
zi_allvb(:,:,:) = zero
ENDIF
IF (int_mob .AND. carrier) THEN
ALLOCATE (inv_tau_allcb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
ALLOCATE (zi_allcb(nstemp, ibndmax-ibndmin+1, nkqtotf/2))
inv_tau_allcb(:,:,:) = zero
zi_allcb(:,:,:) = zero
ENDIF
IF (elecselfen .OR. plselfen) THEN IF (elecselfen .OR. plselfen) THEN
ALLOCATE (sigmar_all(ibndmax-ibndmin+1, nkqtotf/2)) ALLOCATE (sigmar_all(ibndmax-ibndmin+1, nkqtotf/2))
ALLOCATE (sigmai_all(ibndmax-ibndmin+1, nkqtotf/2)) ALLOCATE (sigmai_all(ibndmax-ibndmin+1, nkqtotf/2))

View File

@ -290,18 +290,18 @@
COMPLEX(kind=DP), ALLOCATABLE :: epmatlrT(:,:,:,:) COMPLEX(kind=DP), ALLOCATABLE :: epmatlrT(:,:,:,:)
!! Long-range temp. save !! Long-range temp. save
! !
IF (nbndsub.ne.nbnd) & IF (nbndsub /= nbnd) &
WRITE(stdout, '(/,5x,a,i4)' ) 'Band disentanglement is used: nbndsub = ', nbndsub WRITE(stdout, '(/,5x,a,i4)' ) 'Band disentanglement is used: nbndsub = ', nbndsub
! !
ALLOCATE ( cu ( nbnd, nbndsub, nks), & ALLOCATE (cu(nbnd, nbndsub, nks))
cuq ( nbnd, nbndsub, nks), & ALLOCATE (cuq(nbnd, nbndsub, nks))
lwin ( nbnd, nks ), & ALLOCATE (lwin(nbnd, nks))
lwinq ( nbnd, nks ), & ALLOCATE (lwinq(nbnd, nks))
exband ( nbnd ) ) ALLOCATE (exband(nbnd))
! !
CALL start_clock ( 'ephwann' ) CALL start_clock ( 'ephwann' )
! !
IF ( epwread ) THEN IF (epwread) THEN
! !
! Might have been pre-allocate depending of the restart configuration ! Might have been pre-allocate depending of the restart configuration
IF(ALLOCATED(tau)) DEALLOCATE ( tau ) IF(ALLOCATED(tau)) DEALLOCATE ( tau )
@ -311,7 +311,7 @@
! We need some crystal info ! We need some crystal info
IF (mpime == ionode_id) THEN IF (mpime == ionode_id) THEN
! !
OPEN(UNIT=crystal,FILE='crystal.fmt',status='old',iostat=ios) OPEN (UNIT = crystal, FILE = 'crystal.fmt', STATUS = 'old', IOSTAT = ios)
READ (crystal,*) nat READ (crystal,*) nat
READ (crystal,*) nmodes READ (crystal,*) nmodes
READ (crystal,*) nelec READ (crystal,*) nelec

View File

@ -1307,7 +1307,7 @@
ELSE ELSE
ef0 = efnew ef0 = efnew
!ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk) !ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk)
! if some bands are skipped (nbndskip.neq.0), nelec has already been recalculated ! if some bands are skipped (nbndskip /= 0), nelec has already been recalculated
! in ephwann_shuffle ! in ephwann_shuffle
ENDIF ENDIF
! !

View File

@ -900,7 +900,7 @@
END SUBROUTINE tau_write END SUBROUTINE tau_write
!---------------------------------------------------------------------------- !----------------------------------------------------------------------------
!---------------------------------------------------------------------------- !----------------------------------------------------------------------------
SUBROUTINE tau_read(iqq,totq,nktotf,second) SUBROUTINE tau_read (iqq, totq, nktotf, second)
!---------------------------------------------------------------------------- !----------------------------------------------------------------------------
! !
USE kinds, ONLY : DP USE kinds, ONLY : DP
@ -942,7 +942,7 @@
!! Length of the vector !! Length of the vector
INTEGER :: nqtotf_read INTEGER :: nqtotf_read
!! Total number of q-point read !! Total number of q-point read
REAL(KIND=DP) :: aux ( 2 * nstemp * (ibndmax-ibndmin+1) * nktotf + 2 ) REAL(KIND=DP) :: aux(2 * nstemp * (ibndmax - ibndmin + 1) * nktotf + 2)
!! Vector to store the array !! Vector to store the array
! !
CHARACTER (len=256) :: name1 CHARACTER (len=256) :: name1

View File

@ -187,7 +187,7 @@
ELSE IF (nsmear > 1) THEN ELSE IF (nsmear > 1) THEN
! !
ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw0, ngaussw, 0, isk_dummy) ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw0, ngaussw, 0, isk_dummy)
! if some bands are skipped (nbndskip.neq.0), nelec has already been ! if some bands are skipped (nbndskip /= 0), nelec has already been
! recalculated ! recalculated
! in ephwann_shuffle ! in ephwann_shuffle
! !

View File

@ -109,7 +109,7 @@
ELSE ELSE
! !
ef0 = efnew ! Fermi energy is recalculated on the fine mesh!! ef0 = efnew ! Fermi energy is recalculated on the fine mesh!!
! if some bands are skipped (nbndskip.neq.0), nelec has already been recalculated ! if some bands are skipped (nbndskip /= 0), nelec has already been recalculated
! in ephwann_shuffle ! in ephwann_shuffle
! !
ENDIF ENDIF

View File

@ -144,7 +144,7 @@
ELSE ELSE
! !
ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy) ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy)
! if some bands are skipped (nbndskip.neq.0), nelec has already been recalculated ! if some bands are skipped (nbndskip /= 0), nelec has already been recalculated
! in ephwann_shuffle ! in ephwann_shuffle
! !
ENDIF ENDIF

View File

@ -151,7 +151,7 @@
ELSE IF (nsmear > 1) THEN ELSE IF (nsmear > 1) THEN
! !
ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy) ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy)
! if some bands are skipped (nbndskip.neq.0), nelec has already been ! if some bands are skipped (nbndskip /= 0), nelec has already been
! recalculated in ephwann_shuffle ! recalculated in ephwann_shuffle
! !
ELSE !SP: This is added for efficiency reason because the efermig routine is slow ELSE !SP: This is added for efficiency reason because the efermig routine is slow

View File

@ -94,7 +94,7 @@
ELSE ELSE
! !
ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy) ef0 = efermig(etf, nbndsub, nkqf, nelec, wkf, degaussw, ngaussw, 0, isk_dummy)
! if some bands are skipped (nbndskip.neq.0), nelec has already been recalculated ! if some bands are skipped (nbndskip /= 0), nelec has already been recalculated
! in ephwann_shuffle ! in ephwann_shuffle
! !
ENDIF ENDIF