Metadynamics: first set of routines and variables removed

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@6362 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2010-02-05 17:17:26 +00:00
parent 6f44485a5c
commit 548f4a2f2f
15 changed files with 48 additions and 1061 deletions

View File

@ -492,232 +492,6 @@ SUBROUTINE compute_fes_grads( fii, lii, stat )
!
END SUBROUTINE compute_fes_grads
!
!----------------------------------------------------------------------------
SUBROUTINE metadyn()
!----------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE input_parameters, ONLY : electron_damping, ekin_conv_thr, etot_conv_thr
USE constraints_module, ONLY : constr_target, lagrange
USE cp_main_variables, ONLY : nfi
USE wave_base, ONLY : frice
USE control_flags, ONLY : nomore, ldamped, tconvthrs, tnosep, trane, &
ampre, nbeg, tfor, taurdr, ndr, ndw, isave
USE ions_base, ONLY : nat, nsp, ityp, if_pos
USE io_global, ONLY : stdout, ionode, ionode_id
USE io_files, ONLY : iunmeta, iunaxsf, tmp_dir
USE metadyn_vars, ONLY : ncolvar, fe_grad, new_target, to_target, &
metadyn_fmt, to_new_target, fe_step, &
metadyn_history, max_metadyn_iter, &
first_metadyn_iter, fe_nstep, sw_nstep, &
eq_nstep, dfe_acc, etot_av, gaussian_pos
USE metadyn_base, ONLY : add_gaussians, add_domain_potential, &
evolve_collective_vars
USE metadyn_io, ONLY : write_axsf_file, write_metadyn_restart
USE mp_global, ONLY : intra_image_comm
USE xml_io_base, ONLY : restart_dir, check_restartfile
USE time_step, ONLY : delt, set_time_step
USE mp, ONLY : mp_bcast
USE basic_algebra_routines
!
IMPLICIT NONE
!
CHARACTER(LEN=256) :: dirname
INTEGER :: iter
REAL(DP), ALLOCATABLE :: tau(:,:)
REAL(DP), ALLOCATABLE :: fion(:,:)
REAL(DP) :: etot, norm_fe_grad, delt_saved
LOGICAL :: do_first_scf
LOGICAL :: tnosep_saved
!
!
dirname = restart_dir( tmp_dir, ndw )
!
ALLOCATE( tau( 3, nat ), fion( 3, nat ) )
!
tnosep_saved = tnosep
!
taurdr = .TRUE.
nfi = 0
tfor = .FALSE.
!
tconvthrs%ekin = ekin_conv_thr
tconvthrs%derho = etot_conv_thr
!
delt_saved = delt
!
IF ( nbeg == - 1 ) THEN
!
WRITE( stdout, '(/,3X,"restarting from scratch",/)' )
!
do_first_scf = .TRUE.
!
nomore = 200
trane = .TRUE.
ampre = 0.02D0
!
tnosep = .FALSE.
!
tconvthrs%active = .TRUE.
!
! ... set a smaller value of time-step and a larger one for friction just
! ... for the wavefunction optimisation
!
frice = MIN( 0.2D0, 2.D0*electron_damping )
!
delt = MAX( 4.D0, 0.5D0*delt )
!
CALL set_time_step( delt )
!
ELSE IF ( check_restartfile( tmp_dir, ndr ) ) THEN
!
WRITE( stdout, '(/,3X,"restarting from file",/)' )
!
do_first_scf = .FALSE.
!
nbeg = 0
!
END IF
!
isave = nomore
!
CALL init_run()
!
IF ( do_first_scf ) THEN
!
! ... first we bring the system on the BO surface
!
CALL cprmain( tau, fion, etot )
!
CALL set_time_step( delt_saved )
!
END IF
!
tfor = .TRUE.
tnosep = tnosep_saved
iter = first_metadyn_iter
!
metadyn_loop: DO
!
IF ( iter > 0 ) THEN
!
CALL add_gaussians( iter )
!
CALL add_domain_potential()
!
norm_fe_grad = norm( fe_grad )
!
CALL evolve_collective_vars( norm_fe_grad )
!
! ... the system is "adiabatically" moved to the new constr_target
!
WRITE( stdout, '(/,5X,"adiabatic switch of the system ", &
& "to the new coarse-grained positions",/)' )
!
nfi = 0
nomore = sw_nstep
isave = nomore
!
tconvthrs%active = .FALSE.
to_new_target = .TRUE.
!
frice = electron_damping
!
IF ( ldamped ) CALL reset_vel()
!
CALL cprmain( tau, fion, etot )
!
END IF
!
iter = iter + 1
!
metadyn_history(:,iter) = gaussian_pos(:)
!
IF ( ionode ) CALL write_axsf_file( iter, tau, 1.D0 )
!
WRITE( stdout, '(/,5X,"calculation of the mean force",/)' )
!
nfi = 0
nomore = fe_nstep
isave = fe_nstep
!
IF ( ldamped ) THEN
!
tconvthrs%active = .TRUE.
!
frice = electron_damping
!
CALL reset_vel()
!
ELSE
!
frice = 0.D0
!
END IF
!
to_new_target = .FALSE.
!
dfe_acc(:) = 0.D0
!
CALL cprmain( tau, fion, etot )
!
! ... the averages are computed here
!
IF ( ldamped ) THEN
!
! ... zero temperature case
!
etot_av = etot
!
fe_grad(:) = - lagrange(1:ncolvar)
!
ELSE
!
! ... finite temperature case
!
etot_av = etot_av / DBLE( nomore )
!
fe_grad(:) = dfe_acc(:) / DBLE( fe_nstep - eq_nstep )
!
END IF
!
! ... notice that etot_av and fe_grad have been computed, so far, by
! ... ionode only: here we broadcast to all the other cpus
!
CALL mp_bcast( etot_av, ionode_id, intra_image_comm )
CALL mp_bcast( fe_grad, ionode_id, intra_image_comm )
!
IF ( ionode ) THEN
!
WRITE( UNIT = iunmeta, FMT = metadyn_fmt ) &
iter, constr_target(1:ncolvar), etot_av, gaussian_pos(:), fe_grad(:)
!
CALL flush_unit( iunmeta )
CALL flush_unit( iunaxsf )
!
END IF
!
CALL write_metadyn_restart( dirname, iter, tau, etot_av, 1.D0 )
!
IF ( iter >= max_metadyn_iter ) EXIT metadyn_loop
!
END DO metadyn_loop
!
IF ( ionode ) THEN
!
CLOSE( UNIT = iunaxsf )
CLOSE( UNIT = iunmeta )
!
END IF
!
tnosep = tnosep_saved
!
DEALLOCATE( tau, fion )
!
RETURN
!
END SUBROUTINE metadyn
!
!------------------------------------------------------------------------
SUBROUTINE reset_vel()
!------------------------------------------------------------------------

View File

@ -20,7 +20,7 @@ PROGRAM main
!
USE input, ONLY : read_input_file, iosys_pseudo, iosys
USE mp_global, ONLY : mp_startup
USE control_flags, ONLY : lneb, lsmd, lmetadyn, program_name
USE control_flags, ONLY : lneb, lsmd, program_name
USE environment, ONLY : environment_start
USE check_stop, ONLY : check_stop_init
!

View File

@ -33,7 +33,7 @@ MODULE input
USE read_namelists_module, ONLY : read_namelists
USE read_cards_module, ONLY : read_cards
USE input_parameters, ONLY : calculation, title
USE control_flags, ONLY : lneb, lpath, lwf, lmetadyn
USE control_flags, ONLY : lneb, lpath, lwf
USE printout_base, ONLY : title_ => title
USE io_global, ONLY : meta_ionode, stdout
USE xml_input, ONLY : xml_input_dump
@ -62,8 +62,6 @@ MODULE input
!
lpath = lneb
!
lmetadyn = ( TRIM( calculation ) == 'metadyn' )
!
lwf = ( TRIM( calculation ) == 'cp-wf' )
!
! ... Set job title and print it on standard output
@ -122,8 +120,7 @@ MODULE input
SUBROUTINE iosys()
!-------------------------------------------------------------------------
!
USE control_flags, ONLY : fix_dependencies, &
lconstrain, lmetadyn
USE control_flags, ONLY : fix_dependencies, lconstrain
USE io_global, ONLY : meta_ionode, stdout
USE ions_base, ONLY : nat, tau, ityp
USE constraints_module, ONLY : init_constraint
@ -154,8 +151,6 @@ MODULE input
!
IF ( lconstrain ) CALL init_constraint( nat, tau, ityp, 1.D0 )
!
IF ( lmetadyn ) CALL init_metadyn_vars()
!
! ... write to stdout input module information
!
CALL modules_info()
@ -171,7 +166,7 @@ MODULE input
USE io_global, ONLY : stdout
USE autopilot, ONLY : auto_check
USE autopilot, ONLY : restart_p
USE control_flags, ONLY : lcoarsegrained, ldamped, lmetadyn
USE control_flags, ONLY : lcoarsegrained, ldamped
USE control_flags, ONLY : ndw_ => ndw, &
ndr_ => ndr, &
iprint_ => iprint, &
@ -565,8 +560,6 @@ MODULE input
!
END SELECT
!
IF ( lmetadyn ) lcoarsegrained = .TRUE.
! ... Ions dynamics
tdampions_ = .FALSE.
@ -788,8 +781,7 @@ MODULE input
SUBROUTINE modules_setup()
!-------------------------------------------------------------------------
!
USE control_flags, ONLY : lconstrain, lneb, lmetadyn, &
tpre, thdyn, tksw
USE control_flags, ONLY : lconstrain, lneb, tpre, thdyn, tksw
USE constants, ONLY : amu_au, pi
!

View File

@ -43,8 +43,6 @@ SUBROUTINE cpr_loop( nloop )
!
USE kinds, ONLY : DP
USE ions_base, ONLY : nat
USE control_flags, ONLY : lmetadyn
USE metadyn_base, ONLY : metadyn_init
!
IMPLICIT NONE
!
@ -66,14 +64,6 @@ SUBROUTINE cpr_loop( nloop )
CALL errore( ' cpr_loop ', ' nat less or equal 0 ', 1 )
!
END IF
!
IF ( lmetadyn ) THEN
!
CALL metadyn_init( 'CP', tau )
!
CALL metadyn()
!
ELSE
!
CALL init_run()
!
@ -83,8 +73,6 @@ SUBROUTINE cpr_loop( nloop )
!
END DO
!
END IF
!
CALL terminate_run()
!
DEALLOCATE( tau, fion )

View File

@ -178,7 +178,6 @@ MODULE control_flags
lbfgs =.FALSE., &! if .TRUE. the calc. is a relaxation based on BFGS
lmd =.FALSE., &! if .TRUE. the calc. is a dynamics
llang =.FALSE., &! if .TRUE. the calc. is Langevin dynamics
lmetadyn=.FALSE., &! if .TRUE. the calc. is meta-dynamics
lpath =.FALSE., &! if .TRUE. the calc. is a path optimizations
lneb =.FALSE., &! if .TRUE. the calc. is NEB dynamics
lsmd =.FALSE., &! if .TRUE. the calc. is string dynamics

View File

@ -96,10 +96,9 @@ MODULE input_parameters
CHARACTER(LEN=80) :: calculation = 'none'
! Specify the type of the simulation
! See below for allowed values
CHARACTER(LEN=80) :: calculation_allowed(15)
CHARACTER(LEN=80) :: calculation_allowed(12)
DATA calculation_allowed / 'scf', 'nscf', 'relax', 'md', 'cp', &
'vc-relax', 'vc-md', 'vc-cp', 'bands', 'neb', 'smd', &
'cp-wf', 'fpmd', 'metadyn', 'fpmd-neb' /
'vc-relax', 'vc-md', 'vc-cp', 'bands', 'neb', 'smd', 'cp-wf'/
CHARACTER(LEN=80) :: verbosity = 'default'
! define the verbosity of the code output

View File

@ -23,185 +23,6 @@ MODULE metadyn_base
IMPLICIT NONE
!
CONTAINS
!
!------------------------------------------------------------------------
SUBROUTINE metadyn_init( progname, tau )
!------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE input_parameters, ONLY : restart_mode
USE constraints_module, ONLY : constr_target
USE control_flags, ONLY : nstep, ndr
USE constants, ONLY : bohr_radius_angs
USE cell_base, ONLY : at, alat
USE metadyn_vars, ONLY : ncolvar, g_amplitude, fe_step, &
max_metadyn_iter, metadyn_fmt, &
gaussian_pos, first_metadyn_iter
USE metadyn_io, ONLY : read_metadyn_restart
USE io_files, ONLY : tmp_dir, prefix, iunaxsf, &
iunmeta, delete_if_present
USE io_global, ONLY : stdout, ionode
USE mp, ONLY : mp_bcast
USE xml_io_base, ONLY : restart_dir
!
IMPLICIT NONE
!
CHARACTER(LEN=*), INTENT(IN) :: progname
REAL(DP), INTENT(INOUT) :: tau(:,:)
!
CHARACTER(LEN=256) :: dirname
CHARACTER(LEN=4) :: c_ncolvar
CHARACTER(LEN=16) :: fe_step_fmt
!
CHARACTER(LEN=6), EXTERNAL :: int_to_char
!
!
IF ( ncolvar < 1 ) &
CALL errore( 'metadyn_init', &
'number of collective variables must be at least 1', 1 )
!
c_ncolvar = int_to_char( ncolvar )
!
metadyn_fmt = '(I5,' // TRIM( c_ncolvar ) // '(2X,F10.5),2X,F14.8,' // &
& TRIM( c_ncolvar ) // '(2X,F10.5),' // &
& TRIM( c_ncolvar ) // '(2X,F10.7))'
!
IF ( nstep < 1 ) CALL errore( 'metadyn_init', 'nstep < 1', 1 )
!
max_metadyn_iter = nstep
!
IF ( restart_mode == 'from_scratch' ) THEN
!
IF ( ionode ) THEN
!
OPEN( UNIT = iunaxsf, &
FILE = TRIM( prefix ) // ".axsf", STATUS = 'UNKNOWN' )
!
WRITE( UNIT = iunaxsf, &
FMT = '(" ANIMSTEPS ",I5)' ) max_metadyn_iter
!
WRITE( UNIT = iunaxsf, FMT = '(" CRYSTAL ")' )
WRITE( UNIT = iunaxsf, FMT = '(" PRIMVEC ")' )
WRITE( UNIT = iunaxsf, FMT = '(3F14.10)' ) &
at(1,1) * alat * bohr_radius_angs, &
at(2,1) * alat * bohr_radius_angs, &
at(3,1) * alat * bohr_radius_angs
WRITE( UNIT = iunaxsf, FMT = '(3F14.10)' ) &
at(1,2) * alat * bohr_radius_angs, &
at(2,2) * alat * bohr_radius_angs, &
at(3,2) * alat * bohr_radius_angs
WRITE( UNIT = iunaxsf, FMT = '(3F14.10)' ) &
at(1,3) * alat * bohr_radius_angs, &
at(2,3) * alat * bohr_radius_angs, &
at(3,3) * alat * bohr_radius_angs
!
END IF
!
CALL delete_if_present( TRIM( prefix ) // '.metadyn' )
!
IF ( ionode ) THEN
!
OPEN( UNIT = iunmeta, &
FILE = TRIM( prefix ) // '.metadyn', STATUS = 'NEW' )
!
WRITE( iunmeta, '(2(2X,I5))' ) ncolvar, max_metadyn_iter
WRITE( iunmeta, '(2(2X,F12.8))' ) g_amplitude
!
fe_step_fmt = '(' // TRIM( c_ncolvar ) // '(2X,F12.8))'
!
WRITE( iunmeta, fe_step_fmt ) fe_step(:)
!
END IF
!
first_metadyn_iter = 0
!
ELSE
!
! ... restarting from file
!
IF ( progname == 'PW' ) THEN
!
dirname = TRIM( tmp_dir ) // TRIM( prefix ) // '.save'
!
ELSE IF ( progname == 'CP' ) THEN
!
dirname = restart_dir( tmp_dir, ndr )
!
ELSE
!
CALL errore( 'metadyn_init', &
'wrong calling program: ' // TRIM( progname ), 1 )
!
END IF
!
CALL read_metadyn_restart( dirname, tau, alat )
!
IF ( ionode ) THEN
!
OPEN( UNIT = iunaxsf, FILE = TRIM( prefix ) // ".axsf", &
STATUS = 'UNKNOWN', ACTION = 'WRITE', POSITION = 'APPEND' )
OPEN( UNIT = iunmeta, FILE = TRIM( prefix ) // '.metadyn', &
STATUS = 'UNKNOWN', ACTION = 'WRITE', POSITION = 'APPEND' )
!
END IF
!
END IF
!
IF ( first_metadyn_iter == max_metadyn_iter ) THEN
!
WRITE( stdout, '(/,5X,"Simulation already completed",/)' )
!
CLOSE( UNIT = iunmeta, STATUS = 'KEEP' )
!
CALL stop_run( .FALSE. )
!
END IF
!
gaussian_pos(:) = constr_target(1:ncolvar)
!
RETURN
!
END SUBROUTINE metadyn_init
!
!------------------------------------------------------------------------
SUBROUTINE add_gaussians( iter )
!------------------------------------------------------------------------
!
USE metadyn_vars, ONLY : ncolvar, metadyn_history, fe_grad, fe_step, &
dfe_acc, g_amplitude
USE basic_algebra_routines
!
IMPLICIT NONE
!
INTEGER, INTENT(IN) :: iter
!
INTEGER :: i
REAL(DP), ALLOCATABLE :: delta(:)
!
! ... history dependent term
!
IF ( iter == 1 ) RETURN
!
ALLOCATE( delta( ncolvar ) )
!
dfe_acc = 0.0_DP
!
DO i = 1, iter - 1
!
delta = metadyn_history(:,iter) - metadyn_history(:,i)
!
dfe_acc(:) = dfe_acc(:) + delta(:) / fe_step(:)**2 * &
EXP( - SUM( delta(:)**2 / ( 2.0_DP*fe_step(:)**2 ) ) )
!
END DO
!
fe_grad(:) = fe_grad(:) - g_amplitude*dfe_acc(:)
!
DEALLOCATE( delta )
!
RETURN
!
END SUBROUTINE add_gaussians
!
!------------------------------------------------------------------------
SUBROUTINE add_domain_potential()
@ -261,52 +82,6 @@ MODULE metadyn_base
END SUBROUTINE add_domain_potential
!
!------------------------------------------------------------------------
SUBROUTINE evolve_collective_vars( norm_fe_grad )
!------------------------------------------------------------------------
!
! ... the collective variables are evolved taking care of the
! ... additional constraints imposed by the domain definition
!
USE constants, ONLY : eps32
USE constraints_module, ONLY : constr_target
USE metadyn_vars, ONLY : ncolvar, fe_grad, fe_step, new_target, &
to_target, sw_nstep, gaussian_pos, &
g_amplitude
USE random_numbers, ONLY : randy
!
IMPLICIT NONE
!
REAL(DP), INTENT(IN) :: norm_fe_grad
!
INTEGER :: i
REAL(DP) :: step
!
!
IF ( norm_fe_grad < eps32 ) &
CALL errore( 'evolve_collective_vars', 'norm( fe_grad ) = 0', 1 )
!
IF ( g_amplitude > 0.0_DP ) fe_grad(:) = fe_grad(:) / norm_fe_grad
!
DO i = 1, ncolvar
!
gaussian_pos(i) = constr_target(i) - fe_step(i)*fe_grad(i)
!
step = ( 1.0_DP + 0.5_DP*randy() )*fe_step(i)
!
new_target(i) = constr_target(i) - step*fe_grad(i)
!
END DO
!
CALL impose_domain_constraints()
!
to_target(:) = ( new_target(:) - &
constr_target(1:ncolvar) ) / DBLE( sw_nstep )
!
RETURN
!
END SUBROUTINE evolve_collective_vars
!
!------------------------------------------------------------------------
SUBROUTINE impose_domain_constraints()
!------------------------------------------------------------------------
!

View File

@ -25,261 +25,9 @@ MODULE metadyn_io
!
PRIVATE
!
PUBLIC :: write_metadyn_restart, &
read_metadyn_restart, &
write_axsf_file
PUBLIC :: write_axsf_file
!
CONTAINS
!
!------------------------------------------------------------------------
SUBROUTINE write_metadyn_restart( dirname, iter, tau, energy, pos_unit )
!------------------------------------------------------------------------
!
USE metadyn_vars, ONLY : ncolvar, max_metadyn_iter, g_amplitude, &
gaussian_pos, fe_grad, fe_step
USE constraints_module, ONLY : constr_target
USE io_global, ONLY : ionode, ionode_id
USE mp, ONLY : mp_bcast
!
IMPLICIT NONE
!
CHARACTER(LEN=*), INTENT(IN) :: dirname
INTEGER, INTENT(IN) :: iter
REAL(DP), INTENT(IN) :: tau(:,:)
REAL(DP), INTENT(IN) :: energy
REAL(DP), INTENT(IN) :: pos_unit
!
INTEGER :: i
CHARACTER(LEN=256) :: filename, metadyn_dir
INTEGER :: iunit, ierr
!
!
IF ( ionode ) THEN
!
! ... look for an empty unit (only ionode needs it)
!
CALL iotk_free_unit( iunit, ierr )
!
END IF
!
CALL mp_bcast( ierr, ionode_id )
!
CALL errore( 'write_metadyn_restart', &
'no free units to write the restart file', ierr )
!
! ... the restart information is written in a sub-directory of
! .. the 'save' directory
!
CALL create_directory( dirname )
!
metadyn_dir = TRIM( dirname ) // '/meta-dynamics'
!
CALL create_directory( metadyn_dir )
!
filename = TRIM( metadyn_dir ) // '/' // "metadyn-descriptor.xml"
!
! ... only ionode writes the file
!
IF ( .NOT. ionode ) RETURN
!
! ... descriptor file
!
CALL iotk_open_write( iunit, FILE = filename, &
ROOT = "METADYNAMICS", BINARY = .FALSE. )
!
CALL iotk_write_dat( iunit, &
"NUM_OF_COLLECTIVE_VARIABLES", ncolvar )
!
CALL iotk_write_dat( iunit, &
"NUM_OF_STEPS", max_metadyn_iter )
!
CALL iotk_write_attr( attr, "UNITS", "Hartree", FIRST = .TRUE. )
CALL iotk_write_dat( iunit, &
"GAUSSIAN_AMPLITUDE", g_amplitude, ATTR = attr )
!
CALL iotk_write_attr( attr, "UNITS", "depend on the" // &
& "type of collective variables", FIRST = .TRUE. )
CALL iotk_write_dat( iunit, "GAUSSIAN_SPREAD", fe_step(:), ATTR = attr )
!
CALL iotk_write_dat( iunit, "STEP", iter )
!
DO i = 1, iter
!
filename = 'iteration' // TRIM( iotk_index( i ) ) // '.xml'
!
CALL iotk_link( iunit, "ITERATION" // TRIM( iotk_index( i ) ), &
filename, CREATE = .FALSE., BINARY = .FALSE. )
!
END DO
!
CALL iotk_close_write( iunit )
!
! ... information about the last step
!
filename = TRIM( metadyn_dir ) // '/' // &
& 'iteration' // TRIM( iotk_index( iter ) ) // '.xml'
!
CALL iotk_open_write( iunit, FILE = filename, ROOT = 'iteration' // &
& TRIM( iotk_index( iter ) ), BINARY = .FALSE. )
!
CALL iotk_write_begin( iunit, "IONS" )
!
CALL iotk_write_attr( attr, "UNITS", "Bohr", FIRST = .TRUE. )
CALL iotk_write_empty( iunit, "UNITS_FOR_IONIC_POS", attr )
!
DO i = 1, SIZE( tau, DIM = 2 )
!
CALL iotk_write_attr( attr, "tau", tau(:,i)*pos_unit, FIRST = .TRUE. )
CALL iotk_write_empty( iunit, &
& "ATOM" // TRIM( iotk_index( i ) ), attr )
!
END DO
!
CALL iotk_write_end( iunit, "IONS" )
!
CALL iotk_write_dat( iunit, &
"COLLECTIVE_VARIABLES", constr_target(1:ncolvar) )
!
CALL iotk_write_dat( iunit, "GAUSSIAN_CENTERS", gaussian_pos(:) )
!
CALL iotk_write_attr( attr, "UNITS", "Hartree", FIRST = .TRUE. )
CALL iotk_write_dat( iunit, "POTENTIAL_ENERGY", energy, ATTR = attr )
!
CALL iotk_write_attr( attr, "UNITS", "Hartree / Bohr", FIRST = .TRUE. )
CALL iotk_write_dat( iunit, &
"POTENTIAL_OF_MEAN_FORCE", fe_grad(:), ATTR = attr )
!
CALL iotk_close_write( iunit )
!
RETURN
!
END SUBROUTINE write_metadyn_restart
!
!------------------------------------------------------------------------
SUBROUTINE read_metadyn_restart( dirname, tau, pos_unit )
!------------------------------------------------------------------------
!
USE metadyn_vars, ONLY : ncolvar, gaussian_pos, fe_grad, &
metadyn_history, first_metadyn_iter
USE constraints_module, ONLY : constr_target
USE io_global, ONLY : ionode, ionode_id
USE mp, ONLY : mp_bcast
!
IMPLICIT NONE
!
CHARACTER(LEN=*), INTENT(IN) :: dirname
REAL(DP), INTENT(OUT) :: tau(:,:)
REAL(DP), INTENT(IN) :: pos_unit
!
INTEGER :: ncolvar_in
INTEGER :: i
CHARACTER(LEN=256) :: filename, tag
INTEGER :: iunit, ierr
!
!
! ... look for an empty unit
!
IF ( ionode ) THEN
!
CALL iotk_free_unit( iunit, ierr )
!
CALL errore( 'read_metadyn_restart', &
'no free units to read the restart file', ierr )
!
filename = TRIM( dirname ) // &
& '/meta-dynamics/' // "metadyn-descriptor.xml"
!
! ... descriptor file
!
CALL iotk_open_read( iunit, FILE = filename, IERR = ierr )
!
END IF
!
CALL mp_bcast( ierr, ionode_id )
!
CALL errore( 'read_metadyn_restart', &
'restart file ' // TRIM( filename ) // ' not found', ierr )
!
IF ( ionode ) THEN
!
CALL iotk_scan_dat( iunit, &
"NUM_OF_COLLECTIVE_VARIABLES", ncolvar_in )
!
IF ( ncolvar_in == ncolvar ) THEN
!
ncolvar = ncolvar_in
!
ELSE
!
CALL errore( 'read_metadyn_restart', &
'wrong number of collective variables', 1 )
!
END IF
!
CALL iotk_scan_dat( iunit, "STEP", first_metadyn_iter )
!
DO i = 1, first_metadyn_iter
!
tag = "ITERATION" // TRIM( iotk_index( i ) )
!
CALL iotk_scan_begin( iunit, TRIM( tag ) )
!
CALL iotk_scan_dat( iunit, &
"GAUSSIAN_CENTERS", metadyn_history(:,i) )
!
CALL iotk_scan_end( iunit, TRIM( tag ) )
!
END DO
!
CALL iotk_close_read( iunit )
!
! ... information about the last step
!
CALL iotk_open_read( iunit, FILE = filename )
!
tag = "ITERATION" // TRIM( iotk_index( first_metadyn_iter ) )
!
CALL iotk_scan_begin( iunit, TRIM( tag ) )
!
CALL iotk_scan_begin( iunit, "IONS" )
!
DO i = 1, SIZE( tau, DIM = 2 )
!
CALL iotk_scan_empty( iunit, &
"ATOM" // TRIM( iotk_index( i ) ), attr )
CALL iotk_scan_attr( attr, "tau", tau(:,i) )
!
END DO
!
CALL iotk_scan_end( iunit, "IONS" )
!
CALL iotk_scan_dat( iunit, &
"COLLECTIVE_VARIABLES", constr_target(1:ncolvar) )
!
CALL iotk_scan_dat( iunit, "GAUSSIAN_CENTERS", gaussian_pos(:) )
CALL iotk_scan_dat( iunit, "POTENTIAL_OF_MEAN_FORCE", fe_grad(:) )
!
CALL iotk_scan_end( iunit, TRIM( tag ) )
!
CALL iotk_close_read( iunit )
!
! ... positions are converted to internal units
!
tau(:,:) = tau(:,:) / pos_unit
!
END IF
!
CALL mp_bcast( ncolvar, ionode_id )
CALL mp_bcast( first_metadyn_iter, ionode_id )
CALL mp_bcast( metadyn_history, ionode_id )
CALL mp_bcast( tau, ionode_id )
CALL mp_bcast( constr_target, ionode_id )
CALL mp_bcast( gaussian_pos, ionode_id )
CALL mp_bcast( fe_grad, ionode_id )
!
RETURN
!
END SUBROUTINE read_metadyn_restart
!
!------------------------------------------------------------------------
SUBROUTINE write_axsf_file( image, tau, tau_units )

View File

@ -9,9 +9,8 @@
MODULE metadyn_vars
!----------------------------------------------------------------------------
!
! ... this module contains the variables necessary for the implementation of
! ... meta-dynamics and for the calculation of free-energy barriers by means
! ... of the fourier string method
! ... this module contains the variables necessary for the calculation of
! ... free-energy barriers by means of the fourier string method
!
! ... code written by Carlo Sbraccia (2005)
!
@ -59,7 +58,7 @@ MODULE metadyn_vars
fe_nstep_ => fe_nstep, &
sw_nstep_ => sw_nstep, &
eq_nstep_ => eq_nstep
USE control_flags, ONLY : lmetadyn, nstep
USE control_flags, ONLY : nstep
!
IMPLICIT NONE
!
@ -72,13 +71,6 @@ MODULE metadyn_vars
ALLOCATE( new_target( ncolvar ) )
ALLOCATE( to_target( ncolvar ) )
!
IF ( lmetadyn ) THEN
!
ALLOCATE( gaussian_pos( ncolvar ) )
ALLOCATE( metadyn_history( ncolvar, nstep ) )
!
END IF
!
fe_nstep = fe_nstep_
sw_nstep = sw_nstep_
eq_nstep = eq_nstep_

View File

@ -1487,8 +1487,7 @@ MODULE read_namelists_module
CALL errore( sub_name, ' opt_scheme '''// &
& TRIM( opt_scheme )//''' not allowed ', 1 )
!
IF ( calculation == 'neb' .OR. &
calculation == 'smd' .OR. calculation == 'fpmd-neb' ) THEN
IF ( calculation == 'neb' .OR. calculation == 'smd' ) THEN
!
IF ( phase_space == 'coarse-grained' ) THEN
!
@ -1702,14 +1701,6 @@ MODULE read_namelists_module
!
END IF
!
CASE ( 'fpmd-neb' )
!
! ... "path" optimizations using fpmd as scf engine
!
electron_dynamics = 'damp'
ion_dynamics = 'none'
cell_dynamics = 'none'
!
CASE ( 'smd' )
!
IF( prog == 'CP' ) THEN
@ -1719,20 +1710,6 @@ MODULE read_namelists_module
!
END IF
!
CASE ( 'fpmd' )
!
! Compatibility with old FPMD
!
IF ( prog == 'PW' ) &
CALL errore( sub_name, ' calculation ' // &
& TRIM( calculation ) // ' not implemented ', 1 )
!
electron_dynamics = 'sd'
ion_dynamics = 'none'
cell_dynamics = 'none'
!
CASE( 'metadyn' )
!
CASE DEFAULT
!
CALL errore( sub_name,' calculation '// &
@ -1766,9 +1743,6 @@ MODULE read_namelists_module
tot_magnetization==1._dp ) )
END IF
!
IF ( calculation == 'metadyn' .AND. &
prog == 'CP' ) g_amplitude = g_amplitude / e2
!
RETURN
!
END SUBROUTINE
@ -1839,11 +1813,6 @@ MODULE read_namelists_module
CALL control_bcast( )
CALL control_checkin( prog )
!
IF( TRIM( calculation ) == 'fpmd' .OR. TRIM( calculation ) == 'fpmd-neb' ) THEN
CALL errore( ' read_namelists ', &
& ' fpmd calculation no more supported, use cp instead ', 1 )
END IF
!
! ... fixval changes some default values according to the value
! ... of "calculation" read in CONTROL namelist
!
@ -1895,10 +1864,7 @@ MODULE read_namelists_module
TRIM( calculation ) == 'vc-cp' .OR. &
TRIM( calculation ) == 'smd' .OR. &
TRIM( calculation ) == 'cp-wf' .OR. &
TRIM( calculation ) == 'neb' .OR. &
TRIM( calculation ) == 'fpmd' .OR. &
TRIM( calculation ) == 'fpmd-neb' .OR. &
TRIM( calculation ) == 'metadyn' ) READ( 5, ions, iostat = ios )
TRIM( calculation ) == 'neb' ) READ( 5, ions, iostat = ios )
!
END IF
CALL mp_bcast( ios, ionode_id )
@ -1917,8 +1883,6 @@ MODULE read_namelists_module
IF( TRIM( calculation ) == 'vc-relax' .OR. &
TRIM( calculation ) == 'vc-cp' .OR. &
TRIM( calculation ) == 'vc-md' .OR. &
TRIM( calculation ) == 'fpmd' .OR. &
TRIM( calculation ) == 'fpmd-neb' .OR. &
TRIM( calculation ) == 'vc-md' ) THEN
READ( 5, cell, iostat = ios )
END IF

View File

@ -358,7 +358,7 @@ SUBROUTINE compute_fes_grads( fii, lii, stat )
END DO
!
! ... here the meta_ionode writes the axsf file for this iteration
! ... by reading the postions from the restart-file
! ... by reading the positions from the restart-file
!
filename = TRIM( prefix ) // "_" // &
& TRIM( int_to_char( istep_path + 1 ) ) // ".axsf"
@ -477,224 +477,6 @@ SUBROUTINE compute_fes_grads( fii, lii, stat )
END SUBROUTINE compute_fes_grads
!
!----------------------------------------------------------------------------
SUBROUTINE metadyn()
!----------------------------------------------------------------------------
!
USE kinds, ONLY : DP
USE constants, ONLY : eps8
USE constraints_module, ONLY : constr_target
USE ions_base, ONLY : tau
USE cell_base, ONLY : alat
USE io_files, ONLY : iunaxsf, iunmeta, prefix, tmp_dir
USE metadyn_vars, ONLY : ncolvar, etot_av, fe_grad, metadyn_fmt, &
to_new_target, metadyn_history, &
max_metadyn_iter, first_metadyn_iter, &
gaussian_pos
USE metadyn_base, ONLY : add_gaussians, add_domain_potential, &
evolve_collective_vars
USE metadyn_io, ONLY : write_axsf_file, write_metadyn_restart
USE io_global, ONLY : ionode, stdout
USE basic_algebra_routines
!
IMPLICIT NONE
!
CHARACTER(LEN=256) :: dirname
INTEGER :: iter
REAL(DP) :: norm_fe_grad
LOGICAL :: lfirst_scf = .TRUE.
!
!
dirname = TRIM( tmp_dir ) // TRIM( prefix ) // '.save'
!
iter = first_metadyn_iter
!
metadyn_loop: DO
!
IF ( iter > 0 ) THEN
!
CALL add_gaussians( iter )
!
CALL add_domain_potential()
!
norm_fe_grad = norm( fe_grad )
!
CALL evolve_collective_vars( norm_fe_grad )
!
WRITE( stdout, '(/,5X,"adiabatic switch of the system ", &
& "to the new coarse-grained positions",/)' )
!
! ... the system is "adiabatically" moved to the new constr_target
!
CALL move_to_target( lfirst_scf )
!
END IF
!
iter = iter + 1
!
metadyn_history(:,iter) = gaussian_pos(:)
!
IF ( ionode ) CALL write_axsf_file( iter, tau, alat )
!
WRITE( stdout, '(/,5X,"calculation of the mean force",/)' )
!
CALL free_energy_grad( lfirst_scf )
!
IF ( ionode ) THEN
!
WRITE( UNIT = iunmeta, FMT = metadyn_fmt ) &
iter, constr_target(1:ncolvar), etot_av, gaussian_pos(:), fe_grad(:)
!
CALL flush_unit( iunmeta )
CALL flush_unit( iunaxsf )
!
END IF
!
CALL write_metadyn_restart( dirname, iter, tau, etot_av, alat )
!
IF ( iter >= max_metadyn_iter ) EXIT metadyn_loop
!
END DO metadyn_loop
!
IF ( ionode ) THEN
!
CLOSE( UNIT = iunaxsf )
CLOSE( UNIT = iunmeta )
!
END IF
!
RETURN
!
CONTAINS
!
!------------------------------------------------------------------------
SUBROUTINE free_energy_grad( lfirst_scf )
!------------------------------------------------------------------------
!
USE constants, ONLY : e2
USE ener, ONLY : etot
USE lsda_mod, ONLY : lsda
USE control_flags, ONLY : ldamped, conv_ions, nstep
USE metadyn_vars, ONLY : fe_nstep, eq_nstep, dfe_acc, etot_av
USE constraints_module, ONLY : lagrange
USE io_files, ONLY : tmp_dir, prefix, delete_if_present
USE io_global, ONLY : ionode_id
USE mp_global, ONLY : intra_image_comm
USE mp, ONLY : mp_bcast
!
IMPLICIT NONE
!
LOGICAL, INTENT(INOUT) :: lfirst_scf
!
INTEGER :: i
LOGICAL :: stat
!
!
etot_av = 0.D0
dfe_acc = 0.D0
!
IF ( lsda ) CALL reset_init_mag()
!
CALL delete_if_present( TRIM( tmp_dir ) // TRIM( prefix ) // '.md' )
CALL delete_if_present( TRIM( tmp_dir ) // TRIM( prefix ) // '.bfgs' )
CALL delete_if_present( TRIM( tmp_dir ) // TRIM( prefix ) // '.update' )
!
to_new_target = .FALSE.
!
nstep = fe_nstep
!
DO i = 1, fe_nstep
!
CALL electronic_scf( lfirst_scf, stat )
!
lfirst_scf = .FALSE.
!
IF ( .NOT. stat ) CALL stop_run( stat )
!
CALL move_ions()
!
IF ( ldamped .AND. conv_ions ) EXIT
!
END DO
!
! ... the averages are computed here and converted to Hartree
!
IF ( ldamped ) THEN
!
! ... zero temperature
!
etot_av = etot / e2
!
fe_grad(:) = - lagrange(1:ncolvar) / e2
!
ELSE
!
! ... finite temperature
!
etot_av = etot_av / DBLE( fe_nstep ) / e2
!
fe_grad(:) = dfe_acc(:) / DBLE( fe_nstep - eq_nstep ) / e2
!
END IF
!
! ... notice that etot_av and fe_grad have been computed, so far, by
! ... ionode only: here we broadcast to all the other cpus
!
CALL mp_bcast( etot_av, ionode_id, intra_image_comm )
CALL mp_bcast( fe_grad, ionode_id, intra_image_comm )
!
RETURN
!
END SUBROUTINE free_energy_grad
!
!------------------------------------------------------------------------
SUBROUTINE move_to_target( lfirst_scf )
!------------------------------------------------------------------------
!
USE metadyn_vars, ONLY : sw_nstep
USE lsda_mod, ONLY : lsda
USE control_flags, ONLY : ldamped, nstep
USE io_files, ONLY : tmp_dir, prefix, delete_if_present
!
LOGICAL, INTENT(INOUT) :: lfirst_scf
!
INTEGER :: i
LOGICAL :: stat, ldamped_saved
!
!
ldamped_saved = ldamped
!
IF ( lsda ) CALL reset_init_mag()
!
CALL delete_if_present( TRIM( tmp_dir ) // TRIM( prefix ) // '.md' )
CALL delete_if_present( TRIM( tmp_dir ) // TRIM( prefix ) // '.update' )
!
ldamped = .FALSE.
!
to_new_target = .TRUE.
!
nstep = sw_nstep
!
DO i = 1, sw_nstep
!
CALL electronic_scf( lfirst_scf, stat )
!
lfirst_scf = .FALSE.
!
IF ( .NOT. stat ) CALL stop_run( stat )
!
CALL move_ions()
!
END DO
!
ldamped = ldamped_saved
!
RETURN
!
END SUBROUTINE move_to_target
!
END SUBROUTINE metadyn
!
!----------------------------------------------------------------------------
SUBROUTINE reset_init_mag()
!----------------------------------------------------------------------------
!

View File

@ -503,7 +503,7 @@ SUBROUTINE electrons()
conv_elec = .false.
iter = 0
CALL save_in_electrons( iter, dr2 )
WRITE( stdout, * ) " NOW GO BACK TO REFINE HYBRID CALCULATION"
WRITE( stdout,'(5x,"EXX: now go back to refine exchange calculation"
WRITE( stdout, * ) fock0
!
GO TO 10
@ -710,7 +710,7 @@ SUBROUTINE electrons()
9062 FORMAT( ' - averaged Fock potential =',F17.8,' Ry' )
9064 FORMAT( ' + Fock energy =',F17.8,' Ry' )
9065 FORMAT( ' Hubbard energy =',F17.8,' Ry' )
9066 FORMAT( ' dexx =',F17.8,' Ry' )
9066 FORMAT( ' est. exchange err (dexx) =',F17.8,' Ry' )
9067 FORMAT( ' one-center paw contrib. =',F17.8,' Ry' )
9069 FORMAT( ' scf correction =',F17.8,' Ry' )
9070 FORMAT( ' smearing contrib. (-TS) =',F17.8,' Ry' )

View File

@ -1276,8 +1276,6 @@ CONTAINS
call stop_clock ('exx_div')
call print_clock ('exx_div')
return
end function exx_divergence

View File

@ -166,7 +166,7 @@ SUBROUTINE iosys()
lkpoint_dir_ => lkpoint_dir, &
tqr_ => tqr, &
io_level, ethr, lscf, lbfgs, lmd, lpath, lneb, &
lsmd, ldamped, lbands, lmetadyn, llang, &
lsmd, ldamped, lbands, llang, &
lconstrain, lcoarsegrained, restart, twfcollect, &
use_para_diag, llondon, nofrac, do_makov_payne
!
@ -318,7 +318,6 @@ SUBROUTINE iosys()
!
lscf = .FALSE.
lmd = .FALSE.
lmetadyn = .FALSE.
lpath = .FALSE.
lneb = .FALSE.
lsmd = .FALSE.
@ -495,11 +494,6 @@ SUBROUTINE iosys()
lpath = .TRUE.
lsmd = .TRUE.
!
CASE( 'metadyn' )
!
lscf = .TRUE.
lmetadyn= .TRUE.
!
CASE DEFAULT
!
CALL errore( 'iosys', 'calculation ' // &
@ -989,7 +983,7 @@ SUBROUTINE iosys()
!
END SELECT
!
lcoarsegrained = lmetadyn .OR. ( TRIM( phase_space ) == 'coarse-grained' )
lcoarsegrained = ( TRIM( phase_space ) == 'coarse-grained' )
!
IF ( lcoarsegrained ) THEN
!

View File

@ -14,14 +14,12 @@ PROGRAM pwscf
USE io_global, ONLY : stdout, ionode
USE parameters, ONLY : ntypx, npk, lmaxx
USE noncollin_module, ONLY : noncolin
USE control_flags, ONLY : conv_elec, conv_ions, lpath, lmetadyn, &
gamma_only
USE control_flags, ONLY : conv_elec, conv_ions, lpath, gamma_only
USE environment, ONLY : environment_start
USE ions_base, ONLY : tau
USE path_variables, ONLY : conv_path
USE check_stop, ONLY : check_stop_init
USE path_base, ONLY : initialize_path, search_mep
USE metadyn_base, ONLY : metadyn_init
USE path_io_routines, ONLY : io_path_start, path_summary
USE mp_global, ONLY : nimage, mp_startup
!
@ -65,19 +63,6 @@ PROGRAM pwscf
!
ELSE
!
IF ( lmetadyn ) THEN
!
! ... meta-dynamics
!
CALL metadyn_init( 'PW', tau )
!
CALL setup ()
CALL init_run()
!
CALL metadyn()
!
ELSE
!
#if defined (EXX)
if(nimage>1) CALL io_path_start()
CALL exx_loop()
@ -107,11 +92,8 @@ PROGRAM pwscf
CALL hinit1()
!
END DO main_loop
!
#endif
!
END IF
!
CALL stop_run( conv_ions )
!
END IF