cumulative module updated

This commit is contained in:
zx199323 2020-07-03 16:37:44 -04:00
parent 5589beee2e
commit 1f2f97aacf
1 changed files with 157 additions and 148 deletions

View File

@ -35,16 +35,18 @@
!!
!-----------------------------------------------------------------------
USE kinds, ONLY : DP, i4b
USE constants_epw, ONLY : two, zero, ryd2ev, ryd2mev, ci
USE constants_epw, ONLY : kelvin2eV, two, zero, ryd2ev, ryd2mev, ci
USE constants, ONLY : pi
USE io_global, ONLY : stdout
USE io_var, ONLY : iospectral_sup, iospectral_cum
USE epwcom, ONLY : eptemp, wmin_specfun, wmax_specfun, nw_specfun, &
bnd_cum
USE elph2, ONLY : ibndmin, ibndmax
bnd_cum, nstemp
USE elph2, ONLY : ibndmin, ibndmax, gtemp
!
IMPLICIT NONE
!
CHARACTER(LEN = 20) :: tp
CHARACTER(LEN = 256) :: filespecsup
CHARACTER(LEN = 64) :: line
!! Auxiliary string
CHARACTER(LEN = 64) :: filespec
@ -67,6 +69,8 @@
!! Total number of k-points
INTEGER :: i0
!! Energy index of Fermi level (w=0)
INTEGER :: itemp
!! Counter on temperatures
INTEGER :: ierr
!! Error status
REAL(KIND = DP) :: dw
@ -107,7 +111,10 @@
WRITE(stdout, '(5x,a)') 'Warning: the routine is sequential but very fast.'
WRITE(stdout, '(5x,a/)') REPEAT('=',75)
!
OPEN (UNIT = iospectral_sup, FILE = 'specfun_sup.elself', STATUS = 'old', IOSTAT = ios)
DO itemp = 1, nstemp
WRITE(tp, "(f8.3)") gtemp(itemp) * ryd2ev / kelvin2eV
filespecsup = 'specfun_sup.elself.' // trim(adjustl(tp)) // 'K'
OPEN (UNIT = iospectral_sup, FILE = filespecsup, STATUS = 'old', IOSTAT = ios)
IF (ios /= 0) CALL errore('spectral_cumulant', 'opening file specfun_sup.elself', ABS(ios))
!
! determine number of k points, ibndmin, ibndmax
@ -127,7 +134,7 @@
ibndmax = i2
WRITE(stdout, '(5x,a/)') "Read self-energy from file specfun_sup.elself"
WRITE(stdout, '(5x,a,i4,a,i4,a,i4,a,f12.6/)') "Check: nk = ", nk, &
", ibndmin = ", ibndmin, ", ibndmax = ", ibndmax, " kbT (eV) = ", eptemp * ryd2ev
", ibndmin = ", ibndmin, ", ibndmax = ", ibndmax, " kbT (eV) = ", gtemp(itemp) * ryd2ev
!
ALLOCATE(ww(nw_specfun), STAT = ierr)
IF (ierr /= 0) CALL errore('spectral_cumulant', 'Error allocating ww', 1)
@ -170,12 +177,13 @@
CLOSE(iospectral_sup)
!
! open file for cumulant spectral function
WRITE(tp, "(f8.3)") gtemp(itemp) * ryd2ev / kelvin2eV
IF (bnd_cum < 10) THEN
WRITE(filespec, '(a,i1,a)') 'specfun_cum', bnd_cum, '.elself'
WRITE(filespec, '(a,i1,a,a,a)') 'specfun_cum', bnd_cum, '.elself.', trim(adjustl(tp)), 'K'
ELSEIF (bnd_cum > 9 .AND. bnd_cum < 100) THEN
WRITE(filespec, '(a,i2,a)') 'specfun_cum', bnd_cum, '.elself'
WRITE(filespec, '(a,i2,a,a,a)') 'specfun_cum', bnd_cum, '.elself.', trim(adjustl(tp)), 'K'
ELSE
WRITE(filespec, '(a,i3,a)') 'specfun_cum', bnd_cum, '.elself'
WRITE(filespec, '(a,i3,a,a,a)') 'specfun_cum', bnd_cum, '.elself.', trim(adjustl(tp)), 'K'
ENDIF
OPEN(UNIT = iospectral_cum, FILE = filespec)
!
@ -255,6 +263,7 @@
IF (ierr /= 0) CALL errore('spectral_cumulant', 'Error deallocating a_ct', 1)
DEALLOCATE(a_tmp, STAT = ierr)
IF (ierr /= 0) CALL errore('spectral_cumulant', 'Error deallocating a_tmp', 1)
ENDDO !itemp
!
!-----------------------------------------------------------------------
END SUBROUTINE spectral_cumulant