Added prefix.EXIT feature to the PH program - Kostya

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3538 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
kkudin 2006-11-15 23:43:43 +00:00
parent 2452b9805e
commit edb1613564
6 changed files with 27 additions and 37 deletions

View File

@ -18,7 +18,7 @@ SUBROUTINE phqscf
!
USE io_global, ONLY : stdout, ionode
USE check_stop, ONLY: max_seconds
! USE check_stop, ONLY: max_seconds
USE pwcom
USE kinds, ONLY : DP
USE phcom

View File

@ -24,7 +24,7 @@ subroutine solve_e
USE io_global, ONLY : stdout, ionode
USE io_files, ONLY : prefix, iunigk
use pwcom
USE check_stop, ONLY : max_seconds
USE check_stop, ONLY : check_stop_now
USE wavefunctions_module, ONLY : evc
USE kinds, ONLY : DP
USE becmod, ONLY : becp
@ -364,16 +364,14 @@ subroutine solve_e
if (okvan) write (iunrec) int3
close (unit = iunrec, status = 'keep')
tcpu = get_clock ('PHONON')
if (convt .or. tcpu > max_seconds) goto 155
if (check_stop_now()) then
call stop_ph (.false.)
goto 155
endif
if (convt) goto 155
enddo
155 continue
if (tcpu > max_seconds) then
WRITE( stdout, "(/,5x,'Stopping for time limit ',2f10.0)") tcpu, &
max_seconds
call stop_ph (.false.)
endif
deallocate (eprec)
deallocate (h_diag)
deallocate (ps)

View File

@ -25,7 +25,7 @@ subroutine solve_e2
USE wavefunctions_module, ONLY: evc
USE phcom
USE ramanm
USE check_stop, ONLY: max_seconds
USE check_stop, ONLY: check_stop_now
implicit none
real(DP) :: thresh, weight, avg_iter, dr2
@ -63,9 +63,6 @@ subroutine solve_e2
! the record number
! integer variable for I/O control
real(DP) :: tcpu, get_clock
! timing variables
character (len=256) :: flmixdpot
! the name of the file with the
! mixing potential
@ -263,16 +260,14 @@ subroutine solve_e2
if (okvan) write (iunrec) int3
close (unit = iunrec, status = 'keep')
tcpu = get_clock ('PHONON')
if (convt .or. tcpu > max_seconds) goto 155
if ( check_stop_now() ) then
call stop_ph (.false.)
goto 155
endif
if ( convt ) goto 155
enddo
155 continue
if (tcpu > max_seconds) then
write (6, "(/,5x,'Stopping for time limit ',2f10.0)") tcpu, &
max_seconds
call stop_ph (.false.)
endif
deallocate (dvscfin )
if (doublegrid) deallocate (dvscfins )
deallocate (dvscfout )

View File

@ -24,7 +24,7 @@ subroutine solve_e_fpol ( iw )
USE io_global, ONLY : stdout, ionode
USE io_files, ONLY : prefix, iunigk
use pwcom
USE check_stop, ONLY : max_seconds
USE check_stop, ONLY : check_stop_now
USE wavefunctions_module, ONLY : evc
USE kinds, ONLY : DP
USE becmod, ONLY : becp
@ -388,16 +388,13 @@ subroutine solve_e_fpol ( iw )
!if (okvan) write (iunrec) int3
!close (unit = iunrec, status = 'keep')
tcpu = get_clock ('PHONON')
if (convt .or. tcpu > max_seconds) goto 155
if (check_stop_now()) then
call stop_ph (.false.)
goto 155
endif
if (convt) goto 155
enddo
155 continue
if (tcpu > max_seconds) then
WRITE( stdout, "(/,5x,'Stopping for time limit ',2f10.0)") tcpu, &
max_seconds
call stop_ph (.false.)
endif
deallocate (eprec)
deallocate (h_diag)
deallocate (ps)

View File

@ -24,7 +24,7 @@ subroutine solve_linter (irr, imode0, npe, drhoscf)
USE ions_base, ONLY : nat
USE io_global, ONLY : stdout, ionode
USE io_files, ONLY : prefix, iunigk
USE check_stop, ONLY : max_seconds
USE check_stop, ONLY : check_stop_now
USE wavefunctions_module, ONLY : evc
USE constants, ONLY : degspin
USE kinds, ONLY : DP
@ -549,14 +549,13 @@ subroutine solve_linter (irr, imode0, npe, drhoscf)
close (unit = iunrec, status = 'keep')
call stop_clock ('write_rec')
if (convt .or. tcpu > max_seconds) goto 155
if (check_stop_now()) then
call stop_ph (.false.)
goto 155
endif
if (convt) goto 155
enddo
155 iter0=0
if (tcpu > max_seconds .and..not.convt) then
WRITE( stdout, '(/,5x,"Stopping for time limit ",2f10.0)') tcpu, max_seconds
call stop_ph (.false.)
endif
!
! There is a part of the dynamical matrix which requires the integral
! self consistent change of the potential and the variation of the ch

3
TODO
View File

@ -111,7 +111,8 @@ POSTPROCESSING
PH, D3, Gamma
- stop with 'prefix.EXIT' and restart
- stop with 'prefix.EXIT' and restart (PH now has it; D3 & Gamma do not
have any infrastructure for stopping like this)
- use charge mixing instead of potential mixing