- cpr.f90 changed such that when convergence is achieved an additional step is

performed in order to print out relevant physical quantities.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4758 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
cavazzon 2008-03-24 18:14:55 +00:00
parent 2555d5b26f
commit 2a21de27d6
3 changed files with 12 additions and 13 deletions

View File

@ -208,8 +208,8 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
CALL start_clock( 'total_time' ) CALL start_clock( 'total_time' )
! !
nfi = nfi + 1 nfi = nfi + 1
tlast = ( nfi == nomore ) tlast = ( nfi == nomore ) .OR. tlast
ttprint = ( MOD( nfi, iprint ) == 0 ).or.tlast ttprint = ( MOD( nfi, iprint ) == 0 ) .OR. tlast
tfile = ( MOD( nfi, iprint ) == 0 ) tfile = ( MOD( nfi, iprint ) == 0 )
! !
IF ( abivol ) THEN IF ( abivol ) THEN
@ -780,7 +780,8 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
! !
delta_etot = ABS( epre - enow ) delta_etot = ABS( epre - enow )
! !
tstop = check_stop_now() tstop = check_stop_now() .OR. tlast
!
tconv = .FALSE. tconv = .FALSE.
! !
IF ( tconvthrs%active ) THEN IF ( tconvthrs%active ) THEN
@ -807,6 +808,8 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
IF ( lwf .AND. tfirst ) tconv = .FALSE. IF ( lwf .AND. tfirst ) tconv = .FALSE.
! !
IF ( tconv ) THEN IF ( tconv ) THEN
!
tlast = .TRUE.
! !
IF ( ionode ) THEN IF ( ionode ) THEN
! !
@ -823,8 +826,6 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
! !
END IF END IF
! !
tstop = tstop .OR. tconv
!
IF ( lwf ) & IF ( lwf ) &
CALL wf_closing_options( nfi, c0, cm, bec, becdr, eigr, eigrb, taub, & CALL wf_closing_options( nfi, c0, cm, bec, becdr, eigr, eigrb, taub, &
irb, ibrav, b1, b2, b3, taus, tausm, vels, & irb, ibrav, b1, b2, b3, taus, tausm, vels, &
@ -833,7 +834,7 @@ SUBROUTINE cprmain( tau_out, fion_out, etot_out )
ekincm, xnhh0, xnhhm, vnhh, velh, ecutp, & ekincm, xnhh0, xnhhm, vnhh, velh, ecutp, &
ecutw, delt, celldm, fion, tps, z0t, f, rhor ) ecutw, delt, celldm, fion, tps, z0t, f, rhor )
! !
IF ( ( nfi >= nomore ) .OR. tstop ) EXIT main_loop IF ( tstop ) EXIT main_loop
! !
END DO main_loop END DO main_loop
! !

View File

@ -6,8 +6,8 @@
! or http://www.gnu.org/copyleft/gpl.txt . ! or http://www.gnu.org/copyleft/gpl.txt .
! !
! ---------------------------------------------- ! ----------------------------------------------
! This Module written by Carlo Cavazzoni ! This Subroutines written by Carlo Cavazzoni
! Last modified April 2003 ! Last modified December 2008
! ---------------------------------------------- ! ----------------------------------------------
#include "f_defs.h" #include "f_defs.h"

View File

@ -192,6 +192,8 @@
fccc = 1.0d0 fccc = 1.0d0
nstep_this_run = 0 nstep_this_run = 0
IF( tcg ) &
CALL errore( ' fpmd ', ' CG not allowed, use CP instead ', 1 )
ttexit = .FALSE. ttexit = .FALSE.
@ -214,11 +216,7 @@
! ... set the right flags for the current MD step ! ... set the right flags for the current MD step
! !
IF ( .NOT. tcg ) THEN ttprint = ( MOD(nfi, iprint) == 0 ) .OR. ( iprsta > 2 ) .OR. ttexit
ttprint = ( MOD(nfi, iprint) == 0 ) .OR. ( iprsta > 2 ) .OR. ttexit
ELSE
ttprint = .TRUE.
ENDIF
! !
ttsave = MOD(nfi, isave) == 0 ttsave = MOD(nfi, isave) == 0
! !