bfgs reads and writes from file, whose name is built from tmp_dir, prefix, and

a file name. tmp_dir was passed as a variable in the call, prefix was passed
via a module, the file name is hardcoded. It seems to me more sensible to pass
the file name including the path as a single variable.
This commit is contained in:
Paolo Giannozzi 2020-12-29 09:49:48 +01:00
parent 43efc5bc00
commit 81fc1e5159
2 changed files with 26 additions and 25 deletions

View File

@ -44,7 +44,6 @@ MODULE bfgs_module
!
!
USE kinds, ONLY : DP
USE io_files, ONLY : iunbfgs, prefix
USE constants, ONLY : eps4, eps8, eps16, RYTOEV
USE cell_base, ONLY : iforceh ! FIXME: should be passed as argument
!
@ -63,7 +62,10 @@ MODULE bfgs_module
!
SAVE
!
CHARACTER (len=18) :: fname="energy" ! name of the function to be minimized
CHARACTER (len=18) :: fname="energy"
!! name of the function to be minimized
CHARACTER (len=256):: bfgs_file=" "
!! name of file (with path) used to store and retrieve the status
!
REAL(DP), ALLOCATABLE :: &
pos(:), &! positions + cell
@ -145,7 +147,7 @@ CONTAINS
END SUBROUTINE init_bfgs
!------------------------------------------------------------------------
!
SUBROUTINE bfgs( pos_in, h, nelec, energy, grad_in, fcell, felec, scratch, &
SUBROUTINE bfgs( filebfgs, pos_in, h, nelec, energy, grad_in, fcell, felec, &
energy_thr, grad_thr, cell_thr, fcp_thr, energy_error, grad_error, &
cell_error, fcp_error, lmovecell, lfcp, fcp_cap, &
step_accepted, stop_bfgs, istep )
@ -153,10 +155,10 @@ CONTAINS
!
! ... list of input/output arguments :
!
! filebfgs : file name for storing and retrieving data
! pos : vector containing 3N coordinates of the system ( x )
! energy : energy of the system ( V(x) )
! grad : vector containing 3N components of grad( V(x) )
! scratch : scratch directory
! energy_thr : treshold on energy difference for BFGS convergence
! grad_thr : treshold on grad difference for BFGS convergence
! the largest component of grad( V(x) ) is considered
@ -178,7 +180,7 @@ CONTAINS
REAL(DP), INTENT(INOUT) :: grad_in(:)
REAL(DP), INTENT(INOUT) :: fcell(3,3)
REAL(DP), INTENT(INOUT) :: felec ! force on FCP
CHARACTER(LEN=*), INTENT(IN) :: scratch
CHARACTER(LEN=*), INTENT(IN) :: filebfgs
REAL(DP), INTENT(IN) :: energy_thr, grad_thr, cell_thr, fcp_thr
LOGICAL, INTENT(IN) :: lmovecell
LOGICAL, INTENT(IN) :: lfcp ! include FCP, or not ?
@ -197,6 +199,7 @@ CONTAINS
INTEGER, PARAMETER :: NADD = 9 + 1
!
!
IF ( bfgs_file == " ") bfgs_file = TRIM(filebfgs)
lwolfe=.false.
n = SIZE( pos_in ) + NADD
nat = size (pos_in) / 3
@ -270,7 +273,7 @@ CONTAINS
IF ( lmovecell ) fname="enthalpy"
IF ( lfcp ) fname = "grand-" // TRIM(fname)
!
CALL read_bfgs_file( pos, grad, energy, scratch, n, lfcp, fcp_cap )
CALL read_bfgs_file( pos, grad, energy, n, lfcp, fcp_cap )
!
scf_iter = scf_iter + 1
istep = scf_iter
@ -501,7 +504,7 @@ CONTAINS
! ... information required by next iteration is saved here ( this must
! ... be done before positions are updated )
!
CALL write_bfgs_file( pos, energy, grad, scratch )
CALL write_bfgs_file( pos, energy, grad )
!
! ... positions and cell are updated
!
@ -671,33 +674,30 @@ CONTAINS
END SUBROUTINE reset_bfgs
!
!------------------------------------------------------------------------
SUBROUTINE read_bfgs_file( pos, grad, energy, scratch, n, lfcp, fcp_cap )
SUBROUTINE read_bfgs_file( pos, grad, energy, n, lfcp, fcp_cap )
!------------------------------------------------------------------------
!
IMPLICIT NONE
!
REAL(DP), INTENT(INOUT) :: pos(:)
REAL(DP), INTENT(INOUT) :: grad(:)
CHARACTER(LEN=*), INTENT(IN) :: scratch
INTEGER, INTENT(IN) :: n
LOGICAL, INTENT(IN) :: lfcp
REAL(DP), INTENT(IN) :: fcp_cap
REAL(DP), INTENT(INOUT) :: energy
!
CHARACTER(LEN=256) :: bfgs_file
INTEGER :: iunbfgs
LOGICAL :: file_exists
REAL(DP) :: helec
!
!
bfgs_file = TRIM( scratch ) // TRIM( prefix ) // '.bfgs'
!
INQUIRE( FILE = TRIM( bfgs_file ) , EXIST = file_exists )
INQUIRE( FILE = bfgs_file, EXIST = file_exists )
!
IF ( file_exists ) THEN
!
! ... bfgs is restarted from file
!
OPEN( UNIT = iunbfgs, FILE = TRIM( bfgs_file ), &
OPEN( NEWUNIT = iunbfgs, FILE = bfgs_file, &
STATUS = 'UNKNOWN', ACTION = 'READ' )
!
READ( iunbfgs, * ) pos_p
@ -767,7 +767,7 @@ CONTAINS
END SUBROUTINE read_bfgs_file
!
!------------------------------------------------------------------------
SUBROUTINE write_bfgs_file( pos, energy, grad, scratch )
SUBROUTINE write_bfgs_file( pos, energy, grad )
!------------------------------------------------------------------------
!
IMPLICIT NONE
@ -775,11 +775,10 @@ CONTAINS
REAL(DP), INTENT(IN) :: pos(:)
REAL(DP), INTENT(IN) :: energy
REAL(DP), INTENT(IN) :: grad(:)
CHARACTER(LEN=*), INTENT(IN) :: scratch
!
INTEGER :: iunbfgs
!
OPEN( UNIT = iunbfgs, FILE = TRIM( scratch )//TRIM( prefix )//'.bfgs', &
STATUS = 'UNKNOWN', ACTION = 'WRITE' )
OPEN( NEWUNIT = iunbfgs, FILE = bfgs_file, STATUS = 'UNKNOWN', ACTION = 'WRITE' )
!
WRITE( iunbfgs, * ) pos
WRITE( iunbfgs, * ) grad
@ -1035,7 +1034,7 @@ CONTAINS
!
!------------------------------------------------------------------------
SUBROUTINE terminate_bfgs( energy, energy_thr, grad_thr, cell_thr, fcp_thr, &
lmovecell, lfcp, scratch )
lmovecell, lfcp )
!------------------------------------------------------------------------
!
USE io_files, ONLY : delete_if_present
@ -1043,7 +1042,6 @@ CONTAINS
IMPLICIT NONE
REAL(DP), INTENT(IN) :: energy, energy_thr, grad_thr, cell_thr, fcp_thr
LOGICAL, INTENT(IN) :: lmovecell, lfcp
CHARACTER(LEN=*), INTENT(IN) :: scratch
!
IF ( conv_bfgs ) THEN
!
@ -1070,7 +1068,8 @@ CONTAINS
WRITE( UNIT = stdout, &
& FMT = '(/,5X,"Final ",A," = ",F18.10," Ry")' ) fname, energy
!
CALL delete_if_present( TRIM( scratch ) // TRIM( prefix ) // '.bfgs' )
CALL delete_if_present( bfgs_file )
bfgs_file = " "
!
ELSE
!

View File

@ -26,7 +26,7 @@ SUBROUTINE move_ions( idone, ions_status )
!
USE constants, ONLY : e2, eps6, ry_kbar
USE io_global, ONLY : stdout
USE io_files, ONLY : tmp_dir
USE io_files, ONLY : tmp_dir, prefix
USE kinds, ONLY : DP
USE cell_base, ONLY : alat, at, bg, omega, cell_force, &
fix_volume, fix_area, ibrav, press, &
@ -66,6 +66,7 @@ SUBROUTINE move_ions( idone, ions_status )
REAL(DP) :: h(3,3), fcell(3,3)=0.d0, epsp1
REAL(DP) :: relec, felec, capacitance, tot_charge_
LOGICAL :: conv_ions
CHARACTER(LEN=256) :: filebfgs
!
! ... only one node does the calculation in the parallel case
!
@ -117,7 +118,8 @@ SUBROUTINE move_ions( idone, ions_status )
!
IF ( ANY( if_pos(:,:) == 1 ) .OR. lmovecell .OR. lfcp ) THEN
!
CALL bfgs( pos, h, relec, etot, grad, fcell, felec, tmp_dir, epse, &
filebfgs = TRIM(tmp_dir) // TRIM(prefix) // '.bfgs'
CALL bfgs( filebfgs, pos, h, relec, etot, grad, fcell, felec, epse, &
epsf, epsp1, fcp_eps, energy_error, gradient_error, cell_error, fcp_error, &
lmovecell, lfcp, capacitance, step_accepted, conv_ions, istep )
!
@ -197,7 +199,7 @@ SUBROUTINE move_ions( idone, ions_status )
IF ( ANY( if_pos(:,:) == 1 ) .OR. lmovecell .OR. lfcp ) THEN
!
CALL terminate_bfgs ( etot, epse, epsf, epsp, fcp_eps, &
lmovecell, lfcp, tmp_dir )
lmovecell, lfcp )
!
END IF
!
@ -206,7 +208,7 @@ SUBROUTINE move_ions( idone, ions_status )
ELSEIF ( idone == nstep ) THEN
!
CALL terminate_bfgs( etot, epse, epsf, epsp, fcp_eps, &
lmovecell, lfcp, tmp_dir )
lmovecell, lfcp )
!
ELSE
!