Yet another problem with phonon + pools + lsda + wf_collect solved (maybe).

The solution is not especially satisfactory but it seems to work.

Calls to "check_stop_now" removed from c_bands. They are likely to
interfere with neb in a scf calculation; with phonons in a nscf calculation;
it is very unlikely that they will be useful in a band structure calculation.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3795 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2007-02-19 15:15:45 +00:00
parent 7059ece72a
commit 880ff250b7
2 changed files with 22 additions and 36 deletions

View File

@ -24,16 +24,12 @@ SUBROUTINE c_bands( iter, ik_, dr2 )
USE uspp, ONLY : vkb, nkb
USE gvect, ONLY : g, nrxx, nr1, nr2, nr3
USE wvfct, ONLY : et, nbnd, npwx, igk, npw, current_k
USE control_flags, ONLY : ethr, lbands, isolve, reduce_io
USE control_flags, ONLY : ethr, isolve, reduce_io
USE ldaU, ONLY : lda_plus_u, swfcatom
USE lsda_mod, ONLY : current_spin, lsda, isk
USE noncollin_module, ONLY : noncolin, npol
USE wavefunctions_module, ONLY : evc
USE bp, ONLY : lelfield
#ifdef __PARA
USE mp_global, ONLY : npool, kunit
#endif
USE check_stop, ONLY : check_stop_now
!
IMPLICIT NONE
!
@ -136,23 +132,6 @@ SUBROUTINE c_bands( iter, ik_, dr2 )
!
CALL save_in_cbands( iter, ik, dr2 )
!
! IF ( lbands) THEN
#ifdef __PARA
! ... beware: with pools, if the number of k-points on different
! ... pools differs, make sure that all processors are still in
! ... the loop on k-points before checking for stop condition
!
! ... FIXME: stopping here will make trouble in phonon
!
!!!nkdum = kunit * ( nkstot / kunit / npool )
!!!IF (ik .le. nkdum) THEN
!!! IF (check_stop_now()) call stop_run(.FALSE.)
!!!ENDIF
#else
!!!IF ( check_stop_now() ) call stop_run(.FALSE.)
#endif
!ENDIF
!
END DO k_loop
!
ik_ = 0
@ -591,12 +570,11 @@ SUBROUTINE c_bands_nscf( ik_ )
USE uspp, ONLY : vkb, nkb
USE gvect, ONLY : g, nrxx, nr1, nr2, nr3
USE wvfct, ONLY : et, nbnd, npwx, igk, npw, current_k
USE control_flags, ONLY : ethr, lbands, isolve
USE control_flags, ONLY : ethr, isolve
USE ldaU, ONLY : lda_plus_u, swfcatom
USE lsda_mod, ONLY : current_spin, lsda, isk
USE noncollin_module, ONLY : noncolin, npol
USE wavefunctions_module, ONLY : evc
USE check_stop, ONLY : check_stop_now
!
IMPLICIT NONE
!
@ -700,10 +678,6 @@ SUBROUTINE c_bands_nscf( ik_ )
!
CALL save_in_cbands( iter, ik, dr2 )
!
! ... FIXME: this call is a source of trouble with phonons
!
!!! IF ( check_stop_now() ) call stop_run(.FALSE.)
!
END DO k_loop
!
CALL poolreduce( 1, avg_iter )

View File

@ -147,12 +147,20 @@ MODULE pw_restart
!
! ... create the k-points subdirectories
!
IF ( nspin == 2 ) THEN
num_k_points = nkstot / 2
ELSE
num_k_points = nkstot
END IF
!
IF (lkpoint_dir) THEN
DO i = 1, nkstot
!
DO i = 1, num_k_points
!
CALL create_directory( kpoint_dir( dirname, i ) )
!
END DO
!
END IF
!
IF ( nkstot > 0 ) THEN
@ -358,10 +366,6 @@ MODULE pw_restart
NELUP = nbnd, NELDW = nbnd, F_INP = f_inp )
END IF
!
num_k_points = nkstot
!
IF ( nspin == 2 ) num_k_points = nkstot / 2
!
IF ( ionode ) THEN
!
!-------------------------------------------------------------------------------
@ -584,6 +588,8 @@ MODULE pw_restart
! ... wavefunctions
!
IF ( nspin == 2 ) THEN
!
! ... beware: with pools, this is correct only on ionode
!
ispin = isk(ik)
!
@ -2497,7 +2503,10 @@ MODULE pw_restart
IF ( nspin == 2 ) THEN
!
ispin = 1
isk(ik) = 1
!
! ... no need to read isk here: they are read from band structure
! ... and correctly distributed across pools in read_file
!!! isk(ik) = 1
!
IF ( ionode ) THEN
!
@ -2518,7 +2527,9 @@ MODULE pw_restart
!
ispin = 2
ik_eff = ik + num_k_points
isk(ik_eff) = 2
!
! ... no need to read isk here (see above why)
!isk(ik_eff) = 2
!
IF ( ionode ) THEN
!
@ -2539,7 +2550,8 @@ MODULE pw_restart
!
ELSE
!
isk(ik) = 1
! ... no need to read isk here (see above why)
!isk(ik) = 1
!
IF ( noncolin ) THEN
!