Page 1 of 1

bug report for scatread = .true.

Posted: Tue Jul 15, 2025 11:39 am
by guodonglin
for io_transport.f90 in EPW5.9

!
!----------------------------------------------------------------------------
SUBROUTINE scattering_write(itemp, etemp, ef0, etf_all)
!----------------------------------------------------------------------------
!!
!! Write scattering rates
!!
USE kinds, ONLY : DP
USE io_global, ONLY : stdout
USE io_var, ONLY : iufilscatt_rate
USE global_var,ONLY : ibndmin, nkqtotf, inv_tau_all, nbndfst, nktotf
USE input, ONLY : nbndsub, nstemp
USE ep_constants, ONLY : ryd2mev, kelvin2eV, ryd2ev, &
meV2invps, eps4
USE mp, ONLY : mp_barrier
USE mp_world, ONLY : mpime
USE io_global, ONLY : ionode_id
!
IMPLICIT NONE
!
INTEGER, INTENT(in) :: itemp
!! Temperature index
REAL(KIND = DP), INTENT(in) :: etemp
!! Temperature in Ry (this includes division by kb)
REAL(KIND = DP), INTENT(in) :: ef0(nstemp)
!! Fermi level for the temperature itemp
REAL(KIND = DP), INTENT(in) :: etf_all(nbndsub, nkqtotf)
!! Eigen-energies on the fine grid collected from all pools in parallel case
!
! Local variables
CHARACTER(LEN = 256) :: name1
!! Name used to write scattering rates to file.
INTEGER :: ik
!! K-point index
INTEGER :: ikk
!! Odd index to read etf
INTEGER :: ikq
!! Even k+q index to read etf
INTEGER :: ibnd
!! Local band index
REAL(KIND = DP) :: ekk
!! Energy relative to Fermi level: $$\varepsilon_{n\mathbf{k}}-\varepsilon_F$$
REAL(KIND = DP) :: temp
!! Temporary file name used to write scattering rate to file.
!
WRITE(stdout, '(/5x,"Writing scattering rate to file"/)')
!
IF (mpime == ionode_id) THEN
!
! Write to file
temp = etemp * ryd2ev / kelvin2eV
IF (temp < 10.d0 - eps4) THEN
WRITE(name1,'(a18,f4.2)') 'scattering_rate_00', temp
ELSEIF (temp >= 10.d0 - eps4 .AND. temp < 100.d0 -eps4) THEN
WRITE(name1,'(a17,f5.2)') 'scattering_rate_0', temp
ELSEIF (temp >= 100.d0 -eps4) THEN
WRITE(name1,'(a16,f6.2)') 'scattering_rate_', temp
ENDIF
OPEN(iufilscatt_rate, FILE = name1, FORM = 'formatted')
WRITE(iufilscatt_rate, '(a)') '# Inverse scattering time (ps)'
WRITE(iufilscatt_rate, '(a)') '# ik ibnd E(ibnd) scattering rate(1/ps)'
!
DO ik = 1, nktotf
!
ikk = 2 * ik - 1
ikq = ikk + 1
!
DO ibnd = 1, nbndfst
!
! note that ekk does not depend on q
ekk = etf_all(ibndmin - 1 + ibnd, ikk) - ef0(itemp)
!
WRITE(iufilscatt_rate, '(i9,2x)', ADVANCE = 'no') ik
WRITE(iufilscatt_rate, '(i9,2x)', ADVANCE = 'no') ibndmin - 1 + ibnd
WRITE(iufilscatt_rate, '(E22.14)', ADVANCE = 'no') ryd2ev * ekk
WRITE(iufilscatt_rate, '(E26.16E3)') ryd2mev * meV2invps * inv_tau_all(itemp, ibnd, ik)
!
ENDDO
!
ENDDO
!
CLOSE(iufilscatt_rate)
ENDIF
!CALL mp_barrier(inter_pool_comm)
!
!----------------------------------------------------------------------------
END SUBROUTINE scattering_write
!----------------------------------------------------------------------------
!
!----------------------------------------------------------------------------
SUBROUTINE scattering_read(etemp, ef0, etf_all, inv_tau_all)
!----------------------------------------------------------------------------
!!
!! Read scattering files
!!
USE kinds, ONLY : DP
USE io_global, ONLY : stdout
USE io_var, ONLY : iufilscatt_rate
USE global_var,ONLY : ibndmin, nktotf, nbndfst
USE input, ONLY : nbndsub, nstemp
USE ep_constants, ONLY : ryd2mev, kelvin2eV, ryd2ev, &
meV2invps, eps4
USE mp, ONLY : mp_barrier, mp_bcast
USE mp_world, ONLY : mpime, world_comm
USE io_global, ONLY : ionode_id
!
IMPLICIT NONE
!
REAL(KIND = DP), INTENT(in) :: etemp
!! Temperature in Ry (this includes division by kb)
REAL(KIND = DP), INTENT(in) :: ef0
!! Fermi level for the temperature itemp
REAL(KIND = DP), INTENT(out) :: etf_all(nbndsub, nktotf)
!! Eigen-energies on the fine grid collected from all pools in parallel case
REAL(KIND = DP), INTENT(out) :: inv_tau_all(nstemp, nbndfst, nktotf)
!! Inverse scattering rates
!
! Local variables
CHARACTER(LEN = 256) :: name1
!! Name used to write scattering rates to file.
CHARACTER(LEN = 256) :: dummy1
!! Dummy variable to store the text of the scattering_rate file
INTEGER :: ik
!! K-point index
INTEGER :: ik_tmp
!! K-point index read from file
INTEGER :: ibnd
!! Local band index
INTEGER :: ibnd_tmp
!! Local band index read from file
INTEGER :: ios
!! Status of reading file
REAL(KIND = DP) :: temp
!! Temporary file name used to write scattering rate to file.
!
WRITE(stdout,'(/5x,"Reading scattering rate from file"/)')
!
IF (mpime == ionode_id) THEN
! Write to file
temp = etemp * ryd2ev / kelvin2eV
IF (temp < 10.d0 - eps4) THEN
WRITE(name1, '(a18,f4.2)') 'scattering_rate_00', temp
ELSEIF (temp >= 10.d0 - eps4 .AND. temp < 100.d0 -eps4) THEN
WRITE(name1, '(a17,f5.2)') 'scattering_rate_0', temp
ELSEIF (temp >= 100.d0 -eps4) THEN
WRITE(name1, '(a16,f6.2)') 'scattering_rate_', temp
ENDIF
OPEN(iufilscatt_rate, FILE = name1, STATUS = 'old', IOSTAT = ios)
WRITE(stdout,'(a16,a22)') ' Open file: ',name1
! There are two comment line at the beginning of the file
READ(iufilscatt_rate, *) dummy1
READ(iufilscatt_rate, *) dummy1
!
DO ik = 1, nktotf
!
DO ibnd = 1, nbndfst
!
READ(iufilscatt_rate, *) ik_tmp, ibnd_tmp, etf_all(ibndmin - 1 + ibnd, ik), inv_tau_all(1, ibnd, ik)
inv_tau_all(1, ibnd, ik) = inv_tau_all(1, ibnd, ik) / (ryd2mev * meV2invps)
!
! Check that the file corresponds to the run we are making
IF (ABS(ibnd_tmp - ibndmin - ibnd + 1) > 0) CALL errore('scattering_read', &
'Band read from the scattering_rate file do not match current calculation ', 1)
!
ENDDO
! Check that the file corresponds to the run we are making
IF (ABS(ik_tmp - ik) > 0) CALL errore('scattering_read', &
'k-point read from the scattering_rate file do not match current calculation ', 1)
!
ENDDO
!
etf_all = etf_all / ryd2ev
etf_all = etf_all + ef0
!
CLOSE(iufilscatt_rate)
ENDIF
CALL mp_bcast(etf_all, ionode_id, world_comm)
CALL mp_bcast(inv_tau_all, ionode_id, world_comm)
!
WRITE(stdout,'(/5x,"Scattering rate read from file"/)')
!
!----------------------------------------------------------------------------
END SUBROUTINE scattering_read
!----------------------------------------------------------------------------


The scattering_rate_300.00 file is produced by the scattering_write part, but the scattering_rate_300.00 file can not readed by the scattering_read part. and the error comes from teh line " READ(iufilscatt_rate, *) ik_tmp, ibnd_tmp, etf_all(ibndmin - 1 + ibnd, ik), inv_tau_all(1, ibnd, ik)"

I do not know why this happens. The file generated by the EPW code itself reports errors when being read by the same code. I'm not sure whether it's a file issue or a code issue. After reading the above code—scattering_write and scattering_read—I found that the file should be fine. I suspect it might be a code problem.



scattering_rate_300.00 file likes this

# Inverse scattering time (ps)
# ik ibnd E(ibnd) scattering rate(1/ps)
1 4 0.21005663240261E+01 0.145038259671E+03
2 4 0.24700383639738E+01 0.145038259671E+03
3 4 0.27568758691801E+01 0.145038259671E+03
4 4 0.23343551898906E+01 0.145038259671E+03
5 4 0.20116892523688E+01 0.145038259671E+03
6 4 0.19722408977009E+01 0.145038259671E+03
7 4 0.20057239257547E+01 0.145038259671E+03
8 4 0.28576426770856E+01 0.145038259671E+03
9 4 0.27655248572311E+01 0.145038259671E+03
10 4 0.23555900115941E+01 0.145038259671E+03
11 4 0.21646697019633E+01 0.145038259671E+03
12 4 0.21582082354968E+01 0.145038259671E+03
13 4 0.27429032697439E+01 0.145038259671E+03
14 4 0.25562880660053E+01 0.145038259671E+03
15 4 0.23801436191581E+01 0.145038259671E+03
16 4 0.23170043201253E+01 0.145038259671E+03
17 4 0.24757332930697E+01 0.145038259671E+03
18 4 0.22568130106030E+01 0.145038259671E+03
19 4 0.21287757927244E+01 0.145038259671E+03