The main loop over q in the phonon code moved to a separate subroutine that

can be called by other external drivers. 


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@10672 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
dalcorso 2014-01-07 17:06:57 +00:00
parent a0d66bca95
commit c717458205
3 changed files with 125 additions and 88 deletions

View File

@ -60,6 +60,7 @@ dfile_autoname.o \
dfile_star.o \
dgradcorr.o \
dielec.o \
do_phonon.o \
drho.o \
drhodv.o \
drhodvloc.o \

116
PHonon/PH/do_phonon.f90 Normal file
View File

@ -0,0 +1,116 @@
!
! Copyright (C) 2001-2013 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!-----------------------------------------------------------------------
SUBROUTINE do_phonon(auxdyn)
!-----------------------------------------------------------------------
!
! ... This is the main driver of the phonon code.
! ... It assumes that the preparatory stuff has been already done.
! ... When the code calls this routine it has already read input
! ... decided which irreducible representations have to be calculated
! ... and it has set the variables that decide which work this routine
! ... will do. The parallel stuff has been already setup by the calling
! ... codes. This routine makes the two loops over
! ... the q points and the irreps and does only the calculations
! ... that have been decided by the driver routine.
! ... At a generic q, if necessary it recalculates the band structure
! ... calling pwscf again.
! ... Then it can calculate the response to an atomic displacement,
! ... the dynamical matrix at that q, and the electron-phonon
! ... interaction at that q. At q=0 it can calculate the linear response
! ... to an electric field perturbation and hence the dielectric
! ... constant, the Born effective charges and the polarizability
! ... at imaginary frequencies.
! ... At q=0, from the second order response to an electric field,
! ... it can calculate also the electro-optic and the raman tensors.
!
USE disp, ONLY : nqs
USE control_ph, ONLY : epsil, trans, qplot, only_init, &
only_wfc
USE el_phon, ONLY : elph, elph_mat, elph_simple
IMPLICIT NONE
!
CHARACTER (LEN=256), INTENT(IN) :: auxdyn
INTEGER :: iq
LOGICAL :: do_band, do_iq, setup_pw
!
DO iq = 1, nqs
!
CALL prepare_q(auxdyn, do_band, do_iq, setup_pw, iq)
!
! If this q is not done in this run, cycle
!
IF (.NOT.do_iq) CYCLE
!
! If necessary the bands are recalculated
!
IF (setup_pw) CALL run_nscf(do_band, iq)
!
! If only_wfc=.TRUE. the code computes only the wavefunctions
!
IF (only_wfc) GOTO 100
!
! Initialize the quantities which do not depend on
! the linear response of the system
!
CALL initialize_ph()
!
! electric field perturbation
!
IF (epsil) CALL phescf()
!
! IF only_init is .true. the code computes only the
! initialization parts.
!
IF (only_init) GOTO 100
!
! phonon perturbation
!
IF ( trans ) THEN
!
CALL phqscf()
CALL dynmatrix_new(iq)
!
END IF
!
CALL rotate_dvscf_star(iq)
!
! electron-phonon interaction
!
IF ( elph ) THEN
!
IF ( .NOT. trans ) THEN
!
CALL dvanqq()
IF ( elph_mat ) THEN
CALL ep_matrix_element_wannier()
ELSE
CALL elphon()
END IF
!
END IF
!
IF ( elph_mat ) THEN
CALL elphsum_wannier(iq)
ELSEIF( elph_simple ) THEN
CALL elphsum_simple()
ELSE
CALL elphsum()
END IF
!
END IF
!
! ... cleanup of the variables for the next q point
!
100 CALL clean_pw_ph(iq)
!
END DO
END SUBROUTINE do_phonon

View File

@ -12,17 +12,8 @@ PROGRAM phonon
! ... This is the main driver of the phonon code.
! ... It reads all the quantities calculated by pwscf, it
! ... checks if some recover file is present and determines
! ... which calculation needs to be done. Finally, it makes
! ... a loop over the q points. At a generic q, if necessary it
! ... recalculates the band structure calling pwscf again.
! ... Then it can calculate the response to an atomic displacement,
! ... the dynamical matrix at that q, and the electron-phonon
! ... interaction at that q. At q=0 it can calculate the linear response
! ... to an electric field perturbation and hence the dielectric
! ... constant, the Born effective charges and the polarizability
! ... at imaginary frequencies.
! ... At q=0, from the second order response to an electric field,
! ... it can calculate also the electro-optic and the raman tensors.
! ... which calculation needs to be done. Finally, it calls do_phonon
! ... that does the loop over the q points.
! ... Presently implemented:
! ... dynamical matrix (q/=0) NC [4], US [4], PAW [4]
! ... dynamical matrix (q=0) NC [5], US [5], PAW [4]
@ -49,14 +40,10 @@ PROGRAM phonon
! [9] ? + External Electric field
! [10] ? + nonperiodic boundary conditions.
USE disp, ONLY : nqs
USE control_ph, ONLY : epsil, trans, bands_computed, qplot, only_init, &
only_wfc
USE el_phon, ONLY : elph, elph_mat, elph_simple
USE output, ONLY : fildrho
USE control_ph, ONLY : bands_computed, qplot
USE check_stop, ONLY : check_stop_init
USE ph_restart, ONLY : ph_writefile
USE mp_global, ONLY: mp_startup, nimage
USE mp_global, ONLY : mp_startup
USE environment, ONLY : environment_start
!
@ -83,76 +70,9 @@ PROGRAM phonon
!
CALL check_initial_status(auxdyn)
!
DO iq = 1, nqs
! ... Do the loop over the q points and irreps.
!
CALL prepare_q(auxdyn, do_band, do_iq, setup_pw, iq)
!
! If this q is not done in this run, cycle
!
IF (.NOT.do_iq) CYCLE
!
! If necessary the bands are recalculated
!
IF (setup_pw) CALL run_nscf(do_band, iq)
!
! If only_wfc=.TRUE. the code computes only the wavefunctions
!
IF (only_wfc) GOTO 100
!
! Initialize the quantities which do not depend on
! the linear response of the system
!
CALL initialize_ph()
!
! electric field perturbation
!
IF (epsil) CALL phescf()
!
! IF only_init is .true. the code computes only the initialization parts.
!
IF (only_init) GOTO 100
!
! phonon perturbation
!
IF ( trans ) THEN
!
CALL phqscf()
CALL dynmatrix_new(iq)
!
END IF
!
call rotate_dvscf_star(iq)
!
! electron-phonon interaction
!
IF ( elph ) THEN
!
IF ( .NOT. trans ) THEN
!
CALL dvanqq()
IF ( elph_mat ) then
call ep_matrix_element_wannier()
ELSE
CALL elphon()
END IF
!
END IF
!
IF ( elph_mat ) then
call elphsum_wannier(iq)
ELSEIF( elph_simple ) then
CALL elphsum_simple()
ELSE
CALL elphsum()
END IF
!
END IF
!
! ... cleanup of the variables for the next q point
!
100 CALL clean_pw_ph(iq)
!
END DO
CALL do_phonon(auxdyn)
!
! reset the status of the recover files
!