nrapp or nat_todo with gamma_gamma tricks is not programmed. Added

a check to avoid these cases and a new input variable to disable
gamma_gamma tricks from input.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@5498 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
dalcorso 2009-04-02 20:37:46 +00:00
parent f0148c65c7
commit 1114664827
3 changed files with 11 additions and 3 deletions

View File

@ -20,7 +20,7 @@ subroutine bcast_ph_input ( )
USE control_ph, ONLY : start_irr, last_irr, start_q, last_q, nmix_ph, &
niter_ph, lnoloc, alpha_mix, tr2_ph, lrpa, recover, &
ldisp, lnscf, elph, reduce_io, zue, epsil, trans, &
lgamma
lgamma, nogg
USE gamma_gamma, ONLY : asr
USE disp, ONLY : iq1, iq2, iq3, nq1, nq2, nq3
USE freq_ph, ONLY : fpol, nfs, fiu
@ -53,6 +53,7 @@ subroutine bcast_ph_input ( )
call mp_bcast (asr, ionode_id)
call mp_bcast (lrpa, ionode_id)
call mp_bcast (lnoloc, ionode_id)
call mp_bcast (nogg, ionode_id)
!
! integers
!

View File

@ -329,6 +329,7 @@ MODULE control_ph
ldisp, &! if .TRUE. the run calculates full phonon dispersion
reduce_io, &! if .TRUE. reduces needed I/O
done_bands, &! if .TRUE. the bands have been calculated
nogg, &! if .TRUE. gamma_gamma tricks are disabled
all_done, &! if .TRUE. all representations have been done
xml_not_of_pw ! if .TRUE. the xml file has been written by ph.
!

View File

@ -32,7 +32,7 @@ SUBROUTINE phq_readin()
USE lsda_mod, ONLY : lsda, nspin
USE printout_base, ONLY : title
USE control_ph, ONLY : maxter, alpha_mix, lgamma, lgamma_gamma, epsil, &
zue, trans, reduce_io, &
zue, trans, reduce_io, nogg, &
elph, tr2_ph, niter_ph, nmix_ph, lnscf, &
ldisp, recover, lrpa, lnoloc, start_irr, &
last_irr, start_q, last_q
@ -81,7 +81,7 @@ SUBROUTINE phq_readin()
lnscf, ldisp, nq1, nq2, nq3, iq1, iq2, iq3, &
eth_rps, eth_ns, lraman, elop, dek, recover, &
fpol, asr, lrpa, lnoloc, start_irr, last_irr, &
start_q, last_q
start_q, last_q, nogg
! tr2_ph : convergence threshold
! amass : atomic masses
! alpha_mix : the mixing parameter
@ -113,6 +113,7 @@ SUBROUTINE phq_readin()
! last_q :
! start_irr : does the irred. representation from start_irr to last_irr
! last_irr :
! nogg : if .true. gamma_gamma tricks are not used
!
IF ( .NOT. ionode ) GOTO 400
@ -160,6 +161,7 @@ SUBROUTINE phq_readin()
fildvscf = ' '
lnscf = .TRUE.
ldisp = .FALSE.
nogg = .FALSE.
nq1 = 0
nq2 = 0
nq3 = 0
@ -311,6 +313,7 @@ SUBROUTINE phq_readin()
.AND.(ABS(xk(2,1))<1.D-12) &
.AND.(ABS(xk(3,1))<1.D-12) )
ENDIF
IF (nogg) lgamma_gamma=.FALSE.
!
IF (lgamma) THEN
nksq = nks
@ -366,6 +369,9 @@ SUBROUTINE phq_readin()
nat_todo = 0
list (1) = modenum
ENDIF
IF ((nat_todo /= 0 .or. nrapp /= 0 ) .and. lgamma_gamma) CALL errore( &
'phq_readin', 'gamma_gamma tricks with nat_todo or nrapp &
& not available. Use nogg=.true.', 1)
IF (modenum > 0 .OR. ldisp .OR. lraman ) lgamma_gamma=.FALSE.
IF (.not.lgamma_gamma) asr=.FALSE.