Skip to content

Commit

Permalink
Print thresholds and bfgs errors
Browse files Browse the repository at this point in the history
  • Loading branch information
Sasha Fonari committed Dec 11, 2020
1 parent 2fcda6b commit e470d2e
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 2 deletions.
6 changes: 6 additions & 0 deletions Modules/bfgs_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -262,6 +262,12 @@ SUBROUTINE bfgs( pos_in, h, energy, grad_in, fcell, fixion, scratch, stdout,&
IF ( .NOT. conv_bfgs .AND. ( tr_min_hit > 1 ) ) CALL infomsg( 'bfgs',&
'history already reset at previous step: stopping' )
conv_bfgs = conv_bfgs .OR. ( tr_min_hit > 1 )
!
WRITE(stdout, '(5X,"Energy error",T30,"= ",1PE12.1)') energy_error
WRITE(stdout, '(5X,"Gradient error",T30,"= ",1PE12.1)') grad_error
IF( lmovecell ) WRITE(stdout, &
'(5X,"Cell gradient error",T30,"= ",1PE12.1,/)') cell_error
!
IF ( conv_bfgs ) GOTO 1000
!
! ... some output is written
Expand Down
12 changes: 10 additions & 2 deletions PW/src/summary.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ SUBROUTINE summary()
USE constants, ONLY : amu_ry, rytoev
USE cell_base, ONLY : alat, ibrav, omega, at, bg, celldm, wmass
USE ions_base, ONLY : nat, atm, zv, tau, ntyp => nsp, ityp
USE cellmd, ONLY : calc
USE cellmd, ONLY : calc, lmovecell
USE ions_base, ONLY : amass
USE gvect, ONLY : ecutrho, ngm, ngm_g, gcutm
USE gvecs, ONLY : doublegrid, ngms, ngms_g, gcutms
Expand Down Expand Up @@ -52,6 +52,7 @@ SUBROUTINE summary()
USE exx, ONLY : ecutfock
USE fcp_variables, ONLY : lfcpopt, lfcpdyn
USE fcp, ONLY : fcp_summary
USE relax, ONLY : epse, epsf, epsp ! threshold on pressure
!
IMPLICIT NONE
!
Expand Down Expand Up @@ -94,6 +95,8 @@ SUBROUTINE summary()
WRITE( stdout, 103) nbnd, ecutwfc, ecutrho
IF ( dft_is_hybrid () ) WRITE( stdout, 104) ecutfock
IF ( lscf) WRITE( stdout, 105) tr2, mixing_beta, nmix, mixing_style
IF ( lmd .OR. lbfgs ) WRITE (stdout, 106) epse, epsf
IF ( lmovecell ) WRITE (stdout, 107) epsp
!
100 FORMAT( /,/,5X, &
& 'bravais-lattice index = ',I12,/,5X, &
Expand All @@ -112,9 +115,14 @@ SUBROUTINE summary()
104 FORMAT(5X, &
& 'cutoff for Fock operator = ',F12.4,' Ry')
105 FORMAT(5X, &
& 'convergence threshold = ',1PE12.1,/,5X, &
& 'scf convergence threshold = ',1PE12.1,/,5X, &
& 'mixing beta = ',0PF12.4,/,5X, &
& 'number of iterations used = ',I12,2X,A,' mixing')
106 FORMAT(5X, &
& 'energy convergence thresh.= ',1PE12.1,/,5X, &
& 'force convergence thresh. = ',1PE12.1)
107 FORMAT(5X, &
& 'press convergence thresh. = ',1PE12.1)
!
call write_dft_name ( )
!
Expand Down

0 comments on commit e470d2e

Please sign in to comment.